{-# OPTIONS_GHC -fffi -fglasgow-exts #-} module Main where import qualified Scripting.Lua as Lua import Foreign.C.Types import Foreign.Ptr foreign export ccall hs_lua_c_func :: Lua.LuaState -> IO CInt foreign import ccall "&hs_lua_c_func" hs_lua_c_func_addr :: FunPtr Lua.LuaCFunction hs_lua_c_func l = do putStrLn "from haskell" return 0 main = do l <- Lua.newstate Lua.openlibs l Lua.getglobal l "print" Lua.pushstring l "from print" putStrLn "NEXT: from print" Lua.call l 1 0 Lua.register l "kill" hs_lua_c_func_addr Lua.getglobal l "kill" putStrLn "NEXT: from haskell" Lua.call l 0 0 c <- Lua.load l "print \"preparation\"; function f () print \"in lua def fun\"; end" "inline code" putStrLn "NEXT: result 0" putStrLn ("result " ++ show c) putStrLn "NEXT: preparation" Lua.call l 0 Lua.multret Lua.getglobal l "f" putStrLn "NEXT: in lua def fun" Lua.call l 0 0 Lua.getglobal l "print" Lua.push l (42::Int) putStrLn "NEXT: 42" Lua.call l 1 0 Lua.push l (42::Int) putStrLn "NEXT: number 42" Just (x::Int) <- Lua.peek l (-1) putStrLn ("number " ++ show x) putStrLn "NEXT: string 42" Just (x::String) <- Lua.peek l (-1) putStrLn ("string " ++ x) Lua.close l