Skip to content

Commit 8f089d4

Browse files
authored
clean up ghc-api pragmas (#1785)
We no longer depend on ghc-lib so it's cleanup time
1 parent 35927c8 commit 8f089d4

File tree

26 files changed

+57
-100
lines changed

26 files changed

+57
-100
lines changed

ghcide/ghcide.cabal

+3-3
Original file line numberDiff line numberDiff line change
@@ -14,7 +14,7 @@ description:
1414
homepage: https://github.com/haskell/haskell-language-server/tree/master/ghcide#readme
1515
bug-reports: https://github.com/haskell/haskell-language-server/issues
1616
tested-with: GHC == 8.6.4 || == 8.6.5 || == 8.8.2 || == 8.8.3 || == 8.8.4 || == 8.10.2 || == 8.10.3 || == 8.10.4
17-
extra-source-files: include/ghc-api-version.h README.md CHANGELOG.md
17+
extra-source-files: README.md CHANGELOG.md
1818
test/data/**/*.project
1919
test/data/**/*.cabal
2020
test/data/**/*.yaml
@@ -333,9 +333,9 @@ test-suite ghcide-tests
333333
extra,
334334
filepath,
335335
--------------------------------------------------------------
336-
-- The MIN_GHC_API_VERSION macro relies on MIN_VERSION pragmas
336+
-- The MIN_VERSION_ghc macro relies on MIN_VERSION pragmas
337337
-- which require depending on ghc. So the tests need to depend
338-
-- on ghc if they need to use MIN_GHC_API_VERSION. Maybe a
338+
-- on ghc if they need to use MIN_VERSION_ghc. Maybe a
339339
-- better solution can be found, but this is a quick solution
340340
-- which works for now.
341341
ghc,

ghcide/include/ghc-api-version.h

-12
This file was deleted.

ghcide/session-loader/Development/IDE/Session.hs

-1
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,5 @@
11
{-# LANGUAGE CPP #-}
22
{-# LANGUAGE TypeFamilies #-}
3-
#include "ghc-api-version.h"
43

54
{-|
65
The logic for setting up a ghcide session by tapping into hie-bios.

ghcide/src/Development/IDE/Core/Compile.hs

+10-11
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,6 @@
44
{-# LANGUAGE CPP #-}
55
{-# LANGUAGE GADTs #-}
66
{-# LANGUAGE RankNTypes #-}
7-
#include "ghc-api-version.h"
87

98
-- | Based on https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/API.
109
-- Given a list of paths to find libraries, and a file to compile, produce a list of 'CoreModule' values.
@@ -57,7 +56,7 @@ import LoadIface (loadModuleInterface)
5756

5857
import Lexer
5958
import qualified Parser
60-
#if MIN_GHC_API_VERSION(8,10,0)
59+
#if MIN_VERSION_ghc(8,10,0)
6160
import Control.DeepSeq (force, rnf)
6261
#else
6362
import Control.DeepSeq (rnf)
@@ -234,7 +233,7 @@ mkHiFileResultNoCompile session tcm = do
234233
tcGblEnv = tmrTypechecked tcm
235234
details <- makeSimpleDetails hsc_env_tmp tcGblEnv
236235
sf <- finalSafeMode (ms_hspp_opts ms) tcGblEnv
237-
#if MIN_GHC_API_VERSION(8,10,0)
236+
#if MIN_VERSION_ghc(8,10,0)
238237
iface <- mkIfaceTc hsc_env_tmp sf details tcGblEnv
239238
#else
240239
(iface, _) <- mkIfaceTc hsc_env_tmp Nothing sf details tcGblEnv
@@ -268,7 +267,7 @@ mkHiFileResultCompile session' tcm simplified_guts ltype = catchErrs $ do
268267
(guts, details) <- tidyProgram session simplified_guts
269268
(diags, linkable) <- genLinkable session ms guts
270269
pure (linkable, details, diags)
271-
#if MIN_GHC_API_VERSION(8,10,0)
270+
#if MIN_VERSION_ghc(8,10,0)
272271
let !partial_iface = force (mkPartialIface session details simplified_guts)
273272
final_iface <- mkFullIface session partial_iface
274273
#else
@@ -330,14 +329,14 @@ generateObjectCode session summary guts = do
330329
(warnings, dot_o_fp) <-
331330
withWarnings "object" $ \_tweak -> do
332331
let summary' = _tweak summary
333-
#if MIN_GHC_API_VERSION(8,10,0)
332+
#if MIN_VERSION_ghc(8,10,0)
334333
target = defaultObjectTarget $ hsc_dflags session
335334
#else
336335
target = defaultObjectTarget $ targetPlatform $ hsc_dflags session
337336
#endif
338337
session' = session { hsc_dflags = updOptLevel 0 $ (ms_hspp_opts summary') { outputFile = Just dot_o , hscTarget = target}}
339338
(outputFilename, _mStub, _foreign_files) <- hscGenHardCode session' guts
340-
#if MIN_GHC_API_VERSION(8,10,0)
339+
#if MIN_VERSION_ghc(8,10,0)
341340
(ms_location summary')
342341
#else
343342
summary'
@@ -360,7 +359,7 @@ generateByteCode hscEnv summary guts = do
360359
let summary' = _tweak summary
361360
session = hscEnv { hsc_dflags = ms_hspp_opts summary' }
362361
hscInteractive session guts
363-
#if MIN_GHC_API_VERSION(8,10,0)
362+
#if MIN_VERSION_ghc(8,10,0)
364363
(ms_location summary')
365364
#else
366365
summary'
@@ -419,7 +418,7 @@ unnecessaryDeprecationWarningFlags
419418
, Opt_WarnUnusedMatches
420419
, Opt_WarnUnusedTypePatterns
421420
, Opt_WarnUnusedForalls
422-
#if MIN_GHC_API_VERSION(8,10,0)
421+
#if MIN_VERSION_ghc(8,10,0)
423422
, Opt_WarnUnusedRecordWildcards
424423
#endif
425424
, Opt_WarnInaccessibleCode
@@ -738,7 +737,7 @@ getModSummaryFromImports env fp modTime contents = do
738737
msrModSummary =
739738
ModSummary
740739
{ ms_mod = modl
741-
#if MIN_GHC_API_VERSION(8,8,0)
740+
#if MIN_VERSION_ghc(8,8,0)
742741
, ms_hie_date = Nothing
743742
#endif
744743
, ms_hs_date = modTime
@@ -782,7 +781,7 @@ parseHeader
782781
parseHeader dflags filename contents = do
783782
let loc = mkRealSrcLoc (mkFastString filename) 1 1
784783
case unP Parser.parseHeader (mkPState dflags contents loc) of
785-
#if MIN_GHC_API_VERSION(8,10,0)
784+
#if MIN_VERSION_ghc(8,10,0)
786785
PFailed pst ->
787786
throwE $ diagFromErrMsgs "parser" dflags $ getErrorMessages pst dflags
788787
#else
@@ -820,7 +819,7 @@ parseFileContents env customPreprocessor filename ms = do
820819
dflags = ms_hspp_opts ms
821820
contents = fromJust $ ms_hspp_buf ms
822821
case unP Parser.parseModule (mkPState dflags contents loc) of
823-
#if MIN_GHC_API_VERSION(8,10,0)
822+
#if MIN_VERSION_ghc(8,10,0)
824823
PFailed pst -> throwE $ diagFromErrMsgs "parser" dflags $ getErrorMessages pst dflags
825824
#else
826825
PFailed _ locErr msgErr ->

ghcide/src/Development/IDE/Core/Rules.hs

-1
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,6 @@
55
{-# LANGUAGE DuplicateRecordFields #-}
66
{-# LANGUAGE FlexibleInstances #-}
77
{-# LANGUAGE TypeFamilies #-}
8-
#include "ghc-api-version.h"
98

109
-- | A Shake implementation of the compiler service, built
1110
-- using the "Shaker" abstraction layer for in-memory use.

ghcide/src/Development/IDE/Core/Tracing.hs

+1-2
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,5 @@
11
{-# LANGUAGE NoApplicativeDo #-}
22
{-# LANGUAGE CPP #-}
3-
#include "ghc-api-version.h"
43
module Development.IDE.Core.Tracing
54
( otTracedHandler
65
, otTracedAction
@@ -96,7 +95,7 @@ otTracedAction key file success act
9695
return res)
9796
| otherwise = act
9897

99-
#if MIN_GHC_API_VERSION(8,8,0)
98+
#if MIN_VERSION_ghc(8,8,0)
10099
otTracedProvider :: MonadUnliftIO m => PluginId -> ByteString -> m a -> m a
101100
#else
102101
otTracedProvider :: MonadUnliftIO m => PluginId -> String -> m a -> m a

ghcide/src/Development/IDE/GHC/CPP.hs

+7-8
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,6 @@
1212
{-# LANGUAGE NamedFieldPuns #-}
1313
{-# LANGUAGE NondecreasingIndentation #-}
1414
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
15-
#include "ghc-api-version.h"
1615

1716
-----------------------------------------------------------------------------
1817
--
@@ -31,12 +30,12 @@ import Module
3130
import Packages
3231
import Panic
3332
import SysTools
34-
#if MIN_GHC_API_VERSION(8,8,2)
33+
#if MIN_VERSION_ghc(8,8,2)
3534
import LlvmCodeGen (llvmVersionList)
36-
#elif MIN_GHC_API_VERSION(8,8,0)
35+
#elif MIN_VERSION_ghc(8,8,0)
3736
import LlvmCodeGen (LlvmVersion (..))
3837
#endif
39-
#if MIN_GHC_API_VERSION (8,10,0)
38+
#if MIN_VERSION_ghc (8,10,0)
4039
import Fingerprint
4140
import ToolSettings
4241
#endif
@@ -66,7 +65,7 @@ doCpp dflags raw input_fn output_fn = do
6665
let verbFlags = getVerbFlags dflags
6766

6867
let cpp_prog args | raw = SysTools.runCpp dflags args
69-
#if MIN_GHC_API_VERSION(8,10,0)
68+
#if MIN_VERSION_ghc(8,10,0)
7069
| otherwise = SysTools.runCc Nothing
7170
#else
7271
| otherwise = SysTools.runCc
@@ -150,11 +149,11 @@ getBackendDefs :: DynFlags -> IO [String]
150149
getBackendDefs dflags | hscTarget dflags == HscLlvm = do
151150
llvmVer <- figureLlvmVersion dflags
152151
return $ case llvmVer of
153-
#if MIN_GHC_API_VERSION(8,8,2)
152+
#if MIN_VERSION_ghc(8,8,2)
154153
Just v
155154
| [m] <- llvmVersionList v -> [ "-D__GLASGOW_HASKELL_LLVM__=" ++ format (m, 0) ]
156155
| m:n:_ <- llvmVersionList v -> [ "-D__GLASGOW_HASKELL_LLVM__=" ++ format (m, n) ]
157-
#elif MIN_GHC_API_VERSION(8,8,0)
156+
#elif MIN_VERSION_ghc(8,8,0)
158157
Just (LlvmVersion n) -> [ "-D__GLASGOW_HASKELL_LLVM__=" ++ format (n,0) ]
159158
Just (LlvmVersionOld m n) -> [ "-D__GLASGOW_HASKELL_LLVM__=" ++ format (m,n) ]
160159
#else
@@ -170,7 +169,7 @@ getBackendDefs _ =
170169
return []
171170

172171
addOptP :: String -> DynFlags -> DynFlags
173-
#if MIN_GHC_API_VERSION (8,10,0)
172+
#if MIN_VERSION_ghc (8,10,0)
174173
addOptP f = alterToolSettings $ \s -> s
175174
{ toolSettings_opt_P = f : toolSettings_opt_P s
176175
, toolSettings_opt_P_fingerprint = fingerprintStrings (f : toolSettings_opt_P s)

ghcide/src/Development/IDE/GHC/Compat.hs

+20-21
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,6 @@
66
{-# LANGUAGE FlexibleInstances #-}
77
{-# LANGUAGE PatternSynonyms #-}
88
{-# OPTIONS -Wno-dodgy-imports -Wno-incomplete-uni-patterns #-}
9-
#include "ghc-api-version.h"
109

1110
-- | Attempt at hiding the GHC version differences we can.
1211
module Development.IDE.GHC.Compat(
@@ -23,7 +22,7 @@ module Development.IDE.GHC.Compat(
2322
supportsHieFiles,
2423
setHieDir,
2524
dontWriteHieFiles,
26-
#if !MIN_GHC_API_VERSION(8,8,0)
25+
#if !MIN_VERSION_ghc(8,8,0)
2726
ml_hie_file,
2827
addBootSuffixLocnOut,
2928
#endif
@@ -44,7 +43,7 @@ module Development.IDE.GHC.Compat(
4443
tcg_exports,
4544
pattern FunTy,
4645

47-
#if MIN_GHC_API_VERSION(8,10,0)
46+
#if MIN_VERSION_ghc(8,10,0)
4847
module GHC.Hs.Extension,
4948
module LinkerTypes,
5049
#else
@@ -62,7 +61,7 @@ module Development.IDE.GHC.Compat(
6261
dropForAll
6362
,isQualifiedImport) where
6463

65-
#if MIN_GHC_API_VERSION(8,10,0)
64+
#if MIN_VERSION_ghc(8,10,0)
6665
import LinkerTypes
6766
#endif
6867

@@ -83,7 +82,7 @@ import Compat.HieBin
8382
import Compat.HieTypes
8483
import Compat.HieUtils
8584

86-
#if MIN_GHC_API_VERSION(8,10,0)
85+
#if MIN_VERSION_ghc(8,10,0)
8786
import GHC.Hs.Extension
8887
#else
8988
import HsExtension
@@ -98,7 +97,7 @@ import GHC hiding (
9897
getLoc
9998
)
10099
import Avail
101-
#if MIN_GHC_API_VERSION(8,8,0)
100+
#if MIN_VERSION_ghc(8,8,0)
102101
import Data.List (foldl')
103102
#else
104103
import Data.List (foldl', isSuffixOf)
@@ -108,11 +107,11 @@ import DynamicLoading
108107
import Plugins (Plugin(parsedResultAction), withPlugins)
109108
import Data.Map.Strict (Map)
110109

111-
#if !MIN_GHC_API_VERSION(8,8,0)
110+
#if !MIN_VERSION_ghc(8,8,0)
112111
import System.FilePath ((-<.>))
113112
#endif
114113

115-
#if !MIN_GHC_API_VERSION(8,8,0)
114+
#if !MIN_VERSION_ghc(8,8,0)
116115
import qualified EnumSet
117116

118117
import System.IO
@@ -126,7 +125,7 @@ hPutStringBuffer hdl (StringBuffer buf len cur)
126125

127126
#endif
128127

129-
#if !MIN_GHC_API_VERSION(8,10,0)
128+
#if !MIN_VERSION_ghc(8,10,0)
130129
noExtField :: NoExt
131130
noExtField = noExt
132131
#endif
@@ -137,15 +136,15 @@ supportsHieFiles = True
137136
hieExportNames :: HieFile -> [(SrcSpan, Name)]
138137
hieExportNames = nameListFromAvails . hie_exports
139138

140-
#if !MIN_GHC_API_VERSION(8,8,0)
139+
#if !MIN_VERSION_ghc(8,8,0)
141140
ml_hie_file :: GHC.ModLocation -> FilePath
142141
ml_hie_file ml
143142
| "boot" `isSuffixOf ` ml_hi_file ml = ml_hi_file ml -<.> ".hie-boot"
144143
| otherwise = ml_hi_file ml -<.> ".hie"
145144
#endif
146145

147146
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)
149148
upNameCache ref upd_fn
150149
= atomicModifyIORef' ref upd_fn
151150
#else
@@ -179,23 +178,23 @@ addIncludePathsQuote path x = x{includePaths = f $ includePaths x}
179178

180179
pattern ModLocation :: Maybe FilePath -> FilePath -> FilePath -> GHC.ModLocation
181180
pattern ModLocation a b c <-
182-
#if MIN_GHC_API_VERSION(8,8,0)
181+
#if MIN_VERSION_ghc(8,8,0)
183182
GHC.ModLocation a b c _ where ModLocation a b c = GHC.ModLocation a b c ""
184183
#else
185184
GHC.ModLocation a b c where ModLocation a b c = GHC.ModLocation a b c
186185
#endif
187186

188187
setHieDir :: FilePath -> DynFlags -> DynFlags
189188
setHieDir _f d =
190-
#if MIN_GHC_API_VERSION(8,8,0)
189+
#if MIN_VERSION_ghc(8,8,0)
191190
d { hieDir = Just _f}
192191
#else
193192
d
194193
#endif
195194

196195
dontWriteHieFiles :: DynFlags -> DynFlags
197196
dontWriteHieFiles d =
198-
#if MIN_GHC_API_VERSION(8,8,0)
197+
#if MIN_VERSION_ghc(8,8,0)
199198
gopt_unset d Opt_WriteHie
200199
#else
201200
d
@@ -204,7 +203,7 @@ dontWriteHieFiles d =
204203
setUpTypedHoles ::DynFlags -> DynFlags
205204
setUpTypedHoles df
206205
= flip gopt_unset Opt_AbstractRefHoleFits -- too spammy
207-
#if MIN_GHC_API_VERSION(8,8,0)
206+
#if MIN_VERSION_ghc(8,8,0)
208207
$ flip gopt_unset Opt_ShowDocsOfHoleFits -- not used
209208
#endif
210209
$ flip gopt_unset Opt_ShowMatchesOfHoleFits -- nice but broken (forgets module qualifiers)
@@ -226,7 +225,7 @@ nameListFromAvails :: [AvailInfo] -> [(SrcSpan, Name)]
226225
nameListFromAvails as =
227226
map (\n -> (nameSrcSpan n, n)) (concatMap availNames as)
228227

229-
#if MIN_GHC_API_VERSION(8,8,0)
228+
#if MIN_VERSION_ghc(8,8,0)
230229

231230
type HasSrcSpan = GHC.HasSrcSpan
232231
getLoc :: HasSrcSpan a => a -> SrcSpan
@@ -251,7 +250,7 @@ addBootSuffixLocnOut locn
251250
#endif
252251

253252
getModuleHash :: ModIface -> Fingerprint
254-
#if MIN_GHC_API_VERSION(8,10,0)
253+
#if MIN_VERSION_ghc(8,10,0)
255254
getModuleHash = mi_mod_hash . mi_final_exts
256255
#else
257256
getModuleHash = mi_mod_hash
@@ -264,7 +263,7 @@ disableWarningsAsErrors :: DynFlags -> DynFlags
264263
disableWarningsAsErrors df =
265264
flip gopt_unset Opt_WarnIsError $ foldl' wopt_unset_fatal df [toEnum 0 ..]
266265

267-
#if !MIN_GHC_API_VERSION(8,8,0)
266+
#if !MIN_VERSION_ghc(8,8,0)
268267
wopt_unset_fatal :: DynFlags -> WarningFlag -> DynFlags
269268
wopt_unset_fatal dfs f
270269
= dfs { fatalWarningFlags = EnumSet.delete f (fatalWarningFlags dfs) }
@@ -288,21 +287,21 @@ pattern ExposePackage s a mr = DynFlags.ExposePackage s a mr
288287

289288
-- | Take AST representation of type signature and drop `forall` part from it (if any), returning just type's body
290289
dropForAll :: LHsType pass -> LHsType pass
291-
#if MIN_GHC_API_VERSION(8,10,0)
290+
#if MIN_VERSION_ghc(8,10,0)
292291
dropForAll = snd . GHC.splitLHsForAllTyInvis
293292
#else
294293
dropForAll = snd . GHC.splitLHsForAllTy
295294
#endif
296295

297296
pattern FunTy :: Type -> Type -> Type
298-
#if MIN_GHC_API_VERSION(8, 10, 0)
297+
#if MIN_VERSION_ghc(8, 10, 0)
299298
pattern FunTy arg res <- TyCoRep.FunTy {ft_arg = arg, ft_res = res}
300299
#else
301300
pattern FunTy arg res <- TyCoRep.FunTy arg res
302301
#endif
303302

304303
isQualifiedImport :: ImportDecl a -> Bool
305-
#if MIN_GHC_API_VERSION(8,10,0)
304+
#if MIN_VERSION_ghc(8,10,0)
306305
isQualifiedImport ImportDecl{ideclQualified = NotQualified} = False
307306
isQualifiedImport ImportDecl{} = True
308307
#else

0 commit comments

Comments
 (0)