{-# LANGUAGE CPP #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE ScopedTypeVariables #-}

module SysTools.Settings
 ( SettingsError (..)
 , initSettings
 ) where

#include "HsVersions.h"

import GhcPrelude

import GHC.Settings

import Config
import CliOption
import FileSettings
import Fingerprint
import GHC.Platform
import GhcNameVersion
import Outputable
import Settings
import SysTools.BaseDir
import ToolSettings

import Control.Monad.Trans.Except
import Control.Monad.IO.Class
import qualified Data.Map as Map
import System.FilePath
import System.Directory

data SettingsError
  = SettingsError_MissingData String
  | SettingsError_BadData String

initSettings
  :: forall m
  .  MonadIO m
  => String -- ^ TopDir path
  -> ExceptT SettingsError m Settings
initSettings :: String -> ExceptT SettingsError m Settings
initSettings String
top_dir = do
  -- see Note [topdir: How GHC finds its files]
  -- NB: top_dir is assumed to be in standard Unix
  -- format, '/' separated
  Maybe String
mtool_dir <- IO (Maybe String) -> ExceptT SettingsError m (Maybe String)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe String) -> ExceptT SettingsError m (Maybe String))
-> IO (Maybe String) -> ExceptT SettingsError m (Maybe String)
forall a b. (a -> b) -> a -> b
$ String -> IO (Maybe String)
findToolDir String
top_dir
        -- see Note [tooldir: How GHC finds mingw on Windows]

  let installed :: FilePath -> FilePath
      installed :: String -> String
installed String
file = String
top_dir String -> String -> String
</> String
file
      libexec :: FilePath -> FilePath
      libexec :: String -> String
libexec String
file = String
top_dir String -> String -> String
</> String
"bin" String -> String -> String
</> String
file
      settingsFile :: String
settingsFile = String -> String
installed String
"settings"
      platformConstantsFile :: String
platformConstantsFile = String -> String
installed String
"platformConstants"

      readFileSafe :: FilePath -> ExceptT SettingsError m String
      readFileSafe :: String -> ExceptT SettingsError m String
readFileSafe String
path = IO Bool -> ExceptT SettingsError m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (String -> IO Bool
doesFileExist String
path) ExceptT SettingsError m Bool
-> (Bool -> ExceptT SettingsError m String)
-> ExceptT SettingsError m String
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
        Bool
True -> IO String -> ExceptT SettingsError m String
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> ExceptT SettingsError m String)
-> IO String -> ExceptT SettingsError m String
forall a b. (a -> b) -> a -> b
$ String -> IO String
readFile String
path
        Bool
False -> SettingsError -> ExceptT SettingsError m String
forall (m :: * -> *) e a. Monad m => e -> ExceptT e m a
throwE (SettingsError -> ExceptT SettingsError m String)
-> SettingsError -> ExceptT SettingsError m String
forall a b. (a -> b) -> a -> b
$ String -> SettingsError
SettingsError_MissingData (String -> SettingsError) -> String -> SettingsError
forall a b. (a -> b) -> a -> b
$ String
"Missing file: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
path

  String
settingsStr <- String -> ExceptT SettingsError m String
readFileSafe String
settingsFile
  String
platformConstantsStr <- String -> ExceptT SettingsError m String
readFileSafe String
platformConstantsFile
  [(String, String)]
settingsList <- case String -> Maybe [(String, String)]
forall a. Read a => String -> Maybe a
maybeReadFuzzy String
settingsStr of
    Just [(String, String)]
s -> [(String, String)] -> ExceptT SettingsError m [(String, String)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure [(String, String)]
s
    Maybe [(String, String)]
Nothing -> SettingsError -> ExceptT SettingsError m [(String, String)]
forall (m :: * -> *) e a. Monad m => e -> ExceptT e m a
throwE (SettingsError -> ExceptT SettingsError m [(String, String)])
-> SettingsError -> ExceptT SettingsError m [(String, String)]
forall a b. (a -> b) -> a -> b
$ String -> SettingsError
SettingsError_BadData (String -> SettingsError) -> String -> SettingsError
forall a b. (a -> b) -> a -> b
$
      String
"Can't parse " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show String
settingsFile
  let mySettings :: Map String String
mySettings = [(String, String)] -> Map String String
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(String, String)]
settingsList
  PlatformConstants
platformConstants <- case String -> Maybe PlatformConstants
forall a. Read a => String -> Maybe a
maybeReadFuzzy String
platformConstantsStr of
    Just PlatformConstants
s -> PlatformConstants -> ExceptT SettingsError m PlatformConstants
forall (f :: * -> *) a. Applicative f => a -> f a
pure PlatformConstants
s
    Maybe PlatformConstants
Nothing -> SettingsError -> ExceptT SettingsError m PlatformConstants
forall (m :: * -> *) e a. Monad m => e -> ExceptT e m a
throwE (SettingsError -> ExceptT SettingsError m PlatformConstants)
-> SettingsError -> ExceptT SettingsError m PlatformConstants
forall a b. (a -> b) -> a -> b
$ String -> SettingsError
SettingsError_BadData (String -> SettingsError) -> String -> SettingsError
forall a b. (a -> b) -> a -> b
$
      String
"Can't parse " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show String
platformConstantsFile
  -- See Note [Settings file] for a little more about this file. We're
  -- just partially applying those functions and throwing 'Left's; they're
  -- written in a very portable style to keep ghc-boot light.
  let getSetting :: String -> f String
getSetting String
key = (String -> f String)
-> (String -> f String) -> Either String String -> f String
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> f String
forall a. String -> a
pgmError String -> f String
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String String -> f String)
-> Either String String -> f String
forall a b. (a -> b) -> a -> b
$
        String
-> String -> Map String String -> String -> Either String String
getFilePathSetting0 String
top_dir String
settingsFile Map String String
mySettings String
key
      getToolSetting :: String -> ExceptT SettingsError m String
      getToolSetting :: String -> ExceptT SettingsError m String
getToolSetting String
key = Maybe String -> String -> String
expandToolDir Maybe String
mtool_dir (String -> String)
-> ExceptT SettingsError m String -> ExceptT SettingsError m String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> ExceptT SettingsError m String
forall (f :: * -> *). Applicative f => String -> f String
getSetting String
key
      getBooleanSetting :: String -> ExceptT SettingsError m Bool
      getBooleanSetting :: String -> ExceptT SettingsError m Bool
getBooleanSetting String
key = (String -> ExceptT SettingsError m Bool)
-> (Bool -> ExceptT SettingsError m Bool)
-> Either String Bool
-> ExceptT SettingsError m Bool
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> ExceptT SettingsError m Bool
forall a. String -> a
pgmError Bool -> ExceptT SettingsError m Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String Bool -> ExceptT SettingsError m Bool)
-> Either String Bool -> ExceptT SettingsError m Bool
forall a b. (a -> b) -> a -> b
$
        String -> Map String String -> String -> Either String Bool
getBooleanSetting0 String
settingsFile Map String String
mySettings String
key
  String
targetPlatformString <- String -> ExceptT SettingsError m String
forall (f :: * -> *). Applicative f => String -> f String
getSetting String
"target platform string"
  Bool
tablesNextToCode <- String -> ExceptT SettingsError m Bool
getBooleanSetting String
"Tables next to code"
  String
myExtraGccViaCFlags <- String -> ExceptT SettingsError m String
forall (f :: * -> *). Applicative f => String -> f String
getSetting String
"GCC extra via C opts"
  -- On Windows, mingw is distributed with GHC,
  -- so we look in TopDir/../mingw/bin,
  -- as well as TopDir/../../mingw/bin for hadrian.
  -- It would perhaps be nice to be able to override this
  -- with the settings file, but it would be a little fiddly
  -- to make that possible, so for now you can't.
  String
cc_prog <- String -> ExceptT SettingsError m String
getToolSetting String
"C compiler command"
  String
cc_args_str <- String -> ExceptT SettingsError m String
forall (f :: * -> *). Applicative f => String -> f String
getSetting String
"C compiler flags"
  String
cxx_args_str <- String -> ExceptT SettingsError m String
forall (f :: * -> *). Applicative f => String -> f String
getSetting String
"C++ compiler flags"
  Bool
gccSupportsNoPie <- String -> ExceptT SettingsError m Bool
getBooleanSetting String
"C compiler supports -no-pie"
  String
cpp_prog <- String -> ExceptT SettingsError m String
getToolSetting String
"Haskell CPP command"
  String
cpp_args_str <- String -> ExceptT SettingsError m String
forall (f :: * -> *). Applicative f => String -> f String
getSetting String
"Haskell CPP flags"

  Platform
platform <- (String -> ExceptT SettingsError m Platform)
-> (Platform -> ExceptT SettingsError m Platform)
-> Either String Platform
-> ExceptT SettingsError m Platform
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> ExceptT SettingsError m Platform
forall a. String -> a
pgmError Platform -> ExceptT SettingsError m Platform
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String Platform -> ExceptT SettingsError m Platform)
-> Either String Platform -> ExceptT SettingsError m Platform
forall a b. (a -> b) -> a -> b
$ String -> Map String String -> Either String Platform
getTargetPlatform String
settingsFile Map String String
mySettings

  let unreg_cc_args :: [String]
unreg_cc_args = if Platform -> Bool
platformUnregisterised Platform
platform
                      then [String
"-DNO_REGS", String
"-DUSE_MINIINTERPRETER"]
                      else []
      cpp_args :: [Option]
cpp_args = (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
Option (String -> [String]
words String
cpp_args_str)
      cc_args :: [String]
cc_args  = String -> [String]
words String
cc_args_str [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
unreg_cc_args
      cxx_args :: [String]
cxx_args = String -> [String]
words String
cxx_args_str
  Bool
ldSupportsCompactUnwind <- String -> ExceptT SettingsError m Bool
getBooleanSetting String
"ld supports compact unwind"
  Bool
ldSupportsBuildId       <- String -> ExceptT SettingsError m Bool
getBooleanSetting String
"ld supports build-id"
  Bool
ldSupportsFilelist      <- String -> ExceptT SettingsError m Bool
getBooleanSetting String
"ld supports filelist"
  Bool
ldIsGnuLd               <- String -> ExceptT SettingsError m Bool
getBooleanSetting String
"ld is GNU ld"

  let pkgconfig_path :: String
pkgconfig_path = String -> String
installed String
"package.conf.d"
      ghc_usage_msg_path :: String
ghc_usage_msg_path  = String -> String
installed String
"ghc-usage.txt"
      ghci_usage_msg_path :: String
ghci_usage_msg_path = String -> String
installed String
"ghci-usage.txt"

  -- For all systems, unlit, split, mangle are GHC utilities
  -- architecture-specific stuff is done when building Config.hs
  String
unlit_path <- String -> ExceptT SettingsError m String
getToolSetting String
"unlit command"

  String
windres_path <- String -> ExceptT SettingsError m String
getToolSetting String
"windres command"
  String
libtool_path <- String -> ExceptT SettingsError m String
getToolSetting String
"libtool command"
  String
ar_path <- String -> ExceptT SettingsError m String
getToolSetting String
"ar command"
  String
ranlib_path <- String -> ExceptT SettingsError m String
getToolSetting String
"ranlib command"

  -- TODO this side-effect doesn't belong here. Reading and parsing the settings
  -- should be idempotent and accumulate no resources.
  String
tmpdir <- IO String -> ExceptT SettingsError m String
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> ExceptT SettingsError m String)
-> IO String -> ExceptT SettingsError m String
forall a b. (a -> b) -> a -> b
$ IO String
getTemporaryDirectory

  String
touch_path <- String -> ExceptT SettingsError m String
getToolSetting String
"touch command"

  String
mkdll_prog <- String -> ExceptT SettingsError m String
getToolSetting String
"dllwrap command"
  let mkdll_args :: [a]
mkdll_args = []

  -- cpp is derived from gcc on all platforms
  -- HACK, see setPgmP below. We keep 'words' here to remember to fix
  -- Config.hs one day.


  -- Other things being equal, as and ld are simply gcc
  String
cc_link_args_str <- String -> ExceptT SettingsError m String
forall (f :: * -> *). Applicative f => String -> f String
getSetting String
"C compiler link flags"
  let   as_prog :: String
as_prog  = String
cc_prog
        as_args :: [Option]
as_args  = (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
Option [String]
cc_args
        ld_prog :: String
ld_prog  = String
cc_prog
        ld_args :: [Option]
ld_args  = (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
Option ([String]
cc_args [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ String -> [String]
words String
cc_link_args_str)
  String
ld_r_prog <- String -> ExceptT SettingsError m String
forall (f :: * -> *). Applicative f => String -> f String
getSetting String
"Merge objects command"
  String
ld_r_args <- String -> ExceptT SettingsError m String
forall (f :: * -> *). Applicative f => String -> f String
getSetting String
"Merge objects flags"

  String
llvmTarget <- String -> ExceptT SettingsError m String
forall (f :: * -> *). Applicative f => String -> f String
getSetting String
"LLVM target"

  -- We just assume on command line
  String
lc_prog <- String -> ExceptT SettingsError m String
forall (f :: * -> *). Applicative f => String -> f String
getSetting String
"LLVM llc command"
  String
lo_prog <- String -> ExceptT SettingsError m String
forall (f :: * -> *). Applicative f => String -> f String
getSetting String
"LLVM opt command"
  String
lcc_prog <- String -> ExceptT SettingsError m String
forall (f :: * -> *). Applicative f => String -> f String
getSetting String
"LLVM clang command"

  let iserv_prog :: String
iserv_prog = String -> String
libexec String
"ghc-iserv"

  String
integerLibrary <- String -> ExceptT SettingsError m String
forall (f :: * -> *). Applicative f => String -> f String
getSetting String
"integer library"
  IntegerLibrary
integerLibraryType <- case String
integerLibrary of
    String
"integer-gmp" -> IntegerLibrary -> ExceptT SettingsError m IntegerLibrary
forall (f :: * -> *) a. Applicative f => a -> f a
pure IntegerLibrary
IntegerGMP
    String
"integer-simple" -> IntegerLibrary -> ExceptT SettingsError m IntegerLibrary
forall (f :: * -> *) a. Applicative f => a -> f a
pure IntegerLibrary
IntegerSimple
    String
_ -> String -> ExceptT SettingsError m IntegerLibrary
forall a. String -> a
pgmError (String -> ExceptT SettingsError m IntegerLibrary)
-> String -> ExceptT SettingsError m IntegerLibrary
forall a b. (a -> b) -> a -> b
$ [String] -> String
unwords
      [ String
"Entry for"
      , String -> String
forall a. Show a => a -> String
show String
"integer library"
      , String
"must be one of"
      , String -> String
forall a. Show a => a -> String
show String
"integer-gmp"
      , String
"or"
      , String -> String
forall a. Show a => a -> String
show String
"integer-simple"
      ]

  Bool
ghcWithInterpreter <- String -> ExceptT SettingsError m Bool
getBooleanSetting String
"Use interpreter"
  Bool
ghcWithNativeCodeGen <- String -> ExceptT SettingsError m Bool
getBooleanSetting String
"Use native code generator"
  Bool
ghcWithSMP <- String -> ExceptT SettingsError m Bool
getBooleanSetting String
"Support SMP"
  String
ghcRTSWays <- String -> ExceptT SettingsError m String
forall (f :: * -> *). Applicative f => String -> f String
getSetting String
"RTS ways"
  Bool
leadingUnderscore <- String -> ExceptT SettingsError m Bool
getBooleanSetting String
"Leading underscore"
  Bool
useLibFFI <- String -> ExceptT SettingsError m Bool
getBooleanSetting String
"Use LibFFI"
  Bool
ghcThreaded <- String -> ExceptT SettingsError m Bool
getBooleanSetting String
"Use Threads"
  Bool
ghcDebugged <- String -> ExceptT SettingsError m Bool
getBooleanSetting String
"Use Debugging"
  Bool
ghcRtsWithLibdw <- String -> ExceptT SettingsError m Bool
getBooleanSetting String
"RTS expects libdw"

  Settings -> ExceptT SettingsError m Settings
forall (m :: * -> *) a. Monad m => a -> m a
return (Settings -> ExceptT SettingsError m Settings)
-> Settings -> ExceptT SettingsError m Settings
forall a b. (a -> b) -> a -> b
$ Settings :: GhcNameVersion
-> FileSettings
-> Platform
-> ToolSettings
-> PlatformMisc
-> PlatformConstants
-> [(String, String)]
-> Settings
Settings
    { sGhcNameVersion :: GhcNameVersion
sGhcNameVersion = GhcNameVersion :: String -> String -> GhcNameVersion
GhcNameVersion
      { ghcNameVersion_programName :: String
ghcNameVersion_programName = String
"ghc"
      , ghcNameVersion_projectVersion :: String
ghcNameVersion_projectVersion = String
cProjectVersion
      }

    , sFileSettings :: FileSettings
sFileSettings = FileSettings :: String
-> String
-> Maybe String
-> String
-> String
-> String
-> FileSettings
FileSettings
      { fileSettings_tmpDir :: String
fileSettings_tmpDir         = String -> String
normalise String
tmpdir
      , fileSettings_ghcUsagePath :: String
fileSettings_ghcUsagePath   = String
ghc_usage_msg_path
      , fileSettings_ghciUsagePath :: String
fileSettings_ghciUsagePath  = String
ghci_usage_msg_path
      , fileSettings_toolDir :: Maybe String
fileSettings_toolDir        = Maybe String
mtool_dir
      , fileSettings_topDir :: String
fileSettings_topDir         = String
top_dir
      , fileSettings_systemPackageConfig :: String
fileSettings_systemPackageConfig = String
pkgconfig_path
      }

    , sToolSettings :: ToolSettings
sToolSettings = ToolSettings :: Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> String
-> (String, [Option])
-> String
-> String
-> (String, [Option])
-> (String, [Option])
-> (String, [Option])
-> (String, [Option])
-> String
-> String
-> String
-> String
-> String
-> (String, [Option])
-> (String, [Option])
-> (String, [Option])
-> String
-> [String]
-> [String]
-> Fingerprint
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> ToolSettings
ToolSettings
      { toolSettings_ldSupportsCompactUnwind :: Bool
toolSettings_ldSupportsCompactUnwind = Bool
ldSupportsCompactUnwind
      , toolSettings_ldSupportsBuildId :: Bool
toolSettings_ldSupportsBuildId       = Bool
ldSupportsBuildId
      , toolSettings_ldSupportsFilelist :: Bool
toolSettings_ldSupportsFilelist      = Bool
ldSupportsFilelist
      , toolSettings_ldIsGnuLd :: Bool
toolSettings_ldIsGnuLd               = Bool
ldIsGnuLd
      , toolSettings_ccSupportsNoPie :: Bool
toolSettings_ccSupportsNoPie         = Bool
gccSupportsNoPie

      , toolSettings_pgm_L :: String
toolSettings_pgm_L   = String
unlit_path
      , toolSettings_pgm_P :: (String, [Option])
toolSettings_pgm_P   = (String
cpp_prog, [Option]
cpp_args)
      , toolSettings_pgm_F :: String
toolSettings_pgm_F   = String
""
      , toolSettings_pgm_c :: String
toolSettings_pgm_c   = String
cc_prog
      , toolSettings_pgm_a :: (String, [Option])
toolSettings_pgm_a   = (String
as_prog, [Option]
as_args)
      , toolSettings_pgm_l :: (String, [Option])
toolSettings_pgm_l   = (String
ld_prog, [Option]
ld_args)
      , toolSettings_pgm_lm :: (String, [Option])
toolSettings_pgm_lm  = (String
ld_r_prog, (String -> Option) -> [String] -> [Option]
forall a b. (a -> b) -> [a] -> [b]
map String -> Option
Option ([String] -> [Option]) -> [String] -> [Option]
forall a b. (a -> b) -> a -> b
$ String -> [String]
words String
ld_r_args)
      , toolSettings_pgm_dll :: (String, [Option])
toolSettings_pgm_dll = (String
mkdll_prog,[Option]
forall a. [a]
mkdll_args)
      , toolSettings_pgm_T :: String
toolSettings_pgm_T   = String
touch_path
      , toolSettings_pgm_windres :: String
toolSettings_pgm_windres = String
windres_path
      , toolSettings_pgm_libtool :: String
toolSettings_pgm_libtool = String
libtool_path
      , toolSettings_pgm_ar :: String
toolSettings_pgm_ar = String
ar_path
      , toolSettings_pgm_ranlib :: String
toolSettings_pgm_ranlib = String
ranlib_path
      , toolSettings_pgm_lo :: (String, [Option])
toolSettings_pgm_lo  = (String
lo_prog,[])
      , toolSettings_pgm_lc :: (String, [Option])
toolSettings_pgm_lc  = (String
lc_prog,[])
      , toolSettings_pgm_lcc :: (String, [Option])
toolSettings_pgm_lcc = (String
lcc_prog,[])
      , toolSettings_pgm_i :: String
toolSettings_pgm_i   = String
iserv_prog
      , toolSettings_opt_L :: [String]
toolSettings_opt_L       = []
      , toolSettings_opt_P :: [String]
toolSettings_opt_P       = []
      , toolSettings_opt_P_fingerprint :: Fingerprint
toolSettings_opt_P_fingerprint = Fingerprint
fingerprint0
      , toolSettings_opt_F :: [String]
toolSettings_opt_F       = []
      , toolSettings_opt_c :: [String]
toolSettings_opt_c       = [String]
cc_args
      , toolSettings_opt_cxx :: [String]
toolSettings_opt_cxx     = [String]
cxx_args
      , toolSettings_opt_a :: [String]
toolSettings_opt_a       = []
      , toolSettings_opt_l :: [String]
toolSettings_opt_l       = []
      , toolSettings_opt_lm :: [String]
toolSettings_opt_lm      = []
      , toolSettings_opt_windres :: [String]
toolSettings_opt_windres = []
      , toolSettings_opt_lcc :: [String]
toolSettings_opt_lcc     = []
      , toolSettings_opt_lo :: [String]
toolSettings_opt_lo      = []
      , toolSettings_opt_lc :: [String]
toolSettings_opt_lc      = []
      , toolSettings_opt_i :: [String]
toolSettings_opt_i       = []

      , toolSettings_extraGccViaCFlags :: [String]
toolSettings_extraGccViaCFlags = String -> [String]
words String
myExtraGccViaCFlags
      }

    , sTargetPlatform :: Platform
sTargetPlatform = Platform
platform
    , sPlatformMisc :: PlatformMisc
sPlatformMisc = PlatformMisc :: String
-> String
-> IntegerLibrary
-> Bool
-> Bool
-> Bool
-> String
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> String
-> PlatformMisc
PlatformMisc
      { platformMisc_targetPlatformString :: String
platformMisc_targetPlatformString = String
targetPlatformString
      , platformMisc_integerLibrary :: String
platformMisc_integerLibrary = String
integerLibrary
      , platformMisc_integerLibraryType :: IntegerLibrary
platformMisc_integerLibraryType = IntegerLibrary
integerLibraryType
      , platformMisc_ghcWithInterpreter :: Bool
platformMisc_ghcWithInterpreter = Bool
ghcWithInterpreter
      , platformMisc_ghcWithNativeCodeGen :: Bool
platformMisc_ghcWithNativeCodeGen = Bool
ghcWithNativeCodeGen
      , platformMisc_ghcWithSMP :: Bool
platformMisc_ghcWithSMP = Bool
ghcWithSMP
      , platformMisc_ghcRTSWays :: String
platformMisc_ghcRTSWays = String
ghcRTSWays
      , platformMisc_tablesNextToCode :: Bool
platformMisc_tablesNextToCode = Bool
tablesNextToCode
      , platformMisc_leadingUnderscore :: Bool
platformMisc_leadingUnderscore = Bool
leadingUnderscore
      , platformMisc_libFFI :: Bool
platformMisc_libFFI = Bool
useLibFFI
      , platformMisc_ghcThreaded :: Bool
platformMisc_ghcThreaded = Bool
ghcThreaded
      , platformMisc_ghcDebugged :: Bool
platformMisc_ghcDebugged = Bool
ghcDebugged
      , platformMisc_ghcRtsWithLibdw :: Bool
platformMisc_ghcRtsWithLibdw = Bool
ghcRtsWithLibdw
      , platformMisc_llvmTarget :: String
platformMisc_llvmTarget = String
llvmTarget
      }

    , sPlatformConstants :: PlatformConstants
sPlatformConstants = PlatformConstants
platformConstants

    , sRawSettings :: [(String, String)]
sRawSettings    = [(String, String)]
settingsList
    }