{-# LINE 1 "src/Foreign/Lua/FunctionCalling.hsc" #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Foreign.Lua.FunctionCalling
( Peekable (..)
, LuaCallFunc (..)
, ToHaskellFunction (..)
, HaskellFunction
, Pushable (..)
, PreCFunction
, toHaskellFunction
, callFunc
, freeCFunction
, newCFunction
, pushHaskellFunction
, registerHaskellFunction
) where
import Data.ByteString (ByteString)
import Data.Monoid ((<>))
import Foreign.C (CInt (..))
import Foreign.Lua.Core as Lua
import Foreign.Lua.Types
import Foreign.Lua.Userdata ( ensureUserdataMetatable, pushAnyWithMetatable
, toAnyWithName )
import Foreign.Lua.Util (getglobal', popValue, raiseError)
import Foreign.Ptr (freeHaskellFunPtr)
type PreCFunction = Lua.State -> IO NumResults
type HaskellFunction = Lua NumResults
class ToHaskellFunction a where
toHsFun :: StackIndex -> a -> Lua NumResults
instance {-# OVERLAPPING #-} ToHaskellFunction HaskellFunction where
toHsFun _ = id
instance Pushable a => ToHaskellFunction (Lua a) where
toHsFun _narg x = 1 <$ (x >>= push)
instance (Peekable a, ToHaskellFunction b) =>
ToHaskellFunction (a -> b) where
toHsFun narg f = getArg >>= toHsFun (narg + 1) . f
where
getArg = Lua.withExceptionMessage (errorPrefix <>) (peek narg)
errorPrefix = "could not read argument " <>
show (fromStackIndex narg) <> ": "
toHaskellFunction :: ToHaskellFunction a => a -> HaskellFunction
toHaskellFunction a = toHsFun 1 a `catchException` \(Lua.Exception msg) ->
raiseError ("Error during function call: " <> msg)
newCFunction :: ToHaskellFunction a => a -> Lua CFunction
newCFunction = liftIO . mkWrapper . flip runWith . toHaskellFunction
foreign import ccall "wrapper"
mkWrapper :: PreCFunction -> IO CFunction
freeCFunction :: CFunction -> Lua ()
freeCFunction = liftIO . freeHaskellFunPtr
class LuaCallFunc a where
callFunc' :: String -> Lua () -> NumArgs -> a
instance Peekable a => LuaCallFunc (Lua a) where
callFunc' fnName pushArgs nargs = do
getglobal' fnName
pushArgs
call nargs 1
popValue
instance (Pushable a, LuaCallFunc b) => LuaCallFunc (a -> b) where
callFunc' fnName pushArgs nargs x =
callFunc' fnName (pushArgs *> push x) (nargs + 1)
callFunc :: (LuaCallFunc a) => String -> a
callFunc f = callFunc' f (return ()) 0
registerHaskellFunction :: ToHaskellFunction a => String -> a -> Lua ()
registerHaskellFunction n f = do
pushHaskellFunction f
setglobal n
pushHaskellFunction :: ToHaskellFunction a => a -> Lua ()
pushHaskellFunction hsFn = do
pushPreCFunction . flip runWith $ toHaskellFunction hsFn
pushcclosure hslua_call_hs_ptr 1
foreign import ccall "error-conversion.h &hslua_call_hs"
hslua_call_hs_ptr :: CFunction
hsLuaFunctionName :: String
hsLuaFunctionName = "HsLuaFunction"
pushPreCFunction :: PreCFunction -> Lua ()
pushPreCFunction f =
let pushMetatable = ensureUserdataMetatable hsLuaFunctionName $ do
pushcfunction hslua_call_wrapped_hs_fun_ptr
setfield (-2) "__call"
in pushAnyWithMetatable pushMetatable f
hslua_call_wrapped_hs_fun :: Lua.State -> IO NumResults
hslua_call_wrapped_hs_fun l = do
mbFn <- runWith l (toAnyWithName stackBottom hsLuaFunctionName
<* remove stackBottom)
case mbFn of
Nothing -> runWith l (raiseError ("Could not call function" :: ByteString))
Just fn -> fn l
foreign export ccall hslua_call_wrapped_hs_fun :: PreCFunction
foreign import ccall "&hslua_call_wrapped_hs_fun"
hslua_call_wrapped_hs_fun_ptr :: CFunction