{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-|
Module      : Foreign.Lua.Types.Peekable
Copyright   : © 2007–2012 Gracjan Polak,
                2012–2016 Ömer Sinan Ağacan,
                2017-2020 Albert Krewinkel
License     : MIT
Maintainer  : Albert Krewinkel <tarleb+hslua@zeitkraut.de>
Stability   : beta
Portability : non-portable (depends on GHC)

Sending haskell objects to the lua stack.
-}
module Foreign.Lua.Types.Peekable
  ( Peekable (..)
  , peekKeyValuePairs
  , peekList
  , reportValueOnFailure
  ) where

import Control.Monad ((>=>))
import Data.ByteString (ByteString)
import Data.Map (Map, fromList)
import Data.Set (Set)
import Foreign.Lua.Core as Lua
import Foreign.Ptr (Ptr)

import qualified Control.Monad.Catch as Catch
import qualified Data.Set as Set
import qualified Data.Text as T
import qualified Data.ByteString.Lazy as BL
import qualified Foreign.Lua.Peek as Peek
import qualified Foreign.Lua.Utf8 as Utf8

-- | Use @test@ to check whether the value at stack index @n@ has the correct
-- type and use @peekfn@ to convert it to a haskell value if possible. Throws
-- and exception if the test failes with the expected type name as part of the
-- message.
typeChecked :: String                   -- ^ expected type
            -> (StackIndex -> Lua Bool) -- ^ pre-condition Checker
            -> (StackIndex -> Lua a)    -- ^ retrieval function
            -> StackIndex -> Lua a
typeChecked :: String
-> (StackIndex -> Lua Bool)
-> (StackIndex -> Lua a)
-> StackIndex
-> Lua a
typeChecked String
expectedType StackIndex -> Lua Bool
test StackIndex -> Lua a
peekfn StackIndex
idx = do
  Bool
v <- StackIndex -> Lua Bool
test StackIndex
idx
  if Bool
v then StackIndex -> Lua a
peekfn StackIndex
idx else String -> StackIndex -> Lua a
forall a. String -> StackIndex -> Lua a
mismatchError String
expectedType StackIndex
idx

-- | Report the expected and actual type of the value under the given index if
-- conversion failed.
reportValueOnFailure :: String
                     -> (StackIndex -> Lua (Maybe a))
                     -> StackIndex -> Lua a
reportValueOnFailure :: String -> (StackIndex -> Lua (Maybe a)) -> StackIndex -> Lua a
reportValueOnFailure String
expected StackIndex -> Lua (Maybe a)
peekMb StackIndex
idx = do
  Maybe a
res <- StackIndex -> Lua (Maybe a)
peekMb StackIndex
idx
  case Maybe a
res of
    (Just a
x) -> a -> Lua a
forall (m :: * -> *) a. Monad m => a -> m a
return a
x
    Maybe a
Nothing -> String -> StackIndex -> Lua a
forall a. String -> StackIndex -> Lua a
mismatchError String
expected StackIndex
idx

-- | Return a Result error containing a message about the assertion failure.
mismatchError :: String -> StackIndex -> Lua a
mismatchError :: String -> StackIndex -> Lua a
mismatchError String
expected StackIndex
idx = do
  String
actualType <- StackIndex -> Lua Type
ltype StackIndex
idx Lua Type -> (Type -> Lua String) -> Lua String
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Type -> Lua String
typename
  String
actualValue <- ByteString -> String
Utf8.toString (ByteString -> String) -> Lua ByteString -> Lua String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StackIndex -> Lua ByteString
tostring' StackIndex
idx Lua String -> Lua () -> Lua String
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* StackIndex -> Lua ()
pop StackIndex
1
  let msg :: String
msg = String
"expected " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
expected String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
", got '" String -> String -> String
forall a. Semigroup a => a -> a -> a
<>
            String
actualValue String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"' (" String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
actualType String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
")"
  String -> Lua a
forall a. String -> Lua a
Lua.throwMessage String
msg

-- | A value that can be read from the Lua stack.
class Peekable a where
  -- | Check if at index @n@ there is a convertible Lua value and if so return
  -- it.  Throws a @'Lua.Exception'@ otherwise.
  peek :: StackIndex -> Lua a

instance Peekable () where
  peek :: StackIndex -> Lua ()
peek = String -> (StackIndex -> Lua (Maybe ())) -> StackIndex -> Lua ()
forall a.
String -> (StackIndex -> Lua (Maybe a)) -> StackIndex -> Lua a
reportValueOnFailure String
"nil" ((StackIndex -> Lua (Maybe ())) -> StackIndex -> Lua ())
-> (StackIndex -> Lua (Maybe ())) -> StackIndex -> Lua ()
forall a b. (a -> b) -> a -> b
$ \StackIndex
idx -> do
    Bool
isNil <- StackIndex -> Lua Bool
isnil StackIndex
idx
    Maybe () -> Lua (Maybe ())
forall (m :: * -> *) a. Monad m => a -> m a
return (if Bool
isNil then () -> Maybe ()
forall a. a -> Maybe a
Just () else Maybe ()
forall a. Maybe a
Nothing)

instance Peekable Lua.Integer where
  peek :: StackIndex -> Lua Integer
peek = String
-> (StackIndex -> Lua (Maybe Integer)) -> StackIndex -> Lua Integer
forall a.
String -> (StackIndex -> Lua (Maybe a)) -> StackIndex -> Lua a
reportValueOnFailure String
"integer" StackIndex -> Lua (Maybe Integer)
tointeger

instance Peekable Lua.Number where
  peek :: StackIndex -> Lua Number
peek = String
-> (StackIndex -> Lua (Maybe Number)) -> StackIndex -> Lua Number
forall a.
String -> (StackIndex -> Lua (Maybe a)) -> StackIndex -> Lua a
reportValueOnFailure String
"number" StackIndex -> Lua (Maybe Number)
tonumber

instance Peekable ByteString where
  peek :: StackIndex -> Lua ByteString
peek = Peeker ByteString
Peek.peekByteString Peeker ByteString
-> (Either PeekError ByteString -> Lua ByteString)
-> StackIndex
-> Lua ByteString
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> Either PeekError ByteString -> Lua ByteString
forall a. Either PeekError a -> Lua a
Peek.force

instance Peekable Bool where
  peek :: StackIndex -> Lua Bool
peek = StackIndex -> Lua Bool
toboolean

instance Peekable CFunction where
  peek :: StackIndex -> Lua CFunction
peek = String
-> (StackIndex -> Lua (Maybe CFunction))
-> StackIndex
-> Lua CFunction
forall a.
String -> (StackIndex -> Lua (Maybe a)) -> StackIndex -> Lua a
reportValueOnFailure String
"C function" StackIndex -> Lua (Maybe CFunction)
tocfunction

instance Peekable (Ptr a) where
  peek :: StackIndex -> Lua (Ptr a)
peek = String
-> (StackIndex -> Lua (Maybe (Ptr a))) -> StackIndex -> Lua (Ptr a)
forall a.
String -> (StackIndex -> Lua (Maybe a)) -> StackIndex -> Lua a
reportValueOnFailure String
"userdata" StackIndex -> Lua (Maybe (Ptr a))
forall a. StackIndex -> Lua (Maybe (Ptr a))
touserdata

instance Peekable Lua.State where
  peek :: StackIndex -> Lua State
peek = String
-> (StackIndex -> Lua (Maybe State)) -> StackIndex -> Lua State
forall a.
String -> (StackIndex -> Lua (Maybe a)) -> StackIndex -> Lua a
reportValueOnFailure String
"Lua state (i.e., a thread)" StackIndex -> Lua (Maybe State)
tothread

instance Peekable T.Text where
  peek :: StackIndex -> Lua Text
peek = Peeker Text
Peek.peekText Peeker Text
-> (Either PeekError Text -> Lua Text) -> StackIndex -> Lua Text
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> Either PeekError Text -> Lua Text
forall a. Either PeekError a -> Lua a
Peek.force

instance Peekable BL.ByteString where
  peek :: StackIndex -> Lua ByteString
peek = Peeker ByteString
Peek.peekLazyByteString Peeker ByteString
-> (Either PeekError ByteString -> Lua ByteString)
-> StackIndex
-> Lua ByteString
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> Either PeekError ByteString -> Lua ByteString
forall a. Either PeekError a -> Lua a
Peek.force

instance Peekable Prelude.Integer where
  peek :: StackIndex -> Lua Integer
peek = Peeker Integer
forall a. (Integral a, Read a) => Peeker a
Peek.peekIntegral Peeker Integer
-> (Either PeekError Integer -> Lua Integer)
-> StackIndex
-> Lua Integer
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> Either PeekError Integer -> Lua Integer
forall a. Either PeekError a -> Lua a
Peek.force

instance Peekable Int where
  peek :: StackIndex -> Lua Int
peek = Peeker Int
forall a. (Integral a, Read a) => Peeker a
Peek.peekIntegral Peeker Int
-> (Either PeekError Int -> Lua Int) -> StackIndex -> Lua Int
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> Either PeekError Int -> Lua Int
forall a. Either PeekError a -> Lua a
Peek.force

instance Peekable Float where
  peek :: StackIndex -> Lua Float
peek = Peeker Float
forall a. (RealFloat a, Read a) => Peeker a
Peek.peekRealFloat Peeker Float
-> (Either PeekError Float -> Lua Float) -> StackIndex -> Lua Float
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> Either PeekError Float -> Lua Float
forall a. Either PeekError a -> Lua a
Peek.force

instance Peekable Double where
  peek :: StackIndex -> Lua Double
peek = Peeker Double
forall a. (RealFloat a, Read a) => Peeker a
Peek.peekRealFloat Peeker Double
-> (Either PeekError Double -> Lua Double)
-> StackIndex
-> Lua Double
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> Either PeekError Double -> Lua Double
forall a. Either PeekError a -> Lua a
Peek.force

instance {-# OVERLAPS #-} Peekable [Char] where
  peek :: StackIndex -> Lua String
peek = Peeker String
Peek.peekString Peeker String
-> (Either PeekError String -> Lua String)
-> StackIndex
-> Lua String
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> Either PeekError String -> Lua String
forall a. Either PeekError a -> Lua a
Peek.force

instance Peekable a => Peekable [a] where
  peek :: StackIndex -> Lua [a]
peek = StackIndex -> Lua [a]
forall a. Peekable a => StackIndex -> Lua [a]
peekList

instance (Ord a, Peekable a, Peekable b) => Peekable (Map a b) where
  peek :: StackIndex -> Lua (Map a b)
peek = ([(a, b)] -> Map a b) -> Lua [(a, b)] -> Lua (Map a b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [(a, b)] -> Map a b
forall k a. Ord k => [(k, a)] -> Map k a
fromList (Lua [(a, b)] -> Lua (Map a b))
-> (StackIndex -> Lua [(a, b)]) -> StackIndex -> Lua (Map a b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StackIndex -> Lua [(a, b)]
forall a b. (Peekable a, Peekable b) => StackIndex -> Lua [(a, b)]
peekKeyValuePairs

instance (Ord a, Peekable a) => Peekable (Set a) where
  peek :: StackIndex -> Lua (Set a)
peek = -- All keys with non-nil values are in the set
    ([(a, Bool)] -> Set a) -> Lua [(a, Bool)] -> Lua (Set a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([a] -> Set a
forall a. Ord a => [a] -> Set a
Set.fromList ([a] -> Set a) -> ([(a, Bool)] -> [a]) -> [(a, Bool)] -> Set a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((a, Bool) -> a) -> [(a, Bool)] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map (a, Bool) -> a
forall a b. (a, b) -> a
fst ([(a, Bool)] -> [a])
-> ([(a, Bool)] -> [(a, Bool)]) -> [(a, Bool)] -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((a, Bool) -> Bool) -> [(a, Bool)] -> [(a, Bool)]
forall a. (a -> Bool) -> [a] -> [a]
filter (a, Bool) -> Bool
forall a b. (a, b) -> b
snd) (Lua [(a, Bool)] -> Lua (Set a))
-> (StackIndex -> Lua [(a, Bool)]) -> StackIndex -> Lua (Set a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StackIndex -> Lua [(a, Bool)]
forall a b. (Peekable a, Peekable b) => StackIndex -> Lua [(a, b)]
peekKeyValuePairs

-- | Read a table into a list
peekList :: Peekable a => StackIndex -> Lua [a]
peekList :: StackIndex -> Lua [a]
peekList = String
-> (StackIndex -> Lua Bool)
-> (StackIndex -> Lua [a])
-> StackIndex
-> Lua [a]
forall a.
String
-> (StackIndex -> Lua Bool)
-> (StackIndex -> Lua a)
-> StackIndex
-> Lua a
typeChecked String
"table" StackIndex -> Lua Bool
istable ((StackIndex -> Lua [a]) -> StackIndex -> Lua [a])
-> (StackIndex -> Lua [a]) -> StackIndex -> Lua [a]
forall a b. (a -> b) -> a -> b
$ \StackIndex
idx -> do
  let elementsAt :: [Integer] -> Lua [a]
elementsAt [] = [a] -> Lua [a]
forall (m :: * -> *) a. Monad m => a -> m a
return []
      elementsAt (Integer
i : [Integer]
is) = do
        a
x <- (StackIndex -> Integer -> Lua ()
rawgeti StackIndex
idx Integer
i Lua () -> Lua a -> Lua a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> StackIndex -> Lua a
forall a. Peekable a => StackIndex -> Lua a
peek (CInt -> StackIndex
nthFromTop CInt
1)) Lua a -> Lua () -> Lua a
forall (m :: * -> *) a b. MonadMask m => m a -> m b -> m a
`Catch.finally` StackIndex -> Lua ()
pop StackIndex
1
        (a
xa -> [a] -> [a]
forall a. a -> [a] -> [a]
:) ([a] -> [a]) -> Lua [a] -> Lua [a]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Integer] -> Lua [a]
elementsAt [Integer]
is
  Integer
listLength <- Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Integer) -> Lua Int -> Lua Integer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StackIndex -> Lua Int
rawlen StackIndex
idx
  String -> Lua [a] -> Lua [a]
forall a. String -> Lua a -> Lua a
inContext String
"Could not read list: " ([Integer] -> Lua [a]
forall a. Peekable a => [Integer] -> Lua [a]
elementsAt [Integer
1..Integer
listLength])

-- | Read a table into a list of pairs.
peekKeyValuePairs :: (Peekable a, Peekable b)
                      => StackIndex -> Lua [(a, b)]
peekKeyValuePairs :: StackIndex -> Lua [(a, b)]
peekKeyValuePairs = String
-> (StackIndex -> Lua Bool)
-> (StackIndex -> Lua [(a, b)])
-> StackIndex
-> Lua [(a, b)]
forall a.
String
-> (StackIndex -> Lua Bool)
-> (StackIndex -> Lua a)
-> StackIndex
-> Lua a
typeChecked String
"table" StackIndex -> Lua Bool
istable ((StackIndex -> Lua [(a, b)]) -> StackIndex -> Lua [(a, b)])
-> (StackIndex -> Lua [(a, b)]) -> StackIndex -> Lua [(a, b)]
forall a b. (a -> b) -> a -> b
$ \StackIndex
idx -> do
  let remainingPairs :: Lua [(a, b)]
remainingPairs = do
        Maybe (a, b)
res <- StackIndex -> Lua (Maybe (a, b))
forall a b.
(Peekable a, Peekable b) =>
StackIndex -> Lua (Maybe (a, b))
nextPair (if StackIndex
idx StackIndex -> StackIndex -> Bool
forall a. Ord a => a -> a -> Bool
< StackIndex
0 then StackIndex
idx StackIndex -> StackIndex -> StackIndex
forall a. Num a => a -> a -> a
- StackIndex
1 else StackIndex
idx)
        case Maybe (a, b)
res of
          Maybe (a, b)
Nothing -> [] [(a, b)] -> Lua () -> Lua [(a, b)]
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ () -> Lua ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
          Just (a, b)
a  -> ((a, b)
a(a, b) -> [(a, b)] -> [(a, b)]
forall a. a -> [a] -> [a]
:) ([(a, b)] -> [(a, b)]) -> Lua [(a, b)] -> Lua [(a, b)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Lua [(a, b)]
remainingPairs
  Lua ()
pushnil
  Lua [(a, b)]
remainingPairs
    -- ensure the remaining key is removed from the stack on exception
    Lua [(a, b)] -> Lua () -> Lua [(a, b)]
forall (m :: * -> *) a b. MonadCatch m => m a -> m b -> m a
`Catch.onException` StackIndex -> Lua ()
pop StackIndex
1

-- | Get the next key-value pair from a table. Assumes the last key to be on the
-- top of the stack and the table at the given index @idx@.
nextPair :: (Peekable a, Peekable b)
         => StackIndex -> Lua (Maybe (a, b))
nextPair :: StackIndex -> Lua (Maybe (a, b))
nextPair StackIndex
idx = do
  Bool
hasNext <- StackIndex -> Lua Bool
next StackIndex
idx
  if Bool
hasNext
    then let pair :: Lua (a, b)
pair = (,) (a -> b -> (a, b)) -> Lua a -> Lua (b -> (a, b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> Lua a -> Lua a
forall a. String -> Lua a -> Lua a
inContext String
"Could not read key of key-value pair: "
                                      (StackIndex -> Lua a
forall a. Peekable a => StackIndex -> Lua a
peek (CInt -> StackIndex
nthFromTop CInt
2))
                        Lua (b -> (a, b)) -> Lua b -> Lua (a, b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> String -> Lua b -> Lua b
forall a. String -> Lua a -> Lua a
inContext String
"Could not read value of key-value pair: "
                                      (StackIndex -> Lua b
forall a. Peekable a => StackIndex -> Lua a
peek (CInt -> StackIndex
nthFromTop CInt
1))
         in (a, b) -> Maybe (a, b)
forall a. a -> Maybe a
Just ((a, b) -> Maybe (a, b)) -> Lua (a, b) -> Lua (Maybe (a, b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Lua (a, b)
pair Lua (a, b) -> Lua () -> Lua (a, b)
forall (m :: * -> *) a b. MonadMask m => m a -> m b -> m a
`Catch.finally` StackIndex -> Lua ()
pop StackIndex
1
            -- removes the value, keeps the key
    else Maybe (a, b) -> Lua (Maybe (a, b))
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (a, b)
forall a. Maybe a
Nothing

-- | Specify a name for the context in which a computation is run. The name is
-- added to the error message in case of an exception.
inContext :: String -> Lua a -> Lua a
inContext :: String -> Lua a -> Lua a
inContext String
ctx Lua a
op = Lua ErrorConversion
Lua.errorConversion Lua ErrorConversion -> (ErrorConversion -> Lua a) -> Lua a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \ErrorConversion
ec ->
  ErrorConversion -> String -> Lua a -> Lua a
ErrorConversion -> forall a. String -> Lua a -> Lua a
Lua.addContextToException ErrorConversion
ec String
ctx Lua a
op

--
-- Tuples
--

instance (Peekable a, Peekable b) => Peekable (a, b) where
  peek :: StackIndex -> Lua (a, b)
peek = String
-> (StackIndex -> Lua Bool)
-> (StackIndex -> Lua (a, b))
-> StackIndex
-> Lua (a, b)
forall a.
String
-> (StackIndex -> Lua Bool)
-> (StackIndex -> Lua a)
-> StackIndex
-> Lua a
typeChecked String
"table" StackIndex -> Lua Bool
istable ((StackIndex -> Lua (a, b)) -> StackIndex -> Lua (a, b))
-> (StackIndex -> Lua (a, b)) -> StackIndex -> Lua (a, b)
forall a b. (a -> b) -> a -> b
$ \StackIndex
idx ->
    (,) (a -> b -> (a, b)) -> Lua a -> Lua (b -> (a, b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StackIndex -> Integer -> Lua a
forall a. Peekable a => StackIndex -> Integer -> Lua a
nthValue StackIndex
idx Integer
1 Lua (b -> (a, b)) -> Lua b -> Lua (a, b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StackIndex -> Integer -> Lua b
forall a. Peekable a => StackIndex -> Integer -> Lua a
nthValue StackIndex
idx Integer
2

instance (Peekable a, Peekable b, Peekable c) =>
         Peekable (a, b, c)
 where
  peek :: StackIndex -> Lua (a, b, c)
peek = String
-> (StackIndex -> Lua Bool)
-> (StackIndex -> Lua (a, b, c))
-> StackIndex
-> Lua (a, b, c)
forall a.
String
-> (StackIndex -> Lua Bool)
-> (StackIndex -> Lua a)
-> StackIndex
-> Lua a
typeChecked String
"table" StackIndex -> Lua Bool
istable ((StackIndex -> Lua (a, b, c)) -> StackIndex -> Lua (a, b, c))
-> (StackIndex -> Lua (a, b, c)) -> StackIndex -> Lua (a, b, c)
forall a b. (a -> b) -> a -> b
$ \StackIndex
idx ->
    (,,) (a -> b -> c -> (a, b, c)) -> Lua a -> Lua (b -> c -> (a, b, c))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StackIndex -> Integer -> Lua a
forall a. Peekable a => StackIndex -> Integer -> Lua a
nthValue StackIndex
idx Integer
1 Lua (b -> c -> (a, b, c)) -> Lua b -> Lua (c -> (a, b, c))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StackIndex -> Integer -> Lua b
forall a. Peekable a => StackIndex -> Integer -> Lua a
nthValue StackIndex
idx Integer
2 Lua (c -> (a, b, c)) -> Lua c -> Lua (a, b, c)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StackIndex -> Integer -> Lua c
forall a. Peekable a => StackIndex -> Integer -> Lua a
nthValue StackIndex
idx Integer
3

instance (Peekable a, Peekable b, Peekable c, Peekable d) =>
         Peekable (a, b, c, d)
 where
  peek :: StackIndex -> Lua (a, b, c, d)
peek = String
-> (StackIndex -> Lua Bool)
-> (StackIndex -> Lua (a, b, c, d))
-> StackIndex
-> Lua (a, b, c, d)
forall a.
String
-> (StackIndex -> Lua Bool)
-> (StackIndex -> Lua a)
-> StackIndex
-> Lua a
typeChecked String
"table" StackIndex -> Lua Bool
istable ((StackIndex -> Lua (a, b, c, d))
 -> StackIndex -> Lua (a, b, c, d))
-> (StackIndex -> Lua (a, b, c, d))
-> StackIndex
-> Lua (a, b, c, d)
forall a b. (a -> b) -> a -> b
$ \StackIndex
idx ->
    (,,,) (a -> b -> c -> d -> (a, b, c, d))
-> Lua a -> Lua (b -> c -> d -> (a, b, c, d))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StackIndex -> Integer -> Lua a
forall a. Peekable a => StackIndex -> Integer -> Lua a
nthValue StackIndex
idx Integer
1 Lua (b -> c -> d -> (a, b, c, d))
-> Lua b -> Lua (c -> d -> (a, b, c, d))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StackIndex -> Integer -> Lua b
forall a. Peekable a => StackIndex -> Integer -> Lua a
nthValue StackIndex
idx Integer
2 Lua (c -> d -> (a, b, c, d)) -> Lua c -> Lua (d -> (a, b, c, d))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StackIndex -> Integer -> Lua c
forall a. Peekable a => StackIndex -> Integer -> Lua a
nthValue StackIndex
idx Integer
3
          Lua (d -> (a, b, c, d)) -> Lua d -> Lua (a, b, c, d)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StackIndex -> Integer -> Lua d
forall a. Peekable a => StackIndex -> Integer -> Lua a
nthValue StackIndex
idx Integer
4

instance (Peekable a, Peekable b, Peekable c,
          Peekable d, Peekable e) =>
         Peekable (a, b, c, d, e)
 where
  peek :: StackIndex -> Lua (a, b, c, d, e)
peek = String
-> (StackIndex -> Lua Bool)
-> (StackIndex -> Lua (a, b, c, d, e))
-> StackIndex
-> Lua (a, b, c, d, e)
forall a.
String
-> (StackIndex -> Lua Bool)
-> (StackIndex -> Lua a)
-> StackIndex
-> Lua a
typeChecked String
"table" StackIndex -> Lua Bool
istable ((StackIndex -> Lua (a, b, c, d, e))
 -> StackIndex -> Lua (a, b, c, d, e))
-> (StackIndex -> Lua (a, b, c, d, e))
-> StackIndex
-> Lua (a, b, c, d, e)
forall a b. (a -> b) -> a -> b
$ \StackIndex
idx ->
    (,,,,) (a -> b -> c -> d -> e -> (a, b, c, d, e))
-> Lua a -> Lua (b -> c -> d -> e -> (a, b, c, d, e))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StackIndex -> Integer -> Lua a
forall a. Peekable a => StackIndex -> Integer -> Lua a
nthValue StackIndex
idx Integer
1 Lua (b -> c -> d -> e -> (a, b, c, d, e))
-> Lua b -> Lua (c -> d -> e -> (a, b, c, d, e))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StackIndex -> Integer -> Lua b
forall a. Peekable a => StackIndex -> Integer -> Lua a
nthValue StackIndex
idx Integer
2 Lua (c -> d -> e -> (a, b, c, d, e))
-> Lua c -> Lua (d -> e -> (a, b, c, d, e))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StackIndex -> Integer -> Lua c
forall a. Peekable a => StackIndex -> Integer -> Lua a
nthValue StackIndex
idx Integer
3
           Lua (d -> e -> (a, b, c, d, e))
-> Lua d -> Lua (e -> (a, b, c, d, e))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StackIndex -> Integer -> Lua d
forall a. Peekable a => StackIndex -> Integer -> Lua a
nthValue StackIndex
idx Integer
4 Lua (e -> (a, b, c, d, e)) -> Lua e -> Lua (a, b, c, d, e)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StackIndex -> Integer -> Lua e
forall a. Peekable a => StackIndex -> Integer -> Lua a
nthValue StackIndex
idx Integer
5

instance (Peekable a, Peekable b, Peekable c,
          Peekable d, Peekable e, Peekable f) =>
         Peekable (a, b, c, d, e, f)
 where
  peek :: StackIndex -> Lua (a, b, c, d, e, f)
peek = String
-> (StackIndex -> Lua Bool)
-> (StackIndex -> Lua (a, b, c, d, e, f))
-> StackIndex
-> Lua (a, b, c, d, e, f)
forall a.
String
-> (StackIndex -> Lua Bool)
-> (StackIndex -> Lua a)
-> StackIndex
-> Lua a
typeChecked String
"table" StackIndex -> Lua Bool
istable ((StackIndex -> Lua (a, b, c, d, e, f))
 -> StackIndex -> Lua (a, b, c, d, e, f))
-> (StackIndex -> Lua (a, b, c, d, e, f))
-> StackIndex
-> Lua (a, b, c, d, e, f)
forall a b. (a -> b) -> a -> b
$ \StackIndex
idx ->
    (,,,,,) (a -> b -> c -> d -> e -> f -> (a, b, c, d, e, f))
-> Lua a -> Lua (b -> c -> d -> e -> f -> (a, b, c, d, e, f))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StackIndex -> Integer -> Lua a
forall a. Peekable a => StackIndex -> Integer -> Lua a
nthValue StackIndex
idx Integer
1 Lua (b -> c -> d -> e -> f -> (a, b, c, d, e, f))
-> Lua b -> Lua (c -> d -> e -> f -> (a, b, c, d, e, f))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StackIndex -> Integer -> Lua b
forall a. Peekable a => StackIndex -> Integer -> Lua a
nthValue StackIndex
idx Integer
2 Lua (c -> d -> e -> f -> (a, b, c, d, e, f))
-> Lua c -> Lua (d -> e -> f -> (a, b, c, d, e, f))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StackIndex -> Integer -> Lua c
forall a. Peekable a => StackIndex -> Integer -> Lua a
nthValue StackIndex
idx Integer
3
            Lua (d -> e -> f -> (a, b, c, d, e, f))
-> Lua d -> Lua (e -> f -> (a, b, c, d, e, f))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StackIndex -> Integer -> Lua d
forall a. Peekable a => StackIndex -> Integer -> Lua a
nthValue StackIndex
idx Integer
4 Lua (e -> f -> (a, b, c, d, e, f))
-> Lua e -> Lua (f -> (a, b, c, d, e, f))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StackIndex -> Integer -> Lua e
forall a. Peekable a => StackIndex -> Integer -> Lua a
nthValue StackIndex
idx Integer
5 Lua (f -> (a, b, c, d, e, f)) -> Lua f -> Lua (a, b, c, d, e, f)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StackIndex -> Integer -> Lua f
forall a. Peekable a => StackIndex -> Integer -> Lua a
nthValue StackIndex
idx Integer
6


instance (Peekable a, Peekable b, Peekable c, Peekable d,
          Peekable e, Peekable f, Peekable g) =>
         Peekable (a, b, c, d, e, f, g)
 where
  peek :: StackIndex -> Lua (a, b, c, d, e, f, g)
peek = String
-> (StackIndex -> Lua Bool)
-> (StackIndex -> Lua (a, b, c, d, e, f, g))
-> StackIndex
-> Lua (a, b, c, d, e, f, g)
forall a.
String
-> (StackIndex -> Lua Bool)
-> (StackIndex -> Lua a)
-> StackIndex
-> Lua a
typeChecked String
"table" StackIndex -> Lua Bool
istable ((StackIndex -> Lua (a, b, c, d, e, f, g))
 -> StackIndex -> Lua (a, b, c, d, e, f, g))
-> (StackIndex -> Lua (a, b, c, d, e, f, g))
-> StackIndex
-> Lua (a, b, c, d, e, f, g)
forall a b. (a -> b) -> a -> b
$ \StackIndex
idx ->
    (,,,,,,) (a -> b -> c -> d -> e -> f -> g -> (a, b, c, d, e, f, g))
-> Lua a
-> Lua (b -> c -> d -> e -> f -> g -> (a, b, c, d, e, f, g))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StackIndex -> Integer -> Lua a
forall a. Peekable a => StackIndex -> Integer -> Lua a
nthValue StackIndex
idx Integer
1 Lua (b -> c -> d -> e -> f -> g -> (a, b, c, d, e, f, g))
-> Lua b -> Lua (c -> d -> e -> f -> g -> (a, b, c, d, e, f, g))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StackIndex -> Integer -> Lua b
forall a. Peekable a => StackIndex -> Integer -> Lua a
nthValue StackIndex
idx Integer
2 Lua (c -> d -> e -> f -> g -> (a, b, c, d, e, f, g))
-> Lua c -> Lua (d -> e -> f -> g -> (a, b, c, d, e, f, g))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StackIndex -> Integer -> Lua c
forall a. Peekable a => StackIndex -> Integer -> Lua a
nthValue StackIndex
idx Integer
3
             Lua (d -> e -> f -> g -> (a, b, c, d, e, f, g))
-> Lua d -> Lua (e -> f -> g -> (a, b, c, d, e, f, g))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StackIndex -> Integer -> Lua d
forall a. Peekable a => StackIndex -> Integer -> Lua a
nthValue StackIndex
idx Integer
4 Lua (e -> f -> g -> (a, b, c, d, e, f, g))
-> Lua e -> Lua (f -> g -> (a, b, c, d, e, f, g))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StackIndex -> Integer -> Lua e
forall a. Peekable a => StackIndex -> Integer -> Lua a
nthValue StackIndex
idx Integer
5 Lua (f -> g -> (a, b, c, d, e, f, g))
-> Lua f -> Lua (g -> (a, b, c, d, e, f, g))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StackIndex -> Integer -> Lua f
forall a. Peekable a => StackIndex -> Integer -> Lua a
nthValue StackIndex
idx Integer
6
             Lua (g -> (a, b, c, d, e, f, g))
-> Lua g -> Lua (a, b, c, d, e, f, g)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StackIndex -> Integer -> Lua g
forall a. Peekable a => StackIndex -> Integer -> Lua a
nthValue StackIndex
idx Integer
7

instance (Peekable a, Peekable b, Peekable c, Peekable d,
          Peekable e, Peekable f, Peekable g, Peekable h) =>
         Peekable (a, b, c, d, e, f, g, h)
 where
  peek :: StackIndex -> Lua (a, b, c, d, e, f, g, h)
peek = String
-> (StackIndex -> Lua Bool)
-> (StackIndex -> Lua (a, b, c, d, e, f, g, h))
-> StackIndex
-> Lua (a, b, c, d, e, f, g, h)
forall a.
String
-> (StackIndex -> Lua Bool)
-> (StackIndex -> Lua a)
-> StackIndex
-> Lua a
typeChecked String
"table" StackIndex -> Lua Bool
istable ((StackIndex -> Lua (a, b, c, d, e, f, g, h))
 -> StackIndex -> Lua (a, b, c, d, e, f, g, h))
-> (StackIndex -> Lua (a, b, c, d, e, f, g, h))
-> StackIndex
-> Lua (a, b, c, d, e, f, g, h)
forall a b. (a -> b) -> a -> b
$ \StackIndex
idx ->
    (,,,,,,,) (a -> b -> c -> d -> e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
-> Lua a
-> Lua
     (b -> c -> d -> e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StackIndex -> Integer -> Lua a
forall a. Peekable a => StackIndex -> Integer -> Lua a
nthValue StackIndex
idx Integer
1 Lua (b -> c -> d -> e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
-> Lua b
-> Lua (c -> d -> e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StackIndex -> Integer -> Lua b
forall a. Peekable a => StackIndex -> Integer -> Lua a
nthValue StackIndex
idx Integer
2 Lua (c -> d -> e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
-> Lua c -> Lua (d -> e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StackIndex -> Integer -> Lua c
forall a. Peekable a => StackIndex -> Integer -> Lua a
nthValue StackIndex
idx Integer
3
              Lua (d -> e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
-> Lua d -> Lua (e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StackIndex -> Integer -> Lua d
forall a. Peekable a => StackIndex -> Integer -> Lua a
nthValue StackIndex
idx Integer
4 Lua (e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
-> Lua e -> Lua (f -> g -> h -> (a, b, c, d, e, f, g, h))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StackIndex -> Integer -> Lua e
forall a. Peekable a => StackIndex -> Integer -> Lua a
nthValue StackIndex
idx Integer
5 Lua (f -> g -> h -> (a, b, c, d, e, f, g, h))
-> Lua f -> Lua (g -> h -> (a, b, c, d, e, f, g, h))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StackIndex -> Integer -> Lua f
forall a. Peekable a => StackIndex -> Integer -> Lua a
nthValue StackIndex
idx Integer
6
              Lua (g -> h -> (a, b, c, d, e, f, g, h))
-> Lua g -> Lua (h -> (a, b, c, d, e, f, g, h))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StackIndex -> Integer -> Lua g
forall a. Peekable a => StackIndex -> Integer -> Lua a
nthValue StackIndex
idx Integer
7 Lua (h -> (a, b, c, d, e, f, g, h))
-> Lua h -> Lua (a, b, c, d, e, f, g, h)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StackIndex -> Integer -> Lua h
forall a. Peekable a => StackIndex -> Integer -> Lua a
nthValue StackIndex
idx Integer
8

-- | Helper function to get the nth table value
nthValue :: Peekable a => StackIndex -> Lua.Integer -> Lua a
nthValue :: StackIndex -> Integer -> Lua a
nthValue StackIndex
idx Integer
n = do
  StackIndex -> Integer -> Lua ()
rawgeti StackIndex
idx Integer
n
  StackIndex -> Lua a
forall a. Peekable a => StackIndex -> Lua a
peek (-StackIndex
1) Lua a -> Lua () -> Lua a
forall (m :: * -> *) a b. MonadMask m => m a -> m b -> m a
`Catch.finally` StackIndex -> Lua ()
pop StackIndex
1