From a73c95f61dbf47bbb54345855b07127d9fd82e62 Mon Sep 17 00:00:00 2001 From: Alex Ivkin Date: Tue, 28 Jun 2016 23:11:42 -0700 Subject: [PATCH] Added Zim Wiki writer, template and tests. --- data/templates | 2 +- pandoc.cabal | 1 + src/Text/Pandoc.hs | 3 + src/Text/Pandoc/Writers/ZimWiki.hs | 361 +++++++++++++++++ tests/Tests/Old.hs | 2 +- tests/tables.zimwiki | 56 +++ tests/writer.zimwiki | 627 +++++++++++++++++++++++++++++ 7 files changed, 1050 insertions(+), 2 deletions(-) create mode 100644 src/Text/Pandoc/Writers/ZimWiki.hs create mode 100644 tests/tables.zimwiki create mode 100644 tests/writer.zimwiki diff --git a/data/templates b/data/templates index 856a50932..ba3a8f742 160000 --- a/data/templates +++ b/data/templates @@ -1 +1 @@ -Subproject commit 856a5093269cc8e5aaa429fc1775157ff5857c30 +Subproject commit ba3a8f742371f9e9f04100d0e61638cf65fd6ceb diff --git a/pandoc.cabal b/pandoc.cabal index 496600ac7..c2267b8d1 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -363,6 +363,7 @@ Library Text.Pandoc.Writers.Textile, Text.Pandoc.Writers.MediaWiki, Text.Pandoc.Writers.DokuWiki, + Text.Pandoc.Writers.ZimWiki, Text.Pandoc.Writers.RTF, Text.Pandoc.Writers.ODT, Text.Pandoc.Writers.Docx, diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs index cd93e0b7b..a302be8f4 100644 --- a/src/Text/Pandoc.hs +++ b/src/Text/Pandoc.hs @@ -104,6 +104,7 @@ module Text.Pandoc , writeMan , writeMediaWiki , writeDokuWiki + , writeZimWiki , writeTextile , writeRTF , writeODT @@ -164,6 +165,7 @@ import Text.Pandoc.Writers.Man import Text.Pandoc.Writers.RTF import Text.Pandoc.Writers.MediaWiki import Text.Pandoc.Writers.DokuWiki +import Text.Pandoc.Writers.ZimWiki import Text.Pandoc.Writers.Textile import Text.Pandoc.Writers.Org import Text.Pandoc.Writers.AsciiDoc @@ -310,6 +312,7 @@ writers = [ ,("rst" , PureStringWriter writeRST) ,("mediawiki" , PureStringWriter writeMediaWiki) ,("dokuwiki" , PureStringWriter writeDokuWiki) + ,("zimwiki" , PureStringWriter writeZimWiki) ,("textile" , PureStringWriter writeTextile) ,("rtf" , IOStringWriter writeRTFWithEmbeddedImages) ,("org" , PureStringWriter writeOrg) diff --git a/src/Text/Pandoc/Writers/ZimWiki.hs b/src/Text/Pandoc/Writers/ZimWiki.hs new file mode 100644 index 000000000..38a03cd83 --- /dev/null +++ b/src/Text/Pandoc/Writers/ZimWiki.hs @@ -0,0 +1,361 @@ +{- +Copyright (C) 2008-2015 John MacFarlane + +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.ZimWiki + Copyright : Copyright (C) 2008-2015 John MacFarlane, 2016 Alex Ivkin + License : GNU GPL, version 2 or above + + Maintainer : Alex Ivkin + Stability : alpha + Portability : portable + +Conversion of 'Pandoc' documents to ZimWiki markup. + +http://zim-wiki.org/manual/Help/Wiki_Syntax.html +-} + +module Text.Pandoc.Writers.ZimWiki ( writeZimWiki ) where +import Text.Pandoc.Definition +import Text.Pandoc.Options ( WriterOptions(writerTableOfContents, writerStandalone, writerTemplate, writerWrapText), WrapOption(..) ) +import Text.Pandoc.Shared ( escapeURI, removeFormatting, trimr, substitute ) +import Text.Pandoc.Writers.Shared ( defField, metaToJSON ) +import Text.Pandoc.ImageSize +import Text.Pandoc.Templates ( renderTemplate' ) +import Data.List ( intercalate, isPrefixOf, transpose, isInfixOf ) +import Data.Text ( breakOnAll, pack ) +import Data.Default (Default(..)) +import Network.URI ( isURI ) +import Control.Monad ( zipWithM ) +import Control.Monad.State ( modify, State, get, evalState ) +--import Control.Monad.Reader ( ReaderT, runReaderT, ask, local ) + +data WriterState = WriterState { + stItemNum :: Int, + stIndent :: String -- Indent after the marker at the beginning of list items + } + +instance Default WriterState where + def = WriterState { stItemNum = 1, stIndent = "" } + +-- | Convert Pandoc to ZimWiki. +writeZimWiki :: WriterOptions -> Pandoc -> String +writeZimWiki opts document = evalState (pandocToZimWiki opts document) (WriterState 1 "") + +-- | Return ZimWiki representation of document. +pandocToZimWiki :: WriterOptions -> Pandoc -> State WriterState String +pandocToZimWiki opts (Pandoc meta blocks) = do + metadata <- metaToJSON opts + (fmap trimr . blockListToZimWiki opts) + (inlineListToZimWiki opts) + meta + body <- blockListToZimWiki opts blocks + --let header = "Content-Type: text/x-zim-wiki\nWiki-Format: zim 0.4\n" + let main = body + 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 ZimWiki. +escapeString :: String -> String +escapeString = substitute "__" "''__''" . + substitute "**" "''**''" . + substitute "~~" "''~~''" . + substitute "//" "''//''" + +-- | Convert Pandoc block element to ZimWiki. +blockToZimWiki :: WriterOptions -> Block -> State WriterState String + +blockToZimWiki _ Null = return "" + +blockToZimWiki opts (Div _attrs bs) = do + contents <- blockListToZimWiki opts bs + return $ contents ++ "\n" + +blockToZimWiki opts (Plain inlines) = inlineListToZimWiki opts inlines + +-- title beginning with fig: indicates that the image is a figure +-- ZimWiki doesn't support captions - so combine together alt and caption into alt +blockToZimWiki opts (Para [Image attr txt (src,'f':'i':'g':':':tit)]) = do + capt <- if null txt + then return "" + else (" " ++) `fmap` inlineListToZimWiki opts txt + let opt = if null txt + then "" + else "|" ++ if null tit then capt else tit ++ capt + -- Relative links fail isURI and receive a colon + prefix = if isURI src then "" else ":" + return $ "{{" ++ prefix ++ src ++ imageDims opts attr ++ opt ++ "}}\n" + +blockToZimWiki opts (Para inlines) = do + indent <- stIndent <$> get + -- useTags <- stUseTags <$> get + contents <- inlineListToZimWiki opts inlines + return $ contents ++ if null indent then "\n" else "" + +blockToZimWiki opts (RawBlock f str) + | f == Format "zimwiki" = return str + | f == Format "html" = do cont <- indentFromHTML opts str; return cont + | otherwise = return "" -- $ "** unknown raw block "++ show f ++ "=" ++ str ++ " **" + +blockToZimWiki _ HorizontalRule = return "\n----\n" + +blockToZimWiki opts (Header level _ inlines) = do + contents <- inlineListToZimWiki opts $ removeFormatting inlines -- emphasis, links etc. not allowed in headers + let eqs = replicate ( 7 - level ) '=' + return $ eqs ++ " " ++ contents ++ " " ++ eqs ++ "\n" + +blockToZimWiki _ (CodeBlock (_,classes,_) str) = do + return $ case classes of + [] -> "'''\n" ++ cleanupCode str ++ "\n'''\n" -- no lang block is a quote block + (x:_) -> "{{{code: lang=\"" ++ x ++ "\" linenumbers=\"True\"\n" ++ str ++ "\n}}}\n" -- for zim's code plugin, go verbatim on the lang spec + +blockToZimWiki opts (BlockQuote blocks) = do + contents <- blockListToZimWiki opts blocks + return $ unlines $ map ("> " ++) $ lines contents + +blockToZimWiki opts (Table capt aligns _ headers rows) = do + captionDoc <- if null capt + then return "" + else do + c <- inlineListToZimWiki opts capt + return $ "" ++ c ++ "\n" + headers' <- if all null headers + then zipWithM (tableItemToZimWiki opts) aligns (rows !! 0) + else zipWithM (tableItemToZimWiki opts) aligns headers + rows' <- mapM (zipWithM (tableItemToZimWiki opts) aligns) rows + let widths = map (maximum . map length) $ transpose (headers':rows') + let padTo (width, al) s = + case (width - length s) of + x | x > 0 -> + if al == AlignLeft || al == AlignDefault + then s ++ replicate x ' ' + else if al == AlignRight + then replicate x ' ' ++ s + else replicate (x `div` 2) ' ' ++ + s ++ replicate (x - x `div` 2) ' ' + | otherwise -> s + let borderCell (width, al) _ = + if al == AlignLeft + then ":"++ replicate (width-1) '-' + else if al == AlignDefault + then replicate width '-' + else if al == AlignRight + then replicate (width-1) '-' ++ ":" + else ":" ++ replicate (width-2) '-' ++ ":" + let underheader = "|" ++ intercalate "|" (zipWith borderCell (zip widths aligns) headers') ++ "|" + let renderRow sep cells = sep ++ intercalate sep (zipWith padTo (zip widths aligns) cells) ++ sep + return $ captionDoc ++ + (if null headers' then "" else renderRow "|" headers' ++ "\n") ++ underheader ++ "\n" ++ + unlines (map (renderRow "|") rows') + +blockToZimWiki opts (BulletList items) = do + indent <- stIndent <$> get + modify $ \s -> s { stIndent = stIndent s ++ "\t" } + contents <- (mapM (listItemToZimWiki opts) items) + modify $ \s -> s{ stIndent = indent } -- drop 1 (stIndent s) } + return $ vcat contents ++ if null indent then "\n" else "" + +blockToZimWiki opts (OrderedList _ items) = do + indent <- stIndent <$> get + modify $ \s -> s { stIndent = stIndent s ++ "\t", stItemNum = 1 } + contents <- (mapM (orderedListItemToZimWiki opts) items) + modify $ \s -> s{ stIndent = indent } -- drop 1 (stIndent s) } + return $ vcat contents ++ if null indent then "\n" else "" + +blockToZimWiki opts (DefinitionList items) = do + contents <- (mapM (definitionListItemToZimWiki opts) items) + return $ vcat contents + +definitionListItemToZimWiki :: WriterOptions -> ([Inline],[[Block]]) -> State WriterState String +definitionListItemToZimWiki opts (label, items) = do + labelText <- inlineListToZimWiki opts label + contents <- mapM (blockListToZimWiki opts) items + indent <- stIndent <$> get + return $ indent ++ "* **" ++ labelText ++ "** " ++ concat contents + +-- Auxiliary functions for lists: +indentFromHTML :: WriterOptions -> String -> State WriterState String +indentFromHTML _ str = do + indent <- stIndent <$> get + itemnum <- stItemNum <$> get + if isInfixOf "
  • " str then return $ indent ++ show itemnum ++ "." + else if isInfixOf "
  • " str then return "\n" + else if isInfixOf "
  • " str then do + let olcount=countSubStrs "
      " str + modify $ \s -> s { stIndent = stIndent s ++ replicate olcount '\t', stItemNum = 1 } + return "" -- $ "OL-ON[" ++ newfix ++"]" + else if isInfixOf "
    " str then do + let olcount=countSubStrs "/
      " str + modify $ \s -> s{ stIndent = drop olcount (stIndent s) } + return "" -- $ "OL-OFF[" ++ newfix ++"]" + else + return $ "" -- ** unknown inner HTML "++ str ++"**" + +countSubStrs :: String -> String -> Int +countSubStrs sub str = length $ breakOnAll (pack sub) (pack str) + +cleanupCode :: String -> String +cleanupCode = substitute "" "" . substitute "" "" + +vcat :: [String] -> String +vcat = intercalate "\n" + +-- | Convert bullet list item (list of blocks) to ZimWiki. +listItemToZimWiki :: WriterOptions -> [Block] -> State WriterState String +listItemToZimWiki opts items = do + contents <- blockListToZimWiki opts items + indent <- stIndent <$> get + return $ indent ++ "* " ++ contents + +-- | Convert ordered list item (list of blocks) to ZimWiki. +orderedListItemToZimWiki :: WriterOptions -> [Block] -> State WriterState String +orderedListItemToZimWiki opts items = do + contents <- blockListToZimWiki opts items + indent <- stIndent <$> get + itemnum <- stItemNum <$> get + --modify $ \s -> s { stItemNum = itemnum + 1 } -- this is not strictly necessary for zim as zim does its own renumbering + return $ indent ++ show itemnum ++ ". " ++ contents + +-- Auxiliary functions for tables: +tableItemToZimWiki :: WriterOptions -> Alignment -> [Block] -> State WriterState String +tableItemToZimWiki opts align' item = do + let mkcell x = (if align' == AlignRight || align' == AlignCenter + then " " + else "") ++ x ++ + (if align' == AlignLeft || align' == AlignCenter + then " " + else "") + contents <- blockListToZimWiki opts item -- local (\s -> s { stBackSlashLB = True }) $ + return $ mkcell contents + +-- | Convert list of Pandoc block elements to ZimWiki. +blockListToZimWiki :: WriterOptions -> [Block] -> State WriterState String +blockListToZimWiki opts blocks = vcat <$> mapM (blockToZimWiki opts) blocks + +-- | Convert list of Pandoc inline elements to ZimWiki. +inlineListToZimWiki :: WriterOptions -> [Inline] -> State WriterState String +inlineListToZimWiki opts lst = concat <$> (mapM (inlineToZimWiki opts) lst) + +-- | Convert Pandoc inline element to ZimWiki. +inlineToZimWiki :: WriterOptions -> Inline -> State WriterState String + +inlineToZimWiki opts (Emph lst) = do + contents <- inlineListToZimWiki opts lst + return $ "//" ++ contents ++ "//" + +inlineToZimWiki opts (Strong lst) = do + contents <- inlineListToZimWiki opts lst + return $ "**" ++ contents ++ "**" + +inlineToZimWiki opts (Strikeout lst) = do + contents <- inlineListToZimWiki opts lst + return $ "~~" ++ contents ++ "~~" + +inlineToZimWiki opts (Superscript lst) = do + contents <- inlineListToZimWiki opts lst + return $ "^{" ++ contents ++ "}" + +inlineToZimWiki opts (Subscript lst) = do + contents <- inlineListToZimWiki opts lst + return $ "_{" ++ contents ++ "}" + +inlineToZimWiki opts (Quoted SingleQuote lst) = do + contents <- inlineListToZimWiki opts lst + return $ "\8216" ++ contents ++ "\8217" + +inlineToZimWiki opts (Quoted DoubleQuote lst) = do + contents <- inlineListToZimWiki opts lst + return $ "\8220" ++ contents ++ "\8221" + +inlineToZimWiki opts (Span _attrs ils) = inlineListToZimWiki opts ils + +inlineToZimWiki opts (SmallCaps lst) = inlineListToZimWiki opts lst + +inlineToZimWiki opts (Cite _ lst) = inlineListToZimWiki opts lst + +inlineToZimWiki _ (Code _ str) = return $ "''" ++ str ++ "''" + +inlineToZimWiki _ (Str str) = return $ escapeString str + +inlineToZimWiki _ (Math mathType str) = return $ delim ++ str ++ delim -- note: str should NOT be escaped + where delim = case mathType of + DisplayMath -> "$$" + InlineMath -> "$" + +-- | f == Format "html" = return $ "" ++ str ++ "" +inlineToZimWiki opts (RawInline f str) + | f == Format "zimwiki" = return str + | f == Format "html" = do cont <- indentFromHTML opts str; return cont + | otherwise = return "" + +inlineToZimWiki _ (LineBreak) = return "\n" -- was \\\\ + +inlineToZimWiki opts SoftBreak = + case writerWrapText opts of + WrapNone -> return " " + WrapAuto -> return " " + WrapPreserve -> return "\n" + +inlineToZimWiki _ Space = return " " + +inlineToZimWiki opts (Link _ txt (src, _)) = do + label <- inlineListToZimWiki opts txt + case txt of + [Str s] | "mailto:" `isPrefixOf` src -> return $ "<" ++ 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 +inlineToZimWiki opts (Image attr alt (source, tit)) = do + alt' <- inlineListToZimWiki opts alt + let txt = case (tit, alt) of + ("", []) -> "" + ("", _ ) -> "|" ++ alt' + (_ , _ ) -> "|" ++ tit + -- Relative links fail isURI and receive a colon + prefix = if isURI source then "" else ":" + return $ "{{" ++ prefix ++ source ++ imageDims opts attr ++ txt ++ "}}" + +inlineToZimWiki opts (Note contents) = do + contents' <- blockListToZimWiki opts contents + return $ "((" ++ contents' ++ "))" + -- note - may not work for notes with multiple blocks + +imageDims :: WriterOptions -> Attr -> String +imageDims opts attr = go (toPx $ dimension Width attr) (toPx $ dimension Height attr) + where + toPx = fmap (showInPixel opts) . checkPct + checkPct (Just (Percent _)) = Nothing + checkPct maybeDim = maybeDim + go (Just w) Nothing = "?" ++ w + go (Just w) (Just h) = "?" ++ w ++ "x" ++ h + go Nothing (Just h) = "?0x" ++ h + go Nothing Nothing = "" diff --git a/tests/Tests/Old.hs b/tests/Tests/Old.hs index 4e0eb46a4..b2600a9c5 100644 --- a/tests/Tests/Old.hs +++ b/tests/Tests/Old.hs @@ -166,7 +166,7 @@ tests = [ testGroup "markdown" "twiki-reader.twiki" "twiki-reader.native" ] , testGroup "other writers" $ map (\f -> testGroup f $ writerTests f) [ "opendocument" , "context" , "texinfo", "icml", "tei" - , "man" , "plain" , "rtf", "org", "asciidoc" + , "man" , "plain" , "rtf", "org", "asciidoc", "zimwiki" ] , testGroup "writers-lang-and-dir" [ test "latex" ["-f", "native", "-t", "latex", "-s"] diff --git a/tests/tables.zimwiki b/tests/tables.zimwiki new file mode 100644 index 000000000..1f02c9908 --- /dev/null +++ b/tests/tables.zimwiki @@ -0,0 +1,56 @@ +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| +|----:|:----|:-----:|----:| +| 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. | +|:--------:|:----|-----:|-----------------------------------------------------| +| 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.zimwiki b/tests/writer.zimwiki new file mode 100644 index 000000000..848ca955e --- /dev/null +++ b/tests/writer.zimwiki @@ -0,0 +1,627 @@ +Content-Type: text/x-zim-wiki +Wiki-Format: zim 0.4 + +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 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 +> 1. 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 + 1. Second + 1. Third + +and: + + 1. One + 1. Two + 1. Three + +Loose using tabs: + + 1. First + 1. Second + 1. Third + +and using spaces: + + 1. One + 1. Two + 1. Three + +Multiple paragraphs: + + 1. Item 1, graf one. +Item 1. graf two. The quick brown fox jumped over the lazy dog’s back. + 1. Item 2. + 1. Item 3. + +===== Nested ===== + + * Tab + * Tab + * Tab + +Here’s another: + + 1. First + 1. Second: + * Fee + * Fie + * Foe + 1. Third + +Same thing but with paragraphs: + + 1. First + 1. Second: + * Fee + * Fie + * Foe + 1. 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 ===== + + 1. begins with 2 + 1. and now 3 +with a continuation + 1. sublist with roman numerals, starting with 4 + 1. more items + 1. a subsublist + 1. a subsublist + +Nesting: + + 1. Upper Alpha + 1. Upper Roman. + 1. Decimal start with 6 + 1. Lower alpha with paren + +Autonumbering: + + 1. Autonumber. + 1. 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 fruitcomputer +* **orange** orange fruitbank +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 + 1. 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: + +''' +
      + foo +
      +''' + +As should this: + +''' +
      foo
      +''' + +Now, nested: + +foo + + + +This should just be an HTML comment: + + +Multiline: + + + +Code block: + +''' + +''' + +Just plain comment, with trailing spaces on the line: + + +Code: + +''' +
      +''' + +Hr’s: + + + + + + + + + + + +---- + +====== 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: ''>'', ''$'', ''\'', ''\$'', ''''. + +~~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 ====== + + * + * $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: + + + +---- + +====== 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. + +''' +[not]: /url +''' + +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: + +> Blockquoted: http://example.com/ + +Auto-links should not occur here: '''' + +''' +or here: +''' + + +---- + +====== 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). + +''' + { } +''' + +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]. +)) + +> Notes can go in quotes.((In quote. +> )) + + 1. And in list items.((In list.)) + +This paragraph should not be part of the note, as it is not indented.