{- |
   Module      : Text.Pandoc.Lua.Marshaling.SimpleTable
   Copyright   : © 2020-2021 Albert Krewinkel
   License     : GNU GPL, version 2 or above

   Maintainer  : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
   Stability   : alpha

Definition and marshaling of the 'SimpleTable' data type used as a
convenience type when dealing with tables.
-}
module Text.Pandoc.Lua.Marshaling.SimpleTable
  ( SimpleTable (..)
  , peekSimpleTable
  , pushSimpleTable
  )
  where

import Foreign.Lua (Lua, Peekable, Pushable, StackIndex)
import Text.Pandoc.Definition
import Text.Pandoc.Lua.Util (defineHowTo, pushViaConstructor, rawField)
import Text.Pandoc.Lua.Marshaling.AST ()

import qualified Foreign.Lua as Lua

-- | A simple (legacy-style) table.
data SimpleTable = SimpleTable
  { SimpleTable -> [Inline]
simpleTableCaption :: [Inline]
  , SimpleTable -> [Alignment]
simpleTableAlignments :: [Alignment]
  , SimpleTable -> [Double]
simpleTableColumnWidths :: [Double]
  , SimpleTable -> [[Block]]
simpleTableHeader :: [[Block]]
  , SimpleTable -> [[[Block]]]
simpleTableBody :: [[[Block]]]
  }

instance Pushable SimpleTable where
  push :: SimpleTable -> Lua ()
push = SimpleTable -> Lua ()
pushSimpleTable

instance Peekable SimpleTable where
  peek :: StackIndex -> Lua SimpleTable
peek = StackIndex -> Lua SimpleTable
peekSimpleTable

-- | Push a simple table to the stack by calling the
-- @pandoc.SimpleTable@ constructor.
pushSimpleTable :: SimpleTable -> Lua ()
pushSimpleTable :: SimpleTable -> Lua ()
pushSimpleTable SimpleTable
tbl = String
-> [Inline]
-> [Alignment]
-> [Double]
-> [[Block]]
-> [[[Block]]]
-> Lua ()
forall a. PushViaCall a => String -> a
pushViaConstructor String
"SimpleTable"
  (SimpleTable -> [Inline]
simpleTableCaption SimpleTable
tbl)
  (SimpleTable -> [Alignment]
simpleTableAlignments SimpleTable
tbl)
  (SimpleTable -> [Double]
simpleTableColumnWidths SimpleTable
tbl)
  (SimpleTable -> [[Block]]
simpleTableHeader SimpleTable
tbl)
  (SimpleTable -> [[[Block]]]
simpleTableBody SimpleTable
tbl)

-- | Retrieve a simple table from the stack.
peekSimpleTable :: StackIndex -> Lua SimpleTable
peekSimpleTable :: StackIndex -> Lua SimpleTable
peekSimpleTable StackIndex
idx = String -> Lua SimpleTable -> Lua SimpleTable
forall a. String -> Lua a -> Lua a
defineHowTo String
"get SimpleTable" (Lua SimpleTable -> Lua SimpleTable)
-> Lua SimpleTable -> Lua SimpleTable
forall a b. (a -> b) -> a -> b
$
  [Inline]
-> [Alignment]
-> [Double]
-> [[Block]]
-> [[[Block]]]
-> SimpleTable
SimpleTable
    ([Inline]
 -> [Alignment]
 -> [Double]
 -> [[Block]]
 -> [[[Block]]]
 -> SimpleTable)
-> Lua [Inline]
-> Lua
     ([Alignment]
      -> [Double] -> [[Block]] -> [[[Block]]] -> SimpleTable)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StackIndex -> String -> Lua [Inline]
forall a. Peekable a => StackIndex -> String -> Lua a
rawField StackIndex
idx String
"caption"
    Lua
  ([Alignment]
   -> [Double] -> [[Block]] -> [[[Block]]] -> SimpleTable)
-> Lua [Alignment]
-> Lua ([Double] -> [[Block]] -> [[[Block]]] -> SimpleTable)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StackIndex -> String -> Lua [Alignment]
forall a. Peekable a => StackIndex -> String -> Lua a
rawField StackIndex
idx String
"aligns"
    Lua ([Double] -> [[Block]] -> [[[Block]]] -> SimpleTable)
-> Lua [Double] -> Lua ([[Block]] -> [[[Block]]] -> SimpleTable)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StackIndex -> String -> Lua [Double]
forall a. Peekable a => StackIndex -> String -> Lua a
rawField StackIndex
idx String
"widths"
    Lua ([[Block]] -> [[[Block]]] -> SimpleTable)
-> Lua [[Block]] -> Lua ([[[Block]]] -> SimpleTable)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StackIndex -> String -> Lua [[Block]]
forall a. Peekable a => StackIndex -> String -> Lua a
rawField StackIndex
idx String
"headers"
    Lua ([[[Block]]] -> SimpleTable)
-> Lua [[[Block]]] -> Lua SimpleTable
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StackIndex -> String -> Lua [[[Block]]]
forall a. Peekable a => StackIndex -> String -> Lua a
rawField StackIndex
idx String
"rows"