Safe Haskell | None |
---|---|
Language | GHC2021 |
Synopsis
- mkArgDescr :: Platform -> [Id] -> ArgDescr
- emitCall :: (Convention, Convention) -> CmmExpr -> [CmmExpr] -> FCode ReturnKind
- emitReturn :: [CmmExpr] -> FCode ReturnKind
- adjustHpBackwards :: FCode ()
- emitClosureProcAndInfoTable :: Bool -> Id -> LambdaFormInfo -> CmmInfoTable -> [NonVoid Id] -> ((Int, LocalReg, [LocalReg]) -> FCode ()) -> FCode ()
- emitClosureAndInfoTable :: Platform -> CmmInfoTable -> Convention -> [LocalReg] -> FCode () -> FCode ()
- slowCall :: CmmExpr -> [StgArg] -> FCode ReturnKind
- directCall :: Convention -> CLabel -> RepArity -> [StgArg] -> FCode ReturnKind
- data FieldOffOrPadding a
- data ClosureHeader
- mkVirtHeapOffsets :: Profile -> ClosureHeader -> [NonVoid (PrimRep, a)] -> (WordOff, WordOff, [(NonVoid a, ByteOff)])
- mkVirtHeapOffsetsWithPadding :: Profile -> ClosureHeader -> [NonVoid (PrimRep, a)] -> (WordOff, WordOff, [FieldOffOrPadding a])
- mkVirtConstrOffsets :: Profile -> [NonVoid (PrimRep, a)] -> (WordOff, WordOff, [(NonVoid a, ByteOff)])
- mkVirtConstrSizes :: Profile -> [PrimRep] -> (WordOff, WordOff)
- getHpRelOffset :: VirtualHpOffset -> FCode CmmExpr
- data ArgRep
- toArgRep :: Platform -> PrimRep -> ArgRep
- toArgRepOrV :: Platform -> PrimOrVoidRep -> ArgRep
- idArgRep :: Platform -> Id -> ArgRep
- argRepSizeW :: Platform -> ArgRep -> WordOff
- getArgAmode :: NonVoid StgArg -> FCode CmmExpr
- getNonVoidArgAmodes :: [StgArg] -> FCode [CmmExpr]
Documentation
emitCall :: (Convention, Convention) -> CmmExpr -> [CmmExpr] -> FCode ReturnKind Source #
emitCall conv fun args
makes a call to the entry-code of fun
,
using the call/return convention conv
, passing args
, and
returning the results to the current sequel.
emitReturn :: [CmmExpr] -> FCode ReturnKind Source #
Return multiple values to the sequel
If the sequel is Return
return (x,y)
If the sequel is AssignTo [p,q]
p=x; q=y;
adjustHpBackwards :: FCode () Source #
emitClosureProcAndInfoTable :: Bool -> Id -> LambdaFormInfo -> CmmInfoTable -> [NonVoid Id] -> ((Int, LocalReg, [LocalReg]) -> FCode ()) -> FCode () Source #
emitClosureAndInfoTable :: Platform -> CmmInfoTable -> Convention -> [LocalReg] -> FCode () -> FCode () Source #
directCall :: Convention -> CLabel -> RepArity -> [StgArg] -> FCode ReturnKind Source #
data ClosureHeader Source #
Used to tell the various mkVirtHeapOffsets
functions what kind
of header the object has. This will be accounted for in the
offsets of the fields returned.
mkVirtHeapOffsets :: Profile -> ClosureHeader -> [NonVoid (PrimRep, a)] -> (WordOff, WordOff, [(NonVoid a, ByteOff)]) Source #
mkVirtHeapOffsetsWithPadding :: Profile -> ClosureHeader -> [NonVoid (PrimRep, a)] -> (WordOff, WordOff, [FieldOffOrPadding a]) Source #
mkVirtConstrOffsets :: Profile -> [NonVoid (PrimRep, a)] -> (WordOff, WordOff, [(NonVoid a, ByteOff)]) Source #
Just like mkVirtHeapOffsets, but for constructors
mkVirtConstrSizes :: Profile -> [PrimRep] -> (WordOff, WordOff) Source #
Just like mkVirtConstrOffsets, but used when we don't have the actual arguments. Useful when e.g. generating info tables; we just need to know sizes of pointer and non-pointer fields.
toArgRepOrV :: Platform -> PrimOrVoidRep -> ArgRep Source #