Skip to content

Commit 7d605b2

Browse files
committed
Cache annotated AST
1 parent 4b0e456 commit 7d605b2

File tree

3 files changed

+37
-9
lines changed

3 files changed

+37
-9
lines changed

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

Lines changed: 26 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@
33
{-# LANGUAGE GADTs #-}
44
{-# LANGUAGE OverloadedStrings #-}
55
{-# LANGUAGE RankNTypes #-}
6+
{-# LANGUAGE TypeFamilies #-}
67

78
module Development.IDE.GHC.ExactPrint
89
( Graft(..),
@@ -16,8 +17,11 @@ module Development.IDE.GHC.ExactPrint
1617
transformM,
1718
useAnnotatedSource,
1819
annotateParsedSource,
20+
getAnnotatedParsedSourceRule,
21+
GetAnnotatedParsedSource(..),
1922
ASTElement (..),
2023
ExceptStringT (..),
24+
Annotated(..),
2125
)
2226
where
2327

@@ -39,6 +43,9 @@ import Development.IDE.Core.Rules
3943
import Development.IDE.Core.Shake
4044
import Development.IDE.GHC.Compat hiding (parseExpr)
4145
import Development.IDE.Types.Location
46+
import Development.Shake (RuleResult, Rules)
47+
import Development.Shake.Classes
48+
import qualified GHC.Generics as GHC
4249
import Generics.SYB
4350
import Ide.PluginUtils
4451
import Language.Haskell.GHC.ExactPrint
@@ -54,19 +61,30 @@ import Control.Arrow
5461

5562
------------------------------------------------------------------------------
5663

64+
data GetAnnotatedParsedSource = GetAnnotatedParsedSource
65+
deriving (Eq, Show, Typeable, GHC.Generic)
66+
67+
instance Hashable GetAnnotatedParsedSource
68+
instance NFData GetAnnotatedParsedSource
69+
instance Binary GetAnnotatedParsedSource
70+
type instance RuleResult GetAnnotatedParsedSource = Annotated ParsedSource
71+
5772
-- | 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)
73+
getAnnotatedParsedSourceRule :: Rules ()
74+
getAnnotatedParsedSourceRule = define $ \GetAnnotatedParsedSource nfp -> do
75+
pm <- use GetParsedModule nfp
76+
return ([], fmap annotateParsedSource pm)
6677

6778
annotateParsedSource :: ParsedModule -> Annotated ParsedSource
6879
annotateParsedSource = fixAnns
6980

81+
useAnnotatedSource ::
82+
String ->
83+
IdeState ->
84+
NormalizedFilePath ->
85+
IO (Maybe (Annotated ParsedSource))
86+
useAnnotatedSource herald state nfp =
87+
runAction herald state (use GetAnnotatedParsedSource nfp)
7088
------------------------------------------------------------------------------
7189

7290
{- | A transformation for grafting source trees together. Use the semigroup

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

Lines changed: 7 additions & 0 deletions
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

ghcide/src/Development/IDE/Plugin/CodeAction.hs

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -30,6 +30,7 @@ import Development.IDE.Core.RuleTypes
3030
import Development.IDE.Core.Service
3131
import Development.IDE.Core.Shake
3232
import Development.IDE.GHC.Error
33+
import Development.IDE.GHC.ExactPrint
3334
import Development.IDE.LSP.Server
3435
import Development.IDE.Plugin.CodeAction.PositionIndexed
3536
import Development.IDE.Plugin.CodeAction.RuleTypes
@@ -66,7 +67,9 @@ plugin :: Plugin c
6667
plugin = codeActionPluginWithRules rules codeAction <> Plugin mempty setHandlersCodeLens
6768

6869
rules :: Rules ()
69-
rules = rulePackageExports
70+
rules = do
71+
rulePackageExports
72+
getAnnotatedParsedSourceRule
7073

7174
-- | a command that blocks forever. Used for testing
7275
blockCommandId :: T.Text

0 commit comments

Comments
 (0)