module GHC.Platform
( PlatformMini(..)
, PlatformWordSize(..)
, Platform(..)
, platformArch
, platformOS
, Arch(..)
, OS(..)
, ArmISA(..)
, ArmISAExt(..)
, ArmABI(..)
, PPC_64ABI(..)
, ByteOrder(..)
, target32Bit
, isARM
, osElfTarget
, osMachOTarget
, osSubsectionsViaSymbols
, platformUsesFrameworks
, platformWordSizeInBytes
, platformWordSizeInBits
, platformMinInt
, platformMaxInt
, platformMaxWord
, platformInIntRange
, platformInWordRange
, platformCConvNeedsExtension
, PlatformMisc(..)
, stringEncodeArch
, stringEncodeOS
, SseVersion (..)
, BmiVersion (..)
)
where
import Prelude
import GHC.Read
import GHC.ByteOrder (ByteOrder(..))
import Data.Word
import Data.Int
data PlatformMini
= PlatformMini
{ platformMini_arch :: Arch
, platformMini_os :: OS
}
deriving (Read, Show, Eq)
data Platform = Platform
{ platformMini :: !PlatformMini
, platformWordSize :: !PlatformWordSize
, platformByteOrder :: !ByteOrder
, platformUnregisterised :: !Bool
, platformHasGnuNonexecStack :: !Bool
, platformHasIdentDirective :: !Bool
, platformHasSubsectionsViaSymbols :: !Bool
, platformIsCrossCompiling :: !Bool
, platformLeadingUnderscore :: !Bool
, platformTablesNextToCode :: !Bool
}
deriving (Read, Show, Eq)
data PlatformWordSize
= PW4
| PW8
deriving (Eq)
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 = platformMini_arch . platformMini
platformOS :: Platform -> OS
platformOS = platformMini_os . platformMini
data Arch
= ArchUnknown
| ArchX86
| ArchX86_64
| ArchPPC
| ArchPPC_64
{ ppc_64ABI :: PPC_64ABI
}
| ArchS390X
| ArchSPARC
| ArchSPARC64
| ArchARM
{ armISA :: ArmISA
, armISAExt :: [ArmISAExt]
, armABI :: ArmABI
}
| ArchAArch64
| ArchAlpha
| ArchMipseb
| ArchMipsel
| ArchJavaScript
deriving (Read, Show, Eq)
stringEncodeArch :: Arch -> String
stringEncodeArch = \case
ArchUnknown -> "unknown"
ArchX86 -> "i386"
ArchX86_64 -> "x86_64"
ArchPPC -> "powerpc"
ArchPPC_64 { ppc_64ABI = abi } -> case abi of
ELF_V1 -> "powerpc64"
ELF_V2 -> "powerpc64le"
ArchS390X -> "s390x"
ArchSPARC -> "sparc"
ArchSPARC64 -> "sparc64"
ArchARM { armISA = isa, armISAExt = _, armABI = _ } -> "arm" ++ vsuf
where
vsuf = case isa of
ARMv5 -> "v5"
ARMv6 -> "v6"
ARMv7 -> "v7"
ArchAArch64 -> "aarch64"
ArchAlpha -> "alpha"
ArchMipseb -> "mipseb"
ArchMipsel -> "mipsel"
ArchJavaScript -> "js"
isARM :: Arch -> Bool
isARM (ArchARM {}) = True
isARM ArchAArch64 = True
isARM _ = False
data OS
= OSUnknown
| OSLinux
| OSDarwin
| OSSolaris2
| OSMinGW32
| OSFreeBSD
| OSDragonFly
| OSOpenBSD
| OSNetBSD
| OSKFreeBSD
| OSHaiku
| OSQNXNTO
| OSAIX
| OSHurd
deriving (Read, Show, Eq)
stringEncodeOS :: OS -> String
stringEncodeOS = \case
OSUnknown -> "unknown"
OSLinux -> "linux"
OSDarwin -> "darwin"
OSSolaris2 -> "solaris2"
OSMinGW32 -> "mingw32"
OSFreeBSD -> "freebsd"
OSDragonFly -> "dragonfly"
OSOpenBSD -> "openbsd"
OSNetBSD -> "netbsd"
OSKFreeBSD -> "kfreebsdgnu"
OSHaiku -> "haiku"
OSQNXNTO -> "nto-qnx"
OSAIX -> "aix"
OSHurd -> "hurd"
data ArmISA
= ARMv5
| ARMv6
| ARMv7
deriving (Read, Show, Eq)
data ArmISAExt
= VFPv2
| VFPv3
| VFPv3D16
| NEON
| IWMMX2
deriving (Read, Show, Eq)
data ArmABI
= SOFT
| SOFTFP
| HARD
deriving (Read, Show, Eq)
data PPC_64ABI
= ELF_V1
| ELF_V2
deriving (Read, Show, Eq)
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
data PlatformMisc = PlatformMisc
{
platformMisc_targetPlatformString :: String
, platformMisc_ghcWithInterpreter :: Bool
, platformMisc_ghcWithSMP :: Bool
, platformMisc_ghcRTSWays :: String
, platformMisc_libFFI :: Bool
, platformMisc_ghcThreaded :: Bool
, platformMisc_ghcDebugged :: Bool
, platformMisc_ghcRtsWithLibdw :: Bool
, platformMisc_llvmTarget :: String
}
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)