Skip to content

Commit fa4474a

Browse files
committed
Fix hlint warnings
1 parent aedf448 commit fa4474a

File tree

6 files changed

+21
-23
lines changed

6 files changed

+21
-23
lines changed

ghcide/test/exe/InitializeResponseTests.hs

Lines changed: 3 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -79,19 +79,16 @@ tests = withResource acquire release tests where
7979
che :: TestName -> (ServerCapabilities -> Maybe ExecuteCommandOptions) -> [T.Text] -> TestTree
8080
che title getActual expected = testCase title $ do
8181
ir <- getInitializeResponse
82-
ExecuteCommandOptions {_commands = commands} <- assertJust "ExecuteCommandOptions" $ getActual $ innerCaps ir
82+
ExecuteCommandOptions {_commands = commands} <- case getActual $ innerCaps ir of
83+
Just eco -> pure eco
84+
Nothing -> assertFailure "Was expecting Just ExecuteCommandOptions, got Nothing"
8385
let commandNames = (!! 2) . T.splitOn ":" <$> commands
8486
zipWithM_ (\e o -> T.isSuffixOf e o @? show (e,o)) (sort expected) (sort commandNames)
8587

8688
innerCaps :: TResponseMessage Method_Initialize -> ServerCapabilities
8789
innerCaps (TResponseMessage _ _ (Right (InitializeResult c _))) = c
8890
innerCaps (TResponseMessage _ _ (Left _)) = error "Initialization error"
8991

90-
assertJust :: String -> Maybe a -> IO a
91-
assertJust s = \case
92-
Nothing -> assertFailure $ "Expecting Just " <> s <> ", got Nothing"
93-
Just x -> pure x
94-
9592
acquire :: IO (TResponseMessage Method_Initialize)
9693
acquire = run initializeResponse
9794

plugins/hls-refactor-plugin/src/Development/IDE/GHC/Dump.hs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -156,15 +156,15 @@ showAstDataHtml a0 = html $
156156

157157
srcSpan :: SrcSpan -> SDoc
158158
srcSpan ss = char ' ' <>
159-
(hang (ppr ss) 1
159+
hang (ppr ss) 1
160160
-- TODO: show annotations here
161-
(text ""))
161+
(text "")
162162

163163
realSrcSpan :: RealSrcSpan -> SDoc
164164
realSrcSpan ss = braces $ char ' ' <>
165-
(hang (ppr ss) 1
165+
hang (ppr ss) 1
166166
-- TODO: show annotations here
167-
(text ""))
167+
(text "")
168168

169169
addEpAnn :: AddEpAnn -> SDoc
170170
addEpAnn (AddEpAnn a s) = text "AddEpAnn" <+> ppr a <+> epaAnchor s
@@ -201,7 +201,7 @@ showAstDataHtml a0 = html $
201201

202202
located :: (Data a, Data b) => GenLocated a b -> SDoc
203203
located (L ss a)
204-
= nested "L" $ (li (showAstDataHtml' ss) $$ li (showAstDataHtml' a))
204+
= nested "L" (li (showAstDataHtml' ss) $$ li (showAstDataHtml' a))
205205

206206
-- -------------------------
207207

plugins/hls-refactor-plugin/src/Development/IDE/GHC/ExactPrint.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -435,7 +435,7 @@ modifySmallestDeclWithM validSpan f a = do
435435
TransformT (lift $ validSpan $ locA src) >>= \case
436436
True -> do
437437
(decs', r) <- f ldecl
438-
pure $ (DL.fromList decs' <> DL.fromList rest, Just r)
438+
pure (DL.fromList decs' <> DL.fromList rest, Just r)
439439
False -> first (DL.singleton ldecl <>) <$> modifyMatchingDecl rest
440440
modifyDeclsT' (fmap (first DL.toList) . modifyMatchingDecl) a
441441

@@ -477,7 +477,7 @@ modifySigWithM ::
477477
TransformT m a
478478
modifySigWithM queryId f a = do
479479
let modifyMatchingSigD :: [LHsDecl GhcPs] -> TransformT m (DL.DList (LHsDecl GhcPs))
480-
modifyMatchingSigD [] = pure (DL.empty)
480+
modifyMatchingSigD [] = pure DL.empty
481481
modifyMatchingSigD (ldecl@(L annSigD (SigD xsig (TypeSig xTypeSig ids (HsWC xHsWc lHsSig)))) : rest)
482482
| queryId `elem` (unLoc <$> ids) = do
483483
let newSig = f lHsSig
@@ -547,7 +547,7 @@ modifyMgMatchesT' (MG xMg (L locMatches matches)) f def combineResults = do
547547
modifyMgMatchesT' (MG xMg (L locMatches matches) originMg) f def combineResults = do
548548
(unzip -> (matches', rs)) <- mapM f matches
549549
r' <- lift $ foldM combineResults def rs
550-
pure $ (MG xMg (L locMatches matches') originMg, r')
550+
pure (MG xMg (L locMatches matches') originMg, r')
551551
#endif
552552

553553
graftSmallestDeclsWithM ::
@@ -716,7 +716,7 @@ modifyAnns x f = first ((fmap.fmap) f) x
716716
removeComma :: SrcSpanAnnA -> SrcSpanAnnA
717717
removeComma it@(SrcSpanAnn EpAnnNotUsed _) = it
718718
removeComma (SrcSpanAnn (EpAnn anc (AnnListItem as) cs) l)
719-
= (SrcSpanAnn (EpAnn anc (AnnListItem (filter (not . isCommaAnn) as)) cs) l)
719+
= SrcSpanAnn (EpAnn anc (AnnListItem (filter (not . isCommaAnn) as)) cs) l
720720
where
721721
isCommaAnn AddCommaAnn{} = True
722722
isCommaAnn _ = False

plugins/hls-refactor-plugin/src/Development/IDE/Plugin/CodeAction.hs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -120,7 +120,7 @@ codeAction state _ (CodeActionParams _ _ (TextDocumentIdentifier uri) _range Cod
120120
let
121121
actions = caRemoveRedundantImports parsedModule text diag xs uri
122122
<> caRemoveInvalidExports parsedModule text diag xs uri
123-
pure $ InL $ actions
123+
pure $ InL actions
124124

125125
-------------------------------------------------------------------------------------------------
126126

@@ -189,7 +189,7 @@ extendImportHandler :: CommandFunction IdeState ExtendImport
189189
extendImportHandler ideState _ edit@ExtendImport {..} = ExceptT $ do
190190
res <- liftIO $ runMaybeT $ extendImportHandler' ideState edit
191191
whenJust res $ \(nfp, wedit@WorkspaceEdit {_changes}) -> do
192-
let (_, (head -> TextEdit {_range})) = fromJust $ _changes >>= listToMaybe . M.toList
192+
let (_, head -> TextEdit {_range}) = fromJust $ _changes >>= listToMaybe . M.toList
193193
srcSpan = rangeToSrcSpan nfp _range
194194
LSP.sendNotification SMethod_WindowShowMessage $
195195
ShowMessageParams MessageType_Info $
@@ -1532,7 +1532,8 @@ constructNewImportSuggestions
15321532
constructNewImportSuggestions exportsMap (qual, thingMissing) notTheseModules qis = nubOrdBy simpleCompareImportSuggestion
15331533
[ suggestion
15341534
| Just name <- [T.stripPrefix (maybe "" (<> ".") qual) $ notInScope thingMissing] -- strip away qualified module names from the unknown name
1535-
, identInfo <- maybe [] Set.toList $ (lookupOccEnv (getExportsMap exportsMap) (mkVarOrDataOcc name)) <> (lookupOccEnv (getExportsMap exportsMap) (mkTypeOcc name)) -- look up the modified unknown name in the export map
1535+
, identInfo <- maybe [] Set.toList $ lookupOccEnv (getExportsMap exportsMap) (mkVarOrDataOcc name)
1536+
<> lookupOccEnv (getExportsMap exportsMap) (mkTypeOcc name) -- look up the modified unknown name in the export map
15361537
, canUseIdent thingMissing identInfo -- check if the identifier information retrieved can be used
15371538
, moduleNameText identInfo `notElem` fromMaybe [] notTheseModules -- check if the module of the identifier is allowed
15381539
, suggestion <- renderNewImport identInfo -- creates a list of import suggestions for the retrieved identifier information

plugins/hls-refactor-plugin/src/Development/IDE/Plugin/CodeAction/ExactPrint.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -343,9 +343,9 @@ extendImportViaParent df parent child (L l it@ImportDecl{..})
343343
#endif
344344
thing = IEThingWith newl twIE (IEWildcard 2) []
345345
#if MIN_VERSION_ghc(9,7,0)
346-
newl = fmap (\ann -> ann ++ [(AddEpAnn AnnDotdot d0)]) <$> l'''
346+
newl = fmap (\ann -> ann ++ [AddEpAnn AnnDotdot d0]) <$> l'''
347347
#else
348-
newl = (\ann -> ann ++ [(AddEpAnn AnnDotdot d0)]) <$> l'''
348+
newl = (\ann -> ann ++ [AddEpAnn AnnDotdot d0]) <$> l'''
349349
#endif
350350
lies = L l' $ reverse pre ++ [L l'' thing] ++ xs
351351
return $ L l it'
@@ -383,12 +383,12 @@ extendImportViaParent df parent child (L l it@ImportDecl{..})
383383
parentRdr <- liftParseAST df parent
384384
let childRdr = reLocA $ L srcChild $ mkRdrUnqual $ mkVarOcc child
385385
isParentOperator = hasParen parent
386-
let parentLIE = reLocA $ L srcParent $ (if isParentOperator then IEType (epl 0) parentRdr'
386+
let parentLIE = reLocA $ L srcParent $ if isParentOperator then IEType (epl 0) parentRdr'
387387
else IEName
388388
#if MIN_VERSION_ghc(9,5,0)
389389
noExtField
390390
#endif
391-
parentRdr')
391+
parentRdr'
392392
parentRdr' = modifyAnns parentRdr $ \case
393393
it@NameAnn{nann_adornment = NameParens} -> it{nann_open = epl 1, nann_close = epl 0}
394394
other -> other

plugins/hls-refactor-plugin/test/Main.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -94,7 +94,7 @@ initializeTests = withResource acquire release tests
9494
ir <- getInitializeResponse
9595
ExecuteCommandOptions {_commands = commands} <- case getActual $ innerCaps ir of
9696
Just eco -> pure eco
97-
Nothing -> assertFailure $ "Was expecting Just ExecuteCommandOptions, got Nothing"
97+
Nothing -> assertFailure "Was expecting Just ExecuteCommandOptions, got Nothing"
9898
-- Check if expected exists in commands. Note that commands can arrive in different order.
9999
mapM_ (\e -> any (\o -> T.isSuffixOf e o) commands @? show (expected, show commands)) expected
100100

0 commit comments

Comments
 (0)