module GHC.Settings
( Settings (..)
, ToolSettings (..)
, FileSettings (..)
, GhcNameVersion (..)
, Platform (..)
, PlatformMisc (..)
, dynLibSuffix
, sProgramName
, sProjectVersion
, sGhcUsagePath
, sGhciUsagePath
, sToolDir
, sTopDir
, sGlobalPackageDatabasePath
, sLdSupportsCompactUnwind
, sLdSupportsBuildId
, sLdSupportsFilelist
, sLdIsGnuLd
, sGccSupportsNoPie
, sUseInplaceMinGW
, sArSupportsDashL
, sPgm_L
, sPgm_P
, sPgm_F
, sPgm_c
, sPgm_cxx
, sPgm_a
, sPgm_l
, sPgm_lm
, sPgm_dll
, sPgm_T
, sPgm_windres
, sPgm_libtool
, sPgm_ar
, sPgm_otool
, sPgm_install_name_tool
, sPgm_ranlib
, sPgm_lo
, sPgm_lc
, sPgm_lcc
, sPgm_i
, sOpt_L
, sOpt_P
, sOpt_P_fingerprint
, sOpt_F
, sOpt_c
, sOpt_cxx
, sOpt_a
, sOpt_l
, sOpt_lm
, sOpt_windres
, sOpt_lo
, sOpt_lc
, sOpt_lcc
, sOpt_i
, sExtraGccViaCFlags
, sTargetPlatformString
, sGhcWithInterpreter
, sLibFFI
) where
import GHC.Prelude
import GHC.Utils.CliOption
import GHC.Utils.Fingerprint
import GHC.Platform
data Settings = Settings
{ Settings -> GhcNameVersion
sGhcNameVersion :: {-# UNPACk #-} !GhcNameVersion
, Settings -> FileSettings
sFileSettings :: {-# UNPACK #-} !FileSettings
, Settings -> Platform
sTargetPlatform :: Platform
, Settings -> ToolSettings
sToolSettings :: {-# UNPACK #-} !ToolSettings
, Settings -> PlatformMisc
sPlatformMisc :: {-# UNPACK #-} !PlatformMisc
, Settings -> [(String, String)]
sRawSettings :: [(String, String)]
}
data ToolSettings = ToolSettings
{ ToolSettings -> Bool
toolSettings_ldSupportsCompactUnwind :: Bool
, ToolSettings -> Bool
toolSettings_ldSupportsBuildId :: Bool
, ToolSettings -> Bool
toolSettings_ldSupportsFilelist :: Bool
, ToolSettings -> Bool
toolSettings_ldIsGnuLd :: Bool
, ToolSettings -> Bool
toolSettings_ccSupportsNoPie :: Bool
, ToolSettings -> Bool
toolSettings_useInplaceMinGW :: Bool
, ToolSettings -> Bool
toolSettings_arSupportsDashL :: Bool
, ToolSettings -> String
toolSettings_pgm_L :: String
, ToolSettings -> (String, [Option])
toolSettings_pgm_P :: (String, [Option])
, ToolSettings -> String
toolSettings_pgm_F :: String
, ToolSettings -> String
toolSettings_pgm_c :: String
, ToolSettings -> String
toolSettings_pgm_cxx :: String
, ToolSettings -> (String, [Option])
toolSettings_pgm_a :: (String, [Option])
, ToolSettings -> (String, [Option])
toolSettings_pgm_l :: (String, [Option])
, ToolSettings -> Maybe (String, [Option])
toolSettings_pgm_lm :: Maybe (String, [Option])
, ToolSettings -> (String, [Option])
toolSettings_pgm_dll :: (String, [Option])
, ToolSettings -> String
toolSettings_pgm_T :: String
, ToolSettings -> String
toolSettings_pgm_windres :: String
, ToolSettings -> String
toolSettings_pgm_libtool :: String
, ToolSettings -> String
toolSettings_pgm_ar :: String
, ToolSettings -> String
toolSettings_pgm_otool :: String
, ToolSettings -> String
toolSettings_pgm_install_name_tool :: String
, ToolSettings -> String
toolSettings_pgm_ranlib :: String
,
ToolSettings -> (String, [Option])
toolSettings_pgm_lo :: (String, [Option])
,
ToolSettings -> (String, [Option])
toolSettings_pgm_lc :: (String, [Option])
,
ToolSettings -> (String, [Option])
toolSettings_pgm_lcc :: (String, [Option])
, ToolSettings -> String
toolSettings_pgm_i :: String
, ToolSettings -> [String]
toolSettings_opt_L :: [String]
, ToolSettings -> [String]
toolSettings_opt_P :: [String]
,
ToolSettings -> Fingerprint
toolSettings_opt_P_fingerprint :: Fingerprint
, ToolSettings -> [String]
toolSettings_opt_F :: [String]
, ToolSettings -> [String]
toolSettings_opt_c :: [String]
, ToolSettings -> [String]
toolSettings_opt_cxx :: [String]
, ToolSettings -> [String]
toolSettings_opt_a :: [String]
, ToolSettings -> [String]
toolSettings_opt_l :: [String]
, ToolSettings -> [String]
toolSettings_opt_lm :: [String]
, ToolSettings -> [String]
toolSettings_opt_windres :: [String]
,
ToolSettings -> [String]
toolSettings_opt_lo :: [String]
,
ToolSettings -> [String]
toolSettings_opt_lc :: [String]
,
ToolSettings -> [String]
toolSettings_opt_lcc :: [String]
,
ToolSettings -> [String]
toolSettings_opt_i :: [String]
, :: [String]
}
data FileSettings = FileSettings
{ FileSettings -> String
fileSettings_ghcUsagePath :: FilePath
, FileSettings -> String
fileSettings_ghciUsagePath :: FilePath
, FileSettings -> Maybe String
fileSettings_toolDir :: Maybe FilePath
, FileSettings -> String
fileSettings_topDir :: FilePath
, FileSettings -> String
fileSettings_globalPackageDatabase :: FilePath
}
data GhcNameVersion = GhcNameVersion
{ GhcNameVersion -> String
ghcNameVersion_programName :: String
, GhcNameVersion -> String
ghcNameVersion_projectVersion :: String
}
dynLibSuffix :: GhcNameVersion -> String
dynLibSuffix :: GhcNameVersion -> String
dynLibSuffix (GhcNameVersion String
name String
ver) = Char
'-'Char -> String -> String
forall a. a -> [a] -> [a]
:String
name String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
ver
sProgramName :: Settings -> String
sProgramName :: Settings -> String
sProgramName = GhcNameVersion -> String
ghcNameVersion_programName (GhcNameVersion -> String)
-> (Settings -> GhcNameVersion) -> Settings -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> GhcNameVersion
sGhcNameVersion
sProjectVersion :: Settings -> String
sProjectVersion :: Settings -> String
sProjectVersion = GhcNameVersion -> String
ghcNameVersion_projectVersion (GhcNameVersion -> String)
-> (Settings -> GhcNameVersion) -> Settings -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> GhcNameVersion
sGhcNameVersion
sGhcUsagePath :: Settings -> FilePath
sGhcUsagePath :: Settings -> String
sGhcUsagePath = FileSettings -> String
fileSettings_ghcUsagePath (FileSettings -> String)
-> (Settings -> FileSettings) -> Settings -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> FileSettings
sFileSettings
sGhciUsagePath :: Settings -> FilePath
sGhciUsagePath :: Settings -> String
sGhciUsagePath = FileSettings -> String
fileSettings_ghciUsagePath (FileSettings -> String)
-> (Settings -> FileSettings) -> Settings -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> FileSettings
sFileSettings
sToolDir :: Settings -> Maybe FilePath
sToolDir :: Settings -> Maybe String
sToolDir = FileSettings -> Maybe String
fileSettings_toolDir (FileSettings -> Maybe String)
-> (Settings -> FileSettings) -> Settings -> Maybe String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> FileSettings
sFileSettings
sTopDir :: Settings -> FilePath
sTopDir :: Settings -> String
sTopDir = FileSettings -> String
fileSettings_topDir (FileSettings -> String)
-> (Settings -> FileSettings) -> Settings -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> FileSettings
sFileSettings
sGlobalPackageDatabasePath :: Settings -> FilePath
sGlobalPackageDatabasePath :: Settings -> String
sGlobalPackageDatabasePath = FileSettings -> String
fileSettings_globalPackageDatabase (FileSettings -> String)
-> (Settings -> FileSettings) -> Settings -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> FileSettings
sFileSettings
sLdSupportsCompactUnwind :: Settings -> Bool
sLdSupportsCompactUnwind :: Settings -> Bool
sLdSupportsCompactUnwind = ToolSettings -> Bool
toolSettings_ldSupportsCompactUnwind (ToolSettings -> Bool)
-> (Settings -> ToolSettings) -> Settings -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sLdSupportsBuildId :: Settings -> Bool
sLdSupportsBuildId :: Settings -> Bool
sLdSupportsBuildId = ToolSettings -> Bool
toolSettings_ldSupportsBuildId (ToolSettings -> Bool)
-> (Settings -> ToolSettings) -> Settings -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sLdSupportsFilelist :: Settings -> Bool
sLdSupportsFilelist :: Settings -> Bool
sLdSupportsFilelist = ToolSettings -> Bool
toolSettings_ldSupportsFilelist (ToolSettings -> Bool)
-> (Settings -> ToolSettings) -> Settings -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sLdIsGnuLd :: Settings -> Bool
sLdIsGnuLd :: Settings -> Bool
sLdIsGnuLd = ToolSettings -> Bool
toolSettings_ldIsGnuLd (ToolSettings -> Bool)
-> (Settings -> ToolSettings) -> Settings -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sGccSupportsNoPie :: Settings -> Bool
sGccSupportsNoPie :: Settings -> Bool
sGccSupportsNoPie = ToolSettings -> Bool
toolSettings_ccSupportsNoPie (ToolSettings -> Bool)
-> (Settings -> ToolSettings) -> Settings -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sUseInplaceMinGW :: Settings -> Bool
sUseInplaceMinGW :: Settings -> Bool
sUseInplaceMinGW = ToolSettings -> Bool
toolSettings_useInplaceMinGW (ToolSettings -> Bool)
-> (Settings -> ToolSettings) -> Settings -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sArSupportsDashL :: Settings -> Bool
sArSupportsDashL :: Settings -> Bool
sArSupportsDashL = ToolSettings -> Bool
toolSettings_arSupportsDashL (ToolSettings -> Bool)
-> (Settings -> ToolSettings) -> Settings -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_L :: Settings -> String
sPgm_L :: Settings -> String
sPgm_L = ToolSettings -> String
toolSettings_pgm_L (ToolSettings -> String)
-> (Settings -> ToolSettings) -> Settings -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_P :: Settings -> (String, [Option])
sPgm_P :: Settings -> (String, [Option])
sPgm_P = ToolSettings -> (String, [Option])
toolSettings_pgm_P (ToolSettings -> (String, [Option]))
-> (Settings -> ToolSettings) -> Settings -> (String, [Option])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_F :: Settings -> String
sPgm_F :: Settings -> String
sPgm_F = ToolSettings -> String
toolSettings_pgm_F (ToolSettings -> String)
-> (Settings -> ToolSettings) -> Settings -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_c :: Settings -> String
sPgm_c :: Settings -> String
sPgm_c = ToolSettings -> String
toolSettings_pgm_c (ToolSettings -> String)
-> (Settings -> ToolSettings) -> Settings -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_cxx :: Settings -> String
sPgm_cxx :: Settings -> String
sPgm_cxx = ToolSettings -> String
toolSettings_pgm_cxx (ToolSettings -> String)
-> (Settings -> ToolSettings) -> Settings -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_a :: Settings -> (String, [Option])
sPgm_a :: Settings -> (String, [Option])
sPgm_a = ToolSettings -> (String, [Option])
toolSettings_pgm_a (ToolSettings -> (String, [Option]))
-> (Settings -> ToolSettings) -> Settings -> (String, [Option])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_l :: Settings -> (String, [Option])
sPgm_l :: Settings -> (String, [Option])
sPgm_l = ToolSettings -> (String, [Option])
toolSettings_pgm_l (ToolSettings -> (String, [Option]))
-> (Settings -> ToolSettings) -> Settings -> (String, [Option])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_lm :: Settings -> Maybe (String, [Option])
sPgm_lm :: Settings -> Maybe (String, [Option])
sPgm_lm = ToolSettings -> Maybe (String, [Option])
toolSettings_pgm_lm (ToolSettings -> Maybe (String, [Option]))
-> (Settings -> ToolSettings)
-> Settings
-> Maybe (String, [Option])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_dll :: Settings -> (String, [Option])
sPgm_dll :: Settings -> (String, [Option])
sPgm_dll = ToolSettings -> (String, [Option])
toolSettings_pgm_dll (ToolSettings -> (String, [Option]))
-> (Settings -> ToolSettings) -> Settings -> (String, [Option])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_T :: Settings -> String
sPgm_T :: Settings -> String
sPgm_T = ToolSettings -> String
toolSettings_pgm_T (ToolSettings -> String)
-> (Settings -> ToolSettings) -> Settings -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_windres :: Settings -> String
sPgm_windres :: Settings -> String
sPgm_windres = ToolSettings -> String
toolSettings_pgm_windres (ToolSettings -> String)
-> (Settings -> ToolSettings) -> Settings -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_libtool :: Settings -> String
sPgm_libtool :: Settings -> String
sPgm_libtool = ToolSettings -> String
toolSettings_pgm_libtool (ToolSettings -> String)
-> (Settings -> ToolSettings) -> Settings -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_ar :: Settings -> String
sPgm_ar :: Settings -> String
sPgm_ar = ToolSettings -> String
toolSettings_pgm_ar (ToolSettings -> String)
-> (Settings -> ToolSettings) -> Settings -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_otool :: Settings -> String
sPgm_otool :: Settings -> String
sPgm_otool = ToolSettings -> String
toolSettings_pgm_otool (ToolSettings -> String)
-> (Settings -> ToolSettings) -> Settings -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_install_name_tool :: Settings -> String
sPgm_install_name_tool :: Settings -> String
sPgm_install_name_tool = ToolSettings -> String
toolSettings_pgm_install_name_tool (ToolSettings -> String)
-> (Settings -> ToolSettings) -> Settings -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_ranlib :: Settings -> String
sPgm_ranlib :: Settings -> String
sPgm_ranlib = ToolSettings -> String
toolSettings_pgm_ranlib (ToolSettings -> String)
-> (Settings -> ToolSettings) -> Settings -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_lo :: Settings -> (String, [Option])
sPgm_lo :: Settings -> (String, [Option])
sPgm_lo = ToolSettings -> (String, [Option])
toolSettings_pgm_lo (ToolSettings -> (String, [Option]))
-> (Settings -> ToolSettings) -> Settings -> (String, [Option])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_lc :: Settings -> (String, [Option])
sPgm_lc :: Settings -> (String, [Option])
sPgm_lc = ToolSettings -> (String, [Option])
toolSettings_pgm_lc (ToolSettings -> (String, [Option]))
-> (Settings -> ToolSettings) -> Settings -> (String, [Option])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_lcc :: Settings -> (String, [Option])
sPgm_lcc :: Settings -> (String, [Option])
sPgm_lcc = ToolSettings -> (String, [Option])
toolSettings_pgm_lcc (ToolSettings -> (String, [Option]))
-> (Settings -> ToolSettings) -> Settings -> (String, [Option])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sPgm_i :: Settings -> String
sPgm_i :: Settings -> String
sPgm_i = ToolSettings -> String
toolSettings_pgm_i (ToolSettings -> String)
-> (Settings -> ToolSettings) -> Settings -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sOpt_L :: Settings -> [String]
sOpt_L :: Settings -> [String]
sOpt_L = ToolSettings -> [String]
toolSettings_opt_L (ToolSettings -> [String])
-> (Settings -> ToolSettings) -> Settings -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sOpt_P :: Settings -> [String]
sOpt_P :: Settings -> [String]
sOpt_P = ToolSettings -> [String]
toolSettings_opt_P (ToolSettings -> [String])
-> (Settings -> ToolSettings) -> Settings -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sOpt_P_fingerprint :: Settings -> Fingerprint
sOpt_P_fingerprint :: Settings -> Fingerprint
sOpt_P_fingerprint = ToolSettings -> Fingerprint
toolSettings_opt_P_fingerprint (ToolSettings -> Fingerprint)
-> (Settings -> ToolSettings) -> Settings -> Fingerprint
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sOpt_F :: Settings -> [String]
sOpt_F :: Settings -> [String]
sOpt_F = ToolSettings -> [String]
toolSettings_opt_F (ToolSettings -> [String])
-> (Settings -> ToolSettings) -> Settings -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sOpt_c :: Settings -> [String]
sOpt_c :: Settings -> [String]
sOpt_c = ToolSettings -> [String]
toolSettings_opt_c (ToolSettings -> [String])
-> (Settings -> ToolSettings) -> Settings -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sOpt_cxx :: Settings -> [String]
sOpt_cxx :: Settings -> [String]
sOpt_cxx = ToolSettings -> [String]
toolSettings_opt_cxx (ToolSettings -> [String])
-> (Settings -> ToolSettings) -> Settings -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sOpt_a :: Settings -> [String]
sOpt_a :: Settings -> [String]
sOpt_a = ToolSettings -> [String]
toolSettings_opt_a (ToolSettings -> [String])
-> (Settings -> ToolSettings) -> Settings -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sOpt_l :: Settings -> [String]
sOpt_l :: Settings -> [String]
sOpt_l = ToolSettings -> [String]
toolSettings_opt_l (ToolSettings -> [String])
-> (Settings -> ToolSettings) -> Settings -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sOpt_lm :: Settings -> [String]
sOpt_lm :: Settings -> [String]
sOpt_lm = ToolSettings -> [String]
toolSettings_opt_lm (ToolSettings -> [String])
-> (Settings -> ToolSettings) -> Settings -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sOpt_windres :: Settings -> [String]
sOpt_windres :: Settings -> [String]
sOpt_windres = ToolSettings -> [String]
toolSettings_opt_windres (ToolSettings -> [String])
-> (Settings -> ToolSettings) -> Settings -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sOpt_lo :: Settings -> [String]
sOpt_lo :: Settings -> [String]
sOpt_lo = ToolSettings -> [String]
toolSettings_opt_lo (ToolSettings -> [String])
-> (Settings -> ToolSettings) -> Settings -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sOpt_lc :: Settings -> [String]
sOpt_lc :: Settings -> [String]
sOpt_lc = ToolSettings -> [String]
toolSettings_opt_lc (ToolSettings -> [String])
-> (Settings -> ToolSettings) -> Settings -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sOpt_lcc :: Settings -> [String]
sOpt_lcc :: Settings -> [String]
sOpt_lcc = ToolSettings -> [String]
toolSettings_opt_lcc (ToolSettings -> [String])
-> (Settings -> ToolSettings) -> Settings -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sOpt_i :: Settings -> [String]
sOpt_i :: Settings -> [String]
sOpt_i = ToolSettings -> [String]
toolSettings_opt_i (ToolSettings -> [String])
-> (Settings -> ToolSettings) -> Settings -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sExtraGccViaCFlags :: Settings -> [String]
= ToolSettings -> [String]
toolSettings_extraGccViaCFlags (ToolSettings -> [String])
-> (Settings -> ToolSettings) -> Settings -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> ToolSettings
sToolSettings
sTargetPlatformString :: Settings -> String
sTargetPlatformString :: Settings -> String
sTargetPlatformString = PlatformMisc -> String
platformMisc_targetPlatformString (PlatformMisc -> String)
-> (Settings -> PlatformMisc) -> Settings -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> PlatformMisc
sPlatformMisc
sGhcWithInterpreter :: Settings -> Bool
sGhcWithInterpreter :: Settings -> Bool
sGhcWithInterpreter = PlatformMisc -> Bool
platformMisc_ghcWithInterpreter (PlatformMisc -> Bool)
-> (Settings -> PlatformMisc) -> Settings -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> PlatformMisc
sPlatformMisc
sLibFFI :: Settings -> Bool
sLibFFI :: Settings -> Bool
sLibFFI = PlatformMisc -> Bool
platformMisc_libFFI (PlatformMisc -> Bool)
-> (Settings -> PlatformMisc) -> Settings -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> PlatformMisc
sPlatformMisc