binaryen-0.0.6.0: Haskell bindings to binaryen
Safe HaskellNone
LanguageHaskell2010

Binaryen.Module

Description

Modules.

See https://github.com/WebAssembly/binaryen/blob/master/src/binaryen-c.h for API documentation.

This module is intended to be imported qualified.

Documentation

newtype Module Source #

Constructors

Module (Ptr Module) 

Instances

Instances details
Eq Module Source # 
Instance details

Defined in Binaryen.Module

Methods

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

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

Show Module Source # 
Instance details

Defined in Binaryen.Module

Methods

showsPrec :: Int -> Module -> ShowS

show :: Module -> String

showList :: [Module] -> ShowS

Storable Module Source # 
Instance details

Defined in Binaryen.Module

Methods

sizeOf :: Module -> Int

alignment :: Module -> Int

peekElemOff :: Ptr Module -> Int -> IO Module

pokeElemOff :: Ptr Module -> Int -> Module -> IO ()

peekByteOff :: Ptr b -> Int -> IO Module

pokeByteOff :: Ptr b -> Int -> Module -> IO ()

peek :: Ptr Module -> IO Module

poke :: Ptr Module -> Module -> IO ()

dispose :: Module -> IO () Source #

addFunction :: Module -> Ptr CChar -> Type -> Type -> Ptr Type -> Index -> Expression -> IO Function Source #

getFunction :: Module -> Ptr CChar -> IO Function Source #

removeFunction :: Module -> Ptr CChar -> IO () Source #

addFunctionImport :: Module -> Ptr CChar -> Ptr CChar -> Ptr CChar -> Type -> Type -> IO () Source #

addTableImport :: Module -> Ptr CChar -> Ptr CChar -> Ptr CChar -> IO () Source #

addMemoryImport :: Module -> Ptr CChar -> Ptr CChar -> Ptr CChar -> Word8 -> IO () Source #

addGlobalImport :: Module -> Ptr CChar -> Ptr CChar -> Ptr CChar -> Type -> CInt -> IO () Source #

addEventImport :: Module -> Ptr CChar -> Ptr CChar -> Ptr CChar -> Word32 -> Type -> Type -> IO () Source #

addFunctionExport :: Module -> Ptr CChar -> Ptr CChar -> IO Export Source #

addTableExport :: Module -> Ptr CChar -> Ptr CChar -> IO Export Source #

addMemoryExport :: Module -> Ptr CChar -> Ptr CChar -> IO Export Source #

addGlobalExport :: Module -> Ptr CChar -> Ptr CChar -> IO Export Source #

addEventExport :: Module -> Ptr CChar -> Ptr CChar -> IO Export Source #

removeExport :: Module -> Ptr CChar -> IO () Source #

addEvent :: Module -> Ptr CChar -> Word32 -> Type -> Type -> IO Event Source #

getEvent :: Module -> Ptr CChar -> IO Event Source #

removeEvent :: Module -> Ptr CChar -> IO () Source #

setFunctionTable :: Module -> Index -> Index -> Ptr (Ptr CChar) -> Index -> Expression -> IO () Source #

setMemory :: Module -> Index -> Index -> Ptr CChar -> Ptr (Ptr CChar) -> Ptr Int8 -> Ptr Expression -> Ptr Index -> Index -> Word8 -> IO () Source #

copyMemorySegmentData :: Module -> Index -> Ptr CChar -> IO () Source #

parse :: Ptr CChar -> IO Module Source #

print :: Module -> IO () Source #

validate :: Module -> IO CInt Source #

optimize :: Module -> IO () Source #

addCustomSection :: Module -> Ptr CChar -> Ptr CChar -> Index -> IO () Source #

runPasses :: Module -> Ptr (Ptr CChar) -> Index -> IO () Source #

autoDrop :: Module -> IO () Source #

write :: Module -> Ptr CChar -> CSize -> IO CSize Source #

writeText :: Module -> Ptr CChar -> CSize -> IO CSize Source #

allocateAndWriteMut :: Module -> Ptr CChar -> Ptr (Ptr ()) -> Ptr CSize -> Ptr (Ptr CChar) -> IO () Source #

allocateAndWriteText :: Module -> IO (Ptr CChar) Source #

read :: Ptr CChar -> CSize -> IO Module Source #

interpret :: Module -> IO () Source #

addDebugInfoFileName :: Module -> Ptr CChar -> IO Index Source #

getDebugInfoFileName :: Module -> Index -> IO (Ptr CChar) Source #

addGlobal :: Module -> Ptr CChar -> Type -> Int8 -> Expression -> IO Global Source #

getGlobal :: Module -> Ptr CChar -> IO Global Source #

removeGlobal :: Module -> Ptr CChar -> IO () Source #