Skip to content

Commit c89225e

Browse files
author
Santiago Weight
committed
support add to where
1 parent 0fce830 commit c89225e

File tree

3 files changed

+378
-26
lines changed

3 files changed

+378
-26
lines changed

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

+93
Original file line numberDiff line numberDiff line change
@@ -47,6 +47,8 @@ module Development.IDE.GHC.ExactPrint
4747
ExceptStringT (..),
4848
TransformT,
4949
Log(..),
50+
prependDecl,
51+
prependDeclToWhereDecls,
5052
)
5153
where
5254

@@ -109,6 +111,13 @@ import GHC.Parser.Annotation (AnnContext (..),
109111
DeltaPos (SameLine),
110112
EpaLocation (EpaDelta),
111113
deltaPos)
114+
import GHC (DeltaPos(..))
115+
import GHC.Types.SrcLoc (generatedSrcSpan)
116+
import GHC (Anchor(..))
117+
import GHC (AnchorOperation(..))
118+
import GHC (realSrcSpan)
119+
import GHC (EpAnnComments(..))
120+
import Debug.Trace (traceShowM, trace, traceM)
112121
#endif
113122

114123
#if MIN_VERSION_ghc(9,2,0)
@@ -475,6 +484,90 @@ modifyMgMatchesT ::
475484
modifyMgMatchesT (MG xMg (L locMatches matches) originMg) f = do
476485
matches' <- mapM f matches
477486
pure $ MG xMg (L locMatches matches') originMg
487+
488+
insertAtStart' :: (Monad m, HasDecls ast) => ast -> HsDecl GhcPs -> TransformT m ast
489+
insertAtStart' old newDecl = do
490+
srcs <- replicateM 5 uniqueSrcSpanT
491+
liftT $ insertAt (insertDeclAtStart srcs) old . noLocA $ newDecl
492+
where
493+
insertDeclAtStart ssps (L _ newDecl) [] = [L (noAnnSrcSpanDP (ssps !! 0) (DifferentLine 1 4)) newDecl]
494+
insertDeclAtStart _ (L _ newDecl) [L (SrcSpanAnn (EpAnn (Anchor dRealSpan (MovedAnchor (SameLine _))) dAnn dComments) dSpan) d] =
495+
[ L (noAnnSrcSpanDP generatedSrcSpan (DifferentLine 1 2)) newDecl,
496+
L (SrcSpanAnn (EpAnn (Anchor dRealSpan (MovedAnchor $ DifferentLine 1 0)) dAnn dComments) dSpan) d
497+
]
498+
insertDeclAtStart ssps (L _ newDecl) (L (SrcSpanAnn (EpAnn (Anchor dRealSpan ancOp) dAnn dComments) dSpan) d:ds) =
499+
let newDeclSpan = ssps !! 0
500+
newDecl' = L
501+
(SrcSpanAnn
502+
(EpAnn (Anchor dRealSpan ancOp) mempty emptyComments)
503+
newDeclSpan)
504+
newDecl
505+
secondDecl' = L
506+
(SrcSpanAnn
507+
(EpAnn
508+
(Anchor (realSrcSpan $ newDeclSpan) (MovedAnchor $ DifferentLine 1 0))
509+
dAnn
510+
dComments)
511+
dSpan)
512+
d
513+
in newDecl' : secondDecl' : ds
514+
insertDeclAtStart _ d ds = d : ds
515+
516+
prependDeclToWhereDecls decl newWhereDecl = do
517+
traceShowM "tag2"
518+
ds <- balanceCommentsList =<< hsDecls decl
519+
traceShowM "tag3"
520+
let ds' = prependDecl (wrapDecl newWhereDecl) ds
521+
traceShowM "tag4"
522+
replaceDecls decl ds'
523+
524+
prependDecl :: LHsDecl GhcPs -> [LHsDecl GhcPs] -> [LHsDecl GhcPs]
525+
prependDecl ldecl = \case
526+
[] -> [setEntryDP ldecl (DifferentLine 1 2)]
527+
ld1:lds -> ldecl':ld1'':lds
528+
where
529+
(ancOp, ld1'') = case ld1 of
530+
L (SrcSpanAnn (EpAnn d1Anc d1Ann (EpaComments (L (Anchor c1Rss cAnc) c1:restCs))) ss) d1 ->
531+
-- NOTE cannot use setEntryDP to simply assign `DL 1 0` here because when there is no prior decl, the
532+
-- DeltaPos on the declaration is absolute instead of relative, and so we must manually update the
533+
-- DeltaPos to be relative (since there is about to be a prior declaration).
534+
let ld1' = L
535+
(SrcSpanAnn
536+
(EpAnn
537+
(setAnchorDp d1Anc $ DifferentLine 1 0)
538+
d1Ann
539+
(EpaCommentsBalanced (L (Anchor c1Rss $ MovedAnchor $ DifferentLine 1 0) c1:restCs) []))
540+
ss)
541+
d1
542+
in (cAnc, ld1')
543+
(L (SrcSpanAnn (EpAnn d1Anc d1Ann (EpaCommentsBalanced (L (Anchor c1Rss cAnc) c1:restCs) d1AfterCs)) ss) d1) ->
544+
-- NOTE cannot use setEntryDP to simply assign `DL 1 0` here because when there is no prior decl, the
545+
-- DeltaPos on the declaration is absolute instead of relative, and so we must manually update the
546+
-- DeltaPos to be relative (since there is about to be a prior declaration).
547+
let ld1' = L
548+
(SrcSpanAnn
549+
(EpAnn
550+
(setAnchorDp d1Anc $ DifferentLine 1 0)
551+
d1Ann
552+
(EpaCommentsBalanced (L (Anchor c1Rss $ MovedAnchor $ DifferentLine 1 0) c1:restCs) d1AfterCs))
553+
ss)
554+
d1
555+
in (cAnc, ld1')
556+
(L (SrcSpanAnn (EpAnn (Anchor d1Rss d1AncOp) d1Ann epaCs@(EpaComments [])) ss) d1) ->
557+
let ld1' = L (SrcSpanAnn (EpAnn (Anchor d1Rss $ MovedAnchor $ DifferentLine 1 0) d1Ann epaCs) ss) d1
558+
in (d1AncOp, ld1')
559+
(L (SrcSpanAnn (EpAnn (Anchor d1Rss d1AncOp) d1Ann epaCs@(EpaCommentsBalanced [] _)) ss) d1) ->
560+
let ld1' = L (SrcSpanAnn (EpAnn (Anchor d1Rss $ MovedAnchor $ DifferentLine 1 0) d1Ann epaCs) ss) d1
561+
in (d1AncOp, ld1')
562+
L (SrcSpanAnn EpAnnNotUsed _) _ -> trace "tag6" error "Unexpected EpAnnNotUsed"
563+
ldecl' = setEntryDP ldecl (maybe (trace "tag7" error "what to do with UnchangedAnchor?") id $ getAnchorOpDp ancOp)
564+
565+
setAnchorDp :: Anchor -> DeltaPos -> Anchor
566+
setAnchorDp (Anchor rss _) dp = Anchor rss (MovedAnchor dp)
567+
568+
getAnchorOpDp :: AnchorOperation -> Maybe DeltaPos
569+
getAnchorOpDp (MovedAnchor dp) = Just dp
570+
getAnchorOpDp UnchangedAnchor = Nothing
478571
#endif
479572

480573
graftSmallestDeclsWithM ::

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

+77-22
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
-- Copyright (c) 2019 The DAML Authors. All rights reserved.
22
-- SPDX-License-Identifier: Apache-2.0
3-
{-# LANGUAGE GADTs #-}
3+
{-# LANGUAGE GADTs #-}
44

55
module Development.IDE.Plugin.CodeAction
66
(
@@ -92,21 +92,27 @@ import qualified Text.Fuzzy.Parallel as TFP
9292
import Text.Regex.TDFA (mrAfter,
9393
(=~), (=~~))
9494
#if MIN_VERSION_ghc(9,2,1)
95+
import GHC (realSrcSpan)
96+
import GHC.Parser.Annotation (emptyComments)
9597
import GHC.Types.SrcLoc (generatedSrcSpan)
96-
import Language.Haskell.GHC.ExactPrint (noAnnSrcSpanDP1,
97-
runTransformT)
98+
import Language.Haskell.GHC.ExactPrint.Transform
9899
#endif
99100
#if MIN_VERSION_ghc(9,2,0)
101+
import Control.Monad.Except (lift)
102+
import Control.Monad.Identity (Identity (..))
100103
import Extra (maybeToEither)
101104
import GHC (AddEpAnn (AddEpAnn),
102-
Anchor (anchor_op),
105+
Anchor (..),
103106
AnchorOperation (..),
104107
AnnsModule (am_main),
105108
DeltaPos (..),
106109
EpAnn (..),
107110
EpaLocation (..),
108111
LEpaComment,
109112
LocatedA)
113+
import Debug.Trace
114+
import Control.Lens (bimap)
115+
110116
#else
111117
import Language.Haskell.GHC.ExactPrint.Types (Annotation (annsDP),
112118
DeltaPos,
@@ -177,7 +183,8 @@ bindingsPluginDescriptor recorder plId = mkExactprintPluginDescriptor recorder $
177183
#endif
178184
, wrap suggestNewDefinition
179185
#if MIN_VERSION_ghc(9,2,1)
180-
, wrap suggestAddArgument
186+
, wrap (undefinedVariableCodeAction addAsLastArgument)
187+
, wrap (undefinedVariableCodeAction addToWhere)
181188
#endif
182189
, wrap suggestDeleteUnusedBinding
183190
]
@@ -950,12 +957,30 @@ newDefinitionAction IdeOptions {..} parsedModule Range {_start} name typ
950957
ParsedModule {pm_parsed_source = L _ HsModule {hsmodDecls}} = parsedModule
951958

952959
#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+
953965
-- When GHC tells us that a variable is not bound, it will tell us either:
954966
-- - there is an unbound variable with a given type
955967
-- - there is an unbound variable (GHC provides no type suggestion)
968+
-- - there is a typed hole `_`
956969
--
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.
959984
--
960985
-- TODO Include logic to also update the type signature of a binding
961986
--
@@ -964,17 +989,8 @@ newDefinitionAction IdeOptions {..} parsedModule Range {_start} name typ
964989
-- foo :: a -> b -> c -> d
965990
-- foo a b = \c -> ...
966991
-- 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 =
978994
do
979995
let addArgToMatch (L locMatch (Match xMatch ctxMatch pats rhs)) = do
980996
let unqualName = mkRdrUnqual $ mkVarOcc $ T.unpack name
@@ -986,17 +1002,56 @@ addArgumentAction (ParsedModule _ parsedSource _ _) range name _typ =
9861002
let decl' = L locDecl (ValD xVal (FunBind xFunBind idFunBind mg' coreFunBind))
9871003
pure [decl']
9881004
decl -> pure [decl]
989-
case runTransformT $ modifySmallestDeclWithM spanContainsRangeOrErr insertArg (makeDeltaAst parsedSource) of
1005+
case runTransformT $ modifySmallestDeclWithM (flip spanContainsRangeOrErr range) insertArg (makeDeltaAst parsedSource) of
9901006
Left err -> Left err
9911007
Right (newSource, _, _) ->
9921008
let diff = makeDiffTextEdit (T.pack $ exactPrint parsedSource) (T.pack $ exactPrint newSource)
9931009
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
9971051

9981052
fromLspList :: List a -> [a]
9991053
fromLspList (List a) = a
1054+
#endif
10001055

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

0 commit comments

Comments
 (0)