Skip to content

Commit 24137cd

Browse files
committed
Add back-compat for GHC 9.0
1 parent f811c7f commit 24137cd

File tree

2 files changed

+43
-12
lines changed

2 files changed

+43
-12
lines changed

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

Lines changed: 11 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -476,7 +476,17 @@ graftDeclsWithM dst toDecls = Graft $ \dflags a -> do
476476
modifyDeclsT (fmap DL.toList . go) a
477477

478478

479-
class (Data ast, Default l, Typeable l, Outputable l, Outputable ast) => ASTElement l ast | ast -> l where
479+
-- In 9.2+, we need `Default l` to do `setPrecedingLines` on annotated elements.
480+
-- In older versions, we pass around annotations explicitly, so the instance isn't needed.
481+
class
482+
( Data ast
483+
, Typeable l
484+
, Outputable l
485+
, Outputable ast
486+
#if MIN_VERSION_ghc(9,2,0)
487+
, Default l
488+
#endif
489+
) => ASTElement l ast | ast -> l where
480490
parseAST :: Parser (LocatedAn l ast)
481491
maybeParensAST :: LocatedAn l ast -> LocatedAn l ast
482492
{- | Construct a 'Graft', replacing the node at the given 'SrcSpan' with

plugins/hls-splice-plugin/src/Ide/Plugin/Splice.hs

Lines changed: 32 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -15,6 +15,7 @@
1515
{-# LANGUAGE TypeApplications #-}
1616
{-# LANGUAGE TypeFamilies #-}
1717
{-# LANGUAGE ViewPatterns #-}
18+
{-# LANGUAGE PatternSynonyms #-}
1819
{-# LANGUAGE MultiParamTypeClasses #-}
1920
{-# LANGUAGE FlexibleInstances #-}
2021

@@ -51,15 +52,17 @@ import Development.IDE.GHC.Compat.ExactPrint
5152
import qualified Development.IDE.GHC.Compat.Util as Util
5253
import Development.IDE.GHC.ExactPrint
5354
import GHC.Exts
55+
#if __GLASGOW_HASKELL__ >= 902
56+
import GHC.Parser.Annotation (SrcSpanAnn'(..))
57+
import qualified GHC.Types.Error as Error
58+
#endif
5459
import Ide.Plugin.Splice.Types
5560
import Ide.Types
5661
import Language.Haskell.GHC.ExactPrint (uniqueSrcSpanT)
5762
import Language.LSP.Server
5863
import Language.LSP.Types
5964
import Language.LSP.Types.Capabilities
6065
import qualified Language.LSP.Types.Lens as J
61-
import GHC.Hs (SrcSpanAnn'(..))
62-
import qualified GHC.Types.Error as Error
6366

6467
descriptor :: PluginId -> PluginDescriptor IdeState
6568
descriptor plId =
@@ -264,11 +267,23 @@ adjustToRange uri ran (WorkspaceEdit mhult mlt x) =
264267
J.range %~ \r ->
265268
if r == bad then ran else bad
266269

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+
267282
findSubSpansDesc :: SrcSpan -> [(LHsExpr GhcTc, a)] -> [(SrcSpan, a)]
268283
findSubSpansDesc srcSpan =
269284
sortOn (Down . SubSpan . fst)
270285
. mapMaybe
271-
( \(L (SrcSpanAnn {locA = spn}) _, e) -> do
286+
( \(L (AsSrcSpan spn) _, e) -> do
272287
guard (spn `isSubspanOf` srcSpan)
273288
pure (spn, e)
274289
)
@@ -354,11 +369,11 @@ manualCalcEdit clientCapabilities reportEditor ran ps hscEnv typechkd srcSpan _e
354369
Right y -> unRenamedE dflags y
355370
_ -> pure Nothing
356371
let (warns, errs) =
357-
#if __GLASGOW_HASKELL__ >= 902
372+
#if __GLASGOW_HASKELL__ >= 902
358373
(Error.getWarningMessages msgs, Error.getErrorMessages msgs)
359-
#else
374+
#else
360375
msgs
361-
#endif
376+
#endif
362377
pure $ (warns,) <$> fromMaybe (Left $ show errs) eresl
363378

364379
unless
@@ -382,9 +397,15 @@ unRenamedE ::
382397
TransformT m (LocatedAn l (ast GhcPs))
383398
unRenamedE dflags expr = do
384399
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 $
386406
parseAST @_ @(ast GhcPs) dflags uniq $
387407
showSDoc dflags $ ppr expr
408+
pure expr'
388409

389410
data SearchResult r =
390411
Continue | Stop | Here r
@@ -428,7 +449,7 @@ codeAction state plId (CodeActionParams _ _ docId ran _) = liftIO $
428449
mkQ
429450
Continue
430451
( \case
431-
(L (SrcSpanAnn {locA = l@(RealSrcSpan spLoc _)}) expr :: LHsExpr GhcPs)
452+
(L (AsSrcSpan l@(RealSrcSpan spLoc _)) expr :: LHsExpr GhcPs)
432453
| spanIsRelevant l ->
433454
case expr of
434455
HsSpliceE {} -> Here (spLoc, Expr)
@@ -439,22 +460,22 @@ codeAction state plId (CodeActionParams _ _ docId ran _) = liftIO $
439460
#if __GLASGOW_HASKELL__ == 808
440461
(dL @(Pat GhcPs) -> L l@(RealSrcSpan spLoc _) pat :: Located (Pat GhcPs))
441462
#else
442-
(L (SrcSpanAnn {locA = l@(RealSrcSpan spLoc _)}) pat :: LPat GhcPs)
463+
(L (AsSrcSpan l@(RealSrcSpan spLoc _)) pat :: LPat GhcPs)
443464
#endif
444465
| spanIsRelevant l ->
445466
case pat of
446467
SplicePat{} -> Here (spLoc, Pat)
447468
_ -> Continue
448469
_ -> Stop
449470
`extQ` \case
450-
(L (SrcSpanAnn {locA = l@(RealSrcSpan spLoc _)}) ty :: LHsType GhcPs)
471+
(L (AsSrcSpan l@(RealSrcSpan spLoc _)) ty :: LHsType GhcPs)
451472
| spanIsRelevant l ->
452473
case ty of
453474
HsSpliceTy {} -> Here (spLoc, HsType)
454475
_ -> Continue
455476
_ -> Stop
456477
`extQ` \case
457-
(L (SrcSpanAnn {locA = l@(RealSrcSpan spLoc _)}) decl :: LHsDecl GhcPs)
478+
(L (AsSrcSpan l@(RealSrcSpan spLoc _)) decl :: LHsDecl GhcPs)
458479
| spanIsRelevant l ->
459480
case decl of
460481
SpliceD {} -> Here (spLoc, HsDecl)

0 commit comments

Comments
 (0)