wasm-1.1.1: WebAssembly Language Toolkit and Interpreter
Safe HaskellNone
LanguageHaskell2010

Language.Wasm

Synopsis

Documentation

data Module Source #

Instances

Instances details
Eq Module Source # 
Instance details

Defined in Language.Wasm.Structure

Methods

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

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

Show Module Source # 
Instance details

Defined in Language.Wasm.Structure

Generic Module Source # 
Instance details

Defined in Language.Wasm.Structure

Associated Types

type Rep Module :: Type -> Type #

Methods

from :: Module -> Rep Module x #

to :: Rep Module x -> Module #

Serialize Module Source # 
Instance details

Defined in Language.Wasm.Binary

NFData Module Source # 
Instance details

Defined in Language.Wasm.Structure

Methods

rnf :: Module -> () #

type Rep Module Source # 
Instance details

Defined in Language.Wasm.Structure

data ValidModule Source #

Instances

Instances details
Eq ValidModule Source # 
Instance details

Defined in Language.Wasm.Validate

Show ValidModule Source # 
Instance details

Defined in Language.Wasm.Validate

parse :: ByteString -> Either String Module Source #

Parse WebAssembly text representation to Module

parseScript :: ByteString -> Either String Script Source #

Parse WebAssembly extended script grammar

encode :: Module -> ByteString Source #

Dump Module to binary representation

encodeLazy :: Module -> ByteString Source #

Dump Module to binary representation lazily

decode :: ByteString -> Either String Module Source #

Decode Module from binary representation

decodeLazy :: ByteString -> Either String Module Source #

Decode Module from binary representation lazily

data Command Source #

Instances

Instances details
Eq Command Source # 
Instance details

Defined in Language.Wasm.Parser

Methods

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

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

Show Command Source # 
Instance details

Defined in Language.Wasm.Parser

data ModuleDef Source #

Instances

Instances details
Eq ModuleDef Source # 
Instance details

Defined in Language.Wasm.Parser

Show ModuleDef Source # 
Instance details

Defined in Language.Wasm.Parser

data Action Source #

Instances

Instances details
Eq Action Source # 
Instance details

Defined in Language.Wasm.Parser

Methods

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

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

Show Action Source # 
Instance details

Defined in Language.Wasm.Parser

newtype Ident Source #

Constructors

Ident Text 

Instances

Instances details
Eq Ident Source # 
Instance details

Defined in Language.Wasm.Parser

Methods

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

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

Show Ident Source # 
Instance details

Defined in Language.Wasm.Parser

Methods

showsPrec :: Int -> Ident -> ShowS #

show :: Ident -> String #

showList :: [Ident] -> ShowS #

Generic Ident Source # 
Instance details

Defined in Language.Wasm.Parser

Associated Types

type Rep Ident :: Type -> Type #

Methods

from :: Ident -> Rep Ident x #

to :: Rep Ident x -> Ident #

NFData Ident Source # 
Instance details

Defined in Language.Wasm.Parser

Methods

rnf :: Ident -> () #

type Rep Ident Source # 
Instance details

Defined in Language.Wasm.Parser

type Rep Ident = D1 ('MetaData "Ident" "Language.Wasm.Parser" "wasm-1.1.1-DXxNcY7mvYrKAXJfL54aUD" 'True) (C1 ('MetaCons "Ident" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data Meta Source #

Instances

Instances details
Eq Meta Source # 
Instance details

Defined in Language.Wasm.Parser

Methods

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

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

Show Meta Source # 
Instance details

Defined in Language.Wasm.Parser

Methods

showsPrec :: Int -> Meta -> ShowS #

show :: Meta -> String #

showList :: [Meta] -> ShowS #