module HsLua.Core.Closures
( pushPreCFunction
, pushHaskellFunction
) where
import Prelude hiding (error)
import HsLua.Core.Error (LuaError (..))
import HsLua.Core.Primary (error)
import HsLua.Core.Types (LuaE, PreCFunction, HaskellFunction, liftLua, runWith)
import Lua.Call (hslua_pushhsfunction)
import qualified Control.Monad.Catch as Catch
pushPreCFunction :: PreCFunction -> LuaE e ()
pushPreCFunction :: forall e. PreCFunction -> LuaE e ()
pushPreCFunction PreCFunction
preCFn = (State -> IO ()) -> LuaE e ()
forall a e. (State -> IO a) -> LuaE e a
liftLua ((State -> IO ()) -> LuaE e ()) -> (State -> IO ()) -> LuaE e ()
forall a b. (a -> b) -> a -> b
$ \State
l ->
State -> PreCFunction -> IO ()
hslua_pushhsfunction State
l PreCFunction
preCFn
{-# INLINABLE pushPreCFunction #-}
pushHaskellFunction :: LuaError e => HaskellFunction e -> LuaE e ()
pushHaskellFunction :: forall e. LuaError e => HaskellFunction e -> LuaE e ()
pushHaskellFunction HaskellFunction e
fn = do
let preCFn :: PreCFunction
preCFn State
l = State -> HaskellFunction e -> IO NumResults
forall e a. State -> LuaE e a -> IO a
runWith State
l (HaskellFunction e -> HaskellFunction e
forall e. LuaError e => HaskellFunction e -> HaskellFunction e
exceptionToError HaskellFunction e
fn)
PreCFunction -> LuaE e ()
forall e. PreCFunction -> LuaE e ()
pushPreCFunction PreCFunction
preCFn
{-# INLINABLE pushHaskellFunction #-}
exceptionToError :: LuaError e => HaskellFunction e -> HaskellFunction e
exceptionToError :: forall e. LuaError e => HaskellFunction e -> HaskellFunction e
exceptionToError HaskellFunction e
op = HaskellFunction e
op HaskellFunction e -> (e -> HaskellFunction e) -> HaskellFunction e
forall e a.
(HasCallStack, Exception e) =>
LuaE e a -> (e -> LuaE e a) -> LuaE e a
forall (m :: * -> *) e a.
(MonadCatch m, HasCallStack, Exception e) =>
m a -> (e -> m a) -> m a
`Catch.catch` \e
e -> e -> LuaE e ()
forall e. LuaError e => e -> LuaE e ()
pushException e
e LuaE e () -> HaskellFunction e -> HaskellFunction e
forall a b. LuaE e a -> LuaE e b -> LuaE e b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> HaskellFunction e
forall e. LuaE e NumResults
error
{-# INLINABLE exceptionToError #-}