aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
m---------data/templates13
-rw-r--r--pandoc.cabal3
-rw-r--r--pandoc.hs1
-rw-r--r--src/Text/Pandoc.hs3
-rw-r--r--src/Text/Pandoc/Writers/DokuWiki.hs466
-rw-r--r--tests/Tests/Old.hs5
-rw-r--r--tests/dokuwiki-writer.dokuwiki3
-rw-r--r--tests/dokuwiki-writer.native2
-rw-r--r--tests/tables.dokuwiki47
-rw-r--r--tests/writer.dokuwiki607
10 files changed, 1144 insertions, 6 deletions
diff --git a/data/templates b/data/templates
-Subproject f3b3f2dda6737b9c6af03e1f470186139403277
+Subproject 95f515decb05a77ea8d37c5bb9f13203f09bc32
diff --git a/pandoc.cabal b/pandoc.cabal
index eeb233d3d..93c9b4dc7 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -19,7 +19,7 @@ Description: Pandoc is a Haskell library for converting from one markup
reStructuredText, LaTeX, DocBook, MediaWiki markup, Haddock
markup, OPML, Emacs Org-Mode, and Textile, and it can write
markdown, reStructuredText, HTML, LaTeX, ConTeXt, Docbook, OPML,
- OpenDocument, ODT, Word docx, RTF, MediaWiki, Textile,
+ OpenDocument, ODT, Word docx, RTF, MediaWiki, DokuWiki, Textile,
groff man pages, plain text, Emacs Org-Mode, AsciiDoc,
Haddock markup, EPUB (v2 and v3), FictionBook2,
InDesign ICML, and several kinds of HTML/javascript
@@ -315,6 +315,7 @@ Library
Text.Pandoc.Writers.Custom,
Text.Pandoc.Writers.Textile,
Text.Pandoc.Writers.MediaWiki,
+ Text.Pandoc.Writers.DokuWiki,
Text.Pandoc.Writers.RTF,
Text.Pandoc.Writers.ODT,
Text.Pandoc.Writers.Docx,
diff --git a/pandoc.hs b/pandoc.hs
index bf5f387dd..30c575a69 100644
--- a/pandoc.hs
+++ b/pandoc.hs
@@ -871,6 +871,7 @@ defaultReaderName fallback (x:xs) =
".db" -> "docbook"
".opml" -> "opml"
".wiki" -> "mediawiki"
+ ".dokuwiki" -> "dokuwiki"
".textile" -> "textile"
".native" -> "native"
".json" -> "json"
diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs
index d2e7887b5..23b97e6c1 100644
--- a/src/Text/Pandoc.hs
+++ b/src/Text/Pandoc.hs
@@ -94,6 +94,7 @@ module Text.Pandoc
, writeOpenDocument
, writeMan
, writeMediaWiki
+ , writeDokuWiki
, writeTextile
, writeRTF
, writeODT
@@ -147,6 +148,7 @@ import Text.Pandoc.Writers.OpenDocument
import Text.Pandoc.Writers.Man
import Text.Pandoc.Writers.RTF
import Text.Pandoc.Writers.MediaWiki
+import Text.Pandoc.Writers.DokuWiki
import Text.Pandoc.Writers.Textile
import Text.Pandoc.Writers.Org
import Text.Pandoc.Writers.AsciiDoc
@@ -277,6 +279,7 @@ writers = [
,("plain" , PureStringWriter writePlain)
,("rst" , PureStringWriter writeRST)
,("mediawiki" , PureStringWriter writeMediaWiki)
+ ,("dokuwiki" , PureStringWriter writeDokuWiki)
,("textile" , PureStringWriter writeTextile)
,("rtf" , IOStringWriter writeRTFWithEmbeddedImages)
,("org" , PureStringWriter writeOrg)
diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs
new file mode 100644
index 000000000..31057f09e
--- /dev/null
+++ b/src/Text/Pandoc/Writers/DokuWiki.hs
@@ -0,0 +1,466 @@
+{-
+Copyright (C) 2008-2014 John MacFarlane <jgm@berkeley.edu>
+
+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
+ Copyright : Copyright (C) 2008-2014 John MacFarlane
+ License : GNU GPL, version 2 or above
+
+ Maintainer : John MacFarlane <jgm@berkeley.edu>
+ Stability : alpha
+ Portability : portable
+
+Conversion of 'Pandoc' documents to DokuWiki markup.
+
+DokuWiki: <https://www.dokuwiki.org/dokuwiki>
+-}
+
+{-
+ [ ] Correct handling of Span
+ [ ] Don't generate <blockquote>...
+ [ ] Don't generate lists using <ol> and <ul>
+ [ ] Implement alignment of text in tables
+ [ ] Implement comments
+ [ ] Work through the Dokuwiki spec, and check I've not missed anything out
+ [ ] Test the output in Dokuwiki - and compare against the display of another format, e.g. HTML
+ [ ] Remove dud/duplicate code
+-}
+
+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
+ , stIndent :: String -- Indent after the marker at the beginning of list items
+ , 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)
+ (WriterState { stNotes = False, stIndent = "", stUseTags = False })
+
+-- | 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
+ 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
+ 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
+
+-- | Escape special characters for MediaWiki.
+escapeString :: String -> String
+escapeString str = substitute "__" "%%__%%" ( substitute "**" "%%**%%" ( substitute "//" "%%//%%" str ) )
+
+-- | Convert Pandoc block element to DokuWiki.
+blockToDokuWiki :: WriterOptions -- ^ Options
+ -> Block -- ^ Block element
+ -> State WriterState String
+
+blockToDokuWiki _ Null = return ""
+
+blockToDokuWiki opts (Div _attrs bs) = do
+ contents <- blockListToDokuWiki opts bs
+ return $ contents ++ "\n"
+
+blockToDokuWiki opts (Plain inlines) =
+ inlineListToDokuWiki opts inlines
+
+-- title beginning with fig: indicates that the image is a figure
+-- dokuwiki doesn't support captions - so combine together alt and caption into alt
+blockToDokuWiki opts (Para [Image txt (src,'f':'i':'g':':':tit)]) = do
+ capt <- if null txt
+ then return ""
+ else (" " ++) `fmap` inlineListToDokuWiki opts txt
+ let opt = if null txt
+ then ""
+ else "|" ++ if null tit then capt else tit ++ capt
+ return $ "{{:" ++ src ++ opt ++ "}}\n"
+
+blockToDokuWiki opts (Para inlines) = do
+ useTags <- get >>= return . stUseTags
+ indent <- get >>= return . stIndent
+ contents <- inlineListToDokuWiki opts inlines
+ return $ if useTags
+ then "<p>" ++ contents ++ "</p>"
+ else contents ++ if null indent then "\n" else ""
+
+blockToDokuWiki _ (RawBlock f str)
+ | f == Format "mediawiki" = return str
+ | f == Format "html" = return $ "<html>\n" ++ str ++ "</html>"
+ | otherwise = return ""
+
+blockToDokuWiki _ HorizontalRule = return "\n----\n"
+
+blockToDokuWiki opts (Header level _ inlines) = do
+ contents <- inlineListToDokuWiki opts inlines
+ let eqs = replicate ( 7 - level ) '='
+ 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
+ then ("<code" ++ if null classes then ">" else " class=\"" ++ unwords classes ++ "\">", "</code>")
+ else ("<source lang=\"" ++ head at ++ "\">", "</source>")
+ return $ beg ++ str ++ end
+
+blockToDokuWiki opts (BlockQuote blocks) = do
+ contents <- blockListToDokuWiki opts blocks
+ return $ "<blockquote>" ++ contents ++ "</blockquote>"
+
+blockToDokuWiki opts (Table capt aligns _ headers rows') = do
+ let alignStrings = map alignmentToString aligns
+ captionDoc <- if null capt
+ then return ""
+ else do
+ c <- inlineListToDokuWiki opts capt
+ return $ "" ++ c ++ "\n"
+ head' <- if all null headers
+ then return ""
+ else do
+ hs <- tableHeaderToDokuWiki opts alignStrings 0 headers
+ return $ hs ++ "\n"
+ body' <- zipWithM (tableRowToDokuWiki opts alignStrings) [1..] rows'
+ return $ captionDoc ++ head' ++
+ unlines body'
+
+blockToDokuWiki opts x@(BulletList items) = do
+ oldUseTags <- get >>= return . stUseTags
+ indent <- get >>= return . stIndent
+ 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
+ modify $ \s -> s { stIndent = stIndent s ++ " " }
+ contents <- mapM (listItemToDokuWiki opts) items
+ modify $ \s -> s { stIndent = indent }
+ return $ vcat contents ++ if null indent then "\n" else ""
+
+blockToDokuWiki opts x@(OrderedList attribs items) = do
+ oldUseTags <- get >>= return . stUseTags
+ indent <- get >>= return . stIndent
+ let useTags = oldUseTags || not (isSimpleList x)
+ if useTags
+ then do
+ modify $ \s -> s { stUseTags = True }
+ contents <- mapM (orderedListItemToDokuWiki opts) items
+ modify $ \s -> s { stUseTags = oldUseTags }
+ return $ "<ol" ++ listAttribsToString attribs ++ ">\n" ++ vcat contents ++ "</ol>\n"
+ else do
+ modify $ \s -> s { stIndent = stIndent s ++ " " }
+ contents <- mapM (orderedListItemToDokuWiki opts) items
+ modify $ \s -> s { stIndent = indent }
+ return $ vcat contents ++ if null indent then "\n" else ""
+
+-- 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
+blockToDokuWiki opts x@(DefinitionList items) = do
+ oldUseTags <- get >>= return . stUseTags
+ indent <- get >>= return . stIndent
+ 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
+ modify $ \s -> s { stIndent = stIndent s ++ " " }
+ contents <- mapM (definitionListItemToDokuWiki opts) items
+ modify $ \s -> s { stIndent = indent }
+ return $ vcat contents ++ if null indent then "\n" else ""
+
+-- 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 "")
+
+-- | Convert bullet list item (list of blocks) to DokuWiki.
+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
+ indent <- get >>= return . stIndent
+ return $ indent ++ "* " ++ contents
+
+-- | 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
+ indent <- get >>= return . stIndent
+ return $ indent ++ "- " ++ contents
+
+-- | 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
+ indent <- get >>= return . stIndent
+ return $ indent ++ "* **" ++ labelText ++ "** " ++ concat contents
+
+-- | 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
+ BulletList _ -> True
+ OrderedList _ _ -> True
+ DefinitionList _ -> True
+ _ -> False
+
+-- | True if list item can be handled with the simple wiki syntax. False if
+-- HTML tags will be needed.
+isSimpleListItem :: [Block] -> Bool
+isSimpleListItem [] = True
+isSimpleListItem [x] =
+ case x of
+ Plain _ -> True
+ Para _ -> True
+ BulletList _ -> isSimpleList x
+ OrderedList _ _ -> isSimpleList x
+ DefinitionList _ -> isSimpleList x
+ _ -> False
+isSimpleListItem [x, y] | isPlainOrPara x =
+ case y of
+ BulletList _ -> isSimpleList y
+ OrderedList _ _ -> isSimpleList y
+ DefinitionList _ -> isSimpleList y
+ _ -> False
+isSimpleListItem _ = False
+
+isPlainOrPara :: Block -> Bool
+isPlainOrPara (Plain _) = True
+isPlainOrPara (Para _) = True
+isPlainOrPara _ = False
+
+-- | Concatenates strings with line breaks between them.
+vcat :: [String] -> String
+vcat = intercalate "\n"
+
+-- Auxiliary functions for tables:
+
+-- 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'' ++ " ^"
+
+tableRowToDokuWiki :: WriterOptions
+ -> [String]
+ -> Int
+ -> [[Block]]
+ -> State WriterState String
+tableRowToDokuWiki 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 $ "| " ++ "" ++ joinColumns cols'' ++ " |"
+
+alignmentToString :: Alignment -> [Char]
+alignmentToString alignment = case alignment of
+ AlignLeft -> ""
+ AlignRight -> ""
+ AlignCenter -> ""
+ AlignDefault -> ""
+
+tableItemToDokuWiki :: WriterOptions
+ -> String
+ -> String
+ -> [Block]
+ -> State WriterState String
+-- TODO Fix celltype and align' defined but not used
+tableItemToDokuWiki opts _celltype _align' item = do
+ let mkcell x = "" ++ x ++ ""
+ contents <- blockListToDokuWiki opts item
+ return $ mkcell contents
+
+-- | Concatenates columns together.
+joinColumns :: [String] -> String
+joinColumns = intercalate " | "
+
+-- | Concatenates headers together.
+joinHeaders :: [String] -> String
+joinHeaders = intercalate " ^ "
+
+-- | 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
+inlineListToDokuWiki opts lst = mapM (inlineToDokuWiki opts) lst >>= return . concat
+
+-- | Convert Pandoc inline element to DokuWiki.
+inlineToDokuWiki :: WriterOptions -> Inline -> State WriterState String
+
+inlineToDokuWiki _opts (Span _attrs _ils) = do
+ return ""
+ {-
+ contents <- inlineListToDokuWiki opts ils
+ return $ render Nothing (tagWithAttrs "span" attrs) ++ contents ++ "</span>"
+ -}
+
+inlineToDokuWiki opts (Emph lst) = do
+ contents <- inlineListToDokuWiki opts lst
+ return $ "//" ++ contents ++ "//"
+
+inlineToDokuWiki opts (Strong lst) = do
+ contents <- inlineListToDokuWiki opts lst
+ return $ "**" ++ contents ++ "**"
+
+inlineToDokuWiki opts (Strikeout lst) = do
+ contents <- inlineListToDokuWiki opts lst
+ return $ "<del>" ++ contents ++ "</del>"
+
+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) =
+ -- 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 ++ "%%''"
+
+inlineToDokuWiki _ (Str str) = return $ escapeString str
+
+inlineToDokuWiki _ (Math _ str) = return $ "<math>" ++ str ++ "</math>"
+ -- note: str should NOT be escaped
+
+inlineToDokuWiki _ (RawInline f str)
+ | f == Format "mediawiki" = return str
+ | f == Format "html" = return str
+ | otherwise = return ""
+
+inlineToDokuWiki _ (LineBreak) = return "\\\\ "
+
+inlineToDokuWiki _ Space = return " "
+
+inlineToDokuWiki opts (Link txt (src, _)) = do
+ label <- inlineListToDokuWiki opts txt
+ case txt of
+ [Str s] | escapeURI s == src -> return src
+ _ -> if isURI src
+ then return $ "[[" ++ src ++ "|" ++ label ++ "]]"
+ 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
+ return $ "{{:" ++ source ++ txt ++ "}}"
+
+inlineToDokuWiki opts (Note contents) = do
+ contents' <- blockListToDokuWiki opts contents
+ modify (\s -> s { stNotes = True })
+ return $ "((" ++ contents' ++ "))"
+ -- note - may not work for notes with multiple blocks
diff --git a/tests/Tests/Old.hs b/tests/Tests/Old.hs
index fa01b1358..44ed9f53a 100644
--- a/tests/Tests/Old.hs
+++ b/tests/Tests/Old.hs
@@ -124,6 +124,11 @@ tests = [ testGroup "markdown"
, test "reader" ["-r", "mediawiki", "-w", "native", "-s"]
"mediawiki-reader.wiki" "mediawiki-reader.native"
]
+ , testGroup "dokuwiki"
+ [ testGroup "writer" $ writerTests "dokuwiki"
+ , test "writer-more" ["-r", "native", "-w", "dokuwiki", "-s"]
+ "dokuwiki-writer.native" "dokuwiki-writer.dokuwiki"
+ ]
, testGroup "opml"
[ test "basic" ["-r", "native", "-w", "opml", "--columns=78", "-s"]
"testsuite.native" "writer.opml"
diff --git a/tests/dokuwiki-writer.dokuwiki b/tests/dokuwiki-writer.dokuwiki
new file mode 100644
index 000000000..6ddacc480
--- /dev/null
+++ b/tests/dokuwiki-writer.dokuwiki
@@ -0,0 +1,3 @@
+hello %%//%% world %%**%% from %%__%% me
+
+''%%hello // world ** from __ me%%''
diff --git a/tests/dokuwiki-writer.native b/tests/dokuwiki-writer.native
new file mode 100644
index 000000000..fc24451bc
--- /dev/null
+++ b/tests/dokuwiki-writer.native
@@ -0,0 +1,2 @@
+[Para [Str "hello",Space,Str "//",Space,Str "world",Space,Str "**",Space,Str "from",Space,Str "__",Space,Str "me"]
+,Para [Code ("",[],[]) "hello // world ** from __ me"]]
diff --git a/tests/tables.dokuwiki b/tests/tables.dokuwiki
new file mode 100644
index 000000000..4fcae4e6f
--- /dev/null
+++ b/tests/tables.dokuwiki
@@ -0,0 +1,47 @@
+Simple table with caption:
+
+Demonstration of simple table syntax.
+^ Right ^ Left ^ Center ^ Default ^
+| 12 | 12 | 12 | 12 |
+| 123 | 123 | 123 | 123 |
+| 1 | 1 | 1 | 1 |
+
+Simple table without caption:
+
+^ Right ^ Left ^ Center ^ Default ^
+| 12 | 12 | 12 | 12 |
+| 123 | 123 | 123 | 123 |
+| 1 | 1 | 1 | 1 |
+
+Simple table indented two spaces:
+
+Demonstration of simple table syntax.
+^ Right ^ Left ^ Center ^ Default ^
+| 12 | 12 | 12 | 12 |
+| 123 | 123 | 123 | 123 |
+| 1 | 1 | 1 | 1 |
+
+Multiline table with caption:
+
+Here's the caption. It may span multiple lines.
+^ Centered Header ^ Left Aligned ^ Right Aligned ^ Default aligned ^
+| First | row | 12.0 | Example of a row that spans multiple lines. |
+| Second | row | 5.0 | Here's another one. Note the blank line between rows. |
+
+Multiline table without caption:
+
+^ Centered Header ^ Left Aligned ^ Right Aligned ^ Default aligned ^
+| First | row | 12.0 | Example of a row that spans multiple lines. |
+| Second | row | 5.0 | Here's another one. Note the blank line between rows. |
+
+Table without column headers:
+
+| 12 | 12 | 12 | 12 |
+| 123 | 123 | 123 | 123 |
+| 1 | 1 | 1 | 1 |
+
+Multiline table without column headers:
+
+| First | row | 12.0 | Example of a row that spans multiple lines. |
+| Second | row | 5.0 | Here's another one. Note the blank line between rows. |
+
diff --git a/tests/writer.dokuwiki b/tests/writer.dokuwiki
new file mode 100644
index 000000000..3e47ee7ee
--- /dev/null
+++ b/tests/writer.dokuwiki
@@ -0,0 +1,607 @@
+This is a set of tests for pandoc. Most of them are adapted from John Gruber’s markdown test suite.
+
+
+----
+
+====== Headers ======
+
+===== Level 2 with an [[url|embedded link]] =====
+
+==== Level 3 with //emphasis// ====
+
+=== Level 4 ===
+
+== Level 5 ==
+
+====== Level 1 ======
+
+===== Level 2 with //emphasis// =====
+
+==== Level 3 ====
+
+with no blank line
+
+===== Level 2 =====
+
+with no blank line
+
+
+----
+
+====== Paragraphs ======
+
+Here’s a regular paragraph.
+
+In Markdown 1.0.0 and earlier. Version 8. This line turns into a list item. Because a hard-wrapped line in the middle of a paragraph looked like a list item.
+
+Here’s one with a bullet. * criminey.
+
+There should be a hard line break\\ here.
+
+
+----
+
+====== Block Quotes ======
+
+E-mail style:
+
+<blockquote>This is a block quote. It is pretty short.
+</blockquote>
+<blockquote>Code in a block quote:
+
+<code>sub status {
+ print "working";
+}</code>
+A list:
+
+ - item one
+ - item two
+
+Nested block quotes:
+
+<blockquote>nested
+</blockquote>
+<blockquote>nested
+</blockquote></blockquote>
+This should not be a block quote: 2 > 1.
+
+And a following paragraph.
+
+
+----
+
+====== Code Blocks ======
+
+Code:
+
+<code>---- (should be four hyphens)
+
+sub status {
+ print "working";
+}
+
+this code block is indented by one tab</code>
+And:
+
+<code> this code block is indented by two tabs
+
+These should not be escaped: \$ \\ \> \[ \{</code>
+
+----
+
+====== Lists ======
+
+===== Unordered =====
+
+Asterisks tight:
+
+ * asterisk 1
+ * asterisk 2
+ * asterisk 3
+
+Asterisks loose:
+
+ * asterisk 1
+ * asterisk 2
+ * asterisk 3
+
+Pluses tight:
+
+ * Plus 1
+ * Plus 2
+ * Plus 3
+
+Pluses loose:
+
+ * Plus 1
+ * Plus 2
+ * Plus 3
+
+Minuses tight:
+
+ * Minus 1
+ * Minus 2
+ * Minus 3
+
+Minuses loose:
+
+ * Minus 1
+ * Minus 2
+ * Minus 3
+
+===== Ordered =====
+
+Tight:
+
+ - First
+ - Second
+ - Third
+
+and:
+
+ - One
+ - Two
+ - Three
+
+Loose using tabs:
+
+ - First
+ - Second
+ - Third
+
+and using spaces:
+
+ - One
+ - Two
+ - Three
+
+Multiple paragraphs:
+
+ - Item 1, graf one.
+Item 1. graf two. The quick brown fox jumped over the lazy dog’s back.
+ - Item 2.
+ - Item 3.
+
+===== Nested =====
+
+ * Tab
+ * Tab
+ * Tab
+
+Here’s another:
+
+ - First
+ - Second:
+ * Fee
+ * Fie
+ * Foe
+ - Third
+
+Same thing but with paragraphs:
+
+ - First
+ - Second:
+ * Fee
+ * Fie
+ * Foe
+ - Third
+
+===== Tabs and spaces =====
+
+ * this is a list item indented with tabs
+ * this is a list item indented with spaces
+ * this is an example list item indented with tabs
+ * this is an example list item indented with spaces
+
+===== Fancy list markers =====
+
+ - begins with 2
+ - and now 3
+with a continuation
+ - sublist with roman numerals, starting with 4
+ - more items
+ - a subsublist
+ - a subsublist
+
+Nesting:
+
+ - Upper Alpha
+ - Upper Roman.
+ - Decimal start with 6
+ - Lower alpha with paren
+
+Autonumbering:
+
+ - Autonumber.
+ - More.
+ - Nested.
+
+Should not be a list item:
+
+M.A. 2007
+
+B. Williams
+
+
+----
+
+====== Definition Lists ======
+
+Tight using spaces:
+
+ * **apple** red fruit
+ * **orange** orange fruit
+ * **banana** yellow fruit
+
+Tight using tabs:
+
+ * **apple** red fruit
+ * **orange** orange fruit
+ * **banana** yellow fruit
+
+Loose:
+
+ * **apple** red fruit
+ * **orange** orange fruit
+ * **banana** yellow fruit
+
+Multiple blocks with italics:
+
+ * **//apple//** red fruit
+contains seeds, crisp, pleasant to taste
+ * **//orange//** orange fruit
+<code>{ orange code block }</code>
+<blockquote>orange block quote</blockquote>
+
+Multiple definitions, tight:
+
+ * **apple** red fruitcomputer
+ * **orange** orange fruitbank
+
+Multiple definitions, loose:
+
+ * **apple** red fruitcomputer
+ * **orange** orange fruitbank
+
+Blank line after term, indented marker, alternate markers:
+
+ * **apple** red fruitcomputer
+ * **orange** orange fruit
+ - sublist
+ - sublist
+
+====== HTML Blocks ======
+
+Simple block on one line:
+
+foo
+
+And nested without indentation:
+
+foo
+
+
+bar
+
+
+Interpreted markdown in a table:
+
+<html>
+<table>
+<tr>
+<td></html>
+This is //emphasized//
+<html>
+</td>
+<td></html>
+And this is **strong**
+<html>
+</td>
+</tr>
+</table>
+
+<script type="text/javascript">document.write('This *should not* be interpreted as markdown');</script>
+</html>
+Here’s a simple block:
+
+foo
+
+This should be a code block, though:
+
+<code><div>
+ foo
+</div></code>
+As should this:
+
+<code><div>foo</div></code>
+Now, nested:
+
+foo
+
+
+
+This should just be an HTML comment:
+
+<html>
+<!-- Comment -->
+</html>
+Multiline:
+
+<html>
+<!--
+Blah
+Blah
+-->
+
+<!--
+ This is another comment.
+-->
+</html>
+Code block:
+
+<code><!-- Comment --></code>
+Just plain comment, with trailing spaces on the line:
+
+<html>
+<!-- foo -->
+</html>
+Code:
+
+<code><hr /></code>
+Hr’s:
+
+<html>
+<hr>
+
+<hr />
+
+<hr />
+
+<hr>
+
+<hr />
+
+<hr />
+
+<hr class="foo" id="bar" />
+
+<hr class="foo" id="bar" />
+
+<hr class="foo" id="bar">
+</html>
+
+----
+
+====== Inline Markup ======
+
+This is //emphasized//, and so //is this//.
+
+This is **strong**, and so **is this**.
+
+An //[[url|emphasized link]]//.
+
+**//This is strong and em.//**
+
+So is **//this//** word.
+
+**//This is strong and em.//**
+
+So is **//this//** word.
+
+This is code: ''%%>%%'', ''%%$%%'', ''%%\%%'', ''%%\$%%'', ''%%<html>%%''.
+
+<del>This is //strikeout//.</del>
+
+Superscripts: a<sup>bc</sup>d a<sup>//hello//</sup> a<sup>hello there</sup>.
+
+Subscripts: H<sub>2</sub>O, H<sub>23</sub>O, H<sub>many of them</sub>O.
+
+These should not be superscripts or subscripts, because of the unescaped spaces: a^b c^d, a~b c~d.
+
+
+----
+
+====== Smart quotes, ellipses, dashes ======
+
+“Hello,” said the spider. “‘Shelob’ is my name.”
+
+‘A’, ‘B’, and ‘C’ are letters.
+
+‘Oak,’ ‘elm,’ and ‘beech’ are names of trees. So is ‘pine.’
+
+‘He said, “I want to go.”’ Were you alive in the 70’s?
+
+Here is some quoted ‘''%%code%%''’ and a “[[http://example.com/?foo=1&bar=2|quoted link]]”.
+
+Some dashes: one—two — three—four — five.
+
+Dashes between numbers: 5–7, 255–66, 1987–1999.
+
+Ellipses…and…and….
+
+
+----
+
+====== LaTeX ======
+
+ *
+ * <math>2+2=4</math>
+ * <math>x \in y</math>
+ * <math>\alpha \wedge \omega</math>
+ * <math>223</math>
+ * <math>p</math>-Tree
+ * Here’s some display math: <math>\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}</math>
+ * Here’s one that has a line break in it: <math>\alpha + \omega \times x^2</math>.
+
+These shouldn’t be math:
+
+ * To get the famous equation, write ''%%$e = mc^2$%%''.
+ * $22,000 is a //lot// of money. So is $34,000. (It worked if “lot” is emphasized.)
+ * Shoes ($20) and socks ($5).
+ * Escaped ''%%$%%'': $73 //this should be emphasized// 23$.
+
+Here’s a LaTeX table:
+
+
+
+----
+
+====== Special Characters ======
+
+Here is some unicode:
+
+ * I hat: Î
+ * o umlaut: ö
+ * section: §
+ * set membership: ∈
+ * copyright: ©
+
+AT&T has an ampersand in their name.
+
+AT&T is another way to write it.
+
+This & that.
+
+4 < 5.
+
+6 > 5.
+
+Backslash: \
+
+Backtick: `
+
+Asterisk: *
+
+Underscore: _
+
+Left brace: {
+
+Right brace: }
+
+Left bracket: [
+
+Right bracket: ]
+
+Left paren: (
+
+Right paren: )
+
+Greater-than: >
+
+Hash: #
+
+Period: .
+
+Bang: !
+
+Plus: +
+
+Minus: -
+
+
+----
+
+====== Links ======
+
+===== Explicit =====
+
+Just a [[url/|URL]].
+
+[[url/|URL and title]].
+
+[[url/|URL and title]].
+
+[[url/|URL and title]].
+
+[[url/|URL and title]]
+
+[[url/|URL and title]]
+
+[[url/with_underscore|with_underscore]]
+
+[[mailto:nobody@nowhere.net|Email link]]
+
+[[|Empty]].
+
+===== Reference =====
+
+Foo [[url/|bar]].
+
+Foo [[url/|bar]].
+
+Foo [[url/|bar]].
+
+With [[url/|embedded [brackets]]].
+
+[[url/|b]] by itself should be a link.
+
+Indented [[url|once]].
+
+Indented [[url|twice]].
+
+Indented [[url|thrice]].
+
+This should [not][] be a link.
+
+<code>[not]: /url</code>
+Foo [[url/|bar]].
+
+Foo [[url/|biz]].
+
+===== With ampersands =====
+
+Here’s a [[http://example.com/?foo=1&bar=2|link with an ampersand in the URL]].
+
+Here’s a link with an amersand in the link text: [[http://att.com/|AT&T]].
+
+Here’s an [[script?foo=1&bar=2|inline link]].
+
+Here’s an [[script?foo=1&bar=2|inline link in pointy braces]].
+
+===== Autolinks =====
+
+With an ampersand: http://example.com/?foo=1&bar=2
+
+ * In a list?
+ * http://example.com/
+ * It should.
+
+An e-mail address: [[mailto:nobody@nowhere.net|nobody@nowhere.net]]
+
+<blockquote>Blockquoted: http://example.com/
+</blockquote>
+Auto-links should not occur here: ''%%<http://example.com/>%%''
+
+<code>or here: <http://example.com/></code>
+
+----
+
+====== Images ======
+
+From “Voyage dans la Lune” by Georges Melies (1902):
+
+{{:lalune.jpg|Voyage dans la Lune lalune}}
+
+Here is a movie {{:movie.jpg|movie}} icon.
+
+
+----
+
+====== Footnotes ======
+
+Here is a footnote reference,((Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document.
+)) and another.((Here’s the long note. This one contains multiple blocks.
+
+Subsequent blocks are indented to show that they belong to the footnote (as with list items).
+
+<code> { <code> }</code>
+If you want, you can indent every line, but you can also be lazy and just indent the first line of each block.
+)) This should //not// be a footnote reference, because it contains a space.[^my note] Here is an inline note.((This is //easier// to type. Inline notes may contain [[http://google.com|links]] and ''%%]%%'' verbatim characters, as well as [bracketed text].
+))
+
+<blockquote>Notes can go in quotes.((In quote.
+))
+</blockquote>
+ - And in list items.((In list.))
+
+This paragraph should not be part of the note, as it is not indented.