1{-|
2Module      : Foreign.Lua.Core.Functions
3Copyright   : © 2007–2012 Gracjan Polak,
4                2012–2016 Ömer Sinan Ağacan,
5                2017-2020 Albert Krewinkel
6License     : MIT
7Maintainer  : Albert Krewinkel <tarleb+hslua@zeitkraut.de>
8Stability   : beta
9Portability : non-portable (depends on GHC)
10
11Monadic functions which operate within the Lua type.
12
13The functions in this module are mostly just thin wrappers around the respective
14C functions. However, C function which can throw an error are wrapped such that
15the error is converted into an @'Exception'@. Memory allocation errors,
16however, are not caught and will cause the host program to terminate.
17-}
18module Foreign.Lua.Core.Functions where
19
20import Prelude hiding (EQ, LT, compare, concat, error)
21
22import Control.Monad
23import Data.ByteString (ByteString)
24import Data.Maybe (fromMaybe)
25import Foreign.Lua.Core.Constants
26import Foreign.Lua.Core.Error
27import Foreign.Lua.Core.RawBindings
28import Foreign.Lua.Core.Types as Lua
29import Foreign.Marshal.Alloc (alloca)
30import Foreign.Ptr
31
32import qualified Data.ByteString as B
33import qualified Data.ByteString.Unsafe as B
34import qualified Foreign.C as C
35import qualified Foreign.Lua.Utf8 as Utf8
36import qualified Foreign.Storable as F
37
38--
39-- Helper functions
40--
41
42-- | Execute an action only if the given index is a table. Throw an
43-- error otherwise.
44ensureTable :: StackIndex -> (Lua.State -> IO ()) -> Lua ()
45ensureTable idx ioOp = do
46  isTbl <- istable idx
47  if isTbl
48    then liftLua ioOp
49    else do
50      tyName <- ltype idx >>= typename
51      throwMessage ("table expected, got " <> tyName)
52
53--
54-- API functions
55--
56
57-- | Converts the acceptable index @idx@ into an equivalent absolute index (that
58-- is, one that does not depend on the stack top).
59absindex :: StackIndex -> Lua StackIndex
60absindex = liftLua1 lua_absindex
61
62-- |  Calls a function.
63--
64-- To call a function you must use the following protocol: first, the function
65-- to be called is pushed onto the stack; then, the arguments to the function
66-- are pushed in direct order; that is, the first argument is pushed first.
67-- Finally you call @call@; @nargs@ is the number of arguments that you pushed
68-- onto the stack. All arguments and the function value are popped from the
69-- stack when the function is called. The function results are pushed onto the
70-- stack when the function returns. The number of results is adjusted to
71-- @nresults@, unless @nresults@ is @multret@. In this case, all results from
72-- the function are pushed. Lua takes care that the returned values fit into the
73-- stack space. The function results are pushed onto the stack in direct order
74-- (the first result is pushed first), so that after the call the last result is
75-- on the top of the stack.
76--
77-- Any error inside the called function cause a @'Exception'@ to be thrown.
78--
79-- The following example shows how the host program can do the equivalent to
80-- this Lua code:
81--
82-- > a = f("how", t.x, 14)
83--
84-- Here it is in Haskell (assuming the OverloadedStrings language extension):
85--
86-- > getglobal "f"         -- function to be called
87-- > pushstring  "how"     -- 1st argument
88-- > getglobal "t"         -- table to be indexed
89-- > getfield (-1) "x"     -- push result of t.x (2nd arg)
90-- > remove (-2)           -- remove 't' from the stack
91-- > pushinteger 14        -- 3rd argument
92-- > call 3 1              -- call 'f' with 3 arguments and 1 result
93-- > setglobal "a"         -- set global 'a'
94--
95-- Note that the code above is "balanced": at its end, the stack is back to its
96-- original configuration. This is considered good programming practice.
97--
98-- See <https://www.lua.org/manual/5.3/manual.html#lua_call lua_call>.
99call :: NumArgs -> NumResults -> Lua ()
100call nargs nresults = do
101  res <- pcall nargs nresults Nothing
102  when (res /= OK) throwTopMessage
103
104-- | Ensures that the stack has space for at least @n@ extra slots (that is,
105-- that you can safely push up to @n@ values into it). It returns false if it
106-- cannot fulfill the request, either because it would cause the stack to be
107-- larger than a fixed maximum size (typically at least several thousand
108-- elements) or because it cannot allocate memory for the extra space. This
109-- function never shrinks the stack; if the stack already has space for the
110-- extra slots, it is left unchanged.
111--
112-- This is a wrapper function of
113-- <https://www.lua.org/manual/5.3/manual.html#lua_checkstack lua_checkstack>.
114checkstack :: Int -> Lua Bool
115checkstack n = liftLua $ \l -> fromLuaBool <$> lua_checkstack l (fromIntegral n)
116
117-- | Destroys all objects in the given Lua state (calling the corresponding
118-- garbage-collection metamethods, if any) and frees all dynamic memory used by
119-- this state. On several platforms, you may not need to call this function,
120-- because all resources are naturally released when the host program ends. On
121-- the other hand, long-running programs that create multiple states, such as
122-- daemons or web servers, will probably need to close states as soon as they
123-- are not needed.
124--
125-- This is a wrapper function of
126-- <https://www.lua.org/manual/5.3/manual.html#lua_close lua_close>.
127close :: Lua.State -> IO ()
128close = lua_close
129
130-- | Compares two Lua values. Returns @True@ if the value at index @idx1@
131-- satisfies @op@ when compared with the value at index @idx2@, following the
132-- semantics of the corresponding Lua operator (that is, it may call
133-- metamethods). Otherwise returns @False@. Also returns @False@ if any of the
134-- indices is not valid.
135--
136-- The value of op must be of type @RelationalOperator@:
137--
138--    EQ: compares for equality (==)
139--    LT: compares for less than (<)
140--    LE: compares for less or equal (<=)
141--
142-- This is a wrapper function of
143-- <https://www.lua.org/manual/5.3/manual.html#lua_compare lua_compare>.
144compare :: StackIndex -> StackIndex -> RelationalOperator -> Lua Bool
145compare idx1 idx2 relOp = fromLuaBool <$> do
146  liftLuaThrow $ \l -> hslua_compare l idx1 idx2 (fromRelationalOperator relOp)
147
148-- | Concatenates the @n@ values at the top of the stack, pops them, and leaves
149-- the result at the top. If @n@ is 1, the result is the single value on the
150-- stack (that is, the function does nothing); if @n@ is 0, the result is the
151-- empty string. Concatenation is performed following the usual semantics of Lua
152-- (see <https://www.lua.org/manual/5.3/manual.html#3.4.6 §3.4.6> of the lua
153-- manual).
154--
155-- This is a wrapper function of
156-- <https://www.lua.org/manual/5.3/manual.html#lua_concat lua_concat>.
157concat :: NumArgs -> Lua ()
158concat n = liftLuaThrow (`hslua_concat` n)
159
160-- | Copies the element at index @fromidx@ into the valid index @toidx@,
161-- replacing the value at that position. Values at other positions are not
162-- affected.
163--
164-- See also <https://www.lua.org/manual/5.3/manual.html#lua_copy lua_copy> in
165-- the lua manual.
166copy :: StackIndex -> StackIndex -> Lua ()
167copy fromidx toidx = liftLua $ \l -> lua_copy l fromidx toidx
168
169-- | Creates a new empty table and pushes it onto the stack. Parameter narr is a
170-- hint for how many elements the table will have as a sequence; parameter nrec
171-- is a hint for how many other elements the table will have. Lua may use these
172-- hints to preallocate memory for the new table. This preallocation is useful
173-- for performance when you know in advance how many elements the table will
174-- have. Otherwise you can use the function lua_newtable.
175--
176-- This is a wrapper for function
177-- <https://www.lua.org/manual/5.3/manual.html#lua_createtable lua_createtable>.
178createtable :: Int -> Int -> Lua ()
179createtable narr nrec = liftLua $ \l ->
180  lua_createtable l (fromIntegral narr) (fromIntegral nrec)
181
182-- TODO: implement dump
183
184-- | Returns @True@ if the two values in acceptable indices index1 and
185-- index2 are equal, following the semantics of the Lua @==@ operator
186-- (that is, may call metamethods). Otherwise returns @False@. Also
187-- returns @False@ if any of the indices is non valid. Uses @'compare'@
188-- internally.
189equal :: StackIndex  -- ^ index1
190      -> StackIndex  -- ^ index2
191      -> Lua Bool
192equal index1 index2 = compare index1 index2 EQ
193
194-- | This is a convenience function to implement error propagation
195-- convention described in [Error handling in hslua](#g:1). hslua
196-- doesn't implement the @lua_error@ function from Lua C API because
197-- it's never safe to use. (see [Error handling in hslua](#g:1) for
198-- details)
199error :: Lua NumResults
200error = liftLua hslua_error
201
202-- |  Controls the garbage collector.
203--
204-- This function performs several tasks, according to the value of the parameter
205-- what:
206--
207--   * @'GCSTOP'@: stops the garbage collector.
208--
209--   * @'GCRESTART'@: restarts the garbage collector.
210--
211--   * @'GCCOLLECT'@: performs a full garbage-collection cycle.
212--
213--   * @'GCCOUNT'@: returns the current amount of memory (in Kbytes) in use by
214--     Lua.
215--
216--   * @'GCCOUNTB'@: returns the remainder of dividing the current amount of
217--     bytes of memory in use by Lua by 1024.
218--
219--   * @'GCSTEP'@: performs an incremental step of garbage collection. The step
220--     "size" is controlled by data (larger values mean more steps) in a
221--     non-specified way. If you want to control the step size you must
222--     experimentally tune the value of data. The function returns 1 if the step
223--     finished a garbage-collection cycle.
224--
225--   * @'GCSETPAUSE@': sets data as the new value for the pause of the collector
226--     (see §2.10). The function returns the previous value of the pause.
227--
228--   * @'GCSETSTEPMUL'@: sets data as the new value for the step multiplier of
229--     the collector (see §2.10). The function returns the previous value of the
230--     step multiplier.
231--
232-- See <https://www.lua.org/manual/5.3/manual.html#lua_gc lua_gc>.
233gc :: GCCONTROL -> Int -> Lua Int
234gc what data' = liftLua $ \l ->
235  fromIntegral <$> lua_gc l (fromIntegral (fromEnum what)) (fromIntegral data')
236
237-- | Pushes onto the stack the value @t[k]@, where @t@ is the value at the given
238-- stack index. As in Lua, this function may trigger a metamethod for the
239-- "index" event (see <https://www.lua.org/manual/5.3/manual.html#2.4 §2.4> of
240-- lua's manual).
241--
242-- Errors on the Lua side are caught and rethrown as @'Exception'@.
243--
244-- See also:
245-- <https://www.lua.org/manual/5.3/manual.html#lua_getfield lua_getfield>.
246getfield :: StackIndex -> String -> Lua ()
247getfield i s = do
248  absidx <- absindex i
249  pushstring (Utf8.fromString s)
250  gettable absidx
251
252-- | Pushes onto the stack the value of the global @name@.
253--
254-- Errors on the Lua side are caught and rethrown as @'Exception'@.
255--
256-- Wrapper of
257-- <https://www.lua.org/manual/5.3/manual.html#lua_getglobal lua_getglobal>.
258getglobal :: String -> Lua ()
259getglobal name = liftLuaThrow $ \l status' ->
260  C.withCStringLen name $ \(namePtr, len) ->
261  hslua_getglobal l namePtr (fromIntegral len) status'
262
263-- | If the value at the given index has a metatable, the function pushes that
264-- metatable onto the stack and returns @True@. Otherwise, the function returns
265-- @False@ and pushes nothing on the stack.
266--
267-- See also:
268-- <https://www.lua.org/manual/5.3/manual.html#lua_getmetatable lua_getmetatable>.
269getmetatable :: StackIndex -> Lua Bool
270getmetatable n = liftLua $ \l ->
271  fromLuaBool <$> lua_getmetatable l n
272
273-- | Pushes onto the stack the value @t[k]@, where @t@ is the value at the given
274-- index and @k@ is the value at the top of the stack.
275--
276-- This function pops the key from the stack, pushing the resulting value in its
277-- place. As in Lua, this function may trigger a metamethod for the "index"
278-- event (see <https://www.lua.org/manual/5.3/manual.html#2.4 §2.4> of lua's
279-- manual).
280--
281-- Errors on the Lua side are caught and rethrown as @'Exception'@.
282--
283-- See also:
284-- <https://www.lua.org/manual/5.3/manual.html#lua_gettable lua_gettable>.
285gettable :: StackIndex -> Lua ()
286gettable n = liftLuaThrow (\l -> hslua_gettable l n)
287
288-- | Returns the index of the top element in the stack. Because indices start at
289-- 1, this result is equal to the number of elements in the stack (and so 0
290-- means an empty stack).
291--
292-- See also: <https://www.lua.org/manual/5.3/manual.html#lua_gettop lua_gettop>.
293gettop :: Lua StackIndex
294gettop = liftLua lua_gettop
295
296-- | Moves the top element into the given valid index, shifting up the elements
297-- above this index to open space. This function cannot be called with a
298-- pseudo-index, because a pseudo-index is not an actual stack position.
299--
300-- See also:
301-- <https://www.lua.org/manual/5.3/manual.html#lua_insert lua_insert>.
302insert :: StackIndex -> Lua ()
303insert index = liftLua $ \l -> lua_insert l index
304
305-- | Returns @True@ if the value at the given index is a boolean, and @False@
306-- otherwise.
307--
308-- See also:
309-- <https://www.lua.org/manual/5.3/manual.html#lua_isboolean lua_isboolean>.
310isboolean :: StackIndex -> Lua Bool
311isboolean n = (== TypeBoolean) <$> ltype n
312
313-- | Returns @True@ if the value at the given index is a C function, and @False@
314-- otherwise.
315--
316-- See also:
317-- <https://www.lua.org/manual/5.3/manual.html#lua_iscfunction lua_iscfunction>.
318iscfunction :: StackIndex -> Lua Bool
319iscfunction n = liftLua $ \l -> fromLuaBool <$> lua_iscfunction l n
320
321-- | Returns @True@ if the value at the given index is a function (either C or
322-- Lua), and @False@ otherwise.
323--
324-- See also:
325-- <https://www.lua.org/manual/5.3/manual.html#lua_isfunction lua_isfunction>.
326isfunction :: StackIndex -> Lua Bool
327isfunction n = (== TypeFunction) <$> ltype n
328
329-- | Returns @True@ if the value at the given index is an integer (that is, the
330-- value is a number and is represented as an integer), and @False@ otherwise.
331isinteger :: StackIndex -> Lua Bool
332isinteger n = liftLua $ \l -> fromLuaBool <$> lua_isinteger l n
333
334-- | Returns @True@ if the value at the given index is a light userdata, and
335-- @False@ otherwise.
336--
337-- See also:
338-- <https://www.lua.org/manual/5.3/manual.html#lua_islightuserdata \
339-- lua_islightuserdata>.
340islightuserdata :: StackIndex -> Lua Bool
341islightuserdata n = (== TypeLightUserdata) <$> ltype n
342
343-- | Returns @True@ if the value at the given index is @nil@, and @False@
344-- otherwise.
345--
346-- See also:
347-- <https://www.lua.org/manual/5.3/manual.html#lua_isnil lua_isnil>.
348isnil :: StackIndex -> Lua Bool
349isnil n = (== TypeNil) <$> ltype n
350
351-- | Returns @True@ if the given index is not valid, and @False@ otherwise.
352--
353-- See also:
354-- <https://www.lua.org/manual/5.3/manual.html#lua_isnone lua_isnone>.
355isnone :: StackIndex -> Lua Bool
356isnone n = (== TypeNone) <$> ltype n
357
358-- | Returns @True@ if the given index is not valid or if the value at the given
359-- index is @nil@, and @False@ otherwise.
360--
361-- See also:
362-- <https://www.lua.org/manual/5.3/manual.html#lua_isnoneornil lua_isnoneornil>.
363isnoneornil :: StackIndex -> Lua Bool
364isnoneornil idx = (<= TypeNil) <$> ltype idx
365
366-- | Returns @True@ if the value at the given index is a number or a string
367-- convertible to a number, and @False@ otherwise.
368--
369-- See also:
370-- <https://www.lua.org/manual/5.3/manual.html#lua_isnumber lua_isnumber>.
371isnumber :: StackIndex -> Lua Bool
372isnumber n = liftLua $ \l -> fromLuaBool <$> lua_isnumber l n
373
374-- | Returns @True@ if the value at the given index is a string or a number
375-- (which is always convertible to a string), and @False@ otherwise.
376--
377-- See also:
378-- <https://www.lua.org/manual/5.3/manual.html#lua_isstring lua_isstring>.
379isstring :: StackIndex -> Lua Bool
380isstring n = liftLua $ \l -> fromLuaBool <$> lua_isstring l n
381
382-- | Returns @True@ if the value at the given index is a table, and @False@
383-- otherwise.
384--
385-- See also:
386-- <https://www.lua.org/manual/5.3/manual.html#lua_istable lua_istable>.
387istable :: StackIndex -> Lua Bool
388istable n = (== TypeTable) <$> ltype n
389
390-- | Returns @True@ if the value at the given index is a thread, and @False@
391-- otherwise.
392--
393-- See also:
394-- <https://www.lua.org/manual/5.3/manual.html#lua_isthread lua_isthread>.
395isthread :: StackIndex -> Lua Bool
396isthread n = (== TypeThread) <$> ltype n
397
398-- | Returns @True@ if the value at the given index is a userdata (either full
399-- or light), and @False@ otherwise.
400--
401-- See also:
402-- <https://www.lua.org/manual/5.3/manual.html#lua_isuserdata lua_isuserdata>.
403isuserdata :: StackIndex -> Lua Bool
404isuserdata n = liftLua $ \l -> fromLuaBool <$> lua_isuserdata l n
405
406-- | Tests whether the object under the first index is smaller than that under
407-- the second. Uses @'compare'@ internally.
408lessthan :: StackIndex -> StackIndex -> Lua Bool
409lessthan index1 index2 = compare index1 index2 LT
410
411-- | Loads a Lua chunk (without running it). If there are no errors, @'load'@
412-- pushes the compiled chunk as a Lua function on top of the stack. Otherwise,
413-- it pushes an error message.
414--
415-- The return values of @'load'@ are:
416--
417-- - @'OK'@: no errors;
418-- - @'ErrSyntax'@: syntax error during pre-compilation;
419-- - @'ErrMem'@: memory allocation error;
420-- - @'ErrGcmm'@: error while running a @__gc@ metamethod. (This error has no
421--   relation with the chunk being loaded. It is generated by the garbage
422--   collector.)
423--
424-- This function only loads a chunk; it does not run it.
425--
426-- @load@ automatically detects whether the chunk is text or binary, and loads
427-- it accordingly (see program luac).
428--
429-- The @'load'@ function uses a user-supplied reader function to read the chunk
430-- (see @'Lua.Reader'@). The data argument is an opaque value passed to the
431-- reader function.
432--
433-- The @chunkname@ argument gives a name to the chunk, which is used for error
434-- messages and in debug information (see
435-- <https://www.lua.org/manual/5.3/manual.html#4.9 §4.9>). Note that the
436-- @chunkname@ is used as a C string, so it may not contain null-bytes.
437load :: Lua.Reader -> Ptr () -> ByteString -> Lua Status
438load reader data' chunkname = liftLua $ \l ->
439  B.useAsCString chunkname $ \namePtr ->
440  toStatus <$> lua_load l reader data' namePtr nullPtr
441
442-- | Returns the type of the value in the given valid index, or @'TypeNone'@ for
443-- a non-valid (but acceptable) index.
444--
445-- See <https://www.lua.org/manual/5.3/manual.html#lua_type lua_type>.
446ltype :: StackIndex -> Lua Type
447ltype idx = toType <$> liftLua (`lua_type` idx)
448
449-- | Creates a new empty table and pushes it onto the stack. It is equivalent to
450-- @createtable 0 0@.
451--
452-- See also:
453-- <https://www.lua.org/manual/5.3/manual.html#lua_newtable lua_newtable>.
454newtable :: Lua ()
455newtable = createtable 0 0
456
457-- | This function allocates a new block of memory with the given size, pushes
458-- onto the stack a new full userdata with the block address, and returns this
459-- address. The host program can freely use this memory.
460--
461-- See also:
462-- <https://www.lua.org/manual/5.3/manual.html#lua_newuserdata lua_newuserdata>.
463newuserdata :: Int -> Lua (Ptr ())
464newuserdata = liftLua1 lua_newuserdata . fromIntegral
465
466-- | Pops a key from the stack, and pushes a key–value pair from the table at
467-- the given index (the "next" pair after the given key). If there are no more
468-- elements in the table, then @next@ returns @False@ (and pushes nothing).
469--
470-- Errors on the Lua side are caught and rethrown as a @'Exception'@.
471--
472-- See also:
473-- <https://www.lua.org/manual/5.3/manual.html#lua_next lua_next>.
474next :: StackIndex -> Lua Bool
475next idx = fromLuaBool <$> liftLuaThrow (\l -> hslua_next l idx)
476
477-- | Opens all standard Lua libraries into the current state and sets each
478-- library name as a global value.
479--
480-- See also:
481-- <https://www.lua.org/manual/5.3/manual.html#luaL_openlibs luaL_openlibs>.
482openlibs :: Lua ()
483openlibs = liftLua luaL_openlibs
484
485-- | Pushes Lua's /base/ library onto the stack.
486--
487-- See <https://www.lua.org/manual/5.3/manual.html#pdf-luaopen_base luaopen_base>.
488openbase :: Lua ()
489openbase = pushcfunction lua_open_base_ptr *> call 0 multret
490
491-- | Pushes Lua's /debug/ library onto the stack.
492--
493-- See also:
494-- <https://www.lua.org/manual/5.3/manual.html#pdf-luaopen_debug luaopen_debug>.
495opendebug :: Lua ()
496opendebug = pushcfunction lua_open_debug_ptr *> call 0 multret
497
498-- | Pushes Lua's /io/ library onto the stack.
499--
500-- See also:
501-- <https://www.lua.org/manual/5.3/manual.html#pdf-luaopen_io luaopen_io>.
502openio :: Lua ()
503openio = pushcfunction lua_open_io_ptr *> call 0 multret
504
505-- | Pushes Lua's /math/ library onto the stack.
506--
507-- See also:
508-- <https://www.lua.org/manual/5.3/manual.html#pdf-luaopen_math luaopen_math>.
509openmath :: Lua ()
510openmath = pushcfunction lua_open_math_ptr *> call 0 multret
511
512-- | Pushes Lua's /os/ library onto the stack.
513--
514-- See also:
515-- <https://www.lua.org/manual/5.3/manual.html#pdf-luaopen_os luaopen_os>.
516openos :: Lua ()
517openos = pushcfunction lua_open_os_ptr *> call 0 multret
518
519-- | Pushes Lua's /package/ library onto the stack.
520--
521-- See also:
522-- <https://www.lua.org/manual/5.3/manual.html#pdf-luaopen_package luaopen_package>.
523openpackage :: Lua ()
524openpackage = pushcfunction lua_open_package_ptr *> call 0 multret
525
526-- | Pushes Lua's /string/ library onto the stack.
527--
528-- See also:
529-- <https://www.lua.org/manual/5.3/manual.html#pdf-luaopen_string luaopen_string>.
530openstring :: Lua ()
531openstring = pushcfunction lua_open_string_ptr *> call 0 multret
532
533-- | Pushes Lua's /table/ library onto the stack.
534--
535-- See also:
536-- <https://www.lua.org/manual/5.3/manual.html#pdf-luaopen_table luaopen_table>.
537opentable :: Lua ()
538opentable = pushcfunction lua_open_table_ptr *> call 0 multret
539
540-- | Calls a function in protected mode.
541--
542-- Both @nargs@ and @nresults@ have the same meaning as in @'call'@. If there
543-- are no errors during the call, @pcall@ behaves exactly like @'call'@.
544-- However, if there is any error, @pcall@ catches it, pushes a single value on
545-- the stack (the error message), and returns the error code. Like @'call'@,
546-- @pcall@ always removes the function and its arguments from the stack.
547--
548-- If @msgh@ is @Nothing@, then the error object returned on the stack is
549-- exactly the original error object. Otherwise, when @msgh@ is @Just idx@, the
550-- stack index @idx@ is the location of a message handler. (This index cannot be
551-- a pseudo-index.) In case of runtime errors, this function will be called with
552-- the error object and its return value will be the object returned on the
553-- stack by @'pcall'@.
554--
555-- Typically, the message handler is used to add more debug information to the
556-- error object, such as a stack traceback. Such information cannot be gathered
557-- after the return of @'pcall'@, since by then the stack has unwound.
558--
559-- See <https://www.lua.org/manual/5.3/manual.html#lua_pcall lua_pcall>.
560pcall :: NumArgs -> NumResults -> Maybe StackIndex -> Lua Status
561pcall nargs nresults msgh = liftLua $ \l ->
562  toStatus <$> lua_pcall l nargs nresults (fromMaybe 0 msgh)
563
564-- | Pops @n@ elements from the stack.
565--
566-- See also: <https://www.lua.org/manual/5.3/manual.html#lua_pop lua_pop>.
567pop :: StackIndex -> Lua ()
568pop n = liftLua $ \l -> lua_pop l n
569
570-- | Pushes a boolean value with the given value onto the stack.
571--
572-- See also:
573-- <https://www.lua.org/manual/5.3/manual.html#lua_pushboolean lua_pushboolean>.
574pushboolean :: Bool -> Lua ()
575pushboolean b = liftLua $ \l -> lua_pushboolean l (toLuaBool b)
576
577-- | Pushes a new C closure onto the stack.
578--
579-- When a C function is created, it is possible to associate some values with
580-- it, thus creating a C closure (see
581-- <https://www.lua.org/manual/5.1/manual.html#3.4 §3.4>); these values are then
582-- accessible to the function whenever it is called. To associate values with a
583-- C function, first these values should be pushed onto the stack (when there
584-- are multiple values, the first value is pushed first). Then lua_pushcclosure
585-- is called to create and push the C function onto the stack, with the argument
586-- @n@ telling how many values should be associated with the function.
587-- lua_pushcclosure also pops these values from the stack.
588--
589-- The maximum value for @n@ is 255.
590--
591-- See also:
592-- <https://www.lua.org/manual/5.3/manual.html#lua_pushcclosure lua_pushcclosure>.
593pushcclosure :: CFunction -> NumArgs -> Lua ()
594pushcclosure f n = liftLua $ \l -> lua_pushcclosure l f n
595
596-- | Pushes a C function onto the stack. This function receives a pointer to a C
597-- function and pushes onto the stack a Lua value of type function that, when
598-- called, invokes the corresponding C function.
599--
600-- Any function to be callable by Lua must follow the correct protocol to
601-- receive its parameters and return its results (see @'CFunction'@)
602--
603-- See also:
604-- <https://www.lua.org/manual/5.3/manual.html#lua_pushcfunction lua_pushcfunction>.
605pushcfunction :: CFunction -> Lua ()
606pushcfunction f = pushcclosure f 0
607
608-- | Pushes the global environment onto the stack.
609--
610-- Wraps <https://www.lua.org/manual/5.3/manual.html#lua_pushglobaltable \
611-- lua_pushglobaltable>.
612pushglobaltable :: Lua ()
613pushglobaltable = liftLua lua_pushglobaltable
614
615-- | Pushes an integer with with the given value onto the stack.
616--
617-- See also:
618-- <https://www.lua.org/manual/5.3/manual.html#lua_pushinteger lua_pushinteger>.
619pushinteger :: Lua.Integer -> Lua ()
620pushinteger = liftLua1 lua_pushinteger
621
622-- |  Pushes a light userdata onto the stack.
623--
624-- Userdata represent C values in Lua. A light userdata represents a pointer, a
625-- @Ptr ()@ (i.e., @void*@ in C lingo). It is a value (like a number): you do
626-- not create it, it has no individual metatable, and it is not collected (as it
627-- was never created). A light userdata is equal to "any" light userdata with
628-- the same C address.
629--
630-- See also:
631-- <https://www.lua.org/manual/5.3/manual.html#lua_pushlightuserdata lua_pushlightuserdata>.
632pushlightuserdata :: Ptr a -> Lua ()
633pushlightuserdata = liftLua1 lua_pushlightuserdata
634
635-- | Pushes a nil value onto the stack.
636--
637-- See <https://www.lua.org/manual/5.3/manual.html#lua_pushnil lua_pushnil>.
638pushnil :: Lua ()
639pushnil = liftLua lua_pushnil
640
641-- | Pushes a float with the given value onto the stack.
642--
643-- See <https://www.lua.org/manual/5.3/manual.html#lua_pushnumber lua_pushnumber>.
644pushnumber :: Lua.Number -> Lua ()
645pushnumber = liftLua1 lua_pushnumber
646
647-- | Pushes the zero-terminated string pointed to by s onto the stack. Lua makes
648-- (or reuses) an internal copy of the given string, so the memory at s can be
649-- freed or reused immediately after the function returns.
650--
651-- See also: <https://www.lua.org/manual/5.3/manual.html#lua_pushstring \
652-- lua_pushstring>.
653pushstring :: ByteString -> Lua ()
654pushstring s = liftLua $ \l ->
655  B.unsafeUseAsCStringLen s $ \(sPtr, z) -> lua_pushlstring l sPtr (fromIntegral z)
656
657-- | Pushes the current thread onto the stack. Returns @True@ if this thread is
658-- the main thread of its state, @False@ otherwise.
659--
660-- See also:
661-- <https://www.lua.org/manual/5.3/manual.html#lua_pushthread lua_pushthread>.
662pushthread :: Lua Bool
663pushthread = (1 ==)  <$> liftLua lua_pushthread
664
665-- | Pushes a copy of the element at the given index onto the stack.
666--
667-- See <https://www.lua.org/manual/5.3/manual.html#lua_pushvalue lua_pushvalue>.
668pushvalue :: StackIndex -> Lua ()
669pushvalue n = liftLua $ \l -> lua_pushvalue l n
670
671-- | Returns @True@ if the two values in indices @idx1@ and @idx2@ are
672-- primitively equal (that is, without calling the @__eq@ metamethod). Otherwise
673-- returns @False@. Also returns @False@ if any of the indices are not valid.
674--
675-- See also:
676-- <https://www.lua.org/manual/5.3/manual.html#lua_rawequal lua_rawequal>.
677rawequal :: StackIndex -> StackIndex -> Lua Bool
678rawequal idx1 idx2 = liftLua $ \l ->
679  fromLuaBool <$> lua_rawequal l idx1 idx2
680
681-- | Similar to @'gettable'@, but does a raw access (i.e., without metamethods).
682--
683-- See also:
684-- <https://www.lua.org/manual/5.3/manual.html#lua_rawget lua_rawget>.
685rawget :: StackIndex -> Lua ()
686rawget n = ensureTable n (\l -> lua_rawget l n)
687
688-- | Pushes onto the stack the value @t[n]@, where @t@ is the table at the given
689-- index. The access is raw, that is, it does not invoke the @__index@
690-- metamethod.
691--
692-- See also:
693-- <https://www.lua.org/manual/5.3/manual.html#lua_rawgeti lua_rawgeti>.
694rawgeti :: StackIndex -> Lua.Integer -> Lua ()
695rawgeti k n = ensureTable k (\l -> lua_rawgeti l k n)
696
697-- | Returns the raw "length" of the value at the given index: for strings, this
698-- is the string length; for tables, this is the result of the length operator
699-- (@#@) with no metamethods; for userdata, this is the size of the block of
700-- memory allocated for the userdata; for other values, it is 0.
701--
702-- See also:
703-- <https://www.lua.org/manual/5.3/manual.html#lua_rawlen lua_rawlen>.
704rawlen :: StackIndex -> Lua Int
705rawlen idx = liftLua $ \l -> fromIntegral <$> lua_rawlen l idx
706
707-- | Similar to @'settable'@, but does a raw assignment (i.e., without
708-- metamethods).
709--
710-- See also:
711-- <https://www.lua.org/manual/5.3/manual.html#lua_rawset lua_rawset>.
712rawset :: StackIndex -> Lua ()
713rawset n = ensureTable n (\l -> lua_rawset l n)
714
715-- | Does the equivalent of @t[i] = v@, where @t@ is the table at the given
716-- index and @v@ is the value at the top of the stack.
717--
718-- This function pops the value from the stack. The assignment is raw, that is,
719-- it does not invoke the @__newindex@ metamethod.
720--
721-- See also:
722-- <https://www.lua.org/manual/5.3/manual.html#lua_rawseti lua_rawseti>.
723rawseti :: StackIndex -> Lua.Integer -> Lua ()
724rawseti k m = ensureTable k (\l -> lua_rawseti l k m)
725
726-- | Sets the C function @f@ as the new value of global @name@.
727--
728-- See <https://www.lua.org/manual/5.3/manual.html#lua_register lua_register>.
729register :: String -> CFunction -> Lua ()
730register name f = do
731  pushcfunction f
732  setglobal name
733
734-- | Removes the element at the given valid index, shifting down the elements
735-- above this index to fill the gap. This function cannot be called with a
736-- pseudo-index, because a pseudo-index is not an actual stack position.
737--
738-- See <https://www.lua.org/manual/5.3/manual.html#lua_remove lua_remove>.
739remove :: StackIndex -> Lua ()
740remove n = liftLua $ \l -> lua_remove l n
741
742-- | Moves the top element into the given valid index without shifting any
743-- element (therefore replacing the value at that given index), and then pops
744-- the top element.
745--
746-- See <https://www.lua.org/manual/5.3/manual.html#lua_replace lua_replace>.
747replace :: StackIndex -> Lua ()
748replace n = liftLua $ \l ->  lua_replace l n
749
750-- | Does the equivalent to @t[k] = v@, where @t@ is the value at the given
751-- index and @v@ is the value at the top of the stack.
752--
753-- This function pops the value from the stack. As in Lua, this function may
754-- trigger a metamethod for the "newindex" event (see
755-- <https://www.lua.org/manual/5.3/manual.html#2.4 §2.4> of the Lua 5.3
756-- Reference Manual).
757--
758-- Errors on the Lua side are caught and rethrown as a @'Exception'@.
759--
760-- See also:
761-- <https://www.lua.org/manual/5.3/manual.html#lua_setfield lua_setfield>.
762setfield :: StackIndex -> String -> Lua ()
763setfield i s = do
764  absidx <- absindex i
765  pushstring (Utf8.fromString s)
766  insert (nthFromTop 2)
767  settable absidx
768
769-- | Pops a value from the stack and sets it as the new value of global @name@.
770--
771-- Errors on the Lua side are caught and rethrown as a @'Exception'@.
772--
773-- See also:
774-- <https://www.lua.org/manual/5.3/manual.html#lua_setglobal lua_setglobal>.
775setglobal :: String -> Lua ()
776setglobal name = liftLuaThrow $ \l status' ->
777  C.withCStringLen name $ \(namePtr, nameLen) ->
778  hslua_setglobal l namePtr (fromIntegral nameLen) status'
779
780-- | Pops a table from the stack and sets it as the new metatable for the value
781-- at the given index.
782--
783-- See also:
784-- <https://www.lua.org/manual/5.3/manual.html#lua_setmetatable \
785-- lua_setmetatable>.
786setmetatable :: StackIndex -> Lua ()
787setmetatable idx = liftLua $ \l -> lua_setmetatable l idx
788
789-- | Does the equivalent to @t[k] = v@, where @t@ is the value at the given
790-- index, @v@ is the value at the top of the stack, and @k@ is the value just
791-- below the top.
792--
793-- This function pops both the key and the value from the stack. As in Lua, this
794-- function may trigger a metamethod for the "newindex" event (see
795-- <https://www.lua.org/manual/5.3/manual.html#2.4 §2.4> of the Lua 5.3
796-- Reference Manual).
797--
798-- Errors on the Lua side are caught and rethrown as a @'Exception'@.
799--
800-- See also:
801-- <https://www.lua.org/manual/5.3/manual.html#lua_settable lua_settable>.
802settable :: StackIndex -> Lua ()
803settable index = liftLuaThrow $ \l -> hslua_settable l index
804
805-- | Accepts any index, or 0, and sets the stack top to this index. If the new
806-- top is larger than the old one, then the new elements are filled with nil. If
807-- index is 0, then all stack elements are removed.
808--
809-- See also:
810-- <https://www.lua.org/manual/5.3/manual.html#lua_settop lua_settop>.
811settop :: StackIndex -> Lua ()
812settop = liftLua1 lua_settop
813
814-- |  Returns the status of this Lua thread.
815--
816-- The status can be 'OK' for a normal thread, an error value if the
817-- thread finished the execution of a @lua_resume@ with an error, or
818-- 'Yield' if the thread is suspended.
819--
820-- You can only call functions in threads with status 'OK'. You can
821-- resume threads with status 'OK' (to start a new coroutine) or 'Yield'
822-- (to resume a coroutine).
823--
824-- See also: <https://www.lua.org/manual/5.3/manual.html#lua_status lua_status>.
825status :: Lua Status
826status = liftLua $ fmap toStatus . lua_status
827
828-- | Converts the Lua value at the given index to a haskell boolean value. Like
829-- all tests in Lua, @toboolean@ returns @True@ for any Lua value different from
830-- @false@ and @nil@; otherwise it returns @False@. (If you want to accept only
831-- actual boolean values, use @'isboolean'@ to test the value's type.)
832--
833-- See also:
834-- <https://www.lua.org/manual/5.3/manual.html#lua_toboolean lua_toboolean>.
835toboolean :: StackIndex -> Lua Bool
836toboolean n = liftLua $ \l -> fromLuaBool <$> lua_toboolean l n
837
838-- | Converts a value at the given index to a C function. That value must be a C
839-- function; otherwise, returns @Nothing@.
840--
841-- See also:
842-- <https://www.lua.org/manual/5.3/manual.html#lua_tocfunction lua_tocfunction>.
843tocfunction :: StackIndex -> Lua (Maybe CFunction)
844tocfunction n = liftLua $ \l -> do
845  fnPtr <- lua_tocfunction l n
846  return (if fnPtr == nullFunPtr then Nothing else Just fnPtr)
847
848-- | Converts the Lua value at the given acceptable index to the signed integral
849-- type 'Lua.Integer'. The Lua value must be an integer, a number or a string
850-- convertible to an integer (see
851-- <https://www.lua.org/manual/5.3/manual.html#3.4.3 §3.4.3> of the Lua 5.3
852-- Reference Manual); otherwise, @tointeger@ returns @Nothing@.
853--
854-- If the number is not an integer, it is truncated in some non-specified way.
855--
856-- See also:
857-- <https://www.lua.org/manual/5.3/manual.html#lua_tointeger lua_tointeger>.
858tointeger :: StackIndex -> Lua (Maybe Lua.Integer)
859tointeger n = liftLua $ \l -> alloca $ \boolPtr -> do
860  res <- lua_tointegerx l n boolPtr
861  isNum <- fromLuaBool <$> F.peek boolPtr
862  return (if isNum then Just res else Nothing)
863
864-- | Converts the Lua value at the given index to the C type lua_Number. The Lua
865-- value must be a number or a string convertible to a number; otherwise,
866-- @tonumber@ returns @'Nothing'@.
867--
868-- See <https://www.lua.org/manual/5.3/manual.html#lua_tonumber lua_tonumber>.
869tonumber :: StackIndex -> Lua (Maybe Lua.Number)
870tonumber n = liftLua $ \l -> alloca $ \bptr -> do
871  res <- lua_tonumberx l n bptr
872  isNum <- fromLuaBool <$> F.peek bptr
873  return (if isNum then Just res else Nothing)
874
875-- | Converts the value at the given index to a generic C pointer (void*). The
876-- value can be a userdata, a table, a thread, or a function; otherwise,
877-- lua_topointer returns @nullPtr@. Different objects will give different
878-- pointers. There is no way to convert the pointer back to its original value.
879--
880-- Typically this function is used only for hashing and debug information.
881--
882-- See also:
883-- <https://www.lua.org/manual/5.3/manual.html#lua_topointer lua_topointer>.
884topointer :: StackIndex -> Lua (Ptr ())
885topointer n = liftLua $ \l -> lua_topointer l n
886
887-- | Converts the Lua value at the given index to a @'ByteString'@. The Lua
888-- value must be a string or a number; otherwise, the function returns
889-- @'Nothing'@. If the value is a number, then @'tostring'@ also changes the
890-- actual value in the stack to a string. (This change confuses @'next'@ when
891-- @'tostring'@ is applied to keys during a table traversal.)
892--
893-- See <https://www.lua.org/manual/5.3/manual.html#lua_tolstring lua_tolstring>.
894tostring :: StackIndex -> Lua (Maybe ByteString)
895tostring n = liftLua $ \l ->
896  alloca $ \lenPtr -> do
897    cstr <- lua_tolstring l n lenPtr
898    if cstr == nullPtr
899      then return Nothing
900      else do
901      cstrLen <- F.peek lenPtr
902      Just <$> B.packCStringLen (cstr, fromIntegral cstrLen)
903
904-- | Converts the value at the given index to a Lua thread (represented as
905-- lua_State*). This value must be a thread; otherwise, the function returns
906-- @Nothing@.
907--
908-- See also:
909-- <https://www.lua.org/manual/5.3/manual.html#lua_tothread lua_tothread>.
910tothread :: StackIndex -> Lua (Maybe Lua.State)
911tothread n = liftLua $ \l -> do
912  thread@(Lua.State ptr) <- lua_tothread l n
913  if ptr == nullPtr
914    then return Nothing
915    else return (Just thread)
916
917-- | If the value at the given index is a full userdata, returns its block
918-- address. If the value is a light userdata, returns its pointer. Otherwise,
919-- returns @Nothing@..
920--
921-- See also:
922-- <https://www.lua.org/manual/5.3/manual.html#lua_touserdata lua_touserdata>.
923touserdata :: StackIndex -> Lua (Maybe (Ptr a))
924touserdata n = liftLua $ \l -> do
925  ptr <- lua_touserdata l n
926  if ptr == nullPtr
927    then return Nothing
928    else return (Just ptr)
929
930-- | Returns the name of the type encoded by the value @tp@, which must be one
931-- the values returned by @'ltype'@.
932--
933-- See also:
934-- <https://www.lua.org/manual/5.3/manual.html#lua_typename lua_typename>.
935typename :: Type -> Lua String
936typename tp = liftLua $ \l ->
937  lua_typename l (fromType tp) >>= C.peekCString
938
939-- | Returns the pseudo-index that represents the @i@-th upvalue of the running
940-- function (see <https://www.lua.org/manual/5.3/manual.html#4.4 §4.4> of the
941-- Lua 5.3 reference manual).
942--
943-- See also:
944-- <https://www.lua.org/manual/5.3/manual.html#lua_upvalueindex lua_upvalueindex>.
945upvalueindex :: StackIndex -> StackIndex
946upvalueindex i = registryindex - i
947