{-# LANGUAGE OverloadedStrings #-}
module Text.Pandoc.Writers.ZimWiki ( writeZimWiki ) where
import Control.Monad (zipWithM)
import Control.Monad.State.Strict (StateT, evalStateT, gets, modify)
import Data.Default (Default (..))
import Data.List (transpose)
import Data.List.NonEmpty (nonEmpty)
import qualified Data.Map as Map
import Text.DocLayout (render, literal)
import Data.Maybe (fromMaybe)
import Data.Text (Text)
import qualified Data.Text as T
import Text.Pandoc.Class.PandocMonad (PandocMonad, report)
import Text.Pandoc.Definition
import Text.Pandoc.ImageSize
import Text.Pandoc.Logging
import Text.Pandoc.Options (WrapOption (..),
WriterOptions (writerTableOfContents, writerTemplate,
writerWrapText))
import Text.Pandoc.Shared (figureDiv, linesToPara, removeFormatting, trimr)
import Text.Pandoc.URI (escapeURI, isURI)
import Text.Pandoc.Templates (renderTemplate)
import Text.Pandoc.Writers.Shared (defField, metaToContext, toLegacyTable)
data WriterState = WriterState {
WriterState -> Text
stIndent :: Text,
WriterState -> Bool
stInTable :: Bool,
WriterState -> Bool
stInLink :: Bool
}
instance Default WriterState where
def :: WriterState
def = WriterState { stIndent :: Text
stIndent = Text
"", stInTable :: Bool
stInTable = Bool
False, stInLink :: Bool
stInLink = Bool
False }
type ZW = StateT WriterState
writeZimWiki :: PandocMonad m => WriterOptions -> Pandoc -> m Text
writeZimWiki :: forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Pandoc -> m Text
writeZimWiki WriterOptions
opts Pandoc
document = StateT WriterState m Text -> WriterState -> m Text
forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m a
evalStateT (WriterOptions -> Pandoc -> StateT WriterState m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Pandoc -> ZW m Text
pandocToZimWiki WriterOptions
opts Pandoc
document) WriterState
forall a. Default a => a
def
pandocToZimWiki :: PandocMonad m => WriterOptions -> Pandoc -> ZW m Text
pandocToZimWiki :: forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Pandoc -> ZW m Text
pandocToZimWiki WriterOptions
opts (Pandoc Meta
meta [Block]
blocks) = do
Context Text
metadata <- WriterOptions
-> ([Block] -> StateT WriterState m (Doc Text))
-> ([Inline] -> StateT WriterState m (Doc Text))
-> Meta
-> StateT WriterState m (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
((Text -> Doc Text) -> ZW m Text -> StateT WriterState m (Doc Text)
forall a b.
(a -> b) -> StateT WriterState m a -> StateT WriterState m b
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) -> (Text -> Text) -> Text -> Doc Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
trimr) (ZW m Text -> StateT WriterState m (Doc Text))
-> ([Block] -> ZW m Text)
-> [Block]
-> StateT WriterState m (Doc Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WriterOptions -> [Block] -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Block] -> ZW m Text
blockListToZimWiki WriterOptions
opts)
((Text -> Doc Text) -> ZW m Text -> StateT WriterState m (Doc Text)
forall a b.
(a -> b) -> StateT WriterState m a -> StateT WriterState m b
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) -> (Text -> Text) -> Text -> Doc Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
trimr) (ZW m Text -> StateT WriterState m (Doc Text))
-> ([Inline] -> ZW m Text)
-> [Inline]
-> StateT WriterState m (Doc Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WriterOptions -> [Inline] -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ZW m Text
inlineListToZimWiki WriterOptions
opts)
Meta
meta
Text
main <- WriterOptions -> [Block] -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Block] -> ZW m Text
blockListToZimWiki WriterOptions
opts [Block]
blocks
let context :: Context Text
context = Text -> Text -> Context Text -> Context Text
forall a b. ToContext a b => Text -> b -> Context a -> Context a
defField Text
"body" Text
main
(Context Text -> Context Text) -> Context Text -> Context Text
forall a b. (a -> b) -> a -> b
$ Text -> Bool -> Context Text -> Context Text
forall a b. ToContext a b => Text -> b -> Context a -> Context a
defField Text
"toc" (WriterOptions -> Bool
writerTableOfContents WriterOptions
opts) Context Text
metadata
Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ZW m Text) -> Text -> ZW m Text
forall a b. (a -> b) -> a -> b
$
case WriterOptions -> Maybe (Template Text)
writerTemplate WriterOptions
opts of
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
context
Maybe (Template Text)
Nothing -> Text
main
escapeText :: Text -> Text
escapeText :: Text -> Text
escapeText = HasCallStack => Text -> Text -> Text -> Text
Text -> Text -> Text -> Text
T.replace Text
"__" Text
"''__''" (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
HasCallStack => Text -> Text -> Text -> Text
Text -> Text -> Text -> Text
T.replace Text
"**" Text
"''**''" (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
HasCallStack => Text -> Text -> Text -> Text
Text -> Text -> Text -> Text
T.replace Text
"~~" Text
"''~~''" (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
HasCallStack => Text -> Text -> Text -> Text
Text -> Text -> Text -> Text
T.replace Text
"//" Text
"''//''"
blockToZimWiki :: PandocMonad m => WriterOptions -> Block -> ZW m Text
blockToZimWiki :: forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Block -> ZW m Text
blockToZimWiki WriterOptions
opts (Div Attr
_attrs [Block]
bs) = do
Text
contents <- WriterOptions -> [Block] -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Block] -> ZW m Text
blockListToZimWiki WriterOptions
opts [Block]
bs
Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ZW m Text) -> Text -> ZW m Text
forall a b. (a -> b) -> a -> b
$ Text
contents Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\n"
blockToZimWiki WriterOptions
opts (Plain [Inline]
inlines) = WriterOptions -> [Inline] -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ZW m Text
inlineListToZimWiki WriterOptions
opts [Inline]
inlines
blockToZimWiki WriterOptions
opts (Para [Inline]
inlines) = do
Text
indent <- (WriterState -> Text) -> ZW m Text
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Text
stIndent
Text
contents <- WriterOptions -> [Inline] -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ZW m Text
inlineListToZimWiki WriterOptions
opts [Inline]
inlines
Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ZW m Text) -> Text -> ZW m Text
forall a b. (a -> b) -> a -> b
$ Text
contents Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> if Text -> Bool
T.null Text
indent then Text
"\n" else Text
""
blockToZimWiki WriterOptions
opts (LineBlock [[Inline]]
lns) =
WriterOptions -> Block -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Block -> ZW m Text
blockToZimWiki WriterOptions
opts (Block -> ZW m Text) -> Block -> ZW m Text
forall a b. (a -> b) -> a -> b
$ [[Inline]] -> Block
linesToPara [[Inline]]
lns
blockToZimWiki WriterOptions
opts b :: Block
b@(RawBlock Format
f Text
str)
| Format
f Format -> Format -> Bool
forall a. Eq a => a -> a -> Bool
== Text -> Format
Format Text
"zimwiki" = Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
str
| Format
f Format -> Format -> Bool
forall a. Eq a => a -> a -> Bool
== Text -> Format
Format Text
"html" = WriterOptions -> Text -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Text -> ZW m Text
indentFromHTML WriterOptions
opts Text
str
| Bool
otherwise = do
LogMessage -> StateT WriterState m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> StateT WriterState m ())
-> LogMessage -> StateT WriterState m ()
forall a b. (a -> b) -> a -> b
$ Block -> LogMessage
BlockNotRendered Block
b
Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
""
blockToZimWiki WriterOptions
_ Block
HorizontalRule = Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
"\n----\n"
blockToZimWiki WriterOptions
opts (Header Int
level Attr
_ [Inline]
inlines) = do
Text
contents <- WriterOptions -> [Inline] -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ZW m Text
inlineListToZimWiki WriterOptions
opts [Inline]
inlines
let eqs :: Text
eqs = Int -> Text -> Text
T.replicate ( Int
7 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
level ) Text
"="
Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ZW m Text) -> Text -> ZW m Text
forall a b. (a -> b) -> a -> b
$ Text
eqs Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
contents Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
eqs Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\n"
blockToZimWiki WriterOptions
_ (CodeBlock (Text
_,[Text]
classes,[(Text, Text)]
_) Text
str) = do
let langal :: [(Text, Text)]
langal = [(Text
"javascript", Text
"js"), (Text
"bash", Text
"sh"), (Text
"winbatch", Text
"dosbatch")]
let langmap :: Map Text Text
langmap = [(Text, Text)] -> Map Text Text
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(Text, Text)]
langal
Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ZW m Text) -> Text -> ZW m Text
forall a b. (a -> b) -> a -> b
$ case [Text]
classes of
[] -> Text
"'''\n" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
cleanupCode Text
str Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\n'''\n"
(Text
x:[Text]
_) -> Text
"{{{code: lang=\"" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
x (Text -> Map Text Text -> Maybe Text
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Text
x Map Text Text
langmap) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\" linenumbers=\"True\"\n" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
str Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\n}}}\n"
blockToZimWiki WriterOptions
opts (BlockQuote [Block]
blocks) = do
Text
contents <- WriterOptions -> [Block] -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Block] -> ZW m Text
blockListToZimWiki WriterOptions
opts [Block]
blocks
Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ZW m Text) -> Text -> ZW m Text
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.unlines ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Text
"> " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>) ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ Text -> [Text]
T.lines Text
contents
blockToZimWiki WriterOptions
opts (Table Attr
_ Caption
blkCapt [ColSpec]
specs TableHead
thead [TableBody]
tbody TableFoot
tfoot) = do
let ([Inline]
capt, [Alignment]
aligns, [Double]
_, [[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
Text
captionDoc <- if [Inline] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Inline]
capt
then Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
""
else do
Text
c <- WriterOptions -> [Inline] -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ZW m Text
inlineListToZimWiki WriterOptions
opts [Inline]
capt
Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ZW m Text) -> Text -> ZW m Text
forall a b. (a -> b) -> a -> b
$ Text
"" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
c Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\n"
[Text]
headers' <- if ([Block] -> Bool) -> [[Block]] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all [Block] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [[Block]]
headers
then (Alignment -> [Block] -> ZW m Text)
-> [Alignment] -> [[Block]] -> StateT WriterState m [Text]
forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> m c) -> [a] -> [b] -> m [c]
zipWithM (WriterOptions -> Alignment -> [Block] -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Alignment -> [Block] -> ZW m Text
tableItemToZimWiki WriterOptions
opts) [Alignment]
aligns ([[[Block]]] -> [[Block]]
forall a. HasCallStack => [a] -> a
head [[[Block]]]
rows)
else ([Block] -> ZW m Text) -> [[Block]] -> StateT WriterState m [Text]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (WriterOptions -> [Inline] -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ZW m Text
inlineListToZimWiki WriterOptions
opts ([Inline] -> ZW m Text)
-> ([Block] -> [Inline]) -> [Block] -> ZW m Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Block] -> [Inline]
forall a. Walkable Inline a => a -> [Inline]
removeFormatting)[[Block]]
headers
[[Text]]
rows' <- ([[Block]] -> StateT WriterState m [Text])
-> [[[Block]]] -> StateT WriterState m [[Text]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((Alignment -> [Block] -> ZW m Text)
-> [Alignment] -> [[Block]] -> StateT WriterState m [Text]
forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> m c) -> [a] -> [b] -> m [c]
zipWithM (WriterOptions -> Alignment -> [Block] -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Alignment -> [Block] -> ZW m Text
tableItemToZimWiki WriterOptions
opts) [Alignment]
aligns) [[[Block]]]
rows
let widths :: [Int]
widths = ([Text] -> Int) -> [[Text]] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> (NonEmpty Int -> Int) -> Maybe (NonEmpty Int) -> Int
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Int
0 NonEmpty Int -> Int
forall a. Ord a => NonEmpty a -> a
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum (Maybe (NonEmpty Int) -> Int)
-> ([Text] -> Maybe (NonEmpty Int)) -> [Text] -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> Maybe (NonEmpty Int)
forall a. [a] -> Maybe (NonEmpty a)
nonEmpty ([Int] -> Maybe (NonEmpty Int))
-> ([Text] -> [Int]) -> [Text] -> Maybe (NonEmpty Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Int) -> [Text] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Text -> Int
T.length) ([[Text]] -> [Int]) -> [[Text]] -> [Int]
forall a b. (a -> b) -> a -> b
$
[[Text]] -> [[Text]]
forall a. [[a]] -> [[a]]
transpose ([Text]
headers'[Text] -> [[Text]] -> [[Text]]
forall a. a -> [a] -> [a]
:[[Text]]
rows')
let padTo :: (Int, Alignment) -> Text -> Text
padTo (Int
width, Alignment
al) Text
s =
case Int
width Int -> Int -> Int
forall a. Num a => a -> a -> a
- Text -> Int
T.length Text
s of
Int
x | Int
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 ->
if Alignment
al Alignment -> Alignment -> Bool
forall a. Eq a => a -> a -> Bool
== Alignment
AlignLeft Bool -> Bool -> Bool
|| Alignment
al Alignment -> Alignment -> Bool
forall a. Eq a => a -> a -> Bool
== Alignment
AlignDefault
then Text
s Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text -> Text
T.replicate Int
x Text
" "
else if Alignment
al Alignment -> Alignment -> Bool
forall a. Eq a => a -> a -> Bool
== Alignment
AlignRight
then Int -> Text -> Text
T.replicate Int
x Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
s
else Int -> Text -> Text
T.replicate (Int
x Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
2) Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
Text
s Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text -> Text
T.replicate (Int
x Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
x Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
2) Text
" "
| Bool
otherwise -> Text
s
let borderCell :: (Int, Alignment) -> p -> Text
borderCell (Int
width, Alignment
al) p
_
| Alignment
al Alignment -> Alignment -> Bool
forall a. Eq a => a -> a -> Bool
== Alignment
AlignLeft = Text
":"Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text -> Text
T.replicate (Int
widthInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) Text
"-"
| Alignment
al Alignment -> Alignment -> Bool
forall a. Eq a => a -> a -> Bool
== Alignment
AlignDefault = Int -> Text -> Text
T.replicate Int
width Text
"-"
| Alignment
al Alignment -> Alignment -> Bool
forall a. Eq a => a -> a -> Bool
== Alignment
AlignRight = Int -> Text -> Text
T.replicate (Int
widthInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) Text
"-" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":"
| Bool
otherwise = Text
":" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text -> Text
T.replicate (Int
widthInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
2) Text
"-" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":"
let underheader :: Text
underheader = Text
"|" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> [Text] -> Text
T.intercalate Text
"|" (((Int, Alignment) -> Text -> Text)
-> [(Int, Alignment)] -> [Text] -> [Text]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (Int, Alignment) -> Text -> Text
forall {p}. (Int, Alignment) -> p -> Text
borderCell ([Int] -> [Alignment] -> [(Int, Alignment)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int]
widths [Alignment]
aligns) [Text]
headers') Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"|"
let renderRow :: [Text] -> Text
renderRow [Text]
cells = Text
"|" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> [Text] -> Text
T.intercalate Text
"|" (((Int, Alignment) -> Text -> Text)
-> [(Int, Alignment)] -> [Text] -> [Text]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (Int, Alignment) -> Text -> Text
padTo ([Int] -> [Alignment] -> [(Int, Alignment)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int]
widths [Alignment]
aligns) [Text]
cells) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"|"
Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ZW m Text) -> Text -> ZW m Text
forall a b. (a -> b) -> a -> b
$ Text
captionDoc Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
(if [Text] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Text]
headers' then Text
"" else [Text] -> Text
renderRow [Text]
headers' Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\n") Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
underheader Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\n" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
[Text] -> Text
T.unlines (([Text] -> Text) -> [[Text]] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map [Text] -> Text
renderRow [[Text]]
rows')
blockToZimWiki WriterOptions
opts (BulletList [[Block]]
items) = do
[Text]
contents <- ([Block] -> ZW m Text) -> [[Block]] -> StateT WriterState m [Text]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (WriterOptions -> [Block] -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Block] -> ZW m Text
listItemToZimWiki WriterOptions
opts) [[Block]]
items
Text
indent <- (WriterState -> Text) -> ZW m Text
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Text
stIndent
Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ZW m Text) -> Text -> ZW m Text
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
vcat [Text]
contents Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> if Text -> Bool
T.null Text
indent then Text
"\n" else Text
""
blockToZimWiki WriterOptions
opts (OrderedList ListAttributes
_ [[Block]]
items) = do
[Text]
contents <- (Int -> [Block] -> ZW m Text)
-> [Int] -> [[Block]] -> StateT WriterState m [Text]
forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> m c) -> [a] -> [b] -> m [c]
zipWithM (WriterOptions -> Int -> [Block] -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Int -> [Block] -> ZW m Text
orderedListItemToZimWiki WriterOptions
opts) [Int
1..] [[Block]]
items
Text
indent <- (WriterState -> Text) -> ZW m Text
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Text
stIndent
Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ZW m Text) -> Text -> ZW m Text
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
vcat [Text]
contents Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> if Text -> Bool
T.null Text
indent then Text
"\n" else Text
""
blockToZimWiki WriterOptions
opts (DefinitionList [([Inline], [[Block]])]
items) = do
[Text]
contents <- (([Inline], [[Block]]) -> ZW m Text)
-> [([Inline], [[Block]])] -> StateT WriterState m [Text]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (WriterOptions -> ([Inline], [[Block]]) -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> ([Inline], [[Block]]) -> ZW m Text
definitionListItemToZimWiki WriterOptions
opts) [([Inline], [[Block]])]
items
Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ZW m Text) -> Text -> ZW m Text
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
vcat [Text]
contents
blockToZimWiki WriterOptions
opts (Figure Attr
attr Caption
capt [Block]
body) = do
WriterOptions -> Block -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Block -> ZW m Text
blockToZimWiki WriterOptions
opts (Attr -> Caption -> [Block] -> Block
figureDiv Attr
attr Caption
capt [Block]
body)
definitionListItemToZimWiki :: PandocMonad m
=> WriterOptions
-> ([Inline],[[Block]])
-> ZW m Text
definitionListItemToZimWiki :: forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> ([Inline], [[Block]]) -> ZW m Text
definitionListItemToZimWiki WriterOptions
opts ([Inline]
label, [[Block]]
items) = do
Text
labelText <- WriterOptions -> [Inline] -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ZW m Text
inlineListToZimWiki WriterOptions
opts [Inline]
label
[Text]
contents <- ([Block] -> ZW m Text) -> [[Block]] -> StateT WriterState m [Text]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (WriterOptions -> [Block] -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Block] -> ZW m Text
blockListToZimWiki WriterOptions
opts) [[Block]]
items
Text
indent <- (WriterState -> Text) -> ZW m Text
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Text
stIndent
Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ZW m Text) -> Text -> ZW m Text
forall a b. (a -> b) -> a -> b
$ Text
indent Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"* **" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
labelText Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"** " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Text] -> Text
T.concat [Text]
contents
indentFromHTML :: PandocMonad m => WriterOptions -> Text -> ZW m Text
indentFromHTML :: forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Text -> ZW m Text
indentFromHTML WriterOptions
_ Text
str = do
Text
indent <- (WriterState -> Text) -> ZW m Text
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Text
stIndent
if Text
"<li>" Text -> Text -> Bool
`T.isInfixOf` Text
str
then Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
indent
else if Text
"</li>" Text -> Text -> Bool
`T.isInfixOf` Text
str
then Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
"\n"
else if Text
"<li value=" Text -> Text -> Bool
`T.isInfixOf` Text
str
then Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
""
else if Text
"<ol>" Text -> Text -> Bool
`T.isInfixOf` Text
str
then do
let olcount :: Int
olcount=Text -> Text -> Int
countSubStrs Text
"<ol>" Text
str
(WriterState -> WriterState) -> StateT WriterState m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((WriterState -> WriterState) -> StateT WriterState m ())
-> (WriterState -> WriterState) -> StateT WriterState m ()
forall a b. (a -> b) -> a -> b
$ \WriterState
s -> WriterState
s { stIndent = stIndent s <>
T.replicate olcount "\t" }
Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
""
else if Text
"</ol>" Text -> Text -> Bool
`T.isInfixOf` Text
str
then do
let olcount :: Int
olcount=Text -> Text -> Int
countSubStrs Text
"/<ol>" Text
str
(WriterState -> WriterState) -> StateT WriterState m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((WriterState -> WriterState) -> StateT WriterState m ())
-> (WriterState -> WriterState) -> StateT WriterState m ()
forall a b. (a -> b) -> a -> b
$ \WriterState
s -> WriterState
s{ stIndent = T.drop olcount (stIndent s) }
Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
""
else Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
""
countSubStrs :: Text -> Text -> Int
countSubStrs :: Text -> Text -> Int
countSubStrs Text
sub Text
str = [(Text, Text)] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([(Text, Text)] -> Int) -> [(Text, Text)] -> Int
forall a b. (a -> b) -> a -> b
$ HasCallStack => Text -> Text -> [(Text, Text)]
Text -> Text -> [(Text, Text)]
T.breakOnAll Text
sub Text
str
cleanupCode :: Text -> Text
cleanupCode :: Text -> Text
cleanupCode = HasCallStack => Text -> Text -> Text -> Text
Text -> Text -> Text -> Text
T.replace Text
"<nowiki>" Text
"" (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HasCallStack => Text -> Text -> Text -> Text
Text -> Text -> Text -> Text
T.replace Text
"</nowiki>" Text
""
vcat :: [Text] -> Text
vcat :: [Text] -> Text
vcat = Text -> [Text] -> Text
T.intercalate Text
"\n"
listItemToZimWiki :: PandocMonad m => WriterOptions -> [Block] -> ZW m Text
listItemToZimWiki :: forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Block] -> ZW m Text
listItemToZimWiki WriterOptions
opts [Block]
items = do
Text
indent <- (WriterState -> Text) -> ZW m Text
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Text
stIndent
(WriterState -> WriterState) -> StateT WriterState m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((WriterState -> WriterState) -> StateT WriterState m ())
-> (WriterState -> WriterState) -> StateT WriterState m ()
forall a b. (a -> b) -> a -> b
$ \WriterState
s -> WriterState
s { stIndent = indent <> "\t" }
Text
contents <- WriterOptions -> [Block] -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Block] -> ZW m Text
blockListToZimWiki WriterOptions
opts [Block]
items
(WriterState -> WriterState) -> StateT WriterState m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((WriterState -> WriterState) -> StateT WriterState m ())
-> (WriterState -> WriterState) -> StateT WriterState m ()
forall a b. (a -> b) -> a -> b
$ \WriterState
s -> WriterState
s{ stIndent = indent }
Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ZW m Text) -> Text -> ZW m Text
forall a b. (a -> b) -> a -> b
$ Text
indent Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"* " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
contents
orderedListItemToZimWiki :: PandocMonad m
=> WriterOptions -> Int -> [Block] -> ZW m Text
orderedListItemToZimWiki :: forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Int -> [Block] -> ZW m Text
orderedListItemToZimWiki WriterOptions
opts Int
itemnum [Block]
items = do
Text
indent <- (WriterState -> Text) -> ZW m Text
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Text
stIndent
(WriterState -> WriterState) -> StateT WriterState m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((WriterState -> WriterState) -> StateT WriterState m ())
-> (WriterState -> WriterState) -> StateT WriterState m ()
forall a b. (a -> b) -> a -> b
$ \WriterState
s -> WriterState
s { stIndent = indent <> "\t" }
Text
contents <- WriterOptions -> [Block] -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Block] -> ZW m Text
blockListToZimWiki WriterOptions
opts [Block]
items
(WriterState -> WriterState) -> StateT WriterState m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((WriterState -> WriterState) -> StateT WriterState m ())
-> (WriterState -> WriterState) -> StateT WriterState m ()
forall a b. (a -> b) -> a -> b
$ \WriterState
s -> WriterState
s{ stIndent = indent }
Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ZW m Text) -> Text -> ZW m Text
forall a b. (a -> b) -> a -> b
$ Text
indent Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (Int -> String
forall a. Show a => a -> String
show Int
itemnum) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
". " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
contents
tableItemToZimWiki :: PandocMonad m
=> WriterOptions -> Alignment -> [Block] -> ZW m Text
tableItemToZimWiki :: forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Alignment -> [Block] -> ZW m Text
tableItemToZimWiki WriterOptions
opts Alignment
align' [Block]
item = do
let mkcell :: a -> a
mkcell a
x = (if Alignment
align' Alignment -> Alignment -> Bool
forall a. Eq a => a -> a -> Bool
== Alignment
AlignRight Bool -> Bool -> Bool
|| Alignment
align' Alignment -> Alignment -> Bool
forall a. Eq a => a -> a -> Bool
== Alignment
AlignCenter
then a
" "
else a
"") a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
x a -> a -> a
forall a. Semigroup a => a -> a -> a
<>
(if Alignment
align' Alignment -> Alignment -> Bool
forall a. Eq a => a -> a -> Bool
== Alignment
AlignLeft Bool -> Bool -> Bool
|| Alignment
align' Alignment -> Alignment -> Bool
forall a. Eq a => a -> a -> Bool
== Alignment
AlignCenter
then a
" "
else a
"")
(WriterState -> WriterState) -> StateT WriterState m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((WriterState -> WriterState) -> StateT WriterState m ())
-> (WriterState -> WriterState) -> StateT WriterState m ()
forall a b. (a -> b) -> a -> b
$ \WriterState
s -> WriterState
s { stInTable = True }
Text
contents <- WriterOptions -> [Block] -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Block] -> ZW m Text
blockListToZimWiki WriterOptions
opts [Block]
item
(WriterState -> WriterState) -> StateT WriterState m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((WriterState -> WriterState) -> StateT WriterState m ())
-> (WriterState -> WriterState) -> StateT WriterState m ()
forall a b. (a -> b) -> a -> b
$ \WriterState
s -> WriterState
s { stInTable = False }
Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ZW m Text) -> Text -> ZW m Text
forall a b. (a -> b) -> a -> b
$ Text -> Text
forall {a}. (Semigroup a, IsString a) => a -> a
mkcell Text
contents
blockListToZimWiki :: PandocMonad m
=> WriterOptions -> [Block] -> ZW m Text
blockListToZimWiki :: forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Block] -> ZW m Text
blockListToZimWiki WriterOptions
opts [Block]
blocks = [Text] -> Text
vcat ([Text] -> Text)
-> StateT WriterState m [Text] -> StateT WriterState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Block -> StateT WriterState m Text)
-> [Block] -> StateT WriterState m [Text]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (WriterOptions -> Block -> StateT WriterState m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Block -> ZW m Text
blockToZimWiki WriterOptions
opts) [Block]
blocks
inlineListToZimWiki :: PandocMonad m
=> WriterOptions -> [Inline] -> ZW m Text
inlineListToZimWiki :: forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ZW m Text
inlineListToZimWiki WriterOptions
opts [Inline]
lst = [Text] -> Text
T.concat ([Text] -> Text)
-> StateT WriterState m [Text] -> StateT WriterState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Inline -> StateT WriterState m Text)
-> [Inline] -> StateT WriterState m [Text]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (WriterOptions -> Inline -> StateT WriterState m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Inline -> ZW m Text
inlineToZimWiki WriterOptions
opts) [Inline]
lst
inlineToZimWiki :: PandocMonad m
=> WriterOptions -> Inline -> ZW m Text
inlineToZimWiki :: forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Inline -> ZW m Text
inlineToZimWiki WriterOptions
opts (Emph [Inline]
lst) = do
Text
contents <- WriterOptions -> [Inline] -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ZW m Text
inlineListToZimWiki WriterOptions
opts [Inline]
lst
Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ZW m Text) -> Text -> ZW m Text
forall a b. (a -> b) -> a -> b
$ Text
"//" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
contents Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"//"
inlineToZimWiki WriterOptions
opts (Underline [Inline]
lst) = do
Text
contents <- WriterOptions -> [Inline] -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ZW m Text
inlineListToZimWiki WriterOptions
opts [Inline]
lst
Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ZW m Text) -> Text -> ZW m Text
forall a b. (a -> b) -> a -> b
$ Text
"__" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
contents Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"__"
inlineToZimWiki WriterOptions
opts (Strong [Inline]
lst) = do
Text
contents <- WriterOptions -> [Inline] -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ZW m Text
inlineListToZimWiki WriterOptions
opts [Inline]
lst
Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ZW m Text) -> Text -> ZW m Text
forall a b. (a -> b) -> a -> b
$ Text
"**" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
contents Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"**"
inlineToZimWiki WriterOptions
opts (Strikeout [Inline]
lst) = do
Text
contents <- WriterOptions -> [Inline] -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ZW m Text
inlineListToZimWiki WriterOptions
opts [Inline]
lst
Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ZW m Text) -> Text -> ZW m Text
forall a b. (a -> b) -> a -> b
$ Text
"~~" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
contents Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"~~"
inlineToZimWiki WriterOptions
opts (Superscript [Inline]
lst) = do
Text
contents <- WriterOptions -> [Inline] -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ZW m Text
inlineListToZimWiki WriterOptions
opts [Inline]
lst
Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ZW m Text) -> Text -> ZW m Text
forall a b. (a -> b) -> a -> b
$ Text
"^{" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
contents Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"}"
inlineToZimWiki WriterOptions
opts (Subscript [Inline]
lst) = do
Text
contents <- WriterOptions -> [Inline] -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ZW m Text
inlineListToZimWiki WriterOptions
opts [Inline]
lst
Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ZW m Text) -> Text -> ZW m Text
forall a b. (a -> b) -> a -> b
$ Text
"_{" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
contents Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"}"
inlineToZimWiki WriterOptions
opts (Quoted QuoteType
SingleQuote [Inline]
lst) = do
Text
contents <- WriterOptions -> [Inline] -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ZW m Text
inlineListToZimWiki WriterOptions
opts [Inline]
lst
Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ZW m Text) -> Text -> ZW m Text
forall a b. (a -> b) -> a -> b
$ Text
"\8216" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
contents Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\8217"
inlineToZimWiki WriterOptions
opts (Quoted QuoteType
DoubleQuote [Inline]
lst) = do
Text
contents <- WriterOptions -> [Inline] -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ZW m Text
inlineListToZimWiki WriterOptions
opts [Inline]
lst
Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ZW m Text) -> Text -> ZW m Text
forall a b. (a -> b) -> a -> b
$ Text
"\8220" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
contents Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\8221"
inlineToZimWiki WriterOptions
opts (Span Attr
_attrs [Inline]
ils) = WriterOptions -> [Inline] -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ZW m Text
inlineListToZimWiki WriterOptions
opts [Inline]
ils
inlineToZimWiki WriterOptions
opts (SmallCaps [Inline]
lst) = WriterOptions -> [Inline] -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ZW m Text
inlineListToZimWiki WriterOptions
opts [Inline]
lst
inlineToZimWiki WriterOptions
opts (Cite [Citation]
_ [Inline]
lst) = WriterOptions -> [Inline] -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ZW m Text
inlineListToZimWiki WriterOptions
opts [Inline]
lst
inlineToZimWiki WriterOptions
_ (Code Attr
_ Text
str) = Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ZW m Text) -> Text -> ZW m Text
forall a b. (a -> b) -> a -> b
$ Text
"''" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
str Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"''"
inlineToZimWiki WriterOptions
_ (Str Text
str) = do
Bool
inTable <- (WriterState -> Bool) -> StateT WriterState m Bool
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Bool
stInTable
Bool
inLink <- (WriterState -> Bool) -> StateT WriterState m Bool
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Bool
stInLink
if Bool
inTable
then Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ZW m Text) -> Text -> ZW m Text
forall a b. (a -> b) -> a -> b
$ HasCallStack => Text -> Text -> Text -> Text
Text -> Text -> Text -> Text
T.replace Text
"|" Text
"\\|" (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
escapeText (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text
str
else
if Bool
inLink
then Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
str
else Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ZW m Text) -> Text -> ZW m Text
forall a b. (a -> b) -> a -> b
$ Text -> Text
escapeText Text
str
inlineToZimWiki WriterOptions
_ (Math MathType
mathType Text
str) = Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ZW m Text) -> Text -> ZW m Text
forall a b. (a -> b) -> a -> b
$ Text
delim Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
str Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
delim
where delim :: Text
delim = case MathType
mathType of
MathType
DisplayMath -> Text
"$$"
MathType
InlineMath -> Text
"$"
inlineToZimWiki WriterOptions
opts il :: Inline
il@(RawInline Format
f Text
str)
| Format
f Format -> Format -> Bool
forall a. Eq a => a -> a -> Bool
== Text -> Format
Format Text
"zimwiki" = Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
str
| Format
f Format -> Format -> Bool
forall a. Eq a => a -> a -> Bool
== Text -> Format
Format Text
"html" = WriterOptions -> Text -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> Text -> ZW m Text
indentFromHTML WriterOptions
opts Text
str
| Bool
otherwise = do
LogMessage -> StateT WriterState m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> StateT WriterState m ())
-> LogMessage -> StateT WriterState m ()
forall a b. (a -> b) -> a -> b
$ Inline -> LogMessage
InlineNotRendered Inline
il
Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
""
inlineToZimWiki WriterOptions
_ Inline
LineBreak = do
Bool
inTable <- (WriterState -> Bool) -> StateT WriterState m Bool
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Bool
stInTable
if Bool
inTable
then Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
"\\n"
else Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
"\n"
inlineToZimWiki WriterOptions
opts Inline
SoftBreak =
case WriterOptions -> WrapOption
writerWrapText WriterOptions
opts of
WrapOption
WrapNone -> Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
" "
WrapOption
WrapAuto -> Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
" "
WrapOption
WrapPreserve -> Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
"\n"
inlineToZimWiki WriterOptions
_ Inline
Space = Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
" "
inlineToZimWiki WriterOptions
opts (Link Attr
_ [Inline]
txt (Text
src, Text
_)) = do
Bool
inTable <- (WriterState -> Bool) -> StateT WriterState m Bool
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Bool
stInTable
(WriterState -> WriterState) -> StateT WriterState m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((WriterState -> WriterState) -> StateT WriterState m ())
-> (WriterState -> WriterState) -> StateT WriterState m ()
forall a b. (a -> b) -> a -> b
$ \WriterState
s -> WriterState
s { stInLink = True }
Text
label <- WriterOptions -> [Inline] -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ZW m Text
inlineListToZimWiki WriterOptions
opts ([Inline] -> ZW m Text) -> [Inline] -> ZW m Text
forall a b. (a -> b) -> a -> b
$ [Inline] -> [Inline]
forall a. Walkable Inline a => a -> [Inline]
removeFormatting [Inline]
txt
(WriterState -> WriterState) -> StateT WriterState m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((WriterState -> WriterState) -> StateT WriterState m ())
-> (WriterState -> WriterState) -> StateT WriterState m ()
forall a b. (a -> b) -> a -> b
$ \WriterState
s -> WriterState
s { stInLink = False }
let label' :: Text
label'= if Bool
inTable
then Text
""
else Text
"|"Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>Text
label
case [Inline]
txt of
[Str Text
s] | Text
"mailto:" Text -> Text -> Bool
`T.isPrefixOf` Text
src -> Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ZW m Text) -> Text -> ZW m Text
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
">"
| Text -> Text
escapeURI Text
s Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
src -> Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
src
[Inline]
_ -> if Text -> Bool
isURI Text
src
then Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ZW m Text) -> Text -> ZW m Text
forall a b. (a -> b) -> a -> b
$ Text
"[[" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
src Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
label' Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"]]"
else Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ZW m Text) -> Text -> ZW m Text
forall a b. (a -> b) -> a -> b
$ Text
"[[" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
src' Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
label' Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"]]"
where
src' :: Text
src' = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
src (Maybe Text -> Text) -> Maybe Text -> Text
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Maybe Text
T.stripPrefix Text
"/" Text
src
inlineToZimWiki WriterOptions
opts (Image Attr
attr [Inline]
alt (Text
source, Text
tit)) = do
Text
alt' <- WriterOptions -> [Inline] -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Inline] -> ZW m Text
inlineListToZimWiki WriterOptions
opts [Inline]
alt
Bool
inTable <- (WriterState -> Bool) -> StateT WriterState m Bool
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets WriterState -> Bool
stInTable
let txt :: Text
txt = case (Text
tit, [Inline]
alt, Bool
inTable) of
(Text
"",[], Bool
_) -> Text
""
(Text
"", [Inline]
_, Bool
False ) -> Text
"|" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
alt'
(Text
_ , [Inline]
_, Bool
False ) -> Text
"|" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
tit
(Text
_ , [Inline]
_, Bool
True ) -> Text
""
Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ZW m Text) -> Text -> ZW m Text
forall a b. (a -> b) -> a -> b
$ Text
"{{" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
source Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> WriterOptions -> Attr -> Text
imageDims WriterOptions
opts Attr
attr Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
txt Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"}}"
inlineToZimWiki WriterOptions
opts (Note [Block]
contents) = do
Text
contents' <- WriterOptions -> [Block] -> ZW m Text
forall (m :: * -> *).
PandocMonad m =>
WriterOptions -> [Block] -> ZW m Text
blockListToZimWiki WriterOptions
opts [Block]
contents
Text -> ZW m Text
forall a. a -> StateT WriterState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ZW m Text) -> Text -> ZW m Text
forall a b. (a -> b) -> a -> b
$ Text
" **{Note:** " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
trimr Text
contents' Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"**}**"
imageDims :: WriterOptions -> Attr -> Text
imageDims :: WriterOptions -> Attr -> Text
imageDims WriterOptions
opts Attr
attr = Maybe Text -> Maybe Text -> Text
forall {a}. (Semigroup a, IsString a) => Maybe a -> Maybe a -> a
go (Maybe Dimension -> Maybe Text
toPx (Maybe Dimension -> Maybe Text) -> Maybe Dimension -> Maybe Text
forall a b. (a -> b) -> a -> b
$ Direction -> Attr -> Maybe Dimension
dimension Direction
Width Attr
attr) (Maybe Dimension -> Maybe Text
toPx (Maybe Dimension -> Maybe Text) -> Maybe Dimension -> Maybe Text
forall a b. (a -> b) -> a -> b
$ Direction -> Attr -> Maybe Dimension
dimension Direction
Height Attr
attr)
where
toPx :: Maybe Dimension -> Maybe Text
toPx = (Dimension -> Text) -> Maybe Dimension -> Maybe Text
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (WriterOptions -> Dimension -> Text
showInPixel WriterOptions
opts) (Maybe Dimension -> Maybe Text)
-> (Maybe Dimension -> Maybe Dimension)
-> Maybe Dimension
-> Maybe Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe Dimension -> Maybe Dimension
checkPct
checkPct :: Maybe Dimension -> Maybe Dimension
checkPct (Just (Percent Double
_)) = Maybe Dimension
forall a. Maybe a
Nothing
checkPct Maybe Dimension
maybeDim = Maybe Dimension
maybeDim
go :: Maybe a -> Maybe a -> a
go (Just a
w) Maybe a
Nothing = a
"?" a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
w
go (Just a
w) (Just a
h) = a
"?" a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
w a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
"x" a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
h
go Maybe a
Nothing (Just a
h) = a
"?0x" a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
h
go Maybe a
Nothing Maybe a
Nothing = a
""