Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- assignToTypedExprs :: [TypedExpr] -> [JExpr] -> JStat
- assignCoerce1 :: [TypedExpr] -> [TypedExpr] -> JStat
- assignToExprCtx :: ExprCtx -> [JExpr] -> JStat
- isUnboxableCon :: DataCon -> Bool
- isUnboxable :: VarType -> Bool
- data SlotCount
- slotCount :: SlotCount -> Int
- varSize :: VarType -> Int
- varSlotCount :: VarType -> SlotCount
- typeSize :: Type -> Int
- isVoid :: VarType -> Bool
- isPtr :: VarType -> Bool
- isSingleVar :: VarType -> Bool
- isMultiVar :: VarType -> Bool
- isMatchable :: [VarType] -> Bool
- tyConVt :: HasDebugCallStack => TyCon -> [VarType]
- idVt :: HasDebugCallStack => Id -> [VarType]
- typeVt :: HasDebugCallStack => Type -> [VarType]
- uTypeVt :: HasDebugCallStack => UnaryType -> VarType
- primRepVt :: HasDebugCallStack => PrimRep -> VarType
- typePrimRep' :: HasDebugCallStack => UnaryType -> [PrimRep]
- tyConPrimRep' :: HasDebugCallStack => TyCon -> [PrimRep]
- kindPrimRep' :: HasDebugCallStack => SDoc -> Kind -> [PrimRep]
- primTypeVt :: HasDebugCallStack => Type -> VarType
- argVt :: StgArg -> VarType
- dataConType :: DataCon -> Type
- isBoolDataCon :: DataCon -> Bool
- fixedLayout :: [VarType] -> CILayout
- stackSlotType :: Id -> VarType
- idPrimReps :: Id -> [PrimRep]
- typePrimReps :: Type -> [PrimRep]
- primRepSize :: PrimRep -> SlotCount
- assocPrimReps :: [PrimRep] -> [JExpr] -> [(PrimRep, [JExpr])]
- assocIdPrimReps :: Id -> [JExpr] -> [(PrimRep, [JExpr])]
- assocIdExprs :: Id -> [JExpr] -> [TypedExpr]
- mkArityTag :: Int -> Int -> Int
- toTypeList :: [VarType] -> [Int]
- bindingRefs :: UniqFM Id CgStgExpr -> CgStgBinding -> Set Id
- rhsRefs :: UniqFM Id CgStgExpr -> CgStgRhs -> Set Id
- exprRefs :: UniqFM Id CgStgExpr -> CgStgExpr -> Set Id
- altRefs :: UniqFM Id CgStgExpr -> CgStgAlt -> Set Id
- argRefs :: UniqFM Id CgStgExpr -> StgArg -> Set Id
- hasExport :: CgStgBinding -> Bool
- collectTopIds :: CgStgBinding -> [Id]
- collectIds :: UniqFM Id CgStgExpr -> CgStgBinding -> [Id]
- removeTick :: CgStgExpr -> CgStgExpr
- type LiveVars = DVarSet
- liveStatic :: LiveVars -> LiveVars
- liveVars :: LiveVars -> LiveVars
- stgTopBindLive :: CgStgTopBinding -> [(Id, LiveVars)]
- stgBindLive :: CgStgBinding -> [(Id, LiveVars)]
- stgBindRhsLive :: CgStgBinding -> LiveVars
- stgRhsLive :: CgStgRhs -> LiveVars
- stgArgLive :: StgArg -> LiveVars
- stgExprLive :: Bool -> CgStgExpr -> LiveVars
- stgAltLive :: CgStgAlt -> LiveVars
- stgLetNoEscapeLive :: Bool -> StgBinding -> StgExpr -> LiveVars
- bindees :: CgStgBinding -> [Id]
- isUpdatableRhs :: CgStgRhs -> Bool
- stgLneLive :: CgStgBinding -> [Id]
- stgLneLive' :: CgStgBinding -> [Id]
- stgLneLiveExpr :: CgStgRhs -> [Id]
- isInlineExpr :: UniqSet Id -> CgStgExpr -> (UniqSet Id, Bool)
- inspectInlineBinding :: UniqSet Id -> CgStgBinding -> UniqSet Id
- inspectInlineRhs :: UniqSet Id -> Id -> CgStgRhs -> UniqSet Id
- isInlineForeignCall :: ForeignCall -> Bool
- isInlineApp :: UniqSet Id -> Id -> [StgArg] -> Bool
Documentation
assignCoerce1 :: [TypedExpr] -> [TypedExpr] -> JStat Source #
Assign first expr only (if it exists), performing coercions between some PrimReps (e.g. StablePtr# and Addr#).
Core Utils
isUnboxableCon :: DataCon -> Bool Source #
can we unbox C x to x, only if x is represented as a Number
isUnboxable :: VarType -> Bool Source #
one-constructor types with one primitive field represented as a JS Number can be unboxed
Number of slots occupied by a PrimRep
varSlotCount :: VarType -> SlotCount Source #
isSingleVar :: VarType -> Bool Source #
isMultiVar :: VarType -> Bool Source #
isMatchable :: [VarType] -> Bool Source #
can we pattern match on these values in a case?
typePrimRep' :: HasDebugCallStack => UnaryType -> [PrimRep] Source #
tyConPrimRep' :: HasDebugCallStack => TyCon -> [PrimRep] Source #
Find the primitive representation of a TyCon
. Defined here to
avoid module loops. Call this only on unlifted tycons.
kindPrimRep' :: HasDebugCallStack => SDoc -> Kind -> [PrimRep] Source #
Take a kind (of shape TYPE rr
) and produce the PrimRep
s
of values of types of this kind.
primTypeVt :: HasDebugCallStack => Type -> VarType Source #
dataConType :: DataCon -> Type Source #
isBoolDataCon :: DataCon -> Bool Source #
fixedLayout :: [VarType] -> CILayout Source #
stackSlotType :: Id -> VarType Source #
idPrimReps :: Id -> [PrimRep] Source #
typePrimReps :: Type -> [PrimRep] Source #
primRepSize :: PrimRep -> SlotCount Source #
assocPrimReps :: [PrimRep] -> [JExpr] -> [(PrimRep, [JExpr])] Source #
Associate the given values to each RrimRep in the given order, taking into account the number of slots per PrimRep
assocIdPrimReps :: Id -> [JExpr] -> [(PrimRep, [JExpr])] Source #
Associate the given values to the Id's PrimReps, taking into account the number of slots per PrimRep
assocIdExprs :: Id -> [JExpr] -> [TypedExpr] Source #
Associate the given JExpr to the Id's PrimReps, taking into account the number of slots per PrimRep
toTypeList :: [VarType] -> [Int] Source #
Stg Utils
bindingRefs :: UniqFM Id CgStgExpr -> CgStgBinding -> Set Id Source #
collect Ids that this binding refers to (does not include the bindees themselves) first argument is Id -> StgExpr map for unfloated arguments
hasExport :: CgStgBinding -> Bool Source #
collectTopIds :: CgStgBinding -> [Id] Source #
collectIds :: UniqFM Id CgStgExpr -> CgStgBinding -> [Id] Source #
removeTick :: CgStgExpr -> CgStgExpr Source #
liveStatic :: LiveVars -> LiveVars Source #
stgTopBindLive :: CgStgTopBinding -> [(Id, LiveVars)] Source #
stgBindLive :: CgStgBinding -> [(Id, LiveVars)] Source #
stgRhsLive :: CgStgRhs -> LiveVars Source #
stgArgLive :: StgArg -> LiveVars Source #
stgAltLive :: CgStgAlt -> LiveVars Source #
stgLetNoEscapeLive :: Bool -> StgBinding -> StgExpr -> LiveVars Source #
bindees :: CgStgBinding -> [Id] Source #
isUpdatableRhs :: CgStgRhs -> Bool Source #
stgLneLive :: CgStgBinding -> [Id] Source #
stgLneLive' :: CgStgBinding -> [Id] Source #
stgLneLiveExpr :: CgStgRhs -> [Id] Source #
isInlineExpr :: UniqSet Id -> CgStgExpr -> (UniqSet Id, Bool) Source #
returns True if the expression is definitely inline
inspectInlineBinding :: UniqSet Id -> CgStgBinding -> UniqSet Id Source #