Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Documentation
Instances
data DataSegment Source #
Instances
data ElemSegment Source #
ElemSegment | |
|
Instances
data StartFunction Source #
Instances
Eq StartFunction Source # | |
Defined in Language.Wasm.Structure (==) :: StartFunction -> StartFunction -> Bool # (/=) :: StartFunction -> StartFunction -> Bool # | |
Show StartFunction Source # | |
Defined in Language.Wasm.Structure showsPrec :: Int -> StartFunction -> ShowS # show :: StartFunction -> String # showList :: [StartFunction] -> ShowS # | |
Generic StartFunction Source # | |
Defined in Language.Wasm.Structure type Rep StartFunction :: Type -> Type # from :: StartFunction -> Rep StartFunction x # to :: Rep StartFunction x -> StartFunction # | |
NFData StartFunction Source # | |
Defined in Language.Wasm.Structure rnf :: StartFunction -> () # | |
type Rep StartFunction Source # | |
Defined in Language.Wasm.Structure type Rep StartFunction = D1 ('MetaData "StartFunction" "Language.Wasm.Structure" "wasm-1.1.1-DXxNcY7mvYrKAXJfL54aUD" 'False) (C1 ('MetaCons "StartFunction" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FuncIndex))) |
Export | |
|
Instances
Eq Export Source # | |
Show Export Source # | |
Generic Export Source # | |
Serialize Export Source # | |
NFData Export Source # | |
Defined in Language.Wasm.Structure | |
type Rep Export Source # | |
Defined in Language.Wasm.Structure type Rep Export = D1 ('MetaData "Export" "Language.Wasm.Structure" "wasm-1.1.1-DXxNcY7mvYrKAXJfL54aUD" 'False) (C1 ('MetaCons "Export" 'PrefixI 'True) (S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "desc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ExportDesc))) |
data ExportDesc Source #
Instances
Instances
Eq Global Source # | |
Show Global Source # | |
Generic Global Source # | |
Serialize Global Source # | |
NFData Global Source # | |
Defined in Language.Wasm.Structure | |
type Rep Global Source # | |
Defined in Language.Wasm.Structure type Rep Global = D1 ('MetaData "Global" "Language.Wasm.Structure" "wasm-1.1.1-DXxNcY7mvYrKAXJfL54aUD" 'False) (C1 ('MetaCons "Global" 'PrefixI 'True) (S1 ('MetaSel ('Just "globalType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GlobalType) :*: S1 ('MetaSel ('Just "initializer") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Expression))) |
Function | |
|
Instances
Eq Function Source # | |
Show Function Source # | |
Generic Function Source # | |
Serialize Function Source # | |
NFData Function Source # | |
Defined in Language.Wasm.Structure | |
type Rep Function Source # | |
Defined in Language.Wasm.Structure type Rep Function = D1 ('MetaData "Function" "Language.Wasm.Structure" "wasm-1.1.1-DXxNcY7mvYrKAXJfL54aUD" 'False) (C1 ('MetaCons "Function" 'PrefixI 'True) (S1 ('MetaSel ('Just "funcType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TypeIndex) :*: (S1 ('MetaSel ('Just "localTypes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LocalsType) :*: S1 ('MetaSel ('Just "body") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Expression)))) |
Import | |
|
Instances
Eq Import Source # | |
Show Import Source # | |
Generic Import Source # | |
Serialize Import Source # | |
NFData Import Source # | |
Defined in Language.Wasm.Structure | |
type Rep Import Source # | |
Defined in Language.Wasm.Structure type Rep Import = D1 ('MetaData "Import" "Language.Wasm.Structure" "wasm-1.1.1-DXxNcY7mvYrKAXJfL54aUD" 'False) (C1 ('MetaCons "Import" 'PrefixI 'True) (S1 ('MetaSel ('Just "sourceModule") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "desc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ImportDesc)))) |
data ImportDesc Source #
Instances
data Instruction index Source #
Instances
Instances
Eq MemArg Source # | |
Show MemArg Source # | |
Generic MemArg Source # | |
Serialize MemArg Source # | |
NFData MemArg Source # | |
Defined in Language.Wasm.Structure | |
type Rep MemArg Source # | |
Defined in Language.Wasm.Structure type Rep MemArg = D1 ('MetaData "MemArg" "Language.Wasm.Structure" "wasm-1.1.1-DXxNcY7mvYrKAXJfL54aUD" 'False) (C1 ('MetaCons "MemArg" 'PrefixI 'True) (S1 ('MetaSel ('Just "offset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural) :*: S1 ('MetaSel ('Just "align") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural))) |
Instances
Eq IUnOp Source # | |
Show IUnOp Source # | |
Generic IUnOp Source # | |
NFData IUnOp Source # | |
Defined in Language.Wasm.Structure | |
type Rep IUnOp Source # | |
Defined in Language.Wasm.Structure type Rep IUnOp = D1 ('MetaData "IUnOp" "Language.Wasm.Structure" "wasm-1.1.1-DXxNcY7mvYrKAXJfL54aUD" 'False) ((C1 ('MetaCons "IClz" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ICtz" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IPopcnt" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "IExtend8S" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "IExtend16S" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IExtend32S" 'PrefixI 'False) (U1 :: Type -> Type)))) |
Instances
Instances
Eq IRelOp Source # | |
Show IRelOp Source # | |
Generic IRelOp Source # | |
NFData IRelOp Source # | |
Defined in Language.Wasm.Structure | |
type Rep IRelOp Source # | |
Defined in Language.Wasm.Structure type Rep IRelOp = D1 ('MetaData "IRelOp" "Language.Wasm.Structure" "wasm-1.1.1-DXxNcY7mvYrKAXJfL54aUD" 'False) (((C1 ('MetaCons "IEq" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "INe" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ILtU" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ILtS" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IGtU" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "IGtS" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ILeU" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ILeS" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "IGeU" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IGeS" 'PrefixI 'False) (U1 :: Type -> Type))))) |
Instances
Eq FUnOp Source # | |
Show FUnOp Source # | |
Generic FUnOp Source # | |
NFData FUnOp Source # | |
Defined in Language.Wasm.Structure | |
type Rep FUnOp Source # | |
Defined in Language.Wasm.Structure type Rep FUnOp = D1 ('MetaData "FUnOp" "Language.Wasm.Structure" "wasm-1.1.1-DXxNcY7mvYrKAXJfL54aUD" 'False) ((C1 ('MetaCons "FAbs" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "FNeg" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FCeil" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "FFloor" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FTrunc" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "FNearest" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FSqrt" 'PrefixI 'False) (U1 :: Type -> Type)))) |
Instances
Eq FBinOp Source # | |
Show FBinOp Source # | |
Generic FBinOp Source # | |
NFData FBinOp Source # | |
Defined in Language.Wasm.Structure | |
type Rep FBinOp Source # | |
Defined in Language.Wasm.Structure type Rep FBinOp = D1 ('MetaData "FBinOp" "Language.Wasm.Structure" "wasm-1.1.1-DXxNcY7mvYrKAXJfL54aUD" 'False) ((C1 ('MetaCons "FAdd" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "FSub" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FMul" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "FDiv" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FMin" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "FMax" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FCopySign" 'PrefixI 'False) (U1 :: Type -> Type)))) |
Instances
Eq FRelOp Source # | |
Show FRelOp Source # | |
Generic FRelOp Source # | |
NFData FRelOp Source # | |
Defined in Language.Wasm.Structure | |
type Rep FRelOp Source # | |
Defined in Language.Wasm.Structure type Rep FRelOp = D1 ('MetaData "FRelOp" "Language.Wasm.Structure" "wasm-1.1.1-DXxNcY7mvYrKAXJfL54aUD" 'False) ((C1 ('MetaCons "FEq" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "FNe" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FLt" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "FGt" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "FLe" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FGe" 'PrefixI 'False) (U1 :: Type -> Type)))) |
Instances
Eq TableType Source # | |
Show TableType Source # | |
Generic TableType Source # | |
Serialize TableType Source # | |
NFData TableType Source # | |
Defined in Language.Wasm.Structure | |
type Rep TableType Source # | |
Defined in Language.Wasm.Structure type Rep TableType = D1 ('MetaData "TableType" "Language.Wasm.Structure" "wasm-1.1.1-DXxNcY7mvYrKAXJfL54aUD" 'False) (C1 ('MetaCons "TableType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Limit) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ElemType))) |
Instances
Eq Limit Source # | |
Show Limit Source # | |
Generic Limit Source # | |
Serialize Limit Source # | |
NFData Limit Source # | |
Defined in Language.Wasm.Structure | |
type Rep Limit Source # | |
Defined in Language.Wasm.Structure type Rep Limit = D1 ('MetaData "Limit" "Language.Wasm.Structure" "wasm-1.1.1-DXxNcY7mvYrKAXJfL54aUD" 'False) (C1 ('MetaCons "Limit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Natural)))) |
data GlobalType Source #
Instances
Instances
Eq FuncType Source # | |
Show FuncType Source # | |
Generic FuncType Source # | |
Serialize FuncType Source # | |
NFData FuncType Source # | |
Defined in Language.Wasm.Structure | |
type Rep FuncType Source # | |
Defined in Language.Wasm.Structure type Rep FuncType = D1 ('MetaData "FuncType" "Language.Wasm.Structure" "wasm-1.1.1-DXxNcY7mvYrKAXJfL54aUD" 'False) (C1 ('MetaCons "FuncType" 'PrefixI 'True) (S1 ('MetaSel ('Just "params") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ParamsType) :*: S1 ('MetaSel ('Just "results") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ResultType))) |
Instances
Eq ValueType Source # | |
Show ValueType Source # | |
Generic ValueType Source # | |
Serialize ValueType Source # | |
NFData ValueType Source # | |
Defined in Language.Wasm.Structure | |
type Rep ValueType Source # | |
Defined in Language.Wasm.Structure type Rep ValueType = D1 ('MetaData "ValueType" "Language.Wasm.Structure" "wasm-1.1.1-DXxNcY7mvYrKAXJfL54aUD" 'False) ((C1 ('MetaCons "I32" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "I64" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "F32" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "F64" 'PrefixI 'False) (U1 :: Type -> Type))) |
Instances
Eq BlockType Source # | |
Show BlockType Source # | |
Generic BlockType Source # | |
NFData BlockType Source # | |
Defined in Language.Wasm.Structure | |
type Rep BlockType Source # | |
Defined in Language.Wasm.Structure type Rep BlockType = D1 ('MetaData "BlockType" "Language.Wasm.Structure" "wasm-1.1.1-DXxNcY7mvYrKAXJfL54aUD" 'False) (C1 ('MetaCons "Inline" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ValueType))) :+: C1 ('MetaCons "TypeIndex" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TypeIndex))) |
type ParamsType = [ValueType] Source #
type ResultType = [ValueType] Source #
type LocalsType = [ValueType] Source #
type Expression = [Instruction Natural] Source #
type LabelIndex = Natural Source #
type LocalIndex = Natural Source #
type GlobalIndex = Natural Source #
type MemoryIndex = Natural Source #
type TableIndex = Natural Source #
emptyModule :: Module Source #
isFuncImport :: Import -> Bool Source #
isTableImport :: Import -> Bool Source #
isMemImport :: Import -> Bool Source #
isGlobalImport :: Import -> Bool Source #