{-# LANGUAGE OverloadedStrings #-}
module HsLua.Core.Primary where
import Prelude hiding (EQ, LT, compare, concat, error)
import Control.Monad
import Data.ByteString (ByteString)
import Data.Maybe (fromMaybe)
import HsLua.Core.Error
import HsLua.Core.Types as Lua
import 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.Storable as F
ensureTable :: LuaError e => StackIndex -> (Lua.State -> IO ()) -> LuaE e ()
ensureTable :: StackIndex -> (State -> IO ()) -> LuaE e ()
ensureTable StackIndex
idx State -> IO ()
ioOp = do
Bool
isTbl <- StackIndex -> LuaE e Bool
forall e. StackIndex -> LuaE e Bool
istable StackIndex
idx
if Bool
isTbl
then (State -> IO ()) -> LuaE e ()
forall a e. (State -> IO a) -> LuaE e a
liftLua State -> IO ()
ioOp
else ByteString -> StackIndex -> LuaE e ()
forall e a. LuaError e => ByteString -> StackIndex -> LuaE e a
throwTypeMismatchError ByteString
"table" StackIndex
idx
{-# INLINE ensureTable #-}
absindex :: StackIndex -> LuaE e StackIndex
absindex :: StackIndex -> LuaE e StackIndex
absindex = (State -> StackIndex -> IO StackIndex)
-> StackIndex -> LuaE e StackIndex
forall a b e. (State -> a -> IO b) -> a -> LuaE e b
liftLua1 State -> StackIndex -> IO StackIndex
lua_absindex
{-# INLINABLE absindex #-}
call :: LuaError e => NumArgs -> NumResults -> LuaE e ()
call :: NumArgs -> NumResults -> LuaE e ()
call NumArgs
nargs NumResults
nresults = do
Status
res <- NumArgs -> NumResults -> Maybe StackIndex -> LuaE e Status
forall e.
NumArgs -> NumResults -> Maybe StackIndex -> LuaE e Status
pcall NumArgs
nargs NumResults
nresults Maybe StackIndex
forall a. Maybe a
Nothing
Bool -> LuaE e () -> LuaE e ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Status
res Status -> Status -> Bool
forall a. Eq a => a -> a -> Bool
/= Status
OK) LuaE e ()
forall e a. LuaError e => LuaE e a
throwErrorAsException
{-# INLINABLE call #-}
checkstack :: Int -> LuaE e Bool
checkstack :: Int -> LuaE e Bool
checkstack Int
n = (State -> IO Bool) -> LuaE e Bool
forall a e. (State -> IO a) -> LuaE e a
liftLua ((State -> IO Bool) -> LuaE e Bool)
-> (State -> IO Bool) -> LuaE e Bool
forall a b. (a -> b) -> a -> b
$ \State
l ->
LuaBool -> Bool
fromLuaBool (LuaBool -> Bool) -> IO LuaBool -> IO Bool
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> State -> CInt -> IO LuaBool
lua_checkstack State
l (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n)
{-# INLINABLE checkstack #-}
close :: Lua.State -> IO ()
close :: State -> IO ()
close = State -> IO ()
lua_close
{-# INLINABLE close #-}
compare :: LuaError e
=> StackIndex
-> StackIndex
-> RelationalOperator
-> LuaE e Bool
compare :: StackIndex -> StackIndex -> RelationalOperator -> LuaE e Bool
compare StackIndex
idx1 StackIndex
idx2 RelationalOperator
relOp = LuaBool -> Bool
fromLuaBool (LuaBool -> Bool) -> LuaE e LuaBool -> LuaE e Bool
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> (State -> Ptr StatusCode -> IO LuaBool) -> LuaE e LuaBool
forall e a.
LuaError e =>
(State -> Ptr StatusCode -> IO a) -> LuaE e a
liftLuaThrow
(\State
l -> State
-> StackIndex
-> StackIndex
-> OPCode
-> Ptr StatusCode
-> IO LuaBool
hslua_compare State
l StackIndex
idx1 StackIndex
idx2 (RelationalOperator -> OPCode
fromRelationalOperator RelationalOperator
relOp))
{-# INLINABLE compare #-}
concat :: LuaError e => NumArgs -> LuaE e ()
concat :: NumArgs -> LuaE e ()
concat NumArgs
n = (State -> Ptr StatusCode -> IO ()) -> LuaE e ()
forall e a.
LuaError e =>
(State -> Ptr StatusCode -> IO a) -> LuaE e a
liftLuaThrow (State -> NumArgs -> Ptr StatusCode -> IO ()
`hslua_concat` NumArgs
n)
{-# INLINABLE concat #-}
copy :: StackIndex -> StackIndex -> LuaE e ()
copy :: StackIndex -> StackIndex -> LuaE e ()
copy StackIndex
fromidx StackIndex
toidx = (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 -> StackIndex -> StackIndex -> IO ()
lua_copy State
l StackIndex
fromidx StackIndex
toidx
{-# INLINABLE copy #-}
createtable :: Int -> Int -> LuaE e ()
createtable :: Int -> Int -> LuaE e ()
createtable Int
narr Int
nrec = (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 -> 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)
{-# INLINABLE createtable #-}
equal :: LuaError e
=> StackIndex
-> StackIndex
-> LuaE e Bool
equal :: StackIndex -> StackIndex -> LuaE e Bool
equal StackIndex
index1 StackIndex
index2 = StackIndex -> StackIndex -> RelationalOperator -> LuaE e Bool
forall e.
LuaError e =>
StackIndex -> StackIndex -> RelationalOperator -> LuaE e Bool
compare StackIndex
index1 StackIndex
index2 RelationalOperator
EQ
{-# INLINABLE equal #-}
error :: LuaE e NumResults
error :: LuaE e NumResults
error = (State -> IO NumResults) -> LuaE e NumResults
forall a e. (State -> IO a) -> LuaE e a
liftLua State -> IO NumResults
hslua_error
{-# INLINABLE error #-}
gc :: GCControl -> LuaE e Int
gc :: GCControl -> LuaE e Int
gc GCControl
what = (State -> IO Int) -> LuaE e Int
forall a e. (State -> IO a) -> LuaE e a
liftLua ((State -> IO Int) -> LuaE e Int)
-> (State -> IO Int) -> LuaE e 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 (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> State -> GCCode -> CInt -> IO CInt
lua_gc State
l (GCControl -> GCCode
toGCcode GCControl
what) (GCControl -> CInt
toGCdata GCControl
what)
{-# INLINABLE gc #-}
getfield :: LuaError e => StackIndex -> Name -> LuaE e Type
getfield :: StackIndex -> Name -> LuaE e Type
getfield StackIndex
i (Name ByteString
s) = do
StackIndex
absidx <- StackIndex -> LuaE e StackIndex
forall e. StackIndex -> LuaE e StackIndex
absindex StackIndex
i
ByteString -> LuaE e ()
forall e. ByteString -> LuaE e ()
pushstring ByteString
s
StackIndex -> LuaE e Type
forall e. LuaError e => StackIndex -> LuaE e Type
gettable StackIndex
absidx
{-# INLINABLE getfield #-}
getglobal :: LuaError e => Name -> LuaE e Type
getglobal :: Name -> LuaE e Type
getglobal (Name ByteString
name) = (State -> Ptr StatusCode -> IO Type) -> LuaE e Type
forall e a.
LuaError e =>
(State -> Ptr StatusCode -> IO a) -> LuaE e a
liftLuaThrow ((State -> Ptr StatusCode -> IO Type) -> LuaE e Type)
-> (State -> Ptr StatusCode -> IO Type) -> LuaE e Type
forall a b. (a -> b) -> a -> b
$ \State
l Ptr StatusCode
status' ->
ByteString -> (CStringLen -> IO Type) -> IO Type
forall a. ByteString -> (CStringLen -> IO a) -> IO a
B.unsafeUseAsCStringLen ByteString
name ((CStringLen -> IO Type) -> IO Type)
-> (CStringLen -> IO Type) -> IO Type
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
namePtr, Int
len) ->
TypeCode -> Type
toType (TypeCode -> Type) -> IO TypeCode -> IO Type
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> State -> Ptr CChar -> CSize -> Ptr StatusCode -> IO TypeCode
hslua_getglobal State
l Ptr CChar
namePtr (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len) Ptr StatusCode
status'
{-# INLINABLE getglobal #-}
getmetatable :: StackIndex -> LuaE e Bool
getmetatable :: StackIndex -> LuaE e Bool
getmetatable StackIndex
n = (State -> IO Bool) -> LuaE e Bool
forall a e. (State -> IO a) -> LuaE e a
liftLua ((State -> IO Bool) -> LuaE e Bool)
-> (State -> IO Bool) -> LuaE e Bool
forall a b. (a -> b) -> a -> b
$ \State
l ->
LuaBool -> Bool
fromLuaBool (LuaBool -> Bool) -> IO LuaBool -> IO Bool
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> State -> StackIndex -> IO LuaBool
lua_getmetatable State
l StackIndex
n
{-# INLINABLE getmetatable #-}
gettable :: LuaError e => StackIndex -> LuaE e Type
gettable :: StackIndex -> LuaE e Type
gettable StackIndex
n = (State -> Ptr StatusCode -> IO Type) -> LuaE e Type
forall e a.
LuaError e =>
(State -> Ptr StatusCode -> IO a) -> LuaE e a
liftLuaThrow (\State
l -> (TypeCode -> Type) -> IO TypeCode -> IO Type
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap TypeCode -> Type
toType (IO TypeCode -> IO Type)
-> (Ptr StatusCode -> IO TypeCode) -> Ptr StatusCode -> IO Type
forall b c a. (b -> c) -> (a -> b) -> a -> c
. State -> StackIndex -> Ptr StatusCode -> IO TypeCode
hslua_gettable State
l StackIndex
n)
{-# INLINABLE gettable #-}
gettop :: LuaE e StackIndex
gettop :: LuaE e StackIndex
gettop = (State -> IO StackIndex) -> LuaE e StackIndex
forall a e. (State -> IO a) -> LuaE e a
liftLua State -> IO StackIndex
lua_gettop
{-# INLINABLE gettop #-}
getuservalue :: StackIndex -> LuaE e Type
getuservalue :: StackIndex -> LuaE e Type
getuservalue StackIndex
idx = TypeCode -> Type
toType (TypeCode -> Type) -> LuaE e TypeCode -> LuaE e Type
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (State -> IO TypeCode) -> LuaE e TypeCode
forall a e. (State -> IO a) -> LuaE e a
liftLua (State -> StackIndex -> IO TypeCode
`lua_getuservalue` StackIndex
idx)
insert :: StackIndex -> LuaE e ()
insert :: StackIndex -> LuaE e ()
insert StackIndex
index = (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 -> StackIndex -> IO ()
lua_insert State
l StackIndex
index
{-# INLINABLE insert #-}
isboolean :: StackIndex -> LuaE e Bool
isboolean :: StackIndex -> LuaE e Bool
isboolean StackIndex
n = (State -> IO Bool) -> LuaE e Bool
forall a e. (State -> IO a) -> LuaE e a
liftLua ((State -> IO Bool) -> LuaE e Bool)
-> (State -> IO Bool) -> LuaE e Bool
forall a b. (a -> b) -> a -> b
$ \State
l -> LuaBool -> Bool
fromLuaBool (LuaBool -> Bool) -> IO LuaBool -> IO Bool
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> State -> StackIndex -> IO LuaBool
lua_isboolean State
l StackIndex
n
{-# INLINABLE isboolean #-}
iscfunction :: StackIndex -> LuaE e Bool
iscfunction :: StackIndex -> LuaE e Bool
iscfunction StackIndex
n = (State -> IO Bool) -> LuaE e Bool
forall a e. (State -> IO a) -> LuaE e a
liftLua ((State -> IO Bool) -> LuaE e Bool)
-> (State -> IO Bool) -> LuaE e Bool
forall a b. (a -> b) -> a -> b
$ \State
l -> LuaBool -> Bool
fromLuaBool (LuaBool -> Bool) -> IO LuaBool -> IO Bool
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> State -> StackIndex -> IO LuaBool
lua_iscfunction State
l StackIndex
n
{-# INLINABLE iscfunction #-}
isfunction :: StackIndex -> LuaE e Bool
isfunction :: StackIndex -> LuaE e Bool
isfunction StackIndex
n = (State -> IO Bool) -> LuaE e Bool
forall a e. (State -> IO a) -> LuaE e a
liftLua ((State -> IO Bool) -> LuaE e Bool)
-> (State -> IO Bool) -> LuaE e Bool
forall a b. (a -> b) -> a -> b
$ \State
l -> LuaBool -> Bool
fromLuaBool (LuaBool -> Bool) -> IO LuaBool -> IO Bool
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> State -> StackIndex -> IO LuaBool
lua_isfunction State
l StackIndex
n
{-# INLINABLE isfunction #-}
isinteger :: StackIndex -> LuaE e Bool
isinteger :: StackIndex -> LuaE e Bool
isinteger StackIndex
n = (State -> IO Bool) -> LuaE e Bool
forall a e. (State -> IO a) -> LuaE e a
liftLua ((State -> IO Bool) -> LuaE e Bool)
-> (State -> IO Bool) -> LuaE e Bool
forall a b. (a -> b) -> a -> b
$ \State
l -> LuaBool -> Bool
fromLuaBool (LuaBool -> Bool) -> IO LuaBool -> IO Bool
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> State -> StackIndex -> IO LuaBool
lua_isinteger State
l StackIndex
n
{-# INLINABLE isinteger #-}
islightuserdata :: StackIndex -> LuaE e Bool
islightuserdata :: StackIndex -> LuaE e Bool
islightuserdata StackIndex
n = (State -> IO Bool) -> LuaE e Bool
forall a e. (State -> IO a) -> LuaE e a
liftLua ((State -> IO Bool) -> LuaE e Bool)
-> (State -> IO Bool) -> LuaE e Bool
forall a b. (a -> b) -> a -> b
$ \State
l -> LuaBool -> Bool
fromLuaBool (LuaBool -> Bool) -> IO LuaBool -> IO Bool
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> State -> StackIndex -> IO LuaBool
lua_islightuserdata State
l StackIndex
n
{-# INLINABLE islightuserdata #-}
isnil :: StackIndex -> LuaE e Bool
isnil :: StackIndex -> LuaE e Bool
isnil StackIndex
n = (State -> IO Bool) -> LuaE e Bool
forall a e. (State -> IO a) -> LuaE e a
liftLua ((State -> IO Bool) -> LuaE e Bool)
-> (State -> IO Bool) -> LuaE e Bool
forall a b. (a -> b) -> a -> b
$ \State
l -> LuaBool -> Bool
fromLuaBool (LuaBool -> Bool) -> IO LuaBool -> IO Bool
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> State -> StackIndex -> IO LuaBool
lua_isnil State
l StackIndex
n
{-# INLINABLE isnil #-}
isnone :: StackIndex -> LuaE e Bool
isnone :: StackIndex -> LuaE e Bool
isnone StackIndex
n = (State -> IO Bool) -> LuaE e Bool
forall a e. (State -> IO a) -> LuaE e a
liftLua ((State -> IO Bool) -> LuaE e Bool)
-> (State -> IO Bool) -> LuaE e Bool
forall a b. (a -> b) -> a -> b
$ \State
l -> LuaBool -> Bool
fromLuaBool (LuaBool -> Bool) -> IO LuaBool -> IO Bool
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> State -> StackIndex -> IO LuaBool
lua_isnone State
l StackIndex
n
{-# INLINABLE isnone #-}
isnoneornil :: StackIndex -> LuaE e Bool
isnoneornil :: StackIndex -> LuaE e Bool
isnoneornil StackIndex
n = (State -> IO Bool) -> LuaE e Bool
forall a e. (State -> IO a) -> LuaE e a
liftLua ((State -> IO Bool) -> LuaE e Bool)
-> (State -> IO Bool) -> LuaE e Bool
forall a b. (a -> b) -> a -> b
$ \State
l -> LuaBool -> Bool
fromLuaBool (LuaBool -> Bool) -> IO LuaBool -> IO Bool
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> State -> StackIndex -> IO LuaBool
lua_isnoneornil State
l StackIndex
n
{-# INLINABLE isnoneornil #-}
isnumber :: StackIndex -> LuaE e Bool
isnumber :: StackIndex -> LuaE e Bool
isnumber StackIndex
n = (State -> IO Bool) -> LuaE e Bool
forall a e. (State -> IO a) -> LuaE e a
liftLua ((State -> IO Bool) -> LuaE e Bool)
-> (State -> IO Bool) -> LuaE e Bool
forall a b. (a -> b) -> a -> b
$ \State
l -> LuaBool -> Bool
fromLuaBool (LuaBool -> Bool) -> IO LuaBool -> IO Bool
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> State -> StackIndex -> IO LuaBool
lua_isnumber State
l StackIndex
n
{-# INLINABLE isnumber #-}
isstring :: StackIndex -> LuaE e Bool
isstring :: StackIndex -> LuaE e Bool
isstring StackIndex
n = (State -> IO Bool) -> LuaE e Bool
forall a e. (State -> IO a) -> LuaE e a
liftLua ((State -> IO Bool) -> LuaE e Bool)
-> (State -> IO Bool) -> LuaE e Bool
forall a b. (a -> b) -> a -> b
$ \State
l -> LuaBool -> Bool
fromLuaBool (LuaBool -> Bool) -> IO LuaBool -> IO Bool
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> State -> StackIndex -> IO LuaBool
lua_isstring State
l StackIndex
n
{-# INLINABLE isstring #-}
istable :: StackIndex -> LuaE e Bool
istable :: StackIndex -> LuaE e Bool
istable StackIndex
n = (State -> IO Bool) -> LuaE e Bool
forall a e. (State -> IO a) -> LuaE e a
liftLua ((State -> IO Bool) -> LuaE e Bool)
-> (State -> IO Bool) -> LuaE e Bool
forall a b. (a -> b) -> a -> b
$ \State
l -> LuaBool -> Bool
fromLuaBool (LuaBool -> Bool) -> IO LuaBool -> IO Bool
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> State -> StackIndex -> IO LuaBool
lua_istable State
l StackIndex
n
{-# INLINABLE istable #-}
isthread :: StackIndex -> LuaE e Bool
isthread :: StackIndex -> LuaE e Bool
isthread StackIndex
n = (State -> IO Bool) -> LuaE e Bool
forall a e. (State -> IO a) -> LuaE e a
liftLua ((State -> IO Bool) -> LuaE e Bool)
-> (State -> IO Bool) -> LuaE e Bool
forall a b. (a -> b) -> a -> b
$ \State
l -> LuaBool -> Bool
fromLuaBool (LuaBool -> Bool) -> IO LuaBool -> IO Bool
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> State -> StackIndex -> IO LuaBool
lua_isthread State
l StackIndex
n
{-# INLINABLE isthread #-}
isuserdata :: StackIndex -> LuaE e Bool
isuserdata :: StackIndex -> LuaE e Bool
isuserdata StackIndex
n = (State -> IO Bool) -> LuaE e Bool
forall a e. (State -> IO a) -> LuaE e a
liftLua ((State -> IO Bool) -> LuaE e Bool)
-> (State -> IO Bool) -> LuaE e Bool
forall a b. (a -> b) -> a -> b
$ \State
l -> LuaBool -> Bool
fromLuaBool (LuaBool -> Bool) -> IO LuaBool -> IO Bool
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> State -> StackIndex -> IO LuaBool
lua_isuserdata State
l StackIndex
n
{-# INLINABLE isuserdata #-}
lessthan :: LuaError e => StackIndex -> StackIndex -> LuaE e Bool
lessthan :: StackIndex -> StackIndex -> LuaE e Bool
lessthan StackIndex
index1 StackIndex
index2 = StackIndex -> StackIndex -> RelationalOperator -> LuaE e Bool
forall e.
LuaError e =>
StackIndex -> StackIndex -> RelationalOperator -> LuaE e Bool
compare StackIndex
index1 StackIndex
index2 RelationalOperator
LT
{-# INLINABLE lessthan #-}
load :: Lua.Reader -> Ptr () -> Name -> LuaE e Status
load :: Reader -> Ptr () -> Name -> LuaE e Status
load Reader
reader Ptr ()
data' (Name ByteString
chunkname) = (State -> IO Status) -> LuaE e Status
forall a e. (State -> IO a) -> LuaE e a
liftLua ((State -> IO Status) -> LuaE e Status)
-> (State -> IO Status) -> LuaE e 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 (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m 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
{-# INLINABLE load #-}
ltype :: StackIndex -> LuaE e Type
ltype :: StackIndex -> LuaE e Type
ltype StackIndex
idx = TypeCode -> Type
toType (TypeCode -> Type) -> LuaE e TypeCode -> LuaE e Type
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> (State -> IO TypeCode) -> LuaE e TypeCode
forall a e. (State -> IO a) -> LuaE e a
liftLua (State -> StackIndex -> IO TypeCode
`lua_type` StackIndex
idx)
{-# INLINABLE ltype #-}
newtable :: LuaE e ()
newtable :: LuaE e ()
newtable = Int -> Int -> LuaE e ()
forall e. Int -> Int -> LuaE e ()
createtable Int
0 Int
0
{-# INLINABLE newtable #-}
newuserdata :: Int -> LuaE e (Ptr ())
newuserdata :: Int -> LuaE e (Ptr ())
newuserdata = (State -> CSize -> IO (Ptr ())) -> CSize -> LuaE e (Ptr ())
forall a b e. (State -> a -> IO b) -> a -> LuaE e b
liftLua1 State -> CSize -> IO (Ptr ())
lua_newuserdata (CSize -> LuaE e (Ptr ()))
-> (Int -> CSize) -> Int -> LuaE e (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# INLINABLE newuserdata #-}
next :: LuaError e => StackIndex -> LuaE e Bool
next :: StackIndex -> LuaE e Bool
next StackIndex
idx = LuaBool -> Bool
fromLuaBool (LuaBool -> Bool) -> LuaE e LuaBool -> LuaE e Bool
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> (State -> Ptr StatusCode -> IO LuaBool) -> LuaE e LuaBool
forall e a.
LuaError e =>
(State -> Ptr StatusCode -> IO a) -> LuaE e a
liftLuaThrow (\State
l -> State -> StackIndex -> Ptr StatusCode -> IO LuaBool
hslua_next State
l StackIndex
idx)
{-# INLINABLE next #-}
openlibs :: LuaE e ()
openlibs :: LuaE e ()
openlibs = (State -> IO ()) -> LuaE e ()
forall a e. (State -> IO a) -> LuaE e a
liftLua State -> IO ()
luaL_openlibs
{-# INLINABLE openlibs #-}
openbase :: LuaError e => LuaE e ()
openbase :: LuaE e ()
openbase = CFunction -> LuaE e ()
forall e. CFunction -> LuaE e ()
pushcfunction CFunction
luaopen_base LuaE e () -> LuaE e () -> LuaE e ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> NumArgs -> NumResults -> LuaE e ()
forall e. LuaError e => NumArgs -> NumResults -> LuaE e ()
call NumArgs
0 NumResults
multret
{-# INLINABLE openbase #-}
opendebug :: LuaError e => LuaE e ()
opendebug :: LuaE e ()
opendebug = CFunction -> LuaE e ()
forall e. CFunction -> LuaE e ()
pushcfunction CFunction
luaopen_debug LuaE e () -> LuaE e () -> LuaE e ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> NumArgs -> NumResults -> LuaE e ()
forall e. LuaError e => NumArgs -> NumResults -> LuaE e ()
call NumArgs
0 NumResults
multret
{-# INLINABLE opendebug #-}
openio :: LuaError e => LuaE e ()
openio :: LuaE e ()
openio = CFunction -> LuaE e ()
forall e. CFunction -> LuaE e ()
pushcfunction CFunction
luaopen_io LuaE e () -> LuaE e () -> LuaE e ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> NumArgs -> NumResults -> LuaE e ()
forall e. LuaError e => NumArgs -> NumResults -> LuaE e ()
call NumArgs
0 NumResults
multret
{-# INLINABLE openio #-}
openmath :: LuaError e => LuaE e ()
openmath :: LuaE e ()
openmath = CFunction -> LuaE e ()
forall e. CFunction -> LuaE e ()
pushcfunction CFunction
luaopen_math LuaE e () -> LuaE e () -> LuaE e ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> NumArgs -> NumResults -> LuaE e ()
forall e. LuaError e => NumArgs -> NumResults -> LuaE e ()
call NumArgs
0 NumResults
multret
{-# INLINABLE openmath #-}
openos :: LuaError e => LuaE e ()
openos :: LuaE e ()
openos = CFunction -> LuaE e ()
forall e. CFunction -> LuaE e ()
pushcfunction CFunction
luaopen_os LuaE e () -> LuaE e () -> LuaE e ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> NumArgs -> NumResults -> LuaE e ()
forall e. LuaError e => NumArgs -> NumResults -> LuaE e ()
call NumArgs
0 NumResults
multret
{-# INLINABLE openos #-}
openpackage :: LuaError e => LuaE e ()
openpackage :: LuaE e ()
openpackage = CFunction -> LuaE e ()
forall e. CFunction -> LuaE e ()
pushcfunction CFunction
luaopen_package LuaE e () -> LuaE e () -> LuaE e ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> NumArgs -> NumResults -> LuaE e ()
forall e. LuaError e => NumArgs -> NumResults -> LuaE e ()
call NumArgs
0 NumResults
multret
{-# INLINABLE openpackage #-}
openstring :: LuaError e => LuaE e ()
openstring :: LuaE e ()
openstring = CFunction -> LuaE e ()
forall e. CFunction -> LuaE e ()
pushcfunction CFunction
luaopen_string LuaE e () -> LuaE e () -> LuaE e ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> NumArgs -> NumResults -> LuaE e ()
forall e. LuaError e => NumArgs -> NumResults -> LuaE e ()
call NumArgs
0 NumResults
multret
{-# INLINABLE openstring #-}
opentable :: LuaError e => LuaE e ()
opentable :: LuaE e ()
opentable = CFunction -> LuaE e ()
forall e. CFunction -> LuaE e ()
pushcfunction CFunction
luaopen_table LuaE e () -> LuaE e () -> LuaE e ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> NumArgs -> NumResults -> LuaE e ()
forall e. LuaError e => NumArgs -> NumResults -> LuaE e ()
call NumArgs
0 NumResults
multret
{-# INLINABLE opentable #-}
pcall :: NumArgs -> NumResults -> Maybe StackIndex -> LuaE e Status
pcall :: NumArgs -> NumResults -> Maybe StackIndex -> LuaE e Status
pcall NumArgs
nargs NumResults
nresults Maybe StackIndex
msgh = (State -> IO Status) -> LuaE e Status
forall a e. (State -> IO a) -> LuaE e a
liftLua ((State -> IO Status) -> LuaE e Status)
-> (State -> IO Status) -> LuaE e Status
forall a b. (a -> b) -> a -> b
$ \State
l ->
StatusCode -> Status
toStatus (StatusCode -> Status) -> IO StatusCode -> IO Status
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m 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)
{-# INLINABLE pcall #-}
pop :: Int -> LuaE e ()
pop :: Int -> LuaE e ()
pop Int
n = (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 -> CInt -> IO ()
lua_pop State
l (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n)
{-# INLINABLE pop #-}
pushboolean :: Bool -> LuaE e ()
pushboolean :: Bool -> LuaE e ()
pushboolean Bool
b = (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 -> LuaBool -> IO ()
lua_pushboolean State
l (Bool -> LuaBool
toLuaBool Bool
b)
{-# INLINABLE pushboolean #-}
pushcclosure :: CFunction -> NumArgs -> LuaE e ()
pushcclosure :: CFunction -> NumArgs -> LuaE e ()
pushcclosure CFunction
f NumArgs
n = (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 -> CFunction -> NumArgs -> IO ()
lua_pushcclosure State
l CFunction
f NumArgs
n
{-# INLINABLE pushcclosure #-}
pushcfunction :: CFunction -> LuaE e ()
pushcfunction :: CFunction -> LuaE e ()
pushcfunction CFunction
f = CFunction -> NumArgs -> LuaE e ()
forall e. CFunction -> NumArgs -> LuaE e ()
pushcclosure CFunction
f NumArgs
0
{-# INLINABLE pushcfunction #-}
pushglobaltable :: LuaE e ()
pushglobaltable :: LuaE e ()
pushglobaltable = (State -> IO ()) -> LuaE e ()
forall a e. (State -> IO a) -> LuaE e a
liftLua State -> IO ()
lua_pushglobaltable
{-# INLINABLE pushglobaltable #-}
pushinteger :: Lua.Integer -> LuaE e ()
pushinteger :: Integer -> LuaE e ()
pushinteger = (State -> Integer -> IO ()) -> Integer -> LuaE e ()
forall a b e. (State -> a -> IO b) -> a -> LuaE e b
liftLua1 State -> Integer -> IO ()
lua_pushinteger
{-# INLINABLE pushinteger #-}
pushlightuserdata :: Ptr a -> LuaE e ()
pushlightuserdata :: Ptr a -> LuaE e ()
pushlightuserdata = (State -> Ptr a -> IO ()) -> Ptr a -> LuaE e ()
forall a b e. (State -> a -> IO b) -> a -> LuaE e b
liftLua1 State -> Ptr a -> IO ()
forall a. State -> Ptr a -> IO ()
lua_pushlightuserdata
{-# INLINABLE pushlightuserdata #-}
pushnil :: LuaE e ()
pushnil :: LuaE e ()
pushnil = (State -> IO ()) -> LuaE e ()
forall a e. (State -> IO a) -> LuaE e a
liftLua State -> IO ()
lua_pushnil
{-# INLINABLE pushnil #-}
pushnumber :: Lua.Number -> LuaE e ()
pushnumber :: Number -> LuaE e ()
pushnumber = (State -> Number -> IO ()) -> Number -> LuaE e ()
forall a b e. (State -> a -> IO b) -> a -> LuaE e b
liftLua1 State -> Number -> IO ()
lua_pushnumber
{-# INLINABLE pushnumber #-}
pushstring :: ByteString -> LuaE e ()
pushstring :: ByteString -> LuaE e ()
pushstring ByteString
s = (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 ->
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)
{-# INLINABLE pushstring #-}
pushthread :: LuaE e Bool
pushthread :: LuaE e Bool
pushthread = (CInt
1 CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
==) (CInt -> Bool) -> LuaE e CInt -> LuaE e Bool
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> (State -> IO CInt) -> LuaE e CInt
forall a e. (State -> IO a) -> LuaE e a
liftLua State -> IO CInt
lua_pushthread
{-# INLINABLE pushthread #-}
pushvalue :: StackIndex -> LuaE e ()
pushvalue :: StackIndex -> LuaE e ()
pushvalue StackIndex
n = (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 -> StackIndex -> IO ()
lua_pushvalue State
l StackIndex
n
{-# INLINABLE pushvalue #-}
rawequal :: StackIndex -> StackIndex -> LuaE e Bool
rawequal :: StackIndex -> StackIndex -> LuaE e Bool
rawequal StackIndex
idx1 StackIndex
idx2 = (State -> IO Bool) -> LuaE e Bool
forall a e. (State -> IO a) -> LuaE e a
liftLua ((State -> IO Bool) -> LuaE e Bool)
-> (State -> IO Bool) -> LuaE e Bool
forall a b. (a -> b) -> a -> b
$ \State
l ->
LuaBool -> Bool
fromLuaBool (LuaBool -> Bool) -> IO LuaBool -> IO Bool
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> State -> StackIndex -> StackIndex -> IO LuaBool
lua_rawequal State
l StackIndex
idx1 StackIndex
idx2
{-# INLINABLE rawequal #-}
rawget :: LuaError e => StackIndex -> LuaE e ()
rawget :: StackIndex -> LuaE e ()
rawget StackIndex
n = StackIndex -> (State -> IO ()) -> LuaE e ()
forall e. LuaError e => StackIndex -> (State -> IO ()) -> LuaE e ()
ensureTable StackIndex
n (\State
l -> State -> StackIndex -> IO ()
lua_rawget State
l StackIndex
n)
{-# INLINABLE rawget #-}
rawgeti :: LuaError e => StackIndex -> Lua.Integer -> LuaE e ()
rawgeti :: StackIndex -> Integer -> LuaE e ()
rawgeti StackIndex
k Integer
n = StackIndex -> (State -> IO ()) -> LuaE e ()
forall e. LuaError e => StackIndex -> (State -> IO ()) -> LuaE e ()
ensureTable StackIndex
k (\State
l -> State -> StackIndex -> Integer -> IO ()
lua_rawgeti State
l StackIndex
k Integer
n)
{-# INLINABLE rawgeti #-}
rawlen :: StackIndex -> LuaE e Int
rawlen :: StackIndex -> LuaE e Int
rawlen StackIndex
idx = (State -> IO Int) -> LuaE e Int
forall a e. (State -> IO a) -> LuaE e a
liftLua ((State -> IO Int) -> LuaE e Int)
-> (State -> IO Int) -> LuaE e 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 (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> State -> StackIndex -> IO CSize
lua_rawlen State
l StackIndex
idx
{-# INLINABLE rawlen #-}
rawset :: LuaError e => StackIndex -> LuaE e ()
rawset :: StackIndex -> LuaE e ()
rawset StackIndex
n = StackIndex -> (State -> IO ()) -> LuaE e ()
forall e. LuaError e => StackIndex -> (State -> IO ()) -> LuaE e ()
ensureTable StackIndex
n (\State
l -> State -> StackIndex -> IO ()
lua_rawset State
l StackIndex
n)
{-# INLINABLE rawset #-}
rawseti :: LuaError e => StackIndex -> Lua.Integer -> LuaE e ()
rawseti :: StackIndex -> Integer -> LuaE e ()
rawseti StackIndex
k Integer
m = StackIndex -> (State -> IO ()) -> LuaE e ()
forall e. LuaError e => StackIndex -> (State -> IO ()) -> LuaE e ()
ensureTable StackIndex
k (\State
l -> State -> StackIndex -> Integer -> IO ()
lua_rawseti State
l StackIndex
k Integer
m)
{-# INLINABLE rawseti #-}
register :: LuaError e => Name -> CFunction -> LuaE e ()
register :: Name -> CFunction -> LuaE e ()
register Name
name CFunction
f = do
CFunction -> LuaE e ()
forall e. CFunction -> LuaE e ()
pushcfunction CFunction
f
Name -> LuaE e ()
forall e. LuaError e => Name -> LuaE e ()
setglobal Name
name
{-# INLINABLE register #-}
remove :: StackIndex -> LuaE e ()
remove :: StackIndex -> LuaE e ()
remove StackIndex
n = (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 -> StackIndex -> IO ()
lua_remove State
l StackIndex
n
{-# INLINABLE remove #-}
replace :: StackIndex -> LuaE e ()
replace :: StackIndex -> LuaE e ()
replace StackIndex
n = (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 -> StackIndex -> IO ()
lua_replace State
l StackIndex
n
{-# INLINABLE replace #-}
setfield :: LuaError e => StackIndex -> Name -> LuaE e ()
setfield :: StackIndex -> Name -> LuaE e ()
setfield StackIndex
i (Name ByteString
s) = do
StackIndex
absidx <- StackIndex -> LuaE e StackIndex
forall e. StackIndex -> LuaE e StackIndex
absindex StackIndex
i
ByteString -> LuaE e ()
forall e. ByteString -> LuaE e ()
pushstring ByteString
s
StackIndex -> LuaE e ()
forall e. StackIndex -> LuaE e ()
insert (CInt -> StackIndex
nthTop CInt
2)
StackIndex -> LuaE e ()
forall e. LuaError e => StackIndex -> LuaE e ()
settable StackIndex
absidx
{-# INLINABLE setfield #-}
setglobal :: LuaError e => Name -> LuaE e ()
setglobal :: Name -> LuaE e ()
setglobal (Name ByteString
name) = (State -> Ptr StatusCode -> IO ()) -> LuaE e ()
forall e a.
LuaError e =>
(State -> Ptr StatusCode -> IO a) -> LuaE e a
liftLuaThrow ((State -> Ptr StatusCode -> IO ()) -> LuaE e ())
-> (State -> Ptr StatusCode -> IO ()) -> LuaE e ()
forall a b. (a -> b) -> a -> b
$ \State
l Ptr StatusCode
status' ->
ByteString -> (CStringLen -> IO ()) -> IO ()
forall a. ByteString -> (CStringLen -> IO a) -> IO a
B.unsafeUseAsCStringLen ByteString
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'
{-# INLINABLE setglobal #-}
setmetatable :: StackIndex -> LuaE e ()
setmetatable :: StackIndex -> LuaE e ()
setmetatable StackIndex
idx = (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 -> StackIndex -> IO ()
lua_setmetatable State
l StackIndex
idx
{-# INLINABLE setmetatable #-}
settable :: LuaError e => StackIndex -> LuaE e ()
settable :: StackIndex -> LuaE e ()
settable StackIndex
index = (State -> Ptr StatusCode -> IO ()) -> LuaE e ()
forall e a.
LuaError e =>
(State -> Ptr StatusCode -> IO a) -> LuaE e a
liftLuaThrow ((State -> Ptr StatusCode -> IO ()) -> LuaE e ())
-> (State -> Ptr StatusCode -> IO ()) -> LuaE e ()
forall a b. (a -> b) -> a -> b
$ \State
l -> State -> StackIndex -> Ptr StatusCode -> IO ()
hslua_settable State
l StackIndex
index
{-# INLINABLE settable #-}
settop :: StackIndex -> LuaE e ()
settop :: StackIndex -> LuaE e ()
settop = (State -> StackIndex -> IO ()) -> StackIndex -> LuaE e ()
forall a b e. (State -> a -> IO b) -> a -> LuaE e b
liftLua1 State -> StackIndex -> IO ()
lua_settop
{-# INLINABLE settop #-}
setuservalue :: StackIndex -> LuaE e ()
setuservalue :: StackIndex -> LuaE e ()
setuservalue StackIndex
idx = (State -> IO ()) -> LuaE e ()
forall a e. (State -> IO a) -> LuaE e a
liftLua (State -> StackIndex -> IO ()
`lua_setuservalue` StackIndex
idx)
status :: LuaE e Status
status :: LuaE e Status
status = (State -> IO Status) -> LuaE e Status
forall a e. (State -> IO a) -> LuaE e a
liftLua ((State -> IO Status) -> LuaE e Status)
-> (State -> IO Status) -> LuaE e 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
{-# INLINABLE status #-}
toboolean :: StackIndex -> LuaE e Bool
toboolean :: StackIndex -> LuaE e Bool
toboolean StackIndex
n = (State -> IO Bool) -> LuaE e Bool
forall a e. (State -> IO a) -> LuaE e a
liftLua ((State -> IO Bool) -> LuaE e Bool)
-> (State -> IO Bool) -> LuaE e Bool
forall a b. (a -> b) -> a -> b
$ \State
l -> LuaBool -> Bool
fromLuaBool (LuaBool -> Bool) -> IO LuaBool -> IO Bool
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> State -> StackIndex -> IO LuaBool
lua_toboolean State
l StackIndex
n
{-# INLINABLE toboolean #-}
tocfunction :: StackIndex -> LuaE e (Maybe CFunction)
tocfunction :: StackIndex -> LuaE e (Maybe CFunction)
tocfunction StackIndex
n = (State -> IO (Maybe CFunction)) -> LuaE e (Maybe CFunction)
forall a e. (State -> IO a) -> LuaE e a
liftLua ((State -> IO (Maybe CFunction)) -> LuaE e (Maybe CFunction))
-> (State -> IO (Maybe CFunction)) -> LuaE e (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)
{-# INLINABLE tocfunction #-}
tointeger :: StackIndex -> LuaE e (Maybe Lua.Integer)
tointeger :: StackIndex -> LuaE e (Maybe Integer)
tointeger StackIndex
n = (State -> IO (Maybe Integer)) -> LuaE e (Maybe Integer)
forall a e. (State -> IO a) -> LuaE e a
liftLua ((State -> IO (Maybe Integer)) -> LuaE e (Maybe Integer))
-> (State -> IO (Maybe Integer)) -> LuaE e (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 (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m 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)
{-# INLINABLE tointeger #-}
tonumber :: StackIndex -> LuaE e (Maybe Lua.Number)
tonumber :: StackIndex -> LuaE e (Maybe Number)
tonumber StackIndex
n = (State -> IO (Maybe Number)) -> LuaE e (Maybe Number)
forall a e. (State -> IO a) -> LuaE e a
liftLua ((State -> IO (Maybe Number)) -> LuaE e (Maybe Number))
-> (State -> IO (Maybe Number)) -> LuaE e (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 (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m 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)
{-# INLINABLE tonumber #-}
topointer :: StackIndex -> LuaE e (Ptr ())
topointer :: StackIndex -> LuaE e (Ptr ())
topointer StackIndex
n = (State -> IO (Ptr ())) -> LuaE e (Ptr ())
forall a e. (State -> IO a) -> LuaE e a
liftLua ((State -> IO (Ptr ())) -> LuaE e (Ptr ()))
-> (State -> IO (Ptr ())) -> LuaE e (Ptr ())
forall a b. (a -> b) -> a -> b
$ \State
l -> State -> StackIndex -> IO (Ptr ())
lua_topointer State
l StackIndex
n
{-# INLINABLE topointer #-}
tostring :: StackIndex -> LuaE e (Maybe ByteString)
tostring :: StackIndex -> LuaE e (Maybe ByteString)
tostring StackIndex
n = (State -> IO (Maybe ByteString)) -> LuaE e (Maybe ByteString)
forall a e. (State -> IO a) -> LuaE e a
liftLua ((State -> IO (Maybe ByteString)) -> LuaE e (Maybe ByteString))
-> (State -> IO (Maybe ByteString)) -> LuaE e (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 (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> CStringLen -> IO ByteString
B.packCStringLen (Ptr CChar
cstr, CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
cstrLen)
{-# INLINABLE tostring #-}
tothread :: StackIndex -> LuaE e (Maybe Lua.State)
tothread :: StackIndex -> LuaE e (Maybe State)
tothread StackIndex
n = (State -> IO (Maybe State)) -> LuaE e (Maybe State)
forall a e. (State -> IO a) -> LuaE e a
liftLua ((State -> IO (Maybe State)) -> LuaE e (Maybe State))
-> (State -> IO (Maybe State)) -> LuaE e (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)
{-# INLINABLE tothread #-}
touserdata :: StackIndex -> LuaE e (Maybe (Ptr a))
touserdata :: StackIndex -> LuaE e (Maybe (Ptr a))
touserdata StackIndex
n = (State -> IO (Maybe (Ptr a))) -> LuaE e (Maybe (Ptr a))
forall a e. (State -> IO a) -> LuaE e a
liftLua ((State -> IO (Maybe (Ptr a))) -> LuaE e (Maybe (Ptr a)))
-> (State -> IO (Maybe (Ptr a))) -> LuaE e (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)
{-# INLINABLE touserdata #-}
typename :: Type -> LuaE e ByteString
typename :: Type -> LuaE e ByteString
typename Type
tp = (State -> IO ByteString) -> LuaE e ByteString
forall a e. (State -> IO a) -> LuaE e a
liftLua ((State -> IO ByteString) -> LuaE e ByteString)
-> (State -> IO ByteString) -> LuaE e ByteString
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 ByteString) -> IO ByteString
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Ptr CChar -> IO ByteString
B.packCString
{-# INLINABLE typename #-}
upvalueindex :: StackIndex -> StackIndex
upvalueindex :: StackIndex -> StackIndex
upvalueindex StackIndex
i = StackIndex
registryindex StackIndex -> StackIndex -> StackIndex
forall a. Num a => a -> a -> a
- StackIndex
i
{-# INLINABLE upvalueindex #-}