Skip to content

Commit 4c8a255

Browse files
committed
Fix hlints
1 parent 6d73cf6 commit 4c8a255

File tree

3 files changed

+8
-28
lines changed

3 files changed

+8
-28
lines changed

ghcide/src/Development/IDE/Plugin/HLS.hs

Lines changed: 8 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -1,11 +1,4 @@
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 #-}
92

103
module Development.IDE.Plugin.HLS
114
(
@@ -77,7 +70,7 @@ asGhcIdePlugin mp =
7770
rulesPlugins :: [(PluginId, Rules ())] -> Plugin Config
7871
rulesPlugins rs = Plugin rules mempty
7972
where
80-
rules = mconcat $ map snd rs
73+
rules = foldMap snd rs
8174

8275
codeActionPlugins :: [(PluginId, CodeActionProvider IdeState)] -> Plugin Config
8376
codeActionPlugins cas = Plugin codeActionRules (codeActionHandlers cas)
@@ -104,7 +97,7 @@ makeCodeAction cas lf ideState (CodeActionParams docId range context _) = do
10497
then provider lf ideState pid docId range context
10598
else return $ Right (List [])
10699
r <- mapM makeAction cas
107-
let actions = filter wasRequested . concat $ map unL $ rights r
100+
let actions = filter wasRequested . foldMap unL $ rights r
108101
res <- send caps actions
109102
return $ Right res
110103
where
@@ -320,7 +313,7 @@ makeHover hps lf ideState params
320313
-- work out range here?
321314
let hs = catMaybes (rights mhs)
322315
r = listToMaybe $ mapMaybe (^. range) hs
323-
h = case mconcat ((map (^. contents) hs) :: [HoverContents]) of
316+
h = case foldMap (^. contents) hs of
324317
HoverContentsMS (List []) -> Nothing
325318
hh -> Just $ Hover hh r
326319
return $ Right h
@@ -347,8 +340,7 @@ makeSymbols sps lf ideState params
347340
= do
348341
let uri' = params ^. textDocument . uri
349342
(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)
352344
convertSymbols :: [DocumentSymbol] -> DSResult
353345
convertSymbols symbs
354346
| supportsHierarchy = DSDocumentSymbols $ List symbs
@@ -400,7 +392,7 @@ renameWith providers lspFuncs state params = do
400392
-- TODO:AZ: we need to consider the right way to combine possible renamers
401393
results <- mapM makeAction providers
402394
case partitionEithers results of
403-
(errors, []) -> return $ Left $ responseError $ T.pack $ show $ errors
395+
(errors, []) -> return $ Left $ responseError $ T.pack $ show errors
404396
(_, edits) -> return $ Right $ mconcat edits
405397

406398
-- ---------------------------------------------------------------------
@@ -443,7 +435,7 @@ makeCompletions :: [(PluginId, CompletionProvider IdeState)]
443435
makeCompletions sps lf ideState params@(CompletionParams (TextDocumentIdentifier doc) pos _context _mt)
444436
= do
445437
mprefix <- getPrefixAtPos lf doc pos
446-
_snippets <- WithSnippets <$> completionSnippetsOn <$> getClientConfig lf
438+
_snippets <- WithSnippets . completionSnippetsOn <$> getClientConfig lf
447439

448440
let
449441
combine :: [CompletionResponseResult] -> CompletionResponseResult
@@ -474,7 +466,7 @@ makeCompletions sps lf ideState params@(CompletionParams (TextDocumentIdentifier
474466

475467
getPrefixAtPos :: LSP.LspFuncs Config -> Uri -> Position -> IO (Maybe VFS.PosPrefixInfo)
476468
getPrefixAtPos lf uri pos = do
477-
mvf <- (LSP.getVirtualFileFunc lf) (J.toNormalizedUri uri)
469+
mvf <- LSP.getVirtualFileFunc lf (J.toNormalizedUri uri)
478470
case mvf of
479471
Just vf -> VFS.getCompletionPrefix pos vf
480472
Nothing -> return Nothing

ghcide/src/Development/IDE/Plugin/HLS/Formatter.hs

Lines changed: 0 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,3 @@
1-
{-# LANGUAGE RecordWildCards #-}
2-
{-# LANGUAGE OverloadedStrings #-}
3-
{-# LANGUAGE ScopedTypeVariables #-}
4-
{-# LANGUAGE TypeApplications #-}
5-
{-# LANGUAGE ViewPatterns #-}
61

72
module Development.IDE.Plugin.HLS.Formatter
83
(

ghcide/src/Development/IDE/Types/Options.hs

Lines changed: 0 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1,13 +1,6 @@
11
-- Copyright (c) 2019 The DAML Authors. All rights reserved.
22
-- SPDX-License-Identifier: Apache-2.0
33

4-
{-# LANGUAGE RankNTypes #-}
5-
{-# LANGUAGE DeriveGeneric #-}
6-
{-# LANGUAGE DeriveAnyClass #-}
7-
{-# LANGUAGE DerivingStrategies #-}
8-
9-
{- HLINT ignore "Avoid restricted extensions" -}
10-
114
-- | Options
125
module Development.IDE.Types.Options
136
( IdeOptions(..)

0 commit comments

Comments
 (0)