Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data WasmControl :: Type -> Type -> [WasmType] -> [WasmType] -> Type where
- WasmPush :: WasmTypeTag t -> e -> WasmControl s e stack (t : stack)
- WasmBlock :: WasmFunctionType pre post -> WasmControl s e pre post -> WasmControl s e pre post
- WasmLoop :: WasmFunctionType pre post -> WasmControl s e pre post -> WasmControl s e pre post
- WasmIfTop :: WasmFunctionType pre post -> WasmControl s e pre post -> WasmControl s e pre post -> WasmControl s e ('I32 : pre) post
- WasmBr :: Int -> WasmControl s e dropped destination
- WasmFallthrough :: WasmControl s e dropped destination
- WasmBrTable :: e -> BrTableInterval -> [Int] -> Int -> WasmControl s e dropped destination
- WasmTailCall :: e -> WasmControl s e t1star t2star
- WasmActions :: s -> WasmControl s e stack stack
- WasmSeq :: WasmControl s e pre mid -> WasmControl s e mid post -> WasmControl s e pre post
- (<>) :: forall s e pre mid post. WasmControl s e pre mid -> WasmControl s e mid post -> WasmControl s e pre post
- pattern WasmIf :: WasmFunctionType pre post -> e -> WasmControl s e pre post -> WasmControl s e pre post -> WasmControl s e pre post
- data BrTableInterval = BrTableInterval {}
- inclusiveInterval :: Integer -> Integer -> BrTableInterval
- data WasmType
- data WasmTypeTag :: WasmType -> Type where
- TagI32 :: WasmTypeTag 'I32
- TagI64 :: WasmTypeTag 'I64
- TagF32 :: WasmTypeTag 'F32
- TagF64 :: WasmTypeTag 'F64
- data TypeList :: [WasmType] -> Type where
- TypeListNil :: TypeList '[]
- TypeListCons :: WasmTypeTag t -> TypeList ts -> TypeList (t : ts)
- data WasmFunctionType pre post = WasmFunctionType {}
Documentation
data WasmControl :: Type -> Type -> [WasmType] -> [WasmType] -> Type where Source #
Representation of WebAssembly control flow.
Normally written as
WasmControl s e pre post
Type parameter s
is the type of (unspecified) statements.
It might be instantiated with an open Cmm block or with a sequence
of Wasm instructions.
Parameter e
is the type of expressions.
Parameter pre
represents the values that are expected on the
WebAssembly stack when the code runs, and post
represents
the state of the stack on completion.
WasmPush :: WasmTypeTag t -> e -> WasmControl s e stack (t : stack) | |
WasmBlock :: WasmFunctionType pre post -> WasmControl s e pre post -> WasmControl s e pre post | |
WasmLoop :: WasmFunctionType pre post -> WasmControl s e pre post -> WasmControl s e pre post | |
WasmIfTop :: WasmFunctionType pre post -> WasmControl s e pre post -> WasmControl s e pre post -> WasmControl s e ('I32 : pre) post | |
WasmBr :: Int -> WasmControl s e dropped destination | |
WasmFallthrough :: WasmControl s e dropped destination | |
WasmBrTable :: e -> BrTableInterval -> [Int] -> Int -> WasmControl s e dropped destination | |
WasmTailCall :: e -> WasmControl s e t1star t2star | |
WasmActions :: s -> WasmControl s e stack stack | |
WasmSeq :: WasmControl s e pre mid -> WasmControl s e mid post -> WasmControl s e pre post |
(<>) :: forall s e pre mid post. WasmControl s e pre mid -> WasmControl s e mid post -> WasmControl s e pre post Source #
pattern WasmIf :: WasmFunctionType pre post -> e -> WasmControl s e pre post -> WasmControl s e pre post -> WasmControl s e pre post Source #
data BrTableInterval Source #
Instances
Show BrTableInterval Source # | |
Defined in GHC.CmmToAsm.Wasm.Types | |
Outputable BrTableInterval Source # | |
Defined in GHC.CmmToAsm.Wasm.Types ppr :: BrTableInterval -> SDoc Source # |
inclusiveInterval :: Integer -> Integer -> BrTableInterval Source #
Module : GHC.Wasm.ControlFlow Description : Representation of control-flow portion of the WebAssembly instruction set
WebAssembly type of a WebAssembly value that WebAssembly code could either expect on the evaluation stack or leave on the evaluation stack.
Instances
TestEquality WasmTypeTag Source # | |
Defined in GHC.CmmToAsm.Wasm.Types testEquality :: forall (a :: k) (b :: k). WasmTypeTag a -> WasmTypeTag b -> Maybe (a :~: b) Source # |
data WasmTypeTag :: WasmType -> Type where Source #
Singleton type useful for programming with WasmType
at the type
level.
TagI32 :: WasmTypeTag 'I32 | |
TagI64 :: WasmTypeTag 'I64 | |
TagF32 :: WasmTypeTag 'F32 | |
TagF64 :: WasmTypeTag 'F64 |
Instances
TestEquality WasmTypeTag Source # | |
Defined in GHC.CmmToAsm.Wasm.Types testEquality :: forall (a :: k) (b :: k). WasmTypeTag a -> WasmTypeTag b -> Maybe (a :~: b) Source # | |
Show (WasmTypeTag t) Source # | |
Defined in GHC.CmmToAsm.Wasm.Types |
data TypeList :: [WasmType] -> Type where Source #
List of WebAssembly types used to describe the sequence of WebAssembly values that a block of code may expect on the stack or leave on the stack.
TypeListNil :: TypeList '[] | |
TypeListCons :: WasmTypeTag t -> TypeList ts -> TypeList (t : ts) |
data WasmFunctionType pre post Source #
The type of a WebAssembly function, loop, block, or conditional. This type says what values the code expects to pop off the stack and what values it promises to push. The WebAssembly standard requires that this type appear explicitly in the code.