module Settings
  ( Settings (..)
  , sProgramName
  , sProjectVersion
  , sGhcUsagePath
  , sGhciUsagePath
  , sToolDir
  , sTopDir
  , sTmpDir
  , sSystemPackageConfig
  , sLdSupportsCompactUnwind
  , sLdSupportsBuildId
  , sLdSupportsFilelist
  , sLdIsGnuLd
  , sGccSupportsNoPie
  , sPgm_L
  , sPgm_P
  , sPgm_F
  , sPgm_c
  , sPgm_a
  , sPgm_l
  , sPgm_lm
  , sPgm_dll
  , sPgm_T
  , sPgm_windres
  , sPgm_libtool
  , sPgm_ar
  , 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
  , sIntegerLibrary
  , sIntegerLibraryType
  , sGhcWithInterpreter
  , sGhcWithNativeCodeGen
  , sGhcWithSMP
  , sGhcRTSWays
  , sTablesNextToCode
  , sLeadingUnderscore
  , sLibFFI
  , sGhcThreaded
  , sGhcDebugged
  , sGhcRtsWithLibdw
  ) where

import GhcPrelude

import CliOption
import Fingerprint
import FileSettings
import GhcNameVersion
import GHC.Platform
import PlatformConstants
import ToolSettings

data Settings = Settings
  { Settings -> GhcNameVersion
sGhcNameVersion    :: {-# UNPACk #-} !GhcNameVersion
  , Settings -> FileSettings
sFileSettings      :: {-# UNPACK #-} !FileSettings
  , Settings -> Platform
sTargetPlatform    :: Platform       -- Filled in by SysTools
  , Settings -> ToolSettings
sToolSettings      :: {-# UNPACK #-} !ToolSettings
  , Settings -> PlatformMisc
sPlatformMisc      :: {-# UNPACK #-} !PlatformMisc
  , Settings -> PlatformConstants
sPlatformConstants :: PlatformConstants

  -- You shouldn't need to look things up in rawSettings directly.
  -- They should have their own fields instead.
  , Settings -> [(String, String)]
sRawSettings       :: [(String, String)]
  }

-----------------------------------------------------------------------------
-- Accessessors from 'Settings'

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
sTmpDir              :: Settings -> String
sTmpDir :: Settings -> String
sTmpDir = FileSettings -> String
fileSettings_tmpDir (FileSettings -> String)
-> (Settings -> FileSettings) -> Settings -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> FileSettings
sFileSettings
sSystemPackageConfig :: Settings -> FilePath
sSystemPackageConfig :: Settings -> String
sSystemPackageConfig = FileSettings -> String
fileSettings_systemPackageConfig (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

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_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 -> (String, [Option])
sPgm_lm :: Settings -> (String, [Option])
sPgm_lm = ToolSettings -> (String, [Option])
toolSettings_pgm_lm (ToolSettings -> (String, [Option]))
-> (Settings -> ToolSettings) -> Settings -> (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_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]
sExtraGccViaCFlags :: Settings -> [String]
sExtraGccViaCFlags = 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
sIntegerLibrary :: Settings -> String
sIntegerLibrary :: Settings -> String
sIntegerLibrary = PlatformMisc -> String
platformMisc_integerLibrary (PlatformMisc -> String)
-> (Settings -> PlatformMisc) -> Settings -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> PlatformMisc
sPlatformMisc
sIntegerLibraryType :: Settings -> IntegerLibrary
sIntegerLibraryType :: Settings -> IntegerLibrary
sIntegerLibraryType = PlatformMisc -> IntegerLibrary
platformMisc_integerLibraryType (PlatformMisc -> IntegerLibrary)
-> (Settings -> PlatformMisc) -> Settings -> IntegerLibrary
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
sGhcWithNativeCodeGen :: Settings -> Bool
sGhcWithNativeCodeGen :: Settings -> Bool
sGhcWithNativeCodeGen = PlatformMisc -> Bool
platformMisc_ghcWithNativeCodeGen (PlatformMisc -> Bool)
-> (Settings -> PlatformMisc) -> Settings -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> PlatformMisc
sPlatformMisc
sGhcWithSMP :: Settings -> Bool
sGhcWithSMP :: Settings -> Bool
sGhcWithSMP = PlatformMisc -> Bool
platformMisc_ghcWithSMP (PlatformMisc -> Bool)
-> (Settings -> PlatformMisc) -> Settings -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> PlatformMisc
sPlatformMisc
sGhcRTSWays :: Settings -> String
sGhcRTSWays :: Settings -> String
sGhcRTSWays = PlatformMisc -> String
platformMisc_ghcRTSWays (PlatformMisc -> String)
-> (Settings -> PlatformMisc) -> Settings -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> PlatformMisc
sPlatformMisc
sTablesNextToCode :: Settings -> Bool
sTablesNextToCode :: Settings -> Bool
sTablesNextToCode = PlatformMisc -> Bool
platformMisc_tablesNextToCode (PlatformMisc -> Bool)
-> (Settings -> PlatformMisc) -> Settings -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> PlatformMisc
sPlatformMisc
sLeadingUnderscore :: Settings -> Bool
sLeadingUnderscore :: Settings -> Bool
sLeadingUnderscore = PlatformMisc -> Bool
platformMisc_leadingUnderscore (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
sGhcThreaded :: Settings -> Bool
sGhcThreaded :: Settings -> Bool
sGhcThreaded = PlatformMisc -> Bool
platformMisc_ghcThreaded (PlatformMisc -> Bool)
-> (Settings -> PlatformMisc) -> Settings -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> PlatformMisc
sPlatformMisc
sGhcDebugged :: Settings -> Bool
sGhcDebugged :: Settings -> Bool
sGhcDebugged = PlatformMisc -> Bool
platformMisc_ghcDebugged (PlatformMisc -> Bool)
-> (Settings -> PlatformMisc) -> Settings -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> PlatformMisc
sPlatformMisc
sGhcRtsWithLibdw :: Settings -> Bool
sGhcRtsWithLibdw :: Settings -> Bool
sGhcRtsWithLibdw = PlatformMisc -> Bool
platformMisc_ghcRtsWithLibdw (PlatformMisc -> Bool)
-> (Settings -> PlatformMisc) -> Settings -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Settings -> PlatformMisc
sPlatformMisc