| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
RepType
Synopsis
- type UnaryType = Type
 - type NvUnaryType = Type
 - isNvUnaryType :: Type -> Bool
 - unwrapType :: Type -> Type
 - isVoidTy :: Type -> Bool
 - typePrimRep :: HasDebugCallStack => Type -> [PrimRep]
 - typePrimRep1 :: HasDebugCallStack => UnaryType -> PrimRep
 - runtimeRepPrimRep :: HasDebugCallStack => SDoc -> Type -> [PrimRep]
 - typePrimRepArgs :: HasDebugCallStack => Type -> [PrimRep]
 - data PrimRep
 - primRepToType :: PrimRep -> Type
 - countFunRepArgs :: Arity -> Type -> RepArity
 - countConRepArgs :: DataCon -> RepArity
 - tyConPrimRep :: HasDebugCallStack => TyCon -> [PrimRep]
 - tyConPrimRep1 :: HasDebugCallStack => TyCon -> PrimRep
 - ubxSumRepType :: [[PrimRep]] -> [SlotTy]
 - layoutUbxSum :: SortedSlotTys -> [SlotTy] -> [Int]
 - typeSlotTy :: UnaryType -> Maybe SlotTy
 - data SlotTy
 - slotPrimRep :: SlotTy -> PrimRep
 - primRepSlot :: PrimRep -> SlotTy
 
Code generator views onto Types
type NvUnaryType = Type Source #
isNvUnaryType :: Type -> Bool Source #
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
Type representation for the code generator
typePrimRep :: HasDebugCallStack => Type -> [PrimRep] Source #
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]
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]
typePrimRepArgs :: HasDebugCallStack => Type -> [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 RepType
 and Note [VoidRep] in 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 (with 32-bit words only)  | 
| 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 (with 32-bit words only)  | 
| WordRep | Unsigned, word-sized value  | 
| AddrRep | A pointer, but not to a Haskell value (use '(Un)liftedRep')  | 
| FloatRep | |
| DoubleRep | |
| VecRep Int PrimElemRep | A vector  | 
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]
countConRepArgs :: DataCon -> RepArity Source #
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.
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 #
Constructors
| PtrSlot | |
| WordSlot | |
| Word64Slot | |
| FloatSlot | |
| DoubleSlot | 
slotPrimRep :: SlotTy -> PrimRep Source #
primRepSlot :: PrimRep -> SlotTy Source #