Skip to content

Commit 9d70df0

Browse files
santiweightSantiago Weightpepeiborramichaelpj
authoredNov 6, 2022
support "add argument" action (#3149)
* support add-argument action * respond to review comments * review: add ability to report errors in CodeAction api * review: use already-defined function * attempts at cpp * fix format error * fix broken test * doc: add self to codeowners; add doc to features.md * formatting * formatting * fix an import * review * formatting * add testcase with comments * fix build error Co-authored-by: Santiago Weight <santiago.weight@lmns.com> Co-authored-by: Pepe Iborra <pepeiborra@gmail.com> Co-authored-by: Michael Peyton Jones <me@michaelpj.com>
1 parent d17d9fd commit 9d70df0

File tree

9 files changed

+444
-57
lines changed

9 files changed

+444
-57
lines changed
 

‎CODEOWNERS

+1
Original file line numberDiff line numberDiff line change
@@ -24,6 +24,7 @@
2424
/plugins/hls-qualify-imported-names-plugin @eddiemundo
2525
/plugins/hls-refine-imports-plugin
2626
/plugins/hls-rename-plugin @OliverMadine
27+
/plugins/hls-refactor-plugin @santiweight
2728
/plugins/hls-retrie-plugin @pepeiborra
2829
/plugins/hls-code-range-plugin @kokobd
2930
/plugins/hls-splice-plugin @konn

‎docs/features.md

+8
Original file line numberDiff line numberDiff line change
@@ -271,6 +271,14 @@ Known Limitations:
271271

272272
![Link to Docs](../plugins/hls-change-type-signature-plugin/README.md)
273273

274+
### Add argument to function
275+
276+
Provided by: `hls-refactor-plugin`
277+
278+
Code action kind: `quickfix`
279+
280+
Add an undefined variable as an argument to the top-level binding.
281+
274282
### Convert to GADT syntax
275283

276284
Provided by: `hls-gadt-plugin`

‎ghcide/src/Development/IDE/GHC/Error.hs

+6
Original file line numberDiff line numberDiff line change
@@ -24,6 +24,7 @@ module Development.IDE.GHC.Error
2424
, zeroSpan
2525
, realSpan
2626
, isInsideSrcSpan
27+
, spanContainsRange
2728
, noSpan
2829

2930
-- * utilities working with severities
@@ -43,6 +44,7 @@ import Development.IDE.GHC.Orphans ()
4344
import Development.IDE.Types.Diagnostics as D
4445
import Development.IDE.Types.Location
4546
import GHC
47+
import Language.LSP.Types (isSubrangeOf)
4648

4749

4850
diagFromText :: T.Text -> D.DiagnosticSeverity -> SrcSpan -> T.Text -> FileDiagnostic
@@ -119,6 +121,10 @@ p `isInsideSrcSpan` r = case srcSpanToRange r of
119121
Just (Range sp ep) -> sp <= p && p <= ep
120122
_ -> False
121123

124+
-- Returns Nothing if the SrcSpan does not represent a valid range
125+
spanContainsRange :: SrcSpan -> Range -> Maybe Bool
126+
spanContainsRange srcSpan range = (range `isSubrangeOf`) <$> srcSpanToRange srcSpan
127+
122128
-- | Convert a GHC severity to a DAML compiler Severity. Severities below
123129
-- "Warning" level are dropped (returning Nothing).
124130
toDSeverity :: GHC.Severity -> Maybe D.DiagnosticSeverity

‎plugins/hls-qualify-imported-names-plugin/src/Ide/Plugin/QualifyImportedNames.hs

+4-7
Original file line numberDiff line numberDiff line change
@@ -18,9 +18,10 @@ import qualified Data.HashMap.Strict as HashMap
1818
import Data.List (sortOn)
1919
import qualified Data.List as List
2020
import qualified Data.Map.Strict as Map
21-
import Data.Maybe (mapMaybe)
21+
import Data.Maybe (fromMaybe, mapMaybe)
2222
import Data.Text (Text)
2323
import qualified Data.Text as Text
24+
import Development.IDE (spanContainsRange)
2425
import Development.IDE.Core.RuleTypes (GetFileContents (GetFileContents),
2526
GetHieAst (GetHieAst),
2627
HieAstResult (HAR, refMap),
@@ -87,16 +88,12 @@ descriptor pluginId = (defaultPluginDescriptor pluginId) {
8788
]
8889
}
8990

90-
isRangeWithinSrcSpan :: Range -> SrcSpan -> Bool
91-
isRangeWithinSrcSpan (Range start end) srcSpan =
92-
isInsideSrcSpan start srcSpan && isInsideSrcSpan end srcSpan
93-
9491
findLImportDeclAt :: Range -> ParsedModule -> Maybe (LImportDecl GhcPs)
9592
findLImportDeclAt range parsedModule
9693
| ParsedModule {..} <- parsedModule
9794
, L _ hsModule <- pm_parsed_source
9895
, locatedImportDecls <- hsmodImports hsModule =
99-
find (\ (L (locA -> srcSpan) _) -> isRangeWithinSrcSpan range srcSpan) locatedImportDecls
96+
find (\ (L (locA -> srcSpan) _) -> fromMaybe False $ srcSpan `spanContainsRange` range) locatedImportDecls
10097

10198
makeCodeActions :: Uri -> [TextEdit] -> [a |? CodeAction]
10299
makeCodeActions uri textEdits = [InR CodeAction {..} | not (null textEdits)]
@@ -132,7 +129,7 @@ data ImportedBy = ImportedBy {
132129
}
133130

134131
isRangeWithinImportedBy :: Range -> ImportedBy -> Bool
135-
isRangeWithinImportedBy range (ImportedBy _ srcSpan) = isRangeWithinSrcSpan range srcSpan
132+
isRangeWithinImportedBy range (ImportedBy _ srcSpan) = fromMaybe False $ spanContainsRange srcSpan range
136133

137134
globalRdrEnvToNameToImportedByMap :: GlobalRdrEnv -> NameEnv [ImportedBy]
138135
globalRdrEnvToNameToImportedByMap =

‎plugins/hls-refactor-plugin/hls-refactor-plugin.cabal

+2
Original file line numberDiff line numberDiff line change
@@ -113,6 +113,8 @@ test-suite tests
113113
, extra
114114
, text-rope
115115
, containers
116+
-- ghc is included to enable the MIN_VERSION_ghc macro
117+
, ghc
116118
, ghcide
117119
, ghcide-test-utils
118120
, shake

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

+39
Original file line numberDiff line numberDiff line change
@@ -20,6 +20,10 @@ module Development.IDE.GHC.ExactPrint
2020
transform,
2121
transformM,
2222
ExactPrint(..),
23+
#if MIN_VERSION_ghc(9,2,1)
24+
modifySmallestDeclWithM,
25+
modifyMgMatchesT,
26+
#endif
2327
#if !MIN_VERSION_ghc(9,2,0)
2428
Anns,
2529
Annotate,
@@ -438,6 +442,41 @@ graftDecls dst decs0 = Graft $ \dflags a -> do
438442
| otherwise = DL.singleton (L src e) <> go rest
439443
modifyDeclsT (pure . DL.toList . go) a
440444

445+
#if MIN_VERSION_ghc(9,2,1)
446+
447+
-- | Replace the smallest declaration whose SrcSpan satisfies the given condition with a new
448+
-- list of declarations.
449+
--
450+
-- For example, if you would like to move a where-clause-defined variable to the same
451+
-- level as its parent HsDecl, you could use this function.
452+
modifySmallestDeclWithM ::
453+
forall a m.
454+
(HasDecls a, Monad m) =>
455+
(SrcSpan -> m Bool) ->
456+
(LHsDecl GhcPs -> TransformT m [LHsDecl GhcPs]) ->
457+
a ->
458+
TransformT m a
459+
modifySmallestDeclWithM validSpan f a = do
460+
let modifyMatchingDecl [] = pure DL.empty
461+
modifyMatchingDecl (e@(L src _) : rest) =
462+
lift (validSpan $ locA src) >>= \case
463+
True -> do
464+
decs' <- f e
465+
pure $ DL.fromList decs' <> DL.fromList rest
466+
False -> (DL.singleton e <>) <$> modifyMatchingDecl rest
467+
modifyDeclsT (fmap DL.toList . modifyMatchingDecl) a
468+
469+
-- | Modify the each LMatch in a MatchGroup
470+
modifyMgMatchesT ::
471+
Monad m =>
472+
MatchGroup GhcPs (LHsExpr GhcPs) ->
473+
(LMatch GhcPs (LHsExpr GhcPs) -> TransformT m (LMatch GhcPs (LHsExpr GhcPs))) ->
474+
TransformT m (MatchGroup GhcPs (LHsExpr GhcPs))
475+
modifyMgMatchesT (MG xMg (L locMatches matches) originMg) f = do
476+
matches' <- mapM f matches
477+
pure $ MG xMg (L locMatches matches') originMg
478+
#endif
479+
441480
graftSmallestDeclsWithM ::
442481
forall a.
443482
(HasDecls a) =>

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

+114-26
Original file line numberDiff line numberDiff line change
@@ -38,6 +38,7 @@ import Data.Ord (comparing)
3838
import qualified Data.Set as S
3939
import qualified Data.Text as T
4040
import qualified Data.Text.Utf16.Rope as Rope
41+
import Data.Tuple.Extra (first)
4142
import Development.IDE.Core.Rules
4243
import Development.IDE.Core.RuleTypes
4344
import Development.IDE.Core.Service
@@ -63,7 +64,8 @@ import Development.IDE.Types.Logger hiding
6364
import Development.IDE.Types.Options
6465
import GHC.Exts (fromList)
6566
import qualified GHC.LanguageExtensions as Lang
66-
import Ide.PluginUtils (subRange)
67+
import Ide.PluginUtils (makeDiffTextEdit,
68+
subRange)
6769
import Ide.Types
6870
import qualified Language.LSP.Server as LSP
6971
import Language.LSP.Types (ApplyWorkspaceEditParams (..),
@@ -89,7 +91,13 @@ import Language.LSP.VFS (VirtualFile,
8991
import qualified Text.Fuzzy.Parallel as TFP
9092
import Text.Regex.TDFA (mrAfter,
9193
(=~), (=~~))
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
9299
#if MIN_VERSION_ghc(9,2,0)
100+
import Extra (maybeToEither)
93101
import GHC (AddEpAnn (AddEpAnn),
94102
Anchor (anchor_op),
95103
AnchorOperation (..),
@@ -168,6 +176,9 @@ bindingsPluginDescriptor recorder plId = mkExactprintPluginDescriptor recorder $
168176
, wrap suggestImplicitParameter
169177
#endif
170178
, wrap suggestNewDefinition
179+
#if MIN_VERSION_ghc(9,2,1)
180+
, wrap suggestAddArgument
181+
#endif
171182
, wrap suggestDeleteUnusedBinding
172183
]
173184
plId
@@ -243,7 +254,7 @@ extendImportHandler' ideState ExtendImport {..}
243254
Nothing -> newThing
244255
Just p -> p <> "(" <> newThing <> ")"
245256
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})
247258
| otherwise =
248259
mzero
249260

@@ -385,7 +396,7 @@ suggestHideShadow ps fileContents mTcM mHar Diagnostic {_message, _range}
385396
Just matched <- allMatchRegexUnifySpaces _message "imported from ‘([^’]+)’ at ([^ ]*)",
386397
mods <- [(modName, s) | [_, modName, s] <- matched],
387398
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) =
389400
result <> [hideAll]
390401
| otherwise = []
391402
where
@@ -881,34 +892,111 @@ suggestReplaceIdentifier contents Diagnostic{_range=_range,..}
881892
= [ ("Replace with ‘" <> name <> "", [mkRenameEdit contents _range name]) | name <- renameSuggestions ]
882893
| otherwise = []
883894

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+
884923
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
896933

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 : _ <-
900937
[ 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 = []
908947
where
909948
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
9121000

9131001
suggestFillTypeWildcard :: Diagnostic -> [(T.Text, TextEdit)]
9141002
suggestFillTypeWildcard Diagnostic{_range=_range,..}

0 commit comments

Comments
 (0)