6
6
{-# LANGUAGE FlexibleInstances #-}
7
7
{-# LANGUAGE PatternSynonyms #-}
8
8
{-# OPTIONS -Wno-dodgy-imports -Wno-incomplete-uni-patterns #-}
9
- #include "ghc-api-version.h"
10
9
11
10
-- | Attempt at hiding the GHC version differences we can.
12
11
module Development.IDE.GHC.Compat (
@@ -23,7 +22,7 @@ module Development.IDE.GHC.Compat(
23
22
supportsHieFiles ,
24
23
setHieDir ,
25
24
dontWriteHieFiles ,
26
- #if !MIN_GHC_API_VERSION (8,8,0)
25
+ #if !MIN_VERSION_ghc (8,8,0)
27
26
ml_hie_file ,
28
27
addBootSuffixLocnOut ,
29
28
#endif
@@ -44,7 +43,7 @@ module Development.IDE.GHC.Compat(
44
43
tcg_exports ,
45
44
pattern FunTy ,
46
45
47
- #if MIN_GHC_API_VERSION (8,10,0)
46
+ #if MIN_VERSION_ghc (8,10,0)
48
47
module GHC.Hs.Extension ,
49
48
module LinkerTypes ,
50
49
#else
@@ -62,7 +61,7 @@ module Development.IDE.GHC.Compat(
62
61
dropForAll
63
62
,isQualifiedImport ) where
64
63
65
- #if MIN_GHC_API_VERSION (8,10,0)
64
+ #if MIN_VERSION_ghc (8,10,0)
66
65
import LinkerTypes
67
66
#endif
68
67
@@ -83,7 +82,7 @@ import Compat.HieBin
83
82
import Compat.HieTypes
84
83
import Compat.HieUtils
85
84
86
- #if MIN_GHC_API_VERSION (8,10,0)
85
+ #if MIN_VERSION_ghc (8,10,0)
87
86
import GHC.Hs.Extension
88
87
#else
89
88
import HsExtension
@@ -98,7 +97,7 @@ import GHC hiding (
98
97
getLoc
99
98
)
100
99
import Avail
101
- #if MIN_GHC_API_VERSION (8,8,0)
100
+ #if MIN_VERSION_ghc (8,8,0)
102
101
import Data.List (foldl' )
103
102
#else
104
103
import Data.List (foldl' , isSuffixOf )
@@ -108,11 +107,11 @@ import DynamicLoading
108
107
import Plugins (Plugin (parsedResultAction ), withPlugins )
109
108
import Data.Map.Strict (Map )
110
109
111
- #if !MIN_GHC_API_VERSION (8,8,0)
110
+ #if !MIN_VERSION_ghc (8,8,0)
112
111
import System.FilePath ((-<.>) )
113
112
#endif
114
113
115
- #if !MIN_GHC_API_VERSION (8,8,0)
114
+ #if !MIN_VERSION_ghc (8,8,0)
116
115
import qualified EnumSet
117
116
118
117
import System.IO
@@ -126,7 +125,7 @@ hPutStringBuffer hdl (StringBuffer buf len cur)
126
125
127
126
#endif
128
127
129
- #if !MIN_GHC_API_VERSION (8,10,0)
128
+ #if !MIN_VERSION_ghc (8,10,0)
130
129
noExtField :: NoExt
131
130
noExtField = noExt
132
131
#endif
@@ -137,15 +136,15 @@ supportsHieFiles = True
137
136
hieExportNames :: HieFile -> [(SrcSpan , Name )]
138
137
hieExportNames = nameListFromAvails . hie_exports
139
138
140
- #if !MIN_GHC_API_VERSION (8,8,0)
139
+ #if !MIN_VERSION_ghc (8,8,0)
141
140
ml_hie_file :: GHC. ModLocation -> FilePath
142
141
ml_hie_file ml
143
142
| " boot" `isSuffixOf ` ml_hi_file ml = ml_hi_file ml -<.> " .hie-boot"
144
143
| otherwise = ml_hi_file ml -<.> " .hie"
145
144
#endif
146
145
147
146
upNameCache :: IORef NameCache -> (NameCache -> (NameCache , c )) -> IO c
148
- #if !MIN_GHC_API_VERSION (8,8,0)
147
+ #if !MIN_VERSION_ghc (8,8,0)
149
148
upNameCache ref upd_fn
150
149
= atomicModifyIORef' ref upd_fn
151
150
#else
@@ -179,23 +178,23 @@ addIncludePathsQuote path x = x{includePaths = f $ includePaths x}
179
178
180
179
pattern ModLocation :: Maybe FilePath -> FilePath -> FilePath -> GHC. ModLocation
181
180
pattern ModLocation a b c <-
182
- #if MIN_GHC_API_VERSION (8,8,0)
181
+ #if MIN_VERSION_ghc (8,8,0)
183
182
GHC. ModLocation a b c _ where ModLocation a b c = GHC. ModLocation a b c " "
184
183
#else
185
184
GHC. ModLocation a b c where ModLocation a b c = GHC. ModLocation a b c
186
185
#endif
187
186
188
187
setHieDir :: FilePath -> DynFlags -> DynFlags
189
188
setHieDir _f d =
190
- #if MIN_GHC_API_VERSION (8,8,0)
189
+ #if MIN_VERSION_ghc (8,8,0)
191
190
d { hieDir = Just _f}
192
191
#else
193
192
d
194
193
#endif
195
194
196
195
dontWriteHieFiles :: DynFlags -> DynFlags
197
196
dontWriteHieFiles d =
198
- #if MIN_GHC_API_VERSION (8,8,0)
197
+ #if MIN_VERSION_ghc (8,8,0)
199
198
gopt_unset d Opt_WriteHie
200
199
#else
201
200
d
@@ -204,7 +203,7 @@ dontWriteHieFiles d =
204
203
setUpTypedHoles :: DynFlags -> DynFlags
205
204
setUpTypedHoles df
206
205
= flip gopt_unset Opt_AbstractRefHoleFits -- too spammy
207
- #if MIN_GHC_API_VERSION (8,8,0)
206
+ #if MIN_VERSION_ghc (8,8,0)
208
207
$ flip gopt_unset Opt_ShowDocsOfHoleFits -- not used
209
208
#endif
210
209
$ flip gopt_unset Opt_ShowMatchesOfHoleFits -- nice but broken (forgets module qualifiers)
@@ -226,7 +225,7 @@ nameListFromAvails :: [AvailInfo] -> [(SrcSpan, Name)]
226
225
nameListFromAvails as =
227
226
map (\ n -> (nameSrcSpan n, n)) (concatMap availNames as)
228
227
229
- #if MIN_GHC_API_VERSION (8,8,0)
228
+ #if MIN_VERSION_ghc (8,8,0)
230
229
231
230
type HasSrcSpan = GHC. HasSrcSpan
232
231
getLoc :: HasSrcSpan a => a -> SrcSpan
@@ -251,7 +250,7 @@ addBootSuffixLocnOut locn
251
250
#endif
252
251
253
252
getModuleHash :: ModIface -> Fingerprint
254
- #if MIN_GHC_API_VERSION (8,10,0)
253
+ #if MIN_VERSION_ghc (8,10,0)
255
254
getModuleHash = mi_mod_hash . mi_final_exts
256
255
#else
257
256
getModuleHash = mi_mod_hash
@@ -264,7 +263,7 @@ disableWarningsAsErrors :: DynFlags -> DynFlags
264
263
disableWarningsAsErrors df =
265
264
flip gopt_unset Opt_WarnIsError $ foldl' wopt_unset_fatal df [toEnum 0 .. ]
266
265
267
- #if !MIN_GHC_API_VERSION (8,8,0)
266
+ #if !MIN_VERSION_ghc (8,8,0)
268
267
wopt_unset_fatal :: DynFlags -> WarningFlag -> DynFlags
269
268
wopt_unset_fatal dfs f
270
269
= dfs { fatalWarningFlags = EnumSet. delete f (fatalWarningFlags dfs) }
@@ -288,21 +287,21 @@ pattern ExposePackage s a mr = DynFlags.ExposePackage s a mr
288
287
289
288
-- | Take AST representation of type signature and drop `forall` part from it (if any), returning just type's body
290
289
dropForAll :: LHsType pass -> LHsType pass
291
- #if MIN_GHC_API_VERSION (8,10,0)
290
+ #if MIN_VERSION_ghc (8,10,0)
292
291
dropForAll = snd . GHC. splitLHsForAllTyInvis
293
292
#else
294
293
dropForAll = snd . GHC. splitLHsForAllTy
295
294
#endif
296
295
297
296
pattern FunTy :: Type -> Type -> Type
298
- #if MIN_GHC_API_VERSION (8, 10, 0)
297
+ #if MIN_VERSION_ghc (8, 10, 0)
299
298
pattern FunTy arg res <- TyCoRep. FunTy {ft_arg = arg, ft_res = res}
300
299
#else
301
300
pattern FunTy arg res <- TyCoRep. FunTy arg res
302
301
#endif
303
302
304
303
isQualifiedImport :: ImportDecl a -> Bool
305
- #if MIN_GHC_API_VERSION (8,10,0)
304
+ #if MIN_VERSION_ghc (8,10,0)
306
305
isQualifiedImport ImportDecl {ideclQualified = NotQualified } = False
307
306
isQualifiedImport ImportDecl {} = True
308
307
#else
0 commit comments