@@ -38,6 +38,7 @@ import Data.Ord (comparing)
38
38
import qualified Data.Set as S
39
39
import qualified Data.Text as T
40
40
import qualified Data.Text.Utf16.Rope as Rope
41
+ import Data.Tuple.Extra (first )
41
42
import Development.IDE.Core.Rules
42
43
import Development.IDE.Core.RuleTypes
43
44
import Development.IDE.Core.Service
@@ -63,7 +64,8 @@ import Development.IDE.Types.Logger hiding
63
64
import Development.IDE.Types.Options
64
65
import GHC.Exts (fromList )
65
66
import qualified GHC.LanguageExtensions as Lang
66
- import Ide.PluginUtils (subRange )
67
+ import Ide.PluginUtils (makeDiffTextEdit ,
68
+ subRange )
67
69
import Ide.Types
68
70
import qualified Language.LSP.Server as LSP
69
71
import Language.LSP.Types (ApplyWorkspaceEditParams (.. ),
@@ -89,7 +91,13 @@ import Language.LSP.VFS (VirtualFile,
89
91
import qualified Text.Fuzzy.Parallel as TFP
90
92
import Text.Regex.TDFA (mrAfter ,
91
93
(=~) , (=~~) )
94
+ #if MIN_VERSION_ghc(9,2,1)
95
+ import GHC.Types.SrcLoc (generatedSrcSpan )
96
+ import Language.Haskell.GHC.ExactPrint (noAnnSrcSpanDP1 ,
97
+ runTransformT )
98
+ #endif
92
99
#if MIN_VERSION_ghc(9,2,0)
100
+ import Extra (maybeToEither )
93
101
import GHC (AddEpAnn (AddEpAnn ),
94
102
Anchor (anchor_op ),
95
103
AnchorOperation (.. ),
@@ -168,6 +176,9 @@ bindingsPluginDescriptor recorder plId = mkExactprintPluginDescriptor recorder $
168
176
, wrap suggestImplicitParameter
169
177
#endif
170
178
, wrap suggestNewDefinition
179
+ #if MIN_VERSION_ghc(9,2,1)
180
+ , wrap suggestAddArgument
181
+ #endif
171
182
, wrap suggestDeleteUnusedBinding
172
183
]
173
184
plId
@@ -243,7 +254,7 @@ extendImportHandler' ideState ExtendImport {..}
243
254
Nothing -> newThing
244
255
Just p -> p <> " (" <> newThing <> " )"
245
256
t <- liftMaybe $ snd <$> newImportToEdit n ps (fromMaybe " " contents)
246
- return (nfp, WorkspaceEdit {_changes= Just (fromList [(doc,List [t])]), _documentChanges= Nothing , _changeAnnotations= Nothing })
257
+ return (nfp, WorkspaceEdit {_changes= Just (GHC.Exts. fromList [(doc,List [t])]), _documentChanges= Nothing , _changeAnnotations= Nothing })
247
258
| otherwise =
248
259
mzero
249
260
@@ -385,7 +396,7 @@ suggestHideShadow ps fileContents mTcM mHar Diagnostic {_message, _range}
385
396
Just matched <- allMatchRegexUnifySpaces _message " imported from ‘([^’]+)’ at ([^ ]*)" ,
386
397
mods <- [(modName, s) | [_, modName, s] <- matched],
387
398
result <- nubOrdBy (compare `on` fst ) $ mods >>= uncurry (suggests identifier),
388
- hideAll <- (" Hide " <> identifier <> " from all occurence imports" , concat $ snd <$> result) =
399
+ hideAll <- (" Hide " <> identifier <> " from all occurence imports" , concatMap snd result) =
389
400
result <> [hideAll]
390
401
| otherwise = []
391
402
where
@@ -881,34 +892,111 @@ suggestReplaceIdentifier contents Diagnostic{_range=_range,..}
881
892
= [ (" Replace with ‘" <> name <> " ’" , [mkRenameEdit contents _range name]) | name <- renameSuggestions ]
882
893
| otherwise = []
883
894
895
+ matchVariableNotInScope :: T. Text -> Maybe (T. Text , Maybe T. Text )
896
+ matchVariableNotInScope message
897
+ -- * Variable not in scope:
898
+ -- suggestAcion :: Maybe T.Text -> Range -> Range
899
+ -- * Variable not in scope:
900
+ -- suggestAcion
901
+ | Just (name, typ) <- matchVariableNotInScopeTyped message = Just (name, Just typ)
902
+ | Just name <- matchVariableNotInScopeUntyped message = Just (name, Nothing )
903
+ | otherwise = Nothing
904
+ where
905
+ matchVariableNotInScopeTyped message
906
+ | Just [name, typ] <- matchRegexUnifySpaces message " Variable not in scope: ([^ ]+) :: ([^*•]+)" =
907
+ Just (name, typ)
908
+ | otherwise = Nothing
909
+ matchVariableNotInScopeUntyped message
910
+ | Just [name] <- matchRegexUnifySpaces message " Variable not in scope: ([^ ]+)" =
911
+ Just name
912
+ | otherwise = Nothing
913
+
914
+ matchFoundHole :: T. Text -> Maybe (T. Text , T. Text )
915
+ matchFoundHole message
916
+ | Just [name, typ] <- matchRegexUnifySpaces message " Found hole: _([^ ]+) :: ([^*•]+) Or perhaps" =
917
+ Just (name, typ)
918
+ | otherwise = Nothing
919
+
920
+ matchFoundHoleIncludeUnderscore :: T. Text -> Maybe (T. Text , T. Text )
921
+ matchFoundHoleIncludeUnderscore message = first (" _" <> ) <$> matchFoundHole message
922
+
884
923
suggestNewDefinition :: IdeOptions -> ParsedModule -> Maybe T. Text -> Diagnostic -> [(T. Text , [TextEdit ])]
885
- suggestNewDefinition ideOptions parsedModule contents Diagnostic {_message, _range}
886
- -- * Variable not in scope:
887
- -- suggestAcion :: Maybe T.Text -> Range -> Range
888
- | Just [name, typ] <- matchRegexUnifySpaces message " Variable not in scope: ([^ ]+) :: ([^*•]+)"
889
- = newDefinitionAction ideOptions parsedModule _range name typ
890
- | Just [name, typ] <- matchRegexUnifySpaces message " Found hole: _([^ ]+) :: ([^*•]+) Or perhaps"
891
- , [(label, newDefinitionEdits)] <- newDefinitionAction ideOptions parsedModule _range name typ
892
- = [(label, mkRenameEdit contents _range name : newDefinitionEdits)]
893
- | otherwise = []
894
- where
895
- message = unifySpaces _message
924
+ suggestNewDefinition ideOptions parsedModule contents Diagnostic {_message, _range}
925
+ | Just (name, typ) <- matchVariableNotInScope message =
926
+ newDefinitionAction ideOptions parsedModule _range name typ
927
+ | Just (name, typ) <- matchFoundHole message,
928
+ [(label, newDefinitionEdits)] <- newDefinitionAction ideOptions parsedModule _range name (Just typ) =
929
+ [(label, mkRenameEdit contents _range name : newDefinitionEdits)]
930
+ | otherwise = []
931
+ where
932
+ message = unifySpaces _message
896
933
897
- newDefinitionAction :: IdeOptions -> ParsedModule -> Range -> T. Text -> T. Text -> [(T. Text , [TextEdit ])]
898
- newDefinitionAction IdeOptions {.. } parsedModule Range {_start} name typ
899
- | Range _ lastLineP : _ <-
934
+ newDefinitionAction :: IdeOptions -> ParsedModule -> Range -> T. Text -> Maybe T. Text -> [(T. Text , [TextEdit ])]
935
+ newDefinitionAction IdeOptions {.. } parsedModule Range {_start} name typ
936
+ | Range _ lastLineP : _ <-
900
937
[ realSrcSpanToRange sp
901
- | (L (locA -> l@ (RealSrcSpan sp _)) _) <- hsmodDecls
902
- , _start `isInsideSrcSpan` l]
903
- , nextLineP <- Position { _line = _line lastLineP + 1 , _character = 0 }
904
- = [ (" Define " <> sig
905
- , [TextEdit (Range nextLineP nextLineP) (T. unlines [" " , sig, name <> " = _" ])]
906
- )]
907
- | otherwise = []
938
+ | (L (locA -> l@ (RealSrcSpan sp _)) _) <- hsmodDecls,
939
+ _start `isInsideSrcSpan` l
940
+ ],
941
+ nextLineP <- Position {_line = _line lastLineP + 1 , _character = 0 } =
942
+ [ ( " Define " <> sig,
943
+ [TextEdit (Range nextLineP nextLineP) (T. unlines [" " , sig, name <> " = _" ])]
944
+ )
945
+ ]
946
+ | otherwise = []
908
947
where
909
948
colon = if optNewColonConvention then " : " else " :: "
910
- sig = name <> colon <> T. dropWhileEnd isSpace typ
911
- ParsedModule {pm_parsed_source = L _ HsModule {hsmodDecls}} = parsedModule
949
+ sig = name <> colon <> T. dropWhileEnd isSpace (fromMaybe " _" typ)
950
+ ParsedModule {pm_parsed_source = L _ HsModule {hsmodDecls}} = parsedModule
951
+
952
+ #if MIN_VERSION_ghc(9,2,1)
953
+ -- When GHC tells us that a variable is not bound, it will tell us either:
954
+ -- - there is an unbound variable with a given type
955
+ -- - there is an unbound variable (GHC provides no type suggestion)
956
+ --
957
+ -- When we receive either of these errors, we produce a text edit that will add a new argument (as a new pattern in the
958
+ -- last position of each LHS of the top-level bindings for this HsDecl).
959
+ --
960
+ -- TODO Include logic to also update the type signature of a binding
961
+ --
962
+ -- NOTE When adding a new argument to a declaration, the corresponding argument's type in declaration's signature might
963
+ -- not be the last type in the signature, such as:
964
+ -- foo :: a -> b -> c -> d
965
+ -- foo a b = \c -> ...
966
+ -- In this case a new argument would have to add its type between b and c in the signature.
967
+ suggestAddArgument :: ParsedModule -> Diagnostic -> Either ResponseError [(T. Text , [TextEdit ])]
968
+ suggestAddArgument parsedModule Diagnostic {_message, _range}
969
+ | Just (name, typ) <- matchVariableNotInScope message = addArgumentAction parsedModule _range name typ
970
+ | Just (name, typ) <- matchFoundHoleIncludeUnderscore message = addArgumentAction parsedModule _range name (Just typ)
971
+ | otherwise = pure []
972
+ where
973
+ message = unifySpaces _message
974
+
975
+ -- TODO use typ to modify type signature
976
+ addArgumentAction :: ParsedModule -> Range -> T. Text -> Maybe T. Text -> Either ResponseError [(T. Text , [TextEdit ])]
977
+ addArgumentAction (ParsedModule _ parsedSource _ _) range name _typ =
978
+ do
979
+ let addArgToMatch (L locMatch (Match xMatch ctxMatch pats rhs)) = do
980
+ let unqualName = mkRdrUnqual $ mkVarOcc $ T. unpack name
981
+ let newPat = L (noAnnSrcSpanDP1 generatedSrcSpan) $ VarPat NoExtField (noLocA unqualName)
982
+ pure $ L locMatch (Match xMatch ctxMatch (pats <> [newPat]) rhs)
983
+ insertArg = \ case
984
+ (L locDecl (ValD xVal (FunBind xFunBind idFunBind mg coreFunBind))) -> do
985
+ mg' <- modifyMgMatchesT mg addArgToMatch
986
+ let decl' = L locDecl (ValD xVal (FunBind xFunBind idFunBind mg' coreFunBind))
987
+ pure [decl']
988
+ decl -> pure [decl]
989
+ case runTransformT $ modifySmallestDeclWithM spanContainsRangeOrErr insertArg (makeDeltaAst parsedSource) of
990
+ Left err -> Left err
991
+ Right (newSource, _, _) ->
992
+ let diff = makeDiffTextEdit (T. pack $ exactPrint parsedSource) (T. pack $ exactPrint newSource)
993
+ in pure [(" Add argument ‘" <> name <> " ’ to function" , fromLspList diff)]
994
+ where
995
+ spanContainsRangeOrErr = maybeToEither (responseError " SrcSpan was not valid range" ) . (`spanContainsRange` range)
996
+ #endif
997
+
998
+ fromLspList :: List a -> [a ]
999
+ fromLspList (List a) = a
912
1000
913
1001
suggestFillTypeWildcard :: Diagnostic -> [(T. Text , TextEdit )]
914
1002
suggestFillTypeWildcard Diagnostic {_range= _range,.. }
0 commit comments