aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJohn MacFarlane <fiddlosopher@gmail.com>2011-11-16 14:52:10 -0800
committerJohn MacFarlane <fiddlosopher@gmail.com>2011-11-16 19:14:55 -0800
commitfc1c17b174eabf10f11bf45c4762569cce505956 (patch)
treee2aacbff63e8c3ae9d48f8a67bb1048c66919ee4
parent1da1d4ec24533e0213d91efb3529d5f84e189465 (diff)
downloadpandoc-fc1c17b174eabf10f11bf45c4762569cce505956.tar.gz
Added an asciidoc writer (partial).
Still TODO: - documentation in README - add default.asciidoc to templates/ - lists - tables - proper escaping - footnotes with blank lines - print separately at end? currently they are just ignored. - fix header (date gives weird result on pandoc README)
-rw-r--r--pandoc.cabal9
-rw-r--r--src/Tests/Old.hs2
-rw-r--r--src/Text/Pandoc.hs3
-rw-r--r--src/Text/Pandoc/Writers/Asciidoc.hs333
-rw-r--r--src/pandoc.hs1
-rw-r--r--tests/tables.asciidoc1
-rw-r--r--tests/writer.asciidoc754
7 files changed, 1099 insertions, 4 deletions
diff --git a/pandoc.cabal b/pandoc.cabal
index 538f26ce2..f4559be3d 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -19,8 +19,8 @@ Description: Pandoc is a Haskell library for converting from one markup
reStructuredText, HTML, LaTeX and Textile, and it can write
markdown, reStructuredText, HTML, LaTeX, ConTeXt, Docbook,
OpenDocument, ODT, RTF, MediaWiki, Textile, groff man pages,
- plain text, Emacs Org-Mode, EPUB, and S5 and Slidy HTML
- slide shows.
+ plain text, Emacs Org-Mode, Asciidoc, EPUB,
+ and S5 and Slidy HTML slide shows.
.
Pandoc extends standard markdown syntax with footnotes,
embedded LaTeX, definition lists, tables, and other
@@ -44,7 +44,7 @@ Data-Files:
templates/default.rst, templates/default.plain,
templates/default.mediawiki, templates/default.rtf,
templates/default.s5, templates/default.slidy,
- templates/default.dzslides,
+ templates/default.dzslides, templates/default.asciidoc,
templates/default.textile, templates/default.org
-- data for ODT writer
reference.odt,
@@ -122,6 +122,7 @@ Extra-Source-Files:
tests/tables.native,
tests/tables.opendocument,
tests/tables.org,
+ tests/tables.asciidoc,
tests/tables.texinfo,
tests/tables.rst,
tests/tables.rtf,
@@ -141,6 +142,7 @@ Extra-Source-Files:
tests/writer.native,
tests/writer.opendocument,
tests/writer.org,
+ tests/writer.asciidoc,
tests/writer.rst,
tests/writer.rtf,
tests/writer.texinfo,
@@ -253,6 +255,7 @@ Library
Text.Pandoc.Writers.Markdown,
Text.Pandoc.Writers.RST,
Text.Pandoc.Writers.Org,
+ Text.Pandoc.Writers.Asciidoc,
Text.Pandoc.Writers.Textile,
Text.Pandoc.Writers.MediaWiki,
Text.Pandoc.Writers.RTF,
diff --git a/src/Tests/Old.hs b/src/Tests/Old.hs
index cb1417ffa..71a198ca1 100644
--- a/src/Tests/Old.hs
+++ b/src/Tests/Old.hs
@@ -105,7 +105,7 @@ tests = [ testGroup "markdown"
]
, testGroup "other writers" $ map (\f -> testGroup f $ writerTests f)
[ "docbook", "opendocument" , "context" , "texinfo"
- , "man" , "plain" , "mediawiki", "rtf", "org"
+ , "man" , "plain" , "mediawiki", "rtf", "org", "asciidoc"
]
]
diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs
index 4517b0d52..27b263011 100644
--- a/src/Text/Pandoc.hs
+++ b/src/Text/Pandoc.hs
@@ -96,6 +96,7 @@ module Text.Pandoc
, writeODT
, writeEPUB
, writeOrg
+ , writeAsciidoc
-- * Writer options used in writers
, WriterOptions (..)
, HTMLSlideVariant (..)
@@ -135,6 +136,7 @@ import Text.Pandoc.Writers.RTF
import Text.Pandoc.Writers.MediaWiki
import Text.Pandoc.Writers.Textile
import Text.Pandoc.Writers.Org
+import Text.Pandoc.Writers.Asciidoc
import Text.Pandoc.Templates
import Text.Pandoc.Parsing
import Text.Pandoc.Shared
@@ -193,6 +195,7 @@ writers = [("native" , writeNative)
,("textile" , writeTextile)
,("rtf" , writeRTF)
,("org" , writeOrg)
+ ,("asciidoc" , writeAsciidoc)
]
-- | Converts a transformation on the Pandoc AST into a function
diff --git a/src/Text/Pandoc/Writers/Asciidoc.hs b/src/Text/Pandoc/Writers/Asciidoc.hs
new file mode 100644
index 000000000..c8319764a
--- /dev/null
+++ b/src/Text/Pandoc/Writers/Asciidoc.hs
@@ -0,0 +1,333 @@
+{-# LANGUAGE OverloadedStrings #-}
+{-
+Copyright (C) 2006-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.Asciidoc
+ Copyright : Copyright (C) 2006-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 asciidoc.
+
+Asciidoc: <http://www.methods.co.nz/asciidoc/>
+-}
+module Text.Pandoc.Writers.Asciidoc (writeAsciidoc) where
+import Text.Pandoc.Definition
+import Text.Pandoc.Templates (renderTemplate)
+import Text.Pandoc.Shared
+import Text.Pandoc.Parsing hiding (blankline)
+import Text.ParserCombinators.Parsec ( runParser, GenParser )
+import Data.List ( isPrefixOf, intersperse, intercalate, transpose )
+import Text.Pandoc.Pretty
+import Control.Monad.State
+
+data WriterState = WriterState { }
+
+-- | Convert Pandoc to Asciidoc.
+writeAsciidoc :: WriterOptions -> Pandoc -> String
+writeAsciidoc opts document =
+ evalState (pandocToAsciidoc opts document) WriterState{ }
+
+-- | Return markdown representation of document.
+pandocToAsciidoc :: WriterOptions -> Pandoc -> State WriterState String
+pandocToAsciidoc opts (Pandoc (Meta title authors date) blocks) = do
+ title' <- inlineListToAsciidoc opts title
+ let title'' = title' $$ text (replicate (offset title') '=')
+ authors' <- take 1 `fmap` mapM (inlineListToAsciidoc opts) authors
+ -- asciidoc only allows a singel author
+ date' <- inlineListToAsciidoc opts date
+ let titleblock = not $ null title && null authors && null date
+ body <- blockListToAsciidoc opts blocks
+ let colwidth = if writerWrapText opts
+ then Just $ writerColumns opts
+ else Nothing
+ let main = render colwidth body
+ let context = writerVariables opts ++
+ [ ("body", main)
+ , ("title", render colwidth title'')
+ , ("date", render colwidth date')
+ ] ++
+ [ ("toc", "yes") | writerTableOfContents opts &&
+ writerStandalone opts ] ++
+ [ ("titleblock", "yes") | titleblock ] ++
+ [ ("author", render colwidth a) | a <- authors' ]
+ if writerStandalone opts
+ then return $ renderTemplate context $ writerTemplate opts
+ else return main
+
+-- | Escape special characters for Asciidoc.
+escapeString :: String -> String
+escapeString = escapeStringUsing markdownEscapes
+ where markdownEscapes = backslashEscapes "\\`*_>#~^{+"
+
+-- | Ordered list start parser for use in Para below.
+olMarker :: GenParser Char ParserState Char
+olMarker = do (start, style', delim) <- anyOrderedListMarker
+ if delim == Period &&
+ (style' == UpperAlpha || (style' == UpperRoman &&
+ start `elem` [1, 5, 10, 50, 100, 500, 1000]))
+ then spaceChar >> spaceChar
+ else spaceChar
+
+-- | True if string begins with an ordered list marker
+beginsWithOrderedListMarker :: String -> Bool
+beginsWithOrderedListMarker str =
+ case runParser olMarker defaultParserState "para start" (take 10 str) of
+ Left _ -> False
+ Right _ -> True
+
+-- | Convert Pandoc block element to markdown.
+blockToAsciidoc :: WriterOptions -- ^ Options
+ -> Block -- ^ Block element
+ -> State WriterState Doc
+blockToAsciidoc _ Null = return empty
+blockToAsciidoc opts (Plain inlines) = do
+ contents <- inlineListToAsciidoc opts inlines
+ return $ contents <> cr
+blockToAsciidoc opts (Para inlines) = do
+ contents <- inlineListToAsciidoc opts inlines
+ -- escape if para starts with ordered list marker
+ let esc = if beginsWithOrderedListMarker (render Nothing contents)
+ then text "\\"
+ else empty
+ return $ esc <> contents <> blankline
+blockToAsciidoc _ (RawBlock f str) | f == "html" || f == "docbook" = do
+ return $ "+++" $$ text str $$ "+++" <> blankline
+blockToAsciidoc _ (RawBlock _ _) = return empty
+blockToAsciidoc _ HorizontalRule =
+ return $ blankline <> text "'''''" <> blankline
+blockToAsciidoc opts (Header level inlines) = do
+ contents <- inlineListToAsciidoc opts inlines
+ let len = offset contents
+ return $ contents <> cr <>
+ (case level of
+ 1 -> text $ replicate len '-'
+ 2 -> text $ replicate len '~'
+ 3 -> text $ replicate len '^'
+ 4 -> text $ replicate len '+'
+ _ -> empty) <> blankline
+blockToAsciidoc _ (CodeBlock (_,classes,_) str) = return $
+ flush (attrs <> dashes <> space <> attrs <> cr <> text str <>
+ cr <> dashes) <> blankline
+ where dashes = text $ replicate (maximum $ map length $ lines str) '-'
+ attrs = if null classes
+ then empty
+ else text $ intercalate "," $ "code" : classes
+blockToAsciidoc opts (BlockQuote blocks) = do
+ contents <- blockListToAsciidoc opts blocks
+ let cols = offset contents
+ let bar = text $ replicate cols '_'
+ return $ bar $$ contents $$ bar <> blankline
+blockToAsciidoc opts (Table caption aligns widths headers rows) = do
+ caption' <- inlineListToAsciidoc opts caption
+ let caption'' = if null caption
+ then empty
+ else blankline <> ": " <> caption' <> blankline
+ headers' <- mapM (blockListToAsciidoc opts) headers
+ let alignHeader alignment = case alignment of
+ AlignLeft -> lblock
+ AlignCenter -> cblock
+ AlignRight -> rblock
+ AlignDefault -> lblock
+ rawRows <- mapM (mapM (blockListToAsciidoc opts)) rows
+ let isSimple = all (==0) widths
+ let numChars = maximum . map offset
+ let widthsInChars =
+ if isSimple
+ then map ((+2) . numChars) $ transpose (headers' : rawRows)
+ else map (floor . (fromIntegral (writerColumns opts) *)) widths
+ let makeRow = hcat . intersperse (lblock 1 (text " ")) .
+ (zipWith3 alignHeader aligns widthsInChars)
+ let rows' = map makeRow rawRows
+ let head' = makeRow headers'
+ let maxRowHeight = maximum $ map height (head':rows')
+ let underline = cat $ intersperse (text " ") $
+ map (\width -> text (replicate width '-')) widthsInChars
+ let border = if maxRowHeight > 1
+ then text (replicate (sum widthsInChars +
+ length widthsInChars - 1) '-')
+ else if all null headers
+ then underline
+ else empty
+ let head'' = if all null headers
+ then empty
+ else border <> cr <> head'
+ let body = if maxRowHeight > 1
+ then vsep rows'
+ else vcat rows'
+ let bottom = if all null headers
+ then underline
+ else border
+ return $ nest 2 $ head'' $$ underline $$ body $$
+ bottom $$ blankline $$ caption'' $$ blankline
+blockToAsciidoc opts (BulletList items) = do
+ contents <- mapM (bulletListItemToAsciidoc opts) items
+ return $ cat contents <> blankline
+blockToAsciidoc opts (OrderedList attribs items) = do
+ let markers = orderedListMarkers attribs
+ let markers' = map (\m -> if length m < 3
+ then m ++ replicate (3 - length m) ' '
+ else m) markers
+ contents <- mapM (\(item, num) -> orderedListItemToAsciidoc opts item num) $
+ zip markers' items
+ return $ cat contents <> blankline
+blockToAsciidoc opts (DefinitionList items) = do
+ contents <- mapM (definitionListItemToAsciidoc opts) items
+ return $ cat contents <> blankline
+
+-- | Convert bullet list item (list of blocks) to markdown.
+bulletListItemToAsciidoc :: WriterOptions -> [Block] -> State WriterState Doc
+bulletListItemToAsciidoc opts items = do
+ contents <- blockListToAsciidoc opts items
+ let sps = replicate (writerTabStop opts - 2) ' '
+ let start = text ('-' : ' ' : sps)
+ return $ hang (writerTabStop opts) start $ contents <> cr
+
+-- | Convert ordered list item (a list of blocks) to markdown.
+orderedListItemToAsciidoc :: WriterOptions -- ^ options
+ -> String -- ^ list item marker
+ -> [Block] -- ^ list item (list of blocks)
+ -> State WriterState Doc
+orderedListItemToAsciidoc opts marker items = do
+ contents <- blockListToAsciidoc opts items
+ let sps = case length marker - writerTabStop opts of
+ n | n > 0 -> text $ replicate n ' '
+ _ -> text " "
+ let start = text marker <> sps
+ return $ hang (writerTabStop opts) start $ contents <> cr
+
+-- | Convert definition list item (label, list of blocks) to markdown.
+definitionListItemToAsciidoc :: WriterOptions
+ -> ([Inline],[[Block]])
+ -> State WriterState Doc
+definitionListItemToAsciidoc opts (label, defs) = do
+ labelText <- inlineListToAsciidoc opts label
+ let tabStop = writerTabStop opts
+ let leader = " ~"
+ let sps = case writerTabStop opts - 3 of
+ n | n > 0 -> text $ replicate n ' '
+ _ -> text " "
+ defs' <- mapM (mapM (blockToAsciidoc opts)) defs
+ let contents = vcat $ map (\d -> hang tabStop (leader <> sps) $ vcat d <> cr) defs'
+ return $ labelText <> cr <> contents <> cr
+
+-- | Convert list of Pandoc block elements to markdown.
+blockListToAsciidoc :: WriterOptions -- ^ Options
+ -> [Block] -- ^ List of block elements
+ -> State WriterState Doc
+blockListToAsciidoc opts blocks =
+ mapM (blockToAsciidoc opts) (fixBlocks blocks) >>= return . cat
+ -- insert comment between list and indented code block, or the
+ -- code block will be treated as a list continuation paragraph
+ where fixBlocks (b : CodeBlock attr x : rest)
+ | (attr == nullAttr) && isListBlock b =
+ b : RawBlock "html" "<!-- -->\n" : CodeBlock attr x :
+ fixBlocks rest
+ fixBlocks (x : xs) = x : fixBlocks xs
+ fixBlocks [] = []
+ isListBlock (BulletList _) = True
+ isListBlock (OrderedList _ _) = True
+ isListBlock (DefinitionList _) = True
+ isListBlock _ = False
+
+-- | Convert list of Pandoc inline elements to markdown.
+inlineListToAsciidoc :: WriterOptions -> [Inline] -> State WriterState Doc
+inlineListToAsciidoc opts lst =
+ mapM (inlineToAsciidoc opts) lst >>= return . cat
+
+-- | Convert Pandoc inline element to markdown.
+inlineToAsciidoc :: WriterOptions -> Inline -> State WriterState Doc
+inlineToAsciidoc opts (Emph lst) = do
+ contents <- inlineListToAsciidoc opts lst
+ return $ "_" <> contents <> "_"
+inlineToAsciidoc opts (Strong lst) = do
+ contents <- inlineListToAsciidoc opts lst
+ return $ "*" <> contents <> "*"
+inlineToAsciidoc opts (Strikeout lst) = do
+ contents <- inlineListToAsciidoc opts lst
+ return $ "[line-through]*" <> contents <> "*"
+inlineToAsciidoc opts (Superscript lst) = do
+ contents <- inlineListToAsciidoc opts lst
+ return $ "^" <> contents <> "^"
+inlineToAsciidoc opts (Subscript lst) = do
+ contents <- inlineListToAsciidoc opts lst
+ return $ "~" <> contents <> "~"
+inlineToAsciidoc opts (SmallCaps lst) = inlineListToAsciidoc opts lst
+inlineToAsciidoc opts (Quoted SingleQuote lst) = do
+ contents <- inlineListToAsciidoc opts lst
+ return $ "`" <> contents <> "'"
+inlineToAsciidoc opts (Quoted DoubleQuote lst) = do
+ contents <- inlineListToAsciidoc opts lst
+ return $ "``" <> contents <> "''"
+inlineToAsciidoc _ EmDash = return "\8212"
+inlineToAsciidoc _ EnDash = return "\8211"
+inlineToAsciidoc _ Apostrophe = return "\8217"
+inlineToAsciidoc _ Ellipses = return "\8230"
+inlineToAsciidoc _ (Code _ str) = return $
+ text "`" <> text (escapeStringUsing (backslashEscapes "`") str) <> "`"
+inlineToAsciidoc _ (Str str) = return $ text $ escapeString str
+inlineToAsciidoc _ (Math InlineMath str) =
+ return $ "latexmath:[$" <> text str <> "$]"
+inlineToAsciidoc _ (Math DisplayMath str) =
+ return $ "latexmath:[$$" <> text str <> "$$]"
+inlineToAsciidoc _ (RawInline _ _) = return empty
+inlineToAsciidoc _ (LineBreak) = return $ " +" <> cr
+inlineToAsciidoc _ Space = return space
+inlineToAsciidoc opts (Cite _ lst) = inlineListToAsciidoc opts lst
+inlineToAsciidoc opts (Link txt (src', tit)) = do
+-- relative: link:downloads/foo.zip[download foo.zip]
+-- abs: http://google.cod[Google]
+-- or my@email.com[email john]
+ linktext <- inlineListToAsciidoc opts txt
+ let linktitle = if null tit
+ then empty
+ else text $ ",title=\"" ++ tit ++ "\""
+ let src = unescapeURI src'
+ let isRelative = ':' `elem` src
+ let prefix = if isRelative
+ then text "link:"
+ else empty
+ let srcSuffix = if isPrefixOf "mailto:" src then drop 7 src else src
+ let useAuto = case (tit,txt) of
+ ("", [Code _ s]) | s == srcSuffix -> True
+ _ -> False
+ return $ if useAuto
+ then text srcSuffix
+ else prefix <> text src <> "[" <> linktext <> linktitle <> "]"
+inlineToAsciidoc opts (Image alternate (src', tit)) = do
+-- image:images/logo.png[Company logo, title="blah"]
+ let txt = if (null alternate) || (alternate == [Str ""])
+ then [Str "image"]
+ else alternate
+ linktext <- inlineListToAsciidoc opts txt
+ let linktitle = if null tit
+ then empty
+ else text $ ",title=\"" ++ tit ++ "\""
+ let src = unescapeURI src'
+ return $ "image:" <> text src <> "[" <> linktext <> linktitle <> "]"
+inlineToAsciidoc opts (Note [Para inlines]) =
+ inlineToAsciidoc opts (Note [Plain inlines])
+inlineToAsciidoc opts (Note [Plain inlines]) = do
+ contents <- inlineListToAsciidoc opts inlines
+ return $ text "footnote:[" <> contents <> "]"
+-- asciidoc can't handle blank lines in notes
+inlineToAsciidoc _ (Note _) = return empty
diff --git a/src/pandoc.hs b/src/pandoc.hs
index 387fc8095..1caa6d58a 100644
--- a/src/pandoc.hs
+++ b/src/pandoc.hs
@@ -647,6 +647,7 @@ defaultWriterName x =
".odt" -> "odt"
".epub" -> "epub"
".org" -> "org"
+ ".asciidoc" -> "asciidoc"
['.',y] | y `elem` ['1'..'9'] -> "man"
_ -> "html"
diff --git a/tests/tables.asciidoc b/tests/tables.asciidoc
new file mode 100644
index 000000000..48cdce852
--- /dev/null
+++ b/tests/tables.asciidoc
@@ -0,0 +1 @@
+placeholder
diff --git a/tests/writer.asciidoc b/tests/writer.asciidoc
new file mode 100644
index 000000000..60a9518a7
--- /dev/null
+++ b/tests/writer.asciidoc
@@ -0,0 +1,754 @@
+Pandoc Test Suite
+=================
+John MacFarlane; Anonymous
+July 17, 2006
+
+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 link:/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:
+
+__________________________________________
+This is a block quote. It is pretty short.
+__________________________________________
+
+------------------------
+Code in a block quote:
+
+ sub status {
+ print "working";
+ }
+------------------------
+
+A list:
+
+. item one
+. item two
+
+Nested block quotes:
+
+______
+nested
+______
+nested
+______
+______
+
+This should not be a block quote: 2 \> 1.
+
+And a following paragraph.
+
+'''''
+
+Code Blocks
+-----------
+
+Code:
+
+----
+---- (should be four hyphens)
+
+sub status {
+ print "working";
+}
+
+this code block is indented by one tab
+----
+
+And:
+
+----
+ this code block is indented by two tabs
+
+These should not be escaped: \$ \\ \> \[ \{
+----
+
+'''''
+
+Lists
+-----
+
+Unordered
+~~~~~~~~~
+
+Asterisks tight:
+
+[options="compact"]
+* asterisk 1
+* asterisk 2
+* asterisk 3
+
+Asterisks loose:
+
+* asterisk 1
+
+* asterisk 2
+
+* asterisk 3
+
+Pluses tight:
+
+[options="compact"]
+* Plus 1
+* Plus 2
+* Plus 3
+
+Pluses loose:
+
+* Plus 1
+
+* Plus 2
+
+* Plus 3
+
+Minuses tight:
+
+[options="compact"]
+* Minus 1
+* Minus 2
+* Minus 3
+
+Minuses loose:
+
+* Minus 1
+
+* Minus 2
+
+* Minus 3
+
+Ordered
+~~~~~~~
+
+Tight:
+
+[options="compact"]
+1. First
+2. Second
+3. Third
+
+and:
+
+[options="compact"]
+1. One
+2. Two
+3. Three
+
+Loose using tabs:
+
+1. First
+
+2. Second
+
+3. Third
+
+and using spaces:
+
+1. One
+
+2. Two
+
+3. Three
+
+Multiple paragraphs:
+
+1. Item 1, graf one.
++
+Item 1. graf two. The quick brown fox jumped over the lazy dog’s back.
+
+2. Item 2.
+
+3. Item 3.
+
+Nested
+~~~~~~
+
+* Tab
+** Tab
+*** Tab
+
+Here’s another:
+
+1. First
+2. Second:
+ [options="compact"]
+ * Fee
+ * Fie
+ * Foe
+
+3. Third
+
+Same thing but with paragraphs:
+
+1. First
+
+2. Second:
+
+ [options="compact"]
+ * Fee
+ * Fie
+ * Foe
+
+3. 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
+~~~~~~~~~~~~~~~~~~
+
+[start=2]
+2. begins with 2
+3. and now 3
++
+with a continuation
++
+[start=4]
+4. sublist with roman numerals, starting with 4
+5. more items
+ A. a subsublist
+ B. a subsublist
+
+Nesting:
+
+A. Upper Alpha
+ 1. Upper Roman.
+ +
+ [start=6]
+ 6. Decimal start with 6
+ +
+ [start=3]
+ c. Lower alpha with paren
+
+Autonumbering:
+
+1. Autonumber.
+2. More.
+ 1. 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
+
+ { orange code block }
+
+ > orange block quote
+
+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
+
+ 1. sublist
+ 2. 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>
+
+Here’s a simple block:
+
+<div>
+
+foo
+</div>
+
+This should be a code block, though:
+
+ <div>
+ foo
+ </div>
+
+As should this:
+
+ <div>foo</div>
+
+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:
+
+ <!-- Comment -->
+
+Just plain comment, with trailing spaces on the line:
+
+<!-- foo -->
+
+Code:
+
+ <hr />
+
+Hr’s:
+
+<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 *[emphasized link](/url)*.
+
+***This is strong and em.***
+
+So is ***this*** word.
+
+***This is strong and em.***
+
+So is ***this*** word.
+
+This is code: `>`, `$`, `\`, `\$`, `<html>`.
+
+~~This is *strikeout*.~~
+
+Superscripts: a^bc^d a^*hello*^ a^hello there^.
+
+Subscripts: H~2~O, H~23~O, H~many of them~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 “[quoted
+link](http://example.com/?foo=1&bar=2)”.
+
+Some dashes: one—two — three—four — five.
+
+Dashes between numbers: 5–7, 255–66, 1987–1999.
+
+Ellipses…and…and….
+
+'''''
+
+LaTeX
+-----
+
+- \cite[22-23]{smith.1899}
+- $2+2=4$
+- $x \in y$
+- $\alpha \wedge \omega$
+- $223$
+- $p$-Tree
+- Here’s some display math:
+ $$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$
+- Here’s one that has a line break in it: $\alpha + \omega \times x^2$.
+
+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:
+
+\begin{tabular}{|l|l|}\hline
+Animal & Number \\ \hline
+Dog & 2 \\
+Cat & 1 \\ \hline
+\end{tabular}
+
+'''''
+
+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 and title](/url/ "title").
+
+[URL and title](/url/ "title preceded by two spaces").
+
+[URL and title](/url/ "title preceded by a tab").
+
+[URL and title](/url/ "title with "quotes" in it")
+
+[URL and title](/url/ "title with single quotes")
+
+[with\_underscore](/url/with_underscore)
+
+[Email link](mailto:nobody@nowhere.net)
+
+[Empty]().
+
+Reference
+~~~~~~~~~
+
+Foo [bar](/url/).
+
+Foo [bar](/url/).
+
+Foo [bar](/url/).
+
+With [embedded [brackets]](/url/).
+
+[b](/url/) by itself should be a link.
+
+Indented [once](/url).
+
+Indented [twice](/url).
+
+Indented [thrice](/url).
+
+This should [not][] be a link.
+
+ [not]: /url
+
+Foo [bar](/url/ "Title with "quotes" inside").
+
+Foo [biz](/url/ "Title with "quote" inside").
+
+With ampersands
+~~~~~~~~~~~~~~~
+
+Here’s a [link with an ampersand in the URL](http://example.com/?foo=1&bar=2).
+
+Here’s a link with an amersand in the link text:
+[AT&T](http://att.com/ "AT&T").
+
+Here’s an [inline link](/script?foo=1&bar=2).
+
+Here’s an [inline link in pointy braces](/script?foo=1&bar=2).
+
+Autolinks
+~~~~~~~~~
+
+With an ampersand: <http://example.com/?foo=1&bar=2>
+
+- In a list?
+- <http://example.com/>
+- It should.
+
+An e-mail address: <nobody@nowhere.net>
+
+> Blockquoted: <http://example.com/>
+
+Auto-links should not occur here: `<http://example.com/>`
+
+ or here: <http://example.com/>
+
+'''''
+
+Images
+------
+
+From “Voyage dans la Lune” by Georges Melies (1902):
+
+![lalune](lalune.jpg "Voyage dans la Lune")
+
+Here is a movie ![movie](movie.jpg) icon.
+
+'''''
+
+Footnotes
+---------
+
+Here is a footnote reference,[^1] and another.[^2] This should *not* be a
+footnote reference, because it contains a space.[\^my note] Here is an inline
+note.[^3]
+
+> Notes can go in quotes.[^4]
+
+1. And in list items.[^5]
+
+This paragraph should not be part of the note, as it is not indented.
+
+[^1]: Here is the footnote. It can go anywhere after the footnote reference.
+ It need not be placed at the end of the document.
+
+[^2]: 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> }
+
+ If you want, you can indent every line, but you can also be lazy and just
+ indent the first line of each block.
+
+[^3]: This is *easier* to type. Inline notes may contain
+ [links](http://google.com) and `]` verbatim characters, as well as
+ [bracketed text].
+
+[^4]: In quote.
+
+[^5]: In list.