Copyright | © 2020-2021 Albert Krewinkel |
---|---|
License | MIT |
Maintainer | Albert Krewinkel <tarleb+hslua@zeitkraut.de> |
Stability | beta |
Portability | Portable |
Safe Haskell | None |
Language | Haskell2010 |
Functions which unmarshal and retrieve Haskell values from Lua's stack.
Synopsis
- 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 :: Peeker e a -> Peeker e b -> Peeker e [(a, b)]
- peekList :: forall a e. LuaError e => Peeker e a -> Peeker e [a]
- peekMap :: Ord a => Peeker e a -> Peeker e b -> Peeker e (Map a b)
- peekSet :: 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
- peekIndexRaw :: LuaError e => Integer -> Peeker e a -> 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)
- typeChecked :: Name -> (StackIndex -> LuaE e Bool) -> Peeker e a -> Peeker e a
- reportValueOnFailure :: Name -> (StackIndex -> LuaE e (Maybe a)) -> Peeker e a
- typeMismatchMessage :: Name -> StackIndex -> Peek e ByteString
Peeking values from the stack
Primitives
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 :: 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 :: Ord a => Peeker e a -> Peeker e b -> Peeker e (Map a b) Source #
Retrieves a key-value Lua table as Map
.
peekSet :: 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.
peekIndexRaw :: LuaError e => Integer -> Peeker e a -> Peeker e a Source #
Get value at integer index 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.
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 -> LuaE e (Maybe a)) | |
-> Peeker e a |
Report the expected and actual type of the value under the given index if conversion failed.
:: Name | expected type |
-> StackIndex | index of offending value |
-> Peek e ByteString |
Generate a type mismatch error.