{-# LANGUAGE CPP #-}
module Config where

import GhcPrelude

#include "ghc_boot_platform.h"

data IntegerLibrary = IntegerGMP
                    | IntegerSimple
                    deriving IntegerLibrary -> IntegerLibrary -> Bool
(IntegerLibrary -> IntegerLibrary -> Bool)
-> (IntegerLibrary -> IntegerLibrary -> Bool) -> Eq IntegerLibrary
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IntegerLibrary -> IntegerLibrary -> Bool
$c/= :: IntegerLibrary -> IntegerLibrary -> Bool
== :: IntegerLibrary -> IntegerLibrary -> Bool
$c== :: IntegerLibrary -> IntegerLibrary -> Bool
Eq

cBuildPlatformString :: String
cBuildPlatformString :: String
cBuildPlatformString = BuildPlatform_NAME
cHostPlatformString :: String
cHostPlatformString :: String
cHostPlatformString = HostPlatform_NAME
cTargetPlatformString :: String
cTargetPlatformString :: String
cTargetPlatformString = TargetPlatform_NAME

cProjectName          :: String
cProjectName :: String
cProjectName          = String
"The Glorious Glasgow Haskell Compilation System"
cProjectGitCommitId   :: String
cProjectGitCommitId :: String
cProjectGitCommitId   = String
"9c787d4d24f2b515934c8503ee2bbd7cfac4da20"
cProjectVersion       :: String
cProjectVersion :: String
cProjectVersion       = String
"8.8.1"
cProjectVersionInt    :: String
cProjectVersionInt :: String
cProjectVersionInt    = String
"808"
cProjectPatchLevel    :: String
cProjectPatchLevel :: String
cProjectPatchLevel    = String
"1"
cProjectPatchLevel1   :: String
cProjectPatchLevel1 :: String
cProjectPatchLevel1   = String
"1"
cProjectPatchLevel2   :: String
cProjectPatchLevel2 :: String
cProjectPatchLevel2   = String
""
cBooterVersion        :: String
cBooterVersion :: String
cBooterVersion        = String
"8.4.3"
cStage                :: String
cStage :: String
cStage                = Int -> String
forall a. Show a => a -> String
show (STAGE :: Int)
cIntegerLibrary       :: String
cIntegerLibrary :: String
cIntegerLibrary       = String
"integer-simple"
cIntegerLibraryType   :: IntegerLibrary
cIntegerLibraryType :: IntegerLibrary
cIntegerLibraryType   = IntegerLibrary
IntegerSimple
cSupportsSplitObjs    :: String
cSupportsSplitObjs :: String
cSupportsSplitObjs    = String
"YES"
cGhcWithInterpreter   :: String
cGhcWithInterpreter :: String
cGhcWithInterpreter   = String
"YES"
cGhcWithNativeCodeGen :: String
cGhcWithNativeCodeGen :: String
cGhcWithNativeCodeGen = String
"YES"
cGhcWithSMP           :: String
cGhcWithSMP :: String
cGhcWithSMP           = String
"YES"
cGhcRTSWays           :: String
cGhcRTSWays :: String
cGhcRTSWays           = String
"v thr"
cGhcEnableTablesNextToCode :: String
cGhcEnableTablesNextToCode :: String
cGhcEnableTablesNextToCode = String
"YES"
cLeadingUnderscore    :: String
cLeadingUnderscore :: String
cLeadingUnderscore    = String
"YES"
cGHC_UNLIT_PGM        :: String
cGHC_UNLIT_PGM :: String
cGHC_UNLIT_PGM        = String
"unlit"
cGHC_SPLIT_PGM        :: String
cGHC_SPLIT_PGM :: String
cGHC_SPLIT_PGM        = String
"ghc-split"
cLibFFI               :: Bool
cLibFFI :: Bool
cLibFFI               = Bool
False
cGhcThreaded :: Bool
cGhcThreaded :: Bool
cGhcThreaded = Bool
True
cGhcDebugged :: Bool
cGhcDebugged :: Bool
cGhcDebugged = Bool
False
cGhcRtsWithLibdw :: Bool
cGhcRtsWithLibdw :: Bool
cGhcRtsWithLibdw = Bool
False