Skip to content

Commit 1872dc4

Browse files
Fix a few more hints and some mistakes made during merge.
1 parent 41b8bf9 commit 1872dc4

File tree

17 files changed

+30
-91
lines changed

17 files changed

+30
-91
lines changed

ghcide/session-loader/Development/IDE/Session.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -120,7 +120,7 @@ setInitialDynFlags = do
120120
hPutStrLn stderr $ "Couldn't load cradle for libdir: " ++ show (err,dir,hieYaml,cradle)
121121
pure Nothing
122122
CradleNone -> do
123-
hPutStrLn stderr $ "Couldn't load cradle (CradleNone)"
123+
hPutStrLn stderr "Couldn't load cradle (CradleNone)"
124124
pure Nothing
125125
dynFlags <- mapM dynFlagsForPrinting libdir
126126
mapM_ setUnsafeGlobalDynFlags dynFlags

ghcide/src/Development/IDE/Spans/AtPoint.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -266,12 +266,12 @@ typeLocationsAtPoint hiedb lookupModule _ideOptions pos (HAR _ ast _ _ hieKind)
266266
HQualTy a b -> getTypes [a,b]
267267
HCastTy a -> getTypes [a]
268268
_ -> []
269-
in fmap nubOrd $ concatMapM (fmap (maybe [] id) . nameToLocation hiedb lookupModule) (getTypes ts)
269+
in fmap nubOrd $ concatMapM (fmap (fromMaybe []) . nameToLocation hiedb lookupModule) (getTypes ts)
270270
HieFresh ->
271271
let ts = concat $ pointCommand ast pos getts
272272
getts x = nodeType ni ++ (mapMaybe identType $ M.elems $ nodeIdentifiers ni)
273273
where ni = nodeInfo x
274-
in fmap nubOrd $ concatMapM (fmap (maybe [] id) . nameToLocation hiedb lookupModule) (getTypes ts)
274+
in fmap nubOrd $ concatMapM (fmap (fromMaybe []) . nameToLocation hiedb lookupModule) (getTypes ts)
275275

276276
namesInType :: Type -> [Name]
277277
namesInType (TyVarTy n) = [Var.varName n]

hls-plugin-api/src/Ide/Types.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,6 @@
11
{-# LANGUAGE GADTs #-}
22
{-# LANGUAGE OverloadedStrings #-}
33
{-# LANGUAGE ScopedTypeVariables #-}
4-
{-# LANGUAGE TupleSections #-}
54
{-# LANGUAGE FlexibleContexts #-}
65
{-# LANGUAGE PolyKinds #-}
76
{-# LANGUAGE ViewPatterns #-}

plugins/default/src/Ide/Plugin/Pragmas.hs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,3 @@
1-
{-# LANGUAGE DeriveAnyClass #-}
2-
{-# LANGUAGE DeriveGeneric #-}
31
{-# LANGUAGE DuplicateRecordFields #-}
42
{-# LANGUAGE OverloadedStrings #-}
53
{-# LANGUAGE ViewPatterns #-}

plugins/hls-eval-plugin/src/Ide/Plugin/Eval/CodeLens.hs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,6 @@
11
{-# LANGUAGE TypeApplications #-}
22
{-# LANGUAGE ViewPatterns #-}
33
{-# LANGUAGE LambdaCase #-}
4-
{-# LANGUAGE DeriveAnyClass #-}
5-
{-# LANGUAGE DeriveGeneric #-}
64
{-# LANGUAGE DuplicateRecordFields #-}
75
{-# LANGUAGE ExtendedDefaultRules #-}
86
{-# LANGUAGE FlexibleContexts #-}

plugins/hls-hlint-plugin/src/Ide/Plugin/Hlint.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -278,7 +278,7 @@ codeActionProvider ideState plId (CodeActionParams _ _ docId _ context) = Right
278278
in LSP.CodeAction "Apply all hints" (Just LSP.CodeActionQuickFix) Nothing Nothing Nothing Nothing (Just cmd)
279279

280280
applyOneActions :: [LSP.CodeAction]
281-
applyOneActions = catMaybes $ map mkHlintAction (filter validCommand diags)
281+
applyOneActions = mapMaybe mkHlintAction (filter validCommand diags)
282282

283283
-- |Some hints do not have an associated refactoring
284284
validCommand (LSP.Diagnostic _ _ (Just (InR code)) (Just "hlint") _ _ _) =

plugins/hls-retrie-plugin/src/Ide/Plugin/Retrie.hs

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -147,14 +147,14 @@ extractImports ModSummary{ms_mod} topLevelBinds (Unfold thing)
147147
, names <- listify p fun_matches
148148
=
149149
[ AddImport {..}
150-
| name <- names,
151-
Just ideclNameString <-
152-
[moduleNameString . GHC.moduleName <$> nameModule_maybe name],
153-
let ideclSource = False,
150+
| let ideclSource = False,
151+
name <- names,
154152
let r = nameRdrName name,
155153
let ideclQualifiedBool = isQual r,
156154
let ideclAsString = moduleNameString . fst <$> isQual_maybe r,
157-
let ideclThing = Just (IEVar $ occNameString $ rdrNameOcc r)
155+
let ideclThing = Just (IEVar $ occNameString $ rdrNameOcc r),
156+
Just ideclNameString <-
157+
[moduleNameString . GHC.moduleName <$> nameModule_maybe name]
158158
]
159159
where
160160
p name = nameModule_maybe name /= Just ms_mod
@@ -179,8 +179,8 @@ provider state plId (CodeActionParams _ _ (TextDocumentIdentifier uri) range ca)
179179
++ [ r
180180
| TyClGroup {group_tyclds} <- hs_tyclds,
181181
L l g <- group_tyclds,
182-
r <- suggestTypeRewrites uri ms_mod g,
183-
pos `isInsideSrcSpan` l
182+
pos `isInsideSrcSpan` l,
183+
r <- suggestTypeRewrites uri ms_mod g
184184

185185
]
186186

plugins/hls-tactics-plugin/src/Ide/Plugin/Tactic.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -235,7 +235,7 @@ filterBindingType p tp dflags plId uri range jdg =
235235
g = jGoal jdg
236236
in fmap join $ for (unHypothesis hy) $ \hi ->
237237
let ty = unCType $ hi_type hi
238-
in if $ p (unCType g) ty
238+
in if p (unCType g) ty
239239
then tp (hi_name hi) ty dflags plId uri range jdg
240240
else pure []
241241

plugins/hls-tactics-plugin/src/Ide/Plugin/Tactic/CodeGen.hs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,6 @@
11
{-# LANGUAGE FlexibleContexts #-}
22
{-# LANGUAGE TupleSections #-}
33
{-# LANGUAGE TypeApplications #-}
4-
{-# LANGUAGE ViewPatterns #-}
54

65
module Ide.Plugin.Tactic.CodeGen
76
( module Ide.Plugin.Tactic.CodeGen
@@ -202,4 +201,3 @@ buildDataCon jdg dc tyapps = do
202201
pure
203202
. (rose (show dc) $ pure tr,)
204203
$ mkCon dc sgs
205-

plugins/hls-tactics-plugin/src/Ide/Plugin/Tactic/Judgements.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -273,7 +273,7 @@ introducingPat scrutinee dc ns jdg
273273
disallowing :: DisallowReason -> [OccName] -> Judgement' a -> Judgement' a
274274
disallowing reason (S.fromList -> ns) =
275275
field @"_jHypothesis" %~ (\z -> Hypothesis . flip fmap (unHypothesis z) $ \hi ->
276-
if $ hi_name hi `S.member` ns
276+
if hi_name hi `S.member` ns
277277
then overProvenance (DisallowedPrv reason) hi
278278
else hi
279279
)

0 commit comments

Comments
 (0)