module Foreign.Lua.Core.Functions where
import Prelude hiding (EQ, LT, compare, concat, error)
import Control.Monad
import Data.ByteString (ByteString)
import Data.Maybe (fromMaybe)
import Foreign.Lua.Core.Constants
import Foreign.Lua.Core.Error
import Foreign.Lua.Core.RawBindings
import Foreign.Lua.Core.Types as Lua
import Foreign.Marshal.Alloc (alloca)
import Foreign.Ptr
import qualified Data.ByteString as B
import qualified Data.ByteString.Unsafe as B
import qualified Foreign.C as C
import qualified Foreign.Lua.Utf8 as Utf8
import qualified Foreign.Storable as F
ensureTable :: StackIndex -> (Lua.State -> IO ()) -> Lua ()
ensureTable :: StackIndex -> (State -> IO ()) -> Lua ()
ensureTable StackIndex
idx State -> IO ()
ioOp = do
Bool
isTbl <- StackIndex -> Lua Bool
istable StackIndex
idx
if Bool
isTbl
then (State -> IO ()) -> Lua ()
forall a. (State -> IO a) -> Lua a
liftLua State -> IO ()
ioOp
else do
String
tyName <- StackIndex -> Lua Type
ltype StackIndex
idx Lua Type -> (Type -> Lua String) -> Lua String
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Type -> Lua String
typename
String -> Lua ()
forall a. String -> Lua a
throwMessage (String
"table expected, got " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
tyName)
absindex :: StackIndex -> Lua StackIndex
absindex :: StackIndex -> Lua StackIndex
absindex = (State -> StackIndex -> IO StackIndex)
-> StackIndex -> Lua StackIndex
forall a b. (State -> a -> IO b) -> a -> Lua b
liftLua1 State -> StackIndex -> IO StackIndex
lua_absindex
call :: NumArgs -> NumResults -> Lua ()
call :: NumArgs -> NumResults -> Lua ()
call NumArgs
nargs NumResults
nresults = do
Status
res <- NumArgs -> NumResults -> Maybe StackIndex -> Lua Status
pcall NumArgs
nargs NumResults
nresults Maybe StackIndex
forall a. Maybe a
Nothing
Bool -> Lua () -> Lua ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Status
res Status -> Status -> Bool
forall a. Eq a => a -> a -> Bool
/= Status
OK) Lua ()
forall a. Lua a
throwTopMessage
checkstack :: Int -> Lua Bool
checkstack :: Int -> Lua Bool
checkstack Int
n = (State -> IO Bool) -> Lua Bool
forall a. (State -> IO a) -> Lua a
liftLua ((State -> IO Bool) -> Lua Bool) -> (State -> IO Bool) -> Lua Bool
forall a b. (a -> b) -> a -> b
$ \State
l -> LuaBool -> Bool
fromLuaBool (LuaBool -> Bool) -> IO LuaBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> State -> CInt -> IO LuaBool
lua_checkstack State
l (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n)
close :: Lua.State -> IO ()
close :: State -> IO ()
close = State -> IO ()
lua_close
compare :: StackIndex -> StackIndex -> RelationalOperator -> Lua Bool
compare :: StackIndex -> StackIndex -> RelationalOperator -> Lua Bool
compare StackIndex
idx1 StackIndex
idx2 RelationalOperator
relOp = LuaBool -> Bool
fromLuaBool (LuaBool -> Bool) -> Lua LuaBool -> Lua Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> do
(State -> Ptr StatusCode -> IO LuaBool) -> Lua LuaBool
forall a. (State -> Ptr StatusCode -> IO a) -> Lua a
liftLuaThrow ((State -> Ptr StatusCode -> IO LuaBool) -> Lua LuaBool)
-> (State -> Ptr StatusCode -> IO LuaBool) -> Lua LuaBool
forall a b. (a -> b) -> a -> b
$ \State
l -> State
-> StackIndex -> StackIndex -> CInt -> Ptr StatusCode -> IO LuaBool
hslua_compare State
l StackIndex
idx1 StackIndex
idx2 (RelationalOperator -> CInt
fromRelationalOperator RelationalOperator
relOp)
concat :: NumArgs -> Lua ()
concat :: NumArgs -> Lua ()
concat NumArgs
n = (State -> Ptr StatusCode -> IO ()) -> Lua ()
forall a. (State -> Ptr StatusCode -> IO a) -> Lua a
liftLuaThrow (State -> NumArgs -> Ptr StatusCode -> IO ()
`hslua_concat` NumArgs
n)
copy :: StackIndex -> StackIndex -> Lua ()
copy :: StackIndex -> StackIndex -> Lua ()
copy StackIndex
fromidx StackIndex
toidx = (State -> IO ()) -> Lua ()
forall a. (State -> IO a) -> Lua a
liftLua ((State -> IO ()) -> Lua ()) -> (State -> IO ()) -> Lua ()
forall a b. (a -> b) -> a -> b
$ \State
l -> State -> StackIndex -> StackIndex -> IO ()
lua_copy State
l StackIndex
fromidx StackIndex
toidx
createtable :: Int -> Int -> Lua ()
createtable :: Int -> Int -> Lua ()
createtable Int
narr Int
nrec = (State -> IO ()) -> Lua ()
forall a. (State -> IO a) -> Lua a
liftLua ((State -> IO ()) -> Lua ()) -> (State -> IO ()) -> Lua ()
forall a b. (a -> b) -> a -> b
$ \State
l ->
State -> CInt -> CInt -> IO ()
lua_createtable State
l (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
narr) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
nrec)
equal :: StackIndex
-> StackIndex
-> Lua Bool
equal :: StackIndex -> StackIndex -> Lua Bool
equal StackIndex
index1 StackIndex
index2 = StackIndex -> StackIndex -> RelationalOperator -> Lua Bool
compare StackIndex
index1 StackIndex
index2 RelationalOperator
EQ
error :: Lua NumResults
error :: Lua NumResults
error = (State -> IO NumResults) -> Lua NumResults
forall a. (State -> IO a) -> Lua a
liftLua State -> IO NumResults
hslua_error
gc :: GCCONTROL -> Int -> Lua Int
gc :: GCCONTROL -> Int -> Lua Int
gc GCCONTROL
what Int
data' = (State -> IO Int) -> Lua Int
forall a. (State -> IO a) -> Lua a
liftLua ((State -> IO Int) -> Lua Int) -> (State -> IO Int) -> Lua Int
forall a b. (a -> b) -> a -> b
$ \State
l ->
CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt -> Int) -> IO CInt -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> State -> CInt -> CInt -> IO CInt
lua_gc State
l (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (GCCONTROL -> Int
forall a. Enum a => a -> Int
fromEnum GCCONTROL
what)) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
data')
getfield :: StackIndex -> String -> Lua ()
getfield :: StackIndex -> String -> Lua ()
getfield StackIndex
i String
s = do
StackIndex
absidx <- StackIndex -> Lua StackIndex
absindex StackIndex
i
ByteString -> Lua ()
pushstring (String -> ByteString
Utf8.fromString String
s)
StackIndex -> Lua ()
gettable StackIndex
absidx
getglobal :: String -> Lua ()
getglobal :: String -> Lua ()
getglobal String
name = (State -> Ptr StatusCode -> IO ()) -> Lua ()
forall a. (State -> Ptr StatusCode -> IO a) -> Lua a
liftLuaThrow ((State -> Ptr StatusCode -> IO ()) -> Lua ())
-> (State -> Ptr StatusCode -> IO ()) -> Lua ()
forall a b. (a -> b) -> a -> b
$ \State
l Ptr StatusCode
status' ->
String -> (CStringLen -> IO ()) -> IO ()
forall a. String -> (CStringLen -> IO a) -> IO a
C.withCStringLen String
name ((CStringLen -> IO ()) -> IO ()) -> (CStringLen -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
namePtr, Int
len) ->
State -> Ptr CChar -> CSize -> Ptr StatusCode -> IO ()
hslua_getglobal State
l Ptr CChar
namePtr (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len) Ptr StatusCode
status'
getmetatable :: StackIndex -> Lua Bool
getmetatable :: StackIndex -> Lua Bool
getmetatable StackIndex
n = (State -> IO Bool) -> Lua Bool
forall a. (State -> IO a) -> Lua a
liftLua ((State -> IO Bool) -> Lua Bool) -> (State -> IO Bool) -> Lua Bool
forall a b. (a -> b) -> a -> b
$ \State
l ->
LuaBool -> Bool
fromLuaBool (LuaBool -> Bool) -> IO LuaBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> State -> StackIndex -> IO LuaBool
lua_getmetatable State
l StackIndex
n
gettable :: StackIndex -> Lua ()
gettable :: StackIndex -> Lua ()
gettable StackIndex
n = (State -> Ptr StatusCode -> IO ()) -> Lua ()
forall a. (State -> Ptr StatusCode -> IO a) -> Lua a
liftLuaThrow (\State
l -> State -> StackIndex -> Ptr StatusCode -> IO ()
hslua_gettable State
l StackIndex
n)
gettop :: Lua StackIndex
gettop :: Lua StackIndex
gettop = (State -> IO StackIndex) -> Lua StackIndex
forall a. (State -> IO a) -> Lua a
liftLua State -> IO StackIndex
lua_gettop
insert :: StackIndex -> Lua ()
insert :: StackIndex -> Lua ()
insert StackIndex
index = (State -> IO ()) -> Lua ()
forall a. (State -> IO a) -> Lua a
liftLua ((State -> IO ()) -> Lua ()) -> (State -> IO ()) -> Lua ()
forall a b. (a -> b) -> a -> b
$ \State
l -> State -> StackIndex -> IO ()
lua_insert State
l StackIndex
index
isboolean :: StackIndex -> Lua Bool
isboolean :: StackIndex -> Lua Bool
isboolean StackIndex
n = (Type -> Type -> Bool
forall a. Eq a => a -> a -> Bool
== Type
TypeBoolean) (Type -> Bool) -> Lua Type -> Lua Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StackIndex -> Lua Type
ltype StackIndex
n
iscfunction :: StackIndex -> Lua Bool
iscfunction :: StackIndex -> Lua Bool
iscfunction StackIndex
n = (State -> IO Bool) -> Lua Bool
forall a. (State -> IO a) -> Lua a
liftLua ((State -> IO Bool) -> Lua Bool) -> (State -> IO Bool) -> Lua Bool
forall a b. (a -> b) -> a -> b
$ \State
l -> LuaBool -> Bool
fromLuaBool (LuaBool -> Bool) -> IO LuaBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> State -> StackIndex -> IO LuaBool
lua_iscfunction State
l StackIndex
n
isfunction :: StackIndex -> Lua Bool
isfunction :: StackIndex -> Lua Bool
isfunction StackIndex
n = (Type -> Type -> Bool
forall a. Eq a => a -> a -> Bool
== Type
TypeFunction) (Type -> Bool) -> Lua Type -> Lua Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StackIndex -> Lua Type
ltype StackIndex
n
isinteger :: StackIndex -> Lua Bool
isinteger :: StackIndex -> Lua Bool
isinteger StackIndex
n = (State -> IO Bool) -> Lua Bool
forall a. (State -> IO a) -> Lua a
liftLua ((State -> IO Bool) -> Lua Bool) -> (State -> IO Bool) -> Lua Bool
forall a b. (a -> b) -> a -> b
$ \State
l -> LuaBool -> Bool
fromLuaBool (LuaBool -> Bool) -> IO LuaBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> State -> StackIndex -> IO LuaBool
lua_isinteger State
l StackIndex
n
islightuserdata :: StackIndex -> Lua Bool
islightuserdata :: StackIndex -> Lua Bool
islightuserdata StackIndex
n = (Type -> Type -> Bool
forall a. Eq a => a -> a -> Bool
== Type
TypeLightUserdata) (Type -> Bool) -> Lua Type -> Lua Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StackIndex -> Lua Type
ltype StackIndex
n
isnil :: StackIndex -> Lua Bool
isnil :: StackIndex -> Lua Bool
isnil StackIndex
n = (Type -> Type -> Bool
forall a. Eq a => a -> a -> Bool
== Type
TypeNil) (Type -> Bool) -> Lua Type -> Lua Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StackIndex -> Lua Type
ltype StackIndex
n
isnone :: StackIndex -> Lua Bool
isnone :: StackIndex -> Lua Bool
isnone StackIndex
n = (Type -> Type -> Bool
forall a. Eq a => a -> a -> Bool
== Type
TypeNone) (Type -> Bool) -> Lua Type -> Lua Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StackIndex -> Lua Type
ltype StackIndex
n
isnoneornil :: StackIndex -> Lua Bool
isnoneornil :: StackIndex -> Lua Bool
isnoneornil StackIndex
idx = (Type -> Type -> Bool
forall a. Ord a => a -> a -> Bool
<= Type
TypeNil) (Type -> Bool) -> Lua Type -> Lua Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StackIndex -> Lua Type
ltype StackIndex
idx
isnumber :: StackIndex -> Lua Bool
isnumber :: StackIndex -> Lua Bool
isnumber StackIndex
n = (State -> IO Bool) -> Lua Bool
forall a. (State -> IO a) -> Lua a
liftLua ((State -> IO Bool) -> Lua Bool) -> (State -> IO Bool) -> Lua Bool
forall a b. (a -> b) -> a -> b
$ \State
l -> LuaBool -> Bool
fromLuaBool (LuaBool -> Bool) -> IO LuaBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> State -> StackIndex -> IO LuaBool
lua_isnumber State
l StackIndex
n
isstring :: StackIndex -> Lua Bool
isstring :: StackIndex -> Lua Bool
isstring StackIndex
n = (State -> IO Bool) -> Lua Bool
forall a. (State -> IO a) -> Lua a
liftLua ((State -> IO Bool) -> Lua Bool) -> (State -> IO Bool) -> Lua Bool
forall a b. (a -> b) -> a -> b
$ \State
l -> LuaBool -> Bool
fromLuaBool (LuaBool -> Bool) -> IO LuaBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> State -> StackIndex -> IO LuaBool
lua_isstring State
l StackIndex
n
istable :: StackIndex -> Lua Bool
istable :: StackIndex -> Lua Bool
istable StackIndex
n = (Type -> Type -> Bool
forall a. Eq a => a -> a -> Bool
== Type
TypeTable) (Type -> Bool) -> Lua Type -> Lua Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StackIndex -> Lua Type
ltype StackIndex
n
isthread :: StackIndex -> Lua Bool
isthread :: StackIndex -> Lua Bool
isthread StackIndex
n = (Type -> Type -> Bool
forall a. Eq a => a -> a -> Bool
== Type
TypeThread) (Type -> Bool) -> Lua Type -> Lua Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StackIndex -> Lua Type
ltype StackIndex
n
isuserdata :: StackIndex -> Lua Bool
isuserdata :: StackIndex -> Lua Bool
isuserdata StackIndex
n = (State -> IO Bool) -> Lua Bool
forall a. (State -> IO a) -> Lua a
liftLua ((State -> IO Bool) -> Lua Bool) -> (State -> IO Bool) -> Lua Bool
forall a b. (a -> b) -> a -> b
$ \State
l -> LuaBool -> Bool
fromLuaBool (LuaBool -> Bool) -> IO LuaBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> State -> StackIndex -> IO LuaBool
lua_isuserdata State
l StackIndex
n
lessthan :: StackIndex -> StackIndex -> Lua Bool
lessthan :: StackIndex -> StackIndex -> Lua Bool
lessthan StackIndex
index1 StackIndex
index2 = StackIndex -> StackIndex -> RelationalOperator -> Lua Bool
compare StackIndex
index1 StackIndex
index2 RelationalOperator
LT
load :: Lua.Reader -> Ptr () -> ByteString -> Lua Status
load :: Reader -> Ptr () -> ByteString -> Lua Status
load Reader
reader Ptr ()
data' ByteString
chunkname = (State -> IO Status) -> Lua Status
forall a. (State -> IO a) -> Lua a
liftLua ((State -> IO Status) -> Lua Status)
-> (State -> IO Status) -> Lua Status
forall a b. (a -> b) -> a -> b
$ \State
l ->
ByteString -> (Ptr CChar -> IO Status) -> IO Status
forall a. ByteString -> (Ptr CChar -> IO a) -> IO a
B.useAsCString ByteString
chunkname ((Ptr CChar -> IO Status) -> IO Status)
-> (Ptr CChar -> IO Status) -> IO Status
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
namePtr ->
StatusCode -> Status
toStatus (StatusCode -> Status) -> IO StatusCode -> IO Status
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> State
-> Reader -> Ptr () -> Ptr CChar -> Ptr CChar -> IO StatusCode
lua_load State
l Reader
reader Ptr ()
data' Ptr CChar
namePtr Ptr CChar
forall a. Ptr a
nullPtr
ltype :: StackIndex -> Lua Type
ltype :: StackIndex -> Lua Type
ltype StackIndex
idx = TypeCode -> Type
toType (TypeCode -> Type) -> Lua TypeCode -> Lua Type
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (State -> IO TypeCode) -> Lua TypeCode
forall a. (State -> IO a) -> Lua a
liftLua (State -> StackIndex -> IO TypeCode
`lua_type` StackIndex
idx)
newtable :: Lua ()
newtable :: Lua ()
newtable = Int -> Int -> Lua ()
createtable Int
0 Int
0
newuserdata :: Int -> Lua (Ptr ())
newuserdata :: Int -> Lua (Ptr ())
newuserdata = (State -> CSize -> IO (Ptr ())) -> CSize -> Lua (Ptr ())
forall a b. (State -> a -> IO b) -> a -> Lua b
liftLua1 State -> CSize -> IO (Ptr ())
lua_newuserdata (CSize -> Lua (Ptr ())) -> (Int -> CSize) -> Int -> Lua (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral
next :: StackIndex -> Lua Bool
next :: StackIndex -> Lua Bool
next StackIndex
idx = LuaBool -> Bool
fromLuaBool (LuaBool -> Bool) -> Lua LuaBool -> Lua Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (State -> Ptr StatusCode -> IO LuaBool) -> Lua LuaBool
forall a. (State -> Ptr StatusCode -> IO a) -> Lua a
liftLuaThrow (\State
l -> State -> StackIndex -> Ptr StatusCode -> IO LuaBool
hslua_next State
l StackIndex
idx)
openlibs :: Lua ()
openlibs :: Lua ()
openlibs = (State -> IO ()) -> Lua ()
forall a. (State -> IO a) -> Lua a
liftLua State -> IO ()
luaL_openlibs
openbase :: Lua ()
openbase :: Lua ()
openbase = CFunction -> Lua ()
pushcfunction CFunction
lua_open_base_ptr Lua () -> Lua () -> Lua ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> NumArgs -> NumResults -> Lua ()
call NumArgs
0 NumResults
multret
opendebug :: Lua ()
opendebug :: Lua ()
opendebug = CFunction -> Lua ()
pushcfunction CFunction
lua_open_debug_ptr Lua () -> Lua () -> Lua ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> NumArgs -> NumResults -> Lua ()
call NumArgs
0 NumResults
multret
openio :: Lua ()
openio :: Lua ()
openio = CFunction -> Lua ()
pushcfunction CFunction
lua_open_io_ptr Lua () -> Lua () -> Lua ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> NumArgs -> NumResults -> Lua ()
call NumArgs
0 NumResults
multret
openmath :: Lua ()
openmath :: Lua ()
openmath = CFunction -> Lua ()
pushcfunction CFunction
lua_open_math_ptr Lua () -> Lua () -> Lua ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> NumArgs -> NumResults -> Lua ()
call NumArgs
0 NumResults
multret
openos :: Lua ()
openos :: Lua ()
openos = CFunction -> Lua ()
pushcfunction CFunction
lua_open_os_ptr Lua () -> Lua () -> Lua ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> NumArgs -> NumResults -> Lua ()
call NumArgs
0 NumResults
multret
openpackage :: Lua ()
openpackage :: Lua ()
openpackage = CFunction -> Lua ()
pushcfunction CFunction
lua_open_package_ptr Lua () -> Lua () -> Lua ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> NumArgs -> NumResults -> Lua ()
call NumArgs
0 NumResults
multret
openstring :: Lua ()
openstring :: Lua ()
openstring = CFunction -> Lua ()
pushcfunction CFunction
lua_open_string_ptr Lua () -> Lua () -> Lua ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> NumArgs -> NumResults -> Lua ()
call NumArgs
0 NumResults
multret
opentable :: Lua ()
opentable :: Lua ()
opentable = CFunction -> Lua ()
pushcfunction CFunction
lua_open_table_ptr Lua () -> Lua () -> Lua ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> NumArgs -> NumResults -> Lua ()
call NumArgs
0 NumResults
multret
pcall :: NumArgs -> NumResults -> Maybe StackIndex -> Lua Status
pcall :: NumArgs -> NumResults -> Maybe StackIndex -> Lua Status
pcall NumArgs
nargs NumResults
nresults Maybe StackIndex
msgh = (State -> IO Status) -> Lua Status
forall a. (State -> IO a) -> Lua a
liftLua ((State -> IO Status) -> Lua Status)
-> (State -> IO Status) -> Lua Status
forall a b. (a -> b) -> a -> b
$ \State
l ->
StatusCode -> Status
toStatus (StatusCode -> Status) -> IO StatusCode -> IO Status
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> State -> NumArgs -> NumResults -> StackIndex -> IO StatusCode
lua_pcall State
l NumArgs
nargs NumResults
nresults (StackIndex -> Maybe StackIndex -> StackIndex
forall a. a -> Maybe a -> a
fromMaybe StackIndex
0 Maybe StackIndex
msgh)
pop :: StackIndex -> Lua ()
pop :: StackIndex -> Lua ()
pop StackIndex
n = (State -> IO ()) -> Lua ()
forall a. (State -> IO a) -> Lua a
liftLua ((State -> IO ()) -> Lua ()) -> (State -> IO ()) -> Lua ()
forall a b. (a -> b) -> a -> b
$ \State
l -> State -> StackIndex -> IO ()
lua_pop State
l StackIndex
n
pushboolean :: Bool -> Lua ()
pushboolean :: Bool -> Lua ()
pushboolean Bool
b = (State -> IO ()) -> Lua ()
forall a. (State -> IO a) -> Lua a
liftLua ((State -> IO ()) -> Lua ()) -> (State -> IO ()) -> Lua ()
forall a b. (a -> b) -> a -> b
$ \State
l -> State -> LuaBool -> IO ()
lua_pushboolean State
l (Bool -> LuaBool
toLuaBool Bool
b)
pushcclosure :: CFunction -> NumArgs -> Lua ()
pushcclosure :: CFunction -> NumArgs -> Lua ()
pushcclosure CFunction
f NumArgs
n = (State -> IO ()) -> Lua ()
forall a. (State -> IO a) -> Lua a
liftLua ((State -> IO ()) -> Lua ()) -> (State -> IO ()) -> Lua ()
forall a b. (a -> b) -> a -> b
$ \State
l -> State -> CFunction -> NumArgs -> IO ()
lua_pushcclosure State
l CFunction
f NumArgs
n
pushcfunction :: CFunction -> Lua ()
pushcfunction :: CFunction -> Lua ()
pushcfunction CFunction
f = CFunction -> NumArgs -> Lua ()
pushcclosure CFunction
f NumArgs
0
pushglobaltable :: Lua ()
pushglobaltable :: Lua ()
pushglobaltable = (State -> IO ()) -> Lua ()
forall a. (State -> IO a) -> Lua a
liftLua State -> IO ()
lua_pushglobaltable
pushinteger :: Lua.Integer -> Lua ()
pushinteger :: Integer -> Lua ()
pushinteger = (State -> Integer -> IO ()) -> Integer -> Lua ()
forall a b. (State -> a -> IO b) -> a -> Lua b
liftLua1 State -> Integer -> IO ()
lua_pushinteger
pushlightuserdata :: Ptr a -> Lua ()
pushlightuserdata :: Ptr a -> Lua ()
pushlightuserdata = (State -> Ptr a -> IO ()) -> Ptr a -> Lua ()
forall a b. (State -> a -> IO b) -> a -> Lua b
liftLua1 State -> Ptr a -> IO ()
forall a. State -> Ptr a -> IO ()
lua_pushlightuserdata
pushnil :: Lua ()
pushnil :: Lua ()
pushnil = (State -> IO ()) -> Lua ()
forall a. (State -> IO a) -> Lua a
liftLua State -> IO ()
lua_pushnil
pushnumber :: Lua.Number -> Lua ()
pushnumber :: Number -> Lua ()
pushnumber = (State -> Number -> IO ()) -> Number -> Lua ()
forall a b. (State -> a -> IO b) -> a -> Lua b
liftLua1 State -> Number -> IO ()
lua_pushnumber
pushstring :: ByteString -> Lua ()
pushstring :: ByteString -> Lua ()
pushstring ByteString
s = (State -> IO ()) -> Lua ()
forall a. (State -> IO a) -> Lua a
liftLua ((State -> IO ()) -> Lua ()) -> (State -> IO ()) -> Lua ()
forall a b. (a -> b) -> a -> b
$ \State
l ->
ByteString -> (CStringLen -> IO ()) -> IO ()
forall a. ByteString -> (CStringLen -> IO a) -> IO a
B.unsafeUseAsCStringLen ByteString
s ((CStringLen -> IO ()) -> IO ()) -> (CStringLen -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
sPtr, Int
z) -> State -> Ptr CChar -> CSize -> IO ()
lua_pushlstring State
l Ptr CChar
sPtr (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
z)
pushthread :: Lua Bool
pushthread :: Lua Bool
pushthread = (CInt
1 CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
==) (CInt -> Bool) -> Lua CInt -> Lua Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (State -> IO CInt) -> Lua CInt
forall a. (State -> IO a) -> Lua a
liftLua State -> IO CInt
lua_pushthread
pushvalue :: StackIndex -> Lua ()
pushvalue :: StackIndex -> Lua ()
pushvalue StackIndex
n = (State -> IO ()) -> Lua ()
forall a. (State -> IO a) -> Lua a
liftLua ((State -> IO ()) -> Lua ()) -> (State -> IO ()) -> Lua ()
forall a b. (a -> b) -> a -> b
$ \State
l -> State -> StackIndex -> IO ()
lua_pushvalue State
l StackIndex
n
rawequal :: StackIndex -> StackIndex -> Lua Bool
rawequal :: StackIndex -> StackIndex -> Lua Bool
rawequal StackIndex
idx1 StackIndex
idx2 = (State -> IO Bool) -> Lua Bool
forall a. (State -> IO a) -> Lua a
liftLua ((State -> IO Bool) -> Lua Bool) -> (State -> IO Bool) -> Lua Bool
forall a b. (a -> b) -> a -> b
$ \State
l ->
LuaBool -> Bool
fromLuaBool (LuaBool -> Bool) -> IO LuaBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> State -> StackIndex -> StackIndex -> IO LuaBool
lua_rawequal State
l StackIndex
idx1 StackIndex
idx2
rawget :: StackIndex -> Lua ()
rawget :: StackIndex -> Lua ()
rawget StackIndex
n = StackIndex -> (State -> IO ()) -> Lua ()
ensureTable StackIndex
n (\State
l -> State -> StackIndex -> IO ()
lua_rawget State
l StackIndex
n)
rawgeti :: StackIndex -> Lua.Integer -> Lua ()
rawgeti :: StackIndex -> Integer -> Lua ()
rawgeti StackIndex
k Integer
n = StackIndex -> (State -> IO ()) -> Lua ()
ensureTable StackIndex
k (\State
l -> State -> StackIndex -> Integer -> IO ()
lua_rawgeti State
l StackIndex
k Integer
n)
rawlen :: StackIndex -> Lua Int
rawlen :: StackIndex -> Lua Int
rawlen StackIndex
idx = (State -> IO Int) -> Lua Int
forall a. (State -> IO a) -> Lua a
liftLua ((State -> IO Int) -> Lua Int) -> (State -> IO Int) -> Lua Int
forall a b. (a -> b) -> a -> b
$ \State
l -> CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CSize -> Int) -> IO CSize -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> State -> StackIndex -> IO CSize
lua_rawlen State
l StackIndex
idx
rawset :: StackIndex -> Lua ()
rawset :: StackIndex -> Lua ()
rawset StackIndex
n = StackIndex -> (State -> IO ()) -> Lua ()
ensureTable StackIndex
n (\State
l -> State -> StackIndex -> IO ()
lua_rawset State
l StackIndex
n)
rawseti :: StackIndex -> Lua.Integer -> Lua ()
rawseti :: StackIndex -> Integer -> Lua ()
rawseti StackIndex
k Integer
m = StackIndex -> (State -> IO ()) -> Lua ()
ensureTable StackIndex
k (\State
l -> State -> StackIndex -> Integer -> IO ()
lua_rawseti State
l StackIndex
k Integer
m)
register :: String -> CFunction -> Lua ()
register :: String -> CFunction -> Lua ()
register String
name CFunction
f = do
CFunction -> Lua ()
pushcfunction CFunction
f
String -> Lua ()
setglobal String
name
remove :: StackIndex -> Lua ()
remove :: StackIndex -> Lua ()
remove StackIndex
n = (State -> IO ()) -> Lua ()
forall a. (State -> IO a) -> Lua a
liftLua ((State -> IO ()) -> Lua ()) -> (State -> IO ()) -> Lua ()
forall a b. (a -> b) -> a -> b
$ \State
l -> State -> StackIndex -> IO ()
lua_remove State
l StackIndex
n
replace :: StackIndex -> Lua ()
replace :: StackIndex -> Lua ()
replace StackIndex
n = (State -> IO ()) -> Lua ()
forall a. (State -> IO a) -> Lua a
liftLua ((State -> IO ()) -> Lua ()) -> (State -> IO ()) -> Lua ()
forall a b. (a -> b) -> a -> b
$ \State
l -> State -> StackIndex -> IO ()
lua_replace State
l StackIndex
n
setfield :: StackIndex -> String -> Lua ()
setfield :: StackIndex -> String -> Lua ()
setfield StackIndex
i String
s = do
StackIndex
absidx <- StackIndex -> Lua StackIndex
absindex StackIndex
i
ByteString -> Lua ()
pushstring (String -> ByteString
Utf8.fromString String
s)
StackIndex -> Lua ()
insert (CInt -> StackIndex
nthFromTop CInt
2)
StackIndex -> Lua ()
settable StackIndex
absidx
setglobal :: String -> Lua ()
setglobal :: String -> Lua ()
setglobal String
name = (State -> Ptr StatusCode -> IO ()) -> Lua ()
forall a. (State -> Ptr StatusCode -> IO a) -> Lua a
liftLuaThrow ((State -> Ptr StatusCode -> IO ()) -> Lua ())
-> (State -> Ptr StatusCode -> IO ()) -> Lua ()
forall a b. (a -> b) -> a -> b
$ \State
l Ptr StatusCode
status' ->
String -> (CStringLen -> IO ()) -> IO ()
forall a. String -> (CStringLen -> IO a) -> IO a
C.withCStringLen String
name ((CStringLen -> IO ()) -> IO ()) -> (CStringLen -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
namePtr, Int
nameLen) ->
State -> Ptr CChar -> CSize -> Ptr StatusCode -> IO ()
hslua_setglobal State
l Ptr CChar
namePtr (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
nameLen) Ptr StatusCode
status'
setmetatable :: StackIndex -> Lua ()
setmetatable :: StackIndex -> Lua ()
setmetatable StackIndex
idx = (State -> IO ()) -> Lua ()
forall a. (State -> IO a) -> Lua a
liftLua ((State -> IO ()) -> Lua ()) -> (State -> IO ()) -> Lua ()
forall a b. (a -> b) -> a -> b
$ \State
l -> State -> StackIndex -> IO ()
lua_setmetatable State
l StackIndex
idx
settable :: StackIndex -> Lua ()
settable :: StackIndex -> Lua ()
settable StackIndex
index = (State -> Ptr StatusCode -> IO ()) -> Lua ()
forall a. (State -> Ptr StatusCode -> IO a) -> Lua a
liftLuaThrow ((State -> Ptr StatusCode -> IO ()) -> Lua ())
-> (State -> Ptr StatusCode -> IO ()) -> Lua ()
forall a b. (a -> b) -> a -> b
$ \State
l -> State -> StackIndex -> Ptr StatusCode -> IO ()
hslua_settable State
l StackIndex
index
settop :: StackIndex -> Lua ()
settop :: StackIndex -> Lua ()
settop = (State -> StackIndex -> IO ()) -> StackIndex -> Lua ()
forall a b. (State -> a -> IO b) -> a -> Lua b
liftLua1 State -> StackIndex -> IO ()
lua_settop
status :: Lua Status
status :: Lua Status
status = (State -> IO Status) -> Lua Status
forall a. (State -> IO a) -> Lua a
liftLua ((State -> IO Status) -> Lua Status)
-> (State -> IO Status) -> Lua Status
forall a b. (a -> b) -> a -> b
$ (StatusCode -> Status) -> IO StatusCode -> IO Status
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap StatusCode -> Status
toStatus (IO StatusCode -> IO Status)
-> (State -> IO StatusCode) -> State -> IO Status
forall b c a. (b -> c) -> (a -> b) -> a -> c
. State -> IO StatusCode
lua_status
toboolean :: StackIndex -> Lua Bool
toboolean :: StackIndex -> Lua Bool
toboolean StackIndex
n = (State -> IO Bool) -> Lua Bool
forall a. (State -> IO a) -> Lua a
liftLua ((State -> IO Bool) -> Lua Bool) -> (State -> IO Bool) -> Lua Bool
forall a b. (a -> b) -> a -> b
$ \State
l -> LuaBool -> Bool
fromLuaBool (LuaBool -> Bool) -> IO LuaBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> State -> StackIndex -> IO LuaBool
lua_toboolean State
l StackIndex
n
tocfunction :: StackIndex -> Lua (Maybe CFunction)
tocfunction :: StackIndex -> Lua (Maybe CFunction)
tocfunction StackIndex
n = (State -> IO (Maybe CFunction)) -> Lua (Maybe CFunction)
forall a. (State -> IO a) -> Lua a
liftLua ((State -> IO (Maybe CFunction)) -> Lua (Maybe CFunction))
-> (State -> IO (Maybe CFunction)) -> Lua (Maybe CFunction)
forall a b. (a -> b) -> a -> b
$ \State
l -> do
CFunction
fnPtr <- State -> StackIndex -> IO CFunction
lua_tocfunction State
l StackIndex
n
Maybe CFunction -> IO (Maybe CFunction)
forall (m :: * -> *) a. Monad m => a -> m a
return (if CFunction
fnPtr CFunction -> CFunction -> Bool
forall a. Eq a => a -> a -> Bool
== CFunction
forall a. FunPtr a
nullFunPtr then Maybe CFunction
forall a. Maybe a
Nothing else CFunction -> Maybe CFunction
forall a. a -> Maybe a
Just CFunction
fnPtr)
tointeger :: StackIndex -> Lua (Maybe Lua.Integer)
tointeger :: StackIndex -> Lua (Maybe Integer)
tointeger StackIndex
n = (State -> IO (Maybe Integer)) -> Lua (Maybe Integer)
forall a. (State -> IO a) -> Lua a
liftLua ((State -> IO (Maybe Integer)) -> Lua (Maybe Integer))
-> (State -> IO (Maybe Integer)) -> Lua (Maybe Integer)
forall a b. (a -> b) -> a -> b
$ \State
l -> (Ptr LuaBool -> IO (Maybe Integer)) -> IO (Maybe Integer)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr LuaBool -> IO (Maybe Integer)) -> IO (Maybe Integer))
-> (Ptr LuaBool -> IO (Maybe Integer)) -> IO (Maybe Integer)
forall a b. (a -> b) -> a -> b
$ \Ptr LuaBool
boolPtr -> do
Integer
res <- State -> StackIndex -> Ptr LuaBool -> IO Integer
lua_tointegerx State
l StackIndex
n Ptr LuaBool
boolPtr
Bool
isNum <- LuaBool -> Bool
fromLuaBool (LuaBool -> Bool) -> IO LuaBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr LuaBool -> IO LuaBool
forall a. Storable a => Ptr a -> IO a
F.peek Ptr LuaBool
boolPtr
Maybe Integer -> IO (Maybe Integer)
forall (m :: * -> *) a. Monad m => a -> m a
return (if Bool
isNum then Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
res else Maybe Integer
forall a. Maybe a
Nothing)
tonumber :: StackIndex -> Lua (Maybe Lua.Number)
tonumber :: StackIndex -> Lua (Maybe Number)
tonumber StackIndex
n = (State -> IO (Maybe Number)) -> Lua (Maybe Number)
forall a. (State -> IO a) -> Lua a
liftLua ((State -> IO (Maybe Number)) -> Lua (Maybe Number))
-> (State -> IO (Maybe Number)) -> Lua (Maybe Number)
forall a b. (a -> b) -> a -> b
$ \State
l -> (Ptr LuaBool -> IO (Maybe Number)) -> IO (Maybe Number)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr LuaBool -> IO (Maybe Number)) -> IO (Maybe Number))
-> (Ptr LuaBool -> IO (Maybe Number)) -> IO (Maybe Number)
forall a b. (a -> b) -> a -> b
$ \Ptr LuaBool
bptr -> do
Number
res <- State -> StackIndex -> Ptr LuaBool -> IO Number
lua_tonumberx State
l StackIndex
n Ptr LuaBool
bptr
Bool
isNum <- LuaBool -> Bool
fromLuaBool (LuaBool -> Bool) -> IO LuaBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr LuaBool -> IO LuaBool
forall a. Storable a => Ptr a -> IO a
F.peek Ptr LuaBool
bptr
Maybe Number -> IO (Maybe Number)
forall (m :: * -> *) a. Monad m => a -> m a
return (if Bool
isNum then Number -> Maybe Number
forall a. a -> Maybe a
Just Number
res else Maybe Number
forall a. Maybe a
Nothing)
topointer :: StackIndex -> Lua (Ptr ())
topointer :: StackIndex -> Lua (Ptr ())
topointer StackIndex
n = (State -> IO (Ptr ())) -> Lua (Ptr ())
forall a. (State -> IO a) -> Lua a
liftLua ((State -> IO (Ptr ())) -> Lua (Ptr ()))
-> (State -> IO (Ptr ())) -> Lua (Ptr ())
forall a b. (a -> b) -> a -> b
$ \State
l -> State -> StackIndex -> IO (Ptr ())
lua_topointer State
l StackIndex
n
tostring :: StackIndex -> Lua (Maybe ByteString)
tostring :: StackIndex -> Lua (Maybe ByteString)
tostring StackIndex
n = (State -> IO (Maybe ByteString)) -> Lua (Maybe ByteString)
forall a. (State -> IO a) -> Lua a
liftLua ((State -> IO (Maybe ByteString)) -> Lua (Maybe ByteString))
-> (State -> IO (Maybe ByteString)) -> Lua (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ \State
l ->
(Ptr CSize -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CSize -> IO (Maybe ByteString)) -> IO (Maybe ByteString))
-> (Ptr CSize -> IO (Maybe ByteString)) -> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ \Ptr CSize
lenPtr -> do
Ptr CChar
cstr <- State -> StackIndex -> Ptr CSize -> IO (Ptr CChar)
lua_tolstring State
l StackIndex
n Ptr CSize
lenPtr
if Ptr CChar
cstr Ptr CChar -> Ptr CChar -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr CChar
forall a. Ptr a
nullPtr
then Maybe ByteString -> IO (Maybe ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ByteString
forall a. Maybe a
Nothing
else do
CSize
cstrLen <- Ptr CSize -> IO CSize
forall a. Storable a => Ptr a -> IO a
F.peek Ptr CSize
lenPtr
ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString)
-> IO ByteString -> IO (Maybe ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CStringLen -> IO ByteString
B.packCStringLen (Ptr CChar
cstr, CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
cstrLen)
tothread :: StackIndex -> Lua (Maybe Lua.State)
tothread :: StackIndex -> Lua (Maybe State)
tothread StackIndex
n = (State -> IO (Maybe State)) -> Lua (Maybe State)
forall a. (State -> IO a) -> Lua a
liftLua ((State -> IO (Maybe State)) -> Lua (Maybe State))
-> (State -> IO (Maybe State)) -> Lua (Maybe State)
forall a b. (a -> b) -> a -> b
$ \State
l -> do
thread :: State
thread@(Lua.State Ptr ()
ptr) <- State -> StackIndex -> IO State
lua_tothread State
l StackIndex
n
if Ptr ()
ptr Ptr () -> Ptr () -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr ()
forall a. Ptr a
nullPtr
then Maybe State -> IO (Maybe State)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe State
forall a. Maybe a
Nothing
else Maybe State -> IO (Maybe State)
forall (m :: * -> *) a. Monad m => a -> m a
return (State -> Maybe State
forall a. a -> Maybe a
Just State
thread)
touserdata :: StackIndex -> Lua (Maybe (Ptr a))
touserdata :: StackIndex -> Lua (Maybe (Ptr a))
touserdata StackIndex
n = (State -> IO (Maybe (Ptr a))) -> Lua (Maybe (Ptr a))
forall a. (State -> IO a) -> Lua a
liftLua ((State -> IO (Maybe (Ptr a))) -> Lua (Maybe (Ptr a)))
-> (State -> IO (Maybe (Ptr a))) -> Lua (Maybe (Ptr a))
forall a b. (a -> b) -> a -> b
$ \State
l -> do
Ptr a
ptr <- State -> StackIndex -> IO (Ptr a)
forall a. State -> StackIndex -> IO (Ptr a)
lua_touserdata State
l StackIndex
n
if Ptr a
ptr Ptr a -> Ptr a -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr a
forall a. Ptr a
nullPtr
then Maybe (Ptr a) -> IO (Maybe (Ptr a))
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (Ptr a)
forall a. Maybe a
Nothing
else Maybe (Ptr a) -> IO (Maybe (Ptr a))
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr a -> Maybe (Ptr a)
forall a. a -> Maybe a
Just Ptr a
ptr)
typename :: Type -> Lua String
typename :: Type -> Lua String
typename Type
tp = (State -> IO String) -> Lua String
forall a. (State -> IO a) -> Lua a
liftLua ((State -> IO String) -> Lua String)
-> (State -> IO String) -> Lua String
forall a b. (a -> b) -> a -> b
$ \State
l ->
State -> TypeCode -> IO (Ptr CChar)
lua_typename State
l (Type -> TypeCode
fromType Type
tp) IO (Ptr CChar) -> (Ptr CChar -> IO String) -> IO String
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr CChar -> IO String
C.peekCString
upvalueindex :: StackIndex -> StackIndex
upvalueindex :: StackIndex -> StackIndex
upvalueindex StackIndex
i = StackIndex
registryindex StackIndex -> StackIndex -> StackIndex
forall a. Num a => a -> a -> a
- StackIndex
i