wasm-1.1.1: WebAssembly Language Toolkit and Interpreter
Safe HaskellSafe-Inferred
LanguageHaskell2010

Language.Wasm.Builder

Documentation

type GenMod = State GenModState Source #

global :: ValueTypeable t => (ValueType -> GlobalType) -> Proxy t -> ValType t -> GenMod (Glob t) Source #

typedef :: Returnable res => res -> [ValueType] -> GenMod (TypeDef res) Source #

fun :: Returnable res => res -> GenFun res -> GenMod (Fn res) Source #

funRec :: Returnable res => res -> (Fn res -> GenFun res) -> GenMod (Fn res) Source #

declare :: Returnable res => res -> [ValueType] -> GenMod (Fn res) Source #

implement :: Returnable res => Fn res -> GenFun res -> GenMod (Fn res) Source #

dataSegment :: (Producer offset, OutType offset ~ Proxy I32) => offset -> ByteString -> GenMod () Source #

importFunction :: Returnable res => Text -> Text -> res -> [ValueType] -> GenMod (Fn res) Source #

importGlobal :: ValueTypeable t => Text -> Text -> Proxy t -> GenMod (Glob t) Source #

export :: Exportable e => Text -> e -> GenMod (AfterExport e) Source #

setGlobalInitializer :: forall t. ValueTypeable t => Glob t -> ValType t -> GenMod () Source #

type GenFun = ReaderT Natural (State FuncDef) Source #

data Glob t Source #

Instances

Instances details
Eq (Glob t) Source # 
Instance details

Defined in Language.Wasm.Builder

Methods

(==) :: Glob t -> Glob t -> Bool #

(/=) :: Glob t -> Glob t -> Bool #

Show (Glob t) Source # 
Instance details

Defined in Language.Wasm.Builder

Methods

showsPrec :: Int -> Glob t -> ShowS #

show :: Glob t -> String #

showList :: [Glob t] -> ShowS #

Consumer (Glob t) Source # 
Instance details

Defined in Language.Wasm.Builder

Methods

(.=) :: Producer expr => Glob t -> expr -> GenFun () Source #

ValueTypeable t => Producer (Glob t) Source # 
Instance details

Defined in Language.Wasm.Builder

Associated Types

type OutType (Glob t) Source #

Methods

asTypedExpr :: Glob t -> TypedExpr

asValueType :: Glob t -> ValueType

produce :: Glob t -> GenFun (OutType (Glob t)) Source #

type OutType (Glob t) Source # 
Instance details

Defined in Language.Wasm.Builder

type OutType (Glob t) = Proxy t

data Loc t Source #

Instances

Instances details
Eq (Loc t) Source # 
Instance details

Defined in Language.Wasm.Builder

Methods

(==) :: Loc t -> Loc t -> Bool #

(/=) :: Loc t -> Loc t -> Bool #

Show (Loc t) Source # 
Instance details

Defined in Language.Wasm.Builder

Methods

showsPrec :: Int -> Loc t -> ShowS #

show :: Loc t -> String #

showList :: [Loc t] -> ShowS #

Consumer (Loc t) Source # 
Instance details

Defined in Language.Wasm.Builder

Methods

(.=) :: Producer expr => Loc t -> expr -> GenFun () Source #

ValueTypeable t => Producer (Loc t) Source # 
Instance details

Defined in Language.Wasm.Builder

Associated Types

type OutType (Loc t) Source #

Methods

asTypedExpr :: Loc t -> TypedExpr

asValueType :: Loc t -> ValueType

produce :: Loc t -> GenFun (OutType (Loc t)) Source #

type OutType (Loc t) Source # 
Instance details

Defined in Language.Wasm.Builder

type OutType (Loc t) = Proxy t

newtype Fn a Source #

Constructors

Fn Natural 

Instances

Instances details
Eq (Fn a) Source # 
Instance details

Defined in Language.Wasm.Builder

Methods

(==) :: Fn a -> Fn a -> Bool #

(/=) :: Fn a -> Fn a -> Bool #

Show (Fn a) Source # 
Instance details

Defined in Language.Wasm.Builder

Methods

showsPrec :: Int -> Fn a -> ShowS #

show :: Fn a -> String #

showList :: [Fn a] -> ShowS #

data Mem Source #

Instances

Instances details
Eq Mem Source # 
Instance details

Defined in Language.Wasm.Builder

Methods

(==) :: Mem -> Mem -> Bool #

(/=) :: Mem -> Mem -> Bool #

Show Mem Source # 
Instance details

Defined in Language.Wasm.Builder

Methods

showsPrec :: Int -> Mem -> ShowS #

show :: Mem -> String #

showList :: [Mem] -> ShowS #

data Tbl Source #

Instances

Instances details
Eq Tbl Source # 
Instance details

Defined in Language.Wasm.Builder

Methods

(==) :: Tbl -> Tbl -> Bool #

(/=) :: Tbl -> Tbl -> Bool #

Show Tbl Source # 
Instance details

Defined in Language.Wasm.Builder

Methods

showsPrec :: Int -> Tbl -> ShowS #

show :: Tbl -> String #

showList :: [Tbl] -> ShowS #

data Label i Source #

Instances

Instances details
Eq (Label i) Source # 
Instance details

Defined in Language.Wasm.Builder

Methods

(==) :: Label i -> Label i -> Bool #

(/=) :: Label i -> Label i -> Bool #

Show (Label i) Source # 
Instance details

Defined in Language.Wasm.Builder

Methods

showsPrec :: Int -> Label i -> ShowS #

show :: Label i -> String #

showList :: [Label i] -> ShowS #

param :: ValueTypeable t => Proxy t -> GenFun (Loc t) Source #

local :: ValueTypeable t => Proxy t -> GenFun (Loc t) Source #

ret :: Producer expr => expr -> GenFun (OutType expr) Source #

arg :: Producer expr => expr -> GenFun () Source #

add :: (Producer a, Producer b, OutType a ~ OutType b) => a -> b -> GenFun (OutType a) Source #

inc :: (Consumer a, Producer a, Integral i) => i -> a -> GenFun () Source #

sub :: (Producer a, Producer b, OutType a ~ OutType b) => a -> b -> GenFun (OutType a) Source #

dec :: (Consumer a, Producer a, Integral i) => i -> a -> GenFun () Source #

mul :: (Producer a, Producer b, OutType a ~ OutType b) => a -> b -> GenFun (OutType a) Source #

div_u :: (Producer a, Producer b, OutType a ~ OutType b, IsInt (OutType a) ~ True) => a -> b -> GenFun (OutType a) Source #

div_s :: (Producer a, Producer b, OutType a ~ OutType b, IsInt (OutType a) ~ True) => a -> b -> GenFun (OutType a) Source #

rem_u :: (Producer a, Producer b, OutType a ~ OutType b, IsInt (OutType a) ~ True) => a -> b -> GenFun (OutType a) Source #

rem_s :: (Producer a, Producer b, OutType a ~ OutType b, IsInt (OutType a) ~ True) => a -> b -> GenFun (OutType a) Source #

and :: (Producer a, Producer b, OutType a ~ OutType b, IsInt (OutType a) ~ True) => a -> b -> GenFun (OutType a) Source #

or :: (Producer a, Producer b, OutType a ~ OutType b, IsInt (OutType a) ~ True) => a -> b -> GenFun (OutType a) Source #

xor :: (Producer a, Producer b, OutType a ~ OutType b, IsInt (OutType a) ~ True) => a -> b -> GenFun (OutType a) Source #

shl :: (Producer a, Producer b, OutType a ~ OutType b, IsInt (OutType a) ~ True) => a -> b -> GenFun (OutType a) Source #

shr_u :: (Producer a, Producer b, OutType a ~ OutType b, IsInt (OutType a) ~ True) => a -> b -> GenFun (OutType a) Source #

shr_s :: (Producer a, Producer b, OutType a ~ OutType b, IsInt (OutType a) ~ True) => a -> b -> GenFun (OutType a) Source #

rotl :: (Producer a, Producer b, OutType a ~ OutType b, IsInt (OutType a) ~ True) => a -> b -> GenFun (OutType a) Source #

rotr :: (Producer a, Producer b, OutType a ~ OutType b, IsInt (OutType a) ~ True) => a -> b -> GenFun (OutType a) Source #

clz :: (Producer a, IsInt (OutType a) ~ True) => a -> GenFun (OutType a) Source #

ctz :: (Producer a, IsInt (OutType a) ~ True) => a -> GenFun (OutType a) Source #

popcnt :: (Producer a, IsInt (OutType a) ~ True) => a -> GenFun (OutType a) Source #

eq :: (Producer a, Producer b, OutType a ~ OutType b) => a -> b -> GenFun (Proxy I32) Source #

ne :: (Producer a, Producer b, OutType a ~ OutType b) => a -> b -> GenFun (Proxy I32) Source #

lt_s :: (Producer a, Producer b, OutType a ~ OutType b, IsInt (OutType a) ~ True) => a -> b -> GenFun (Proxy I32) Source #

lt_u :: (Producer a, Producer b, OutType a ~ OutType b, IsInt (OutType a) ~ True) => a -> b -> GenFun (Proxy I32) Source #

gt_s :: (Producer a, Producer b, OutType a ~ OutType b, IsInt (OutType a) ~ True) => a -> b -> GenFun (Proxy I32) Source #

gt_u :: (Producer a, Producer b, OutType a ~ OutType b, IsInt (OutType a) ~ True) => a -> b -> GenFun (Proxy I32) Source #

le_s :: (Producer a, Producer b, OutType a ~ OutType b, IsInt (OutType a) ~ True) => a -> b -> GenFun (Proxy I32) Source #

le_u :: (Producer a, Producer b, OutType a ~ OutType b, IsInt (OutType a) ~ True) => a -> b -> GenFun (Proxy I32) Source #

ge_s :: (Producer a, Producer b, OutType a ~ OutType b, IsInt (OutType a) ~ True) => a -> b -> GenFun (Proxy I32) Source #

ge_u :: (Producer a, Producer b, OutType a ~ OutType b, IsInt (OutType a) ~ True) => a -> b -> GenFun (Proxy I32) Source #

eqz :: (Producer a, IsInt (OutType a) ~ True) => a -> GenFun (Proxy I32) Source #

div_f :: (Producer a, Producer b, OutType a ~ OutType b, IsFloat (OutType a) ~ True) => a -> b -> GenFun (OutType a) Source #

min_f :: (Producer a, Producer b, OutType a ~ OutType b, IsFloat (OutType a) ~ True) => a -> b -> GenFun (OutType a) Source #

max_f :: (Producer a, Producer b, OutType a ~ OutType b, IsFloat (OutType a) ~ True) => a -> b -> GenFun (OutType a) Source #

copySign :: (Producer a, Producer b, OutType a ~ OutType b, IsFloat (OutType a) ~ True) => a -> b -> GenFun (OutType a) Source #

abs_f :: (Producer a, IsFloat (OutType a) ~ True) => a -> GenFun (OutType a) Source #

neg_f :: (Producer a, IsFloat (OutType a) ~ True) => a -> GenFun (OutType a) Source #

ceil_f :: (Producer a, IsFloat (OutType a) ~ True) => a -> GenFun (OutType a) Source #

floor_f :: (Producer a, IsFloat (OutType a) ~ True) => a -> GenFun (OutType a) Source #

trunc_f :: (Producer a, IsFloat (OutType a) ~ True) => a -> GenFun (OutType a) Source #

nearest_f :: (Producer a, IsFloat (OutType a) ~ True) => a -> GenFun (OutType a) Source #

sqrt_f :: (Producer a, IsFloat (OutType a) ~ True) => a -> GenFun (OutType a) Source #

lt_f :: (Producer a, Producer b, OutType a ~ OutType b, IsFloat (OutType a) ~ True) => a -> b -> GenFun (Proxy I32) Source #

gt_f :: (Producer a, Producer b, OutType a ~ OutType b, IsFloat (OutType a) ~ True) => a -> b -> GenFun (Proxy I32) Source #

le_f :: (Producer a, Producer b, OutType a ~ OutType b, IsFloat (OutType a) ~ True) => a -> b -> GenFun (Proxy I32) Source #

ge_f :: (Producer a, Producer b, OutType a ~ OutType b, IsFloat (OutType a) ~ True) => a -> b -> GenFun (Proxy I32) Source #

trunc_s :: (Producer f, IsFloat (OutType f) ~ True, IsInt (Proxy t) ~ True, ValueTypeable t) => Proxy t -> f -> GenFun (Proxy t) Source #

trunc_u :: (Producer f, IsFloat (OutType f) ~ True, IsInt (Proxy t) ~ True, ValueTypeable t) => Proxy t -> f -> GenFun (Proxy t) Source #

convert_s :: (Producer i, IsInt (OutType i) ~ True, IsFloat (Proxy t) ~ True, ValueTypeable t) => Proxy t -> i -> GenFun (Proxy t) Source #

convert_u :: (Producer i, IsInt (OutType i) ~ True, IsFloat (Proxy t) ~ True, ValueTypeable t) => Proxy t -> i -> GenFun (Proxy t) Source #

reinterpret :: (ValueTypeable t, Producer val, SameSize (Proxy t) (OutType val) ~ True) => Proxy t -> val -> GenFun (Proxy t) Source #

load :: (ValueTypeable t, Producer addr, OutType addr ~ Proxy I32, Integral offset, Integral align) => Proxy t -> addr -> offset -> align -> GenFun (Proxy t) Source #

load8_u :: (ValueTypeable t, IsInt (Proxy t) ~ True, Producer addr, OutType addr ~ Proxy I32, Integral offset, Integral align) => Proxy t -> addr -> offset -> align -> GenFun (Proxy t) Source #

load8_s :: (ValueTypeable t, IsInt (Proxy t) ~ True, Producer addr, OutType addr ~ Proxy I32, Integral offset, Integral align) => Proxy t -> addr -> offset -> align -> GenFun (Proxy t) Source #

load16_u :: (ValueTypeable t, IsInt (Proxy t) ~ True, Producer addr, OutType addr ~ Proxy I32, Integral offset, Integral align) => Proxy t -> addr -> offset -> align -> GenFun (Proxy t) Source #

load16_s :: (ValueTypeable t, IsInt (Proxy t) ~ True, Producer addr, OutType addr ~ Proxy I32, Integral offset, Integral align) => Proxy t -> addr -> offset -> align -> GenFun (Proxy t) Source #

load32_u :: (ValueTypeable t, IsInt (Proxy t) ~ True, Producer addr, OutType addr ~ Proxy I32, Integral offset, Integral align) => Proxy t -> addr -> offset -> align -> GenFun (Proxy t) Source #

load32_s :: (ValueTypeable t, IsInt (Proxy t) ~ True, Producer addr, OutType addr ~ Proxy I32, Integral offset, Integral align) => Proxy t -> addr -> offset -> align -> GenFun (Proxy t) Source #

store :: (Producer addr, OutType addr ~ Proxy I32, Producer val, Integral offset, Integral align) => addr -> val -> offset -> align -> GenFun () Source #

store8 :: (Producer addr, OutType addr ~ Proxy I32, Producer val, IsInt (OutType val) ~ True, Integral offset, Integral align) => addr -> val -> offset -> align -> GenFun () Source #

store16 :: (Producer addr, OutType addr ~ Proxy I32, Producer val, IsInt (OutType val) ~ True, Integral offset, Integral align) => addr -> val -> offset -> align -> GenFun () Source #

store32 :: (Producer addr, OutType addr ~ Proxy I32, Producer val, OutType val ~ Proxy I64, Integral offset, Integral align) => addr -> val -> offset -> align -> GenFun () Source #

growMemory :: (Producer size, OutType size ~ Proxy I32) => size -> GenFun () Source #

drop :: Producer val => val -> GenFun () Source #

select :: (Producer a, Producer b, OutType a ~ OutType b, Producer pred, OutType pred ~ Proxy I32) => pred -> a -> b -> GenFun (OutType a) Source #

call :: Returnable res => Fn res -> [GenFun a] -> GenFun res Source #

callIndirect :: (Producer index, OutType index ~ Proxy I32, Returnable res) => TypeDef res -> index -> [GenFun a] -> GenFun res Source #

finish :: Producer val => val -> GenFun () Source #

br :: Label t -> GenFun () Source #

brIf :: (Producer pred, OutType pred ~ Proxy I32) => pred -> Label t -> GenFun () Source #

brTable :: (Producer selector, OutType selector ~ Proxy I32) => selector -> [Label t] -> Label t -> GenFun () Source #

class Producer expr Source #

Minimal complete definition

asTypedExpr, asValueType, produce

Instances

Instances details
ValueTypeable t => Producer (GenFun (Proxy t)) Source # 
Instance details

Defined in Language.Wasm.Builder

Associated Types

type OutType (GenFun (Proxy t)) Source #

Methods

asTypedExpr :: GenFun (Proxy t) -> TypedExpr

asValueType :: GenFun (Proxy t) -> ValueType

produce :: GenFun (Proxy t) -> GenFun (OutType (GenFun (Proxy t))) Source #

ValueTypeable t => Producer (Glob t) Source # 
Instance details

Defined in Language.Wasm.Builder

Associated Types

type OutType (Glob t) Source #

Methods

asTypedExpr :: Glob t -> TypedExpr

asValueType :: Glob t -> ValueType

produce :: Glob t -> GenFun (OutType (Glob t)) Source #

ValueTypeable t => Producer (Loc t) Source # 
Instance details

Defined in Language.Wasm.Builder

Associated Types

type OutType (Loc t) Source #

Methods

asTypedExpr :: Loc t -> TypedExpr

asValueType :: Loc t -> ValueType

produce :: Loc t -> GenFun (OutType (Loc t)) Source #

type family OutType expr Source #

Instances

Instances details
type OutType (GenFun (Proxy t)) Source # 
Instance details

Defined in Language.Wasm.Builder

type OutType (GenFun (Proxy t)) = Proxy t
type OutType (Glob t) Source # 
Instance details

Defined in Language.Wasm.Builder

type OutType (Glob t) = Proxy t
type OutType (Loc t) Source # 
Instance details

Defined in Language.Wasm.Builder

type OutType (Loc t) = Proxy t

produce :: Producer expr => expr -> GenFun (OutType expr) Source #

class Consumer loc Source #

Minimal complete definition

(.=)

Instances

Instances details
Consumer (Glob t) Source # 
Instance details

Defined in Language.Wasm.Builder

Methods

(.=) :: Producer expr => Glob t -> expr -> GenFun () Source #

Consumer (Loc t) Source # 
Instance details

Defined in Language.Wasm.Builder

Methods

(.=) :: Producer expr => Loc t -> expr -> GenFun () Source #

(.=) :: (Consumer loc, Producer expr) => loc -> expr -> GenFun () infixr 2 Source #