#if !MIN_VERSION_base(4,8,0)
#endif
module Foreign.Lua.Types.ToLuaStack
  ( ToLuaStack (..)
  , pushList
  ) where
import Control.Monad (zipWithM_)
import Data.ByteString (ByteString)
import Data.Map (Map, toList)
import Foreign.Lua.Api
import Foreign.Lua.Types.Lua
import Foreign.Ptr (Ptr)
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.ByteString.Lazy as BL
class ToLuaStack a where
  
  
  push :: a -> Lua ()
instance ToLuaStack () where
  push = const pushnil
instance ToLuaStack LuaInteger where
  push = pushinteger
instance ToLuaStack LuaNumber where
  push = pushnumber
instance ToLuaStack ByteString where
  push = pushstring
instance ToLuaStack Bool where
  push = pushboolean
instance ToLuaStack CFunction where
  push = pushcfunction
instance ToLuaStack (Ptr a) where
  push = pushlightuserdata
instance ToLuaStack T.Text where
  push = push . T.encodeUtf8
instance ToLuaStack BL.ByteString where
  push = push . BL.toStrict
#if MIN_VERSION_base(4,8,0)
instance  ToLuaStack [Char] where
#else
instance ToLuaStack [Char] where
#endif
  push = push . T.pack
instance ToLuaStack a => ToLuaStack [a] where
  push = pushList
pushList :: ToLuaStack a => [a] -> Lua ()
pushList xs = do
  let setField i x = push x *> rawseti (2) i
  newtable
  zipWithM_ setField [1..] xs
instance (ToLuaStack a, ToLuaStack b) => ToLuaStack (Map a b) where
  push m = do
    let addValue (k, v) = push k *> push v *> rawset (3)
    newtable
    mapM_ addValue (toList m)
instance (ToLuaStack a, ToLuaStack b) => ToLuaStack (a, b) where
  push (a, b) = do
    newtable
    addRawInt 1 a
    addRawInt 2 b
instance (ToLuaStack a, ToLuaStack b, ToLuaStack c) =>
         ToLuaStack (a, b, c)
 where
  push (a, b, c) = do
    newtable
    addRawInt 1 a
    addRawInt 2 b
    addRawInt 3 c
instance (ToLuaStack a, ToLuaStack b, ToLuaStack c, ToLuaStack d) =>
         ToLuaStack (a, b, c, d)
 where
  push (a, b, c, d) = do
    newtable
    addRawInt 1 a
    addRawInt 2 b
    addRawInt 3 c
    addRawInt 4 d
instance (ToLuaStack a, ToLuaStack b, ToLuaStack c,
          ToLuaStack d, ToLuaStack e) =>
         ToLuaStack (a, b, c, d, e)
 where
  push (a, b, c, d, e) = do
    newtable
    addRawInt 1 a
    addRawInt 2 b
    addRawInt 3 c
    addRawInt 4 d
    addRawInt 5 e
instance (ToLuaStack a, ToLuaStack b, ToLuaStack c,
          ToLuaStack d, ToLuaStack e, ToLuaStack f) =>
         ToLuaStack (a, b, c, d, e, f)
 where
  push (a, b, c, d, e, f) = do
    newtable
    addRawInt 1 a
    addRawInt 2 b
    addRawInt 3 c
    addRawInt 4 d
    addRawInt 5 e
    addRawInt 6 f
instance (ToLuaStack a, ToLuaStack b, ToLuaStack c, ToLuaStack d,
          ToLuaStack e, ToLuaStack f, ToLuaStack g) =>
         ToLuaStack (a, b, c, d, e, f, g)
 where
  push (a, b, c, d, e, f, g) = do
    newtable
    addRawInt 1 a
    addRawInt 2 b
    addRawInt 3 c
    addRawInt 4 d
    addRawInt 5 e
    addRawInt 6 f
    addRawInt 7 g
instance (ToLuaStack a, ToLuaStack b, ToLuaStack c, ToLuaStack d,
          ToLuaStack e, ToLuaStack f, ToLuaStack g, ToLuaStack h) =>
         ToLuaStack (a, b, c, d, e, f, g, h)
 where
  push (a, b, c, d, e, f, g, h) = do
    newtable
    addRawInt 1 a
    addRawInt 2 b
    addRawInt 3 c
    addRawInt 4 d
    addRawInt 5 e
    addRawInt 6 f
    addRawInt 7 g
    addRawInt 8 h
addRawInt :: ToLuaStack a => Int -> a -> Lua ()
addRawInt idx val = do
  push val
  rawseti (2) idx