module GHC.Platform
( Platform (..)
, PlatformWordSize(..)
, PlatformConstants(..)
, platformArch
, platformOS
, ArchOS(..)
, Arch(..)
, OS(..)
, ArmISA(..)
, ArmISAExt(..)
, ArmABI(..)
, PPC_64ABI(..)
, ByteOrder(..)
, target32Bit
, isARM
, osElfTarget
, osMachOTarget
, osSubsectionsViaSymbols
, platformUsesFrameworks
, platformWordSizeInBytes
, platformWordSizeInBits
, platformMinInt
, platformMaxInt
, platformMaxWord
, platformInIntRange
, platformInWordRange
, platformCConvNeedsExtension
, PlatformMisc(..)
, SseVersion (..)
, BmiVersion (..)
, platformSOName
, platformHsSOName
, platformSOExt
)
where
import Prelude
import GHC.Read
import GHC.ByteOrder (ByteOrder(..))
import GHC.Platform.Constants
import GHC.Platform.ArchOS
import Data.Word
import Data.Int
import System.FilePath
data Platform = Platform
{ platformArchOS :: !ArchOS
, platformWordSize :: !PlatformWordSize
, platformByteOrder :: !ByteOrder
, platformUnregisterised :: !Bool
, platformHasGnuNonexecStack :: !Bool
, platformHasIdentDirective :: !Bool
, platformHasSubsectionsViaSymbols :: !Bool
, platformIsCrossCompiling :: !Bool
, platformLeadingUnderscore :: !Bool
, platformTablesNextToCode :: !Bool
, platformConstants :: !PlatformConstants
}
deriving (Read, Show, Eq)
data PlatformWordSize
= PW4
| PW8
deriving (Eq, Ord)
instance Show PlatformWordSize where
show PW4 = "4"
show PW8 = "8"
instance Read PlatformWordSize where
readPrec = do
i :: Int <- readPrec
case i of
4 -> return PW4
8 -> return PW8
other -> fail ("Invalid PlatformWordSize: " ++ show other)
platformWordSizeInBytes :: Platform -> Int
platformWordSizeInBytes p =
case platformWordSize p of
PW4 -> 4
PW8 -> 8
platformWordSizeInBits :: Platform -> Int
platformWordSizeInBits p = platformWordSizeInBytes p * 8
platformArch :: Platform -> Arch
platformArch platform = case platformArchOS platform of
ArchOS arch _ -> arch
platformOS :: Platform -> OS
platformOS platform = case platformArchOS platform of
ArchOS _ os -> os
isARM :: Arch -> Bool
isARM (ArchARM {}) = True
isARM ArchAArch64 = True
isARM _ = False
target32Bit :: Platform -> Bool
target32Bit p =
case platformWordSize p of
PW4 -> True
PW8 -> False
osElfTarget :: OS -> Bool
osElfTarget OSLinux = True
osElfTarget OSFreeBSD = True
osElfTarget OSDragonFly = True
osElfTarget OSOpenBSD = True
osElfTarget OSNetBSD = True
osElfTarget OSSolaris2 = True
osElfTarget OSDarwin = False
osElfTarget OSMinGW32 = False
osElfTarget OSKFreeBSD = True
osElfTarget OSHaiku = True
osElfTarget OSQNXNTO = False
osElfTarget OSAIX = False
osElfTarget OSHurd = True
osElfTarget OSUnknown = False
osMachOTarget :: OS -> Bool
osMachOTarget OSDarwin = True
osMachOTarget _ = False
osUsesFrameworks :: OS -> Bool
osUsesFrameworks OSDarwin = True
osUsesFrameworks _ = False
platformUsesFrameworks :: Platform -> Bool
platformUsesFrameworks = osUsesFrameworks . platformOS
osSubsectionsViaSymbols :: OS -> Bool
osSubsectionsViaSymbols OSDarwin = True
osSubsectionsViaSymbols _ = False
platformMinInt :: Platform -> Integer
platformMinInt p = case platformWordSize p of
PW4 -> toInteger (minBound :: Int32)
PW8 -> toInteger (minBound :: Int64)
platformMaxInt :: Platform -> Integer
platformMaxInt p = case platformWordSize p of
PW4 -> toInteger (maxBound :: Int32)
PW8 -> toInteger (maxBound :: Int64)
platformMaxWord :: Platform -> Integer
platformMaxWord p = case platformWordSize p of
PW4 -> toInteger (maxBound :: Word32)
PW8 -> toInteger (maxBound :: Word64)
platformInIntRange :: Platform -> Integer -> Bool
platformInIntRange platform x = x >= platformMinInt platform && x <= platformMaxInt platform
platformInWordRange :: Platform -> Integer -> Bool
platformInWordRange platform x = x >= 0 && x <= platformMaxWord platform
platformCConvNeedsExtension :: Platform -> Bool
platformCConvNeedsExtension platform = case platformArch platform of
ArchPPC_64 _ -> True
ArchS390X -> True
_ -> False
data SseVersion
= SSE1
| SSE2
| SSE3
| SSE4
| SSE42
deriving (Eq, Ord)
data BmiVersion
= BMI1
| BMI2
deriving (Eq, Ord)
data PlatformMisc = PlatformMisc
{
platformMisc_targetPlatformString :: String
, platformMisc_ghcWithInterpreter :: Bool
, platformMisc_ghcWithSMP :: Bool
, platformMisc_ghcRTSWays :: String
, platformMisc_libFFI :: Bool
, platformMisc_ghcRtsWithLibdw :: Bool
, platformMisc_llvmTarget :: String
}
platformSOName :: Platform -> FilePath -> FilePath
platformSOName platform root = case platformOS platform of
OSMinGW32 -> root <.> platformSOExt platform
_ -> ("lib" ++ root) <.> platformSOExt platform
platformHsSOName :: Platform -> FilePath -> FilePath
platformHsSOName platform root = ("lib" ++ root) <.> platformSOExt platform
platformSOExt :: Platform -> FilePath
platformSOExt platform
= case platformOS platform of
OSDarwin -> "dylib"
OSMinGW32 -> "dll"
_ -> "so"