Rebuilding GHC on Mac OSX PPC
Joel Reymont
joelr1 at gmail.com
Thu Jul 27 12:19:45 EDT 2006
More on allocateExec... I see this at the end of ./ghc/compiler/ghci/
ByteCodeItbls.lhs
foreign import ccall unsafe "allocateExec"
_allocateExec :: CUInt -> IO (Ptr a)
malloc_exec :: Int -> IO (Ptr a)
malloc_exec bytes = _allocateExec (fromIntegral bytes)
It does not appear that malloc_exec is used anywhere else but here
it's used in the function below. I don't know where allocateExec is
supposed to be coming from.
-- Assumes constructors are numbered from zero, not one
make_constr_itbls :: [DataCon] -> IO ItblEnv
make_constr_itbls cons
| listLengthCmp cons 8 /= GT -- <= 8 elements in the list
= do is <- mapM mk_vecret_itbl (zip cons [0..])
return (mkItblEnv is)
| otherwise
= do is <- mapM mk_dirret_itbl (zip cons [0..])
return (mkItblEnv is)
where
mk_vecret_itbl (dcon, conNo)
= mk_itbl dcon conNo (vecret_entry conNo)
mk_dirret_itbl (dcon, conNo)
= mk_itbl dcon conNo stg_interp_constr_entry
mk_itbl :: DataCon -> Int -> Ptr () -> IO (Name,ItblPtr)
mk_itbl dcon conNo entry_addr
= let rep_args = [ (typeCgRep arg,arg)
| arg <- dataConRepArgTys dcon ]
(tot_wds, ptr_wds, _) = mkVirtHeapOffsets rep_args
ptrs = ptr_wds
nptrs = tot_wds - ptr_wds
nptrs_really
| ptrs + nptrs >= mIN_SIZE_NonUpdHeapObject = nptrs
| otherwise = mIN_SIZE_NonUpdHeapObject - ptrs
itbl = StgInfoTable {
ptrs = fromIntegral ptrs,
nptrs = fromIntegral nptrs_really,
tipe = fromIntegral cONSTR,
srtlen = fromIntegral conNo,
code = code
}
-- Make a piece of code to jump to "entry_label".
-- This is the only arch-dependent bit.
code = mkJumpToAddr entry_addr
in
do addr <- malloc_exec (sizeOf itbl)
--putStrLn ("SIZE of itbl is " ++ show (sizeOf
itbl))
--putStrLn ("# ptrs of itbl is " ++ show ptrs)
--putStrLn ("# nptrs of itbl is " ++ show
nptrs_really)
poke addr itbl
return (getName dcon, addr `plusPtr` (2 *
wORD_SIZE))
More information about the Glasgow-haskell-users
mailing list