module CmmInfo (
mkEmptyContInfoTable,
cmmToRawCmm,
mkInfoTable,
) where
#include "HsVersions.h"
import OldCmm as Old
import CmmUtils
import CLabel
import SMRep
import Bitmap
import Stream (Stream)
import qualified Stream
import Maybes
import Constants
import Panic
import Platform
import StaticFlags
import UniqSupply
import MonadUtils
import Util
import Data.Bits
import Data.Word
mkEmptyContInfoTable :: CLabel -> CmmInfoTable
mkEmptyContInfoTable info_lbl
= CmmInfoTable { cit_lbl = info_lbl
, cit_rep = mkStackRep []
, cit_prof = NoProfilingInfo
, cit_srt = NoC_SRT }
cmmToRawCmm :: Platform -> Stream IO Old.CmmGroup ()
-> IO (Stream IO Old.RawCmmGroup ())
cmmToRawCmm platform cmms
= do { uniqs <- mkSplitUniqSupply 'i'
; let do_one uniqs cmm = do
case initUs uniqs $ concatMapM (mkInfoTable platform) cmm of
(b,uniqs') -> return (uniqs',b)
; return (Stream.mapAccumL do_one uniqs cmms >> return ())
}
mkInfoTable :: Platform -> CmmDecl -> UniqSM [RawCmmDecl]
mkInfoTable _ (CmmData sec dat)
= return [CmmData sec dat]
mkInfoTable platform (CmmProc info entry_label blocks)
| CmmNonInfoTable <- info
= return [CmmProc Nothing entry_label blocks]
| CmmInfoTable { cit_lbl = info_lbl } <- info
= do { (top_decls, info_cts) <- mkInfoTableContents platform info Nothing
; return (top_decls ++
mkInfoTableAndCode info_lbl info_cts
entry_label blocks) }
| otherwise = panic "mkInfoTable"
type InfoTableContents = ( [CmmLit]
, [CmmLit] )
mkInfoTableContents :: Platform
-> CmmInfoTable
-> Maybe StgHalfWord
-> UniqSM ([RawCmmDecl],
InfoTableContents)
mkInfoTableContents platform
info@(CmmInfoTable { cit_lbl = info_lbl
, cit_rep = smrep
, cit_prof = prof
, cit_srt = srt })
mb_rts_tag
| RTSRep rts_tag rep <- smrep
= mkInfoTableContents platform info{cit_rep = rep} (Just rts_tag)
| StackRep frame <- smrep
= do { (prof_lits, prof_data) <- mkProfLits prof
; let (srt_label, srt_bitmap) = mkSRTLit srt
; (liveness_lit, liveness_data) <- mkLivenessBits frame
; let
std_info = mkStdInfoTable prof_lits rts_tag srt_bitmap liveness_lit
rts_tag | Just tag <- mb_rts_tag = tag
| null liveness_data = rET_SMALL
| otherwise = rET_BIG
; return (prof_data ++ liveness_data, (std_info, srt_label)) }
| HeapRep _ ptrs nonptrs closure_type <- smrep
= do { let layout = packHalfWordsCLit ptrs nonptrs
; (prof_lits, prof_data) <- mkProfLits prof
; let (srt_label, srt_bitmap) = mkSRTLit srt
; (mb_srt_field, mb_layout, extra_bits, ct_data)
<- mk_pieces closure_type srt_label
; let std_info = mkStdInfoTable prof_lits
(mb_rts_tag `orElse` rtsClosureType smrep)
(mb_srt_field `orElse` srt_bitmap)
(mb_layout `orElse` layout)
; return (prof_data ++ ct_data, (std_info, extra_bits)) }
where
mk_pieces :: ClosureTypeInfo -> [CmmLit]
-> UniqSM ( Maybe StgHalfWord
, Maybe CmmLit
, [CmmLit]
, [RawCmmDecl])
mk_pieces (Constr con_tag con_descr) _no_srt
= do { (descr_lit, decl) <- newStringLit con_descr
; return (Just con_tag, Nothing, [descr_lit], [decl]) }
mk_pieces Thunk srt_label
= return (Nothing, Nothing, srt_label, [])
mk_pieces (ThunkSelector offset) _no_srt
= return (Just 0, Just (mkWordCLit offset), [], [])
mk_pieces (Fun arity (ArgSpec fun_type)) srt_label
= do { let extra_bits = packHalfWordsCLit fun_type arity : srt_label
; return (Nothing, Nothing, extra_bits, []) }
mk_pieces (Fun arity (ArgGen arg_bits)) srt_label
= do { (liveness_lit, liveness_data) <- mkLivenessBits arg_bits
; let fun_type | null liveness_data = aRG_GEN
| otherwise = aRG_GEN_BIG
extra_bits = [ packHalfWordsCLit fun_type arity
, srt_lit, liveness_lit, slow_entry ]
; return (Nothing, Nothing, extra_bits, liveness_data) }
where
slow_entry = CmmLabel (toSlowEntryLbl info_lbl)
srt_lit = case srt_label of
[] -> mkIntCLit 0
(lit:_rest) -> ASSERT( null _rest ) lit
mk_pieces BlackHole _ = panic "mk_pieces: BlackHole"
mkInfoTableContents _ _ _ = panic "mkInfoTableContents"
mkSRTLit :: C_SRT
-> ([CmmLit],
StgHalfWord)
mkSRTLit NoC_SRT = ([], 0)
mkSRTLit (C_SRT lbl off bitmap) = ([cmmLabelOffW lbl off], bitmap)
mkInfoTableAndCode :: CLabel
-> InfoTableContents
-> CLabel
-> ListGraph CmmStmt
-> [RawCmmDecl]
mkInfoTableAndCode info_lbl (std_info, extra_bits) entry_lbl blocks
| tablesNextToCode
= [CmmProc (Just $ Statics info_lbl $ map CmmStaticLit $
reverse rel_extra_bits ++ rel_std_info)
entry_lbl blocks]
| ListGraph [] <- blocks
=
[mkRODataLits info_lbl (zeroCLit : rel_std_info ++ rel_extra_bits)]
| otherwise
=
[CmmProc Nothing entry_lbl blocks,
mkDataLits Data info_lbl (CmmLabel entry_lbl : rel_std_info ++ rel_extra_bits)]
where
rel_std_info = map (makeRelativeRefTo info_lbl) std_info
rel_extra_bits = map (makeRelativeRefTo info_lbl) extra_bits
makeRelativeRefTo :: CLabel -> CmmLit -> CmmLit
makeRelativeRefTo info_lbl (CmmLabel lbl)
| tablesNextToCode
= CmmLabelDiffOff lbl info_lbl 0
makeRelativeRefTo info_lbl (CmmLabelOff lbl off)
| tablesNextToCode
= CmmLabelDiffOff lbl info_lbl off
makeRelativeRefTo _ lit = lit
mkLivenessBits :: Liveness -> UniqSM (CmmLit, [RawCmmDecl])
mkLivenessBits liveness
| n_bits > mAX_SMALL_BITMAP_SIZE
= do { uniq <- getUniqueUs
; let bitmap_lbl = mkBitmapLabel uniq
; return (CmmLabel bitmap_lbl,
[mkRODataLits bitmap_lbl lits]) }
| otherwise
= return (mkWordCLit bitmap_word, [])
where
n_bits = length liveness
bitmap :: Bitmap
bitmap = mkBitmap liveness
small_bitmap = case bitmap of
[] -> 0
[b] -> b
_ -> panic "mkLiveness"
bitmap_word = fromIntegral n_bits
.|. (small_bitmap `shiftL` bITMAP_BITS_SHIFT)
lits = mkWordCLit (fromIntegral n_bits) : map mkWordCLit bitmap
mkStdInfoTable
:: (CmmLit,CmmLit)
-> StgHalfWord
-> StgHalfWord
-> CmmLit
-> [CmmLit]
mkStdInfoTable (type_descr, closure_descr) cl_type srt_len layout_lit
=
prof_info
++ [layout_lit, type_lit]
where
prof_info
| opt_SccProfilingOn = [type_descr, closure_descr]
| otherwise = []
type_lit = packHalfWordsCLit cl_type srt_len
mkProfLits :: ProfilingInfo -> UniqSM ((CmmLit,CmmLit), [RawCmmDecl])
mkProfLits NoProfilingInfo = return ((zeroCLit, zeroCLit), [])
mkProfLits (ProfilingInfo td cd)
= do { (td_lit, td_decl) <- newStringLit td
; (cd_lit, cd_decl) <- newStringLit cd
; return ((td_lit,cd_lit), [td_decl,cd_decl]) }
newStringLit :: [Word8] -> UniqSM (CmmLit, GenCmmDecl CmmStatics info stmt)
newStringLit bytes
= do { uniq <- getUniqueUs
; return (mkByteStringCLit uniq bytes) }