ghc-9.2.4: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Platform

Description

Platform description

Synopsis

Documentation

data Platform Source #

Platform description

This is used to describe platforms so that we can generate code for them.

Constructors

Platform 

Fields

Instances

Instances details
Read Platform Source # 
Instance details

Defined in GHC.Platform

Show Platform Source # 
Instance details

Defined in GHC.Platform

Eq Platform Source # 
Instance details

Defined in GHC.Platform

OutputableP Platform CmmGraph Source # 
Instance details

Defined in GHC.Cmm.Ppr

Methods

pdoc :: Platform -> CmmGraph -> SDoc Source #

OutputableP Platform CmmInfoTable Source # 
Instance details

Defined in GHC.Cmm.Ppr.Decl

OutputableP Platform CmmStatic Source # 
Instance details

Defined in GHC.Cmm.Ppr.Decl

OutputableP Platform CmmTopInfo Source # 
Instance details

Defined in GHC.Cmm.Ppr

OutputableP Platform CLabel Source # 
Instance details

Defined in GHC.Cmm.CLabel

Methods

pdoc :: Platform -> CLabel -> SDoc Source #

OutputableP Platform CmmExpr Source # 
Instance details

Defined in GHC.Cmm.Ppr.Expr

Methods

pdoc :: Platform -> CmmExpr -> SDoc Source #

OutputableP Platform CmmLit Source # 
Instance details

Defined in GHC.Cmm.Ppr.Expr

Methods

pdoc :: Platform -> CmmLit -> SDoc Source #

OutputableP Platform ForeignTarget Source # 
Instance details

Defined in GHC.Cmm.Ppr

OutputableP Platform LiveInfo Source # 
Instance details

Defined in GHC.CmmToAsm.Reg.Liveness

Methods

pdoc :: Platform -> LiveInfo -> SDoc Source #

OutputableP Platform Instr Source # 
Instance details

Defined in GHC.CmmToAsm.SPARC.Ppr

Methods

pdoc :: Platform -> Instr -> SDoc Source #

OutputableP Platform CgLoc Source # 
Instance details

Defined in GHC.StgToCmm.Closure

Methods

pdoc :: Platform -> CgLoc -> SDoc Source #

OutputableP Platform CgIdInfo Source # 
Instance details

Defined in GHC.StgToCmm.Monad

Methods

pdoc :: Platform -> CgIdInfo -> SDoc Source #

OutputableP Platform (GenCmmStatics a) Source # 
Instance details

Defined in GHC.Cmm.Ppr.Decl

OutputableP Platform (CmmNode e x) Source # 
Instance details

Defined in GHC.Cmm.Ppr

Methods

pdoc :: Platform -> CmmNode e x -> SDoc Source #

(OutputableP Platform d, OutputableP Platform info, OutputableP Platform i) => OutputableP Platform (GenCmmDecl d info i) Source # 
Instance details

Defined in GHC.Cmm.Ppr.Decl

Methods

pdoc :: Platform -> GenCmmDecl d info i -> SDoc Source #

OutputableP Platform (Block CmmNode C C) Source # 
Instance details

Defined in GHC.Cmm.Ppr

OutputableP Platform (Block CmmNode C O) Source # 
Instance details

Defined in GHC.Cmm.Ppr

OutputableP Platform (Block CmmNode O C) Source # 
Instance details

Defined in GHC.Cmm.Ppr

OutputableP Platform (Block CmmNode O O) Source # 
Instance details

Defined in GHC.Cmm.Ppr

OutputableP Platform (Graph CmmNode e x) Source # 
Instance details

Defined in GHC.Cmm.Ppr

Methods

pdoc :: Platform -> Graph CmmNode e x -> SDoc Source #

platformArch :: Platform -> Arch Source #

Platform architecture

platformOS :: Platform -> OS Source #

Platform OS

data ArchOS Source #

Platform architecture and OS.

Constructors

ArchOS 

Fields

Instances

Instances details
Read ArchOS 
Instance details

Defined in GHC.Platform.ArchOS

Show ArchOS 
Instance details

Defined in GHC.Platform.ArchOS

Eq ArchOS 
Instance details

Defined in GHC.Platform.ArchOS

Methods

(==) :: ArchOS -> ArchOS -> Bool #

(/=) :: ArchOS -> ArchOS -> Bool #

data Arch Source #

Architectures

TODO: It might be nice to extend these constructors with information about what instruction set extensions an architecture might support.

Instances

Instances details
Read Arch 
Instance details

Defined in GHC.Platform.ArchOS

Show Arch 
Instance details

Defined in GHC.Platform.ArchOS

Eq Arch 
Instance details

Defined in GHC.Platform.ArchOS

Methods

(==) :: Arch -> Arch -> Bool #

(/=) :: Arch -> Arch -> Bool #

data OS Source #

Operating systems.

Using OSUnknown to generate code should produce a sensible default, but no promises.

Instances

Instances details
Read OS 
Instance details

Defined in GHC.Platform.ArchOS

Show OS 
Instance details

Defined in GHC.Platform.ArchOS

Eq OS 
Instance details

Defined in GHC.Platform.ArchOS

Methods

(==) :: OS -> OS -> Bool #

(/=) :: OS -> OS -> Bool #

data ArmISA Source #

ARM Instruction Set Architecture

Constructors

ARMv5 
ARMv6 
ARMv7 

Instances

Instances details
Read ArmISA 
Instance details

Defined in GHC.Platform.ArchOS

Show ArmISA 
Instance details

Defined in GHC.Platform.ArchOS

Eq ArmISA 
Instance details

Defined in GHC.Platform.ArchOS

Methods

(==) :: ArmISA -> ArmISA -> Bool #

(/=) :: ArmISA -> ArmISA -> Bool #

data ArmISAExt Source #

ARM extensions

Constructors

VFPv2 
VFPv3 
VFPv3D16 
NEON 
IWMMX2 

data ArmABI Source #

ARM ABI

Constructors

SOFT 
SOFTFP 
HARD 

Instances

Instances details
Read ArmABI 
Instance details

Defined in GHC.Platform.ArchOS

Show ArmABI 
Instance details

Defined in GHC.Platform.ArchOS

Eq ArmABI 
Instance details

Defined in GHC.Platform.ArchOS

Methods

(==) :: ArmABI -> ArmABI -> Bool #

(/=) :: ArmABI -> ArmABI -> Bool #

data PPC_64ABI Source #

PowerPC 64-bit ABI

Constructors

ELF_V1

PowerPC64

ELF_V2

PowerPC64 LE

data ByteOrder Source #

Byte ordering.

Constructors

BigEndian

most-significant-byte occurs in lowest address.

LittleEndian

least-significant-byte occurs in lowest address.

Instances

Instances details
Bounded ByteOrder

Since: base-4.11.0.0

Instance details

Defined in GHC.ByteOrder

Enum ByteOrder

Since: base-4.11.0.0

Instance details

Defined in GHC.ByteOrder

Generic ByteOrder 
Instance details

Defined in GHC.ByteOrder

Associated Types

type Rep ByteOrder :: Type -> Type Source #

Read ByteOrder

Since: base-4.11.0.0

Instance details

Defined in GHC.ByteOrder

Show ByteOrder

Since: base-4.11.0.0

Instance details

Defined in GHC.ByteOrder

Eq ByteOrder

Since: base-4.11.0.0

Instance details

Defined in GHC.ByteOrder

Ord ByteOrder

Since: base-4.11.0.0

Instance details

Defined in GHC.ByteOrder

type Rep ByteOrder

Since: base-4.15.0.0

Instance details

Defined in GHC.ByteOrder

type Rep ByteOrder = D1 ('MetaData "ByteOrder" "GHC.ByteOrder" "base" 'False) (C1 ('MetaCons "BigEndian" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LittleEndian" 'PrefixI 'False) (U1 :: Type -> Type))

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.

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).

data SseVersion Source #

x86 SSE instructions

Constructors

SSE1 
SSE2 
SSE3 
SSE4 
SSE42 

data BmiVersion Source #

x86 BMI (bit manipulation) instructions

Constructors

BMI1 
BMI2 

Platform constants

data PlatformConstants Source #

Constructors

PlatformConstants 

Fields

lookupPlatformConstants :: [FilePath] -> IO (Maybe PlatformConstants) Source #

Try to locate "DerivedConstants.h" file in the given dirs and to parse the PlatformConstants from it.

See Note [Platform constants]

Shared libraries