hslua-marshalling-2.3.0: Marshalling of values between Haskell and Lua.
Copyright© 2020-2023 Albert Krewinkel
LicenseMIT
MaintainerAlbert Krewinkel <tarleb@hslua.org>
Stabilitybeta
PortabilityPortable
Safe HaskellSafe-Inferred
LanguageHaskell2010

HsLua.Marshalling.Peek

Description

Types for unmarshalling of values from Lua.

Synopsis

Documentation

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
MonadFail Result Source # 
Instance details

Defined in HsLua.Marshalling.Peek

Methods

fail :: String -> Result a #

Foldable Result Source # 
Instance details

Defined in HsLua.Marshalling.Peek

Methods

fold :: Monoid m => Result m -> m #

foldMap :: Monoid m => (a -> m) -> Result a -> m #

foldMap' :: Monoid m => (a -> m) -> Result a -> m #

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

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

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

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

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

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

toList :: Result a -> [a] #

null :: Result a -> Bool #

length :: Result a -> Int #

elem :: Eq a => a -> Result a -> Bool #

maximum :: Ord a => Result a -> a #

minimum :: Ord a => Result a -> a #

sum :: Num a => Result a -> a #

product :: Num a => Result a -> a #

Traversable Result Source # 
Instance details

Defined in HsLua.Marshalling.Peek

Methods

traverse :: Applicative f => (a -> f b) -> Result a -> f (Result b) #

sequenceA :: Applicative f => Result (f a) -> f (Result a) #

mapM :: Monad m => (a -> m b) -> Result a -> m (Result b) #

sequence :: Monad m => Result (m a) -> m (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] #

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 #

Functor Result Source # 
Instance details

Defined in HsLua.Marshalling.Peek

Methods

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

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

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 #

MonadPlus Result Source # 
Instance details

Defined in HsLua.Marshalling.Peek

Methods

mzero :: Result a #

mplus :: Result a -> Result a -> Result a #

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 #

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

Defined in HsLua.Marshalling.Peek

Methods

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

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

isFailure :: Result a -> Bool Source #

Returns True iff the peek result is a Failure.

failure :: ByteString -> Result a Source #

Create a peek failure record from an error message.

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.

resultToEither :: Result a -> Either String a Source #

Converts a Result into an Either, where Left holds the reportable string in case of an failure.

toPeeker :: LuaError e => (StackIndex -> LuaE e a) -> Peeker e a Source #

Converts an old peek funtion to a Peeker.

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
MonadFail (Peek e) Source # 
Instance details

Defined in HsLua.Marshalling.Peek

Methods

fail :: String -> 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] #

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 #

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 #

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 #

MonadPlus (Peek e) Source # 
Instance details

Defined in HsLua.Marshalling.Peek

Methods

mzero :: Peek e a #

mplus :: Peek e a -> 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.

failPeek :: forall a e. ByteString -> Peek e a Source #

Fails the peek operation.

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.

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.