From 1c368574651c7584439290181564e5d449e894b3 Mon Sep 17 00:00:00 2001 From: Albert Krewinkel Date: Wed, 5 Jun 2019 23:52:23 +0200 Subject: Add jira writer (#5548) This adds support for Atlassian's jira markup. Closes #2497 --- data/templates/default.jira | 9 + pandoc.cabal | 4 + src/Text/Pandoc/Writers.hs | 3 + src/Text/Pandoc/Writers/Jira.hs | 322 ++++++++++++++++++++ test/Tests/Old.hs | 3 + test/tables.jira | 44 +++ test/writer.jira | 630 ++++++++++++++++++++++++++++++++++++++++ 7 files changed, 1015 insertions(+) create mode 100644 data/templates/default.jira create mode 100644 src/Text/Pandoc/Writers/Jira.hs create mode 100644 test/tables.jira create mode 100644 test/writer.jira diff --git a/data/templates/default.jira b/data/templates/default.jira new file mode 100644 index 000000000..69bd05b56 --- /dev/null +++ b/data/templates/default.jira @@ -0,0 +1,9 @@ +$for(include-before)$ +$include-before$ + +$endfor$ +$body$ +$for(include-after)$ + +$include-after$ +$endfor$ diff --git a/pandoc.cabal b/pandoc.cabal index 0fabe65e3..807905381 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -53,6 +53,7 @@ data-files: data/templates/default.latex data/templates/default.context data/templates/default.texinfo + data/templates/default.jira data/templates/default.man data/templates/default.ms data/templates/default.markdown @@ -242,6 +243,7 @@ extra-source-files: test/tables.docbook4 test/tables.docbook5 test/tables.jats + test/tables.jira test/tables.dokuwiki test/tables.zimwiki test/tables.icml @@ -273,6 +275,7 @@ extra-source-files: test/writer.docbook4 test/writer.docbook5 test/writer.jats + test/writer.jira test/writer.html4 test/writer.html5 test/writer.man @@ -500,6 +503,7 @@ library Text.Pandoc.Writers.HTML, Text.Pandoc.Writers.Ipynb, Text.Pandoc.Writers.ICML, + Text.Pandoc.Writers.Jira, Text.Pandoc.Writers.LaTeX, Text.Pandoc.Writers.ConTeXt, Text.Pandoc.Writers.OpenDocument, diff --git a/src/Text/Pandoc/Writers.hs b/src/Text/Pandoc/Writers.hs index d93128731..ecf45839e 100644 --- a/src/Text/Pandoc/Writers.hs +++ b/src/Text/Pandoc/Writers.hs @@ -41,6 +41,7 @@ module Text.Pandoc.Writers , writeICML , writeJATS , writeJSON + , writeJira , writeLaTeX , writeMan , writeMarkdown @@ -91,6 +92,7 @@ import Text.Pandoc.Writers.Haddock import Text.Pandoc.Writers.HTML import Text.Pandoc.Writers.ICML import Text.Pandoc.Writers.JATS +import Text.Pandoc.Writers.Jira import Text.Pandoc.Writers.LaTeX import Text.Pandoc.Writers.Man import Text.Pandoc.Writers.Markdown @@ -141,6 +143,7 @@ writers = [ ,("docbook4" , TextWriter writeDocbook4) ,("docbook5" , TextWriter writeDocbook5) ,("jats" , TextWriter writeJATS) + ,("jira" , TextWriter writeJira) ,("opml" , TextWriter writeOPML) ,("opendocument" , TextWriter writeOpenDocument) ,("latex" , TextWriter writeLaTeX) diff --git a/src/Text/Pandoc/Writers/Jira.hs b/src/Text/Pandoc/Writers/Jira.hs new file mode 100644 index 000000000..08e5c8e40 --- /dev/null +++ b/src/Text/Pandoc/Writers/Jira.hs @@ -0,0 +1,322 @@ +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE NoImplicitPrelude #-} +{- | + Module : Text.Pandoc.Writers.Jira + Copyright : © 2010-2019 Albert Krewinkel, John MacFarlane + License : GNU GPL, version 2 or above + + Maintainer : Albert Krewinkel + Stability : alpha + Portability : portable + +Conversion of 'Pandoc' documents to Jira markup. + +JIRA: + +-} +module Text.Pandoc.Writers.Jira ( writeJira ) where +import Prelude +import Control.Monad.State.Strict +import Data.Char (toLower) +import Data.Foldable (find) +import Data.Text (Text, pack) +import Text.Pandoc.Class (PandocMonad, report) +import Text.Pandoc.Definition +import Text.Pandoc.Logging (LogMessage (BlockNotRendered, InlineNotRendered)) +import Text.Pandoc.Options (WriterOptions (writerTemplate)) +import Text.Pandoc.Shared (blocksToInlines, linesToPara) +import Text.Pandoc.Templates (renderTemplate') +import Text.Pandoc.Writers.Math (texMathToInlines) +import Text.Pandoc.Writers.Shared (metaToJSON, defField) +import qualified Data.Text as T + +data WriterState = WriterState + { stNotes :: [Text] -- Footnotes + , stListLevel :: Text -- String at beginning of list items, e.g. "**" + } + +-- | Initial writer state +startState :: WriterState +startState = WriterState + { stNotes = [] + , stListLevel = "" + } + +type JiraWriter = StateT WriterState + +-- | Convert Pandoc to Jira. +writeJira :: PandocMonad m => WriterOptions -> Pandoc -> m Text +writeJira opts document = + evalStateT (pandocToJira opts document) startState + +-- | Return Jira representation of document. +pandocToJira :: PandocMonad m + => WriterOptions -> Pandoc -> JiraWriter m Text +pandocToJira opts (Pandoc meta blocks) = do + metadata <- metaToJSON opts (blockListToJira opts) + (inlineListToJira opts) meta + body <- blockListToJira opts blocks + notes <- gets $ T.intercalate "\n" . reverse . stNotes + let main = body <> if T.null notes then "" else "\n\n" <> notes + let context = defField "body" main metadata + case writerTemplate opts of + Nothing -> return main + Just tpl -> renderTemplate' tpl context + +-- | Escape one character as needed for Jira. +escapeCharForJira :: Char -> Text +escapeCharForJira c = case c of + '&' -> "&" + '<' -> "<" + '>' -> ">" + '"' -> """ + '*' -> "*" + '_' -> "_" + '@' -> "@" + '+' -> "+" + '-' -> "‐" + '|' -> "|" + '{' -> "\\{" + '\x2014' -> " -- " + '\x2013' -> " - " + '\x2019' -> "'" + '\x2026' -> "..." + _ -> T.singleton c + +-- | Escape string as needed for Jira. +escapeStringForJira :: Text -> Text +escapeStringForJira = T.concatMap escapeCharForJira + +-- | Create an anchor macro from the given element attributes. +anchor :: Attr -> Text +anchor (ident,_,_) = + if ident == "" + then "" + else "{anchor:" <> pack ident <> "}" + +-- | Append a newline character unless we are in a list. +appendNewlineUnlessInList :: PandocMonad m + => Text + -> JiraWriter m Text +appendNewlineUnlessInList t = do + listLevel <- gets stListLevel + return (if T.null listLevel then t <> "\n" else t) + +-- | Convert Pandoc block element to Jira. +blockToJira :: PandocMonad m + => WriterOptions -- ^ Options + -> Block -- ^ Block element + -> JiraWriter m Text + +blockToJira _ Null = return "" + +blockToJira opts (Div attr bs) = + (anchor attr <>) <$> blockListToJira opts bs + +blockToJira opts (Plain inlines) = + inlineListToJira opts inlines + +blockToJira opts (Para inlines) = do + contents <- inlineListToJira opts inlines + appendNewlineUnlessInList contents + +blockToJira opts (LineBlock lns) = + blockToJira opts $ linesToPara lns + +blockToJira _ b@(RawBlock f str) = + if f == Format "jira" + then return (pack str) + else "" <$ report (BlockNotRendered b) + +blockToJira _ HorizontalRule = return "----\n" + +blockToJira opts (Header level attr inlines) = do + contents <- inlineListToJira opts inlines + let prefix = "h" <> pack (show level) <> ". " + return $ prefix <> anchor attr <> contents <> "\n" + +blockToJira _ (CodeBlock attr@(_,classes,_) str) = do + let lang = find (\c -> map toLower c `elem` knownLanguages) classes + let start = case lang of + Nothing -> "{code}" + Just l -> "{code:" <> pack l <> "}" + let anchorMacro = anchor attr + appendNewlineUnlessInList . T.intercalate "\n" $ + (if anchorMacro == "" then id else (anchorMacro :)) + [start, escapeStringForJira (pack str), "{code}"] + +blockToJira opts (BlockQuote [p@(Para _)]) = do + contents <- blockToJira opts p + appendNewlineUnlessInList ("bq. " <> contents) + +blockToJira opts (BlockQuote blocks) = do + contents <- blockListToJira opts blocks + appendNewlineUnlessInList . T.intercalate "\n" $ + [ "{quote}", contents, "{quote}"] + +blockToJira opts (Table _caption _aligns _widths headers rows) = do + headerCells <- mapM blocksToCell headers + bodyRows <- mapM (mapM blocksToCell) rows + let tblHead = headerCellsToRow headerCells + let tblBody = map cellsToRow bodyRows + return $ if all null headers + then T.unlines tblBody + else T.unlines (tblHead : tblBody) + where + blocksToCell :: PandocMonad m => [Block] -> JiraWriter m Text + blocksToCell = inlineListToJira opts . blocksToInlines + + cellsToRow :: [Text] -> Text + cellsToRow cells = "|" <> T.intercalate "|" cells <> "|" + + headerCellsToRow :: [Text] -> Text + headerCellsToRow cells = "||" <> T.intercalate "||" cells <> "||" + +blockToJira opts (BulletList items) = + listWithMarker opts items '*' + +blockToJira opts (OrderedList _listAttr items) = + listWithMarker opts items '#' + +blockToJira opts (DefinitionList items) = + blockToJira opts (BulletList (map defToBulletItem items)) + where + defToBulletItem :: ([Inline], [[Block]]) -> [Block] + defToBulletItem (inlns, defs) = + let term = Plain [Strong inlns] + blks = mconcat defs + in term : blks + +-- Auxiliary functions for lists: + +-- | Create a list using the given character as bullet item marker. +listWithMarker :: PandocMonad m + => WriterOptions + -> [[Block]] + -> Char + -> JiraWriter m Text +listWithMarker opts items marker = do + modify $ \s -> s { stListLevel = stListLevel s `T.snoc` marker } + contents <- mapM (listItemToJira opts) items + modify $ \s -> s { stListLevel = T.init (stListLevel s) } + appendNewlineUnlessInList $ T.intercalate "\n" contents + +-- | Convert bullet or ordered list item (list of blocks) to Jira. +listItemToJira :: PandocMonad m + => WriterOptions + -> [Block] + -> JiraWriter m Text +listItemToJira opts items = do + contents <- blockListToJira opts items + marker <- gets stListLevel + return $ marker <> " " <> contents + +-- | Convert list of Pandoc block elements to Jira. +blockListToJira :: PandocMonad m + => WriterOptions -- ^ Options + -> [Block] -- ^ List of block elements + -> JiraWriter m Text +blockListToJira opts blocks = + T.intercalate "\n" <$> mapM (blockToJira opts) blocks + +-- | Convert list of Pandoc inline elements to Jira. +inlineListToJira :: PandocMonad m + => WriterOptions + -> [Inline] + -> JiraWriter m Text +inlineListToJira opts lst = + T.concat <$> mapM (inlineToJira opts) lst + +-- | Convert Pandoc inline element to Jira. +inlineToJira :: PandocMonad m + => WriterOptions + -> Inline + -> JiraWriter m Text + +inlineToJira opts (Span attr lst) = + (anchor attr <>) <$> inlineListToJira opts lst + +inlineToJira opts (Emph lst) = do + contents <- inlineListToJira opts lst + return $ "_" <> contents <> "_" + +inlineToJira opts (Strong lst) = do + contents <- inlineListToJira opts lst + return $ "*" <> contents <> "*" + +inlineToJira opts (Strikeout lst) = do + contents <- inlineListToJira opts lst + return $ "-" <> contents <> "-" + +inlineToJira opts (Superscript lst) = do + contents <- inlineListToJira opts lst + return $ "{^" <> contents <> "^}" + +inlineToJira opts (Subscript lst) = do + contents <- inlineListToJira opts lst + return $ "{~" <> contents <> "~}" + +inlineToJira opts (SmallCaps lst) = inlineListToJira opts lst + +inlineToJira opts (Quoted SingleQuote lst) = do + contents <- inlineListToJira opts lst + return $ "'" <> contents <> "'" + +inlineToJira opts (Quoted DoubleQuote lst) = do + contents <- inlineListToJira opts lst + return $ "\"" <> contents <> "\"" + +inlineToJira opts (Cite _ lst) = inlineListToJira opts lst + +inlineToJira _ (Code attr str) = + return (anchor attr <> "{{" <> escapeStringForJira (pack str) <> "}}") + +inlineToJira _ (Str str) = return $ escapeStringForJira (pack str) + +inlineToJira opts (Math InlineMath str) = + lift (texMathToInlines InlineMath str) >>= inlineListToJira opts + +inlineToJira opts (Math DisplayMath str) = do + mathInlines <- lift (texMathToInlines DisplayMath str) + contents <- inlineListToJira opts mathInlines + return $ "\\\\" <> contents <> "\\\\" + +inlineToJira _opts il@(RawInline f str) = + if f == Format "jira" + then return (pack str) + else "" <$ report (InlineNotRendered il) + +inlineToJira _ LineBreak = return "\n" + +inlineToJira _ SoftBreak = return " " + +inlineToJira _ Space = return " " + +inlineToJira opts (Link _attr txt (src, _title)) = do + linkText <- inlineListToJira opts txt + return $ T.concat + [ "[" + , if null txt then "" else linkText <> "|" + , pack src + , "]" + ] + +inlineToJira _opts (Image attr _alt (src, _title)) = + return . T.concat $ [anchor attr, "!", pack src, "!"] + +inlineToJira opts (Note contents) = do + curNotes <- gets stNotes + let newnum = length curNotes + 1 + contents' <- blockListToJira opts contents + let thisnote = "[" <> pack (show newnum) <> "] " <> contents' <> "\n" + modify $ \s -> s { stNotes = thisnote : curNotes } + return $ "[" <> pack (show newnum) <> "]" + +-- | Language codes recognized by jira +knownLanguages :: [String] +knownLanguages = + [ "actionscript", "ada", "applescript", "bash", "c", "c#", "c++" + , "css", "erlang", "go", "groovy", "haskell", "html", "javascript" + , "json", "lua", "nyan", "objc", "perl", "php", "python", "r", "ruby" + , "scala", "sql", "swift", "visualbasic", "xml", "yaml" + ] diff --git a/test/Tests/Old.hs b/test/Tests/Old.hs index ae7c471af..d0a1e0e4f 100644 --- a/test/Tests/Old.hs +++ b/test/Tests/Old.hs @@ -96,6 +96,9 @@ tests pandocPath = , test' "reader" ["-r", "jats", "-w", "native", "-s"] "jats-reader.xml" "jats-reader.native" ] + , testGroup "jira" + [ testGroup "writer" $ writerTests' "jira" + ] , testGroup "native" [ testGroup "writer" $ writerTests' "native" , test' "reader" ["-r", "native", "-w", "native", "-s"] diff --git a/test/tables.jira b/test/tables.jira new file mode 100644 index 000000000..d04b559cc --- /dev/null +++ b/test/tables.jira @@ -0,0 +1,44 @@ +Simple table with caption: + +||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: + +||Right||Left||Center||Default|| +|12|12|12|12| +|123|123|123|123| +|1|1|1|1| + +Multiline table with 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.| + +Multiline table without caption: + +||Centered Header||Left Aligned||Right Aligned||Default aligned|| +|First|row|12.0|Example of a row that spans multiple lines.| +|Second|row|5.0|Here's another one. Note the blank line between rows.| + +Table without column headers: + +|12|12|12|12| +|123|123|123|123| +|1|1|1|1| + +Multiline table without column headers: + +|First|row|12.0|Example of a row that spans multiple lines.| +|Second|row|5.0|Here's another one. Note the blank line between rows.| + diff --git a/test/writer.jira b/test/writer.jira new file mode 100644 index 000000000..7d9766c1e --- /dev/null +++ b/test/writer.jira @@ -0,0 +1,630 @@ +This is a set of tests for pandoc. Most of them are adapted from John Gruber's markdown test suite. + +---- + +h1. {anchor:headers}Headers + +h2. {anchor:level-2-with-an-embedded-link}Level 2 with an [embedded link|/url] + +h3. {anchor:level-3-with-emphasis}Level 3 with _emphasis_ + +h4. {anchor:level-4}Level 4 + +h5. {anchor:level-5}Level 5 + +h1. {anchor:level-1}Level 1 + +h2. {anchor:level-2-with-emphasis}Level 2 with _emphasis_ + +h3. {anchor:level-3}Level 3 + +with no blank line + +h2. {anchor:level-2}Level 2 + +with no blank line + +---- + +h1. {anchor:paragraphs}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. + +---- + +h1. {anchor:block-quotes}Block Quotes + +E‐mail style: + +bq. This is a block quote. It is pretty short. + + +{quote} +Code in a block quote: + +{code} +sub status \{ + print "working"; +} +{code} + +A list: + +# item one +# item two + +Nested block quotes: + +bq. nested + + +bq. nested + + +{quote} + +This should not be a block quote: 2 > 1. + +And a following paragraph. + +---- + +h1. {anchor:code-blocks}Code Blocks + +Code: + +{code} +‐‐‐‐ (should be four hyphens) + +sub status \{ + print "working"; +} + +this code block is indented by one tab +{code} + +And: + +{code} + this code block is indented by two tabs + +These should not be escaped: \$ \\ \> \[ \\{ +{code} + +---- + +h1. {anchor:lists}Lists + +h2. {anchor:unordered}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 + +h2. {anchor:ordered}Ordered + +Tight: + +# First +# Second +# Third + +and: + +# One +# Two +# Three + +Loose using tabs: + +# First +# Second +# Third + +and using spaces: + +# One +# Two +# Three + +Multiple paragraphs: + +# Item 1, graf one. +Item 1. graf two. The quick brown fox jumped over the lazy dog's back. +# Item 2. +# Item 3. + +h2. {anchor:nested}Nested + +* Tab +** Tab +*** Tab + +Here's another: + +# First +# Second: +#* Fee +#* Fie +#* Foe +# Third + +Same thing but with paragraphs: + +# First +# Second: +#* Fee +#* Fie +#* Foe +# Third + +h2. {anchor:tabs-and-spaces}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 + +h2. {anchor:fancy-list-markers}Fancy list markers + +# begins with 2 +# and now 3 +with a continuation +## sublist with roman numerals, starting with 4 +## more items +### a subsublist +### a subsublist + +Nesting: + +# Upper Alpha +## Upper Roman. +### Decimal start with 6 +#### Lower alpha with paren + +Autonumbering: + +# Autonumber. +# More. +## Nested. + +Should not be a list item: + +M.A. 2007 + +B. Williams + +---- + +h1. {anchor:definition-lists}Definition Lists + +Tight using spaces: + +* *apple* +red fruit +* *orange* +orange fruit +* *banana* +yellow fruit + +Tight using tabs: + +* *apple* +red fruit +* *orange* +orange fruit +* *banana* +yellow fruit + +Loose: + +* *apple* +red fruit +* *orange* +orange fruit +* *banana* +yellow fruit + +Multiple blocks with italics: + +* *_apple_* +red fruit +contains seeds, crisp, pleasant to taste +* *_orange_* +orange fruit +{code} +\{ orange code block } +{code} +bq. 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 +*# sublist +*# sublist + +h1. {anchor:html-blocks}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: + +{code} +<div> + foo +</div> +{code} + +As should this: + +{code} +<div>foo</div> +{code} + +Now, nested: + +foo +This should just be an HTML comment: + + +Multiline: + + + +Code block: + +{code} +<!‐‐ Comment ‐‐> +{code} + +Just plain comment, with trailing spaces on the line: + + +Code: + +{code} +<hr /> +{code} + +Hr's: + + + + + + + + + + +---- + +h1. {anchor:inline-markup}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. + +---- + +h1. {anchor:smart-quotes-ellipses-dashes}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.... + +---- + +h1. {anchor:latex}LaTeX + +* +* 2 + 2 = 4 +* _x_ ∈ _y_ +* _α_ ∧ _ω_ +* 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: _α_ + _ω_ × _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: + + +---- + +h1. {anchor:special-characters}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: ‐ + +---- + +h1. {anchor:links}Links + +h2. {anchor:explicit}Explicit + +Just a [URL|/url/]. + +[URL and title|/url/]. + +[URL and title|/url/]. + +[URL and title|/url/]. + +[URL and title|/url/] + +[URL and title|/url/] + +[with_underscore|/url/with_underscore] + +[Email link|mailto:nobody@nowhere.net] + +[Empty|]. + +h2. {anchor:reference}Reference + +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. + +{code} +[not]: /url +{code} + +Foo [bar|/url/]. + +Foo [biz|/url/]. + +h2. {anchor:with-ampersands}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/]. + +Here's an [inline link|/script?foo=1&bar=2]. + +Here's an [inline link in pointy braces|/script?foo=1&bar=2]. + +h2. {anchor:autolinks}Autolinks + +With an ampersand: [http://example.com/?foo=1&bar=2|http://example.com/?foo=1&bar=2] + +* In a list? +* [http://example.com/|http://example.com/] +* It should. + +An e‐mail address: [nobody@nowhere.net|mailto:nobody@nowhere.net] + +bq. Blockquoted: [http://example.com/|http://example.com/] + + +Auto‐links should not occur here: {{<http://example.com/>}} + +{code} +or here: <http://example.com/> +{code} + +---- + +h1. {anchor:images}Images + +From "Voyage dans la Lune" by Georges Melies (1902): + +!lalune.jpg! + +Here is a movie !movie.jpg! icon. + +---- + +h1. {anchor:footnotes}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] + +bq. Notes can go in quotes.[4] + + +# 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} + \{ <code> } +{code} + +If you want, you can indent every line, but you can also be lazy and just indent the first line of each block. + + +[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. -- cgit v1.2.3