diff options
-rw-r--r-- | pandoc.cabal | 9 | ||||
-rw-r--r-- | src/Tests/Old.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc.hs | 3 | ||||
-rw-r--r-- | src/Text/Pandoc/Pretty.hs | 13 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Asciidoc.hs | 369 | ||||
-rw-r--r-- | src/pandoc.hs | 1 | ||||
m--------- | templates | 10 | ||||
-rw-r--r-- | tests/tables.asciidoc | 71 | ||||
-rw-r--r-- | tests/writer.asciidoc | 656 |
9 files changed, 1125 insertions, 9 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/Pretty.hs b/src/Text/Pandoc/Pretty.hs index 54d65af6f..5c6eee27c 100644 --- a/src/Text/Pandoc/Pretty.hs +++ b/src/Text/Pandoc/Pretty.hs @@ -59,6 +59,7 @@ module Text.Pandoc.Pretty ( , hsep , vcat , vsep + , chomp , inside , braces , brackets @@ -164,6 +165,17 @@ vcat = foldr ($$) empty vsep :: [Doc] -> Doc vsep = foldr ($+$) empty +-- | Chomps trailing blank space off of a 'Doc'. +chomp :: Doc -> Doc +chomp d = Doc (fromList dl') + where dl = toList (unDoc d) + dl' = reverse $ dropWhile removeable $ reverse dl + removeable BreakingSpace = True + removeable CarriageReturn = True + removeable NewLine = True + removeable BlankLine = True + removeable _ = False + outp :: (IsString a, Monoid a) => Int -> String -> DocState a outp off s | off <= 0 = do @@ -427,3 +439,4 @@ quotes = inside (char '\'') (char '\'') -- | Wraps a 'Doc' in double quotes. doubleQuotes :: Doc -> Doc doubleQuotes = inside (char '"') (char '"') + diff --git a/src/Text/Pandoc/Writers/Asciidoc.hs b/src/Text/Pandoc/Writers/Asciidoc.hs new file mode 100644 index 000000000..91930ac68 --- /dev/null +++ b/src/Text/Pandoc/Writers/Asciidoc.hs @@ -0,0 +1,369 @@ +{-# 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. + +Note that some information may be lost in conversion, due to +expressive limitations of asciidoc. Footnotes and table cells with +paragraphs (or other block items) are not possible in asciidoc. +If pandoc encounters one of these, it will insert a message indicating +that it has omitted the construct. + +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 ) +import Text.Pandoc.Pretty +import Control.Monad.State + +data WriterState = WriterState { defListMarker :: String + , orderedListLevel :: Int + , bulletListLevel :: Int + } + +-- | Convert Pandoc to Asciidoc. +writeAsciidoc :: WriterOptions -> Pandoc -> String +writeAsciidoc opts document = + evalState (pandocToAsciidoc opts document) WriterState{ + defListMarker = "::" + , orderedListLevel = 1 + , bulletListLevel = 1 + } + +-- | 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' <- 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 _ _) = 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 isBlock (BlockQuote _) = True + isBlock _ = False + -- if there are nested block quotes, put in an open block + let contents' = if any isBlock blocks + then "--" $$ contents $$ "--" + else contents + let cols = offset contents' + let bar = text $ replicate cols '_' + return $ bar $$ chomp contents' $$ bar <> blankline +blockToAsciidoc opts (Table caption aligns widths headers rows) = do + caption' <- inlineListToAsciidoc opts caption + let caption'' = if null caption + then empty + else "." <> caption' <> cr + let isSimple = all (== 0) widths + let relativePercentWidths = if isSimple + then widths + else map (/ (sum widths)) widths + let widths'' :: [Integer] + widths'' = map (floor . (* 100)) relativePercentWidths + -- ensure that the widths sum to 100 + let widths' = case widths'' of + _ | isSimple -> widths'' + (w:ws) | sum (w:ws) < 100 + -> (100 - sum ws) : ws + ws -> ws + let totalwidth :: Integer + totalwidth = floor $ sum widths * 100 + let colspec al wi = (case al of + AlignLeft -> "<" + AlignCenter -> "^" + AlignRight -> ">" + AlignDefault -> "") ++ + if wi == 0 then "" else (show wi ++ "%") + let headerspec = if all null headers + then empty + else text "options=\"header\"," + let widthspec = if totalwidth == 0 + then empty + else text "width=" + <> doubleQuotes (text $ show totalwidth ++ "%") + <> text "," + let tablespec = text "[" + <> widthspec + <> text "cols=" + <> doubleQuotes (text $ intercalate "," + $ zipWith colspec aligns widths') + <> text "," + <> headerspec <> text "]" + let makeCell [Plain x] = do d <- blockListToAsciidoc opts [Plain x] + return $ text "|" <> chomp d + makeCell [Para x] = makeCell [Plain x] + makeCell _ = return $ text "|" <> "[multiblock cell omitted]" + let makeRow cells = hsep `fmap` mapM makeCell cells + rows' <- mapM makeRow rows + head' <- makeRow headers + let head'' = if all null headers then empty else head' + let colwidth = if writerWrapText opts + then writerColumns opts + else 100000 + let maxwidth = maximum $ map offset (head':rows') + let body = if maxwidth > colwidth then vsep rows' else vcat rows' + let border = text $ "|" ++ replicate ((min maxwidth colwidth) - 1) '=' + return $ + caption'' $$ tablespec $$ border $$ head'' $$ body $$ border $$ blankline +blockToAsciidoc opts (BulletList items) = do + contents <- mapM (bulletListItemToAsciidoc opts) items + return $ cat contents <> blankline +blockToAsciidoc opts (OrderedList (start, sty, _delim) items) = do + let markers = orderedListMarkers (start, sty, Period) + 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 blocks = do + let addBlock :: Doc -> Block -> State WriterState Doc + addBlock d b | isEmpty d = chomp `fmap` blockToAsciidoc opts b + addBlock d b@(BulletList _) = do x <- blockToAsciidoc opts b + return $ d <> cr <> chomp x + addBlock d b@(OrderedList _ _) = do x <- blockToAsciidoc opts b + return $ d <> cr <> chomp x + addBlock d b = do x <- blockToAsciidoc opts b + return $ d <> cr <> text "+" <> cr <> chomp x + lev <- bulletListLevel `fmap` get + modify $ \s -> s{ bulletListLevel = lev + 1 } + contents <- foldM addBlock empty blocks + modify $ \s -> s{ bulletListLevel = lev } + let marker = text (replicate lev '*') + return $ marker <> space <> 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 blocks = do + let addBlock :: Doc -> Block -> State WriterState Doc + addBlock d b | isEmpty d = chomp `fmap` blockToAsciidoc opts b + addBlock d b@(BulletList _) = do x <- blockToAsciidoc opts b + return $ d <> cr <> chomp x + addBlock d b@(OrderedList _ _) = do x <- blockToAsciidoc opts b + return $ d <> cr <> chomp x + addBlock d b = do x <- blockToAsciidoc opts b + return $ d <> cr <> text "+" <> cr <> chomp x + lev <- orderedListLevel `fmap` get + modify $ \s -> s{ orderedListLevel = lev + 1 } + contents <- foldM addBlock empty blocks + modify $ \s -> s{ orderedListLevel = lev } + return $ text marker <> space <> 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 + marker <- defListMarker `fmap` get + if marker == "::" + then modify (\st -> st{ defListMarker = ";;"}) + else modify (\st -> st{ defListMarker = "::"}) + let divider = cr <> text "+" <> cr + let defsToAsciidoc :: [Block] -> State WriterState Doc + defsToAsciidoc ds = (vcat . intersperse divider . map chomp) + `fmap` mapM (blockToAsciidoc opts) ds + defs' <- mapM defsToAsciidoc defs + modify (\st -> st{ defListMarker = marker }) + let contents = nest 2 $ vcat $ intersperse divider $ map chomp defs' + return $ labelText <> text marker <> 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 = cat `fmap` mapM (blockToAsciidoc opts) blocks + +-- | 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 src = unescapeURI src' + let isRelative = ':' `notElem` 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 txt of + [Code _ s] | s == srcSuffix -> True + _ -> False + return $ if useAuto + then text srcSuffix + else prefix <> text src <> "[" <> linktext <> "]" +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 "[multiblock footnote omitted]" 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/templates b/templates -Subproject f632b1cdb9cf23e4d5d0d78d9422303c47d1da3 +Subproject 279110eb7cfedd20e626cdeaaf94ccc6fbb1e8a diff --git a/tests/tables.asciidoc b/tests/tables.asciidoc new file mode 100644 index 000000000..38daca192 --- /dev/null +++ b/tests/tables.asciidoc @@ -0,0 +1,71 @@ +Simple table with caption: + +.Demonstration of simple table syntax. +[cols=">,<,^,",options="header",] +|============================ +|Right |Left |Center |Default +|12 |12 |12 |12 +|123 |123 |123 |123 +|1 |1 |1 |1 +|============================ + +Simple table without caption: + +[cols=">,<,^,",options="header",] +|============================ +|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. +[cols=">,<,^,",options="header",] +|============================ +|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. +[width="78%",cols="^21%,<17%,>20%,<42%",options="header",] +|======================================================================= +|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: + +[width="78%",cols="^21%,<17%,>20%,<42%",options="header",] +|======================================================================= +|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: + +[cols=">,<,^,>",] +|============================================================================= +|12 |12 |12 |12 + +|123 |123 |123 |123 + +|1 |1 |1 |1 +|============================================================================= + +Multiline table without column headers: + +[width="78%",cols="^21%,<17%,>20%,42%",] +|============================================================================= +|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.asciidoc b/tests/writer.asciidoc new file mode 100644 index 000000000..af27e02ce --- /dev/null +++ b/tests/writer.asciidoc @@ -0,0 +1,656 @@ +Pandoc Test Suite +================= +:author: John MacFarlane +:author: Anonymous +:date: 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: + +1. item one +2. 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: + +* 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: + +1. First +2. Second +3. Third + +and: + +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: +* Fee +* Fie +* Foe +3. Third + +Same thing but with paragraphs: + +1. First +2. Second: +* 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 +~~~~~~~~~~~~~~~~~~ + +2. begins with 2 +3. and now 3 ++ +with a continuation +iv. sublist with roman numerals, starting with 4 +v. more items +A. a subsublist +B. a subsublist + +Nesting: + +A. Upper Alpha +I. Upper Roman. +6. Decimal start with 6 +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: + +foo +And nested without indentation: + +foo +bar +Interpreted markdown in a table: + +This is _emphasized_ +And this is *strong* +Here’s a simple block: + +foo +This should be a code block, though: + +------- +<div> + foo +</div> +------- + +As should this: + +-------------- +<div>foo</div> +-------------- + +Now, nested: + +foo +This should just be an HTML comment: + +Multiline: + +Code block: + +---------------- +<!-- Comment --> +---------------- + +Just plain comment, with trailing spaces on the line: + +Code: + +------ +<hr /> +------ + +Hr’s: + +''''' + +Inline Markup +------------- + +This is _emphasized_, and so _is this_. + +This is *strong*, and so *is this*. + +An _link:/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>`. + +[line-through]*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 ``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 +----- + +* +* latexmath:[$2+2=4$] +* latexmath:[$x \in y$] +* latexmath:[$\alpha \wedge \omega$] +* latexmath:[$223$] +* latexmath:[$p$]-Tree +* Here’s some display math: +latexmath:[$$\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: +latexmath:[$\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: + +''''' + +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 link:/url/[URL]. + +link:/url/[URL and title]. + +link:/url/[URL and title]. + +link:/url/[URL and title]. + +link:/url/[URL and title] + +link:/url/[URL and title] + +link:/url/with_underscore[with\_underscore] + +mailto:nobody@nowhere.net[Email link] + +link:[Empty]. + +Reference +~~~~~~~~~ + +Foo link:/url/[bar]. + +Foo link:/url/[bar]. + +Foo link:/url/[bar]. + +With link:/url/[embedded [brackets]]. + +link:/url/[b] by itself should be a link. + +Indented link:/url[once]. + +Indented link:/url[twice]. + +Indented link:/url[thrice]. + +This should [not][] be a link. + +----------- +[not]: /url +----------- + +Foo link:/url/[bar]. + +Foo link:/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 link:/script?foo=1&bar=2[inline link]. + +Here’s an link:/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: 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): + +image:lalune.jpg[lalune,title="Voyage dans la Lune"] + +Here is a movie image:movie.jpg[movie] icon. + +''''' + +Footnotes +--------- + +Here is a footnote reference,footnote:[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.[multiblock footnote omitted] This should _not_ be a +footnote reference, because it contains a space.[\^my note] Here is an inline +note.footnote:[This is _easier_ to type. Inline notes may contain +http://google.com[links] and `]` verbatim characters, as well as [bracketed +text].] + +___________________________________________ +Notes can go in quotes.footnote:[In quote.] +___________________________________________ + +1. And in list items.footnote:[In list.] + +This paragraph should not be part of the note, as it is not indented. |