Skip to content

Commit

Permalink
Drop old GHC version support (#414)
Browse files Browse the repository at this point in the history
  • Loading branch information
fendor committed Oct 4, 2023
1 parent a4c5b4f commit 7d086c3
Show file tree
Hide file tree
Showing 9 changed files with 15 additions and 111 deletions.
2 changes: 1 addition & 1 deletion .github/workflows/haskell.yml
Expand Up @@ -15,7 +15,7 @@ jobs:
strategy:
fail-fast: false
matrix:
ghc: ['9.6.2', '9.4.6', '9.2.8', '9.0.2', '8.10.7', '8.8.4', '8.6.5']
ghc: ['9.6.2', '9.4.6', '9.2.8', '9.0.2', '8.10.7']
os: [ubuntu-latest, macOS-latest, windows-latest]

steps:
Expand Down
6 changes: 3 additions & 3 deletions hie-bios.cabal
Expand Up @@ -139,7 +139,7 @@ Extra-Source-Files: ChangeLog.md
tests/projects/stack-with-yaml/stack-with-yaml.cabal
tests/projects/stack-with-yaml/src/Lib.hs

tested-with: GHC ==8.6.5 || ==8.8.4 || ==8.10.7 || ==9.0.2 || ==9.2.8 || ==9.4.6 || ==9.6.2
tested-with: GHC ==8.10.7 || ==9.0.2 || ==9.2.8 || ==9.4.6 || ==9.6.2

Library
Default-Language: Haskell2010
Expand All @@ -163,7 +163,7 @@ Library
Other-Modules: Paths_hie_bios
autogen-modules: Paths_hie_bios
Build-Depends:
base >= 4.8 && < 5,
base >= 4.14 && < 5,
aeson >= 1.4.4 && < 2.3,
base16-bytestring >= 0.1.1 && < 1.1,
bytestring >= 0.10.8 && < 0.13,
Expand All @@ -176,7 +176,7 @@ Library
time >= 1.8.0 && < 1.13,
extra >= 1.6.14 && < 1.8,
prettyprinter ^>= 1.6 || ^>= 1.7.0,
ghc >= 8.6.1 && < 9.7,
ghc >= 8.10.1 && < 9.7,
transformers >= 0.5.2 && < 0.7,
temporary >= 1.2 && < 1.4,
template-haskell,
Expand Down
10 changes: 5 additions & 5 deletions src/HIE/Bios/Cradle.hs
Expand Up @@ -190,7 +190,7 @@ addActionDeps deps =
CradleNone
(\err -> CradleFail (err { cradleErrorDependencies = cradleErrorDependencies err `union` deps }))
(\(ComponentOptions os' dir ds) -> CradleSuccess (ComponentOptions os' dir (ds `union` deps)))


resolvedCradlesToCradle :: Show a => LogAction IO (WithSeverity Log) -> (b -> CradleAction a) -> FilePath -> [ResolvedCradle b] -> IO (Cradle a)
resolvedCradlesToCradle logger buildCustomCradle root cs = mdo
Expand Down Expand Up @@ -275,7 +275,7 @@ resolveCradleAction l buildCustomCradle cs root cradle =
ConcreteOther a -> buildCustomCradle a

resolveCradleTree :: FilePath -> CradleConfig a -> [ResolvedCradle a]
resolveCradleTree root (CradleConfig deps tree) = go root deps tree
resolveCradleTree root (CradleConfig confDeps confTree) = go root confDeps confTree
where
go pfix deps tree = case tree of
Cabal t -> [ResolvedCradle pfix deps (ConcreteCabal t)]
Expand Down Expand Up @@ -422,7 +422,7 @@ noneCradle =
canonicalizeResolvedCradles :: FilePath -> [ResolvedCradle a] -> IO [ResolvedCradle a]
canonicalizeResolvedCradles cur_dir cs =
sortOn (Down . prefix)
<$> mapM (\c -> (\abs -> c {prefix = abs}) <$> makeAbsolute (cur_dir </> prefix c)) cs
<$> mapM (\c -> (\abs_fp -> c {prefix = abs_fp}) <$> makeAbsolute (cur_dir </> prefix c)) cs

selectCradle :: (a -> FilePath) -> FilePath -> [a] -> Maybe a
selectCradle _ _ [] = Nothing
Expand All @@ -442,7 +442,7 @@ directCradle l wdir args
return (CradleSuccess (ComponentOptions (args ++ argDynamic) wdir []))
, runGhcCmd = runGhcCmdOnPath l wdir
}


-------------------------------------------------------------------------

Expand Down Expand Up @@ -526,7 +526,7 @@ cabalCradle l cs wdir mc projectFile
cabalProc <- cabalProcess l projectFile wdir "v2-exec" $ ["ghc", "-v0", "--"] ++ args
readProcessWithCwd' l cabalProc ""
}


-- | Execute a cabal process in our custom cache-build directory configured
-- with the custom ghc executable.
Expand Down
1 change: 0 additions & 1 deletion src/HIE/Bios/Environment.hs
Expand Up @@ -13,7 +13,6 @@ import System.FilePath
import System.Environment (lookupEnv)

import qualified Crypto.Hash.SHA1 as H
import Colog.Core (LogAction, WithSeverity)
import qualified Data.ByteString.Char8 as B
import Data.ByteString.Base16
import Data.List
Expand Down
2 changes: 1 addition & 1 deletion src/HIE/Bios/Flags.hs
Expand Up @@ -2,7 +2,7 @@ module HIE.Bios.Flags (getCompilerOptions) where

import HIE.Bios.Types

import Colog.Core (LogAction (..), WithSeverity (..), Severity (..), (<&))
import Colog.Core (WithSeverity (..), Severity (..), (<&))

-- | Initialize the 'DynFlags' relating to the compilation of a single
-- file or GHC session according to the provided 'Cradle'.
Expand Down
1 change: 0 additions & 1 deletion src/HIE/Bios/Ghc/Api.hs
Expand Up @@ -23,7 +23,6 @@ import qualified GhcMake as G
import qualified HIE.Bios.Ghc.Gap as Gap
import Control.Monad (void)
import Control.Monad.IO.Class
import Colog.Core (LogAction (..), WithSeverity (..))
import HIE.Bios.Types
import HIE.Bios.Environment
import HIE.Bios.Flags
Expand Down
26 changes: 2 additions & 24 deletions src/HIE/Bios/Ghc/Check.hs
Expand Up @@ -7,14 +7,9 @@ module HIE.Bios.Ghc.Check (
, check
) where

import GHC (DynFlags(..), GhcMonad)
import GHC (GhcMonad)
import qualified GHC as G

#if __GLASGOW_HASKELL__ >= 900
import qualified GHC.Driver.Session as G
#else
import qualified DynFlags as G
#endif

import Control.Exception
import Control.Monad.IO.Class
Expand All @@ -28,8 +23,6 @@ import qualified HIE.Bios.Types as T
import qualified HIE.Bios.Ghc.Load as Load
import HIE.Bios.Environment

import System.IO.Unsafe (unsafePerformIO)
import qualified HIE.Bios.Ghc.Gap as Gap

data Log =
LoadLog Load.Log
Expand Down Expand Up @@ -74,23 +67,8 @@ check :: (GhcMonad m)
-> [FilePath] -- ^ The target files.
-> m (Either String String)
check logger fileNames = do
libDir <- G.topDir <$> G.getDynFlags
withLogger (setAllWarningFlags libDir) $ Load.setTargetFiles (cmap (fmap LoadLog) logger) (map dup fileNames)
withLogger id $ Load.setTargetFiles (cmap (fmap LoadLog) logger) (map dup fileNames)

dup :: a -> (a, a)
dup x = (x, x)

----------------------------------------------------------------

-- | Set 'DynFlags' equivalent to "-Wall".
setAllWarningFlags :: FilePath -> DynFlags -> DynFlags
setAllWarningFlags libDir df = df { warningFlags = allWarningFlags libDir }

{-# NOINLINE allWarningFlags #-}
allWarningFlags :: FilePath -> Gap.WarnFlags
allWarningFlags libDir = unsafePerformIO $
G.runGhcT (Just libDir) $ do
df <- G.getSessionDynFlags
(df', _) <- addCmdOpts ["-Wall"] df
return $ G.warningFlags df'

70 changes: 3 additions & 67 deletions src/HIE/Bios/Ghc/Gap.hs
Expand Up @@ -3,8 +3,6 @@
module HIE.Bios.Ghc.Gap (
ghcVersion
-- * Warnings, Doc Compat
, WarnFlags
, emptyWarnFlags
, makeUserStyle
, PprStyle
-- * Argument parsing
Expand All @@ -27,11 +25,6 @@ module HIE.Bios.Ghc.Gap (
, HIE.Bios.Ghc.Gap.getLogger
-- * AST compat
, pattern HIE.Bios.Ghc.Gap.RealSrcSpan
, LExpression
, LBinding
, LPattern
, inTypes
, outType
-- * Exceptions
, catch
, bracket
Expand All @@ -49,7 +42,6 @@ module HIE.Bios.Ghc.Gap (
-- * Platform constants
, hostIsDynamic
-- * misc
, getModuleName
, getTyThing
, fixInfo
, Tc.FrontendResult(..)
Expand All @@ -68,7 +60,7 @@ import qualified Control.Monad.Catch as E
import GHC
import qualified GHC as G

#if __GLASGOW_HASKELL__ >= 804 && __GLASGOW_HASKELL__ < 900
#if __GLASGOW_HASKELL__ >= 810 && __GLASGOW_HASKELL__ < 900
import Data.List
import System.FilePath

Expand All @@ -89,25 +81,13 @@ import DriverPhases as G
import Util as G
import qualified GhcMonad as G

#if __GLASGOW_HASKELL__ >= 808
import qualified DynamicLoading (initializePlugins)
import qualified Plugins (plugins)
#endif

#if __GLASGOW_HASKELL__ >= 806 && __GLASGOW_HASKELL__ < 810
import HsExtension (GhcTc)
import HsExpr (MatchGroup, MatchGroupTc(..))
#elif __GLASGOW_HASKELL__ >= 804 && __GLASGOW_HASKELL__ < 810
import HsExtension (GhcTc)
import HsExpr (MatchGroup)
#endif
#endif
----------------------------------------------------------------
----------------------------------------------------------------

#if __GLASGOW_HASKELL__ >= 902
import GHC.Core.Multiplicity (irrelevantMult)
import GHC.Data.EnumSet as E
import GHC.Driver.CmdLine as CmdLine
import GHC.Driver.Env as G
import GHC.Driver.Session as G
Expand Down Expand Up @@ -195,15 +175,9 @@ handle :: (G.ExceptionMonad m, E.Exception e) => (e -> m a) -> m a -> m a
handle = G.ghandle
#endif

#if __GLASGOW_HASKELL__ >= 810
catch :: (E.MonadCatch m, E.Exception e) => m a -> (e -> m a) -> m a
catch =
E.catch
#else
catch :: (G.ExceptionMonad m, E.Exception e) => m a -> (e -> m a) -> m a
catch =
G.gcatch
#endif

----------------------------------------------------------------

Expand Down Expand Up @@ -264,20 +238,8 @@ makeUserStyle _dflags style = mkUserStyle style AllTheWay
makeUserStyle dflags style = mkUserStyle dflags style AllTheWay
#endif

#if __GLASGOW_HASKELL__ >= 804
getModuleName :: (a, b) -> a
getModuleName = fst
#endif

----------------------------------------------------------------

#if __GLASGOW_HASKELL__ >= 804
type WarnFlags = E.EnumSet WarningFlag
emptyWarnFlags :: WarnFlags
emptyWarnFlags = E.empty
#endif

#if __GLASGOW_HASKELL__ >= 804
#if __GLASGOW_HASKELL__ >= 810
getModSummaries :: ModuleGraph -> [ModSummary]
getModSummaries = mgModSummaries

Expand All @@ -293,44 +255,18 @@ fixInfo (t,f,cs,fs,_) = (t,f,cs,fs)
mapOverIncludePaths :: (FilePath -> FilePath) -> DynFlags -> DynFlags
mapOverIncludePaths f df = df
{ includePaths =
#if __GLASGOW_HASKELL__ > 804
#if __GLASGOW_HASKELL__ >= 810
G.IncludeSpecs
(map f $ G.includePathsQuote (includePaths df))
(map f $ G.includePathsGlobal (includePaths df))
#if MIN_VERSION_GLASGOW_HASKELL(9,0,2,0)
(map f $ G.includePathsQuoteImplicit (includePaths df))
#endif
#else
map f (includePaths df)
#endif
}

----------------------------------------------------------------

#if __GLASGOW_HASKELL__ >= 806
type LExpression = LHsExpr GhcTc
type LBinding = LHsBind GhcTc
type LPattern = LPat GhcTc

inTypes :: MatchGroup GhcTc LExpression -> [Type]
#if __GLASGOW_HASKELL__ >= 900
inTypes = map irrelevantMult . mg_arg_tys . mg_ext
#else
inTypes = mg_arg_tys . mg_ext
#endif
outType :: MatchGroup GhcTc LExpression -> Type
outType = mg_res_ty . mg_ext
#elif __GLASGOW_HASKELL__ >= 804
type LExpression = LHsExpr GhcTc
type LBinding = LHsBind GhcTc
type LPattern = LPat GhcTc

inTypes :: MatchGroup GhcTc LExpression -> [Type]
inTypes = mg_arg_tys
outType :: MatchGroup GhcTc LExpression -> Type
outType = mg_res_ty
#endif

unsetLogAction :: GhcMonad m => m ()
unsetLogAction = do
#if __GLASGOW_HASKELL__ >= 902
Expand Down
8 changes: 0 additions & 8 deletions tests/BiosTests.hs
Expand Up @@ -352,14 +352,6 @@ stackYamlResolver =
"lts-19.33" -- GHC 9.0.2
#elif (defined(MIN_VERSION_GLASGOW_HASKELL) && (MIN_VERSION_GLASGOW_HASKELL(8,10,7,0)))
"lts-18.28" -- GHC 8.10.7
#elif (defined(MIN_VERSION_GLASGOW_HASKELL) && (MIN_VERSION_GLASGOW_HASKELL(8,10,1,0)))
"lts-18.6" -- GHC 8.10.4
#elif (defined(MIN_VERSION_GLASGOW_HASKELL) && (MIN_VERSION_GLASGOW_HASKELL(8,8,1,0)))
"lts-16.31" -- GHC 8.8.4
#elif (defined(MIN_VERSION_GLASGOW_HASKELL) && (MIN_VERSION_GLASGOW_HASKELL(8,6,5,0)))
"lts-14.27" -- GHC 8.6.5
#elif (defined(MIN_VERSION_GLASGOW_HASKELL) && (MIN_VERSION_GLASGOW_HASKELL(8,6,4,0)))
"lts-13.19" -- GHC 8.6.4
#endif

-- ------------------------------------------------------------------
Expand Down

0 comments on commit 7d086c3

Please sign in to comment.