module GHC.StgToCmm.Layout (
mkArgDescr,
emitCall, emitReturn, adjustHpBackwards,
emitClosureProcAndInfoTable,
emitClosureAndInfoTable,
slowCall, directCall,
FieldOffOrPadding(..),
ClosureHeader(..),
mkVirtHeapOffsets,
mkVirtHeapOffsetsWithPadding,
mkVirtConstrOffsets,
mkVirtConstrSizes,
getHpRelOffset,
ArgRep(..), toArgRep, argRepSizeW
) where
#include "HsVersions.h"
import GHC.Prelude hiding ((<*>))
import GHC.Driver.Session
import GHC.Driver.Ppr
import GHC.StgToCmm.Closure
import GHC.StgToCmm.Env
import GHC.StgToCmm.ArgRep
import GHC.StgToCmm.Ticky
import GHC.StgToCmm.Monad
import GHC.StgToCmm.Utils
import GHC.Cmm.Graph
import GHC.Runtime.Heap.Layout
import GHC.Cmm.BlockId
import GHC.Cmm
import GHC.Cmm.Utils
import GHC.Cmm.Info
import GHC.Cmm.CLabel
import GHC.Stg.Syntax
import GHC.Types.Id
import GHC.Core.TyCon ( PrimRep(..), primRepSizeB )
import GHC.Types.Basic ( RepArity )
import GHC.Platform
import GHC.Platform.Profile
import GHC.Unit
import GHC.Utils.Misc
import Data.List (mapAccumL, partition)
import GHC.Utils.Outputable
import GHC.Utils.Panic
import GHC.Data.FastString
import Control.Monad
emitReturn :: [CmmExpr] -> FCode ReturnKind
emitReturn results
= do { profile <- getProfile
; platform <- getPlatform
; sequel <- getSequel
; updfr_off <- getUpdFrameOff
; case sequel of
Return ->
do { adjustHpBackwards
; let e = CmmLoad (CmmStackSlot Old updfr_off) (gcWord platform)
; emit (mkReturn profile (entryCode platform e) results updfr_off)
}
AssignTo regs adjust ->
do { when adjust adjustHpBackwards
; emitMultiAssign regs results }
; return AssignedDirectly
}
emitCall :: (Convention, Convention) -> CmmExpr -> [CmmExpr] -> FCode ReturnKind
emitCall convs fun args
= emitCallWithExtraStack convs fun args noExtraStack
emitCallWithExtraStack
:: (Convention, Convention) -> CmmExpr -> [CmmExpr]
-> [CmmExpr] -> FCode ReturnKind
emitCallWithExtraStack (callConv, retConv) fun args extra_stack
= do { profile <- getProfile
; adjustHpBackwards
; sequel <- getSequel
; updfr_off <- getUpdFrameOff
; case sequel of
Return -> do
emit $ mkJumpExtra profile callConv fun args updfr_off extra_stack
return AssignedDirectly
AssignTo res_regs _ -> do
k <- newBlockId
let area = Young k
(off, _, copyin) = copyInOflow profile retConv area res_regs []
copyout = mkCallReturnsTo profile fun callConv args k off updfr_off
extra_stack
tscope <- getTickScope
emit (copyout <*> mkLabel k tscope <*> copyin)
return (ReturnedTo k off)
}
adjustHpBackwards :: FCode ()
adjustHpBackwards
= do { hp_usg <- getHpUsage
; let rHp = realHp hp_usg
vHp = virtHp hp_usg
adjust_words = vHp rHp
; new_hp <- getHpRelOffset vHp
; emit (if adjust_words == 0
then mkNop
else mkAssign hpReg new_hp)
; tickyAllocHeap False adjust_words
; setRealHp vHp
}
directCall :: Convention -> CLabel -> RepArity -> [StgArg] -> FCode ReturnKind
directCall conv lbl arity stg_args
= do { argreps <- getArgRepsAmodes stg_args
; direct_call "directCall" conv lbl arity argreps }
slowCall :: CmmExpr -> [StgArg] -> FCode ReturnKind
slowCall fun stg_args
= do dflags <- getDynFlags
profile <- getProfile
let platform = profilePlatform profile
argsreps <- getArgRepsAmodes stg_args
let (rts_fun, arity) = slowCallPattern (map fst argsreps)
(r, slow_code) <- getCodeR $ do
r <- direct_call "slow_call" NativeNodeCall
(mkRtsApFastLabel rts_fun) arity ((P,Just fun):argsreps)
emitComment $ mkFastString ("slow_call for " ++
showSDoc dflags (pdoc platform fun) ++
" with pat " ++ unpackFS rts_fun)
return r
let n_args = length stg_args
if n_args > arity && optLevel dflags >= 2
then do
ptr_opts <- getPtrOpts
funv <- (CmmReg . CmmLocal) `fmap` assignTemp fun
fun_iptr <- (CmmReg . CmmLocal) `fmap`
assignTemp (closureInfoPtr ptr_opts (cmmUntag platform funv))
fast_code <- getCode $
emitCall (NativeNodeCall, NativeReturn)
(entryCode platform fun_iptr)
(nonVArgs ((P,Just funv):argsreps))
slow_lbl <- newBlockId
fast_lbl <- newBlockId
is_tagged_lbl <- newBlockId
end_lbl <- newBlockId
let correct_arity = cmmEqWord platform (funInfoArity profile fun_iptr)
(mkIntExpr platform n_args)
tscope <- getTickScope
emit (mkCbranch (cmmIsTagged platform funv)
is_tagged_lbl slow_lbl (Just True)
<*> mkLabel is_tagged_lbl tscope
<*> mkCbranch correct_arity fast_lbl slow_lbl (Just True)
<*> mkLabel fast_lbl tscope
<*> fast_code
<*> mkBranch end_lbl
<*> mkLabel slow_lbl tscope
<*> slow_code
<*> mkLabel end_lbl tscope)
return r
else do
emit slow_code
return r
direct_call :: String
-> Convention
-> CLabel -> RepArity
-> [(ArgRep,Maybe CmmExpr)] -> FCode ReturnKind
direct_call caller call_conv lbl arity args
| debugIsOn && args `lengthLessThan` real_arity
= do
platform <- getPlatform
pprPanic "direct_call" $
text caller <+> ppr arity <+>
pdoc platform lbl <+> ppr (length args) <+>
pdoc platform (map snd args) <+> ppr (map fst args)
| null rest_args
= emitCall (call_conv, NativeReturn) target (nonVArgs args)
| otherwise
= do dflags <- getDynFlags
emitCallWithExtraStack (call_conv, NativeReturn)
target
(nonVArgs fast_args)
(nonVArgs (stack_args dflags))
where
target = CmmLit (CmmLabel lbl)
(fast_args, rest_args) = splitAt real_arity args
stack_args dflags = slowArgs dflags rest_args
real_arity = case call_conv of
NativeNodeCall -> arity+1
_ -> arity
getArgRepsAmodes :: [StgArg] -> FCode [(ArgRep, Maybe CmmExpr)]
getArgRepsAmodes args = do
platform <- profilePlatform <$> getProfile
mapM (getArgRepAmode platform) args
where getArgRepAmode platform arg
| V <- rep = return (V, Nothing)
| otherwise = do expr <- getArgAmode (NonVoid arg)
return (rep, Just expr)
where rep = toArgRep platform (argPrimRep arg)
nonVArgs :: [(ArgRep, Maybe CmmExpr)] -> [CmmExpr]
nonVArgs [] = []
nonVArgs ((_,Nothing) : args) = nonVArgs args
nonVArgs ((_,Just arg) : args) = arg : nonVArgs args
slowArgs :: DynFlags -> [(ArgRep, Maybe CmmExpr)] -> [(ArgRep, Maybe CmmExpr)]
slowArgs _ [] = []
slowArgs dflags args
| sccProfilingEnabled dflags
= save_cccs ++ this_pat ++ slowArgs dflags rest_args
| otherwise = this_pat ++ slowArgs dflags rest_args
where
(arg_pat, n) = slowCallPattern (map fst args)
(call_args, rest_args) = splitAt n args
stg_ap_pat = mkCmmRetInfoLabel rtsUnitId arg_pat
this_pat = (N, Just (mkLblExpr stg_ap_pat)) : call_args
save_cccs = [(N, Just (mkLblExpr save_cccs_lbl)), (N, Just cccsExpr)]
save_cccs_lbl = mkCmmRetInfoLabel rtsUnitId (fsLit "stg_restore_cccs")
hpRel :: VirtualHpOffset
-> VirtualHpOffset
-> WordOff
hpRel hp off = off hp
getHpRelOffset :: VirtualHpOffset -> FCode CmmExpr
getHpRelOffset virtual_offset
= do platform <- getPlatform
hp_usg <- getHpUsage
return (cmmRegOffW platform hpReg (hpRel (realHp hp_usg) virtual_offset))
data FieldOffOrPadding a
= FieldOff (NonVoid a)
ByteOff
| Padding ByteOff
ByteOff
data ClosureHeader
= NoHeader
| StdHeader
| ThunkHeader
mkVirtHeapOffsetsWithPadding
:: Profile
-> ClosureHeader
-> [NonVoid (PrimRep, a)]
-> ( WordOff
, WordOff
, [FieldOffOrPadding a]
)
mkVirtHeapOffsetsWithPadding profile header things =
ASSERT(not (any (isVoidRep . fst . fromNonVoid) things))
( tot_wds
, bytesToWordsRoundUp platform bytes_of_ptrs
, concat (ptrs_w_offsets ++ non_ptrs_w_offsets) ++ final_pad
)
where
platform = profilePlatform profile
hdr_words = case header of
NoHeader -> 0
StdHeader -> fixedHdrSizeW profile
ThunkHeader -> thunkHdrSize profile
hdr_bytes = wordsToBytes platform hdr_words
(ptrs, non_ptrs) = partition (isGcPtrRep . fst . fromNonVoid) things
(bytes_of_ptrs, ptrs_w_offsets) =
mapAccumL computeOffset 0 ptrs
(tot_bytes, non_ptrs_w_offsets) =
mapAccumL computeOffset bytes_of_ptrs non_ptrs
tot_wds = bytesToWordsRoundUp platform tot_bytes
final_pad_size = tot_wds * word_size tot_bytes
final_pad
| final_pad_size > 0 = [(Padding final_pad_size
(hdr_bytes + tot_bytes))]
| otherwise = []
word_size = platformWordSizeInBytes platform
computeOffset bytes_so_far nv_thing =
(new_bytes_so_far, with_padding field_off)
where
(rep, thing) = fromNonVoid nv_thing
!sizeB = primRepSizeB platform rep
!align = min word_size sizeB
!start = roundUpTo bytes_so_far align
!padding = start bytes_so_far
!final_offset = hdr_bytes + bytes_so_far + padding
!new_bytes_so_far = start + sizeB
field_off = FieldOff (NonVoid thing) final_offset
with_padding field_off
| padding == 0 = [field_off]
| otherwise = [ Padding padding (hdr_bytes + bytes_so_far)
, field_off
]
mkVirtHeapOffsets
:: Profile
-> ClosureHeader
-> [NonVoid (PrimRep,a)]
-> (WordOff,
WordOff,
[(NonVoid a, ByteOff)])
mkVirtHeapOffsets profile header things =
( tot_wds
, ptr_wds
, [ (field, offset) | (FieldOff field offset) <- things_offsets ]
)
where
(tot_wds, ptr_wds, things_offsets) =
mkVirtHeapOffsetsWithPadding profile header things
mkVirtConstrOffsets
:: Profile -> [NonVoid (PrimRep, a)]
-> (WordOff, WordOff, [(NonVoid a, ByteOff)])
mkVirtConstrOffsets profile = mkVirtHeapOffsets profile StdHeader
mkVirtConstrSizes :: Profile -> [NonVoid PrimRep] -> (WordOff, WordOff)
mkVirtConstrSizes profile field_reps
= (tot_wds, ptr_wds)
where
(tot_wds, ptr_wds, _) =
mkVirtConstrOffsets profile
(map (\nv_rep -> NonVoid (fromNonVoid nv_rep, ())) field_reps)
#include "../includes/rts/storage/FunTypes.h"
mkArgDescr :: Platform -> [Id] -> ArgDescr
mkArgDescr platform args
= let arg_bits = argBits platform arg_reps
arg_reps = filter isNonV (map (idArgRep platform) args)
in case stdPattern arg_reps of
Just spec_id -> ArgSpec spec_id
Nothing -> ArgGen arg_bits
argBits :: Platform -> [ArgRep] -> [Bool]
argBits _ [] = []
argBits platform (P : args) = False : argBits platform args
argBits platform (arg : args) = take (argRepSizeW platform arg) (repeat True)
++ argBits platform args
stdPattern :: [ArgRep] -> Maybe Int
stdPattern reps
= case reps of
[] -> Just ARG_NONE
[N] -> Just ARG_N
[P] -> Just ARG_P
[F] -> Just ARG_F
[D] -> Just ARG_D
[L] -> Just ARG_L
[V16] -> Just ARG_V16
[V32] -> Just ARG_V32
[V64] -> Just ARG_V64
[N,N] -> Just ARG_NN
[N,P] -> Just ARG_NP
[P,N] -> Just ARG_PN
[P,P] -> Just ARG_PP
[N,N,N] -> Just ARG_NNN
[N,N,P] -> Just ARG_NNP
[N,P,N] -> Just ARG_NPN
[N,P,P] -> Just ARG_NPP
[P,N,N] -> Just ARG_PNN
[P,N,P] -> Just ARG_PNP
[P,P,N] -> Just ARG_PPN
[P,P,P] -> Just ARG_PPP
[P,P,P,P] -> Just ARG_PPPP
[P,P,P,P,P] -> Just ARG_PPPPP
[P,P,P,P,P,P] -> Just ARG_PPPPPP
_ -> Nothing
emitClosureProcAndInfoTable :: Bool
-> Id
-> LambdaFormInfo
-> CmmInfoTable
-> [NonVoid Id]
-> ((Int, LocalReg, [LocalReg]) -> FCode ())
-> FCode ()
emitClosureProcAndInfoTable top_lvl bndr lf_info info_tbl args body
= do { profile <- getProfile
; platform <- getPlatform
; node <- if top_lvl then return $ idToReg platform (NonVoid bndr)
else bindToReg (NonVoid bndr) lf_info
; let node_points = nodeMustPointToIt profile lf_info
; arg_regs <- bindArgsToRegs args
; let args' = if node_points then (node : arg_regs) else arg_regs
conv = if nodeMustPointToIt profile lf_info then NativeNodeCall
else NativeDirectCall
(offset, _, _) = mkCallEntry profile conv args' []
; emitClosureAndInfoTable (profilePlatform profile) info_tbl conv args' $ body (offset, node, arg_regs)
}
emitClosureAndInfoTable
:: Platform -> CmmInfoTable -> Convention -> [LocalReg] -> FCode () -> FCode ()
emitClosureAndInfoTable platform info_tbl conv args body
= do { (_, blks) <- getCodeScoped body
; let entry_lbl = toEntryLbl platform (cit_lbl info_tbl)
; emitProcWithConvention conv (Just info_tbl) entry_lbl args blks
}