extism-1.2.1.0: Extism bindings
Safe HaskellNone
LanguageHaskell2010

Extism.HostFunction

Synopsis

Documentation

data CurrentPlugin Source #

Access the plugin that is currently executing from inside a host function

Constructors

CurrentPlugin (Ptr ExtismCurrentPlugin) [Val] (Ptr Val) Int 

data ValType Source #

Low-level Wasm types

Constructors

I32 
I64 
F32 
F64 
V128 
FuncRef 
ExternRef 

Instances

Instances details
Storable ValType Source # 
Instance details

Defined in Extism.Bindings

Show ValType Source # 
Instance details

Defined in Extism.Bindings

Eq ValType Source # 
Instance details

Defined in Extism.Bindings

Methods

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

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

data Val Source #

Low-level Wasm values

Instances

Instances details
Storable Val Source # 
Instance details

Defined in Extism.Bindings

Methods

sizeOf :: Val -> Int #

alignment :: Val -> Int #

peekElemOff :: Ptr Val -> Int -> IO Val #

pokeElemOff :: Ptr Val -> Int -> Val -> IO () #

peekByteOff :: Ptr b -> Int -> IO Val #

pokeByteOff :: Ptr b -> Int -> Val -> IO () #

peek :: Ptr Val -> IO Val #

poke :: Ptr Val -> Val -> IO () #

Show Val Source # 
Instance details

Defined in Extism.Bindings

Methods

showsPrec :: Int -> Val -> ShowS #

show :: Val -> String #

showList :: [Val] -> ShowS #

Eq Val Source # 
Instance details

Defined in Extism.Bindings

Methods

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

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

data MemoryHandle Source #

A memory handle represents an allocated block of Extism memory

Instances

Instances details
Enum MemoryHandle Source # 
Instance details

Defined in Extism.HostFunction

Num MemoryHandle Source # 
Instance details

Defined in Extism.HostFunction

Integral MemoryHandle Source # 
Instance details

Defined in Extism.HostFunction

Real MemoryHandle Source # 
Instance details

Defined in Extism.HostFunction

Show MemoryHandle Source # 
Instance details

Defined in Extism.HostFunction

Eq MemoryHandle Source # 
Instance details

Defined in Extism.HostFunction

Ord MemoryHandle Source # 
Instance details

Defined in Extism.HostFunction

data Function Source #

Host function, see hostFunction

Instances

Instances details
Eq Function Source # 
Instance details

Defined in Extism

memoryAlloc :: CurrentPlugin -> Word64 -> IO MemoryHandle Source #

Allocate a new handle of the given size

memoryLength :: CurrentPlugin -> MemoryHandle -> IO Word64 Source #

Get the length of a handle, returns 0 if the handle is invalid

memoryFree :: CurrentPlugin -> MemoryHandle -> IO () Source #

Free allocated memory

memory :: CurrentPlugin -> IO (Ptr Word8) Source #

Access a pointer to the entire memory region

memoryOffset :: CurrentPlugin -> MemoryHandle -> IO (Ptr Word8) Source #

Access the pointer for the given MemoryHandle

memoryBytes :: CurrentPlugin -> MemoryHandle -> IO ByteString Source #

Access the data associated with a handle as a ByteString

memoryString :: CurrentPlugin -> MemoryHandle -> IO String Source #

Access the data associated with a handle as a String

memoryGet :: FromBytes a => CurrentPlugin -> MemoryHandle -> IO (Result a) Source #

Access the data associated with a handle and convert it into a Haskell type

allocBytes :: CurrentPlugin -> ByteString -> IO MemoryHandle Source #

Allocate memory and copy an existing ByteString into it

allocString :: CurrentPlugin -> String -> IO MemoryHandle Source #

Allocate memory and copy an existing String into it

toI32 :: Integral a => a -> Val Source #

Create a new I32 Val

toI64 :: Integral a => a -> Val Source #

Create a new I64 Val

toF32 :: Float -> Val Source #

Create a new F32 Val

toF64 :: Double -> Val Source #

Create a new F64 Val

fromI32 :: Integral a => Val -> Maybe a Source #

Get I32 Val

fromI64 :: Integral a => Val -> Maybe a Source #

Get I64 Val

hostFunction :: String -> [ValType] -> [ValType] -> (CurrentPlugin -> a -> IO ()) -> a -> IO Function Source #

hostFunction "function_name" inputTypes outputTypes callback userData creates a new | Function in the default namespace that can be called from a Plugin

hostFunction' :: String -> String -> [ValType] -> [ValType] -> (CurrentPlugin -> a -> IO ()) -> a -> IO Function Source #

hostFunction' "namespace" "function_name" inputTypes outputTypes callback userData creates a new | Function in the provided namespace that can be called from a Plugin

newFunction :: String -> [ValType] -> [ValType] -> a -> (CurrentPlugin -> a -> IO ()) -> IO Function Source #

newFunction' "function_name" inputTypes outputTypes userData callback creates a new | Function in the default namespace that can be called from a Plugin

newFunction' :: String -> String -> [ValType] -> [ValType] -> a -> (CurrentPlugin -> a -> IO ()) -> IO Function Source #

newFunction' "namespace" "function_name" inputTypes outputTypes userData callback creates a new | Function in the provided namespace that can be called from a Plugin

output :: ToBytes a => CurrentPlugin -> Int -> a -> IO () Source #