{-# LANGUAGE CPP #-}
module Config where

#include "ghc_boot_platform.h"

cBuildPlatform :: String
cBuildPlatform = BuildPlatform_NAME
cHostPlatform :: String
cHostPlatform = HostPlatform_NAME
cTargetPlatform :: String
cTargetPlatform = TargetPlatform_NAME

cProjectName          :: String
cProjectName          = "The Glorious Glasgow Haskell Compilation System"
cProjectVersion       :: String
cProjectVersion       = "7.0.3"
cProjectVersionInt    :: String
cProjectVersionInt    = "700"
cProjectPatchLevel    :: String
cProjectPatchLevel    = "3"
cBooterVersion        :: String
cBooterVersion        = "6.12.1"
cStage                :: String
cStage                = show (STAGE :: Int)
cCcOpts               :: [String]
cCcOpts               = words "-fno-stack-protector"
cGccLinkerOpts        :: [String]
cGccLinkerOpts        = words ""
cLdLinkerOpts         :: [String]
cLdLinkerOpts         = words ""
cIntegerLibrary       :: String
cIntegerLibrary       = "integer-gmp"
cSplitObjs            :: String
cSplitObjs            = "YES"
cGhcWithInterpreter   :: String
cGhcWithInterpreter   = "YES"
cGhcWithNativeCodeGen :: String
cGhcWithNativeCodeGen = "YES"
cGhcWithLlvmCodeGen   :: String
cGhcWithLlvmCodeGen   = "YES"
cGhcWithSMP           :: String
cGhcWithSMP           = "YES"
cGhcRTSWays           :: String
cGhcRTSWays           = "l debug  thr thr_debug thr_l thr_p  dyn debug_dyn thr_dyn thr_debug_dyn"
cGhcUnregisterised    :: String
cGhcUnregisterised    = "NO"
cGhcEnableTablesNextToCode :: String
cGhcEnableTablesNextToCode = "YES"
cLeadingUnderscore    :: String
cLeadingUnderscore    = "NO"
cRAWCPP_FLAGS         :: String
cRAWCPP_FLAGS         = "-undef -traditional"
cGCC                  :: String
cGCC                  = "/usr/bin/gcc"
cMKDLL                :: String
cMKDLL                = "dllwrap"
cLdIsGNULd            :: String
cLdIsGNULd            = "YES"
cLD_X                 :: String
cLD_X                 = "-x"
cGHC_DRIVER_DIR       :: String
cGHC_DRIVER_DIR       = "driver"
cGHC_TOUCHY_PGM       :: String
cGHC_TOUCHY_PGM       = "touchy"
cGHC_TOUCHY_DIR       :: String
cGHC_TOUCHY_DIR       = "utils/touchy"
cGHC_UNLIT_PGM        :: String
cGHC_UNLIT_PGM        = "unlit"
cGHC_UNLIT_DIR        :: String
cGHC_UNLIT_DIR        = "utils/unlit"
cGHC_MANGLER_PGM      :: String
cGHC_MANGLER_PGM      = "ghc-asm"
cGHC_MANGLER_DIR      :: String
cGHC_MANGLER_DIR      = "driver/mangler"
cGHC_SPLIT_PGM        :: String
cGHC_SPLIT_PGM        = "ghc-split"
cGHC_SPLIT_DIR        :: String
cGHC_SPLIT_DIR        = "driver/split"
cGHC_SYSMAN_PGM       :: String
cGHC_SYSMAN_PGM       = ""
cGHC_SYSMAN_DIR       :: String
cGHC_SYSMAN_DIR       = "rts/parallel"
cGHC_PERL             :: String
cGHC_PERL             = "/usr/bin/perl"
cDEFAULT_TMPDIR       :: String
cDEFAULT_TMPDIR       = "/tmp"
cRelocatableBuild     :: Bool
cRelocatableBuild     = False
cLibFFI               :: Bool
cLibFFI               = False