{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
module Text.Pandoc.Lua.Marshal.Content
( Content (..)
, contentTypeDescription
, peekContent
, pushContent
, peekDefinitionItem
) where
import Control.Applicative ((<|>))
import Control.Monad ((<$!>))
import HsLua
import {-# SOURCE #-} Text.Pandoc.Lua.Marshal.Block
( peekBlocksFuzzy, pushBlocks )
import {-# SOURCE #-} Text.Pandoc.Lua.Marshal.Inline
( peekInlinesFuzzy, pushInlines )
import Text.Pandoc.Lua.Marshal.List (pushPandocList)
import Text.Pandoc.Definition (Inline, Block)
data Content
= ContentBlocks [Block]
| ContentInlines [Inline]
| ContentLines [[Inline]]
| ContentDefItems [([Inline], [[Block]])]
| ContentListItems [[Block]]
contentTypeDescription :: Content -> String
contentTypeDescription :: Content -> String
contentTypeDescription = \case
ContentBlocks {} -> String
"list of Block items"
ContentInlines {} -> String
"list of Inline items"
ContentLines {} -> String
"list of Inline lists (i.e., a list of lines)"
ContentDefItems {} -> String
"list of definition items items"
ContentListItems {} -> String
"list items (i.e., list of list of Block elements)"
pushContent :: LuaError e => Pusher e Content
pushContent :: Pusher e Content
pushContent = \case
ContentBlocks [Block]
blks -> Pusher e [Block]
forall e. LuaError e => Pusher e [Block]
pushBlocks [Block]
blks
ContentInlines [Inline]
inlns -> Pusher e [Inline]
forall e. LuaError e => Pusher e [Inline]
pushInlines [Inline]
inlns
ContentLines [[Inline]]
lns -> Pusher e [Inline] -> Pusher e [[Inline]]
forall e a. LuaError e => Pusher e a -> Pusher e [a]
pushPandocList Pusher e [Inline]
forall e. LuaError e => Pusher e [Inline]
pushInlines [[Inline]]
lns
ContentDefItems [([Inline], [[Block]])]
itms -> Pusher e ([Inline], [[Block]]) -> Pusher e [([Inline], [[Block]])]
forall e a. LuaError e => Pusher e a -> Pusher e [a]
pushPandocList Pusher e ([Inline], [[Block]])
forall e. LuaError e => Pusher e ([Inline], [[Block]])
pushDefinitionItem [([Inline], [[Block]])]
itms
ContentListItems [[Block]]
itms -> Pusher e [Block] -> Pusher e [[Block]]
forall e a. LuaError e => Pusher e a -> Pusher e [a]
pushPandocList Pusher e [Block]
forall e. LuaError e => Pusher e [Block]
pushBlocks [[Block]]
itms
peekContent :: LuaError e => Peeker e Content
peekContent :: Peeker e Content
peekContent StackIndex
idx =
([Inline] -> Content
ContentInlines ([Inline] -> Content) -> Peek e [Inline] -> Peek e Content
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> Peeker e [Inline]
forall e. LuaError e => Peeker e [Inline]
peekInlinesFuzzy StackIndex
idx) Peek e Content -> Peek e Content -> Peek e Content
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
([[Inline]] -> Content
ContentLines ([[Inline]] -> Content) -> Peek e [[Inline]] -> Peek e Content
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> Peeker e [Inline] -> Peeker e [[Inline]]
forall a e. LuaError e => Peeker e a -> Peeker e [a]
peekList Peeker e [Inline]
forall e. LuaError e => Peeker e [Inline]
peekInlinesFuzzy StackIndex
idx) Peek e Content -> Peek e Content -> Peek e Content
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
([Block] -> Content
ContentBlocks ([Block] -> Content) -> Peek e [Block] -> Peek e Content
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> Peeker e [Block]
forall e. LuaError e => Peeker e [Block]
peekBlocksFuzzy StackIndex
idx ) Peek e Content -> Peek e Content -> Peek e Content
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
([[Block]] -> Content
ContentListItems ([[Block]] -> Content) -> Peek e [[Block]] -> Peek e Content
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> Peeker e [Block] -> Peeker e [[Block]]
forall a e. LuaError e => Peeker e a -> Peeker e [a]
peekList Peeker e [Block]
forall e. LuaError e => Peeker e [Block]
peekBlocksFuzzy StackIndex
idx) Peek e Content -> Peek e Content -> Peek e Content
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
([([Inline], [[Block]])] -> Content
ContentDefItems ([([Inline], [[Block]])] -> Content)
-> Peek e [([Inline], [[Block]])] -> Peek e Content
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> Peeker e ([Inline], [[Block]]) -> Peeker e [([Inline], [[Block]])]
forall a e. LuaError e => Peeker e a -> Peeker e [a]
peekList Peeker e ([Inline], [[Block]])
forall e. LuaError e => Peeker e ([Inline], [[Block]])
peekDefinitionItem StackIndex
idx)
peekDefinitionItem :: LuaError e => Peeker e ([Inline], [[Block]])
peekDefinitionItem :: Peeker e ([Inline], [[Block]])
peekDefinitionItem = Peeker e [Inline]
-> Peeker e [[Block]] -> Peeker e ([Inline], [[Block]])
forall e a b.
LuaError e =>
Peeker e a -> Peeker e b -> Peeker e (a, b)
peekPair Peeker e [Inline]
forall e. LuaError e => Peeker e [Inline]
peekInlinesFuzzy (Peeker e [[Block]] -> Peeker e ([Inline], [[Block]]))
-> Peeker e [[Block]] -> Peeker e ([Inline], [[Block]])
forall a b. (a -> b) -> a -> b
$ [Peeker e [[Block]]] -> Peeker e [[Block]]
forall e a. LuaError e => [Peeker e a] -> Peeker e a
choice
[ Peeker e [Block] -> Peeker e [[Block]]
forall a e. LuaError e => Peeker e a -> Peeker e [a]
peekList Peeker e [Block]
forall e. LuaError e => Peeker e [Block]
peekBlocksFuzzy
, \StackIndex
idx -> ([Block] -> [[Block]] -> [[Block]]
forall a. a -> [a] -> [a]
:[]) ([Block] -> [[Block]]) -> Peek e [Block] -> Peek e [[Block]]
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> Peeker e [Block]
forall e. LuaError e => Peeker e [Block]
peekBlocksFuzzy StackIndex
idx
]
pushDefinitionItem :: LuaError e => Pusher e ([Inline], [[Block]])
pushDefinitionItem :: Pusher e ([Inline], [[Block]])
pushDefinitionItem = Pusher e [Inline]
-> Pusher e [[Block]] -> Pusher e ([Inline], [[Block]])
forall e a b.
LuaError e =>
Pusher e a -> Pusher e b -> (a, b) -> LuaE e ()
pushPair Pusher e [Inline]
forall e. LuaError e => Pusher e [Inline]
pushInlines
(Pusher e [Block] -> Pusher e [[Block]]
forall e a. LuaError e => Pusher e a -> Pusher e [a]
pushPandocList Pusher e [Block]
forall e. LuaError e => Pusher e [Block]
pushBlocks)