Skip to content

Commit

Permalink
clean up ghc-api pragmas
Browse files Browse the repository at this point in the history
We no longer depend on ghc-lib so it's cleanup time
  • Loading branch information
pepeiborra committed May 2, 2021
1 parent 35927c8 commit 35173dc
Show file tree
Hide file tree
Showing 26 changed files with 57 additions and 100 deletions.
6 changes: 3 additions & 3 deletions ghcide/ghcide.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@ description:
homepage: https://github.com/haskell/haskell-language-server/tree/master/ghcide#readme
bug-reports: https://github.com/haskell/haskell-language-server/issues
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
extra-source-files: include/ghc-api-version.h README.md CHANGELOG.md
extra-source-files: README.md CHANGELOG.md
test/data/**/*.project
test/data/**/*.cabal
test/data/**/*.yaml
Expand Down Expand Up @@ -333,9 +333,9 @@ test-suite ghcide-tests
extra,
filepath,
--------------------------------------------------------------
-- The MIN_GHC_API_VERSION macro relies on MIN_VERSION pragmas
-- The MIN_VERSION_ghc macro relies on MIN_VERSION pragmas
-- which require depending on ghc. So the tests need to depend
-- on ghc if they need to use MIN_GHC_API_VERSION. Maybe a
-- on ghc if they need to use MIN_VERSION_ghc. Maybe a
-- better solution can be found, but this is a quick solution
-- which works for now.
ghc,
Expand Down
12 changes: 0 additions & 12 deletions ghcide/include/ghc-api-version.h

This file was deleted.

1 change: 0 additions & 1 deletion ghcide/session-loader/Development/IDE/Session.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,5 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE TypeFamilies #-}
#include "ghc-api-version.h"

{-|
The logic for setting up a ghcide session by tapping into hie-bios.
Expand Down
21 changes: 10 additions & 11 deletions ghcide/src/Development/IDE/Core/Compile.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,6 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE RankNTypes #-}
#include "ghc-api-version.h"

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

import Lexer
import qualified Parser
#if MIN_GHC_API_VERSION(8,10,0)
#if MIN_VERSION_ghc(8,10,0)
import Control.DeepSeq (force, rnf)
#else
import Control.DeepSeq (rnf)
Expand Down Expand Up @@ -234,7 +233,7 @@ mkHiFileResultNoCompile session tcm = do
tcGblEnv = tmrTypechecked tcm
details <- makeSimpleDetails hsc_env_tmp tcGblEnv
sf <- finalSafeMode (ms_hspp_opts ms) tcGblEnv
#if MIN_GHC_API_VERSION(8,10,0)
#if MIN_VERSION_ghc(8,10,0)
iface <- mkIfaceTc hsc_env_tmp sf details tcGblEnv
#else
(iface, _) <- mkIfaceTc hsc_env_tmp Nothing sf details tcGblEnv
Expand Down Expand Up @@ -268,7 +267,7 @@ mkHiFileResultCompile session' tcm simplified_guts ltype = catchErrs $ do
(guts, details) <- tidyProgram session simplified_guts
(diags, linkable) <- genLinkable session ms guts
pure (linkable, details, diags)
#if MIN_GHC_API_VERSION(8,10,0)
#if MIN_VERSION_ghc(8,10,0)
let !partial_iface = force (mkPartialIface session details simplified_guts)
final_iface <- mkFullIface session partial_iface
#else
Expand Down Expand Up @@ -330,14 +329,14 @@ generateObjectCode session summary guts = do
(warnings, dot_o_fp) <-
withWarnings "object" $ \_tweak -> do
let summary' = _tweak summary
#if MIN_GHC_API_VERSION(8,10,0)
#if MIN_VERSION_ghc(8,10,0)
target = defaultObjectTarget $ hsc_dflags session
#else
target = defaultObjectTarget $ targetPlatform $ hsc_dflags session
#endif
session' = session { hsc_dflags = updOptLevel 0 $ (ms_hspp_opts summary') { outputFile = Just dot_o , hscTarget = target}}
(outputFilename, _mStub, _foreign_files) <- hscGenHardCode session' guts
#if MIN_GHC_API_VERSION(8,10,0)
#if MIN_VERSION_ghc(8,10,0)
(ms_location summary')
#else
summary'
Expand All @@ -360,7 +359,7 @@ generateByteCode hscEnv summary guts = do
let summary' = _tweak summary
session = hscEnv { hsc_dflags = ms_hspp_opts summary' }
hscInteractive session guts
#if MIN_GHC_API_VERSION(8,10,0)
#if MIN_VERSION_ghc(8,10,0)
(ms_location summary')
#else
summary'
Expand Down Expand Up @@ -419,7 +418,7 @@ unnecessaryDeprecationWarningFlags
, Opt_WarnUnusedMatches
, Opt_WarnUnusedTypePatterns
, Opt_WarnUnusedForalls
#if MIN_GHC_API_VERSION(8,10,0)
#if MIN_VERSION_ghc(8,10,0)
, Opt_WarnUnusedRecordWildcards
#endif
, Opt_WarnInaccessibleCode
Expand Down Expand Up @@ -738,7 +737,7 @@ getModSummaryFromImports env fp modTime contents = do
msrModSummary =
ModSummary
{ ms_mod = modl
#if MIN_GHC_API_VERSION(8,8,0)
#if MIN_VERSION_ghc(8,8,0)
, ms_hie_date = Nothing
#endif
, ms_hs_date = modTime
Expand Down Expand Up @@ -782,7 +781,7 @@ parseHeader
parseHeader dflags filename contents = do
let loc = mkRealSrcLoc (mkFastString filename) 1 1
case unP Parser.parseHeader (mkPState dflags contents loc) of
#if MIN_GHC_API_VERSION(8,10,0)
#if MIN_VERSION_ghc(8,10,0)
PFailed pst ->
throwE $ diagFromErrMsgs "parser" dflags $ getErrorMessages pst dflags
#else
Expand Down Expand Up @@ -820,7 +819,7 @@ parseFileContents env customPreprocessor filename ms = do
dflags = ms_hspp_opts ms
contents = fromJust $ ms_hspp_buf ms
case unP Parser.parseModule (mkPState dflags contents loc) of
#if MIN_GHC_API_VERSION(8,10,0)
#if MIN_VERSION_ghc(8,10,0)
PFailed pst -> throwE $ diagFromErrMsgs "parser" dflags $ getErrorMessages pst dflags
#else
PFailed _ locErr msgErr ->
Expand Down
1 change: 0 additions & 1 deletion ghcide/src/Development/IDE/Core/Rules.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,6 @@
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeFamilies #-}
#include "ghc-api-version.h"

-- | A Shake implementation of the compiler service, built
-- using the "Shaker" abstraction layer for in-memory use.
Expand Down
3 changes: 1 addition & 2 deletions ghcide/src/Development/IDE/Core/Tracing.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,5 @@
{-# LANGUAGE NoApplicativeDo #-}
{-# LANGUAGE CPP #-}
#include "ghc-api-version.h"
module Development.IDE.Core.Tracing
( otTracedHandler
, otTracedAction
Expand Down Expand Up @@ -96,7 +95,7 @@ otTracedAction key file success act
return res)
| otherwise = act

#if MIN_GHC_API_VERSION(8,8,0)
#if MIN_VERSION_ghc(8,8,0)
otTracedProvider :: MonadUnliftIO m => PluginId -> ByteString -> m a -> m a
#else
otTracedProvider :: MonadUnliftIO m => PluginId -> String -> m a -> m a
Expand Down
15 changes: 7 additions & 8 deletions ghcide/src/Development/IDE/GHC/CPP.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,6 @@
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE NondecreasingIndentation #-}
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
#include "ghc-api-version.h"

-----------------------------------------------------------------------------
--
Expand All @@ -31,12 +30,12 @@ import Module
import Packages
import Panic
import SysTools
#if MIN_GHC_API_VERSION(8,8,2)
#if MIN_VERSION_ghc(8,8,2)
import LlvmCodeGen (llvmVersionList)
#elif MIN_GHC_API_VERSION(8,8,0)
#elif MIN_VERSION_ghc(8,8,0)
import LlvmCodeGen (LlvmVersion (..))
#endif
#if MIN_GHC_API_VERSION (8,10,0)
#if MIN_VERSION_ghc (8,10,0)
import Fingerprint
import ToolSettings
#endif
Expand Down Expand Up @@ -66,7 +65,7 @@ doCpp dflags raw input_fn output_fn = do
let verbFlags = getVerbFlags dflags

let cpp_prog args | raw = SysTools.runCpp dflags args
#if MIN_GHC_API_VERSION(8,10,0)
#if MIN_VERSION_ghc(8,10,0)
| otherwise = SysTools.runCc Nothing
#else
| otherwise = SysTools.runCc
Expand Down Expand Up @@ -150,11 +149,11 @@ getBackendDefs :: DynFlags -> IO [String]
getBackendDefs dflags | hscTarget dflags == HscLlvm = do
llvmVer <- figureLlvmVersion dflags
return $ case llvmVer of
#if MIN_GHC_API_VERSION(8,8,2)
#if MIN_VERSION_ghc(8,8,2)
Just v
| [m] <- llvmVersionList v -> [ "-D__GLASGOW_HASKELL_LLVM__=" ++ format (m, 0) ]
| m:n:_ <- llvmVersionList v -> [ "-D__GLASGOW_HASKELL_LLVM__=" ++ format (m, n) ]
#elif MIN_GHC_API_VERSION(8,8,0)
#elif MIN_VERSION_ghc(8,8,0)
Just (LlvmVersion n) -> [ "-D__GLASGOW_HASKELL_LLVM__=" ++ format (n,0) ]
Just (LlvmVersionOld m n) -> [ "-D__GLASGOW_HASKELL_LLVM__=" ++ format (m,n) ]
#else
Expand All @@ -170,7 +169,7 @@ getBackendDefs _ =
return []

addOptP :: String -> DynFlags -> DynFlags
#if MIN_GHC_API_VERSION (8,10,0)
#if MIN_VERSION_ghc (8,10,0)
addOptP f = alterToolSettings $ \s -> s
{ toolSettings_opt_P = f : toolSettings_opt_P s
, toolSettings_opt_P_fingerprint = fingerprintStrings (f : toolSettings_opt_P s)
Expand Down
41 changes: 20 additions & 21 deletions ghcide/src/Development/IDE/GHC/Compat.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,6 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE PatternSynonyms #-}
{-# OPTIONS -Wno-dodgy-imports -Wno-incomplete-uni-patterns #-}
#include "ghc-api-version.h"

-- | Attempt at hiding the GHC version differences we can.
module Development.IDE.GHC.Compat(
Expand All @@ -23,7 +22,7 @@ module Development.IDE.GHC.Compat(
supportsHieFiles,
setHieDir,
dontWriteHieFiles,
#if !MIN_GHC_API_VERSION(8,8,0)
#if !MIN_VERSION_ghc(8,8,0)
ml_hie_file,
addBootSuffixLocnOut,
#endif
Expand All @@ -44,7 +43,7 @@ module Development.IDE.GHC.Compat(
tcg_exports,
pattern FunTy,

#if MIN_GHC_API_VERSION(8,10,0)
#if MIN_VERSION_ghc(8,10,0)
module GHC.Hs.Extension,
module LinkerTypes,
#else
Expand All @@ -62,7 +61,7 @@ module Development.IDE.GHC.Compat(
dropForAll
,isQualifiedImport) where

#if MIN_GHC_API_VERSION(8,10,0)
#if MIN_VERSION_ghc(8,10,0)
import LinkerTypes
#endif

Expand All @@ -83,7 +82,7 @@ import Compat.HieBin
import Compat.HieTypes
import Compat.HieUtils

#if MIN_GHC_API_VERSION(8,10,0)
#if MIN_VERSION_ghc(8,10,0)
import GHC.Hs.Extension
#else
import HsExtension
Expand All @@ -98,7 +97,7 @@ import GHC hiding (
getLoc
)
import Avail
#if MIN_GHC_API_VERSION(8,8,0)
#if MIN_VERSION_ghc(8,8,0)
import Data.List (foldl')
#else
import Data.List (foldl', isSuffixOf)
Expand All @@ -108,11 +107,11 @@ import DynamicLoading
import Plugins (Plugin(parsedResultAction), withPlugins)
import Data.Map.Strict (Map)

#if !MIN_GHC_API_VERSION(8,8,0)
#if !MIN_VERSION_ghc(8,8,0)
import System.FilePath ((-<.>))
#endif

#if !MIN_GHC_API_VERSION(8,8,0)
#if !MIN_VERSION_ghc(8,8,0)
import qualified EnumSet

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

#endif

#if !MIN_GHC_API_VERSION(8,10,0)
#if !MIN_VERSION_ghc(8,10,0)
noExtField :: NoExt
noExtField = noExt
#endif
Expand All @@ -137,15 +136,15 @@ supportsHieFiles = True
hieExportNames :: HieFile -> [(SrcSpan, Name)]
hieExportNames = nameListFromAvails . hie_exports

#if !MIN_GHC_API_VERSION(8,8,0)
#if !MIN_VERSION_ghc(8,8,0)
ml_hie_file :: GHC.ModLocation -> FilePath
ml_hie_file ml
| "boot" `isSuffixOf ` ml_hi_file ml = ml_hi_file ml -<.> ".hie-boot"
| otherwise = ml_hi_file ml -<.> ".hie"
#endif

upNameCache :: IORef NameCache -> (NameCache -> (NameCache, c)) -> IO c
#if !MIN_GHC_API_VERSION(8,8,0)
#if !MIN_VERSION_ghc(8,8,0)
upNameCache ref upd_fn
= atomicModifyIORef' ref upd_fn
#else
Expand Down Expand Up @@ -179,23 +178,23 @@ addIncludePathsQuote path x = x{includePaths = f $ includePaths x}

pattern ModLocation :: Maybe FilePath -> FilePath -> FilePath -> GHC.ModLocation
pattern ModLocation a b c <-
#if MIN_GHC_API_VERSION(8,8,0)
#if MIN_VERSION_ghc(8,8,0)
GHC.ModLocation a b c _ where ModLocation a b c = GHC.ModLocation a b c ""
#else
GHC.ModLocation a b c where ModLocation a b c = GHC.ModLocation a b c
#endif

setHieDir :: FilePath -> DynFlags -> DynFlags
setHieDir _f d =
#if MIN_GHC_API_VERSION(8,8,0)
#if MIN_VERSION_ghc(8,8,0)
d { hieDir = Just _f}
#else
d
#endif

dontWriteHieFiles :: DynFlags -> DynFlags
dontWriteHieFiles d =
#if MIN_GHC_API_VERSION(8,8,0)
#if MIN_VERSION_ghc(8,8,0)
gopt_unset d Opt_WriteHie
#else
d
Expand All @@ -204,7 +203,7 @@ dontWriteHieFiles d =
setUpTypedHoles ::DynFlags -> DynFlags
setUpTypedHoles df
= flip gopt_unset Opt_AbstractRefHoleFits -- too spammy
#if MIN_GHC_API_VERSION(8,8,0)
#if MIN_VERSION_ghc(8,8,0)
$ flip gopt_unset Opt_ShowDocsOfHoleFits -- not used
#endif
$ flip gopt_unset Opt_ShowMatchesOfHoleFits -- nice but broken (forgets module qualifiers)
Expand All @@ -226,7 +225,7 @@ nameListFromAvails :: [AvailInfo] -> [(SrcSpan, Name)]
nameListFromAvails as =
map (\n -> (nameSrcSpan n, n)) (concatMap availNames as)

#if MIN_GHC_API_VERSION(8,8,0)
#if MIN_VERSION_ghc(8,8,0)

type HasSrcSpan = GHC.HasSrcSpan
getLoc :: HasSrcSpan a => a -> SrcSpan
Expand All @@ -251,7 +250,7 @@ addBootSuffixLocnOut locn
#endif

getModuleHash :: ModIface -> Fingerprint
#if MIN_GHC_API_VERSION(8,10,0)
#if MIN_VERSION_ghc(8,10,0)
getModuleHash = mi_mod_hash . mi_final_exts
#else
getModuleHash = mi_mod_hash
Expand All @@ -264,7 +263,7 @@ disableWarningsAsErrors :: DynFlags -> DynFlags
disableWarningsAsErrors df =
flip gopt_unset Opt_WarnIsError $ foldl' wopt_unset_fatal df [toEnum 0 ..]

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

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

pattern FunTy :: Type -> Type -> Type
#if MIN_GHC_API_VERSION(8, 10, 0)
#if MIN_VERSION_ghc(8, 10, 0)
pattern FunTy arg res <- TyCoRep.FunTy {ft_arg = arg, ft_res = res}
#else
pattern FunTy arg res <- TyCoRep.FunTy arg res
#endif

isQualifiedImport :: ImportDecl a -> Bool
#if MIN_GHC_API_VERSION(8,10,0)
#if MIN_VERSION_ghc(8,10,0)
isQualifiedImport ImportDecl{ideclQualified = NotQualified} = False
isQualifiedImport ImportDecl{} = True
#else
Expand Down
Loading

0 comments on commit 35173dc

Please sign in to comment.