7
7
{-# OPTIONS_GHC -Wno-overlapping -patterns #-}
8
8
module Ide.Plugin.GHC where
9
9
10
+ #if !MIN_VERSION_ghc(9,11,0)
10
11
import Data.Functor ((<&>) )
12
+ #endif
11
13
import Data.List.Extra (stripInfix )
12
14
import qualified Data.Text as T
13
15
import Development.IDE
14
16
import Development.IDE.GHC.Compat
15
17
import Development.IDE.GHC.Compat.ExactPrint
16
- import GHC.Parser.Annotation (AddEpAnn (.. ),
17
- DeltaPos (.. ),
18
+ import GHC.Parser.Annotation (DeltaPos (.. ),
18
19
EpAnn (.. ),
19
20
EpAnnComments (EpaComments ))
20
21
import Ide.PluginUtils (subRange )
@@ -44,6 +45,11 @@ import GHC.Parser.Annotation (EpUniToken (..),
44
45
import Language.Haskell.GHC.ExactPrint.Utils (showAst )
45
46
#endif
46
47
48
+ #if MIN_VERSION_ghc(9,11,0)
49
+ import GHC.Types.SrcLoc (UnhelpfulSpanReason (.. ))
50
+ #else
51
+ import GHC.Parser.Annotation (AddEpAnn (.. ))
52
+ #endif
47
53
48
54
type GP = GhcPass Parsed
49
55
@@ -97,7 +103,9 @@ h98ToGADTConDecl ::
97
103
h98ToGADTConDecl dataName tyVars ctxt = \ case
98
104
ConDeclH98 {.. } ->
99
105
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)
101
109
(NoEpUniTok , con_ext)
102
110
#else
103
111
con_ext
@@ -218,7 +226,11 @@ prettyGADTDecl df decl =
218
226
219
227
-- Make every data constructor start with a new line and 2 spaces
220
228
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)
222
234
adjustCon (L _ r) =
223
235
let delta = EpaDelta (DifferentLine 1 3 ) []
224
236
in L (EpAnn delta (AnnListItem [] ) (EpaComments [] )) r
@@ -229,16 +241,20 @@ prettyGADTDecl df decl =
229
241
#endif
230
242
231
243
-- 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
232
248
adjustWhere tcdDExt = tcdDExt <&>
233
249
#if !MIN_VERSION_ghc(9,9,0)
234
250
map
235
251
#endif
236
- (\ (AddEpAnn ann l) ->
252
+ (\ (AddEpAnn ann l) ->
237
253
if ann == AnnWhere
238
254
then AddEpAnn AnnWhere d1
239
255
else AddEpAnn ann l
240
256
)
241
-
257
+ #endif
242
258
-- Remove the first extra line if exist
243
259
removeExtraEmptyLine s = case stripInfix " \n\n " s of
244
260
Just (x, xs) -> x <> " \n " <> xs
@@ -257,6 +273,10 @@ noUsed = EpAnnNotUsed
257
273
#endif
258
274
259
275
pattern UserTyVar' :: LIdP pass -> HsTyVarBndr flag pass
276
+ #if MIN_VERSION_ghc(9,11,0)
277
+ pattern UserTyVar' s <- HsTvb _ _ (HsBndrVar _ s) _
278
+ #else
260
279
pattern UserTyVar' s <- UserTyVar _ _ s
280
+ #endif
261
281
262
282
implicitTyVars = wrapXRec @ GP mkHsOuterImplicit
0 commit comments