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 ))
21+ #if MIN_VERSION_ghc(9,11,0)
22+ import GHC.Parser.Annotation (EpToken (.. ))
23+ #endif
2024import Ide.PluginUtils (subRange )
2125import Language.Haskell.GHC.ExactPrint.Parsers (parseDecl )
2226
@@ -44,6 +48,11 @@ import GHC.Parser.Annotation (EpUniToken (..),
4448import Language.Haskell.GHC.ExactPrint.Utils (showAst )
4549#endif
4650
51+ #if MIN_VERSION_ghc(9,11,0)
52+ import GHC.Types.SrcLoc (UnhelpfulSpanReason (.. ))
53+ #else
54+ import GHC.Parser.Annotation (AddEpAnn (.. ))
55+ #endif
4756
4857type GP = GhcPass Parsed
4958
@@ -97,7 +106,9 @@ h98ToGADTConDecl ::
97106h98ToGADTConDecl dataName tyVars ctxt = \ case
98107 ConDeclH98 {.. } ->
99108 ConDeclGADT
100- #if MIN_VERSION_ghc(9,9,0)
109+ #if MIN_VERSION_ghc(9,11,0)
110+ (AnnConDeclGADT [] [] NoEpUniTok )
111+ #elif MIN_VERSION_ghc(9,9,0)
101112 (NoEpUniTok , con_ext)
102113#else
103114 con_ext
@@ -209,7 +220,11 @@ prettyGADTDecl df decl =
209220 adjustDataDecl DataDecl {.. } = DataDecl
210221 { tcdDExt = adjustWhere tcdDExt
211222 , tcdDataDefn = tcdDataDefn
212- { dd_cons =
223+ {
224+ #if MIN_VERSION_ghc(9,11,0)
225+ dd_ext = adjustDefnWhere (dd_ext tcdDataDefn),
226+ #endif
227+ dd_cons =
213228 fmap adjustCon (dd_cons tcdDataDefn)
214229 }
215230 , ..
@@ -218,7 +233,11 @@ prettyGADTDecl df decl =
218233
219234 -- Make every data constructor start with a new line and 2 spaces
220235 adjustCon :: LConDecl GP -> LConDecl GP
221- #if MIN_VERSION_ghc(9,9,0)
236+ #if MIN_VERSION_ghc(9,11,0)
237+ adjustCon (L _ r) =
238+ let delta = EpaDelta (UnhelpfulSpan UnhelpfulNoLocationInfo ) (DifferentLine 1 2 ) []
239+ in L (EpAnn delta (AnnListItem [] ) (EpaComments [] )) r
240+ #elif MIN_VERSION_ghc(9,9,0)
222241 adjustCon (L _ r) =
223242 let delta = EpaDelta (DifferentLine 1 3 ) []
224243 in L (EpAnn delta (AnnListItem [] ) (EpaComments [] )) r
@@ -229,6 +248,10 @@ prettyGADTDecl df decl =
229248#endif
230249
231250 -- Adjust where annotation to the same line of the type constructor
251+ #if MIN_VERSION_ghc(9,11,0)
252+ -- tcdDext is just a placeholder in ghc-9.12
253+ adjustWhere = id
254+ #else
232255 adjustWhere tcdDExt = tcdDExt <&>
233256#if !MIN_VERSION_ghc(9,9,0)
234257 map
@@ -238,7 +261,16 @@ prettyGADTDecl df decl =
238261 then AddEpAnn AnnWhere d1
239262 else AddEpAnn ann l
240263 )
264+ #endif
241265
266+ #if MIN_VERSION_ghc(9,11,0)
267+ adjustDefnWhere annDataDefn
268+ | andd_where annDataDefn == NoEpTok = annDataDefn
269+ | otherwise = annDataDefn {andd_where = andd_where'}
270+ where
271+ (EpTok (EpaSpan aw)) = andd_where annDataDefn
272+ andd_where' = EpTok (EpaDelta aw (SameLine 1 ) [] )
273+ #endif
242274 -- Remove the first extra line if exist
243275 removeExtraEmptyLine s = case stripInfix " \n\n " s of
244276 Just (x, xs) -> x <> " \n " <> xs
@@ -257,6 +289,10 @@ noUsed = EpAnnNotUsed
257289#endif
258290
259291pattern UserTyVar' :: LIdP pass -> HsTyVarBndr flag pass
292+ #if MIN_VERSION_ghc(9,11,0)
293+ pattern UserTyVar' s <- HsTvb _ _ (HsBndrVar _ s) _
294+ #else
260295pattern UserTyVar' s <- UserTyVar _ _ s
296+ #endif
261297
262298implicitTyVars = wrapXRec @ GP mkHsOuterImplicit
0 commit comments