summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--pandoc.cabal4
-rw-r--r--src/Text/Pandoc/Parsing.hs2
-rw-r--r--src/Text/Pandoc/Readers/HTML.hs8
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs10
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs5
-rw-r--r--src/Text/Pandoc/Readers/RST.hs3
-rw-r--r--src/Text/Pandoc/Readers/TeXMath.hs2
-rw-r--r--src/Text/Pandoc/Readers/Textile.hs4
-rw-r--r--src/Text/Pandoc/Shared.hs8
-rw-r--r--src/Text/Pandoc/Writers/ConTeXt.hs6
-rw-r--r--src/Text/Pandoc/Writers/Docbook.hs10
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs17
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs6
-rw-r--r--src/Text/Pandoc/Writers/Man.hs9
-rw-r--r--src/Text/Pandoc/Writers/Markdown.hs48
-rw-r--r--src/Text/Pandoc/Writers/MediaWiki.hs14
-rw-r--r--src/Text/Pandoc/Writers/OpenDocument.hs2
-rw-r--r--src/Text/Pandoc/Writers/Org.hs4
-rw-r--r--src/Text/Pandoc/Writers/RST.hs6
-rw-r--r--src/Text/Pandoc/Writers/RTF.hs2
-rw-r--r--src/Text/Pandoc/Writers/Texinfo.hs4
-rw-r--r--src/Text/Pandoc/Writers/Textile.hs6
-rw-r--r--tests/Tests/Arbitrary.hs2
-rw-r--r--tests/html-reader.native10
-rw-r--r--tests/latex-reader.native20
-rw-r--r--tests/lhs-test.fragment.html+lhs3
-rw-r--r--tests/lhs-test.html3
-rw-r--r--tests/lhs-test.html+lhs3
-rw-r--r--tests/lhs-test.native4
-rw-r--r--tests/markdown-reader-more.native10
-rw-r--r--tests/rst-reader.native2
-rw-r--r--tests/testsuite.native20
-rw-r--r--tests/textile-reader.native2
-rw-r--r--tests/writer.html6
-rw-r--r--tests/writer.native20
35 files changed, 152 insertions, 133 deletions
diff --git a/pandoc.cabal b/pandoc.cabal
index e35c2e638..739dc046f 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -211,7 +211,7 @@ Library
else
Build-depends: base >= 3 && < 4
if flag(highlighting)
- Build-depends: highlighting-kate >= 0.2.7.1 && < 0.2.9
+ Build-depends: highlighting-kate >= 0.2.8.2 && < 0.2.9
cpp-options: -D_HIGHLIGHTING
if impl(ghc >= 6.12)
Ghc-Options: -O2 -Wall -fno-warn-unused-do-bind
@@ -295,7 +295,7 @@ Executable pandoc
else
Build-depends: base >= 3 && < 4
if flag(highlighting)
- Build-depends: highlighting-kate >= 0.2.7.1 && < 0.2.9
+ Build-depends: highlighting-kate >= 0.2.8.2 && < 0.2.9
cpp-options: -D_HIGHLIGHTING
if impl(ghc >= 6.12)
Ghc-Options: -O2 -Wall -fno-warn-unused-do-bind
diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs
index 4a2671157..9ce064f91 100644
--- a/src/Text/Pandoc/Parsing.hs
+++ b/src/Text/Pandoc/Parsing.hs
@@ -664,7 +664,7 @@ toKey = Key . bottomUp lowercase
where lowercase :: Inline -> Inline
lowercase (Str xs) = Str (map toLower xs)
lowercase (Math t xs) = Math t (map toLower xs)
- lowercase (Code xs) = Code (map toLower xs)
+ lowercase (Code attr xs) = Code attr (map toLower xs)
lowercase (RawInline f xs) = RawInline f (map toLower xs)
lowercase LineBreak = Space
lowercase x = x
diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs
index d267a4ff2..18e3113d3 100644
--- a/src/Text/Pandoc/Readers/HTML.hs
+++ b/src/Text/Pandoc/Readers/HTML.hs
@@ -338,9 +338,13 @@ pImage = do
pCode :: TagParser [Inline]
pCode = try $ do
- (TagOpen open _) <- pSatisfy $ tagOpen (`elem` ["code","tt"]) (const True)
+ (TagOpen open attr) <- pSatisfy $ tagOpen (`elem` ["code","tt"]) (const True)
result <- manyTill pAnyTag (pCloses open)
- return [Code $ intercalate " " $ lines $ innerText result]
+ let ident = fromMaybe "" $ lookup "id" attr
+ let classes = words $ fromMaybe [] $ lookup "class" attr
+ let rest = filter (\(x,_) -> x /= "id" && x /= "class") attr
+ return [Code (ident,classes,rest)
+ $ intercalate " " $ lines $ innerText result]
pRawHtmlInline :: TagParser [Inline]
pRawHtmlInline = do
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index d20acac92..83b74a489 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -710,27 +710,27 @@ code1 = try $ do
string "\\verb"
marker <- anyChar
result <- manyTill anyChar (char marker)
- return $ Code $ removeLeadingTrailingSpace result
+ return $ Code nullAttr $ removeLeadingTrailingSpace result
code2 :: GenParser Char st Inline
code2 = try $ do
string "\\texttt{"
result <- manyTill (noneOf "\\\n~$%^&{}") (char '}')
- return $ Code result
+ return $ Code nullAttr result
code3 :: GenParser Char st Inline
code3 = try $ do
string "\\lstinline"
marker <- anyChar
result <- manyTill anyChar (char marker)
- return $ Code $ removeLeadingTrailingSpace result
+ return $ Code nullAttr $ removeLeadingTrailingSpace result
lhsInlineCode :: GenParser Char ParserState Inline
lhsInlineCode = try $ do
failUnlessLHS
char '|'
result <- manyTill (noneOf "|\n") (char '|')
- return $ Code result
+ return $ Code ("",["haskell"],[]) result
emph :: GenParser Char ParserState Inline
emph = try $ oneOfStrings [ "\\emph{", "\\textit{" ] >>
@@ -861,7 +861,7 @@ url :: GenParser Char ParserState Inline
url = try $ do
string "\\url"
url' <- charsInBalanced '{' '}'
- return $ Link [Code url'] (escapeURI url', "")
+ return $ Link [Code ("",["url"],[]) url'] (escapeURI url', "")
link :: GenParser Char ParserState Inline
link = try $ do
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index ed04ee034..1b9094ab9 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -977,7 +977,8 @@ code = try $ do
(char '\n' >> notFollowedBy' blankline >> return " "))
(try (skipSpaces >> count (length starts) (char '`') >>
notFollowedBy (char '`')))
- return $ Code $ removeLeadingTrailingSpace $ concat result
+ attr <- option ([],[],[]) (try $ optional whitespace >> attributes)
+ return $ Code attr $ removeLeadingTrailingSpace $ concat result
mathWord :: GenParser Char st [Char]
mathWord = liftM concat $ many1 mathChunk
@@ -1163,7 +1164,7 @@ autoLink = try $ do
st <- getState
return $ if stateStrict st
then Link [Str orig] (src, "")
- else Link [Code orig] (src, "")
+ else Link [Code ("",["url"],[]) orig] (src, "")
image :: GenParser Char ParserState Inline
image = try $ do
diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs
index 16ae384d1..582766d38 100644
--- a/src/Text/Pandoc/Readers/RST.hs
+++ b/src/Text/Pandoc/Readers/RST.hs
@@ -746,7 +746,8 @@ code :: GenParser Char ParserState Inline
code = try $ do
string "``"
result <- manyTill anyChar (try (string "``"))
- return $ Code $ removeLeadingTrailingSpace $ intercalate " " $ lines result
+ return $ Code nullAttr
+ $ removeLeadingTrailingSpace $ intercalate " " $ lines result
emph :: GenParser Char ParserState Inline
emph = enclosed (char '*') (char '*') inline >>=
diff --git a/src/Text/Pandoc/Readers/TeXMath.hs b/src/Text/Pandoc/Readers/TeXMath.hs
index 8c9fe2c7e..b9a46e8ff 100644
--- a/src/Text/Pandoc/Readers/TeXMath.hs
+++ b/src/Text/Pandoc/Readers/TeXMath.hs
@@ -90,7 +90,7 @@ expToInlines (EUp x y) = expToInlines (ESuper x y)
expToInlines (EDownup x y z) = expToInlines (ESubsup x y z)
expToInlines (EText "normal" x) = Just [Str x]
expToInlines (EText "bold" x) = Just [Strong [Str x]]
-expToInlines (EText "monospace" x) = Just [Code x]
+expToInlines (EText "monospace" x) = Just [Code nullAttr x]
expToInlines (EText "italic" x) = Just [Emph [Str x]]
expToInlines (EText _ x) = Just [Str x]
expToInlines (EOver (EGrouped [EIdentifier [c]]) (ESymbol Accent [accent])) =
diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs
index 714cac9f4..19357b343 100644
--- a/src/Text/Pandoc/Readers/Textile.hs
+++ b/src/Text/Pandoc/Readers/Textile.hs
@@ -494,13 +494,13 @@ code :: GenParser Char ParserState Inline
code = code1 <|> code2
code1 :: GenParser Char ParserState Inline
-code1 = surrounded (char '@') anyChar >>= return . Code
+code1 = surrounded (char '@') anyChar >>= return . Code nullAttr
code2 :: GenParser Char ParserState Inline
code2 = do
htmlTag (tagOpen (=="tt") null)
result' <- manyTill anyChar (try $ htmlTag $ tagClose (=="tt"))
- return $ Code result'
+ return $ Code nullAttr result'
-- | Html / CSS attributes
attributes :: GenParser Char ParserState String
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index 0235a536a..876a2b21b 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -279,7 +279,7 @@ removeEmptyInlines (Superscript [] : zs) = removeEmptyInlines zs
removeEmptyInlines (SmallCaps [] : zs) = removeEmptyInlines zs
removeEmptyInlines (Strikeout [] : zs) = removeEmptyInlines zs
removeEmptyInlines (RawInline _ [] : zs) = removeEmptyInlines zs
-removeEmptyInlines (Code [] : zs) = removeEmptyInlines zs
+removeEmptyInlines (Code _ [] : zs) = removeEmptyInlines zs
removeEmptyInlines (x : xs) = x : removeEmptyInlines xs
removeEmptyInlines [] = []
@@ -312,8 +312,8 @@ consolidateInlines (Strikeout xs : Strikeout ys : zs) = consolidateInlines $
Strikeout (xs ++ ys) : zs
consolidateInlines (RawInline f x : RawInline f' y : zs) | f == f' =
consolidateInlines $ RawInline f (x ++ y) : zs
-consolidateInlines (Code x : Code y : zs) = consolidateInlines $
- Code (x ++ y) : zs
+consolidateInlines (Code a1 x : Code a2 y : zs) | a1 == a2 =
+ consolidateInlines $ Code a1 (x ++ y) : zs
consolidateInlines (x : xs) = x : consolidateInlines xs
consolidateInlines [] = []
@@ -323,7 +323,7 @@ stringify = queryWith go
where go :: Inline -> [Char]
go Space = " "
go (Str x) = x
- go (Code x) = x
+ go (Code _ x) = x
go (Math _ x) = x
go EmDash = "--"
go EnDash = "-"
diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs
index b6f5352c6..0f6e00a3b 100644
--- a/src/Text/Pandoc/Writers/ConTeXt.hs
+++ b/src/Text/Pandoc/Writers/ConTeXt.hs
@@ -245,9 +245,9 @@ inlineToConTeXt (Subscript lst) = do
inlineToConTeXt (SmallCaps lst) = do
contents <- inlineListToConTeXt lst
return $ braces $ "\\sc " <> contents
-inlineToConTeXt (Code str) | not ('{' `elem` str || '}' `elem` str) =
+inlineToConTeXt (Code _ str) | not ('{' `elem` str || '}' `elem` str) =
return $ "\\type" <> braces (text str)
-inlineToConTeXt (Code str) =
+inlineToConTeXt (Code _ str) =
return $ "\\mono" <> braces (text $ stringToConTeXt str)
inlineToConTeXt (Quoted SingleQuote lst) = do
contents <- inlineListToConTeXt lst
@@ -270,7 +270,7 @@ inlineToConTeXt (RawInline "tex" str) = return $ text str
inlineToConTeXt (RawInline _ _) = return empty
inlineToConTeXt (LineBreak) = return $ text "\\crlf" <> cr
inlineToConTeXt Space = return space
-inlineToConTeXt (Link [Code str] (src, tit)) = -- since ConTeXt has its own
+inlineToConTeXt (Link [Code _ str] (src, tit)) = -- since ConTeXt has its own
inlineToConTeXt (Link [Str str] (src, tit)) -- way of printing links...
inlineToConTeXt (Link txt (src, _)) = do
st <- get
diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs
index aac4002f5..9d09d46e3 100644
--- a/src/Text/Pandoc/Writers/Docbook.hs
+++ b/src/Text/Pandoc/Writers/Docbook.hs
@@ -258,7 +258,7 @@ inlineToDocbook _ Apostrophe = char '\''
inlineToDocbook _ Ellipses = text "…"
inlineToDocbook _ EmDash = text "—"
inlineToDocbook _ EnDash = text "–"
-inlineToDocbook _ (Code str) =
+inlineToDocbook _ (Code _ str) =
inTagsSimple "literal" $ text (escapeStringForXML str)
inlineToDocbook opts (Math _ str) = inlinesToDocbook opts $ readTeXMath str
inlineToDocbook _ (RawInline _ _) = empty
@@ -269,10 +269,10 @@ inlineToDocbook opts (Link txt (src, _)) =
then let src' = drop 7 src
emailLink = inTagsSimple "email" $ text $
escapeStringForXML $ src'
- in if txt == [Code src']
- then emailLink
- else inlinesToDocbook opts txt <+> char '(' <> emailLink <>
- char ')'
+ in case txt of
+ [Code _ s] | s == src' -> emailLink
+ _ -> inlinesToDocbook opts txt <+>
+ char '(' <> emailLink <> char ')'
else (if isPrefixOf "#" src
then inTags False "link" [("linkend", drop 1 src)]
else inTags False "ulink" [("url", src)]) $
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index 94dec864e..3b40515da 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -298,6 +298,12 @@ obfuscateChar char =
obfuscateString :: String -> String
obfuscateString = concatMap obfuscateChar . decodeCharacterReferences
+attrsToHtml :: WriterOptions -> Attr -> [HtmlAttr]
+attrsToHtml opts (id',classes',keyvals) =
+ [theclass (unwords classes') | not (null classes')] ++
+ [prefixedId opts id' | not (null id')] ++
+ map (\(x,y) -> strAttr x y) keyvals
+
-- | Convert Pandoc block element to HTML.
blockToHtml :: WriterOptions -> Block -> State WriterState Html
blockToHtml _ Null = return $ noHtml
@@ -322,9 +328,7 @@ blockToHtml opts (CodeBlock (id',classes,keyvals) rawCode) = do
Left _ -> -- change leading newlines into <br /> tags, because some
-- browsers ignore leading newlines in pre blocks
let (leadingBreaks, rawCode') = span (=='\n') rawCode
- attrs = [theclass (unwords classes') | not (null classes')] ++
- [prefixedId opts id' | not (null id')] ++
- map (\(x,y) -> strAttr x y) keyvals
+ attrs = attrsToHtml opts (id', classes', keyvals)
addBird = if "literate" `elem` classes'
then unlines . map ("> " ++) . lines
else unlines . lines
@@ -479,7 +483,10 @@ inlineToHtml opts inline =
(Apostrophe) -> return $ stringToHtml "’"
(Emph lst) -> inlineListToHtml opts lst >>= return . emphasize
(Strong lst) -> inlineListToHtml opts lst >>= return . strong
- (Code str) -> return $ thecode << str
+ (Code attr str) -> return $ thecode ! (attrsToHtml opts attr) << str'
+ where str' = case highlightHtml attr str of
+ Left _ -> stringToHtml str
+ Right h -> h
(Strikeout lst) -> inlineListToHtml opts lst >>=
return . (thespan ! [thestyle "text-decoration: line-through;"])
(SmallCaps lst) -> inlineListToHtml opts lst >>=
@@ -547,7 +554,7 @@ inlineToHtml opts inline =
_ -> return noHtml
(RawInline "html" str) -> return $ primHtml str
(RawInline _ _) -> return noHtml
- (Link [Code str] (s,_)) | "mailto:" `isPrefixOf` s ->
+ (Link [Code _ str] (s,_)) | "mailto:" `isPrefixOf` s ->
return $ obfuscateLink opts str s
(Link txt (s,_)) | "mailto:" `isPrefixOf` s -> do
linkText <- inlineListToHtml opts txt
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index 101ae628a..d2f8553e3 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -150,7 +150,7 @@ inCmd cmd contents = char '\\' <> text cmd <> braces contents
-- (because it's illegal to have verbatim inside some command arguments)
deVerb :: [Inline] -> [Inline]
deVerb [] = []
-deVerb ((Code str):rest) =
+deVerb ((Code _ str):rest) =
(RawInline "latex" $ "\\texttt{" ++ stringToLaTeX str ++ "}"):(deVerb rest)
deVerb (other:rest) = other:(deVerb rest)
@@ -331,7 +331,7 @@ inlineToLaTeX (Cite cits lst) = do
Biblatex -> citationsToBiblatex cits
_ -> inlineListToLaTeX lst
-inlineToLaTeX (Code str) = do
+inlineToLaTeX (Code _ str) = do
st <- get
when (stInNote st) $ modify $ \s -> s{ stVerbInNote = True }
let chr = ((enumFromTo '!' '~') \\ str) !! 0
@@ -368,7 +368,7 @@ inlineToLaTeX (LineBreak) = return "\\\\"
inlineToLaTeX Space = return space
inlineToLaTeX (Link txt (src, _)) =
case txt of
- [Code x] | x == src -> -- autolink
+ [Code _ x] | x == src -> -- autolink
do modify $ \s -> s{ stUrl = True }
return $ text $ "\\url{" ++ x ++ "}"
_ -> do contents <- inlineListToLaTeX $ deVerb txt
diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs
index c3e4ea3bb..78b9274d6 100644
--- a/src/Text/Pandoc/Writers/Man.hs
+++ b/src/Text/Pandoc/Writers/Man.hs
@@ -307,7 +307,7 @@ inlineToMan _ EmDash = return $ text "\\[em]"
inlineToMan _ EnDash = return $ text "\\[en]"
inlineToMan _ Apostrophe = return $ char '\''
inlineToMan _ Ellipses = return $ text "\\&..."
-inlineToMan _ (Code str) =
+inlineToMan _ (Code _ str) =
return $ text $ "\\f[C]" ++ escapeCode str ++ "\\f[]"
inlineToMan _ (Str str) = return $ text $ escapeString str
inlineToMan opts (Math InlineMath str) = inlineListToMan opts $ readTeXMath str
@@ -322,9 +322,10 @@ inlineToMan _ Space = return space
inlineToMan opts (Link txt (src, _)) = do
linktext <- inlineListToMan opts txt
let srcSuffix = if isPrefixOf "mailto:" src then drop 7 src else src
- return $ if txt == [Code srcSuffix]
- then char '<' <> text srcSuffix <> char '>'
- else linktext <> text " (" <> text src <> char ')'
+ return $ case txt of
+ [Code _ s]
+ | s == srcSuffix -> char '<' <> text srcSuffix <> char '>'
+ _ -> linktext <> text " (" <> text src <> char ')'
inlineToMan opts (Image alternate (source, tit)) = do
let txt = if (null alternate) || (alternate == [Str ""]) ||
(alternate == [Str source]) -- to prevent autolinks
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index d1b16b34e..5e12c4aca 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -73,7 +73,7 @@ plainify = bottomUp go
go (Superscript xs) = SmallCaps xs
go (Subscript xs) = SmallCaps xs
go (SmallCaps xs) = SmallCaps xs
- go (Code s) = Str s
+ go (Code _ s) = Str s
go (Math _ s) = Str s
go (RawInline _ _) = Str ""
go (Link xs _) = SmallCaps xs
@@ -171,6 +171,22 @@ elementToListItem (Sec _ _ _ headerText subsecs) = [Plain headerText] ++
then []
else [BulletList $ map elementToListItem subsecs]
+attrsToMarkdown :: Attr -> Doc
+attrsToMarkdown attribs = braces $ hsep [attribId, attribClasses, attribKeys]
+ where attribId = case attribs of
+ ([],_,_) -> empty
+ (i,_,_) -> "#" <> text i
+ attribClasses = case attribs of
+ (_,[],_) -> empty
+ (_,cs,_) -> hsep $
+ map (text . ('.':))
+ cs
+ attribKeys = case attribs of
+ (_,_,[]) -> empty
+ (_,_,ks) -> hsep $
+ map (\(k,v) -> text k
+ <> "=\"" <> text v <> "\"") ks
+
-- | Ordered list start parser for use in Para below.
olMarker :: GenParser Char ParserState Char
olMarker = do (start, style', delim) <- anyOrderedListMarker
@@ -233,26 +249,13 @@ blockToMarkdown opts (CodeBlock (_,classes,_) str)
writerLiterateHaskell opts =
return $ prefixed "> " (text str) <> blankline
blockToMarkdown opts (CodeBlock attribs str) = return $
- if writerStrictMarkdown opts || attribs == ([],[],[])
+ if writerStrictMarkdown opts || attribs == nullAttr
then nest (writerTabStop opts) (text str) <> blankline
else -- use delimited code block
flush (tildes <> space <> attrs <> cr <> text str <>
cr <> tildes) <> blankline
where tildes = text "~~~~"
- attrs = braces $ hsep [attribId, attribClasses, attribKeys]
- attribId = case attribs of
- ([],_,_) -> empty
- (i,_,_) -> "#" <> text i
- attribClasses = case attribs of
- (_,[],_) -> empty
- (_,cs,_) -> hsep $
- map (text . ('.':))
- cs
- attribKeys = case attribs of
- (_,_,[]) -> empty
- (_,_,ks) -> hsep $
- map (\(k,v) -> text k
- <> "=\"" <> text v <> "\"") ks
+ attrs = attrsToMarkdown attribs
blockToMarkdown opts (BlockQuote blocks) = do
st <- get
-- if we're writing literate haskell, put a space before the bird tracks
@@ -423,14 +426,17 @@ inlineToMarkdown _ EmDash = return "\8212"
inlineToMarkdown _ EnDash = return "\8211"
inlineToMarkdown _ Apostrophe = return "\8217"
inlineToMarkdown _ Ellipses = return "\8230"
-inlineToMarkdown _ (Code str) =
+inlineToMarkdown opts (Code attr str) =
let tickGroups = filter (\s -> '`' `elem` s) $ group str
longest = if null tickGroups
then 0
else maximum $ map length tickGroups
marker = replicate (longest + 1) '`'
- spacer = if (longest == 0) then "" else " " in
- return $ text (marker ++ spacer ++ str ++ spacer ++ marker)
+ spacer = if (longest == 0) then "" else " "
+ attrs = if writerStrictMarkdown opts || attr == nullAttr
+ then empty
+ else attrsToMarkdown attr
+ in return $ text (marker ++ spacer ++ str ++ spacer ++ marker) <> attrs
inlineToMarkdown _ (Str str) = do
st <- get
if stPlain st
@@ -485,7 +491,9 @@ inlineToMarkdown opts (Link txt (src', tit)) = do
let src = unescapeURI src'
let srcSuffix = if isPrefixOf "mailto:" src then drop 7 src else src
let useRefLinks = writerReferenceLinks opts
- let useAuto = null tit && txt == [Code srcSuffix]
+ let useAuto = case (tit,txt) of
+ ("", [Code _ s]) | s == srcSuffix -> True
+ _ -> False
ref <- if useRefLinks then getReference txt (src, tit) else return []
reftext <- inlineListToMarkdown opts ref
return $ if useAuto
diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs
index 1400b5846..a7c7fc482 100644
--- a/src/Text/Pandoc/Writers/MediaWiki.hs
+++ b/src/Text/Pandoc/Writers/MediaWiki.hs
@@ -362,7 +362,7 @@ inlineToMediaWiki _ Apostrophe = return "&rsquo;"
inlineToMediaWiki _ Ellipses = return "&hellip;"
-inlineToMediaWiki _ (Code str) =
+inlineToMediaWiki _ (Code _ str) =
return $ "<tt>" ++ (escapeString str) ++ "</tt>"
inlineToMediaWiki _ (Str str) = return $ escapeString str
@@ -380,12 +380,12 @@ inlineToMediaWiki _ Space = return " "
inlineToMediaWiki opts (Link txt (src, _)) = do
label <- inlineListToMediaWiki opts txt
- if txt == [Code src] -- autolink
- then return src
- else if isURI src
- then return $ "[" ++ src ++ " " ++ label ++ "]"
- else return $ "[[" ++ src' ++ "|" ++ label ++ "]]"
- where src' = case src of
+ case txt of
+ [Code _ s] | s == src -> return src
+ _ -> if isURI src
+ then return $ "[" ++ src ++ " " ++ label ++ "]"
+ else return $ "[[" ++ src' ++ "|" ++ label ++ "]]"
+ where src' = case src of
'/':xs -> xs -- with leading / it's a
_ -> src -- link to a help page
inlineToMediaWiki opts (Image alt (source, tit)) = do
diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs
index 59980a30c..b9444aac7 100644
--- a/src/Text/Pandoc/Writers/OpenDocument.hs
+++ b/src/Text/Pandoc/Writers/OpenDocument.hs
@@ -362,7 +362,7 @@ inlineToOpenDocument o ils
| Subscript l <- ils = withTextStyle Sub $ inlinesToOpenDocument o l
| SmallCaps l <- ils = withTextStyle SmallC $ inlinesToOpenDocument o l
| Quoted t l <- ils = inQuotes t <$> inlinesToOpenDocument o l
- | Code s <- ils = preformatted s
+ | Code _ s <- ils = preformatted s
| Math _ s <- ils = inlinesToOpenDocument o (readTeXMath s)
| Cite _ l <- ils = inlinesToOpenDocument o l
| RawInline "opendocument" s <- ils = preformatted s
diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs
index 8f3ff6f3e..f7f314428 100644
--- a/src/Text/Pandoc/Writers/Org.hs
+++ b/src/Text/Pandoc/Writers/Org.hs
@@ -253,7 +253,7 @@ inlineToOrg EmDash = return "---"
inlineToOrg EnDash = return "--"
inlineToOrg Apostrophe = return "'"
inlineToOrg Ellipses = return "..."
-inlineToOrg (Code str) = return $ "=" <> text str <> "="
+inlineToOrg (Code _ str) = return $ "=" <> text str <> "="
inlineToOrg (Str str) = return $ text $ escapeString str
inlineToOrg (Math t str) = do
modify $ \st -> st{ stHasMath = True }
@@ -266,7 +266,7 @@ inlineToOrg (LineBreak) = return cr -- there's no line break in Org
inlineToOrg Space = return space
inlineToOrg (Link txt (src, _)) = do
case txt of
- [Code x] | x == src -> -- autolink
+ [Code _ x] | x == src -> -- autolink
do modify $ \s -> s{ stLinks = True }
return $ "[[" <> text x <> "]]"
_ -> do contents <- inlineListToOrg txt
diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs
index 1d1f79d57..d4adaa929 100644
--- a/src/Text/Pandoc/Writers/RST.hs
+++ b/src/Text/Pandoc/Writers/RST.hs
@@ -285,7 +285,7 @@ inlineToRST EmDash = return $ char '\8212'
inlineToRST EnDash = return $ char '\8211'
inlineToRST Apostrophe = return $ char '\8217'
inlineToRST Ellipses = return $ char '\8230'
-inlineToRST (Code str) = return $ "``" <> text str <> "``"
+inlineToRST (Code _ str) = return $ "``" <> text str <> "``"
inlineToRST (Str str) = return $ text $ escapeString str
inlineToRST (Math t str) = do
modify $ \st -> st{ stHasMath = True }
@@ -295,8 +295,8 @@ inlineToRST (Math t str) = do
inlineToRST (RawInline _ _) = return empty
inlineToRST (LineBreak) = return cr -- there's no line break in RST
inlineToRST Space = return space
-inlineToRST (Link [Code str] (src, _)) | src == str ||
- src == "mailto:" ++ str = do
+inlineToRST (Link [Code _ str] (src, _)) | src == str ||
+ src == "mailto:" ++ str = do
let srcSuffix = if isPrefixOf "mailto:" src then drop 7 src else src
return $ text $ unescapeURI srcSuffix
inlineToRST (Link txt (src', tit)) = do
diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs
index 31a28101c..63954cebf 100644
--- a/src/Text/Pandoc/Writers/RTF.hs
+++ b/src/Text/Pandoc/Writers/RTF.hs
@@ -265,7 +265,7 @@ inlineToRTF Apostrophe = "\\u8217'"
inlineToRTF Ellipses = "\\u8230?"
inlineToRTF EmDash = "\\u8212-"
inlineToRTF EnDash = "\\u8211-"
-inlineToRTF (Code str) = "{\\f1 " ++ (codeStringToRTF str) ++ "}"
+inlineToRTF (Code _ str) = "{\\f1 " ++ (codeStringToRTF str) ++ "}"
inlineToRTF (Str str) = stringToRTF str
inlineToRTF (Math _ str) = inlineListToRTF $ readTeXMath str
inlineToRTF (Cite _ lst) = inlineListToRTF lst
diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs
index 037d7bdbe..c8638cdd7 100644
--- a/src/Text/Pandoc/Writers/Texinfo.hs
+++ b/src/Text/Pandoc/Writers/Texinfo.hs
@@ -372,7 +372,7 @@ inlineToTexinfo (Subscript lst) = do
inlineToTexinfo (SmallCaps lst) =
inlineListToTexinfo lst >>= return . inCmd "sc"
-inlineToTexinfo (Code str) = do
+inlineToTexinfo (Code _ str) = do
return $ text $ "@code{" ++ stringToTexinfo str ++ "}"
inlineToTexinfo (Quoted SingleQuote lst) = do
@@ -400,7 +400,7 @@ inlineToTexinfo Space = return $ char ' '
inlineToTexinfo (Link txt (src, _)) = do
case txt of
- [Code x] | x == src -> -- autolink
+ [Code _ x] | x == src -> -- autolink
do return $ text $ "@url{" ++ x ++ "}"
_ -> do contents <- inlineListToTexinfo txt
let src1 = stringToTexinfo src
diff --git a/src/Text/Pandoc/Writers/Textile.hs b/src/Text/Pandoc/Writers/Textile.hs
index 9bfff0dba..6614ec28e 100644
--- a/src/Text/Pandoc/Writers/Textile.hs
+++ b/src/Text/Pandoc/Writers/Textile.hs
@@ -378,7 +378,7 @@ inlineToTextile _ Apostrophe = return "'"
inlineToTextile _ Ellipses = return "..."
-inlineToTextile _ (Code str) =
+inlineToTextile _ (Code _ str) =
return $ if '@' `elem` str
then "<tt>" ++ escapeStringForXML str ++ "</tt>"
else "@" ++ str ++ "@"
@@ -399,8 +399,8 @@ inlineToTextile _ Space = return " "
inlineToTextile opts (Link txt (src, _)) = do
label <- case txt of
- [Code s] -> return s
- _ -> inlineListToTextile opts txt
+ [Code _ s] -> return s
+ _ -> inlineListToTextile opts txt
return $ "\"" ++ label ++ "\":" ++ src
inlineToTextile opts (Image alt (source, tit)) = do
diff --git a/tests/Tests/Arbitrary.hs b/tests/Tests/Arbitrary.hs
index 0191fda7b..70809a71a 100644
--- a/tests/Tests/Arbitrary.hs
+++ b/tests/Tests/Arbitrary.hs
@@ -30,7 +30,7 @@ instance Arbitrary Inline where
arbInline :: Int -> Gen Inline
arbInline n = frequency $ [ (60, liftM Str realString)
, (60, return Space)
- , (10, liftM Code realString)
+ , (10, liftM2 Code arbitrary realString)
, (5, return EmDash)
, (5, return EnDash)
, (5, return Apostrophe)
diff --git a/tests/html-reader.native b/tests/html-reader.native
index 1510d5d7c..c7ba26568 100644
--- a/tests/html-reader.native
+++ b/tests/html-reader.native
@@ -224,14 +224,14 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
,Para [Str "So",Space,Str "is",Space,Strong [Emph [Str "this"]],Space,Str "word",Str "."]
,Para [Strong [Emph [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em",Str "."]]]
,Para [Str "So",Space,Str "is",Space,Strong [Emph [Str "this"]],Space,Str "word",Str "."]
-,Para [Str "This",Space,Str "is",Space,Str "code:",Space,Code ">",Str ",",Space,Code "$",Str ",",Space,Code "\\",Str ",",Space,Code "\\$",Str ",",Space,Code "<html>",Str "."]
+,Para [Str "This",Space,Str "is",Space,Str "code:",Space,Code ("",[],[]) ">",Str ",",Space,Code ("",[],[]) "$",Str ",",Space,Code ("",[],[]) "\\",Str ",",Space,Code ("",[],[]) "\\$",Str ",",Space,Code ("",[],[]) "<html>",Str "."]
,HorizontalRule
,Header 1 [Str "Smart",Space,Str "quotes,",Space,Str "ellipses,",Space,Str "dashes"]
,Para [Str "\"",Str "Hello,",Str "\"",Space,Str "said",Space,Str "the",Space,Str "spider",Str ".",Space,Str "\"",Str "'",Str "Shelob",Str "'",Space,Str "is",Space,Str "my",Space,Str "name",Str ".",Str "\""]
,Para [Str "'",Str "A",Str "'",Str ",",Space,Str "'",Str "B",Str "'",Str ",",Space,Str "and",Space,Str "'",Str "C",Str "'",Space,Str "are",Space,Str "letters",Str "."]
,Para [Str "'",Str "Oak,",Str "'",Space,Str "'",Str "elm,",Str "'",Space,Str "and",Space,Str "'",Str "beech",Str "'",Space,Str "are",Space,Str "names",Space,Str "of",Space,Str "trees",Str ".",Space,Str "So",Space,Str "is",Space,Str "'",Str "pine",Str ".",Str "'"]
,Para [Str "'",Str "He",Space,Str "said,",Space,Str "\"",Str "I",Space,Str "want",Space,Str "to",Space,Str "go",Str ".",Str "\"",Str "'",Space,Str "Were",Space,Str "you",Space,Str "alive",Space,Str "in",Space,Str "the",Space,Str "70",Str "'",Str "s?"]
-,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "quoted",Space,Str "'",Code "code",Str "'",Space,Str "and",Space,Str "a",Space,Str "\"",Link [Str "quoted",Space,Str "link"] ("http://example.com/?foo=1&bar=2",""),Str "\"",Str "."]
+,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "quoted",Space,Str "'",Code ("",[],[]) "code",Str "'",Space,Str "and",Space,Str "a",Space,Str "\"",Link [Str "quoted",Space,Str "link"] ("http://example.com/?foo=1&bar=2",""),Str "\"",Str "."]
,Para [Str "Some",Space,Str "dashes:",Space,Str "one",Str "-",Str "-",Str "-",Str "two",Space,Str "-",Str "-",Str "-",Space,Str "three",Str "-",Str "-",Str "four",Space,Str "-",Str "-",Space,Str "five",Str "."]
,Para [Str "Dashes",Space,Str "between",Space,Str "numbers:",Space,Str "5",Str "-",Str "7,",Space,Str "255",Str "-",Str "66,",Space,Str "1987",Str "-",Str "1999",Str "."]
,Para [Str "Ellipses",Str ".",Str ".",Str ".",Str "and",Str ".",Space,Str ".",Space,Str ".",Str "and",Space,Str ".",Space,Str ".",Space,Str ".",Space,Str "."]
@@ -249,9 +249,9 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
,[Plain [Str "Here",Str "'",Str "s",Space,Str "one",Space,Str "that",Space,Str "has",Space,Str "a",Space,Str "line",Space,Str "break",Space,Str "in",Space,Str "it:",Space,Str "$\\alpha",Space,Str "+",Space,Str "\\omega",Space,Str "\\times",Space,Str "x^2$",Str "."]]]
,Para [Str "These",Space,Str "shouldn",Str "'",Str "t",Space,Str "be",Space,Str "math:"]
,BulletList
- [[Plain [Str "To",Space,Str "get",Space,Str "the",Space,Str "famous",Space,Str "equation,",Space,Str "write",Space,Code "$e = mc^2$",Str "."]]
+ [[Plain [Str "To",Space,Str "get",Space,Str "the",Space,Str "famous",Space,Str "equation,",Space,Str "write",Space,Code ("",[],[]) "$e = mc^2$",Str "."]]
,[Plain [Str "$22,000",Space,Str "is",Space,Str "a",Space,Emph [Str "lot"],Space,Str "of",Space,Str "money",Str ".",Space,Str "So",Space,Str "is",Space,Str "$34,000",Str ".",Space,Str "(It",Space,Str "worked",Space,Str "if",Space,Str "\"",Str "lot",Str "\"",Space,Str "is",Space,Str "emphasized",Str ".",Str ")"]]
- ,[Plain [Str "Escaped",Space,Code "$",Str ":",Space,Str "$73",Space,Emph [Str "this",Space,Str "should",Space,Str "be",Space,Str "emphasized"],Space,Str "23$",Str "."]]]
+ ,[Plain [Str "Escaped",Space,Code ("",[],[]) "$",Str ":",Space,Str "$73",Space,Emph [Str "this",Space,Str "should",Space,Str "be",Space,Str "emphasized"],Space,Str "23$",Str "."]]]
,Para [Str "Here",Str "'",Str "s",Space,Str "a",Space,Str "LaTeX",Space,Str "table:"]
,Para [Str "\\begin{tabular}{|l|l|}\\hline",Space,Str "Animal",Space,Str "&",Space,Str "Number",Space,Str "\\\\",Space,Str "\\hline",Space,Str "Dog",Space,Str "&",Space,Str "2",Space,Str "\\\\",Space,Str "Cat",Space,Str "&",Space,Str "1",Space,Str "\\\\",Space,Str "\\hline",Space,Str "\\end{tabular}"]
,HorizontalRule
@@ -322,7 +322,7 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
,Plain [Str "An",Space,Str "e",Str "-",Str "mail",Space,Str "address:",Space,Str "nobody",Space,Str "[at]",Space,Str "nowhere",Str ".",Str "net"]
,BlockQuote
[Para [Str "Blockquoted:",Space,Link [Str "http://example",Str ".",Str "com/"] ("http://example.com/","")]]
-,Para [Str "Auto",Str "-",Str "links",Space,Str "should",Space,Str "not",Space,Str "occur",Space,Str "here:",Space,Code "<http://example.com/>"]
+,Para [Str "Auto",Str "-",Str "links",Space,Str "should",Space,Str "not",Space,Str "occur",Space,Str "here:",Space,Code ("",[],[]) "<http://example.com/>"]
,CodeBlock ("",[],[]) "or here: <http://example.com/>"
,HorizontalRule
,Header 1 [Str "Images"]
diff --git a/tests/latex-reader.native b/tests/latex-reader.native
index cb5f201aa..a5e14dd8f 100644
--- a/tests/latex-reader.native
+++ b/tests/latex-reader.native
@@ -240,7 +240,7 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
,Para [Str "So",Space,Str "is",Space,Strong [Emph [Str "this"]],Space,Str "word."]
,Para [Strong [Emph [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em."]]]
,Para [Str "So",Space,Str "is",Space,Strong [Emph [Str "this"]],Space,Str "word."]
-,Para [Str "This",Space,Str "is",Space,Str "code:",Space,Code ">",Str ",",Space,Code "$",Str ",",Space,Code "\\",Str ",",Space,Code "\\$",Str ",",Space,Code "<html>",Str "."]
+,Para [Str "This",Space,Str "is",Space,Str "code:",Space,Code ("",[],[]) ">",Str ",",Space,Code ("",[],[]) "$",Str ",",Space,Code ("",[],[]) "\\",Str ",",Space,Code ("",[],[]) "\\$",Str ",",Space,Code ("",[],[]) "<html>",Str "."]
,Para [Strikeout [Str "This",Space,Str "is",Space,Emph [Str "strikeout"],Str "."]]
,Para [Str "Superscripts:",Space,Str "a",Superscript [Str "bc"],Str "d",Space,Str "a",Superscript [Emph [Str "hello"]],Space,Str "a",Superscript [Str "hello",Space,Str "there"],Str "."]
,Para [Str "Subscripts:",Space,Str "H",Subscript [Str "2"],Str "O,",Space,Str "H",Subscript [Str "23"],Str "O,",Space,Str "H",Subscript [Str "many",Space,Str "of",Space,Str "them"],Str "O."]
@@ -251,7 +251,7 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
,Para [Quoted SingleQuote [Str "A"],Str ",",Space,Quoted SingleQuote [Str "B"],Str ",",Space,Str "and",Space,Quoted SingleQuote [Str "C"],Space,Str "are",Space,Str "letters."]
,Para [Quoted SingleQuote [Str "Oak,"],Space,Quoted SingleQuote [Str "elm,"],Space,Str "and",Space,Quoted SingleQuote [Str "beech"],Space,Str "are",Space,Str "names",Space,Str "of",Space,Str "trees.",Space,Str "So",Space,Str "is",Space,Quoted SingleQuote [Str "pine."]]
,Para [Quoted SingleQuote [Str "He",Space,Str "said,",Space,Quoted DoubleQuote [Str "I",Space,Str "want",Space,Str "to",Space,Str "go."]],Space,Str "Were",Space,Str "you",Space,Str "alive",Space,Str "in",Space,Str "the",Space,Str "70",Apostrophe,Str "s?"]
-,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "quoted",Space,Quoted SingleQuote [Code "code"],Space,Str "and",Space,Str "a",Space,Quoted DoubleQuote [Link [Str "quoted",Space,Str "link"] ("http://example.com/?foo=1&bar=2","")],Str "."]
+,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "quoted",Space,Quoted SingleQuote [Code ("",[],[]) "code"],Space,Str "and",Space,Str "a",Space,Quoted DoubleQuote [Link [Str "quoted",Space,Str "link"] ("http://example.com/?foo=1&bar=2","")],Str "."]
,Para [Str "Some",Space,Str "dashes:",Space,Str "one",EmDash,Str "two",EmDash,Str "three",EmDash,Str "four",EmDash,Str "five."]
,Para [Str "Dashes",Space,Str "between",Space,Str "numbers:",Space,Str "5",EnDash,Str "7,",Space,Str "255",EnDash,Str "66,",Space,Str "1987",EnDash,Str "1999."]
,Para [Str "Ellipses",Ellipses,Str "and",Ellipses,Str "and",Ellipses,Str "."]
@@ -269,9 +269,9 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
,[Para [Str "Here",Apostrophe,Str "s",Space,Str "one",Space,Str "that",Space,Str "has",Space,Str "a",Space,Str "line",Space,Str "break",Space,Str "in",Space,Str "it:",Space,Math InlineMath "\\alpha + \\omega \\times x^2",Str "."]]]
,Para [Str "These",Space,Str "shouldn",Apostrophe,Str "t",Space,Str "be",Space,Str "math:"]
,BulletList
- [[Para [Str "To",Space,Str "get",Space,Str "the",Space,Str "famous",Space,Str "equation,",Space,Str "write",Space,Code "$e = mc^2$",Str "."]]
+ [[Para [Str "To",Space,Str "get",Space,Str "the",Space,Str "famous",Space,Str "equation,",Space,Str "write",Space,Code ("",[],[]) "$e = mc^2$",Str "."]]
,[Para [Str "$",Str "22,000",Space,Str "is",Space,Str "a",Space,Emph [Str "lot"],Space,Str "of",Space,Str "money.",Space,Str "So",Space,Str "is",Space,Str "$",Str "34,000.",Space,Str "(It",Space,Str "worked",Space,Str "if",Space,Quoted DoubleQuote [Str "lot"],Space,Str "is",Space,Str "emphasized.)"]]
- ,[Para [Str "Escaped",Space,Code "$",Str ":",Space,Str "$",Str "73",Space,Emph [Str "this",Space,Str "should",Space,Str "be",Space,Str "emphasized"],Space,Str "23",Str "$",Str "."]]]
+ ,[Para [Str "Escaped",Space,Code ("",[],[]) "$",Str ":",Space,Str "$",Str "73",Space,Emph [Str "this",Space,Str "should",Space,Str "be",Space,Str "emphasized"],Space,Str "23",Str "$",Str "."]]]
,Para [Str "Here",Apostrophe,Str "s",Space,Str "a",Space,Str "LaTeX",Space,Str "table:"]
,Table [] [AlignLeft,AlignLeft] [0.0,0.0]
[[Plain [Str "Animal"]]
@@ -341,15 +341,15 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
,Para [Str "Here",Apostrophe,Str "s",Space,Str "an",Space,Link [Str "inline",Space,Str "link"] ("/script?foo=1&bar=2",""),Str "."]
,Para [Str "Here",Apostrophe,Str "s",Space,Str "an",Space,Link [Str "inline",Space,Str "link",Space,Str "in",Space,Str "pointy",Space,Str "braces"] ("/script?foo=1&bar=2",""),Str "."]
,Header 2 [Str "Autolinks"]
-,Para [Str "With",Space,Str "an",Space,Str "ampersand:",Space,Link [Code "http://example.com/?foo=1&bar=2"] ("http://example.com/?foo=1&bar=2","")]
+,Para [Str "With",Space,Str "an",Space,Str "ampersand:",Space,Link [Code ("",["url"],[]) "http://example.com/?foo=1&bar=2"] ("http://example.com/?foo=1&bar=2","")]
,BulletList
[[Para [Str "In",Space,Str "a",Space,Str "list?"]]
- ,[Para [Link [Code "http://example.com/"] ("http://example.com/","")]]
+ ,[Para [Link [Code ("",["url"],[]) "http://example.com/"] ("http://example.com/","")]]
,[Para [Str "It",Space,Str "should."]]]
-,Para [Str "An",Space,Str "e",Str "-",Str "mail",Space,Str "address:",Space,Link [Code "nobody@nowhere.net"] ("mailto:nobody@nowhere.net","")]
+,Para [Str "An",Space,Str "e",Str "-",Str "mail",Space,Str "address:",Space,Link [Code ("",[],[]) "nobody@nowhere.net"] ("mailto:nobody@nowhere.net","")]
,BlockQuote
- [Para [Str "Blockquoted:",Space,Link [Code "http://example.com/"] ("http://example.com/","")]]
-,Para [Str "Auto",Str "-",Str "links",Space,Str "should",Space,Str "not",Space,Str "occur",Space,Str "here:",Space,Code "<http://example.com/>"]
+ [Para [Str "Blockquoted:",Space,Link [Code ("",["url"],[]) "http://example.com/"] ("http://example.com/","")]]
+,Para [Str "Auto",Str "-",Str "links",Space,Str "should",Space,Str "not",Space,Str "occur",Space,Str "here:",Space,Code ("",[],[]) "<http://example.com/>"]
,CodeBlock ("",[],[]) "or here: <http://example.com/>"
,HorizontalRule
,Header 1 [Str "Images"]
@@ -358,7 +358,7 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "movie",Space,Image [Str "image"] ("movie.jpg",""),Space,Str "icon."]
,HorizontalRule
,Header 1 [Str "Footnotes"]
-,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "footnote",Space,Str "reference,",Note [Para [Str "Here",Space,Str "is",Space,Str "the",Space,Str "footnote.",Space,Str "It",Space,Str "can",Space,Str "go",Space,Str "anywhere",Space,Str "after",Space,Str "the",Space,Str "footnote",Space,Str "reference.",Space,Str "It",Space,Str "need",Space,Str "not",Space,Str "be",Space,Str "placed",Space,Str "at",Space,Str "the",Space,Str "end",Space,Str "of",Space,Str "the",Space,Str "document."]],Space,Str "and",Space,Str "another.",Note [Para [Str "Here",Apostrophe,Str "s",Space,Str "the",Space,Str "long",Space,Str "note.",Space,Str "This",Space,Str "one",Space,Str "contains",Space,Str "multiple",Space,Str "blocks."],Para [Str "Subsequent",Space,Str "blocks",Space,Str "are",Space,Str "indented",Space,Str "to",Space,Str "show",Space,Str "that",Space,Str "they",Space,Str "belong",Space,Str "to",Space,Str "the",Space,Str "footnote",Space,Str "(as",Space,Str "with",Space,Str "list",Space,Str "items)."],CodeBlock ("",[],[]) " { <code> }",Para [Str "If",Space,Str "you",Space,Str "want,",Space,Str "you",Space,Str "can",Space,Str "indent",Space,Str "every",Space,Str "line,",Space,Str "but",Space,Str "you",Space,Str "can",Space,Str "also",Space,Str "be",Space,Str "lazy",Space,Str "and",Space,Str "just",Space,Str "indent",Space,Str "the",Space,Str "first",Space,Str "line",Space,Str "of",Space,Str "each",Space,Str "block."]],Space,Str "This",Space,Str "should",Space,Emph [Str "not"],Space,Str "be",Space,Str "a",Space,Str "footnote",Space,Str "reference,",Space,Str "because",Space,Str "it",Space,Str "contains",Space,Str "a",Space,Str "space.",Str "[",Str "^",Str "my",Space,Str "note",Str "]",Space,Str "Here",Space,Str "is",Space,Str "an",Space,Str "inline",Space,Str "note.",Note [Para [Str "This",Space,Str "is",Space,Emph [Str "easier"],Space,Str "to",Space,Str "type.",Space,Str "Inline",Space,Str "notes",Space,Str "may",Space,Str "contain",Space,Link [Str "links"] ("http://google.com",""),Space,Str "and",Space,Code "]",Space,Str "verbatim",Space,Str "characters,",Space,Str "as",Space,Str "well",Space,Str "as",Space,Str "[",Str "bracketed",Space,Str "text",Str "]",Str "."]]]
+,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "footnote",Space,Str "reference,",Note [Para [Str "Here",Space,Str "is",Space,Str "the",Space,Str "footnote.",Space,Str "It",Space,Str "can",Space,Str "go",Space,Str "anywhere",Space,Str "after",Space,Str "the",Space,Str "footnote",Space,Str "reference.",Space,Str "It",Space,Str "need",Space,Str "not",Space,Str "be",Space,Str "placed",Space,Str "at",Space,Str "the",Space,Str "end",Space,Str "of",Space,Str "the",Space,Str "document."]],Space,Str "and",Space,Str "another.",Note [Para [Str "Here",Apostrophe,Str "s",Space,Str "the",Space,Str "long",Space,Str "note.",Space,Str "This",Space,Str "one",Space,Str "contains",Space,Str "multiple",Space,Str "blocks."],Para [Str "Subsequent",Space,Str "blocks",Space,Str "are",Space,Str "indented",Space,Str "to",Space,Str "show",Space,Str "that",Space,Str "they",Space,Str "belong",Space,Str "to",Space,Str "the",Space,Str "footnote",Space,Str "(as",Space,Str "with",Space,Str "list",Space,Str "items)."],CodeBlock ("",[],[]) " { <code> }",Para [Str "If",Space,Str "you",Space,Str "want,",Space,Str "you",Space,Str "can",Space,Str "indent",Space,Str "every",Space,Str "line,",Space,Str "but",Space,Str "you",Space,Str "can",Space,Str "also",Space,Str "be",Space,Str "lazy",Space,Str "and",Space,Str "just",Space,Str "indent",Space,Str "the",Space,Str "first",Space,Str "line",Space,Str "of",Space,Str "each",Space,Str "block."]],Space,Str "This",Space,Str "should",Space,Emph [Str "not"],Space,Str "be",Space,Str "a",Space,Str "footnote",Space,Str "reference,",Space,Str "because",Space,Str "it",Space,Str "contains",Space,Str "a",Space,Str "space.",Str "[",Str "^",Str "my",Space,Str "note",Str "]",Space,Str "Here",Space,Str "is",Space,Str "an",Space,Str "inline",Space,Str "note.",Note [Para [Str "This",Space,Str "is",Space,Emph [Str "easier"],Space,Str "to",Space,Str "type.",Space,Str "Inline",Space,Str "notes",Space,Str "may",Space,Str "contain",Space,Link [Str "links"] ("http://google.com",""),Space,Str "and",Space,Code ("",[],[]) "]",Space,Str "verbatim",Space,Str "characters,",Space,Str "as",Space,Str "well",Space,Str "as",Space,Str "[",Str "bracketed",Space,Str "text",Str "]",Str "."]]]
,BlockQuote
[Para [Str "Notes",Space,Str "can",Space,Str "go",Space,Str "in",Space,Str "quotes.",Note [Para [Str "In",Space,Str "quote."]]]]
,OrderedList (1,Decimal,Period)
diff --git a/tests/lhs-test.fragment.html+lhs b/tests/lhs-test.fragment.html+lhs
index 64a235936..7757bc634 100644
--- a/tests/lhs-test.fragment.html+lhs
+++ b/tests/lhs-test.fragment.html+lhs
@@ -30,8 +30,7 @@
> <br
/>&gt; <span class="co"
>-- arr (\op (x,y) -&gt; x `op` y) </span
- ><br
- /></code
+ ></code
></pre
><p
><code
diff --git a/tests/lhs-test.html b/tests/lhs-test.html
index 2c4bedc00..46ab8f2e4 100644
--- a/tests/lhs-test.html
+++ b/tests/lhs-test.html
@@ -57,8 +57,7 @@ pre.sourceCode span.er { color: red; font-weight: bold; }
> <br
/> <span class="co"
>-- arr (\op (x,y) -&gt; x `op` y) </span
- ><br
- /></code
+ ></code
></pre
><p
><code
diff --git a/tests/lhs-test.html+lhs b/tests/lhs-test.html+lhs
index 536490af5..dd6b5b33c 100644
--- a/tests/lhs-test.html+lhs
+++ b/tests/lhs-test.html+lhs
@@ -57,8 +57,7 @@ pre.sourceCode span.er { color: red; font-weight: bold; }
> <br
/>&gt; <span class="co"
>-- arr (\op (x,y) -&gt; x `op` y) </span
- ><br
- /></code
+ ></code
></pre
><p
><code
diff --git a/tests/lhs-test.native b/tests/lhs-test.native
index 19c002309..4b5a3e112 100644
--- a/tests/lhs-test.native
+++ b/tests/lhs-test.native
@@ -1,7 +1,7 @@
[Header 1 [Str "lhs",Space,Str "test"]
-,Para [Code "unsplit",Space,Str "is",Space,Str "an",Space,Str "arrow",Space,Str "that",Space,Str "takes",Space,Str "a",Space,Str "pair",Space,Str "of",Space,Str "values",Space,Str "and",Space,Str "combines",Space,Str "them",Space,Str "to",Space,Str "return",Space,Str "a",Space,Str "single",Space,Str "value",Str ":"]
+,Para [Code ("",[],[]) "unsplit",Space,Str "is",Space,Str "an",Space,Str "arrow",Space,Str "that",Space,Str "takes",Space,Str "a",Space,Str "pair",Space,Str "of",Space,Str "values",Space,Str "and",Space,Str "combines",Space,Str "them",Space,Str "to",Space,Str "return",Space,Str "a",Space,Str "single",Space,Str "value",Str ":"]
,CodeBlock ("",["sourceCode","literate","haskell"],[]) "unsplit :: (Arrow a) => (b -> c -> d) -> a (b, c) d\nunsplit = arr . uncurry \n -- arr (\\op (x,y) -> x `op` y) "
-,Para [Code "(***)",Space,Str "combines",Space,Str "two",Space,Str "arrows",Space,Str "into",Space,Str "a",Space,Str "new",Space,Str "arrow",Space,Str "by",Space,Str "running",Space,Str "the",Space,Str "two",Space,Str "arrows",Space,Str "on",Space,Str "a",Space,Str "pair",Space,Str "of",Space,Str "values",Space,Str "(one",Space,Str "arrow",Space,Str "on",Space,Str "the",Space,Str "first",Space,Str "item",Space,Str "of",Space,Str "the",Space,Str "pair",Space,Str "and",Space,Str "one",Space,Str "arrow",Space,Str "on",Space,Str "the",Space,Str "second",Space,Str "item",Space,Str "of",Space,Str "the",Space,Str "pair)",Str "."]
+,Para [Code ("",[],[]) "(***)",Space,Str "combines",Space,Str "two",Space,Str "arrows",Space,Str "into",Space,Str "a",Space,Str "new",Space,Str "arrow",Space,Str "by",Space,Str "running",Space,Str "the",Space,Str "two",Space,Str "arrows",Space,Str "on",Space,Str "a",Space,Str "pair",Space,Str "of",Space,Str "values",Space,Str "(one",Space,Str "arrow",Space,Str "on",Space,Str "the",Space,Str "first",Space,Str "item",Space,Str "of",Space,Str "the",Space,Str "pair",Space,Str "and",Space,Str "one",Space,Str "arrow",Space,Str "on",Space,Str "the",Space,Str "second",Space,Str "item",Space,Str "of",Space,Str "the",Space,Str "pair)",Str "."]
,CodeBlock ("",[],[]) "f *** g = first f >>> second g"
,Para [Str "Block",Space,Str "quote",Str ":"]
,BlockQuote
diff --git a/tests/markdown-reader-more.native b/tests/markdown-reader-more.native
index 216c7ade9..e5e079e9f 100644
--- a/tests/markdown-reader-more.native
+++ b/tests/markdown-reader-more.native
@@ -23,15 +23,15 @@
,Header 2 [Str "Backslash",Space,Str "newline"]
,Para [Str "hi",LineBreak,Str "there"]
,Header 2 [Str "Code",Space,Str "spans"]
-,Para [Code "hi\\"]
-,Para [Code "hi there"]
-,Para [Code "hi````there"]
+,Para [Code ("",[],[]) "hi\\"]
+,Para [Code ("",[],[]) "hi there"]
+,Para [Code ("",[],[]) "hi````there"]
,Para [Str "`",Str "hi"]
,Para [Str "there",Str "`"]
,Header 2 [Str "Multilingual",Space,Str "URLs"]
-,Para [Link [Code "http://\27979.com?\27979=\27979"] ("http://%E6%B5%8B.com?%E6%B5%8B=%E6%B5%8B","")]
+,Para [Link [Code ("",["url"],[]) "http://\27979.com?\27979=\27979"] ("http://%E6%B5%8B.com?%E6%B5%8B=%E6%B5%8B","")]
,Para [Link [Str "foo"] ("/bar/%E6%B5%8B?x=%E6%B5%8B","title")]
-,Para [Link [Code "\27979@foo.\27979.baz"] ("mailto:%E6%B5%8B@foo.%E6%B5%8B.baz","")]
+,Para [Link [Code ("",["url"],[]) "\27979@foo.\27979.baz"] ("mailto:%E6%B5%8B@foo.%E6%B5%8B.baz","")]
,Header 2 [Str "Numbered",Space,Str "examples"]
,OrderedList (1,Example,TwoParens)
[[Plain [Str "First",Space,Str "example",Str "."]]
diff --git a/tests/rst-reader.native b/tests/rst-reader.native
index 0213f789e..a88d499b0 100644
--- a/tests/rst-reader.native
+++ b/tests/rst-reader.native
@@ -182,7 +182,7 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite",Str ":
,RawBlock "latex" "\\begin{tabular}{|l|l|}\\hline\nAnimal & Number \\\\ \\hline\nDog & 2 \\\\\nCat & 1 \\\\ \\hline\n\\end{tabular}\n"
,Header 1 [Str "Inline",Space,Str "Markup"]
,Para [Str "This",Space,Str "is",Space,Emph [Str "emphasized"],Str ".",Space,Str "This",Space,Str "is",Space,Strong [Str "strong"],Str "."]
-,Para [Str "This",Space,Str "is",Space,Str "code",Str ":",Space,Code ">",Str ",",Space,Code "$",Str ",",Space,Code "\\",Str ",",Space,Code "\\$",Str ",",Space,Code "<html>",Str "."]
+,Para [Str "This",Space,Str "is",Space,Str "code",Str ":",Space,Code ("",[],[]) ">",Str ",",Space,Code ("",[],[]) "$",Str ",",Space,Code ("",[],[]) "\\",Str ",",Space,Code ("",[],[]) "\\$",Str ",",Space,Code ("",[],[]) "<html>",Str "."]
,Para [Str "This",Space,Str "is",Subscript [Str "subscripted"],Space,Str "and",Space,Str "this",Space,Str "is",Space,Superscript [Str "superscripted"],Str "."]
,Header 1 [Str "Special",Space,Str "Characters"]
,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "unicode",Str ":"]
diff --git a/tests/testsuite.native b/tests/testsuite.native
index d8d62264e..879cb24fc 100644
--- a/tests/testsuite.native
+++ b/tests/testsuite.native
@@ -276,7 +276,7 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
,Para [Str "So",Space,Str "is",Space,Strong [Emph [Str "this"]],Space,Str "word",Str "."]
,Para [Strong [Emph [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em",Str "."]]]
,Para [Str "So",Space,Str "is",Space,Strong [Emph [Str "this"]],Space,Str "word",Str "."]
-,Para [Str "This",Space,Str "is",Space,Str "code",Str ":",Space,Code ">",Str ",",Space,Code "$",Str ",",Space,Code "\\",Str ",",Space,Code "\\$",Str ",",Space,Code "<html>",Str "."]
+,Para [Str "This",Space,Str "is",Space,Str "code",Str ":",Space,Code ("",[],[]) ">",Str ",",Space,Code ("",[],[]) "$",Str ",",Space,Code ("",[],[]) "\\",Str ",",Space,Code ("",[],[]) "\\$",Str ",",Space,Code ("",[],[]) "<html>",Str "."]
,Para [Strikeout [Str "This",Space,Str "is",Space,Emph [Str "strikeout"],Str "."]]
,Para [Str "Superscripts",Str ":",Space,Str "a",Superscript [Str "bc"],Str "d",Space,Str "a",Superscript [Emph [Str "hello"]],Space,Str "a",Superscript [Str "hello",Str "\160",Str "there"],Str "."]
,Para [Str "Subscripts",Str ":",Space,Str "H",Subscript [Str "2"],Str "O",Str ",",Space,Str "H",Subscript [Str "23"],Str "O",Str ",",Space,Str "H",Subscript [Str "many",Str "\160",Str "of",Str "\160",Str "them"],Str "O",Str "."]
@@ -287,7 +287,7 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
,Para [Quoted SingleQuote [Str "A"],Str ",",Space,Quoted SingleQuote [Str "B"],Str ",",Space,Str "and",Space,Quoted SingleQuote [Str "C"],Space,Str "are",Space,Str "letters",Str "."]
,Para [Quoted SingleQuote [Str "Oak",Str ","],Space,Quoted SingleQuote [Str "elm",Str ","],Space,Str "and",Space,Quoted SingleQuote [Str "beech"],Space,Str "are",Space,Str "names",Space,Str "of",Space,Str "trees",Str ".",Space,Str "So",Space,Str "is",Space,Quoted SingleQuote [Str "pine",Str "."]]
,Para [Quoted SingleQuote [Str "He",Space,Str "said",Str ",",Space,Quoted DoubleQuote [Str "I",Space,Str "want",Space,Str "to",Space,Str "go",Str "."]],Space,Str "Were",Space,Str "you",Space,Str "alive",Space,Str "in",Space,Str "the",Space,Str "70",Apostrophe,Str "s",Str "?"]
-,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "quoted",Space,Quoted SingleQuote [Code "code"],Space,Str "and",Space,Str "a",Space,Quoted DoubleQuote [Link [Str "quoted",Space,Str "link"] ("http://example.com/?foo=1&bar=2","")],Str "."]
+,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "quoted",Space,Quoted SingleQuote [Code ("",[],[]) "code"],Space,Str "and",Space,Str "a",Space,Quoted DoubleQuote [Link [Str "quoted",Space,Str "link"] ("http://example.com/?foo=1&bar=2","")],Str "."]
,Para [Str "Some",Space,Str "dashes",Str ":",Space,Str "one",EmDash,Str "two",Space,EmDash,Space,Str "three",EmDash,Str "four",Space,EmDash,Space,Str "five",Str "."]
,Para [Str "Dashes",Space,Str "between",Space,Str "numbers",Str ":",Space,Str "5",EnDash,Str "7",Str ",",Space,Str "255",EnDash,Str "66",Str ",",Space,Str "1987",EnDash,Str "1999",Str "."]
,Para [Str "Ellipses",Ellipses,Str "and",Ellipses,Str "and",Ellipses,Str "."]
@@ -304,10 +304,10 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
,[Plain [Str "Here",Apostrophe,Str "s",Space,Str "one",Space,Str "that",Space,Str "has",Space,Str "a",Space,Str "line",Space,Str "break",Space,Str "in",Space,Str "it",Str ":",Space,Math InlineMath "\\alpha + \\omega \\times x^2",Str "."]]]
,Para [Str "These",Space,Str "shouldn",Apostrophe,Str "t",Space,Str "be",Space,Str "math",Str ":"]
,BulletList
- [[Plain [Str "To",Space,Str "get",Space,Str "the",Space,Str "famous",Space,Str "equation",Str ",",Space,Str "write",Space,Code "$e = mc^2$",Str "."]]
+ [[Plain [Str "To",Space,Str "get",Space,Str "the",Space,Str "famous",Space,Str "equation",Str ",",Space,Str "write",Space,Code ("",[],[]) "$e = mc^2$",Str "."]]
,[Plain [Str "$",Str "22",Str ",",Str "000",Space,Str "is",Space,Str "a",Space,Emph [Str "lot"],Space,Str "of",Space,Str "money",Str ".",Space,Str "So",Space,Str "is",Space,Str "$",Str "34",Str ",",Str "000",Str ".",Space,Str "(",Str "It",Space,Str "worked",Space,Str "if",Space,Quoted DoubleQuote [Str "lot"],Space,Str "is",Space,Str "emphasized",Str ".",Str ")"]]
,[Plain [Str "Shoes",Space,Str "(",Str "$",Str "20",Str ")",Space,Str "and",Space,Str "socks",Space,Str "(",Str "$",Str "5",Str ")",Str "."]]
- ,[Plain [Str "Escaped",Space,Code "$",Str ":",Space,Str "$",Str "73",Space,Emph [Str "this",Space,Str "should",Space,Str "be",Space,Str "emphasized"],Space,Str "23",Str "$",Str "."]]]
+ ,[Plain [Str "Escaped",Space,Code ("",[],[]) "$",Str ":",Space,Str "$",Str "73",Space,Emph [Str "this",Space,Str "should",Space,Str "be",Space,Str "emphasized"],Space,Str "23",Str "$",Str "."]]]
,Para [Str "Here",Apostrophe,Str "s",Space,Str "a",Space,Str "LaTeX",Space,Str "table",Str ":"]
,RawBlock "latex" "\\begin{tabular}{|l|l|}\\hline\nAnimal & Number \\\\ \\hline\nDog & 2 \\\\\nCat & 1 \\\\ \\hline\n\\end{tabular}"
,HorizontalRule
@@ -371,15 +371,15 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
,Para [Str "Here",Apostrophe,Str "s",Space,Str "an",Space,Link [Str "inline",Space,Str "link"] ("/script?foo=1&bar=2",""),Str "."]
,Para [Str "Here",Apostrophe,Str "s",Space,Str "an",Space,Link [Str "inline",Space,Str "link",Space,Str "in",Space,Str "pointy",Space,Str "braces"] ("/script?foo=1&bar=2",""),Str "."]
,Header 2 [Str "Autolinks"]
-,Para [Str "With",Space,Str "an",Space,Str "ampersand",Str ":",Space,Link [Code "http://example.com/?foo=1&bar=2"] ("http://example.com/?foo=1&bar=2","")]
+,Para [Str "With",Space,Str "an",Space,Str "ampersand",Str ":",Space,Link [Code ("",["url"],[]) "http://example.com/?foo=1&bar=2"] ("http://example.com/?foo=1&bar=2","")]
,BulletList
[[Plain [Str "In",Space,Str "a",Space,Str "list",Str "?"]]
- ,[Plain [Link [Code "http://example.com/"] ("http://example.com/","")]]
+ ,[Plain [Link [Code ("",["url"],[]) "http://example.com/"] ("http://example.com/","")]]
,[Plain [Str "It",Space,Str "should",Str "."]]]
-,Para [Str "An",Space,Str "e",Str "-",Str "mail",Space,Str "address",Str ":",Space,Link [Code "nobody@nowhere.net"] ("mailto:nobody@nowhere.net","")]
+,Para [Str "An",Space,Str "e",Str "-",Str "mail",Space,Str "address",Str ":",Space,Link [Code ("",["url"],[]) "nobody@nowhere.net"] ("mailto:nobody@nowhere.net","")]
,BlockQuote
- [Para [Str "Blockquoted",Str ":",Space,Link [Code "http://example.com/"] ("http://example.com/","")]]
-,Para [Str "Auto",Str "-",Str "links",Space,Str "should",Space,Str "not",Space,Str "occur",Space,Str "here",Str ":",Space,Code "<http://example.com/>"]
+ [Para [Str "Blockquoted",Str ":",Space,Link [Code ("",["url"],[]) "http://example.com/"] ("http://example.com/","")]]
+,Para [Str "Auto",Str "-",Str "links",Space,Str "should",Space,Str "not",Space,Str "occur",Space,Str "here",Str ":",Space,Code ("",[],[]) "<http://example.com/>"]
,CodeBlock ("",[],[]) "or here: <http://example.com/>"
,HorizontalRule
,Header 1 [Str "Images"]
@@ -388,7 +388,7 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "movie",Space,Image [Str "movie"] ("movie.jpg",""),Space,Str "icon",Str "."]
,HorizontalRule
,Header 1 [Str "Footnotes"]
-,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "footnote",Space,Str "reference",Str ",",Note [Para [Str "Here",Space,Str "is",Space,Str "the",Space,Str "footnote",Str ".",Space,Str "It",Space,Str "can",Space,Str "go",Space,Str "anywhere",Space,Str "after",Space,Str "the",Space,Str "footnote",Space,Str "reference",Str ".",Space,Str "It",Space,Str "need",Space,Str "not",Space,Str "be",Space,Str "placed",Space,Str "at",Space,Str "the",Space,Str "end",Space,Str "of",Space,Str "the",Space,Str "document",Str "."]],Space,Str "and",Space,Str "another",Str ".",Note [Para [Str "Here",Apostrophe,Str "s",Space,Str "the",Space,Str "long",Space,Str "note",Str ".",Space,Str "This",Space,Str "one",Space,Str "contains",Space,Str "multiple",Space,Str "blocks",Str "."],Para [Str "Subsequent",Space,Str "blocks",Space,Str "are",Space,Str "indented",Space,Str "to",Space,Str "show",Space,Str "that",Space,Str "they",Space,Str "belong",Space,Str "to",Space,Str "the",Space,Str "footnote",Space,Str "(",Str "as",Space,Str "with",Space,Str "list",Space,Str "items",Str ")",Str "."],CodeBlock ("",[],[]) " { <code> }",Para [Str "If",Space,Str "you",Space,Str "want",Str ",",Space,Str "you",Space,Str "can",Space,Str "indent",Space,Str "every",Space,Str "line",Str ",",Space,Str "but",Space,Str "you",Space,Str "can",Space,Str "also",Space,Str "be",Space,Str "lazy",Space,Str "and",Space,Str "just",Space,Str "indent",Space,Str "the",Space,Str "first",Space,Str "line",Space,Str "of",Space,Str "each",Space,Str "block",Str "."]],Space,Str "This",Space,Str "should",Space,Emph [Str "not"],Space,Str "be",Space,Str "a",Space,Str "footnote",Space,Str "reference",Str ",",Space,Str "because",Space,Str "it",Space,Str "contains",Space,Str "a",Space,Str "space",Str ".",Str "[",Str "^",Str "my",Space,Str "note",Str "]",Space,Str "Here",Space,Str "is",Space,Str "an",Space,Str "inline",Space,Str "note",Str ".",Note [Para [Str "This",Space,Str "is",Space,Emph [Str "easier"],Space,Str "to",Space,Str "type",Str ".",Space,Str "Inline",Space,Str "notes",Space,Str "may",Space,Str "contain",Space,Link [Str "links"] ("http://google.com",""),Space,Str "and",Space,Code "]",Space,Str "verbatim",Space,Str "characters",Str ",",Space,Str "as",Space,Str "well",Space,Str "as",Space,Str "[",Str "bracketed",Space,Str "text",Str "]",Str "."]]]
+,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "footnote",Space,Str "reference",Str ",",Note [Para [Str "Here",Space,Str "is",Space,Str "the",Space,Str "footnote",Str ".",Space,Str "It",Space,Str "can",Space,Str "go",Space,Str "anywhere",Space,Str "after",Space,Str "the",Space,Str "footnote",Space,Str "reference",Str ".",Space,Str "It",Space,Str "need",Space,Str "not",Space,Str "be",Space,Str "placed",Space,Str "at",Space,Str "the",Space,Str "end",Space,Str "of",Space,Str "the",Space,Str "document",Str "."]],Space,Str "and",Space,Str "another",Str ".",Note [Para [Str "Here",Apostrophe,Str "s",Space,Str "the",Space,Str "long",Space,Str "note",Str ".",Space,Str "This",Space,Str "one",Space,Str "contains",Space,Str "multiple",Space,Str "blocks",Str "."],Para [Str "Subsequent",Space,Str "blocks",Space,Str "are",Space,Str "indented",Space,Str "to",Space,Str "show",Space,Str "that",Space,Str "they",Space,Str "belong",Space,Str "to",Space,Str "the",Space,Str "footnote",Space,Str "(",Str "as",Space,Str "with",Space,Str "list",Space,Str "items",Str ")",Str "."],CodeBlock ("",[],[]) " { <code> }",Para [Str "If",Space,Str "you",Space,Str "want",Str ",",Space,Str "you",Space,Str "can",Space,Str "indent",Space,Str "every",Space,Str "line",Str ",",Space,Str "but",Space,Str "you",Space,Str "can",Space,Str "also",Space,Str "be",Space,Str "lazy",Space,Str "and",Space,Str "just",Space,Str "indent",Space,Str "the",Space,Str "first",Space,Str "line",Space,Str "of",Space,Str "each",Space,Str "block",Str "."]],Space,Str "This",Space,Str "should",Space,Emph [Str "not"],Space,Str "be",Space,Str "a",Space,Str "footnote",Space,Str "reference",Str ",",Space,Str "because",Space,Str "it",Space,Str "contains",Space,Str "a",Space,Str "space",Str ".",Str "[",Str "^",Str "my",Space,Str "note",Str "]",Space,Str "Here",Space,Str "is",Space,Str "an",Space,Str "inline",Space,Str "note",Str ".",Note [Para [Str "This",Space,Str "is",Space,Emph [Str "easier"],Space,Str "to",Space,Str "type",Str ".",Space,Str "Inline",Space,Str "notes",Space,Str "may",Space,Str "contain",Space,Link [Str "links"] ("http://google.com",""),Space,Str "and",Space,Code ("",[],[]) "]",Space,Str "verbatim",Space,Str "characters",Str ",",Space,Str "as",Space,Str "well",Space,Str "as",Space,Str "[",Str "bracketed",Space,Str "text",Str "]",Str "."]]]
,BlockQuote
[Para [Str "Notes",Space,Str "can",Space,Str "go",Space,Str "in",Space,Str "quotes",Str ".",Note [Para [Str "In",Space,Str "quote",Str "."]]]]
,OrderedList (1,Decimal,Period)
diff --git a/tests/textile-reader.native b/tests/textile-reader.native
index fad1c0972..8c276d194 100644
--- a/tests/textile-reader.native
+++ b/tests/textile-reader.native
@@ -26,7 +26,7 @@ Pandoc (Meta {docTitle = [], docAuthors = [], docDate = []})
,Para [Str "And",Str ":"]
,CodeBlock ("",[],[]) " this code block is indented by two tabs\n\n These should not be escaped: \\$ \\\\ \\> \\[ \\{"
,CodeBlock ("",[],[]) "Code block with .bc\n continued\n @</\\\n"
-,Para [Str "Inline",Space,Str "code",Str ":",Space,Code "<tt>",Str ",",Space,Code "@",Str "."]
+,Para [Str "Inline",Space,Str "code",Str ":",Space,Code ("",[],[]) "<tt>",Str ",",Space,Code ("",[],[]) "@",Str "."]
,Header 1 [Str "Lists"]
,Header 2 [Str "Unordered"]
,Para [Str "Asterisks",Space,Str "tight",Str ":"]
diff --git a/tests/writer.html b/tests/writer.html
index f2c850c81..60f5f4a45 100644
--- a/tests/writer.html
+++ b/tests/writer.html
@@ -1024,7 +1024,7 @@ document.write('<a h'+'ref'+'="ma'+'ilto'+':'+e+'">'+'Email link'+'<\/'+'a'+'>')
>Autolinks</h2
><p
>With an ampersand: <a href="http://example.com/?foo=1&amp;bar=2"
- ><code
+ ><code class="url"
>http://example.com/?foo=1&amp;bar=2</code
></a
></p
@@ -1033,7 +1033,7 @@ document.write('<a h'+'ref'+'="ma'+'ilto'+':'+e+'">'+'Email link'+'<\/'+'a'+'>')
>In a list?</li
><li
><a href="http://example.com/"
- ><code
+ ><code class="url"
>http://example.com/</code
></a
></li
@@ -1054,7 +1054,7 @@ document.write('<a h'+'ref'+'="ma'+'ilto'+':'+e+'">'+'<code>'+e+'</code>'+'<\/'+
><blockquote
><p
>Blockquoted: <a href="http://example.com/"
- ><code
+ ><code class="url"
>http://example.com/</code
></a
></p
diff --git a/tests/writer.native b/tests/writer.native
index d8d62264e..879cb24fc 100644
--- a/tests/writer.native
+++ b/tests/writer.native
@@ -276,7 +276,7 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
,Para [Str "So",Space,Str "is",Space,Strong [Emph [Str "this"]],Space,Str "word",Str "."]
,Para [Strong [Emph [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em",Str "."]]]
,Para [Str "So",Space,Str "is",Space,Strong [Emph [Str "this"]],Space,Str "word",Str "."]
-,Para [Str "This",Space,Str "is",Space,Str "code",Str ":",Space,Code ">",Str ",",Space,Code "$",Str ",",Space,Code "\\",Str ",",Space,Code "\\$",Str ",",Space,Code "<html>",Str "."]
+,Para [Str "This",Space,Str "is",Space,Str "code",Str ":",Space,Code ("",[],[]) ">",Str ",",Space,Code ("",[],[]) "$",Str ",",Space,Code ("",[],[]) "\\",Str ",",Space,Code ("",[],[]) "\\$",Str ",",Space,Code ("",[],[]) "<html>",Str "."]
,Para [Strikeout [Str "This",Space,Str "is",Space,Emph [Str "strikeout"],Str "."]]
,Para [Str "Superscripts",Str ":",Space,Str "a",Superscript [Str "bc"],Str "d",Space,Str "a",Superscript [Emph [Str "hello"]],Space,Str "a",Superscript [Str "hello",Str "\160",Str "there"],Str "."]
,Para [Str "Subscripts",Str ":",Space,Str "H",Subscript [Str "2"],Str "O",Str ",",Space,Str "H",Subscript [Str "23"],Str "O",Str ",",Space,Str "H",Subscript [Str "many",Str "\160",Str "of",Str "\160",Str "them"],Str "O",Str "."]
@@ -287,7 +287,7 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
,Para [Quoted SingleQuote [Str "A"],Str ",",Space,Quoted SingleQuote [Str "B"],Str ",",Space,Str "and",Space,Quoted SingleQuote [Str "C"],Space,Str "are",Space,Str "letters",Str "."]
,Para [Quoted SingleQuote [Str "Oak",Str ","],Space,Quoted SingleQuote [Str "elm",Str ","],Space,Str "and",Space,Quoted SingleQuote [Str "beech"],Space,Str "are",Space,Str "names",Space,Str "of",Space,Str "trees",Str ".",Space,Str "So",Space,Str "is",Space,Quoted SingleQuote [Str "pine",Str "."]]
,Para [Quoted SingleQuote [Str "He",Space,Str "said",Str ",",Space,Quoted DoubleQuote [Str "I",Space,Str "want",Space,Str "to",Space,Str "go",Str "."]],Space,Str "Were",Space,Str "you",Space,Str "alive",Space,Str "in",Space,Str "the",Space,Str "70",Apostrophe,Str "s",Str "?"]
-,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "quoted",Space,Quoted SingleQuote [Code "code"],Space,Str "and",Space,Str "a",Space,Quoted DoubleQuote [Link [Str "quoted",Space,Str "link"] ("http://example.com/?foo=1&bar=2","")],Str "."]
+,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "quoted",Space,Quoted SingleQuote [Code ("",[],[]) "code"],Space,Str "and",Space,Str "a",Space,Quoted DoubleQuote [Link [Str "quoted",Space,Str "link"] ("http://example.com/?foo=1&bar=2","")],Str "."]
,Para [Str "Some",Space,Str "dashes",Str ":",Space,Str "one",EmDash,Str "two",Space,EmDash,Space,Str "three",EmDash,Str "four",Space,EmDash,Space,Str "five",Str "."]
,Para [Str "Dashes",Space,Str "between",Space,Str "numbers",Str ":",Space,Str "5",EnDash,Str "7",Str ",",Space,Str "255",EnDash,Str "66",Str ",",Space,Str "1987",EnDash,Str "1999",Str "."]
,Para [Str "Ellipses",Ellipses,Str "and",Ellipses,Str "and",Ellipses,Str "."]
@@ -304,10 +304,10 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
,[Plain [Str "Here",Apostrophe,Str "s",Space,Str "one",Space,Str "that",Space,Str "has",Space,Str "a",Space,Str "line",Space,Str "break",Space,Str "in",Space,Str "it",Str ":",Space,Math InlineMath "\\alpha + \\omega \\times x^2",Str "."]]]
,Para [Str "These",Space,Str "shouldn",Apostrophe,Str "t",Space,Str "be",Space,Str "math",Str ":"]
,BulletList
- [[Plain [Str "To",Space,Str "get",Space,Str "the",Space,Str "famous",Space,Str "equation",Str ",",Space,Str "write",Space,Code "$e = mc^2$",Str "."]]
+ [[Plain [Str "To",Space,Str "get",Space,Str "the",Space,Str "famous",Space,Str "equation",Str ",",Space,Str "write",Space,Code ("",[],[]) "$e = mc^2$",Str "."]]
,[Plain [Str "$",Str "22",Str ",",Str "000",Space,Str "is",Space,Str "a",Space,Emph [Str "lot"],Space,Str "of",Space,Str "money",Str ".",Space,Str "So",Space,Str "is",Space,Str "$",Str "34",Str ",",Str "000",Str ".",Space,Str "(",Str "It",Space,Str "worked",Space,Str "if",Space,Quoted DoubleQuote [Str "lot"],Space,Str "is",Space,Str "emphasized",Str ".",Str ")"]]
,[Plain [Str "Shoes",Space,Str "(",Str "$",Str "20",Str ")",Space,Str "and",Space,Str "socks",Space,Str "(",Str "$",Str "5",Str ")",Str "."]]
- ,[Plain [Str "Escaped",Space,Code "$",Str ":",Space,Str "$",Str "73",Space,Emph [Str "this",Space,Str "should",Space,Str "be",Space,Str "emphasized"],Space,Str "23",Str "$",Str "."]]]
+ ,[Plain [Str "Escaped",Space,Code ("",[],[]) "$",Str ":",Space,Str "$",Str "73",Space,Emph [Str "this",Space,Str "should",Space,Str "be",Space,Str "emphasized"],Space,Str "23",Str "$",Str "."]]]
,Para [Str "Here",Apostrophe,Str "s",Space,Str "a",Space,Str "LaTeX",Space,Str "table",Str ":"]
,RawBlock "latex" "\\begin{tabular}{|l|l|}\\hline\nAnimal & Number \\\\ \\hline\nDog & 2 \\\\\nCat & 1 \\\\ \\hline\n\\end{tabular}"
,HorizontalRule
@@ -371,15 +371,15 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
,Para [Str "Here",Apostrophe,Str "s",Space,Str "an",Space,Link [Str "inline",Space,Str "link"] ("/script?foo=1&bar=2",""),Str "."]
,Para [Str "Here",Apostrophe,Str "s",Space,Str "an",Space,Link [Str "inline",Space,Str "link",Space,Str "in",Space,Str "pointy",Space,Str "braces"] ("/script?foo=1&bar=2",""),Str "."]
,Header 2 [Str "Autolinks"]
-,Para [Str "With",Space,Str "an",Space,Str "ampersand",Str ":",Space,Link [Code "http://example.com/?foo=1&bar=2"] ("http://example.com/?foo=1&bar=2","")]
+,Para [Str "With",Space,Str "an",Space,Str "ampersand",Str ":",Space,Link [Code ("",["url"],[]) "http://example.com/?foo=1&bar=2"] ("http://example.com/?foo=1&bar=2","")]
,BulletList
[[Plain [Str "In",Space,Str "a",Space,Str "list",Str "?"]]
- ,[Plain [Link [Code "http://example.com/"] ("http://example.com/","")]]
+ ,[Plain [Link [Code ("",["url"],[]) "http://example.com/"] ("http://example.com/","")]]
,[Plain [Str "It",Space,Str "should",Str "."]]]
-,Para [Str "An",Space,Str "e",Str "-",Str "mail",Space,Str "address",Str ":",Space,Link [Code "nobody@nowhere.net"] ("mailto:nobody@nowhere.net","")]
+,Para [Str "An",Space,Str "e",Str "-",Str "mail",Space,Str "address",Str ":",Space,Link [Code ("",["url"],[]) "nobody@nowhere.net"] ("mailto:nobody@nowhere.net","")]
,BlockQuote
- [Para [Str "Blockquoted",Str ":",Space,Link [Code "http://example.com/"] ("http://example.com/","")]]
-,Para [Str "Auto",Str "-",Str "links",Space,Str "should",Space,Str "not",Space,Str "occur",Space,Str "here",Str ":",Space,Code "<http://example.com/>"]
+ [Para [Str "Blockquoted",Str ":",Space,Link [Code ("",["url"],[]) "http://example.com/"] ("http://example.com/","")]]
+,Para [Str "Auto",Str "-",Str "links",Space,Str "should",Space,Str "not",Space,Str "occur",Space,Str "here",Str ":",Space,Code ("",[],[]) "<http://example.com/>"]
,CodeBlock ("",[],[]) "or here: <http://example.com/>"
,HorizontalRule
,Header 1 [Str "Images"]
@@ -388,7 +388,7 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite"], docA
,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "movie",Space,Image [Str "movie"] ("movie.jpg",""),Space,Str "icon",Str "."]
,HorizontalRule
,Header 1 [Str "Footnotes"]
-,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "footnote",Space,Str "reference",Str ",",Note [Para [Str "Here",Space,Str "is",Space,Str "the",Space,Str "footnote",Str ".",Space,Str "It",Space,Str "can",Space,Str "go",Space,Str "anywhere",Space,Str "after",Space,Str "the",Space,Str "footnote",Space,Str "reference",Str ".",Space,Str "It",Space,Str "need",Space,Str "not",Space,Str "be",Space,Str "placed",Space,Str "at",Space,Str "the",Space,Str "end",Space,Str "of",Space,Str "the",Space,Str "document",Str "."]],Space,Str "and",Space,Str "another",Str ".",Note [Para [Str "Here",Apostrophe,Str "s",Space,Str "the",Space,Str "long",Space,Str "note",Str ".",Space,Str "This",Space,Str "one",Space,Str "contains",Space,Str "multiple",Space,Str "blocks",Str "."],Para [Str "Subsequent",Space,Str "blocks",Space,Str "are",Space,Str "indented",Space,Str "to",Space,Str "show",Space,Str "that",Space,Str "they",Space,Str "belong",Space,Str "to",Space,Str "the",Space,Str "footnote",Space,Str "(",Str "as",Space,Str "with",Space,Str "list",Space,Str "items",Str ")",Str "."],CodeBlock ("",[],[]) " { <code> }",Para [Str "If",Space,Str "you",Space,Str "want",Str ",",Space,Str "you",Space,Str "can",Space,Str "indent",Space,Str "every",Space,Str "line",Str ",",Space,Str "but",Space,Str "you",Space,Str "can",Space,Str "also",Space,Str "be",Space,Str "lazy",Space,Str "and",Space,Str "just",Space,Str "indent",Space,Str "the",Space,Str "first",Space,Str "line",Space,Str "of",Space,Str "each",Space,Str "block",Str "."]],Space,Str "This",Space,Str "should",Space,Emph [Str "not"],Space,Str "be",Space,Str "a",Space,Str "footnote",Space,Str "reference",Str ",",Space,Str "because",Space,Str "it",Space,Str "contains",Space,Str "a",Space,Str "space",Str ".",Str "[",Str "^",Str "my",Space,Str "note",Str "]",Space,Str "Here",Space,Str "is",Space,Str "an",Space,Str "inline",Space,Str "note",Str ".",Note [Para [Str "This",Space,Str "is",Space,Emph [Str "easier"],Space,Str "to",Space,Str "type",Str ".",Space,Str "Inline",Space,Str "notes",Space,Str "may",Space,Str "contain",Space,Link [Str "links"] ("http://google.com",""),Space,Str "and",Space,Code "]",Space,Str "verbatim",Space,Str "characters",Str ",",Space,Str "as",Space,Str "well",Space,Str "as",Space,Str "[",Str "bracketed",Space,Str "text",Str "]",Str "."]]]
+,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "footnote",Space,Str "reference",Str ",",Note [Para [Str "Here",Space,Str "is",Space,Str "the",Space,Str "footnote",Str ".",Space,Str "It",Space,Str "can",Space,Str "go",Space,Str "anywhere",Space,Str "after",Space,Str "the",Space,Str "footnote",Space,Str "reference",Str ".",Space,Str "It",Space,Str "need",Space,Str "not",Space,Str "be",Space,Str "placed",Space,Str "at",Space,Str "the",Space,Str "end",Space,Str "of",Space,Str "the",Space,Str "document",Str "."]],Space,Str "and",Space,Str "another",Str ".",Note [Para [Str "Here",Apostrophe,Str "s",Space,Str "the",Space,Str "long",Space,Str "note",Str ".",Space,Str "This",Space,Str "one",Space,Str "contains",Space,Str "multiple",Space,Str "blocks",Str "."],Para [Str "Subsequent",Space,Str "blocks",Space,Str "are",Space,Str "indented",Space,Str "to",Space,Str "show",Space,Str "that",Space,Str "they",Space,Str "belong",Space,Str "to",Space,Str "the",Space,Str "footnote",Space,Str "(",Str "as",Space,Str "with",Space,Str "list",Space,Str "items",Str ")",Str "."],CodeBlock ("",[],[]) " { <code> }",Para [Str "If",Space,Str "you",Space,Str "want",Str ",",Space,Str "you",Space,Str "can",Space,Str "indent",Space,Str "every",Space,Str "line",Str ",",Space,Str "but",Space,Str "you",Space,Str "can",Space,Str "also",Space,Str "be",Space,Str "lazy",Space,Str "and",Space,Str "just",Space,Str "indent",Space,Str "the",Space,Str "first",Space,Str "line",Space,Str "of",Space,Str "each",Space,Str "block",Str "."]],Space,Str "This",Space,Str "should",Space,Emph [Str "not"],Space,Str "be",Space,Str "a",Space,Str "footnote",Space,Str "reference",Str ",",Space,Str "because",Space,Str "it",Space,Str "contains",Space,Str "a",Space,Str "space",Str ".",Str "[",Str "^",Str "my",Space,Str "note",Str "]",Space,Str "Here",Space,Str "is",Space,Str "an",Space,Str "inline",Space,Str "note",Str ".",Note [Para [Str "This",Space,Str "is",Space,Emph [Str "easier"],Space,Str "to",Space,Str "type",Str ".",Space,Str "Inline",Space,Str "notes",Space,Str "may",Space,Str "contain",Space,Link [Str "links"] ("http://google.com",""),Space,Str "and",Space,Code ("",[],[]) "]",Space,Str "verbatim",Space,Str "characters",Str ",",Space,Str "as",Space,Str "well",Space,Str "as",Space,Str "[",Str "bracketed",Space,Str "text",Str "]",Str "."]]]
,BlockQuote
[Para [Str "Notes",Space,Str "can",Space,Str "go",Space,Str "in",Space,Str "quotes",Str ".",Note [Para [Str "In",Space,Str "quote",Str "."]]]]
,OrderedList (1,Decimal,Period)