{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
module Text.Pandoc.Lua.Writer.Classic
( runCustom
) where
import Control.Applicative (optional)
import Control.Arrow ((***))
import Data.List (intersperse)
import Data.Maybe (fromMaybe)
import qualified Data.Text as T
import Data.Text (Text, pack)
import HsLua as Lua hiding (Operation (Div))
#if !MIN_VERSION_hslua(2,2,0)
import HsLua.Aeson (peekViaJSON)
#endif
import Text.DocLayout (literal, render)
import Text.DocTemplates (Context)
import Text.Pandoc.Definition
import Text.Pandoc.Lua.Marshal.Attr (pushAttributeList)
import Text.Pandoc.Lua.Orphans ()
import Text.Pandoc.Options
import Text.Pandoc.Templates (renderTemplate)
import Text.Pandoc.Writers.Shared
newtype AttributeList = AttributeList [(Text, Text)]
instance Pushable AttributeList where
push :: forall e. LuaError e => AttributeList -> LuaE e ()
push (AttributeList [(Text, Text)]
kvs) = Pusher e [(Text, Text)]
forall e. LuaError e => Pusher e [(Text, Text)]
pushAttributeList [(Text, Text)]
kvs
attrToMap :: Attr -> AttributeList
attrToMap :: Attr -> AttributeList
attrToMap (Text
id',[Text]
classes,[(Text, Text)]
keyvals) = [(Text, Text)] -> AttributeList
AttributeList
([(Text, Text)] -> AttributeList)
-> [(Text, Text)] -> AttributeList
forall a b. (a -> b) -> a -> b
$ (Text
"id", Text
id')
(Text, Text) -> [(Text, Text)] -> [(Text, Text)]
forall a. a -> [a] -> [a]
: (Text
"class", [Text] -> Text
T.unwords [Text]
classes)
(Text, Text) -> [(Text, Text)] -> [(Text, Text)]
forall a. a -> [a] -> [a]
: [(Text, Text)]
keyvals
newtype Stringify a = Stringify a
instance Pushable (Stringify Format) where
push :: forall e. LuaError e => Stringify Format -> LuaE e ()
push (Stringify (Format Text
f)) = Text -> LuaE e ()
forall a e. (Pushable a, LuaError e) => a -> LuaE e ()
Lua.push (Text -> Text
T.toLower Text
f)
instance Pushable (Stringify [Inline]) where
push :: forall e. LuaError e => Stringify [Inline] -> LuaE e ()
push (Stringify [Inline]
ils) = String -> LuaE e ()
forall a e. (Pushable a, LuaError e) => a -> LuaE e ()
Lua.push (String -> LuaE e ()) -> LuaE e String -> LuaE e ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [Inline] -> LuaE e String
forall e. LuaError e => [Inline] -> LuaE e String
inlineListToCustom [Inline]
ils
instance Pushable (Stringify [Block]) where
push :: forall e. LuaError e => Stringify [Block] -> LuaE e ()
push (Stringify [Block]
blks) = String -> LuaE e ()
forall a e. (Pushable a, LuaError e) => a -> LuaE e ()
Lua.push (String -> LuaE e ()) -> LuaE e String -> LuaE e ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [Block] -> LuaE e String
forall e. LuaError e => [Block] -> LuaE e String
blockListToCustom [Block]
blks
instance Pushable (Stringify MetaValue) where
push :: forall e. LuaError e => Stringify MetaValue -> LuaE e ()
push (Stringify (MetaMap Map Text MetaValue
m)) = Map Text (Stringify MetaValue) -> LuaE e ()
forall a e. (Pushable a, LuaError e) => a -> LuaE e ()
Lua.push ((MetaValue -> Stringify MetaValue)
-> Map Text MetaValue -> Map Text (Stringify MetaValue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MetaValue -> Stringify MetaValue
forall a. a -> Stringify a
Stringify Map Text MetaValue
m)
push (Stringify (MetaList [MetaValue]
xs)) = [Stringify MetaValue] -> LuaE e ()
forall a e. (Pushable a, LuaError e) => a -> LuaE e ()
Lua.push ((MetaValue -> Stringify MetaValue)
-> [MetaValue] -> [Stringify MetaValue]
forall a b. (a -> b) -> [a] -> [b]
map MetaValue -> Stringify MetaValue
forall a. a -> Stringify a
Stringify [MetaValue]
xs)
push (Stringify (MetaBool Bool
x)) = Bool -> LuaE e ()
forall a e. (Pushable a, LuaError e) => a -> LuaE e ()
Lua.push Bool
x
push (Stringify (MetaString Text
s)) = Text -> LuaE e ()
forall a e. (Pushable a, LuaError e) => a -> LuaE e ()
Lua.push Text
s
push (Stringify (MetaInlines [Inline]
ils)) = Stringify [Inline] -> LuaE e ()
forall a e. (Pushable a, LuaError e) => a -> LuaE e ()
Lua.push ([Inline] -> Stringify [Inline]
forall a. a -> Stringify a
Stringify [Inline]
ils)
push (Stringify (MetaBlocks [Block]
bs)) = Stringify [Block] -> LuaE e ()
forall a e. (Pushable a, LuaError e) => a -> LuaE e ()
Lua.push ([Block] -> Stringify [Block]
forall a. a -> Stringify a
Stringify [Block]
bs)
instance Pushable (Stringify Citation) where
push :: forall e. LuaError e => Stringify Citation -> LuaE e ()
push (Stringify Citation
cit) = ([(Name, Citation -> LuaE e ())] -> Citation -> LuaE e ())
-> Citation -> [(Name, Citation -> LuaE e ())] -> LuaE e ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip [(Name, Citation -> LuaE e ())] -> Citation -> LuaE e ()
forall e a.
LuaError e =>
[(Name, a -> LuaE e ())] -> a -> LuaE e ()
pushAsTable Citation
cit
[ (Name
"citationId", Text -> LuaE e ()
forall a e. (Pushable a, LuaError e) => a -> LuaE e ()
push (Text -> LuaE e ()) -> (Citation -> Text) -> Citation -> LuaE e ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Citation -> Text
citationId)
, (Name
"citationPrefix", Stringify [Inline] -> LuaE e ()
forall a e. (Pushable a, LuaError e) => a -> LuaE e ()
push (Stringify [Inline] -> LuaE e ())
-> (Citation -> Stringify [Inline]) -> Citation -> LuaE e ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inline] -> Stringify [Inline]
forall a. a -> Stringify a
Stringify ([Inline] -> Stringify [Inline])
-> (Citation -> [Inline]) -> Citation -> Stringify [Inline]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Citation -> [Inline]
citationPrefix)
, (Name
"citationSuffix", Stringify [Inline] -> LuaE e ()
forall a e. (Pushable a, LuaError e) => a -> LuaE e ()
push (Stringify [Inline] -> LuaE e ())
-> (Citation -> Stringify [Inline]) -> Citation -> LuaE e ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inline] -> Stringify [Inline]
forall a. a -> Stringify a
Stringify ([Inline] -> Stringify [Inline])
-> (Citation -> [Inline]) -> Citation -> Stringify [Inline]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Citation -> [Inline]
citationSuffix)
, (Name
"citationMode", CitationMode -> LuaE e ()
forall a e. (Pushable a, LuaError e) => a -> LuaE e ()
push (CitationMode -> LuaE e ())
-> (Citation -> CitationMode) -> Citation -> LuaE e ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Citation -> CitationMode
citationMode)
, (Name
"citationNoteNum", Int -> LuaE e ()
forall a e. (Pushable a, LuaError e) => a -> LuaE e ()
push (Int -> LuaE e ()) -> (Citation -> Int) -> Citation -> LuaE e ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Citation -> Int
citationNoteNum)
, (Name
"citationHash", Int -> LuaE e ()
forall a e. (Pushable a, LuaError e) => a -> LuaE e ()
push (Int -> LuaE e ()) -> (Citation -> Int) -> Citation -> LuaE e ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Citation -> Int
citationHash)
]
newtype KeyValue a b = KeyValue (a, b)
instance (Pushable a, Pushable b) => Pushable (KeyValue a b) where
push :: forall e. LuaError e => KeyValue a b -> LuaE e ()
push (KeyValue (a
k, b
v)) = do
LuaE e ()
forall e. LuaE e ()
Lua.newtable
a -> LuaE e ()
forall a e. (Pushable a, LuaError e) => a -> LuaE e ()
Lua.push a
k
b -> LuaE e ()
forall a e. (Pushable a, LuaError e) => a -> LuaE e ()
Lua.push b
v
StackIndex -> LuaE e ()
forall e. LuaError e => StackIndex -> LuaE e ()
Lua.rawset (CInt -> StackIndex
Lua.nth CInt
3)
runCustom :: LuaError e
=> WriterOptions
-> Pandoc
-> LuaE e Text
runCustom :: forall e. LuaError e => WriterOptions -> Pandoc -> LuaE e Text
runCustom WriterOptions
opts doc :: Pandoc
doc@(Pandoc Meta
meta [Block]
_) = do
(Text
body, Context Text
context) <- WriterOptions -> Pandoc -> LuaE e (Text, Context Text)
forall e.
LuaError e =>
WriterOptions -> Pandoc -> LuaE e (Text, Context Text)
docToCustom WriterOptions
opts Pandoc
doc
Context Text
metaContext <- WriterOptions
-> ([Block] -> LuaE e (Doc Text))
-> ([Inline] -> LuaE e (Doc Text))
-> Meta
-> LuaE e (Context Text)
forall (m :: * -> *) a.
(Monad m, TemplateTarget a) =>
WriterOptions
-> ([Block] -> m (Doc a))
-> ([Inline] -> m (Doc a))
-> Meta
-> m (Context a)
metaToContext WriterOptions
opts
((String -> Doc Text) -> LuaE e String -> LuaE e (Doc Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal (Text -> Doc Text) -> (String -> Text) -> String -> Doc Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
pack) (LuaE e String -> LuaE e (Doc Text))
-> ([Block] -> LuaE e String) -> [Block] -> LuaE e (Doc Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Block] -> LuaE e String
forall e. LuaError e => [Block] -> LuaE e String
blockListToCustom)
((String -> Doc Text) -> LuaE e String -> LuaE e (Doc Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Text -> Doc Text
forall a. HasChars a => a -> Doc a
literal (Text -> Doc Text) -> (String -> Text) -> String -> Doc Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
pack) (LuaE e String -> LuaE e (Doc Text))
-> ([Inline] -> LuaE e String) -> [Inline] -> LuaE e (Doc Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inline] -> LuaE e String
forall e. LuaError e => [Inline] -> LuaE e String
inlineListToCustom)
Meta
meta
let renderContext :: Context Text
renderContext = Context Text
context Context Text -> Context Text -> Context Text
forall a. Semigroup a => a -> a -> a
<> Context Text
metaContext
Text -> LuaE e Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> LuaE e Text) -> Text -> LuaE e Text
forall a b. (a -> b) -> a -> b
$ case WriterOptions -> Maybe (Template Text)
writerTemplate WriterOptions
opts of
Maybe (Template Text)
Nothing -> Text
body
Just Template Text
tpl -> Maybe Int -> Doc Text -> Text
forall a. HasChars a => Maybe Int -> Doc a -> a
render Maybe Int
forall a. Maybe a
Nothing (Doc Text -> Text) -> Doc Text -> Text
forall a b. (a -> b) -> a -> b
$
Template Text -> Context Text -> Doc Text
forall a b.
(TemplateTarget a, ToContext a b) =>
Template a -> b -> Doc a
renderTemplate Template Text
tpl (Context Text -> Doc Text) -> Context Text -> Doc Text
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Context Text -> Context Text
forall a b. ToContext a b => Text -> b -> Context a -> Context a
setField Text
"body" Text
body Context Text
renderContext
docToCustom :: forall e. LuaError e
=> WriterOptions -> Pandoc -> LuaE e (Text, Context Text)
docToCustom :: forall e.
LuaError e =>
WriterOptions -> Pandoc -> LuaE e (Text, Context Text)
docToCustom WriterOptions
opts (Pandoc (Meta Map Text MetaValue
metamap) [Block]
blocks) = do
String
body <- [Block] -> LuaE e String
forall e. LuaError e => [Block] -> LuaE e String
blockListToCustom [Block]
blocks
Name -> LuaE e Type
forall e. LuaError e => Name -> LuaE e Type
Lua.getglobal Name
"Doc"
String -> LuaE e ()
forall a e. (Pushable a, LuaError e) => a -> LuaE e ()
push String
body
Map Text (Stringify MetaValue) -> LuaE e ()
forall a e. (Pushable a, LuaError e) => a -> LuaE e ()
push ((MetaValue -> Stringify MetaValue)
-> Map Text MetaValue -> Map Text (Stringify MetaValue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MetaValue -> Stringify MetaValue
forall a. a -> Stringify a
Stringify Map Text MetaValue
metamap)
Context Text -> LuaE e ()
forall a e. (Pushable a, LuaError e) => a -> LuaE e ()
push (WriterOptions -> Context Text
writerVariables WriterOptions
opts)
NumArgs -> NumResults -> LuaE e ()
forall e. LuaError e => NumArgs -> NumResults -> LuaE e ()
call NumArgs
3 NumResults
2
Text
rendered <- StackIndex -> LuaE e Text
forall a e. (LuaError e, Peekable a) => StackIndex -> LuaE e a
peek (CInt -> StackIndex
nth CInt
2)
Maybe (Context Text)
context <- Peek e (Maybe (Context Text)) -> LuaE e (Maybe (Context Text))
forall e a. LuaError e => Peek e a -> LuaE e a
forcePeek (Peek e (Maybe (Context Text)) -> LuaE e (Maybe (Context Text)))
-> (Peek e (Context Text) -> Peek e (Maybe (Context Text)))
-> Peek e (Context Text)
-> LuaE e (Maybe (Context Text))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Peek e (Context Text) -> Peek e (Maybe (Context Text))
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Peek e (Context Text) -> LuaE e (Maybe (Context Text)))
-> Peek e (Context Text) -> LuaE e (Maybe (Context Text))
forall a b. (a -> b) -> a -> b
$ Peeker e (Context Text)
forall a e. (FromJSON a, LuaError e) => Peeker e a
peekViaJSON StackIndex
top
(Text, Context Text) -> LuaE e (Text, Context Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Text
rendered, Context Text -> Maybe (Context Text) -> Context Text
forall a. a -> Maybe a -> a
fromMaybe Context Text
forall a. Monoid a => a
mempty Maybe (Context Text)
context)
blockToCustom :: forall e. LuaError e
=> Block
-> LuaE e String
blockToCustom :: forall e. LuaError e => Block -> LuaE e String
blockToCustom Block
Null = String -> LuaE e String
forall (m :: * -> *) a. Monad m => a -> m a
return String
""
blockToCustom (Plain [Inline]
inlines) = Name -> Stringify [Inline] -> LuaE e String
forall a. Invokable a => Name -> a
invoke Name
"Plain" ([Inline] -> Stringify [Inline]
forall a. a -> Stringify a
Stringify [Inline]
inlines)
blockToCustom (Para [Image Attr
attr [Inline]
txt (Text
src,Text
tit)]) =
Name
-> Text
-> Text
-> Stringify [Inline]
-> AttributeList
-> LuaE e String
forall a. Invokable a => Name -> a
invoke Name
"CaptionedImage" Text
src Text
tit ([Inline] -> Stringify [Inline]
forall a. a -> Stringify a
Stringify [Inline]
txt) (Attr -> AttributeList
attrToMap Attr
attr)
blockToCustom (Para [Inline]
inlines) = Name -> Stringify [Inline] -> LuaE e String
forall a. Invokable a => Name -> a
invoke Name
"Para" ([Inline] -> Stringify [Inline]
forall a. a -> Stringify a
Stringify [Inline]
inlines)
blockToCustom (LineBlock [[Inline]]
linesList) =
Name -> [Stringify [Inline]] -> LuaE e String
forall a. Invokable a => Name -> a
invoke Name
"LineBlock" (([Inline] -> Stringify [Inline])
-> [[Inline]] -> [Stringify [Inline]]
forall a b. (a -> b) -> [a] -> [b]
map ([Inline] -> Stringify [Inline]
forall a. a -> Stringify a
Stringify) [[Inline]]
linesList)
blockToCustom (RawBlock Format
format Text
str) =
Name -> Stringify Format -> Text -> LuaE e String
forall a. Invokable a => Name -> a
invoke Name
"RawBlock" (Format -> Stringify Format
forall a. a -> Stringify a
Stringify Format
format) Text
str
blockToCustom Block
HorizontalRule = Name -> LuaE e String
forall a. Invokable a => Name -> a
invoke Name
"HorizontalRule"
blockToCustom (Header Int
level Attr
attr [Inline]
inlines) =
Name -> Int -> Stringify [Inline] -> AttributeList -> LuaE e String
forall a. Invokable a => Name -> a
invoke Name
"Header" Int
level ([Inline] -> Stringify [Inline]
forall a. a -> Stringify a
Stringify [Inline]
inlines) (Attr -> AttributeList
attrToMap Attr
attr)
blockToCustom (CodeBlock Attr
attr Text
str) =
Name -> Text -> AttributeList -> LuaE e String
forall a. Invokable a => Name -> a
invoke Name
"CodeBlock" Text
str (Attr -> AttributeList
attrToMap Attr
attr)
blockToCustom (BlockQuote [Block]
blocks) =
Name -> Stringify [Block] -> LuaE e String
forall a. Invokable a => Name -> a
invoke Name
"BlockQuote" ([Block] -> Stringify [Block]
forall a. a -> Stringify a
Stringify [Block]
blocks)
blockToCustom (Table Attr
_ Caption
blkCapt [ColSpec]
specs TableHead
thead [TableBody]
tbody TableFoot
tfoot) =
let ([Inline]
capt, [Alignment]
aligns, [Double]
widths, [[Block]]
headers, [[[Block]]]
rows) = Caption
-> [ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> ([Inline], [Alignment], [Double], [[Block]], [[[Block]]])
toLegacyTable Caption
blkCapt [ColSpec]
specs TableHead
thead [TableBody]
tbody TableFoot
tfoot
aligns' :: [String]
aligns' = (Alignment -> String) -> [Alignment] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Alignment -> String
forall a. Show a => a -> String
show [Alignment]
aligns
capt' :: Stringify [Inline]
capt' = [Inline] -> Stringify [Inline]
forall a. a -> Stringify a
Stringify [Inline]
capt
headers' :: [Stringify [Block]]
headers' = ([Block] -> Stringify [Block]) -> [[Block]] -> [Stringify [Block]]
forall a b. (a -> b) -> [a] -> [b]
map ([Block] -> Stringify [Block]
forall a. a -> Stringify a
Stringify) [[Block]]
headers
rows' :: [[Stringify [Block]]]
rows' = ([[Block]] -> [Stringify [Block]])
-> [[[Block]]] -> [[Stringify [Block]]]
forall a b. (a -> b) -> [a] -> [b]
map (([Block] -> Stringify [Block]) -> [[Block]] -> [Stringify [Block]]
forall a b. (a -> b) -> [a] -> [b]
map ([Block] -> Stringify [Block]
forall a. a -> Stringify a
Stringify)) [[[Block]]]
rows
in Name
-> Stringify [Inline]
-> [String]
-> [Double]
-> [Stringify [Block]]
-> [[Stringify [Block]]]
-> LuaE e String
forall a. Invokable a => Name -> a
invoke Name
"Table" Stringify [Inline]
capt' [String]
aligns' [Double]
widths [Stringify [Block]]
headers' [[Stringify [Block]]]
rows'
blockToCustom (BulletList [[Block]]
items) =
Name -> [Stringify [Block]] -> LuaE e String
forall a. Invokable a => Name -> a
invoke Name
"BulletList" (([Block] -> Stringify [Block]) -> [[Block]] -> [Stringify [Block]]
forall a b. (a -> b) -> [a] -> [b]
map ([Block] -> Stringify [Block]
forall a. a -> Stringify a
Stringify) [[Block]]
items)
blockToCustom (OrderedList (Int
num,ListNumberStyle
sty,ListNumberDelim
delim) [[Block]]
items) =
Name
-> [Stringify [Block]] -> Int -> String -> String -> LuaE e String
forall a. Invokable a => Name -> a
invoke Name
"OrderedList" (([Block] -> Stringify [Block]) -> [[Block]] -> [Stringify [Block]]
forall a b. (a -> b) -> [a] -> [b]
map ([Block] -> Stringify [Block]
forall a. a -> Stringify a
Stringify) [[Block]]
items) Int
num (ListNumberStyle -> String
forall a. Show a => a -> String
show ListNumberStyle
sty) (ListNumberDelim -> String
forall a. Show a => a -> String
show ListNumberDelim
delim)
blockToCustom (DefinitionList [([Inline], [[Block]])]
items) =
Name
-> [KeyValue (Stringify [Inline]) [Stringify [Block]]]
-> LuaE e String
forall a. Invokable a => Name -> a
invoke Name
"DefinitionList"
((([Inline], [[Block]])
-> KeyValue (Stringify [Inline]) [Stringify [Block]])
-> [([Inline], [[Block]])]
-> [KeyValue (Stringify [Inline]) [Stringify [Block]]]
forall a b. (a -> b) -> [a] -> [b]
map ((Stringify [Inline], [Stringify [Block]])
-> KeyValue (Stringify [Inline]) [Stringify [Block]]
forall a b. (a, b) -> KeyValue a b
KeyValue ((Stringify [Inline], [Stringify [Block]])
-> KeyValue (Stringify [Inline]) [Stringify [Block]])
-> (([Inline], [[Block]])
-> (Stringify [Inline], [Stringify [Block]]))
-> ([Inline], [[Block]])
-> KeyValue (Stringify [Inline]) [Stringify [Block]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Inline] -> Stringify [Inline]
forall a. a -> Stringify a
Stringify ([Inline] -> Stringify [Inline])
-> ([[Block]] -> [Stringify [Block]])
-> ([Inline], [[Block]])
-> (Stringify [Inline], [Stringify [Block]])
forall (a :: * -> * -> *) b c b' c'.
Arrow a =>
a b c -> a b' c' -> a (b, b') (c, c')
*** ([Block] -> Stringify [Block]) -> [[Block]] -> [Stringify [Block]]
forall a b. (a -> b) -> [a] -> [b]
map ([Block] -> Stringify [Block]
forall a. a -> Stringify a
Stringify))) [([Inline], [[Block]])]
items)
blockToCustom (Div Attr
attr [Block]
items) =
Name -> Stringify [Block] -> AttributeList -> LuaE e String
forall a. Invokable a => Name -> a
invoke Name
"Div" ([Block] -> Stringify [Block]
forall a. a -> Stringify a
Stringify [Block]
items) (Attr -> AttributeList
attrToMap Attr
attr)
blockListToCustom :: forall e. LuaError e
=> [Block]
-> LuaE e String
blockListToCustom :: forall e. LuaError e => [Block] -> LuaE e String
blockListToCustom [Block]
xs = do
String
blocksep <- Name -> LuaE e String
forall a. Invokable a => Name -> a
invoke Name
"Blocksep"
[String]
bs <- (Block -> LuaE e String) -> [Block] -> LuaE e [String]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Block -> LuaE e String
forall e. LuaError e => Block -> LuaE e String
blockToCustom [Block]
xs
String -> LuaE e String
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> LuaE e String) -> String -> LuaE e String
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall a. Monoid a => [a] -> a
mconcat ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ String -> [String] -> [String]
forall a. a -> [a] -> [a]
intersperse String
blocksep [String]
bs
inlineListToCustom :: forall e. LuaError e => [Inline] -> LuaE e String
inlineListToCustom :: forall e. LuaError e => [Inline] -> LuaE e String
inlineListToCustom [Inline]
lst = do
[String]
xs <- (Inline -> LuaE e String) -> [Inline] -> LuaE e [String]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (forall e. LuaError e => Inline -> LuaE e String
inlineToCustom @e) [Inline]
lst
String -> LuaE e String
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> LuaE e String) -> String -> LuaE e String
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall a. Monoid a => [a] -> a
mconcat [String]
xs
inlineToCustom :: forall e. LuaError e => Inline -> LuaE e String
inlineToCustom :: forall e. LuaError e => Inline -> LuaE e String
inlineToCustom (Str Text
str) = Name -> Text -> LuaE e String
forall a. Invokable a => Name -> a
invoke Name
"Str" Text
str
inlineToCustom Inline
Space = Name -> LuaE e String
forall a. Invokable a => Name -> a
invoke Name
"Space"
inlineToCustom Inline
SoftBreak = Name -> LuaE e String
forall a. Invokable a => Name -> a
invoke Name
"SoftBreak"
inlineToCustom (Emph [Inline]
lst) = Name -> Stringify [Inline] -> LuaE e String
forall a. Invokable a => Name -> a
invoke Name
"Emph" ([Inline] -> Stringify [Inline]
forall a. a -> Stringify a
Stringify [Inline]
lst)
inlineToCustom (Underline [Inline]
lst) = Name -> Stringify [Inline] -> LuaE e String
forall a. Invokable a => Name -> a
invoke Name
"Underline" ([Inline] -> Stringify [Inline]
forall a. a -> Stringify a
Stringify [Inline]
lst)
inlineToCustom (Strong [Inline]
lst) = Name -> Stringify [Inline] -> LuaE e String
forall a. Invokable a => Name -> a
invoke Name
"Strong" ([Inline] -> Stringify [Inline]
forall a. a -> Stringify a
Stringify [Inline]
lst)
inlineToCustom (Strikeout [Inline]
lst) = Name -> Stringify [Inline] -> LuaE e String
forall a. Invokable a => Name -> a
invoke Name
"Strikeout" ([Inline] -> Stringify [Inline]
forall a. a -> Stringify a
Stringify [Inline]
lst)
inlineToCustom (Superscript [Inline]
lst) = Name -> Stringify [Inline] -> LuaE e String
forall a. Invokable a => Name -> a
invoke Name
"Superscript" ([Inline] -> Stringify [Inline]
forall a. a -> Stringify a
Stringify [Inline]
lst)
inlineToCustom (Subscript [Inline]
lst) = Name -> Stringify [Inline] -> LuaE e String
forall a. Invokable a => Name -> a
invoke Name
"Subscript" ([Inline] -> Stringify [Inline]
forall a. a -> Stringify a
Stringify [Inline]
lst)
inlineToCustom (SmallCaps [Inline]
lst) = Name -> Stringify [Inline] -> LuaE e String
forall a. Invokable a => Name -> a
invoke Name
"SmallCaps" ([Inline] -> Stringify [Inline]
forall a. a -> Stringify a
Stringify [Inline]
lst)
inlineToCustom (Quoted QuoteType
SingleQuote [Inline]
lst) =
Name -> Stringify [Inline] -> LuaE e String
forall a. Invokable a => Name -> a
invoke Name
"SingleQuoted" ([Inline] -> Stringify [Inline]
forall a. a -> Stringify a
Stringify [Inline]
lst)
inlineToCustom (Quoted QuoteType
DoubleQuote [Inline]
lst) =
Name -> Stringify [Inline] -> LuaE e String
forall a. Invokable a => Name -> a
invoke Name
"DoubleQuoted" ([Inline] -> Stringify [Inline]
forall a. a -> Stringify a
Stringify [Inline]
lst)
inlineToCustom (Cite [Citation]
cs [Inline]
lst) =
Name -> Stringify [Inline] -> [Stringify Citation] -> LuaE e String
forall a. Invokable a => Name -> a
invoke Name
"Cite" ([Inline] -> Stringify [Inline]
forall a. a -> Stringify a
Stringify [Inline]
lst) ((Citation -> Stringify Citation)
-> [Citation] -> [Stringify Citation]
forall a b. (a -> b) -> [a] -> [b]
map (Citation -> Stringify Citation
forall a. a -> Stringify a
Stringify) [Citation]
cs)
inlineToCustom (Code Attr
attr Text
str) =
Name -> Text -> AttributeList -> LuaE e String
forall a. Invokable a => Name -> a
invoke Name
"Code" Text
str (Attr -> AttributeList
attrToMap Attr
attr)
inlineToCustom (Math MathType
DisplayMath Text
str) =
Name -> Text -> LuaE e String
forall a. Invokable a => Name -> a
invoke Name
"DisplayMath" Text
str
inlineToCustom (Math MathType
InlineMath Text
str) =
Name -> Text -> LuaE e String
forall a. Invokable a => Name -> a
invoke Name
"InlineMath" Text
str
inlineToCustom (RawInline Format
format Text
str) =
Name -> Stringify Format -> Text -> LuaE e String
forall a. Invokable a => Name -> a
invoke Name
"RawInline" (Format -> Stringify Format
forall a. a -> Stringify a
Stringify Format
format) Text
str
inlineToCustom Inline
LineBreak = Name -> LuaE e String
forall a. Invokable a => Name -> a
invoke Name
"LineBreak"
inlineToCustom (Link Attr
attr [Inline]
txt (Text
src,Text
tit)) =
Name
-> Stringify [Inline]
-> Text
-> Text
-> AttributeList
-> LuaE e String
forall a. Invokable a => Name -> a
invoke Name
"Link" ([Inline] -> Stringify [Inline]
forall a. a -> Stringify a
Stringify [Inline]
txt) Text
src Text
tit (Attr -> AttributeList
attrToMap Attr
attr)
inlineToCustom (Image Attr
attr [Inline]
alt (Text
src,Text
tit)) =
Name
-> Stringify [Inline]
-> Text
-> Text
-> AttributeList
-> LuaE e String
forall a. Invokable a => Name -> a
invoke Name
"Image" ([Inline] -> Stringify [Inline]
forall a. a -> Stringify a
Stringify [Inline]
alt) Text
src Text
tit (Attr -> AttributeList
attrToMap Attr
attr)
inlineToCustom (Note [Block]
contents) = Name -> Stringify [Block] -> LuaE e String
forall a. Invokable a => Name -> a
invoke Name
"Note" ([Block] -> Stringify [Block]
forall a. a -> Stringify a
Stringify [Block]
contents)
inlineToCustom (Span Attr
attr [Inline]
items) =
Name -> Stringify [Inline] -> AttributeList -> LuaE e String
forall a. Invokable a => Name -> a
invoke Name
"Span" ([Inline] -> Stringify [Inline]
forall a. a -> Stringify a
Stringify [Inline]
items) (Attr -> AttributeList
attrToMap Attr
attr)