11
11
{-# LANGUAGE StandaloneDeriving #-}
12
12
{-# LANGUAGE TypeApplications #-}
13
13
{-# LANGUAGE TypeFamilies #-}
14
+ {-# LANGUAGE ViewPatterns #-}
14
15
15
16
{-# OPTIONS -Wno-orphans #-}
16
17
17
18
module Ide.Plugin.Retrie (descriptor ) where
18
19
19
- import Control.Concurrent.Extra (readVar )
20
20
import Control.Concurrent.STM (readTVarIO )
21
21
import Control.Exception.Safe (Exception (.. ),
22
22
SomeException , catch ,
@@ -29,11 +29,8 @@ import Control.Monad.Trans.Except (ExceptT (ExceptT),
29
29
import Control.Monad.Trans.Maybe
30
30
import Data.Aeson (FromJSON (.. ),
31
31
ToJSON (.. ),
32
- Value (Null ),
33
- genericParseJSON )
34
- import qualified Data.Aeson as Aeson
35
- import Data.Bifunctor (Bifunctor (first ),
36
- second )
32
+ Value (Null ))
33
+ import Data.Bifunctor (second )
37
34
import qualified Data.ByteString as BS
38
35
import Data.Coerce
39
36
import Data.Either (partitionEithers )
@@ -43,44 +40,47 @@ import qualified Data.HashSet as Set
43
40
import Data.IORef.Extra (atomicModifyIORef'_ ,
44
41
newIORef , readIORef )
45
42
import Data.List.Extra (find , nubOrdOn )
46
- import Data.String (IsString ( fromString ) )
43
+ import Data.String (IsString )
47
44
import qualified Data.Text as T
48
45
import qualified Data.Text.Encoding as T
49
46
import Data.Typeable (Typeable )
50
47
import Development.IDE hiding (pluginHandlers )
51
48
import Development.IDE.Core.PositionMapping
52
49
import Development.IDE.Core.Shake (ShakeExtras (knownTargetsVar ),
53
50
toKnownFiles )
54
- import Development.IDE.GHC.Compat (GenLocated (L ), GhcRn ,
51
+ import Development.IDE.GHC.Compat (GenLocated (L ), GhcPs ,
52
+ GhcRn , GhcTc ,
55
53
HsBindLR (FunBind ),
56
54
HsGroup (.. ),
57
55
HsValBindsLR (.. ),
58
56
HscEnv , IdP , LRuleDecls ,
59
57
ModSummary (ModSummary , ms_hspp_buf , ms_mod ),
60
- NHsValBindsLR (.. ),
61
58
Outputable ,
62
59
ParsedModule (.. ),
63
60
RuleDecl (HsRule ),
64
61
RuleDecls (HsRules ),
65
62
SourceText (.. ),
66
- SrcSpan (.. ),
67
63
TyClDecl (SynDecl ),
68
64
TyClGroup (.. ), fun_id ,
69
65
hm_iface , isQual ,
70
- isQual_maybe ,
66
+ isQual_maybe , locA ,
71
67
mi_fixities ,
72
68
moduleNameString ,
69
+ ms_hspp_opts ,
73
70
nameModule_maybe ,
74
- nameRdrName , occNameFS ,
75
- occNameString ,
76
- parseModule ,
71
+ nameRdrName , noLocA ,
72
+ occNameFS , occNameString ,
77
73
pattern IsBoot ,
78
74
pattern NotBoot ,
79
75
pattern RealSrcSpan ,
76
+ pm_parsed_source ,
80
77
rdrNameOcc , rds_rules ,
81
- srcSpanFile )
78
+ srcSpanFile , topDir ,
79
+ unLocA )
82
80
import Development.IDE.GHC.Compat.Util hiding (catch , try )
83
- import qualified GHC (parseModule )
81
+ import qualified GHC (Module ,
82
+ ParsedModule (.. ),
83
+ moduleName , parseModule )
84
84
import GHC.Generics (Generic )
85
85
import Ide.PluginUtils
86
86
import Ide.Types
@@ -94,8 +94,13 @@ import Language.LSP.Types as J hiding
94
94
SemanticTokenRelative (length ),
95
95
SemanticTokensEdit (_start ))
96
96
import Retrie.CPP (CPP (NoCPP ), parseCPP )
97
- import Retrie.ExactPrint (fix , relativiseApiAnns ,
97
+ import Retrie.ExactPrint (Annotated , fix ,
98
98
transformA , unsafeMkA )
99
+ #if MIN_VERSION_ghc(9,2,0)
100
+ import Retrie.ExactPrint (makeDeltaAst )
101
+ #else
102
+ import Retrie.ExactPrint (relativiseApiAnns )
103
+ #endif
99
104
import Retrie.Fixity (mkFixityEnv )
100
105
import qualified Retrie.GHC as GHC
101
106
import Retrie.Monad (addImports , apply ,
@@ -202,7 +207,7 @@ provider state plId (CodeActionParams _ _ (TextDocumentIdentifier uri) range ca)
202
207
++ concatMap (suggestRuleRewrites uri pos ms_mod) hs_ruleds
203
208
++ [ r
204
209
| TyClGroup {group_tyclds} <- hs_tyclds,
205
- L l g <- group_tyclds,
210
+ L (locA -> l) g <- group_tyclds,
206
211
pos `isInsideSrcSpan` l,
207
212
r <- suggestTypeRewrites uri ms_mod g
208
213
@@ -225,7 +230,7 @@ getBinds nfp = runMaybeT $ do
225
230
( HsGroup
226
231
{ hs_valds =
227
232
XValBindsLR
228
- (NValBinds binds _sigs :: NHsValBindsLR GHC. GhcRn ),
233
+ (GHC. NValBinds binds _sigs :: GHC. NHsValBindsLR GhcRn ),
229
234
hs_ruleds,
230
235
hs_tyclds
231
236
},
@@ -247,7 +252,7 @@ suggestBindRewrites ::
247
252
GHC. Module ->
248
253
HsBindLR GhcRn GhcRn ->
249
254
[(T. Text , CodeActionKind , RunRetrieParams )]
250
- suggestBindRewrites originatingFile pos ms_mod FunBind {fun_id = L l' rdrName}
255
+ suggestBindRewrites originatingFile pos ms_mod FunBind {fun_id = L (locA -> l') rdrName}
251
256
| pos `isInsideSrcSpan` l' =
252
257
let pprNameText = printOutputable rdrName
253
258
pprName = T. unpack pprNameText
@@ -267,13 +272,13 @@ describeRestriction restrictToOriginatingFile =
267
272
if restrictToOriginatingFile then " in current file" else " "
268
273
269
274
suggestTypeRewrites ::
270
- (Outputable (IdP pass )) =>
275
+ (Outputable (IdP GhcRn )) =>
271
276
Uri ->
272
277
GHC. Module ->
273
- TyClDecl pass ->
278
+ TyClDecl GhcRn ->
274
279
[(T. Text , CodeActionKind , RunRetrieParams )]
275
- suggestTypeRewrites originatingFile ms_mod SynDecl {tcdLName = L _ rdrName } =
276
- let pprNameText = printOutputable rdrName
280
+ suggestTypeRewrites originatingFile ms_mod SynDecl {tcdLName} =
281
+ let pprNameText = printOutputable (unLocA tcdLName)
277
282
pprName = T. unpack pprNameText
278
283
unfoldRewrite restrictToOriginatingFile =
279
284
let rewrites = [TypeForward (qualify ms_mod pprName)]
@@ -290,7 +295,7 @@ suggestRuleRewrites ::
290
295
Uri ->
291
296
Position ->
292
297
GHC. Module ->
293
- LRuleDecls pass ->
298
+ LRuleDecls GhcRn ->
294
299
[(T. Text , CodeActionKind , RunRetrieParams )]
295
300
suggestRuleRewrites originatingFile pos ms_mod (L _ HsRules {rds_rules}) =
296
301
concat
@@ -299,7 +304,7 @@ suggestRuleRewrites originatingFile pos ms_mod (L _ HsRules {rds_rules}) =
299
304
, backwardsRewrite ruleName True
300
305
, backwardsRewrite ruleName False
301
306
]
302
- | L l r <- rds_rules,
307
+ | L (locA -> l) r <- rds_rules,
303
308
pos `isInsideSrcSpan` l,
304
309
#if MIN_VERSION_ghc(8,8,0)
305
310
let HsRule {rd_name = L _ (_, rn)} = r,
@@ -326,7 +331,6 @@ suggestRuleRewrites originatingFile pos ms_mod (L _ HsRules {rds_rules}) =
326
331
CodeActionRefactor ,
327
332
RunRetrieParams {.. }
328
333
)
329
-
330
334
suggestRuleRewrites _ _ _ _ = []
331
335
332
336
qualify :: GHC. Module -> String -> String
@@ -359,24 +363,26 @@ callRetrie ::
359
363
IO ([CallRetrieError ], WorkspaceEdit )
360
364
callRetrie state session rewrites origin restrictToOriginatingFile = do
361
365
knownFiles <- toKnownFiles . unhashed <$> readTVarIO (knownTargetsVar $ shakeExtras state)
366
+ #if MIN_VERSION_ghc(9,2,0)
367
+ -- retrie needs the libdir for `parseRewriteSpecs`
368
+ libdir <- topDir . ms_hspp_opts . msrModSummary <$> useOrFail " Retrie.GetModSummary" (CallRetrieInternalError " file not found" ) GetModSummary origin
369
+ #endif
362
370
let reuseParsedModule f = do
363
- pm <-
364
- useOrFail " GetParsedModule" NoParse GetParsedModule f
365
- (fixities, pm) <- fixFixities f (fixAnns pm)
366
- return (fixities, pm)
371
+ pm <- useOrFail " Retrie.GetParsedModule" NoParse GetParsedModule f
372
+ (fixities, pm') <- fixFixities f (fixAnns pm)
373
+ return (fixities, pm')
367
374
getCPPmodule t = do
368
375
nt <- toNormalizedFilePath' <$> makeAbsolute t
369
376
let getParsedModule f contents = do
370
377
modSummary <- msrModSummary <$>
371
- useOrFail " GetModSummary" (CallRetrieInternalError " file not found" ) GetModSummary nt
378
+ useOrFail " Retrie. GetModSummary" (CallRetrieInternalError " file not found" ) GetModSummary nt
372
379
let ms' =
373
380
modSummary
374
381
{ ms_hspp_buf =
375
382
Just (stringToStringBuffer contents)
376
383
}
377
384
logPriority (ideLogger state) Info $ T. pack $ " Parsing module: " <> t
378
- parsed <-
379
- evalGhcEnv session (GHC. parseModule ms')
385
+ parsed <- evalGhcEnv session (GHC. parseModule ms')
380
386
`catch` \ e -> throwIO (GHCParseError nt (show @ SomeException e))
381
387
(fixities, parsed) <- fixFixities f (fixAnns parsed)
382
388
return (fixities, parsed)
@@ -416,12 +422,19 @@ callRetrie state session rewrites origin restrictToOriginatingFile = do
416
422
(theImports, theRewrites) = partitionEithers rewrites
417
423
418
424
annotatedImports =
419
- unsafeMkA (map (GHC. noLoc . toImportDecl) theImports) mempty 0
425
+ #if MIN_VERSION_ghc(9,2,0)
426
+ unsafeMkA (map (noLocA . toImportDecl) theImports) 0
427
+ #else
428
+ unsafeMkA (map (noLocA . toImportDecl) theImports) mempty 0
429
+ #endif
420
430
421
431
(originFixities, originParsedModule) <- reuseParsedModule origin
422
432
retrie <-
423
433
(\ specs -> apply specs >> addImports annotatedImports)
424
434
<$> parseRewriteSpecs
435
+ #if MIN_VERSION_ghc(9,2,0)
436
+ libdir
437
+ #endif
425
438
(\ _f -> return $ NoCPP originParsedModule)
426
439
originFixities
427
440
theRewrites
@@ -463,9 +476,13 @@ callRetrie state session rewrites origin restrictToOriginatingFile = do
463
476
let fixities = fixityEnvFromModIface hirModIface
464
477
res <- transformA pm (fix fixities)
465
478
return (fixities, res)
466
- fixAnns ParsedModule {.. } =
479
+ #if MIN_VERSION_ghc(9,2,0)
480
+ fixAnns GHC. ParsedModule {pm_parsed_source} = unsafeMkA (makeDeltaAst pm_parsed_source) 0
481
+ #else
482
+ fixAnns GHC. ParsedModule {.. } =
467
483
let ranns = relativiseApiAnns pm_parsed_source pm_annotations
468
484
in unsafeMkA pm_parsed_source ranns 0
485
+ #endif
469
486
470
487
asEditMap :: [[(Uri , TextEdit )]] -> WorkspaceEditMap
471
488
asEditMap = coerce . HM. fromListWith (++) . concatMap (map (second pure ))
@@ -533,14 +550,18 @@ toImportDecl :: ImportSpec -> GHC.ImportDecl GHC.GhcPs
533
550
toImportDecl AddImport {.. } = GHC. ImportDecl {ideclSource = ideclSource', .. }
534
551
where
535
552
ideclSource' = if ideclSource then IsBoot else NotBoot
536
- toMod = GHC. noLoc . GHC. mkModuleName
553
+ toMod = noLocA . GHC. mkModuleName
537
554
ideclName = toMod ideclNameString
538
555
ideclPkgQual = Nothing
539
556
ideclSafe = False
540
557
ideclImplicit = False
541
558
ideclHiding = Nothing
542
559
ideclSourceSrc = NoSourceText
560
+ #if MIN_VERSION_ghc(9,2,0)
561
+ ideclExt = GHC. EpAnnNotUsed
562
+ #else
543
563
ideclExt = GHC. noExtField
564
+ #endif
544
565
ideclAs = toMod <$> ideclAsString
545
566
#if MIN_VERSION_ghc(8,10,0)
546
567
ideclQualified = if ideclQualifiedBool then GHC. QualifiedPre else GHC. NotQualified
0 commit comments