1
- {-# LANGUAGE FlexibleInstances #-}
2
- {-# LANGUAGE MultiParamTypeClasses #-}
3
- {-# LANGUAGE DeriveAnyClass #-}
4
- {-# LANGUAGE GADTs #-}
5
- {-# LANGUAGE DeriveGeneric #-}
6
- {-# LANGUAGE OverloadedStrings #-}
7
- {-# LANGUAGE RecordWildCards #-}
8
- {-# LANGUAGE ScopedTypeVariables #-}
1
+ {-# LANGUAGE DeriveAnyClass #-}
9
2
10
3
module Development.IDE.Plugin.HLS
11
4
(
@@ -77,7 +70,7 @@ asGhcIdePlugin mp =
77
70
rulesPlugins :: [(PluginId , Rules () )] -> Plugin Config
78
71
rulesPlugins rs = Plugin rules mempty
79
72
where
80
- rules = mconcat $ map snd rs
73
+ rules = foldMap snd rs
81
74
82
75
codeActionPlugins :: [(PluginId , CodeActionProvider IdeState )] -> Plugin Config
83
76
codeActionPlugins cas = Plugin codeActionRules (codeActionHandlers cas)
@@ -104,7 +97,7 @@ makeCodeAction cas lf ideState (CodeActionParams docId range context _) = do
104
97
then provider lf ideState pid docId range context
105
98
else return $ Right (List [] )
106
99
r <- mapM makeAction cas
107
- let actions = filter wasRequested . concat $ map unL $ rights r
100
+ let actions = filter wasRequested . foldMap unL $ rights r
108
101
res <- send caps actions
109
102
return $ Right res
110
103
where
@@ -320,7 +313,7 @@ makeHover hps lf ideState params
320
313
-- work out range here?
321
314
let hs = catMaybes (rights mhs)
322
315
r = listToMaybe $ mapMaybe (^. range) hs
323
- h = case mconcat (( map ( ^. contents) hs) :: [ HoverContents ]) of
316
+ h = case foldMap ( ^. contents) hs of
324
317
HoverContentsMS (List [] ) -> Nothing
325
318
hh -> Just $ Hover hh r
326
319
return $ Right h
@@ -347,8 +340,7 @@ makeSymbols sps lf ideState params
347
340
= do
348
341
let uri' = params ^. textDocument . uri
349
342
(C. ClientCapabilities _ tdc _ _) = LSP. clientCapabilities lf
350
- supportsHierarchy = fromMaybe False $ tdc >>= C. _documentSymbol
351
- >>= C. _hierarchicalDocumentSymbolSupport
343
+ supportsHierarchy = Just True == (tdc >>= C. _documentSymbol >>= C. _hierarchicalDocumentSymbolSupport)
352
344
convertSymbols :: [DocumentSymbol ] -> DSResult
353
345
convertSymbols symbs
354
346
| supportsHierarchy = DSDocumentSymbols $ List symbs
@@ -400,7 +392,7 @@ renameWith providers lspFuncs state params = do
400
392
-- TODO:AZ: we need to consider the right way to combine possible renamers
401
393
results <- mapM makeAction providers
402
394
case partitionEithers results of
403
- (errors, [] ) -> return $ Left $ responseError $ T. pack $ show $ errors
395
+ (errors, [] ) -> return $ Left $ responseError $ T. pack $ show errors
404
396
(_, edits) -> return $ Right $ mconcat edits
405
397
406
398
-- ---------------------------------------------------------------------
@@ -443,7 +435,7 @@ makeCompletions :: [(PluginId, CompletionProvider IdeState)]
443
435
makeCompletions sps lf ideState params@ (CompletionParams (TextDocumentIdentifier doc) pos _context _mt)
444
436
= do
445
437
mprefix <- getPrefixAtPos lf doc pos
446
- _snippets <- WithSnippets <$> completionSnippetsOn <$> getClientConfig lf
438
+ _snippets <- WithSnippets . completionSnippetsOn <$> getClientConfig lf
447
439
448
440
let
449
441
combine :: [CompletionResponseResult ] -> CompletionResponseResult
@@ -474,7 +466,7 @@ makeCompletions sps lf ideState params@(CompletionParams (TextDocumentIdentifier
474
466
475
467
getPrefixAtPos :: LSP. LspFuncs Config -> Uri -> Position -> IO (Maybe VFS. PosPrefixInfo )
476
468
getPrefixAtPos lf uri pos = do
477
- mvf <- ( LSP. getVirtualFileFunc lf) (J. toNormalizedUri uri)
469
+ mvf <- LSP. getVirtualFileFunc lf (J. toNormalizedUri uri)
478
470
case mvf of
479
471
Just vf -> VFS. getCompletionPrefix pos vf
480
472
Nothing -> return Nothing
0 commit comments