{-# LANGUAGE RecordWildCards #-}
module Heist.Extra.Splices.Pandoc.Render (
renderPandocWith,
rpBlock,
rpInline,
rpBlock',
rpInline',
) where
import Data.Map.Strict qualified as Map
import Data.Map.Syntax ((##))
import Data.Text qualified as T
import Heist qualified as H
import Heist.Extra (runCustomNode)
import Heist.Extra.Splices.Pandoc.Attr (concatAttr, rpAttr)
import Heist.Extra.Splices.Pandoc.Ctx (
RenderCtx (..),
rewriteClass,
)
import Heist.Extra.Splices.Pandoc.TaskList qualified as TaskList
import Heist.Interpreted qualified as HI
import Text.Pandoc.Builder qualified as B
import Text.Pandoc.Definition (Pandoc (..))
import Text.Pandoc.Walk as W
import Text.XmlHtml qualified as X
renderPandocWith :: RenderCtx -> Pandoc -> HI.Splice Identity
renderPandocWith :: RenderCtx -> Pandoc -> Splice Identity
renderPandocWith RenderCtx
ctx (Pandoc Meta
_meta [Block]
blocks) =
(Block -> Splice Identity) -> [Block] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
foldMapM (RenderCtx -> Block -> Splice Identity
rpBlock RenderCtx
ctx) [Block]
blocks
rpBlock :: RenderCtx -> B.Block -> HI.Splice Identity
rpBlock :: RenderCtx -> Block -> Splice Identity
rpBlock ctx :: RenderCtx
ctx@RenderCtx {Maybe Node
Map Text Text
Inline -> Maybe (Splice Identity)
Inline -> Attr
Block -> Maybe (Splice Identity)
Block -> Attr
rootNode :: Maybe Node
bAttr :: Block -> Attr
iAttr :: Inline -> Attr
classMap :: Map Text Text
blockSplice :: Block -> Maybe (Splice Identity)
inlineSplice :: Inline -> Maybe (Splice Identity)
inlineSplice :: RenderCtx -> Inline -> Maybe (Splice Identity)
blockSplice :: RenderCtx -> Block -> Maybe (Splice Identity)
classMap :: RenderCtx -> Map Text Text
iAttr :: RenderCtx -> Inline -> Attr
bAttr :: RenderCtx -> Block -> Attr
rootNode :: RenderCtx -> Maybe Node
..} Block
b = do
Splice Identity -> Maybe (Splice Identity) -> Splice Identity
forall a. a -> Maybe a -> a
fromMaybe (RenderCtx -> Block -> Splice Identity
rpBlock' RenderCtx
ctx Block
b) (Maybe (Splice Identity) -> Splice Identity)
-> Maybe (Splice Identity) -> Splice Identity
forall a b. (a -> b) -> a -> b
$ Block -> Maybe (Splice Identity)
blockSplice Block
b
withTplTag :: RenderCtx -> Text -> H.Splices (HI.Splice Identity) -> HI.Splice Identity -> HI.Splice Identity
withTplTag :: RenderCtx
-> Text
-> Splices (Splice Identity)
-> Splice Identity
-> Splice Identity
withTplTag RenderCtx {Maybe Node
Map Text Text
Inline -> Maybe (Splice Identity)
Inline -> Attr
Block -> Maybe (Splice Identity)
Block -> Attr
inlineSplice :: RenderCtx -> Inline -> Maybe (Splice Identity)
blockSplice :: RenderCtx -> Block -> Maybe (Splice Identity)
classMap :: RenderCtx -> Map Text Text
iAttr :: RenderCtx -> Inline -> Attr
bAttr :: RenderCtx -> Block -> Attr
rootNode :: RenderCtx -> Maybe Node
rootNode :: Maybe Node
bAttr :: Block -> Attr
iAttr :: Inline -> Attr
classMap :: Map Text Text
blockSplice :: Block -> Maybe (Splice Identity)
inlineSplice :: Inline -> Maybe (Splice Identity)
..} Text
name Splices (Splice Identity)
splices Splice Identity
default_ =
case Text -> Node -> Maybe Node
X.childElementTag Text
name (Node -> Maybe Node) -> Maybe Node -> Maybe Node
forall (m :: Type -> Type) a b. Monad m => (a -> m b) -> m a -> m b
=<< Maybe Node
rootNode of
Maybe Node
Nothing -> Splice Identity
default_
Just Node
node -> Node -> Splices (Splice Identity) -> Splice Identity
runCustomNode Node
node Splices (Splice Identity)
splices
rpBlock' :: RenderCtx -> B.Block -> HI.Splice Identity
rpBlock' :: RenderCtx -> Block -> Splice Identity
rpBlock' ctx :: RenderCtx
ctx@RenderCtx {Maybe Node
Map Text Text
Inline -> Maybe (Splice Identity)
Inline -> Attr
Block -> Maybe (Splice Identity)
Block -> Attr
inlineSplice :: RenderCtx -> Inline -> Maybe (Splice Identity)
blockSplice :: RenderCtx -> Block -> Maybe (Splice Identity)
classMap :: RenderCtx -> Map Text Text
iAttr :: RenderCtx -> Inline -> Attr
bAttr :: RenderCtx -> Block -> Attr
rootNode :: RenderCtx -> Maybe Node
rootNode :: Maybe Node
bAttr :: Block -> Attr
iAttr :: Inline -> Attr
classMap :: Map Text Text
blockSplice :: Block -> Maybe (Splice Identity)
inlineSplice :: Inline -> Maybe (Splice Identity)
..} Block
b = case Block
b of
B.Plain [Inline]
is ->
RenderCtx -> [Inline] -> Splice Identity
rpInlineWithTasks RenderCtx
ctx ([Inline] -> [Inline] -> [Inline]
convertRawInline [] [Inline]
is)
B.Para [Inline]
is -> do
let innerSplice :: Splice Identity
innerSplice = RenderCtx -> [Inline] -> Splice Identity
rpInlineWithTasks RenderCtx
ctx ([Inline] -> [Inline] -> [Inline]
convertRawInline [] [Inline]
is)
RenderCtx
-> Text
-> Splices (Splice Identity)
-> Splice Identity
-> Splice Identity
withTplTag RenderCtx
ctx Text
"Para" (Text
"inlines" Text -> Splice Identity -> Splices (Splice Identity)
forall k v. k -> v -> MapSyntax k v
## Splice Identity
innerSplice) (Splice Identity -> Splice Identity)
-> Splice Identity -> Splice Identity
forall a b. (a -> b) -> a -> b
$
OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> ([Node] -> Node) -> [Node] -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
"p" [(Text, Text)]
forall a. Monoid a => a
mempty ([Node] -> [Node]) -> Splice Identity -> Splice Identity
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Splice Identity
innerSplice
B.LineBlock [[Inline]]
iss ->
(([Inline] -> Splice Identity) -> [[Inline]] -> Splice Identity)
-> [[Inline]] -> ([Inline] -> Splice Identity) -> Splice Identity
forall a b c. (a -> b -> c) -> b -> a -> c
flip ([Inline] -> Splice Identity) -> [[Inline]] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
foldMapM [[Inline]]
iss (([Inline] -> Splice Identity) -> Splice Identity)
-> ([Inline] -> Splice Identity) -> Splice Identity
forall a b. (a -> b) -> a -> b
$ \[Inline]
is ->
(Inline -> Splice Identity) -> [Inline] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
foldMapM (RenderCtx -> Inline -> Splice Identity
rpInline RenderCtx
ctx) ([Inline] -> [Inline] -> [Inline]
convertRawInline [] [Inline]
is) Splice Identity -> Splice Identity -> Splice Identity
forall a b.
HeistT Identity Identity a
-> HeistT Identity Identity b -> HeistT Identity Identity b
forall (m :: Type -> Type) a b. Monad m => m a -> m b -> m b
>> [Node] -> Splice Identity
forall a. a -> HeistT Identity Identity a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure [Text -> Node
X.TextNode Text
"\n"]
B.CodeBlock (Text
id', [Text] -> [Text]
forall {a}. (IsString a, Semigroup a) => [a] -> [a]
mkLangClass -> [Text]
classes, [(Text, Text)]
attrs) Text
s -> do
[Node] -> Splice Identity
forall a. a -> HeistT Identity Identity a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure ([Node] -> Splice Identity) -> [Node] -> Splice Identity
forall a b. (a -> b) -> a -> b
$
OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> ([Node] -> Node) -> [Node] -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
"div" (Attr -> [(Text, Text)]
rpAttr (Attr -> [(Text, Text)]) -> Attr -> [(Text, Text)]
forall a b. (a -> b) -> a -> b
$ Block -> Attr
bAttr Block
b) ([Node] -> [Node]) -> [Node] -> [Node]
forall a b. (a -> b) -> a -> b
$
OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> ([Node] -> Node) -> [Node] -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
"pre" [(Text, Text)]
forall a. Monoid a => a
mempty ([Node] -> [Node]) -> [Node] -> [Node]
forall a b. (a -> b) -> a -> b
$
OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> ([Node] -> Node) -> [Node] -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
"code" (Attr -> [(Text, Text)]
rpAttr (Text
id', [Text]
classes, [(Text, Text)]
attrs)) ([Node] -> [Node]) -> [Node] -> [Node]
forall a b. (a -> b) -> a -> b
$
OneItem [Node] -> [Node]
forall x. One x => OneItem x -> x
one (OneItem [Node] -> [Node]) -> OneItem [Node] -> [Node]
forall a b. (a -> b) -> a -> b
$
Text -> Node
X.TextNode Text
s
B.RawBlock (B.Format Text
fmt) Text
s -> do
[Node] -> Splice Identity
forall a. a -> HeistT Identity Identity a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure ([Node] -> Splice Identity) -> [Node] -> Splice Identity
forall a b. (a -> b) -> a -> b
$ case Text
fmt of
Text
"html" ->
Text -> Text -> [Node]
rawNode Text
"div" Text
s
Text
_ ->
OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> ([Node] -> Node) -> [Node] -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
"pre" [(Text
"class", Text
"pandoc-raw-" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
forall b a. (Show a, IsString b) => a -> b
show Text
fmt)] ([Node] -> [Node]) -> [Node] -> [Node]
forall a b. (a -> b) -> a -> b
$ OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> (Text -> Node) -> Text -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Node
X.TextNode (Text -> [Node]) -> Text -> [Node]
forall a b. (a -> b) -> a -> b
$ Text
s
B.BlockQuote [Block]
bs ->
RenderCtx
-> Text
-> Splices (Splice Identity)
-> Splice Identity
-> Splice Identity
withTplTag RenderCtx
ctx Text
"BlockQuote" (Text
"blocks" Text -> Splice Identity -> Splices (Splice Identity)
forall k v. k -> v -> MapSyntax k v
## RenderCtx -> Block -> Splice Identity
rpBlock RenderCtx
ctx (Block -> Splice Identity) -> [Block] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
`foldMapM` [Block]
bs) (Splice Identity -> Splice Identity)
-> Splice Identity -> Splice Identity
forall a b. (a -> b) -> a -> b
$
OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> ([Node] -> Node) -> [Node] -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
"blockquote" [(Text, Text)]
forall a. Monoid a => a
mempty ([Node] -> [Node]) -> Splice Identity -> Splice Identity
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (Block -> Splice Identity) -> [Block] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
foldMapM (RenderCtx -> Block -> Splice Identity
rpBlock RenderCtx
ctx) [Block]
bs
B.OrderedList ListAttributes
_ [[Block]]
bss ->
RenderCtx
-> Text
-> Splices (Splice Identity)
-> Splice Identity
-> Splice Identity
withTplTag RenderCtx
ctx Text
"OrderedList" (Text -> [[Block]] -> Splices (Splice Identity)
pandocListSplices Text
"OrderedList" [[Block]]
bss) (Splice Identity -> Splice Identity)
-> Splice Identity -> Splice Identity
forall a b. (a -> b) -> a -> b
$ do
([Node] -> [Node]) -> Splice Identity -> Splice Identity
forall a b.
(a -> b)
-> HeistT Identity Identity a -> HeistT Identity Identity b
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap (OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> ([Node] -> Node) -> [Node] -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
"ol" (Attr -> [(Text, Text)]
rpAttr (Attr -> [(Text, Text)]) -> Attr -> [(Text, Text)]
forall a b. (a -> b) -> a -> b
$ Block -> Attr
bAttr Block
b)) (Splice Identity -> Splice Identity)
-> Splice Identity -> Splice Identity
forall a b. (a -> b) -> a -> b
$
(([Block] -> Splice Identity) -> [[Block]] -> Splice Identity)
-> [[Block]] -> ([Block] -> Splice Identity) -> Splice Identity
forall a b c. (a -> b -> c) -> b -> a -> c
flip ([Block] -> Splice Identity) -> [[Block]] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
foldMapM [[Block]]
bss (([Block] -> Splice Identity) -> Splice Identity)
-> ([Block] -> Splice Identity) -> Splice Identity
forall a b. (a -> b) -> a -> b
$
([Node] -> [Node]) -> Splice Identity -> Splice Identity
forall a b.
(a -> b)
-> HeistT Identity Identity a -> HeistT Identity Identity b
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap (OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> ([Node] -> Node) -> [Node] -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
"li" [(Text, Text)]
forall a. Monoid a => a
mempty) (Splice Identity -> Splice Identity)
-> ([Block] -> Splice Identity) -> [Block] -> Splice Identity
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Block -> Splice Identity) -> [Block] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
foldMapM (RenderCtx -> Block -> Splice Identity
rpBlock RenderCtx
ctx)
B.BulletList [[Block]]
bss ->
RenderCtx
-> Text
-> Splices (Splice Identity)
-> Splice Identity
-> Splice Identity
withTplTag RenderCtx
ctx Text
"BulletList" (Text -> [[Block]] -> Splices (Splice Identity)
pandocListSplices Text
"BulletList" [[Block]]
bss) (Splice Identity -> Splice Identity)
-> Splice Identity -> Splice Identity
forall a b. (a -> b) -> a -> b
$ do
([Node] -> [Node]) -> Splice Identity -> Splice Identity
forall a b.
(a -> b)
-> HeistT Identity Identity a -> HeistT Identity Identity b
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap (OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> ([Node] -> Node) -> [Node] -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
"ul" (Attr -> [(Text, Text)]
rpAttr (Attr -> [(Text, Text)]) -> Attr -> [(Text, Text)]
forall a b. (a -> b) -> a -> b
$ Block -> Attr
bAttr Block
b)) (Splice Identity -> Splice Identity)
-> Splice Identity -> Splice Identity
forall a b. (a -> b) -> a -> b
$
(([Block] -> Splice Identity) -> [[Block]] -> Splice Identity)
-> [[Block]] -> ([Block] -> Splice Identity) -> Splice Identity
forall a b c. (a -> b -> c) -> b -> a -> c
flip ([Block] -> Splice Identity) -> [[Block]] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
foldMapM [[Block]]
bss (([Block] -> Splice Identity) -> Splice Identity)
-> ([Block] -> Splice Identity) -> Splice Identity
forall a b. (a -> b) -> a -> b
$
([Node] -> [Node]) -> Splice Identity -> Splice Identity
forall a b.
(a -> b)
-> HeistT Identity Identity a -> HeistT Identity Identity b
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap (OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> ([Node] -> Node) -> [Node] -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
"li" [(Text, Text)]
forall a. Monoid a => a
mempty) (Splice Identity -> Splice Identity)
-> ([Block] -> Splice Identity) -> [Block] -> Splice Identity
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Block -> Splice Identity) -> [Block] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
foldMapM (RenderCtx -> Block -> Splice Identity
rpBlock RenderCtx
ctx)
B.DefinitionList [([Inline], [[Block]])]
defs ->
RenderCtx
-> Text
-> Splices (Splice Identity)
-> Splice Identity
-> Splice Identity
withTplTag RenderCtx
ctx Text
"DefinitionList" ([([Inline], [[Block]])] -> Splices (Splice Identity)
definitionListSplices [([Inline], [[Block]])]
defs) (Splice Identity -> Splice Identity)
-> Splice Identity -> Splice Identity
forall a b. (a -> b) -> a -> b
$
([Node] -> [Node]) -> Splice Identity -> Splice Identity
forall a b.
(a -> b)
-> HeistT Identity Identity a -> HeistT Identity Identity b
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap (OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> ([Node] -> Node) -> [Node] -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
"dl" [(Text, Text)]
forall a. Monoid a => a
mempty) (Splice Identity -> Splice Identity)
-> Splice Identity -> Splice Identity
forall a b. (a -> b) -> a -> b
$
((([Inline], [[Block]]) -> Splice Identity)
-> [([Inline], [[Block]])] -> Splice Identity)
-> [([Inline], [[Block]])]
-> (([Inline], [[Block]]) -> Splice Identity)
-> Splice Identity
forall a b c. (a -> b -> c) -> b -> a -> c
flip (([Inline], [[Block]]) -> Splice Identity)
-> [([Inline], [[Block]])] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
foldMapM [([Inline], [[Block]])]
defs ((([Inline], [[Block]]) -> Splice Identity) -> Splice Identity)
-> (([Inline], [[Block]]) -> Splice Identity) -> Splice Identity
forall a b. (a -> b) -> a -> b
$ \([Inline]
term, [[Block]]
descList) -> do
[Node]
a <- (Inline -> Splice Identity) -> [Inline] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
foldMapM (RenderCtx -> Inline -> Splice Identity
rpInline RenderCtx
ctx) ([Inline] -> [Inline] -> [Inline]
convertRawInline [] [Inline]
term)
[Node]
as <-
(([Block] -> Splice Identity) -> [[Block]] -> Splice Identity)
-> [[Block]] -> ([Block] -> Splice Identity) -> Splice Identity
forall a b c. (a -> b -> c) -> b -> a -> c
flip ([Block] -> Splice Identity) -> [[Block]] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
foldMapM [[Block]]
descList (([Block] -> Splice Identity) -> Splice Identity)
-> ([Block] -> Splice Identity) -> Splice Identity
forall a b. (a -> b) -> a -> b
$
([Node] -> [Node]) -> Splice Identity -> Splice Identity
forall a b.
(a -> b)
-> HeistT Identity Identity a -> HeistT Identity Identity b
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap (OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> ([Node] -> Node) -> [Node] -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
"dd" [(Text, Text)]
forall a. Monoid a => a
mempty) (Splice Identity -> Splice Identity)
-> ([Block] -> Splice Identity) -> [Block] -> Splice Identity
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Block -> Splice Identity) -> [Block] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
foldMapM (RenderCtx -> Block -> Splice Identity
rpBlock RenderCtx
ctx)
[Node] -> Splice Identity
forall a. a -> HeistT Identity Identity a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure ([Node] -> Splice Identity) -> [Node] -> Splice Identity
forall a b. (a -> b) -> a -> b
$ [Node]
a [Node] -> [Node] -> [Node]
forall a. Semigroup a => a -> a -> a
<> [Node]
as
B.Header Int
level attr :: Attr
attr@(Text
headerId, [Text]
_, [(Text, Text)]
_) [Inline]
is -> do
let innerSplice :: Splice Identity
innerSplice = (Inline -> Splice Identity) -> [Inline] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
foldMapM (RenderCtx -> Inline -> Splice Identity
rpInline RenderCtx
ctx) ([Inline] -> [Inline] -> [Inline]
convertRawInline [] [Inline]
is)
RenderCtx
-> Text
-> Splices (Splice Identity)
-> Splice Identity
-> Splice Identity
withTplTag RenderCtx
ctx (Text
"Header:" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text
forall b a. (Show a, IsString b) => a -> b
show Int
level) (Text -> Splice Identity -> Splices (Splice Identity)
forall {k} {m :: Type -> Type} {n :: Type -> Type}.
(IsString k, Monad m) =>
Text -> HeistT n m [Node] -> MapSyntaxM k (HeistT n m [Node]) ()
headerSplices Text
headerId Splice Identity
innerSplice) (Splice Identity -> Splice Identity)
-> Splice Identity -> Splice Identity
forall a b. (a -> b) -> a -> b
$
OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> ([Node] -> Node) -> [Node] -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> [Node] -> Node
X.Element (HasCallStack => Int -> Text
Int -> Text
headerTag Int
level) (Attr -> [(Text, Text)]
rpAttr (Attr -> [(Text, Text)]) -> Attr -> [(Text, Text)]
forall a b. (a -> b) -> a -> b
$ Attr -> Attr -> Attr
concatAttr Attr
attr (Attr -> Attr) -> Attr -> Attr
forall a b. (a -> b) -> a -> b
$ Block -> Attr
bAttr Block
b)
([Node] -> [Node]) -> Splice Identity -> Splice Identity
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Splice Identity
innerSplice
Block
B.HorizontalRule ->
RenderCtx
-> Text
-> Splices (Splice Identity)
-> Splice Identity
-> Splice Identity
withTplTag RenderCtx
ctx Text
"HorizontalRule" Splices (Splice Identity)
forall a. Monoid a => a
mempty ([Node] -> Splice Identity
forall a. a -> HeistT Identity Identity a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure ([Node] -> Splice Identity) -> [Node] -> Splice Identity
forall a b. (a -> b) -> a -> b
$ OneItem [Node] -> [Node]
forall x. One x => OneItem x -> x
one (OneItem [Node] -> [Node]) -> OneItem [Node] -> [Node]
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
"hr" [(Text, Text)]
forall a. Monoid a => a
mempty [Node]
forall a. Monoid a => a
mempty)
B.Table Attr
attr Caption
_captions [ColSpec]
_colSpec (B.TableHead Attr
_ [Row]
hrows) [TableBody]
tbodys TableFoot
_tfoot -> do
let borderStyle :: Text
borderStyle = Text
"border-gray-300"
rowStyle :: [(Text, Text)]
rowStyle = [(Text
"class", Text
"border-b-2 border-t-2 " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
borderStyle)]
cellStyle :: [(Text, Text)]
cellStyle = [(Text
"class", Text
"py-2 px-2 align-top border-r-2 border-l-2 " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
borderStyle)]
tableAttr :: Attr
tableAttr = (Text
"", [Text
"mb-3"], [(Text, Text)]
forall a. Monoid a => a
mempty)
([Node] -> [Node]) -> Splice Identity -> Splice Identity
forall a b.
(a -> b)
-> HeistT Identity Identity a -> HeistT Identity Identity b
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap (OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> ([Node] -> Node) -> [Node] -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
"table" (Attr -> [(Text, Text)]
rpAttr (Attr -> [(Text, Text)]) -> Attr -> [(Text, Text)]
forall a b. (a -> b) -> a -> b
$ Attr -> Attr -> Attr
concatAttr Attr
attr Attr
tableAttr)) (Splice Identity -> Splice Identity)
-> Splice Identity -> Splice Identity
forall a b. (a -> b) -> a -> b
$ do
[Node]
thead <- ([Node] -> [Node]) -> Splice Identity -> Splice Identity
forall a b.
(a -> b)
-> HeistT Identity Identity a -> HeistT Identity Identity b
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap (OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> ([Node] -> Node) -> [Node] -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
"thead" [(Text, Text)]
forall a. Monoid a => a
mempty) (Splice Identity -> Splice Identity)
-> Splice Identity -> Splice Identity
forall a b. (a -> b) -> a -> b
$
((Row -> Splice Identity) -> [Row] -> Splice Identity)
-> [Row] -> (Row -> Splice Identity) -> Splice Identity
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Row -> Splice Identity) -> [Row] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
foldMapM [Row]
hrows ((Row -> Splice Identity) -> Splice Identity)
-> (Row -> Splice Identity) -> Splice Identity
forall a b. (a -> b) -> a -> b
$ \(B.Row Attr
_ [Cell]
cells) ->
([Node] -> [Node]) -> Splice Identity -> Splice Identity
forall a b.
(a -> b)
-> HeistT Identity Identity a -> HeistT Identity Identity b
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap (OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> ([Node] -> Node) -> [Node] -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
"tr" [(Text, Text)]
rowStyle) (Splice Identity -> Splice Identity)
-> Splice Identity -> Splice Identity
forall a b. (a -> b) -> a -> b
$
((Cell -> Splice Identity) -> [Cell] -> Splice Identity)
-> [Cell] -> (Cell -> Splice Identity) -> Splice Identity
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Cell -> Splice Identity) -> [Cell] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
foldMapM [Cell]
cells ((Cell -> Splice Identity) -> Splice Identity)
-> (Cell -> Splice Identity) -> Splice Identity
forall a b. (a -> b) -> a -> b
$ \(B.Cell Attr
_ Alignment
_ RowSpan
_ ColSpan
_ [Block]
blks) ->
OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> ([Node] -> Node) -> [Node] -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
"th" [(Text, Text)]
cellStyle ([Node] -> [Node]) -> Splice Identity -> Splice Identity
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (Block -> Splice Identity) -> [Block] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
foldMapM (RenderCtx -> Block -> Splice Identity
rpBlock RenderCtx
ctx) [Block]
blks
[Node]
tbody <- ([Node] -> [Node]) -> Splice Identity -> Splice Identity
forall a b.
(a -> b)
-> HeistT Identity Identity a -> HeistT Identity Identity b
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap (OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> ([Node] -> Node) -> [Node] -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
"tbody" [(Text, Text)]
forall a. Monoid a => a
mempty) (Splice Identity -> Splice Identity)
-> Splice Identity -> Splice Identity
forall a b. (a -> b) -> a -> b
$
((TableBody -> Splice Identity) -> [TableBody] -> Splice Identity)
-> [TableBody] -> (TableBody -> Splice Identity) -> Splice Identity
forall a b c. (a -> b -> c) -> b -> a -> c
flip (TableBody -> Splice Identity) -> [TableBody] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
foldMapM [TableBody]
tbodys ((TableBody -> Splice Identity) -> Splice Identity)
-> (TableBody -> Splice Identity) -> Splice Identity
forall a b. (a -> b) -> a -> b
$ \(B.TableBody Attr
_ RowHeadColumns
_ [Row]
_ [Row]
rows) ->
((Row -> Splice Identity) -> [Row] -> Splice Identity)
-> [Row] -> (Row -> Splice Identity) -> Splice Identity
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Row -> Splice Identity) -> [Row] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
foldMapM [Row]
rows ((Row -> Splice Identity) -> Splice Identity)
-> (Row -> Splice Identity) -> Splice Identity
forall a b. (a -> b) -> a -> b
$ \(B.Row Attr
_ [Cell]
cells) ->
([Node] -> [Node]) -> Splice Identity -> Splice Identity
forall a b.
(a -> b)
-> HeistT Identity Identity a -> HeistT Identity Identity b
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap (OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> ([Node] -> Node) -> [Node] -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
"tr" [(Text, Text)]
rowStyle) (Splice Identity -> Splice Identity)
-> Splice Identity -> Splice Identity
forall a b. (a -> b) -> a -> b
$
((Cell -> Splice Identity) -> [Cell] -> Splice Identity)
-> [Cell] -> (Cell -> Splice Identity) -> Splice Identity
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Cell -> Splice Identity) -> [Cell] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
foldMapM [Cell]
cells ((Cell -> Splice Identity) -> Splice Identity)
-> (Cell -> Splice Identity) -> Splice Identity
forall a b. (a -> b) -> a -> b
$ \(B.Cell Attr
_ Alignment
_ RowSpan
_ ColSpan
_ [Block]
blks) ->
OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> ([Node] -> Node) -> [Node] -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
"td" [(Text, Text)]
cellStyle ([Node] -> [Node]) -> Splice Identity -> Splice Identity
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (Block -> Splice Identity) -> [Block] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
foldMapM (RenderCtx -> Block -> Splice Identity
rpBlock RenderCtx
ctx) [Block]
blks
[Node] -> Splice Identity
forall a. a -> HeistT Identity Identity a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure ([Node] -> Splice Identity) -> [Node] -> Splice Identity
forall a b. (a -> b) -> a -> b
$ [Node]
thead [Node] -> [Node] -> [Node]
forall a. Semigroup a => a -> a -> a
<> [Node]
tbody
B.Div Attr
attr [Block]
bs ->
OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> ([Node] -> Node) -> [Node] -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> [Node] -> Node
X.Element (Text -> Attr -> Text
forall {k} {b} {a} {b}.
(Ord k, IsString k) =>
b -> (a, b, [(k, b)]) -> b
getTag Text
"div" Attr
attr) (Attr -> [(Text, Text)]
rpAttr (Attr -> [(Text, Text)]) -> Attr -> [(Text, Text)]
forall a b. (a -> b) -> a -> b
$ RenderCtx -> Attr -> Attr
rewriteClass RenderCtx
ctx Attr
attr)
([Node] -> [Node]) -> Splice Identity -> Splice Identity
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (Block -> Splice Identity) -> [Block] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
foldMapM (RenderCtx -> Block -> Splice Identity
rpBlock RenderCtx
ctx) [Block]
bs
B.Figure Attr
attr Caption
_caption [Block]
bs ->
OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> ([Node] -> Node) -> [Node] -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
"figure" (Attr -> [(Text, Text)]
rpAttr Attr
attr) ([Node] -> [Node]) -> Splice Identity -> Splice Identity
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (Block -> Splice Identity) -> [Block] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
foldMapM (RenderCtx -> Block -> Splice Identity
rpBlock RenderCtx
ctx) [Block]
bs
where
getTag :: b -> (a, b, [(k, b)]) -> b
getTag b
defaultTag (a
_, b
_, [(k, b)] -> Map k b
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList -> Map k b
attrs) =
k -> Map k b -> Maybe b
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup k
"tag" Map k b
attrs Maybe b -> (Maybe b -> b) -> b
forall a b. a -> (a -> b) -> b
& b -> Maybe b -> b
forall a. a -> Maybe a -> a
fromMaybe b
defaultTag
mkLangClass :: [a] -> [a]
mkLangClass [a]
classes' =
[a] -> Maybe [a] -> [a]
forall a. a -> Maybe a -> a
fromMaybe [a
"language-none"] (Maybe [a] -> [a]) -> Maybe [a] -> [a]
forall a b. (a -> b) -> a -> b
$ do
NonEmpty a
classes <- [a] -> Maybe (NonEmpty a)
forall a. [a] -> Maybe (NonEmpty a)
nonEmpty [a]
classes'
let lang :: a
lang = NonEmpty a -> a
forall (f :: Type -> Type) a. IsNonEmpty f a a "head" => f a -> a
head NonEmpty a
classes
[a] -> Maybe [a]
forall a. a -> Maybe a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure ([a] -> Maybe [a]) -> [a] -> Maybe [a]
forall a b. (a -> b) -> a -> b
$ a
lang a -> [a] -> [a]
forall a. a -> [a] -> [a]
: (a
"language-" a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
lang) a -> [a] -> [a]
forall a. a -> [a] -> [a]
: NonEmpty a -> [a]
forall (f :: Type -> Type) a.
IsNonEmpty f a [a] "tail" =>
f a -> [a]
tail NonEmpty a
classes
headerSplices :: Text -> HeistT n m [Node] -> MapSyntaxM k (HeistT n m [Node]) ()
headerSplices Text
headerId HeistT n m [Node]
innerSplice = do
k
"header:id" k -> HeistT n m [Node] -> MapSyntaxM k (HeistT n m [Node]) ()
forall k v. k -> v -> MapSyntax k v
## Text -> HeistT n m [Node]
forall (m :: Type -> Type) (n :: Type -> Type).
Monad m =>
Text -> HeistT n m [Node]
HI.textSplice Text
headerId
k
"inlines" k -> HeistT n m [Node] -> MapSyntaxM k (HeistT n m [Node]) ()
forall k v. k -> v -> MapSyntax k v
## HeistT n m [Node]
innerSplice
definitionListSplices :: [([B.Inline], [[B.Block]])] -> H.Splices (HI.Splice Identity)
definitionListSplices :: [([Inline], [[Block]])] -> Splices (Splice Identity)
definitionListSplices [([Inline], [[Block]])]
defs = do
Text
"DefinitionList:Items" Text -> Splice Identity -> Splices (Splice Identity)
forall k v. k -> v -> MapSyntax k v
## (Splices (Splice Identity) -> Splice Identity
forall (n :: Type -> Type).
Monad n =>
Splices (Splice n) -> Splice n
HI.runChildrenWith (Splices (Splice Identity) -> Splice Identity)
-> (([Inline], [[Block]]) -> Splices (Splice Identity))
-> ([Inline], [[Block]])
-> Splice Identity
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Inline] -> [[Block]] -> Splices (Splice Identity))
-> ([Inline], [[Block]]) -> Splices (Splice Identity)
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry [Inline] -> [[Block]] -> Splices (Splice Identity)
itemsSplices) (([Inline], [[Block]]) -> Splice Identity)
-> [([Inline], [[Block]])] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
`foldMapM` [([Inline], [[Block]])]
defs
where
itemsSplices :: [B.Inline] -> [[B.Block]] -> H.Splices (HI.Splice Identity)
itemsSplices :: [Inline] -> [[Block]] -> Splices (Splice Identity)
itemsSplices [Inline]
term [[Block]]
descriptions = do
Text
"DefinitionList:Item:Term" Text -> Splice Identity -> Splices (Splice Identity)
forall k v. k -> v -> MapSyntax k v
## (Inline -> Splice Identity) -> [Inline] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
foldMapM (RenderCtx -> Inline -> Splice Identity
rpInline RenderCtx
ctx) [Inline]
term
Text
"DefinitionList:Item:DescList" Text -> Splice Identity -> Splices (Splice Identity)
forall k v. k -> v -> MapSyntax k v
## (Splices (Splice Identity) -> Splice Identity
forall (n :: Type -> Type).
Monad n =>
Splices (Splice n) -> Splice n
HI.runChildrenWith (Splices (Splice Identity) -> Splice Identity)
-> ([Block] -> Splices (Splice Identity))
-> [Block]
-> Splice Identity
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Block] -> Splices (Splice Identity)
descListSplices) ([Block] -> Splice Identity) -> [[Block]] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
`foldMapM` [[Block]]
descriptions
descListSplices :: [B.Block] -> H.Splices (HI.Splice Identity)
descListSplices :: [Block] -> Splices (Splice Identity)
descListSplices [Block]
bs = Text
"DefinitionList:Item:Desc" Text -> Splice Identity -> Splices (Splice Identity)
forall k v. k -> v -> MapSyntax k v
## RenderCtx -> Block -> Splice Identity
rpBlock RenderCtx
ctx (Block -> Splice Identity) -> [Block] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
`foldMapM` [Block]
bs
pandocListSplices :: Text -> [[B.Block]] -> H.Splices (HI.Splice Identity)
pandocListSplices :: Text -> [[Block]] -> Splices (Splice Identity)
pandocListSplices Text
tagPrefix [[Block]]
bss =
(Text
tagPrefix Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":Items") Text -> Splice Identity -> Splices (Splice Identity)
forall k v. k -> v -> MapSyntax k v
## (Splices (Splice Identity) -> Splice Identity
forall (n :: Type -> Type).
Monad n =>
Splices (Splice n) -> Splice n
HI.runChildrenWith (Splices (Splice Identity) -> Splice Identity)
-> ([Block] -> Splices (Splice Identity))
-> [Block]
-> Splice Identity
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Block] -> Splices (Splice Identity)
itemsSplices) ([Block] -> Splice Identity) -> [[Block]] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
`foldMapM` [[Block]]
bss
where
itemsSplices :: [B.Block] -> H.Splices (HI.Splice Identity)
itemsSplices :: [Block] -> Splices (Splice Identity)
itemsSplices [Block]
bs = do
(Text
tagPrefix Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":Item") Text -> Splice Identity -> Splices (Splice Identity)
forall k v. k -> v -> MapSyntax k v
## (Block -> Splice Identity) -> [Block] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
foldMapM (RenderCtx -> Block -> Splice Identity
rpBlock RenderCtx
ctx) [Block]
bs
headerTag :: HasCallStack => Int -> Text
Int
n =
if Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
1 Bool -> Bool -> Bool
&& Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
6
then Text
"h" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text
forall b a. (Show a, IsString b) => a -> b
show Int
n
else Text -> Text
forall a t. (HasCallStack, IsText t) => t -> a
error Text
"Invalid pandoc header level"
rpInline :: RenderCtx -> B.Inline -> HI.Splice Identity
rpInline :: RenderCtx -> Inline -> Splice Identity
rpInline ctx :: RenderCtx
ctx@RenderCtx {Maybe Node
Map Text Text
Inline -> Maybe (Splice Identity)
Inline -> Attr
Block -> Maybe (Splice Identity)
Block -> Attr
inlineSplice :: RenderCtx -> Inline -> Maybe (Splice Identity)
blockSplice :: RenderCtx -> Block -> Maybe (Splice Identity)
classMap :: RenderCtx -> Map Text Text
iAttr :: RenderCtx -> Inline -> Attr
bAttr :: RenderCtx -> Block -> Attr
rootNode :: RenderCtx -> Maybe Node
rootNode :: Maybe Node
bAttr :: Block -> Attr
iAttr :: Inline -> Attr
classMap :: Map Text Text
blockSplice :: Block -> Maybe (Splice Identity)
inlineSplice :: Inline -> Maybe (Splice Identity)
..} Inline
i = do
Splice Identity -> Maybe (Splice Identity) -> Splice Identity
forall a. a -> Maybe a -> a
fromMaybe (RenderCtx -> Inline -> Splice Identity
rpInline' RenderCtx
ctx Inline
i) (Maybe (Splice Identity) -> Splice Identity)
-> Maybe (Splice Identity) -> Splice Identity
forall a b. (a -> b) -> a -> b
$ Inline -> Maybe (Splice Identity)
inlineSplice Inline
i
rpInline' :: RenderCtx -> B.Inline -> HI.Splice Identity
rpInline' :: RenderCtx -> Inline -> Splice Identity
rpInline' ctx :: RenderCtx
ctx@RenderCtx {Maybe Node
Map Text Text
Inline -> Maybe (Splice Identity)
Inline -> Attr
Block -> Maybe (Splice Identity)
Block -> Attr
inlineSplice :: RenderCtx -> Inline -> Maybe (Splice Identity)
blockSplice :: RenderCtx -> Block -> Maybe (Splice Identity)
classMap :: RenderCtx -> Map Text Text
iAttr :: RenderCtx -> Inline -> Attr
bAttr :: RenderCtx -> Block -> Attr
rootNode :: RenderCtx -> Maybe Node
rootNode :: Maybe Node
bAttr :: Block -> Attr
iAttr :: Inline -> Attr
classMap :: Map Text Text
blockSplice :: Block -> Maybe (Splice Identity)
inlineSplice :: Inline -> Maybe (Splice Identity)
..} Inline
i = case Inline
i of
B.Str Text
s ->
[Node] -> Splice Identity
forall a. a -> HeistT Identity Identity a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure ([Node] -> Splice Identity) -> [Node] -> Splice Identity
forall a b. (a -> b) -> a -> b
$ OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> (Text -> Node) -> Text -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Node
X.TextNode (Text -> [Node]) -> Text -> [Node]
forall a b. (a -> b) -> a -> b
$ Text
s
B.Emph [Inline]
is ->
OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> ([Node] -> Node) -> [Node] -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
"em" [(Text, Text)]
forall a. Monoid a => a
mempty ([Node] -> [Node]) -> Splice Identity -> Splice Identity
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (Inline -> Splice Identity) -> [Inline] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
foldMapM (RenderCtx -> Inline -> Splice Identity
rpInline RenderCtx
ctx) [Inline]
is
B.Strong [Inline]
is ->
OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> ([Node] -> Node) -> [Node] -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
"strong" [(Text, Text)]
forall a. Monoid a => a
mempty ([Node] -> [Node]) -> Splice Identity -> Splice Identity
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (Inline -> Splice Identity) -> [Inline] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
foldMapM (RenderCtx -> Inline -> Splice Identity
rpInline RenderCtx
ctx) [Inline]
is
B.Underline [Inline]
is ->
OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> ([Node] -> Node) -> [Node] -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
"u" [(Text, Text)]
forall a. Monoid a => a
mempty ([Node] -> [Node]) -> Splice Identity -> Splice Identity
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (Inline -> Splice Identity) -> [Inline] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
foldMapM (RenderCtx -> Inline -> Splice Identity
rpInline RenderCtx
ctx) [Inline]
is
B.Strikeout [Inline]
is ->
OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> ([Node] -> Node) -> [Node] -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
"s" [(Text, Text)]
forall a. Monoid a => a
mempty ([Node] -> [Node]) -> Splice Identity -> Splice Identity
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (Inline -> Splice Identity) -> [Inline] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
foldMapM (RenderCtx -> Inline -> Splice Identity
rpInline RenderCtx
ctx) [Inline]
is
B.Superscript [Inline]
is ->
OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> ([Node] -> Node) -> [Node] -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
"sup" [(Text, Text)]
forall a. Monoid a => a
mempty ([Node] -> [Node]) -> Splice Identity -> Splice Identity
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (Inline -> Splice Identity) -> [Inline] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
foldMapM (RenderCtx -> Inline -> Splice Identity
rpInline RenderCtx
ctx) [Inline]
is
B.Subscript [Inline]
is ->
OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> ([Node] -> Node) -> [Node] -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
"sub" [(Text, Text)]
forall a. Monoid a => a
mempty ([Node] -> [Node]) -> Splice Identity -> Splice Identity
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (Inline -> Splice Identity) -> [Inline] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
foldMapM (RenderCtx -> Inline -> Splice Identity
rpInline RenderCtx
ctx) [Inline]
is
B.Quoted QuoteType
qt [Inline]
is ->
(Splice Identity -> QuoteType -> Splice Identity)
-> QuoteType -> Splice Identity -> Splice Identity
forall a b c. (a -> b -> c) -> b -> a -> c
flip Splice Identity -> QuoteType -> Splice Identity
inQuotes QuoteType
qt (Splice Identity -> Splice Identity)
-> Splice Identity -> Splice Identity
forall a b. (a -> b) -> a -> b
$ (Inline -> Splice Identity) -> [Inline] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
foldMapM (RenderCtx -> Inline -> Splice Identity
rpInline RenderCtx
ctx) [Inline]
is
B.Code Attr
attr Text
s ->
[Node] -> Splice Identity
forall a. a -> HeistT Identity Identity a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure ([Node] -> Splice Identity) -> [Node] -> Splice Identity
forall a b. (a -> b) -> a -> b
$
OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> ([Node] -> Node) -> [Node] -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
"code" (Attr -> [(Text, Text)]
rpAttr (Attr -> [(Text, Text)]) -> Attr -> [(Text, Text)]
forall a b. (a -> b) -> a -> b
$ Attr -> Attr -> Attr
concatAttr Attr
attr (Attr -> Attr) -> Attr -> Attr
forall a b. (a -> b) -> a -> b
$ Inline -> Attr
iAttr Inline
i) ([Node] -> [Node]) -> [Node] -> [Node]
forall a b. (a -> b) -> a -> b
$
OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> (Text -> Node) -> Text -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Node
X.TextNode (Text -> [Node]) -> Text -> [Node]
forall a b. (a -> b) -> a -> b
$
Text
s
Inline
B.Space -> [Node] -> Splice Identity
forall a. a -> HeistT Identity Identity a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure ([Node] -> Splice Identity) -> [Node] -> Splice Identity
forall a b. (a -> b) -> a -> b
$ OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> (Text -> Node) -> Text -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Node
X.TextNode (Text -> [Node]) -> Text -> [Node]
forall a b. (a -> b) -> a -> b
$ Text
" "
Inline
B.SoftBreak -> [Node] -> Splice Identity
forall a. a -> HeistT Identity Identity a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure ([Node] -> Splice Identity) -> [Node] -> Splice Identity
forall a b. (a -> b) -> a -> b
$ OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> (Text -> Node) -> Text -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Node
X.TextNode (Text -> [Node]) -> Text -> [Node]
forall a b. (a -> b) -> a -> b
$ Text
" "
Inline
B.LineBreak ->
[Node] -> Splice Identity
forall a. a -> HeistT Identity Identity a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure ([Node] -> Splice Identity) -> [Node] -> Splice Identity
forall a b. (a -> b) -> a -> b
$ OneItem [Node] -> [Node]
forall x. One x => OneItem x -> x
one (OneItem [Node] -> [Node]) -> OneItem [Node] -> [Node]
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
"br" [(Text, Text)]
forall a. Monoid a => a
mempty [Node]
forall a. Monoid a => a
mempty
B.RawInline (B.Format Text
fmt) Text
s ->
if Text
fmt Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"html"
then [Node] -> Splice Identity
forall a. a -> HeistT Identity Identity a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure ([Node] -> Splice Identity) -> [Node] -> Splice Identity
forall a b. (a -> b) -> a -> b
$ Text -> Text -> [Node]
rawNode Text
"span" Text
s
else
[Node] -> Splice Identity
forall a. a -> HeistT Identity Identity a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure ([Node] -> Splice Identity) -> [Node] -> Splice Identity
forall a b. (a -> b) -> a -> b
$
OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> ([Node] -> Node) -> [Node] -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
"pre" [(Text
"class", Text
"pandoc-raw-" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
forall b a. (Show a, IsString b) => a -> b
show Text
fmt)] ([Node] -> [Node]) -> [Node] -> [Node]
forall a b. (a -> b) -> a -> b
$
OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> (Text -> Node) -> Text -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Node
X.TextNode (Text -> [Node]) -> Text -> [Node]
forall a b. (a -> b) -> a -> b
$
Text
s
B.Math MathType
mathType Text
s ->
case MathType
mathType of
MathType
B.InlineMath ->
[Node] -> Splice Identity
forall a. a -> HeistT Identity Identity a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure ([Node] -> Splice Identity) -> [Node] -> Splice Identity
forall a b. (a -> b) -> a -> b
$
OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> ([Node] -> Node) -> [Node] -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
"span" [(Text
"class", Text
"math inline")] ([Node] -> [Node]) -> [Node] -> [Node]
forall a b. (a -> b) -> a -> b
$
OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> (Text -> Node) -> Text -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Node
X.TextNode (Text -> [Node]) -> Text -> [Node]
forall a b. (a -> b) -> a -> b
$
Text
"\\(" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
s Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\\)"
MathType
B.DisplayMath ->
[Node] -> Splice Identity
forall a. a -> HeistT Identity Identity a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure ([Node] -> Splice Identity) -> [Node] -> Splice Identity
forall a b. (a -> b) -> a -> b
$
OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> ([Node] -> Node) -> [Node] -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
"span" [(Text
"class", Text
"math display")] ([Node] -> [Node]) -> [Node] -> [Node]
forall a b. (a -> b) -> a -> b
$
OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> (Text -> Node) -> Text -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Node
X.TextNode (Text -> [Node]) -> Text -> [Node]
forall a b. (a -> b) -> a -> b
$
Text
"$$" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
s Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"$$"
B.Link Attr
attr [Inline]
is (Text
url, Text
tit) -> do
let attrs :: [(Text, Text)]
attrs =
[Maybe (Text, Text)] -> [(Text, Text)]
forall a. [Maybe a] -> [a]
catMaybes [(Text, Text) -> Maybe (Text, Text)
forall a. a -> Maybe a
Just (Text
"href", Text
url), Bool -> Maybe ()
forall (f :: Type -> Type). Alternative f => Bool -> f ()
guard (Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ Text -> Bool
T.null Text
tit) Maybe () -> Maybe (Text, Text) -> Maybe (Text, Text)
forall a b. Maybe a -> Maybe b -> Maybe b
forall (m :: Type -> Type) a b. Monad m => m a -> m b -> m b
>> (Text, Text) -> Maybe (Text, Text)
forall a. a -> Maybe a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (Text
"title", Text
tit)]
[(Text, Text)] -> [(Text, Text)] -> [(Text, Text)]
forall a. Semigroup a => a -> a -> a
<> Attr -> [(Text, Text)]
rpAttr (Attr -> Attr -> Attr
concatAttr Attr
attr (Attr -> Attr) -> Attr -> Attr
forall a b. (a -> b) -> a -> b
$ Inline -> Attr
iAttr Inline
i)
OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> ([Node] -> Node) -> [Node] -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
"a" [(Text, Text)]
attrs ([Node] -> [Node]) -> Splice Identity -> Splice Identity
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (Inline -> Splice Identity) -> [Inline] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
foldMapM (RenderCtx -> Inline -> Splice Identity
rpInline RenderCtx
ctx) [Inline]
is
B.Image Attr
attr [Inline]
is (Text
url, Text
tit) -> do
let attrs :: [(Text, Text)]
attrs =
[Maybe (Text, Text)] -> [(Text, Text)]
forall a. [Maybe a] -> [a]
catMaybes
[ (Text, Text) -> Maybe (Text, Text)
forall a. a -> Maybe a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (Text
"src", Text
url)
, Bool -> Maybe ()
forall (f :: Type -> Type). Alternative f => Bool -> f ()
guard (Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ Text -> Bool
T.null Text
tit) Maybe () -> Maybe (Text, Text) -> Maybe (Text, Text)
forall a b. Maybe a -> Maybe b -> Maybe b
forall (m :: Type -> Type) a b. Monad m => m a -> m b -> m b
>> (Text, Text) -> Maybe (Text, Text)
forall a. a -> Maybe a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (Text
"title", Text
tit)
, (Text, Text) -> Maybe (Text, Text)
forall a. a -> Maybe a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (Text
"alt", [Inline] -> Text
plainify [Inline]
is)
]
[(Text, Text)] -> [(Text, Text)] -> [(Text, Text)]
forall a. Semigroup a => a -> a -> a
<> Attr -> [(Text, Text)]
rpAttr (RenderCtx -> Attr -> Attr
rewriteClass RenderCtx
ctx Attr
attr)
[Node] -> Splice Identity
forall a. a -> HeistT Identity Identity a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure ([Node] -> Splice Identity) -> [Node] -> Splice Identity
forall a b. (a -> b) -> a -> b
$ OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> ([Node] -> Node) -> [Node] -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
"img" [(Text, Text)]
attrs ([Node] -> [Node]) -> [Node] -> [Node]
forall a b. (a -> b) -> a -> b
$ [Node]
forall a. Monoid a => a
mempty
B.Note [Block]
_bs -> do
[Node] -> Splice Identity
forall a. a -> HeistT Identity Identity a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure ([Node] -> Splice Identity) -> [Node] -> Splice Identity
forall a b. (a -> b) -> a -> b
$ OneItem [Node] -> [Node]
forall x. One x => OneItem x -> x
one (OneItem [Node] -> [Node]) -> OneItem [Node] -> [Node]
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
"sup" [(Text, Text)]
forall a. Monoid a => a
mempty ([Node] -> Node) -> [Node] -> Node
forall a b. (a -> b) -> a -> b
$ OneItem [Node] -> [Node]
forall x. One x => OneItem x -> x
one (OneItem [Node] -> [Node]) -> OneItem [Node] -> [Node]
forall a b. (a -> b) -> a -> b
$ Text -> Node
X.TextNode Text
"*"
B.Span Attr
attr [Inline]
is -> do
OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> ([Node] -> Node) -> [Node] -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
"span" (Attr -> [(Text, Text)]
rpAttr (Attr -> [(Text, Text)]) -> Attr -> [(Text, Text)]
forall a b. (a -> b) -> a -> b
$ RenderCtx -> Attr -> Attr
rewriteClass RenderCtx
ctx Attr
attr) ([Node] -> [Node]) -> Splice Identity -> Splice Identity
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (Inline -> Splice Identity) -> [Inline] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
foldMapM (RenderCtx -> Inline -> Splice Identity
rpInline RenderCtx
ctx) [Inline]
is
B.SmallCaps [Inline]
is ->
(Inline -> Splice Identity) -> [Inline] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
foldMapM (RenderCtx -> Inline -> Splice Identity
rpInline RenderCtx
ctx) [Inline]
is
B.Cite [Citation]
_citations [Inline]
is ->
RenderCtx
-> Text
-> Splices (Splice Identity)
-> Splice Identity
-> Splice Identity
withTplTag RenderCtx
ctx Text
"Cite" (Text
"inlines" Text -> Splice Identity -> Splices (Splice Identity)
forall k v. k -> v -> MapSyntax k v
## RenderCtx -> Inline -> Splice Identity
rpInline RenderCtx
ctx (Inline -> Splice Identity) -> [Inline] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
`foldMapM` [Inline]
is) (Splice Identity -> Splice Identity)
-> Splice Identity -> Splice Identity
forall a b. (a -> b) -> a -> b
$
OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> ([Node] -> Node) -> [Node] -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
"cite" [(Text, Text)]
forall a. Monoid a => a
mempty ([Node] -> [Node]) -> Splice Identity -> Splice Identity
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (Inline -> Splice Identity) -> [Inline] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
foldMapM (RenderCtx -> Inline -> Splice Identity
rpInline RenderCtx
ctx) [Inline]
is
where
inQuotes :: HI.Splice Identity -> B.QuoteType -> HI.Splice Identity
inQuotes :: Splice Identity -> QuoteType -> Splice Identity
inQuotes Splice Identity
w = \case
QuoteType
B.SingleQuote ->
Splice Identity
w Splice Identity -> ([Node] -> [Node]) -> Splice Identity
forall (f :: Type -> Type) a b. Functor f => f a -> (a -> b) -> f b
<&> \[Node]
nodes ->
[Text -> Node
X.TextNode Text
"‘"] [Node] -> [Node] -> [Node]
forall a. Semigroup a => a -> a -> a
<> [Node]
nodes [Node] -> [Node] -> [Node]
forall a. Semigroup a => a -> a -> a
<> [Text -> Node
X.TextNode Text
"’"]
QuoteType
B.DoubleQuote ->
Splice Identity
w Splice Identity -> ([Node] -> [Node]) -> Splice Identity
forall (f :: Type -> Type) a b. Functor f => f a -> (a -> b) -> f b
<&> \[Node]
nodes ->
[Text -> Node
X.TextNode Text
"“"] [Node] -> [Node] -> [Node]
forall a. Semigroup a => a -> a -> a
<> [Node]
nodes [Node] -> [Node] -> [Node]
forall a. Semigroup a => a -> a -> a
<> [Text -> Node
X.TextNode Text
"”"]
convertRawInline :: [B.Inline] -> [B.Inline] -> [B.Inline]
convertRawInline :: [Inline] -> [Inline] -> [Inline]
convertRawInline [Inline]
acc = \case
[] -> [Inline] -> [Inline]
forall a. [a] -> [a]
reverse [Inline]
acc
(B.RawInline (B.Format Text
"html") Text
oTag : [Inline]
rest)
|
Just (Inline
newElem, [Inline]
is) <- Text -> [Inline] -> Maybe (Inline, [Inline])
mkHtmlInline Text
oTag [Inline]
rest ->
[Inline] -> [Inline] -> [Inline]
convertRawInline (Inline
newElem Inline -> [Inline] -> [Inline]
forall a. a -> [a] -> [a]
: [Inline]
acc) [Inline]
is
Inline
i : [Inline]
is -> [Inline] -> [Inline] -> [Inline]
convertRawInline (Inline
i Inline -> [Inline] -> [Inline]
forall a. a -> [a] -> [a]
: [Inline]
acc) [Inline]
is
where
mkHtmlInline :: Text -> [B.Inline] -> Maybe (B.Inline, [B.Inline])
mkHtmlInline :: Text -> [Inline] -> Maybe (Inline, [Inline])
mkHtmlInline Text
oTag [Inline]
rest = case (Inline -> Bool) -> [Inline] -> ([Inline], [Inline])
forall a. (a -> Bool) -> [a] -> ([a], [a])
span (Bool -> Bool
not (Bool -> Bool) -> (Inline -> Bool) -> Inline -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Inline -> Bool
isClosingTag Text
oTag) [Inline]
rest of
([Inline]
inner, (Inline
closing : [Inline]
is))
|
Text -> Inline -> Bool
isClosingTag Text
oTag Inline
closing ->
let inner' :: Text
inner' = Text
oTag Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Inline] -> Text
plainify [Inline]
inner Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"</" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text -> Text
T.drop Int
1 Text
oTag
in (Inline, [Inline]) -> Maybe (Inline, [Inline])
forall a. a -> Maybe a
Just (Format -> Text -> Inline
B.RawInline (Text -> Format
B.Format Text
"html") Text
inner', [Inline]
is)
([Inline], [Inline])
_ -> Maybe (Inline, [Inline])
forall a. Maybe a
Nothing
isClosingTag :: Text -> B.Inline -> Bool
isClosingTag :: Text -> Inline -> Bool
isClosingTag Text
oTag = \case
B.RawInline (B.Format Text
"html") Text
eTag ->
Text
"<" Text -> Text -> Bool
`T.isPrefixOf` Text
oTag Bool -> Bool -> Bool
&& Text
"</" Text -> Text -> Bool
`T.isPrefixOf` Text
eTag Bool -> Bool -> Bool
&& Int -> Text -> Text
T.drop Int
1 Text
oTag Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Text -> Text
T.drop Int
2 Text
eTag
Inline
_ -> Bool
False
rpInlineWithTasks :: RenderCtx -> [B.Inline] -> HI.Splice Identity
rpInlineWithTasks :: RenderCtx -> [Inline] -> Splice Identity
rpInlineWithTasks RenderCtx
ctx [Inline]
is =
RenderCtx -> [Inline] -> Splice Identity -> Splice Identity
rpTask RenderCtx
ctx [Inline]
is (Splice Identity -> Splice Identity)
-> Splice Identity -> Splice Identity
forall a b. (a -> b) -> a -> b
$
RenderCtx -> Inline -> Splice Identity
rpInline RenderCtx
ctx (Inline -> Splice Identity) -> [Inline] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
`foldMapM` [Inline]
is
rpTask :: RenderCtx -> [B.Inline] -> HI.Splice Identity -> HI.Splice Identity
rpTask :: RenderCtx -> [Inline] -> Splice Identity -> Splice Identity
rpTask RenderCtx
ctx [Inline]
is Splice Identity
default_ =
Splice Identity
-> ((Bool, [Inline]) -> Splice Identity)
-> Maybe (Bool, [Inline])
-> Splice Identity
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Splice Identity
default_ (Bool, [Inline]) -> Splice Identity
render ([Inline] -> Maybe (Bool, [Inline])
TaskList.parseTaskFromInlines [Inline]
is)
where
render :: (Bool, [Inline]) -> Splice Identity
render (Bool
checked, [Inline]
taskInlines) = do
let tag :: Text
tag = Text -> Text -> Bool -> Text
forall a. a -> a -> Bool -> a
bool Text
"Task:Unchecked" Text
"Task:Checked" Bool
checked
RenderCtx
-> Text
-> Splices (Splice Identity)
-> Splice Identity
-> Splice Identity
withTplTag
RenderCtx
ctx
Text
tag
(Text
"inlines" Text -> Splice Identity -> Splices (Splice Identity)
forall k v. k -> v -> MapSyntax k v
## RenderCtx -> Inline -> Splice Identity
rpInline RenderCtx
ctx (Inline -> Splice Identity) -> [Inline] -> Splice Identity
forall b (m :: Type -> Type) (f :: Type -> Type) a.
(Monoid b, Monad m, Foldable f) =>
(a -> m b) -> f a -> m b
`foldMapM` [Inline]
taskInlines)
Splice Identity
default_
rawNode :: Text -> Text -> [X.Node]
rawNode :: Text -> Text -> [Node]
rawNode Text
wrapperTag Text
s =
OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> ([Node] -> Node) -> [Node] -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [(Text, Text)] -> [Node] -> Node
X.Element Text
wrapperTag (OneItem [(Text, Text)] -> [(Text, Text)]
forall x. One x => OneItem x -> x
one (Text
"xmlhtmlRaw", Text
"")) ([Node] -> [Node]) -> [Node] -> [Node]
forall a b. (a -> b) -> a -> b
$
OneItem [Node] -> [Node]
Node -> [Node]
forall x. One x => OneItem x -> x
one (Node -> [Node]) -> (Text -> Node) -> Text -> [Node]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Node
X.TextNode (Text -> [Node]) -> Text -> [Node]
forall a b. (a -> b) -> a -> b
$
Text
s
plainify :: [B.Inline] -> Text
plainify :: [Inline] -> Text
plainify = (Inline -> Text) -> [Inline] -> Text
forall c. Monoid c => (Inline -> c) -> [Inline] -> c
forall a b c. (Walkable a b, Monoid c) => (a -> c) -> b -> c
W.query ((Inline -> Text) -> [Inline] -> Text)
-> (Inline -> Text) -> [Inline] -> Text
forall a b. (a -> b) -> a -> b
$ \case
B.Str Text
x -> Text
x
B.Code Attr
_attr Text
x -> Text
x
Inline
B.Space -> Text
" "
Inline
B.SoftBreak -> Text
" "
Inline
B.LineBreak -> Text
" "
B.RawInline Format
_fmt Text
s -> Text
s
B.Span Attr
_ [Inline]
_ -> Text
""
B.Math MathType
_mathTyp Text
s -> Text
s
Inline
_ -> Text
""