Copyright | © 2007–2012 Gracjan Polak; © 2012–2016 Ömer Sinan Ağacan; © 2017-2022 Albert Krewinkel |
---|---|
License | MIT |
Maintainer | Albert Krewinkel <tarleb+hslua@zeitkraut.de> |
Safe Haskell | None |
Language | Haskell2010 |
Functions to push and retrieve data to and from Lua.
Synopsis
- type Peeker e a = StackIndex -> Peek e a
- runPeeker :: Peeker e a -> StackIndex -> LuaE e (Result a)
- data Result a
- = Success !a
- | Failure ByteString [Name]
- force :: LuaError e => Result a -> LuaE e a
- retrieving :: Name -> Peek e a -> Peek e a
- failure :: ByteString -> Result a
- resultToEither :: Result a -> Either String a
- peekNil :: Peeker e ()
- peekNoneOrNil :: Peeker e ()
- peekBool :: Peeker e Bool
- peekIntegral :: forall a e. (Integral a, Read a) => Peeker e a
- peekRealFloat :: forall a e. (RealFloat a, Read a) => Peeker e a
- peekByteString :: Peeker e ByteString
- peekLazyByteString :: Peeker e ByteString
- peekString :: Peeker e String
- peekText :: Peeker e Text
- peekStringy :: forall a e. IsString a => Peeker e a
- peekName :: Peeker e Name
- peekRead :: forall a e. Read a => Peeker e a
- peekKeyValuePairs :: LuaError e => Peeker e a -> Peeker e b -> Peeker e [(a, b)]
- peekList :: forall a e. LuaError e => Peeker e a -> Peeker e [a]
- peekMap :: (LuaError e, Ord a) => Peeker e a -> Peeker e b -> Peeker e (Map a b)
- peekSet :: (LuaError e, Ord a) => Peeker e a -> Peeker e (Set a)
- choice :: LuaError e => [Peeker e a] -> Peeker e a
- peekFieldRaw :: LuaError e => Peeker e a -> Name -> Peeker e a
- peekPair :: LuaError e => Peeker e a -> Peeker e b -> Peeker e (a, b)
- peekTriple :: LuaError e => Peeker e a -> Peeker e b -> Peeker e c -> Peeker e (a, b, c)
- newtype Peek e a = Peek {}
- forcePeek :: LuaError e => Peek e a -> LuaE e a
- liftLua :: LuaE e a -> Peek e a
- withContext :: Name -> Peek e a -> Peek e a
- failPeek :: forall a e. ByteString -> Peek e a
- lastly :: Peek e a -> LuaE e b -> Peek e a
- cleanup :: Peek e a -> Peek e a
- typeChecked :: Name -> (StackIndex -> LuaE e Bool) -> Peeker e a -> Peeker e a
- typeMismatchMessage :: Name -> StackIndex -> Peek e ByteString
- reportValueOnFailure :: Name -> (StackIndex -> LuaE e (Maybe a)) -> Peeker e a
- module HsLua.Marshalling.Push
- pushIterator :: forall a e. LuaError e => (a -> LuaE e NumResults) -> [a] -> LuaE e NumResults
Receiving values from Lua stack (Lua → Haskell)
type Peeker e a = StackIndex -> Peek e a Source #
Function to retrieve a value from Lua's stack.
Record to keep track of failure contexts while retrieving objects from the Lua stack.
Success !a | |
Failure ByteString [Name] | Error message and stack of contexts |
force :: LuaError e => Result a -> LuaE e a Source #
Force creation of an unwrapped result, throwing an exception if that's not possible.
retrieving :: Name -> Peek e a -> Peek e a Source #
Add context information to the peek traceback stack.
failure :: ByteString -> Result a Source #
Create a peek failure record from an error message.
resultToEither :: Result a -> Either String a Source #
Converts a Result into an Either, where Left
holds the reportable
string in case of an failure.
Primitive types
peekNoneOrNil :: Peeker e () Source #
Succeeds if the given index is not valid or if the value at this
index is nil
.
peekIntegral :: forall a e. (Integral a, Read a) => Peeker e a Source #
Retrieves an Integral
value from the Lua stack.
Strings
peekByteString :: Peeker e ByteString Source #
Retrieves a ByteString
as a raw string.
peekLazyByteString :: Peeker e ByteString Source #
Retrieves a lazy ByteString
as a raw string.
peekStringy :: forall a e. IsString a => Peeker e a Source #
Retrieves a String-like value from an UTF-8 encoded Lua string.
This should not be used to peek ByteString
values or other values
for which construction via fromString
can result in loss of
information.
Readable types
peekRead :: forall a e. Read a => Peeker e a Source #
Retrieves a value by getting a String from Lua, then using
readMaybe
to convert the String into a Haskell value.
Collections
peekKeyValuePairs :: LuaError e => Peeker e a -> Peeker e b -> Peeker e [(a, b)] Source #
Read a table into a list of pairs.
peekList :: forall a e. LuaError e => Peeker e a -> Peeker e [a] Source #
Reads a numerically indexed table t
into a list, where the length
of
the list is equal to rawlen(t)
. The operation will fail unless all
numerical fields between 1
and rawlen(t)
can be retrieved.
peekMap :: (LuaError e, Ord a) => Peeker e a -> Peeker e b -> Peeker e (Map a b) Source #
Retrieves a key-value Lua table as Map
.
peekSet :: (LuaError e, Ord a) => Peeker e a -> Peeker e (Set a) Source #
Retrieves a Set
from an idiomatic Lua representation. A
set in Lua is idiomatically represented as a table with the
elements as keys. Elements with falsy values are omitted.
Combinators
choice :: LuaError e => [Peeker e a] -> Peeker e a Source #
Try all peekers and return the result of the first to succeed.
peekFieldRaw :: LuaError e => Peeker e a -> Name -> Peeker e a Source #
Get value at key from a table.
peekPair :: LuaError e => Peeker e a -> Peeker e b -> Peeker e (a, b) Source #
Retrieves a value pair from a table. Expects the values to be stored in a numerically indexed table; does not access metamethods.
peekTriple :: LuaError e => Peeker e a -> Peeker e b -> Peeker e c -> Peeker e (a, b, c) Source #
Retrieves a value triple from a table. Expects the values to be stored in a numerically indexed table, with no metamethods.
Lua peek monad
Lua operation with an additional failure mode that can stack errors from different contexts; errors are not based on exceptions).
forcePeek :: LuaError e => Peek e a -> LuaE e a Source #
Converts a Peek action into a LuaE action, throwing an exception in case of a peek failure.
failPeek :: forall a e. ByteString -> Peek e a Source #
Fails the peek operation.
lastly :: Peek e a -> LuaE e b -> Peek e a Source #
Runs the peek action and Lua action in sequence, even if the peek action fails.
cleanup :: Peek e a -> Peek e a Source #
Runs the peek action, resetting the stack top afterwards. This can be used with peek actions that might otherwise leave elements on the stack in case of a failure.
Building Peek functions
Use test
to check whether the value at stack index n
has
the correct type and use peekfn
to convert it to a Haskell
value if possible. A successfully received value is wrapped
using the Right
constructor, while a type mismatch results
in Left PeekError
with the given error message.
:: Name | expected type |
-> StackIndex | index of offending value |
-> Peek e ByteString |
Generate a type mismatch error.
:: Name | expected type |
-> (StackIndex -> LuaE e (Maybe a)) | |
-> Peeker e a |
Report the expected and actual type of the value under the given index if conversion failed.
Pushing values to Lua stack (Haskell → Lua)
module HsLua.Marshalling.Push
Utilities
:: forall a e. LuaError e | |
=> (a -> LuaE e NumResults) | pusher for the values |
-> [a] | list to iterate over lazily |
-> LuaE e NumResults |
Pushes three values to the stack that can be used in a generic for loop to lazily iterate over all values in the list. Keeps the remaining list in a userdata state.
If the values pusher function returns
for a list
item, then this item will be skipped and the values for the next item
will be pushed.NumResults
0