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 ))
21
+ #if MIN_VERSION_ghc(9,11,0)
22
+ import GHC.Parser.Annotation (EpToken (.. ))
23
+ #endif
20
24
import Ide.PluginUtils (subRange )
21
25
import Language.Haskell.GHC.ExactPrint.Parsers (parseDecl )
22
26
@@ -44,6 +48,11 @@ import GHC.Parser.Annotation (EpUniToken (..),
44
48
import Language.Haskell.GHC.ExactPrint.Utils (showAst )
45
49
#endif
46
50
51
+ #if MIN_VERSION_ghc(9,11,0)
52
+ import GHC.Types.SrcLoc (UnhelpfulSpanReason (.. ))
53
+ #else
54
+ import GHC.Parser.Annotation (AddEpAnn (.. ))
55
+ #endif
47
56
48
57
type GP = GhcPass Parsed
49
58
@@ -97,7 +106,9 @@ h98ToGADTConDecl ::
97
106
h98ToGADTConDecl dataName tyVars ctxt = \ case
98
107
ConDeclH98 {.. } ->
99
108
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)
101
112
(NoEpUniTok , con_ext)
102
113
#else
103
114
con_ext
@@ -209,7 +220,11 @@ prettyGADTDecl df decl =
209
220
adjustDataDecl DataDecl {.. } = DataDecl
210
221
{ tcdDExt = adjustWhere tcdDExt
211
222
, 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 =
213
228
fmap adjustCon (dd_cons tcdDataDefn)
214
229
}
215
230
, ..
@@ -218,7 +233,11 @@ prettyGADTDecl df decl =
218
233
219
234
-- Make every data constructor start with a new line and 2 spaces
220
235
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)
222
241
adjustCon (L _ r) =
223
242
let delta = EpaDelta (DifferentLine 1 3 ) []
224
243
in L (EpAnn delta (AnnListItem [] ) (EpaComments [] )) r
@@ -229,6 +248,10 @@ prettyGADTDecl df decl =
229
248
#endif
230
249
231
250
-- 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
232
255
adjustWhere tcdDExt = tcdDExt <&>
233
256
#if !MIN_VERSION_ghc(9,9,0)
234
257
map
@@ -238,7 +261,16 @@ prettyGADTDecl df decl =
238
261
then AddEpAnn AnnWhere d1
239
262
else AddEpAnn ann l
240
263
)
264
+ #endif
241
265
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
242
274
-- Remove the first extra line if exist
243
275
removeExtraEmptyLine s = case stripInfix " \n\n " s of
244
276
Just (x, xs) -> x <> " \n " <> xs
@@ -257,6 +289,10 @@ noUsed = EpAnnNotUsed
257
289
#endif
258
290
259
291
pattern UserTyVar' :: LIdP pass -> HsTyVarBndr flag pass
292
+ #if MIN_VERSION_ghc(9,11,0)
293
+ pattern UserTyVar' s <- HsTvb _ _ (HsBndrVar _ s) _
294
+ #else
260
295
pattern UserTyVar' s <- UserTyVar _ _ s
296
+ #endif
261
297
262
298
implicitTyVars = wrapXRec @ GP mkHsOuterImplicit
0 commit comments