module Distribution.Simple.GHC.ImplInfo (
GhcImplInfo(..), getImplInfo,
ghcVersionImplInfo, ghcjsVersionImplInfo, lhcVersionImplInfo
) where
import Distribution.Simple.Compiler
import Distribution.Version
data GhcImplInfo = GhcImplInfo
{ hasCcOdirBug :: Bool
, flagInfoLanguages :: Bool
, fakeRecordPuns :: Bool
, flagStubdir :: Bool
, flagOutputDir :: Bool
, noExtInSplitSuffix :: Bool
, flagFfiIncludes :: Bool
, flagBuildingCabalPkg :: Bool
, flagPackageId :: Bool
, separateGccMingw :: Bool
, supportsHaskell2010 :: Bool
, reportsNoExt :: Bool
, alwaysNondecIndent :: Bool
, flagGhciScript :: Bool
, flagProfAuto :: Bool
, flagPackageConf :: Bool
, flagDebugInfo :: Bool
}
getImplInfo :: Compiler -> GhcImplInfo
getImplInfo comp =
case compilerFlavor comp of
GHC -> ghcVersionImplInfo (compilerVersion comp)
LHC -> lhcVersionImplInfo (compilerVersion comp)
GHCJS -> case compilerCompatVersion GHC comp of
Just ghcVer -> ghcjsVersionImplInfo (compilerVersion comp) ghcVer
_ -> error ("Distribution.Simple.GHC.Props.getImplProps: " ++
"could not find GHC version for GHCJS compiler")
x -> error ("Distribution.Simple.GHC.Props.getImplProps only works" ++
"for GHC-like compilers (GHC, GHCJS, LHC)" ++
", but found " ++ show x)
ghcVersionImplInfo :: Version -> GhcImplInfo
ghcVersionImplInfo (Version v _) = GhcImplInfo
{ hasCcOdirBug = v < [6,4,1]
, flagInfoLanguages = v >= [6,7]
, fakeRecordPuns = v >= [6,8] && v < [6,10]
, flagStubdir = v >= [6,8]
, flagOutputDir = v >= [6,10]
, noExtInSplitSuffix = v < [6,11]
, flagFfiIncludes = v < [6,11]
, flagBuildingCabalPkg = v >= [6,11]
, flagPackageId = v > [6,11]
, separateGccMingw = v < [6,12]
, supportsHaskell2010 = v >= [7]
, reportsNoExt = v >= [7]
, alwaysNondecIndent = v < [7,1]
, flagGhciScript = v >= [7,2]
, flagProfAuto = v >= [7,4]
, flagPackageConf = v < [7,5]
, flagDebugInfo = v >= [7,10]
}
ghcjsVersionImplInfo :: Version -> Version -> GhcImplInfo
ghcjsVersionImplInfo _ghcjsVer _ghcVer = GhcImplInfo
{ hasCcOdirBug = False
, flagInfoLanguages = True
, fakeRecordPuns = False
, flagStubdir = True
, flagOutputDir = True
, noExtInSplitSuffix = False
, flagFfiIncludes = False
, flagBuildingCabalPkg = True
, flagPackageId = True
, separateGccMingw = False
, supportsHaskell2010 = True
, reportsNoExt = True
, alwaysNondecIndent = False
, flagGhciScript = True
, flagProfAuto = True
, flagPackageConf = False
, flagDebugInfo = False
}
lhcVersionImplInfo :: Version -> GhcImplInfo
lhcVersionImplInfo = ghcVersionImplInfo