15
15
{-# LANGUAGE TypeApplications #-}
16
16
{-# LANGUAGE TypeFamilies #-}
17
17
{-# LANGUAGE ViewPatterns #-}
18
+ {-# LANGUAGE PatternSynonyms #-}
18
19
{-# LANGUAGE MultiParamTypeClasses #-}
19
20
{-# LANGUAGE FlexibleInstances #-}
20
21
@@ -51,15 +52,17 @@ import Development.IDE.GHC.Compat.ExactPrint
51
52
import qualified Development.IDE.GHC.Compat.Util as Util
52
53
import Development.IDE.GHC.ExactPrint
53
54
import GHC.Exts
55
+ #if __GLASGOW_HASKELL__ >= 902
56
+ import GHC.Parser.Annotation (SrcSpanAnn' (.. ))
57
+ import qualified GHC.Types.Error as Error
58
+ #endif
54
59
import Ide.Plugin.Splice.Types
55
60
import Ide.Types
56
61
import Language.Haskell.GHC.ExactPrint (uniqueSrcSpanT )
57
62
import Language.LSP.Server
58
63
import Language.LSP.Types
59
64
import Language.LSP.Types.Capabilities
60
65
import qualified Language.LSP.Types.Lens as J
61
- import GHC.Hs (SrcSpanAnn' (.. ))
62
- import qualified GHC.Types.Error as Error
63
66
64
67
descriptor :: PluginId -> PluginDescriptor IdeState
65
68
descriptor plId =
@@ -264,11 +267,23 @@ adjustToRange uri ran (WorkspaceEdit mhult mlt x) =
264
267
J. range %~ \ r ->
265
268
if r == bad then ran else bad
266
269
270
+ -- Define a pattern to get hold of a `SrcSpan` from the location part of a
271
+ -- `GenLocated`. In GHC >= 9.2 this will be a SrcSpanAnn', with annotations;
272
+ -- earlier it will just be a plain `SrcSpan`.
273
+ {-# COMPLETE AsSrcSpan #-}
274
+ #if __GLASGOW_HASKELL__ >= 902
275
+ pattern AsSrcSpan :: SrcSpan -> SrcSpanAnn' a
276
+ pattern AsSrcSpan locA <- SrcSpanAnn {locA}
277
+ #else
278
+ pattern AsSrcSpan :: SrcSpan -> SrcSpan
279
+ pattern AsSrcSpan loc <- loc
280
+ #endif
281
+
267
282
findSubSpansDesc :: SrcSpan -> [(LHsExpr GhcTc , a )] -> [(SrcSpan , a )]
268
283
findSubSpansDesc srcSpan =
269
284
sortOn (Down . SubSpan . fst )
270
285
. mapMaybe
271
- ( \ (L (SrcSpanAnn {locA = spn} ) _, e) -> do
286
+ ( \ (L (AsSrcSpan spn) _, e) -> do
272
287
guard (spn `isSubspanOf` srcSpan)
273
288
pure (spn, e)
274
289
)
@@ -354,11 +369,11 @@ manualCalcEdit clientCapabilities reportEditor ran ps hscEnv typechkd srcSpan _e
354
369
Right y -> unRenamedE dflags y
355
370
_ -> pure Nothing
356
371
let (warns, errs) =
357
- # if __GLASGOW_HASKELL__ >= 902
372
+ #if __GLASGOW_HASKELL__ >= 902
358
373
(Error. getWarningMessages msgs, Error. getErrorMessages msgs)
359
- # else
374
+ #else
360
375
msgs
361
- # endif
376
+ #endif
362
377
pure $ (warns,) <$> fromMaybe (Left $ show errs) eresl
363
378
364
379
unless
@@ -382,9 +397,15 @@ unRenamedE ::
382
397
TransformT m (LocatedAn l (ast GhcPs ))
383
398
unRenamedE dflags expr = do
384
399
uniq <- show <$> uniqueSrcSpanT
385
- either (fail . show ) pure $
400
+ #if __GLASGOW_HASKELL__ >= 902
401
+ expr' <-
402
+ #else
403
+ (_anns, expr') <-
404
+ #endif
405
+ either (fail . show ) pure $
386
406
parseAST @ _ @ (ast GhcPs ) dflags uniq $
387
407
showSDoc dflags $ ppr expr
408
+ pure expr'
388
409
389
410
data SearchResult r =
390
411
Continue | Stop | Here r
@@ -428,7 +449,7 @@ codeAction state plId (CodeActionParams _ _ docId ran _) = liftIO $
428
449
mkQ
429
450
Continue
430
451
( \ case
431
- (L (SrcSpanAnn {locA = l@ (RealSrcSpan spLoc _)} ) expr :: LHsExpr GhcPs )
452
+ (L (AsSrcSpan l@ (RealSrcSpan spLoc _)) expr :: LHsExpr GhcPs )
432
453
| spanIsRelevant l ->
433
454
case expr of
434
455
HsSpliceE {} -> Here (spLoc, Expr )
@@ -439,22 +460,22 @@ codeAction state plId (CodeActionParams _ _ docId ran _) = liftIO $
439
460
#if __GLASGOW_HASKELL__ == 808
440
461
(dL @ (Pat GhcPs ) -> L l@ (RealSrcSpan spLoc _) pat :: Located (Pat GhcPs ))
441
462
#else
442
- (L (SrcSpanAnn {locA = l@ (RealSrcSpan spLoc _)} ) pat :: LPat GhcPs )
463
+ (L (AsSrcSpan l@ (RealSrcSpan spLoc _)) pat :: LPat GhcPs )
443
464
#endif
444
465
| spanIsRelevant l ->
445
466
case pat of
446
467
SplicePat {} -> Here (spLoc, Pat )
447
468
_ -> Continue
448
469
_ -> Stop
449
470
`extQ` \ case
450
- (L (SrcSpanAnn {locA = l@ (RealSrcSpan spLoc _)} ) ty :: LHsType GhcPs )
471
+ (L (AsSrcSpan l@ (RealSrcSpan spLoc _)) ty :: LHsType GhcPs )
451
472
| spanIsRelevant l ->
452
473
case ty of
453
474
HsSpliceTy {} -> Here (spLoc, HsType )
454
475
_ -> Continue
455
476
_ -> Stop
456
477
`extQ` \ case
457
- (L (SrcSpanAnn {locA = l@ (RealSrcSpan spLoc _)} ) decl :: LHsDecl GhcPs )
478
+ (L (AsSrcSpan l@ (RealSrcSpan spLoc _)) decl :: LHsDecl GhcPs )
458
479
| spanIsRelevant l ->
459
480
case decl of
460
481
SpliceD {} -> Here (spLoc, HsDecl )
0 commit comments