diff options
-rw-r--r-- | src/Text/Pandoc/Templates.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/HTML.hs | 168 | ||||
-rw-r--r-- | src/pandoc.hs | 2 | ||||
-rw-r--r-- | templates/html.template | 126 | ||||
-rw-r--r-- | tests/writer.html | 2227 |
5 files changed, 1246 insertions, 1279 deletions
diff --git a/src/Text/Pandoc/Templates.hs b/src/Text/Pandoc/Templates.hs index 5c21cc8be..de2991566 100644 --- a/src/Text/Pandoc/Templates.hs +++ b/src/Text/Pandoc/Templates.hs @@ -66,7 +66,7 @@ renderTemplate :: [(String,String)] -- ^ Assoc. list of values for variables -> String renderTemplate vals templ = case runParser (do x <- parseTemplate; eof; return x) vals "template" templ of - Left e -> show e + Left e -> error $ show e Right r -> concat r reservedWords :: [String] diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 4e2eb4e26..a544ad781 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -30,36 +30,31 @@ Conversion of 'Pandoc' documents to HTML. -} module Text.Pandoc.Writers.HTML ( writeHtml , writeHtmlString ) where import Text.Pandoc.Definition -import Text.Pandoc.LaTeXMathML import Text.Pandoc.CharacterReferences ( decodeCharacterReferences ) import Text.Pandoc.Shared import Text.Pandoc.Templates import Text.Pandoc.Readers.TeXMath -import Text.Pandoc.Highlighting ( highlightHtml, defaultHighlightingCss ) +import Text.Pandoc.Highlighting ( highlightHtml ) import Text.Pandoc.XML (stripTags) import Numeric ( showHex ) import Data.Char ( ord, toLower ) -import Data.List ( isPrefixOf, intersperse ) +import Data.List ( isPrefixOf, intersperse, intercalate ) import Data.Maybe ( catMaybes ) -import qualified Data.Set as S import Control.Monad.State import Text.XHtml.Transitional hiding ( stringToHtml ) data WriterState = WriterState - { stNotes :: [Html] -- ^ List of notes - , stMath :: Bool -- ^ Math is used in document - , stCSS :: S.Set String -- ^ CSS to include in header - , stSecNum :: [Int] -- ^ Number of current section + { stNotes :: [Html] -- ^ List of notes + , stMath :: Bool -- ^ Math is used in document + , stHighlighting :: Bool -- ^ Syntax highlighting is used + , stSecNum :: [Int] -- ^ Number of current section } deriving Show defaultWriterState :: WriterState -defaultWriterState = WriterState {stNotes= [], stMath = False, stCSS = S.empty, stSecNum = []} +defaultWriterState = WriterState {stNotes= [], stMath = False, stHighlighting = False, stSecNum = []} -- Helpers to render HTML with the appropriate function. -render :: (HTML html) => WriterOptions -> html -> String -render opts = if writerWrapText opts then renderHtml else showHtml - renderFragment :: (HTML html) => WriterOptions -> html -> String renderFragment opts = if writerWrapText opts then renderHtmlFragment @@ -81,71 +76,87 @@ stringToHtml = primHtml . concatMap fixChar -- | Convert Pandoc document to Html string. writeHtmlString :: WriterOptions -> Pandoc -> String -writeHtmlString opts = - if writerStandalone opts - then render opts . writeHtml opts - else renderFragment opts . writeHtml opts +writeHtmlString opts d = + let (tit, auths, date, toc, body', newvars) = evalState (pandocToHtml opts d) + defaultWriterState + in if writerStandalone opts + then inTemplate opts tit auths date toc body' newvars + else renderFragment opts body' -- | Convert Pandoc document to Html structure. writeHtml :: WriterOptions -> Pandoc -> Html -writeHtml opts (Pandoc (Meta tit authors date) blocks) = - noHtml -- TODO --- let titlePrefix = writerTitlePrefix opts --- (topTitle,st) = runState (inlineListToHtml opts tit) defaultWriterState --- topTitle'' = stripTags $ showHtmlFragment topTitle --- topTitle' = titlePrefix ++ --- (if null topTitle'' || null titlePrefix --- then "" --- else " - ") ++ topTitle'' --- metadata = thetitle << topTitle' +++ --- meta ! [httpequiv "Content-Type", --- content "text/html; charset=UTF-8"] +++ --- meta ! [name "generator", content "pandoc"] +++ --- (toHtmlFromList $ --- map (\a -> meta ! [name "author", content a]) authors) +++ --- (if null date --- then noHtml --- else meta ! [name "date", content date]) --- titleHeader = if writerStandalone opts && not (null tit) && --- not (writerS5 opts) --- then h1 ! [theclass "title"] $ topTitle --- else noHtml --- sects = hierarchicalize blocks --- toc = if writerTableOfContents opts --- then evalState (tableOfContents opts sects) st --- else noHtml --- (blocks', st') = runState --- (mapM (elementToHtml opts) sects >>= return . toHtmlFromList) --- st --- cssLines = stCSS st' --- css = if S.null cssLines --- then noHtml --- else style ! [thetype "text/css"] $ primHtml $ --- '\n':(unlines $ S.toList cssLines) --- math = if stMath st' --- then case writerHTMLMathMethod opts of --- LaTeXMathML Nothing -> --- primHtml latexMathMLScript --- LaTeXMathML (Just url) -> --- script ! --- [src url, thetype "text/javascript"] $ --- noHtml --- JsMath (Just url) -> --- script ! --- [src url, thetype "text/javascript"] $ --- noHtml --- _ -> noHtml --- else noHtml --- head' = header $ metadata +++ math +++ css +++ --- primHtml (renderTemplate [] $ writerHeader opts) --- notes = reverse (stNotes st') --- before = primHtml $ writerIncludeBefore opts --- after = primHtml $ writerIncludeAfter opts --- thebody = before +++ titleHeader +++ toc +++ blocks' +++ --- footnoteSection notes +++ after --- in if writerStandalone opts --- then head' +++ body thebody --- else thebody +writeHtml opts d = + let (tit, auths, date, toc, body', newvars) = evalState (pandocToHtml opts d) + defaultWriterState + in if writerStandalone opts + then primHtml $ inTemplate opts tit auths date toc body' newvars + else body' + +-- result is (title, authors, date, toc, body, new variables) +pandocToHtml :: WriterOptions + -> Pandoc + -> State WriterState (Html, [Html], Html, Html, Html, [(String,String)]) +pandocToHtml opts (Pandoc (Meta title' authors' date') blocks) = do + let standalone = writerStandalone opts + tit <- if standalone + then inlineListToHtml opts title' + else return noHtml + auths <- if standalone + then mapM (inlineListToHtml opts) authors' + else return [] + date <- if standalone + then inlineListToHtml opts date' + else return noHtml + let sects = hierarchicalize blocks + toc <- if writerTableOfContents opts + then tableOfContents opts sects + else return noHtml + blocks' <- liftM toHtmlFromList $ mapM (elementToHtml opts) sects + st <- get + let notes = reverse (stNotes st) + let before = primHtml $ writerIncludeBefore opts + let after = primHtml $ writerIncludeAfter opts + let thebody = before +++ blocks' +++ footnoteSection notes +++ after + let math = if stMath st + then case writerHTMLMathMethod opts of + LaTeXMathML (Just url) -> + script ! + [src url, thetype "text/javascript"] $ noHtml + JsMath (Just url) -> + script ! + [src url, thetype "text/javascript"] $ noHtml + _ -> case lookup "latexmathml-script" (writerVariables opts) of + Just s -> + script ! [thetype "text/javascript"] << + primHtml s + Nothing -> noHtml + else noHtml + let newvars = [("highlighting","yes") | stHighlighting st] ++ + [("math", renderHtmlFragment math) | stMath st] + return (tit, auths, date, toc, thebody, newvars) + +inTemplate :: WriterOptions + -> Html + -> [Html] + -> Html + -> Html + -> Html + -> [(String,String)] + -> String +inTemplate opts tit auths date toc body' newvars = + let renderedTit = showHtmlFragment tit + topTitle' = stripTags renderedTit + authors = map (stripTags . showHtmlFragment) auths + date' = stripTags $ showHtmlFragment date + variables = writerVariables opts ++ newvars + context = variables ++ + [ ("body", renderHtmlFragment body') + , ("pagetitle", topTitle') + , ("toc", renderHtmlFragment toc) + , ("title", renderHtmlFragment tit) + , ("authors", intercalate "; " authors) + , ("date", date') ] + in renderTemplate context $ writerTemplate opts -- | Like Text.XHtml's identifier, but adds the writerIdentifierPrefix prefixedId :: WriterOptions -> String -> HtmlAttr @@ -251,13 +262,6 @@ obfuscateChar char = obfuscateString :: String -> String obfuscateString = concatMap obfuscateChar . decodeCharacterReferences --- | Add CSS for document header. -addToCSS :: String -> State WriterState () -addToCSS item = do - st <- get - let current = stCSS st - put $ st {stCSS = S.insert item current} - -- | Convert Pandoc block element to HTML. blockToHtml :: WriterOptions -> Block -> State WriterState Html blockToHtml _ Null = return $ noHtml @@ -279,7 +283,7 @@ blockToHtml opts (CodeBlock (id',classes,keyvals) rawCode) = do in return $ pre ! attrs $ thecode << (replicate (length leadingBreaks) br +++ [stringToHtml $ rawCode' ++ "\n"]) - Right h -> addToCSS defaultHighlightingCss >> return h + Right h -> modify (\st -> st{ stHighlighting = True }) >> return h blockToHtml opts (BlockQuote blocks) = -- in S5, treat list in blockquote specially -- if default is incremental, make it nonincremental; diff --git a/src/pandoc.hs b/src/pandoc.hs index 69c7ad895..48d8353db 100644 --- a/src/pandoc.hs +++ b/src/pandoc.hs @@ -643,7 +643,7 @@ main = do else return variables variables'' <- case mathMethod of - LaTeXMathML (Just _) -> do + LaTeXMathML Nothing -> do s <- latexMathMLScript return $ ("latexmathml-script", s) : variables' _ -> return variables' diff --git a/templates/html.template b/templates/html.template index 9a5f3ce95..3a756ee6e 100644 --- a/templates/html.template +++ b/templates/html.template @@ -1,81 +1,47 @@ <!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> -<html xmlns="http://www.w3.org/1999/xhtml" -><head - ><title - >title</title - ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" - /><meta name="generator" content="pandoc" - /><meta name="author" content="$authors$" - /><meta name="date" content="$date$" - /> - $if(latexmathml-script)$ - $latexmathml-script$ - $endif$ - $if(header-includes)$ - $header-includes$ - $endif$ -</head - ><body - > -<h1 class="title" - ><span class="math" - ><em - >title</em - ></span - ></h1 - ><div id="TOC" - ><ul - ><li - ><a href="#section-oen" - >section oen</a - ></li - ></ul - ></div - ><div id="section-oen" - ><h1 - ><a href="#TOC" - >section oen</a - ></h1 - ><ol style="list-style-type: decimal;" - ><li - >one<ol style="list-style-type: lower-alpha;" - ><li - >two<ol start="3" style="list-style-type: lower-roman;" - ><li - >three</li - ></ol - ></li - ></ol - ></li - ></ol - ><pre class="haskell" - ><code - >hi -</code - ></pre - ><p - >footnote<a href="#fn1" class="footnoteRef" id="fnref1" - ><sup - >1</sup - ></a - ></p - ></div - ><div class="footnotes" - ><hr - /><ol - ><li id="fn1" - ><p - >with code</p - ><pre - ><code - >code -</code - ></pre - > <a href="#fnref1" class="footnoteBackLink" title="Jump back to footnote 1">↩</a></li - ></ol - ></div - > -</body - ></html -> - +<html xmlns="http://www.w3.org/1999/xhtml"> +<head> + <title>$if(title-prefix)$$title-prefix$ - $endif$$if(pagetitle)$$pagetitle$$endif$</title> + <meta http-equiv="Content-Type" content="text/html; charset=utf-8" /> + <meta name="generator" content="pandoc" /> + <meta name="author" content="$authors$" /> + <meta name="date" content="$date$" /> + $if(highlighting)$ + <style type="text/css"> + table.sourceCode, tr.sourceCode, td.lineNumbers, td.sourceCode, table.sourceCode pre { margin: 0; padding: 0; border: 0; vertical-align: baseline; border: none; } + td.lineNumbers { border-right: 1px solid #AAAAAA; text-align: right; color: #AAAAAA; padding-right: 5px; padding-left: 5px; } + td.sourceCode { padding-left: 5px; } + pre.sourceCode { } + pre.sourceCode span.Normal { } + pre.sourceCode span.Keyword { color: #007020; font-weight: bold; } + pre.sourceCode span.DataType { color: #902000; } + pre.sourceCode span.DecVal { color: #40a070; } + pre.sourceCode span.BaseN { color: #40a070; } + pre.sourceCode span.Float { color: #40a070; } + pre.sourceCode span.Char { color: #4070a0; } + pre.sourceCode span.String { color: #4070a0; } + pre.sourceCode span.Comment { color: #60a0b0; font-style: italic; } + pre.sourceCode span.Others { color: #007020; } + pre.sourceCode span.Alert { color: red; font-weight: bold; } + pre.sourceCode span.Function { color: #06287e; } + pre.sourceCode span.RegionMarker { } + pre.sourceCode span.Error { color: red; font-weight: bold; } + </style> + $endif$ + $if(header-includes)$ + $header-includes$ + $endif$ + $if(latexmathml-script)$ + $latexmathml-script$ + $endif$ +</head> +<body> +$if(title)$ + <h1 class="title">$title$</h1> +$endif$ +$if(toc)$ +$toc$ +$endif$ +$body$ +</body> +</html> diff --git a/tests/writer.html b/tests/writer.html index ea9c99649..01b93481c 100644 --- a/tests/writer.html +++ b/tests/writer.html @@ -1,133 +1,130 @@ <!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> -<html xmlns="http://www.w3.org/1999/xhtml" -><head - ><title - >Pandoc Test Suite</title - ><meta http-equiv="Content-Type" content="text/html; charset=UTF-8" - /><meta name="generator" content="pandoc" - /><meta name="author" content="John MacFarlane" - /><meta name="author" content="Anonymous" - /><meta name="date" content="July 17, 2006" - /></head - ><body - ><h1 class="title" - >Pandoc Test Suite</h1 - ><p - >This is a set of tests for pandoc. Most of them are adapted from John Gruber’s markdown test suite.</p - ><hr - /><div id="headers" - ><h1 - >Headers</h1 - ><div id="level-2-with-an-embedded-link" - ><h2 - >Level 2 with an <a href="/url" - >embedded link</a - ></h2 - ><div id="level-3-with-emphasis" - ><h3 - >Level 3 with <em - >emphasis</em - ></h3 - ><div id="level-4" - ><h4 - >Level 4</h4 - ><div id="level-5" - ><h5 - >Level 5</h5 - ></div - ></div +<html xmlns="http://www.w3.org/1999/xhtml"> +<head> + <title>Pandoc Test Suite</title> + <meta http-equiv="Content-Type" content="text/html; charset=utf-8" /> + <meta name="generator" content="pandoc" /> + <meta name="author" content="John MacFarlane; Anonymous" /> + <meta name="date" content="July 17, 2006" /> + </head> +<body> + <h1 class="title">Pandoc Test Suite</h1> +<p +>This is a set of tests for pandoc. Most of them are adapted from John Gruber’s markdown test suite.</p +><hr + /><div id="headers" +><h1 + >Headers</h1 + ><div id="level-2-with-an-embedded-link" + ><h2 + >Level 2 with an <a href="/url" + >embedded link</a + ></h2 + ><div id="level-3-with-emphasis" + ><h3 + >Level 3 with <em + >emphasis</em + ></h3 + ><div id="level-4" + ><h4 + >Level 4</h4 + ><div id="level-5" + ><h5 + >Level 5</h5 ></div ></div ></div - ><div id="level-1" - ><h1 - >Level 1</h1 - ><div id="level-2-with-emphasis" - ><h2 - >Level 2 with <em - >emphasis</em - ></h2 - ><div id="level-3" - ><h3 - >Level 3</h3 - ><p - >with no blank line</p - ></div - ></div - ><div id="level-2" - ><h2 - >Level 2</h2 - ><p - >with no blank line</p - ><hr - /></div + ></div + ></div +><div id="level-1" +><h1 + >Level 1</h1 + ><div id="level-2-with-emphasis" + ><h2 + >Level 2 with <em + >emphasis</em + ></h2 + ><div id="level-3" + ><h3 + >Level 3</h3 + ><p + >with no blank line</p ></div - ><div id="paragraphs" - ><h1 - >Paragraphs</h1 - ><p - >Here’s a regular paragraph.</p - ><p - >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.</p - ><p - >Here’s one with a bullet. * criminey.</p - ><p - >There should be a hard line break<br - />here.</p - ><hr - /></div - ><div id="block-quotes" - ><h1 - >Block Quotes</h1 - ><p - >E-mail style:</p - ><blockquote - ><p - >This is a block quote. It is pretty short.</p - ></blockquote - ><blockquote - ><p - >Code in a block quote:</p - ><pre - ><code - >sub status { + ></div + ><div id="level-2" + ><h2 + >Level 2</h2 + ><p + >with no blank line</p + ><hr + /></div + ></div +><div id="paragraphs" +><h1 + >Paragraphs</h1 + ><p + >Here’s a regular paragraph.</p + ><p + >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.</p + ><p + >Here’s one with a bullet. * criminey.</p + ><p + >There should be a hard line break<br + />here.</p + ><hr + /></div +><div id="block-quotes" +><h1 + >Block Quotes</h1 + ><p + >E-mail style:</p + ><blockquote + ><p + >This is a block quote. It is pretty short.</p + ></blockquote + ><blockquote + ><p + >Code in a block quote:</p + ><pre + ><code + >sub status { print "working"; } </code - ></pre - ><p - >A list:</p - ><ol style="list-style-type: decimal;" - ><li - >item one</li - ><li - >item two</li - ></ol - ><p - >Nested block quotes:</p - ><blockquote - ><p - >nested</p - ></blockquote - ><blockquote - ><p - >nested</p - ></blockquote - ></blockquote - ><p - >This should not be a block quote: 2 > 1.</p - ><p - >And a following paragraph.</p - ><hr - /></div - ><div id="code-blocks" - ><h1 - >Code Blocks</h1 - ><p - >Code:</p - ><pre - ><code - >---- (should be four hyphens) + ></pre + ><p + >A list:</p + ><ol style="list-style-type: decimal;" + ><li + >item one</li + ><li + >item two</li + ></ol + ><p + >Nested block quotes:</p + ><blockquote + ><p + >nested</p + ></blockquote + ><blockquote + ><p + >nested</p + ></blockquote + ></blockquote + ><p + >This should not be a block quote: 2 > 1.</p + ><p + >And a following paragraph.</p + ><hr + /></div +><div id="code-blocks" +><h1 + >Code Blocks</h1 + ><p + >Code:</p + ><pre + ><code + >---- (should be four hyphens) sub status { print "working"; @@ -135,540 +132,540 @@ sub status { this code block is indented by one tab </code - ></pre - ><p - >And:</p - ><pre - ><code - > this code block is indented by two tabs + ></pre + ><p + >And:</p + ><pre + ><code + > this code block is indented by two tabs These should not be escaped: \$ \\ \> \[ \{ </code - ></pre - ><hr - /></div - ><div id="lists" - ><h1 - >Lists</h1 - ><div id="unordered" - ><h2 - >Unordered</h2 - ><p - >Asterisks tight:</p - ><ul - ><li - >asterisk 1</li - ><li - >asterisk 2</li - ><li - >asterisk 3</li - ></ul + ></pre + ><hr + /></div +><div id="lists" +><h1 + >Lists</h1 + ><div id="unordered" + ><h2 + >Unordered</h2 + ><p + >Asterisks tight:</p + ><ul + ><li + >asterisk 1</li + ><li + >asterisk 2</li + ><li + >asterisk 3</li + ></ul + ><p + >Asterisks loose:</p + ><ul + ><li + ><p + >asterisk 1</p + ></li + ><li + ><p + >asterisk 2</p + ></li + ><li + ><p + >asterisk 3</p + ></li + ></ul + ><p + >Pluses tight:</p + ><ul + ><li + >Plus 1</li + ><li + >Plus 2</li + ><li + >Plus 3</li + ></ul + ><p + >Pluses loose:</p + ><ul + ><li + ><p + >Plus 1</p + ></li + ><li + ><p + >Plus 2</p + ></li + ><li + ><p + >Plus 3</p + ></li + ></ul + ><p + >Minuses tight:</p + ><ul + ><li + >Minus 1</li + ><li + >Minus 2</li + ><li + >Minus 3</li + ></ul + ><p + >Minuses loose:</p + ><ul + ><li + ><p + >Minus 1</p + ></li + ><li + ><p + >Minus 2</p + ></li + ><li + ><p + >Minus 3</p + ></li + ></ul + ></div + ><div id="ordered" + ><h2 + >Ordered</h2 + ><p + >Tight:</p + ><ol style="list-style-type: decimal;" + ><li + >First</li + ><li + >Second</li + ><li + >Third</li + ></ol + ><p + >and:</p + ><ol style="list-style-type: decimal;" + ><li + >One</li + ><li + >Two</li + ><li + >Three</li + ></ol + ><p + >Loose using tabs:</p + ><ol style="list-style-type: decimal;" + ><li + ><p + >First</p + ></li + ><li + ><p + >Second</p + ></li + ><li + ><p + >Third</p + ></li + ></ol + ><p + >and using spaces:</p + ><ol style="list-style-type: decimal;" + ><li + ><p + >One</p + ></li + ><li + ><p + >Two</p + ></li + ><li + ><p + >Three</p + ></li + ></ol + ><p + >Multiple paragraphs:</p + ><ol style="list-style-type: decimal;" + ><li + ><p + >Item 1, graf one.</p ><p - >Asterisks loose:</p - ><ul + >Item 1. graf two. The quick brown fox jumped over the lazy dog’s back.</p + ></li + ><li + ><p + >Item 2.</p + ></li + ><li + ><p + >Item 3.</p + ></li + ></ol + ></div + ><div id="nested" + ><h2 + >Nested</h2 + ><ul + ><li + >Tab<ul ><li - ><p - >asterisk 1</p - ></li - ><li - ><p - >asterisk 2</p - ></li - ><li - ><p - >asterisk 3</p + >Tab<ul + ><li + >Tab</li + ></ul ></li ></ul - ><p - >Pluses tight:</p - ><ul - ><li - >Plus 1</li - ><li - >Plus 2</li - ><li - >Plus 3</li - ></ul - ><p - >Pluses loose:</p - ><ul + ></li + ></ul + ><p + >Here’s another:</p + ><ol style="list-style-type: decimal;" + ><li + >First</li + ><li + >Second:<ul ><li - ><p - >Plus 1</p - ></li + >Fee</li ><li - ><p - >Plus 2</p - ></li + >Fie</li ><li - ><p - >Plus 3</p - ></li + >Foe</li ></ul - ><p - >Minuses tight:</p + ></li + ><li + >Third</li + ></ol + ><p + >Same thing but with paragraphs:</p + ><ol style="list-style-type: decimal;" + ><li + ><p + >First</p + ></li + ><li + ><p + >Second:</p ><ul ><li - >Minus 1</li + >Fee</li ><li - >Minus 2</li + >Fie</li ><li - >Minus 3</li + >Foe</li ></ul - ><p - >Minuses loose:</p + ></li + ><li + ><p + >Third</p + ></li + ></ol + ></div + ><div id="tabs-and-spaces" + ><h2 + >Tabs and spaces</h2 + ><ul + ><li + ><p + >this is a list item indented with tabs</p + ></li + ><li + ><p + >this is a list item indented with spaces</p ><ul ><li ><p - >Minus 1</p - ></li - ><li - ><p - >Minus 2</p - ></li - ><li - ><p - >Minus 3</p - ></li - ></ul - ></div - ><div id="ordered" - ><h2 - >Ordered</h2 - ><p - >Tight:</p - ><ol style="list-style-type: decimal;" - ><li - >First</li - ><li - >Second</li - ><li - >Third</li - ></ol - ><p - >and:</p - ><ol style="list-style-type: decimal;" - ><li - >One</li - ><li - >Two</li - ><li - >Three</li - ></ol - ><p - >Loose using tabs:</p - ><ol style="list-style-type: decimal;" - ><li - ><p - >First</p - ></li - ><li - ><p - >Second</p - ></li - ><li - ><p - >Third</p - ></li - ></ol - ><p - >and using spaces:</p - ><ol style="list-style-type: decimal;" - ><li - ><p - >One</p - ></li - ><li - ><p - >Two</p - ></li - ><li - ><p - >Three</p - ></li - ></ol - ><p - >Multiple paragraphs:</p - ><ol style="list-style-type: decimal;" - ><li - ><p - >Item 1, graf one.</p - ><p - >Item 1. graf two. The quick brown fox jumped over the lazy dog’s back.</p + >this is an example list item indented with tabs</p ></li ><li ><p - >Item 2.</p - ></li - ><li - ><p - >Item 3.</p - ></li - ></ol - ></div - ><div id="nested" - ><h2 - >Nested</h2 - ><ul - ><li - >Tab<ul - ><li - >Tab<ul - ><li - >Tab</li - ></ul - ></li - ></ul + >this is an example list item indented with spaces</p ></li ></ul + ></li + ></ul + ></div + ><div id="fancy-list-markers" + ><h2 + >Fancy list markers</h2 + ><ol start="2" style="list-style-type: decimal;" + ><li + >begins with 2</li + ><li + ><p + >and now 3</p ><p - >Here’s another:</p - ><ol style="list-style-type: decimal;" - ><li - >First</li - ><li - >Second:<ul - ><li - >Fee</li - ><li - >Fie</li - ><li - >Foe</li - ></ul - ></li - ><li - >Third</li - ></ol - ><p - >Same thing but with paragraphs:</p - ><ol style="list-style-type: decimal;" + >with a continuation</p + ><ol start="4" style="list-style-type: lower-roman;" ><li - ><p - >First</p - ></li + >sublist with roman numerals, starting with 4</li ><li - ><p - >Second:</p - ><ul + >more items<ol style="list-style-type: upper-alpha;" ><li - >Fee</li + >a subsublist</li ><li - >Fie</li - ><li - >Foe</li - ></ul - ></li - ><li - ><p - >Third</p - ></li - ></ol - ></div - ><div id="tabs-and-spaces" - ><h2 - >Tabs and spaces</h2 - ><ul - ><li - ><p - >this is a list item indented with tabs</p - ></li - ><li - ><p - >this is a list item indented with spaces</p - ><ul - ><li - ><p - >this is an example list item indented with tabs</p - ></li - ><li - ><p - >this is an example list item indented with spaces</p - ></li - ></ul - ></li - ></ul - ></div - ><div id="fancy-list-markers" - ><h2 - >Fancy list markers</h2 - ><ol start="2" style="list-style-type: decimal;" - ><li - >begins with 2</li - ><li - ><p - >and now 3</p - ><p - >with a continuation</p - ><ol start="4" style="list-style-type: lower-roman;" - ><li - >sublist with roman numerals, starting with 4</li - ><li - >more items<ol style="list-style-type: upper-alpha;" - ><li - >a subsublist</li - ><li - >a subsublist</li - ></ol - ></li + >a subsublist</li ></ol ></li ></ol - ><p - >Nesting:</p - ><ol style="list-style-type: upper-alpha;" + ></li + ></ol + ><p + >Nesting:</p + ><ol style="list-style-type: upper-alpha;" + ><li + >Upper Alpha<ol style="list-style-type: upper-roman;" ><li - >Upper Alpha<ol style="list-style-type: upper-roman;" + >Upper Roman.<ol start="6" style="list-style-type: decimal;" ><li - >Upper Roman.<ol start="6" style="list-style-type: decimal;" + >Decimal start with 6<ol start="3" style="list-style-type: lower-alpha;" ><li - >Decimal start with 6<ol start="3" style="list-style-type: lower-alpha;" - ><li - >Lower alpha with paren</li - ></ol - ></li + >Lower alpha with paren</li ></ol ></li ></ol ></li ></ol - ><p - >Autonumbering:</p - ><ol + ></li + ></ol + ><p + >Autonumbering:</p + ><ol + ><li + >Autonumber.</li + ><li + >More.<ol ><li - >Autonumber.</li - ><li - >More.<ol - ><li - >Nested.</li - ></ol - ></li + >Nested.</li ></ol - ><p - >Should not be a list item:</p - ><p - >M.A. 2007</p - ><p - >B. Williams</p - ><hr - /></div - ></div - ><div id="definition-lists" - ><h1 - >Definition Lists</h1 - ><p - >Tight using spaces:</p - ><dl - ><dt - >apple</dt - ><dd - >red fruit</dd - ><dt - >orange</dt - ><dd - >orange fruit</dd - ><dt - >banana</dt - ><dd - >yellow fruit</dd - ></dl - ><p - >Tight using tabs:</p - ><dl - ><dt - >apple</dt - ><dd - >red fruit</dd - ><dt - >orange</dt - ><dd - >orange fruit</dd - ><dt - >banana</dt - ><dd - >yellow fruit</dd - ></dl - ><p - >Loose:</p - ><dl - ><dt - >apple</dt - ><dd - ><p - >red fruit</p - ></dd - ><dt - >orange</dt - ><dd - ><p - >orange fruit</p - ></dd - ><dt - >banana</dt - ><dd - ><p - >yellow fruit</p - ></dd - ></dl - ><p - >Multiple blocks with italics:</p - ><dl - ><dt - ><em - >apple</em - ></dt - ><dd - ><p - >red fruit</p - ><p - >contains seeds, crisp, pleasant to taste</p - ></dd - ><dt - ><em - >orange</em - ></dt - ><dd - ><p - >orange fruit</p - ><pre - ><code - >{ orange code block } + ></li + ></ol + ><p + >Should not be a list item:</p + ><p + >M.A. 2007</p + ><p + >B. Williams</p + ><hr + /></div + ></div +><div id="definition-lists" +><h1 + >Definition Lists</h1 + ><p + >Tight using spaces:</p + ><dl + ><dt + >apple</dt + ><dd + >red fruit</dd + ><dt + >orange</dt + ><dd + >orange fruit</dd + ><dt + >banana</dt + ><dd + >yellow fruit</dd + ></dl + ><p + >Tight using tabs:</p + ><dl + ><dt + >apple</dt + ><dd + >red fruit</dd + ><dt + >orange</dt + ><dd + >orange fruit</dd + ><dt + >banana</dt + ><dd + >yellow fruit</dd + ></dl + ><p + >Loose:</p + ><dl + ><dt + >apple</dt + ><dd + ><p + >red fruit</p + ></dd + ><dt + >orange</dt + ><dd + ><p + >orange fruit</p + ></dd + ><dt + >banana</dt + ><dd + ><p + >yellow fruit</p + ></dd + ></dl + ><p + >Multiple blocks with italics:</p + ><dl + ><dt + ><em + >apple</em + ></dt + ><dd + ><p + >red fruit</p + ><p + >contains seeds, crisp, pleasant to taste</p + ></dd + ><dt + ><em + >orange</em + ></dt + ><dd + ><p + >orange fruit</p + ><pre + ><code + >{ orange code block } </code - ></pre - ><blockquote - ><p - >orange block quote</p - ></blockquote - ></dd - ></dl - ><p - >Multiple definitions, tight:</p - ><dl - ><dt - >apple</dt - ><dd - >red fruit</dd - ><dd - >computer</dd - ><dt - >orange</dt - ><dd - >orange fruit</dd - ><dd - >bank</dd - ></dl - ><p - >Multiple definitions, loose:</p - ><dl - ><dt - >apple</dt - ><dd - ><p - >red fruit</p - ></dd - ><dd - ><p - >computer</p - ></dd - ><dt - >orange</dt - ><dd - ><p - >orange fruit</p - ></dd - ><dd - ><p - >bank</p - ></dd - ></dl - ><p - >Blank line after term, indented marker, alternate markers:</p - ><dl - ><dt - >apple</dt - ><dd - ><p - >red fruit</p - ></dd - ><dd - ><p - >computer</p - ></dd - ><dt - >orange</dt - ><dd - ><p - >orange fruit</p - ><ol style="list-style-type: decimal;" - ><li - >sublist</li - ><li - >sublist</li - ></ol - ></dd - ></dl - ></div - ><div id="html-blocks" - ><h1 - >HTML Blocks</h1 + ></pre + ><blockquote ><p - >Simple block on one line:</p - ><div>foo</div> + >orange block quote</p + ></blockquote + ></dd + ></dl + ><p + >Multiple definitions, tight:</p + ><dl + ><dt + >apple</dt + ><dd + >red fruit</dd + ><dd + >computer</dd + ><dt + >orange</dt + ><dd + >orange fruit</dd + ><dd + >bank</dd + ></dl + ><p + >Multiple definitions, loose:</p + ><dl + ><dt + >apple</dt + ><dd + ><p + >red fruit</p + ></dd + ><dd + ><p + >computer</p + ></dd + ><dt + >orange</dt + ><dd + ><p + >orange fruit</p + ></dd + ><dd + ><p + >bank</p + ></dd + ></dl + ><p + >Blank line after term, indented marker, alternate markers:</p + ><dl + ><dt + >apple</dt + ><dd + ><p + >red fruit</p + ></dd + ><dd + ><p + >computer</p + ></dd + ><dt + >orange</dt + ><dd + ><p + >orange fruit</p + ><ol style="list-style-type: decimal;" + ><li + >sublist</li + ><li + >sublist</li + ></ol + ></dd + ></dl + ></div +><div id="html-blocks" +><h1 + >HTML Blocks</h1 + ><p + >Simple block on one line:</p + ><div>foo</div> <p - >And nested without indentation:</p - ><div> + >And nested without indentation:</p + ><div> <div> <div>foo</div> </div> <div>bar</div> </div> <p - >Interpreted markdown in a table:</p - ><table> + >Interpreted markdown in a table:</p + ><table> <tr> <td>This is <em - >emphasized</em - ></td> + >emphasized</em + ></td> <td>And this is <strong - >strong</strong - ></td> + >strong</strong + ></td> </tr> </table> <script type="text/javascript">document.write('This *should not* be interpreted as markdown');</script> <p - >Here’s a simple block:</p - ><div> + >Here’s a simple block:</p + ><div> foo</div> <p - >This should be a code block, though:</p - ><pre - ><code - ><div> + >This should be a code block, though:</p + ><pre + ><code + ><div> foo </div> </code - ></pre - ><p - >As should this:</p - ><pre - ><code - ><div>foo</div> + ></pre + ><p + >As should this:</p + ><pre + ><code + ><div>foo</div> </code - ></pre - ><p - >Now, nested:</p - ><div> + ></pre + ><p + >Now, nested:</p + ><div> <div> <div> foo</div> </div> </div> <p - >This should just be an HTML comment:</p - ><!-- Comment --> + >This should just be an HTML comment:</p + ><!-- Comment --> <p - >Multiline:</p - ><!-- + >Multiline:</p + ><!-- Blah Blah --> @@ -677,25 +674,25 @@ Blah This is another comment. --> <p - >Code block:</p - ><pre - ><code - ><!-- Comment --> + >Code block:</p + ><pre + ><code + ><!-- Comment --> </code - ></pre - ><p - >Just plain comment, with trailing spaces on the line:</p - ><!-- foo --> + ></pre + ><p + >Just plain comment, with trailing spaces on the line:</p + ><!-- foo --> <p - >Code:</p - ><pre - ><code - ><hr /> + >Code:</p + ><pre + ><code + ><hr /> </code - ></pre - ><p - >Hr’s:</p - ><hr> + ></pre + ><p + >Hr’s:</p + ><hr> <hr /> @@ -713,538 +710,538 @@ Blah <hr class="foo" id="bar"> <hr - /></div - ><div id="inline-markup" - ><h1 - >Inline Markup</h1 - ><p - >This is <em - >emphasized</em - >, and so <em - >is this</em - >.</p - ><p - >This is <strong - >strong</strong - >, and so <strong - >is this</strong - >.</p - ><p - >An <em - ><a href="/url" - >emphasized link</a - ></em - >.</p - ><p - ><strong - ><em - >This is strong and em.</em - ></strong - ></p - ><p - >So is <strong - ><em - >this</em - ></strong - > word.</p - ><p - ><strong + /></div +><div id="inline-markup" +><h1 + >Inline Markup</h1 + ><p + >This is <em + >emphasized</em + >, and so <em + >is this</em + >.</p + ><p + >This is <strong + >strong</strong + >, and so <strong + >is this</strong + >.</p + ><p + >An <em + ><a href="/url" + >emphasized link</a + ></em + >.</p + ><p + ><strong + ><em + >This is strong and em.</em + ></strong + ></p + ><p + >So is <strong + ><em + >this</em + ></strong + > word.</p + ><p + ><strong + ><em + >This is strong and em.</em + ></strong + ></p + ><p + >So is <strong + ><em + >this</em + ></strong + > word.</p + ><p + >This is code: <code + >></code + >, <code + >$</code + >, <code + >\</code + >, <code + >\$</code + >, <code + ><html></code + >.</p + ><p + ><span style="text-decoration: line-through;" + >This is <em + >strikeout</em + >.</span + ></p + ><p + >Superscripts: a<sup + >bc</sup + >d a<sup + ><em + >hello</em + ></sup + > a<sup + >hello there</sup + >.</p + ><p + >Subscripts: H<sub + >2</sub + >O, H<sub + >23</sub + >O, H<sub + >many of them</sub + >O.</p + ><p + >These should not be superscripts or subscripts, because of the unescaped spaces: a^b c^d, a~b c~d.</p + ><hr + /></div +><div id="smart-quotes-ellipses-dashes" +><h1 + >Smart quotes, ellipses, dashes</h1 + ><p + >“Hello,” said the spider. “‘Shelob’ is my name.”</p + ><p + >‘A’, ‘B’, and ‘C’ are letters.</p + ><p + >‘Oak,’ ‘elm,’ and ‘beech’ are names of trees. So is ‘pine.’</p + ><p + >‘He said, “I want to go.”’ Were you alive in the 70’s?</p + ><p + >Here is some quoted ‘<code + >code</code + >’ and a “<a href="http://example.com/?foo=1&bar=2" + >quoted link</a + >”.</p + ><p + >Some dashes: one—two — three—four — five.</p + ><p + >Dashes between numbers: 5–7, 255–66, 1987–1999.</p + ><p + >Ellipses…and…and….</p + ><hr + /></div +><div id="latex" +><h1 + >LaTeX</h1 + ><ul + ><li + ></li + ><li + ><span class="math" + >2+2=4</span + ></li + ><li + ><span class="math" + ><em + >x</em + > ∈ <em + >y</em + ></span + ></li + ><li + ><span class="math" + >α ∧ ω</span + ></li + ><li + ><span class="math" + >223</span + ></li + ><li + ><span class="math" + ><em + >p</em + ></span + >-Tree</li + ><li + >Here’s some display math: <span class="math" + >\frac{<em + >d</em + >}{<em + >dx</em + >}<em + >f</em + >(<em + >x</em + >)=\lim<sub ><em - >This is strong and em.</em - ></strong - ></p - ><p - >So is <strong - ><em - >this</em - ></strong - > word.</p - ><p - >This is code: <code - >></code - >, <code - >$</code - >, <code - >\</code - >, <code - >\$</code - >, <code - ><html></code - >.</p - ><p - ><span style="text-decoration: line-through;" - >This is <em - >strikeout</em - >.</span - ></p - ><p - >Superscripts: a<sup - >bc</sup - >d a<sup - ><em - >hello</em - ></sup - > a<sup - >hello there</sup - >.</p - ><p - >Subscripts: H<sub - >2</sub - >O, H<sub - >23</sub - >O, H<sub - >many of them</sub - >O.</p - ><p - >These should not be superscripts or subscripts, because of the unescaped spaces: a^b c^d, a~b c~d.</p - ><hr - /></div - ><div id="smart-quotes-ellipses-dashes" - ><h1 - >Smart quotes, ellipses, dashes</h1 - ><p - >“Hello,” said the spider. “‘Shelob’ is my name.”</p - ><p - >‘A’, ‘B’, and ‘C’ are letters.</p - ><p - >‘Oak,’ ‘elm,’ and ‘beech’ are names of trees. So is ‘pine.’</p - ><p - >‘He said, “I want to go.”’ Were you alive in the 70’s?</p - ><p - >Here is some quoted ‘<code - >code</code - >’ and a “<a href="http://example.com/?foo=1&bar=2" - >quoted link</a - >”.</p - ><p - >Some dashes: one—two — three—four — five.</p - ><p - >Dashes between numbers: 5–7, 255–66, 1987–1999.</p - ><p - >Ellipses…and…and….</p - ><hr - /></div - ><div id="latex" - ><h1 - >LaTeX</h1 - ><ul - ><li - ></li - ><li - ><span class="math" - >2+2=4</span - ></li - ><li - ><span class="math" - ><em - >x</em - > ∈ <em - >y</em - ></span - ></li - ><li - ><span class="math" - >α ∧ ω</span - ></li - ><li - ><span class="math" - >223</span - ></li - ><li - ><span class="math" - ><em - >p</em - ></span - >-Tree</li - ><li - >Here’s some display math: <span class="math" - >\frac{<em - >d</em - >}{<em - >dx</em - >}<em - >f</em - >(<em - >x</em - >)=\lim<sub - ><em - >h</em - > → 0</sub - >\frac{<em - >f</em - >(<em - >x</em - >+<em - >h</em - >)-<em - >f</em - >(<em - >x</em - >)}{<em - >h</em - >}</span - ></li - ><li - >Here’s one that has a line break in it: <span class="math" - >α+ω × <em - >x</em - ><sup - >2</sup - ></span - >.</li - ></ul - ><p - >These shouldn’t be math:</p - ><ul - ><li - >To get the famous equation, write <code - >$e = mc^2$</code - >.</li - ><li - >$22,000 is a <em - >lot</em - > of money. So is $34,000. (It worked if “lot” is emphasized.)</li - ><li - >Shoes ($20) and socks ($5).</li - ><li - >Escaped <code - >$</code - >: $73 <em - >this should be emphasized</em - > 23$.</li - ></ul - ><p - >Here’s a LaTeX table:</p - ><p + >h</em + > → 0</sub + >\frac{<em + >f</em + >(<em + >x</em + >+<em + >h</em + >)-<em + >f</em + >(<em + >x</em + >)}{<em + >h</em + >}</span + ></li + ><li + >Here’s one that has a line break in it: <span class="math" + >α+ω × <em + >x</em + ><sup + >2</sup + ></span + >.</li + ></ul + ><p + >These shouldn’t be math:</p + ><ul + ><li + >To get the famous equation, write <code + >$e = mc^2$</code + >.</li + ><li + >$22,000 is a <em + >lot</em + > of money. So is $34,000. (It worked if “lot” is emphasized.)</li + ><li + >Shoes ($20) and socks ($5).</li + ><li + >Escaped <code + >$</code + >: $73 <em + >this should be emphasized</em + > 23$.</li + ></ul + ><p + >Here’s a LaTeX table:</p + ><p + ></p + ><hr + /></div +><div id="special-characters" +><h1 + >Special Characters</h1 + ><p + >Here is some unicode:</p + ><ul + ><li + >I hat: Î</li + ><li + >o umlaut: ö</li + ><li + >section: §</li + ><li + >set membership: ∈</li + ><li + >copyright: ©</li + ></ul + ><p + >AT&T has an ampersand in their name.</p + ><p + >AT&T is another way to write it.</p + ><p + >This & that.</p + ><p + >4 < 5.</p + ><p + >6 > 5.</p + ><p + >Backslash: \</p + ><p + >Backtick: `</p + ><p + >Asterisk: *</p + ><p + >Underscore: _</p + ><p + >Left brace: {</p + ><p + >Right brace: }</p + ><p + >Left bracket: [</p + ><p + >Right bracket: ]</p + ><p + >Left paren: (</p + ><p + >Right paren: )</p + ><p + >Greater-than: ></p + ><p + >Hash: #</p + ><p + >Period: .</p + ><p + >Bang: !</p + ><p + >Plus: +</p + ><p + >Minus: -</p + ><hr + /></div +><div id="links" +><h1 + >Links</h1 + ><div id="explicit" + ><h2 + >Explicit</h2 + ><p + >Just a <a href="/url/" + >URL</a + >.</p + ><p + ><a href="/url/" title="title" + >URL and title</a + >.</p + ><p + ><a href="/url/" title="title preceded by two spaces" + >URL and title</a + >.</p + ><p + ><a href="/url/" title="title preceded by a tab" + >URL and title</a + >.</p + ><p + ><a href="/url/" title="title with "quotes" in it" + >URL and title</a ></p - ><hr - /></div - ><div id="special-characters" - ><h1 - >Special Characters</h1 - ><p - >Here is some unicode:</p - ><ul - ><li - >I hat: Î</li - ><li - >o umlaut: ö</li - ><li - >section: §</li - ><li - >set membership: ∈</li - ><li - >copyright: ©</li - ></ul - ><p - >AT&T has an ampersand in their name.</p - ><p - >AT&T is another way to write it.</p - ><p - >This & that.</p - ><p - >4 < 5.</p - ><p - >6 > 5.</p - ><p - >Backslash: \</p - ><p - >Backtick: `</p - ><p - >Asterisk: *</p - ><p - >Underscore: _</p - ><p - >Left brace: {</p - ><p - >Right brace: }</p - ><p - >Left bracket: [</p - ><p - >Right bracket: ]</p - ><p - >Left paren: (</p - ><p - >Right paren: )</p - ><p - >Greater-than: ></p - ><p - >Hash: #</p - ><p - >Period: .</p - ><p - >Bang: !</p - ><p - >Plus: +</p - ><p - >Minus: -</p - ><hr - /></div - ><div id="links" - ><h1 - >Links</h1 - ><div id="explicit" - ><h2 - >Explicit</h2 - ><p - >Just a <a href="/url/" - >URL</a - >.</p - ><p - ><a href="/url/" title="title" - >URL and title</a - >.</p - ><p - ><a href="/url/" title="title preceded by two spaces" - >URL and title</a - >.</p - ><p - ><a href="/url/" title="title preceded by a tab" - >URL and title</a - >.</p - ><p - ><a href="/url/" title="title with "quotes" in it" - >URL and title</a - ></p - ><p - ><a href="/url/" title="title with single quotes" - >URL and title</a - ></p - ><p - ><a href="/url/with_underscore" - >with_underscore</a - ></p - ><p - ><script type="text/javascript" - > + ><p + ><a href="/url/" title="title with single quotes" + >URL and title</a + ></p + ><p + ><a href="/url/with_underscore" + >with_underscore</a + ></p + ><p + ><script type="text/javascript" + > <!-- h='nowhere.net';a='@';n='nobody';e=n+a+h; document.write('<a h'+'ref'+'="ma'+'ilto'+':'+e+'">'+'Email link'+'<\/'+'a'+'>'); // --> </script - ><noscript - >Email link (nobody at nowhere dot net)</noscript - ></p - ><p - ><a href="" - >Empty</a - >.</p - ></div - ><div id="reference" - ><h2 - >Reference</h2 - ><p - >Foo <a href="/url/" - >bar</a - >.</p - ><p - >Foo <a href="/url/" - >bar</a - >.</p - ><p - >Foo <a href="/url/" - >bar</a - >.</p - ><p - >With <a href="/url/" - >embedded [brackets]</a - >.</p - ><p - ><a href="/url/" - >b</a - > by itself should be a link.</p - ><p - >Indented <a href="/url" - >once</a - >.</p - ><p - >Indented <a href="/url" - >twice</a - >.</p - ><p - >Indented <a href="/url" - >thrice</a - >.</p - ><p - >This should [not][] be a link.</p - ><pre - ><code - >[not]: /url + ><noscript + >Email link (nobody at nowhere dot net)</noscript + ></p + ><p + ><a href="" + >Empty</a + >.</p + ></div + ><div id="reference" + ><h2 + >Reference</h2 + ><p + >Foo <a href="/url/" + >bar</a + >.</p + ><p + >Foo <a href="/url/" + >bar</a + >.</p + ><p + >Foo <a href="/url/" + >bar</a + >.</p + ><p + >With <a href="/url/" + >embedded [brackets]</a + >.</p + ><p + ><a href="/url/" + >b</a + > by itself should be a link.</p + ><p + >Indented <a href="/url" + >once</a + >.</p + ><p + >Indented <a href="/url" + >twice</a + >.</p + ><p + >Indented <a href="/url" + >thrice</a + >.</p + ><p + >This should [not][] be a link.</p + ><pre + ><code + >[not]: /url </code - ></pre - ><p - >Foo <a href="/url/" title="Title with "quotes" inside" - >bar</a - >.</p - ><p - >Foo <a href="/url/" title="Title with "quote" inside" - >biz</a - >.</p - ></div - ><div id="with-ampersands" - ><h2 - >With ampersands</h2 - ><p - >Here’s a <a href="http://example.com/?foo=1&bar=2" - >link with an ampersand in the URL</a - >.</p - ><p - >Here’s a link with an amersand in the link text: <a href="http://att.com/" title="AT&T" - >AT&T</a - >.</p - ><p - >Here’s an <a href="/script?foo=1&bar=2" - >inline link</a - >.</p - ><p - >Here’s an <a href="/script?foo=1&bar=2" - >inline link in pointy braces</a - >.</p - ></div - ><div id="autolinks" - ><h2 - >Autolinks</h2 - ><p - >With an ampersand: <a href="http://example.com/?foo=1&bar=2" - ><code - >http://example.com/?foo=1&bar=2</code - ></a - ></p - ><ul - ><li - >In a list?</li - ><li - ><a href="http://example.com/" - ><code - >http://example.com/</code - ></a - ></li - ><li - >It should.</li - ></ul - ><p - >An e-mail address: <script type="text/javascript" - > + ></pre + ><p + >Foo <a href="/url/" title="Title with "quotes" inside" + >bar</a + >.</p + ><p + >Foo <a href="/url/" title="Title with "quote" inside" + >biz</a + >.</p + ></div + ><div id="with-ampersands" + ><h2 + >With ampersands</h2 + ><p + >Here’s a <a href="http://example.com/?foo=1&bar=2" + >link with an ampersand in the URL</a + >.</p + ><p + >Here’s a link with an amersand in the link text: <a href="http://att.com/" title="AT&T" + >AT&T</a + >.</p + ><p + >Here’s an <a href="/script?foo=1&bar=2" + >inline link</a + >.</p + ><p + >Here’s an <a href="/script?foo=1&bar=2" + >inline link in pointy braces</a + >.</p + ></div + ><div id="autolinks" + ><h2 + >Autolinks</h2 + ><p + >With an ampersand: <a href="http://example.com/?foo=1&bar=2" + ><code + >http://example.com/?foo=1&bar=2</code + ></a + ></p + ><ul + ><li + >In a list?</li + ><li + ><a href="http://example.com/" + ><code + >http://example.com/</code + ></a + ></li + ><li + >It should.</li + ></ul + ><p + >An e-mail address: <script type="text/javascript" + > <!-- h='nowhere.net';a='@';n='nobody';e=n+a+h; document.write('<a h'+'ref'+'="ma'+'ilto'+':'+e+'">'+'<code>'+e+'</code>'+'<\/'+'a'+'>'); // --> </script - ><noscript - >nobody at nowhere dot net</noscript - ></p - ><blockquote - ><p - >Blockquoted: <a href="http://example.com/" - ><code - >http://example.com/</code - ></a - ></p - ></blockquote - ><p - >Auto-links should not occur here: <code - ><http://example.com/></code - ></p - ><pre + ><noscript + >nobody at nowhere dot net</noscript + ></p + ><blockquote + ><p + >Blockquoted: <a href="http://example.com/" ><code - >or here: <http://example.com/> -</code - ></pre - ><hr - /></div - ></div - ><div id="images" - ><h1 - >Images</h1 - ><p - >From “Voyage dans la Lune” by Georges Melies (1902):</p - ><p - ><img src="lalune.jpg" title="Voyage dans la Lune" alt="lalune" - /></p - ><p - >Here is a movie <img src="movie.jpg" alt="movie" - /> icon.</p - ><hr - /></div - ><div id="footnotes" - ><h1 - >Footnotes</h1 - ><p - >Here is a footnote reference,<a href="#fn1" class="footnoteRef" id="fnref1" - ><sup - >1</sup - ></a - > and another.<a href="#fn2" class="footnoteRef" id="fnref2" - ><sup - >2</sup - ></a - > This should <em - >not</em - > be a footnote reference, because it contains a space.[^my note] Here is an inline note.<a href="#fn3" class="footnoteRef" id="fnref3" - ><sup - >3</sup + >http://example.com/</code ></a ></p - ><blockquote - ><p - >Notes can go in quotes.<a href="#fn4" class="footnoteRef" id="fnref4" - ><sup - >4</sup - ></a - ></p - ></blockquote - ><ol style="list-style-type: decimal;" - ><li - >And in list items.<a href="#fn5" class="footnoteRef" id="fnref5" - ><sup - >5</sup - ></a - ></li - ></ol - ><p - >This paragraph should not be part of the note, as it is not indented.</p - ></div - ><div class="footnotes" + ></blockquote + ><p + >Auto-links should not occur here: <code + ><http://example.com/></code + ></p + ><pre + ><code + >or here: <http://example.com/> +</code + ></pre ><hr - /><ol - ><li id="fn1" - ><p - >Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document. <a href="#fnref1" class="footnoteBackLink" title="Jump back to footnote 1">↩</a></p - ></li - ><li id="fn2" - ><p - >Here’s the long note. This one contains multiple blocks.</p - ><p - >Subsequent blocks are indented to show that they belong to the footnote (as with list items).</p - ><pre - ><code - > { <code> } + /></div + ></div +><div id="images" +><h1 + >Images</h1 + ><p + >From “Voyage dans la Lune” by Georges Melies (1902):</p + ><p + ><img src="lalune.jpg" title="Voyage dans la Lune" alt="lalune" + /></p + ><p + >Here is a movie <img src="movie.jpg" alt="movie" + /> icon.</p + ><hr + /></div +><div id="footnotes" +><h1 + >Footnotes</h1 + ><p + >Here is a footnote reference,<a href="#fn1" class="footnoteRef" id="fnref1" + ><sup + >1</sup + ></a + > and another.<a href="#fn2" class="footnoteRef" id="fnref2" + ><sup + >2</sup + ></a + > This should <em + >not</em + > be a footnote reference, because it contains a space.[^my note] Here is an inline note.<a href="#fn3" class="footnoteRef" id="fnref3" + ><sup + >3</sup + ></a + ></p + ><blockquote + ><p + >Notes can go in quotes.<a href="#fn4" class="footnoteRef" id="fnref4" + ><sup + >4</sup + ></a + ></p + ></blockquote + ><ol style="list-style-type: decimal;" + ><li + >And in list items.<a href="#fn5" class="footnoteRef" id="fnref5" + ><sup + >5</sup + ></a + ></li + ></ol + ><p + >This paragraph should not be part of the note, as it is not indented.</p + ></div +><div class="footnotes" +><hr + /><ol + ><li id="fn1" + ><p + >Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document. <a href="#fnref1" class="footnoteBackLink" title="Jump back to footnote 1">↩</a></p + ></li + ><li id="fn2" + ><p + >Here’s the long note. This one contains multiple blocks.</p + ><p + >Subsequent blocks are indented to show that they belong to the footnote (as with list items).</p + ><pre + ><code + > { <code> } </code - ></pre - ><p - >If you want, you can indent every line, but you can also be lazy and just indent the first line of each block. <a href="#fnref2" class="footnoteBackLink" title="Jump back to footnote 2">↩</a></p - ></li - ><li id="fn3" - ><p - >This is <em - >easier</em - > to type. Inline notes may contain <a href="http://google.com" - >links</a - > and <code - >]</code - > verbatim characters, as well as [bracketed text]. <a href="#fnref3" class="footnoteBackLink" title="Jump back to footnote 3">↩</a></p - ></li - ><li id="fn4" - ><p - >In quote. <a href="#fnref4" class="footnoteBackLink" title="Jump back to footnote 4">↩</a></p - ></li - ><li id="fn5" - ><p - >In list. <a href="#fnref5" class="footnoteBackLink" title="Jump back to footnote 5">↩</a></p - ></li - ></ol - ></div - ></body - ></html + ></pre + ><p + >If you want, you can indent every line, but you can also be lazy and just indent the first line of each block. <a href="#fnref2" class="footnoteBackLink" title="Jump back to footnote 2">↩</a></p + ></li + ><li id="fn3" + ><p + >This is <em + >easier</em + > to type. Inline notes may contain <a href="http://google.com" + >links</a + > and <code + >]</code + > verbatim characters, as well as [bracketed text]. <a href="#fnref3" class="footnoteBackLink" title="Jump back to footnote 3">↩</a></p + ></li + ><li id="fn4" + ><p + >In quote. <a href="#fnref4" class="footnoteBackLink" title="Jump back to footnote 4">↩</a></p + ></li + ><li id="fn5" + ><p + >In list. <a href="#fnref5" class="footnoteBackLink" title="Jump back to footnote 5">↩</a></p + ></li + ></ol + ></div > +</body> +</html> |