{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE OverloadedStrings #-}
{-|
Module      : HsLua.Packaging.Function
Copyright   : © 2020-2024 Albert Krewinkel
License     : MIT
Maintainer  : Albert Krewinkel <tarleb@hslua.org>
Stability   : alpha
Portability : Portable

Marshaling and documenting Haskell functions.
-}
module HsLua.Packaging.Function
  ( DocumentedFunction (..)
    -- * Creating documented functions
  , defun
  , lambda
  , applyParameter
  , returnResult
  , returnResults
  , returnResultsOnStack
  , updateFunctionDescription
  , liftPure
  , liftPure2
  , liftPure3
  , liftPure4
  , liftPure5
    -- ** Types
  , Parameter (..)
  , FunctionResult (..)
  , FunctionResults
    -- ** Operators
  , (###)
  , (<#>)
  , (=#>)
  , (=?>)
  , (#?)
    -- * Modifying functions
  , setName
  , since
    -- * Pushing to Lua
  , pushDocumentedFunction
    -- * Convenience functions
  , parameter
  , opt
  , optionalParameter
  , functionResult
    -- * Internal
  , HsFnPrecursor
  , toHsFnPrecursor
  ) where

import Control.Applicative ((<|>))
import Control.Monad ((<$!>), forM_)
import Data.Text (Text)
import Data.Version (Version)
import HsLua.Core
import HsLua.Marshalling
import HsLua.Packaging.Documentation
import HsLua.Packaging.Types
import HsLua.Typing (TypeSpec)
import qualified HsLua.Core as Lua
import qualified HsLua.Core.Utf8 as Utf8

--
-- Haskell function building
--

-- | Helper type used to create 'HaskellFunction's.
data HsFnPrecursor e a = HsFnPrecursor
  { forall e a. HsFnPrecursor e a -> Peek e a
hsFnPrecursorAction :: Peek e a
  , forall e a. HsFnPrecursor e a -> StackIndex
hsFnMaxParameterIdx :: StackIndex
  , forall e a. HsFnPrecursor e a -> [ParameterDoc]
hsFnParameterDocs :: [ParameterDoc]
  , forall e a. HsFnPrecursor e a -> Name
hsFnName :: Name
  }
  deriving ((forall a b. (a -> b) -> HsFnPrecursor e a -> HsFnPrecursor e b)
-> (forall a b. a -> HsFnPrecursor e b -> HsFnPrecursor e a)
-> Functor (HsFnPrecursor e)
forall a b. a -> HsFnPrecursor e b -> HsFnPrecursor e a
forall a b. (a -> b) -> HsFnPrecursor e a -> HsFnPrecursor e b
forall e a b. a -> HsFnPrecursor e b -> HsFnPrecursor e a
forall e a b. (a -> b) -> HsFnPrecursor e a -> HsFnPrecursor e b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall e a b. (a -> b) -> HsFnPrecursor e a -> HsFnPrecursor e b
fmap :: forall a b. (a -> b) -> HsFnPrecursor e a -> HsFnPrecursor e b
$c<$ :: forall e a b. a -> HsFnPrecursor e b -> HsFnPrecursor e a
<$ :: forall a b. a -> HsFnPrecursor e b -> HsFnPrecursor e a
Functor)

-- | Result of a call to a Haskell function.
data FunctionResult e a
  = FunctionResult
  { forall e a. FunctionResult e a -> Pusher e a
fnResultPusher  :: Pusher e a
  , forall e a. FunctionResult e a -> ResultValueDoc
fnResultDoc     :: ResultValueDoc
  }

-- | List of function results in the order in which they are
-- returned in Lua.
type FunctionResults e a = [FunctionResult e a]

-- | Function parameter.
data Parameter e a = Parameter
  { forall e a. Parameter e a -> Peeker e a
parameterPeeker :: Peeker e a
  , forall e a. Parameter e a -> ParameterDoc
parameterDoc    :: ParameterDoc
  }


-- | Begin wrapping a monadic Lua function such that it can be turned
-- into a documented function exposable to Lua.
defun :: Name -> a -> HsFnPrecursor e a
defun :: forall a e. Name -> a -> HsFnPrecursor e a
defun = StackIndex -> Name -> a -> HsFnPrecursor e a
forall a e. StackIndex -> Name -> a -> HsFnPrecursor e a
toHsFnPrecursor (CInt -> StackIndex
StackIndex CInt
0)

-- | Just like @defun@, but uses an empty name for the documented
-- function. Should be used when defining methods or operators.
lambda :: a -> HsFnPrecursor e a
lambda :: forall a e. a -> HsFnPrecursor e a
lambda = Name -> a -> HsFnPrecursor e a
forall a e. Name -> a -> HsFnPrecursor e a
defun (ByteString -> Name
Name ByteString
forall a. Monoid a => a
mempty)

-- | Turns a pure function into a monadic Lua function.
--
-- The resulting function is strict.
liftPure :: (a -> b)
         -> (a -> LuaE e b)
liftPure :: forall a b e. (a -> b) -> a -> LuaE e b
liftPure a -> b
f !a
a = b -> LuaE e b
forall a. a -> LuaE e a
forall (m :: * -> *) a. Monad m => a -> m a
return (b -> LuaE e b) -> b -> LuaE e b
forall a b. (a -> b) -> a -> b
$! a -> b
f a
a

-- | Turns a binary function into a Lua function.
--
-- The resulting function is strict in both its arguments.
liftPure2 :: (a -> b -> c)
          -> (a -> b -> LuaE e c)
liftPure2 :: forall a b c e. (a -> b -> c) -> a -> b -> LuaE e c
liftPure2 a -> b -> c
f !a
a !b
b = c -> LuaE e c
forall a. a -> LuaE e a
forall (m :: * -> *) a. Monad m => a -> m a
return (c -> LuaE e c) -> c -> LuaE e c
forall a b. (a -> b) -> a -> b
$! a -> b -> c
f a
a b
b

-- | Turns a ternary function into a Lua function.
--
-- The resulting function is strict in all of its arguments.
liftPure3 :: (a -> b -> c -> d)
          -> (a -> b -> c -> LuaE e d)
liftPure3 :: forall a b c d e. (a -> b -> c -> d) -> a -> b -> c -> LuaE e d
liftPure3 a -> b -> c -> d
f !a
a !b
b !c
c = d -> LuaE e d
forall a. a -> LuaE e a
forall (m :: * -> *) a. Monad m => a -> m a
return (d -> LuaE e d) -> d -> LuaE e d
forall a b. (a -> b) -> a -> b
$! a -> b -> c -> d
f a
a b
b c
c

-- | Turns a quarternary 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)
liftPure4 :: forall a b c d e err.
(a -> b -> c -> d -> e) -> a -> b -> c -> d -> LuaE err e
liftPure4 a -> b -> c -> d -> e
f !a
a !b
b !c
c !d
d = e -> LuaE err e
forall a. a -> LuaE err a
forall (m :: * -> *) a. Monad m => a -> m a
return (e -> LuaE err e) -> e -> LuaE err e
forall a b. (a -> b) -> a -> b
$! a -> b -> c -> d -> e
f a
a b
b c
c d
d

-- | Turns a quinary 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)
liftPure5 :: forall a b c d e f err.
(a -> b -> c -> d -> e -> f) -> a -> b -> c -> d -> e -> LuaE err f
liftPure5 a -> b -> c -> d -> e -> f
f !a
a !b
b !c
c !d
d !e
e = f -> LuaE err f
forall a. a -> LuaE err a
forall (m :: * -> *) a. Monad m => a -> m a
return (f -> LuaE err f) -> f -> LuaE err f
forall a b. (a -> b) -> a -> b
$! a -> b -> c -> d -> e -> f
f a
a b
b c
c d
d e
e

-- | Create a HaskellFunction precursor from a monadic function,
-- selecting the stack index after which the first function parameter
-- will be placed.
toHsFnPrecursor :: StackIndex -> Name -> a -> HsFnPrecursor e a
toHsFnPrecursor :: forall a e. StackIndex -> Name -> a -> HsFnPrecursor e a
toHsFnPrecursor StackIndex
idx Name
name a
f = HsFnPrecursor
  { hsFnPrecursorAction :: Peek e a
hsFnPrecursorAction = a -> Peek e a
forall a. a -> Peek e a
forall (m :: * -> *) a. Monad m => a -> m a
return a
f
  , hsFnMaxParameterIdx :: StackIndex
hsFnMaxParameterIdx = StackIndex
idx
  , hsFnParameterDocs :: [ParameterDoc]
hsFnParameterDocs = [ParameterDoc]
forall a. Monoid a => a
mempty
  , hsFnName :: Name
hsFnName = Name
name
  }

-- | Partially apply a parameter.
applyParameter :: HsFnPrecursor e (a -> b)
               -> Parameter e a
               -> HsFnPrecursor e b
applyParameter :: forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
applyParameter HsFnPrecursor e (a -> b)
bldr Parameter e a
param = do
  let action :: Peek e (a -> b)
action = HsFnPrecursor e (a -> b) -> Peek e (a -> b)
forall e a. HsFnPrecursor e a -> Peek e a
hsFnPrecursorAction HsFnPrecursor e (a -> b)
bldr
  let i :: StackIndex
i = HsFnPrecursor e (a -> b) -> StackIndex
forall e a. HsFnPrecursor e a -> StackIndex
hsFnMaxParameterIdx HsFnPrecursor e (a -> b)
bldr StackIndex -> StackIndex -> StackIndex
forall a. Num a => a -> a -> a
+ StackIndex
1
  let context :: Name
context = ByteString -> Name
Name (ByteString -> Name) -> (Text -> ByteString) -> Text -> Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
Utf8.fromText (Text -> Name) -> Text -> Name
forall a b. (a -> b) -> a -> b
$ Text
"function argument " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
        (ParameterDoc -> Text
parameterName (ParameterDoc -> Text)
-> (Parameter e a -> ParameterDoc) -> Parameter e a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Parameter e a -> ParameterDoc
forall e a. Parameter e a -> ParameterDoc
parameterDoc) Parameter e a
param
  let nextAction :: (a -> a) -> Peek e a
nextAction a -> a
f = Name -> Peek e a -> Peek e a
forall e a. Name -> Peek e a -> Peek e a
retrieving Name
context (Peek e a -> Peek e a) -> Peek e a -> Peek e a
forall a b. (a -> b) -> a -> b
$ do
        !a
x <- Parameter e a -> Peeker e a
forall e a. Parameter e a -> Peeker e a
parameterPeeker Parameter e a
param StackIndex
i
        a -> Peek e a
forall a. a -> Peek e a
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> Peek e a) -> a -> Peek e a
forall a b. (a -> b) -> a -> b
$ a -> a
f a
x
  HsFnPrecursor e (a -> b)
bldr
    { hsFnPrecursorAction = action >>= nextAction
    , hsFnMaxParameterIdx = i
    , hsFnParameterDocs = parameterDoc param : hsFnParameterDocs bldr
    }

-- | Take a 'HaskellFunction' precursor and convert it into a full
-- 'HaskellFunction', using the given 'FunctionResult's to return
-- the result to Lua.
returnResults :: HsFnPrecursor e (LuaE e a)
              -> FunctionResults e a
              -> DocumentedFunction e
returnResults :: forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
returnResults HsFnPrecursor e (LuaE e a)
bldr FunctionResults e a
fnResults = DocumentedFunction
  { callFunction :: LuaE e NumResults
callFunction = do
      Result (LuaE e a)
hsResult <- Peek e (LuaE e a) -> LuaE e (Result (LuaE e a))
forall e a. Peek e a -> LuaE e (Result a)
runPeek
                (Peek e (LuaE e a) -> LuaE e (Result (LuaE e a)))
-> (Peek e (LuaE e a) -> Peek e (LuaE e a))
-> Peek e (LuaE e a)
-> LuaE e (Result (LuaE e a))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> Peek e (LuaE e a) -> Peek e (LuaE e a)
forall e a. Name -> Peek e a -> Peek e a
retrieving (Name
"arguments for function " Name -> Name -> Name
forall a. Semigroup a => a -> a -> a
<> HsFnPrecursor e (LuaE e a) -> Name
forall e a. HsFnPrecursor e a -> Name
hsFnName HsFnPrecursor e (LuaE e a)
bldr)
                (Peek e (LuaE e a) -> LuaE e (Result (LuaE e a)))
-> Peek e (LuaE e a) -> LuaE e (Result (LuaE e a))
forall a b. (a -> b) -> a -> b
$ HsFnPrecursor e (LuaE e a) -> Peek e (LuaE e a)
forall e a. HsFnPrecursor e a -> Peek e a
hsFnPrecursorAction HsFnPrecursor e (LuaE e a)
bldr
      case Result (LuaE e a) -> Either String (LuaE e a)
forall a. Result a -> Either String a
resultToEither Result (LuaE e a)
hsResult of
        Left String
err -> do
          String -> LuaE e ()
forall e. String -> LuaE e ()
pushString String
err
          LuaE e NumResults
forall e. LuaE e NumResults
Lua.error
        Right LuaE e a
x -> do
          a
result <- LuaE e a
x
          FunctionResults e a
-> (FunctionResult e a -> LuaE e ()) -> LuaE e ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ FunctionResults e a
fnResults ((FunctionResult e a -> LuaE e ()) -> LuaE e ())
-> (FunctionResult e a -> LuaE e ()) -> LuaE e ()
forall a b. (a -> b) -> a -> b
$ \(FunctionResult Pusher e a
push ResultValueDoc
_) -> Pusher e a
push a
result
          NumResults -> LuaE e NumResults
forall a. a -> LuaE e a
forall (m :: * -> *) a. Monad m => a -> m a
return (NumResults -> LuaE e NumResults)
-> NumResults -> LuaE e NumResults
forall a b. (a -> b) -> a -> b
$! CInt -> NumResults
NumResults (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> Int -> CInt
forall a b. (a -> b) -> a -> b
$ FunctionResults e a -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length FunctionResults e a
fnResults)
  , functionName :: Name
functionName = HsFnPrecursor e (LuaE e a) -> Name
forall e a. HsFnPrecursor e a -> Name
hsFnName HsFnPrecursor e (LuaE e a)
bldr
  , functionDoc :: FunctionDoc
functionDoc = FunctionDoc
    { functionDescription :: Text
functionDescription = Text
""
    , parameterDocs :: [ParameterDoc]
parameterDocs = [ParameterDoc] -> [ParameterDoc]
forall a. [a] -> [a]
reverse ([ParameterDoc] -> [ParameterDoc])
-> [ParameterDoc] -> [ParameterDoc]
forall a b. (a -> b) -> a -> b
$ HsFnPrecursor e (LuaE e a) -> [ParameterDoc]
forall e a. HsFnPrecursor e a -> [ParameterDoc]
hsFnParameterDocs HsFnPrecursor e (LuaE e a)
bldr
    , functionResultsDocs :: ResultsDoc
functionResultsDocs = [ResultValueDoc] -> ResultsDoc
ResultsDocList ([ResultValueDoc] -> ResultsDoc) -> [ResultValueDoc] -> ResultsDoc
forall a b. (a -> b) -> a -> b
$ (FunctionResult e a -> ResultValueDoc)
-> FunctionResults e a -> [ResultValueDoc]
forall a b. (a -> b) -> [a] -> [b]
map FunctionResult e a -> ResultValueDoc
forall e a. FunctionResult e a -> ResultValueDoc
fnResultDoc FunctionResults e a
fnResults
    , functionSince :: Maybe Version
functionSince = Maybe Version
forall a. Maybe a
Nothing
    }
  }

-- | Take a 'HaskellFunction' precursor and convert it into a full
-- 'HaskellFunction', using the given 'FunctionResult's to return
-- the result to Lua.
returnResultsOnStack :: HsFnPrecursor e (LuaE e NumResults)
                     -> Text
                     -> DocumentedFunction e
returnResultsOnStack :: forall e.
HsFnPrecursor e (LuaE e NumResults) -> Text -> DocumentedFunction e
returnResultsOnStack HsFnPrecursor e (LuaE e NumResults)
bldr Text
desc = DocumentedFunction
  { callFunction :: LuaE e NumResults
callFunction = do
      Result (LuaE e NumResults)
hsResult <- Peek e (LuaE e NumResults) -> LuaE e (Result (LuaE e NumResults))
forall e a. Peek e a -> LuaE e (Result a)
runPeek
                (Peek e (LuaE e NumResults) -> LuaE e (Result (LuaE e NumResults)))
-> (Peek e (LuaE e NumResults) -> Peek e (LuaE e NumResults))
-> Peek e (LuaE e NumResults)
-> LuaE e (Result (LuaE e NumResults))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> Peek e (LuaE e NumResults) -> Peek e (LuaE e NumResults)
forall e a. Name -> Peek e a -> Peek e a
retrieving (Name
"arguments for function " Name -> Name -> Name
forall a. Semigroup a => a -> a -> a
<> HsFnPrecursor e (LuaE e NumResults) -> Name
forall e a. HsFnPrecursor e a -> Name
hsFnName HsFnPrecursor e (LuaE e NumResults)
bldr)
                (Peek e (LuaE e NumResults) -> LuaE e (Result (LuaE e NumResults)))
-> Peek e (LuaE e NumResults)
-> LuaE e (Result (LuaE e NumResults))
forall a b. (a -> b) -> a -> b
$ HsFnPrecursor e (LuaE e NumResults) -> Peek e (LuaE e NumResults)
forall e a. HsFnPrecursor e a -> Peek e a
hsFnPrecursorAction HsFnPrecursor e (LuaE e NumResults)
bldr
      case Result (LuaE e NumResults) -> Either String (LuaE e NumResults)
forall a. Result a -> Either String a
resultToEither Result (LuaE e NumResults)
hsResult of
        Left String
err -> do
          String -> LuaE e ()
forall e. String -> LuaE e ()
pushString String
err
          LuaE e NumResults
forall e. LuaE e NumResults
Lua.error
        Right LuaE e NumResults
x -> LuaE e NumResults
x
  , functionName :: Name
functionName = HsFnPrecursor e (LuaE e NumResults) -> Name
forall e a. HsFnPrecursor e a -> Name
hsFnName HsFnPrecursor e (LuaE e NumResults)
bldr
  , functionDoc :: FunctionDoc
functionDoc = FunctionDoc
    { functionDescription :: Text
functionDescription = Text
""
    , parameterDocs :: [ParameterDoc]
parameterDocs = [ParameterDoc] -> [ParameterDoc]
forall a. [a] -> [a]
reverse ([ParameterDoc] -> [ParameterDoc])
-> [ParameterDoc] -> [ParameterDoc]
forall a b. (a -> b) -> a -> b
$ HsFnPrecursor e (LuaE e NumResults) -> [ParameterDoc]
forall e a. HsFnPrecursor e a -> [ParameterDoc]
hsFnParameterDocs HsFnPrecursor e (LuaE e NumResults)
bldr
    , functionResultsDocs :: ResultsDoc
functionResultsDocs = Text -> ResultsDoc
ResultsDocMult Text
desc
    , functionSince :: Maybe Version
functionSince = Maybe Version
forall a. Maybe a
Nothing
    }
  }

-- | Like @'returnResult'@, but returns only a single result.
returnResult :: HsFnPrecursor e (LuaE e a)
             -> FunctionResult e a
             -> DocumentedFunction e
returnResult :: forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResult e a -> DocumentedFunction e
returnResult HsFnPrecursor e (LuaE e a)
bldr = HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
returnResults HsFnPrecursor e (LuaE e a)
bldr (FunctionResults e a -> DocumentedFunction e)
-> (FunctionResult e a -> FunctionResults e a)
-> FunctionResult e a
-> DocumentedFunction e
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FunctionResult e a -> FunctionResults e a -> FunctionResults e a
forall a. a -> [a] -> [a]
:[])

-- | Updates the description of a Haskell function. Leaves the function
-- unchanged if it has no documentation.
updateFunctionDescription :: DocumentedFunction e
                          -> Text
                          -> DocumentedFunction e
updateFunctionDescription :: forall e. DocumentedFunction e -> Text -> DocumentedFunction e
updateFunctionDescription DocumentedFunction e
fn Text
desc =
  let fnDoc :: FunctionDoc
fnDoc = DocumentedFunction e -> FunctionDoc
forall e. DocumentedFunction e -> FunctionDoc
functionDoc DocumentedFunction e
fn
  in DocumentedFunction e
fn { functionDoc = fnDoc { functionDescription = desc} }

-- | Renames a documented function.
setName :: Name -> DocumentedFunction e -> DocumentedFunction e
setName :: forall e. Name -> DocumentedFunction e -> DocumentedFunction e
setName Name
name DocumentedFunction e
fn = DocumentedFunction e
fn { functionName = name }

-- | Sets the library version at which the function was introduced in its
-- current form.
since :: DocumentedFunction e -> Version -> DocumentedFunction e
since :: forall e. DocumentedFunction e -> Version -> DocumentedFunction e
since DocumentedFunction e
fn Version
version =
  let fnDoc :: FunctionDoc
fnDoc = DocumentedFunction e -> FunctionDoc
forall e. DocumentedFunction e -> FunctionDoc
functionDoc DocumentedFunction e
fn
  in DocumentedFunction e
fn { functionDoc = fnDoc { functionSince = Just version  }}

--
-- Operators
--

infixl 8 ###, <#>, =#>, =?>, #?, `since`

-- | Like '($)', but left associative.
(###) :: (a -> HsFnPrecursor e a) -> a -> HsFnPrecursor e a
### :: forall a e. (a -> HsFnPrecursor e a) -> a -> HsFnPrecursor e a
(###) = (a -> HsFnPrecursor e a) -> a -> HsFnPrecursor e a
forall a b. (a -> b) -> a -> b
($)

-- | Inline version of @'applyParameter'@.
(<#>) :: HsFnPrecursor e (a -> b)
      -> Parameter e a
      -> HsFnPrecursor e b
<#> :: forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
(<#>) = HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
applyParameter

-- | Inline version of @'returnResults'@.
(=#>) :: HsFnPrecursor e (LuaE e a)
      -> FunctionResults e a
      -> DocumentedFunction e
=#> :: forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
(=#>) = HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
returnResults

-- | Return a flexible number of results that have been pushed by the
-- function action.
(=?>) :: HsFnPrecursor e (LuaE e NumResults)
      -> Text
      -> DocumentedFunction e
=?> :: forall e.
HsFnPrecursor e (LuaE e NumResults) -> Text -> DocumentedFunction e
(=?>) = HsFnPrecursor e (LuaE e NumResults) -> Text -> DocumentedFunction e
forall e.
HsFnPrecursor e (LuaE e NumResults) -> Text -> DocumentedFunction e
returnResultsOnStack

-- | Inline version of @'updateFunctionDescription'@.
(#?) :: DocumentedFunction e -> Text -> DocumentedFunction e
#? :: forall e. DocumentedFunction e -> Text -> DocumentedFunction e
(#?) = DocumentedFunction e -> Text -> DocumentedFunction e
forall e. DocumentedFunction e -> Text -> DocumentedFunction e
updateFunctionDescription

--
-- Push to Lua
--

-- | 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.
pushDocumentedFunction :: LuaError e
                       => DocumentedFunction e -> LuaE e ()
pushDocumentedFunction :: forall e. LuaError e => DocumentedFunction e -> LuaE e ()
pushDocumentedFunction DocumentedFunction e
fn = do
  HaskellFunction e -> LuaE e ()
forall e. LuaError e => HaskellFunction e -> LuaE e ()
Lua.pushHaskellFunction (HaskellFunction e -> LuaE e ()) -> HaskellFunction e -> LuaE e ()
forall a b. (a -> b) -> a -> b
$ DocumentedFunction e -> HaskellFunction e
forall e. DocumentedFunction e -> LuaE e NumResults
callFunction DocumentedFunction e
fn  -- push function
  Pusher e (DocumentedFunction e)
forall e. LuaError e => DocumentedFunction e -> LuaE e ()
pushFunctionDoc DocumentedFunction e
fn                         -- function documentation
  StackIndex -> LuaE e ()
forall e. LuaError e => StackIndex -> LuaE e ()
registerDocumentation (CInt -> StackIndex
Lua.nth CInt
2)          -- store documentation

--
-- Convenience functions
--

-- | Creates a parameter.
parameter :: Peeker e a   -- ^ method to retrieve value from Lua
          -> TypeSpec     -- ^ expected Lua type
          -> Text         -- ^ parameter name
          -> Text         -- ^ parameter description
          -> Parameter e a
parameter :: forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker e a
peeker TypeSpec
type_ Text
name Text
desc = Parameter
  { parameterPeeker :: Peeker e a
parameterPeeker = Peeker e a
peeker
  , parameterDoc :: ParameterDoc
parameterDoc = ParameterDoc
    { parameterName :: Text
parameterName = Text
name
    , parameterDescription :: Text
parameterDescription = Text
desc
    , parameterType :: TypeSpec
parameterType = TypeSpec
type_
    , parameterIsOptional :: Bool
parameterIsOptional = Bool
False
    }
  }

-- | Makes a parameter optional.
opt :: Parameter e a -> Parameter e (Maybe a)
opt :: forall e a. Parameter e a -> Parameter e (Maybe a)
opt Parameter e a
p = Parameter
  { parameterPeeker :: Peeker e (Maybe a)
parameterPeeker = \StackIndex
idx ->
      (Maybe a
forall a. Maybe a
Nothing Maybe a -> Peek e () -> Peek e (Maybe a)
forall a b. a -> Peek e b -> Peek e a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Peeker e ()
forall e. Peeker e ()
peekNoneOrNil StackIndex
idx) Peek e (Maybe a) -> Peek e (Maybe a) -> Peek e (Maybe a)
forall a. Peek e a -> Peek e a -> Peek e a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
      (a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> Peek e a -> Peek e (Maybe a)
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> Parameter e a -> Peeker e a
forall e a. Parameter e a -> Peeker e a
parameterPeeker Parameter e a
p StackIndex
idx)
  , parameterDoc :: ParameterDoc
parameterDoc = (Parameter e a -> ParameterDoc
forall e a. Parameter e a -> ParameterDoc
parameterDoc Parameter e a
p){ parameterIsOptional = True }
  }

-- | Creates an optional parameter.
--
-- DEPRECATED: Use @opt (parameter ...)@ instead.
optionalParameter :: Peeker e a   -- ^ method to retrieve the value from Lua
                  -> TypeSpec     -- ^ expected Lua type
                  -> Text         -- ^ parameter name
                  -> Text         -- ^ parameter description
                  -> Parameter e (Maybe a)
optionalParameter :: forall e a.
Peeker e a -> TypeSpec -> Text -> Text -> Parameter e (Maybe a)
optionalParameter Peeker e a
peeker TypeSpec
type_ Text
name Text
desc = Parameter e a -> Parameter e (Maybe a)
forall e a. Parameter e a -> Parameter e (Maybe a)
opt (Parameter e a -> Parameter e (Maybe a))
-> Parameter e a -> Parameter e (Maybe a)
forall a b. (a -> b) -> a -> b
$
  Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
forall e a. Peeker e a -> TypeSpec -> Text -> Text -> Parameter e a
parameter Peeker e a
peeker TypeSpec
type_ Text
name Text
desc
{-# DEPRECATED optionalParameter "Use `opt (parameter ...)` instead." #-}

-- | Creates a function result.
functionResult :: Pusher e a      -- ^ method to push the Haskell result to Lua
               -> TypeSpec        -- ^ Lua type of result
               -> Text            -- ^ result description
               -> FunctionResults e a
functionResult :: forall e a. Pusher e a -> TypeSpec -> Text -> FunctionResults e a
functionResult Pusher e a
pusher TypeSpec
type_ Text
desc = (FunctionResult e a -> [FunctionResult e a] -> [FunctionResult e a]
forall a. a -> [a] -> [a]
:[]) (FunctionResult e a -> [FunctionResult e a])
-> FunctionResult e a -> [FunctionResult e a]
forall a b. (a -> b) -> a -> b
$ FunctionResult
  { fnResultPusher :: Pusher e a
fnResultPusher = Pusher e a
pusher
  , fnResultDoc :: ResultValueDoc
fnResultDoc = ResultValueDoc
                  { resultValueType :: TypeSpec
resultValueType = TypeSpec
type_
                  , resultValueDescription :: Text
resultValueDescription = Text
desc
                  }
  }