77{-# OPTIONS_GHC -Wno-overlapping -patterns #-}
88module Ide.Plugin.GHC where
99
10+ #if !MIN_VERSION_ghc(9,11,0)
1011import Data.Functor ((<&>) )
12+ #endif
1113import Data.List.Extra (stripInfix )
1214import qualified Data.Text as T
1315import Development.IDE
1416import Development.IDE.GHC.Compat
1517import Development.IDE.GHC.Compat.ExactPrint
16- import GHC.Parser.Annotation (AddEpAnn (.. ),
17- DeltaPos (.. ),
18+ import GHC.Parser.Annotation (DeltaPos (.. ),
1819 EpAnn (.. ),
1920 EpAnnComments (EpaComments ))
2021import Ide.PluginUtils (subRange )
@@ -44,6 +45,11 @@ import GHC.Parser.Annotation (EpUniToken (..),
4445import Language.Haskell.GHC.ExactPrint.Utils (showAst )
4546#endif
4647
48+ #if MIN_VERSION_ghc(9,11,0)
49+ import GHC.Types.SrcLoc (UnhelpfulSpanReason (.. ))
50+ #else
51+ import GHC.Parser.Annotation (AddEpAnn (.. ))
52+ #endif
4753
4854type GP = GhcPass Parsed
4955
@@ -97,7 +103,9 @@ h98ToGADTConDecl ::
97103h98ToGADTConDecl dataName tyVars ctxt = \ case
98104 ConDeclH98 {.. } ->
99105 ConDeclGADT
100- #if MIN_VERSION_ghc(9,9,0)
106+ #if MIN_VERSION_ghc(9,11,0)
107+ (AnnConDeclGADT [] [] NoEpUniTok )
108+ #elif MIN_VERSION_ghc(9,9,0)
101109 (NoEpUniTok , con_ext)
102110#else
103111 con_ext
@@ -218,7 +226,11 @@ prettyGADTDecl df decl =
218226
219227 -- Make every data constructor start with a new line and 2 spaces
220228 adjustCon :: LConDecl GP -> LConDecl GP
221- #if MIN_VERSION_ghc(9,9,0)
229+ #if MIN_VERSION_ghc(9,11,0)
230+ adjustCon (L _ r) =
231+ let delta = EpaDelta (UnhelpfulSpan UnhelpfulNoLocationInfo ) (DifferentLine 1 3 ) []
232+ in L (EpAnn delta (AnnListItem [] ) (EpaComments [] )) r
233+ #elif MIN_VERSION_ghc(9,9,0)
222234 adjustCon (L _ r) =
223235 let delta = EpaDelta (DifferentLine 1 3 ) []
224236 in L (EpAnn delta (AnnListItem [] ) (EpaComments [] )) r
@@ -229,16 +241,20 @@ prettyGADTDecl df decl =
229241#endif
230242
231243 -- Adjust where annotation to the same line of the type constructor
244+ #if MIN_VERSION_ghc(9,11,0)
245+ -- tcdDext is just a placeholder in ghc-9.12
246+ adjustWhere tcdDExt = tcdDExt
247+ #else
232248 adjustWhere tcdDExt = tcdDExt <&>
233249#if !MIN_VERSION_ghc(9,9,0)
234250 map
235251#endif
236- (\ (AddEpAnn ann l) ->
252+ (\ (AddEpAnn ann l) ->
237253 if ann == AnnWhere
238254 then AddEpAnn AnnWhere d1
239255 else AddEpAnn ann l
240256 )
241-
257+ #endif
242258 -- Remove the first extra line if exist
243259 removeExtraEmptyLine s = case stripInfix " \n\n " s of
244260 Just (x, xs) -> x <> " \n " <> xs
@@ -257,6 +273,10 @@ noUsed = EpAnnNotUsed
257273#endif
258274
259275pattern UserTyVar' :: LIdP pass -> HsTyVarBndr flag pass
276+ #if MIN_VERSION_ghc(9,11,0)
277+ pattern UserTyVar' s <- HsTvb _ _ (HsBndrVar _ s) _
278+ #else
260279pattern UserTyVar' s <- UserTyVar _ _ s
280+ #endif
261281
262282implicitTyVars = wrapXRec @ GP mkHsOuterImplicit
0 commit comments