Copyright | © 2020 Albert Krewinkel |
---|---|
License | MIT |
Maintainer | Albert Krewinkel <tarleb+hslua@zeitkraut.de> |
Stability | alpha |
Portability | Portable |
Safe Haskell | None |
Language | Haskell2010 |
Marshaling and documenting Haskell functions.
Synopsis
- data HaskellFunction = HaskellFunction {}
- toHsFnPrecursor :: a -> HsFnPrecursor a
- toHsFnPrecursorWithStartIndex :: StackIndex -> a -> HsFnPrecursor a
- applyParameter :: HsFnPrecursor (a -> b) -> Parameter a -> HsFnPrecursor b
- returnResult :: HsFnPrecursor a -> FunctionResult a -> HaskellFunction
- data Parameter a = Parameter {}
- data FunctionResult a = FunctionResult {}
- type FunctionResults a = [FunctionResult a]
- (<#>) :: HsFnPrecursor (a -> b) -> Parameter a -> HsFnPrecursor b
- (=#>) :: HsFnPrecursor a -> FunctionResults a -> HaskellFunction
- (#?) :: HaskellFunction -> Text -> HaskellFunction
- data FunctionDoc = FunctionDoc {}
- data ParameterDoc = ParameterDoc {}
- data FunctionResultDoc = FunctionResultDoc {}
- render :: FunctionDoc -> Text
- pushHaskellFunction :: HaskellFunction -> Lua ()
- parameter :: Peeker a -> Text -> Text -> Text -> Parameter a
- optionalParameter :: Peeker a -> Text -> Text -> Text -> Parameter (Maybe a)
- functionResult :: Pusher a -> Text -> Text -> FunctionResults a
Documentation
data HaskellFunction Source #
Haskell equivallent to CFunction, i.e., function callable from Lua.
toHsFnPrecursor :: a -> HsFnPrecursor a Source #
Create a HaskellFunction precursor from a pure function.
toHsFnPrecursorWithStartIndex :: StackIndex -> a -> HsFnPrecursor a Source #
applyParameter :: HsFnPrecursor (a -> b) -> Parameter a -> HsFnPrecursor b Source #
Partially apply a parameter.
returnResult :: HsFnPrecursor a -> FunctionResult a -> HaskellFunction Source #
Like
, but returns only a single result.returnResult
Function parameter.
data FunctionResult a Source #
Result of a call to a Haskell function.
type FunctionResults a = [FunctionResult a] Source #
List of function results in the order in which they are returned in Lua.
Operators
(<#>) :: HsFnPrecursor (a -> b) -> Parameter a -> HsFnPrecursor b infixl 8 Source #
Inline version of
.applyParameter
(=#>) :: HsFnPrecursor a -> FunctionResults a -> HaskellFunction infixl 8 Source #
Inline version of
.returnResult
(#?) :: HaskellFunction -> Text -> HaskellFunction infixl 8 Source #
Inline version of
.updateFunctionDescription
Documentation
data FunctionDoc Source #
Documentation for a Haskell function
Instances
Eq FunctionDoc Source # | |
Defined in Foreign.Lua.Call (==) :: FunctionDoc -> FunctionDoc -> Bool # (/=) :: FunctionDoc -> FunctionDoc -> Bool # | |
Ord FunctionDoc Source # | |
Defined in Foreign.Lua.Call compare :: FunctionDoc -> FunctionDoc -> Ordering # (<) :: FunctionDoc -> FunctionDoc -> Bool # (<=) :: FunctionDoc -> FunctionDoc -> Bool # (>) :: FunctionDoc -> FunctionDoc -> Bool # (>=) :: FunctionDoc -> FunctionDoc -> Bool # max :: FunctionDoc -> FunctionDoc -> FunctionDoc # min :: FunctionDoc -> FunctionDoc -> FunctionDoc # | |
Show FunctionDoc Source # | |
Defined in Foreign.Lua.Call showsPrec :: Int -> FunctionDoc -> ShowS # show :: FunctionDoc -> String # showList :: [FunctionDoc] -> ShowS # |
data ParameterDoc Source #
Documentation for function parameters.
Instances
Eq ParameterDoc Source # | |
Defined in Foreign.Lua.Call (==) :: ParameterDoc -> ParameterDoc -> Bool # (/=) :: ParameterDoc -> ParameterDoc -> Bool # | |
Ord ParameterDoc Source # | |
Defined in Foreign.Lua.Call compare :: ParameterDoc -> ParameterDoc -> Ordering # (<) :: ParameterDoc -> ParameterDoc -> Bool # (<=) :: ParameterDoc -> ParameterDoc -> Bool # (>) :: ParameterDoc -> ParameterDoc -> Bool # (>=) :: ParameterDoc -> ParameterDoc -> Bool # max :: ParameterDoc -> ParameterDoc -> ParameterDoc # min :: ParameterDoc -> ParameterDoc -> ParameterDoc # | |
Show ParameterDoc Source # | |
Defined in Foreign.Lua.Call showsPrec :: Int -> ParameterDoc -> ShowS # show :: ParameterDoc -> String # showList :: [ParameterDoc] -> ShowS # |
data FunctionResultDoc Source #
Documentation for the result of a function.
Instances
Eq FunctionResultDoc Source # | |
Defined in Foreign.Lua.Call (==) :: FunctionResultDoc -> FunctionResultDoc -> Bool # (/=) :: FunctionResultDoc -> FunctionResultDoc -> Bool # | |
Ord FunctionResultDoc Source # | |
Defined in Foreign.Lua.Call compare :: FunctionResultDoc -> FunctionResultDoc -> Ordering # (<) :: FunctionResultDoc -> FunctionResultDoc -> Bool # (<=) :: FunctionResultDoc -> FunctionResultDoc -> Bool # (>) :: FunctionResultDoc -> FunctionResultDoc -> Bool # (>=) :: FunctionResultDoc -> FunctionResultDoc -> Bool # max :: FunctionResultDoc -> FunctionResultDoc -> FunctionResultDoc # min :: FunctionResultDoc -> FunctionResultDoc -> FunctionResultDoc # | |
Show FunctionResultDoc Source # | |
Defined in Foreign.Lua.Call showsPrec :: Int -> FunctionResultDoc -> ShowS # show :: FunctionResultDoc -> String # showList :: [FunctionResultDoc] -> ShowS # |
render :: FunctionDoc -> Text Source #
Pushing to Lua
pushHaskellFunction :: HaskellFunction -> Lua () Source #
Convenience functions
:: Peeker a | method to retrieve value from Lua |
-> Text | expected Lua type |
-> Text | parameter name |
-> Text | parameter description |
-> Parameter a |
Creates a parameter.
:: Peeker a | method to retrieve the value from Lua |
-> Text | expected Lua type |
-> Text | parameter name |
-> Text | parameter description |
-> Parameter (Maybe a) |
Creates an optional parameter.
:: Pusher a | method to push the Haskell result to Lua |
-> Text | Lua type of result |
-> Text | result description |
-> FunctionResults a |
Creates a function result.