hslua-marshalling-2.0.1: Marshalling of values between Haskell and Lua.
Copyright© 2007–2012 Gracjan Polak;
© 2012–2016 Ömer Sinan Ağacan;
© 2017-2021 Albert Krewinkel
LicenseMIT
MaintainerAlbert Krewinkel <tarleb+hslua@zeitkraut.de>
Safe HaskellNone
LanguageHaskell2010

HsLua.Marshalling

Description

Functions to push and retrieve data to and from Lua.

Synopsis

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.

runPeeker :: Peeker e a -> StackIndex -> LuaE e (Result a) Source #

Runs the peeker function.

data Result a Source #

Record to keep track of failure contexts while retrieving objects from the Lua stack.

Constructors

Success a 
Failure ByteString [Name]

Error message and stack of contexts

Instances

Instances details
Monad Result Source # 
Instance details

Defined in HsLua.Marshalling.Peek

Methods

(>>=) :: Result a -> (a -> Result b) -> Result b #

(>>) :: Result a -> Result b -> Result b #

return :: a -> Result a #

Functor Result Source # 
Instance details

Defined in HsLua.Marshalling.Peek

Methods

fmap :: (a -> b) -> Result a -> Result b #

(<$) :: a -> Result b -> Result a #

Applicative Result Source # 
Instance details

Defined in HsLua.Marshalling.Peek

Methods

pure :: a -> Result a #

(<*>) :: Result (a -> b) -> Result a -> Result b #

liftA2 :: (a -> b -> c) -> Result a -> Result b -> Result c #

(*>) :: Result a -> Result b -> Result b #

(<*) :: Result a -> Result b -> Result a #

Alternative Result Source # 
Instance details

Defined in HsLua.Marshalling.Peek

Methods

empty :: Result a #

(<|>) :: Result a -> Result a -> Result a #

some :: Result a -> Result [a] #

many :: Result a -> Result [a] #

Eq a => Eq (Result a) Source # 
Instance details

Defined in HsLua.Marshalling.Peek

Methods

(==) :: Result a -> Result a -> Bool #

(/=) :: Result a -> Result a -> Bool #

Show a => Show (Result a) Source # 
Instance details

Defined in HsLua.Marshalling.Peek

Methods

showsPrec :: Int -> Result a -> ShowS #

show :: Result a -> String #

showList :: [Result a] -> ShowS #

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

peekNil :: Peeker e () Source #

Succeeds if the value at the given index is nil.

peekNoneOrNil :: Peeker e () Source #

Succeeds if the given index is not valid or if the value at this index is nil.

peekBool :: Peeker e Bool Source #

Retrieves a Bool as a Lua boolean.

peekIntegral :: forall a e. (Integral a, Read a) => Peeker e a Source #

Retrieves an Integral value from the Lua stack.

peekRealFloat :: forall a e. (RealFloat a, Read a) => Peeker e a Source #

Retrieve a RealFloat (e.g., Float or Double) from the 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.

peekString :: Peeker e String Source #

Retrieves a String from an UTF-8 encoded Lua string.

peekText :: Peeker e Text Source #

Retrieves a Text value as an UTF-8 encoded 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.

peekName :: Peeker e Name Source #

Retrieves a Lua string as Name.

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.

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

newtype Peek e a Source #

Lua operation with an additional failure mode that can stack errors from different contexts; errors are not based on exceptions).

Constructors

Peek 

Fields

Instances

Instances details
Monad (Peek e) Source # 
Instance details

Defined in HsLua.Marshalling.Peek

Methods

(>>=) :: Peek e a -> (a -> Peek e b) -> Peek e b #

(>>) :: Peek e a -> Peek e b -> Peek e b #

return :: a -> Peek e a #

Functor (Peek e) Source # 
Instance details

Defined in HsLua.Marshalling.Peek

Methods

fmap :: (a -> b) -> Peek e a -> Peek e b #

(<$) :: a -> Peek e b -> Peek e a #

MonadFail (Peek e) Source # 
Instance details

Defined in HsLua.Marshalling.Peek

Methods

fail :: String -> Peek e a #

Applicative (Peek e) Source # 
Instance details

Defined in HsLua.Marshalling.Peek

Methods

pure :: a -> Peek e a #

(<*>) :: Peek e (a -> b) -> Peek e a -> Peek e b #

liftA2 :: (a -> b -> c) -> Peek e a -> Peek e b -> Peek e c #

(*>) :: Peek e a -> Peek e b -> Peek e b #

(<*) :: Peek e a -> Peek e b -> Peek e a #

Alternative (Peek e) Source # 
Instance details

Defined in HsLua.Marshalling.Peek

Methods

empty :: Peek e a #

(<|>) :: Peek e a -> Peek e a -> Peek e a #

some :: Peek e a -> Peek e [a] #

many :: Peek e a -> Peek e [a] #

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.

liftLua :: LuaE e a -> Peek e a Source #

Lifts a Lua operation into the Peek monad.

withContext :: Name -> Peek e a -> Peek e a Source #

Transform the result using the given function.

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

typeChecked Source #

Arguments

:: Name

expected type

-> (StackIndex -> LuaE e Bool)

pre-condition checker

-> Peeker e a 
-> Peeker e a 

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.

typeMismatchMessage Source #

Arguments

:: Name

expected type

-> StackIndex

index of offending value

-> Peek e ByteString 

Generate a type mismatch error.

reportValueOnFailure Source #

Arguments

:: 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)

Utilities

pushIterator Source #

Arguments

:: 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 NumResults 0 for a list item, then this item will be skipped and the values for the next item will be pushed.