wasm-1.0.0: WebAssembly Language Toolkit and Interpreter

Safe HaskellNone
LanguageHaskell2010

Language.Wasm.Parser

Documentation

data ModuleField Source #

Instances

Eq ModuleField Source # 
Show ModuleField Source # 
Generic ModuleField Source # 

Associated Types

type Rep ModuleField :: * -> * #

NFData ModuleField Source # 

Methods

rnf :: ModuleField -> () #

type Rep ModuleField Source # 
type Rep ModuleField = D1 * (MetaData "ModuleField" "Language.Wasm.Parser" "wasm-1.0.0-3p6AkTQBgB5H14IIPDel9m" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "MFType" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * TypeDef))) (C1 * (MetaCons "MFImport" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Import)))) ((:+:) * (C1 * (MetaCons "MFFunc" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Function))) ((:+:) * (C1 * (MetaCons "MFTable" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Table))) (C1 * (MetaCons "MFMem" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Memory)))))) ((:+:) * ((:+:) * (C1 * (MetaCons "MFGlobal" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Global))) (C1 * (MetaCons "MFExport" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Export)))) ((:+:) * (C1 * (MetaCons "MFStart" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * StartFunction))) ((:+:) * (C1 * (MetaCons "MFElem" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ElemSegment))) (C1 * (MetaCons "MFData" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * DataSegment)))))))

data Export Source #

Constructors

Export 

Fields

Instances

Eq Export Source # 

Methods

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

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

Show Export Source # 
Generic Export Source # 

Associated Types

type Rep Export :: * -> * #

Methods

from :: Export -> Rep Export x #

to :: Rep Export x -> Export #

NFData Export Source # 

Methods

rnf :: Export -> () #

type Rep Export Source # 
type Rep Export = D1 * (MetaData "Export" "Language.Wasm.Parser" "wasm-1.0.0-3p6AkTQBgB5H14IIPDel9m" False) (C1 * (MetaCons "Export" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "name") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "desc") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ExportDesc))))

data ExportDesc Source #

Constructors

ExportFunc FuncIndex 
ExportTable TableIndex 
ExportMemory MemoryIndex 
ExportGlobal GlobalIndex 

data Table Source #

Constructors

Table [Text] (Maybe Ident) TableType 

Instances

data Global Source #

Instances

Eq Global Source # 

Methods

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

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

Show Global Source # 
Generic Global Source # 

Associated Types

type Rep Global :: * -> * #

Methods

from :: Global -> Rep Global x #

to :: Rep Global x -> Global #

NFData Global Source # 

Methods

rnf :: Global -> () #

type Rep Global Source # 

data LocalType Source #

Constructors

LocalType 

Instances

Eq LocalType Source # 
Show LocalType Source # 
Generic LocalType Source # 

Associated Types

type Rep LocalType :: * -> * #

NFData LocalType Source # 

Methods

rnf :: LocalType -> () #

type Rep LocalType Source # 
type Rep LocalType = D1 * (MetaData "LocalType" "Language.Wasm.Parser" "wasm-1.0.0-3p6AkTQBgB5H14IIPDel9m" False) (C1 * (MetaCons "LocalType" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "ident") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Ident))) (S1 * (MetaSel (Just Symbol "localType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ValueType))))

data Import Source #

Constructors

Import 

Instances

data ImportDesc Source #

Instances

Eq ImportDesc Source # 
Show ImportDesc Source # 
Generic ImportDesc Source # 

Associated Types

type Rep ImportDesc :: * -> * #

NFData ImportDesc Source # 

Methods

rnf :: ImportDesc -> () #

type Rep ImportDesc Source # 

data Instruction Source #

Instances

Eq Instruction Source # 
Show Instruction Source # 
Generic Instruction Source # 

Associated Types

type Rep Instruction :: * -> * #

NFData Instruction Source # 

Methods

rnf :: Instruction -> () #

type Rep Instruction Source # 
type Rep Instruction = D1 * (MetaData "Instruction" "Language.Wasm.Parser" "wasm-1.0.0-3p6AkTQBgB5H14IIPDel9m" False) ((:+:) * ((:+:) * (C1 * (MetaCons "PlainInstr" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * PlainInstr))) (C1 * (MetaCons "BlockInstr" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "label") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Ident))) ((:*:) * (S1 * (MetaSel (Just Symbol "resultType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ValueType])) (S1 * (MetaSel (Just Symbol "body") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Instruction])))))) ((:+:) * (C1 * (MetaCons "LoopInstr" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "label") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Ident))) ((:*:) * (S1 * (MetaSel (Just Symbol "resultType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ValueType])) (S1 * (MetaSel (Just Symbol "body") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Instruction]))))) (C1 * (MetaCons "IfInstr" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "label") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Ident))) (S1 * (MetaSel (Just Symbol "resultType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ValueType]))) ((:*:) * (S1 * (MetaSel (Just Symbol "trueBranch") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Instruction])) (S1 * (MetaSel (Just Symbol "falseBranch") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Instruction])))))))

data TypeUse Source #

Instances

Eq TypeUse Source # 

Methods

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

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

Show TypeUse Source # 
Generic TypeUse Source # 

Associated Types

type Rep TypeUse :: * -> * #

Methods

from :: TypeUse -> Rep TypeUse x #

to :: Rep TypeUse x -> TypeUse #

NFData TypeUse Source # 

Methods

rnf :: TypeUse -> () #

type Rep TypeUse Source # 

data TypeDef Source #

Constructors

TypeDef (Maybe Ident) FuncType 

Instances

Eq TypeDef Source # 

Methods

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

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

Show TypeDef Source # 
Generic TypeDef Source # 

Associated Types

type Rep TypeDef :: * -> * #

Methods

from :: TypeDef -> Rep TypeDef x #

to :: Rep TypeDef x -> TypeDef #

NFData TypeDef Source # 

Methods

rnf :: TypeDef -> () #

type Rep TypeDef Source # 

data PlainInstr Source #

data Index Source #

Constructors

Named Ident 
Index Natural 

Instances

Eq Index Source # 

Methods

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

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

Show Index Source # 

Methods

showsPrec :: Int -> Index -> ShowS #

show :: Index -> String #

showList :: [Index] -> ShowS #

Generic Index Source # 

Associated Types

type Rep Index :: * -> * #

Methods

from :: Index -> Rep Index x #

to :: Rep Index x -> Index #

NFData Index Source # 

Methods

rnf :: Index -> () #

type Rep Index Source # 

newtype Ident Source #

Constructors

Ident Text 

Instances

Eq Ident Source # 

Methods

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

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

Show Ident Source # 

Methods

showsPrec :: Int -> Ident -> ShowS #

show :: Ident -> String #

showList :: [Ident] -> ShowS #

Generic Ident Source # 

Associated Types

type Rep Ident :: * -> * #

Methods

from :: Ident -> Rep Ident x #

to :: Rep Ident x -> Ident #

NFData Ident Source # 

Methods

rnf :: Ident -> () #

type Rep Ident Source # 
type Rep Ident = D1 * (MetaData "Ident" "Language.Wasm.Parser" "wasm-1.0.0-3p6AkTQBgB5H14IIPDel9m" True) (C1 * (MetaCons "Ident" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

data ParamType Source #

Constructors

ParamType 

Instances

Eq ParamType Source # 
Show ParamType Source # 
Generic ParamType Source # 

Associated Types

type Rep ParamType :: * -> * #

NFData ParamType Source # 

Methods

rnf :: ParamType -> () #

type Rep ParamType Source # 
type Rep ParamType = D1 * (MetaData "ParamType" "Language.Wasm.Parser" "wasm-1.0.0-3p6AkTQBgB5H14IIPDel9m" False) (C1 * (MetaCons "ParamType" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "ident") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Ident))) (S1 * (MetaSel (Just Symbol "paramType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ValueType))))

data FuncType Source #

Constructors

FuncType 

Fields

Instances

Eq FuncType Source # 
Show FuncType Source # 
Generic FuncType Source # 

Associated Types

type Rep FuncType :: * -> * #

Methods

from :: FuncType -> Rep FuncType x #

to :: Rep FuncType x -> FuncType #

NFData FuncType Source # 

Methods

rnf :: FuncType -> () #

type Rep FuncType Source # 
type Rep FuncType = D1 * (MetaData "FuncType" "Language.Wasm.Parser" "wasm-1.0.0-3p6AkTQBgB5H14IIPDel9m" False) (C1 * (MetaCons "FuncType" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "params") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ParamType])) (S1 * (MetaSel (Just Symbol "results") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ValueType]))))

data Action Source #

Instances

data Meta Source #

Instances

Eq Meta Source # 

Methods

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

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

Show Meta Source # 

Methods

showsPrec :: Int -> Meta -> ShowS #

show :: Meta -> String #

showList :: [Meta] -> ShowS #