1
1
mirror of https://github.com/tweag/asterius.git synced 2024-09-21 05:48:04 +03:00

Implement fully growable Haskell heap for both regular closures & allocate* invocations #44 (+5 squashed commit)

Squashed commit:

[927e97b] no message

[4224024] no message

[a68642c] Handle ThreadYielding ret code for stg_yieldzh #44

[17012c7] Cleanup redundant constants in ghc-toolkit

[d5d32cc] Add no-op threadPaused #44
This commit is contained in:
Shao Cheng 2018-12-15 19:31:21 +08:00
parent 09568dd9a3
commit 1f6f0e0f88
7 changed files with 94 additions and 249 deletions

View File

@ -8,7 +8,7 @@ import System.FilePath
parseTask :: Parser Task
parseTask =
(\t i m_wasm m_js m_html m_report m_gv wasm_toolkit dbg ir r m_ns m_with_i ghc_flags export_funcs root_syms ->
(\t i m_wasm m_js m_html m_report m_gv wasm_toolkit dbg ir r m_with_i ghc_flags export_funcs root_syms ->
Task
{ target = t
, input = i
@ -21,7 +21,6 @@ parseTask =
, debug = dbg
, outputIR = ir || dbg
, run = r
, nurserySize = maybe 512 read m_ns
, asteriusInstanceCallback =
fromMaybe
"i => {\ni.wasmInstance.exports.hs_init();\ni.wasmInstance.exports.main();\n}"
@ -64,9 +63,6 @@ parseTask =
switch (long "debug" <> help "Enable debug mode in the runtime") <*>
switch (long "output-ir" <> help "Output Asterius IR of compiled modules") <*>
switch (long "run" <> help "Run the compiled module with Node.js") <*>
optional
(strOption
(long "nursery-size" <> help "Nursery size in MBs, defaults to 512.")) <*>
optional
(strOption
(long "asterius-instance-callback" <>

View File

@ -22,6 +22,7 @@ import Asterius.Internals
import Asterius.Types
import qualified Data.ByteString.Short as SBS
import Data.Foldable
import Data.Functor
import Data.List
import qualified Data.Map.Strict as Map
import Data.Maybe
@ -190,6 +191,7 @@ rtsAsteriusModule opts =
, ("__asterius_toJSArrayBuffer", toJSArrayBufferFunction opts)
, ("__asterius_fromJSString", fromJSStringFunction opts)
, ("__asterius_fromJSArray", fromJSArrayFunction opts)
, ("threadPaused", threadPausedFunction opts)
] <>
map (\(func_sym, (_, func)) -> (func_sym, func)) byteStringCBits
}
@ -632,7 +634,7 @@ generateWrapperFunction func_sym AsteriusFunction {functionType = FunctionType {
[I64] -> ([F64], Unary ConvertSInt64ToFloat64)
_ -> (returnTypes, id)
mainFunction, hsInitFunction, rtsApplyFunction, rtsEvalFunction, rtsEvalIOFunction, rtsEvalLazyIOFunction, rtsEvalStableIOFunction, rtsGetSchedStatusFunction, rtsCheckSchedStatusFunction, scheduleWaitThreadFunction, createThreadFunction, createGenThreadFunction, createIOThreadFunction, createStrictIOThreadFunction, allocateFunction, allocateWrapperFunction, allocateProxyFunction, allocGroupFunction, newCAFFunction, stgReturnFunction, getStablePtrWrapperFunction, deRefStablePtrWrapperFunction, freeStablePtrWrapperFunction, rtsMkBoolFunction, rtsMkDoubleFunction, rtsMkCharFunction, rtsMkIntFunction, rtsMkWordFunction, rtsMkPtrFunction, rtsMkStablePtrFunction, rtsGetBoolFunction, rtsGetDoubleFunction, rtsGetCharFunction, rtsGetIntFunction, loadI64Function, printI64Function, printF32Function, printF64Function, strlenFunction, memchrFunction, memcpyFunction, memsetFunction, memcmpFunction, fromJSArrayBufferFunction, toJSArrayBufferFunction, fromJSStringFunction, fromJSArrayFunction ::
mainFunction, hsInitFunction, rtsApplyFunction, rtsEvalFunction, rtsEvalIOFunction, rtsEvalLazyIOFunction, rtsEvalStableIOFunction, rtsGetSchedStatusFunction, rtsCheckSchedStatusFunction, scheduleWaitThreadFunction, createThreadFunction, createGenThreadFunction, createIOThreadFunction, createStrictIOThreadFunction, allocateFunction, allocateWrapperFunction, allocateProxyFunction, allocGroupFunction, newCAFFunction, stgReturnFunction, getStablePtrWrapperFunction, deRefStablePtrWrapperFunction, freeStablePtrWrapperFunction, rtsMkBoolFunction, rtsMkDoubleFunction, rtsMkCharFunction, rtsMkIntFunction, rtsMkWordFunction, rtsMkPtrFunction, rtsMkStablePtrFunction, rtsGetBoolFunction, rtsGetDoubleFunction, rtsGetCharFunction, rtsGetIntFunction, loadI64Function, printI64Function, printF32Function, printF64Function, strlenFunction, memchrFunction, memcpyFunction, memsetFunction, memcmpFunction, fromJSArrayBufferFunction, toJSArrayBufferFunction, fromJSStringFunction, fromJSArrayFunction, threadPausedFunction ::
BuiltinsOptions -> AsteriusFunction
mainFunction BuiltinsOptions {..} =
runEDSL [] $ do
@ -663,16 +665,14 @@ initCapability = do
storeI64 mainCapability (offset_Capability_r + offset_StgRegTable_rCurrentTSO) $
constI64 0
hsInitFunction BuiltinsOptions {..} =
hsInitFunction _ =
runEDSL [] $ do
initCapability
bd_nursery <-
call' "allocGroup" [constI64 $ nurseryMBlocks * blocks_per_mblock] I64
putLVal hp $ loadI64 bd_nursery offset_bdescr_start
putLVal hpLim $
bd_nursery `addInt64`
constI64
(fromIntegral ((mblock_size * nurseryMBlocks) - offset_first_bdescr))
bd_nursery <- call' "allocGroup" [constI64 1] I64
block_nursery <- i64Local $ loadI64 bd_nursery offset_bdescr_start
putLVal hp block_nursery
putLVal hpLim $ block_nursery `addInt64` constI64 block_size
putLVal hpAlloc (constI64 0)
putLVal cccs (constI64 0)
putLVal currentNursery bd_nursery
storeI64 (getLVal baseReg) offset_StgRegTable_rCurrentAlloc (constI64 0)
@ -771,45 +771,17 @@ dirtySTACK _ stack =
(storeI32 stack offset_StgStack_dirty $ constI32 1)
mempty
scheduleHandleThreadFinished :: Expression -> EDSL Expression
scheduleHandleThreadFinished t = do
if'
[]
(loadI16 t offset_StgTSO_what_next `eqInt32` constI32 next_ThreadComplete)
(do callImport
"__asterius_setTSOret"
[ loadI32 t offset_StgTSO_id
, Unary ConvertUInt64ToFloat64 $
loadI64
(loadI64 (loadI64 t offset_StgTSO_stackobj) offset_StgStack_sp)
8
]
callImport
"__asterius_setTSOrstat"
[loadI32 t offset_StgTSO_id, constI32 scheduler_Success])
(do callImport
"__asterius_setTSOret"
[loadI32 t offset_StgTSO_id, ConstF64 0]
callImport
"__asterius_setTSOrstat"
[loadI32 t offset_StgTSO_id, constI32 scheduler_Killed])
storeI64 t offset_StgTSO_bound $ constI64 0
pure $ constI32 1
schedule :: Expression -> EDSL ()
schedule t = do
ret <- i32MutLocal
block' [] $ \sched_block_lbl ->
loop' [] $ \sched_loop_lbl -> do
if'
[]
(loadI8 mainCapability offset_Capability_in_haskell)
(emit
(emitErrorMessage
[]
"schedule failed: scheduler reentered from Haskell"))
mempty
loop' [] $ \_ -> do
scheduleWaitThreadFunction _ =
runEDSL [] $ do
t <- param I64
ret <- i32MutLocal
block' [] $ \sched_block_lbl ->
loop' [] $ \sched_loop_lbl -> do
if'
[]
(loadI8 mainCapability offset_Capability_in_haskell)
(emit (emitErrorMessage [] "Scheduler reentered from Haskell"))
mempty
storeI64
mainCapability
(offset_Capability_r + offset_StgRegTable_rCurrentTSO)
@ -826,23 +798,59 @@ schedule t = do
mainCapability
(offset_Capability_r + offset_StgRegTable_rCurrentTSO) $
constI64 0
switchI64 (extendUInt32 (getLVal ret)) $ \brake ->
( [ (ret_HeapOverflow, emit $ emitErrorMessage [] "HeapOverflow")
, (ret_StackOverflow, emit $ emitErrorMessage [] "StackOverflow")
, (ret_ThreadYielding, emit $ emitErrorMessage [] "ThreadYielding")
, (ret_ThreadBlocked, emit $ emitErrorMessage [] "ThreadBlocked")
, ( ret_ThreadFinished
, do scheduleHandleThreadFinished t >>=
break' sched_block_lbl . Just
brake)
]
, emit $ emitErrorMessage [] "Illegal thread return code")
break' sched_loop_lbl Nothing
scheduleWaitThreadFunction _ =
runEDSL [] $ do
tso <- param I64
schedule tso
switchI64 (extendUInt32 (getLVal ret)) $
const
( [ ( ret_HeapOverflow
, do bytes <- i64Local $ getLVal hpAlloc
putLVal hpAlloc $ constI64 0
if'
[]
(eqZInt64 bytes)
(emit $ emitErrorMessage [] "HeapOverflow with HpAlloc=0")
mempty
blocks <- i64Local $ bytesToBlocks bytes
bd <- call' "allocGroup" [blocks] I64
block <- i64Local $ loadI64 bd offset_bdescr_start
putLVal currentNursery bd
putLVal hp block
putLVal hpLim $
block `addInt64` (constI64 block_size `mulInt64` blocks)
break' sched_loop_lbl Nothing)
, (ret_StackOverflow, emit $ emitErrorMessage [] "StackOverflow")
, (ret_ThreadYielding, break' sched_loop_lbl Nothing)
, (ret_ThreadBlocked, emit $ emitErrorMessage [] "ThreadBlocked")
, ( ret_ThreadFinished
, if'
[]
(loadI16 t offset_StgTSO_what_next `eqInt32`
constI32 next_ThreadComplete)
(do callImport
"__asterius_setTSOret"
[ loadI32 t offset_StgTSO_id
, Unary ConvertUInt64ToFloat64 $
loadI64
(loadI64
(loadI64 t offset_StgTSO_stackobj)
offset_StgStack_sp)
8
]
callImport
"__asterius_setTSOrstat"
[ loadI32 t offset_StgTSO_id
, constI32 scheduler_Success
]
break' sched_block_lbl Nothing)
(do callImport
"__asterius_setTSOret"
[loadI32 t offset_StgTSO_id, ConstF64 0]
callImport
"__asterius_setTSOrstat"
[ loadI32 t offset_StgTSO_id
, constI32 scheduler_Killed
]
break' sched_block_lbl Nothing))
]
, emit $ emitErrorMessage [] "Illegal thread return code")
createThreadFunction _ =
runEDSL [I64] $ do
@ -867,7 +875,6 @@ createThreadFunction _ =
storeI32 tso_p offset_StgTSO_flags $ constI32 0
storeI32 tso_p offset_StgTSO_dirty $ constI32 1
storeI32 tso_p offset_StgTSO_saved_errno $ constI32 0
storeI64 tso_p offset_StgTSO_bound $ constI64 0
storeI64 tso_p offset_StgTSO_cap cap
storeI64 tso_p offset_StgTSO_stackobj stack_p
storeI32 tso_p offset_StgTSO_tot_stack_size $ wrapInt64 stack_size_w
@ -914,6 +921,10 @@ createStrictIOThreadFunction _ =
, symbol "stg_enter_info"
]
bytesToBlocks :: Expression -> Expression
bytesToBlocks bytes =
(bytes `addInt64` constI64 (block_size - 1)) `divUInt64` constI64 block_size
allocateFunction BuiltinsOptions {..} =
runEDSL [I64] $ do
setReturnTypes [I64]
@ -922,13 +933,7 @@ allocateFunction BuiltinsOptions {..} =
if'
[I64]
(bytes `geUInt64` constI64 block_size)
(do bd <-
call'
"allocGroup"
[ (bytes `addInt64` constI64 (block_size - 1)) `divUInt64`
constI64 block_size
]
I64
(do bd <- call' "allocGroup" [bytesToBlocks bytes] I64
emit $ loadI64 bd offset_bdescr_free)
(do if'
[]
@ -1235,6 +1240,8 @@ fromJSArrayFunction _ =
F64
emit addr
threadPausedFunction _ = runEDSL [] $ void $ params [I64, I64]
getF64GlobalRegFunction ::
BuiltinsOptions -> UnresolvedGlobalReg -> AsteriusFunction
getF64GlobalRegFunction _ gr =

View File

@ -60,7 +60,6 @@ data Task = Task
, input, outputWasm, outputJS, outputHTML :: FilePath
, outputLinkReport, outputGraphViz :: Maybe FilePath
, binaryen, debug, outputIR, run :: Bool
, nurserySize :: Int
, asteriusInstanceCallback :: String
, extraGHCFlags :: [String]
, exportFunctions, extraRootSymbols :: [AsteriusEntitySymbol]
@ -146,8 +145,7 @@ ahcLinkMain task@Task {..} = do
putStrLn $ "[INFO] Loading boot library store from " <> show store_path
decodeStore store_path
putStrLn "[INFO] Populating the store with builtin routines"
let builtins_opts =
defaultBuiltinsOptions {nurseryMBlocks = nurserySize, tracing = debug}
let builtins_opts = defaultBuiltinsOptions {tracing = debug}
!orig_store = builtinsStore builtins_opts <> boot_store
putStrLn $ "[INFO] Compiling " <> input <> " to Cmm"
(c, get_ffi_mod) <- addFFIProcessor mempty

View File

@ -2,6 +2,7 @@
{-# LANGUAGE UnboxedTuples #-}
{-# OPTIONS_GHC -Wall -ddump-to-file -ddump-simpl -ddump-stg -ddump-cmm-raw -ddump-asm #-}
import Control.Concurrent
import Control.Monad
import Data.Foldable
import GHC.Exts
@ -39,5 +40,13 @@ m (I# len) =
, ( I# (indexInt8Array# ba 0#)
, I# (indexInt8Array# ba (len -# 1#)))#))
src :: [Int]
src = w 0 []
where
w 100000 acc = acc
w i acc = w (succ i) (i : acc)
main :: IO ()
main = for_ [63, 511, 8191, 65535] $ m >=> print
main = do
for_ [63, 511, 8191, 65535] $ m >=> print >=> const yield
print $ foldl' (+) (0 :: Int) src

View File

@ -10,9 +10,8 @@ ahc-link - Linker for the Asterius compiler
Usage: ahc-link [--browser] --input ARG [--output-wasm ARG] [--output-js ARG]
[--output-html ARG] [--output-link-report ARG]
[--output-graphviz ARG] [--binaryen] [--debug] [--output-ir]
[--run] [--nursery-size ARG] [--asterius-instance-callback ARG]
[--ghc-option ARG] [--export-function ARG]
[--extra-root-symbol ARG]
[--run] [--asterius-instance-callback ARG] [--ghc-option ARG]
[--export-function ARG] [--extra-root-symbol ARG]
Producing a standalone WebAssembly binary from Haskell
Available options:
@ -31,7 +30,6 @@ Available options:
--debug Enable debug mode in the runtime
--output-ir Output Asterius IR of compiled modules
--run Run the compiled module with Node.js
--nursery-size ARG Nursery size in MBs, defaults to 512.
--asterius-instance-callback ARG
Supply a JavaScript callback expression which will be
invoked on the initiated asterius instance. Defaults

View File

@ -10,8 +10,6 @@ HsInt block_size() { return BLOCK_SIZE; }
HsInt mblock_size() { return MBLOCK_SIZE; }
HsInt mblock_mask() { return MBLOCK_MASK; }
HsInt blocks_per_mblock() { return BLOCKS_PER_MBLOCK; }
HsInt offset_first_bdescr() { return (HsInt)FIRST_BDESCR(0); }
@ -121,17 +119,6 @@ HsInt offset_Capability_free_trec_headers() {
HsInt offset_Capability_transaction_tokens() {
return offsetof(Capability, transaction_tokens);
}
HsInt sizeof_nursery() { return sizeof(nursery); }
HsInt offset_nursery_blocks() { return offsetof(nursery, blocks); }
HsInt offset_nursery_n_blocks() { return offsetof(nursery, n_blocks); }
HsInt sizeof_RTS_FLAGS() { return sizeof(RTS_FLAGS); }
HsInt sizeof_spEntry() { return sizeof(spEntry); }
HsInt offset_spEntry_addr() { return offsetof(spEntry, addr); }
HsInt sizeof_StgArrBytes() { return sizeof(StgArrBytes); }
@ -313,62 +300,6 @@ HsInt offset_StgTSO_tot_stack_size() {
return offsetof(StgTSO, tot_stack_size);
}
HsInt sizeof_StgTSOBlockInfo() { return sizeof(StgTSOBlockInfo); }
HsInt offset_StgTSOBlockInfo_closure() {
return offsetof(StgTSOBlockInfo, closure);
}
HsInt offset_StgTSOBlockInfo_prev() { return offsetof(StgTSOBlockInfo, prev); }
HsInt sizeof_Task() { return sizeof(Task); }
HsInt offset_Task_cap() { return offsetof(Task, cap); }
HsInt offset_Task_incall() { return offsetof(Task, incall); }
HsInt offset_Task_n_spare_incalls() { return offsetof(Task, n_spare_incalls); }
HsInt offset_Task_spare_incalls() { return offsetof(Task, spare_incalls); }
HsInt offset_Task_worker() { return offsetof(Task, worker); }
HsInt offset_Task_stopped() { return offsetof(Task, stopped); }
HsInt offset_Task_running_finalizers() {
return offsetof(Task, running_finalizers);
}
HsInt offset_Task_preferred_capability() {
return offsetof(Task, preferred_capability);
}
HsInt offset_Task_next() { return offsetof(Task, next); }
HsInt offset_Task_all_next() { return offsetof(Task, all_next); }
HsInt offset_Task_all_prev() { return offsetof(Task, all_prev); }
HsInt sizeof_InCall() { return sizeof(InCall); }
HsInt offset_InCall_tso() { return offsetof(InCall, tso); }
HsInt offset_InCall_suspended_tso() { return offsetof(InCall, suspended_tso); }
HsInt offset_InCall_suspended_cap() { return offsetof(InCall, suspended_cap); }
HsInt offset_InCall_rstat() { return offsetof(InCall, rstat); }
HsInt offset_InCall_ret() { return offsetof(InCall, ret); }
HsInt offset_InCall_task() { return offsetof(InCall, task); }
HsInt offset_InCall_prev_stack() { return offsetof(InCall, prev_stack); }
HsInt offset_InCall_prev() { return offsetof(InCall, prev); }
HsInt offset_InCall_next() { return offsetof(InCall, next); }
HsInt next_ThreadRunGHC() { return ThreadRunGHC; }
HsInt next_ThreadInterpret() { return ThreadInterpret; }
@ -405,14 +336,6 @@ HsInt blocked_BlockedOnMsgThrowTo() { return BlockedOnMsgThrowTo; }
HsInt blocked_ThreadMigrating() { return ThreadMigrating; }
HsInt recent_ACTIVITY_YES() { return ACTIVITY_YES; }
HsInt recent_ACTIVITY_MAYBE_NO() { return ACTIVITY_MAYBE_NO; }
HsInt recent_ACTIVITY_INACTIVE() { return ACTIVITY_INACTIVE; }
HsInt recent_ACTIVITY_DONE_GC() { return ACTIVITY_DONE_GC; }
HsInt ret_HeapOverflow() { return HeapOverflow; }
HsInt ret_StackOverflow() { return StackOverflow; }

View File

@ -9,8 +9,6 @@ foreign import ccall unsafe "block_size" block_size :: Int
foreign import ccall unsafe "mblock_size" mblock_size :: Int
foreign import ccall unsafe "mblock_mask" mblock_mask :: Int
foreign import ccall unsafe "blocks_per_mblock" blocks_per_mblock :: Int
foreign import ccall unsafe "offset_first_bdescr" offset_first_bdescr :: Int
@ -112,19 +110,6 @@ foreign import ccall unsafe "offset_Capability_free_trec_headers" offset_Capabil
foreign import ccall unsafe "offset_Capability_transaction_tokens" offset_Capability_transaction_tokens
:: Int
foreign import ccall unsafe "sizeof_nursery" sizeof_nursery :: Int
foreign import ccall unsafe "offset_nursery_blocks" offset_nursery_blocks :: Int
foreign import ccall unsafe "offset_nursery_n_blocks" offset_nursery_n_blocks
:: Int
foreign import ccall unsafe "sizeof_RTS_FLAGS" sizeof_RTS_FLAGS :: Int
foreign import ccall unsafe "sizeof_spEntry" sizeof_spEntry :: Int
foreign import ccall unsafe "offset_spEntry_addr" offset_spEntry_addr :: Int
foreign import ccall unsafe "sizeof_StgArrBytes" sizeof_StgArrBytes :: Int
foreign import ccall unsafe "offset_StgArrBytes_bytes" offset_StgArrBytes_bytes
@ -341,66 +326,6 @@ foreign import ccall unsafe "offset_StgTSO_alloc_limit" offset_StgTSO_alloc_limi
foreign import ccall unsafe "offset_StgTSO_tot_stack_size" offset_StgTSO_tot_stack_size
:: Int
foreign import ccall unsafe "sizeof_StgTSOBlockInfo" sizeof_StgTSOBlockInfo
:: Int
foreign import ccall unsafe "offset_StgTSOBlockInfo_closure" offset_StgTSOBlockInfo_closure
:: Int
foreign import ccall unsafe "offset_StgTSOBlockInfo_prev" offset_StgTSOBlockInfo_prev
:: Int
foreign import ccall unsafe "sizeof_Task" sizeof_Task :: Int
foreign import ccall unsafe "offset_Task_cap" offset_Task_cap :: Int
foreign import ccall unsafe "offset_Task_incall" offset_Task_incall :: Int
foreign import ccall unsafe "offset_Task_n_spare_incalls" offset_Task_n_spare_incalls
:: Int
foreign import ccall unsafe "offset_Task_spare_incalls" offset_Task_spare_incalls
:: Int
foreign import ccall unsafe "offset_Task_worker" offset_Task_worker :: Int
foreign import ccall unsafe "offset_Task_stopped" offset_Task_stopped :: Int
foreign import ccall unsafe "offset_Task_running_finalizers" offset_Task_running_finalizers
:: Int
foreign import ccall unsafe "offset_Task_preferred_capability" offset_Task_preferred_capability
:: Int
foreign import ccall unsafe "offset_Task_next" offset_Task_next :: Int
foreign import ccall unsafe "offset_Task_all_next" offset_Task_all_next :: Int
foreign import ccall unsafe "offset_Task_all_prev" offset_Task_all_prev :: Int
foreign import ccall unsafe "sizeof_InCall" sizeof_InCall :: Int
foreign import ccall unsafe "offset_InCall_tso" offset_InCall_tso :: Int
foreign import ccall unsafe "offset_InCall_suspended_tso" offset_InCall_suspended_tso
:: Int
foreign import ccall unsafe "offset_InCall_suspended_cap" offset_InCall_suspended_cap
:: Int
foreign import ccall unsafe "offset_InCall_rstat" offset_InCall_rstat :: Int
foreign import ccall unsafe "offset_InCall_ret" offset_InCall_ret :: Int
foreign import ccall unsafe "offset_InCall_task" offset_InCall_task :: Int
foreign import ccall unsafe "offset_InCall_prev_stack" offset_InCall_prev_stack
:: Int
foreign import ccall unsafe "offset_InCall_prev" offset_InCall_prev :: Int
foreign import ccall unsafe "offset_InCall_next" offset_InCall_next :: Int
foreign import ccall unsafe "next_ThreadRunGHC" next_ThreadRunGHC :: Int
foreign import ccall unsafe "next_ThreadInterpret" next_ThreadInterpret :: Int
@ -444,17 +369,6 @@ foreign import ccall unsafe "blocked_BlockedOnMsgThrowTo" blocked_BlockedOnMsgTh
foreign import ccall unsafe "blocked_ThreadMigrating" blocked_ThreadMigrating
:: Int
foreign import ccall unsafe "recent_ACTIVITY_YES" recent_ACTIVITY_YES :: Int
foreign import ccall unsafe "recent_ACTIVITY_MAYBE_NO" recent_ACTIVITY_MAYBE_NO
:: Int
foreign import ccall unsafe "recent_ACTIVITY_INACTIVE" recent_ACTIVITY_INACTIVE
:: Int
foreign import ccall unsafe "recent_ACTIVITY_DONE_GC" recent_ACTIVITY_DONE_GC
:: Int
foreign import ccall unsafe "ret_HeapOverflow" ret_HeapOverflow :: Int
foreign import ccall unsafe "ret_StackOverflow" ret_StackOverflow :: Int