ghc-lib-parser-0.20190703: The GHC API, decoupled from GHC versions

Safe HaskellNone
LanguageHaskell2010

RepType

Contents

Synopsis

Code generator views onto Types

unwrapType :: Type -> Type Source #

Gets rid of the stuff that prevents us from understanding the runtime representation of a type. Including: 1. Casts 2. Newtypes 3. Foralls 4. Synonyms But not type/data families, because we don't have the envs to hand.

Predicates on types

isVoidTy :: Type -> Bool Source #

True if the type has zero width.

Type representation for the code generator

typePrimRep :: HasDebugCallStack => Type -> [PrimRep] Source #

Discovers the primitive representation of a Type. Returns a list of PrimRep: it's a list because of the possibility of no runtime representation (void) or multiple (unboxed tuple/sum)

typePrimRep1 :: HasDebugCallStack => UnaryType -> PrimRep Source #

Like typePrimRep, but assumes that there is precisely one PrimRep output; an empty list of PrimReps becomes a VoidRep

runtimeRepPrimRep :: HasDebugCallStack => SDoc -> Type -> [PrimRep] Source #

Take a type of kind RuntimeRep and extract the list of PrimRep that it encodes.

data PrimRep Source #

A PrimRep is an abstraction of a type. It contains information that the code generator needs in order to pass arguments, return results, and store values of this type.

Constructors

VoidRep 
LiftedRep 
UnliftedRep

Unlifted pointer

Int8Rep

Signed, 8-bit value

Int16Rep

Signed, 16-bit value

IntRep

Signed, word-sized value

WordRep

Unsigned, word-sized value

Int64Rep

Signed, 64 bit value (with 32-bit words only)

Word8Rep

Unsigned, 8 bit value

Word16Rep

Unsigned, 16 bit value

Word64Rep

Unsigned, 64 bit value (with 32-bit words only)

AddrRep

A pointer, but not to a Haskell value (use '(Un)liftedRep')

FloatRep 
DoubleRep 
VecRep Int PrimElemRep

A vector

Instances
Eq PrimRep Source # 
Instance details

Defined in TyCon

Methods

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

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

Show PrimRep Source # 
Instance details

Defined in TyCon

Outputable PrimRep Source # 
Instance details

Defined in TyCon

primRepToType :: PrimRep -> Type Source #

Convert a PrimRep back to a Type. Used only in the unariser to give types to fresh Ids. Really, only the type's representation matters.

tyConPrimRep :: HasDebugCallStack => TyCon -> [PrimRep] Source #

Find the runtime representation of a TyCon. Defined here to avoid module loops. Returns a list of the register shapes necessary.

tyConPrimRep1 :: HasDebugCallStack => TyCon -> PrimRep Source #

Like tyConPrimRep, but assumed that there is precisely zero or one PrimRep output

Unboxed sum representation type

ubxSumRepType :: [[PrimRep]] -> [SlotTy] Source #

Given the arguments of a sum type constructor application, return the unboxed sum rep type.

E.g.

( | Maybe Int | (, Float) #)

We call `ubxSumRepType [ [IntRep], [LiftedRep], [IntRep, FloatRep] ]`, which returns [WordSlot, PtrSlot, WordSlot, FloatSlot]

INVARIANT: Result slots are sorted (via Ord SlotTy), except that at the head of the list we have the slot for the tag.

layoutUbxSum :: SortedSlotTys -> [SlotTy] -> [Int] Source #

data SlotTy Source #

Instances
Eq SlotTy Source # 
Instance details

Defined in RepType

Methods

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

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

Ord SlotTy Source # 
Instance details

Defined in RepType

Outputable SlotTy Source # 
Instance details

Defined in RepType