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

Improve scheduler, expose rts_eval* to JavaScript (+13 squashed commit)

Squashed commit:

[c1f0ed2] no message

[45b6f5c] no message

[10398f5] no message

[c64376a] no message

[7577805] Initial skeleton of gen2 scheduler goes live

[752b106] no message

[943eec8] no message

[18e9d3d] no message

[0189889] no message

[a479254] no message

[f9bc356] Update binaryen to 1.38.11

[661e9ac] no message

[4aece02] no message
This commit is contained in:
Shao Cheng 2018-08-02 17:56:38 +08:00
parent de1764bc34
commit 3cd00654e4
131 changed files with 7385 additions and 1861 deletions

View File

@ -20,11 +20,15 @@ root@76bcb511663d:/mirror# ahc-link --help
See the help text of `ahc-link` for further instructions.
What works for now:
What works currently:
* All GHC language features except Template Haskell
* Non-IO parts in `ghc-prim`/`integer-simple`/`base`/`array`
* Importing JavaScript expressions via the `foreign import javascript` syntax
* All GHC language features except Template Haskell.
* Non-IO parts in `ghc-prim`/`integer-simple`/`base`/`array`. IO is achieved via rts primitives like `print_i64` or JavaScript FFI.
* Importing JavaScript expressions via the `foreign import javascript` syntax. First-class `JSRef` type in Haskell land.
* Invoking RTS API on the JavaScript side to manipulate Haskell closures and trigger evaluation.
* A debugger which outputs memory loads/stores and control flow transfers.
* A monadic EDSL to construct WebAssembly code directly in Haskell.
* Besides WebAssembly MVP & the experimental BigInt support, no special requirements on the underlying JavaScript engine.
Better check the [`fib`](asterius/test/fib/fib.hs), [`jsffi`](asterius/test/jsffi/jsffi.hs) and [`array`](asterius/test/array/array.hs) test suites first to get some idea on current capabilities of `asterius`.

View File

@ -14,16 +14,19 @@ import Asterius.JSFFI
import Asterius.Marshal
import Asterius.Resolve
import Asterius.Store
import Asterius.Types
import Bindings.Binaryen.Raw
import Control.Exception
import Control.Monad
import qualified Data.ByteString as BS
import Data.ByteString.Builder
import qualified Data.HashMap.Strict as HM
import qualified Data.HashSet as HS
import Data.IORef
import Data.List
import qualified Data.Map.Strict as M
import Data.Maybe
import qualified Data.Vector as V
import Foreign
import qualified GhcPlugins as GHC
import Language.Haskell.GHC.Toolkit.Constants
@ -41,11 +44,12 @@ data Task = Task
, outputLinkReport, outputGraphViz :: Maybe FilePath
, debug, optimize, outputIR, run :: Bool
, heapSize :: Int
, asteriusInstanceCallback :: String
}
parseTask :: Parser Task
parseTask =
(\i m_wasm m_node m_report m_gv dbg opt ir r m_hs ->
(\i m_wasm m_node m_report m_gv dbg opt ir r m_hs m_with_i ->
Task
{ input = i
, outputWasm = fromMaybe (i -<.> "wasm") m_wasm
@ -57,6 +61,10 @@ parseTask =
, outputIR = ir
, run = r
, heapSize = maybe 1024 read m_hs
, asteriusInstanceCallback =
fromMaybe
"i => {\ni.wasmInstance.exports.hs_init();\ni.wasmInstance.exports.rts_evalLazyIO(i.staticsSymbolMap.MainCapability, i.staticsSymbolMap.Main_main_closure, 0);\n}"
m_with_i
}) <$>
strOption (long "input" <> help "Path of the Main module") <*>
optional
@ -83,7 +91,12 @@ parseTask =
(strOption
(long "heap-size" <>
help
"Heap size in MBs, used for both nursery/object pool. Defaults to 1024."))
"Heap size in MBs, used for both nursery/object pool. Defaults to 1024.")) <*>
optional
(strOption
(long "asterius-instance-callback" <>
help
"Supply a JavaScript callback expression which will be invoked on the initiated asterius instance. Defaults to calling Main.main"))
opts :: ParserInfo Task
opts =
@ -93,6 +106,17 @@ opts =
progDesc "Producing a standalone WebAssembly binary from Haskell" <>
header "ahc-link - Linker for the Asterius compiler")
genSymbolDict :: HM.HashMap AsteriusEntitySymbol Int64 -> Builder
genSymbolDict sym_map =
"{" <>
mconcat
(intersperse
","
[ string7 (show sym) <> ":" <> int64Dec sym_idx
| (sym, sym_idx) <- HM.toList sym_map
]) <>
"}"
genNode :: Task -> LinkReport -> IO Builder
genNode Task {..} LinkReport {..} = do
rts_buf <- BS.readFile $ dataDir </> "rts" </> "rts.js"
@ -106,9 +130,14 @@ genNode Task {..} LinkReport {..} = do
, string7 $ show $ takeFileName outputWasm
, "), jsffiFactory: "
, generateFFIImportObjectFactory bundledFFIMarshalState
, ", staticsSymbolMap: "
, genSymbolDict staticsSymbolMap
, ", functionSymbolMap: "
, genSymbolDict functionSymbolMap
, "});\n"
, "i.wasmInstance.exports.hs_init();\n"
, "i.wasmInstance.exports.main();\n"
, "("
, string7 asteriusInstanceCallback
, ")(i);\n"
, "}\n"
, "process.on('unhandledRejection', err => { throw err; });\n"
, "main();\n"
@ -183,15 +212,10 @@ main = do
putStrLn "[INFO] Attempting to link into a standalone WebAssembly module"
let (!m_final_m, !report) =
linkStart debug final_store $
if debug
then [ "hs_init"
, "main"
, "__asterius_Load_Sp"
, "__asterius_Load_SpLim"
, "__asterius_Load_Hp"
, "__asterius_Load_HpLim"
]
else ["hs_init", "main"]
HS.fromList
[ AsteriusEntitySymbol {entityName = internalName}
| FunctionExport {..} <- V.toList $ rtsAsteriusFunctionExports debug
]
maybe
(pure ())
(\p -> do

View File

@ -38,7 +38,12 @@ async function newAsteriusInstance(req) {
"errUnimplemented",
"errAtomics",
"errSetBaseReg",
"errBrokenFunction"
"errBrokenFunction",
"errAssert",
"errSchedulerReenteredFromHaskell",
"errIllegalSchedState",
"errIllegalPrevWhatNext",
"errIllegalThreadReturnCode"
][e - 1]
),
__asterius_current_memory: p => {
@ -243,6 +248,8 @@ async function newAsteriusInstance(req) {
__asterius_wasm_instance = resultObject.instance;
return {
wasmModule: resultObject.module,
wasmInstance: resultObject.instance
wasmInstance: resultObject.instance,
staticsSymbolMap: req.staticsSymbolMap,
functionSymbolMap: req.functionSymbolMap
};
}

View File

@ -24,6 +24,11 @@ module Asterius.Builtins
, errAtomics
, errSetBaseReg
, errBrokenFunction
, errAssert
, errSchedulerReenteredFromHaskell
, errIllegalSchedState
, errIllegalPrevWhatNext
, errIllegalThreadReturnCode
, wasmPageSize
, cutI64
, generateWasmFunctionTypeName
@ -34,6 +39,7 @@ import Asterius.EDSL
import Asterius.Internals
import Asterius.Types
import Asterius.TypesConv
import Control.Monad (when)
import qualified Data.ByteString.Short as SBS
import Data.Foldable
import Data.List
@ -91,6 +97,9 @@ rtsAsteriusModule opts =
, AsteriusStatics {asteriusStatics = [Uninitialized 8]})
, ( "enabled_capabilities"
, AsteriusStatics {asteriusStatics = [Uninitialized 4]})
, ( "heap_overflow"
, AsteriusStatics
{asteriusStatics = [Serialized (encodePrim (0 :: Word8))]})
, ( "large_alloc_lim"
, AsteriusStatics {asteriusStatics = [Uninitialized 8]})
, ( "MainCapability"
@ -103,6 +112,13 @@ rtsAsteriusModule opts =
})
, ( "n_capabilities"
, AsteriusStatics {asteriusStatics = [Uninitialized 4]})
, ( "recent_activity"
, AsteriusStatics
{ asteriusStatics =
[ Serialized
(encodePrim (fromIntegral recent_ACTIVITY_YES :: Word64))
]
})
, ( "rts_stop_on_exception"
, AsteriusStatics {asteriusStatics = [Uninitialized 4]})
, ( "RtsFlags"
@ -110,16 +126,41 @@ rtsAsteriusModule opts =
{ asteriusStatics =
[Uninitialized (8 * roundup_bytes_to_words sizeof_RTS_FLAGS)]
})
, ( "sched_state"
, AsteriusStatics
{ asteriusStatics =
[ Serialized
(encodePrim (fromIntegral sched_SCHED_RUNNING :: Word64))
]
})
, ( "stable_ptr_table"
, AsteriusStatics {asteriusStatics = [Uninitialized 8]})
]
, functionMap =
[ ("main", mainFunction opts)
, ("hs_init", hsInitFunction opts)
, ("rts_apply", rtsApplyFunction opts)
, ( "rts_apply_wrapper"
, generateWrapperFunction "rts_apply" $ rtsApplyFunction opts)
, ("rts_eval", rtsEvalFunction opts)
, ( "rts_eval_wrapper"
, generateWrapperFunction "rts_eval" $ rtsEvalFunction opts)
, ("rts_evalIO", rtsEvalIOFunction opts)
, ( "rts_evalIO_wrapper"
, generateWrapperFunction "rts_evalIO" $ rtsEvalIOFunction opts)
, ("rts_evalLazyIO", rtsEvalLazyIOFunction opts)
, ( "rts_evalLazyIO_wrapper"
, generateWrapperFunction "rts_evalLazyIO" $
rtsEvalLazyIOFunction opts)
, ("setTSOLink", setTSOLinkFunction opts)
, ("setTSOPrev", setTSOPrevFunction opts)
, ("threadStackOverflow", threadStackOverflowFunction opts)
, ("pushOnRunQueue", pushOnRunQueueFunction opts)
, ("scheduleWaitThread", scheduleWaitThreadFunction opts)
, ("createThread", createThreadFunction opts)
, ("createGenThread", createGenThreadFunction opts)
, ("createIOThread", createIOThreadFunction opts)
, ("createStrictIOThread", createStrictIOThreadFunction opts)
, ("allocate", allocateFunction opts)
, ("allocGroupOnNode", allocGroupOnNodeFunction opts)
, ("getMBlocks", getMBlocksFunction opts)
@ -298,19 +339,21 @@ rtsAsteriusFunctionImports debug =
rtsAsteriusFunctionExports :: Bool -> V.Vector FunctionExport
rtsAsteriusFunctionExports debug =
V.fromList
[ FunctionExport {internalName = f, externalName = f}
| f <-
if debug
then [ "hs_init"
, "main"
, "__asterius_Load_Sp"
, "__asterius_Load_SpLim"
, "__asterius_Load_Hp"
, "__asterius_Load_HpLim"
]
else ["hs_init", "main"]
]
V.fromList $
[ FunctionExport {internalName = f <> "_wrapper", externalName = f}
| f <- ["rts_apply", "rts_eval", "rts_evalIO", "rts_evalLazyIO"]
] <>
[ FunctionExport {internalName = f, externalName = f}
| f <-
(if debug
then [ "__asterius_Load_Sp"
, "__asterius_Load_SpLim"
, "__asterius_Load_Hp"
, "__asterius_Load_HpLim"
]
else []) <>
["hs_init", "main"]
]
{-# INLINEABLE marshalErrorCode #-}
marshalErrorCode :: Int32 -> ValueType -> Expression
@ -328,7 +371,7 @@ marshalErrorCode err vt =
, valueType = vt
}
errGCEnter1, errGCFun, errBarf, errStgGC, errUnreachableBlock, errHeapOverflow, errMegaBlockGroup, errUnimplemented, errAtomics, errSetBaseReg, errBrokenFunction ::
errGCEnter1, errGCFun, errBarf, errStgGC, errUnreachableBlock, errHeapOverflow, errMegaBlockGroup, errUnimplemented, errAtomics, errSetBaseReg, errBrokenFunction, errAssert, errSchedulerReenteredFromHaskell, errIllegalSchedState, errIllegalPrevWhatNext, errIllegalThreadReturnCode ::
Int32
errGCEnter1 = 1
@ -352,14 +395,103 @@ errSetBaseReg = 10
errBrokenFunction = 11
mainFunction, hsInitFunction, rtsEvalLazyIOFunction, scheduleWaitThreadFunction, createThreadFunction, createIOThreadFunction, allocateFunction, allocGroupOnNodeFunction, getMBlocksFunction, freeFunction, newCAFFunction, stgRunFunction, stgReturnFunction, printI64Function, printF32Function, printF64Function, memoryTrapFunction ::
errAssert = 12
errSchedulerReenteredFromHaskell = 13
errIllegalSchedState = 14
errIllegalPrevWhatNext = 15
errIllegalThreadReturnCode = 16
assert :: BuiltinsOptions -> Expression -> EDSL ()
assert BuiltinsOptions {..} cond =
when tracing $ if' cond mempty $ emit $ marshalErrorCode errAssert None
generateWrapperFunction ::
AsteriusEntitySymbol -> AsteriusFunction -> AsteriusFunction
generateWrapperFunction func_sym AsteriusFunction { functionType = FunctionType {..}
, ..
} =
AsteriusFunction
{ functionType =
FunctionType
{ returnType = wrapper_return_type
, paramTypes =
V.fromList
[ wrapper_param_type
| (_, wrapper_param_type, _) <- wrapper_param_types
]
}
, body =
to_wrapper_return_type $
Call
{ target = func_sym
, operands =
V.fromList
[ from_wrapper_param_type
GetLocal {index = i, valueType = wrapper_param_type}
| (i, wrapper_param_type, from_wrapper_param_type) <-
wrapper_param_types
]
, valueType = returnType
}
}
where
wrapper_param_types =
[ case param_type of
I64 -> (i, I32, extendUInt32)
_ -> (i, param_type, id)
| (i, param_type) <- zip [0 ..] $ V.toList paramTypes
]
(wrapper_return_type, to_wrapper_return_type) =
case returnType of
I64 -> (I32, wrapInt64)
_ -> (returnType, id)
mainFunction, hsInitFunction, rtsApplyFunction, rtsEvalFunction, rtsEvalIOFunction, rtsEvalLazyIOFunction, setTSOLinkFunction, setTSOPrevFunction, threadStackOverflowFunction, pushOnRunQueueFunction, scheduleWaitThreadFunction, createThreadFunction, createGenThreadFunction, createIOThreadFunction, createStrictIOThreadFunction, allocateFunction, allocGroupOnNodeFunction, getMBlocksFunction, freeFunction, newCAFFunction, stgRunFunction, stgReturnFunction, printI64Function, printF32Function, printF64Function, memoryTrapFunction ::
BuiltinsOptions -> AsteriusFunction
mainFunction BuiltinsOptions {..} =
runEDSL $
call "rts_evalLazyIO" [mainCapability, symbol "Main_main_closure", constI64 0]
initCapability :: Expression -> Expression -> EDSL ()
initCapability cap i = do
storeI32 cap offset_Capability_no i
storeI32 cap offset_Capability_node $ constI32 0
storeI8 cap offset_Capability_in_haskell $ constI32 0
storeI32 cap offset_Capability_idle $ constI32 0
storeI8 cap offset_Capability_disabled $ constI32 0
storeI64 cap offset_Capability_run_queue_hd endTSOQueue
storeI64 cap offset_Capability_run_queue_tl endTSOQueue
storeI32 cap offset_Capability_n_run_queue $ constI32 0
storeI64 cap offset_Capability_total_allocated $ constI64 0
storeI64 cap (offset_Capability_f + offset_StgFunTable_stgEagerBlackholeInfo) $
symbol "__stg_EAGER_BLACKHOLE_info"
storeI64 cap (offset_Capability_f + offset_StgFunTable_stgGCEnter1) $
symbol "__stg_gc_enter_1"
storeI64 cap (offset_Capability_f + offset_StgFunTable_stgGCFun) $
symbol "__stg_gc_fun"
storeI64 cap offset_Capability_weak_ptr_list_hd $ constI64 0
storeI64 cap offset_Capability_weak_ptr_list_tl $ constI64 0
storeI64 cap offset_Capability_free_tvar_watch_queues $
symbol "stg_END_STM_WATCH_QUEUE_closure"
storeI64 cap offset_Capability_free_trec_chunks $
symbol "stg_END_STM_CHUNK_LIST_closure"
storeI64 cap offset_Capability_free_trec_headers $
symbol "stg_NO_TREC_closure"
storeI32 cap offset_Capability_transaction_tokens $ constI32 0
storeI32 cap offset_Capability_context_switch $ constI32 0
storeI64 cap offset_Capability_pinned_object_block $ constI64 0
storeI64 cap offset_Capability_pinned_object_blocks $ constI64 0
storeI64 cap (offset_Capability_r + offset_StgRegTable_rCCCS) $ constI64 0
storeI64 cap (offset_Capability_r + offset_StgRegTable_rCurrentTSO) $
constI64 0
hsInitFunction BuiltinsOptions {..} =
runEDSL $ do
initCapability mainCapability (constI32 0)
bd <- call' "allocGroupOnNode" [constI32 0, constI64 nurseryGroups] I64
putLVal hp $ loadI64 bd offset_bdescr_start
putLVal hpLim $
@ -384,17 +516,363 @@ hsInitFunction BuiltinsOptions {..} =
storeI64 task offset_Task_incall incall
storeI64 incall offset_InCall_task task
rtsEvalLazyIOFunction BuiltinsOptions {..} =
runEDSL $ do
[cap, p, ret] <- params [I64, I64, I64]
tso <-
call'
"createIOThread"
[cap, constI64 $ roundup_bytes_to_words threadStateSize, p]
I64
call "scheduleWaitThread" [tso, ret, cap]
rtsEvalHelper :: BuiltinsOptions -> AsteriusEntitySymbol -> EDSL ()
rtsEvalHelper BuiltinsOptions {..} create_thread_func_sym = do
[cap, p, ret] <- params [I64, I64, I64]
tso <-
call'
create_thread_func_sym
[cap, constI64 $ roundup_bytes_to_words threadStateSize, p]
I64
call "scheduleWaitThread" [tso, ret, cap]
scheduleWaitThreadFunction _ =
rtsApplyFunction _ =
runEDSL $ do
setReturnType I64
[cap, f, arg] <- params [I64, I64, I64]
ap <-
call'
"allocate"
[cap, constI64 $ roundup_bytes_to_words sizeof_StgThunk + 2]
I64
storeI64 ap 0 $ symbol "stg_ap_2_upd_info"
storeI64 ap offset_StgThunk_payload f
storeI64 ap (offset_StgThunk_payload + 8) arg
emit ap
rtsEvalFunction opts = runEDSL $ rtsEvalHelper opts "createGenThread"
rtsEvalIOFunction opts = runEDSL $ rtsEvalHelper opts "createStrictIOThread"
rtsEvalLazyIOFunction opts = runEDSL $ rtsEvalHelper opts "createIOThread"
appendToRunQueue :: BuiltinsOptions -> Expression -> Expression -> EDSL ()
appendToRunQueue opts cap tso = do
assert opts $ loadI64 tso offset_StgTSO__link `eqInt64` endTSOQueue
if'
(loadI64 cap offset_Capability_run_queue_hd `eqInt64` endTSOQueue)
(do storeI64 cap offset_Capability_run_queue_hd tso
storeI64
tso
(offset_StgTSO_block_info + offset_StgTSOBlockInfo_prev)
endTSOQueue)
(do call "setTSOLink" [cap, loadI64 cap offset_Capability_run_queue_tl, tso]
call "setTSOPrev" [cap, tso, loadI64 cap offset_Capability_run_queue_tl])
storeI64 cap offset_Capability_run_queue_tl tso
storeI32 cap offset_Capability_n_run_queue $
loadI32 cap offset_Capability_n_run_queue `addInt32` constI32 1
setTSOLinkFunction _ =
runEDSL $ do
[_, tso, target] <- params [I64, I64, I64]
if'
(eqZInt32 (loadI32 tso offset_StgTSO_dirty))
(storeI32 tso offset_StgTSO_dirty (constI32 1))
mempty
storeI64 tso offset_StgTSO__link target
setTSOPrevFunction _ =
runEDSL $ do
[_, tso, target] <- params [I64, I64, I64]
if'
(eqZInt32 (loadI32 tso offset_StgTSO_dirty))
(storeI32 tso offset_StgTSO_dirty (constI32 1))
mempty
storeI64 tso (offset_StgTSO_block_info + offset_StgTSOBlockInfo_prev) target
isBoundTask :: Expression -> Expression
isBoundTask task =
loadI64 (loadI64 task offset_Task_incall) offset_InCall_tso `neInt64`
constI64 0
emptyRunQueue :: Expression -> Expression
emptyRunQueue cap = eqZInt32 $ loadI32 cap offset_Capability_n_run_queue
scheduleDoGC :: Expression -> Expression -> Expression -> EDSL ()
scheduleDoGC _ _ _ = emit $ marshalErrorCode errUnimplemented None
popRunQueue :: BuiltinsOptions -> Expression -> EDSL Expression
popRunQueue opts cap = do
t <- i64Local $ loadI64 cap offset_Capability_run_queue_hd
assert opts $ t `neInt64` endTSOQueue
storeI64 cap offset_Capability_run_queue_hd $ loadI64 t offset_StgTSO__link
if'
(loadI64 t offset_StgTSO__link `neInt64` endTSOQueue)
(storeI64
(loadI64 t offset_StgTSO__link)
(offset_StgTSO_block_info + offset_StgTSOBlockInfo_prev)
endTSOQueue)
mempty
storeI64 t offset_StgTSO__link endTSOQueue
if'
(loadI64 cap offset_Capability_run_queue_hd `eqInt64` endTSOQueue)
(storeI64 cap offset_Capability_run_queue_tl endTSOQueue)
mempty
storeI32 cap offset_Capability_n_run_queue $
loadI32 cap offset_Capability_n_run_queue `subInt32` constI32 1
pure t
deleteThread :: Expression -> EDSL ()
deleteThread _ = emit $ marshalErrorCode errUnimplemented None
dirtyTSO :: Expression -> Expression -> EDSL ()
dirtyTSO _ tso =
if'
(eqZInt32 $ loadI32 tso offset_StgTSO_dirty)
(storeI32 tso offset_StgTSO_dirty $ constI32 1)
mempty
dirtySTACK :: Expression -> Expression -> EDSL ()
dirtySTACK _ stack =
if'
(eqZInt32 $ loadI32 stack offset_StgStack_dirty)
(storeI32 stack offset_StgStack_dirty $ constI32 1)
mempty
scheduleHandleHeapOverflow :: Expression -> Expression -> EDSL Expression
scheduleHandleHeapOverflow _ _ =
pure $ marshalErrorCode errIllegalThreadReturnCode None
threadStackOverflowFunction _ =
runEDSL $ do
_ <- params [I64, I64]
emit $ marshalErrorCode errIllegalThreadReturnCode None
pushOnRunQueueFunction _ =
runEDSL $ do
[cap, tso] <- params [I64, I64]
call "setTSOLink" [cap, tso, loadI64 cap offset_Capability_run_queue_hd]
storeI64
tso
(offset_StgTSO_block_info + offset_StgTSOBlockInfo_prev)
endTSOQueue
if'
(loadI64 cap offset_Capability_run_queue_hd `neInt64` endTSOQueue)
(call "setTSOPrev" [cap, loadI64 cap offset_Capability_run_queue_hd, tso])
mempty
storeI64 cap offset_Capability_run_queue_hd tso
if'
(loadI64 cap offset_Capability_run_queue_tl `eqInt64` endTSOQueue)
(storeI64 cap offset_Capability_run_queue_tl tso)
mempty
storeI32 cap offset_Capability_n_run_queue $
loadI32 cap offset_Capability_n_run_queue `addInt32` constI32 1
scheduleHandleYield :: Expression -> Expression -> Expression -> EDSL Expression
scheduleHandleYield _ _ _ =
pure $ marshalErrorCode errIllegalThreadReturnCode None
scheduleHandleThreadBlocked :: Expression -> EDSL ()
scheduleHandleThreadBlocked _ =
emit $ marshalErrorCode errIllegalThreadReturnCode None
scheduleHandleThreadFinished ::
BuiltinsOptions
-> Expression
-> Expression
-> Expression
-> EDSL Expression
scheduleHandleThreadFinished opts cap task t = do
r <- i32MutLocal
block' $ \ret_lbl ->
if'
(loadI64 t offset_StgTSO_bound `neInt64` constI64 0)
(do if'
(loadI64 t offset_StgTSO_bound `neInt64`
loadI64 task offset_Task_incall)
(do appendToRunQueue opts cap t
putLVal r $ constI32 0
break' ret_lbl Null)
mempty
assert opts $
loadI64 (loadI64 task offset_Task_incall) offset_InCall_tso `eqInt64`
t
if'
(loadI16 t offset_StgTSO_what_next `eqInt32`
constI32 next_ThreadComplete)
(do if'
(loadI64 (loadI64 task offset_Task_incall) offset_InCall_ret `neInt64`
constI64 0)
(storeI64
(loadI64
(loadI64 task offset_Task_incall)
offset_InCall_ret)
0 $
loadI64
(loadI64
(loadI64
(loadI64
(loadI64 task offset_Task_incall)
offset_InCall_tso)
offset_StgTSO_stackobj)
offset_StgStack_sp)
8)
mempty
storeI32 (loadI64 task offset_Task_incall) offset_InCall_rstat $
constI32 scheduler_Success)
(do if'
(loadI64 (loadI64 task offset_Task_incall) offset_InCall_ret `neInt64`
constI64 0)
(storeI64
(loadI64
(loadI64 task offset_Task_incall)
offset_InCall_ret)
0 $
constI64 0)
mempty
if'
(loadI64 (symbol "sched_state") 0 `geUInt64`
constI64 sched_SCHED_INTERRUPTING)
(if'
(loadI8 (symbol "heap_overflow") 0)
(storeI32
(loadI64 task offset_Task_incall)
offset_InCall_rstat $
constI32 scheduler_HeapExhausted)
(storeI32
(loadI64 task offset_Task_incall)
offset_InCall_rstat $
constI32 scheduler_Interrupted))
(storeI32
(loadI64 task offset_Task_incall)
offset_InCall_rstat $
constI32 scheduler_Killed))
storeI64 t offset_StgTSO_bound $ constI64 0
storeI64 (loadI64 task offset_Task_incall) offset_InCall_tso $
constI64 0
putLVal r $ constI32 1)
(putLVal r $ constI32 0)
pure $ getLVal r
scheduleNeedHeapProfile :: Expression -> EDSL Expression
scheduleNeedHeapProfile _ = pure $ constI32 0
schedule :: BuiltinsOptions -> Expression -> Expression -> EDSL ()
schedule opts cap task = do
t <- i64MutLocal
ret <- i32MutLocal
ready_to_gc <- i32MutLocal
block' $ \sched_block_lbl ->
loop' $ \sched_loop_lbl -> do
if'
(loadI8 cap offset_Capability_in_haskell)
(emit (marshalErrorCode errSchedulerReenteredFromHaskell None))
mempty
switchI64 (loadI64 (symbol "sched_state") 0) $ \brake ->
( [ (sched_SCHED_RUNNING, brake)
, ( sched_SCHED_INTERRUPTING
, do scheduleDoGC cap task (constI32 1)
assert opts $
loadI64 (symbol "sched_state") 0 `eqInt64`
constI64 sched_SCHED_SHUTTING_DOWN)
, ( sched_SCHED_SHUTTING_DOWN
, if'
(eqZInt32 (isBoundTask task) `andInt32` emptyRunQueue cap)
(break' sched_block_lbl Null)
brake)
]
, emit $ marshalErrorCode errIllegalSchedState None)
if'
(emptyRunQueue cap)
(assert opts $
loadI64 (symbol "sched_state") 0 `geUInt64`
constI64 sched_SCHED_INTERRUPTING)
mempty
popRunQueue opts cap >>= putLVal t
if'
((loadI64 (symbol "sched_state") 0 `geUInt64`
constI64 sched_SCHED_INTERRUPTING) `andInt32`
notInt32
((loadI16 (getLVal t) offset_StgTSO_what_next `eqInt32`
constI32 next_ThreadComplete) `orInt32`
(loadI16 (getLVal t) offset_StgTSO_what_next `eqInt32`
constI32 next_ThreadKilled)))
(deleteThread (getLVal t))
mempty
loop' $ \run_thread_lbl -> do
storeI64
cap
(offset_Capability_r + offset_StgRegTable_rCurrentTSO)
(getLVal t)
assert opts $ loadI64 (getLVal t) offset_StgTSO_cap `eqInt64` cap
assert opts $
(loadI64
(loadI64
(loadI64 (getLVal t) offset_StgTSO_bound)
offset_InCall_task)
offset_Task_cap `eqInt64`
cap) `orInt32`
eqZInt64 (loadI64 (getLVal t) offset_StgTSO_bound)
prev_what_next <- i32Local $ loadI16 (getLVal t) offset_StgTSO_what_next
storeI32 cap offset_Capability_interrupt $ constI32 0
storeI8 cap offset_Capability_in_haskell $ constI32 1
storeI32 cap offset_Capability_idle $ constI32 0
dirtyTSO cap (getLVal t)
dirtySTACK cap (loadI64 (getLVal t) offset_StgTSO_stackobj)
switchI64 (loadI64 (symbol "recent_activity") 0) $ \brake ->
( [ ( recent_ACTIVITY_DONE_GC
, do storeI64
(symbol "recent_activity")
0
(constI64 recent_ACTIVITY_YES)
brake)
, (recent_ACTIVITY_INACTIVE, brake)
]
, storeI64 (symbol "recent_activity") 0 (constI64 recent_ACTIVITY_YES))
switchI64 (extendUInt32 prev_what_next) $ \brake ->
( [ (next_ThreadKilled, mempty)
, ( next_ThreadComplete
, do putLVal ret $ constI32 ret_ThreadFinished
brake)
, ( next_ThreadRunGHC
, do r <-
call'
"StgRun"
[ symbol "stg_returnToStackTop"
, mainCapability `addInt64` constI64 offset_Capability_r
]
I64
putLVal ret $ wrapInt64 $ loadI64 r offset_StgRegTable_rRet
brake)
]
, emit $ marshalErrorCode errIllegalPrevWhatNext None)
storeI8 cap offset_Capability_in_haskell $ constI32 0
putLVal t $
loadI64 cap (offset_Capability_r + offset_StgRegTable_rCurrentTSO)
storeI64 cap (offset_Capability_r + offset_StgRegTable_rCurrentTSO) $
constI64 0
assert opts $ loadI64 (getLVal t) offset_StgTSO_cap `eqInt64` cap
putLVal ready_to_gc $ constI32 0
switchI64 (extendUInt32 (getLVal ret)) $ \brake ->
( [ ( ret_HeapOverflow
, do scheduleHandleHeapOverflow cap (getLVal t) >>=
putLVal ready_to_gc
brake)
, ( ret_StackOverflow
, do call "threadStackOverflow" [cap, getLVal t]
call "pushOnRunQueue" [cap, getLVal t]
brake)
, ( ret_ThreadYielding
, do scheduleHandleYield cap (getLVal t) prev_what_next >>=
break' run_thread_lbl
brake)
, ( ret_ThreadBlocked
, do scheduleHandleThreadBlocked (getLVal t)
brake)
, ( ret_ThreadFinished
, do scheduleHandleThreadFinished opts cap task (getLVal t) >>=
break' sched_block_lbl
brake)
]
, emit $ marshalErrorCode errIllegalThreadReturnCode None)
need_heap_profile <- scheduleNeedHeapProfile (getLVal ready_to_gc)
if'
(getLVal ready_to_gc `orInt32` need_heap_profile)
(scheduleDoGC cap task (constI32 0))
mempty
break' sched_loop_lbl Null
scheduleWaitThreadFunction opts =
runEDSL $ do
[tso, ret, cap] <- params [I64, I64, I64]
task <- i64Local $ loadI64 cap offset_Capability_running_task
@ -403,17 +881,12 @@ scheduleWaitThreadFunction _ =
incall <- i64Local $ loadI64 task offset_Task_incall
storeI64 incall offset_InCall_tso tso
storeI64 incall offset_InCall_ret ret
storeI64 cap (offset_Capability_r + offset_StgRegTable_rCurrentTSO) tso
storeI32 cap offset_Capability_interrupt (constI32 0)
_ <-
call'
"StgRun"
[ symbol "stg_returnToStackTop"
, cap `addInt64` constI64 offset_Capability_r
]
I64
storeI64 incall offset_InCall_ret $
loadI64 (loadI64 tso $ offset_StgTSO_StgStack + offset_StgStack_sp) 8
storeI32 incall offset_InCall_rstat $ constI32 scheduler_NoStatus
appendToRunQueue opts cap tso
schedule opts cap task
assert opts $
loadI32 (loadI64 task offset_Task_incall) offset_InCall_rstat `neInt32`
constI32 scheduler_NoStatus
createThreadFunction _ =
runEDSL $ do
@ -431,9 +904,26 @@ createThreadFunction _ =
storeI64 stack_p offset_StgStack_sp $
(stack_p `addInt64` constI64 offset_StgStack_stack) `addInt64`
stack_size_w
storeI32 stack_p offset_StgStack_dirty $ constI32 1
storeI64 tso_p 0 $ symbol "stg_TSO_info"
storeI16 tso_p offset_StgTSO_what_next $ constI32 next_ThreadRunGHC
storeI16 tso_p offset_StgTSO_why_blocked $ constI32 blocked_NotBlocked
storeI64
tso_p
(offset_StgTSO_block_info + offset_StgTSOBlockInfo_closure)
endTSOQueue
storeI64 tso_p offset_StgTSO_blocked_exceptions endTSOQueue
storeI64 tso_p offset_StgTSO_bq endTSOQueue
storeI32 tso_p offset_StgTSO_flags $ constI32 0
storeI32 tso_p offset_StgTSO_dirty $ constI32 1
storeI64 tso_p offset_StgTSO__link endTSOQueue
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
storeI64 tso_p offset_StgTSO_alloc_limit (constI64 0)
storeI64 tso_p offset_StgTSO_trec $ symbol "stg_NO_TREC_closure"
storeI64 stack_p offset_StgStack_sp $
loadI64 stack_p offset_StgStack_sp `subInt64`
constI64 (8 * roundup_bytes_to_words sizeof_StgStopFrame)
@ -448,15 +938,30 @@ pushClosure tso c = do
loadI64 stack_p offset_StgStack_sp `subInt64` constI64 8
storeI64 (loadI64 stack_p offset_StgStack_sp) 0 c
createThreadHelper :: (Expression -> [Expression]) -> EDSL ()
createThreadHelper mk_closures = do
setReturnType I64
[cap, stack_size, closure] <- params [I64, I64, I64]
t <- call' "createThread" [cap, stack_size] I64
for_ (mk_closures closure) $ pushClosure t
emit t
createGenThreadFunction _ =
runEDSL $ createThreadHelper $ \closure -> [closure, symbol "stg_enter_info"]
createIOThreadFunction _ =
runEDSL $ do
setReturnType I64
[cap, stack_size, closure] <- params [I64, I64, I64]
t <- call' "createThread" [cap, stack_size] I64
pushClosure t $ symbol "stg_ap_v_info"
pushClosure t closure
pushClosure t $ symbol "stg_enter_info"
emit t
runEDSL $
createThreadHelper $ \closure ->
[symbol "stg_ap_v_info", closure, symbol "stg_enter_info"]
createStrictIOThreadFunction _ =
runEDSL $
createThreadHelper $ \closure ->
[ symbol "stg_forceIO_info"
, symbol "stg_ap_v_info"
, closure
, symbol "stg_enter_info"
]
allocateFunction _ =
runEDSL $ do
@ -612,8 +1117,9 @@ memoryTrapFunction _ =
{ condition =
V.foldl1' (Binary OrInt32) $
V.fromList $
[ guard_struct (ConstI64 0) 8 []
, guard_struct
[ guard_struct (ConstI64 0) 16 []
, (task_p `neInt64` constI64 0) `andInt32`
guard_struct
task_p
sizeof_Task
[offset_Task_cap, offset_Task_incall]
@ -625,11 +1131,23 @@ memoryTrapFunction _ =
guard_struct
tso_p
sizeof_StgTSO
[ offset_StgTSO_alloc_limit
[ 0
, offset_StgTSO_alloc_limit
, offset_StgTSO_blocked_exceptions
, offset_StgTSO_block_info
, offset_StgTSO_bound
, offset_StgTSO_bq
, offset_StgTSO_bound
, offset_StgTSO_cap
, offset_StgTSO_dirty
, offset_StgTSO_flags
, offset_StgTSO_saved_errno
, offset_StgTSO_stackobj
, offset_StgTSO_tot_stack_size
, offset_StgTSO_trec
, offset_StgTSO_what_next
, offset_StgTSO_why_blocked
, offset_StgTSO__link
]
}
] <>

View File

@ -26,12 +26,15 @@ module Asterius.EDSL
, pointerI64
, pointerI32
, pointerI16
, pointerI8
, loadI64
, loadI32
, loadI16
, loadI8
, storeI64
, storeI32
, storeI16
, storeI8
, call
, call'
, callImport
@ -43,17 +46,31 @@ module Asterius.EDSL
, if'
, break'
, whileLoop
, switchI64
, notInt32
, eqZInt64
, eqZInt32
, extendUInt32
, wrapInt64
, convertUInt64ToFloat64
, truncUFloat64ToInt64
, growMemory
, addInt64
, subInt64
, mulInt64
, divUInt64
, gtUInt64
, geUInt64
, addInt32
, subInt32
, mulInt32
, eqInt64
, eqInt32
, leUInt64
, neInt64
, neInt32
, andInt32
, orInt32
, symbol
, constI32
, constI64
@ -68,6 +85,7 @@ module Asterius.EDSL
, currentNursery
, hpAlloc
, mainCapability
, endTSOQueue
) where
import Asterius.Internals
@ -110,14 +128,12 @@ instance Monoid a => Monoid (EDSL a) where
emit :: Expression -> EDSL ()
emit e = EDSL $ modify' $ \s@EDSLState {..} -> s {exprBuf = exprBuf `DL.snoc` e}
bundleExpressions :: DL.DList Expression -> Expression
bundleExpressions es =
bundleExpressions :: [Expression] -> Expression
bundleExpressions el =
case el of
[] -> Nop
[e] -> e
_ -> Block {name = mempty, bodys = V.fromList el, valueType = Auto}
where
el = DL.toList es
runEDSL :: EDSL () -> AsteriusFunction
runEDSL (EDSL m) =
@ -125,7 +141,7 @@ runEDSL (EDSL m) =
{ functionType =
FunctionType
{returnType = retType, paramTypes = V.fromList $ DL.toList paramBuf}
, body = bundleExpressions exprBuf
, body = bundleExpressions $ DL.toList exprBuf
}
where
EDSLState {..} = execState m initialEDSLState
@ -225,27 +241,34 @@ pointer vt b bp o =
0 -> bp
_ -> bp `addInt64` constI64 o
pointerI64, pointerI32, pointerI16 :: Expression -> Int -> LVal
pointerI64, pointerI32, pointerI16, pointerI8 :: Expression -> Int -> LVal
pointerI64 = pointer I64 8
pointerI32 = pointer I32 4
pointerI16 = pointer I32 2
loadI64, loadI32, loadI16 :: Expression -> Int -> Expression
pointerI8 = pointer I32 1
loadI64, loadI32, loadI16, loadI8 :: Expression -> Int -> Expression
loadI64 bp o = getLVal $ pointerI64 bp o
loadI32 bp o = getLVal $ pointerI32 bp o
loadI16 bp o = getLVal $ pointerI16 bp o
storeI64, storeI32, storeI16 :: Expression -> Int -> Expression -> EDSL ()
loadI8 bp o = getLVal $ pointerI8 bp o
storeI64, storeI32, storeI16, storeI8 ::
Expression -> Int -> Expression -> EDSL ()
storeI64 bp o = putLVal $ pointerI64 bp o
storeI32 bp o = putLVal $ pointerI32 bp o
storeI16 bp o = putLVal $ pointerI16 bp o
storeI8 bp o = putLVal $ pointerI8 bp o
call :: AsteriusEntitySymbol -> [Expression] -> EDSL ()
call f xs = emit Call {target = f, operands = V.fromList xs, valueType = None}
@ -303,10 +326,17 @@ block' cont = do
Block
{name = unLabel lbl, bodys = V.fromList $ DL.toList es, valueType = Auto}
blockWithLabel :: Label -> EDSL () -> EDSL ()
blockWithLabel lbl m = do
es <- newScope m
emit
Block
{name = unLabel lbl, bodys = V.fromList $ DL.toList es, valueType = Auto}
loop' cont = do
lbl <- newLabel
es <- newScope $ cont lbl
emit Loop {name = unLabel lbl, body = bundleExpressions es}
emit Loop {name = unLabel lbl, body = bundleExpressions $ DL.toList es}
if' :: Expression -> EDSL () -> EDSL () -> EDSL ()
if' cond t f = do
@ -315,8 +345,8 @@ if' cond t f = do
emit
If
{ condition = cond
, ifTrue = bundleExpressions t_es
, ifFalse = bundleExpressions f_es
, ifTrue = bundleExpressions $ DL.toList t_es
, ifFalse = bundleExpressions $ DL.toList f_es
}
break' :: Label -> Expression -> EDSL ()
@ -326,16 +356,51 @@ break' (Label lbl) cond =
whileLoop :: Expression -> EDSL () -> EDSL ()
whileLoop cond body = loop' $ \lbl -> if' cond (body *> break' lbl Null) mempty
eqZInt64, extendUInt32, wrapInt64, growMemory :: Expression -> Expression
switchI64 :: Expression -> (EDSL () -> ([(Int, EDSL ())], EDSL ())) -> EDSL ()
switchI64 cond make_clauses =
block' $ \switch_lbl ->
let exit_switch = break' switch_lbl Null
(clauses, def_clause) = make_clauses exit_switch
switch_block = do
switch_def_lbl <- newLabel
blockWithLabel switch_def_lbl $ do
clause_seq <-
for (reverse clauses) $ \(clause_i, clause_m) -> do
clause_lbl <- newLabel
pure (clause_i, clause_lbl, clause_m)
foldr
(\(_, clause_lbl, clause_m) tot_m -> do
blockWithLabel clause_lbl tot_m
clause_m)
(foldr
(\(clause_i, clause_lbl, _) br_m -> do
break' clause_lbl $ cond `eqInt64` constI64 clause_i
br_m)
(break' switch_def_lbl Null)
clause_seq)
clause_seq
def_clause
in switch_block
notInt32, eqZInt64, eqZInt32, extendUInt32, wrapInt64, convertUInt64ToFloat64, truncUFloat64ToInt64, growMemory ::
Expression -> Expression
notInt32 = eqZInt32
eqZInt64 = Unary EqZInt64
eqZInt32 = Unary EqZInt32
extendUInt32 = Unary ExtendUInt32
wrapInt64 = Unary WrapInt64
convertUInt64ToFloat64 = Unary ConvertUInt64ToFloat64
truncUFloat64ToInt64 = Unary TruncUFloat64ToInt64
growMemory x = Host {hostOp = GrowMemory, name = "", operands = [x]}
addInt64, subInt64, mulInt64, divUInt64, gtUInt64, mulInt32, leUInt64 ::
addInt64, subInt64, mulInt64, divUInt64, gtUInt64, geUInt64, addInt32, subInt32, mulInt32, eqInt64, eqInt32, leUInt64, neInt64, neInt32, andInt32, orInt32 ::
Expression -> Expression -> Expression
addInt64 = Binary AddInt64
@ -347,10 +412,28 @@ divUInt64 = Binary DivUInt64
gtUInt64 = Binary GtUInt64
geUInt64 = Binary GeUInt64
addInt32 = Binary AddInt32
subInt32 = Binary SubInt32
mulInt32 = Binary MulInt32
eqInt64 = Binary EqInt64
eqInt32 = Binary EqInt32
leUInt64 = Binary LeUInt64
neInt64 = Binary NeInt64
neInt32 = Binary NeInt32
andInt32 = Binary AndInt32
orInt32 = Binary OrInt32
symbol :: AsteriusEntitySymbol -> Expression
symbol = Unresolved
@ -381,5 +464,7 @@ currentNursery = global CurrentNursery
hpAlloc = global HpAlloc
mainCapability :: Expression
mainCapability, endTSOQueue :: Expression
mainCapability = symbol "MainCapability"
endTSOQueue = symbol "stg_END_TSO_QUEUE_closure"

View File

@ -331,10 +331,9 @@ makeStaticsOffsetTable ::
makeStaticsOffsetTable AsteriusModule {..} = (last_o, fromList statics_map)
where
(last_o, statics_map) = layoutStatics $ sortOn fst $ HM.toList staticsMap
layoutStatics = foldl' iterLayoutStaticsState (8, [])
layoutStatics = foldl' iterLayoutStaticsState (16, [])
iterLayoutStaticsState (ptr, sym_map) (ss_sym, ss) =
( fromIntegral $
8 * roundup_bytes_to_words (fromIntegral ptr + asteriusStaticsSize ss)
( fromIntegral $ roundup (fromIntegral ptr + asteriusStaticsSize ss) 16
, (ss_sym, ptr) : sym_map)
makeMemory ::

View File

@ -1,6 +1,5 @@
{-# LANGUAGE BangPatterns #-}
{-# OPTIONS_GHC
-Wall -O2 -ddump-to-file -ddump-stg -ddump-cmm-raw -ddump-asm #-}
{-# OPTIONS_GHC -Wall -ddump-to-file -ddump-stg -ddump-cmm-raw -ddump-asm #-}
fib :: Int -> Int
fib n = go 0 1 0

View File

@ -1,4 +1,4 @@
{-# OPTIONS_GHC -Wall -O2 -ddump-to-file -ddump-rn -ddump-stg -ddump-cmm-raw -ddump-asm #-}
{-# OPTIONS_GHC -Wall -ddump-to-file -ddump-rn -ddump-stg -ddump-cmm-raw -ddump-asm #-}
foreign import javascript "new Date()" current_time :: IO JSRef

View File

@ -48,6 +48,8 @@ There are a few differences between Binaryen IR and the WebAssembly language:
As a result, you might notice that round-trip conversions (wasm => Binaryen IR => wasm) change code a little in some corner cases.
* When optimizing Binaryen uses an additional IR, Stack IR (see `src/wasm-stack.h`). Stack IR allows a bunch of optimizations that are tailored for the stack machine form of WebAssembly's binary format (but Stack IR is less efficient for general optimizations than the main Binaryen IR). If you have a wasm file that has been particularly well-optimized, a simple round-trip conversion (just read and write, without optimization) may cause more noticeable differences, as Binaryen fits it into Binaryen IR's more structured format. If you also optimize during the round-trip conversion then Stack IR opts will be run and the final wasm will be better optimized.
Notes when working with Binaryen IR:
* As mentioned above, Binaryen IR has a tree structure. As a result, each expression should have exactly one parent - you should not "reuse" a node by having it appear more than once in the tree. The motivation for this limitation is that when we optimize we modify nodes, so if they appear more than once in the tree, a change in one place can appear in another incorrectly.

View File

@ -131,6 +131,7 @@ echo "building shared bitcode"
$BINARYEN_SRC/passes/SimplifyLocals.cpp \
$BINARYEN_SRC/passes/SpillPointers.cpp \
$BINARYEN_SRC/passes/SSAify.cpp \
$BINARYEN_SRC/passes/StackIR.cpp \
$BINARYEN_SRC/passes/TrapMode.cpp \
$BINARYEN_SRC/passes/Untee.cpp \
$BINARYEN_SRC/passes/Vacuum.cpp \

View File

@ -468,6 +468,8 @@ def run_validator_tests():
run_command(cmd, expected_status=1)
cmd = WASM_AS + ['--validate=none', os.path.join(options.binaryen_test, 'validator', 'invalid_return.wast')]
run_command(cmd)
cmd = WASM_AS + [os.path.join(options.binaryen_test, 'validator', 'invalid_number.wast')]
run_command(cmd, expected_status=1)
def run_vanilla_tests():

View File

@ -58,8 +58,6 @@ class HashedExpressionMap : public std::unordered_map<HashedExpression, T, Expre
struct FunctionHasher : public WalkerPass<PostWalker<FunctionHasher>> {
bool isFunctionParallel() override { return true; }
typedef uint32_t HashType;
struct Map : public std::map<Function*, HashType> {};
FunctionHasher(Map* output) : output(output) {}

View File

@ -52,6 +52,23 @@ struct BinaryIndexes {
}
};
inline Function* copyFunction(Function* func, Module& out) {
auto* ret = new Function();
ret->name = func->name;
ret->result = func->result;
ret->params = func->params;
ret->vars = func->vars;
ret->type = Name(); // start with no named type; the names in the other module may differ
ret->localNames = func->localNames;
ret->localIndices = func->localIndices;
ret->debugLocations = func->debugLocations;
ret->body = ExpressionManipulator::copy(func->body, out);
// TODO: copy Stack IR
assert(!func->stackIR);
out.addFunction(ret);
return ret;
}
inline void copyModule(Module& in, Module& out) {
// we use names throughout, not raw points, so simple copying is fine
// for everything *but* expressions
@ -65,9 +82,7 @@ inline void copyModule(Module& in, Module& out) {
out.addExport(new Export(*curr));
}
for (auto& curr : in.functions) {
auto* func = new Function(*curr);
func->body = ExpressionManipulator::copy(func->body, out);
out.addFunction(func);
copyFunction(curr.get(), out);
}
for (auto& curr : in.globals) {
out.addGlobal(new Global(*curr));
@ -85,19 +100,6 @@ inline void copyModule(Module& in, Module& out) {
out.debugInfoFileNames = in.debugInfoFileNames;
}
inline Function* copyFunction(Module& in, Module& out, Name name) {
Function *ret = out.getFunctionOrNull(name);
if (ret != nullptr) {
return ret;
}
auto* curr = in.getFunction(name);
auto* func = new Function(*curr);
func->body = ExpressionManipulator::copy(func->body, out);
func->type = Name();
out.addFunction(func);
return func;
}
} // namespace ModuleUtils
} // namespace wasm

View File

@ -88,7 +88,7 @@ struct ReFinalize : public WalkerPass<PostWalker<ReFinalize, OverriddenVisitor<R
std::map<Name, Type> breakValues;
void visitBlock(Block *curr) {
void visitBlock(Block* curr) {
if (curr->list.size() == 0) {
curr->type = none;
return;
@ -129,13 +129,13 @@ struct ReFinalize : public WalkerPass<PostWalker<ReFinalize, OverriddenVisitor<R
}
}
}
void visitIf(If *curr) { curr->finalize(); }
void visitLoop(Loop *curr) { curr->finalize(); }
void visitBreak(Break *curr) {
void visitIf(If* curr) { curr->finalize(); }
void visitLoop(Loop* curr) { curr->finalize(); }
void visitBreak(Break* curr) {
curr->finalize();
updateBreakValueType(curr->name, getValueType(curr->value));
}
void visitSwitch(Switch *curr) {
void visitSwitch(Switch* curr) {
curr->finalize();
auto valueType = getValueType(curr->value);
for (auto target : curr->targets) {
@ -143,28 +143,28 @@ struct ReFinalize : public WalkerPass<PostWalker<ReFinalize, OverriddenVisitor<R
}
updateBreakValueType(curr->default_, valueType);
}
void visitCall(Call *curr) { curr->finalize(); }
void visitCallImport(CallImport *curr) { curr->finalize(); }
void visitCallIndirect(CallIndirect *curr) { curr->finalize(); }
void visitGetLocal(GetLocal *curr) { curr->finalize(); }
void visitSetLocal(SetLocal *curr) { curr->finalize(); }
void visitGetGlobal(GetGlobal *curr) { curr->finalize(); }
void visitSetGlobal(SetGlobal *curr) { curr->finalize(); }
void visitLoad(Load *curr) { curr->finalize(); }
void visitStore(Store *curr) { curr->finalize(); }
void visitAtomicRMW(AtomicRMW *curr) { curr->finalize(); }
void visitAtomicCmpxchg(AtomicCmpxchg *curr) { curr->finalize(); }
void visitCall(Call* curr) { curr->finalize(); }
void visitCallImport(CallImport* curr) { curr->finalize(); }
void visitCallIndirect(CallIndirect* curr) { curr->finalize(); }
void visitGetLocal(GetLocal* curr) { curr->finalize(); }
void visitSetLocal(SetLocal* curr) { curr->finalize(); }
void visitGetGlobal(GetGlobal* curr) { curr->finalize(); }
void visitSetGlobal(SetGlobal* curr) { curr->finalize(); }
void visitLoad(Load* curr) { curr->finalize(); }
void visitStore(Store* curr) { curr->finalize(); }
void visitAtomicRMW(AtomicRMW* curr) { curr->finalize(); }
void visitAtomicCmpxchg(AtomicCmpxchg* curr) { curr->finalize(); }
void visitAtomicWait(AtomicWait* curr) { curr->finalize(); }
void visitAtomicWake(AtomicWake* curr) { curr->finalize(); }
void visitConst(Const *curr) { curr->finalize(); }
void visitUnary(Unary *curr) { curr->finalize(); }
void visitBinary(Binary *curr) { curr->finalize(); }
void visitSelect(Select *curr) { curr->finalize(); }
void visitDrop(Drop *curr) { curr->finalize(); }
void visitReturn(Return *curr) { curr->finalize(); }
void visitHost(Host *curr) { curr->finalize(); }
void visitNop(Nop *curr) { curr->finalize(); }
void visitUnreachable(Unreachable *curr) { curr->finalize(); }
void visitConst(Const* curr) { curr->finalize(); }
void visitUnary(Unary* curr) { curr->finalize(); }
void visitBinary(Binary* curr) { curr->finalize(); }
void visitSelect(Select* curr) { curr->finalize(); }
void visitDrop(Drop* curr) { curr->finalize(); }
void visitReturn(Return* curr) { curr->finalize(); }
void visitHost(Host* curr) { curr->finalize(); }
void visitNop(Nop* curr) { curr->finalize(); }
void visitUnreachable(Unreachable* curr) { curr->finalize(); }
void visitFunction(Function* curr) {
// we may have changed the body from unreachable to none, which might be bad
@ -197,33 +197,33 @@ struct ReFinalize : public WalkerPass<PostWalker<ReFinalize, OverriddenVisitor<R
// Re-finalize a single node. This is slow, if you want to refinalize
// an entire ast, use ReFinalize
struct ReFinalizeNode : public OverriddenVisitor<ReFinalizeNode> {
void visitBlock(Block *curr) { curr->finalize(); }
void visitIf(If *curr) { curr->finalize(); }
void visitLoop(Loop *curr) { curr->finalize(); }
void visitBreak(Break *curr) { curr->finalize(); }
void visitSwitch(Switch *curr) { curr->finalize(); }
void visitCall(Call *curr) { curr->finalize(); }
void visitCallImport(CallImport *curr) { curr->finalize(); }
void visitCallIndirect(CallIndirect *curr) { curr->finalize(); }
void visitGetLocal(GetLocal *curr) { curr->finalize(); }
void visitSetLocal(SetLocal *curr) { curr->finalize(); }
void visitGetGlobal(GetGlobal *curr) { curr->finalize(); }
void visitSetGlobal(SetGlobal *curr) { curr->finalize(); }
void visitLoad(Load *curr) { curr->finalize(); }
void visitStore(Store *curr) { curr->finalize(); }
void visitBlock(Block* curr) { curr->finalize(); }
void visitIf(If* curr) { curr->finalize(); }
void visitLoop(Loop* curr) { curr->finalize(); }
void visitBreak(Break* curr) { curr->finalize(); }
void visitSwitch(Switch* curr) { curr->finalize(); }
void visitCall(Call* curr) { curr->finalize(); }
void visitCallImport(CallImport* curr) { curr->finalize(); }
void visitCallIndirect(CallIndirect* curr) { curr->finalize(); }
void visitGetLocal(GetLocal* curr) { curr->finalize(); }
void visitSetLocal(SetLocal* curr) { curr->finalize(); }
void visitGetGlobal(GetGlobal* curr) { curr->finalize(); }
void visitSetGlobal(SetGlobal* curr) { curr->finalize(); }
void visitLoad(Load* curr) { curr->finalize(); }
void visitStore(Store* curr) { curr->finalize(); }
void visitAtomicRMW(AtomicRMW* curr) { curr->finalize(); }
void visitAtomicCmpxchg(AtomicCmpxchg* curr) { curr->finalize(); }
void visitAtomicWait(AtomicWait* curr) { curr->finalize(); }
void visitAtomicWake(AtomicWake* curr) { curr->finalize(); }
void visitConst(Const *curr) { curr->finalize(); }
void visitUnary(Unary *curr) { curr->finalize(); }
void visitBinary(Binary *curr) { curr->finalize(); }
void visitSelect(Select *curr) { curr->finalize(); }
void visitDrop(Drop *curr) { curr->finalize(); }
void visitReturn(Return *curr) { curr->finalize(); }
void visitHost(Host *curr) { curr->finalize(); }
void visitNop(Nop *curr) { curr->finalize(); }
void visitUnreachable(Unreachable *curr) { curr->finalize(); }
void visitConst(Const* curr) { curr->finalize(); }
void visitUnary(Unary* curr) { curr->finalize(); }
void visitBinary(Binary* curr) { curr->finalize(); }
void visitSelect(Select* curr) { curr->finalize(); }
void visitDrop(Drop* curr) { curr->finalize(); }
void visitReturn(Return* curr) { curr->finalize(); }
void visitHost(Host* curr) { curr->finalize(); }
void visitNop(Nop* curr) { curr->finalize(); }
void visitUnreachable(Unreachable* curr) { curr->finalize(); }
void visitFunctionType(FunctionType* curr) { WASM_UNREACHABLE(); }
void visitImport(Import* curr) { WASM_UNREACHABLE(); }

View File

@ -126,6 +126,7 @@ inline Expression* parseConst(cashew::IString s, Type type, MixedArena& allocato
if (modifier) {
std::istringstream istr(modifier);
istr >> std::hex >> pattern;
if (istr.fail()) throw ParseException("invalid f32 format");
pattern |= 0x7f800000U;
} else {
pattern = 0x7fc00000U;
@ -140,6 +141,7 @@ inline Expression* parseConst(cashew::IString s, Type type, MixedArena& allocato
if (modifier) {
std::istringstream istr(modifier);
istr >> std::hex >> pattern;
if (istr.fail()) throw ParseException("invalid f64 format");
pattern |= 0x7ff0000000000000ULL;
} else {
pattern = 0x7ff8000000000000UL;
@ -172,11 +174,13 @@ inline Expression* parseConst(cashew::IString s, Type type, MixedArena& allocato
std::istringstream istr(str);
uint32_t temp;
istr >> std::hex >> temp;
if (istr.fail()) throw ParseException("invalid i32 format");
ret->value = Literal(negative ? -temp : temp);
} else {
std::istringstream istr(str[0] == '-' ? str + 1 : str);
uint32_t temp;
istr >> temp;
if (istr.fail()) throw ParseException("invalid i32 format");
ret->value = Literal(str[0] == '-' ? -temp : temp);
}
break;
@ -188,11 +192,13 @@ inline Expression* parseConst(cashew::IString s, Type type, MixedArena& allocato
std::istringstream istr(str);
uint64_t temp;
istr >> std::hex >> temp;
if (istr.fail()) throw ParseException("invalid i64 format");
ret->value = Literal(negative ? -temp : temp);
} else {
std::istringstream istr(str[0] == '-' ? str + 1 : str);
uint64_t temp;
istr >> temp;
if (istr.fail()) throw ParseException("invalid i64 format");
ret->value = Literal(str[0] == '-' ? -temp : temp);
}
break;

View File

@ -76,6 +76,10 @@ struct PassOptions {
ret.setDefaultOptimizationOptions();
return ret;
}
static PassOptions getWithoutOptimization() {
return PassOptions(); // defaults are to not optimize
}
};
//
@ -137,6 +141,9 @@ struct PassRunner {
// Adds the default optimization passes that work on
// entire modules as a whole, and make sense to
// run after function passes.
// This is run at the very end of the optimization
// process - you can assume no other opts will be run
// afterwards.
void addDefaultGlobalOptimizationPostPasses();
// Run the passes on the module
@ -174,7 +181,16 @@ protected:
private:
void doAdd(Pass* pass);
void runPass(Pass* pass);
void runPassOnFunction(Pass* pass, Function* func);
// After running a pass, handle any changes due to
// how the pass is defined, such as clearing away any
// temporary data structures that the pass declares it
// invalidates.
// If a function is passed, we operate just on that function;
// otherwise, the whole module.
void handleAfterEffects(Pass* pass, Function* func=nullptr);
};
//
@ -223,6 +239,14 @@ public:
// this will create the parent class.
virtual Pass* create() { WASM_UNREACHABLE(); }
// Whether this pass modifies the Binaryen IR in the module. This is true for
// most passes, except for passes that have no side effects, or passes that
// only modify other things than Binaryen IR (for example, the Stack IR
// passes only modify that IR).
// This property is important as if Binaryen IR is modified, we need to throw
// out any Stack IR - it would need to be regenerated and optimized.
virtual bool modifiesBinaryenIR() { return true; }
std::string name;
protected:

View File

@ -32,6 +32,7 @@ SET(passes_SOURCES
Precompute.cpp
Print.cpp
PrintCallGraph.cpp
StackIR.cpp
RedundantSetElimination.cpp
RelooperJumpThreading.cpp
ReReloop.cpp

View File

@ -27,6 +27,7 @@
#include "emscripten-optimizer/istring.h"
#include "support/name.h"
#include "wasm-builder.h"
#include "ir/module-utils.h"
#include "ir/names.h"
#include "asmjs/shared-constants.h"
@ -143,19 +144,20 @@ struct I64ToI32Lowering : public WalkerPass<PostWalker<I64ToI32Lowering>> {
highBitVars.clear();
labelHighBitVars.clear();
freeTemps.clear();
Function oldFunc(*func);
Module temp;
auto* oldFunc = ModuleUtils::copyFunction(func, temp);
func->params.clear();
func->vars.clear();
func->localNames.clear();
func->localIndices.clear();
Index newIdx = 0;
Names::ensureNames(&oldFunc);
for (Index i = 0; i < oldFunc.getNumLocals(); ++i) {
assert(oldFunc.hasLocalName(i));
Name lowName = oldFunc.getLocalName(i);
Names::ensureNames(oldFunc);
for (Index i = 0; i < oldFunc->getNumLocals(); ++i) {
assert(oldFunc->hasLocalName(i));
Name lowName = oldFunc->getLocalName(i);
Name highName = makeHighName(lowName);
Type paramType = oldFunc.getLocalType(i);
auto builderFunc = (i < oldFunc.getVarIndexBase()) ?
Type paramType = oldFunc->getLocalType(i);
auto builderFunc = (i < oldFunc->getVarIndexBase()) ?
Builder::addParam :
static_cast<Index (*)(Function*, Name, Type)>(Builder::addVar);
if (paramType == i64) {

View File

@ -24,6 +24,8 @@ namespace wasm {
const Index OVERHEAD = 8;
struct MemoryPacking : public Pass {
bool modifiesBinaryenIR() override { return false; }
void run(PassRunner* runner, Module* module) override {
if (!module->memory.exists) return;
std::vector<Memory::Segment> packed;

View File

@ -32,6 +32,8 @@ static Counts lastCounts;
// Prints metrics between optimization passes.
struct Metrics : public WalkerPass<PostWalker<Metrics, UnifiedExpressionVisitor<Metrics>>> {
bool modifiesBinaryenIR() override { return false; }
bool byFunction;
Counts counts;

View File

@ -725,6 +725,9 @@ struct PrintSExpression : public Visitor<PrintSExpression> {
}
o << " (; " << functionIndexes[curr->name] << " ;)";
}
if (curr->stackIR && !minify) {
o << " (; has Stack IR ;)";
}
if (curr->type.is()) {
o << maybeSpace << "(type " << curr->type << ')';
}
@ -888,6 +891,8 @@ public:
Printer() : o(std::cout) {}
Printer(std::ostream* o) : o(*o) {}
bool modifiesBinaryenIR() override { return false; }
void run(PassRunner* runner, Module* module) override {
PrintSExpression print(o);
print.visitModule(module);

View File

@ -29,6 +29,8 @@
namespace wasm {
struct PrintCallGraph : public Pass {
bool modifiesBinaryenIR() override { return false; }
void run(PassRunner* runner, Module* module) override {
std::ostream &o = std::cout;
o << "digraph call {\n"

View File

@ -89,7 +89,11 @@ struct RemoveNonJSOpsPass : public WalkerPass<PostWalker<RemoveNonJSOpsPass>> {
// copy we then walk the function to rewrite any non-js operations it has
// as well.
for (auto &name : neededFunctions) {
doWalkFunction(ModuleUtils::copyFunction(intrinsicsModule, *module, name));
auto* func = module->getFunctionOrNull(name);
if (!func) {
func = ModuleUtils::copyFunction(intrinsicsModule.getFunction(name), *module);
}
doWalkFunction(func);
}
neededFunctions.clear();
}

View File

@ -0,0 +1,393 @@
/*
* Copyright 2018 WebAssembly Community Group participants
*
* Licensed under the Apache License, Version 2.0 (the "License");
* you may not use this file except in compliance with the License.
* You may obtain a copy of the License at
*
* http://www.apache.org/licenses/LICENSE-2.0
*
* Unless required by applicable law or agreed to in writing, software
* distributed under the License is distributed on an "AS IS" BASIS,
* WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
* See the License for the specific language governing permissions and
* limitations under the License.
*/
//
// Operations on Stack IR.
//
#include "wasm.h"
#include "pass.h"
#include "wasm-stack.h"
#include "ir/iteration.h"
#include "ir/local-graph.h"
namespace wasm {
// Generate Stack IR from Binaryen IR
struct GenerateStackIR : public WalkerPass<PostWalker<GenerateStackIR>> {
bool isFunctionParallel() override { return true; }
Pass* create() override { return new GenerateStackIR; }
bool modifiesBinaryenIR() override { return false; }
void doWalkFunction(Function* func) {
BufferWithRandomAccess buffer;
// a shim for the parent that a stackWriter expects - we don't need
// it to do anything, as we are just writing to Stack IR
struct Parent {
Module* module;
Parent(Module* module) : module(module) {}
Module* getModule() {
return module;
}
void writeDebugLocation(Expression* curr, Function* func) {
WASM_UNREACHABLE();
}
Index getFunctionIndex(Name name) {
WASM_UNREACHABLE();
}
Index getFunctionTypeIndex(Name name) {
WASM_UNREACHABLE();
}
Index getGlobalIndex(Name name) {
WASM_UNREACHABLE();
}
} parent(getModule());
StackWriter<StackWriterMode::Binaryen2Stack, Parent> stackWriter(parent, buffer, false);
stackWriter.setFunction(func);
stackWriter.visitPossibleBlockContents(func->body);
func->stackIR = make_unique<StackIR>();
func->stackIR->swap(stackWriter.stackIR);
}
};
Pass* createGenerateStackIRPass() {
return new GenerateStackIR();
}
// Print (for debugging purposes)
struct PrintStackIR : public WalkerPass<PostWalker<PrintStackIR>> {
// Not parallel: this pass is just for testing and debugging; keep the output
// sorted by function order.
bool isFunctionParallel() override { return false; }
Pass* create() override { return new PrintStackIR; }
bool modifiesBinaryenIR() override { return false; }
void doWalkFunction(Function* func) {
std::cout << func->name << ":\n";
if (func->stackIR) {
std::cout << *func->stackIR;
} else {
std::cout << " (no stack ir)";
}
std::cout << '\n';
}
};
Pass* createPrintStackIRPass() {
return new PrintStackIR();
}
// Optimize
class StackIROptimizer {
Function* func;
PassOptions& passOptions;
StackIR& insts;
public:
StackIROptimizer(Function* func, PassOptions& passOptions) :
func(func), passOptions(passOptions), insts(*func->stackIR.get()) {
assert(func->stackIR);
}
void run() {
dce();
// FIXME: local2Stack is currently rather slow (due to localGraph),
// so for now run it only when really optimizing
if (passOptions.optimizeLevel >= 3 || passOptions.shrinkLevel >= 1) {
local2Stack();
}
removeUnneededBlocks();
dce();
}
private:
// Passes.
// Remove unreachable code.
void dce() {
bool inUnreachableCode = false;
for (Index i = 0; i < insts.size(); i++) {
auto* inst = insts[i];
if (!inst) continue;
if (inUnreachableCode) {
// Does the unreachable code end here?
if (isControlFlowBarrier(inst)) {
inUnreachableCode = false;
} else {
// We can remove this.
removeAt(i);
}
} else if (inst->type == unreachable) {
inUnreachableCode = true;
}
}
}
// If ordered properly, we can avoid a set_local/get_local pair,
// and use the value directly from the stack, for example
// [..produce a value on the stack..]
// set_local $x
// [..much code..]
// get_local $x
// call $foo ;; use the value, foo(value)
// As long as the code in between does not modify $x, and has
// no control flow branching out, we can remove both the set
// and the get.
void local2Stack() {
// We use the localGraph to tell us if a get-set pair is indeed
// a set that is read by that get, and only that get. Note that we run
// this on the Binaryen IR, so we are assuming that no previous opt
// has changed the interaction of local operations.
// TODO: we can do this a lot faster, as we just care about linear
// control flow.
LocalGraph localGraph(func);
localGraph.computeInfluences();
// We maintain a stack of relevant values. This contains:
// * a null for each actual value that the value stack would have
// * an index of each SetLocal that *could* be on the value
// stack at that location.
const Index null = -1;
std::vector<Index> values;
// We also maintain a stack of values vectors for control flow,
// saving the stack as we enter and restoring it when we exit.
std::vector<std::vector<Index>> savedValues;
#ifdef STACK_OPT_DEBUG
std::cout << "func: " << func->name << '\n' << insts << '\n';
#endif
for (Index i = 0; i < insts.size(); i++) {
auto* inst = insts[i];
if (!inst) continue;
// First, consume values from the stack as required.
auto consumed = getNumConsumedValues(inst);
#ifdef STACK_OPT_DEBUG
std::cout << " " << i << " : " << *inst << ", " << values.size() << " on stack, will consume " << consumed << "\n ";
for (auto s : values) std::cout << s << ' ';
std::cout << '\n';
#endif
// TODO: currently we run dce before this, but if we didn't, we'd need
// to handle unreachable code here - it's ok to pop multiple values
// there even if the stack is at size 0.
while (consumed > 0) {
assert(values.size() > 0);
// Whenever we hit a possible stack value, kill it - it would
// be consumed here, so we can never optimize to it.
while (values.back() != null) {
values.pop_back();
assert(values.size() > 0);
}
// Finally, consume the actual value that is consumed here.
values.pop_back();
consumed--;
}
// After consuming, we can see what to do with this. First, handle
// control flow.
if (isControlFlowBegin(inst)) {
// Save the stack for when we end this control flow.
savedValues.push_back(values); // TODO: optimize copies
values.clear();
} else if (isControlFlowEnd(inst)) {
assert(!savedValues.empty());
values = savedValues.back();
savedValues.pop_back();
} else if (isControlFlow(inst)) {
// Otherwise, in the middle of control flow, just clear it
values.clear();
}
// This is something we should handle, look into it.
if (isConcreteType(inst->type)) {
bool optimized = false;
if (auto* get = inst->origin->dynCast<GetLocal>()) {
// This is a potential optimization opportunity! See if we
// can reach the set.
if (values.size() > 0) {
Index j = values.size() - 1;
while (1) {
// If there's an actual value in the way, we've failed.
auto index = values[j];
if (index == null) break;
auto* set = insts[index]->origin->cast<SetLocal>();
if (set->index == get->index) {
// This might be a proper set-get pair, where the set is
// used by this get and nothing else, check that.
auto& sets = localGraph.getSetses[get];
if (sets.size() == 1 && *sets.begin() == set) {
auto& setInfluences = localGraph.setInfluences[set];
if (setInfluences.size() == 1) {
assert(*setInfluences.begin() == get);
// Do it! The set and the get can go away, the proper
// value is on the stack.
#ifdef STACK_OPT_DEBUG
std::cout << " stackify the get\n";
#endif
insts[index] = nullptr;
insts[i] = nullptr;
// Continuing on from here, replace this on the stack
// with a null, representing a regular value. We
// keep possible values above us active - they may
// be optimized later, as they would be pushed after
// us, and used before us, so there is no conflict.
values[j] = null;
optimized = true;
break;
}
}
}
// We failed here. Can we look some more?
if (j == 0) break;
j--;
}
}
}
if (!optimized) {
// This is an actual regular value on the value stack.
values.push_back(null);
}
} else if (inst->origin->is<SetLocal>() && inst->type == none) {
// This set is potentially optimizable later, add to stack.
values.push_back(i);
}
}
}
// There may be unnecessary blocks we can remove: blocks
// without branches to them are always ok to remove.
// TODO: a branch to a block in an if body can become
// a branch to that if body
void removeUnneededBlocks() {
for (auto*& inst : insts) {
if (!inst) continue;
if (auto* block = inst->origin->dynCast<Block>()) {
if (!BranchUtils::BranchSeeker::hasNamed(block, block->name)) {
// TODO optimize, maybe run remove-unused-names
inst = nullptr;
}
}
}
}
// Utilities.
// A control flow "barrier" - a point where stack machine
// unreachability ends.
bool isControlFlowBarrier(StackInst* inst) {
switch (inst->op) {
case StackInst::BlockEnd:
case StackInst::IfElse:
case StackInst::IfEnd:
case StackInst::LoopEnd: {
return true;
}
default: {
return false;
}
}
}
// A control flow beginning.
bool isControlFlowBegin(StackInst* inst) {
switch (inst->op) {
case StackInst::BlockBegin:
case StackInst::IfBegin:
case StackInst::LoopBegin: {
return true;
}
default: {
return false;
}
}
}
// A control flow ending.
bool isControlFlowEnd(StackInst* inst) {
switch (inst->op) {
case StackInst::BlockEnd:
case StackInst::IfEnd:
case StackInst::LoopEnd: {
return true;
}
default: {
return false;
}
}
}
bool isControlFlow(StackInst* inst) {
return inst->op != StackInst::Basic;
}
// Remove the instruction at index i. If the instruction
// is control flow, and so has been expanded to multiple
// instructions, remove them as well.
void removeAt(Index i) {
auto* inst = insts[i];
insts[i] = nullptr;
if (inst->op == StackInst::Basic) {
return; // that was it
}
auto* origin = inst->origin;
while (1) {
i++;
assert(i < insts.size());
inst = insts[i];
insts[i] = nullptr;
if (inst && inst->origin == origin && isControlFlowEnd(inst)) {
return; // that's it, we removed it all
}
}
}
Index getNumConsumedValues(StackInst* inst) {
if (isControlFlow(inst)) {
// If consumes 1; that's it.
if (inst->op == StackInst::IfBegin) {
return 1;
}
return 0;
}
// Otherwise, for basic instructions, just count the expression children.
return ChildIterator(inst->origin).children.size();
}
};
struct OptimizeStackIR : public WalkerPass<PostWalker<OptimizeStackIR>> {
bool isFunctionParallel() override { return true; }
Pass* create() override { return new OptimizeStackIR; }
bool modifiesBinaryenIR() override { return false; }
void doWalkFunction(Function* func) {
if (!func->stackIR) {
return;
}
StackIROptimizer(func, getPassOptions()).run();
}
};
Pass* createOptimizeStackIRPass() {
return new OptimizeStackIR();
}
} // namespace wasm

View File

@ -22,6 +22,7 @@
#include <pass.h>
#include <wasm-validator.h>
#include <wasm-io.h>
#include "ir/hashed.h"
namespace wasm {
@ -76,6 +77,7 @@ void PassRegistry::registerPasses() {
registerPass("flatten", "flattens out code, removing nesting", createFlattenPass);
registerPass("fpcast-emu", "emulates function pointer casts, allowing incorrect indirect calls to (sometimes) work", createFuncCastEmulationPass);
registerPass("func-metrics", "reports function metrics", createFunctionMetricsPass);
registerPass("generate-stack-ir", "generate Stack IR", createGenerateStackIRPass);
registerPass("inlining", "inline functions (you probably want inlining-optimizing)", createInliningPass);
registerPass("inlining-optimizing", "inline functions and optimizes where we inlined", createInliningOptimizingPass);
registerPass("legalize-js-interface", "legalizes i64 types on the import/export boundary", createLegalizeJSInterfacePass);
@ -90,6 +92,7 @@ void PassRegistry::registerPasses() {
registerPass("metrics", "reports metrics", createMetricsPass);
registerPass("nm", "name list", createNameListPass);
registerPass("optimize-instructions", "optimizes instruction combinations", createOptimizeInstructionsPass);
registerPass("optimize-stack-ir", "optimize Stack IR", createOptimizeStackIRPass);
registerPass("pick-load-signs", "pick load signs based on their uses", createPickLoadSignsPass);
registerPass("post-emscripten", "miscellaneous optimizations for Emscripten-generated code", createPostEmscriptenPass);
registerPass("precompute", "computes compile-time evaluatable expressions", createPrecomputePass);
@ -98,6 +101,7 @@ void PassRegistry::registerPasses() {
registerPass("print-minified", "print in minified s-expression format", createMinifiedPrinterPass);
registerPass("print-full", "print in full s-expression format", createFullPrinterPass);
registerPass("print-call-graph", "print call graph", createPrintCallGraphPass);
registerPass("print-stack-ir", "print out Stack IR (useful for internal debugging)", createPrintStackIRPass);
registerPass("relooper-jump-threading", "thread relooper jumps (fastcomp output only)", createRelooperJumpThreadingPass);
registerPass("remove-non-js-ops", "removes operations incompatible with js", createRemoveNonJSOpsPass);
registerPass("remove-imports", "removes imports and replaces them with nops", createRemoveImportsPass);
@ -201,6 +205,12 @@ void PassRunner::addDefaultGlobalOptimizationPostPasses() {
add("duplicate-function-elimination"); // optimizations show more functions as duplicate
add("remove-unused-module-elements");
add("memory-packing");
// perform Stack IR optimizations here, at the very end of the
// optimization pipeline
if (options.optimizeLevel >= 2 || options.shrinkLevel >= 1) {
add("generate-stack-ir");
add("optimize-stack-ir");
}
}
static void dumpWast(Name name, Module* wasm) {
@ -252,7 +262,7 @@ void PassRunner::run() {
runPassOnFunction(pass, func.get());
}
} else {
pass->run(this, wasm);
runPass(pass);
}
auto after = std::chrono::steady_clock::now();
std::chrono::duration<double> diff = after - before;
@ -320,7 +330,7 @@ void PassRunner::run() {
stack.push_back(pass);
} else {
flush();
pass->run(this, wasm);
runPass(pass);
}
}
flush();
@ -347,11 +357,135 @@ void PassRunner::doAdd(Pass* pass) {
pass->prepareToRun(this, wasm);
}
// Checks that the state is valid before and after a
// pass runs on a function. We run these extra checks when
// pass-debug mode is enabled.
struct AfterEffectFunctionChecker {
Function* func;
Name name;
// Check Stack IR state: if the main IR changes, there should be no
// stack IR, as the stack IR would be wrong.
bool beganWithStackIR;
HashType originalFunctionHash;
// In the creator we can scan the state of the module and function before the
// pass runs.
AfterEffectFunctionChecker(Function* func) : func(func), name(func->name) {
beganWithStackIR = func->stackIR != nullptr;
if (beganWithStackIR) {
originalFunctionHash = FunctionHasher::hashFunction(func);
}
}
// This is called after the pass is run, at which time we can check things.
void check() {
assert(func->name == name); // no global module changes should have occurred
if (beganWithStackIR && func->stackIR) {
auto after = FunctionHasher::hashFunction(func);
if (after != originalFunctionHash) {
Fatal() << "[PassRunner] PASS_DEBUG check failed: had Stack IR before and after the pass ran, and the pass modified the main IR, which invalidates Stack IR - pass should have been marked 'modifiesBinaryenIR'";
}
}
}
};
// Runs checks on the entire module, in a non-function-parallel pass.
// In particular, in such a pass functions may be removed or renamed, track that.
struct AfterEffectModuleChecker {
Module* module;
std::vector<AfterEffectFunctionChecker> checkers;
bool beganWithAnyStackIR;
AfterEffectModuleChecker(Module* module) : module(module) {
for (auto& func : module->functions) {
checkers.emplace_back(func.get());
}
beganWithAnyStackIR = hasAnyStackIR();
}
void check() {
if (beganWithAnyStackIR && hasAnyStackIR()) {
// If anything changed to the functions, that's not good.
if (checkers.size() != module->functions.size()) {
error();
}
for (Index i = 0; i < checkers.size(); i++) {
// Did a pointer change? (a deallocated function could cause that)
if (module->functions[i].get() != checkers[i].func ||
module->functions[i]->body != checkers[i].func->body) {
error();
}
// Did a name change?
if (module->functions[i]->name != checkers[i].name) {
error();
}
}
// Global function state appears to not have been changed: the same
// functions are there. Look into their contents.
for (auto& checker : checkers) {
checker.check();
}
}
}
void error() {
Fatal() << "[PassRunner] PASS_DEBUG check failed: had Stack IR before and after the pass ran, and the pass modified global function state - pass should have been marked 'modifiesBinaryenIR'";
}
bool hasAnyStackIR() {
for (auto& func : module->functions) {
if (func->stackIR) {
return true;
}
}
return false;
}
};
void PassRunner::runPass(Pass* pass) {
std::unique_ptr<AfterEffectModuleChecker> checker;
if (getPassDebug()) {
checker = std::unique_ptr<AfterEffectModuleChecker>(
new AfterEffectModuleChecker(wasm));
}
pass->run(this, wasm);
handleAfterEffects(pass);
if (getPassDebug()) {
checker->check();
}
}
void PassRunner::runPassOnFunction(Pass* pass, Function* func) {
assert(pass->isFunctionParallel());
// function-parallel passes get a new instance per function
auto instance = std::unique_ptr<Pass>(pass->create());
std::unique_ptr<AfterEffectFunctionChecker> checker;
if (getPassDebug()) {
checker = std::unique_ptr<AfterEffectFunctionChecker>(
new AfterEffectFunctionChecker(func));
}
instance->runOnFunction(this, wasm, func);
handleAfterEffects(pass, func);
if (getPassDebug()) {
checker->check();
}
}
void PassRunner::handleAfterEffects(Pass* pass, Function* func) {
if (pass->modifiesBinaryenIR()) {
// If Binaryen IR is modified, Stack IR must be cleared - it would
// be out of sync in a potentially dangerous way.
if (func) {
func->stackIR.reset(nullptr);
} else {
for (auto& func : wasm->functions) {
func->stackIR.reset(nullptr);
}
}
}
}
int PassRunner::getPassDebug() {

View File

@ -34,6 +34,7 @@ Pass* createFlattenPass();
Pass* createFuncCastEmulationPass();
Pass* createFullPrinterPass();
Pass* createFunctionMetricsPass();
Pass* createGenerateStackIRPass();
Pass* createI64ToI32LoweringPass();
Pass* createInliningPass();
Pass* createInliningOptimizingPass();
@ -49,12 +50,14 @@ Pass* createMinifiedPrinterPass();
Pass* createMetricsPass();
Pass* createNameListPass();
Pass* createOptimizeInstructionsPass();
Pass* createOptimizeStackIRPass();
Pass* createPickLoadSignsPass();
Pass* createPostEmscriptenPass();
Pass* createPrecomputePass();
Pass* createPrecomputePropagatePass();
Pass* createPrinterPass();
Pass* createPrintCallGraphPass();
Pass* createPrintStackIRPass();
Pass* createRelooperJumpThreadingPass();
Pass* createRemoveNonJSOpsPass();
Pass* createRemoveImportsPass();

View File

@ -22,9 +22,11 @@
namespace wasm {
inline uint32_t rehash(uint32_t x, uint32_t y) {
typedef uint32_t HashType;
inline HashType rehash(HashType x, HashType y) {
// see http://www.cse.yorku.ca/~oz/hash.html and https://stackoverflow.com/a/2595226/1176841
uint32_t hash = 5381;
HashType hash = 5381;
while (x) {
hash = ((hash << 5) + hash) ^ (x & 0xff);
x >>= 8;
@ -37,9 +39,9 @@ inline uint32_t rehash(uint32_t x, uint32_t y) {
}
inline uint64_t rehash(uint64_t x, uint64_t y) {
auto ret = rehash(uint32_t(x), uint32_t(x >> 32));
ret = rehash(ret, uint32_t(y));
return rehash(ret, uint32_t(y >> 32));
auto ret = rehash(HashType(x), HashType(x >> 32));
ret = rehash(ret, HashType(y));
return rehash(ret, HashType(y >> 32));
}
} // namespace wasm

View File

@ -652,93 +652,14 @@ inline S32LEB binaryType(Type type) {
return S32LEB(ret);
}
class WasmBinaryWriter;
// Writes out binary format stack machine code for a Binaryen IR expression
class StackWriter : public Visitor<StackWriter> {
public:
// Without a function (offset for a global thing, etc.)
StackWriter(WasmBinaryWriter& parent, BufferWithRandomAccess& o, bool debug=false)
: func(nullptr), parent(parent), o(o), sourceMap(false), debug(debug) {}
// With a function - one is created for the entire function
StackWriter(Function* func, WasmBinaryWriter& parent, BufferWithRandomAccess& o, bool sourceMap=false, bool debug=false)
: func(func), parent(parent), o(o), sourceMap(sourceMap), debug(debug) {
mapLocals();
}
std::map<Type, size_t> numLocalsByType; // type => number of locals of that type in the compact form
// visits a node, emitting the proper code for it
void visit(Expression* curr);
// emits a node, but if it is a block with no name, emit a list of its contents
void visitPossibleBlockContents(Expression* curr);
void visitBlock(Block *curr);
void visitIf(If *curr);
void visitLoop(Loop *curr);
void visitBreak(Break *curr);
void visitSwitch(Switch *curr);
void visitCall(Call *curr);
void visitCallImport(CallImport *curr);
void visitCallIndirect(CallIndirect *curr);
void visitGetLocal(GetLocal *curr);
void visitSetLocal(SetLocal *curr);
void visitGetGlobal(GetGlobal *curr);
void visitSetGlobal(SetGlobal *curr);
void visitLoad(Load *curr);
void visitStore(Store *curr);
void visitAtomicRMW(AtomicRMW *curr);
void visitAtomicCmpxchg(AtomicCmpxchg *curr);
void visitAtomicWait(AtomicWait *curr);
void visitAtomicWake(AtomicWake *curr);
void visitConst(Const *curr);
void visitUnary(Unary *curr);
void visitBinary(Binary *curr);
void visitSelect(Select *curr);
void visitReturn(Return *curr);
void visitHost(Host *curr);
void visitNop(Nop *curr);
void visitUnreachable(Unreachable *curr);
void visitDrop(Drop *curr);
private:
Function* func;
WasmBinaryWriter& parent;
BufferWithRandomAccess& o;
bool sourceMap;
bool debug;
std::map<Index, size_t> mappedLocals; // local index => index in compact form of [all int32s][all int64s]etc
std::vector<Name> breakStack;
int32_t getBreakIndex(Name name);
void emitMemoryAccess(size_t alignment, size_t bytes, uint32_t offset);
void mapLocals();
};
// Writes out wasm to the binary format
class WasmBinaryWriter {
Module* wasm;
BufferWithRandomAccess& o;
bool debug;
bool debugInfo = true;
std::ostream* sourceMap = nullptr;
std::string sourceMapUrl;
std::string symbolMap;
MixedArena allocator;
Function::DebugLocation lastDebugLocation;
size_t lastBytecodeOffset;
void prepare();
public:
WasmBinaryWriter(Module* input, BufferWithRandomAccess& o, bool debug = false) : wasm(input), o(o), debug(debug) {
WasmBinaryWriter(Module* input,
BufferWithRandomAccess& o,
bool debug = false) :
wasm(input), o(o), debug(debug) {
prepare();
}
@ -814,6 +735,28 @@ public:
void emitBuffer(const char* data, size_t size);
void emitString(const char *str);
void finishUp();
Module* getModule() { return wasm; }
private:
Module* wasm;
BufferWithRandomAccess& o;
bool debug;
bool debugInfo = true;
std::ostream* sourceMap = nullptr;
std::string sourceMapUrl;
std::string symbolMap;
MixedArena allocator;
// storage of source map locations until the section is placed at its final location
// (shrinking LEBs may cause changes there)
std::vector<std::pair<size_t, const Function::DebugLocation*>> sourceMapLocations;
size_t sourceMapLocationsSizeAtSectionStart;
Function::DebugLocation lastDebugLocation;
void prepare();
};
class WasmBinaryBuilder {
@ -964,16 +907,16 @@ public:
BinaryConsts::ASTNodes readExpression(Expression*& curr);
void pushBlockElements(Block* curr, size_t start, size_t end);
void visitBlock(Block *curr);
void visitBlock(Block* curr);
// Gets a block of expressions. If it's just one, return that singleton.
Expression* getBlockOrSingleton(Type type);
void visitIf(If *curr);
void visitLoop(Loop *curr);
void visitIf(If* curr);
void visitLoop(Loop* curr);
BreakTarget getBreakTarget(int32_t offset);
void visitBreak(Break *curr, uint8_t code);
void visitSwitch(Switch *curr);
void visitSwitch(Switch* curr);
template<typename T>
void fillCall(T* call, FunctionType* type) {
@ -987,11 +930,11 @@ public:
}
Expression* visitCall();
void visitCallIndirect(CallIndirect *curr);
void visitGetLocal(GetLocal *curr);
void visitCallIndirect(CallIndirect* curr);
void visitGetLocal(GetLocal* curr);
void visitSetLocal(SetLocal *curr, uint8_t code);
void visitGetGlobal(GetGlobal *curr);
void visitSetGlobal(SetGlobal *curr);
void visitGetGlobal(GetGlobal* curr);
void visitSetGlobal(SetGlobal* curr);
void readMemoryAccess(Address& alignment, Address& offset);
bool maybeVisitLoad(Expression*& out, uint8_t code, bool isAtomic);
bool maybeVisitStore(Expression*& out, uint8_t code, bool isAtomic);
@ -1002,12 +945,12 @@ public:
bool maybeVisitConst(Expression*& out, uint8_t code);
bool maybeVisitUnary(Expression*& out, uint8_t code);
bool maybeVisitBinary(Expression*& out, uint8_t code);
void visitSelect(Select *curr);
void visitReturn(Return *curr);
void visitSelect(Select* curr);
void visitReturn(Return* curr);
bool maybeVisitHost(Expression*& out, uint8_t code);
void visitNop(Nop *curr);
void visitUnreachable(Unreachable *curr);
void visitDrop(Drop *curr);
void visitNop(Nop* curr);
void visitUnreachable(Unreachable* curr);
void visitDrop(Drop* curr);
void throwError(std::string text);
};

File diff suppressed because it is too large Load Diff

View File

@ -15,29 +15,10 @@
*/
//
// wasm.h: WebAssembly representation and processing library, in one
// header file.
// wasm.h: Define Binaryen IR, a representation for WebAssembly, with
// all core parts in one simple header file.
//
// This represents WebAssembly in an AST format, with a focus on making
// it easy to not just inspect but also to process. For example, some
// things that this enables are:
//
// * Interpreting: See wasm-interpreter.h.
// * Optimizing: See asm2wasm.h, which performs some optimizations
// after code generation.
// * Validation: See wasm-validator.h.
// * Pretty-printing: See Print.cpp.
//
//
// wasm.js internal WebAssembly representation design:
//
// * Unify where possible. Where size isn't a concern, combine
// classes, so binary ops and relational ops are joined. This
// simplifies that AST and makes traversals easier.
// * Optimize for size? This might justify separating if and if_else
// (so that if doesn't have an always-empty else; also it avoids
// a branch).
// For more overview, see README.md
//
#ifndef wasm_wasm_h
@ -601,6 +582,13 @@ public:
// Globals
// Forward declarations of Stack IR, as functions can contain it, see
// the stackIR property.
// Stack IR is a secondary IR to the main IR defined in this file (Binaryen
// IR). See wasm-stack.h.
class StackInst;
typedef std::vector<StackInst*> StackIR;
class Function {
public:
Name name;
@ -608,8 +596,20 @@ public:
std::vector<Type> params; // function locals are
std::vector<Type> vars; // params plus vars
Name type; // if null, it is implicit in params and result
// The body of the function
Expression* body;
// If present, this stack IR was generated from the main Binaryen IR body,
// and possibly optimized. If it is present when writing to wasm binary,
// it will be emitted instead of the main Binaryen IR.
//
// Note that no special care is taken to synchronize the two IRs - if you
// emit stack IR and then optimize the main IR, you need to recompute the
// stack IR. The Pass system will throw away Stack IR if a pass is run
// that declares it may modify Binaryen IR.
std::unique_ptr<StackIR> stackIR;
// local names. these are optional.
std::map<Index, Name> localNames;
std::map<Name, Index> localIndices;

View File

@ -19,7 +19,7 @@
#include "support/bits.h"
#include "wasm-binary.h"
#include "ir/branch-utils.h"
#include "wasm-stack.h"
#include "ir/module-utils.h"
namespace wasm {
@ -95,6 +95,7 @@ void WasmBinaryWriter::writeResizableLimits(Address initial, Address maximum,
template<typename T>
int32_t WasmBinaryWriter::startSection(T code) {
o << U32LEB(code);
if (sourceMap) sourceMapLocationsSizeAtSectionStart = sourceMapLocations.size();
return writeU32LEBPlaceholder(); // section size to be filled in later
}
@ -105,7 +106,13 @@ void WasmBinaryWriter::finishSection(int32_t start) {
// we can save some room, nice
assert(sizeFieldSize < MaxLEB32Bytes);
std::move(&o[start] + MaxLEB32Bytes, &o[start] + MaxLEB32Bytes + size, &o[start] + sizeFieldSize);
o.resize(o.size() - (MaxLEB32Bytes - sizeFieldSize));
auto adjustment = MaxLEB32Bytes - sizeFieldSize;
o.resize(o.size() - adjustment);
if (sourceMap) {
for (auto i = sourceMapLocationsSizeAtSectionStart; i < sourceMapLocations.size(); ++i) {
sourceMapLocations[i].first -= adjustment;
}
}
}
}
@ -210,7 +217,7 @@ void WasmBinaryWriter::writeFunctionSignatures() {
}
void WasmBinaryWriter::writeExpression(Expression* curr) {
StackWriter(*this, o, debug).visit(curr);
ExpressionStackWriter<WasmBinaryWriter>(curr, *this, o, debug);
}
void WasmBinaryWriter::writeFunctions() {
@ -220,25 +227,20 @@ void WasmBinaryWriter::writeFunctions() {
size_t total = wasm->functions.size();
o << U32LEB(total);
for (size_t i = 0; i < total; i++) {
size_t sourceMapLocationsSizeAtFunctionStart = sourceMapLocations.size();
if (debug) std::cerr << "write one at" << o.size() << std::endl;
size_t sizePos = writeU32LEBPlaceholder();
size_t start = o.size();
Function* function = wasm->functions[i].get();
if (debug) std::cerr << "writing" << function->name << std::endl;
StackWriter stackWriter(function, *this, o, sourceMap, debug);
o << U32LEB(
(stackWriter.numLocalsByType[i32] ? 1 : 0) +
(stackWriter.numLocalsByType[i64] ? 1 : 0) +
(stackWriter.numLocalsByType[f32] ? 1 : 0) +
(stackWriter.numLocalsByType[f64] ? 1 : 0)
);
if (stackWriter.numLocalsByType[i32]) o << U32LEB(stackWriter.numLocalsByType[i32]) << binaryType(i32);
if (stackWriter.numLocalsByType[i64]) o << U32LEB(stackWriter.numLocalsByType[i64]) << binaryType(i64);
if (stackWriter.numLocalsByType[f32]) o << U32LEB(stackWriter.numLocalsByType[f32]) << binaryType(f32);
if (stackWriter.numLocalsByType[f64]) o << U32LEB(stackWriter.numLocalsByType[f64]) << binaryType(f64);
stackWriter.visitPossibleBlockContents(function->body);
o << int8_t(BinaryConsts::End);
Function* func = wasm->functions[i].get();
if (debug) std::cerr << "writing" << func->name << std::endl;
// Emit Stack IR if present, and if we can
if (func->stackIR && !sourceMap) {
if (debug) std::cerr << "write Stack IR" << std::endl;
StackIRFunctionStackWriter<WasmBinaryWriter>(func, *this, o, debug);
} else {
if (debug) std::cerr << "write Binaryen IR" << std::endl;
FunctionStackWriter<WasmBinaryWriter>(func, *this, o, sourceMap, debug);
}
size_t size = o.size() - start;
assert(size <= std::numeric_limits<uint32_t>::max());
if (debug) std::cerr << "body size: " << size << ", writing at " << sizePos << ", next starts at " << o.size() << std::endl;
@ -247,9 +249,15 @@ void WasmBinaryWriter::writeFunctions() {
// we can save some room, nice
assert(sizeFieldSize < MaxLEB32Bytes);
std::move(&o[start], &o[start] + size, &o[sizePos] + sizeFieldSize);
o.resize(o.size() - (MaxLEB32Bytes - sizeFieldSize));
auto adjustment = MaxLEB32Bytes - sizeFieldSize;
o.resize(o.size() - adjustment);
if (sourceMap) {
for (auto i = sourceMapLocationsSizeAtFunctionStart; i < sourceMapLocations.size(); ++i) {
sourceMapLocations[i].first -= adjustment;
}
}
}
tableOfContents.functionBodies.emplace_back(function->name, sizePos + sizeFieldSize, size);
tableOfContents.functionBodies.emplace_back(func->name, sizePos + sizeFieldSize, size);
}
finishSection(start);
}
@ -482,7 +490,6 @@ void WasmBinaryWriter::writeSymbolMap() {
void WasmBinaryWriter::writeSourceMapProlog() {
lastDebugLocation = { 0, /* lineNumber = */ 1, 0 };
lastBytecodeOffset = 0;
*sourceMap << "{\"version\":3,\"sources\":[";
for (size_t i = 0; i < wasm->debugInfoFileNames.size(); i++) {
if (i > 0) *sourceMap << ",";
@ -492,10 +499,6 @@ void WasmBinaryWriter::writeSourceMapProlog() {
*sourceMap << "],\"names\":[],\"mappings\":\"";
}
void WasmBinaryWriter::writeSourceMapEpilog() {
*sourceMap << "\"}";
}
static void writeBase64VLQ(std::ostream& out, int32_t n) {
uint32_t value = n >= 0 ? n << 1 : ((-n) << 1) | 1;
while (1) {
@ -512,6 +515,26 @@ static void writeBase64VLQ(std::ostream& out, int32_t n) {
}
}
void WasmBinaryWriter::writeSourceMapEpilog() {
// write source map entries
size_t lastOffset = 0;
Function::DebugLocation lastLoc = { 0, /* lineNumber = */ 1, 0 };
for (const auto &offsetAndlocPair : sourceMapLocations) {
if (lastOffset > 0) {
*sourceMap << ",";
}
size_t offset = offsetAndlocPair.first;
const Function::DebugLocation& loc = *offsetAndlocPair.second;
writeBase64VLQ(*sourceMap, int32_t(offset - lastOffset));
writeBase64VLQ(*sourceMap, int32_t(loc.fileIndex - lastLoc.fileIndex));
writeBase64VLQ(*sourceMap, int32_t(loc.lineNumber - lastLoc.lineNumber));
writeBase64VLQ(*sourceMap, int32_t(loc.columnNumber - lastLoc.columnNumber));
lastLoc = loc;
lastOffset = offset;
}
*sourceMap << "\"}";
}
void WasmBinaryWriter::writeUserSections() {
for (auto& section : wasm->userSections) {
auto start = startSection(0);
@ -529,15 +552,8 @@ void WasmBinaryWriter::writeDebugLocation(Expression* curr, Function* func) {
if (iter != debugLocations.end() && iter->second != lastDebugLocation) {
auto offset = o.size();
auto& loc = iter->second;
if (lastBytecodeOffset > 0) {
*sourceMap << ",";
}
writeBase64VLQ(*sourceMap, int32_t(offset - lastBytecodeOffset));
writeBase64VLQ(*sourceMap, int32_t(loc.fileIndex - lastDebugLocation.fileIndex));
writeBase64VLQ(*sourceMap, int32_t(loc.lineNumber - lastDebugLocation.lineNumber));
writeBase64VLQ(*sourceMap, int32_t(loc.columnNumber - lastDebugLocation.columnNumber));
sourceMapLocations.emplace_back(offset, &loc);
lastDebugLocation = loc;
lastBytecodeOffset = offset;
}
}
@ -579,745 +595,6 @@ void WasmBinaryWriter::finishUp() {
}
}
// StackWriter
void StackWriter::mapLocals() {
for (Index i = 0; i < func->getNumParams(); i++) {
size_t curr = mappedLocals.size();
mappedLocals[i] = curr;
}
for (auto type : func->vars) {
numLocalsByType[type]++;
}
std::map<Type, size_t> currLocalsByType;
for (Index i = func->getVarIndexBase(); i < func->getNumLocals(); i++) {
size_t index = func->getVarIndexBase();
Type type = func->getLocalType(i);
currLocalsByType[type]++; // increment now for simplicity, must decrement it in returns
if (type == i32) {
mappedLocals[i] = index + currLocalsByType[i32] - 1;
continue;
}
index += numLocalsByType[i32];
if (type == i64) {
mappedLocals[i] = index + currLocalsByType[i64] - 1;
continue;
}
index += numLocalsByType[i64];
if (type == f32) {
mappedLocals[i] = index + currLocalsByType[f32] - 1;
continue;
}
index += numLocalsByType[f32];
if (type == f64) {
mappedLocals[i] = index + currLocalsByType[f64] - 1;
continue;
}
abort();
}
}
void StackWriter::visit(Expression* curr) {
if (sourceMap) {
parent.writeDebugLocation(curr, func);
}
Visitor<StackWriter>::visit(curr);
}
static bool brokenTo(Block* block) {
return block->name.is() && BranchUtils::BranchSeeker::hasNamed(block, block->name);
}
// emits a node, but if it is a block with no name, emit a list of its contents
void StackWriter::visitPossibleBlockContents(Expression* curr) {
auto* block = curr->dynCast<Block>();
if (!block || brokenTo(block)) {
visit(curr);
return;
}
for (auto* child : block->list) {
visit(child);
}
if (block->type == unreachable && block->list.back()->type != unreachable) {
// similar to in visitBlock, here we could skip emitting the block itself,
// but must still end the 'block' (the contents, really) with an unreachable
o << int8_t(BinaryConsts::Unreachable);
}
}
void StackWriter::visitBlock(Block *curr) {
if (debug) std::cerr << "zz node: Block" << std::endl;
o << int8_t(BinaryConsts::Block);
o << binaryType(curr->type != unreachable ? curr->type : none);
breakStack.push_back(curr->name);
Index i = 0;
for (auto* child : curr->list) {
if (debug) std::cerr << " " << size_t(curr) << "\n zz Block element " << i++ << std::endl;
visit(child);
}
breakStack.pop_back();
if (curr->type == unreachable) {
// an unreachable block is one that cannot be exited. We cannot encode this directly
// in wasm, where blocks must be none,i32,i64,f32,f64. Since the block cannot be
// exited, we can emit an unreachable at the end, and that will always be valid,
// and then the block is ok as a none
o << int8_t(BinaryConsts::Unreachable);
}
o << int8_t(BinaryConsts::End);
if (curr->type == unreachable) {
// and emit an unreachable *outside* the block too, so later things can pop anything
o << int8_t(BinaryConsts::Unreachable);
}
}
void StackWriter::visitIf(If *curr) {
if (debug) std::cerr << "zz node: If" << std::endl;
if (curr->condition->type == unreachable) {
// this if-else is unreachable because of the condition, i.e., the condition
// does not exit. So don't emit the if, but do consume the condition
visit(curr->condition);
o << int8_t(BinaryConsts::Unreachable);
return;
}
visit(curr->condition);
o << int8_t(BinaryConsts::If);
o << binaryType(curr->type != unreachable ? curr->type : none);
breakStack.push_back(IMPOSSIBLE_CONTINUE); // the binary format requires this; we have a block if we need one; TODO: optimize
visitPossibleBlockContents(curr->ifTrue); // TODO: emit block contents directly, if possible
breakStack.pop_back();
if (curr->ifFalse) {
o << int8_t(BinaryConsts::Else);
breakStack.push_back(IMPOSSIBLE_CONTINUE); // TODO ditto
visitPossibleBlockContents(curr->ifFalse);
breakStack.pop_back();
}
o << int8_t(BinaryConsts::End);
if (curr->type == unreachable) {
// we already handled the case of the condition being unreachable. otherwise,
// we may still be unreachable, if we are an if-else with both sides unreachable.
// wasm does not allow this to be emitted directly, so we must do something more. we could do
// better, but for now we emit an extra unreachable instruction after the if, so it is not consumed itself,
assert(curr->ifFalse);
o << int8_t(BinaryConsts::Unreachable);
}
}
void StackWriter::visitLoop(Loop *curr) {
if (debug) std::cerr << "zz node: Loop" << std::endl;
o << int8_t(BinaryConsts::Loop);
o << binaryType(curr->type != unreachable ? curr->type : none);
breakStack.push_back(curr->name);
visitPossibleBlockContents(curr->body);
breakStack.pop_back();
o << int8_t(BinaryConsts::End);
if (curr->type == unreachable) {
// we emitted a loop without a return type, so it must not be consumed
o << int8_t(BinaryConsts::Unreachable);
}
}
void StackWriter::visitBreak(Break *curr) {
if (debug) std::cerr << "zz node: Break" << std::endl;
if (curr->value) {
visit(curr->value);
}
if (curr->condition) visit(curr->condition);
o << int8_t(curr->condition ? BinaryConsts::BrIf : BinaryConsts::Br)
<< U32LEB(getBreakIndex(curr->name));
if (curr->condition && curr->type == unreachable) {
// a br_if is normally none or emits a value. if it is unreachable,
// then either the condition or the value is unreachable, which is
// extremely rare, and may require us to make the stack polymorphic
// (if the block we branch to has a value, we may lack one as we
// are not a reachable branch; the wasm spec on the other hand does
// presume the br_if emits a value of the right type, even if it
// popped unreachable)
o << int8_t(BinaryConsts::Unreachable);
}
}
void StackWriter::visitSwitch(Switch *curr) {
if (debug) std::cerr << "zz node: Switch" << std::endl;
if (curr->value) {
visit(curr->value);
}
visit(curr->condition);
if (!BranchUtils::isBranchReachable(curr)) {
// if the branch is not reachable, then it's dangerous to emit it, as
// wasm type checking rules are different, especially in unreachable
// code. so just don't emit that unreachable code.
o << int8_t(BinaryConsts::Unreachable);
return;
}
o << int8_t(BinaryConsts::TableSwitch) << U32LEB(curr->targets.size());
for (auto target : curr->targets) {
o << U32LEB(getBreakIndex(target));
}
o << U32LEB(getBreakIndex(curr->default_));
}
void StackWriter::visitCall(Call *curr) {
if (debug) std::cerr << "zz node: Call" << std::endl;
for (auto* operand : curr->operands) {
visit(operand);
}
o << int8_t(BinaryConsts::CallFunction) << U32LEB(parent.getFunctionIndex(curr->target));
if (curr->type == unreachable) {
o << int8_t(BinaryConsts::Unreachable);
}
}
void StackWriter::visitCallImport(CallImport *curr) {
if (debug) std::cerr << "zz node: CallImport" << std::endl;
for (auto* operand : curr->operands) {
visit(operand);
}
o << int8_t(BinaryConsts::CallFunction) << U32LEB(parent.getFunctionIndex(curr->target));
}
void StackWriter::visitCallIndirect(CallIndirect *curr) {
if (debug) std::cerr << "zz node: CallIndirect" << std::endl;
for (auto* operand : curr->operands) {
visit(operand);
}
visit(curr->target);
o << int8_t(BinaryConsts::CallIndirect)
<< U32LEB(parent.getFunctionTypeIndex(curr->fullType))
<< U32LEB(0); // Reserved flags field
if (curr->type == unreachable) {
o << int8_t(BinaryConsts::Unreachable);
}
}
void StackWriter::visitGetLocal(GetLocal *curr) {
if (debug) std::cerr << "zz node: GetLocal " << (o.size() + 1) << std::endl;
o << int8_t(BinaryConsts::GetLocal) << U32LEB(mappedLocals[curr->index]);
}
void StackWriter::visitSetLocal(SetLocal *curr) {
if (debug) std::cerr << "zz node: Set|TeeLocal" << std::endl;
visit(curr->value);
o << int8_t(curr->isTee() ? BinaryConsts::TeeLocal : BinaryConsts::SetLocal) << U32LEB(mappedLocals[curr->index]);
if (curr->type == unreachable) {
o << int8_t(BinaryConsts::Unreachable);
}
}
void StackWriter::visitGetGlobal(GetGlobal *curr) {
if (debug) std::cerr << "zz node: GetGlobal " << (o.size() + 1) << std::endl;
o << int8_t(BinaryConsts::GetGlobal) << U32LEB(parent.getGlobalIndex(curr->name));
}
void StackWriter::visitSetGlobal(SetGlobal *curr) {
if (debug) std::cerr << "zz node: SetGlobal" << std::endl;
visit(curr->value);
o << int8_t(BinaryConsts::SetGlobal) << U32LEB(parent.getGlobalIndex(curr->name));
}
void StackWriter::visitLoad(Load *curr) {
if (debug) std::cerr << "zz node: Load" << std::endl;
visit(curr->ptr);
if (!curr->isAtomic) {
switch (curr->type) {
case i32: {
switch (curr->bytes) {
case 1: o << int8_t(curr->signed_ ? BinaryConsts::I32LoadMem8S : BinaryConsts::I32LoadMem8U); break;
case 2: o << int8_t(curr->signed_ ? BinaryConsts::I32LoadMem16S : BinaryConsts::I32LoadMem16U); break;
case 4: o << int8_t(BinaryConsts::I32LoadMem); break;
default: abort();
}
break;
}
case i64: {
switch (curr->bytes) {
case 1: o << int8_t(curr->signed_ ? BinaryConsts::I64LoadMem8S : BinaryConsts::I64LoadMem8U); break;
case 2: o << int8_t(curr->signed_ ? BinaryConsts::I64LoadMem16S : BinaryConsts::I64LoadMem16U); break;
case 4: o << int8_t(curr->signed_ ? BinaryConsts::I64LoadMem32S : BinaryConsts::I64LoadMem32U); break;
case 8: o << int8_t(BinaryConsts::I64LoadMem); break;
default: abort();
}
break;
}
case f32: o << int8_t(BinaryConsts::F32LoadMem); break;
case f64: o << int8_t(BinaryConsts::F64LoadMem); break;
case unreachable: return; // the pointer is unreachable, so we are never reached; just don't emit a load
default: WASM_UNREACHABLE();
}
} else {
if (curr->type == unreachable) {
// don't even emit it; we don't know the right type
o << int8_t(BinaryConsts::Unreachable);
return;
}
o << int8_t(BinaryConsts::AtomicPrefix);
switch (curr->type) {
case i32: {
switch (curr->bytes) {
case 1: o << int8_t(BinaryConsts::I32AtomicLoad8U); break;
case 2: o << int8_t(BinaryConsts::I32AtomicLoad16U); break;
case 4: o << int8_t(BinaryConsts::I32AtomicLoad); break;
default: WASM_UNREACHABLE();
}
break;
}
case i64: {
switch (curr->bytes) {
case 1: o << int8_t(BinaryConsts::I64AtomicLoad8U); break;
case 2: o << int8_t(BinaryConsts::I64AtomicLoad16U); break;
case 4: o << int8_t(BinaryConsts::I64AtomicLoad32U); break;
case 8: o << int8_t(BinaryConsts::I64AtomicLoad); break;
default: WASM_UNREACHABLE();
}
break;
}
case unreachable: return;
default: WASM_UNREACHABLE();
}
}
emitMemoryAccess(curr->align, curr->bytes, curr->offset);
}
void StackWriter::visitStore(Store *curr) {
if (debug) std::cerr << "zz node: Store" << std::endl;
visit(curr->ptr);
visit(curr->value);
if (!curr->isAtomic) {
switch (curr->valueType) {
case i32: {
switch (curr->bytes) {
case 1: o << int8_t(BinaryConsts::I32StoreMem8); break;
case 2: o << int8_t(BinaryConsts::I32StoreMem16); break;
case 4: o << int8_t(BinaryConsts::I32StoreMem); break;
default: abort();
}
break;
}
case i64: {
switch (curr->bytes) {
case 1: o << int8_t(BinaryConsts::I64StoreMem8); break;
case 2: o << int8_t(BinaryConsts::I64StoreMem16); break;
case 4: o << int8_t(BinaryConsts::I64StoreMem32); break;
case 8: o << int8_t(BinaryConsts::I64StoreMem); break;
default: abort();
}
break;
}
case f32: o << int8_t(BinaryConsts::F32StoreMem); break;
case f64: o << int8_t(BinaryConsts::F64StoreMem); break;
default: abort();
}
} else {
if (curr->type == unreachable) {
// don't even emit it; we don't know the right type
o << int8_t(BinaryConsts::Unreachable);
return;
}
o << int8_t(BinaryConsts::AtomicPrefix);
switch (curr->valueType) {
case i32: {
switch (curr->bytes) {
case 1: o << int8_t(BinaryConsts::I32AtomicStore8); break;
case 2: o << int8_t(BinaryConsts::I32AtomicStore16); break;
case 4: o << int8_t(BinaryConsts::I32AtomicStore); break;
default: WASM_UNREACHABLE();
}
break;
}
case i64: {
switch (curr->bytes) {
case 1: o << int8_t(BinaryConsts::I64AtomicStore8); break;
case 2: o << int8_t(BinaryConsts::I64AtomicStore16); break;
case 4: o << int8_t(BinaryConsts::I64AtomicStore32); break;
case 8: o << int8_t(BinaryConsts::I64AtomicStore); break;
default: WASM_UNREACHABLE();
}
break;
}
default: WASM_UNREACHABLE();
}
}
emitMemoryAccess(curr->align, curr->bytes, curr->offset);
}
void StackWriter::visitAtomicRMW(AtomicRMW *curr) {
if (debug) std::cerr << "zz node: AtomicRMW" << std::endl;
visit(curr->ptr);
// stop if the rest isn't reachable anyhow
if (curr->ptr->type == unreachable) return;
visit(curr->value);
if (curr->value->type == unreachable) return;
if (curr->type == unreachable) {
// don't even emit it; we don't know the right type
o << int8_t(BinaryConsts::Unreachable);
return;
}
o << int8_t(BinaryConsts::AtomicPrefix);
#define CASE_FOR_OP(Op) \
case Op: \
switch (curr->type) { \
case i32: \
switch (curr->bytes) { \
case 1: o << int8_t(BinaryConsts::I32AtomicRMW##Op##8U); break; \
case 2: o << int8_t(BinaryConsts::I32AtomicRMW##Op##16U); break; \
case 4: o << int8_t(BinaryConsts::I32AtomicRMW##Op); break; \
default: WASM_UNREACHABLE(); \
} \
break; \
case i64: \
switch (curr->bytes) { \
case 1: o << int8_t(BinaryConsts::I64AtomicRMW##Op##8U); break; \
case 2: o << int8_t(BinaryConsts::I64AtomicRMW##Op##16U); break; \
case 4: o << int8_t(BinaryConsts::I64AtomicRMW##Op##32U); break; \
case 8: o << int8_t(BinaryConsts::I64AtomicRMW##Op); break; \
default: WASM_UNREACHABLE(); \
} \
break; \
default: WASM_UNREACHABLE(); \
} \
break
switch(curr->op) {
CASE_FOR_OP(Add);
CASE_FOR_OP(Sub);
CASE_FOR_OP(And);
CASE_FOR_OP(Or);
CASE_FOR_OP(Xor);
CASE_FOR_OP(Xchg);
default: WASM_UNREACHABLE();
}
#undef CASE_FOR_OP
emitMemoryAccess(curr->bytes, curr->bytes, curr->offset);
}
void StackWriter::visitAtomicCmpxchg(AtomicCmpxchg *curr) {
if (debug) std::cerr << "zz node: AtomicCmpxchg" << std::endl;
visit(curr->ptr);
// stop if the rest isn't reachable anyhow
if (curr->ptr->type == unreachable) return;
visit(curr->expected);
if (curr->expected->type == unreachable) return;
visit(curr->replacement);
if (curr->replacement->type == unreachable) return;
if (curr->type == unreachable) {
// don't even emit it; we don't know the right type
o << int8_t(BinaryConsts::Unreachable);
return;
}
o << int8_t(BinaryConsts::AtomicPrefix);
switch (curr->type) {
case i32:
switch (curr->bytes) {
case 1: o << int8_t(BinaryConsts::I32AtomicCmpxchg8U); break;
case 2: o << int8_t(BinaryConsts::I32AtomicCmpxchg16U); break;
case 4: o << int8_t(BinaryConsts::I32AtomicCmpxchg); break;
default: WASM_UNREACHABLE();
}
break;
case i64:
switch (curr->bytes) {
case 1: o << int8_t(BinaryConsts::I64AtomicCmpxchg8U); break;
case 2: o << int8_t(BinaryConsts::I64AtomicCmpxchg16U); break;
case 4: o << int8_t(BinaryConsts::I64AtomicCmpxchg32U); break;
case 8: o << int8_t(BinaryConsts::I64AtomicCmpxchg); break;
default: WASM_UNREACHABLE();
}
break;
default: WASM_UNREACHABLE();
}
emitMemoryAccess(curr->bytes, curr->bytes, curr->offset);
}
void StackWriter::visitAtomicWait(AtomicWait *curr) {
if (debug) std::cerr << "zz node: AtomicWait" << std::endl;
visit(curr->ptr);
// stop if the rest isn't reachable anyhow
if (curr->ptr->type == unreachable) return;
visit(curr->expected);
if (curr->expected->type == unreachable) return;
visit(curr->timeout);
if (curr->timeout->type == unreachable) return;
o << int8_t(BinaryConsts::AtomicPrefix);
switch (curr->expectedType) {
case i32: {
o << int8_t(BinaryConsts::I32AtomicWait);
emitMemoryAccess(4, 4, 0);
break;
}
case i64: {
o << int8_t(BinaryConsts::I64AtomicWait);
emitMemoryAccess(8, 8, 0);
break;
}
default: WASM_UNREACHABLE();
}
}
void StackWriter::visitAtomicWake(AtomicWake *curr) {
if (debug) std::cerr << "zz node: AtomicWake" << std::endl;
visit(curr->ptr);
// stop if the rest isn't reachable anyhow
if (curr->ptr->type == unreachable) return;
visit(curr->wakeCount);
if (curr->wakeCount->type == unreachable) return;
o << int8_t(BinaryConsts::AtomicPrefix) << int8_t(BinaryConsts::AtomicWake);
emitMemoryAccess(4, 4, 0);
}
void StackWriter::visitConst(Const *curr) {
if (debug) std::cerr << "zz node: Const" << curr << " : " << curr->type << std::endl;
switch (curr->type) {
case i32: {
o << int8_t(BinaryConsts::I32Const) << S32LEB(curr->value.geti32());
break;
}
case i64: {
o << int8_t(BinaryConsts::I64Const) << S64LEB(curr->value.geti64());
break;
}
case f32: {
o << int8_t(BinaryConsts::F32Const) << curr->value.reinterpreti32();
break;
}
case f64: {
o << int8_t(BinaryConsts::F64Const) << curr->value.reinterpreti64();
break;
}
default: abort();
}
if (debug) std::cerr << "zz const node done.\n";
}
void StackWriter::visitUnary(Unary *curr) {
if (debug) std::cerr << "zz node: Unary" << std::endl;
visit(curr->value);
switch (curr->op) {
case ClzInt32: o << int8_t(BinaryConsts::I32Clz); break;
case CtzInt32: o << int8_t(BinaryConsts::I32Ctz); break;
case PopcntInt32: o << int8_t(BinaryConsts::I32Popcnt); break;
case EqZInt32: o << int8_t(BinaryConsts::I32EqZ); break;
case ClzInt64: o << int8_t(BinaryConsts::I64Clz); break;
case CtzInt64: o << int8_t(BinaryConsts::I64Ctz); break;
case PopcntInt64: o << int8_t(BinaryConsts::I64Popcnt); break;
case EqZInt64: o << int8_t(BinaryConsts::I64EqZ); break;
case NegFloat32: o << int8_t(BinaryConsts::F32Neg); break;
case AbsFloat32: o << int8_t(BinaryConsts::F32Abs); break;
case CeilFloat32: o << int8_t(BinaryConsts::F32Ceil); break;
case FloorFloat32: o << int8_t(BinaryConsts::F32Floor); break;
case TruncFloat32: o << int8_t(BinaryConsts::F32Trunc); break;
case NearestFloat32: o << int8_t(BinaryConsts::F32NearestInt); break;
case SqrtFloat32: o << int8_t(BinaryConsts::F32Sqrt); break;
case NegFloat64: o << int8_t(BinaryConsts::F64Neg); break;
case AbsFloat64: o << int8_t(BinaryConsts::F64Abs); break;
case CeilFloat64: o << int8_t(BinaryConsts::F64Ceil); break;
case FloorFloat64: o << int8_t(BinaryConsts::F64Floor); break;
case TruncFloat64: o << int8_t(BinaryConsts::F64Trunc); break;
case NearestFloat64: o << int8_t(BinaryConsts::F64NearestInt); break;
case SqrtFloat64: o << int8_t(BinaryConsts::F64Sqrt); break;
case ExtendSInt32: o << int8_t(BinaryConsts::I64STruncI32); break;
case ExtendUInt32: o << int8_t(BinaryConsts::I64UTruncI32); break;
case WrapInt64: o << int8_t(BinaryConsts::I32ConvertI64); break;
case TruncUFloat32ToInt32: o << int8_t(BinaryConsts::I32UTruncF32); break;
case TruncUFloat32ToInt64: o << int8_t(BinaryConsts::I64UTruncF32); break;
case TruncSFloat32ToInt32: o << int8_t(BinaryConsts::I32STruncF32); break;
case TruncSFloat32ToInt64: o << int8_t(BinaryConsts::I64STruncF32); break;
case TruncUFloat64ToInt32: o << int8_t(BinaryConsts::I32UTruncF64); break;
case TruncUFloat64ToInt64: o << int8_t(BinaryConsts::I64UTruncF64); break;
case TruncSFloat64ToInt32: o << int8_t(BinaryConsts::I32STruncF64); break;
case TruncSFloat64ToInt64: o << int8_t(BinaryConsts::I64STruncF64); break;
case ConvertUInt32ToFloat32: o << int8_t(BinaryConsts::F32UConvertI32); break;
case ConvertUInt32ToFloat64: o << int8_t(BinaryConsts::F64UConvertI32); break;
case ConvertSInt32ToFloat32: o << int8_t(BinaryConsts::F32SConvertI32); break;
case ConvertSInt32ToFloat64: o << int8_t(BinaryConsts::F64SConvertI32); break;
case ConvertUInt64ToFloat32: o << int8_t(BinaryConsts::F32UConvertI64); break;
case ConvertUInt64ToFloat64: o << int8_t(BinaryConsts::F64UConvertI64); break;
case ConvertSInt64ToFloat32: o << int8_t(BinaryConsts::F32SConvertI64); break;
case ConvertSInt64ToFloat64: o << int8_t(BinaryConsts::F64SConvertI64); break;
case DemoteFloat64: o << int8_t(BinaryConsts::F32ConvertF64); break;
case PromoteFloat32: o << int8_t(BinaryConsts::F64ConvertF32); break;
case ReinterpretFloat32: o << int8_t(BinaryConsts::I32ReinterpretF32); break;
case ReinterpretFloat64: o << int8_t(BinaryConsts::I64ReinterpretF64); break;
case ReinterpretInt32: o << int8_t(BinaryConsts::F32ReinterpretI32); break;
case ReinterpretInt64: o << int8_t(BinaryConsts::F64ReinterpretI64); break;
case ExtendS8Int32: o << int8_t(BinaryConsts::I32ExtendS8); break;
case ExtendS16Int32: o << int8_t(BinaryConsts::I32ExtendS16); break;
case ExtendS8Int64: o << int8_t(BinaryConsts::I64ExtendS8); break;
case ExtendS16Int64: o << int8_t(BinaryConsts::I64ExtendS16); break;
case ExtendS32Int64: o << int8_t(BinaryConsts::I64ExtendS32); break;
default: abort();
}
if (curr->type == unreachable) {
o << int8_t(BinaryConsts::Unreachable);
}
}
void StackWriter::visitBinary(Binary *curr) {
if (debug) std::cerr << "zz node: Binary" << std::endl;
visit(curr->left);
visit(curr->right);
switch (curr->op) {
case AddInt32: o << int8_t(BinaryConsts::I32Add); break;
case SubInt32: o << int8_t(BinaryConsts::I32Sub); break;
case MulInt32: o << int8_t(BinaryConsts::I32Mul); break;
case DivSInt32: o << int8_t(BinaryConsts::I32DivS); break;
case DivUInt32: o << int8_t(BinaryConsts::I32DivU); break;
case RemSInt32: o << int8_t(BinaryConsts::I32RemS); break;
case RemUInt32: o << int8_t(BinaryConsts::I32RemU); break;
case AndInt32: o << int8_t(BinaryConsts::I32And); break;
case OrInt32: o << int8_t(BinaryConsts::I32Or); break;
case XorInt32: o << int8_t(BinaryConsts::I32Xor); break;
case ShlInt32: o << int8_t(BinaryConsts::I32Shl); break;
case ShrUInt32: o << int8_t(BinaryConsts::I32ShrU); break;
case ShrSInt32: o << int8_t(BinaryConsts::I32ShrS); break;
case RotLInt32: o << int8_t(BinaryConsts::I32RotL); break;
case RotRInt32: o << int8_t(BinaryConsts::I32RotR); break;
case EqInt32: o << int8_t(BinaryConsts::I32Eq); break;
case NeInt32: o << int8_t(BinaryConsts::I32Ne); break;
case LtSInt32: o << int8_t(BinaryConsts::I32LtS); break;
case LtUInt32: o << int8_t(BinaryConsts::I32LtU); break;
case LeSInt32: o << int8_t(BinaryConsts::I32LeS); break;
case LeUInt32: o << int8_t(BinaryConsts::I32LeU); break;
case GtSInt32: o << int8_t(BinaryConsts::I32GtS); break;
case GtUInt32: o << int8_t(BinaryConsts::I32GtU); break;
case GeSInt32: o << int8_t(BinaryConsts::I32GeS); break;
case GeUInt32: o << int8_t(BinaryConsts::I32GeU); break;
case AddInt64: o << int8_t(BinaryConsts::I64Add); break;
case SubInt64: o << int8_t(BinaryConsts::I64Sub); break;
case MulInt64: o << int8_t(BinaryConsts::I64Mul); break;
case DivSInt64: o << int8_t(BinaryConsts::I64DivS); break;
case DivUInt64: o << int8_t(BinaryConsts::I64DivU); break;
case RemSInt64: o << int8_t(BinaryConsts::I64RemS); break;
case RemUInt64: o << int8_t(BinaryConsts::I64RemU); break;
case AndInt64: o << int8_t(BinaryConsts::I64And); break;
case OrInt64: o << int8_t(BinaryConsts::I64Or); break;
case XorInt64: o << int8_t(BinaryConsts::I64Xor); break;
case ShlInt64: o << int8_t(BinaryConsts::I64Shl); break;
case ShrUInt64: o << int8_t(BinaryConsts::I64ShrU); break;
case ShrSInt64: o << int8_t(BinaryConsts::I64ShrS); break;
case RotLInt64: o << int8_t(BinaryConsts::I64RotL); break;
case RotRInt64: o << int8_t(BinaryConsts::I64RotR); break;
case EqInt64: o << int8_t(BinaryConsts::I64Eq); break;
case NeInt64: o << int8_t(BinaryConsts::I64Ne); break;
case LtSInt64: o << int8_t(BinaryConsts::I64LtS); break;
case LtUInt64: o << int8_t(BinaryConsts::I64LtU); break;
case LeSInt64: o << int8_t(BinaryConsts::I64LeS); break;
case LeUInt64: o << int8_t(BinaryConsts::I64LeU); break;
case GtSInt64: o << int8_t(BinaryConsts::I64GtS); break;
case GtUInt64: o << int8_t(BinaryConsts::I64GtU); break;
case GeSInt64: o << int8_t(BinaryConsts::I64GeS); break;
case GeUInt64: o << int8_t(BinaryConsts::I64GeU); break;
case AddFloat32: o << int8_t(BinaryConsts::F32Add); break;
case SubFloat32: o << int8_t(BinaryConsts::F32Sub); break;
case MulFloat32: o << int8_t(BinaryConsts::F32Mul); break;
case DivFloat32: o << int8_t(BinaryConsts::F32Div); break;
case CopySignFloat32: o << int8_t(BinaryConsts::F32CopySign);break;
case MinFloat32: o << int8_t(BinaryConsts::F32Min); break;
case MaxFloat32: o << int8_t(BinaryConsts::F32Max); break;
case EqFloat32: o << int8_t(BinaryConsts::F32Eq); break;
case NeFloat32: o << int8_t(BinaryConsts::F32Ne); break;
case LtFloat32: o << int8_t(BinaryConsts::F32Lt); break;
case LeFloat32: o << int8_t(BinaryConsts::F32Le); break;
case GtFloat32: o << int8_t(BinaryConsts::F32Gt); break;
case GeFloat32: o << int8_t(BinaryConsts::F32Ge); break;
case AddFloat64: o << int8_t(BinaryConsts::F64Add); break;
case SubFloat64: o << int8_t(BinaryConsts::F64Sub); break;
case MulFloat64: o << int8_t(BinaryConsts::F64Mul); break;
case DivFloat64: o << int8_t(BinaryConsts::F64Div); break;
case CopySignFloat64: o << int8_t(BinaryConsts::F64CopySign);break;
case MinFloat64: o << int8_t(BinaryConsts::F64Min); break;
case MaxFloat64: o << int8_t(BinaryConsts::F64Max); break;
case EqFloat64: o << int8_t(BinaryConsts::F64Eq); break;
case NeFloat64: o << int8_t(BinaryConsts::F64Ne); break;
case LtFloat64: o << int8_t(BinaryConsts::F64Lt); break;
case LeFloat64: o << int8_t(BinaryConsts::F64Le); break;
case GtFloat64: o << int8_t(BinaryConsts::F64Gt); break;
case GeFloat64: o << int8_t(BinaryConsts::F64Ge); break;
default: abort();
}
if (curr->type == unreachable) {
o << int8_t(BinaryConsts::Unreachable);
}
}
void StackWriter::visitSelect(Select *curr) {
if (debug) std::cerr << "zz node: Select" << std::endl;
visit(curr->ifTrue);
visit(curr->ifFalse);
visit(curr->condition);
o << int8_t(BinaryConsts::Select);
if (curr->type == unreachable) {
o << int8_t(BinaryConsts::Unreachable);
}
}
void StackWriter::visitReturn(Return *curr) {
if (debug) std::cerr << "zz node: Return" << std::endl;
if (curr->value) {
visit(curr->value);
}
o << int8_t(BinaryConsts::Return);
}
void StackWriter::visitHost(Host *curr) {
if (debug) std::cerr << "zz node: Host" << std::endl;
switch (curr->op) {
case CurrentMemory: {
o << int8_t(BinaryConsts::CurrentMemory);
break;
}
case GrowMemory: {
visit(curr->operands[0]);
o << int8_t(BinaryConsts::GrowMemory);
break;
}
default: abort();
}
o << U32LEB(0); // Reserved flags field
}
void StackWriter::visitNop(Nop *curr) {
if (debug) std::cerr << "zz node: Nop" << std::endl;
o << int8_t(BinaryConsts::Nop);
}
void StackWriter::visitUnreachable(Unreachable *curr) {
if (debug) std::cerr << "zz node: Unreachable" << std::endl;
o << int8_t(BinaryConsts::Unreachable);
}
void StackWriter::visitDrop(Drop *curr) {
if (debug) std::cerr << "zz node: Drop" << std::endl;
visit(curr->value);
o << int8_t(BinaryConsts::Drop);
}
int32_t StackWriter::getBreakIndex(Name name) { // -1 if not found
for (int i = breakStack.size() - 1; i >= 0; i--) {
if (breakStack[i] == name) {
return breakStack.size() - 1 - i;
}
}
std::cerr << "bad break: " << name << " in " << func->name << std::endl;
abort();
}
void StackWriter::emitMemoryAccess(size_t alignment, size_t bytes, uint32_t offset) {
o << U32LEB(Log2(alignment ? alignment : bytes));
o << U32LEB(offset);
}
// reader
void WasmBinaryBuilder::read() {
@ -1784,6 +1061,7 @@ void WasmBinaryBuilder::readFunctions() {
}
}
currFunction = nullptr;
useDebugLocation = false;
functions.push_back(func);
}
if (debug) std::cerr << " end function bodies" << std::endl;
@ -2385,7 +1663,7 @@ void WasmBinaryBuilder::pushBlockElements(Block* curr, size_t start, size_t end)
}
}
void WasmBinaryBuilder::visitBlock(Block *curr) {
void WasmBinaryBuilder::visitBlock(Block* curr) {
if (debug) std::cerr << "zz node: Block" << std::endl;
// special-case Block and de-recurse nested blocks in their first position, as that is
// a common pattern that can be very highly nested.
@ -2452,7 +1730,7 @@ Expression* WasmBinaryBuilder::getBlockOrSingleton(Type type) {
return block;
}
void WasmBinaryBuilder::visitIf(If *curr) {
void WasmBinaryBuilder::visitIf(If* curr) {
if (debug) std::cerr << "zz node: If" << std::endl;
curr->type = getType();
curr->condition = popNonVoidExpression();
@ -2466,7 +1744,7 @@ void WasmBinaryBuilder::visitIf(If *curr) {
}
}
void WasmBinaryBuilder::visitLoop(Loop *curr) {
void WasmBinaryBuilder::visitLoop(Loop* curr) {
if (debug) std::cerr << "zz node: Loop" << std::endl;
curr->type = getType();
curr->name = getNextLabel();
@ -2523,7 +1801,7 @@ void WasmBinaryBuilder::visitBreak(Break *curr, uint8_t code) {
curr->finalize();
}
void WasmBinaryBuilder::visitSwitch(Switch *curr) {
void WasmBinaryBuilder::visitSwitch(Switch* curr) {
if (debug) std::cerr << "zz node: Switch" << std::endl;
curr->condition = popNonVoidExpression();
auto numTargets = getU32LEB();
@ -2569,7 +1847,7 @@ Expression* WasmBinaryBuilder::visitCall() {
return ret;
}
void WasmBinaryBuilder::visitCallIndirect(CallIndirect *curr) {
void WasmBinaryBuilder::visitCallIndirect(CallIndirect* curr) {
if (debug) std::cerr << "zz node: CallIndirect" << std::endl;
auto index = getU32LEB();
if (index >= wasm.functionTypes.size()) {
@ -2589,7 +1867,7 @@ void WasmBinaryBuilder::visitCallIndirect(CallIndirect *curr) {
curr->finalize();
}
void WasmBinaryBuilder::visitGetLocal(GetLocal *curr) {
void WasmBinaryBuilder::visitGetLocal(GetLocal* curr) {
if (debug) std::cerr << "zz node: GetLocal " << pos << std::endl;
requireFunctionContext("get_local");
curr->index = getU32LEB();
@ -2613,7 +1891,7 @@ void WasmBinaryBuilder::visitSetLocal(SetLocal *curr, uint8_t code) {
curr->finalize();
}
void WasmBinaryBuilder::visitGetGlobal(GetGlobal *curr) {
void WasmBinaryBuilder::visitGetGlobal(GetGlobal* curr) {
if (debug) std::cerr << "zz node: GetGlobal " << pos << std::endl;
auto index = getU32LEB();
curr->name = getGlobalName(index);
@ -2630,7 +1908,7 @@ void WasmBinaryBuilder::visitGetGlobal(GetGlobal *curr) {
throwError("bad get_global");
}
void WasmBinaryBuilder::visitSetGlobal(SetGlobal *curr) {
void WasmBinaryBuilder::visitSetGlobal(SetGlobal* curr) {
if (debug) std::cerr << "zz node: SetGlobal" << std::endl;
auto index = getU32LEB();
curr->name = getGlobalName(index);
@ -2989,7 +2267,7 @@ bool WasmBinaryBuilder::maybeVisitBinary(Expression*& out, uint8_t code) {
#undef FLOAT_TYPED_CODE
}
void WasmBinaryBuilder::visitSelect(Select *curr) {
void WasmBinaryBuilder::visitSelect(Select* curr) {
if (debug) std::cerr << "zz node: Select" << std::endl;
curr->condition = popNonVoidExpression();
curr->ifFalse = popNonVoidExpression();
@ -2997,7 +2275,7 @@ void WasmBinaryBuilder::visitSelect(Select *curr) {
curr->finalize();
}
void WasmBinaryBuilder::visitReturn(Return *curr) {
void WasmBinaryBuilder::visitReturn(Return* curr) {
if (debug) std::cerr << "zz node: Return" << std::endl;
requireFunctionContext("return");
if (currFunction->result != none) {
@ -3032,15 +2310,15 @@ bool WasmBinaryBuilder::maybeVisitHost(Expression*& out, uint8_t code) {
return true;
}
void WasmBinaryBuilder::visitNop(Nop *curr) {
void WasmBinaryBuilder::visitNop(Nop* curr) {
if (debug) std::cerr << "zz node: Nop" << std::endl;
}
void WasmBinaryBuilder::visitUnreachable(Unreachable *curr) {
void WasmBinaryBuilder::visitUnreachable(Unreachable* curr) {
if (debug) std::cerr << "zz node: Unreachable" << std::endl;
}
void WasmBinaryBuilder::visitDrop(Drop *curr) {
void WasmBinaryBuilder::visitDrop(Drop* curr) {
if (debug) std::cerr << "zz node: Drop" << std::endl;
curr->value = popNonVoidExpression();
curr->finalize();

View File

@ -171,6 +171,8 @@ struct FunctionValidator : public WalkerPass<PostWalker<FunctionValidator>> {
Pass* create() override { return new FunctionValidator(&info); }
bool modifiesBinaryenIR() override { return false; }
ValidationInfo& info;
FunctionValidator(ValidationInfo* info) : info(*info) {}

View File

@ -3,7 +3,7 @@
(import "env" "memoryBase" (global $memoryBase i32))
(data (get_global $memoryBase) "bad_params.asm.js")
(export "ex" (func $ex))
(func $ex (; 0 ;)
(func $ex (; 0 ;) (; has Stack IR ;)
(nop)
)
)

View File

@ -3,7 +3,7 @@
(import "env" "memoryBase" (global $memoryBase i32))
(data (get_global $memoryBase) "bad_params.asm.js")
(export "ex" (func $ex))
(func $ex (; 0 ;)
(func $ex (; 0 ;) (; has Stack IR ;)
(nop)
)
)

View File

@ -1,6 +1,6 @@
(module
(export "ex" (func $ex))
(func $ex (; 0 ;)
(func $ex (; 0 ;) (; has Stack IR ;)
(nop)
)
)

View File

@ -16,7 +16,7 @@ optimized:
(module
(type $iii (func (param i32 i32) (result i32)))
(export "adder" (func $adder))
(func $adder (; 0 ;) (type $iii) (param $0 i32) (param $1 i32) (result i32)
(func $adder (; 0 ;) (; has Stack IR ;) (type $iii) (param $0 i32) (param $1 i32) (result i32)
(i32.add
(get_local $0)
(get_local $1)

View File

@ -36,7 +36,7 @@ shrinkLevel=1
(module
(type $i (func (param i32) (result i32)))
(export "test" (func $test))
(func $test (; 0 ;) (type $i) (param $0 i32) (result i32)
(func $test (; 0 ;) (; has Stack IR ;) (type $i) (param $0 i32) (result i32)
(select
(get_local $0)
(i32.const 0)
@ -66,7 +66,7 @@ shrinkLevel=1
(module
(type $i (func (param i32) (result i32)))
(export "test" (func $test))
(func $test (; 0 ;) (type $i) (param $0 i32) (result i32)
(func $test (; 0 ;) (; has Stack IR ;) (type $i) (param $0 i32) (result i32)
(select
(get_local $0)
(i32.const 0)

View File

@ -19,16 +19,18 @@ var body = module.block(
),
module.get_local(0, Binaryen.i32)
),
module.grow_memory(
module.i32.sub(
module.i32.div_u(
module.i32.add(
module.get_local(0, Binaryen.i32),
module.i32.const(65535)
module.drop(
module.grow_memory(
module.i32.sub(
module.i32.div_u(
module.i32.add(
module.get_local(0, Binaryen.i32),
module.i32.const(65535)
),
module.i32.const(65536)
),
module.i32.const(65536)
),
module.current_memory()
module.current_memory()
)
)
)
),
@ -44,8 +46,8 @@ var body = module.block(
module.i32.const(1)
)),
module.br_if('clear', module.i32.eq(
module.get_local(1),
module.get_local(0)
module.get_local(1, Binaryen.i32),
module.get_local(0, Binaryen.i32)
))
])),
// perform the sieve TODO
@ -63,6 +65,8 @@ module.addFunction('sieve', ii, [Binaryen.i32], body);
// export it as the same name as it has internally)
module.addFunctionExport('sieve', 'sieve');
if (!module.validate()) throw 'did not validate :(';
// Print out the text
console.log(module.emitText());

View File

@ -12,16 +12,18 @@
)
(get_local $0)
)
(grow_memory
(i32.sub
(i32.div_u
(i32.add
(get_local $0)
(i32.const 65535)
(drop
(grow_memory
(i32.sub
(i32.div_u
(i32.add
(get_local $0)
(i32.const 65535)
)
(i32.const 65536)
)
(i32.const 65536)
(current_memory)
)
(current_memory)
)
)
)
@ -58,7 +60,7 @@ optimized:
(type $i (func (param i32) (result i32)))
(memory $0 1 100)
(export "sieve" (func $sieve))
(func $sieve (; 0 ;) (type $i) (param $0 i32) (result i32)
(func $sieve (; 0 ;) (; has Stack IR ;) (type $i) (param $0 i32) (result i32)
(local $1 i32)
(if
(i32.lt_u
@ -68,16 +70,18 @@ optimized:
)
(get_local $0)
)
(grow_memory
(i32.sub
(i32.div_u
(i32.add
(get_local $0)
(i32.const 65535)
(drop
(grow_memory
(i32.sub
(i32.div_u
(i32.add
(get_local $0)
(i32.const 65535)
)
(i32.const 65536)
)
(i32.const 65536)
(current_memory)
)
(current_memory)
)
)
)

View File

@ -5,4 +5,4 @@ module.c
020: u r c e M a p p i n g U R L 0f m
030: o d u l e . w a s m . m a p
{"version":3,"sources":["module.c"],"names":[],"mappings":"gCAAE"}
{"version":3,"sources":["module.c"],"names":[],"mappings":"wBAAE"}

View File

@ -8,14 +8,14 @@
(export "fib" (func $fib))
(export "switch_reach" (func $switch_reach))
(export "nofile" (func $nofile))
(func $add (; 0 ;) (param $0 i32) (param $1 i32) (result i32)
(func $add (; 0 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
;;@ tests/other_file.cpp:314159:0
(i32.add
(get_local $1)
(get_local $1)
)
)
(func $ret (; 1 ;) (param $0 i32) (result i32)
(func $ret (; 1 ;) (; has Stack IR ;) (param $0 i32) (result i32)
;;@ return.cpp:50:0
(set_local $0
(i32.shl
@ -29,7 +29,7 @@
(i32.const 1)
)
)
(func $i32s-rem (; 2 ;) (param $0 i32) (param $1 i32) (result i32)
(func $i32s-rem (; 2 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
(if (result i32)
(get_local $1)
(i32.rem_s
@ -39,7 +39,7 @@
(i32.const 0)
)
)
(func $opts (; 3 ;) (param $0 i32) (param $1 i32) (result i32)
(func $opts (; 3 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
;;@ even-opted.cpp:1:0
(set_local $0
(i32.add
@ -63,7 +63,7 @@
(get_local $1)
)
)
(func $fib (; 4 ;) (param $0 i32) (result i32)
(func $fib (; 4 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -126,7 +126,7 @@
;;@ fib.c:8:0
(get_local $1)
)
(func $switch_reach (; 5 ;) (param $0 i32) (result i32)
(func $switch_reach (; 5 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(set_local $1
(block $__rjto$0 (result i32)
@ -180,7 +180,7 @@
;;@ /tmp/emscripten_test_binaryen2_28hnAe/src.c:59950:0
(get_local $1)
)
(func $nofile (; 6 ;)
(func $nofile (; 6 ;) (; has Stack IR ;)
;;@ (unknown):1337:0
(call $nofile)
)

View File

@ -8,14 +8,14 @@
(export "fib" (func $fib))
(export "switch_reach" (func $switch_reach))
(export "nofile" (func $nofile))
(func $add (; 0 ;) (param $0 i32) (param $1 i32) (result i32)
(func $add (; 0 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
;;@ tests/other_file.cpp:314159:0
(i32.add
(get_local $1)
(get_local $1)
)
)
(func $ret (; 1 ;) (param $0 i32) (result i32)
(func $ret (; 1 ;) (; has Stack IR ;) (param $0 i32) (result i32)
;;@ return.cpp:50:0
(set_local $0
(i32.shl
@ -29,7 +29,7 @@
(i32.const 1)
)
)
(func $i32s-rem (; 2 ;) (param $0 i32) (param $1 i32) (result i32)
(func $i32s-rem (; 2 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
(if (result i32)
(get_local $1)
(i32.rem_s
@ -39,7 +39,7 @@
(i32.const 0)
)
)
(func $opts (; 3 ;) (param $0 i32) (param $1 i32) (result i32)
(func $opts (; 3 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
;;@ even-opted.cpp:1:0
(set_local $0
(i32.add
@ -63,7 +63,7 @@
(get_local $1)
)
)
(func $fib (; 4 ;) (param $0 i32) (result i32)
(func $fib (; 4 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -126,7 +126,7 @@
;;@ fib.c:8:0
(get_local $1)
)
(func $switch_reach (; 5 ;) (param $0 i32) (result i32)
(func $switch_reach (; 5 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(set_local $1
(block $__rjto$0 (result i32)
@ -180,7 +180,7 @@
;;@ /tmp/emscripten_test_binaryen2_28hnAe/src.c:59950:0
(get_local $1)
)
(func $nofile (; 6 ;)
(func $nofile (; 6 ;) (; has Stack IR ;)
;;@ (unknown):1337:0
(call $nofile)
)

View File

@ -1 +1 @@
{"version":3,"sources":["tests/hello_world.c","tests/other_file.cpp","return.cpp","even-opted.cpp","fib.c","/tmp/emscripten_test_binaryen2_28hnAe/src.c","(unknown)"],"names":[],"mappings":"0IC8ylTA,QC7vlTA,OAkDA,wBCnGA,OACA,OACA,cCAA,kBAKA,QAJA,OADA,0BAKA,wECsi1DA,KCrvyDA"}
{"version":3,"sources":["tests/hello_world.c","tests/other_file.cpp","return.cpp","even-opted.cpp","fib.c","/tmp/emscripten_test_binaryen2_28hnAe/src.c","(unknown)"],"names":[],"mappings":"mIC8ylTA,QC7vlTA,OAkDA,wBCnGA,OACA,OACA,cCAA,kBAKA,QAJA,OADA,0BAKA,wECsi1DA,KCrvyDA"}

View File

@ -1 +1 @@
{"version":3,"sources":["tests/hello_world.c","tests/other_file.cpp","return.cpp","even-opted.cpp","fib.c","/tmp/emscripten_test_binaryen2_28hnAe/src.c","(unknown)"],"names":[],"mappings":"0LAIA,IACA,ICyylTA,aC7vlTA,OAkDA,0BCnGA,OACA,OACA,uBCAA,4BAKA,QAJA,OADA,8CAKA,yICsi1DA,OCrvyDA"}
{"version":3,"sources":["tests/hello_world.c","tests/other_file.cpp","return.cpp","even-opted.cpp","fib.c","/tmp/emscripten_test_binaryen2_28hnAe/src.c","(unknown)"],"names":[],"mappings":"mLAIA,IACA,ICyylTA,aC7vlTA,OAkDA,0BCnGA,OACA,OACA,uBCAA,4BAKA,QAJA,OADA,8CAKA,0ICsi1DA,MCrvyDA"}

View File

@ -5,14 +5,14 @@
(export "fib" (func $fib))
(export "switch_reach" (func $switch_reach))
(export "nofile" (func $nofile))
(func $add (; 0 ;) (param $0 i32) (param $1 i32) (result i32)
(func $add (; 0 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
;;@ tests/other_file.cpp:314159:0
(i32.add
(get_local $1)
(get_local $1)
)
)
(func $ret (; 1 ;) (param $0 i32) (result i32)
(func $ret (; 1 ;) (; has Stack IR ;) (param $0 i32) (result i32)
;;@ return.cpp:50:0
(set_local $0
(i32.shl
@ -26,7 +26,7 @@
(i32.const 1)
)
)
(func $opts (; 2 ;) (param $0 i32) (param $1 i32) (result i32)
(func $opts (; 2 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
;;@ even-opted.cpp:1:0
(set_local $0
(i32.add
@ -50,7 +50,7 @@
(get_local $1)
)
)
(func $fib (; 3 ;) (param $0 i32) (result i32)
(func $fib (; 3 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -113,7 +113,7 @@
;;@ fib.c:8:0
(get_local $1)
)
(func $switch_reach (; 4 ;) (param $0 i32) (result i32)
(func $switch_reach (; 4 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(set_local $1
(block $__rjto$0 (result i32)
@ -167,7 +167,7 @@
;;@ /tmp/emscripten_test_binaryen2_28hnAe/src.c:59950:0
(get_local $1)
)
(func $nofile (; 5 ;)
(func $nofile (; 5 ;) (; has Stack IR ;)
;;@ (unknown):1337:0
(call $nofile)
)

View File

@ -1 +1 @@
{"version":3,"sources":["tests/hello_world.c","tests/other_file.cpp","return.cpp","even-opted.cpp","fib.c","/tmp/emscripten_test_binaryen2_28hnAe/src.c","(unknown)"],"names":[],"mappings":"mGC8ylTA,QC7vlTA,OAkDA,QCnGA,OACA,OACA,aCAA,kBAKA,QAJA,OADA,0BAKA,wECsi1DA,KCrvyDA"}
{"version":3,"sources":["tests/hello_world.c","tests/other_file.cpp","return.cpp","even-opted.cpp","fib.c","/tmp/emscripten_test_binaryen2_28hnAe/src.c","(unknown)"],"names":[],"mappings":"4FC8ylTA,QC7vlTA,OAkDA,QCnGA,OACA,OACA,aCAA,kBAKA,QAJA,OADA,0BAKA,wECsi1DA,KCrvyDA"}

View File

@ -1 +1 @@
{"version":3,"sources":["tests/hello_world.c","tests/other_file.cpp","return.cpp","even-opted.cpp","fib.c","/tmp/emscripten_test_binaryen2_28hnAe/src.c","(unknown)"],"names":[],"mappings":"yLAIA,IACA,ICyylTA,aC7vlTA,OAkDA,SCnGA,OACA,OACA,sBCAA,4BAKA,QAJA,OADA,8CAKA,yICsi1DA,OCrvyDA"}
{"version":3,"sources":["tests/hello_world.c","tests/other_file.cpp","return.cpp","even-opted.cpp","fib.c","/tmp/emscripten_test_binaryen2_28hnAe/src.c","(unknown)"],"names":[],"mappings":"kLAIA,IACA,ICyylTA,aC7vlTA,OAkDA,SCnGA,OACA,OACA,sBCAA,4BAKA,QAJA,OADA,8CAKA,0ICsi1DA,MCrvyDA"}

View File

@ -1 +1 @@
{"version":3,"sources":["tests/hello_world.c","tests/other_file.cpp","return.cpp","even-opted.cpp","fib.c","/tmp/emscripten_test_binaryen2_28hnAe/src.c","(unknown)"],"names":[],"mappings":"0IC8ylTA,QC7vlTA,OAkDA,wBCnGA,OACA,OACA,cCAA,kBAKA,QAJA,OADA,0BAKA,wECsi1DA,KCrvyDA"}
{"version":3,"sources":["tests/hello_world.c","tests/other_file.cpp","return.cpp","even-opted.cpp","fib.c","/tmp/emscripten_test_binaryen2_28hnAe/src.c","(unknown)"],"names":[],"mappings":"mIC8ylTA,QC7vlTA,OAkDA,wBCnGA,OACA,OACA,cCAA,kBAKA,QAJA,OADA,0BAKA,wECsi1DA,KCrvyDA"}

View File

@ -1 +1 @@
{"version":3,"sources":["tests/hello_world.c","tests/other_file.cpp","return.cpp","even-opted.cpp","fib.c","/tmp/emscripten_test_binaryen2_28hnAe/src.c","(unknown)"],"names":[],"mappings":"0LAIA,IACA,ICyylTA,aC7vlTA,OAkDA,0BCnGA,OACA,OACA,uBCAA,4BAKA,QAJA,OADA,8CAKA,yICsi1DA,OCrvyDA"}
{"version":3,"sources":["tests/hello_world.c","tests/other_file.cpp","return.cpp","even-opted.cpp","fib.c","/tmp/emscripten_test_binaryen2_28hnAe/src.c","(unknown)"],"names":[],"mappings":"mLAIA,IACA,ICyylTA,aC7vlTA,OAkDA,0BCnGA,OACA,OACA,uBCAA,4BAKA,QAJA,OADA,8CAKA,0ICsi1DA,MCrvyDA"}

View File

@ -12,55 +12,53 @@
(export "switch_reach" (func $switch_reach))
(export "nofile" (func $nofile))
(func $add (; 0 ;) (type $0) (param $var$0 i32) (param $var$1 i32) (result i32)
;;@ tests/other_file.cpp:314159:0
(i32.add
(get_local $var$1)
(get_local $var$1)
)
)
(func $ret (; 1 ;) (type $1) (param $var$0 i32) (result i32)
;;@ return.cpp:50:0
(set_local $var$0
(i32.shl
(get_local $var$0)
(i32.const 1)
)
)
;;@ tests/other_file.cpp:314159:0
;;@ return.cpp:100:0
(i32.add
(get_local $var$0)
(i32.const 1)
)
)
(func $i32s-rem (; 2 ;) (type $0) (param $var$0 i32) (param $var$1 i32) (result i32)
;;@ return.cpp:100:0
(if (result i32)
;;@ return.cpp:50:0
(get_local $var$1)
;;@ return.cpp:100:0
(i32.rem_s
;;@ return.cpp:50:0
(get_local $var$0)
(get_local $var$1)
)
;;@ return.cpp:100:0
(i32.const 0)
)
)
(func $opts (; 3 ;) (type $0) (param $var$0 i32) (param $var$1 i32) (result i32)
;;@ even-opted.cpp:1:0
(set_local $var$0
(i32.add
(get_local $var$0)
(get_local $var$1)
)
)
;;@ even-opted.cpp:2:0
(set_local $var$1
(i32.shr_s
(get_local $var$1)
(get_local $var$0)
)
)
;;@ even-opted.cpp:2:0
;;@ even-opted.cpp:3:0
(i32.add
;;@ even-opted.cpp:1:0
(call $i32s-rem
(get_local $var$0)
(get_local $var$1)
@ -73,9 +71,10 @@
(local $var$2 i32)
(local $var$3 i32)
(local $var$4 i32)
;;@ fib.c:3:0
;;@ fib.c:8:0
(set_local $var$4
(if (result i32)
;;@ fib.c:3:0
(i32.gt_s
(get_local $var$0)
(i32.const 0)
@ -90,35 +89,35 @@
(set_local $var$1
(i32.const 1)
)
;;@ fib.c:8:0
(return
(get_local $var$1)
)
)
)
)
;;@ fib.c:3:0
(loop $label$3
;;@ fib.c:4:0
(set_local $var$1
(i32.add
(get_local $var$3)
(get_local $var$4)
)
)
;;@ fib.c:8:0
;;@ fib.c:3:0
(set_local $var$2
(i32.add
(get_local $var$2)
(i32.const 1)
)
)
;;@ fib.c:3:0
(if
;;@ fib.c:4:0
(i32.ne
(get_local $var$2)
(get_local $var$0)
)
(block
;;@ fib.c:3:0
(set_local $var$4
(get_local $var$3)
)
@ -129,11 +128,11 @@
)
)
)
;;@ fib.c:8:0
(get_local $var$1)
)
(func $switch_reach (; 5 ;) (type $1) (param $var$0 i32) (result i32)
(local $var$1 i32)
;;@ fib.c:8:0
(set_local $var$1
(block $label$1 (result i32)
(block $label$2
@ -183,9 +182,11 @@
(get_local $var$0)
)
)
;;@ /tmp/emscripten_test_binaryen2_28hnAe/src.c:59950:0
(get_local $var$1)
)
(func $nofile (; 6 ;) (type $2)
;;@ (unknown):1337:0
(call $nofile)
)
)

View File

@ -13,7 +13,7 @@
(export "__post_instantiate" (func $__post_instantiate))
(export "runPostSets" (func $runPostSets))
(export "_global" (global $_global))
(func $__ZN3FooC2Ev (; 2 ;) (param $0 i32)
(func $__ZN3FooC2Ev (; 2 ;) (; has Stack IR ;) (param $0 i32)
(local $1 i32)
(set_local $1
(get_global $STACKTOP)
@ -42,10 +42,10 @@
(get_local $1)
)
)
(func $runPostSets (; 3 ;)
(func $runPostSets (; 3 ;) (; has Stack IR ;)
(nop)
)
(func $__post_instantiate (; 4 ;)
(func $__post_instantiate (; 4 ;) (; has Stack IR ;)
(set_global $STACKTOP
(i32.add
(get_global $memoryBase)

View File

@ -13,7 +13,7 @@
(export "__post_instantiate" (func $__post_instantiate))
(export "runPostSets" (func $runPostSets))
(export "_global" (global $_global))
(func $__ZN3FooC2Ev (; 2 ;) (param $0 i32)
(func $__ZN3FooC2Ev (; 2 ;) (; has Stack IR ;) (param $0 i32)
(local $1 i32)
(set_local $1
(get_global $STACKTOP)
@ -42,10 +42,10 @@
(get_local $1)
)
)
(func $runPostSets (; 3 ;)
(func $runPostSets (; 3 ;) (; has Stack IR ;)
(nop)
)
(func $__post_instantiate (; 4 ;)
(func $__post_instantiate (; 4 ;) (; has Stack IR ;)
(set_global $STACKTOP
(i32.add
(get_global $memoryBase)

View File

@ -11,7 +11,7 @@
(export "__post_instantiate" (func $__post_instantiate))
(export "runPostSets" (func $runPostSets))
(export "_global" (global $_global))
(func $__ZN3FooC2Ev (; 2 ;) (param $0 i32)
(func $__ZN3FooC2Ev (; 2 ;) (; has Stack IR ;) (param $0 i32)
(local $1 i32)
(set_local $1
(get_global $STACKTOP)
@ -40,10 +40,10 @@
(get_local $1)
)
)
(func $runPostSets (; 3 ;)
(func $runPostSets (; 3 ;) (; has Stack IR ;)
(nop)
)
(func $__post_instantiate (; 4 ;)
(func $__post_instantiate (; 4 ;) (; has Stack IR ;)
(set_global $STACKTOP
(i32.add
(get_global $memoryBase)

View File

@ -51,7 +51,7 @@
(export "dynCall_ii" (func $dynCall_ii))
(export "dynCall_iiii" (func $dynCall_iiii))
(export "dynCall_vi" (func $dynCall_vi))
(func $_malloc (; 15 ;) (param $0 i32) (result i32)
(func $_malloc (; 15 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -5830,7 +5830,7 @@
)
(i32.const 0)
)
(func $_free (; 16 ;) (param $0 i32)
(func $_free (; 16 ;) (; has Stack IR ;) (param $0 i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -7651,7 +7651,7 @@
(i32.const -1)
)
)
(func $___stdio_write (; 17 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $___stdio_write (; 17 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(local $5 i32)
@ -8025,7 +8025,7 @@
)
(get_local $15)
)
(func $___fwritex (; 18 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $___fwritex (; 18 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(local $5 i32)
@ -8237,7 +8237,7 @@
)
(get_local $4)
)
(func $_fflush (; 19 ;) (param $0 i32) (result i32)
(func $_fflush (; 19 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(block $do-once
@ -8344,7 +8344,7 @@
)
(get_local $1)
)
(func $_strlen (; 20 ;) (param $0 i32) (result i32)
(func $_strlen (; 20 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -8488,7 +8488,7 @@
(get_local $3)
)
)
(func $___overflow (; 21 ;) (param $0 i32) (param $1 i32) (result i32)
(func $___overflow (; 21 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
(local $2 i32)
(local $3 i32)
(local $4 i32)
@ -8642,7 +8642,7 @@
)
(get_local $4)
)
(func $___fflush_unlocked (; 22 ;) (param $0 i32) (result i32)
(func $___fflush_unlocked (; 22 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -8765,7 +8765,7 @@
)
)
)
(func $_memcpy (; 23 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $_memcpy (; 23 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(if
(i32.ge_s
@ -8912,10 +8912,10 @@
)
(get_local $3)
)
(func $runPostSets (; 24 ;)
(func $runPostSets (; 24 ;) (; has Stack IR ;)
(nop)
)
(func $_memset (; 25 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $_memset (; 25 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(local $5 i32)
@ -9053,7 +9053,7 @@
(get_local $2)
)
)
(func $_puts (; 26 ;) (param $0 i32) (result i32)
(func $_puts (; 26 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -9145,7 +9145,7 @@
(i32.const 31)
)
)
(func $___stdio_seek (; 27 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $___stdio_seek (; 27 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(set_local $4
@ -9214,7 +9214,7 @@
)
(get_local $0)
)
(func $___towrite (; 28 ;) (param $0 i32) (result i32)
(func $___towrite (; 28 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(set_local $2
@ -9292,7 +9292,7 @@
)
)
)
(func $_fwrite (; 29 ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(func $_fwrite (; 29 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(local $4 i32)
(set_local $4
(i32.mul
@ -9331,7 +9331,7 @@
)
(get_local $2)
)
(func $___stdout_write (; 30 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $___stdout_write (; 30 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(set_local $4
@ -9400,7 +9400,7 @@
)
(get_local $3)
)
(func $___stdio_close (; 31 ;) (param $0 i32) (result i32)
(func $___stdio_close (; 31 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(set_local $1
(get_global $STACKTOP)
@ -9430,7 +9430,7 @@
)
(get_local $0)
)
(func $___syscall_ret (; 32 ;) (param $0 i32) (result i32)
(func $___syscall_ret (; 32 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(if (result i32)
(i32.gt_u
(get_local $0)
@ -9449,7 +9449,7 @@
(get_local $0)
)
)
(func $dynCall_iiii (; 33 ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(func $dynCall_iiii (; 33 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(call_indirect (type $FUNCSIG$iiii)
(get_local $1)
(get_local $2)
@ -9463,7 +9463,7 @@
)
)
)
(func $stackAlloc (; 34 ;) (param $0 i32) (result i32)
(func $stackAlloc (; 34 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(set_local $1
(get_global $STACKTOP)
@ -9485,7 +9485,7 @@
)
(get_local $1)
)
(func $___errno_location (; 35 ;) (result i32)
(func $___errno_location (; 35 ;) (; has Stack IR ;) (result i32)
(if (result i32)
(i32.load
(i32.const 8)
@ -9496,7 +9496,7 @@
(i32.const 60)
)
)
(func $setThrew (; 36 ;) (param $0 i32) (param $1 i32)
(func $setThrew (; 36 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32)
(if
(i32.eqz
(get_global $__THREW__)
@ -9511,7 +9511,7 @@
)
)
)
(func $dynCall_ii (; 37 ;) (param $0 i32) (param $1 i32) (result i32)
(func $dynCall_ii (; 37 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
(call_indirect (type $FUNCSIG$ii)
(get_local $1)
(i32.and
@ -9520,14 +9520,14 @@
)
)
)
(func $_cleanup_418 (; 38 ;) (param $0 i32)
(func $_cleanup_418 (; 38 ;) (; has Stack IR ;) (param $0 i32)
(drop
(i32.load offset=68
(get_local $0)
)
)
)
(func $establishStackSpace (; 39 ;) (param $0 i32) (param $1 i32)
(func $establishStackSpace (; 39 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32)
(set_global $STACKTOP
(get_local $0)
)
@ -9535,7 +9535,7 @@
(get_local $1)
)
)
(func $dynCall_vi (; 40 ;) (param $0 i32) (param $1 i32)
(func $dynCall_vi (; 40 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32)
(call_indirect (type $FUNCSIG$vi)
(get_local $1)
(i32.add
@ -9547,32 +9547,32 @@
)
)
)
(func $b1 (; 41 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $b1 (; 41 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(call $abort
(i32.const 1)
)
(i32.const 0)
)
(func $stackRestore (; 42 ;) (param $0 i32)
(func $stackRestore (; 42 ;) (; has Stack IR ;) (param $0 i32)
(set_global $STACKTOP
(get_local $0)
)
)
(func $setTempRet0 (; 43 ;) (param $0 i32)
(func $setTempRet0 (; 43 ;) (; has Stack IR ;) (param $0 i32)
(set_global $tempRet0
(get_local $0)
)
)
(func $b0 (; 44 ;) (param $0 i32) (result i32)
(func $b0 (; 44 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(call $abort
(i32.const 0)
)
(i32.const 0)
)
(func $getTempRet0 (; 45 ;) (result i32)
(func $getTempRet0 (; 45 ;) (; has Stack IR ;) (result i32)
(get_global $tempRet0)
)
(func $_main (; 46 ;) (result i32)
(func $_main (; 46 ;) (; has Stack IR ;) (result i32)
(drop
(call $_puts
(i32.const 672)
@ -9580,10 +9580,10 @@
)
(i32.const 0)
)
(func $stackSave (; 47 ;) (result i32)
(func $stackSave (; 47 ;) (; has Stack IR ;) (result i32)
(get_global $STACKTOP)
)
(func $b2 (; 48 ;) (param $0 i32)
(func $b2 (; 48 ;) (; has Stack IR ;) (param $0 i32)
(call $abort
(i32.const 2)
)

View File

@ -51,7 +51,7 @@
(export "dynCall_ii" (func $dynCall_ii))
(export "dynCall_iiii" (func $dynCall_iiii))
(export "dynCall_vi" (func $dynCall_vi))
(func $_malloc (; 15 ;) (param $0 i32) (result i32)
(func $_malloc (; 15 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -5830,7 +5830,7 @@
)
(i32.const 0)
)
(func $_free (; 16 ;) (param $0 i32)
(func $_free (; 16 ;) (; has Stack IR ;) (param $0 i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -7651,7 +7651,7 @@
(i32.const -1)
)
)
(func $___stdio_write (; 17 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $___stdio_write (; 17 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(local $5 i32)
@ -8025,7 +8025,7 @@
)
(get_local $15)
)
(func $___fwritex (; 18 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $___fwritex (; 18 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(local $5 i32)
@ -8237,7 +8237,7 @@
)
(get_local $4)
)
(func $_fflush (; 19 ;) (param $0 i32) (result i32)
(func $_fflush (; 19 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(block $do-once
@ -8344,7 +8344,7 @@
)
(get_local $1)
)
(func $_strlen (; 20 ;) (param $0 i32) (result i32)
(func $_strlen (; 20 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -8488,7 +8488,7 @@
(get_local $3)
)
)
(func $___overflow (; 21 ;) (param $0 i32) (param $1 i32) (result i32)
(func $___overflow (; 21 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
(local $2 i32)
(local $3 i32)
(local $4 i32)
@ -8642,7 +8642,7 @@
)
(get_local $4)
)
(func $___fflush_unlocked (; 22 ;) (param $0 i32) (result i32)
(func $___fflush_unlocked (; 22 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -8765,7 +8765,7 @@
)
)
)
(func $_memcpy (; 23 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $_memcpy (; 23 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(if
(i32.ge_s
@ -8912,10 +8912,10 @@
)
(get_local $3)
)
(func $runPostSets (; 24 ;)
(func $runPostSets (; 24 ;) (; has Stack IR ;)
(nop)
)
(func $_memset (; 25 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $_memset (; 25 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(local $5 i32)
@ -9053,7 +9053,7 @@
(get_local $2)
)
)
(func $_puts (; 26 ;) (param $0 i32) (result i32)
(func $_puts (; 26 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -9145,7 +9145,7 @@
(i32.const 31)
)
)
(func $___stdio_seek (; 27 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $___stdio_seek (; 27 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(set_local $4
@ -9214,7 +9214,7 @@
)
(get_local $0)
)
(func $___towrite (; 28 ;) (param $0 i32) (result i32)
(func $___towrite (; 28 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(set_local $2
@ -9292,7 +9292,7 @@
)
)
)
(func $_fwrite (; 29 ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(func $_fwrite (; 29 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(local $4 i32)
(set_local $4
(i32.mul
@ -9331,7 +9331,7 @@
)
(get_local $2)
)
(func $___stdout_write (; 30 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $___stdout_write (; 30 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(set_local $4
@ -9400,7 +9400,7 @@
)
(get_local $3)
)
(func $___stdio_close (; 31 ;) (param $0 i32) (result i32)
(func $___stdio_close (; 31 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(set_local $1
(get_global $STACKTOP)
@ -9430,7 +9430,7 @@
)
(get_local $0)
)
(func $___syscall_ret (; 32 ;) (param $0 i32) (result i32)
(func $___syscall_ret (; 32 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(if (result i32)
(i32.gt_u
(get_local $0)
@ -9449,7 +9449,7 @@
(get_local $0)
)
)
(func $dynCall_iiii (; 33 ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(func $dynCall_iiii (; 33 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(call_indirect (type $FUNCSIG$iiii)
(get_local $1)
(get_local $2)
@ -9463,7 +9463,7 @@
)
)
)
(func $stackAlloc (; 34 ;) (param $0 i32) (result i32)
(func $stackAlloc (; 34 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(set_local $1
(get_global $STACKTOP)
@ -9485,7 +9485,7 @@
)
(get_local $1)
)
(func $___errno_location (; 35 ;) (result i32)
(func $___errno_location (; 35 ;) (; has Stack IR ;) (result i32)
(if (result i32)
(i32.load
(i32.const 8)
@ -9496,7 +9496,7 @@
(i32.const 60)
)
)
(func $setThrew (; 36 ;) (param $0 i32) (param $1 i32)
(func $setThrew (; 36 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32)
(if
(i32.eqz
(get_global $__THREW__)
@ -9511,7 +9511,7 @@
)
)
)
(func $dynCall_ii (; 37 ;) (param $0 i32) (param $1 i32) (result i32)
(func $dynCall_ii (; 37 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
(call_indirect (type $FUNCSIG$ii)
(get_local $1)
(i32.and
@ -9520,14 +9520,14 @@
)
)
)
(func $_cleanup_418 (; 38 ;) (param $0 i32)
(func $_cleanup_418 (; 38 ;) (; has Stack IR ;) (param $0 i32)
(drop
(i32.load offset=68
(get_local $0)
)
)
)
(func $establishStackSpace (; 39 ;) (param $0 i32) (param $1 i32)
(func $establishStackSpace (; 39 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32)
(set_global $STACKTOP
(get_local $0)
)
@ -9535,7 +9535,7 @@
(get_local $1)
)
)
(func $dynCall_vi (; 40 ;) (param $0 i32) (param $1 i32)
(func $dynCall_vi (; 40 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32)
(call_indirect (type $FUNCSIG$vi)
(get_local $1)
(i32.add
@ -9547,32 +9547,32 @@
)
)
)
(func $b1 (; 41 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $b1 (; 41 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(call $abort
(i32.const 1)
)
(i32.const 0)
)
(func $stackRestore (; 42 ;) (param $0 i32)
(func $stackRestore (; 42 ;) (; has Stack IR ;) (param $0 i32)
(set_global $STACKTOP
(get_local $0)
)
)
(func $setTempRet0 (; 43 ;) (param $0 i32)
(func $setTempRet0 (; 43 ;) (; has Stack IR ;) (param $0 i32)
(set_global $tempRet0
(get_local $0)
)
)
(func $b0 (; 44 ;) (param $0 i32) (result i32)
(func $b0 (; 44 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(call $abort
(i32.const 0)
)
(i32.const 0)
)
(func $getTempRet0 (; 45 ;) (result i32)
(func $getTempRet0 (; 45 ;) (; has Stack IR ;) (result i32)
(get_global $tempRet0)
)
(func $_main (; 46 ;) (result i32)
(func $_main (; 46 ;) (; has Stack IR ;) (result i32)
(drop
(call $_puts
(i32.const 672)
@ -9580,10 +9580,10 @@
)
(i32.const 0)
)
(func $stackSave (; 47 ;) (result i32)
(func $stackSave (; 47 ;) (; has Stack IR ;) (result i32)
(get_global $STACKTOP)
)
(func $b2 (; 48 ;) (param $0 i32)
(func $b2 (; 48 ;) (; has Stack IR ;) (param $0 i32)
(call $abort
(i32.const 2)
)

View File

@ -50,7 +50,7 @@
(export "dynCall_ii" (func $dynCall_ii))
(export "dynCall_iiii" (func $dynCall_iiii))
(export "dynCall_vi" (func $dynCall_vi))
(func $_malloc (; 15 ;) (param $0 i32) (result i32)
(func $_malloc (; 15 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -5829,7 +5829,7 @@
)
(i32.const 0)
)
(func $_free (; 16 ;) (param $0 i32)
(func $_free (; 16 ;) (; has Stack IR ;) (param $0 i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -7650,7 +7650,7 @@
(i32.const -1)
)
)
(func $___stdio_write (; 17 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $___stdio_write (; 17 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(local $5 i32)
@ -8024,7 +8024,7 @@
)
(get_local $15)
)
(func $___fwritex (; 18 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $___fwritex (; 18 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(local $5 i32)
@ -8236,7 +8236,7 @@
)
(get_local $4)
)
(func $_fflush (; 19 ;) (param $0 i32) (result i32)
(func $_fflush (; 19 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(block $do-once
@ -8338,7 +8338,7 @@
)
(get_local $1)
)
(func $_strlen (; 20 ;) (param $0 i32) (result i32)
(func $_strlen (; 20 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -8482,7 +8482,7 @@
(get_local $3)
)
)
(func $___overflow (; 21 ;) (param $0 i32) (param $1 i32) (result i32)
(func $___overflow (; 21 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
(local $2 i32)
(local $3 i32)
(local $4 i32)
@ -8636,7 +8636,7 @@
)
(get_local $4)
)
(func $___fflush_unlocked (; 22 ;) (param $0 i32) (result i32)
(func $___fflush_unlocked (; 22 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -8759,7 +8759,7 @@
)
)
)
(func $_memcpy (; 23 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $_memcpy (; 23 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(if
(i32.ge_s
@ -8906,10 +8906,10 @@
)
(get_local $3)
)
(func $runPostSets (; 24 ;)
(func $runPostSets (; 24 ;) (; has Stack IR ;)
(nop)
)
(func $_memset (; 25 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $_memset (; 25 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(local $5 i32)
@ -9047,7 +9047,7 @@
(get_local $2)
)
)
(func $_puts (; 26 ;) (param $0 i32) (result i32)
(func $_puts (; 26 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -9139,7 +9139,7 @@
(i32.const 31)
)
)
(func $___stdio_seek (; 27 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $___stdio_seek (; 27 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(set_local $4
@ -9208,7 +9208,7 @@
)
(get_local $0)
)
(func $___towrite (; 28 ;) (param $0 i32) (result i32)
(func $___towrite (; 28 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(set_local $2
@ -9286,7 +9286,7 @@
)
)
)
(func $_fwrite (; 29 ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(func $_fwrite (; 29 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(local $4 i32)
(set_local $4
(i32.mul
@ -9314,7 +9314,7 @@
)
(get_local $2)
)
(func $___stdout_write (; 30 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $___stdout_write (; 30 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(set_local $4
@ -9383,7 +9383,7 @@
)
(get_local $3)
)
(func $___stdio_close (; 31 ;) (param $0 i32) (result i32)
(func $___stdio_close (; 31 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(set_local $1
(get_global $STACKTOP)
@ -9413,7 +9413,7 @@
)
(get_local $0)
)
(func $___syscall_ret (; 32 ;) (param $0 i32) (result i32)
(func $___syscall_ret (; 32 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(if (result i32)
(i32.gt_u
(get_local $0)
@ -9432,7 +9432,7 @@
(get_local $0)
)
)
(func $dynCall_iiii (; 33 ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(func $dynCall_iiii (; 33 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(call_indirect (type $FUNCSIG$iiii)
(get_local $1)
(get_local $2)
@ -9446,7 +9446,7 @@
)
)
)
(func $stackAlloc (; 34 ;) (param $0 i32) (result i32)
(func $stackAlloc (; 34 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(set_local $1
(get_global $STACKTOP)
@ -9468,7 +9468,7 @@
)
(get_local $1)
)
(func $___errno_location (; 35 ;) (result i32)
(func $___errno_location (; 35 ;) (; has Stack IR ;) (result i32)
(if (result i32)
(i32.load
(i32.const 8)
@ -9479,7 +9479,7 @@
(i32.const 60)
)
)
(func $setThrew (; 36 ;) (param $0 i32) (param $1 i32)
(func $setThrew (; 36 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32)
(if
(i32.eqz
(get_global $__THREW__)
@ -9494,7 +9494,7 @@
)
)
)
(func $dynCall_ii (; 37 ;) (param $0 i32) (param $1 i32) (result i32)
(func $dynCall_ii (; 37 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
(call_indirect (type $FUNCSIG$ii)
(get_local $1)
(i32.and
@ -9503,10 +9503,10 @@
)
)
)
(func $_cleanup_418 (; 38 ;) (param $0 i32)
(func $_cleanup_418 (; 38 ;) (; has Stack IR ;) (param $0 i32)
(nop)
)
(func $establishStackSpace (; 39 ;) (param $0 i32) (param $1 i32)
(func $establishStackSpace (; 39 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32)
(set_global $STACKTOP
(get_local $0)
)
@ -9514,7 +9514,7 @@
(get_local $1)
)
)
(func $dynCall_vi (; 40 ;) (param $0 i32) (param $1 i32)
(func $dynCall_vi (; 40 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32)
(call_indirect (type $FUNCSIG$vi)
(get_local $1)
(i32.add
@ -9526,32 +9526,32 @@
)
)
)
(func $b1 (; 41 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $b1 (; 41 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(call $abort
(i32.const 1)
)
(i32.const 0)
)
(func $stackRestore (; 42 ;) (param $0 i32)
(func $stackRestore (; 42 ;) (; has Stack IR ;) (param $0 i32)
(set_global $STACKTOP
(get_local $0)
)
)
(func $setTempRet0 (; 43 ;) (param $0 i32)
(func $setTempRet0 (; 43 ;) (; has Stack IR ;) (param $0 i32)
(set_global $tempRet0
(get_local $0)
)
)
(func $b0 (; 44 ;) (param $0 i32) (result i32)
(func $b0 (; 44 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(call $abort
(i32.const 0)
)
(i32.const 0)
)
(func $getTempRet0 (; 45 ;) (result i32)
(func $getTempRet0 (; 45 ;) (; has Stack IR ;) (result i32)
(get_global $tempRet0)
)
(func $_main (; 46 ;) (result i32)
(func $_main (; 46 ;) (; has Stack IR ;) (result i32)
(drop
(call $_puts
(i32.const 672)
@ -9559,10 +9559,10 @@
)
(i32.const 0)
)
(func $stackSave (; 47 ;) (result i32)
(func $stackSave (; 47 ;) (; has Stack IR ;) (result i32)
(get_global $STACKTOP)
)
(func $b2 (; 48 ;) (param $0 i32)
(func $b2 (; 48 ;) (; has Stack IR ;) (param $0 i32)
(call $abort
(i32.const 2)
)

View File

@ -63,7 +63,7 @@
(export "dynCall_iiii" (func $dynCall_iiii))
(export "dynCall_vi" (func $dynCall_vi))
(export "___udivmoddi4" (func $___udivmoddi4))
(func $stackAlloc (; 19 ;) (param $0 i32) (result i32)
(func $stackAlloc (; 19 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(set_local $1
(get_global $STACKTOP)
@ -92,15 +92,15 @@
)
(get_local $1)
)
(func $stackSave (; 20 ;) (result i32)
(func $stackSave (; 20 ;) (; has Stack IR ;) (result i32)
(get_global $STACKTOP)
)
(func $stackRestore (; 21 ;) (param $0 i32)
(func $stackRestore (; 21 ;) (; has Stack IR ;) (param $0 i32)
(set_global $STACKTOP
(get_local $0)
)
)
(func $establishStackSpace (; 22 ;) (param $0 i32) (param $1 i32)
(func $establishStackSpace (; 22 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32)
(set_global $STACKTOP
(get_local $0)
)
@ -108,7 +108,7 @@
(get_local $1)
)
)
(func $setThrew (; 23 ;) (param $0 i32) (param $1 i32)
(func $setThrew (; 23 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32)
(if
(i32.eqz
(get_global $__THREW__)
@ -123,15 +123,15 @@
)
)
)
(func $setTempRet0 (; 24 ;) (param $0 i32)
(func $setTempRet0 (; 24 ;) (; has Stack IR ;) (param $0 i32)
(set_global $tempRet0
(get_local $0)
)
)
(func $getTempRet0 (; 25 ;) (result i32)
(func $getTempRet0 (; 25 ;) (; has Stack IR ;) (result i32)
(get_global $tempRet0)
)
(func $_main (; 26 ;) (result i32)
(func $_main (; 26 ;) (; has Stack IR ;) (result i32)
(local $0 i32)
(set_local $0
(get_global $STACKTOP)
@ -160,7 +160,7 @@
)
(i32.const 0)
)
(func $_frexp (; 27 ;) (param $0 f64) (param $1 i32) (result f64)
(func $_frexp (; 27 ;) (; has Stack IR ;) (param $0 f64) (param $1 i32) (result f64)
(local $2 i32)
(local $3 i32)
(local $4 i32)
@ -265,7 +265,7 @@
)
(get_local $0)
)
(func $_strerror (; 28 ;) (param $0 i32) (result i32)
(func $_strerror (; 28 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(block $__rjto$1
@ -343,7 +343,7 @@
)
(get_local $0)
)
(func $___errno_location (; 29 ;) (result i32)
(func $___errno_location (; 29 ;) (; has Stack IR ;) (result i32)
(if (result i32)
(i32.load
(i32.const 16)
@ -354,7 +354,7 @@
(i32.const 60)
)
)
(func $___stdio_close (; 30 ;) (param $0 i32) (result i32)
(func $___stdio_close (; 30 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(set_local $1
(get_global $STACKTOP)
@ -391,7 +391,7 @@
)
(get_local $0)
)
(func $___stdout_write (; 31 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $___stdout_write (; 31 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(local $5 i32)
@ -471,7 +471,7 @@
)
(get_local $0)
)
(func $___stdio_seek (; 32 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $___stdio_seek (; 32 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(set_local $4
@ -547,7 +547,7 @@
)
(get_local $0)
)
(func $_fflush (; 33 ;) (param $0 i32) (result i32)
(func $_fflush (; 33 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(block $do-once
@ -642,7 +642,7 @@
)
(get_local $0)
)
(func $_printf (; 34 ;) (param $0 i32) (param $1 i32) (result i32)
(func $_printf (; 34 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
(local $2 i32)
(set_local $2
(get_global $STACKTOP)
@ -678,7 +678,7 @@
)
(get_local $0)
)
(func $___stdio_write (; 35 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $___stdio_write (; 35 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(local $5 i32)
@ -1023,7 +1023,7 @@
)
(get_local $2)
)
(func $_vfprintf (; 36 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $_vfprintf (; 36 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(local $5 i32)
@ -1300,7 +1300,7 @@
)
(get_local $0)
)
(func $___fwritex (; 37 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $___fwritex (; 37 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(local $5 i32)
@ -1486,7 +1486,7 @@
)
(get_local $3)
)
(func $___towrite (; 38 ;) (param $0 i32) (result i32)
(func $___towrite (; 38 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(set_local $1
@ -1564,7 +1564,7 @@
)
)
)
(func $_wcrtomb (; 39 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $_wcrtomb (; 39 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(block $do-once (result i32)
(if (result i32)
(get_local $0)
@ -1738,7 +1738,7 @@
)
)
)
(func $_wctomb (; 40 ;) (param $0 i32) (param $1 i32) (result i32)
(func $_wctomb (; 40 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
(if (result i32)
(get_local $0)
(call $_wcrtomb
@ -1749,7 +1749,7 @@
(i32.const 0)
)
)
(func $_memchr (; 41 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $_memchr (; 41 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(local $5 i32)
@ -1980,7 +1980,7 @@
(get_local $0)
)
)
(func $___syscall_ret (; 42 ;) (param $0 i32) (result i32)
(func $___syscall_ret (; 42 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(if (result i32)
(i32.gt_u
(get_local $0)
@ -1999,7 +1999,7 @@
(get_local $0)
)
)
(func $___fflush_unlocked (; 43 ;) (param $0 i32) (result i32)
(func $___fflush_unlocked (; 43 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -2121,14 +2121,14 @@
)
)
)
(func $_cleanup (; 44 ;) (param $0 i32)
(func $_cleanup (; 44 ;) (; has Stack IR ;) (param $0 i32)
(drop
(i32.load offset=68
(get_local $0)
)
)
)
(func $i32s-div (; 45 ;) (param $0 i32) (param $1 i32) (result i32)
(func $i32s-div (; 45 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
(if (result i32)
(get_local $1)
(if (result i32)
@ -2151,7 +2151,7 @@
(i32.const 0)
)
)
(func $i32u-rem (; 46 ;) (param $0 i32) (param $1 i32) (result i32)
(func $i32u-rem (; 46 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
(if (result i32)
(get_local $1)
(i32.rem_u
@ -2161,7 +2161,7 @@
(i32.const 0)
)
)
(func $i32u-div (; 47 ;) (param $0 i32) (param $1 i32) (result i32)
(func $i32u-div (; 47 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
(if (result i32)
(get_local $1)
(i32.div_u
@ -2171,7 +2171,7 @@
(i32.const 0)
)
)
(func $_printf_core (; 48 ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (param $4 i32) (result i32)
(func $_printf_core (; 48 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (param $4 i32) (result i32)
(local $5 i32)
(local $6 i32)
(local $7 i32)
@ -6991,7 +6991,7 @@
)
(get_local $17)
)
(func $_pop_arg_336 (; 49 ;) (param $0 i32) (param $1 i32) (param $2 i32)
(func $_pop_arg_336 (; 49 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32)
(local $3 i32)
(local $4 f64)
(local $5 i32)
@ -7391,7 +7391,7 @@
)
)
)
(func $_fmt_u (; 50 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $_fmt_u (; 50 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(if
@ -7513,7 +7513,7 @@
)
(get_local $2)
)
(func $_pad (; 51 ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (param $4 i32)
(func $_pad (; 51 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (param $4 i32)
(local $5 i32)
(local $6 i32)
(local $7 i32)
@ -7661,7 +7661,7 @@
(get_local $7)
)
)
(func $_malloc (; 52 ;) (param $0 i32) (result i32)
(func $_malloc (; 52 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -13094,7 +13094,7 @@
(i32.const 8)
)
)
(func $_free (; 53 ;) (param $0 i32)
(func $_free (; 53 ;) (; has Stack IR ;) (param $0 i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -14877,10 +14877,10 @@
(i32.const -1)
)
)
(func $runPostSets (; 54 ;)
(func $runPostSets (; 54 ;) (; has Stack IR ;)
(nop)
)
(func $_i64Subtract (; 55 ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(func $_i64Subtract (; 55 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(set_global $tempRet0
(i32.sub
(i32.sub
@ -14898,7 +14898,7 @@
(get_local $2)
)
)
(func $_i64Add (; 56 ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(func $_i64Add (; 56 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(local $4 i32)
(set_global $tempRet0
(i32.add
@ -14919,7 +14919,7 @@
)
(get_local $4)
)
(func $_memset (; 57 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $_memset (; 57 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(local $5 i32)
@ -15057,7 +15057,7 @@
(get_local $2)
)
)
(func $_bitshift64Lshr (; 58 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $_bitshift64Lshr (; 58 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(if
(i32.lt_s
(get_local $2)
@ -15107,7 +15107,7 @@
)
)
)
(func $_bitshift64Shl (; 59 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $_bitshift64Shl (; 59 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(if
(i32.lt_s
(get_local $2)
@ -15163,7 +15163,7 @@
)
(i32.const 0)
)
(func $_memcpy (; 60 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $_memcpy (; 60 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(if
(i32.ge_s
@ -15310,7 +15310,7 @@
)
(get_local $3)
)
(func $___udivdi3 (; 61 ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(func $___udivdi3 (; 61 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(call $___udivmoddi4
(get_local $0)
(get_local $1)
@ -15319,7 +15319,7 @@
(i32.const 0)
)
)
(func $___uremdi3 (; 62 ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(func $___uremdi3 (; 62 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(local $4 i32)
(set_local $4
(get_global $STACKTOP)
@ -15351,7 +15351,7 @@
(get_local $4)
)
)
(func $___udivmoddi4 (; 63 ;) (param $xl i32) (param $xh i32) (param $yl i32) (param $yh i32) (param $r i32) (result i32)
(func $___udivmoddi4 (; 63 ;) (; has Stack IR ;) (param $xl i32) (param $xh i32) (param $yl i32) (param $yh i32) (param $r i32) (result i32)
(local $x64 i64)
(local $y64 i64)
(set_local $x64
@ -15408,7 +15408,7 @@
(get_local $x64)
)
)
(func $dynCall_ii (; 64 ;) (param $0 i32) (param $1 i32) (result i32)
(func $dynCall_ii (; 64 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
(call_indirect (type $FUNCSIG$ii)
(get_local $1)
(i32.and
@ -15417,7 +15417,7 @@
)
)
)
(func $dynCall_iiii (; 65 ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(func $dynCall_iiii (; 65 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(call_indirect (type $FUNCSIG$iiii)
(get_local $1)
(get_local $2)
@ -15431,7 +15431,7 @@
)
)
)
(func $dynCall_vi (; 66 ;) (param $0 i32) (param $1 i32)
(func $dynCall_vi (; 66 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32)
(call_indirect (type $FUNCSIG$vi)
(get_local $1)
(i32.add
@ -15443,19 +15443,19 @@
)
)
)
(func $b0 (; 67 ;) (param $0 i32) (result i32)
(func $b0 (; 67 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(call $nullFunc_ii
(i32.const 0)
)
(i32.const 0)
)
(func $b1 (; 68 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $b1 (; 68 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(call $nullFunc_iiii
(i32.const 1)
)
(i32.const 0)
)
(func $b2 (; 69 ;) (param $0 i32)
(func $b2 (; 69 ;) (; has Stack IR ;) (param $0 i32)
(call $nullFunc_vi
(i32.const 2)
)

View File

@ -61,7 +61,7 @@
(export "dynCall_iiii" (func $dynCall_iiii))
(export "dynCall_vi" (func $dynCall_vi))
(export "___udivmoddi4" (func $___udivmoddi4))
(func $stackAlloc (; 18 ;) (param $0 i32) (result i32)
(func $stackAlloc (; 18 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(set_local $1
(get_global $STACKTOP)
@ -90,15 +90,15 @@
)
(get_local $1)
)
(func $stackSave (; 19 ;) (result i32)
(func $stackSave (; 19 ;) (; has Stack IR ;) (result i32)
(get_global $STACKTOP)
)
(func $stackRestore (; 20 ;) (param $0 i32)
(func $stackRestore (; 20 ;) (; has Stack IR ;) (param $0 i32)
(set_global $STACKTOP
(get_local $0)
)
)
(func $establishStackSpace (; 21 ;) (param $0 i32) (param $1 i32)
(func $establishStackSpace (; 21 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32)
(set_global $STACKTOP
(get_local $0)
)
@ -106,7 +106,7 @@
(get_local $1)
)
)
(func $setThrew (; 22 ;) (param $0 i32) (param $1 i32)
(func $setThrew (; 22 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32)
(if
(i32.eqz
(get_global $__THREW__)
@ -121,15 +121,15 @@
)
)
)
(func $setTempRet0 (; 23 ;) (param $0 i32)
(func $setTempRet0 (; 23 ;) (; has Stack IR ;) (param $0 i32)
(set_global $tempRet0
(get_local $0)
)
)
(func $getTempRet0 (; 24 ;) (result i32)
(func $getTempRet0 (; 24 ;) (; has Stack IR ;) (result i32)
(get_global $tempRet0)
)
(func $_main (; 25 ;) (result i32)
(func $_main (; 25 ;) (; has Stack IR ;) (result i32)
(local $0 i32)
(set_local $0
(get_global $STACKTOP)
@ -158,7 +158,7 @@
)
(i32.const 0)
)
(func $_frexp (; 26 ;) (param $0 f64) (param $1 i32) (result f64)
(func $_frexp (; 26 ;) (; has Stack IR ;) (param $0 f64) (param $1 i32) (result f64)
(local $2 i32)
(local $3 i32)
(local $4 i32)
@ -263,7 +263,7 @@
)
(get_local $0)
)
(func $_strerror (; 27 ;) (param $0 i32) (result i32)
(func $_strerror (; 27 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(block $__rjto$1
@ -341,7 +341,7 @@
)
(get_local $0)
)
(func $___errno_location (; 28 ;) (result i32)
(func $___errno_location (; 28 ;) (; has Stack IR ;) (result i32)
(if (result i32)
(i32.load
(i32.const 16)
@ -352,7 +352,7 @@
(i32.const 60)
)
)
(func $___stdio_close (; 29 ;) (param $0 i32) (result i32)
(func $___stdio_close (; 29 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(set_local $1
(get_global $STACKTOP)
@ -389,7 +389,7 @@
)
(get_local $0)
)
(func $___stdout_write (; 30 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $___stdout_write (; 30 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(local $5 i32)
@ -469,7 +469,7 @@
)
(get_local $0)
)
(func $___stdio_seek (; 31 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $___stdio_seek (; 31 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(set_local $4
@ -545,7 +545,7 @@
)
(get_local $0)
)
(func $_fflush (; 32 ;) (param $0 i32) (result i32)
(func $_fflush (; 32 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(block $do-once
@ -640,7 +640,7 @@
)
(get_local $0)
)
(func $_printf (; 33 ;) (param $0 i32) (param $1 i32) (result i32)
(func $_printf (; 33 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
(local $2 i32)
(set_local $2
(get_global $STACKTOP)
@ -676,7 +676,7 @@
)
(get_local $0)
)
(func $___stdio_write (; 34 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $___stdio_write (; 34 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(local $5 i32)
@ -1021,7 +1021,7 @@
)
(get_local $2)
)
(func $_vfprintf (; 35 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $_vfprintf (; 35 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(local $5 i32)
@ -1298,7 +1298,7 @@
)
(get_local $0)
)
(func $___fwritex (; 36 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $___fwritex (; 36 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(local $5 i32)
@ -1484,7 +1484,7 @@
)
(get_local $3)
)
(func $___towrite (; 37 ;) (param $0 i32) (result i32)
(func $___towrite (; 37 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(set_local $1
@ -1562,7 +1562,7 @@
)
)
)
(func $_wcrtomb (; 38 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $_wcrtomb (; 38 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(block $do-once (result i32)
(if (result i32)
(get_local $0)
@ -1736,7 +1736,7 @@
)
)
)
(func $_wctomb (; 39 ;) (param $0 i32) (param $1 i32) (result i32)
(func $_wctomb (; 39 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
(if (result i32)
(get_local $0)
(call $_wcrtomb
@ -1747,7 +1747,7 @@
(i32.const 0)
)
)
(func $_memchr (; 40 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $_memchr (; 40 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(local $5 i32)
@ -1978,7 +1978,7 @@
(get_local $0)
)
)
(func $___syscall_ret (; 41 ;) (param $0 i32) (result i32)
(func $___syscall_ret (; 41 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(if (result i32)
(i32.gt_u
(get_local $0)
@ -1997,7 +1997,7 @@
(get_local $0)
)
)
(func $___fflush_unlocked (; 42 ;) (param $0 i32) (result i32)
(func $___fflush_unlocked (; 42 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -2119,14 +2119,14 @@
)
)
)
(func $_cleanup (; 43 ;) (param $0 i32)
(func $_cleanup (; 43 ;) (; has Stack IR ;) (param $0 i32)
(drop
(i32.load offset=68
(get_local $0)
)
)
)
(func $f64-to-int (; 44 ;) (param $0 f64) (result i32)
(func $f64-to-int (; 44 ;) (; has Stack IR ;) (param $0 f64) (result i32)
(if (result i32)
(f64.ne
(get_local $0)
@ -2152,7 +2152,7 @@
)
)
)
(func $f64-to-uint (; 45 ;) (param $0 f64) (result i32)
(func $f64-to-uint (; 45 ;) (; has Stack IR ;) (param $0 f64) (result i32)
(if (result i32)
(f64.ne
(get_local $0)
@ -2178,7 +2178,7 @@
)
)
)
(func $i32s-div (; 46 ;) (param $0 i32) (param $1 i32) (result i32)
(func $i32s-div (; 46 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
(if (result i32)
(get_local $1)
(if (result i32)
@ -2201,7 +2201,7 @@
(i32.const 0)
)
)
(func $i32u-rem (; 47 ;) (param $0 i32) (param $1 i32) (result i32)
(func $i32u-rem (; 47 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
(if (result i32)
(get_local $1)
(i32.rem_u
@ -2211,7 +2211,7 @@
(i32.const 0)
)
)
(func $i32u-div (; 48 ;) (param $0 i32) (param $1 i32) (result i32)
(func $i32u-div (; 48 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
(if (result i32)
(get_local $1)
(i32.div_u
@ -2221,7 +2221,7 @@
(i32.const 0)
)
)
(func $_printf_core (; 49 ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (param $4 i32) (result i32)
(func $_printf_core (; 49 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (param $4 i32) (result i32)
(local $5 i32)
(local $6 i32)
(local $7 i32)
@ -7041,7 +7041,7 @@
)
(get_local $17)
)
(func $_pop_arg_336 (; 50 ;) (param $0 i32) (param $1 i32) (param $2 i32)
(func $_pop_arg_336 (; 50 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32)
(local $3 i32)
(local $4 f64)
(local $5 i32)
@ -7441,7 +7441,7 @@
)
)
)
(func $_fmt_u (; 51 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $_fmt_u (; 51 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(if
@ -7563,7 +7563,7 @@
)
(get_local $2)
)
(func $_pad (; 52 ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (param $4 i32)
(func $_pad (; 52 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (param $4 i32)
(local $5 i32)
(local $6 i32)
(local $7 i32)
@ -7711,7 +7711,7 @@
(get_local $7)
)
)
(func $_malloc (; 53 ;) (param $0 i32) (result i32)
(func $_malloc (; 53 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -13144,7 +13144,7 @@
(i32.const 8)
)
)
(func $_free (; 54 ;) (param $0 i32)
(func $_free (; 54 ;) (; has Stack IR ;) (param $0 i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -14927,10 +14927,10 @@
(i32.const -1)
)
)
(func $runPostSets (; 55 ;)
(func $runPostSets (; 55 ;) (; has Stack IR ;)
(nop)
)
(func $_i64Subtract (; 56 ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(func $_i64Subtract (; 56 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(set_global $tempRet0
(i32.sub
(i32.sub
@ -14948,7 +14948,7 @@
(get_local $2)
)
)
(func $_i64Add (; 57 ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(func $_i64Add (; 57 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(local $4 i32)
(set_global $tempRet0
(i32.add
@ -14969,7 +14969,7 @@
)
(get_local $4)
)
(func $_memset (; 58 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $_memset (; 58 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(local $5 i32)
@ -15107,7 +15107,7 @@
(get_local $2)
)
)
(func $_bitshift64Lshr (; 59 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $_bitshift64Lshr (; 59 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(if
(i32.lt_s
(get_local $2)
@ -15157,7 +15157,7 @@
)
)
)
(func $_bitshift64Shl (; 60 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $_bitshift64Shl (; 60 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(if
(i32.lt_s
(get_local $2)
@ -15213,7 +15213,7 @@
)
(i32.const 0)
)
(func $_memcpy (; 61 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $_memcpy (; 61 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(if
(i32.ge_s
@ -15360,7 +15360,7 @@
)
(get_local $3)
)
(func $___udivdi3 (; 62 ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(func $___udivdi3 (; 62 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(call $___udivmoddi4
(get_local $0)
(get_local $1)
@ -15369,7 +15369,7 @@
(i32.const 0)
)
)
(func $___uremdi3 (; 63 ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(func $___uremdi3 (; 63 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(local $4 i32)
(set_local $4
(get_global $STACKTOP)
@ -15401,7 +15401,7 @@
(get_local $4)
)
)
(func $___udivmoddi4 (; 64 ;) (param $xl i32) (param $xh i32) (param $yl i32) (param $yh i32) (param $r i32) (result i32)
(func $___udivmoddi4 (; 64 ;) (; has Stack IR ;) (param $xl i32) (param $xh i32) (param $yl i32) (param $yh i32) (param $r i32) (result i32)
(local $x64 i64)
(local $y64 i64)
(set_local $x64
@ -15458,7 +15458,7 @@
(get_local $x64)
)
)
(func $dynCall_ii (; 65 ;) (param $0 i32) (param $1 i32) (result i32)
(func $dynCall_ii (; 65 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
(call_indirect (type $FUNCSIG$ii)
(get_local $1)
(i32.and
@ -15467,7 +15467,7 @@
)
)
)
(func $dynCall_iiii (; 66 ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(func $dynCall_iiii (; 66 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(call_indirect (type $FUNCSIG$iiii)
(get_local $1)
(get_local $2)
@ -15481,7 +15481,7 @@
)
)
)
(func $dynCall_vi (; 67 ;) (param $0 i32) (param $1 i32)
(func $dynCall_vi (; 67 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32)
(call_indirect (type $FUNCSIG$vi)
(get_local $1)
(i32.add
@ -15493,19 +15493,19 @@
)
)
)
(func $b0 (; 68 ;) (param $0 i32) (result i32)
(func $b0 (; 68 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(call $nullFunc_ii
(i32.const 0)
)
(i32.const 0)
)
(func $b1 (; 69 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $b1 (; 69 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(call $nullFunc_iiii
(i32.const 1)
)
(i32.const 0)
)
(func $b2 (; 70 ;) (param $0 i32)
(func $b2 (; 70 ;) (; has Stack IR ;) (param $0 i32)
(call $nullFunc_vi
(i32.const 2)
)

View File

@ -60,7 +60,7 @@
(export "dynCall_iiii" (func $dynCall_iiii))
(export "dynCall_vi" (func $dynCall_vi))
(export "___udivmoddi4" (func $___udivmoddi4))
(func $stackAlloc (; 18 ;) (param $0 i32) (result i32)
(func $stackAlloc (; 18 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(set_local $1
(get_global $STACKTOP)
@ -89,15 +89,15 @@
)
(get_local $1)
)
(func $stackSave (; 19 ;) (result i32)
(func $stackSave (; 19 ;) (; has Stack IR ;) (result i32)
(get_global $STACKTOP)
)
(func $stackRestore (; 20 ;) (param $0 i32)
(func $stackRestore (; 20 ;) (; has Stack IR ;) (param $0 i32)
(set_global $STACKTOP
(get_local $0)
)
)
(func $establishStackSpace (; 21 ;) (param $0 i32) (param $1 i32)
(func $establishStackSpace (; 21 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32)
(set_global $STACKTOP
(get_local $0)
)
@ -105,7 +105,7 @@
(get_local $1)
)
)
(func $setThrew (; 22 ;) (param $0 i32) (param $1 i32)
(func $setThrew (; 22 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32)
(if
(i32.eqz
(get_global $__THREW__)
@ -120,15 +120,15 @@
)
)
)
(func $setTempRet0 (; 23 ;) (param $0 i32)
(func $setTempRet0 (; 23 ;) (; has Stack IR ;) (param $0 i32)
(set_global $tempRet0
(get_local $0)
)
)
(func $getTempRet0 (; 24 ;) (result i32)
(func $getTempRet0 (; 24 ;) (; has Stack IR ;) (result i32)
(get_global $tempRet0)
)
(func $_main (; 25 ;) (result i32)
(func $_main (; 25 ;) (; has Stack IR ;) (result i32)
(local $0 i32)
(set_local $0
(get_global $STACKTOP)
@ -157,7 +157,7 @@
)
(i32.const 0)
)
(func $_frexp (; 26 ;) (param $0 f64) (param $1 i32) (result f64)
(func $_frexp (; 26 ;) (; has Stack IR ;) (param $0 f64) (param $1 i32) (result f64)
(local $2 i32)
(local $3 i32)
(local $4 i32)
@ -262,7 +262,7 @@
)
(get_local $0)
)
(func $_strerror (; 27 ;) (param $0 i32) (result i32)
(func $_strerror (; 27 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(block $__rjto$1
@ -340,7 +340,7 @@
)
(get_local $0)
)
(func $___errno_location (; 28 ;) (result i32)
(func $___errno_location (; 28 ;) (; has Stack IR ;) (result i32)
(if (result i32)
(i32.load
(i32.const 16)
@ -351,7 +351,7 @@
(i32.const 60)
)
)
(func $___stdio_close (; 29 ;) (param $0 i32) (result i32)
(func $___stdio_close (; 29 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(set_local $1
(get_global $STACKTOP)
@ -388,7 +388,7 @@
)
(get_local $0)
)
(func $___stdout_write (; 30 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $___stdout_write (; 30 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(local $5 i32)
@ -468,7 +468,7 @@
)
(get_local $0)
)
(func $___stdio_seek (; 31 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $___stdio_seek (; 31 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(set_local $4
@ -544,7 +544,7 @@
)
(get_local $0)
)
(func $_fflush (; 32 ;) (param $0 i32) (result i32)
(func $_fflush (; 32 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(block $do-once
@ -634,7 +634,7 @@
)
(get_local $0)
)
(func $_printf (; 33 ;) (param $0 i32) (param $1 i32) (result i32)
(func $_printf (; 33 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
(local $2 i32)
(set_local $2
(get_global $STACKTOP)
@ -670,7 +670,7 @@
)
(get_local $0)
)
(func $___stdio_write (; 34 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $___stdio_write (; 34 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(local $5 i32)
@ -1015,7 +1015,7 @@
)
(get_local $2)
)
(func $_vfprintf (; 35 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $_vfprintf (; 35 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(local $5 i32)
@ -1287,7 +1287,7 @@
)
(get_local $0)
)
(func $___fwritex (; 36 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $___fwritex (; 36 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(local $5 i32)
@ -1473,7 +1473,7 @@
)
(get_local $3)
)
(func $___towrite (; 37 ;) (param $0 i32) (result i32)
(func $___towrite (; 37 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(set_local $1
@ -1551,7 +1551,7 @@
)
)
)
(func $_wcrtomb (; 38 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $_wcrtomb (; 38 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(block $do-once (result i32)
(if (result i32)
(get_local $0)
@ -1725,7 +1725,7 @@
)
)
)
(func $_wctomb (; 39 ;) (param $0 i32) (param $1 i32) (result i32)
(func $_wctomb (; 39 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
(if (result i32)
(get_local $0)
(call $_wcrtomb
@ -1736,7 +1736,7 @@
(i32.const 0)
)
)
(func $_memchr (; 40 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $_memchr (; 40 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(local $5 i32)
@ -1967,7 +1967,7 @@
(get_local $0)
)
)
(func $___syscall_ret (; 41 ;) (param $0 i32) (result i32)
(func $___syscall_ret (; 41 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(if (result i32)
(i32.gt_u
(get_local $0)
@ -1986,7 +1986,7 @@
(get_local $0)
)
)
(func $___fflush_unlocked (; 42 ;) (param $0 i32) (result i32)
(func $___fflush_unlocked (; 42 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -2108,10 +2108,10 @@
)
)
)
(func $_cleanup (; 43 ;) (param $0 i32)
(func $_cleanup (; 43 ;) (; has Stack IR ;) (param $0 i32)
(nop)
)
(func $_printf_core (; 44 ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (param $4 i32) (result i32)
(func $_printf_core (; 44 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (param $4 i32) (result i32)
(local $5 i32)
(local $6 i32)
(local $7 i32)
@ -6906,7 +6906,7 @@
)
(get_local $17)
)
(func $_pop_arg_336 (; 45 ;) (param $0 i32) (param $1 i32) (param $2 i32)
(func $_pop_arg_336 (; 45 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32)
(local $3 i32)
(local $4 f64)
(local $5 i32)
@ -7306,7 +7306,7 @@
)
)
)
(func $_fmt_u (; 46 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $_fmt_u (; 46 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(if
@ -7428,7 +7428,7 @@
)
(get_local $2)
)
(func $_pad (; 47 ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (param $4 i32)
(func $_pad (; 47 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (param $4 i32)
(local $5 i32)
(local $6 i32)
(local $7 i32)
@ -7576,7 +7576,7 @@
(get_local $7)
)
)
(func $_malloc (; 48 ;) (param $0 i32) (result i32)
(func $_malloc (; 48 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -13009,7 +13009,7 @@
(i32.const 8)
)
)
(func $_free (; 49 ;) (param $0 i32)
(func $_free (; 49 ;) (; has Stack IR ;) (param $0 i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -14791,10 +14791,10 @@
(i32.const -1)
)
)
(func $runPostSets (; 50 ;)
(func $runPostSets (; 50 ;) (; has Stack IR ;)
(nop)
)
(func $_i64Subtract (; 51 ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(func $_i64Subtract (; 51 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(set_global $tempRet0
(i32.sub
(i32.sub
@ -14812,7 +14812,7 @@
(get_local $2)
)
)
(func $_i64Add (; 52 ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(func $_i64Add (; 52 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(local $4 i32)
(set_global $tempRet0
(i32.add
@ -14833,7 +14833,7 @@
)
(get_local $4)
)
(func $_memset (; 53 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $_memset (; 53 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(local $5 i32)
@ -14971,7 +14971,7 @@
(get_local $2)
)
)
(func $_bitshift64Lshr (; 54 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $_bitshift64Lshr (; 54 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(if
(i32.lt_s
(get_local $2)
@ -15021,7 +15021,7 @@
)
)
)
(func $_bitshift64Shl (; 55 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $_bitshift64Shl (; 55 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(if
(i32.lt_s
(get_local $2)
@ -15077,7 +15077,7 @@
)
(i32.const 0)
)
(func $_memcpy (; 56 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $_memcpy (; 56 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(if
(i32.ge_s
@ -15224,7 +15224,7 @@
)
(get_local $3)
)
(func $___udivdi3 (; 57 ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(func $___udivdi3 (; 57 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(call $___udivmoddi4
(get_local $0)
(get_local $1)
@ -15233,7 +15233,7 @@
(i32.const 0)
)
)
(func $___uremdi3 (; 58 ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(func $___uremdi3 (; 58 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(local $4 i32)
(set_local $4
(get_global $STACKTOP)
@ -15265,7 +15265,7 @@
(get_local $4)
)
)
(func $___udivmoddi4 (; 59 ;) (param $xl i32) (param $xh i32) (param $yl i32) (param $yh i32) (param $r i32) (result i32)
(func $___udivmoddi4 (; 59 ;) (; has Stack IR ;) (param $xl i32) (param $xh i32) (param $yl i32) (param $yh i32) (param $r i32) (result i32)
(local $x64 i64)
(local $y64 i64)
(set_local $x64
@ -15322,7 +15322,7 @@
(get_local $x64)
)
)
(func $dynCall_ii (; 60 ;) (param $0 i32) (param $1 i32) (result i32)
(func $dynCall_ii (; 60 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
(call_indirect (type $FUNCSIG$ii)
(get_local $1)
(i32.and
@ -15331,7 +15331,7 @@
)
)
)
(func $dynCall_iiii (; 61 ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(func $dynCall_iiii (; 61 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(call_indirect (type $FUNCSIG$iiii)
(get_local $1)
(get_local $2)
@ -15345,7 +15345,7 @@
)
)
)
(func $dynCall_vi (; 62 ;) (param $0 i32) (param $1 i32)
(func $dynCall_vi (; 62 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32)
(call_indirect (type $FUNCSIG$vi)
(get_local $1)
(i32.add
@ -15357,19 +15357,19 @@
)
)
)
(func $b0 (; 63 ;) (param $0 i32) (result i32)
(func $b0 (; 63 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(call $nullFunc_ii
(i32.const 0)
)
(i32.const 0)
)
(func $b1 (; 64 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $b1 (; 64 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(call $nullFunc_iiii
(i32.const 1)
)
(i32.const 0)
)
(func $b2 (; 65 ;) (param $0 i32)
(func $b2 (; 65 ;) (; has Stack IR ;) (param $0 i32)
(call $nullFunc_vi
(i32.const 2)
)

View File

@ -299,7 +299,7 @@
(memory $0 1 1)
(export "mem" (memory $0))
(start $main)
(func $check (; 1 ;) (type $i) (result i32)
(func $check (; 1 ;) (; has Stack IR ;) (type $i) (result i32)
(if
(i32.eq
(i32.load
@ -334,7 +334,7 @@
)
)
)
(func $main (; 2 ;) (type $v)
(func $main (; 2 ;) (; has Stack IR ;) (type $v)
(local $0 i32)
(local $1 i32)
(i32.store

View File

@ -275,7 +275,7 @@
(memory $0 1 1)
(export "mem" (memory $0))
(start $main)
(func $check (; 1 ;) (type $i) (result i32)
(func $check (; 1 ;) (; has Stack IR ;) (type $i) (result i32)
(if
(i32.eq
(i32.load
@ -310,7 +310,7 @@
)
)
)
(func $main (; 2 ;) (type $v)
(func $main (; 2 ;) (; has Stack IR ;) (type $v)
(local $0 i32)
(i32.store
(i32.const 8)

View File

@ -3,7 +3,7 @@
(import "env" "memoryBase" (global $memoryBase i32))
(data (get_global $memoryBase) "hello_world.asm.js")
(export "add" (func $add))
(func $add (; 0 ;) (param $0 i32) (param $1 i32) (result i32)
(func $add (; 0 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
(i32.add
(get_local $0)
(get_local $1)

View File

@ -3,7 +3,7 @@
(import "env" "memoryBase" (global $memoryBase i32))
(data (get_global $memoryBase) "hello_world.asm.js")
(export "add" (func $add))
(func $add (; 0 ;) (param $0 i32) (param $1 i32) (result i32)
(func $add (; 0 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
(i32.add
(get_local $0)
(get_local $1)

View File

@ -1,6 +1,6 @@
(module
(export "add" (func $add))
(func $add (; 0 ;) (param $0 i32) (param $1 i32) (result i32)
(func $add (; 0 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
(i32.add
(get_local $0)
(get_local $1)

View File

@ -7,7 +7,7 @@
(data (get_global $memoryBase) "i64-setTempRet0.asm.js")
(export "illegalResult" (func $legalstub$illegalResult))
(export "imports" (func $imports))
(func $imports (; 1 ;) (result i32)
(func $imports (; 1 ;) (; has Stack IR ;) (result i32)
(i32.wrap/i64
(i64.or
(i64.extend_u/i32
@ -22,7 +22,7 @@
)
)
)
(func $legalstub$illegalResult (; 2 ;) (result i32)
(func $legalstub$illegalResult (; 2 ;) (; has Stack IR ;) (result i32)
(set_global $tempRet0
(i32.const 2)
)

View File

@ -7,7 +7,7 @@
(data (get_global $memoryBase) "i64-setTempRet0.asm.js")
(export "illegalResult" (func $legalstub$illegalResult))
(export "imports" (func $imports))
(func $imports (; 1 ;) (result i32)
(func $imports (; 1 ;) (; has Stack IR ;) (result i32)
(i32.wrap/i64
(i64.or
(i64.extend_u/i32
@ -22,7 +22,7 @@
)
)
)
(func $legalstub$illegalResult (; 2 ;) (result i32)
(func $legalstub$illegalResult (; 2 ;) (; has Stack IR ;) (result i32)
(set_global $tempRet0
(i32.const 2)
)

View File

@ -4,7 +4,7 @@
(global $tempRet0 (mut i32) (i32.const 0))
(export "illegalResult" (func $legalstub$illegalResult))
(export "imports" (func $imports))
(func $imports (; 1 ;) (result i32)
(func $imports (; 1 ;) (; has Stack IR ;) (result i32)
(i32.wrap/i64
(i64.or
(i64.extend_u/i32
@ -19,7 +19,7 @@
)
)
)
(func $legalstub$illegalResult (; 2 ;) (result i32)
(func $legalstub$illegalResult (; 2 ;) (; has Stack IR ;) (result i32)
(set_global $tempRet0
(i32.const 2)
)

View File

@ -8,7 +8,7 @@
(elem (get_global $tableBase) $gm)
(data (get_global $memoryBase) "importedSignCast.asm.js")
(export "func" (func $func))
(func $func (; 1 ;)
(func $func (; 1 ;) (; has Stack IR ;)
(drop
(call $gm
(i32.const 0)

View File

@ -8,7 +8,7 @@
(elem (get_global $tableBase) $gm)
(data (get_global $memoryBase) "importedSignCast.asm.js")
(export "func" (func $func))
(func $func (; 1 ;)
(func $func (; 1 ;) (; has Stack IR ;)
(drop
(call $gm
(i32.const 0)

View File

@ -5,7 +5,7 @@
(import "env" "_emscripten_glIsTexture" (func $gm (param i32) (result i32)))
(elem (get_global $tableBase) $gm)
(export "func" (func $func))
(func $func (; 1 ;)
(func $func (; 1 ;) (; has Stack IR ;)
(drop
(call $gm
(i32.const 0)

View File

@ -3,7 +3,7 @@
(import "env" "memoryBase" (global $memoryBase i32))
(data (get_global $memoryBase) "memorygrowth-minimal.asm.js")
(export "__growWasmMemory" (func $__growWasmMemory))
(func $__growWasmMemory (; 0 ;) (param $0 i32) (result i32)
(func $__growWasmMemory (; 0 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(grow_memory
(get_local $0)
)

View File

@ -3,7 +3,7 @@
(import "env" "memoryBase" (global $memoryBase i32))
(data (get_global $memoryBase) "memorygrowth-minimal.asm.js")
(export "__growWasmMemory" (func $__growWasmMemory))
(func $__growWasmMemory (; 0 ;) (param $0 i32) (result i32)
(func $__growWasmMemory (; 0 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(grow_memory
(get_local $0)
)

View File

@ -1,7 +1,7 @@
(module
(import "env" "memory" (memory $0 256))
(export "__growWasmMemory" (func $__growWasmMemory))
(func $__growWasmMemory (; 0 ;) (param $0 i32) (result i32)
(func $__growWasmMemory (; 0 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(grow_memory
(get_local $0)
)

View File

@ -50,12 +50,12 @@
(export "dynCall_ii" (func $kb))
(export "dynCall_iiii" (func $lb))
(export "dynCall_vi" (func $mb))
(func $__growWasmMemory (; 12 ;) (param $0 i32) (result i32)
(func $__growWasmMemory (; 12 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(grow_memory
(get_local $0)
)
)
(func $eb (; 13 ;) (param $0 i32) (result i32)
(func $eb (; 13 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -5877,7 +5877,7 @@
(i32.const 8)
)
)
(func $fb (; 14 ;) (param $0 i32)
(func $fb (; 14 ;) (; has Stack IR ;) (param $0 i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -7698,7 +7698,7 @@
(i32.const -1)
)
)
(func $Ra (; 15 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $Ra (; 15 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(local $5 i32)
@ -8072,7 +8072,7 @@
)
(get_local $15)
)
(func $Wa (; 16 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $Wa (; 16 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(local $5 i32)
@ -8284,7 +8284,7 @@
)
(get_local $4)
)
(func $Za (; 17 ;) (param $0 i32) (result i32)
(func $Za (; 17 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -8428,7 +8428,7 @@
(get_local $3)
)
)
(func $_a (; 18 ;) (param $0 i32) (result i32)
(func $_a (; 18 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(tee_local $1
@ -8532,7 +8532,7 @@
)
)
)
(func $ab (; 19 ;) (param $0 i32) (param $1 i32) (result i32)
(func $ab (; 19 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
(local $2 i32)
(local $3 i32)
(local $4 i32)
@ -8681,7 +8681,7 @@
)
(get_local $4)
)
(func $$a (; 20 ;) (param $0 i32) (result i32)
(func $$a (; 20 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -8816,7 +8816,7 @@
)
(get_local $2)
)
(func $jb (; 21 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $jb (; 21 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(if
(i32.ge_s
@ -8963,10 +8963,10 @@
)
(get_local $3)
)
(func $gb (; 22 ;)
(func $gb (; 22 ;) (; has Stack IR ;)
(nop)
)
(func $hb (; 23 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $hb (; 23 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(local $5 i32)
@ -9104,7 +9104,7 @@
(get_local $2)
)
)
(func $db (; 24 ;) (param $0 i32) (result i32)
(func $db (; 24 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(drop
@ -9194,7 +9194,7 @@
(i32.const 31)
)
)
(func $Xa (; 25 ;) (param $0 i32) (result i32)
(func $Xa (; 25 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(set_local $2
@ -9272,7 +9272,7 @@
)
)
)
(func $bb (; 26 ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(func $bb (; 26 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(local $4 i32)
(set_local $4
(i32.mul
@ -9311,7 +9311,7 @@
)
(get_local $2)
)
(func $Ua (; 27 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $Ua (; 27 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(set_local $4
@ -9380,7 +9380,7 @@
)
(get_local $0)
)
(func $Va (; 28 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $Va (; 28 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(set_local $4
@ -9450,7 +9450,7 @@
)
(get_local $3)
)
(func $Oa (; 29 ;) (param $0 i32) (result i32)
(func $Oa (; 29 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(set_local $1
(get_global $r)
@ -9480,7 +9480,7 @@
)
(get_local $0)
)
(func $Pa (; 30 ;) (param $0 i32) (result i32)
(func $Pa (; 30 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(if (result i32)
(i32.gt_u
(get_local $0)
@ -9499,7 +9499,7 @@
(get_local $0)
)
)
(func $Qa (; 31 ;) (result i32)
(func $Qa (; 31 ;) (; has Stack IR ;) (result i32)
(if (result i32)
(i32.load
(i32.const 1160)
@ -9510,7 +9510,7 @@
(i32.const 1204)
)
)
(func $lb (; 32 ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(func $lb (; 32 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(call_indirect (type $FUNCSIG$iiii)
(get_local $1)
(get_local $2)
@ -9524,7 +9524,7 @@
)
)
)
(func $Ea (; 33 ;) (param $0 i32) (result i32)
(func $Ea (; 33 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(set_local $1
(get_global $r)
@ -9546,13 +9546,13 @@
)
(get_local $1)
)
(func $ob (; 34 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $ob (; 34 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(call $ja
(i32.const 1)
)
(i32.const 0)
)
(func $Ia (; 35 ;) (param $0 i32) (param $1 i32)
(func $Ia (; 35 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32)
(if
(i32.eqz
(get_global $v)
@ -9567,7 +9567,7 @@
)
)
)
(func $kb (; 36 ;) (param $0 i32) (param $1 i32) (result i32)
(func $kb (; 36 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
(call_indirect (type $FUNCSIG$ii)
(get_local $1)
(i32.and
@ -9576,14 +9576,14 @@
)
)
)
(func $Sa (; 37 ;) (param $0 i32)
(func $Sa (; 37 ;) (; has Stack IR ;) (param $0 i32)
(drop
(i32.load offset=68
(get_local $0)
)
)
)
(func $mb (; 38 ;) (param $0 i32) (param $1 i32)
(func $mb (; 38 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32)
(call_indirect (type $FUNCSIG$vi)
(get_local $1)
(i32.add
@ -9595,7 +9595,7 @@
)
)
)
(func $Ha (; 39 ;) (param $0 i32) (param $1 i32)
(func $Ha (; 39 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32)
(set_global $r
(get_local $0)
)
@ -9603,13 +9603,13 @@
(get_local $1)
)
)
(func $nb (; 40 ;) (param $0 i32) (result i32)
(func $nb (; 40 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(call $ja
(i32.const 0)
)
(i32.const 0)
)
(func $Na (; 41 ;) (result i32)
(func $Na (; 41 ;) (; has Stack IR ;) (result i32)
(drop
(call $db
(i32.const 1144)
@ -9617,28 +9617,28 @@
)
(i32.const 0)
)
(func $pb (; 42 ;) (param $0 i32)
(func $pb (; 42 ;) (; has Stack IR ;) (param $0 i32)
(call $ja
(i32.const 2)
)
)
(func $La (; 43 ;) (param $0 i32)
(func $La (; 43 ;) (; has Stack IR ;) (param $0 i32)
(set_global $K
(get_local $0)
)
)
(func $Ga (; 44 ;) (param $0 i32)
(func $Ga (; 44 ;) (; has Stack IR ;) (param $0 i32)
(set_global $r
(get_local $0)
)
)
(func $Ma (; 45 ;) (result i32)
(func $Ma (; 45 ;) (; has Stack IR ;) (result i32)
(get_global $K)
)
(func $Fa (; 46 ;) (result i32)
(func $Fa (; 46 ;) (; has Stack IR ;) (result i32)
(get_global $r)
)
(func $ib (; 47 ;) (result i32)
(func $ib (; 47 ;) (; has Stack IR ;) (result i32)
(i32.const 0)
)
)

View File

@ -50,12 +50,12 @@
(export "dynCall_ii" (func $kb))
(export "dynCall_iiii" (func $lb))
(export "dynCall_vi" (func $mb))
(func $__growWasmMemory (; 12 ;) (param $0 i32) (result i32)
(func $__growWasmMemory (; 12 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(grow_memory
(get_local $0)
)
)
(func $eb (; 13 ;) (param $0 i32) (result i32)
(func $eb (; 13 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -5877,7 +5877,7 @@
(i32.const 8)
)
)
(func $fb (; 14 ;) (param $0 i32)
(func $fb (; 14 ;) (; has Stack IR ;) (param $0 i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -7698,7 +7698,7 @@
(i32.const -1)
)
)
(func $Ra (; 15 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $Ra (; 15 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(local $5 i32)
@ -8072,7 +8072,7 @@
)
(get_local $15)
)
(func $Wa (; 16 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $Wa (; 16 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(local $5 i32)
@ -8284,7 +8284,7 @@
)
(get_local $4)
)
(func $Za (; 17 ;) (param $0 i32) (result i32)
(func $Za (; 17 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -8428,7 +8428,7 @@
(get_local $3)
)
)
(func $_a (; 18 ;) (param $0 i32) (result i32)
(func $_a (; 18 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(tee_local $1
@ -8532,7 +8532,7 @@
)
)
)
(func $ab (; 19 ;) (param $0 i32) (param $1 i32) (result i32)
(func $ab (; 19 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
(local $2 i32)
(local $3 i32)
(local $4 i32)
@ -8681,7 +8681,7 @@
)
(get_local $4)
)
(func $$a (; 20 ;) (param $0 i32) (result i32)
(func $$a (; 20 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -8816,7 +8816,7 @@
)
(get_local $2)
)
(func $jb (; 21 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $jb (; 21 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(if
(i32.ge_s
@ -8963,10 +8963,10 @@
)
(get_local $3)
)
(func $gb (; 22 ;)
(func $gb (; 22 ;) (; has Stack IR ;)
(nop)
)
(func $hb (; 23 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $hb (; 23 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(local $5 i32)
@ -9104,7 +9104,7 @@
(get_local $2)
)
)
(func $db (; 24 ;) (param $0 i32) (result i32)
(func $db (; 24 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(drop
@ -9194,7 +9194,7 @@
(i32.const 31)
)
)
(func $Xa (; 25 ;) (param $0 i32) (result i32)
(func $Xa (; 25 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(set_local $2
@ -9272,7 +9272,7 @@
)
)
)
(func $bb (; 26 ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(func $bb (; 26 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(local $4 i32)
(set_local $4
(i32.mul
@ -9311,7 +9311,7 @@
)
(get_local $2)
)
(func $Ua (; 27 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $Ua (; 27 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(set_local $4
@ -9380,7 +9380,7 @@
)
(get_local $0)
)
(func $Va (; 28 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $Va (; 28 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(set_local $4
@ -9450,7 +9450,7 @@
)
(get_local $3)
)
(func $Oa (; 29 ;) (param $0 i32) (result i32)
(func $Oa (; 29 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(set_local $1
(get_global $r)
@ -9480,7 +9480,7 @@
)
(get_local $0)
)
(func $Pa (; 30 ;) (param $0 i32) (result i32)
(func $Pa (; 30 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(if (result i32)
(i32.gt_u
(get_local $0)
@ -9499,7 +9499,7 @@
(get_local $0)
)
)
(func $Qa (; 31 ;) (result i32)
(func $Qa (; 31 ;) (; has Stack IR ;) (result i32)
(if (result i32)
(i32.load
(i32.const 1160)
@ -9510,7 +9510,7 @@
(i32.const 1204)
)
)
(func $lb (; 32 ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(func $lb (; 32 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(call_indirect (type $FUNCSIG$iiii)
(get_local $1)
(get_local $2)
@ -9524,7 +9524,7 @@
)
)
)
(func $Ea (; 33 ;) (param $0 i32) (result i32)
(func $Ea (; 33 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(set_local $1
(get_global $r)
@ -9546,13 +9546,13 @@
)
(get_local $1)
)
(func $ob (; 34 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $ob (; 34 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(call $ja
(i32.const 1)
)
(i32.const 0)
)
(func $Ia (; 35 ;) (param $0 i32) (param $1 i32)
(func $Ia (; 35 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32)
(if
(i32.eqz
(get_global $v)
@ -9567,7 +9567,7 @@
)
)
)
(func $kb (; 36 ;) (param $0 i32) (param $1 i32) (result i32)
(func $kb (; 36 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
(call_indirect (type $FUNCSIG$ii)
(get_local $1)
(i32.and
@ -9576,14 +9576,14 @@
)
)
)
(func $Sa (; 37 ;) (param $0 i32)
(func $Sa (; 37 ;) (; has Stack IR ;) (param $0 i32)
(drop
(i32.load offset=68
(get_local $0)
)
)
)
(func $mb (; 38 ;) (param $0 i32) (param $1 i32)
(func $mb (; 38 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32)
(call_indirect (type $FUNCSIG$vi)
(get_local $1)
(i32.add
@ -9595,7 +9595,7 @@
)
)
)
(func $Ha (; 39 ;) (param $0 i32) (param $1 i32)
(func $Ha (; 39 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32)
(set_global $r
(get_local $0)
)
@ -9603,13 +9603,13 @@
(get_local $1)
)
)
(func $nb (; 40 ;) (param $0 i32) (result i32)
(func $nb (; 40 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(call $ja
(i32.const 0)
)
(i32.const 0)
)
(func $Na (; 41 ;) (result i32)
(func $Na (; 41 ;) (; has Stack IR ;) (result i32)
(drop
(call $db
(i32.const 1144)
@ -9617,28 +9617,28 @@
)
(i32.const 0)
)
(func $pb (; 42 ;) (param $0 i32)
(func $pb (; 42 ;) (; has Stack IR ;) (param $0 i32)
(call $ja
(i32.const 2)
)
)
(func $La (; 43 ;) (param $0 i32)
(func $La (; 43 ;) (; has Stack IR ;) (param $0 i32)
(set_global $K
(get_local $0)
)
)
(func $Ga (; 44 ;) (param $0 i32)
(func $Ga (; 44 ;) (; has Stack IR ;) (param $0 i32)
(set_global $r
(get_local $0)
)
)
(func $Ma (; 45 ;) (result i32)
(func $Ma (; 45 ;) (; has Stack IR ;) (result i32)
(get_global $K)
)
(func $Fa (; 46 ;) (result i32)
(func $Fa (; 46 ;) (; has Stack IR ;) (result i32)
(get_global $r)
)
(func $ib (; 47 ;) (result i32)
(func $ib (; 47 ;) (; has Stack IR ;) (result i32)
(i32.const 0)
)
)

View File

@ -48,12 +48,12 @@
(export "dynCall_ii" (func $kb))
(export "dynCall_iiii" (func $lb))
(export "dynCall_vi" (func $mb))
(func $__growWasmMemory (; 12 ;) (param $0 i32) (result i32)
(func $__growWasmMemory (; 12 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(grow_memory
(get_local $0)
)
)
(func $eb (; 13 ;) (param $0 i32) (result i32)
(func $eb (; 13 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -5875,7 +5875,7 @@
(i32.const 8)
)
)
(func $fb (; 14 ;) (param $0 i32)
(func $fb (; 14 ;) (; has Stack IR ;) (param $0 i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -7696,7 +7696,7 @@
(i32.const -1)
)
)
(func $Ra (; 15 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $Ra (; 15 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(local $5 i32)
@ -8070,7 +8070,7 @@
)
(get_local $15)
)
(func $Wa (; 16 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $Wa (; 16 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(local $5 i32)
@ -8282,7 +8282,7 @@
)
(get_local $4)
)
(func $Za (; 17 ;) (param $0 i32) (result i32)
(func $Za (; 17 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -8426,7 +8426,7 @@
(get_local $3)
)
)
(func $_a (; 18 ;) (param $0 i32) (result i32)
(func $_a (; 18 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(tee_local $1
@ -8525,7 +8525,7 @@
)
)
)
(func $ab (; 19 ;) (param $0 i32) (param $1 i32) (result i32)
(func $ab (; 19 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
(local $2 i32)
(local $3 i32)
(local $4 i32)
@ -8674,7 +8674,7 @@
)
(get_local $4)
)
(func $$a (; 20 ;) (param $0 i32) (result i32)
(func $$a (; 20 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(local $3 i32)
@ -8809,7 +8809,7 @@
)
(get_local $2)
)
(func $jb (; 21 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $jb (; 21 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(if
(i32.ge_s
@ -8956,10 +8956,10 @@
)
(get_local $3)
)
(func $gb (; 22 ;)
(func $gb (; 22 ;) (; has Stack IR ;)
(nop)
)
(func $hb (; 23 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $hb (; 23 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(local $5 i32)
@ -9097,7 +9097,7 @@
(get_local $2)
)
)
(func $db (; 24 ;) (param $0 i32) (result i32)
(func $db (; 24 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(drop
@ -9187,7 +9187,7 @@
(i32.const 31)
)
)
(func $Xa (; 25 ;) (param $0 i32) (result i32)
(func $Xa (; 25 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(local $2 i32)
(set_local $2
@ -9265,7 +9265,7 @@
)
)
)
(func $bb (; 26 ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(func $bb (; 26 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(local $4 i32)
(set_local $4
(i32.mul
@ -9293,7 +9293,7 @@
)
(get_local $2)
)
(func $Ua (; 27 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $Ua (; 27 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(set_local $4
@ -9362,7 +9362,7 @@
)
(get_local $0)
)
(func $Va (; 28 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $Va (; 28 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(local $3 i32)
(local $4 i32)
(set_local $4
@ -9432,7 +9432,7 @@
)
(get_local $3)
)
(func $Oa (; 29 ;) (param $0 i32) (result i32)
(func $Oa (; 29 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(set_local $1
(get_global $r)
@ -9462,7 +9462,7 @@
)
(get_local $0)
)
(func $Pa (; 30 ;) (param $0 i32) (result i32)
(func $Pa (; 30 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(if (result i32)
(i32.gt_u
(get_local $0)
@ -9481,7 +9481,7 @@
(get_local $0)
)
)
(func $Qa (; 31 ;) (result i32)
(func $Qa (; 31 ;) (; has Stack IR ;) (result i32)
(select
(i32.load
(i32.const 64)
@ -9492,7 +9492,7 @@
)
)
)
(func $lb (; 32 ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(func $lb (; 32 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(call_indirect (type $FUNCSIG$iiii)
(get_local $1)
(get_local $2)
@ -9506,7 +9506,7 @@
)
)
)
(func $Ea (; 33 ;) (param $0 i32) (result i32)
(func $Ea (; 33 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(local $1 i32)
(set_local $1
(get_global $r)
@ -9528,13 +9528,13 @@
)
(get_local $1)
)
(func $ob (; 34 ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $ob (; 34 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(call $ja
(i32.const 1)
)
(i32.const 0)
)
(func $Ia (; 35 ;) (param $0 i32) (param $1 i32)
(func $Ia (; 35 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32)
(if
(i32.eqz
(get_global $v)
@ -9549,7 +9549,7 @@
)
)
)
(func $kb (; 36 ;) (param $0 i32) (param $1 i32) (result i32)
(func $kb (; 36 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result i32)
(call_indirect (type $FUNCSIG$ii)
(get_local $1)
(i32.and
@ -9558,10 +9558,10 @@
)
)
)
(func $Sa (; 37 ;) (param $0 i32)
(func $Sa (; 37 ;) (; has Stack IR ;) (param $0 i32)
(nop)
)
(func $mb (; 38 ;) (param $0 i32) (param $1 i32)
(func $mb (; 38 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32)
(call_indirect (type $FUNCSIG$vi)
(get_local $1)
(i32.add
@ -9573,7 +9573,7 @@
)
)
)
(func $Ha (; 39 ;) (param $0 i32) (param $1 i32)
(func $Ha (; 39 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32)
(set_global $r
(get_local $0)
)
@ -9581,13 +9581,13 @@
(get_local $1)
)
)
(func $nb (; 40 ;) (param $0 i32) (result i32)
(func $nb (; 40 ;) (; has Stack IR ;) (param $0 i32) (result i32)
(call $ja
(i32.const 0)
)
(i32.const 0)
)
(func $Na (; 41 ;) (result i32)
(func $Na (; 41 ;) (; has Stack IR ;) (result i32)
(drop
(call $db
(i32.const 1144)
@ -9595,28 +9595,28 @@
)
(i32.const 0)
)
(func $pb (; 42 ;) (param $0 i32)
(func $pb (; 42 ;) (; has Stack IR ;) (param $0 i32)
(call $ja
(i32.const 2)
)
)
(func $La (; 43 ;) (param $0 i32)
(func $La (; 43 ;) (; has Stack IR ;) (param $0 i32)
(set_global $K
(get_local $0)
)
)
(func $Ga (; 44 ;) (param $0 i32)
(func $Ga (; 44 ;) (; has Stack IR ;) (param $0 i32)
(set_global $r
(get_local $0)
)
)
(func $Ma (; 45 ;) (result i32)
(func $Ma (; 45 ;) (; has Stack IR ;) (result i32)
(get_global $K)
)
(func $Fa (; 46 ;) (result i32)
(func $Fa (; 46 ;) (; has Stack IR ;) (result i32)
(get_global $r)
)
(func $ib (; 47 ;) (result i32)
(func $ib (; 47 ;) (; has Stack IR ;) (result i32)
(i32.const 0)
)
)

View File

@ -8,16 +8,16 @@
(export "neg" (func $legalstub$neg))
(export "bitcasts" (func $legalstub$bitcasts))
(export "ctzzzz" (func $ctzzzz))
(func $ctzzzz (; 0 ;) (result i32)
(func $ctzzzz (; 0 ;) (; has Stack IR ;) (result i32)
(i32.const 2)
)
(func $ub (; 1 ;) (result i32)
(func $ub (; 1 ;) (; has Stack IR ;) (result i32)
(drop
(call $ub)
)
(get_global $M)
)
(func $legalstub$floats (; 2 ;) (param $0 f64) (result f64)
(func $legalstub$floats (; 2 ;) (; has Stack IR ;) (param $0 f64) (result f64)
(f64.promote/f32
(f32.add
(f32.const 0)
@ -27,7 +27,7 @@
)
)
)
(func $legalstub$neg (; 3 ;) (param $0 i32) (param $1 i32) (result f64)
(func $legalstub$neg (; 3 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result f64)
(i32.store
(get_local $0)
(get_local $1)
@ -40,7 +40,7 @@
)
)
)
(func $legalstub$bitcasts (; 4 ;) (param $0 i32) (param $1 f64)
(func $legalstub$bitcasts (; 4 ;) (; has Stack IR ;) (param $0 i32) (param $1 f64)
(nop)
)
)

View File

@ -8,16 +8,16 @@
(export "neg" (func $legalstub$neg))
(export "bitcasts" (func $legalstub$bitcasts))
(export "ctzzzz" (func $ctzzzz))
(func $ctzzzz (; 0 ;) (result i32)
(func $ctzzzz (; 0 ;) (; has Stack IR ;) (result i32)
(i32.const 2)
)
(func $ub (; 1 ;) (result i32)
(func $ub (; 1 ;) (; has Stack IR ;) (result i32)
(drop
(call $ub)
)
(get_global $M)
)
(func $legalstub$floats (; 2 ;) (param $0 f64) (result f64)
(func $legalstub$floats (; 2 ;) (; has Stack IR ;) (param $0 f64) (result f64)
(f64.promote/f32
(f32.add
(f32.const 0)
@ -27,7 +27,7 @@
)
)
)
(func $legalstub$neg (; 3 ;) (param $0 i32) (param $1 i32) (result f64)
(func $legalstub$neg (; 3 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result f64)
(i32.store
(get_local $0)
(get_local $1)
@ -40,7 +40,7 @@
)
)
)
(func $legalstub$bitcasts (; 4 ;) (param $0 i32) (param $1 f64)
(func $legalstub$bitcasts (; 4 ;) (; has Stack IR ;) (param $0 i32) (param $1 f64)
(nop)
)
)

View File

@ -6,16 +6,16 @@
(export "neg" (func $legalstub$neg))
(export "bitcasts" (func $legalstub$bitcasts))
(export "ctzzzz" (func $ctzzzz))
(func $ctzzzz (; 0 ;) (result i32)
(func $ctzzzz (; 0 ;) (; has Stack IR ;) (result i32)
(i32.const 2)
)
(func $ub (; 1 ;) (result i32)
(func $ub (; 1 ;) (; has Stack IR ;) (result i32)
(drop
(call $ub)
)
(get_global $M)
)
(func $legalstub$floats (; 2 ;) (param $0 f64) (result f64)
(func $legalstub$floats (; 2 ;) (; has Stack IR ;) (param $0 f64) (result f64)
(f64.promote/f32
(f32.add
(f32.const 0)
@ -25,7 +25,7 @@
)
)
)
(func $legalstub$neg (; 3 ;) (param $0 i32) (param $1 i32) (result f64)
(func $legalstub$neg (; 3 ;) (; has Stack IR ;) (param $0 i32) (param $1 i32) (result f64)
(i32.store
(get_local $0)
(get_local $1)
@ -38,7 +38,7 @@
)
)
)
(func $legalstub$bitcasts (; 4 ;) (param $0 i32) (param $1 f64)
(func $legalstub$bitcasts (; 4 ;) (; has Stack IR ;) (param $0 i32) (param $1 f64)
(nop)
)
)

View File

@ -6,13 +6,13 @@
(data (get_global $memoryBase) "noffi_f32.asm.js")
(export "main" (func $main))
(export "exportf" (func $exportf))
(func $exportf (; 1 ;) (param $0 f32) (result f32)
(func $exportf (; 1 ;) (; has Stack IR ;) (param $0 f32) (result f32)
(f32.add
(get_local $0)
(f32.const 1)
)
)
(func $main (; 2 ;) (result i32)
(func $main (; 2 ;) (; has Stack IR ;) (result i32)
(drop
(call $importf
(f32.const 3.4000000953674316)

View File

@ -6,13 +6,13 @@
(data (get_global $memoryBase) "noffi_f32.asm.js")
(export "main" (func $main))
(export "exportf" (func $exportf))
(func $exportf (; 1 ;) (param $0 f32) (result f32)
(func $exportf (; 1 ;) (; has Stack IR ;) (param $0 f32) (result f32)
(f32.add
(get_local $0)
(f32.const 1)
)
)
(func $main (; 2 ;) (result i32)
(func $main (; 2 ;) (; has Stack IR ;) (result i32)
(drop
(call $importf
(f32.const 3.4000000953674316)

View File

@ -3,13 +3,13 @@
(import "env" "_importf" (func $importf (param f32) (result f32)))
(export "main" (func $main))
(export "exportf" (func $exportf))
(func $exportf (; 1 ;) (param $0 f32) (result f32)
(func $exportf (; 1 ;) (; has Stack IR ;) (param $0 f32) (result f32)
(f32.add
(get_local $0)
(f32.const 1)
)
)
(func $main (; 2 ;) (result i32)
(func $main (; 2 ;) (; has Stack IR ;) (result i32)
(drop
(call $importf
(f32.const 3.4000000953674316)

View File

@ -6,13 +6,13 @@
(data (get_global $memoryBase) "noffi_i64.asm.js")
(export "_add" (func $add))
(export "_main" (func $main))
(func $add (; 1 ;) (param $0 i64) (param $1 i64) (result i64)
(func $add (; 1 ;) (; has Stack IR ;) (param $0 i64) (param $1 i64) (result i64)
(i64.add
(get_local $1)
(get_local $0)
)
)
(func $main (; 2 ;) (result i32)
(func $main (; 2 ;) (; has Stack IR ;) (result i32)
(drop
(call $importll
(i64.const 2)

View File

@ -6,13 +6,13 @@
(data (get_global $memoryBase) "noffi_i64.asm.js")
(export "_add" (func $add))
(export "_main" (func $main))
(func $add (; 1 ;) (param $0 i64) (param $1 i64) (result i64)
(func $add (; 1 ;) (; has Stack IR ;) (param $0 i64) (param $1 i64) (result i64)
(i64.add
(get_local $1)
(get_local $0)
)
)
(func $main (; 2 ;) (result i32)
(func $main (; 2 ;) (; has Stack IR ;) (result i32)
(drop
(call $importll
(i64.const 2)

View File

@ -3,13 +3,13 @@
(import "env" "_importll" (func $importll (param i64) (result i64)))
(export "_add" (func $add))
(export "_main" (func $main))
(func $add (; 1 ;) (param $0 i64) (param $1 i64) (result i64)
(func $add (; 1 ;) (; has Stack IR ;) (param $0 i64) (param $1 i64) (result i64)
(i64.add
(get_local $1)
(get_local $0)
)
)
(func $main (; 2 ;) (result i32)
(func $main (; 2 ;) (; has Stack IR ;) (result i32)
(drop
(call $importll
(i64.const 2)

View File

@ -5,7 +5,7 @@
(export "fac-iter" (func $2))
(export "fac-iter-named" (func $3))
(export "fac-opt" (func $4))
(func $0 (; 0 ;) (type $0) (param $0 i64) (result i64)
(func $0 (; 0 ;) (; has Stack IR ;) (type $0) (param $0 i64) (result i64)
(if (result i64)
(i64.eq
(get_local $0)
@ -23,7 +23,7 @@
)
)
)
(func $1 (; 1 ;) (type $0) (param $0 i64) (result i64)
(func $1 (; 1 ;) (; has Stack IR ;) (type $0) (param $0 i64) (result i64)
(if (result i64)
(i64.eq
(get_local $0)
@ -41,10 +41,10 @@
)
)
)
(func $2 (; 2 ;) (type $0) (param $0 i64) (result i64)
(func $2 (; 2 ;) (; has Stack IR ;) (type $0) (param $0 i64) (result i64)
(unreachable)
)
(func $3 (; 3 ;) (type $0) (param $0 i64) (result i64)
(func $3 (; 3 ;) (; has Stack IR ;) (type $0) (param $0 i64) (result i64)
(local $1 i64)
(set_local $1
(i64.const 1)
@ -74,7 +74,7 @@
)
(get_local $1)
)
(func $4 (; 4 ;) (type $0) (param $0 i64) (result i64)
(func $4 (; 4 ;) (; has Stack IR ;) (type $0) (param $0 i64) (result i64)
(local $1 i64)
(set_local $1
(i64.const 1)

View File

@ -3,7 +3,7 @@
(type $1 (func (param i64)))
(export "ret" (func $ret))
(export "waka" (func $if-0-unreachable-to-none))
(func $ret (; 0 ;) (type $0) (result i32)
(func $ret (; 0 ;) (; has Stack IR ;) (type $0) (result i32)
(block $out (result i32)
(drop
(call $ret)
@ -17,7 +17,7 @@
(i32.const 999)
)
)
(func $if-0-unreachable-to-none (; 1 ;) (type $1) (param $0 i64)
(func $if-0-unreachable-to-none (; 1 ;) (; has Stack IR ;) (type $1) (param $0 i64)
(unreachable)
)
)

View File

@ -0,0 +1,29 @@
$stacky-help:
(no stack ir)
(module
(type $0 (func (param i32) (result i32)))
(export "stacky-help" (func $stacky-help))
(func $stacky-help (; 0 ;) (type $0) (param $0 i32) (result i32)
(local $1 i32)
(i32.add
(call $stacky-help
(i32.const 0)
)
(block (result i32)
(set_local $1
(call $stacky-help
(i32.const 1)
)
)
(drop
(call $stacky-help
(i32.const 2)
)
)
(i32.eqz
(get_local $1)
)
)
)
)
)

View File

@ -0,0 +1,16 @@
(module
(export "stacky-help" (func $stacky-help))
(func $stacky-help (param $x i32) (result i32)
(local $temp i32)
(i32.add
(call $stacky-help (i32.const 0))
(i32.eqz
(block (result i32) ;; after we use the stack instead of the local, we can remove this block
(set_local $temp (call $stacky-help (i32.const 1)))
(drop (call $stacky-help (i32.const 2)))
(get_local $temp)
)
)
)
)
)

View File

@ -0,0 +1,16 @@
$0:
(no stack ir)
(module
(type $0 (func (param i32 i32 i32 i64) (result i64)))
(export "func" (func $0))
(func $0 (; 0 ;) (type $0) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i64) (result i64)
(local $4 i32)
(block $label$1
(set_local $3
(i64.const 2147483647)
)
(nop)
)
(i64.const 2147483647)
)
)

View File

@ -0,0 +1,18 @@
(module
(func "func" (param $var$0 i32) (param $var$1 i32) (param $var$2 i32) (param $var$3 i64) (result i64)
(local $var$4 i32)
(block $label$1
(set_local $var$3
(i64.const 2147483647)
)
(br_if $label$1
(get_local $var$4) ;; precompute-propagate will optimize this into 0, then the br_if is nopped
;; in place. if stack ir is not regenerated, that means we have the get
;; on the stack from before, and the br_if is now a nop, which means no one
;; pops the get
)
)
(get_local $var$3)
)
)

View File

@ -0,0 +1,40 @@
$stacky-help:
0 const (i32)
1 call (i32)
2 const (i32)
3 call (i32)
4 set_local (none)
5 const (i32)
6 call (i32)
7 drop (none)
8 get_local (i32)
9 unary (i32)
10 binary (i32)
(module
(type $0 (func (param i32) (result i32)))
(export "stacky-help" (func $stacky-help))
(func $stacky-help (; 0 ;) (; has Stack IR ;) (type $0) (param $0 i32) (result i32)
(local $1 i32)
(i32.add
(call $stacky-help
(i32.const 0)
)
(block (result i32)
(set_local $1
(call $stacky-help
(i32.const 1)
)
)
(drop
(call $stacky-help
(i32.const 2)
)
)
(i32.eqz
(get_local $1)
)
)
)
)
)

View File

@ -0,0 +1,16 @@
(module
(export "stacky-help" (func $stacky-help))
(func $stacky-help (param $x i32) (result i32)
(local $temp i32)
(i32.add
(call $stacky-help (i32.const 0))
(i32.eqz
(block (result i32) ;; after we use the stack instead of the local, we can remove this block
(set_local $temp (call $stacky-help (i32.const 1)))
(drop (call $stacky-help (i32.const 2)))
(get_local $temp)
)
)
)
)
)

View File

@ -0,0 +1,38 @@
$stacky-help:
0 const (i32)
1 call (i32)
2 const (i32)
3 call (i32)
4 const (i32)
5 call (i32)
6 drop (none)
7 unary (i32)
8 binary (i32)
(module
(type $0 (func (param i32) (result i32)))
(export "stacky-help" (func $stacky-help))
(func $stacky-help (; 0 ;) (; has Stack IR ;) (type $0) (param $0 i32) (result i32)
(local $1 i32)
(i32.add
(call $stacky-help
(i32.const 0)
)
(block (result i32)
(set_local $1
(call $stacky-help
(i32.const 1)
)
)
(drop
(call $stacky-help
(i32.const 2)
)
)
(i32.eqz
(get_local $1)
)
)
)
)
)

View File

@ -0,0 +1,16 @@
(module
(export "stacky-help" (func $stacky-help))
(func $stacky-help (param $x i32) (result i32)
(local $temp i32)
(i32.add
(call $stacky-help (i32.const 0))
(i32.eqz
(block (result i32) ;; after we use the stack instead of the local, we can remove this block
(set_local $temp (call $stacky-help (i32.const 1)))
(drop (call $stacky-help (i32.const 2)))
(get_local $temp)
)
)
)
)
)

View File

@ -2,7 +2,7 @@
(type $0 (func))
(global $global$0 (mut i32) (i32.const 10))
(export "func_59_invoker" (func $0))
(func $0 (; 0 ;) (type $0)
(func $0 (; 0 ;) (; has Stack IR ;) (type $0)
(set_global $global$0
(i32.const 0)
)

View File

@ -0,0 +1,38 @@
$stacky-help:
0 const (i32)
1 call (i32)
2 const (i32)
3 call (i32)
4 const (i32)
5 call (i32)
6 drop (none)
7 unary (i32)
8 binary (i32)
(module
(type $0 (func (param i32) (result i32)))
(export "stacky-help" (func $stacky-help))
(func $stacky-help (; 0 ;) (; has Stack IR ;) (type $0) (param $0 i32) (result i32)
(local $1 i32)
(i32.add
(call $stacky-help
(i32.const 0)
)
(block (result i32)
(set_local $1
(call $stacky-help
(i32.const 1)
)
)
(drop
(call $stacky-help
(i32.const 2)
)
)
(i32.eqz
(get_local $1)
)
)
)
)
)

View File

@ -0,0 +1,16 @@
(module
(export "stacky-help" (func $stacky-help))
(func $stacky-help (param $x i32) (result i32)
(local $temp i32)
(i32.add
(call $stacky-help (i32.const 0))
(i32.eqz
(block (result i32) ;; after we use the stack instead of the local, we can remove this block
(set_local $temp (call $stacky-help (i32.const 1)))
(drop (call $stacky-help (i32.const 2)))
(get_local $temp)
)
)
)
)
)

View File

@ -4,7 +4,7 @@
(memory $0 100 100)
(export "localcse" (func $basics))
(export "localcse-2" (func $8))
(func $basics (; 0 ;) (type $0) (param $0 i32) (param $1 i32) (result i32)
(func $basics (; 0 ;) (; has Stack IR ;) (type $0) (param $0 i32) (param $1 i32) (result i32)
(i32.add
(i32.add
(get_local $0)
@ -16,7 +16,7 @@
)
)
)
(func $8 (; 1 ;) (type $1) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(func $8 (; 1 ;) (; has Stack IR ;) (type $1) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (result i32)
(i32.store
(tee_local $2
(i32.add

View File

@ -42,13 +42,13 @@ total
(data (i32.const 18764) "`\0b")
(export "_main" (func $_main))
(export "_malloc" (func $_malloc))
(func $b0 (; 1 ;) (type $6) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (param $4 i32) (param $5 i32) (param $6 i32) (result i32)
(func $b0 (; 1 ;) (; has Stack IR ;) (type $6) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (param $4 i32) (param $5 i32) (param $6 i32) (result i32)
(i32.const 0)
)
(func $_malloc (; 2 ;) (type $2) (param $0 i32) (result i32)
(func $_malloc (; 2 ;) (; has Stack IR ;) (type $2) (param $0 i32) (result i32)
(i32.const 0)
)
(func $___stdio_write (; 3 ;) (type $1) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $___stdio_write (; 3 ;) (; has Stack IR ;) (type $1) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(i32.store
(i32.const 8)
(get_local $1)
@ -79,7 +79,7 @@ total
)
(i32.const 1)
)
(func $_main (; 4 ;) (type $7) (result i32)
(func $_main (; 4 ;) (; has Stack IR ;) (type $7) (result i32)
(local $0 i32)
(call $__ZNSt3__224__put_character_sequenceIcNS_11char_traitsIcEEEERNS_13basic_ostreamIT_T0_EES7_PKS4_j
(block (result i32)
@ -109,7 +109,7 @@ total
)
(i32.const 0)
)
(func $___stdout_write (; 5 ;) (type $1) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $___stdout_write (; 5 ;) (; has Stack IR ;) (type $1) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(set_global $global$0
(i32.const 32)
)
@ -119,7 +119,7 @@ total
(get_local $2)
)
)
(func $__ZNSt3__224__put_character_sequenceIcNS_11char_traitsIcEEEERNS_13basic_ostreamIT_T0_EES7_PKS4_j (; 6 ;) (type $3) (param $0 i32)
(func $__ZNSt3__224__put_character_sequenceIcNS_11char_traitsIcEEEERNS_13basic_ostreamIT_T0_EES7_PKS4_j (; 6 ;) (; has Stack IR ;) (type $3) (param $0 i32)
(local $1 i32)
(set_local $1
(i32.load offset=24
@ -157,7 +157,7 @@ total
)
)
)
(func $__ZNSt3__213basic_ostreamIcNS_11char_traitsIcEEE3putEc (; 7 ;) (type $3) (param $0 i32)
(func $__ZNSt3__213basic_ostreamIcNS_11char_traitsIcEEE3putEc (; 7 ;) (; has Stack IR ;) (type $3) (param $0 i32)
(local $1 i32)
(local $2 i32)
(block $label$1
@ -202,7 +202,7 @@ total
)
)
)
(func $__ZNSt3__211__stdoutbufIcE8overflowEi (; 8 ;) (type $0) (param $0 i32) (param $1 i32) (result i32)
(func $__ZNSt3__211__stdoutbufIcE8overflowEi (; 8 ;) (; has Stack IR ;) (type $0) (param $0 i32) (param $1 i32) (result i32)
(i32.store8
(i32.const 0)
(get_local $1)
@ -227,7 +227,7 @@ total
)
(i32.const 0)
)
(func $__ZNSt3__211__stdoutbufIcE6xsputnEPKci (; 9 ;) (type $1) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $__ZNSt3__211__stdoutbufIcE6xsputnEPKci (; 9 ;) (; has Stack IR ;) (type $1) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(drop
(call_indirect (type $1)
(i32.const 0)
@ -290,13 +290,13 @@ total
(data (i32.const 18764) "`\0b")
(export "_main" (func $_main))
(export "_malloc" (func $_malloc))
(func $b0 (; 1 ;) (type $6) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (param $4 i32) (param $5 i32) (param $6 i32) (result i32)
(func $b0 (; 1 ;) (; has Stack IR ;) (type $6) (param $0 i32) (param $1 i32) (param $2 i32) (param $3 i32) (param $4 i32) (param $5 i32) (param $6 i32) (result i32)
(i32.const 0)
)
(func $_malloc (; 2 ;) (type $2) (param $0 i32) (result i32)
(func $_malloc (; 2 ;) (; has Stack IR ;) (type $2) (param $0 i32) (result i32)
(i32.const 0)
)
(func $___stdio_write (; 3 ;) (type $1) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $___stdio_write (; 3 ;) (; has Stack IR ;) (type $1) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(i32.store
(i32.const 8)
(get_local $1)
@ -327,7 +327,7 @@ total
)
(i32.const 1)
)
(func $_main (; 4 ;) (type $7) (result i32)
(func $_main (; 4 ;) (; has Stack IR ;) (type $7) (result i32)
(local $0 i32)
(call $__ZNSt3__224__put_character_sequenceIcNS_11char_traitsIcEEEERNS_13basic_ostreamIT_T0_EES7_PKS4_j
(block (result i32)
@ -357,7 +357,7 @@ total
)
(i32.const 0)
)
(func $___stdout_write (; 5 ;) (type $1) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $___stdout_write (; 5 ;) (; has Stack IR ;) (type $1) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(set_global $global$0
(i32.const 32)
)
@ -367,7 +367,7 @@ total
(get_local $2)
)
)
(func $__ZNSt3__224__put_character_sequenceIcNS_11char_traitsIcEEEERNS_13basic_ostreamIT_T0_EES7_PKS4_j (; 6 ;) (type $3) (param $0 i32)
(func $__ZNSt3__224__put_character_sequenceIcNS_11char_traitsIcEEEERNS_13basic_ostreamIT_T0_EES7_PKS4_j (; 6 ;) (; has Stack IR ;) (type $3) (param $0 i32)
(local $1 i32)
(set_local $1
(i32.load offset=24
@ -405,7 +405,7 @@ total
)
)
)
(func $__ZNSt3__213basic_ostreamIcNS_11char_traitsIcEEE3putEc (; 7 ;) (type $3) (param $0 i32)
(func $__ZNSt3__213basic_ostreamIcNS_11char_traitsIcEEE3putEc (; 7 ;) (; has Stack IR ;) (type $3) (param $0 i32)
(local $1 i32)
(local $2 i32)
(block $label$1
@ -450,7 +450,7 @@ total
)
)
)
(func $__ZNSt3__211__stdoutbufIcE8overflowEi (; 8 ;) (type $0) (param $0 i32) (param $1 i32) (result i32)
(func $__ZNSt3__211__stdoutbufIcE8overflowEi (; 8 ;) (; has Stack IR ;) (type $0) (param $0 i32) (param $1 i32) (result i32)
(i32.store8
(i32.const 0)
(get_local $1)
@ -475,7 +475,7 @@ total
)
(i32.const 0)
)
(func $__ZNSt3__211__stdoutbufIcE6xsputnEPKci (; 9 ;) (type $1) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(func $__ZNSt3__211__stdoutbufIcE6xsputnEPKci (; 9 ;) (; has Stack IR ;) (type $1) (param $0 i32) (param $1 i32) (param $2 i32) (result i32)
(drop
(call_indirect (type $1)
(i32.const 0)

Some files were not shown because too many files have changed in this diff Show More