@@ -75,7 +75,6 @@ import GHC (AddEpAnn (Ad
75
75
EpAnn (.. ),
76
76
EpaLocation (.. ),
77
77
LEpaComment )
78
- import GHC.Exts (fromList )
79
78
import qualified GHC.LanguageExtensions as Lang
80
79
import Ide.Logger hiding
81
80
(group )
@@ -189,18 +188,18 @@ extendImportHandler :: CommandFunction IdeState ExtendImport
189
188
extendImportHandler ideState _ edit@ ExtendImport {.. } = ExceptT $ do
190
189
res <- liftIO $ runMaybeT $ extendImportHandler' ideState edit
191
190
whenJust res $ \ (nfp, wedit@ WorkspaceEdit {_changes}) -> do
192
- let (_, head -> TextEdit {_range}) = fromJust $ _changes >>= listToMaybe . M. toList
193
- srcSpan = rangeToSrcSpan nfp _range
194
- LSP. sendNotification SMethod_WindowShowMessage $
195
- ShowMessageParams MessageType_Info $
196
- " Import "
197
- <> maybe (" ‘" <> newThing) (\ x -> " ‘" <> x <> " (" <> newThing <> " )" ) thingParent
198
- <> " ’ from "
199
- <> importName
200
- <> " (at "
201
- <> printOutputable srcSpan
202
- <> " )"
203
- void $ LSP. sendRequest SMethod_WorkspaceApplyEdit (ApplyWorkspaceEditParams Nothing wedit) (\ _ -> pure () )
191
+ whenJust (listToMaybe =<< listToMaybe . M. elems =<< _changes) $ \ TextEdit {_range} -> do
192
+ let srcSpan = rangeToSrcSpan nfp _range
193
+ LSP. sendNotification SMethod_WindowShowMessage $
194
+ ShowMessageParams MessageType_Info $
195
+ " Import "
196
+ <> maybe (" ‘" <> newThing) (\ x -> " ‘" <> x <> " (" <> newThing <> " )" ) thingParent
197
+ <> " ’ from "
198
+ <> importName
199
+ <> " (at "
200
+ <> printOutputable srcSpan
201
+ <> " )"
202
+ void $ LSP. sendRequest SMethod_WorkspaceApplyEdit (ApplyWorkspaceEditParams Nothing wedit) (\ _ -> pure () )
204
203
return $ Right $ InR Null
205
204
206
205
extendImportHandler' :: IdeState -> ExtendImport -> MaybeT IO (NormalizedFilePath , WorkspaceEdit )
@@ -223,8 +222,7 @@ extendImportHandler' ideState ExtendImport {..}
223
222
case existingImport of
224
223
Just imp -> do
225
224
fmap (nfp,) $ liftEither $
226
- rewriteToWEdit df doc
227
- $
225
+ rewriteToWEdit df doc $
228
226
extendImport (T. unpack <$> thingParent) (T. unpack newThing) (makeDeltaAst imp)
229
227
230
228
Nothing -> do
@@ -235,7 +233,7 @@ extendImportHandler' ideState ExtendImport {..}
235
233
Nothing -> newThing
236
234
Just p -> p <> " (" <> newThing <> " )"
237
235
t <- liftMaybe $ snd <$> newImportToEdit n ps (fromMaybe " " contents)
238
- return (nfp, WorkspaceEdit {_changes= Just (GHC.Exts. fromList [( doc, [t]) ]), _documentChanges= Nothing , _changeAnnotations= Nothing })
236
+ return (nfp, WorkspaceEdit {_changes= Just (M. singleton doc [t]), _documentChanges= Nothing , _changeAnnotations= Nothing })
239
237
| otherwise =
240
238
mzero
241
239
@@ -609,7 +607,7 @@ suggestDeleteUnusedBinding
609
607
let maybeIdx = findIndex (\ (L _ id ) -> isSameName id name) lnames
610
608
in case maybeIdx of
611
609
Nothing -> Nothing
612
- Just _ | length lnames == 1 -> Just (getLoc $ reLoc $ head lnames , True )
610
+ Just _ | [lname] <- lnames -> Just (getLoc $ reLoc lname , True )
613
611
Just idx ->
614
612
let targetLname = getLoc $ reLoc $ lnames !! idx
615
613
startLoc = srcSpanStart targetLname
@@ -1052,7 +1050,7 @@ suggestImportDisambiguation df (Just txt) ps fileContents diag@Diagnostic {..}
1052
1050
parensed =
1053
1051
" (" `T.isPrefixOf` T. strip (textInRange _range txt)
1054
1052
-- > removeAllDuplicates [1, 1, 2, 3, 2] = [3]
1055
- removeAllDuplicates = map head . filter ((== 1 ) <$> length ) . group . sort
1053
+ removeAllDuplicates = map NE. head . filter ((== 1 ) . length ) . NE. group . sort
1056
1054
hasDuplicate xs = length xs /= length (S. fromList xs)
1057
1055
suggestions symbol mods local
1058
1056
| hasDuplicate mods = case mapM toModuleTarget (removeAllDuplicates mods) of
@@ -1290,7 +1288,7 @@ suggestImplicitParameter (L _ HsModule {hsmodDecls}) Diagnostic {_message, _rang
1290
1288
| otherwise = []
1291
1289
1292
1290
findTypeSignatureName :: T. Text -> Maybe T. Text
1293
- findTypeSignatureName t = matchRegexUnifySpaces t " ([^ ]+) :: " <&> head
1291
+ findTypeSignatureName t = matchRegexUnifySpaces t " ([^ ]+) :: " >>= listToMaybe
1294
1292
1295
1293
-- | Suggests a constraint for a type signature with any number of existing constraints.
1296
1294
suggestFunctionConstraint :: DynFlags -> ParsedSource -> Diagnostic -> T. Text -> [(T. Text , Rewrite )]
@@ -1378,7 +1376,8 @@ removeRedundantConstraints df (makeDeltaAst -> L _ HsModule {hsmodDecls}) Diagno
1378
1376
& take 2
1379
1377
& mapMaybe ((`matchRegexUnifySpaces` " Redundant constraints?: (.+)" ) . T. strip)
1380
1378
& listToMaybe
1381
- <&> (head >>> parseConstraints)
1379
+ >>= listToMaybe
1380
+ <&> parseConstraints
1382
1381
1383
1382
formatConstraints :: [T. Text ] -> T. Text
1384
1383
formatConstraints [] = " "
@@ -1658,7 +1657,7 @@ findPositionAfterModuleName ps hsmodName' = do
1658
1657
#endif
1659
1658
EpAnn _ annsModule _ -> do
1660
1659
-- Find the first 'where'
1661
- whereLocation <- fmap NE. head . NE. nonEmpty . mapMaybe filterWhere . am_main $ annsModule
1660
+ whereLocation <- listToMaybe . mapMaybe filterWhere $ am_main annsModule
1662
1661
epaLocationToLine whereLocation
1663
1662
EpAnnNotUsed -> Nothing
1664
1663
filterWhere (AddEpAnn AnnWhere loc) = Just loc
0 commit comments