Safe Haskell | None |
---|---|
Language | Haskell2010 |
Documentation
parseModuleFields :: [Lexeme] -> Either String [ModuleField] Source #
desugarize :: [ModuleField] -> Either String Module Source #
data ModuleField Source #
MFType TypeDef | |
MFImport Import | |
MFFunc Function | |
MFTable Table | |
MFMem Memory | |
MFGlobal Global | |
MFExport Export | |
MFStart StartFunction | |
MFElem ElemSegment | |
MFData DataSegment |
Instances
data DataSegment Source #
DataSegment | |
|
Instances
Eq DataSegment Source # | |
Defined in Language.Wasm.Parser (==) :: DataSegment -> DataSegment -> Bool # (/=) :: DataSegment -> DataSegment -> Bool # | |
Show DataSegment Source # | |
Defined in Language.Wasm.Parser showsPrec :: Int -> DataSegment -> ShowS # show :: DataSegment -> String # showList :: [DataSegment] -> ShowS # | |
Generic DataSegment Source # | |
Defined in Language.Wasm.Parser type Rep DataSegment :: Type -> Type # from :: DataSegment -> Rep DataSegment x # to :: Rep DataSegment x -> DataSegment # | |
NFData DataSegment Source # | |
Defined in Language.Wasm.Parser rnf :: DataSegment -> () # | |
type Rep DataSegment Source # | |
Defined in Language.Wasm.Parser |
data ElemSegment Source #
ElemSegment | |
|
Instances
Eq ElemSegment Source # | |
Defined in Language.Wasm.Parser (==) :: ElemSegment -> ElemSegment -> Bool # (/=) :: ElemSegment -> ElemSegment -> Bool # | |
Show ElemSegment Source # | |
Defined in Language.Wasm.Parser showsPrec :: Int -> ElemSegment -> ShowS # show :: ElemSegment -> String # showList :: [ElemSegment] -> ShowS # | |
Generic ElemSegment Source # | |
Defined in Language.Wasm.Parser type Rep ElemSegment :: Type -> Type # from :: ElemSegment -> Rep ElemSegment x # to :: Rep ElemSegment x -> ElemSegment # | |
NFData ElemSegment Source # | |
Defined in Language.Wasm.Parser rnf :: ElemSegment -> () # | |
type Rep ElemSegment Source # | |
Defined in Language.Wasm.Parser |
data StartFunction Source #
StartFunction FuncIndex |
Instances
Eq StartFunction Source # | |
Defined in Language.Wasm.Parser (==) :: StartFunction -> StartFunction -> Bool # (/=) :: StartFunction -> StartFunction -> Bool # | |
Show StartFunction Source # | |
Defined in Language.Wasm.Parser showsPrec :: Int -> StartFunction -> ShowS # show :: StartFunction -> String # showList :: [StartFunction] -> ShowS # | |
Generic StartFunction Source # | |
Defined in Language.Wasm.Parser type Rep StartFunction :: Type -> Type # from :: StartFunction -> Rep StartFunction x # to :: Rep StartFunction x -> StartFunction # | |
NFData StartFunction Source # | |
Defined in Language.Wasm.Parser rnf :: StartFunction -> () # | |
type Rep StartFunction Source # | |
Defined in Language.Wasm.Parser |
Export | |
|
Instances
Eq Export Source # | |
Show Export Source # | |
Generic Export Source # | |
NFData Export Source # | |
Defined in Language.Wasm.Parser | |
type Rep Export Source # | |
Defined in Language.Wasm.Parser type Rep Export = D1 ('MetaData "Export" "Language.Wasm.Parser" "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 #
ExportFunc FuncIndex | |
ExportTable TableIndex | |
ExportMemory MemoryIndex | |
ExportGlobal GlobalIndex |
Instances
Eq ExportDesc Source # | |
Defined in Language.Wasm.Parser (==) :: ExportDesc -> ExportDesc -> Bool # (/=) :: ExportDesc -> ExportDesc -> Bool # | |
Show ExportDesc Source # | |
Defined in Language.Wasm.Parser showsPrec :: Int -> ExportDesc -> ShowS # show :: ExportDesc -> String # showList :: [ExportDesc] -> ShowS # | |
Generic ExportDesc Source # | |
Defined in Language.Wasm.Parser type Rep ExportDesc :: Type -> Type # from :: ExportDesc -> Rep ExportDesc x # to :: Rep ExportDesc x -> ExportDesc # | |
NFData ExportDesc Source # | |
Defined in Language.Wasm.Parser rnf :: ExportDesc -> () # | |
type Rep ExportDesc Source # | |
Defined in Language.Wasm.Parser |
Instances
Eq Table Source # | |
Show Table Source # | |
Generic Table Source # | |
NFData Table Source # | |
Defined in Language.Wasm.Parser | |
type Rep Table Source # | |
Defined in Language.Wasm.Parser type Rep Table = D1 ('MetaData "Table" "Language.Wasm.Parser" "wasm-1.1.1-DXxNcY7mvYrKAXJfL54aUD" 'False) (C1 ('MetaCons "Table" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Ident)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TableType)))) |
Instances
Eq Memory Source # | |
Show Memory Source # | |
Generic Memory Source # | |
NFData Memory Source # | |
Defined in Language.Wasm.Parser | |
type Rep Memory Source # | |
Defined in Language.Wasm.Parser type Rep Memory = D1 ('MetaData "Memory" "Language.Wasm.Parser" "wasm-1.1.1-DXxNcY7mvYrKAXJfL54aUD" 'False) (C1 ('MetaCons "Memory" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Ident)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Limit)))) |
Global | |
|
Instances
Eq Global Source # | |
Show Global Source # | |
Generic Global Source # | |
NFData Global Source # | |
Defined in Language.Wasm.Parser | |
type Rep Global Source # | |
Defined in Language.Wasm.Parser type Rep Global = D1 ('MetaData "Global" "Language.Wasm.Parser" "wasm-1.1.1-DXxNcY7mvYrKAXJfL54aUD" 'False) (C1 ('MetaCons "Global" 'PrefixI 'True) ((S1 ('MetaSel ('Just "exportGlobalAs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text]) :*: S1 ('MetaSel ('Just "ident") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Ident))) :*: (S1 ('MetaSel ('Just "globalType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GlobalType) :*: S1 ('MetaSel ('Just "initializer") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Instruction])))) |
Instances
Eq Function Source # | |
Show Function Source # | |
Generic Function Source # | |
NFData Function Source # | |
Defined in Language.Wasm.Parser | |
type Rep Function Source # | |
Defined in Language.Wasm.Parser type Rep Function = D1 ('MetaData "Function" "Language.Wasm.Parser" "wasm-1.1.1-DXxNcY7mvYrKAXJfL54aUD" 'False) (C1 ('MetaCons "Function" 'PrefixI 'True) ((S1 ('MetaSel ('Just "exportFuncAs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text]) :*: S1 ('MetaSel ('Just "ident") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Ident))) :*: (S1 ('MetaSel ('Just "funcType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TypeUse) :*: (S1 ('MetaSel ('Just "locals") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [LocalType]) :*: S1 ('MetaSel ('Just "body") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Instruction]))))) |
Instances
Eq LocalType Source # | |
Show LocalType Source # | |
Generic LocalType Source # | |
NFData LocalType Source # | |
Defined in Language.Wasm.Parser | |
type Rep LocalType Source # | |
Defined in Language.Wasm.Parser type Rep LocalType = D1 ('MetaData "LocalType" "Language.Wasm.Parser" "wasm-1.1.1-DXxNcY7mvYrKAXJfL54aUD" 'False) (C1 ('MetaCons "LocalType" 'PrefixI 'True) (S1 ('MetaSel ('Just "ident") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Ident)) :*: S1 ('MetaSel ('Just "localType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ValueType))) |
Import | |
|
Instances
Eq Import Source # | |
Show Import Source # | |
Generic Import Source # | |
NFData Import Source # | |
Defined in Language.Wasm.Parser | |
type Rep Import Source # | |
Defined in Language.Wasm.Parser type Rep Import = D1 ('MetaData "Import" "Language.Wasm.Parser" "wasm-1.1.1-DXxNcY7mvYrKAXJfL54aUD" 'False) (C1 ('MetaCons "Import" 'PrefixI 'True) ((S1 ('MetaSel ('Just "reExportAs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text]) :*: 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 #
ImportFunc (Maybe Ident) TypeUse | |
ImportTable (Maybe Ident) TableType | |
ImportMemory (Maybe Ident) Limit | |
ImportGlobal (Maybe Ident) GlobalType |
Instances
data Instruction Source #
PlainInstr PlainInstr | |
BlockInstr | |
LoopInstr | |
IfInstr | |
|
Instances
IndexedTypeUse TypeIndex (Maybe FuncType) | |
AnonimousTypeUse FuncType |
Instances
Eq TypeDef Source # | |
Show TypeDef Source # | |
Generic TypeDef Source # | |
NFData TypeDef Source # | |
Defined in Language.Wasm.Parser | |
type Rep TypeDef Source # | |
Defined in Language.Wasm.Parser type Rep TypeDef = D1 ('MetaData "TypeDef" "Language.Wasm.Parser" "wasm-1.1.1-DXxNcY7mvYrKAXJfL54aUD" 'False) (C1 ('MetaCons "TypeDef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Ident)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FuncType))) |
data PlainInstr Source #
Instances
Eq PlainInstr Source # | |
Defined in Language.Wasm.Parser (==) :: PlainInstr -> PlainInstr -> Bool # (/=) :: PlainInstr -> PlainInstr -> Bool # | |
Show PlainInstr Source # | |
Defined in Language.Wasm.Parser showsPrec :: Int -> PlainInstr -> ShowS # show :: PlainInstr -> String # showList :: [PlainInstr] -> ShowS # | |
Generic PlainInstr Source # | |
Defined in Language.Wasm.Parser type Rep PlainInstr :: Type -> Type # from :: PlainInstr -> Rep PlainInstr x # to :: Rep PlainInstr x -> PlainInstr # | |
NFData PlainInstr Source # | |
Defined in Language.Wasm.Parser rnf :: PlainInstr -> () # | |
type Rep PlainInstr Source # | |
Defined in Language.Wasm.Parser |
Instances
Eq Index Source # | |
Show Index Source # | |
Generic Index Source # | |
NFData Index Source # | |
Defined in Language.Wasm.Parser | |
type Rep Index Source # | |
Defined in Language.Wasm.Parser type Rep Index = D1 ('MetaData "Index" "Language.Wasm.Parser" "wasm-1.1.1-DXxNcY7mvYrKAXJfL54aUD" 'False) (C1 ('MetaCons "Named" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident)) :+: C1 ('MetaCons "Index" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural))) |
Instances
Eq ParamType Source # | |
Show ParamType Source # | |
Generic ParamType Source # | |
NFData ParamType Source # | |
Defined in Language.Wasm.Parser | |
type Rep ParamType Source # | |
Defined in Language.Wasm.Parser type Rep ParamType = D1 ('MetaData "ParamType" "Language.Wasm.Parser" "wasm-1.1.1-DXxNcY7mvYrKAXJfL54aUD" 'False) (C1 ('MetaCons "ParamType" 'PrefixI 'True) (S1 ('MetaSel ('Just "ident") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Ident)) :*: S1 ('MetaSel ('Just "paramType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ValueType))) |
Instances
Eq FuncType Source # | |
Show FuncType Source # | |
Generic FuncType Source # | |
NFData FuncType Source # | |
Defined in Language.Wasm.Parser | |
type Rep FuncType Source # | |
Defined in Language.Wasm.Parser type Rep FuncType = D1 ('MetaData "FuncType" "Language.Wasm.Parser" "wasm-1.1.1-DXxNcY7mvYrKAXJfL54aUD" 'False) (C1 ('MetaCons "FuncType" 'PrefixI 'True) (S1 ('MetaSel ('Just "params") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ParamType]) :*: S1 ('MetaSel ('Just "results") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ValueType]))) |
Instances
AssertReturn Action [Expression] | |
AssertReturnCanonicalNaN Action | |
AssertReturnArithmeticNaN Action | |
AssertTrap (Either Action ModuleDef) FailureString | |
AssertMalformed ModuleDef FailureString | |
AssertInvalid ModuleDef FailureString | |
AssertUnlinkable ModuleDef FailureString | |
AssertExhaustion Action FailureString |