Safe Haskell | None |
---|---|
Language | Haskell2010 |
Extism
Description
A Haskell Extism host
Requires a libextism installation, see https://extism.org/docs/install
Synopsis
- data Manifest
- module Extism.Encoding
- data Function = Function (ForeignPtr ExtismFunction) (StablePtr ())
- newtype Plugin = Plugin (ForeignPtr ExtismPlugin)
- newtype CancelHandle = CancelHandle (Ptr ExtismCancelHandle)
- data LogLevel
- newtype Error = ExtismError String
- type Result a = Either Error a
- extismVersion :: () -> IO String
- newPlugin :: PluginInput a => a -> [Function] -> Bool -> IO (Result Plugin)
- newCompiledPlugin :: PluginInput a => a -> [Function] -> Bool -> IO (Result CompiledPlugin)
- newPluginFromCompiled :: CompiledPlugin -> IO (Result Plugin)
- isValid :: Plugin -> IO Bool
- setConfig :: Plugin -> [(String, Maybe String)] -> IO Bool
- setLogFile :: String -> LogLevel -> IO Bool
- functionExists :: Plugin -> String -> IO Bool
- call :: (ToBytes a, FromBytes b) => Plugin -> String -> a -> IO (Result b)
- call' :: (ToBytes a, FromBytes b) => Plugin -> String -> a -> IO b
- callWithHostContext :: (ToBytes a, FromBytes b) => Plugin -> String -> a -> c -> IO (Result b)
- callWithHostContext' :: (ToBytes a, FromBytes b) => Plugin -> String -> a -> c -> IO b
- cancelHandle :: Plugin -> IO CancelHandle
- cancel :: CancelHandle -> IO Bool
- pluginID :: Plugin -> IO UUID
- unwrap :: Either Error b -> b
- class ToBytes a where
- toBytes :: a -> ByteString
- class FromBytes a where
- fromBytes :: ByteString -> Result a
- newtype JSON x = JSON x
- class PluginInput a where
- pluginInput :: a -> ByteString
- reset :: Plugin -> IO ()
Documentation
module Extism.Encoding
Host function, see hostFunction
Constructors
Function (ForeignPtr ExtismFunction) (StablePtr ()) |
Plugins can be used to call WASM function
Constructors
Plugin (ForeignPtr ExtismPlugin) |
newtype CancelHandle Source #
Cancellation handle for Plugins
Constructors
CancelHandle (Ptr ExtismCancelHandle) |
Instances
Show CancelHandle Source # | |
Defined in Extism Methods showsPrec :: Int -> CancelHandle -> ShowS # show :: CancelHandle -> String # showList :: [CancelHandle] -> ShowS # | |
Eq CancelHandle Source # | |
Defined in Extism |
Log level
Extism error
Constructors
ExtismError String |
extismVersion :: () -> IO String Source #
Get the Extism version string
newPlugin :: PluginInput a => a -> [Function] -> Bool -> IO (Result Plugin) Source #
Create a Plugin
from a WASM module, useWasi
determines if WASI should
| be linked
newCompiledPlugin :: PluginInput a => a -> [Function] -> Bool -> IO (Result CompiledPlugin) Source #
Create a Plugin
from a WASM module, useWasi
determines if WASI should
| be linked
newPluginFromCompiled :: CompiledPlugin -> IO (Result Plugin) Source #
Create a new plugin from a CompiledPlugin
setConfig :: Plugin -> [(String, Maybe String)] -> IO Bool Source #
Set configuration values for a plugin
setLogFile :: String -> LogLevel -> IO Bool Source #
Set the log file and level, this is a global configuration
functionExists :: Plugin -> String -> IO Bool Source #
Check if a function exists in the given plugin
callWithHostContext :: (ToBytes a, FromBytes b) => Plugin -> String -> a -> c -> IO (Result b) Source #
cancelHandle :: Plugin -> IO CancelHandle Source #
Create a new CancelHandle
that can be used to cancel a running plugin
| from another thread.
cancel :: CancelHandle -> IO Bool Source #
Cancel a running plugin using a CancelHandle
class ToBytes a where Source #
Methods
toBytes :: a -> ByteString Source #
Instances
ToBytes ByteString Source # | |
Defined in Extism.Encoding Methods toBytes :: ByteString -> ByteString Source # | |
ToBytes Int32 Source # | |
Defined in Extism.Encoding Methods toBytes :: Int32 -> ByteString Source # | |
ToBytes Int64 Source # | |
Defined in Extism.Encoding Methods toBytes :: Int64 -> ByteString Source # | |
ToBytes Word32 Source # | |
Defined in Extism.Encoding Methods toBytes :: Word32 -> ByteString Source # | |
ToBytes Word64 Source # | |
Defined in Extism.Encoding Methods toBytes :: Word64 -> ByteString Source # | |
ToBytes () Source # | |
Defined in Extism.Encoding Methods toBytes :: () -> ByteString Source # | |
ToBytes Double Source # | |
Defined in Extism.Encoding Methods toBytes :: Double -> ByteString Source # | |
ToBytes Float Source # | |
Defined in Extism.Encoding Methods toBytes :: Float -> ByteString Source # | |
Data a => ToBytes (JSON a) Source # | |
Defined in Extism.Encoding Methods toBytes :: JSON a -> ByteString Source # | |
ToBytes [Char] Source # | |
Defined in Extism.Encoding Methods toBytes :: [Char] -> ByteString Source # |
class FromBytes a where Source #
Methods
fromBytes :: ByteString -> Result a Source #
Instances
FromBytes ByteString Source # | |
Defined in Extism.Encoding Methods fromBytes :: ByteString -> Result ByteString Source # | |
FromBytes Int32 Source # | |
Defined in Extism.Encoding | |
FromBytes Int64 Source # | |
Defined in Extism.Encoding | |
FromBytes Word32 Source # | |
Defined in Extism.Encoding | |
FromBytes Word64 Source # | |
Defined in Extism.Encoding | |
FromBytes () Source # | |
Defined in Extism.Encoding Methods fromBytes :: ByteString -> Result () Source # | |
FromBytes Double Source # | |
Defined in Extism.Encoding | |
FromBytes Float Source # | |
Defined in Extism.Encoding | |
Data a => FromBytes (JSON a) Source # | |
Defined in Extism.Encoding | |
FromBytes [Char] Source # | |
Defined in Extism.Encoding |
Constructors
JSON x |
class PluginInput a where Source #
Defines types that can be used to pass Wasm data into a plugin
Methods
pluginInput :: a -> ByteString Source #
Instances
PluginInput ByteString Source # | |
Defined in Extism Methods pluginInput :: ByteString -> ByteString Source # | |
PluginInput Manifest Source # | |
Defined in Extism Methods pluginInput :: Manifest -> ByteString Source # |