{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ViewPatterns #-}
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 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 (escapeURI, isURI, linesToPara, removeFormatting, trimr)
import Text.Pandoc.Templates (renderTemplate)
import Text.Pandoc.Writers.Shared (defField, metaToContext)
data WriterState = WriterState {
stIndent :: Text,
stInTable :: Bool,
stInLink :: Bool
}
instance Default WriterState where
def = WriterState { stIndent = "", stInTable = False, stInLink = False }
type ZW = StateT WriterState
writeZimWiki :: PandocMonad m => WriterOptions -> Pandoc -> m Text
writeZimWiki opts document = evalStateT (pandocToZimWiki opts document) def
pandocToZimWiki :: PandocMonad m => WriterOptions -> Pandoc -> ZW m Text
pandocToZimWiki opts (Pandoc meta blocks) = do
metadata <- metaToContext opts
(fmap (literal . trimr) . blockListToZimWiki opts)
(fmap (literal . trimr) . inlineListToZimWiki opts)
meta
main <- blockListToZimWiki opts blocks
let context = defField "body" main
$ defField "toc" (writerTableOfContents opts) metadata
return $
case writerTemplate opts of
Just tpl -> render Nothing $ renderTemplate tpl context
Nothing -> main
escapeText :: Text -> Text
escapeText = T.replace "__" "''__''" .
T.replace "**" "''**''" .
T.replace "~~" "''~~''" .
T.replace "//" "''//''"
blockToZimWiki :: PandocMonad m => WriterOptions -> Block -> ZW m Text
blockToZimWiki _ Null = return ""
blockToZimWiki opts (Div _attrs bs) = do
contents <- blockListToZimWiki opts bs
return $ contents <> "\n"
blockToZimWiki opts (Plain inlines) = inlineListToZimWiki opts inlines
blockToZimWiki opts (Para [Image attr txt (src,T.stripPrefix "fig:" -> Just tit)]) = do
capt <- if null txt
then return ""
else (" " <>) `fmap` inlineListToZimWiki opts txt
let opt = if null txt
then ""
else "|" <> if T.null tit then capt else tit <> capt
return $ "{{" <> src <> imageDims opts attr <> opt <> "}}\n"
blockToZimWiki opts (Para inlines) = do
indent <- gets stIndent
contents <- inlineListToZimWiki opts inlines
return $ contents <> if T.null indent then "\n" else ""
blockToZimWiki opts (LineBlock lns) =
blockToZimWiki opts $ linesToPara lns
blockToZimWiki opts b@(RawBlock f str)
| f == Format "zimwiki" = return str
| f == Format "html" = indentFromHTML opts str
| otherwise = do
report $ BlockNotRendered b
return ""
blockToZimWiki _ HorizontalRule = return "\n----\n"
blockToZimWiki opts (Header level _ inlines) = do
contents <- inlineListToZimWiki opts $ removeFormatting inlines
let eqs = T.replicate ( 7 - level ) "="
return $ eqs <> " " <> contents <> " " <> eqs <> "\n"
blockToZimWiki _ (CodeBlock (_,classes,_) str) = do
let langal = [("javascript", "js"), ("bash", "sh"), ("winbatch", "dosbatch")]
let langmap = Map.fromList langal
return $ case classes of
[] -> "'''\n" <> cleanupCode str <> "\n'''\n"
(x:_) -> "{{{code: lang=\"" <>
fromMaybe x (Map.lookup x langmap) <> "\" linenumbers=\"True\"\n" <> str <> "\n}}}\n"
blockToZimWiki opts (BlockQuote blocks) = do
contents <- blockListToZimWiki opts blocks
return $ T.unlines $ map ("> " <>) $ T.lines contents
blockToZimWiki opts (Table capt aligns _ headers rows) = do
captionDoc <- if null capt
then return ""
else do
c <- inlineListToZimWiki opts capt
return $ "" <> c <> "\n"
headers' <- if all null headers
then zipWithM (tableItemToZimWiki opts) aligns (head rows)
else mapM (inlineListToZimWiki opts . removeFormatting)headers
rows' <- mapM (zipWithM (tableItemToZimWiki opts) aligns) rows
let widths = map (maximum . map T.length) $ transpose (headers':rows')
let padTo (width, al) s =
case width - T.length s of
x | x > 0 ->
if al == AlignLeft || al == AlignDefault
then s <> T.replicate x " "
else if al == AlignRight
then T.replicate x " " <> s
else T.replicate (x `div` 2) " " <>
s <> T.replicate (x - x `div` 2) " "
| otherwise -> s
let borderCell (width, al) _
| al == AlignLeft = ":"<> T.replicate (width-1) "-"
| al == AlignDefault = T.replicate width "-"
| al == AlignRight = T.replicate (width-1) "-" <> ":"
| otherwise = ":" <> T.replicate (width-2) "-" <> ":"
let underheader = "|" <> T.intercalate "|" (zipWith borderCell (zip widths aligns) headers') <> "|"
let renderRow cells = "|" <> T.intercalate "|" (zipWith padTo (zip widths aligns) cells) <> "|"
return $ captionDoc <>
(if null headers' then "" else renderRow headers' <> "\n") <> underheader <> "\n" <>
T.unlines (map renderRow rows')
blockToZimWiki opts (BulletList items) = do
contents <- mapM (listItemToZimWiki opts) items
indent <- gets stIndent
return $ vcat contents <> if T.null indent then "\n" else ""
blockToZimWiki opts (OrderedList _ items) = do
contents <- zipWithM (orderedListItemToZimWiki opts) [1..] items
indent <- gets stIndent
return $ vcat contents <> if T.null indent then "\n" else ""
blockToZimWiki opts (DefinitionList items) = do
contents <- mapM (definitionListItemToZimWiki opts) items
return $ vcat contents
definitionListItemToZimWiki :: PandocMonad m
=> WriterOptions
-> ([Inline],[[Block]])
-> ZW m Text
definitionListItemToZimWiki opts (label, items) = do
labelText <- inlineListToZimWiki opts label
contents <- mapM (blockListToZimWiki opts) items
indent <- gets stIndent
return $ indent <> "* **" <> labelText <> "** " <> T.concat contents
indentFromHTML :: PandocMonad m => WriterOptions -> Text -> ZW m Text
indentFromHTML _ str = do
indent <- gets stIndent
if "<li>" `T.isInfixOf` str
then return indent
else if "</li>" `T.isInfixOf` str
then return "\n"
else if "<li value=" `T.isInfixOf` str
then return ""
else if "<ol>" `T.isInfixOf` str
then do
let olcount=countSubStrs "<ol>" str
modify $ \s -> s { stIndent = stIndent s <>
T.replicate olcount "\t" }
return ""
else if "</ol>" `T.isInfixOf` str
then do
let olcount=countSubStrs "/<ol>" str
modify $ \s -> s{ stIndent = T.drop olcount (stIndent s) }
return ""
else return ""
countSubStrs :: Text -> Text -> Int
countSubStrs sub str = length $ T.breakOnAll sub str
cleanupCode :: Text -> Text
cleanupCode = T.replace "<nowiki>" "" . T.replace "</nowiki>" ""
vcat :: [Text] -> Text
vcat = T.intercalate "\n"
listItemToZimWiki :: PandocMonad m => WriterOptions -> [Block] -> ZW m Text
listItemToZimWiki opts items = do
indent <- gets stIndent
modify $ \s -> s { stIndent = indent <> "\t" }
contents <- blockListToZimWiki opts items
modify $ \s -> s{ stIndent = indent }
return $ indent <> "* " <> contents
orderedListItemToZimWiki :: PandocMonad m
=> WriterOptions -> Int -> [Block] -> ZW m Text
orderedListItemToZimWiki opts itemnum items = do
indent <- gets stIndent
modify $ \s -> s { stIndent = indent <> "\t" }
contents <- blockListToZimWiki opts items
modify $ \s -> s{ stIndent = indent }
return $ indent <> T.pack (show itemnum) <> ". " <> contents
tableItemToZimWiki :: PandocMonad m
=> WriterOptions -> Alignment -> [Block] -> ZW m Text
tableItemToZimWiki opts align' item = do
let mkcell x = (if align' == AlignRight || align' == AlignCenter
then " "
else "") <> x <>
(if align' == AlignLeft || align' == AlignCenter
then " "
else "")
modify $ \s -> s { stInTable = True }
contents <- blockListToZimWiki opts item
modify $ \s -> s { stInTable = False }
return $ mkcell contents
blockListToZimWiki :: PandocMonad m
=> WriterOptions -> [Block] -> ZW m Text
blockListToZimWiki opts blocks = vcat <$> mapM (blockToZimWiki opts) blocks
inlineListToZimWiki :: PandocMonad m
=> WriterOptions -> [Inline] -> ZW m Text
inlineListToZimWiki opts lst = T.concat <$> mapM (inlineToZimWiki opts) lst
inlineToZimWiki :: PandocMonad m
=> WriterOptions -> Inline -> ZW m Text
inlineToZimWiki opts (Emph lst) = do
contents <- inlineListToZimWiki opts lst
return $ "//" <> contents <> "//"
inlineToZimWiki opts (Strong lst) = do
contents <- inlineListToZimWiki opts lst
return $ "**" <> contents <> "**"
inlineToZimWiki opts (Strikeout lst) = do
contents <- inlineListToZimWiki opts lst
return $ "~~" <> contents <> "~~"
inlineToZimWiki opts (Superscript lst) = do
contents <- inlineListToZimWiki opts lst
return $ "^{" <> contents <> "}"
inlineToZimWiki opts (Subscript lst) = do
contents <- inlineListToZimWiki opts lst
return $ "_{" <> contents <> "}"
inlineToZimWiki opts (Quoted SingleQuote lst) = do
contents <- inlineListToZimWiki opts lst
return $ "\8216" <> contents <> "\8217"
inlineToZimWiki opts (Quoted DoubleQuote lst) = do
contents <- inlineListToZimWiki opts lst
return $ "\8220" <> contents <> "\8221"
inlineToZimWiki opts (Span _attrs ils) = inlineListToZimWiki opts ils
inlineToZimWiki opts (SmallCaps lst) = inlineListToZimWiki opts lst
inlineToZimWiki opts (Cite _ lst) = inlineListToZimWiki opts lst
inlineToZimWiki _ (Code _ str) = return $ "''" <> str <> "''"
inlineToZimWiki _ (Str str) = do
inTable <- gets stInTable
inLink <- gets stInLink
if inTable
then return $ T.replace "|" "\\|" . escapeText $ str
else
if inLink
then return str
else return $ escapeText str
inlineToZimWiki _ (Math mathType str) = return $ delim <> str <> delim
where delim = case mathType of
DisplayMath -> "$$"
InlineMath -> "$"
inlineToZimWiki opts il@(RawInline f str)
| f == Format "zimwiki" = return str
| f == Format "html" = indentFromHTML opts str
| otherwise = do
report $ InlineNotRendered il
return ""
inlineToZimWiki _ LineBreak = do
inTable <- gets stInTable
if inTable
then return "\\n"
else return "\n"
inlineToZimWiki opts SoftBreak =
case writerWrapText opts of
WrapNone -> return " "
WrapAuto -> return " "
WrapPreserve -> return "\n"
inlineToZimWiki _ Space = return " "
inlineToZimWiki opts (Link _ txt (src, _)) = do
inTable <- gets stInTable
modify $ \s -> s { stInLink = True }
label <- inlineListToZimWiki opts $ removeFormatting txt
modify $ \s -> s { stInLink = False }
let label'= if inTable
then ""
else "|"<>label
case txt of
[Str s] | "mailto:" `T.isPrefixOf` src -> return $ "<" <> s <> ">"
| escapeURI s == src -> return src
_ -> if isURI src
then return $ "[[" <> src <> label' <> "]]"
else return $ "[[" <> src' <> label' <> "]]"
where
src' = fromMaybe src $ T.stripPrefix "/" src
inlineToZimWiki opts (Image attr alt (source, tit)) = do
alt' <- inlineListToZimWiki opts alt
inTable <- gets stInTable
let txt = case (tit, alt, inTable) of
("",[], _) -> ""
("", _, False ) -> "|" <> alt'
(_ , _, False ) -> "|" <> tit
(_ , _, True ) -> ""
return $ "{{" <> source <> imageDims opts attr <> txt <> "}}"
inlineToZimWiki opts (Note contents) = do
contents' <- blockListToZimWiki opts contents
return $ " **{Note:** " <> trimr contents' <> "**}**"
imageDims :: WriterOptions -> Attr -> Text
imageDims opts attr = go (toPx $ dimension Width attr) (toPx $ dimension Height attr)
where
toPx = fmap (showInPixel opts) . checkPct
checkPct (Just (Percent _)) = Nothing
checkPct maybeDim = maybeDim
go (Just w) Nothing = "?" <> w
go (Just w) (Just h) = "?" <> w <> "x" <> h
go Nothing (Just h) = "?0x" <> h
go Nothing Nothing = ""