ghc-9.8.2: The GHC API
Safe HaskellNone
LanguageHaskell2010

GHC.Wasm.ControlFlow

Synopsis

Documentation

data WasmControl a b (c :: [WasmType]) (d :: [WasmType]) 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.

Constructors

WasmPush :: forall (t :: WasmType) b a (c :: [WasmType]). WasmTypeTag t -> b -> WasmControl a b c (t ': c) 
WasmBlock :: forall (c :: [WasmType]) (d :: [WasmType]) a b. WasmFunctionType c d -> WasmControl a b c d -> WasmControl a b c d 
WasmLoop :: forall (c :: [WasmType]) (d :: [WasmType]) a b. WasmFunctionType c d -> WasmControl a b c d -> WasmControl a b c d 
WasmIfTop :: forall (pre :: [WasmType]) (d :: [WasmType]) a b. WasmFunctionType pre d -> WasmControl a b pre d -> WasmControl a b pre d -> WasmControl a b ('I32 ': pre) d 
WasmBr :: forall a b (c :: [WasmType]) (d :: [WasmType]). Int -> WasmControl a b c d 
WasmFallthrough :: forall a b (c :: [WasmType]) (d :: [WasmType]). WasmControl a b c d 
WasmBrTable :: forall b a (c :: [WasmType]) (d :: [WasmType]). b -> BrTableInterval -> [Int] -> Int -> WasmControl a b c d 
WasmTailCall :: forall b a (c :: [WasmType]) (d :: [WasmType]). b -> WasmControl a b c d 
WasmActions :: forall a b (c :: [WasmType]). a -> WasmControl a b c c 
WasmSeq :: forall a b (c :: [WasmType]) (mid :: [WasmType]) (d :: [WasmType]). WasmControl a b c mid -> WasmControl a b mid d -> WasmControl a b c d 

(<>) :: forall s e (pre :: [WasmType]) (mid :: [WasmType]) (post :: [WasmType]). 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 #

inclusiveInterval :: Integer -> Integer -> BrTableInterval Source #

Module : GHC.Wasm.ControlFlow Description : Representation of control-flow portion of the WebAssembly instruction set

data WasmType Source #

WebAssembly type of a WebAssembly value that WebAssembly code could either expect on the evaluation stack or leave on the evaluation stack.

Instances

Instances details
TestEquality WasmTypeTag Source # 
Instance details

Defined in GHC.CmmToAsm.Wasm.Types

Methods

testEquality :: forall (a :: WasmType) (b :: WasmType). WasmTypeTag a -> WasmTypeTag b -> Maybe (a :~: b) Source #

data WasmTypeTag (a :: WasmType) where Source #

Singleton type useful for programming with WasmType at the type level.

Instances

Instances details
TestEquality WasmTypeTag Source # 
Instance details

Defined in GHC.CmmToAsm.Wasm.Types

Methods

testEquality :: forall (a :: WasmType) (b :: WasmType). WasmTypeTag a -> WasmTypeTag b -> Maybe (a :~: b) Source #

Show (WasmTypeTag t) Source # 
Instance details

Defined in GHC.CmmToAsm.Wasm.Types

data TypeList (a :: [WasmType]) 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.

Constructors

TypeListNil :: TypeList ('[] :: [WasmType]) 
TypeListCons :: forall (t :: WasmType) (ts :: [WasmType]). WasmTypeTag t -> TypeList ts -> TypeList (t ': ts) 

data WasmFunctionType (pre :: [WasmType]) (post :: [WasmType]) 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.

Constructors

WasmFunctionType 

Fields