{-# LANGUAGE CPP #-}
module Foreign.Lua.Raw.Call
( HsFunction
, hslua_newhsfunction
, hslua_pushhsfunction
) where
import Foreign.C (CInt (CInt))
import Foreign.Ptr (Ptr, castPtr, nullPtr)
import Foreign.StablePtr (StablePtr, deRefStablePtr, newStablePtr)
import Foreign.Storable (peek)
import Foreign.Lua.Raw.Types
( NumResults (NumResults)
, State (State)
)
#ifdef ALLOW_UNSAFE_GC
#define SAFTY unsafe
#else
#define SAFTY safe
#endif
type HsFunction = State -> IO NumResults
foreign import ccall SAFTY "hslua.h hslua_hs_fun_ptr"
hslua_hs_fun_ptr :: State -> IO (Ptr ())
foreign import ccall SAFTY "hslua.h hslua_newhsfunction"
hslua_newhsfunction :: State -> StablePtr a -> IO ()
hslua_pushhsfunction :: State -> HsFunction -> IO ()
hslua_pushhsfunction l preCFn =
newStablePtr preCFn >>= hslua_newhsfunction l
{-# INLINABLE hslua_pushhsfunction #-}
hslua_call_wrapped_hs_fun :: HsFunction
hslua_call_wrapped_hs_fun l = do
udPtr <- hslua_hs_fun_ptr l
if udPtr == nullPtr
then error "Cannot call function; corrupted Lua object!"
else do
fn <- peek (castPtr udPtr) >>= deRefStablePtr
fn l
foreign export ccall hslua_call_wrapped_hs_fun :: HsFunction