2013-07-14 13:40:27 +01:00
|
|
|
{-
|
2014-06-29 21:21:00 +01:00
|
|
|
Copyright (C) 2008-2014 John MacFarlane <jgm@berkeley.edu>
|
2013-07-14 13:40:27 +01:00
|
|
|
|
|
|
|
This program is free software; you can redistribute it and/or modify
|
|
|
|
it under the terms of the GNU General Public License as published by
|
|
|
|
the Free Software Foundation; either version 2 of the License, or
|
|
|
|
(at your option) any later version.
|
|
|
|
|
|
|
|
This program is distributed in the hope that it will be useful,
|
|
|
|
but WITHOUT ANY WARRANTY; without even the implied warranty of
|
|
|
|
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
|
|
|
GNU General Public License for more details.
|
|
|
|
|
|
|
|
You should have received a copy of the GNU General Public License
|
|
|
|
along with this program; if not, write to the Free Software
|
|
|
|
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
|
|
|
-}
|
|
|
|
|
|
|
|
{- |
|
|
|
|
Module : Text.Pandoc.Writers.DokuWiki
|
2014-06-29 21:21:00 +01:00
|
|
|
Copyright : Copyright (C) 2008-2014 John MacFarlane
|
2013-07-14 13:40:27 +01:00
|
|
|
License : GNU GPL, version 2 or above
|
|
|
|
|
2014-07-08 21:18:31 +01:00
|
|
|
Maintainer : Clare Macrae <clare.macrae@googlemail.com>
|
2013-07-14 13:40:27 +01:00
|
|
|
Stability : alpha
|
|
|
|
Portability : portable
|
|
|
|
|
|
|
|
Conversion of 'Pandoc' documents to DokuWiki markup.
|
|
|
|
|
|
|
|
DokuWiki: <https://www.dokuwiki.org/dokuwiki>
|
|
|
|
-}
|
2013-07-26 22:38:13 +01:00
|
|
|
|
|
|
|
{-
|
2014-07-02 21:26:24 +01:00
|
|
|
[ ] Implement nested blockquotes (currently only ever does one level)
|
2013-08-17 08:48:29 +01:00
|
|
|
[ ] Implement alignment of text in tables
|
2013-07-26 22:38:13 +01:00
|
|
|
[ ] Implement comments
|
|
|
|
[ ] Work through the Dokuwiki spec, and check I've not missed anything out
|
2013-07-26 22:49:19 +01:00
|
|
|
[ ] Remove dud/duplicate code
|
2013-07-26 22:38:13 +01:00
|
|
|
-}
|
|
|
|
|
2013-07-14 13:40:27 +01:00
|
|
|
module Text.Pandoc.Writers.DokuWiki ( writeDokuWiki ) where
|
|
|
|
import Text.Pandoc.Definition
|
|
|
|
import Text.Pandoc.Options
|
|
|
|
import Text.Pandoc.Shared
|
|
|
|
import Text.Pandoc.Writers.Shared
|
|
|
|
import Text.Pandoc.Templates (renderTemplate')
|
|
|
|
import Data.List ( intersect, intercalate )
|
|
|
|
import Network.URI ( isURI )
|
|
|
|
import Control.Monad.State
|
|
|
|
|
|
|
|
data WriterState = WriterState {
|
|
|
|
stNotes :: Bool -- True if there are notes
|
2013-08-28 08:09:42 +01:00
|
|
|
, stIndent :: String -- Indent after the marker at the beginning of list items
|
2013-07-14 13:40:27 +01:00
|
|
|
, stUseTags :: Bool -- True if we should use HTML tags because we're in a complex list
|
|
|
|
}
|
|
|
|
|
|
|
|
-- | Convert Pandoc to DokuWiki.
|
|
|
|
writeDokuWiki :: WriterOptions -> Pandoc -> String
|
|
|
|
writeDokuWiki opts document =
|
|
|
|
evalState (pandocToDokuWiki opts document)
|
2013-08-28 08:09:42 +01:00
|
|
|
(WriterState { stNotes = False, stIndent = "", stUseTags = False })
|
2013-07-14 13:40:27 +01:00
|
|
|
|
|
|
|
-- | Return DokuWiki representation of document.
|
|
|
|
pandocToDokuWiki :: WriterOptions -> Pandoc -> State WriterState String
|
|
|
|
pandocToDokuWiki opts (Pandoc meta blocks) = do
|
|
|
|
metadata <- metaToJSON opts
|
|
|
|
(fmap trimr . blockListToDokuWiki opts)
|
|
|
|
(inlineListToDokuWiki opts)
|
|
|
|
meta
|
|
|
|
body <- blockListToDokuWiki opts blocks
|
|
|
|
notesExist <- get >>= return . stNotes
|
|
|
|
let notes = if notesExist
|
2013-07-28 19:19:33 +01:00
|
|
|
then "" -- TODO Was "\n<references />" Check whether I can really remove this:
|
|
|
|
-- if it is definitely to do with footnotes, can remove this whole bit
|
2013-07-14 13:40:27 +01:00
|
|
|
else ""
|
|
|
|
let main = body ++ notes
|
|
|
|
let context = defField "body" main
|
|
|
|
$ defField "toc" (writerTableOfContents opts)
|
|
|
|
$ metadata
|
|
|
|
if writerStandalone opts
|
|
|
|
then return $ renderTemplate' (writerTemplate opts) context
|
|
|
|
else return main
|
|
|
|
|
2014-07-13 15:32:16 -07:00
|
|
|
-- | Escape special characters for DokuWiki.
|
2013-08-17 22:28:07 +01:00
|
|
|
escapeString :: String -> String
|
2014-07-13 15:32:16 -07:00
|
|
|
escapeString = substitute "__" "%%__%%" .
|
|
|
|
substitute "**" "%%**%%" .
|
|
|
|
substitute "//" "%%//%%"
|
2013-08-17 22:28:07 +01:00
|
|
|
|
2013-07-14 13:40:27 +01:00
|
|
|
-- | Convert Pandoc block element to DokuWiki.
|
|
|
|
blockToDokuWiki :: WriterOptions -- ^ Options
|
|
|
|
-> Block -- ^ Block element
|
|
|
|
-> State WriterState String
|
|
|
|
|
|
|
|
blockToDokuWiki _ Null = return ""
|
|
|
|
|
2014-07-01 21:42:21 +01:00
|
|
|
blockToDokuWiki opts (Div _attrs bs) = do
|
2014-06-29 21:15:17 +01:00
|
|
|
contents <- blockListToDokuWiki opts bs
|
2014-07-01 21:42:21 +01:00
|
|
|
return $ contents ++ "\n"
|
2014-06-29 21:15:17 +01:00
|
|
|
|
2013-07-14 13:40:27 +01:00
|
|
|
blockToDokuWiki opts (Plain inlines) =
|
|
|
|
inlineListToDokuWiki opts inlines
|
|
|
|
|
|
|
|
-- title beginning with fig: indicates that the image is a figure
|
2013-07-15 19:29:39 +01:00
|
|
|
-- dokuwiki doesn't support captions - so combine together alt and caption into alt
|
2013-07-14 13:40:27 +01:00
|
|
|
blockToDokuWiki opts (Para [Image txt (src,'f':'i':'g':':':tit)]) = do
|
|
|
|
capt <- if null txt
|
|
|
|
then return ""
|
2013-07-15 19:29:39 +01:00
|
|
|
else (" " ++) `fmap` inlineListToDokuWiki opts txt
|
2013-07-14 13:40:27 +01:00
|
|
|
let opt = if null txt
|
|
|
|
then ""
|
2013-07-15 19:29:39 +01:00
|
|
|
else "|" ++ if null tit then capt else tit ++ capt
|
|
|
|
return $ "{{:" ++ src ++ opt ++ "}}\n"
|
2013-07-14 13:40:27 +01:00
|
|
|
|
|
|
|
blockToDokuWiki opts (Para inlines) = do
|
|
|
|
useTags <- get >>= return . stUseTags
|
2013-08-28 08:09:42 +01:00
|
|
|
indent <- get >>= return . stIndent
|
2013-07-14 13:40:27 +01:00
|
|
|
contents <- inlineListToDokuWiki opts inlines
|
|
|
|
return $ if useTags
|
|
|
|
then "<p>" ++ contents ++ "</p>"
|
2013-08-28 08:09:42 +01:00
|
|
|
else contents ++ if null indent then "\n" else ""
|
2013-07-14 13:40:27 +01:00
|
|
|
|
2014-06-29 21:15:17 +01:00
|
|
|
blockToDokuWiki _ (RawBlock f str)
|
2014-07-13 15:24:52 -07:00
|
|
|
| f == Format "dokuwiki" = return str
|
2014-07-13 15:28:47 -07:00
|
|
|
-- See https://www.dokuwiki.org/wiki:syntax
|
|
|
|
-- use uppercase HTML tag for block-level content:
|
|
|
|
| f == Format "html" = return $ "<HTML>\n" ++ str ++ "\n</HTML>"
|
2014-07-13 15:24:52 -07:00
|
|
|
| otherwise = return ""
|
2013-07-14 13:40:27 +01:00
|
|
|
|
2013-07-14 15:03:40 +01:00
|
|
|
blockToDokuWiki _ HorizontalRule = return "\n----\n"
|
2013-07-14 13:40:27 +01:00
|
|
|
|
|
|
|
blockToDokuWiki opts (Header level _ inlines) = do
|
2014-07-13 14:33:10 -07:00
|
|
|
-- emphasis, links etc. not allowed in headers, apparently,
|
|
|
|
-- so we remove formatting:
|
|
|
|
contents <- inlineListToDokuWiki opts $ removeFormatting inlines
|
2013-07-14 14:24:20 +01:00
|
|
|
let eqs = replicate ( 7 - level ) '='
|
2013-07-14 13:40:27 +01:00
|
|
|
return $ eqs ++ " " ++ contents ++ " " ++ eqs ++ "\n"
|
|
|
|
|
|
|
|
blockToDokuWiki _ (CodeBlock (_,classes,_) str) = do
|
|
|
|
let at = classes `intersect` ["actionscript", "ada", "apache", "applescript", "asm", "asp",
|
|
|
|
"autoit", "bash", "blitzbasic", "bnf", "c", "c_mac", "caddcl", "cadlisp", "cfdg", "cfm",
|
|
|
|
"cpp", "cpp-qt", "csharp", "css", "d", "delphi", "diff", "div", "dos", "eiffel", "fortran",
|
|
|
|
"freebasic", "gml", "groovy", "html4strict", "idl", "ini", "inno", "io", "java", "java5",
|
|
|
|
"javascript", "latex", "lisp", "lua", "matlab", "mirc", "mpasm", "mysql", "nsis", "objc",
|
|
|
|
"ocaml", "ocaml-brief", "oobas", "oracle8", "pascal", "perl", "php", "php-brief", "plsql",
|
|
|
|
"python", "qbasic", "rails", "reg", "robots", "ruby", "sas", "scheme", "sdlbasic",
|
|
|
|
"smalltalk", "smarty", "sql", "tcl", "", "thinbasic", "tsql", "vb", "vbnet", "vhdl",
|
|
|
|
"visualfoxpro", "winbatch", "xml", "xpp", "z80"]
|
|
|
|
let (beg, end) = if null at
|
2013-08-17 11:20:51 +01:00
|
|
|
then ("<code" ++ if null classes then ">" else " class=\"" ++ unwords classes ++ "\">", "</code>")
|
2013-07-14 13:40:27 +01:00
|
|
|
else ("<source lang=\"" ++ head at ++ "\">", "</source>")
|
2013-08-17 12:20:34 +01:00
|
|
|
return $ beg ++ str ++ end
|
2013-07-14 13:40:27 +01:00
|
|
|
|
|
|
|
blockToDokuWiki opts (BlockQuote blocks) = do
|
|
|
|
contents <- blockListToDokuWiki opts blocks
|
2014-07-02 21:26:24 +01:00
|
|
|
return $ "> " ++ contents
|
2013-07-14 13:40:27 +01:00
|
|
|
|
2013-08-11 22:22:07 +01:00
|
|
|
blockToDokuWiki opts (Table capt aligns _ headers rows') = do
|
2013-07-14 13:40:27 +01:00
|
|
|
let alignStrings = map alignmentToString aligns
|
|
|
|
captionDoc <- if null capt
|
|
|
|
then return ""
|
|
|
|
else do
|
|
|
|
c <- inlineListToDokuWiki opts capt
|
2013-08-11 22:22:07 +01:00
|
|
|
return $ "" ++ c ++ "\n"
|
2013-07-14 13:40:27 +01:00
|
|
|
head' <- if all null headers
|
|
|
|
then return ""
|
|
|
|
else do
|
2013-08-17 08:48:29 +01:00
|
|
|
hs <- tableHeaderToDokuWiki opts alignStrings 0 headers
|
2013-08-11 22:22:07 +01:00
|
|
|
return $ hs ++ "\n"
|
2013-07-14 13:40:27 +01:00
|
|
|
body' <- zipWithM (tableRowToDokuWiki opts alignStrings) [1..] rows'
|
2013-08-11 22:22:07 +01:00
|
|
|
return $ captionDoc ++ head' ++
|
|
|
|
unlines body'
|
2013-07-14 13:40:27 +01:00
|
|
|
|
|
|
|
blockToDokuWiki opts x@(BulletList items) = do
|
|
|
|
oldUseTags <- get >>= return . stUseTags
|
2013-08-28 08:09:42 +01:00
|
|
|
indent <- get >>= return . stIndent
|
2013-07-14 13:40:27 +01:00
|
|
|
let useTags = oldUseTags || not (isSimpleList x)
|
|
|
|
if useTags
|
|
|
|
then do
|
|
|
|
modify $ \s -> s { stUseTags = True }
|
|
|
|
contents <- mapM (listItemToDokuWiki opts) items
|
|
|
|
modify $ \s -> s { stUseTags = oldUseTags }
|
|
|
|
return $ "<ul>\n" ++ vcat contents ++ "</ul>\n"
|
|
|
|
else do
|
2013-08-28 08:09:42 +01:00
|
|
|
modify $ \s -> s { stIndent = stIndent s ++ " " }
|
2013-07-14 13:40:27 +01:00
|
|
|
contents <- mapM (listItemToDokuWiki opts) items
|
2013-08-28 08:09:42 +01:00
|
|
|
modify $ \s -> s { stIndent = indent }
|
|
|
|
return $ vcat contents ++ if null indent then "\n" else ""
|
2013-07-14 13:40:27 +01:00
|
|
|
|
|
|
|
blockToDokuWiki opts x@(OrderedList attribs items) = do
|
|
|
|
oldUseTags <- get >>= return . stUseTags
|
2013-08-28 08:09:42 +01:00
|
|
|
indent <- get >>= return . stIndent
|
2013-07-14 13:40:27 +01:00
|
|
|
let useTags = oldUseTags || not (isSimpleList x)
|
|
|
|
if useTags
|
|
|
|
then do
|
|
|
|
modify $ \s -> s { stUseTags = True }
|
2013-07-26 06:19:40 +01:00
|
|
|
contents <- mapM (orderedListItemToDokuWiki opts) items
|
2013-07-14 13:40:27 +01:00
|
|
|
modify $ \s -> s { stUseTags = oldUseTags }
|
|
|
|
return $ "<ol" ++ listAttribsToString attribs ++ ">\n" ++ vcat contents ++ "</ol>\n"
|
|
|
|
else do
|
2013-08-28 08:09:42 +01:00
|
|
|
modify $ \s -> s { stIndent = stIndent s ++ " " }
|
2013-07-26 06:19:40 +01:00
|
|
|
contents <- mapM (orderedListItemToDokuWiki opts) items
|
2013-08-28 08:09:42 +01:00
|
|
|
modify $ \s -> s { stIndent = indent }
|
|
|
|
return $ vcat contents ++ if null indent then "\n" else ""
|
2013-07-14 13:40:27 +01:00
|
|
|
|
2013-07-26 06:19:40 +01:00
|
|
|
-- TODO Need to decide how to make definition lists work on dokuwiki - I don't think there
|
|
|
|
-- is a specific representation of them.
|
|
|
|
-- TODO This creates double '; ; ' if there is a bullet or ordered list inside a definition list
|
2013-07-14 13:40:27 +01:00
|
|
|
blockToDokuWiki opts x@(DefinitionList items) = do
|
|
|
|
oldUseTags <- get >>= return . stUseTags
|
2013-08-28 08:09:42 +01:00
|
|
|
indent <- get >>= return . stIndent
|
2013-07-14 13:40:27 +01:00
|
|
|
let useTags = oldUseTags || not (isSimpleList x)
|
|
|
|
if useTags
|
|
|
|
then do
|
|
|
|
modify $ \s -> s { stUseTags = True }
|
|
|
|
contents <- mapM (definitionListItemToDokuWiki opts) items
|
|
|
|
modify $ \s -> s { stUseTags = oldUseTags }
|
|
|
|
return $ "<dl>\n" ++ vcat contents ++ "</dl>\n"
|
|
|
|
else do
|
2013-08-28 08:09:42 +01:00
|
|
|
modify $ \s -> s { stIndent = stIndent s ++ " " }
|
2013-07-14 13:40:27 +01:00
|
|
|
contents <- mapM (definitionListItemToDokuWiki opts) items
|
2013-08-28 08:09:42 +01:00
|
|
|
modify $ \s -> s { stIndent = indent }
|
|
|
|
return $ vcat contents ++ if null indent then "\n" else ""
|
2013-07-14 13:40:27 +01:00
|
|
|
|
|
|
|
-- Auxiliary functions for lists:
|
|
|
|
|
|
|
|
-- | Convert ordered list attributes to HTML attribute string
|
|
|
|
listAttribsToString :: ListAttributes -> String
|
|
|
|
listAttribsToString (startnum, numstyle, _) =
|
|
|
|
let numstyle' = camelCaseToHyphenated $ show numstyle
|
|
|
|
in (if startnum /= 1
|
|
|
|
then " start=\"" ++ show startnum ++ "\""
|
|
|
|
else "") ++
|
|
|
|
(if numstyle /= DefaultStyle
|
|
|
|
then " style=\"list-style-type: " ++ numstyle' ++ ";\""
|
|
|
|
else "")
|
|
|
|
|
2013-07-26 06:19:40 +01:00
|
|
|
-- | Convert bullet list item (list of blocks) to DokuWiki.
|
2013-07-14 13:40:27 +01:00
|
|
|
listItemToDokuWiki :: WriterOptions -> [Block] -> State WriterState String
|
|
|
|
listItemToDokuWiki opts items = do
|
|
|
|
contents <- blockListToDokuWiki opts items
|
|
|
|
useTags <- get >>= return . stUseTags
|
|
|
|
if useTags
|
|
|
|
then return $ "<li>" ++ contents ++ "</li>"
|
|
|
|
else do
|
2013-08-28 08:09:42 +01:00
|
|
|
indent <- get >>= return . stIndent
|
|
|
|
return $ indent ++ "* " ++ contents
|
2013-07-26 06:19:40 +01:00
|
|
|
|
|
|
|
-- | Convert ordered list item (list of blocks) to DokuWiki.
|
|
|
|
-- | TODO Emiminate dreadful duplication of text from listItemToDokuWiki
|
|
|
|
orderedListItemToDokuWiki :: WriterOptions -> [Block] -> State WriterState String
|
|
|
|
orderedListItemToDokuWiki opts items = do
|
|
|
|
contents <- blockListToDokuWiki opts items
|
|
|
|
useTags <- get >>= return . stUseTags
|
|
|
|
if useTags
|
|
|
|
then return $ "<li>" ++ contents ++ "</li>"
|
|
|
|
else do
|
2013-08-28 08:09:42 +01:00
|
|
|
indent <- get >>= return . stIndent
|
|
|
|
return $ indent ++ "- " ++ contents
|
2013-07-14 13:40:27 +01:00
|
|
|
|
|
|
|
-- | Convert definition list item (label, list of blocks) to DokuWiki.
|
|
|
|
definitionListItemToDokuWiki :: WriterOptions
|
|
|
|
-> ([Inline],[[Block]])
|
|
|
|
-> State WriterState String
|
|
|
|
definitionListItemToDokuWiki opts (label, items) = do
|
|
|
|
labelText <- inlineListToDokuWiki opts label
|
|
|
|
contents <- mapM (blockListToDokuWiki opts) items
|
|
|
|
useTags <- get >>= return . stUseTags
|
|
|
|
if useTags
|
|
|
|
then return $ "<dt>" ++ labelText ++ "</dt>\n" ++
|
|
|
|
(intercalate "\n" $ map (\d -> "<dd>" ++ d ++ "</dd>") contents)
|
|
|
|
else do
|
2013-08-28 08:09:42 +01:00
|
|
|
indent <- get >>= return . stIndent
|
|
|
|
return $ indent ++ "* **" ++ labelText ++ "** " ++ concat contents
|
2013-07-14 13:40:27 +01:00
|
|
|
|
|
|
|
-- | True if the list can be handled by simple wiki markup, False if HTML tags will be needed.
|
|
|
|
isSimpleList :: Block -> Bool
|
|
|
|
isSimpleList x =
|
|
|
|
case x of
|
2013-08-19 21:28:17 +01:00
|
|
|
BulletList _ -> True
|
|
|
|
OrderedList _ _ -> True
|
2013-08-28 08:09:42 +01:00
|
|
|
DefinitionList _ -> True
|
2013-07-14 13:40:27 +01:00
|
|
|
_ -> False
|
|
|
|
|
|
|
|
-- | Concatenates strings with line breaks between them.
|
|
|
|
vcat :: [String] -> String
|
|
|
|
vcat = intercalate "\n"
|
|
|
|
|
|
|
|
-- Auxiliary functions for tables:
|
|
|
|
|
2013-08-17 08:48:29 +01:00
|
|
|
-- TODO Eliminate copy-and-pasted code in tableHeaderToDokuWiki and tableRowToDokuWiki
|
|
|
|
tableHeaderToDokuWiki :: WriterOptions
|
|
|
|
-> [String]
|
|
|
|
-> Int
|
|
|
|
-> [[Block]]
|
|
|
|
-> State WriterState String
|
|
|
|
tableHeaderToDokuWiki opts alignStrings rownum cols' = do
|
|
|
|
let celltype = if rownum == 0 then "" else ""
|
|
|
|
cols'' <- sequence $ zipWith
|
|
|
|
(\alignment item -> tableItemToDokuWiki opts celltype alignment item)
|
|
|
|
alignStrings cols'
|
|
|
|
return $ "^ " ++ "" ++ joinHeaders cols'' ++ " ^"
|
|
|
|
|
2013-07-14 13:40:27 +01:00
|
|
|
tableRowToDokuWiki :: WriterOptions
|
|
|
|
-> [String]
|
|
|
|
-> Int
|
|
|
|
-> [[Block]]
|
|
|
|
-> State WriterState String
|
|
|
|
tableRowToDokuWiki opts alignStrings rownum cols' = do
|
2013-08-11 22:22:07 +01:00
|
|
|
let celltype = if rownum == 0 then "" else ""
|
2013-07-14 13:40:27 +01:00
|
|
|
cols'' <- sequence $ zipWith
|
|
|
|
(\alignment item -> tableItemToDokuWiki opts celltype alignment item)
|
|
|
|
alignStrings cols'
|
2013-08-11 22:22:07 +01:00
|
|
|
return $ "| " ++ "" ++ joinColumns cols'' ++ " |"
|
2013-07-14 13:40:27 +01:00
|
|
|
|
|
|
|
alignmentToString :: Alignment -> [Char]
|
|
|
|
alignmentToString alignment = case alignment of
|
2013-08-11 22:22:07 +01:00
|
|
|
AlignLeft -> ""
|
|
|
|
AlignRight -> ""
|
|
|
|
AlignCenter -> ""
|
|
|
|
AlignDefault -> ""
|
2013-07-14 13:40:27 +01:00
|
|
|
|
|
|
|
tableItemToDokuWiki :: WriterOptions
|
|
|
|
-> String
|
|
|
|
-> String
|
|
|
|
-> [Block]
|
|
|
|
-> State WriterState String
|
2013-08-11 22:22:07 +01:00
|
|
|
-- TODO Fix celltype and align' defined but not used
|
2014-06-30 22:07:17 +01:00
|
|
|
tableItemToDokuWiki opts _celltype _align' item = do
|
2013-08-11 22:22:07 +01:00
|
|
|
let mkcell x = "" ++ x ++ ""
|
2013-07-14 13:40:27 +01:00
|
|
|
contents <- blockListToDokuWiki opts item
|
|
|
|
return $ mkcell contents
|
|
|
|
|
2013-08-11 22:22:07 +01:00
|
|
|
-- | Concatenates columns together.
|
|
|
|
joinColumns :: [String] -> String
|
|
|
|
joinColumns = intercalate " | "
|
|
|
|
|
2013-08-17 08:48:29 +01:00
|
|
|
-- | Concatenates headers together.
|
|
|
|
joinHeaders :: [String] -> String
|
|
|
|
joinHeaders = intercalate " ^ "
|
|
|
|
|
2013-07-14 13:40:27 +01:00
|
|
|
-- | Convert list of Pandoc block elements to DokuWiki.
|
|
|
|
blockListToDokuWiki :: WriterOptions -- ^ Options
|
|
|
|
-> [Block] -- ^ List of block elements
|
|
|
|
-> State WriterState String
|
|
|
|
blockListToDokuWiki opts blocks =
|
|
|
|
mapM (blockToDokuWiki opts) blocks >>= return . vcat
|
|
|
|
|
|
|
|
-- | Convert list of Pandoc inline elements to DokuWiki.
|
|
|
|
inlineListToDokuWiki :: WriterOptions -> [Inline] -> State WriterState String
|
2013-08-28 08:09:42 +01:00
|
|
|
inlineListToDokuWiki opts lst = mapM (inlineToDokuWiki opts) lst >>= return . concat
|
2013-07-14 13:40:27 +01:00
|
|
|
|
|
|
|
-- | Convert Pandoc inline element to DokuWiki.
|
|
|
|
inlineToDokuWiki :: WriterOptions -> Inline -> State WriterState String
|
|
|
|
|
2014-07-02 22:40:34 +01:00
|
|
|
inlineToDokuWiki opts (Span _attrs ils) = do
|
2014-06-29 21:15:17 +01:00
|
|
|
contents <- inlineListToDokuWiki opts ils
|
2014-07-02 22:40:34 +01:00
|
|
|
return contents
|
2014-06-29 21:15:17 +01:00
|
|
|
|
2013-07-14 13:40:27 +01:00
|
|
|
inlineToDokuWiki opts (Emph lst) = do
|
|
|
|
contents <- inlineListToDokuWiki opts lst
|
2013-07-14 14:58:42 +01:00
|
|
|
return $ "//" ++ contents ++ "//"
|
2013-07-14 13:40:27 +01:00
|
|
|
|
|
|
|
inlineToDokuWiki opts (Strong lst) = do
|
|
|
|
contents <- inlineListToDokuWiki opts lst
|
2013-07-14 14:58:42 +01:00
|
|
|
return $ "**" ++ contents ++ "**"
|
2013-07-14 13:40:27 +01:00
|
|
|
|
|
|
|
inlineToDokuWiki opts (Strikeout lst) = do
|
|
|
|
contents <- inlineListToDokuWiki opts lst
|
2013-08-06 07:43:32 +01:00
|
|
|
return $ "<del>" ++ contents ++ "</del>"
|
2013-07-14 13:40:27 +01:00
|
|
|
|
|
|
|
inlineToDokuWiki opts (Superscript lst) = do
|
|
|
|
contents <- inlineListToDokuWiki opts lst
|
|
|
|
return $ "<sup>" ++ contents ++ "</sup>"
|
|
|
|
|
|
|
|
inlineToDokuWiki opts (Subscript lst) = do
|
|
|
|
contents <- inlineListToDokuWiki opts lst
|
|
|
|
return $ "<sub>" ++ contents ++ "</sub>"
|
|
|
|
|
|
|
|
inlineToDokuWiki opts (SmallCaps lst) = inlineListToDokuWiki opts lst
|
|
|
|
|
|
|
|
inlineToDokuWiki opts (Quoted SingleQuote lst) = do
|
|
|
|
contents <- inlineListToDokuWiki opts lst
|
|
|
|
return $ "\8216" ++ contents ++ "\8217"
|
|
|
|
|
|
|
|
inlineToDokuWiki opts (Quoted DoubleQuote lst) = do
|
|
|
|
contents <- inlineListToDokuWiki opts lst
|
|
|
|
return $ "\8220" ++ contents ++ "\8221"
|
|
|
|
|
|
|
|
inlineToDokuWiki opts (Cite _ lst) = inlineListToDokuWiki opts lst
|
|
|
|
|
|
|
|
inlineToDokuWiki _ (Code _ str) =
|
2013-08-18 08:13:34 +01:00
|
|
|
-- In dokuwiki, text surrounded by '' is really just a font statement, i.e. <tt>,
|
|
|
|
-- and so other formatting can be present inside.
|
|
|
|
-- However, in pandoc, and markdown, inlined code doesn't contain formatting.
|
|
|
|
-- So I have opted for using %% to disable all formatting inside inline code blocks.
|
|
|
|
-- This gives the best results when converting from other formats to dokuwiki, even if
|
|
|
|
-- the resultand code is a little ugly, for short strings that don't contain formatting
|
|
|
|
-- characters.
|
|
|
|
-- It does mean that if pandoc could ever read dokuwiki, and so round-trip the format,
|
|
|
|
-- any formatting inside inlined code blocks would be lost, or presented incorrectly.
|
|
|
|
return $ "''%%" ++ str ++ "%%''"
|
2013-07-14 13:40:27 +01:00
|
|
|
|
2013-08-18 08:57:32 +01:00
|
|
|
inlineToDokuWiki _ (Str str) = return $ escapeString str
|
2013-07-14 13:40:27 +01:00
|
|
|
|
|
|
|
inlineToDokuWiki _ (Math _ str) = return $ "<math>" ++ str ++ "</math>"
|
|
|
|
-- note: str should NOT be escaped
|
|
|
|
|
2014-06-29 21:15:17 +01:00
|
|
|
inlineToDokuWiki _ (RawInline f str)
|
2014-07-13 15:24:52 -07:00
|
|
|
| f == Format "dokuwiki" = return str
|
2014-07-13 15:28:47 -07:00
|
|
|
| f == Format "html" = return $ "<html>" ++ str ++ "</html>"
|
2014-07-13 15:24:52 -07:00
|
|
|
| otherwise = return ""
|
2013-07-14 13:40:27 +01:00
|
|
|
|
2013-08-19 08:09:52 +01:00
|
|
|
inlineToDokuWiki _ (LineBreak) = return "\\\\ "
|
2013-07-14 13:40:27 +01:00
|
|
|
|
|
|
|
inlineToDokuWiki _ Space = return " "
|
|
|
|
|
|
|
|
inlineToDokuWiki opts (Link txt (src, _)) = do
|
|
|
|
label <- inlineListToDokuWiki opts txt
|
|
|
|
case txt of
|
|
|
|
[Str s] | escapeURI s == src -> return src
|
2014-07-13 15:36:14 -07:00
|
|
|
| "mailto:" ++ escapeURI s == src -> return $
|
|
|
|
"<" ++ s ++ ">"
|
2013-07-14 13:40:27 +01:00
|
|
|
_ -> if isURI src
|
2013-07-15 09:35:04 +01:00
|
|
|
then return $ "[[" ++ src ++ "|" ++ label ++ "]]"
|
2013-07-14 13:40:27 +01:00
|
|
|
else return $ "[[" ++ src' ++ "|" ++ label ++ "]]"
|
|
|
|
where src' = case src of
|
|
|
|
'/':xs -> xs -- with leading / it's a
|
|
|
|
_ -> src -- link to a help page
|
|
|
|
inlineToDokuWiki opts (Image alt (source, tit)) = do
|
|
|
|
alt' <- inlineListToDokuWiki opts alt
|
|
|
|
let txt = if (null tit)
|
|
|
|
then if null alt
|
|
|
|
then ""
|
|
|
|
else "|" ++ alt'
|
|
|
|
else "|" ++ tit
|
2013-07-15 19:29:39 +01:00
|
|
|
return $ "{{:" ++ source ++ txt ++ "}}"
|
2013-07-14 13:40:27 +01:00
|
|
|
|
|
|
|
inlineToDokuWiki opts (Note contents) = do
|
|
|
|
contents' <- blockListToDokuWiki opts contents
|
|
|
|
modify (\s -> s { stNotes = True })
|
2013-07-28 19:19:33 +01:00
|
|
|
return $ "((" ++ contents' ++ "))"
|
2013-07-14 13:40:27 +01:00
|
|
|
-- note - may not work for notes with multiple blocks
|