summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Text/Pandoc/Shared.hs87
-rw-r--r--src/Text/Pandoc/Writers/Docbook.hs2
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs144
-rw-r--r--src/Text/Pandoc/Writers/Markdown.hs2
-rw-r--r--src/Text/Pandoc/Writers/RTF.hs2
-rw-r--r--tests/s5.basic.html14
-rw-r--r--tests/s5.fancy.html14
-rw-r--r--tests/s5.fragment.html80
-rw-r--r--tests/s5.inserts.html80
-rw-r--r--tests/writer.html1894
10 files changed, 1190 insertions, 1129 deletions
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index 13eab9bdb..82ae08601 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE CPP #-}
+{-# LANGUAGE CPP, DeriveDataTypeable #-}
{-
Copyright (C) 2006-8 John MacFarlane <jgm@berkeley.edu>
@@ -112,13 +112,16 @@ import Text.ParserCombinators.Parsec
import Text.PrettyPrint.HughesPJ ( Doc, fsep, ($$), (<>), empty, isEmpty, text, nest )
import qualified Text.PrettyPrint.HughesPJ as PP
import Text.Pandoc.CharacterReferences ( characterReference )
-import Data.Char ( toLower, toUpper, ord, isLower, isUpper )
+import Data.Char ( toLower, toUpper, ord, isLower, isUpper, isAlpha,
+ isPunctuation )
import Data.List ( find, isPrefixOf, intercalate )
-import Control.Monad ( join )
import Network.URI ( parseURI, URI (..), isAllowedInURI )
import System.Directory
import Prelude hiding ( putStrLn, writeFile, readFile, getContents )
import System.IO.UTF8
+import Data.Generics
+import qualified Control.Monad.State as S
+import Control.Monad (join)
--
-- List processing
@@ -878,22 +881,74 @@ endsWithPlain blocks =
-- | Data structure for defining hierarchical Pandoc documents
data Element = Blk Block
- | Sec [Inline] [Element] deriving (Eq, Read, Show)
-
--- | Returns @True@ on Header block with at least the specified level
-headerAtLeast :: Int -> Block -> Bool
-headerAtLeast level (Header x _) = x <= level
-headerAtLeast _ _ = False
+ | Sec Int String [Inline] [Element]
+ -- lvl ident label contents
+ deriving (Eq, Read, Show, Typeable, Data)
+
+-- | Convert Pandoc inline list to plain text identifier.
+inlineListToIdentifier :: [Inline] -> String
+inlineListToIdentifier = dropWhile (not . isAlpha) . inlineListToIdentifier'
+
+inlineListToIdentifier' :: [Inline] -> [Char]
+inlineListToIdentifier' [] = ""
+inlineListToIdentifier' (x:xs) =
+ xAsText ++ inlineListToIdentifier' xs
+ where xAsText = case x of
+ Str s -> filter (\c -> c == '-' || not (isPunctuation c)) $
+ intercalate "-" $ words $ map toLower s
+ Emph lst -> inlineListToIdentifier' lst
+ Strikeout lst -> inlineListToIdentifier' lst
+ Superscript lst -> inlineListToIdentifier' lst
+ SmallCaps lst -> inlineListToIdentifier' lst
+ Subscript lst -> inlineListToIdentifier' lst
+ Strong lst -> inlineListToIdentifier' lst
+ Quoted _ lst -> inlineListToIdentifier' lst
+ Cite _ lst -> inlineListToIdentifier' lst
+ Code s -> s
+ Space -> "-"
+ EmDash -> "-"
+ EnDash -> "-"
+ Apostrophe -> ""
+ Ellipses -> ""
+ LineBreak -> "-"
+ Math _ _ -> ""
+ TeX _ -> ""
+ HtmlInline _ -> ""
+ Link lst _ -> inlineListToIdentifier' lst
+ Image lst _ -> inlineListToIdentifier' lst
+ Note _ -> ""
-- | Convert list of Pandoc blocks into (hierarchical) list of Elements
hierarchicalize :: [Block] -> [Element]
-hierarchicalize [] = []
-hierarchicalize (block:rest) =
- case block of
- (Header level title) ->
- let (thisSection, rest') = break (headerAtLeast level) rest
- in (Sec title (hierarchicalize thisSection)):(hierarchicalize rest')
- x -> (Blk x):(hierarchicalize rest)
+hierarchicalize blocks = S.evalState (hierarchicalizeWithIds blocks) []
+
+hierarchicalizeWithIds :: [Block] -> S.State [String] [Element]
+hierarchicalizeWithIds [] = return []
+hierarchicalizeWithIds ((Header level title'):xs) = do
+ usedIdents <- S.get
+ let ident = uniqueIdent title' usedIdents
+ S.modify (ident :)
+ let (sectionContents, rest) = break (headerLtEq level) xs
+ sectionContents' <- hierarchicalizeWithIds sectionContents
+ rest' <- hierarchicalizeWithIds rest
+ return $ Sec level ident title' sectionContents' : rest'
+hierarchicalizeWithIds (x:rest) = do
+ rest' <- hierarchicalizeWithIds rest
+ return $ (Blk x) : rest'
+
+headerLtEq :: Int -> Block -> Bool
+headerLtEq level (Header l _) = l <= level
+headerLtEq _ _ = False
+
+uniqueIdent :: [Inline] -> [String] -> String
+uniqueIdent title' usedIdents =
+ let baseIdent = inlineListToIdentifier title'
+ numIdent n = baseIdent ++ "-" ++ show n
+ in if baseIdent `elem` usedIdents
+ then case find (\x -> numIdent x `notElem` usedIdents) ([1..60000] :: [Int]) of
+ Just x -> numIdent x
+ Nothing -> baseIdent -- if we have more than 60,000, allow repeats
+ else baseIdent
-- | True if block is a Header block.
isHeaderBlock :: Block -> Bool
diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs
index 3e535a87e..eed428d23 100644
--- a/src/Text/Pandoc/Writers/Docbook.hs
+++ b/src/Text/Pandoc/Writers/Docbook.hs
@@ -80,7 +80,7 @@ writeDocbook opts (Pandoc (Meta title authors date) blocks) =
-- | Convert an Element to Docbook.
elementToDocbook :: WriterOptions -> Element -> Doc
elementToDocbook opts (Blk block) = blockToDocbook opts block
-elementToDocbook opts (Sec title elements) =
+elementToDocbook opts (Sec _ _ title elements) =
-- Docbook doesn't allow sections with no content, so insert some if needed
let elements' = if null elements
then [Blk (Para [])]
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index fb7320e92..4b6ea5982 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -36,22 +36,21 @@ import Text.Pandoc.Shared
import Text.Pandoc.Readers.TeXMath
import Text.Pandoc.Highlighting ( highlightHtml, defaultHighlightingCss )
import Numeric ( showHex )
-import Data.Char ( ord, toLower, isAlpha )
+import Data.Char ( ord, toLower )
import Data.List ( isPrefixOf, 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
- , stIds :: [String] -- ^ List of header identifiers
, stMath :: Bool -- ^ Math is used in document
, stCSS :: S.Set String -- ^ CSS to include in header
} deriving Show
defaultWriterState :: WriterState
-defaultWriterState = WriterState {stNotes= [], stIds = [],
- stMath = False, stCSS = S.empty}
+defaultWriterState = WriterState {stNotes= [], stMath = False, stCSS = S.empty}
-- Helpers to render HTML with the appropriate function.
@@ -107,15 +106,13 @@ writeHtml opts (Pandoc (Meta tit authors date) blocks) =
not (writerS5 opts)
then h1 ! [theclass "title"] $ topTitle
else noHtml
- headerBlocks = filter isHeaderBlock blocks
- ids = uniqueIdentifiers $
- map (\(Header _ lst) -> lst) headerBlocks
+ sects = hierarchicalize blocks
toc = if writerTableOfContents opts
- then tableOfContents opts headerBlocks ids
+ then evalState (tableOfContents opts sects) defaultWriterState
else noHtml
- (blocks', newstate) =
- runState (blockListToHtml opts blocks)
- (defaultWriterState {stIds = ids})
+ (blocks', newstate) = runState
+ (mapM (elementToHtml opts) sects >>= return . toHtmlFromList)
+ defaultWriterState
cssLines = stCSS newstate
css = if S.null cssLines
then noHtml
@@ -146,35 +143,36 @@ writeHtml opts (Pandoc (Meta tit authors date) blocks) =
then head' +++ body thebody
else thebody
--- | Construct table of contents from list of header blocks and identifiers.
--- Assumes there are as many identifiers as header blocks.
-tableOfContents :: WriterOptions -> [Block] -> [String] -> Html
-tableOfContents _ [] _ = noHtml
-tableOfContents opts headers ids =
+-- | Construct table of contents from list of elements.
+tableOfContents :: WriterOptions -> [Element] -> State WriterState Html
+tableOfContents _ [] = return noHtml
+tableOfContents opts sects = do
let opts' = opts { writerIgnoreNotes = True }
- contentsTree = hierarchicalize headers
- contents = evalState (mapM (elementToListItem opts') contentsTree)
- (defaultWriterState {stIds = ids})
- in thediv ! [identifier "toc"] $ unordList contents
+ contents <- mapM (elementToListItem opts') sects
+ return $ thediv ! [identifier "TOC"] $ unordList $ catMaybes contents
-- | Converts an Element to a list item for a table of contents,
-- retrieving the appropriate identifier from state.
-elementToListItem :: WriterOptions -> Element -> State WriterState Html
-elementToListItem _ (Blk _) = return noHtml
-elementToListItem opts (Sec headerText subsecs) = do
- st <- get
- let ids = stIds st
- let (id', rest) = if null ids
- then ("", [])
- else (head ids, tail ids)
- put $ st {stIds = rest}
+elementToListItem :: WriterOptions -> Element -> State WriterState (Maybe Html)
+elementToListItem _ (Blk _) = return Nothing
+elementToListItem opts (Sec _ id' headerText subsecs) = do
txt <- inlineListToHtml opts headerText
- subHeads <- mapM (elementToListItem opts) subsecs
+ subHeads <- mapM (elementToListItem opts) subsecs >>= return . catMaybes
let subList = if null subHeads
then noHtml
- else unordList subHeads
- return $ (anchor ! [href ("#" ++ id'), identifier ("TOC-" ++ id')] $ txt) +++
- subList
+ else unordList subHeads
+ return $ Just $ (anchor ! [href ("#" ++ id')] $ txt) +++ subList
+
+-- | Convert an Element to Html.
+elementToHtml :: WriterOptions -> Element -> State WriterState Html
+elementToHtml opts (Blk block) = blockToHtml opts block
+elementToHtml opts (Sec level id' title' elements) = do
+ innerContents <- mapM (elementToHtml opts) elements
+ header' <- blockToHtml opts (Header level title')
+ return $ if writerS5 opts || (writerStrictMarkdown opts && not (writerTableOfContents opts))
+ -- S5 gets confused by the extra divs around sections
+ then toHtmlFromList (header' : innerContents)
+ else thediv ! [identifier id'] << (header' : innerContents)
-- | Convert list of Note blocks to a footnote <div>.
-- Assumes notes are sorted.
@@ -236,15 +234,6 @@ obfuscateChar char =
obfuscateString :: String -> String
obfuscateString = concatMap obfuscateChar . decodeCharacterReferences
--- | True if character is a punctuation character (unicode).
-isPunctuation :: Char -> Bool
-isPunctuation c =
- let c' = ord c
- in if c `elem` "!\"'()*,-./:;<>?[\\]`{|}~" || c' >= 0x2000 && c' <= 0x206F ||
- c' >= 0xE000 && c' <= 0xE0FF
- then True
- else False
-
-- | Add CSS for document header.
addToCSS :: String -> State WriterState ()
addToCSS item = do
@@ -252,50 +241,6 @@ addToCSS item = do
let current = stCSS st
put $ st {stCSS = S.insert item current}
--- | Convert Pandoc inline list to plain text identifier.
-inlineListToIdentifier :: [Inline] -> String
-inlineListToIdentifier = dropWhile (not . isAlpha) . inlineListToIdentifier'
-
-inlineListToIdentifier' :: [Inline] -> [Char]
-inlineListToIdentifier' [] = ""
-inlineListToIdentifier' (x:xs) =
- xAsText ++ inlineListToIdentifier' xs
- where xAsText = case x of
- Str s -> filter (\c -> c == '-' || not (isPunctuation c)) $
- intercalate "-" $ words $ map toLower s
- Emph lst -> inlineListToIdentifier' lst
- Strikeout lst -> inlineListToIdentifier' lst
- Superscript lst -> inlineListToIdentifier' lst
- SmallCaps lst -> inlineListToIdentifier' lst
- Subscript lst -> inlineListToIdentifier' lst
- Strong lst -> inlineListToIdentifier' lst
- Quoted _ lst -> inlineListToIdentifier' lst
- Cite _ lst -> inlineListToIdentifier' lst
- Code s -> s
- Space -> "-"
- EmDash -> "-"
- EnDash -> "-"
- Apostrophe -> ""
- Ellipses -> ""
- LineBreak -> "-"
- Math _ _ -> ""
- TeX _ -> ""
- HtmlInline _ -> ""
- Link lst _ -> inlineListToIdentifier' lst
- Image lst _ -> inlineListToIdentifier' lst
- Note _ -> ""
-
--- | Return unique identifiers for list of inline lists.
-uniqueIdentifiers :: [[Inline]] -> [String]
-uniqueIdentifiers ls =
- let addIdentifier (nonuniqueIds, uniqueIds) l =
- let new = inlineListToIdentifier l
- matches = length $ filter (== new) nonuniqueIds
- new' = (if null new then "section" else new) ++
- if matches > 0 then ("-" ++ show matches) else ""
- in (new:nonuniqueIds, new':uniqueIds)
- in reverse $ snd $ foldl addIdentifier ([],[]) ls
-
-- | Convert Pandoc block element to HTML.
blockToHtml :: WriterOptions -> Block -> State WriterState Html
blockToHtml _ Null = return $ noHtml
@@ -335,26 +280,17 @@ blockToHtml opts (BlockQuote blocks) =
else blockListToHtml opts blocks >>= (return . blockquote)
blockToHtml opts (Header level lst) = do
contents <- inlineListToHtml opts lst
- st <- get
- let ids = stIds st
- let (id', rest) = if null ids
- then ("", [])
- else (head ids, tail ids)
- put $ st {stIds = rest}
- let attribs = if writerStrictMarkdown opts && not (writerTableOfContents opts)
- then []
- else [identifier id']
let contents' = if writerTableOfContents opts
- then anchor ! [href ("#TOC-" ++ id')] $ contents
+ then anchor ! [href "#TOC"] $ contents
else contents
return $ case level of
- 1 -> h1 contents' ! attribs
- 2 -> h2 contents' ! attribs
- 3 -> h3 contents' ! attribs
- 4 -> h4 contents' ! attribs
- 5 -> h5 contents' ! attribs
- 6 -> h6 contents' ! attribs
- _ -> paragraph contents' ! attribs
+ 1 -> h1 contents'
+ 2 -> h2 contents'
+ 3 -> h3 contents'
+ 4 -> h4 contents'
+ 5 -> h5 contents'
+ 6 -> h6 contents'
+ _ -> paragraph contents'
blockToHtml opts (BulletList lst) = do
contents <- mapM (blockListToHtml opts) lst
let attribs = if writerIncremental opts
@@ -492,7 +428,7 @@ inlineToHtml opts inline =
return $ primHtml $ "<EQ>" ++ str ++ "</EQ>"
PlainMath ->
inlineListToHtml opts (readTeXMath str) >>=
- return . (thespan ! [theclass "math"]))
+ return . (thespan ! [theclass "math"]) )
(TeX str) -> case writerHTMLMathMethod opts of
LaTeXMathML _ -> do modify (\st -> st {stMath = True})
return $ primHtml str
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index bebb88a76..f376ac0c6 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -138,7 +138,7 @@ tableOfContents opts headers =
-- | Converts an Element to a list item for a table of contents,
elementToListItem :: Element -> [Block]
elementToListItem (Blk _) = []
-elementToListItem (Sec headerText subsecs) = [Plain headerText] ++
+elementToListItem (Sec _ _ headerText subsecs) = [Plain headerText] ++
if null subsecs
then []
else [BulletList $ map elementToListItem subsecs]
diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs
index fc6cd1bf0..62d8c4a0c 100644
--- a/src/Text/Pandoc/Writers/RTF.hs
+++ b/src/Text/Pandoc/Writers/RTF.hs
@@ -59,7 +59,7 @@ tableOfContents headers =
elementToListItem :: Element -> [Block]
elementToListItem (Blk _) = []
-elementToListItem (Sec sectext subsecs) = [Plain sectext] ++
+elementToListItem (Sec _ _ sectext subsecs) = [Plain sectext] ++
if null subsecs
then []
else [BulletList (map elementToListItem subsecs)]
diff --git a/tests/s5.basic.html b/tests/s5.basic.html
index 44dee9d8e..bb2b25ae3 100644
--- a/tests/s5.basic.html
+++ b/tests/s5.basic.html
@@ -276,24 +276,24 @@ window.onload=startup;window.onresize=function(){setTimeout('fontScale()',50);}
<div id="currentSlide"></div>
<div id="header"></div>
<div id="footer">
-<h1 id="july-15-2006"
+<h1
>July 15, 2006</h1
- ><h2 id="my-s5-document"
+ ><h2
>My S5 Document</h2
></div>
</div>
<div class="presentation">
<div class="slide">
-<h1 id="my-s5-document-1"
+<h1
>My S5 Document</h1
- ><h3 id="sam-smith-jen-jones"
+ ><h3
>Sam Smith, Jen Jones</h3
- ><h4 id="july-15-2006-1"
+ ><h4
>July 15, 2006</h4
></div>
<div class="slide">
-<h1 id="first-slide"
+<h1
>First slide</h1
><ul
><li
@@ -303,7 +303,7 @@ window.onload=startup;window.onresize=function(){setTimeout('fontScale()',50);}
></ul
></div>
<div class="slide">
-<h1 id="math"
+<h1
>Math</h1
><ul
><li
diff --git a/tests/s5.fancy.html b/tests/s5.fancy.html
index 01f5c9e7f..9b82feb35 100644
--- a/tests/s5.fancy.html
+++ b/tests/s5.fancy.html
@@ -484,24 +484,24 @@ window.onload=startup;window.onresize=function(){setTimeout('fontScale()',50);}
<div id="currentSlide"></div>
<div id="header"></div>
<div id="footer">
-<h1 id="july-15-2006"
+<h1
>July 15, 2006</h1
- ><h2 id="my-s5-document"
+ ><h2
>My S5 Document</h2
></div>
</div>
<div class="presentation">
<div class="slide">
-<h1 id="my-s5-document-1"
+<h1
>My S5 Document</h1
- ><h3 id="sam-smith-jen-jones"
+ ><h3
>Sam Smith, Jen Jones</h3
- ><h4 id="july-15-2006-1"
+ ><h4
>July 15, 2006</h4
></div>
<div class="slide">
-<h1 id="first-slide"
+<h1
>First slide</h1
><ul class="incremental"
><li
@@ -511,7 +511,7 @@ window.onload=startup;window.onresize=function(){setTimeout('fontScale()',50);}
></ul
></div>
<div class="slide">
-<h1 id="math"
+<h1
>Math</h1
><ul class="incremental"
><li
diff --git a/tests/s5.fragment.html b/tests/s5.fragment.html
index 0cacb4738..1d58e154a 100644
--- a/tests/s5.fragment.html
+++ b/tests/s5.fragment.html
@@ -1,41 +1,45 @@
-<h1 id="first-slide"
->First slide</h1
-><ul
-><li
- >first bullet</li
+<div id="first-slide"
+><h1
+ >First slide</h1
+ ><ul
><li
- >second bullet</li
- ></ul
-><h1 id="math"
->Math</h1
-><ul
-><li
- ><span class="math"
- >\frac{<em
- >d</em
- >}{<em
- >dx</em
- >}<em
- >f</em
- >(<em
- >x</em
- >)=\lim<sub
- ><em
- >h</em
- >&#8201;&#8594;&#8201;0</sub
+ >first bullet</li
+ ><li
+ >second bullet</li
+ ></ul
+ ></div
+><div id="math"
+><h1
+ >Math</h1
+ ><ul
+ ><li
+ ><span class="math"
>\frac{<em
- >f</em
- >(<em
- >x</em
- >+<em
- >h</em
- >)-<em
- >f</em
- >(<em
- >x</em
- >)}{<em
- >h</em
- >}</span
- ></li
- ></ul
+ >d</em
+ >}{<em
+ >dx</em
+ >}<em
+ >f</em
+ >(<em
+ >x</em
+ >)=\lim<sub
+ ><em
+ >h</em
+ >&#8201;&#8594;&#8201;0</sub
+ >\frac{<em
+ >f</em
+ >(<em
+ >x</em
+ >+<em
+ >h</em
+ >)-<em
+ >f</em
+ >(<em
+ >x</em
+ >)}{<em
+ >h</em
+ >}</span
+ ></li
+ ></ul
+ ></div
>
diff --git a/tests/s5.inserts.html b/tests/s5.inserts.html
index fc27da035..d6f0d6fbd 100644
--- a/tests/s5.inserts.html
+++ b/tests/s5.inserts.html
@@ -15,46 +15,50 @@ STUFF INSERTED
>STUFF INSERTED
<h1 class="title"
>My S5 Document</h1
- ><h1 id="first-slide"
- >First slide</h1
- ><ul
- ><li
- >first bullet</li
+ ><div id="first-slide"
+ ><h1
+ >First slide</h1
+ ><ul
><li
- >second bullet</li
- ></ul
- ><h1 id="math"
- >Math</h1
- ><ul
- ><li
- ><span class="math"
- >\frac{<em
- >d</em
- >}{<em
- >dx</em
- >}<em
- >f</em
- >(<em
- >x</em
- >)=\lim<sub
- ><em
- >h</em
- >&#8201;&#8594;&#8201;0</sub
+ >first bullet</li
+ ><li
+ >second bullet</li
+ ></ul
+ ></div
+ ><div id="math"
+ ><h1
+ >Math</h1
+ ><ul
+ ><li
+ ><span class="math"
>\frac{<em
- >f</em
- >(<em
- >x</em
- >+<em
- >h</em
- >)-<em
- >f</em
- >(<em
- >x</em
- >)}{<em
- >h</em
- >}</span
- ></li
- ></ul
+ >d</em
+ >}{<em
+ >dx</em
+ >}<em
+ >f</em
+ >(<em
+ >x</em
+ >)=\lim<sub
+ ><em
+ >h</em
+ >&#8201;&#8594;&#8201;0</sub
+ >\frac{<em
+ >f</em
+ >(<em
+ >x</em
+ >+<em
+ >h</em
+ >)-<em
+ >f</em
+ >(<em
+ >x</em
+ >)}{<em
+ >h</em
+ >}</span
+ ></li
+ ></ul
+ ></div
>STUFF INSERTED
</body
></html
diff --git a/tests/writer.html b/tests/writer.html
index d5f357423..ece782f81 100644
--- a/tests/writer.html
+++ b/tests/writer.html
@@ -15,96 +15,119 @@
><p
>This is a set of tests for pandoc. Most of them are adapted from John Gruber&rsquo;s markdown test suite.</p
><hr
- /><h1 id="headers"
- >Headers</h1
- ><h2 id="level-2-with-an-embedded-link"
- >Level 2 with an <a href="/url"
- >embedded link</a
- ></h2
- ><h3 id="level-3-with-emphasis"
- >Level 3 with <em
- >emphasis</em
- ></h3
- ><h4 id="level-4"
- >Level 4</h4
- ><h5 id="level-5"
- >Level 5</h5
- ><h1 id="level-1"
- >Level 1</h1
- ><h2 id="level-2-with-emphasis"
- >Level 2 with <em
- >emphasis</em
- ></h2
- ><h3 id="level-3"
- >Level 3</h3
- ><p
- >with no blank line</p
- ><h2 id="level-2"
- >Level 2</h2
- ><p
- >with no blank line</p
- ><hr
- /><h1 id="paragraphs"
- >Paragraphs</h1
- ><p
- >Here&rsquo;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&rsquo;s one with a bullet. * criminey.</p
- ><p
- >There should be a hard line break<br
- />here.</p
- ><hr
- /><h1 id="block-quotes"
- >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 &quot;working&quot;;
-}
-</code
- ></pre
+ /><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
+ ></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 id="paragraphs"
+ ><h1
+ >Paragraphs</h1
><p
- >A list:</p
- ><ol style="list-style-type: decimal;"
- ><li
- >item one</li
- ><li
- >item two</li
- ></ol
+ >Here&rsquo;s a regular paragraph.</p
><p
- >Nested block quotes:</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&rsquo;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
- >nested</p
+ >This is a block quote. It is pretty short.</p
></blockquote
><blockquote
><p
- >nested</p
+ >Code in a block quote:</p
+ ><pre
+ ><code
+ >sub status {
+ print &quot;working&quot;;
+}
+</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
- ></blockquote
- ><p
- >This should not be a block quote: 2 &gt; 1.</p
- ><p
- >And a following paragraph.</p
- ><hr
- /><h1 id="code-blocks"
- >Code Blocks</h1
- ><p
- >Code:</p
- ><pre
- ><code
- >---- (should be four hyphens)
+ ><p
+ >This should not be a block quote: 2 &gt; 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 &quot;working&quot;;
@@ -112,458 +135,474 @@ 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: \$ \\ \&gt; \[ \{
</code
- ></pre
- ><hr
- /><h1 id="lists"
- >Lists</h1
- ><h2 id="unordered"
- >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
- ><h2 id="ordered"
- >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
+ ></pre
+ ><hr
+ /></div
+ ><div id="lists"
+ ><h1
+ >Lists</h1
+ ><div id="unordered"
+ ><h2
+ >Unordered</h2
><p
- >Item 1. graf two. The quick brown fox jumped over the lazy dog&rsquo;s back.</p
- ></li
- ><li
- ><p
- >Item 2.</p
- ></li
- ><li
- ><p
- >Item 3.</p
- ></li
- ></ol
- ><h2 id="nested"
- >Nested</h2
- ><ul
- ><li
- >Tab<ul
+ >Asterisks tight:</p
+ ><ul
><li
- >Tab<ul
- ><li
- >Tab</li
- ></ul
+ >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
- ></li
- ></ul
- ><p
- >Here&rsquo;s another:</p
- ><ol style="list-style-type: decimal;"
- ><li
- >First</li
- ><li
- >Second:<ul
+ ><p
+ >Pluses tight:</p
+ ><ul
><li
- >Fee</li
+ >Plus 1</li
><li
- >Fie</li
+ >Plus 2</li
><li
- >Foe</li
+ >Plus 3</li
></ul
- ></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
+ ><p
+ >Pluses loose:</p
><ul
><li
- >Fee</li
+ ><p
+ >Plus 1</p
+ ></li
><li
- >Fie</li
+ ><p
+ >Plus 2</p
+ ></li
><li
- >Foe</li
+ ><p
+ >Plus 3</p
+ ></li
></ul
- ></li
- ><li
- ><p
- >Third</p
- ></li
- ></ol
- ><h2 id="tabs-and-spaces"
- >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
+ ><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
- >this is an example list item indented with tabs</p
+ >Minus 1</p
></li
><li
><p
- >this is an example list item indented with spaces</p
+ >Minus 2</p
+ ></li
+ ><li
+ ><p
+ >Minus 3</p
></li
></ul
- ></li
- ></ul
- ><h2 id="fancy-list-markers"
- >Fancy list markers</h2
- ><ol start="2" style="list-style-type: decimal;"
- ><li
- >begins with 2</li
- ><li
- ><p
- >and now 3</p
+ ></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
- >with a continuation</p
- ><ol start="4" style="list-style-type: lower-roman;"
+ >and using spaces:</p
+ ><ol style="list-style-type: decimal;"
><li
- >sublist with roman numerals, starting with 4</li
+ ><p
+ >One</p
+ ></li
><li
- >more items<ol style="list-style-type: upper-alpha;"
+ ><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&rsquo;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
- >a subsublist</li
+ >Tab<ul
+ ><li
+ >Tab</li
+ ></ul
+ ></li
+ ></ul
+ ></li
+ ></ul
+ ><p
+ >Here&rsquo;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;"
+ ><li
+ ><p
+ >First</p
+ ></li
+ ><li
+ ><p
+ >Second:</p
+ ><ul
+ ><li
+ >Fee</li
+ ><li
+ >Fie</li
><li
- >a subsublist</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
></ol
></li
></ol
- ></li
- ></ol
- ><p
- >Nesting:</p
- ><ol style="list-style-type: upper-alpha;"
- ><li
- >Upper Alpha<ol style="list-style-type: upper-roman;"
+ ><p
+ >Nesting:</p
+ ><ol style="list-style-type: upper-alpha;"
><li
- >Upper Roman.<ol start="6" style="list-style-type: decimal;"
+ >Upper Alpha<ol style="list-style-type: upper-roman;"
><li
- >Decimal start with 6<ol start="3" style="list-style-type: lower-alpha;"
+ >Upper Roman.<ol start="6" style="list-style-type: decimal;"
><li
- >Lower alpha with paren</li
+ >Decimal start with 6<ol start="3" style="list-style-type: lower-alpha;"
+ ><li
+ >Lower alpha with paren</li
+ ></ol
+ ></li
></ol
></li
></ol
></li
></ol
- ></li
- ></ol
- ><p
- >Autonumbering:</p
- ><ol
- ><li
- >Autonumber.</li
- ><li
- >More.<ol
+ ><p
+ >Autonumbering:</p
+ ><ol
><li
- >Nested.</li
+ >Autonumber.</li
+ ><li
+ >More.<ol
+ ><li
+ >Nested.</li
+ ></ol
+ ></li
></ol
- ></li
- ></ol
- ><p
- >Should not be a list item:</p
- ><p
- >M.A.&nbsp;2007</p
- ><p
- >B. Williams</p
- ><hr
- /><h1 id="definition-lists"
- >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
+ ><p
+ >Should not be a list item:</p
+ ><p
+ >M.A.&nbsp;2007</p
+ ><p
+ >B. Williams</p
+ ><hr
+ /></div
+ ></div
+ ><div id="definition-lists"
+ ><h1
+ >Definition Lists</h1
+ ><p
+ >Tight using spaces:</p
+ ><dl
><dt
- >orange</dt
- ><dd
+ >apple</dt
+ ><dd
+ >red fruit</dd
+ ><dt
+ >orange</dt
+ ><dd
+ >orange fruit</dd
+ ><dt
+ >banana</dt
+ ><dd
+ >yellow fruit</dd
+ ></dl
><p
- >orange fruit</p
- ></dd
+ >Tight using tabs:</p
+ ><dl
><dt
- >banana</dt
- ><dd
+ >apple</dt
+ ><dd
+ >red fruit</dd
+ ><dt
+ >orange</dt
+ ><dd
+ >orange fruit</dd
+ ><dt
+ >banana</dt
+ ><dd
+ >yellow fruit</dd
+ ></dl
><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
+ >Loose:</p
+ ><dl
><dt
- ><em
- >orange</em
- ></dt
- ><dd
+ >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
- >orange fruit</p
- ><pre
- ><code
- >{ orange code block }
-</code
- ></pre
- ><blockquote
+ >Multiple blocks with italics:</p
+ ><dl
+ ><dt
+ ><em
+ >apple</em
+ ></dt
+ ><dd
><p
- >orange block quote</p
- ></blockquote
- ></dd
- ></dl
- ><h1 id="html-blocks"
- >HTML Blocks</h1
- ><p
- >Simple block on one line:</p
- ><div>foo</div>
+ >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
+ ></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&rsquo;s a simple block:</p
- ><div>
+ >Here&rsquo;s a simple block:</p
+ ><div>
foo</div>
<p
- >This should be a code block, though:</p
- ><pre
- ><code
- >&lt;div&gt;
+ >This should be a code block, though:</p
+ ><pre
+ ><code
+ >&lt;div&gt;
foo
&lt;/div&gt;
</code
- ></pre
- ><p
- >As should this:</p
- ><pre
- ><code
- >&lt;div&gt;foo&lt;/div&gt;
+ ></pre
+ ><p
+ >As should this:</p
+ ><pre
+ ><code
+ >&lt;div&gt;foo&lt;/div&gt;
</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
-->
@@ -572,25 +611,25 @@ Blah
This is another comment.
-->
<p
- >Code block:</p
- ><pre
- ><code
- >&lt;!-- Comment --&gt;
+ >Code block:</p
+ ><pre
+ ><code
+ >&lt;!-- Comment --&gt;
</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
- >&lt;hr /&gt;
+ >Code:</p
+ ><pre
+ ><code
+ >&lt;hr /&gt;
</code
- ></pre
- ><p
- >Hr&rsquo;s:</p
- ><hr>
+ ></pre
+ ><p
+ >Hr&rsquo;s:</p
+ ><hr>
<hr />
@@ -608,474 +647,497 @@ Blah
<hr class="foo" id="bar">
<hr
- /><h1 id="inline-markup"
- >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
- >&gt;</code
- >, <code
- >$</code
- >, <code
- >\</code
- >, <code
- >\$</code
- >, <code
- >&lt;html&gt;</code
- >.</p
- ><p
- ><span style="text-decoration: line-through;"
+ /></div
+ ><div id="inline-markup"
+ ><h1
+ >Inline Markup</h1
+ ><p
>This is <em
- >strikeout</em
- >.</span
- ></p
- ><p
- >Superscripts: a<sup
- >bc</sup
- >d a<sup
- ><em
- >hello</em
- ></sup
- > a<sup
- >hello&nbsp;there</sup
- >.</p
- ><p
- >Subscripts: H<sub
- >2</sub
- >O, H<sub
- >23</sub
- >O, H<sub
- >many&nbsp;of&nbsp;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
- /><h1 id="smart-quotes-ellipses-dashes"
- >Smart quotes, ellipses, dashes</h1
- ><p
- >&ldquo;Hello,&rdquo; said the spider. &ldquo;&lsquo;Shelob&rsquo; is my name.&rdquo;</p
- ><p
- >&lsquo;A&rsquo;, &lsquo;B&rsquo;, and &lsquo;C&rsquo; are letters.</p
- ><p
- >&lsquo;Oak,&rsquo; &lsquo;elm,&rsquo; and &lsquo;beech&rsquo; are names of trees. So is &lsquo;pine.&rsquo;</p
- ><p
- >&lsquo;He said, &ldquo;I want to go.&rdquo;&rsquo; Were you alive in the 70&rsquo;s?</p
- ><p
- >Here is some quoted &lsquo;<code
- >code</code
- >&rsquo; and a &ldquo;<a href="http://example.com/?foo=1&amp;bar=2"
- >quoted link</a
- >&rdquo;.</p
- ><p
- >Some dashes: one&mdash;two &mdash; three&mdash;four &mdash; five.</p
- ><p
- >Dashes between numbers: 5&ndash;7, 255&ndash;66, 1987&ndash;1999.</p
- ><p
- >Ellipses&hellip;and&hellip;and&hellip;.</p
- ><hr
- /><h1 id="latex"
- >LaTeX</h1
- ><ul
- ><li
- ></li
- ><li
- ><span class="math"
- >2+2=4</span
- ></li
- ><li
- ><span class="math"
+ >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
- >x</em
- >&#8201;&#8712;&#8201;<em
- >y</em
- ></span
- ></li
- ><li
- ><span class="math"
- >&#945;&#8201;&#8743;&#8201;&#969;</span
- ></li
- ><li
- ><span class="math"
- >223</span
- ></li
- ><li
- ><span class="math"
+ >This is strong and em.</em
+ ></strong
+ ></p
+ ><p
+ >So is <strong
+ ><em
+ >this</em
+ ></strong
+ > word.</p
+ ><p
+ ><strong
><em
- >p</em
- ></span
- >-Tree</li
+ >This is strong and em.</em
+ ></strong
+ ></p
+ ><p
+ >So is <strong
+ ><em
+ >this</em
+ ></strong
+ > word.</p
+ ><p
+ >This is code: <code
+ >&gt;</code
+ >, <code
+ >$</code
+ >, <code
+ >\</code
+ >, <code
+ >\$</code
+ >, <code
+ >&lt;html&gt;</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&nbsp;there</sup
+ >.</p
+ ><p
+ >Subscripts: H<sub
+ >2</sub
+ >O, H<sub
+ >23</sub
+ >O, H<sub
+ >many&nbsp;of&nbsp;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
+ >&ldquo;Hello,&rdquo; said the spider. &ldquo;&lsquo;Shelob&rsquo; is my name.&rdquo;</p
+ ><p
+ >&lsquo;A&rsquo;, &lsquo;B&rsquo;, and &lsquo;C&rsquo; are letters.</p
+ ><p
+ >&lsquo;Oak,&rsquo; &lsquo;elm,&rsquo; and &lsquo;beech&rsquo; are names of trees. So is &lsquo;pine.&rsquo;</p
+ ><p
+ >&lsquo;He said, &ldquo;I want to go.&rdquo;&rsquo; Were you alive in the 70&rsquo;s?</p
+ ><p
+ >Here is some quoted &lsquo;<code
+ >code</code
+ >&rsquo; and a &ldquo;<a href="http://example.com/?foo=1&amp;bar=2"
+ >quoted link</a
+ >&rdquo;.</p
+ ><p
+ >Some dashes: one&mdash;two &mdash; three&mdash;four &mdash; five.</p
+ ><p
+ >Dashes between numbers: 5&ndash;7, 255&ndash;66, 1987&ndash;1999.</p
+ ><p
+ >Ellipses&hellip;and&hellip;and&hellip;.</p
+ ><hr
+ /></div
+ ><div id="latex"
+ ><h1
+ >LaTeX</h1
+ ><ul
><li
- >Here&rsquo;s some display math: <span class="math"
- >\frac{<em
- >d</em
- >}{<em
- >dx</em
- >}<em
- >f</em
- >(<em
- >x</em
- >)=\lim<sub
+ ></li
+ ><li
+ ><span class="math"
+ >2+2=4</span
+ ></li
+ ><li
+ ><span class="math"
><em
- >h</em
- >&#8201;&#8594;&#8201;0</sub
+ >x</em
+ >&#8201;&#8712;&#8201;<em
+ >y</em
+ ></span
+ ></li
+ ><li
+ ><span class="math"
+ >&#945;&#8201;&#8743;&#8201;&#969;</span
+ ></li
+ ><li
+ ><span class="math"
+ >223</span
+ ></li
+ ><li
+ ><span class="math"
+ ><em
+ >p</em
+ ></span
+ >-Tree</li
+ ><li
+ >Here&rsquo;s some display math: <span class="math"
>\frac{<em
- >f</em
- >(<em
- >x</em
- >+<em
- >h</em
- >)-<em
- >f</em
- >(<em
- >x</em
- >)}{<em
- >h</em
- >}</span
- ></li
- ><li
- >Here&rsquo;s one that has a line break in it: <span class="math"
- >&#945;+&#969;&#8201;×&#8201;<em
- >x</em
- ><sup
- >2</sup
- ></span
- >.</li
- ></ul
- ><p
- >These shouldn&rsquo;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 &ldquo;lot&rdquo; 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&rsquo;s a LaTeX table:</p
- ><p
- ></p
- ><hr
- /><h1 id="special-characters"
- >Special Characters</h1
- ><p
- >Here is some unicode:</p
- ><ul
- ><li
- >I hat: Î</li
- ><li
- >o umlaut: ö</li
- ><li
- >section: §</li
- ><li
- >set membership: &#8712;</li
+ >d</em
+ >}{<em
+ >dx</em
+ >}<em
+ >f</em
+ >(<em
+ >x</em
+ >)=\lim<sub
+ ><em
+ >h</em
+ >&#8201;&#8594;&#8201;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&rsquo;s one that has a line break in it: <span class="math"
+ >&#945;+&#969;&#8201;×&#8201;<em
+ >x</em
+ ><sup
+ >2</sup
+ ></span
+ >.</li
+ ></ul
+ ><p
+ >These shouldn&rsquo;t be math:</p
+ ><ul
><li
- >copyright: ©</li
- ></ul
- ><p
- >AT&amp;T has an ampersand in their name.</p
- ><p
- >AT&amp;T is another way to write it.</p
- ><p
- >This &amp; that.</p
- ><p
- >4 &lt; 5.</p
- ><p
- >6 &gt; 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: &gt;</p
- ><p
- >Hash: #</p
- ><p
- >Period: .</p
- ><p
- >Bang: !</p
- ><p
- >Plus: +</p
- ><p
- >Minus: -</p
- ><hr
- /><h1 id="links"
- >Links</h1
- ><h2 id="explicit"
- >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 &quot;quotes&quot; 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
+ >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 &ldquo;lot&rdquo; 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&rsquo;s a LaTeX table:</p
+ ><p
></p
- ><p
- ><script type="text/javascript"
- >
+ ><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: &#8712;</li
+ ><li
+ >copyright: ©</li
+ ></ul
+ ><p
+ >AT&amp;T has an ampersand in their name.</p
+ ><p
+ >AT&amp;T is another way to write it.</p
+ ><p
+ >This &amp; that.</p
+ ><p
+ >4 &lt; 5.</p
+ ><p
+ >6 &gt; 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: &gt;</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 &quot;quotes&quot; 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"
+ >
<!--
h='&#110;&#x6f;&#x77;&#104;&#x65;&#114;&#x65;&#46;&#110;&#x65;&#116;';a='&#64;';n='&#110;&#x6f;&#98;&#x6f;&#100;&#x79;';e=n+a+h;
document.write('<a h'+'ref'+'="ma'+'ilto'+':'+e+'">'+'Email link'+'<\/'+'a'+'>');
// -->
</script
- ><noscript
- >&#x45;&#x6d;&#x61;&#x69;&#108;&#32;&#108;&#x69;&#110;&#x6b;&#32;&#40;&#110;&#x6f;&#98;&#x6f;&#100;&#x79;&#32;&#x61;&#116;&#32;&#110;&#x6f;&#x77;&#104;&#x65;&#114;&#x65;&#32;&#100;&#x6f;&#116;&#32;&#110;&#x65;&#116;&#x29;</noscript
- ></p
- ><p
- ><a href=""
- >Empty</a
- >.</p
- ><h2 id="reference"
- >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 &quot;quotes&quot; inside"
- >bar</a
- >.</p
- ><p
- >Foo <a href="/url/" title="Title with &quot;quote&quot; inside"
- >biz</a
- >.</p
- ><h2 id="with-ampersands"
- >With ampersands</h2
- ><p
- >Here&rsquo;s a <a href="http://example.com/?foo=1&amp;bar=2"
- >link with an ampersand in the URL</a
- >.</p
- ><p
- >Here&rsquo;s a link with an amersand in the link text: <a href="http://att.com/" title="AT&amp;T"
- >AT&amp;T</a
- >.</p
- ><p
- >Here&rsquo;s an <a href="/script?foo=1&amp;bar=2"
- >inline link</a
- >.</p
- ><p
- >Here&rsquo;s an <a href="/script?foo=1&amp;bar=2"
- >inline link in pointy braces</a
- >.</p
- ><h2 id="autolinks"
- >Autolinks</h2
- ><p
- >With an ampersand: <a href="http://example.com/?foo=1&amp;bar=2"
- ><code
- >http://example.com/?foo=1&amp;bar=2</code
- ></a
- ></p
- ><ul
- ><li
- >In a list?</li
- ><li
- ><a href="http://example.com/"
+ ><noscript
+ >&#x45;&#x6d;&#x61;&#x69;&#108;&#32;&#108;&#x69;&#110;&#x6b;&#32;&#40;&#110;&#x6f;&#98;&#x6f;&#100;&#x79;&#32;&#x61;&#116;&#32;&#110;&#x6f;&#x77;&#104;&#x65;&#114;&#x65;&#32;&#100;&#x6f;&#116;&#32;&#110;&#x65;&#116;&#x29;</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
- >http://example.com/</code
- ></a
- ></li
- ><li
- >It should.</li
- ></ul
- ><p
- >An e-mail address: <script type="text/javascript"
- >
+ >[not]: /url
+</code
+ ></pre
+ ><p
+ >Foo <a href="/url/" title="Title with &quot;quotes&quot; inside"
+ >bar</a
+ >.</p
+ ><p
+ >Foo <a href="/url/" title="Title with &quot;quote&quot; inside"
+ >biz</a
+ >.</p
+ ></div
+ ><div id="with-ampersands"
+ ><h2
+ >With ampersands</h2
+ ><p
+ >Here&rsquo;s a <a href="http://example.com/?foo=1&amp;bar=2"
+ >link with an ampersand in the URL</a
+ >.</p
+ ><p
+ >Here&rsquo;s a link with an amersand in the link text: <a href="http://att.com/" title="AT&amp;T"
+ >AT&amp;T</a
+ >.</p
+ ><p
+ >Here&rsquo;s an <a href="/script?foo=1&amp;bar=2"
+ >inline link</a
+ >.</p
+ ><p
+ >Here&rsquo;s an <a href="/script?foo=1&amp;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&amp;bar=2"
+ ><code
+ >http://example.com/?foo=1&amp;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='&#110;&#x6f;&#x77;&#104;&#x65;&#114;&#x65;&#46;&#110;&#x65;&#116;';a='&#64;';n='&#110;&#x6f;&#98;&#x6f;&#100;&#x79;';e=n+a+h;
document.write('<a h'+'ref'+'="ma'+'ilto'+':'+e+'">'+'<code>'+e+'</code>'+'<\/'+'a'+'>');
// -->
</script
- ><noscript
- >&#110;&#x6f;&#98;&#x6f;&#100;&#x79;&#32;&#x61;&#116;&#32;&#110;&#x6f;&#x77;&#104;&#x65;&#114;&#x65;&#32;&#100;&#x6f;&#116;&#32;&#110;&#x65;&#116;</noscript
- ></p
- ><blockquote
- ><p
- >Blockquoted: <a href="http://example.com/"
+ ><noscript
+ >&#110;&#x6f;&#98;&#x6f;&#100;&#x79;&#32;&#x61;&#116;&#32;&#110;&#x6f;&#x77;&#104;&#x65;&#114;&#x65;&#32;&#100;&#x6f;&#116;&#32;&#110;&#x65;&#116;</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
+ >&lt;http://example.com/&gt;</code
+ ></p
+ ><pre
><code
- >http://example.com/</code
- ></a
- ></p
- ></blockquote
- ><p
- >Auto-links should not occur here: <code
- >&lt;http://example.com/&gt;</code
- ></p
- ><pre
- ><code
- >or here: &lt;http://example.com/&gt;
+ >or here: &lt;http://example.com/&gt;
</code
- ></pre
- ><hr
- /><h1 id="images"
- >Images</h1
- ><p
- >From &ldquo;Voyage dans la Lune&rdquo; 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
- /><h1 id="footnotes"
- >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"
+ ></pre
+ ><hr
+ /></div
+ ></div
+ ><div id="images"
+ ><h1
+ >Images</h1
+ ><p
+ >From &ldquo;Voyage dans la Lune&rdquo; 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
- >4</sup
+ >1</sup
></a
- ></p
- ></blockquote
- ><ol style="list-style-type: decimal;"
- ><li
- >And in list items.<a href="#fn5" class="footnoteRef" id="fnref5"
+ > and another.<a href="#fn2" class="footnoteRef" id="fnref2"
><sup
- >5</sup
+ >2</sup
></a
- ></li
- ></ol
- ><p
- >This paragraph should not be part of the note, as it is not indented.</p
+ > 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