1
1
-- Copyright (c) 2019 The DAML Authors. All rights reserved.
2
2
-- SPDX-License-Identifier: Apache-2.0
3
- {-# LANGUAGE GADTs #-}
3
+ {-# LANGUAGE GADTs #-}
4
4
5
5
module Development.IDE.Plugin.CodeAction
6
6
(
@@ -92,21 +92,27 @@ import qualified Text.Fuzzy.Parallel as TFP
92
92
import Text.Regex.TDFA (mrAfter ,
93
93
(=~) , (=~~) )
94
94
#if MIN_VERSION_ghc(9,2,1)
95
+ import GHC (realSrcSpan )
96
+ import GHC.Parser.Annotation (emptyComments )
95
97
import GHC.Types.SrcLoc (generatedSrcSpan )
96
- import Language.Haskell.GHC.ExactPrint (noAnnSrcSpanDP1 ,
97
- runTransformT )
98
+ import Language.Haskell.GHC.ExactPrint.Transform
98
99
#endif
99
100
#if MIN_VERSION_ghc(9,2,0)
101
+ import Control.Monad.Except (lift )
102
+ import Control.Monad.Identity (Identity (.. ))
100
103
import Extra (maybeToEither )
101
104
import GHC (AddEpAnn (AddEpAnn ),
102
- Anchor (anchor_op ),
105
+ Anchor (.. ),
103
106
AnchorOperation (.. ),
104
107
AnnsModule (am_main ),
105
108
DeltaPos (.. ),
106
109
EpAnn (.. ),
107
110
EpaLocation (.. ),
108
111
LEpaComment ,
109
112
LocatedA )
113
+ import Debug.Trace
114
+ import Control.Lens (bimap )
115
+
110
116
#else
111
117
import Language.Haskell.GHC.ExactPrint.Types (Annotation (annsDP ),
112
118
DeltaPos ,
@@ -177,7 +183,8 @@ bindingsPluginDescriptor recorder plId = mkExactprintPluginDescriptor recorder $
177
183
#endif
178
184
, wrap suggestNewDefinition
179
185
#if MIN_VERSION_ghc(9,2,1)
180
- , wrap suggestAddArgument
186
+ , wrap (undefinedVariableCodeAction addAsLastArgument)
187
+ , wrap (undefinedVariableCodeAction addToWhere)
181
188
#endif
182
189
, wrap suggestDeleteUnusedBinding
183
190
]
@@ -950,12 +957,30 @@ newDefinitionAction IdeOptions {..} parsedModule Range {_start} name typ
950
957
ParsedModule {pm_parsed_source = L _ HsModule {hsmodDecls}} = parsedModule
951
958
952
959
#if MIN_VERSION_ghc(9,2,1)
960
+
961
+ type UndefinedVariableCodeAction = ParsedModule -> Diagnostic -> Either ResponseError [(T. Text , [TextEdit ])]
962
+
963
+ type UndefinedVariableHandler = ParsedModule -> Range -> T. Text -> Maybe T. Text -> Either ResponseError [(T. Text , [TextEdit ])]
964
+
953
965
-- When GHC tells us that a variable is not bound, it will tell us either:
954
966
-- - there is an unbound variable with a given type
955
967
-- - there is an unbound variable (GHC provides no type suggestion)
968
+ -- - there is a typed hole `_`
956
969
--
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).
970
+ -- When we receive either of these errors, we can produce a text edit that will put this variable in scope, such as:
971
+ -- - Adding an argument binding
972
+ -- - Adding a binding in a where clause
973
+ -- - ... up to your creativity :)
974
+ undefinedVariableCodeAction :: UndefinedVariableHandler -> UndefinedVariableCodeAction
975
+ undefinedVariableCodeAction handler parsedModule Diagnostic {_message, _range}
976
+ | Just (name, typ) <- matchVariableNotInScope message = handler parsedModule _range name typ
977
+ | Just (name, typ) <- matchFoundHoleIncludeUnderscore message = handler parsedModule _range name (Just typ)
978
+ | otherwise = pure []
979
+ where
980
+ message = unifySpaces _message
981
+
982
+ -- Handle unbound variables by adding a new argument as a new pattern in the last position of each LHS of the
983
+ -- top-level bindings for this HsDecl.
959
984
--
960
985
-- TODO Include logic to also update the type signature of a binding
961
986
--
@@ -964,17 +989,8 @@ newDefinitionAction IdeOptions {..} parsedModule Range {_start} name typ
964
989
-- foo :: a -> b -> c -> d
965
990
-- foo a b = \c -> ...
966
991
-- 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 =
992
+ addAsLastArgument :: UndefinedVariableHandler
993
+ addAsLastArgument (ParsedModule _ parsedSource _ _) range name _typ =
978
994
do
979
995
let addArgToMatch (L locMatch (Match xMatch ctxMatch pats rhs)) = do
980
996
let unqualName = mkRdrUnqual $ mkVarOcc $ T. unpack name
@@ -986,17 +1002,56 @@ addArgumentAction (ParsedModule _ parsedSource _ _) range name _typ =
986
1002
let decl' = L locDecl (ValD xVal (FunBind xFunBind idFunBind mg' coreFunBind))
987
1003
pure [decl']
988
1004
decl -> pure [decl]
989
- case runTransformT $ modifySmallestDeclWithM spanContainsRangeOrErr insertArg (makeDeltaAst parsedSource) of
1005
+ case runTransformT $ modifySmallestDeclWithM ( flip spanContainsRangeOrErr range) insertArg (makeDeltaAst parsedSource) of
990
1006
Left err -> Left err
991
1007
Right (newSource, _, _) ->
992
1008
let diff = makeDiffTextEdit (T. pack $ exactPrint parsedSource) (T. pack $ exactPrint newSource)
993
1009
in pure [(" Add argument ‘" <> name <> " ’ to function" , fromLspList diff)]
994
- where
995
- spanContainsRangeOrErr = maybeToEither (responseError " SrcSpan was not valid range" ) . (`spanContainsRange` range)
996
- #endif
1010
+
1011
+ -- TODO use typ to initialise type signature
1012
+ addToWhere :: ParsedModule -> Range -> T. Text -> Maybe T. Text -> Either ResponseError [(T. Text , [TextEdit ])]
1013
+ addToWhere (ParsedModule _ parsedSource _ _) range name _typ = bimap traceShowId id $ do
1014
+ let mkUnqual name = noLocA $ mkRdrUnqual $ mkVarOcc $ T. unpack name
1015
+ equalAnn dp = AddEpAnn AnnEqual (EpaDelta dp [] )
1016
+ addArg = modifySmallestDeclWithM (flip spanContainsRangeOrErr range) $ \ case
1017
+ (L locDecl (ValD xVal (FunBind xFunBind idFunBind mg coreFunBind))) -> do
1018
+ declMatchSrcSpan <- uniqueSrcSpanT
1019
+ grhsSrcSpan <- uniqueSrcSpanT
1020
+ mg' <- modifyMgMatchesT mg $ \ match -> do
1021
+ spanInRange <- lift $ getLoc match `spanContainsRangeOrErr` range
1022
+ if spanInRange
1023
+ then do
1024
+ let grhs_ann = GrhsAnn Nothing $ equalAnn (SameLine 0 )
1025
+ rhs_hole = L (noAnnSrcSpanDP1 generatedSrcSpan) $ HsVar NoExtField (mkUnqual " _" )
1026
+ grhs = GRHS (EpAnn (generatedAnchor m1) grhs_ann emptyComments) [] rhs_hole
1027
+ grhss = GRHSs emptyComments [L grhsSrcSpan grhs] (EmptyLocalBinds NoExtField )
1028
+ newDeclMatchAnn = emptyEpAnnAnchor (generatedAnchor m0)
1029
+ newDeclMatch =
1030
+ noLocA (Match newDeclMatchAnn (FunRhs (mkUnqual name) Prefix SrcStrict ) [] grhss)
1031
+ newDeclMg = MG NoExtField (L (noAnnSrcSpanDP0 declMatchSrcSpan) [newDeclMatch]) Generated
1032
+ newDecl = (FunBind NoExtField (mkUnqual name) newDeclMg [] )
1033
+ traceShowM " tag1"
1034
+ prependDeclToWhereDecls match (noLocA newDecl)
1035
+ else pure match
1036
+ let decl' = L locDecl (ValD xVal (FunBind xFunBind idFunBind mg' coreFunBind))
1037
+ pure [decl']
1038
+ _ -> pure []
1039
+ (newSource, _, _) <- runTransformT $ addArg (makeDeltaAst parsedSource)
1040
+ let diffText = makeDiffTextEdit (T. pack $ exactPrint parsedSource) (T. pack $ exactPrint newSource)
1041
+ pure [(" Add to where ‘" <> name <> " ’" , fromLspList diffText)]
1042
+
1043
+ spanContainsRangeOrErr :: SrcSpan -> Range -> Either ResponseError Bool
1044
+ spanContainsRangeOrErr srcSpan range = maybeToEither (responseError " SrcSpan was not valid range" ) . (`spanContainsRange` range) $ srcSpan
1045
+
1046
+ generatedAnchor :: AnchorOperation -> Anchor
1047
+ generatedAnchor anchorOp = GHC. Anchor (GHC. realSrcSpan generatedSrcSpan) anchorOp
1048
+
1049
+ emptyEpAnnAnchor :: Monoid a => Anchor -> EpAnn a
1050
+ emptyEpAnnAnchor anchor = EpAnn anchor mempty emptyComments
997
1051
998
1052
fromLspList :: List a -> [a ]
999
1053
fromLspList (List a) = a
1054
+ #endif
1000
1055
1001
1056
suggestFillTypeWildcard :: Diagnostic -> [(T. Text , TextEdit )]
1002
1057
suggestFillTypeWildcard Diagnostic {_range= _range,.. }
0 commit comments