{-# OPTIONS_GHC -Wno-warnings-deprecations #-}
{-# LANGUAGE PatternSynonyms #-}
module Lua
(
withNewState
, State (..)
, Reader
, CFunction
, PreCFunction
, Lua.Integer (..)
, Number (..)
, LuaBool (..)
, pattern TRUE
, pattern FALSE
, StackIndex (..)
, pattern LUA_REGISTRYINDEX
, NumArgs (..)
, NumResults (..)
, pattern LUA_MULTRET
, TypeCode (..)
, pattern LUA_TNONE
, pattern LUA_TNIL
, pattern LUA_TBOOLEAN
, pattern LUA_TLIGHTUSERDATA
, pattern LUA_TNUMBER
, pattern LUA_TSTRING
, pattern LUA_TTABLE
, pattern LUA_TFUNCTION
, pattern LUA_TUSERDATA
, pattern LUA_TTHREAD
, OPCode (..)
, pattern LUA_OPEQ
, pattern LUA_OPLT
, pattern LUA_OPLE
, StatusCode (..)
, pattern LUA_OK
, pattern LUA_YIELD
, pattern LUA_ERRRUN
, pattern LUA_ERRSYNTAX
, pattern LUA_ERRMEM
, pattern LUA_ERRGCMM
, pattern LUA_ERRERR
, pattern LUA_ERRFILE
, nthTop
, nthBottom
, nth
, top
,
lua_close
, lua_newthread
, lua_absindex
, lua_gettop
, lua_settop
, lua_pushvalue
, lua_pop
, lua_copy
, lua_remove
, lua_insert
, lua_replace
, lua_checkstack
, lua_isnil
, lua_isboolean
, lua_isnumber
, lua_isinteger
, lua_isstring
, lua_isfunction
, lua_istable
, lua_iscfunction
, lua_isuserdata
, lua_islightuserdata
, lua_isthread
, lua_isnone
, lua_isnoneornil
, lua_type
, lua_typename
, lua_rawequal
, lua_toboolean
, lua_tocfunction
, lua_tointegerx
, lua_tonumberx
, lua_tolstring
, lua_topointer
, lua_tothread
, lua_touserdata
, lua_rawlen
, lua_pushnil
, lua_pushnumber
, lua_pushinteger
, lua_pushlstring
, lua_pushstring
, lua_pushcclosure
, lua_pushboolean
, lua_pushlightuserdata
, lua_pushthread
, lua_rawget
, lua_rawgeti
, lua_createtable
, lua_newuserdata
, lua_getmetatable
, lua_getuservalue
, lua_getglobal
, lua_gettable
, lua_rawset
, lua_rawseti
, lua_setmetatable
, lua_setuservalue
, lua_setglobal
, lua_settable
, lua_concat
, lua_next
, lua_pcall
, lua_load
, lua_status
, lua_gc
, GCCode (..)
, pattern LUA_GCSTOP
, pattern LUA_GCRESTART
, pattern LUA_GCCOLLECT
, pattern LUA_GCCOUNT
, pattern LUA_GCCOUNTB
, pattern LUA_GCSTEP
, pattern LUA_GCSETPAUSE
, pattern LUA_GCSETSTEPMUL
, pattern LUA_GCISRUNNING
, lua_pushglobaltable
, luaL_getmetafield
, luaL_getmetatable
, luaL_loadbuffer
, luaL_openlibs
, luaL_newmetatable
, luaL_ref
, luaL_testudata
, luaL_traceback
, luaL_unref
, loadedTableRegistryField
, preloadTableRegistryField
, Reference (..)
, pattern LUA_REFNIL
, pattern LUA_NOREF
, fromReference
, toReference
, hsluaL_newstate
, hsluaL_tolstring
, hslua_gettable
, hslua_getglobal
, hslua_settable
, hslua_setglobal
, hslua_error
, hslua_next
, hslua_concat
, hslua_compare
, luaopen_base
, luaopen_table
, luaopen_io
, luaopen_os
, luaopen_string
, luaopen_math
, luaopen_debug
, luaopen_package
, hslua_pushhsfunction
) where
import Foreign.C (CInt)
import Lua.Auxiliary
import Lua.Call
import Lua.Constants
import Lua.Ersatz.Functions
import Lua.Ersatz.Auxiliary
import Lua.Lib
import Lua.Primary
import Lua.Types as Lua
withNewState :: (State -> IO a) -> IO a
withNewState :: (State -> IO a) -> IO a
withNewState State -> IO a
f = do
State
l <- IO State
hsluaL_newstate
a
result <- State -> IO a
f State
l
State -> IO ()
lua_close State
l
a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return a
result
nthTop :: CInt -> StackIndex
nthTop :: CInt -> StackIndex
nthTop CInt
n = CInt -> StackIndex
StackIndex (-CInt
n)
{-# INLINABLE nthTop #-}
nthBottom :: CInt -> StackIndex
nthBottom :: CInt -> StackIndex
nthBottom = CInt -> StackIndex
StackIndex
{-# INLINABLE nthBottom #-}
nth :: CInt -> StackIndex
nth :: CInt -> StackIndex
nth = CInt -> StackIndex
nthTop
{-# INLINABLE nth #-}
top :: StackIndex
top :: StackIndex
top = CInt -> StackIndex
nthTop CInt
1
{-# INLINABLE top #-}