Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
GHC.Platform
Description
A description of the platform we're compiling for.
Synopsis
- data PlatformMini = PlatformMini {}
- data PlatformWordSize
- data Platform = Platform {
- platformMini :: !PlatformMini
- platformWordSize :: !PlatformWordSize
- platformByteOrder :: !ByteOrder
- platformUnregisterised :: !Bool
- platformHasGnuNonexecStack :: !Bool
- platformHasIdentDirective :: !Bool
- platformHasSubsectionsViaSymbols :: !Bool
- platformIsCrossCompiling :: !Bool
- platformLeadingUnderscore :: !Bool
- platformTablesNextToCode :: !Bool
- platformArch :: Platform -> Arch
- platformOS :: Platform -> OS
- data Arch
- = ArchUnknown
- | ArchX86
- | ArchX86_64
- | ArchPPC
- | ArchPPC_64 { }
- | ArchS390X
- | ArchSPARC
- | ArchSPARC64
- | ArchARM { }
- | ArchAArch64
- | ArchAlpha
- | ArchMipseb
- | ArchMipsel
- | ArchJavaScript
- data OS
- data ArmISA
- data ArmISAExt
- data ArmABI
- data PPC_64ABI
- data ByteOrder
- target32Bit :: Platform -> Bool
- isARM :: Arch -> Bool
- osElfTarget :: OS -> Bool
- osMachOTarget :: OS -> Bool
- osSubsectionsViaSymbols :: OS -> Bool
- platformUsesFrameworks :: Platform -> Bool
- platformWordSizeInBytes :: Platform -> Int
- platformWordSizeInBits :: Platform -> Int
- platformMinInt :: Platform -> Integer
- platformMaxInt :: Platform -> Integer
- platformMaxWord :: Platform -> Integer
- platformInIntRange :: Platform -> Integer -> Bool
- platformInWordRange :: Platform -> Integer -> Bool
- platformCConvNeedsExtension :: Platform -> Bool
- 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
- stringEncodeArch :: Arch -> String
- stringEncodeOS :: OS -> String
- data SseVersion
- data BmiVersion
Documentation
data PlatformMini Source #
Contains the bare-bones arch and os information. This isn't enough for code gen, but useful for tasks where we can fall back upon the host platform, as this is all we know about the host platform.
Constructors
PlatformMini | |
Fields |
Instances
Eq PlatformMini Source # | |
Defined in GHC.Platform | |
Read PlatformMini Source # | |
Defined in GHC.Platform Methods readsPrec :: Int -> ReadS PlatformMini # readList :: ReadS [PlatformMini] # | |
Show PlatformMini Source # | |
Defined in GHC.Platform Methods showsPrec :: Int -> PlatformMini -> ShowS # show :: PlatformMini -> String # showList :: [PlatformMini] -> ShowS # |
data PlatformWordSize Source #
Instances
Eq PlatformWordSize Source # | |
Defined in GHC.Platform Methods (==) :: PlatformWordSize -> PlatformWordSize -> Bool # (/=) :: PlatformWordSize -> PlatformWordSize -> Bool # | |
Read PlatformWordSize Source # | |
Defined in GHC.Platform Methods readsPrec :: Int -> ReadS PlatformWordSize # readList :: ReadS [PlatformWordSize] # | |
Show PlatformWordSize Source # | |
Defined in GHC.Platform Methods showsPrec :: Int -> PlatformWordSize -> ShowS # show :: PlatformWordSize -> String # showList :: [PlatformWordSize] -> ShowS # |
Contains enough information for the native code generator to emit code for this platform.
Constructors
Platform | |
Fields
|
platformArch :: Platform -> Arch Source #
Legacy accessor
platformOS :: Platform -> OS Source #
Legacy accessor
Architectures that the native code generator knows about. TODO: It might be nice to extend these constructors with information about what instruction set extensions an architecture might support.
Constructors
ArchUnknown | |
ArchX86 | |
ArchX86_64 | |
ArchPPC | |
ArchPPC_64 | |
ArchS390X | |
ArchSPARC | |
ArchSPARC64 | |
ArchARM | |
ArchAArch64 | |
ArchAlpha | |
ArchMipseb | |
ArchMipsel | |
ArchJavaScript |
Operating systems that the native code generator knows about. Having OSUnknown should produce a sensible default, but no promises.
Constructors
OSUnknown | |
OSLinux | |
OSDarwin | |
OSSolaris2 | |
OSMinGW32 | |
OSFreeBSD | |
OSDragonFly | |
OSOpenBSD | |
OSNetBSD | |
OSKFreeBSD | |
OSHaiku | |
OSQNXNTO | |
OSAIX | |
OSHurd |
ARM Instruction Set Architecture, Extensions and ABI
Byte ordering.
Constructors
BigEndian | most-significant-byte occurs in lowest address. |
LittleEndian | least-significant-byte occurs in lowest address. |
Instances
Bounded ByteOrder | Since: base-4.11.0.0 |
Enum ByteOrder | Since: base-4.11.0.0 |
Defined in GHC.ByteOrder Methods succ :: ByteOrder -> ByteOrder # pred :: ByteOrder -> ByteOrder # fromEnum :: ByteOrder -> Int # enumFrom :: ByteOrder -> [ByteOrder] # enumFromThen :: ByteOrder -> ByteOrder -> [ByteOrder] # enumFromTo :: ByteOrder -> ByteOrder -> [ByteOrder] # enumFromThenTo :: ByteOrder -> ByteOrder -> ByteOrder -> [ByteOrder] # | |
Eq ByteOrder | Since: base-4.11.0.0 |
Ord ByteOrder | Since: base-4.11.0.0 |
Read ByteOrder | Since: base-4.11.0.0 |
Show ByteOrder | Since: base-4.11.0.0 |
target32Bit :: Platform -> Bool Source #
This predicate tells us whether the platform is 32-bit.
osElfTarget :: OS -> Bool Source #
This predicate tells us whether the OS supports ELF-like shared libraries.
osMachOTarget :: OS -> Bool Source #
This predicate tells us whether the OS support Mach-O shared libraries.
osSubsectionsViaSymbols :: OS -> Bool Source #
platformWordSizeInBits :: Platform -> Int Source #
platformMinInt :: Platform -> Integer Source #
Minimum representable Int value for the given platform
platformMaxInt :: Platform -> Integer Source #
Maximum representable Int value for the given platform
platformMaxWord :: Platform -> Integer Source #
Maximum representable Word value for the given platform
platformInIntRange :: Platform -> Integer -> Bool Source #
Test if the given Integer is representable with a platform Int
platformInWordRange :: Platform -> Integer -> Bool Source #
Test if the given Integer is representable with a platform Word
platformCConvNeedsExtension :: Platform -> Bool Source #
For some architectures the C calling convention is that any integer shorter than 64 bits is replaced by its 64 bits representation using sign or zero extension.
data PlatformMisc Source #
Platform-specific settings formerly hard-coded in Config.hs.
These should probably be all be triaged whether they can be computed from
other settings or belong in another another place (like Platform
above).
Constructors
stringEncodeArch :: Arch -> String Source #
See Note [Platform Syntax].
stringEncodeOS :: OS -> String Source #
See Note [Platform Syntax].
data SseVersion Source #
x86 SSE instructions
Instances
Eq SseVersion Source # | |
Defined in GHC.Platform | |
Ord SseVersion Source # | |
Defined in GHC.Platform Methods compare :: SseVersion -> SseVersion -> Ordering # (<) :: SseVersion -> SseVersion -> Bool # (<=) :: SseVersion -> SseVersion -> Bool # (>) :: SseVersion -> SseVersion -> Bool # (>=) :: SseVersion -> SseVersion -> Bool # max :: SseVersion -> SseVersion -> SseVersion # min :: SseVersion -> SseVersion -> SseVersion # |
data BmiVersion Source #
x86 BMI (bit manipulation) instructions
Instances
Eq BmiVersion Source # | |
Defined in GHC.Platform | |
Ord BmiVersion Source # | |
Defined in GHC.Platform Methods compare :: BmiVersion -> BmiVersion -> Ordering # (<) :: BmiVersion -> BmiVersion -> Bool # (<=) :: BmiVersion -> BmiVersion -> Bool # (>) :: BmiVersion -> BmiVersion -> Bool # (>=) :: BmiVersion -> BmiVersion -> Bool # max :: BmiVersion -> BmiVersion -> BmiVersion # min :: BmiVersion -> BmiVersion -> BmiVersion # |