| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Binaryen
Contents
Description
Global Binaryen state.
See https://github.com/WebAssembly/binaryen/blob/master/src/binaryen-c.h for API documentation.
This module is intended to be imported qualified.
Synopsis
- areColorsEnabled :: IO CInt
- setColorsEnabled :: CInt -> IO ()
- setOneCallerInlineMaxSize :: Index -> IO ()
- getOneCallerInlineMaxSize :: IO Index
- setFlexibleInlineMaxSize :: Index -> IO ()
- getFlexibleInlineMaxSize :: IO Index
- setAlwaysInlineMaxSize :: Index -> IO ()
- getAlwaysInlineMaxSize :: IO Index
- clearPassArguments :: IO ()
- setPassArgument :: Ptr CChar -> Ptr CChar -> IO ()
- getPassArgument :: Ptr CChar -> IO (Ptr CChar)
- setLowMemoryUnused :: CInt -> IO ()
- getLowMemoryUnused :: IO CInt
- setDebugInfo :: CInt -> IO ()
- getDebugInfo :: IO CInt
- setShrinkLevel :: CInt -> IO ()
- getShrinkLevel :: IO CInt
- setOptimizeLevel :: CInt -> IO ()
- getOptimizeLevel :: IO CInt
- data Event
- data Export
- data Expression
- data ExpressionId
- data ExternalKind
- data Features
- data Function
- data Global
- data Index
- data Module
- data Op
- data Relooper
- data RelooperBlock
- data SideEffects
- data Type
Documentation
areColorsEnabled :: IO CInt Source #
setColorsEnabled :: CInt -> IO () Source #
setOneCallerInlineMaxSize :: Index -> IO () Source #
setFlexibleInlineMaxSize :: Index -> IO () Source #
getFlexibleInlineMaxSize :: IO Index Source #
setAlwaysInlineMaxSize :: Index -> IO () Source #
getAlwaysInlineMaxSize :: IO Index Source #
clearPassArguments :: IO () Source #
setPassArgument :: Ptr CChar -> Ptr CChar -> IO () Source #
getPassArgument :: Ptr CChar -> IO (Ptr CChar) Source #
setLowMemoryUnused :: CInt -> IO () Source #
getLowMemoryUnused :: IO CInt Source #
setDebugInfo :: CInt -> IO () Source #
getDebugInfo :: IO CInt Source #
setShrinkLevel :: CInt -> IO () Source #
getShrinkLevel :: IO CInt Source #
setOptimizeLevel :: CInt -> IO () Source #
getOptimizeLevel :: IO CInt Source #
Re-exports
Instances
| Eq Event Source # | |
| Show Event Source # | |
| Storable Event Source # | |
| Defined in Binaryen.Event Methods peekElemOff :: Ptr Event -> Int -> IO Event pokeElemOff :: Ptr Event -> Int -> Event -> IO () peekByteOff :: Ptr b -> Int -> IO Event pokeByteOff :: Ptr b -> Int -> Event -> IO () | |
Instances
| Eq Export Source # | |
| Show Export Source # | |
| Storable Export Source # | |
| Defined in Binaryen.Export Methods peekElemOff :: Ptr Export -> Int -> IO Export pokeElemOff :: Ptr Export -> Int -> Export -> IO () peekByteOff :: Ptr b -> Int -> IO Export pokeByteOff :: Ptr b -> Int -> Export -> IO () | |
data Expression Source #
Instances
| Eq Expression Source # | |
| Defined in Binaryen.Expression | |
| Show Expression Source # | |
| Defined in Binaryen.Expression Methods showsPrec :: Int -> Expression -> ShowS show :: Expression -> String showList :: [Expression] -> ShowS | |
| Storable Expression Source # | |
| Defined in Binaryen.Expression Methods sizeOf :: Expression -> Int alignment :: Expression -> Int peekElemOff :: Ptr Expression -> Int -> IO Expression pokeElemOff :: Ptr Expression -> Int -> Expression -> IO () peekByteOff :: Ptr b -> Int -> IO Expression pokeByteOff :: Ptr b -> Int -> Expression -> IO () peek :: Ptr Expression -> IO Expression poke :: Ptr Expression -> Expression -> IO () | |
data ExpressionId Source #
Instances
| Eq ExpressionId Source # | |
| Defined in Binaryen.ExpressionId | |
| Show ExpressionId Source # | |
| Defined in Binaryen.ExpressionId Methods showsPrec :: Int -> ExpressionId -> ShowS show :: ExpressionId -> String showList :: [ExpressionId] -> ShowS | |
| Storable ExpressionId Source # | |
| Defined in Binaryen.ExpressionId Methods sizeOf :: ExpressionId -> Int alignment :: ExpressionId -> Int peekElemOff :: Ptr ExpressionId -> Int -> IO ExpressionId pokeElemOff :: Ptr ExpressionId -> Int -> ExpressionId -> IO () peekByteOff :: Ptr b -> Int -> IO ExpressionId pokeByteOff :: Ptr b -> Int -> ExpressionId -> IO () peek :: Ptr ExpressionId -> IO ExpressionId poke :: Ptr ExpressionId -> ExpressionId -> IO () | |
data ExternalKind Source #
Instances
| Eq ExternalKind Source # | |
| Defined in Binaryen.ExternalKind | |
| Show ExternalKind Source # | |
| Defined in Binaryen.ExternalKind Methods showsPrec :: Int -> ExternalKind -> ShowS show :: ExternalKind -> String showList :: [ExternalKind] -> ShowS | |
| Storable ExternalKind Source # | |
| Defined in Binaryen.ExternalKind Methods sizeOf :: ExternalKind -> Int alignment :: ExternalKind -> Int peekElemOff :: Ptr ExternalKind -> Int -> IO ExternalKind pokeElemOff :: Ptr ExternalKind -> Int -> ExternalKind -> IO () peekByteOff :: Ptr b -> Int -> IO ExternalKind pokeByteOff :: Ptr b -> Int -> ExternalKind -> IO () peek :: Ptr ExternalKind -> IO ExternalKind poke :: Ptr ExternalKind -> ExternalKind -> IO () | |
Instances
| Eq Features Source # | |
| Show Features Source # | |
| Bits Features Source # | |
| Defined in Binaryen.Features Methods (.&.) :: Features -> Features -> Features (.|.) :: Features -> Features -> Features xor :: Features -> Features -> Features complement :: Features -> Features shift :: Features -> Int -> Features rotate :: Features -> Int -> Features setBit :: Features -> Int -> Features clearBit :: Features -> Int -> Features complementBit :: Features -> Int -> Features testBit :: Features -> Int -> Bool bitSizeMaybe :: Features -> Maybe Int shiftL :: Features -> Int -> Features unsafeShiftL :: Features -> Int -> Features shiftR :: Features -> Int -> Features unsafeShiftR :: Features -> Int -> Features rotateL :: Features -> Int -> Features | |
| Storable Features Source # | |
| Defined in Binaryen.Features Methods peekElemOff :: Ptr Features -> Int -> IO Features pokeElemOff :: Ptr Features -> Int -> Features -> IO () peekByteOff :: Ptr b -> Int -> IO Features pokeByteOff :: Ptr b -> Int -> Features -> IO () | |
Instances
| Eq Function Source # | |
| Show Function Source # | |
| Storable Function Source # | |
| Defined in Binaryen.Function Methods peekElemOff :: Ptr Function -> Int -> IO Function pokeElemOff :: Ptr Function -> Int -> Function -> IO () peekByteOff :: Ptr b -> Int -> IO Function pokeByteOff :: Ptr b -> Int -> Function -> IO () | |
Instances
| Eq Global Source # | |
| Show Global Source # | |
| Storable Global Source # | |
| Defined in Binaryen.Global Methods peekElemOff :: Ptr Global -> Int -> IO Global pokeElemOff :: Ptr Global -> Int -> Global -> IO () peekByteOff :: Ptr b -> Int -> IO Global pokeByteOff :: Ptr b -> Int -> Global -> IO () | |
Instances
| Enum Index Source # | |
| Eq Index Source # | |
| Integral Index Source # | |
| Num Index Source # | |
| Ord Index Source # | |
| Real Index Source # | |
| Defined in Binaryen.Index Methods toRational :: Index -> Rational | |
| Show Index Source # | |
| Storable Index Source # | |
| Defined in Binaryen.Index Methods peekElemOff :: Ptr Index -> Int -> IO Index pokeElemOff :: Ptr Index -> Int -> Index -> IO () peekByteOff :: Ptr b -> Int -> IO Index pokeByteOff :: Ptr b -> Int -> Index -> IO () | |
Instances
| Eq Module Source # | |
| Show Module Source # | |
| Storable Module Source # | |
| Defined in Binaryen.Module Methods peekElemOff :: Ptr Module -> Int -> IO Module pokeElemOff :: Ptr Module -> Int -> Module -> IO () peekByteOff :: Ptr b -> Int -> IO Module pokeByteOff :: Ptr b -> Int -> Module -> IO () | |
Instances
| Eq Op Source # | |
| Show Op Source # | |
| Storable Op Source # | |
| Defined in Binaryen.Op Methods peekElemOff :: Ptr Op -> Int -> IO Op pokeElemOff :: Ptr Op -> Int -> Op -> IO () peekByteOff :: Ptr b -> Int -> IO Op pokeByteOff :: Ptr b -> Int -> Op -> IO () | |
Instances
| Eq Relooper Source # | |
| Show Relooper Source # | |
| Storable Relooper Source # | |
| Defined in Binaryen.Relooper Methods peekElemOff :: Ptr Relooper -> Int -> IO Relooper pokeElemOff :: Ptr Relooper -> Int -> Relooper -> IO () peekByteOff :: Ptr b -> Int -> IO Relooper pokeByteOff :: Ptr b -> Int -> Relooper -> IO () | |
data RelooperBlock Source #
Instances
| Eq RelooperBlock Source # | |
| Defined in Binaryen.Relooper | |
| Show RelooperBlock Source # | |
| Defined in Binaryen.Relooper Methods showsPrec :: Int -> RelooperBlock -> ShowS show :: RelooperBlock -> String showList :: [RelooperBlock] -> ShowS | |
data SideEffects Source #
Instances
| Eq SideEffects Source # | |
| Defined in Binaryen.SideEffects | |
| Show SideEffects Source # | |
| Defined in Binaryen.SideEffects Methods showsPrec :: Int -> SideEffects -> ShowS show :: SideEffects -> String showList :: [SideEffects] -> ShowS | |
| Storable SideEffects Source # | |
| Defined in Binaryen.SideEffects Methods sizeOf :: SideEffects -> Int alignment :: SideEffects -> Int peekElemOff :: Ptr SideEffects -> Int -> IO SideEffects pokeElemOff :: Ptr SideEffects -> Int -> SideEffects -> IO () peekByteOff :: Ptr b -> Int -> IO SideEffects pokeByteOff :: Ptr b -> Int -> SideEffects -> IO () peek :: Ptr SideEffects -> IO SideEffects poke :: Ptr SideEffects -> SideEffects -> IO () | |
Instances
| Eq Type Source # | |
| Show Type Source # | |
| Storable Type Source # | |
| Defined in Binaryen.Type Methods peekElemOff :: Ptr Type -> Int -> IO Type pokeElemOff :: Ptr Type -> Int -> Type -> IO () peekByteOff :: Ptr b -> Int -> IO Type pokeByteOff :: Ptr b -> Int -> Type -> IO () | |