Copyright | © 2007–2012 Gracjan Polak; © 2012–2016 Ömer Sinan Ağacan; © 2017-2022 Albert Krewinkel |
---|---|
License | MIT |
Maintainer | Albert Krewinkel <tarleb+hslua@zeitkraut.de> |
Stability | beta |
Portability | non-portable (depends on GHC) |
Safe Haskell | None |
Language | Haskell2010 |
Convenience module which re-exports all classes and utility functions provided by the hslua-classes package.
Synopsis
- class Peekable a where
- peekEither :: (LuaError e, Peekable a) => StackIndex -> LuaE e (Either e a)
- class Pushable a where
- pushList :: (LuaError e, Pushable a) => [a] -> LuaE e ()
- class LuaError e => Exposable e a where
- partialApply :: StackIndex -> a -> Peek e NumResults
- toHaskellFunction :: forall e a. Exposable e a => a -> HaskellFunction e
- invoke :: Invokable a => Name -> a
- registerHaskellFunction :: Exposable e a => Name -> a -> LuaE e ()
- raiseError :: (LuaError e, Pushable a) => a -> LuaE e NumResults
- newtype Optional a = Optional {
- fromOptional :: Maybe a
- popValue :: (LuaError e, Peekable a) => LuaE e a
Receiving values from Lua stack (Lua → Haskell)
class Peekable a where Source #
A value that can be read from the Lua stack.
Instances
peekEither :: (LuaError e, Peekable a) => StackIndex -> LuaE e (Either e a) Source #
Try to convert the value at the given stack index to a Haskell value.
Returns Left
with the error on failure.
Pushing values to Lua stack (Haskell → Lua)
class Pushable a where Source #
A value that can be pushed to the Lua stack.
push :: LuaError e => a -> LuaE e () Source #
Pushes a value onto Lua stack, casting it into meaningfully nearest Lua type.
Instances
pushList :: (LuaError e, Pushable a) => [a] -> LuaE e () Source #
Push list as numerically indexed table.
Calling Functions
class LuaError e => Exposable e a where Source #
Operations and functions that can be pushed to the Lua stack. This
is a helper function not intended to be used directly. Use the
wrapper instead.toHaskellFunction
partialApply :: StackIndex -> a -> Peek e NumResults Source #
Helper function, called by
. Should do a
partial application of the argument at the given index to the
underlying function. Recurses if necessary, causing further partial
applications until the operation is a easily exposable to Lua.toHaskellFunction
Instances
LuaError e => Exposable e (HaskellFunction e) Source # | |
Defined in HsLua.Class.Exposable partialApply :: StackIndex -> HaskellFunction e -> Peek e NumResults Source # | |
(Peekable a, Exposable e b) => Exposable e (a -> b) Source # | |
Defined in HsLua.Class.Exposable partialApply :: StackIndex -> (a -> b) -> Peek e NumResults Source # | |
(LuaError e, Pushable a) => Exposable e (Peek e a) Source # | |
Defined in HsLua.Class.Exposable partialApply :: StackIndex -> Peek e a -> Peek e NumResults Source # | |
(LuaError e, Pushable a) => Exposable e (LuaE e a) Source # | |
Defined in HsLua.Class.Exposable partialApply :: StackIndex -> LuaE e a -> Peek e NumResults Source # |
toHaskellFunction :: forall e a. Exposable e a => a -> HaskellFunction e Source #
Convert a Haskell function to a function type directly exposable to Lua. Any Haskell function can be converted provided that:
Any exception of type e
will be caught.
Important: this does not catch exceptions other than e
;
exception handling must be done by the Haskell function. Failure to
do so will cause the program to crash.
E.g., the following code could be used to handle an Exception
of type FooException, if that type is an instance of
MonadCatch
and Pushable
:
toHaskellFunction (myFun `catchM` (\e -> raiseError (e :: FooException)))
invoke :: Invokable a => Name -> a Source #
Invoke a Lua function. Use as:
v <- invoke "proc" "abc" (1::Int) (5.0::Double)
registerHaskellFunction :: Exposable e a => Name -> a -> LuaE e () Source #
Imports a Haskell function and registers it at global name.
Utility functions and types
raiseError :: (LuaError e, Pushable a) => a -> LuaE e NumResults Source #
Raise a Lua error, using the given value as the error object.
Newtype wrapper intended to be used for optional Lua values. Nesting this type is strongly discouraged as missing values on inner levels are indistinguishable from missing values on an outer level; wrong values would be the likely result.
Optional | |
|