{-# LINE 1 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
{-
{-# LINE 2 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
Copyright © 2007-2012 Gracjan Polak
Copyright © 2012-2016 Ömer Sinan Ağacan
Copyright © 2017 Albert Krewinkel

Permission is hereby granted, free of charge, to any person obtaining a copy
of this software and associated documentation files (the "Software"), to deal
in the Software without restriction, including without limitation the rights
to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
copies of the Software, and to permit persons to whom the Software is
furnished to do so, subject to the following conditions:

The above copyright notice and this permission notice shall be included in
all copies or substantial portions of the Software.

THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT.  IN NO EVENT SHALL THE
AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN
THE SOFTWARE.
-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-|
Module      : Foreign.Lua.Api.RawBindings
Copyright   : © 2007–2012 Gracjan Polak,
                2012–2016 Ömer Sinan Ağacan,
                2017 Albert Krewinkel
License     : MIT
Maintainer  : Albert Krewinkel <tarleb+hslua@zeitkraut.de>
Stability   : beta
Portability : ForeignFunctionInterface

Haskell bindings to lua C API functions.
-}
module Foreign.Lua.Api.RawBindings where

import Foreign.C
import Foreign.Lua.Api.Types
import Foreign.Ptr


{-# LINE 45 "src/Foreign/Lua/Api/RawBindings.hsc" #-}

{-# LINE 46 "src/Foreign/Lua/Api/RawBindings.hsc" #-}

-- TODO: lua_getallocf, lua_setallocf
-- TODO: Debugger functions

-- Some of the Lua functions may call a Haskell function, and trigger
-- garbage collection, rescheduling etc. This means we must declare these
-- functions as 'safe'.


--------------------------------------------------------------------------------
-- * State manipulation

-- lua_newstate is currently not supported.

-- | See <https://www.lua.org/manual/5.3/manual.html#lua_close lua_close>
foreign import ccall "lua.h lua_close"
  lua_close :: LuaState -> IO ()

-- lua_newthread is currently not supported.


--------------------------------------------------------------------------------
-- * Basic stack manipulation

-- | See <https://www.lua.org/manual/5.3/manual.html#lua_gettop lua_gettop>
foreign import ccall unsafe "lua.h lua_gettop"
  lua_gettop :: LuaState -> IO StackIndex

-- | See <https://www.lua.org/manual/5.3/manual.html#lua_settop lua_settop>

{-# LINE 76 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lua.h lua_settop"

{-# LINE 80 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  lua_settop :: LuaState -> StackIndex -> IO ()

-- | See <https://www.lua.org/manual/5.3/manual.html#lua_pushvalue lua_pushvalue>

{-# LINE 84 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lua.h lua_pushvalue"

{-# LINE 88 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  lua_pushvalue :: LuaState -> StackIndex -> IO ()


{-# LINE 91 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
-- | See <https://www.lua.org/manual/5.3/manual.html#lua_rotate lua_rotate>

{-# LINE 93 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lua.h lua_rotate"

{-# LINE 97 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  lua_rotate :: LuaState -> StackIndex -> CInt -> IO ()

-- | See <https://www.lua.org/manual/5.3/manual.html#lua_copy lua_copy>

{-# LINE 101 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lua.h lua_copy"

{-# LINE 105 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  lua_copy :: LuaState -> StackIndex -> StackIndex -> IO ()

{-# LINE 131 "src/Foreign/Lua/Api/RawBindings.hsc" #-}

-- | See <https://www.lua.org/manual/5.3/manual.html#lua_checkstack lua_checkstack>

{-# LINE 134 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lua.h lua_checkstack"

{-# LINE 138 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  lua_checkstack :: LuaState -> StackIndex -> IO LuaBool

-- lua_xmove is currently not supported.


--------------------------------------------------------------------------------
-- * Stack access functions

-- | See <https://www.lua.org/manual/5.3/manual.html#lua_isnumber lua_isnumber>

{-# LINE 148 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lua.h lua_isnumber"

{-# LINE 152 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  lua_isnumber :: LuaState -> StackIndex -> IO LuaBool

-- | See <https://www.lua.org/manual/5.3/manual.html#lua_isstring lua_isstring>

{-# LINE 156 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lua.h lua_isstring"

{-# LINE 160 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  lua_isstring :: LuaState -> StackIndex -> IO LuaBool

-- | See <https://www.lua.org/manual/5.3/manual.html#lua_iscfunction lua_iscfunction>

{-# LINE 164 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lua.h lua_iscfunction"

{-# LINE 168 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  lua_iscfunction :: LuaState -> StackIndex -> IO LuaBool

-- | See <https://www.lua.org/manual/5.3/manual.html#lua_isuserdata lua_isuserdata>

{-# LINE 172 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lua.h lua_isuserdata"

{-# LINE 176 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  lua_isuserdata :: LuaState -> StackIndex -> IO LuaBool

-- | See <https://www.lua.org/manual/5.3/manual.html#lua_type lua_type>

{-# LINE 180 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lua.h lua_type"

{-# LINE 184 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  lua_type :: LuaState -> StackIndex -> IO TypeCode

-- | See <https://www.lua.org/manual/5.3/manual.html#lua_typename lua_typename>

{-# LINE 188 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lua.h lua_typename"

{-# LINE 192 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  lua_typename :: LuaState -> TypeCode -> IO (Ptr CChar)

-- lua_compare is unsafe (might cause a longjmp), use hslua_compare instead.

{-# LINE 196 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
-- | Wrapper around <https://lua.org/manual/5.3/manual.html#lua_compare \
-- @lua_compare@> which catches any @longjmp@s.
foreign import ccall "safer-api.h hslua_compare"
  hslua_compare :: LuaState -> StackIndex -> StackIndex -> CInt
                -> IO (Failable LuaBool)

{-# LINE 210 "src/Foreign/Lua/Api/RawBindings.hsc" #-}

-- | See <https://www.lua.org/manual/5.3/manual.html#lua_rawequal lua_rawequal>

{-# LINE 213 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lua.h lua_rawequal"

{-# LINE 217 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  lua_rawequal :: LuaState -> StackIndex -> StackIndex -> IO LuaBool

--
-- Type coercion
--
-- | See <https://www.lua.org/manual/5.3/manual.html#lua_toboolean lua_toboolean>

{-# LINE 224 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lua.h lua_toboolean"

{-# LINE 228 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  lua_toboolean :: LuaState -> StackIndex -> IO StackIndex

-- | See <https://www.lua.org/manual/5.3/manual.html#lua_tocfunction lua_tocfunction>

{-# LINE 232 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lua.h lua_tocfunction"

{-# LINE 236 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  lua_tocfunction :: LuaState -> StackIndex -> IO CFunction


{-# LINE 239 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
-- | See <https://www.lua.org/manual/5.3/manual.html#lua_tointegerx lua_tointegerx>

{-# LINE 241 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lua.h lua_tointegerx"

{-# LINE 245 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  lua_tointegerx :: LuaState -> StackIndex -> Ptr LuaBool -> IO LuaInteger

-- | See <https://www.lua.org/manual/5.3/manual.html#lua_tonumberx lua_tonumberx>

{-# LINE 249 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lua.h lua_tonumberx"

{-# LINE 253 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  lua_tonumberx :: LuaState -> StackIndex -> Ptr LuaBool -> IO LuaNumber

{-# LINE 271 "src/Foreign/Lua/Api/RawBindings.hsc" #-}

-- | See <https://www.lua.org/manual/5.3/manual.html#lua_tolstring lua_tolstring>

{-# LINE 274 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lua.h lua_tolstring"

{-# LINE 278 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  lua_tolstring :: LuaState -> StackIndex -> Ptr CSize -> IO (Ptr CChar)

-- | See <https://www.lua.org/manual/5.3/manual.html#lua_topointer lua_topointer>

{-# LINE 282 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lua.h lua_topointer"

{-# LINE 286 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  lua_topointer :: LuaState -> StackIndex -> IO (Ptr ())

-- | See <https://www.lua.org/manual/5.3/manual.html#lua_tothread lua_tothread>

{-# LINE 290 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lua.h lua_tothread"

{-# LINE 294 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  lua_tothread :: LuaState -> StackIndex -> IO LuaState

-- | See <https://www.lua.org/manual/5.3/manual.html#lua_touserdata lua_touserdata>

{-# LINE 298 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lua.h lua_touserdata"

{-# LINE 302 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  lua_touserdata :: LuaState -> StackIndex -> IO (Ptr a)


--
-- Object size
--


{-# LINE 310 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
-- | See <https://www.lua.org/manual/5.3/manual.html#lua_rawlen lua_rawlen>

{-# LINE 312 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lua.h lua_rawlen"

{-# LINE 316 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  lua_rawlen :: LuaState -> StackIndex -> IO CSize

{-# LINE 326 "src/Foreign/Lua/Api/RawBindings.hsc" #-}


--------------------------------------------------------------------------------
-- * Push functions

-- | See <https://www.lua.org/manual/5.3/manual.html#lua_pushnil lua_pushnil>

{-# LINE 333 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lua.h lua_pushnil"

{-# LINE 337 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  lua_pushnil :: LuaState -> IO ()

-- | See <https://www.lua.org/manual/5.3/manual.html#lua_pushnumber lua_pushnumber>

{-# LINE 341 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lua.h lua_pushnumber"

{-# LINE 345 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  lua_pushnumber :: LuaState -> LuaNumber -> IO ()

-- | See <https://www.lua.org/manual/5.3/manual.html#lua_pushinteger lua_pushinteger>

{-# LINE 349 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lua.h lua_pushinteger"

{-# LINE 353 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  lua_pushinteger :: LuaState -> LuaInteger -> IO ()

-- | See <https://www.lua.org/manual/5.3/manual.html#lua_pushlstring lua_pushlstring>

{-# LINE 357 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lua.h lua_pushlstring"

{-# LINE 361 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  lua_pushlstring :: LuaState -> Ptr CChar -> CSize -> IO ()

-- lua_pushstring is currently not supported. It's difficult to use in a haskell
-- context.

-- | See <https://www.lua.org/manual/5.3/manual.html#lua_pushcclosure lua_pushcclosure>

{-# LINE 368 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lua.h lua_pushcclosure"

{-# LINE 372 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  lua_pushcclosure :: LuaState -> CFunction -> NumArgs -> IO ()

-- | See <https://www.lua.org/manual/5.3/manual.html#lua_pushboolean lua_pushboolean>

{-# LINE 376 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lua.h lua_pushboolean"

{-# LINE 380 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  lua_pushboolean :: LuaState -> LuaBool -> IO ()

-- | See <https://www.lua.org/manual/5.3/manual.html#lua_pushlightuserdata lua_pushlightuserdata>

{-# LINE 384 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lua.h lua_pushlightuserdata"

{-# LINE 388 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  lua_pushlightuserdata :: LuaState -> Ptr a -> IO ()

-- | See <https://www.lua.org/manual/5.3/manual.html#lua_pushthread lua_pushthread>

{-# LINE 392 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lua.h lua_pushthread"

{-# LINE 396 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  lua_pushthread :: LuaState -> IO CInt


--------------------------------------------------------------------------------
-- * Get functions

-- lua_gettable is unsafe, use hslua_gettable instead.
-- lua_getfield is unsafe, use hslua_getfield instead.
-- lua_getglobal is unsafe, use hslua_getglobal instead.
-- lua_getfenv (5.1 only) is not supported.

-- | Wrapper around <https://lua.org/manual/5.3/manual.html#lua_gettable \
-- @lua_gettable@> which catches any @longjmp@s.
foreign import ccall "safer-api.h hslua_gettable"
  hslua_gettable :: LuaState -> StackIndex -> IO CInt

-- | Wrapper around <https://lua.org/manual/5.3/manual.html#lua_getfield \
-- @lua_getfield@> which catches any @longjmp@s.
foreign import ccall "safer-api.h hslua_getfield"
  hslua_getfield :: LuaState -> StackIndex -> Ptr CChar -> IO CInt

-- | See <https://www.lua.org/manual/5.3/manual.html#lua_rawget lua_rawget>

{-# LINE 419 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lua.h lua_rawget"

{-# LINE 423 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  lua_rawget :: LuaState -> StackIndex -> IO ()

-- | See <https://www.lua.org/manual/5.3/manual.html#lua_rawgeti lua_rawgeti>

{-# LINE 427 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lua.h lua_rawgeti"

{-# LINE 431 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  lua_rawgeti :: LuaState -> StackIndex -> CInt -> IO ()

-- | See <https://www.lua.org/manual/5.3/manual.html#lua_createtable lua_createtable>

{-# LINE 435 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lua.h lua_createtable"

{-# LINE 439 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  lua_createtable :: LuaState -> CInt -> CInt -> IO ()

-- | See <https://www.lua.org/manual/5.3/manual.html#lua_newuserdata lua_newuserdata>

{-# LINE 443 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lua.h lua_newuserdata"

{-# LINE 447 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  lua_newuserdata :: LuaState -> CInt -> IO (Ptr ())

-- | See <https://www.lua.org/manual/5.3/manual.html#lua_getmetatable lua_getmetatable>

{-# LINE 451 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lua.h lua_getmetatable"

{-# LINE 455 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  lua_getmetatable :: LuaState -> StackIndex -> IO CInt

-- | Wrapper around <https://lua.org/manual/5.3/manual.html#lua_getglobal \
-- @lua_getglobal@> which catches any @longjmp@s.
foreign import ccall "safer-api.h hslua_getglobal"
  hslua_getglobal :: LuaState -> Ptr CChar -> IO CInt


--------------------------------------------------------------------------------
-- * Set functions

-- lua_settable is unsafe, use hslua_settable instead.
-- lua_setfield is unsafe, use hslua_setfield instead.
-- lua_setglobal is unsafe, use hslua_setglobal instead.
-- lua_setfenv (5.1 only) is not supported.

-- | Wrapper around <https://lua.org/manual/5.3/manual.html#lua_settable \
-- @lua_settable@> which catches any @longjmp@s.
foreign import ccall "safer-api.h hslua_settable"
  hslua_settable :: LuaState -> StackIndex -> IO CInt

-- | Wrapper around <https://lua.org/manual/5.3/manual.html#lua_setfield \
-- @lua_setfield@> which catches any @longjmp@s.
foreign import ccall "safer-api.h hslua_setfield"
  hslua_setfield :: LuaState -> StackIndex -> Ptr CChar -> IO CInt

-- | See <https://www.lua.org/manual/5.3/manual.html#lua_rawset lua_rawset>

{-# LINE 483 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lua.h lua_rawset"

{-# LINE 487 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  lua_rawset :: LuaState -> StackIndex -> IO ()

-- | See <https://www.lua.org/manual/5.3/manual.html#lua_rawseti lua_rawseti>

{-# LINE 491 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lua.h lua_rawseti"

{-# LINE 495 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  lua_rawseti :: LuaState -> StackIndex -> CInt -> IO ()

-- | See <https://www.lua.org/manual/5.3/manual.html#lua_setmetatable lua_setmetatable>

{-# LINE 499 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lua.h lua_setmetatable"

{-# LINE 503 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  lua_setmetatable :: LuaState -> StackIndex -> IO ()

-- | Wrapper around <https://lua.org/manual/5.3/manual.html#lua_setglobal \
-- @lua_setglobal@> which catches any @longjmp@s.
foreign import ccall "safer-api.h hslua_setglobal"
  hslua_setglobal :: LuaState -> Ptr CChar -> IO CInt


--------------------------------------------------------------------------------
-- * 'load' and 'call' functions (load and run Lua code)


{-# LINE 515 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
-- | See <https://www.lua.org/manual/5.3/manual.html#lua_pcallk lua_pcallk>
foreign import ccall "lua.h lua_pcallk"
  lua_pcallk :: LuaState -> NumArgs -> NumResults -> StackIndex
             -> CInt -> Ptr () -> IO StatusCode

{-# LINE 525 "src/Foreign/Lua/Api/RawBindings.hsc" #-}

-- currently unsupported:
-- lua_load
-- lua_dump


------------------------------------------------------------------------------
-- * Coroutine functions

-- lua_yield / lua_yieldk and lua_resume are currently not supported.

-- | See <https://www.lua.org/manual/5.3/manual.html#lua_status lua_status>
foreign import ccall unsafe "lua.h lua_status"
  lua_status :: LuaState -> IO StatusCode


------------------------------------------------------------------------------
-- * Garbage-collection functions and options

-- | See <https://www.lua.org/manual/5.3/manual.html#lua_gc lua_gc>
foreign import ccall "lua.h lua_gc"
  lua_gc :: LuaState -> CInt -> CInt -> IO CInt


------------------------------------------------------------------------------
-- * Miscellaneous functions

-- lua_error is unsafe in a haskell context and hence not supported.
-- lua_next is unsafe, use hslua_next instead.
-- lua_concat is unsafe (may trigger a longjmp), use hslua_concat instead.

-- | Wrapper around <https://lua.org/manual/5.3/manual.html#lua_next \
-- @lua_next@> which catches any @longjmp@s.
foreign import ccall "safer-api.h hslua_next"
  hslua_next :: LuaState -> StackIndex -> IO (Failable LuaBool)

-- | Wrapper around <https://lua.org/manual/5.3/manual.html#lua_concat \
-- @lua_concat@> which catches any @longjmp@s.
foreign import ccall "safer-api.h hslua_concat"
  hslua_concat :: LuaState -> NumArgs -> IO (Failable LuaBool)


------------------------------------------------------------------------------
-- * Lua Libraries

-- | See <https://www.lua.org/manual/5.3/manual.html#luaL_openlibs luaL_openlibs>
foreign import ccall unsafe "lualib.h luaL_openlibs"
  luaL_openlibs :: LuaState -> IO ()

-- | Point to function opening the base library.
foreign import ccall unsafe "lualib.h &luaopen_base"
  lua_open_base_ptr :: CFunction

-- | Point to function opening the table library.
foreign import ccall unsafe "lualib.h &luaopen_table"
  lua_open_table_ptr :: CFunction

-- | Point to function opening the io library.
foreign import ccall unsafe "lualib.h &luaopen_io"
  lua_open_io_ptr :: CFunction

-- | Point to function opening the os library.
foreign import ccall unsafe "lualib.h &luaopen_os"
  lua_open_os_ptr :: CFunction

-- | Point to function opening the string library.
foreign import ccall unsafe "lualib.h &luaopen_string"
  lua_open_string_ptr :: CFunction

-- | Point to function opening the math library.
foreign import ccall unsafe "lualib.h &luaopen_math"
  lua_open_math_ptr :: CFunction

-- | Point to function opening the debug library.
foreign import ccall unsafe "lualib.h &luaopen_debug"
  lua_open_debug_ptr :: CFunction

-- | Point to function opening the package library.
foreign import ccall unsafe "lualib.h &luaopen_package"
  lua_open_package_ptr :: CFunction


--------------------------------------------------------------------------------
-- * The Auxiliary Library

-- | See <https://www.lua.org/manual/5.3/manual.html#luaL_newstate luaL_newstate>
foreign import ccall unsafe "lauxlib.h luaL_newstate"
  luaL_newstate :: IO LuaState

-- | See <https://www.lua.org/manual/5.3/manual.html#luaL_newmetatable luaL_newmetatable>
foreign import ccall "lauxlib.h luaL_newmetatable"
  luaL_newmetatable :: LuaState -> Ptr CChar -> IO LuaBool

-- | See <https://www.lua.org/manual/5.3/manual.html#luaL_ref luaL_ref>
foreign import ccall "lauxlib.h luaL_ref"
  luaL_ref :: LuaState -> StackIndex -> IO CInt

-- | See <https://www.lua.org/manual/5.3/manual.html#luaL_unref luaL_unref>
foreign import ccall "lauxlib.h luaL_unref"
  luaL_unref :: LuaState -> StackIndex -> CInt -> IO ()


{-# LINE 627 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
-- | See <https://www.lua.org/manual/5.3/manual.html#luaL_loadfilex luaL_loadfilex>
foreign import ccall "lauxlib.h luaL_loadfilex"
  luaL_loadfilex :: LuaState -> Ptr CChar -> Ptr CChar -> IO StatusCode

{-# LINE 635 "src/Foreign/Lua/Api/RawBindings.hsc" #-}

-- | See <https://www.lua.org/manual/5.3/manual.html#luaL_loadstring luaL_loadstring>

{-# LINE 638 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
foreign import ccall unsafe "lauxlib.h luaL_loadstring"

{-# LINE 642 "src/Foreign/Lua/Api/RawBindings.hsc" #-}
  luaL_loadstring :: LuaState -> Ptr CChar -> IO StatusCode