ghc-9.15: The GHC API
Safe HaskellNone
LanguageGHC2021

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
Eq Platform Source # 
Instance details

Defined in GHC.Platform

Ord Platform Source # 
Instance details

Defined in GHC.Platform

Read Platform Source # 
Instance details

Defined in GHC.Platform

Show Platform Source # 
Instance details

Defined in GHC.Platform

OutputableP Platform CmmGraph Source # 
Instance details

Defined in GHC.Cmm

Methods

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

OutputableP Platform CmmInfoTable Source # 
Instance details

Defined in GHC.Cmm

OutputableP Platform CmmStatic Source # 
Instance details

Defined in GHC.Cmm

OutputableP Platform CmmTopInfo Source # 
Instance details

Defined in GHC.Cmm

OutputableP Platform CLabel Source # 
Instance details

Defined in GHC.Cmm.CLabel

Methods

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

OutputableP Platform InfoProvEnt Source # 
Instance details

Defined in GHC.Cmm.CLabel

OutputableP Platform DebugBlock Source # 
Instance details

Defined in GHC.Cmm.DebugBlock

OutputableP Platform UnwindExpr Source # 
Instance details

Defined in GHC.Cmm.DebugBlock

OutputableP Platform UnwindPoint Source # 
Instance details

Defined in GHC.Cmm.DebugBlock

OutputableP Platform CmmExpr Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

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

OutputableP Platform CmmLit Source # 
Instance details

Defined in GHC.Cmm.Expr

Methods

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

OutputableP Platform ForeignTarget Source # 
Instance details

Defined in GHC.Cmm.Node

OutputableP Platform DwarfFrameBlock Source # 
Instance details

Defined in GHC.CmmToAsm.Dwarf.Types

OutputableP Platform LiveInfo Source # 
Instance details

Defined in GHC.CmmToAsm.Reg.Liveness

Methods

pdoc :: Platform -> LiveInfo -> 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

OutputableP Platform (CmmNode e x) Source # 
Instance details

Defined in GHC.Cmm.Node

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

Methods

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

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

Defined in GHC.Cmm.Node

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

Defined in GHC.Cmm.Node

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

Defined in GHC.Cmm.Node

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

Defined in GHC.Cmm.Node

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

Defined in GHC.Cmm.Node

Methods

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

platformArch :: Platform -> Arch Source #

Platform architecture

platformOS :: Platform -> OS Source #

Platform OS

data ArchOS #

Constructors

ArchOS 

Fields

Instances

Instances details
Eq ArchOS # 
Instance details

Defined in GHC.Platform.ArchOS

Ord ArchOS # 
Instance details

Defined in GHC.Platform.ArchOS

Read ArchOS # 
Instance details

Defined in GHC.Platform.ArchOS

Show ArchOS # 
Instance details

Defined in GHC.Platform.ArchOS

data OS #

Instances

Instances details
Eq OS # 
Instance details

Defined in GHC.Platform.ArchOS

Methods

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

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

Ord OS # 
Instance details

Defined in GHC.Platform.ArchOS

Methods

compare :: OS -> OS -> Ordering Source #

(<) :: OS -> OS -> Bool Source #

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

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

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

max :: OS -> OS -> OS Source #

min :: OS -> OS -> OS Source #

Read OS # 
Instance details

Defined in GHC.Platform.ArchOS

Show OS # 
Instance details

Defined in GHC.Platform.ArchOS

data ArmISA #

Constructors

ARMv5 
ARMv6 
ARMv7 

Instances

Instances details
Eq ArmISA # 
Instance details

Defined in GHC.Platform.ArchOS

Ord ArmISA # 
Instance details

Defined in GHC.Platform.ArchOS

Read ArmISA # 
Instance details

Defined in GHC.Platform.ArchOS

Show ArmISA # 
Instance details

Defined in GHC.Platform.ArchOS

data ArmABI #

Constructors

SOFT 
SOFTFP 
HARD 

Instances

Instances details
Eq ArmABI # 
Instance details

Defined in GHC.Platform.ArchOS

Ord ArmABI # 
Instance details

Defined in GHC.Platform.ArchOS

Read ArmABI # 
Instance details

Defined in GHC.Platform.ArchOS

Show ArmABI # 
Instance details

Defined in GHC.Platform.ArchOS

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
Eq ByteOrder Source #

Since: base-4.11.0.0

Instance details

Defined in GHC.Internal.ByteOrder

Ord ByteOrder Source #

Since: base-4.11.0.0

Instance details

Defined in GHC.Internal.ByteOrder

Bounded ByteOrder Source #

Since: base-4.11.0.0

Instance details

Defined in GHC.Internal.ByteOrder

Enum ByteOrder Source #

Since: base-4.11.0.0

Instance details

Defined in GHC.Internal.ByteOrder

Generic ByteOrder Source # 
Instance details

Defined in GHC.Internal.ByteOrder

Associated Types

type Rep ByteOrder

Since: base-4.15.0.0

Instance details

Defined in GHC.Internal.ByteOrder

type Rep ByteOrder = D1 ('MetaData "ByteOrder" "GHC.Internal.ByteOrder" "ghc-internal" 'False) (C1 ('MetaCons "BigEndian" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LittleEndian" 'PrefixI 'False) (U1 :: Type -> Type))
Read ByteOrder Source #

Since: base-4.11.0.0

Instance details

Defined in GHC.Internal.ByteOrder

Show ByteOrder Source #

Since: base-4.11.0.0

Instance details

Defined in GHC.Internal.ByteOrder

type Rep ByteOrder Source #

Since: base-4.15.0.0

Instance details

Defined in GHC.Internal.ByteOrder

type Rep ByteOrder = D1 ('MetaData "ByteOrder" "GHC.Internal.ByteOrder" "ghc-internal" '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.

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.

platformHasRTSLinker :: Platform -> Bool Source #

Does this platform have an RTS linker?

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 BmiVersion Source #

x86 BMI (bit manipulation) instructions

Constructors

BMI1 
BMI2 

SSE and AVX

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