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

GHC.Types.RepType

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) See also Note [Getting from RuntimeRep to PrimRep]

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

Like typePrimRep, but assumes that there is precisely one PrimRep output; an empty list of PrimReps becomes a VoidRep. This assumption holds after unarise, see Note [Post-unarisation invariants]. Before unarise it may or may not hold. See also Note [RuntimeRep and PrimRep] and Note [VoidRep]

typeMonoPrimRep_maybe :: Type -> Maybe [PrimRep] Source #

Like typePrimRep, but returns Nothing instead of panicking, when

  • The ty was not of form TYPE rep
  • rep was not monomorphic

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

Take a type of kind RuntimeRep and extract the list of PrimRep that it encodes. See also Note [Getting from RuntimeRep to PrimRep]

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. See also Note [RuntimeRep and PrimRep] in GHC.Types.RepType and Note [VoidRep] in GHC.Types.RepType.

Constructors

VoidRep 
LiftedRep 
UnliftedRep

Unlifted pointer

Int8Rep

Signed, 8-bit value

Int16Rep

Signed, 16-bit value

Int32Rep

Signed, 32-bit value

Int64Rep

Signed, 64 bit value

IntRep

Signed, word-sized value

Word8Rep

Unsigned, 8 bit value

Word16Rep

Unsigned, 16 bit value

Word32Rep

Unsigned, 32 bit value

Word64Rep

Unsigned, 64 bit value

WordRep

Unsigned, word-sized value

AddrRep

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

FloatRep 
DoubleRep 
VecRep Int PrimElemRep

A vector

Instances

Instances details
Data PrimRep Source # 
Instance details

Defined in GHC.Core.TyCon

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PrimRep -> c PrimRep Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PrimRep Source #

toConstr :: PrimRep -> Constr Source #

dataTypeOf :: PrimRep -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PrimRep) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PrimRep) Source #

gmapT :: (forall b. Data b => b -> b) -> PrimRep -> PrimRep Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PrimRep -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PrimRep -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> PrimRep -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PrimRep -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PrimRep -> m PrimRep Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PrimRep -> m PrimRep Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PrimRep -> m PrimRep Source #

Show PrimRep Source # 
Instance details

Defined in GHC.Core.TyCon

Binary PrimRep Source # 
Instance details

Defined in GHC.Core.TyCon

Outputable PrimRep Source # 
Instance details

Defined in GHC.Core.TyCon

Methods

ppr :: PrimRep -> SDoc Source #

Eq PrimRep Source # 
Instance details

Defined in GHC.Core.TyCon

Methods

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

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

Ord PrimRep Source # 
Instance details

Defined in GHC.Core.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. See also Note [RuntimeRep and PrimRep]

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. See also Note [Getting from RuntimeRep to PrimRep]

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

Like tyConPrimRep, but assumed that there is precisely zero or one PrimRep output See also Note [Getting from RuntimeRep to PrimRep] and Note [VoidRep]

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.

(# Int# | Maybe Int | (# 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

Instances details
Outputable SlotTy Source # 
Instance details

Defined in GHC.Types.RepType

Methods

ppr :: SlotTy -> SDoc Source #

Eq SlotTy Source # 
Instance details

Defined in GHC.Types.RepType

Methods

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

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

Ord SlotTy Source # 
Instance details

Defined in GHC.Types.RepType