Skip to content

Commit 0403dbf

Browse files
Use exact print for suggest missing constraint code actions (#1221)
* Cache annotated AST * instance ASTElement RdrName * appendConstraint + Rewrite abstraction The Rewrite abstraction is similar to D.IDE.GHC.ExactPrint.Graft but it does fewer things more efficiently: - It doesn't annotate things for you (so it doesn't destroy user format) - It doesn't provide a Monoid instance (for now) - It doesn't need a fully parsed source - It doesn't use SYB to perform the replacement - It doesn't diff to compute the result The use case is code actions where you don't have the SrcSpan that you need to edit at hand, and instead you need to traverse the AST manually to locate the declaration to edit * Refactor suggest constraint code action to use exactprint Tweaking the suggest constraints tests to reflect the increased precision in whitespace preservation * Catch missing 'Monad m' constraints too * Suggestions for missing implicit parameters * hlints * compat * Include getAnnotatedParsedSourceRule in the main rule Co-authored-by: mergify[bot] <37929162+mergify[bot]@users.noreply.github.com>
1 parent 6f105bd commit 0403dbf

File tree

7 files changed

+417
-140
lines changed

7 files changed

+417
-140
lines changed

ghcide/ghcide.cabal

+1
Original file line numberDiff line numberDiff line change
@@ -169,6 +169,7 @@ library
169169
Development.IDE.Plugin
170170
Development.IDE.Plugin.Completions
171171
Development.IDE.Plugin.CodeAction
172+
Development.IDE.Plugin.CodeAction.ExactPrint
172173
Development.IDE.Plugin.HLS
173174
Development.IDE.Plugin.HLS.GhcIde
174175
Development.IDE.Plugin.Test

ghcide/src/Development/IDE/Core/Rules.hs

+2
Original file line numberDiff line numberDiff line change
@@ -79,6 +79,7 @@ import Development.IDE.Core.FileStore (modificationTime, getFil
7979
import Development.IDE.Types.Diagnostics as Diag
8080
import Development.IDE.Types.Location
8181
import Development.IDE.GHC.Compat hiding (parseModule, typecheckModule, writeHieFile, TargetModule, TargetFile)
82+
import Development.IDE.GHC.ExactPrint
8283
import Development.IDE.GHC.Util
8384
import Data.Either.Extra
8485
import qualified Development.IDE.Types.Logger as L
@@ -1020,6 +1021,7 @@ mainRule = do
10201021
needsCompilationRule
10211022
generateCoreRule
10221023
getImportMapRule
1024+
getAnnotatedParsedSourceRule
10231025

10241026
-- | Given the path to a module src file, this rule returns True if the
10251027
-- corresponding `.hi` file is stable, that is, if it is newer

ghcide/src/Development/IDE/GHC/ExactPrint.hs

+37-9
Original file line numberDiff line numberDiff line change
@@ -3,21 +3,29 @@
33
{-# LANGUAGE GADTs #-}
44
{-# LANGUAGE OverloadedStrings #-}
55
{-# LANGUAGE RankNTypes #-}
6+
{-# LANGUAGE TypeFamilies #-}
67

78
module Development.IDE.GHC.ExactPrint
89
( Graft(..),
910
graft,
1011
graftDecls,
1112
graftDeclsWithM,
13+
annotate,
1214
hoistGraft,
1315
graftWithM,
1416
graftWithSmallestM,
1517
transform,
1618
transformM,
1719
useAnnotatedSource,
1820
annotateParsedSource,
21+
getAnnotatedParsedSourceRule,
22+
GetAnnotatedParsedSource(..),
1923
ASTElement (..),
2024
ExceptStringT (..),
25+
Annotated(..),
26+
TransformT,
27+
Anns,
28+
Annotate,
2129
)
2230
where
2331

@@ -35,10 +43,13 @@ import Data.Functor.Classes
3543
import Data.Functor.Contravariant
3644
import qualified Data.Text as T
3745
import Development.IDE.Core.RuleTypes
38-
import Development.IDE.Core.Rules
46+
import Development.IDE.Core.Service (runAction)
3947
import Development.IDE.Core.Shake
4048
import Development.IDE.GHC.Compat hiding (parseExpr)
4149
import Development.IDE.Types.Location
50+
import Development.Shake (RuleResult, Rules)
51+
import Development.Shake.Classes
52+
import qualified GHC.Generics as GHC
4253
import Generics.SYB
4354
import Ide.PluginUtils
4455
import Language.Haskell.GHC.ExactPrint
@@ -47,26 +58,38 @@ import Language.Haskell.LSP.Types
4758
import Language.Haskell.LSP.Types.Capabilities (ClientCapabilities)
4859
import Outputable (Outputable, ppr, showSDoc)
4960
import Retrie.ExactPrint hiding (parseDecl, parseExpr, parsePattern, parseType)
61+
import Parser (parseIdentifier)
5062
#if __GLASGOW_HASKELL__ == 808
5163
import Control.Arrow
5264
#endif
5365

5466

5567
------------------------------------------------------------------------------
5668

69+
data GetAnnotatedParsedSource = GetAnnotatedParsedSource
70+
deriving (Eq, Show, Typeable, GHC.Generic)
71+
72+
instance Hashable GetAnnotatedParsedSource
73+
instance NFData GetAnnotatedParsedSource
74+
instance Binary GetAnnotatedParsedSource
75+
type instance RuleResult GetAnnotatedParsedSource = Annotated ParsedSource
76+
5777
-- | Get the latest version of the annotated parse source.
58-
useAnnotatedSource ::
59-
String ->
60-
IdeState ->
61-
NormalizedFilePath ->
62-
IO (Maybe (Annotated ParsedSource))
63-
useAnnotatedSource herald state nfp =
64-
fmap annotateParsedSource
65-
<$> runAction herald state (use GetParsedModule nfp)
78+
getAnnotatedParsedSourceRule :: Rules ()
79+
getAnnotatedParsedSourceRule = define $ \GetAnnotatedParsedSource nfp -> do
80+
pm <- use GetParsedModule nfp
81+
return ([], fmap annotateParsedSource pm)
6682

6783
annotateParsedSource :: ParsedModule -> Annotated ParsedSource
6884
annotateParsedSource = fixAnns
6985

86+
useAnnotatedSource ::
87+
String ->
88+
IdeState ->
89+
NormalizedFilePath ->
90+
IO (Maybe (Annotated ParsedSource))
91+
useAnnotatedSource herald state nfp =
92+
runAction herald state (use GetAnnotatedParsedSource nfp)
7093
------------------------------------------------------------------------------
7194

7295
{- | A transformation for grafting source trees together. Use the semigroup
@@ -291,6 +314,10 @@ instance p ~ GhcPs => ASTElement (HsDecl p) where
291314
parseAST = parseDecl
292315
maybeParensAST = id
293316

317+
instance ASTElement RdrName where
318+
parseAST df fp = parseWith df fp parseIdentifier
319+
maybeParensAST = id
320+
294321
------------------------------------------------------------------------------
295322

296323
-- | Dark magic I stole from retrie. No idea what it does.
@@ -302,6 +329,7 @@ fixAnns ParsedModule {..} =
302329
------------------------------------------------------------------------------
303330

304331
-- | Given an 'LHSExpr', compute its exactprint annotations.
332+
-- Note that this function will throw away any existing annotations (and format)
305333
annotate :: ASTElement ast => DynFlags -> Located ast -> TransformT (Either String) (Anns, Located ast)
306334
annotate dflags ast = do
307335
uniq <- show <$> uniqueSrcSpanT

ghcide/src/Development/IDE/GHC/Orphans.hs

+7
Original file line numberDiff line numberDiff line change
@@ -21,6 +21,7 @@ import GhcPlugins
2121
import qualified StringBuffer as SB
2222
import Data.Text (Text)
2323
import Data.String (IsString(fromString))
24+
import Retrie.ExactPrint (Annotated)
2425

2526

2627
-- Orphan instances for types from the GHC API.
@@ -144,3 +145,9 @@ instance NFData ModGuts where
144145

145146
instance NFData (ImportDecl GhcPs) where
146147
rnf = rwhnf
148+
149+
instance Show (Annotated ParsedSource) where
150+
show _ = "<Annotated ParsedSource>"
151+
152+
instance NFData (Annotated ParsedSource) where
153+
rnf = rwhnf

0 commit comments

Comments
 (0)