{-# LANGUAGE LambdaCase        #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Copyright  : © 2021-2023 Albert Krewinkel
License    : MIT
Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>

Lua lists with additional methods.
-}
module Text.Pandoc.Lua.Marshal.List
  ( module HsLua.List
  , pushPandocList
  ) where

import HsLua
import HsLua.List

-- | Pushes a list as a numerically-indexed Lua table, and sets a
-- metatable that offers a number of convenience functions.
pushPandocList :: LuaError e => Pusher e a -> Pusher e [a]
pushPandocList :: forall e a. LuaError e => Pusher e a -> Pusher e [a]
pushPandocList Pusher e a
pushItem [a]
items = do
  forall e a. LuaError e => Pusher e a -> Pusher e [a]
pushList Pusher e a
pushItem [a]
items
  forall e. Name -> LuaE e Type
getmetatable' Name
"List" forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
    Type
TypeTable -> forall e. StackIndex -> LuaE e ()
setmetatable (CInt -> StackIndex
nth CInt
2)
    Type
_ -> forall e a. LuaError e => String -> LuaE e a
failLua String
"List has not been initialized correctly."