@@ -93,12 +93,14 @@ import qualified Text.Fuzzy.Parallel as TFP
93
93
import Text.Regex.TDFA (mrAfter ,
94
94
(=~) , (=~~) )
95
95
#if MIN_VERSION_ghc(9,2,1)
96
+ import Data.Either.Extra (maybeToEither )
96
97
import GHC.Types.SrcLoc (generatedSrcSpan )
97
98
import Language.Haskell.GHC.ExactPrint (noAnnSrcSpanDP1 ,
98
99
runTransformT )
99
100
#endif
100
101
#if MIN_VERSION_ghc(9,2,0)
101
- import Extra (maybeToEither )
102
+ import Control.Monad.Except (lift )
103
+ import Debug.Trace
102
104
import GHC (AddEpAnn (AddEpAnn ),
103
105
Anchor (anchor_op ),
104
106
AnchorOperation (.. ),
@@ -107,7 +109,17 @@ import GHC (AddEpAnn (Ad
107
109
EpAnn (.. ),
108
110
EpaLocation (.. ),
109
111
LEpaComment ,
110
- LocatedA )
112
+ LocatedA ,
113
+ SrcSpanAnn' (SrcSpanAnn ),
114
+ SrcSpanAnnA ,
115
+ SrcSpanAnnN ,
116
+ TrailingAnn (.. ),
117
+ addTrailingAnnToA ,
118
+ emptyComments ,
119
+ noAnn )
120
+ import GHC.Hs (IsUnicodeSyntax (.. ))
121
+ import Language.Haskell.GHC.ExactPrint.Transform (d1 )
122
+
111
123
#else
112
124
import Language.Haskell.GHC.ExactPrint.Types (Annotation (annsDP ),
113
125
DeltaPos ,
@@ -958,8 +970,6 @@ newDefinitionAction IdeOptions {..} parsedModule Range {_start} name typ
958
970
-- When we receive either of these errors, we produce a text edit that will add a new argument (as a new pattern in the
959
971
-- last position of each LHS of the top-level bindings for this HsDecl).
960
972
--
961
- -- TODO Include logic to also update the type signature of a binding
962
- --
963
973
-- NOTE When adding a new argument to a declaration, the corresponding argument's type in declaration's signature might
964
974
-- not be the last type in the signature, such as:
965
975
-- foo :: a -> b -> c -> d
@@ -973,31 +983,100 @@ suggestAddArgument parsedModule Diagnostic {_message, _range}
973
983
where
974
984
message = unifySpaces _message
975
985
976
- -- TODO use typ to modify type signature
986
+ -- Given a name for the new binding, add a new pattern to the match in the last position,
987
+ -- returning how many patterns there were in this match prior to the transformation:
988
+ -- addArgToMatch "foo" `bar arg1 arg2 = ...`
989
+ -- => (`bar arg1 arg2 foo = ...`, 2)
990
+ addArgToMatch :: T. Text -> GenLocated l (Match GhcPs body ) -> (GenLocated l (Match GhcPs body ), Int )
991
+ addArgToMatch name (L locMatch (Match xMatch ctxMatch pats rhs)) =
992
+ let unqualName = mkRdrUnqual $ mkVarOcc $ T. unpack name
993
+ newPat = L (noAnnSrcSpanDP1 generatedSrcSpan) $ VarPat NoExtField (noLocA unqualName)
994
+ in (L locMatch (Match xMatch ctxMatch (pats <> [newPat]) rhs), length pats)
995
+
996
+ -- Attempt to insert a binding pattern into each match for the given LHsDecl; succeeds only if the function is a FunBind.
997
+ -- Also return:
998
+ -- - the declaration's name
999
+ -- - the number of bound patterns in the declaration's matches prior to the transformation
1000
+ --
1001
+ -- For example:
1002
+ -- insertArg "new_pat" `foo bar baz = 1`
1003
+ -- => (`foo bar baz new_pat = 1`, Just ("foo", 2))
1004
+ appendFinalPatToMatches :: T. Text -> LHsDecl GhcPs -> TransformT (Either ResponseError ) (LHsDecl GhcPs , Maybe (GenLocated SrcSpanAnnN RdrName , Int ))
1005
+ appendFinalPatToMatches name = \ case
1006
+ (L locDecl (ValD xVal (FunBind xFunBind idFunBind mg coreFunBind))) -> do
1007
+ (mg', numPatsMay) <- modifyMgMatchesT' mg (pure . second Just . addArgToMatch name) Nothing combineMatchNumPats
1008
+ numPats <- lift $ maybeToEither (responseError " Unexpected empty match group in HsDecl" ) numPatsMay
1009
+ let decl' = L locDecl (ValD xVal (FunBind xFunBind idFunBind mg' coreFunBind))
1010
+ pure (decl', Just (idFunBind, numPats))
1011
+ decl -> pure (decl, Nothing )
1012
+ where
1013
+ combineMatchNumPats Nothing other = pure other
1014
+ combineMatchNumPats other Nothing = pure other
1015
+ combineMatchNumPats (Just l) (Just r)
1016
+ | l == r = pure (Just l)
1017
+ | otherwise = Left $ responseError " Unexpected different numbers of patterns in HsDecl MatchGroup"
1018
+
1019
+ -- The add argument works as follows:
1020
+ -- 1. Attempt to add the given name as the last pattern of the declaration that contains `range`.
1021
+ -- 2. If such a declaration exists, use that declaration's name to modify the signature of said declaration, if it
1022
+ -- has a type signature.
1023
+ --
1024
+ -- NOTE For the following situation, the type signature is not updated (it's unclear what should happen):
1025
+ -- type FunctionTySyn = () -> Int
1026
+ -- foo :: FunctionTySyn
1027
+ -- foo () = new_def
1028
+ --
1029
+ -- TODO instead of inserting a typed hole; use GHC's suggested type from the error
977
1030
addArgumentAction :: ParsedModule -> Range -> T. Text -> Maybe T. Text -> Either ResponseError [(T. Text , [TextEdit ])]
978
- addArgumentAction (ParsedModule _ parsedSource _ _) range name _typ =
979
- do
980
- let addArgToMatch (L locMatch (Match xMatch ctxMatch pats rhs)) = do
981
- let unqualName = mkRdrUnqual $ mkVarOcc $ T. unpack name
982
- let newPat = L (noAnnSrcSpanDP1 generatedSrcSpan) $ VarPat NoExtField (noLocA unqualName)
983
- pure $ L locMatch (Match xMatch ctxMatch (pats <> [newPat]) rhs)
984
- insertArg = \ case
985
- (L locDecl (ValD xVal (FunBind xFunBind idFunBind mg coreFunBind))) -> do
986
- mg' <- modifyMgMatchesT mg addArgToMatch
987
- let decl' = L locDecl (ValD xVal (FunBind xFunBind idFunBind mg' coreFunBind))
988
- pure [decl']
989
- decl -> pure [decl]
990
- case runTransformT $ modifySmallestDeclWithM spanContainsRangeOrErr insertArg (makeDeltaAst parsedSource) of
991
- Left err -> Left err
992
- Right (newSource, _, _) ->
993
- let diff = makeDiffTextEdit (T. pack $ exactPrint parsedSource) (T. pack $ exactPrint newSource)
994
- in pure [(" Add argument ‘" <> name <> " ’ to function" , fromLspList diff)]
995
- where
996
- spanContainsRangeOrErr = maybeToEither (responseError " SrcSpan was not valid range" ) . (`spanContainsRange` range)
997
- #endif
1031
+ addArgumentAction (ParsedModule _ moduleSrc _ _) range name _typ = do
1032
+ (newSource, _, _) <- runTransformT $ do
1033
+ (moduleSrc', join -> matchedDeclNameMay) <- addNameAsLastArgOfMatchingDecl (makeDeltaAst moduleSrc)
1034
+ case matchedDeclNameMay of
1035
+ Just (matchedDeclName, numPats) -> modifySigWithM (unLoc matchedDeclName) (addTyHoleToTySigArg numPats) moduleSrc'
1036
+ Nothing -> pure moduleSrc'
1037
+ let diff = makeDiffTextEdit (T. pack $ exactPrint moduleSrc) (T. pack $ exactPrint newSource)
1038
+ pure [(" Add argument ‘" <> name <> " ’ to function" , fromLspList diff)]
1039
+ where
1040
+ addNameAsLastArgOfMatchingDecl = modifySmallestDeclWithM spanContainsRangeOrErr addNameAsLastArg
1041
+ addNameAsLastArg = fmap (first (: [] )) . appendFinalPatToMatches name
1042
+
1043
+ spanContainsRangeOrErr = maybeToEither (responseError " SrcSpan was not valid range" ) . (`spanContainsRange` range)
1044
+
1045
+ -- Transform an LHsType into a list of arguments and return type, to make transformations easier.
1046
+ hsTypeToFunTypeAsList :: LHsType GhcPs -> ([(SrcSpanAnnA , XFunTy GhcPs , HsArrow GhcPs , LHsType GhcPs )], LHsType GhcPs )
1047
+ hsTypeToFunTypeAsList = \ case
1048
+ L spanAnnA (HsFunTy xFunTy arrow lhs rhs) ->
1049
+ let (rhsArgs, rhsRes) = hsTypeToFunTypeAsList rhs
1050
+ in ((spanAnnA, xFunTy, arrow, lhs): rhsArgs, rhsRes)
1051
+ ty -> ([] , ty)
1052
+
1053
+ -- The inverse of `hsTypeToFunTypeAsList`
1054
+ hsTypeFromFunTypeAsList :: ([(SrcSpanAnnA , XFunTy GhcPs , HsArrow GhcPs , LHsType GhcPs )], LHsType GhcPs ) -> LHsType GhcPs
1055
+ hsTypeFromFunTypeAsList (args, res) =
1056
+ foldr (\ (spanAnnA, xFunTy, arrow, argTy) res -> L spanAnnA $ HsFunTy xFunTy arrow argTy res) res args
1057
+
1058
+ -- Add a typed hole to a type signature in the given argument position:
1059
+ -- 0 `foo :: ()` => foo :: _ -> ()
1060
+ -- 2 `foo :: FunctionTySyn` => foo :: FunctionTySyn
1061
+ -- 1 `foo :: () -> () -> Int` => foo :: () -> _ -> () -> Int
1062
+ addTyHoleToTySigArg :: Int -> LHsSigType GhcPs -> (LHsSigType GhcPs )
1063
+ addTyHoleToTySigArg loc (L annHsSig (HsSig xHsSig tyVarBndrs lsigTy)) =
1064
+ let (args, res) = hsTypeToFunTypeAsList lsigTy
1065
+ wildCardAnn = SrcSpanAnn (EpAnn genAnchor1 (AnnListItem [AddRarrowAnn d1]) emptyComments) generatedSrcSpan
1066
+ newArg = (SrcSpanAnn mempty generatedSrcSpan, noAnn, HsUnrestrictedArrow NormalSyntax , L wildCardAnn $ HsWildCardTy noExtField)
1067
+ -- NOTE if the location that the argument wants to be placed at is not one more than the number of arguments
1068
+ -- in the signature, then we return the original type signature.
1069
+ -- This situation most likely occurs due to a function type synonym in the signature
1070
+ insertArg n _ | n < 0 = error " Not possible"
1071
+ insertArg 0 as = newArg: as
1072
+ insertArg _ [] = []
1073
+ insertArg n (a: as) = a : insertArg (n - 1 ) as
1074
+ lsigTy' = hsTypeFromFunTypeAsList (insertArg loc args, res)
1075
+ in L annHsSig (HsSig xHsSig tyVarBndrs lsigTy')
998
1076
999
1077
fromLspList :: List a -> [a ]
1000
1078
fromLspList (List a) = a
1079
+ #endif
1001
1080
1002
1081
suggestFillTypeWildcard :: Diagnostic -> [(T. Text , TextEdit )]
1003
1082
suggestFillTypeWildcard Diagnostic {_range= _range,.. }
0 commit comments