| Copyright | © 2020-2022 Albert Krewinkel |
|---|---|
| License | MIT |
| Maintainer | Albert Krewinkel <tarleb+hslua@zeitkraut.de> |
| Stability | alpha |
| Portability | Portable |
| Safe Haskell | None |
| Language | Haskell2010 |
HsLua.Packaging.Function
Description
Marshaling and documenting Haskell functions.
Synopsis
- data DocumentedFunction e = DocumentedFunction {}
- defun :: Name -> a -> HsFnPrecursor e a
- lambda :: a -> HsFnPrecursor e a
- applyParameter :: HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
- returnResult :: HsFnPrecursor e (LuaE e a) -> FunctionResult e a -> DocumentedFunction e
- returnResults :: HsFnPrecursor e (LuaE e a) -> FunctionResults e a -> DocumentedFunction e
- returnResultsOnStack :: HsFnPrecursor e (LuaE e NumResults) -> Text -> DocumentedFunction e
- updateFunctionDescription :: DocumentedFunction e -> Text -> DocumentedFunction e
- liftPure :: (a -> b) -> a -> LuaE e b
- liftPure2 :: (a -> b -> c) -> a -> b -> LuaE e c
- liftPure3 :: (a -> b -> c -> d) -> a -> b -> c -> LuaE e d
- liftPure4 :: (a -> b -> c -> d -> e) -> a -> b -> c -> d -> LuaE err e
- liftPure5 :: (a -> b -> c -> d -> e -> f) -> a -> b -> c -> d -> e -> LuaE err f
- data Parameter e a = Parameter {
- parameterPeeker :: Peeker e a
- parameterDoc :: ParameterDoc
- data FunctionResult e a = FunctionResult {
- fnResultPusher :: Pusher e a
- fnResultDoc :: ResultValueDoc
- type FunctionResults e a = [FunctionResult e a]
- (###) :: (a -> HsFnPrecursor e a) -> a -> HsFnPrecursor e a
- (<#>) :: HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
- (=#>) :: HsFnPrecursor e (LuaE e a) -> FunctionResults e a -> DocumentedFunction e
- (=?>) :: HsFnPrecursor e (LuaE e NumResults) -> Text -> DocumentedFunction e
- (#?) :: DocumentedFunction e -> Text -> DocumentedFunction e
- setName :: Name -> DocumentedFunction e -> DocumentedFunction e
- since :: DocumentedFunction e -> Version -> DocumentedFunction e
- pushDocumentedFunction :: LuaError e => DocumentedFunction e -> LuaE e ()
- parameter :: Peeker e a -> Text -> Text -> Text -> Parameter e a
- opt :: Parameter e a -> Parameter e (Maybe a)
- optionalParameter :: Peeker e a -> Text -> Text -> Text -> Parameter e (Maybe a)
- functionResult :: Pusher e a -> Text -> Text -> FunctionResults e a
- data HsFnPrecursor e a
- toHsFnPrecursor :: StackIndex -> Name -> a -> HsFnPrecursor e a
Documentation
data DocumentedFunction e Source #
Haskell equivallent to CFunction, i.e., function callable from Lua.
Constructors
| DocumentedFunction | |
Fields
| |
Creating documented functions
defun :: Name -> a -> HsFnPrecursor e a Source #
Begin wrapping a monadic Lua function such that it can be turned into a documented function exposable to Lua.
lambda :: a -> HsFnPrecursor e a Source #
Just like defun, but uses an empty name for the documented
function. Should be used when defining methods or operators.
applyParameter :: HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b Source #
Partially apply a parameter.
returnResult :: HsFnPrecursor e (LuaE e a) -> FunctionResult e a -> DocumentedFunction e Source #
Like , but returns only a single result.returnResult
returnResults :: HsFnPrecursor e (LuaE e a) -> FunctionResults e a -> DocumentedFunction e Source #
Take a HaskellFunction precursor and convert it into a full
HaskellFunction, using the given FunctionResults to return
the result to Lua.
returnResultsOnStack :: HsFnPrecursor e (LuaE e NumResults) -> Text -> DocumentedFunction e Source #
Take a HaskellFunction precursor and convert it into a full
HaskellFunction, using the given FunctionResults to return
the result to Lua.
updateFunctionDescription :: DocumentedFunction e -> Text -> DocumentedFunction e Source #
Updates the description of a Haskell function. Leaves the function unchanged if it has no documentation.
liftPure :: (a -> b) -> a -> LuaE e b Source #
Turns a pure function into a monadic Lua function.
The resulting function is strict.
liftPure2 :: (a -> b -> c) -> a -> b -> LuaE e c Source #
Turns a binary function into a Lua function.
The resulting function is strict in both its arguments.
liftPure3 :: (a -> b -> c -> d) -> a -> b -> c -> LuaE e d Source #
Turns a ternary function into a Lua function.
The resulting function is strict in all of its arguments.
liftPure4 :: (a -> b -> c -> d -> e) -> a -> b -> c -> d -> LuaE err e Source #
Turns a quarternary function into a Lua function.
The resulting function is strict in all of its arguments.
liftPure5 :: (a -> b -> c -> d -> e -> f) -> a -> b -> c -> d -> e -> LuaE err f Source #
Turns a quinary function into a Lua function.
The resulting function is strict in all of its arguments.
Types
Function parameter.
Constructors
| Parameter | |
Fields
| |
data FunctionResult e a Source #
Result of a call to a Haskell function.
Constructors
| FunctionResult | |
Fields
| |
type FunctionResults e a = [FunctionResult e a] Source #
List of function results in the order in which they are returned in Lua.
Operators
(###) :: (a -> HsFnPrecursor e a) -> a -> HsFnPrecursor e a infixl 8 Source #
Like ($), but left associative.
(<#>) :: HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b infixl 8 Source #
Inline version of .applyParameter
(=#>) :: HsFnPrecursor e (LuaE e a) -> FunctionResults e a -> DocumentedFunction e infixl 8 Source #
Inline version of .returnResults
(=?>) :: HsFnPrecursor e (LuaE e NumResults) -> Text -> DocumentedFunction e infixl 8 Source #
Return a flexible number of results that have been pushed by the function action.
(#?) :: DocumentedFunction e -> Text -> DocumentedFunction e infixl 8 Source #
Inline version of .updateFunctionDescription
Modifying functions
setName :: Name -> DocumentedFunction e -> DocumentedFunction e Source #
Renames a documented function.
since :: DocumentedFunction e -> Version -> DocumentedFunction e infixl 8 Source #
Sets the library version at which the function was introduced in its current form.
Pushing to Lua
pushDocumentedFunction :: LuaError e => DocumentedFunction e -> LuaE e () Source #
Pushes a documented Haskell function to the Lua stack, making it usable as a normal function in Lua. At the same time, the function docs are registered in the documentation table.
Convenience functions
Arguments
| :: Peeker e a | method to retrieve value from Lua |
| -> Text | expected Lua type |
| -> Text | parameter name |
| -> Text | parameter description |
| -> Parameter e a |
Creates a parameter.
Arguments
| :: Peeker e a | method to retrieve the value from Lua |
| -> Text | expected Lua type |
| -> Text | parameter name |
| -> Text | parameter description |
| -> Parameter e (Maybe a) |
Deprecated: Use `opt (parameter ...)` instead.
Creates an optional parameter.
DEPRECATED: Use opt (parameter ...) instead.
Arguments
| :: Pusher e a | method to push the Haskell result to Lua |
| -> Text | Lua type of result |
| -> Text | result description |
| -> FunctionResults e a |
Creates a function result.
Internal
data HsFnPrecursor e a Source #
Helper type used to create HaskellFunctions.
Instances
| Functor (HsFnPrecursor e) Source # | |
Defined in HsLua.Packaging.Function Methods fmap :: (a -> b) -> HsFnPrecursor e a -> HsFnPrecursor e b # (<$) :: a -> HsFnPrecursor e b -> HsFnPrecursor e a # | |
toHsFnPrecursor :: StackIndex -> Name -> a -> HsFnPrecursor e a Source #
Create a HaskellFunction precursor from a monadic function, selecting the stack index after which the first function parameter will be placed.