{-# LANGUAGE DerivingStrategies   #-}
{-# LANGUAGE OverloadedStrings    #-}
{-# LANGUAGE ScopedTypeVariables  #-}
{- |
Copyright   : © 2021-2023 Albert Krewinkel
License     : MIT
Maintainer  : Albert Krewinkel <albert@zeitkraut.de>

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

import Control.Applicative (optional)
import Data.Maybe (fromMaybe)
import HsLua as Lua
import Text.Pandoc.Lua.Marshal.Alignment (peekAlignment, pushAlignment)
import Text.Pandoc.Lua.Marshal.Block (peekBlocksFuzzy, pushBlocks)
import Text.Pandoc.Lua.Marshal.Inline (peekInlinesFuzzy, pushInlines)
import Text.Pandoc.Lua.Marshal.List (pushPandocList)
import Text.Pandoc.Definition

-- | 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]]]
  } deriving stock (SimpleTable -> SimpleTable -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SimpleTable -> SimpleTable -> Bool
$c/= :: SimpleTable -> SimpleTable -> Bool
== :: SimpleTable -> SimpleTable -> Bool
$c== :: SimpleTable -> SimpleTable -> Bool
Eq, Int -> SimpleTable -> ShowS
[SimpleTable] -> ShowS
SimpleTable -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SimpleTable] -> ShowS
$cshowList :: [SimpleTable] -> ShowS
show :: SimpleTable -> String
$cshow :: SimpleTable -> String
showsPrec :: Int -> SimpleTable -> ShowS
$cshowsPrec :: Int -> SimpleTable -> ShowS
Show)

typeSimpleTable :: LuaError e => DocumentedType e SimpleTable
typeSimpleTable :: forall e. LuaError e => DocumentedType e SimpleTable
typeSimpleTable = forall e a.
LuaError e =>
Name
-> [(Operation, DocumentedFunction e)]
-> [Member e (DocumentedFunction e) a]
-> DocumentedType e a
deftype Name
"SimpleTable"
  [ forall e.
Operation
-> DocumentedFunction e -> (Operation, DocumentedFunction e)
operation Operation
Eq forall a b. (a -> b) -> a -> b
$ forall a e. a -> HsFnPrecursor e a
lambda
    ### liftPure2 (\a b -> fromMaybe False ((==) <$> a <*> b))
    forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter (forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e. LuaError e => Peeker e SimpleTable
peekSimpleTable) Text
"value" Text
"a" Text
""
    forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter (forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e. LuaError e => Peeker e SimpleTable
peekSimpleTable) Text
"value" Text
"b" Text
""
    forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult forall e. Pusher e Bool
pushBool Text
"boolean" Text
"whether the two objects are equal"
  , forall e.
Operation
-> DocumentedFunction e -> (Operation, DocumentedFunction e)
operation Operation
Tostring forall a b. (a -> b) -> a -> b
$ forall a e. a -> HsFnPrecursor e a
lambda
    ### liftPure show
    forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> forall e a itemtype.
LuaError e =>
DocumentedTypeWithList e a itemtype
-> Text -> Text -> Parameter e a
udparam forall e. LuaError e => DocumentedType e SimpleTable
typeSimpleTable Text
"self" Text
""
    forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult forall e. String -> LuaE e ()
pushString Text
"string" Text
"Haskell string representation"
  ]
  [ forall e b a fn.
LuaError e =>
Name
-> Text
-> (Pusher e b, a -> b)
-> (Peeker e b, a -> b -> a)
-> Member e fn a
property Name
"caption" Text
"table caption"
      (forall e. LuaError e => Pusher e [Inline]
pushInlines, SimpleTable -> [Inline]
simpleTableCaption)
      (forall e. LuaError e => Peeker e [Inline]
peekInlinesFuzzy, \SimpleTable
t [Inline]
capt -> SimpleTable
t {simpleTableCaption :: [Inline]
simpleTableCaption = [Inline]
capt})
  , forall e b a fn.
LuaError e =>
Name
-> Text
-> (Pusher e b, a -> b)
-> (Peeker e b, a -> b -> a)
-> Member e fn a
property Name
"aligns" Text
"column alignments"
      (forall e a. LuaError e => Pusher e a -> Pusher e [a]
pushPandocList forall e. Pusher e Alignment
pushAlignment, SimpleTable -> [Alignment]
simpleTableAlignments)
      (forall a e. LuaError e => Peeker e a -> Peeker e [a]
peekList forall e. Peeker e Alignment
peekAlignment, \SimpleTable
t [Alignment]
aligns -> SimpleTable
t{simpleTableAlignments :: [Alignment]
simpleTableAlignments = [Alignment]
aligns})
  , forall e b a fn.
LuaError e =>
Name
-> Text
-> (Pusher e b, a -> b)
-> (Peeker e b, a -> b -> a)
-> Member e fn a
property Name
"widths" Text
"relative column widths"
      (forall e a. LuaError e => Pusher e a -> Pusher e [a]
pushPandocList forall a e. RealFloat a => a -> LuaE e ()
pushRealFloat, SimpleTable -> [Double]
simpleTableColumnWidths)
      (forall a e. LuaError e => Peeker e a -> Peeker e [a]
peekList forall a e. (RealFloat a, Read a) => Peeker e a
peekRealFloat, \SimpleTable
t [Double]
ws -> SimpleTable
t{simpleTableColumnWidths :: [Double]
simpleTableColumnWidths = [Double]
ws})
  , forall e b a fn.
LuaError e =>
Name
-> Text
-> (Pusher e b, a -> b)
-> (Peeker e b, a -> b -> a)
-> Member e fn a
property Name
"headers" Text
"table header"
      (Pusher e [[Block]]
pushRow, SimpleTable -> [[Block]]
simpleTableHeader)
      (forall e. LuaError e => Peeker e [[Block]]
peekRow, \SimpleTable
t [[Block]]
h -> SimpleTable
t{simpleTableHeader :: [[Block]]
simpleTableHeader = [[Block]]
h})
  , forall e b a fn.
LuaError e =>
Name
-> Text
-> (Pusher e b, a -> b)
-> (Peeker e b, a -> b -> a)
-> Member e fn a
property Name
"rows" Text
"table body rows"
      (forall e a. LuaError e => Pusher e a -> Pusher e [a]
pushPandocList Pusher e [[Block]]
pushRow, SimpleTable -> [[[Block]]]
simpleTableBody)
      (forall a e. LuaError e => Peeker e a -> Peeker e [a]
peekList forall e. LuaError e => Peeker e [[Block]]
peekRow, \SimpleTable
t [[[Block]]]
bs -> SimpleTable
t{simpleTableBody :: [[[Block]]]
simpleTableBody = [[[Block]]]
bs})

  , forall e b a fn.
Name -> Text -> (Pusher e b, a -> b) -> Member e fn a
readonly Name
"t" Text
"type tag (always 'SimpleTable')"
      (forall e. Pusher e Text
pushText, forall a b. a -> b -> a
const Text
"SimpleTable")

  , forall e fn a. AliasIndex -> Text -> [AliasIndex] -> Member e fn a
alias AliasIndex
"header" Text
"alias for `headers`" [AliasIndex
"headers"]
  ]
 where
  pushRow :: Pusher e [[Block]]
pushRow = forall e a. LuaError e => Pusher e a -> Pusher e [a]
pushPandocList forall e. LuaError e => Pusher e [Block]
pushBlocks

peekRow :: LuaError e => Peeker e [[Block]]
peekRow :: forall e. LuaError e => Peeker e [[Block]]
peekRow = forall a e. LuaError e => Peeker e a -> Peeker e [a]
peekList forall e. LuaError e => Peeker e [Block]
peekBlocksFuzzy

-- | Push a simple table to the stack by calling the
-- @pandoc.SimpleTable@ constructor.
pushSimpleTable :: forall e. LuaError e => SimpleTable -> LuaE e ()
pushSimpleTable :: forall e. LuaError e => SimpleTable -> LuaE e ()
pushSimpleTable = forall e fn a itemtype.
LuaError e =>
UDTypeWithList e fn a itemtype -> a -> LuaE e ()
pushUD forall e. LuaError e => DocumentedType e SimpleTable
typeSimpleTable

-- | Retrieve a simple table from the stack.
peekSimpleTable :: forall e. LuaError e => Peeker e SimpleTable
peekSimpleTable :: forall e. LuaError e => Peeker e SimpleTable
peekSimpleTable = forall e a. Name -> Peek e a -> Peek e a
retrieving Name
"SimpleTable" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e fn a itemtype.
LuaError e =>
UDTypeWithList e fn a itemtype -> Peeker e a
peekUD forall e. LuaError e => DocumentedType e SimpleTable
typeSimpleTable

-- | Constructor for the 'SimpleTable' type.
mkSimpleTable :: LuaError e => DocumentedFunction e
mkSimpleTable :: forall e. LuaError e => DocumentedFunction e
mkSimpleTable = forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"SimpleTable"
  ### liftPure5 SimpleTable
  forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter forall e. LuaError e => Peeker e [Inline]
peekInlinesFuzzy Text
"Inlines" Text
"caption"
        Text
"table caption"
  forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter (forall a e. LuaError e => Peeker e a -> Peeker e [a]
peekList forall e. Peeker e Alignment
peekAlignment) Text
"{Alignment,...}" Text
"align"
        Text
"column alignments"
  forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter (forall a e. LuaError e => Peeker e a -> Peeker e [a]
peekList forall a e. (RealFloat a, Read a) => Peeker e a
peekRealFloat) Text
"{number,...}" Text
"widths"
        Text
"relative column widths"
  forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter forall e. LuaError e => Peeker e [[Block]]
peekRow Text
"{Blocks,...}" Text
"header"
        Text
"table header row"
  forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter (forall a e. LuaError e => Peeker e a -> Peeker e [a]
peekList forall e. LuaError e => Peeker e [[Block]]
peekRow) Text
"{{Blocks,...},...}" Text
"body"
        Text
"table body rows"
  forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult forall e. LuaError e => SimpleTable -> LuaE e ()
pushSimpleTable Text
"SimpleTable" Text
"new SimpleTable object"