Initial work to create dokuwiki writer (#386)

In this first version, all dokuwiki files are straight copies of the
media wiki counterparts.
This commit is contained in:
Clare Macrae 2013-07-14 13:40:27 +01:00
parent bd1079e48e
commit 7eded47bcd
8 changed files with 1280 additions and 3 deletions

@ -1 +1 @@
Subproject commit cb23306c2721d9c1f918f057d7402e03e079476b
Subproject commit c790eff7e1655bcfaf73a26ac4ce53feb0fe1bf7

View file

@ -19,7 +19,7 @@ Description: Pandoc is a Haskell library for converting from one markup
reStructuredText, LaTeX, DocBook, MediaWiki markup, Haddock
markup, OPML, 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,
EPUB (v2 and v3), FictionBook2, and several kinds of
HTML/javascript slide shows (S5, Slidy, Slideous, DZSlides,
@ -324,6 +324,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,

View file

@ -769,6 +769,7 @@ defaultReaderName fallback (x:xs) =
".db" -> "docbook"
".opml" -> "opml"
".wiki" -> "mediawiki"
".dokuwiki" -> "dokuwiki"
".textile" -> "textile"
".native" -> "native"
".json" -> "json"

View file

@ -88,6 +88,7 @@ module Text.Pandoc
, writeOpenDocument
, writeMan
, writeMediaWiki
, writeDokuWiki
, writeTextile
, writeRTF
, writeODT
@ -137,6 +138,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
@ -257,6 +259,7 @@ writers = [
,("plain" , PureStringWriter writePlain)
,("rst" , PureStringWriter writeRST)
,("mediawiki" , PureStringWriter writeMediaWiki)
,("dokuwiki" , PureStringWriter writeDokuWiki)
,("textile" , PureStringWriter writeTextile)
,("rtf" , IOStringWriter writeRTFWithEmbeddedImages)
,("org" , PureStringWriter writeOrg)

View file

@ -0,0 +1,407 @@
{-
Copyright (C) 2008-2010 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-2010 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>
-}
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 Text.Pandoc.XML ( escapeStringForXML )
import Data.List ( intersect, intercalate )
import Network.URI ( isURI )
import Control.Monad.State
data WriterState = WriterState {
stNotes :: Bool -- True if there are notes
, stListLevel :: [Char] -- String at beginning of list items, e.g. "**"
, 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, stListLevel = [], 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 "\n<references />"
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 DokuWiki.
escapeString :: String -> String
escapeString = escapeStringForXML
-- | Convert Pandoc block element to DokuWiki.
blockToDokuWiki :: WriterOptions -- ^ Options
-> Block -- ^ Block element
-> State WriterState String
blockToDokuWiki _ Null = return ""
blockToDokuWiki opts (Plain inlines) =
inlineListToDokuWiki opts inlines
-- title beginning with fig: indicates that the image is a figure
blockToDokuWiki opts (Para [Image txt (src,'f':'i':'g':':':tit)]) = do
capt <- if null txt
then return ""
else ("|caption " ++) `fmap` inlineListToDokuWiki opts txt
let opt = if null txt
then ""
else "|alt=" ++ if null tit then capt else tit ++ capt
return $ "[[Image:" ++ src ++ "|frame|none" ++ opt ++ "]]\n"
blockToDokuWiki opts (Para inlines) = do
useTags <- get >>= return . stUseTags
listLevel <- get >>= return . stListLevel
contents <- inlineListToDokuWiki opts inlines
return $ if useTags
then "<p>" ++ contents ++ "</p>"
else contents ++ if null listLevel then "\n" else ""
blockToDokuWiki _ (RawBlock "mediawiki" str) = return str
blockToDokuWiki _ (RawBlock "html" str) = return str
blockToDokuWiki _ (RawBlock _ _) = return ""
blockToDokuWiki _ HorizontalRule = return "\n-----\n"
blockToDokuWiki opts (Header level _ inlines) = do
contents <- inlineListToDokuWiki opts inlines
let eqs = replicate 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 ("<pre" ++ if null classes then ">" else " class=\"" ++ unwords classes ++ "\">", "</pre>")
else ("<source lang=\"" ++ head at ++ "\">", "</source>")
return $ beg ++ escapeString str ++ end
blockToDokuWiki opts (BlockQuote blocks) = do
contents <- blockListToDokuWiki opts blocks
return $ "<blockquote>" ++ contents ++ "</blockquote>"
blockToDokuWiki opts (Table capt aligns widths headers rows') = do
let alignStrings = map alignmentToString aligns
captionDoc <- if null capt
then return ""
else do
c <- inlineListToDokuWiki opts capt
return $ "<caption>" ++ c ++ "</caption>\n"
let percent w = show (truncate (100*w) :: Integer) ++ "%"
let coltags = if all (== 0.0) widths
then ""
else unlines $ map
(\w -> "<col width=\"" ++ percent w ++ "\" />") widths
head' <- if all null headers
then return ""
else do
hs <- tableRowToDokuWiki opts alignStrings 0 headers
return $ "<thead>\n" ++ hs ++ "\n</thead>\n"
body' <- zipWithM (tableRowToDokuWiki opts alignStrings) [1..] rows'
return $ "<table>\n" ++ captionDoc ++ coltags ++ head' ++
"<tbody>\n" ++ unlines body' ++ "</tbody>\n</table>\n"
blockToDokuWiki opts x@(BulletList items) = do
oldUseTags <- get >>= return . stUseTags
listLevel <- get >>= return . stListLevel
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 { stListLevel = stListLevel s ++ "*" }
contents <- mapM (listItemToDokuWiki opts) items
modify $ \s -> s { stListLevel = init (stListLevel s) }
return $ vcat contents ++ if null listLevel then "\n" else ""
blockToDokuWiki opts x@(OrderedList attribs items) = do
oldUseTags <- get >>= return . stUseTags
listLevel <- get >>= return . stListLevel
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 $ "<ol" ++ listAttribsToString attribs ++ ">\n" ++ vcat contents ++ "</ol>\n"
else do
modify $ \s -> s { stListLevel = stListLevel s ++ "#" }
contents <- mapM (listItemToDokuWiki opts) items
modify $ \s -> s { stListLevel = init (stListLevel s) }
return $ vcat contents ++ if null listLevel then "\n" else ""
blockToDokuWiki opts x@(DefinitionList items) = do
oldUseTags <- get >>= return . stUseTags
listLevel <- get >>= return . stListLevel
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 { stListLevel = stListLevel s ++ ";" }
contents <- mapM (definitionListItemToDokuWiki opts) items
modify $ \s -> s { stListLevel = init (stListLevel s) }
return $ vcat contents ++ if null listLevel 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 or ordered 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
marker <- get >>= return . stListLevel
return $ marker ++ " " ++ 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
marker <- get >>= return . stListLevel
return $ marker ++ " " ++ labelText ++ "\n" ++
(intercalate "\n" $ map (\d -> init marker ++ ": " ++ d) 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 items -> all isSimpleListItem items
OrderedList (num, sty, _) items -> all isSimpleListItem items &&
num == 1 && sty `elem` [DefaultStyle, Decimal]
DefinitionList items -> all isSimpleListItem $ concatMap snd items
_ -> 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:
tableRowToDokuWiki :: WriterOptions
-> [String]
-> Int
-> [[Block]]
-> State WriterState String
tableRowToDokuWiki opts alignStrings rownum cols' = do
let celltype = if rownum == 0 then "th" else "td"
let rowclass = case rownum of
0 -> "header"
x | x `rem` 2 == 1 -> "odd"
_ -> "even"
cols'' <- sequence $ zipWith
(\alignment item -> tableItemToDokuWiki opts celltype alignment item)
alignStrings cols'
return $ "<tr class=\"" ++ rowclass ++ "\">\n" ++ unlines cols'' ++ "</tr>"
alignmentToString :: Alignment -> [Char]
alignmentToString alignment = case alignment of
AlignLeft -> "left"
AlignRight -> "right"
AlignCenter -> "center"
AlignDefault -> "left"
tableItemToDokuWiki :: WriterOptions
-> String
-> String
-> [Block]
-> State WriterState String
tableItemToDokuWiki opts celltype align' item = do
let mkcell x = "<" ++ celltype ++ " align=\"" ++ align' ++ "\">" ++
x ++ "</" ++ celltype ++ ">"
contents <- blockListToDokuWiki opts item
return $ mkcell contents
-- | 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 (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 $ "<s>" ++ contents ++ "</s>"
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) =
return $ "<code>" ++ (escapeString str) ++ "</code>"
inlineToDokuWiki _ (Str str) = return $ escapeString str
inlineToDokuWiki _ (Math _ str) = return $ "<math>" ++ str ++ "</math>"
-- note: str should NOT be escaped
inlineToDokuWiki _ (RawInline "mediawiki" str) = return str
inlineToDokuWiki _ (RawInline "html" str) = return str
inlineToDokuWiki _ (RawInline _ _) = return ""
inlineToDokuWiki _ (LineBreak) = return "<br />"
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 $ "[[Image:" ++ source ++ txt ++ "]]"
inlineToDokuWiki opts (Note contents) = do
contents' <- blockListToDokuWiki opts contents
modify (\s -> s { stNotes = True })
return $ "<ref>" ++ contents' ++ "</ref>"
-- note - may not work for notes with multiple blocks

View file

@ -136,7 +136,7 @@ tests = [ testGroup "markdown"
]
, testGroup "other writers" $ map (\f -> testGroup f $ writerTests f)
[ "opendocument" , "context" , "texinfo"
, "man" , "plain" , "rtf", "org", "asciidoc"
, "man" , "plain" , "rtf", "org", "asciidoc", "dokuwiki"
]
]

212
tests/tables.dokuwiki Normal file
View file

@ -0,0 +1,212 @@
Simple table with caption:
<table>
<caption>Demonstration of simple table syntax.</caption>
<thead>
<tr class="header">
<th align="right">Right</th>
<th align="left">Left</th>
<th align="center">Center</th>
<th align="left">Default</th>
</tr>
</thead>
<tbody>
<tr class="odd">
<td align="right">12</td>
<td align="left">12</td>
<td align="center">12</td>
<td align="left">12</td>
</tr>
<tr class="even">
<td align="right">123</td>
<td align="left">123</td>
<td align="center">123</td>
<td align="left">123</td>
</tr>
<tr class="odd">
<td align="right">1</td>
<td align="left">1</td>
<td align="center">1</td>
<td align="left">1</td>
</tr>
</tbody>
</table>
Simple table without caption:
<table>
<thead>
<tr class="header">
<th align="right">Right</th>
<th align="left">Left</th>
<th align="center">Center</th>
<th align="left">Default</th>
</tr>
</thead>
<tbody>
<tr class="odd">
<td align="right">12</td>
<td align="left">12</td>
<td align="center">12</td>
<td align="left">12</td>
</tr>
<tr class="even">
<td align="right">123</td>
<td align="left">123</td>
<td align="center">123</td>
<td align="left">123</td>
</tr>
<tr class="odd">
<td align="right">1</td>
<td align="left">1</td>
<td align="center">1</td>
<td align="left">1</td>
</tr>
</tbody>
</table>
Simple table indented two spaces:
<table>
<caption>Demonstration of simple table syntax.</caption>
<thead>
<tr class="header">
<th align="right">Right</th>
<th align="left">Left</th>
<th align="center">Center</th>
<th align="left">Default</th>
</tr>
</thead>
<tbody>
<tr class="odd">
<td align="right">12</td>
<td align="left">12</td>
<td align="center">12</td>
<td align="left">12</td>
</tr>
<tr class="even">
<td align="right">123</td>
<td align="left">123</td>
<td align="center">123</td>
<td align="left">123</td>
</tr>
<tr class="odd">
<td align="right">1</td>
<td align="left">1</td>
<td align="center">1</td>
<td align="left">1</td>
</tr>
</tbody>
</table>
Multiline table with caption:
<table>
<caption>Here's the caption. It may span multiple lines.</caption>
<col width="15%" />
<col width="13%" />
<col width="16%" />
<col width="33%" />
<thead>
<tr class="header">
<th align="center">Centered Header</th>
<th align="left">Left Aligned</th>
<th align="right">Right Aligned</th>
<th align="left">Default aligned</th>
</tr>
</thead>
<tbody>
<tr class="odd">
<td align="center">First</td>
<td align="left">row</td>
<td align="right">12.0</td>
<td align="left">Example of a row that spans multiple lines.</td>
</tr>
<tr class="even">
<td align="center">Second</td>
<td align="left">row</td>
<td align="right">5.0</td>
<td align="left">Here's another one. Note the blank line between rows.</td>
</tr>
</tbody>
</table>
Multiline table without caption:
<table>
<col width="15%" />
<col width="13%" />
<col width="16%" />
<col width="33%" />
<thead>
<tr class="header">
<th align="center">Centered Header</th>
<th align="left">Left Aligned</th>
<th align="right">Right Aligned</th>
<th align="left">Default aligned</th>
</tr>
</thead>
<tbody>
<tr class="odd">
<td align="center">First</td>
<td align="left">row</td>
<td align="right">12.0</td>
<td align="left">Example of a row that spans multiple lines.</td>
</tr>
<tr class="even">
<td align="center">Second</td>
<td align="left">row</td>
<td align="right">5.0</td>
<td align="left">Here's another one. Note the blank line between rows.</td>
</tr>
</tbody>
</table>
Table without column headers:
<table>
<tbody>
<tr class="odd">
<td align="right">12</td>
<td align="left">12</td>
<td align="center">12</td>
<td align="right">12</td>
</tr>
<tr class="even">
<td align="right">123</td>
<td align="left">123</td>
<td align="center">123</td>
<td align="right">123</td>
</tr>
<tr class="odd">
<td align="right">1</td>
<td align="left">1</td>
<td align="center">1</td>
<td align="right">1</td>
</tr>
</tbody>
</table>
Multiline table without column headers:
<table>
<col width="15%" />
<col width="13%" />
<col width="16%" />
<col width="33%" />
<tbody>
<tr class="odd">
<td align="center">First</td>
<td align="left">row</td>
<td align="right">12.0</td>
<td align="left">Example of a row that spans multiple lines.</td>
</tr>
<tr class="even">
<td align="center">Second</td>
<td align="left">row</td>
<td align="right">5.0</td>
<td align="left">Here's another one. Note the blank line between rows.</td>
</tr>
</tbody>
</table>

653
tests/writer.dokuwiki Normal file
View file

@ -0,0 +1,653 @@
This is a set of tests for pandoc. Most of them are adapted from John Grubers 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 =
Heres 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.
Heres one with a bullet. * criminey.
There should be a hard line break<br />here.
-----
= Block Quotes =
E-mail style:
<blockquote>This is a block quote. It is pretty short.
</blockquote>
<blockquote>Code in a block quote:
<pre>sub status {
print &quot;working&quot;;
}</pre>
A list:
# item one
# item two
Nested block quotes:
<blockquote>nested
</blockquote>
<blockquote>nested
</blockquote></blockquote>
This should not be a block quote: 2 &gt; 1.
And a following paragraph.
-----
= Code Blocks =
Code:
<pre>---- (should be four hyphens)
sub status {
print &quot;working&quot;;
}
this code block is indented by one tab</pre>
And:
<pre> this code block is indented by two tabs
These should not be escaped: \$ \\ \&gt; \[ \{</pre>
-----
= 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:
<ol style="list-style-type: decimal;">
<li><p>Item 1, graf one.</p>
<p>Item 1. graf two. The quick brown fox jumped over the lazy dogs back.</p></li>
<li><p>Item 2.</p></li>
<li><p>Item 3.</p></li></ol>
== Nested ==
* Tab
** Tab
*** Tab
Heres 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 ==
<ol start="2" style="list-style-type: decimal;">
<li>begins with 2</li>
<li><p>and now 3</p>
<p>with a continuation</p>
<ol start="4" style="list-style-type: lower-roman;">
<li>sublist with roman numerals, starting with 4</li>
<li>more items
<ol style="list-style-type: upper-alpha;">
<li>a subsublist</li>
<li>a subsublist</li></ol>
</li></ol>
</li></ol>
Nesting:
<ol style="list-style-type: upper-alpha;">
<li>Upper Alpha
<ol style="list-style-type: upper-roman;">
<li>Upper Roman.
<ol start="6" style="list-style-type: decimal;">
<li>Decimal start with 6
<ol start="3" style="list-style-type: lower-alpha;">
<li>Lower alpha with paren</li></ol>
</li></ol>
</li></ol>
</li></ol>
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:
<dl>
<dt>''apple''</dt>
<dd><p>red fruit</p>
<p>contains seeds, crisp, pleasant to taste</p></dd>
<dt>''orange''</dt>
<dd><p>orange fruit</p>
<pre>{ orange code block }</pre>
<blockquote><p>orange block quote</p></blockquote></dd></dl>
Multiple definitions, tight:
; apple
: red fruit
: computer
; orange
: orange fruit
: bank
Multiple definitions, loose:
; apple
: red fruit
: computer
; orange
: orange fruit
: bank
Blank line after term, indented marker, alternate markers:
; apple
: red fruit
: computer
; orange
: orange fruit
;# sublist
;# sublist
= HTML Blocks =
Simple block on one line:
<div>
foo
</div>
And nested without indentation:
<div>
<div>
<div>
foo
</div>
</div>
<div>
bar
</div>
</div>
Interpreted markdown in a table:
<table>
<tr>
<td>
This is ''emphasized''
</td>
<td>
And this is '''strong'''
</td>
</tr>
</table>
<script type="text/javascript">document.write('This *should not* be interpreted as markdown');</script>
Heres a simple block:
<div>
foo
</div>
This should be a code block, though:
<pre>&lt;div&gt;
foo
&lt;/div&gt;</pre>
As should this:
<pre>&lt;div&gt;foo&lt;/div&gt;</pre>
Now, nested:
<div>
<div>
<div>
foo
</div>
</div>
</div>
This should just be an HTML comment:
<!-- Comment -->
Multiline:
<!--
Blah
Blah
-->
<!--
This is another comment.
-->
Code block:
<pre>&lt;!-- Comment --&gt;</pre>
Just plain comment, with trailing spaces on the line:
<!-- foo -->
Code:
<pre>&lt;hr /&gt;</pre>
Hrs:
<hr>
<hr />
<hr />
<hr>
<hr />
<hr />
<hr class="foo" id="bar" />
<hr class="foo" id="bar" />
<hr class="foo" id="bar">
-----
= 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: <code>&gt;</code>, <code>$</code>, <code>\</code>, <code>\$</code>, <code>&lt;html&gt;</code>.
<s>This is ''strikeout''.</s>
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 70s?
Here is some quoted <code>code</code> and a “[http://example.com/?foo=1&bar=2 quoted link]”.
Some dashes: one—two — three—four — five.
Dashes between numbers: 57, 25566, 19871999.
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
* Heres some display math: <math>\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}</math>
* Heres one that has a line break in it: <math>\alpha + \omega \times x^2</math>.
These shouldnt be math:
* To get the famous equation, write <code>$e = mc^2$</code>.
* $22,000 is a ''lot'' of money. So is $34,000. (It worked if “lot” is emphasized.)
* Shoes ($20) and socks ($5).
* Escaped <code>$</code>: $73 ''this should be emphasized'' 23$.
Heres a LaTeX table:
-----
= Special Characters =
Here is some unicode:
* I hat: Î
* o umlaut: ö
* section: §
* set membership: ∈
* copyright: ©
AT&amp;T has an ampersand in their name.
AT&amp;T is another way to write it.
This &amp; that.
4 &lt; 5.
6 &gt; 5.
Backslash: \
Backtick: `
Asterisk: *
Underscore: _
Left brace: {
Right brace: }
Left bracket: [
Right bracket: ]
Left paren: (
Right paren: )
Greater-than: &gt;
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.
<pre>[not]: /url</pre>
Foo [[url/|bar]].
Foo [[url/|biz]].
== With ampersands ==
Heres a [http://example.com/?foo=1&bar=2 link with an ampersand in the URL].
Heres a link with an amersand in the link text: [http://att.com/ AT&amp;T].
Heres an [[script?foo=1&bar=2|inline link]].
Heres 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: <code>&lt;http://example.com/&gt;</code>
<pre>or here: &lt;http://example.com/&gt;</pre>
-----
= Images =
From “Voyage dans la Lune” by Georges Melies (1902):
[[Image:lalune.jpg|frame|none|alt=Voyage dans la Lune|caption lalune]]
Here is a movie [[Image:movie.jpg|movie]] icon.
-----
= Footnotes =
Here is a footnote reference,<ref>Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document.
</ref> and another.<ref>Heres the long note. This one contains multiple blocks.
Subsequent blocks are indented to show that they belong to the footnote (as with list items).
<pre> { &lt;code&gt; }</pre>
If you want, you can indent every line, but you can also be lazy and just indent the first line of each block.
</ref> This should ''not'' be a footnote reference, because it contains a space.[^my note] Here is an inline note.<ref>This is ''easier'' to type. Inline notes may contain [http://google.com links] and <code>]</code> verbatim characters, as well as [bracketed text].
</ref>
<blockquote>Notes can go in quotes.<ref>In quote.
</ref>
</blockquote>
# And in list items.<ref>In list.</ref>
This paragraph should not be part of the note, as it is not indented.
<references />