aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--README4
-rw-r--r--pandoc.cabal4
-rw-r--r--src/Text/Pandoc/Parsing.hs2
-rw-r--r--src/Text/Pandoc/Readers/DocBook.hs54
-rw-r--r--src/Text/Pandoc/Readers/Org.hs24
-rw-r--r--src/Text/Pandoc/Writers/Docx.hs5
-rw-r--r--src/Text/Pandoc/Writers/DokuWiki.hs8
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs4
-rw-r--r--tests/Tests/Old.hs2
-rw-r--r--tests/Tests/Readers/Markdown.hs5
-rw-r--r--tests/Tests/Readers/Org.hs9
-rw-r--r--tests/docbook-reader.docbook22
-rw-r--r--tests/docbook-reader.native69
-rw-r--r--tests/dokuwiki_external_images.dokuwiki1
-rw-r--r--tests/dokuwiki_external_images.native1
-rw-r--r--tests/writer.latex2
16 files changed, 152 insertions, 64 deletions
diff --git a/README b/README
index ccd01bba3..de688aa1c 100644
--- a/README
+++ b/README
@@ -2380,6 +2380,10 @@ be followed by a link title, in quotes.)
There can be no space between the bracketed part and the parenthesized part.
The link text can contain formatting (such as emphasis), but the title cannot.
+Email addresses in inline links are not autodetected, so they have to be
+prefixed with `mailto`:
+
+ [Write me!](mailto:sam@green.eggs.ham)
### Reference links ###
diff --git a/pandoc.cabal b/pandoc.cabal
index 20e06121b..6abc8b0bc 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -170,6 +170,8 @@ Extra-Source-Files:
tests/lhs-test.html+lhs
tests/lhs-test.fragment.html+lhs
tests/pipe-tables.txt
+ tests/dokuwiki_external_images.dokuwiki
+ tests/dokuwiki_external_images.native
tests/dokuwiki_multiblock_table.dokuwiki
tests/dokuwiki_multiblock_table.native
tests/fb2/*.markdown
@@ -447,7 +449,7 @@ Test-Suite test-pandoc
Tests.Writers.Plain
Tests.Writers.AsciiDoc
Tests.Writers.LaTeX
- Ghc-Options: -rtsopts -Wall -fno-warn-unused-do-bind
+ Ghc-Options: -rtsopts -Wall -fno-warn-unused-do-bind -threaded
Default-Language: Haskell98
benchmark benchmark-pandoc
diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs
index 4503e31fd..18f38e564 100644
--- a/src/Text/Pandoc/Parsing.hs
+++ b/src/Text/Pandoc/Parsing.hs
@@ -454,7 +454,7 @@ uri = try $ do
let percentEscaped = try $ char '%' >> skipMany1 (satisfy isHexDigit)
let entity = () <$ characterReference
let punct = skipMany1 (char ',')
- <|> () <$ (satisfy (\c -> not (isSpace c) && c /= '<'))
+ <|> () <$ (satisfy (\c -> not (isSpace c) && c /= '<' && c /= '>'))
let uriChunk = skipMany1 wordChar
<|> percentEscaped
<|> entity
diff --git a/src/Text/Pandoc/Readers/DocBook.hs b/src/Text/Pandoc/Readers/DocBook.hs
index 59ff3e717..663960a87 100644
--- a/src/Text/Pandoc/Readers/DocBook.hs
+++ b/src/Text/Pandoc/Readers/DocBook.hs
@@ -70,8 +70,8 @@ List of all DocBook tags, with [x] indicating implemented,
[x] book - A book
[x] bookinfo - Meta-information for a Book
[x] bridgehead - A free-floating heading
-[ ] callout - A “called out” description of a marked Area
-[ ] calloutlist - A list of Callouts
+[x] callout - A “called out” description of a marked Area
+[x] calloutlist - A list of Callouts
[x] caption - A caption
[x] caution - A note of caution
[x] chapter - A chapter, as of a book
@@ -81,7 +81,7 @@ List of all DocBook tags, with [x] indicating implemented,
[ ] citerefentry - A citation to a reference page
[ ] citetitle - The title of a cited work
[ ] city - The name of a city in an address
-[ ] classname - The name of a class, in the object-oriented programming sense
+[x] classname - The name of a class, in the object-oriented programming sense
[ ] classsynopsis - The syntax summary for a class definition
[ ] classsynopsisinfo - Information supplementing the contents of
a ClassSynopsis
@@ -169,9 +169,9 @@ List of all DocBook tags, with [x] indicating implemented,
[ ] guibutton - The text on a button in a GUI
[ ] guiicon - Graphic and/or text appearing as a icon in a GUI
[ ] guilabel - The text of a label in a GUI
-[ ] guimenu - The name of a menu in a GUI
-[ ] guimenuitem - The name of a terminal menu item in a GUI
-[ ] guisubmenu - The name of a submenu in a GUI
+[x] guimenu - The name of a menu in a GUI
+[x] guimenuitem - The name of a terminal menu item in a GUI
+[x] guisubmenu - The name of a submenu in a GUI
[ ] hardware - A physical part of a computer system
[ ] highlights - A summary of the main points of the discussed component
[ ] holder - The name of the individual or organization that holds a copyright
@@ -206,10 +206,10 @@ List of all DocBook tags, with [x] indicating implemented,
other dingbat
[ ] itermset - A set of index terms in the meta-information of a document
[ ] jobtitle - The title of an individual in an organization
-[ ] keycap - The text printed on a key on a keyboard
+[x] keycap - The text printed on a key on a keyboard
[ ] keycode - The internal, frequently numeric, identifier for a key
on a keyboard
-[ ] keycombo - A combination of input actions
+[x] keycombo - A combination of input actions
[ ] keysym - The symbolic name of a key on a keyboard
[ ] keyword - One of a set of keywords describing the content of a document
[ ] keywordset - A set of keywords describing the content of a document
@@ -237,7 +237,7 @@ List of all DocBook tags, with [x] indicating implemented,
[x] mediaobject - A displayed media object (video, audio, image, etc.)
[ ] mediaobjectco - A media object that contains callouts
[x] member - An element of a simple list
-[ ] menuchoice - A selection or series of selections from a menu
+[x] menuchoice - A selection or series of selections from a menu
[ ] methodname - The name of a method
[ ] methodparam - Parameters to a method
[ ] methodsynopsis - A syntax summary for a method
@@ -471,7 +471,7 @@ List of all DocBook tags, with [x] indicating implemented,
[ ] token - A unit of information
[x] tr - A row in an HTML table
[ ] trademark - A trademark
-[ ] type - The classification of a value
+[x] type - The classification of a value
[x] ulink - A link that addresses its target by means of a URL
(Uniform Resource Locator)
[x] uri - A Uniform Resource Identifier
@@ -603,7 +603,7 @@ isBlockElement (Elem e) = qName (elName e) `elem` blocktags
"important","caution","note","tip","warning","qandadiv",
"question","answer","abstract","itemizedlist","orderedlist",
"variablelist","article","book","table","informaltable",
- "screen","programlisting","example"]
+ "screen","programlisting","example","calloutlist"]
isBlockElement _ = False
-- Trim leading and trailing newline characters
@@ -712,6 +712,7 @@ parseBlock (Elem e) =
"question" -> addToStart (strong (str "Q:") <> str " ") <$> getBlocks e
"answer" -> addToStart (strong (str "A:") <> str " ") <$> getBlocks e
"abstract" -> blockQuote <$> getBlocks e
+ "calloutlist" -> bulletList <$> callouts
"itemizedlist" -> bulletList <$> listitems
"orderedlist" -> do
let listStyle = case attrValue "numeration" e of
@@ -772,11 +773,6 @@ parseBlock (Elem e) =
x -> [x]
return $ codeBlockWith (attrValue "id" e, classes', [])
$ trimNl $ strContentRecursive e
- strContentRecursive = strContent . (\e' -> e'{ elContent =
- map elementToStr $ elContent e' })
- elementToStr :: Content -> Content
- elementToStr (Elem e') = Text $ CData CDataText (strContentRecursive e') Nothing
- elementToStr x = x
parseBlockquote = do
attrib <- case filterChild (named "attribution") e of
Nothing -> return mempty
@@ -785,6 +781,7 @@ parseBlock (Elem e) =
contents <- getBlocks e
return $ blockQuote (contents <> attrib)
listitems = mapM getBlocks $ filterChildren (named "listitem") e
+ callouts = mapM getBlocks $ filterChildren (named "callout") e
deflistitems = mapM parseVarListEntry $ filterChildren
(named "varlistentry") e
parseVarListEntry e' = do
@@ -871,13 +868,22 @@ parseBlock (Elem e) =
Nothing -> return mempty
modify $ \st -> st{ dbSectionLevel = n }
b <- getBlocks e
+ let ident = attrValue "id" e
modify $ \st -> st{ dbSectionLevel = n - 1 }
- return $ header n' headerText <> b
+ return $ headerWith (ident,[],[]) n' headerText <> b
metaBlock = acceptingMetadata (getBlocks e) >> return mempty
getInlines :: Element -> DB Inlines
getInlines e' = (trimInlines . mconcat) <$> (mapM parseInline $ elContent e')
+strContentRecursive :: Element -> String
+strContentRecursive = strContent .
+ (\e' -> e'{ elContent = map elementToStr $ elContent e' })
+
+elementToStr :: Content -> Content
+elementToStr (Elem e') = Text $ CData CDataText (strContentRecursive e') Nothing
+elementToStr x = x
+
parseInline :: Content -> DB Inlines
parseInline (Text (CData _ s _)) = return $ text s
parseInline (CRef ref) =
@@ -901,6 +907,7 @@ parseInline (Elem e) =
else doubleQuoted contents
"simplelist" -> simpleList
"segmentedlist" -> segmentedList
+ "classname" -> codeWithLang
"code" -> codeWithLang
"filename" -> codeWithLang
"literal" -> codeWithLang
@@ -920,6 +927,10 @@ parseInline (Elem e) =
"constant" -> codeWithLang
"userinput" -> codeWithLang
"varargs" -> return $ code "(...)"
+ "keycap" -> return (str $ strContent e)
+ "keycombo" -> keycombo <$> (mapM parseInline $ elContent e)
+ "menuchoice" -> menuchoice <$> (mapM parseInline $
+ filter isGuiMenu $ elContent e)
"xref" -> return $ str "?" -- so at least you know something is there
"email" -> return $ link ("mailto:" ++ strContent e) ""
$ str $ strContent e
@@ -959,7 +970,7 @@ parseInline (Elem e) =
let classes' = case attrValue "language" e of
"" -> []
l -> [l]
- return $ codeWith (attrValue "id" e,classes',[]) $ strContent e
+ return $ codeWith (attrValue "id" e,classes',[]) $ strContentRecursive e
simpleList = (mconcat . intersperse (str "," <> space)) <$> mapM getInlines
(filterChildren (named "member") e)
segmentedList = do
@@ -974,3 +985,10 @@ parseInline (Elem e) =
then mempty
else strong tit <> linebreak
return $ linebreak <> tit' <> segs
+ keycombo = spanWith ("",["keycombo"],[]) .
+ mconcat . intersperse (str "+")
+ menuchoice = spanWith ("",["menuchoice"],[]) .
+ mconcat . intersperse (text " > ")
+ isGuiMenu (Elem x) = named "guimenu" x || named "guisubmenu" x ||
+ named "guimenuitem" x
+ isGuiMenu _ = False
diff --git a/src/Text/Pandoc/Readers/Org.hs b/src/Text/Pandoc/Readers/Org.hs
index 579e38a38..440b6d144 100644
--- a/src/Text/Pandoc/Readers/Org.hs
+++ b/src/Text/Pandoc/Readers/Org.hs
@@ -1142,20 +1142,25 @@ applyCustomLinkFormat link = do
formatter <- M.lookup linkType <$> asksF orgStateLinkFormatters
return $ maybe link ($ drop 1 rest) formatter
+-- TODO: might be a lot smarter/cleaner to use parsec and ADTs for this kind
+-- of parsing.
linkToInlinesF :: String -> Inlines -> F Inlines
linkToInlinesF s =
case s of
"" -> pure . B.link "" ""
('#':_) -> pure . B.link s ""
_ | isImageFilename s -> const . pure $ B.image s "" ""
+ _ | isFileLink s -> pure . B.link (dropLinkType s) ""
_ | isUri s -> pure . B.link s ""
- _ | isRelativeFilePath s -> pure . B.link s ""
_ | isAbsoluteFilePath s -> pure . B.link ("file://" ++ s) ""
- _ -> \title -> do
- anchorB <- (s `elem`) <$> asksF orgStateAnchorIds
- if anchorB
- then pure $ B.link ('#':s) "" title
- else pure $ B.emph title
+ _ | isRelativeFilePath s -> pure . B.link s ""
+ _ -> internalLink s
+
+isFileLink :: String -> Bool
+isFileLink s = ("file:" `isPrefixOf` s) && not ("file://" `isPrefixOf` s)
+
+dropLinkType :: String -> String
+dropLinkType = tail . snd . break (== ':')
isRelativeFilePath :: String -> Bool
isRelativeFilePath s = (("./" `isPrefixOf` s) || ("../" `isPrefixOf` s)) &&
@@ -1178,6 +1183,13 @@ isImageFilename filename =
imageExtensions = [ "jpeg" , "jpg" , "png" , "gif" , "svg" ]
protocols = [ "file", "http", "https" ]
+internalLink :: String -> Inlines -> F Inlines
+internalLink link title = do
+ anchorB <- (link `elem`) <$> asksF orgStateAnchorIds
+ if anchorB
+ then return $ B.link ('#':link) "" title
+ else return $ B.emph title
+
-- | Parse an anchor like @<<anchor-id>>@ and return an empty span with
-- @anchor-id@ set as id. Legal anchors in org-mode are defined through
-- @org-target-regexp@, which is fairly liberal. Since no link is created if
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index f8e8cc34d..5b9cc62ab 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -715,7 +715,8 @@ blockToOpenXML opts (Table caption aligns widths headers rows) = do
let mkgridcol w = mknode "w:gridCol"
[("w:w", show (floor (textwidth * w) :: Integer))] ()
return $
- mknode "w:tbl" []
+ caption' ++
+ [mknode "w:tbl" []
( mknode "w:tblPr" []
( mknode "w:tblStyle" [("w:val","TableNormal")] () :
mknode "w:tblW" [("w:type", "pct"), ("w:w", show rowwidth)] () :
@@ -727,7 +728,7 @@ blockToOpenXML opts (Table caption aligns widths headers rows) = do
else map mkgridcol widths)
: [ mkrow True headers' | not (all null headers) ] ++
map (mkrow False) rows'
- ) : caption'
+ )]
blockToOpenXML opts (BulletList lst) = do
let marker = BulletMarker
addList marker
diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs
index 74418aa7e..eed45a965 100644
--- a/src/Text/Pandoc/Writers/DokuWiki.hs
+++ b/src/Text/Pandoc/Writers/DokuWiki.hs
@@ -134,7 +134,9 @@ blockToDokuWiki opts (Para [Image txt (src,'f':'i':'g':':':tit)]) = do
let opt = if null txt
then ""
else "|" ++ if null tit then capt else tit ++ capt
- return $ "{{:" ++ src ++ opt ++ "}}\n"
+ -- Relative links fail isURI and receive a colon
+ prefix = if isURI src then "" else ":"
+ return $ "{{" ++ prefix ++ src ++ opt ++ "}}\n"
blockToDokuWiki opts (Para inlines) = do
indent <- stIndent <$> ask
@@ -478,7 +480,9 @@ inlineToDokuWiki opts (Image alt (source, tit)) = do
("", []) -> ""
("", _ ) -> "|" ++ alt'
(_ , _ ) -> "|" ++ tit
- return $ "{{:" ++ source ++ txt ++ "}}"
+ -- Relative links fail isURI and receive a colon
+ prefix = if isURI source then "" else ":"
+ return $ "{{" ++ prefix ++ source ++ txt ++ "}}"
inlineToDokuWiki opts (Note contents) = do
contents' <- blockListToDokuWiki opts contents
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index ae2f4e907..417317b54 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -746,8 +746,10 @@ inlineToLaTeX (Code (_,classes,_) str) = do
Nothing -> rawCode
Just h -> modify (\st -> st{ stHighlighting = True }) >>
return (text h)
- rawCode = liftM (text . (\s -> "\\texttt{" ++ s ++ "}"))
+ rawCode = liftM (text . (\s -> "\\texttt{" ++ escapeSpaces s ++ "}"))
$ stringToLaTeX CodeString str
+ where
+ escapeSpaces = concatMap (\c -> if c == ' ' then "\\ " else [c])
inlineToLaTeX (Quoted qt lst) = do
contents <- inlineListToLaTeX lst
csquotes <- liftM stCsquotes get
diff --git a/tests/Tests/Old.hs b/tests/Tests/Old.hs
index 0f7b33dd1..5bdf325b1 100644
--- a/tests/Tests/Old.hs
+++ b/tests/Tests/Old.hs
@@ -130,6 +130,8 @@ tests = [ testGroup "markdown"
"dokuwiki_inline_formatting.native" "dokuwiki_inline_formatting.dokuwiki"
, test "multiblock table" ["-r", "native", "-w", "dokuwiki", "-s"]
"dokuwiki_multiblock_table.native" "dokuwiki_multiblock_table.dokuwiki"
+ , test "external images" ["-r", "native", "-w", "dokuwiki", "-s"]
+ "dokuwiki_external_images.native" "dokuwiki_external_images.dokuwiki"
]
, testGroup "opml"
[ test "basic" ["-r", "native", "-w", "opml", "--columns=78", "-s"]
diff --git a/tests/Tests/Readers/Markdown.hs b/tests/Tests/Readers/Markdown.hs
index a7e322306..fdb1a7417 100644
--- a/tests/Tests/Readers/Markdown.hs
+++ b/tests/Tests/Readers/Markdown.hs
@@ -187,6 +187,11 @@ tests = [ testGroup "inline code"
]
, testGroup "bare URIs"
(map testBareLink bareLinkTests)
+ , testGroup "autolinks"
+ [ "with unicode dash following" =:
+ "<http://foo.bar>\8212" =?> para (autolink "http://foo.bar" <>
+ str "\8212")
+ ]
, testGroup "Headers"
[ "blank line before header" =:
"\n# Header\n"
diff --git a/tests/Tests/Readers/Org.hs b/tests/Tests/Readers/Org.hs
index d1f673514..39c40cd45 100644
--- a/tests/Tests/Readers/Org.hs
+++ b/tests/Tests/Readers/Org.hs
@@ -4,7 +4,6 @@ module Tests.Readers.Org (tests) where
import Text.Pandoc.Definition
import Test.Framework
import Tests.Helpers
-import Tests.Arbitrary()
import Text.Pandoc.Builder
import Text.Pandoc
import Data.List (intersperse)
@@ -227,6 +226,14 @@ tests =
, "for", "fnords."
])
+ , "Absolute file link" =:
+ "[[file:///etc/passwd][passwd]]" =?>
+ (para $ link "file:///etc/passwd" "" "passwd")
+
+ , "File link" =:
+ "[[file:target][title]]" =?>
+ (para $ link "target" "" "title")
+
, "Anchor" =:
"<<anchor>> Link here later." =?>
(para $ spanWith ("anchor", [], []) mempty <>
diff --git a/tests/docbook-reader.docbook b/tests/docbook-reader.docbook
index 9ba965d9b..cf5059646 100644
--- a/tests/docbook-reader.docbook
+++ b/tests/docbook-reader.docbook
@@ -509,6 +509,25 @@ These should not be escaped: \$ \\ \&gt; \[ \{
B. Williams
</para>
</sect2>
+ <sect2 id="callout">
+ <title>Callout</title>
+ <para>Simple.</para>
+ <calloutlist>
+ <callout arearefs="loop1-letrec-co" id="loop1-letrec">
+ <para id="x_QA1">A <code>__letrec</code> is equivalent to a normal
+ Haskell &let;.</para>
+ </callout>
+ <callout arearefs="loop1-def-co" id="loop1-def">
+ <para id="x_RA1">&GHC; compiled the body of our list comprehension into
+ a loop named <function>go_s1YC</function>.</para>
+ </callout>
+ <callout arearefs="loop1-pat-empty-co" id="loop1-pat-empty">
+ <para id="x_SA1">If our &case; expression matches the empty list, we
+ return the empty list. This is reassuringly
+ familiar.</para>
+ </callout>
+ </calloutlist>
+ </sect2>
</sect1>
<sect1 id="definition-lists">
<title>Definition Lists</title>
@@ -691,6 +710,9 @@ These should not be escaped: \$ \\ \&gt; \[ \{
<literal>&lt;html&gt;</literal>.
</para>
<para>
+ More code: <classname>Class</classname> and <type>Type</type>
+ </para>
+ <para>
<emphasis role="strikethrough">This is
<emphasis>strikeout</emphasis>.</emphasis>
</para>
diff --git a/tests/docbook-reader.native b/tests/docbook-reader.native
index 90d76b3c2..353a352a2 100644
--- a/tests/docbook-reader.native
+++ b/tests/docbook-reader.native
@@ -1,22 +1,22 @@
Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Space,Str "MacFarlane"],MetaInlines [Str "Anonymous"]]),("date",MetaInlines [Str "July",Space,Str "17,",Space,Str "2006"]),("title",MetaInlines [Str "Pandoc",Space,Str "Test",Space,Str "Suite"])]})
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc.",Space,Str "Most",Space,Str "of",Space,Str "them",Space,Str "are",Space,Str "adapted",Space,Str "from",Space,Str "John",Space,Str "Gruber\8217s",Space,Str "markdown",Space,Str "test",Space,Str "suite."]
-,Header 1 ("",[],[]) [Str "Headers"]
-,Header 2 ("",[],[]) [Str "Level",Space,Str "2",Space,Str "with",Space,Str "an",Space,Link [Str "embedded",Space,Str "link"] ("/url","")]
-,Header 3 ("",[],[]) [Str "Level",Space,Str "3",Space,Str "with",Space,Emph [Str "emphasis"]]
-,Header 4 ("",[],[]) [Str "Level",Space,Str "4"]
-,Header 5 ("",[],[]) [Str "Level",Space,Str "5"]
+,Header 1 ("headers",[],[]) [Str "Headers"]
+,Header 2 ("level-2-with-an-embedded-link",[],[]) [Str "Level",Space,Str "2",Space,Str "with",Space,Str "an",Space,Link [Str "embedded",Space,Str "link"] ("/url","")]
+,Header 3 ("level-3-with-emphasis",[],[]) [Str "Level",Space,Str "3",Space,Str "with",Space,Emph [Str "emphasis"]]
+,Header 4 ("level-4",[],[]) [Str "Level",Space,Str "4"]
+,Header 5 ("level-5",[],[]) [Str "Level",Space,Str "5"]
,Para [Str "Hi."]
-,Header 1 ("",[],[]) [Str "Level",Space,Str "1"]
-,Header 2 ("",[],[]) [Str "Level",Space,Str "2",Space,Str "with",Space,Emph [Str "emphasis"]]
-,Header 3 ("",[],[]) [Str "Level",Space,Str "3"]
+,Header 1 ("level-1",[],[]) [Str "Level",Space,Str "1"]
+,Header 2 ("level-2-with-emphasis",[],[]) [Str "Level",Space,Str "2",Space,Str "with",Space,Emph [Str "emphasis"]]
+,Header 3 ("level-3",[],[]) [Str "Level",Space,Str "3"]
,Para [Str "with",Space,Str "no",Space,Str "blank",Space,Str "line"]
-,Header 2 ("",[],[]) [Str "Level",Space,Str "2"]
+,Header 2 ("level-2",[],[]) [Str "Level",Space,Str "2"]
,Para [Str "with",Space,Str "no",Space,Str "blank",Space,Str "line"]
-,Header 1 ("",[],[]) [Str "Paragraphs"]
+,Header 1 ("paragraphs",[],[]) [Str "Paragraphs"]
,Para [Str "Here\8217s",Space,Str "a",Space,Str "regular",Space,Str "paragraph."]
,Para [Str "In",Space,Str "Markdown",Space,Str "1.0.0",Space,Str "and",Space,Str "earlier.",Space,Str "Version",Space,Str "8.",Space,Str "This",Space,Str "line",Space,Str "turns",Space,Str "into",Space,Str "a",Space,Str "list",Space,Str "item.",Space,Str "Because",Space,Str "a",Space,Str "hard-wrapped",Space,Str "line",Space,Str "in",Space,Str "the",Space,Str "middle",Space,Str "of",Space,Str "a",Space,Str "paragraph",Space,Str "looked",Space,Str "like",Space,Str "a",Space,Str "list",Space,Str "item."]
,Para [Str "Here\8217s",Space,Str "one",Space,Str "with",Space,Str "a",Space,Str "bullet.",Space,Str "*",Space,Str "criminey."]
-,Header 1 ("",[],[]) [Str "Block",Space,Str "Quotes"]
+,Header 1 ("block-quotes",[],[]) [Str "Block",Space,Str "Quotes"]
,Para [Str "E-mail",Space,Str "style:"]
,BlockQuote
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "block",Space,Str "quote.",Space,Str "It",Space,Str "is",Space,Str "pretty",Space,Str "short."]]
@@ -35,13 +35,13 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
[Para [Str "nested"]]]
,Para [Str "This",Space,Str "should",Space,Str "not",Space,Str "be",Space,Str "a",Space,Str "block",Space,Str "quote:",Space,Str "2",Space,Str ">",Space,Str "1."]
,Para [Str "And",Space,Str "a",Space,Str "following",Space,Str "paragraph."]
-,Header 1 ("",[],[]) [Str "Code",Space,Str "Blocks"]
+,Header 1 ("code-blocks",[],[]) [Str "Code",Space,Str "Blocks"]
,Para [Str "Code:"]
,CodeBlock ("",[],[]) "---- (should be four hyphens)\n\nsub status {\n print \"working\";\n}\n\nthis code block is indented by one tab"
,Para [Str "And:"]
,CodeBlock ("",[],[]) " this code block is indented by two tabs\n\nThese should not be escaped: \\$ \\\\ \\> \\[ \\{"
-,Header 1 ("",[],[]) [Str "Lists"]
-,Header 2 ("",[],[]) [Str "Unordered"]
+,Header 1 ("lists",[],[]) [Str "Lists"]
+,Header 2 ("unordered",[],[]) [Str "Unordered"]
,Para [Str "Asterisks",Space,Str "loose:"]
,BulletList
[[Para [Str "asterisk",Space,Str "1"]]
@@ -57,7 +57,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
[[Para [Str "Minus",Space,Str "1"]]
,[Para [Str "Minus",Space,Str "2"]]
,[Para [Str "Minus",Space,Str "3"]]]
-,Header 2 ("",[],[]) [Str "Ordered"]
+,Header 2 ("ordered",[],[]) [Str "Ordered"]
,OrderedList (1,Decimal,DefaultDelim)
[[Para [Str "First"]]
,[Para [Str "Second"]]
@@ -73,7 +73,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,Para [Str "Item",Space,Str "1.",Space,Str "graf",Space,Str "two.",Space,Str "The",Space,Str "quick",Space,Str "brown",Space,Str "fox",Space,Str "jumped",Space,Str "over",Space,Str "the",Space,Str "lazy",Space,Str "dog\8217s",Space,Str "back."]]
,[Para [Str "Item",Space,Str "2."]]
,[Para [Str "Item",Space,Str "3."]]]
-,Header 2 ("",[],[]) [Str "Nested"]
+,Header 2 ("nested",[],[]) [Str "Nested"]
,BulletList
[[Para [Str "Tab"]
,BulletList
@@ -98,14 +98,14 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,[Para [Str "Fie"]]
,[Para [Str "Foe"]]]]
,[Para [Str "Third"]]]
-,Header 2 ("",[],[]) [Str "Tabs",Space,Str "and",Space,Str "spaces"]
+,Header 2 ("tabs-and-spaces",[],[]) [Str "Tabs",Space,Str "and",Space,Str "spaces"]
,BulletList
[[Para [Str "this",Space,Str "is",Space,Str "a",Space,Str "list",Space,Str "item",Space,Str "indented",Space,Str "with",Space,Str "tabs"]]
,[Para [Str "this",Space,Str "is",Space,Str "a",Space,Str "list",Space,Str "item",Space,Str "indented",Space,Str "with",Space,Str "spaces"]
,BulletList
[[Para [Str "this",Space,Str "is",Space,Str "an",Space,Str "example",Space,Str "list",Space,Str "item",Space,Str "indented",Space,Str "with",Space,Str "tabs"]]
,[Para [Str "this",Space,Str "is",Space,Str "an",Space,Str "example",Space,Str "list",Space,Str "item",Space,Str "indented",Space,Str "with",Space,Str "spaces"]]]]]
-,Header 2 ("",[],[]) [Str "Fancy",Space,Str "list",Space,Str "markers"]
+,Header 2 ("fancy-list-markers",[],[]) [Str "Fancy",Space,Str "list",Space,Str "markers"]
,OrderedList (2,Decimal,DefaultDelim)
[[Para [Str "begins",Space,Str "with",Space,Str "2"]]
,[Para [Str "and",Space,Str "now",Space,Str "3"]
@@ -134,7 +134,13 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,Para [Str "Should",Space,Str "not",Space,Str "be",Space,Str "a",Space,Str "list",Space,Str "item:"]
,Para [Str "M.A.\160\&2007"]
,Para [Str "B.",Space,Str "Williams"]
-,Header 1 ("",[],[]) [Str "Definition",Space,Str "Lists"]
+,Header 2 ("callout",[],[]) [Str "Callout"]
+,Para [Str "Simple."]
+,BulletList
+ [[Para [Str "A",Space,Code ("",[],[]) "__letrec",Space,Str "is",Space,Str "equivalent",Space,Str "to",Space,Str "a",Space,Str "normal",Space,Str "Haskell",Space,Str "LET."]]
+ ,[Para [Str "GHC",Space,Str "compiled",Space,Str "the",Space,Str "body",Space,Str "of",Space,Str "our",Space,Str "list",Space,Str "comprehension",Space,Str "into",Space,Str "a",Space,Str "loop",Space,Str "named",Space,Code ("",[],[]) "go_s1YC",Str "."]]
+ ,[Para [Str "If",Space,Str "our",Space,Str "CASE",Space,Str "expression",Space,Str "matches",Space,Str "the",Space,Str "empty",Space,Str "list,",Space,Str "we",Space,Str "return",Space,Str "the",Space,Str "empty",Space,Str "list.",Space,Str "This",Space,Str "is",Space,Str "reassuringly",Space,Str "familiar."]]]
+,Header 1 ("definition-lists",[],[]) [Str "Definition",Space,Str "Lists"]
,DefinitionList
[([Str "apple"],
[[Para [Str "red",Space,Str "fruit"]]])
@@ -170,7 +176,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,OrderedList (1,Decimal,DefaultDelim)
[[Para [Str "sublist"]]
,[Para [Str "sublist"]]]]])]
-,Header 1 ("",[],[]) [Str "Inline",Space,Str "Markup"]
+,Header 1 ("inline-markup",[],[]) [Str "Inline",Space,Str "Markup"]
,Para [Str "This",Space,Str "is",Space,Emph [Str "emphasized"],Str ",",Space,Str "and",Space,Str "so",Space,Emph [Str "is",Space,Str "this"],Str "."]
,Para [Str "This",Space,Str "is",Space,Strong [Str "strong"],Str ",",Space,Str "and",Space,Str "so",Space,Strong [Str "is",Space,Str "this"],Str "."]
,Para [Str "An",Space,Emph [Link [Str "emphasized",Space,Str "link"] ("/url","")],Str "."]
@@ -179,20 +185,21 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,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 "More",Space,Str "code:",Space,Code ("",[],[]) "Class",Space,Str "and",Space,Code ("",[],[]) "Type"]
,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\160there"],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\160of\160them"],Str "O."]
,Para [Str "These",Space,Str "should",Space,Str "not",Space,Str "be",Space,Str "superscripts",Space,Str "or",Space,Str "subscripts,",Space,Str "because",Space,Str "of",Space,Str "the",Space,Str "unescaped",Space,Str "spaces:",Space,Str "a^b",Space,Str "c^d,",Space,Str "a~b",Space,Str "c~d."]
-,Header 1 ("",[],[]) [Str "Smart",Space,Str "quotes,",Space,Str "ellipses,",Space,Str "dashes"]
+,Header 1 ("smart-quotes-ellipses-dashes",[],[]) [Str "Smart",Space,Str "quotes,",Space,Str "ellipses,",Space,Str "dashes"]
,Para [Quoted DoubleQuote [Str "Hello,"],Space,Str "said",Space,Str "the",Space,Str "spider.",Space,Quoted DoubleQuote [Quoted SingleQuote [Str "Shelob"],Space,Str "is",Space,Str "my",Space,Str "name."]]
,Para [Quoted DoubleQuote [Str "A"],Str ",",Space,Quoted DoubleQuote [Str "B"],Str ",",Space,Str "and",Space,Quoted DoubleQuote [Str "C"],Space,Str "are",Space,Str "letters."]
,Para [Quoted DoubleQuote [Str "He",Space,Str "said,",Space,Quoted SingleQuote [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\8217s?"]
,Para [Str "Some",Space,Str "dashes:",Space,Str "one\8212two",Space,Str "\8212",Space,Str "three\8212four",Space,Str "\8212",Space,Str "five."]
,Para [Str "Dashes",Space,Str "between",Space,Str "numbers:",Space,Str "5\8211\&7,",Space,Str "255\8211\&66,",Space,Str "1987\8211\&1999."]
,Para [Str "Ellipses\8230and\8230and\8230."]
-,Header 1 ("",[],[]) []
+,Header 1 ("math",[],[]) []
,Para [Math DisplayMath "e = mc^{2}",Math DisplayMath "1",Space,Math InlineMath "e = mc^{2}",Space,Math DisplayMath "e = mc^{2}"]
-,Header 1 ("",[],[]) [Str "Special",Space,Str "Characters"]
+,Header 1 ("special-characters",[],[]) [Str "Special",Space,Str "Characters"]
,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "unicode:"]
,BulletList
[[Para [Str "I",Space,Str "hat:",Space,Str "\206"]]
@@ -221,8 +228,8 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,Para [Str "Bang:",Space,Str "!"]
,Para [Str "Plus:",Space,Str "+"]
,Para [Str "Minus:",Space,Str "-"]
-,Header 1 ("",[],[]) [Str "Links"]
-,Header 2 ("",[],[]) [Str "Explicit"]
+,Header 1 ("links",[],[]) [Str "Links"]
+,Header 2 ("explicit",[],[]) [Str "Explicit"]
,Para [Str "Just",Space,Str "a",Space,Link [Str "URL"] ("/url/",""),Str "."]
,Para [Link [Str "URL",Space,Str "and",Space,Str "title"] ("/url/",""),Str "."]
,Para [Link [Str "URL",Space,Str "and",Space,Str "title"] ("/url/",""),Str "."]
@@ -232,7 +239,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,Para [Link [Str "with_underscore"] ("/url/with_underscore","")]
,Para [Link [Str "nobody@nowhere.net"] ("mailto:nobody@nowhere.net","")]
,Para [Link [Str "Empty"] ("",""),Str "."]
-,Header 2 ("",[],[]) [Str "Reference"]
+,Header 2 ("reference",[],[]) [Str "Reference"]
,Para [Str "Foo",Space,Link [Str "bar"] ("/url/",""),Str "."]
,Para [Str "Foo",Space,Link [Str "bar"] ("/url/",""),Str "."]
,Para [Str "Foo",Space,Link [Str "bar"] ("/url/",""),Str "."]
@@ -245,12 +252,12 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,CodeBlock ("",[],[]) "[not]: /url"
,Para [Str "Foo",Space,Link [Str "bar"] ("/url/",""),Str "."]
,Para [Str "Foo",Space,Link [Str "biz"] ("/url/",""),Str "."]
-,Header 2 ("",[],[]) [Str "With",Space,Str "ampersands"]
+,Header 2 ("with-ampersands",[],[]) [Str "With",Space,Str "ampersands"]
,Para [Str "Here\8217s",Space,Str "a",Space,Link [Str "link",Space,Str "with",Space,Str "an",Space,Str "ampersand",Space,Str "in",Space,Str "the",Space,Str "URL"] ("http://example.com/?foo=1&bar=2",""),Str "."]
,Para [Str "Here\8217s",Space,Str "a",Space,Str "link",Space,Str "with",Space,Str "an",Space,Str "amersand",Space,Str "in",Space,Str "the",Space,Str "link",Space,Str "text:",Space,Link [Str "AT&T"] ("http://att.com/",""),Str "."]
,Para [Str "Here\8217s",Space,Str "an",Space,Link [Str "inline",Space,Str "link"] ("/script?foo=1&bar=2",""),Str "."]
,Para [Str "Here\8217s",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"]
+,Header 2 ("autolinks",[],[]) [Str "Autolinks"]
,Para [Str "With",Space,Str "an",Space,Str "ampersand:",Space,Link [Str "http://example.com/?foo=1&bar=2"] ("http://example.com/?foo=1&bar=2","")]
,BulletList
[[Para [Str "In",Space,Str "a",Space,Str "list?"]]
@@ -261,18 +268,18 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
[Para [Str "Blockquoted:",Space,Link [Str "http://example.com/"] ("http://example.com/","")]]
,Para [Str "Auto-links",Space,Str "should",Space,Str "not",Space,Str "occur",Space,Str "here:",Space,Code ("",[],[]) "<http://example.com/>"]
,CodeBlock ("",[],[]) "or here: <http://example.com/>"
-,Header 1 ("",[],[]) [Str "Images"]
+,Header 1 ("images",[],[]) [Str "Images"]
,Para [Str "From",Space,Quoted DoubleQuote [Str "Voyage",Space,Str "dans",Space,Str "la",Space,Str "Lune"],Space,Str "by",Space,Str "Georges",Space,Str "Melies",Space,Str "(1902):"]
,Para [Image [Str "lalune"] ("lalune.jpg","")]
,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "movie",Space,Image [] ("movie.jpg",""),Space,Str "icon."]
-,Header 1 ("",[],[]) [Str "Footnotes"]
+,Header 1 ("footnotes",[],[]) [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\8217s",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.[^my",Space,Str "note]",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 "[bracketed",Space,Str "text]."]]]
,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,DefaultDelim)
[[Para [Str "And",Space,Str "in",Space,Str "list",Space,Str "items.",Note [Para [Str "In",Space,Str "list."]]]]]
,Para [Str "This",Space,Str "paragraph",Space,Str "should",Space,Str "not",Space,Str "be",Space,Str "part",Space,Str "of",Space,Str "the",Space,Str "note,",Space,Str "as",Space,Str "it",Space,Str "is",Space,Str "not",Space,Str "indented."]
-,Header 1 ("",[],[]) [Str "Tables"]
+,Header 1 ("tables",[],[]) [Str "Tables"]
,Para [Str "Simple",Space,Str "table",Space,Str "with",Space,Str "caption:"]
,Table [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax."] [AlignRight,AlignLeft,AlignCenter,AlignLeft] [0.0,0.0,0.0,0.0]
[[Plain [Str "Right"]]
diff --git a/tests/dokuwiki_external_images.dokuwiki b/tests/dokuwiki_external_images.dokuwiki
new file mode 100644
index 000000000..cc7eddcda
--- /dev/null
+++ b/tests/dokuwiki_external_images.dokuwiki
@@ -0,0 +1 @@
+{{https://cooluri.com/image.png|HTTPS image}} {{http://cooluri.com/image.png|HTTP image}} {{ftp://ftp.cooluri.com/image.png|FTP image}} {{file:///tmp/coolimage.png|Filesystem image}} {{:/image.jpg|Relative image 1}} {{:image.jpg|Relative image 2}}
diff --git a/tests/dokuwiki_external_images.native b/tests/dokuwiki_external_images.native
new file mode 100644
index 000000000..c2b8876d3
--- /dev/null
+++ b/tests/dokuwiki_external_images.native
@@ -0,0 +1 @@
+[Para [Image [Str "HTTPS",Space,Str "image"] ("https://cooluri.com/image.png",""),Space,Image [Str "HTTP",Space,Str "image"] ("http://cooluri.com/image.png",""),Space,Image [Str "FTP",Space,Str "image"] ("ftp://ftp.cooluri.com/image.png",""),Space,Image [Str "Filesystem",Space,Str "image"] ("file:///tmp/coolimage.png",""),Space,Image [Str "Relative",Space,Str "image",Space,Str "1"] ("/image.jpg",""),Space,Image [Str "Relative",Space,Str "image",Space,Str "2"] ("image.jpg","")]]
diff --git a/tests/writer.latex b/tests/writer.latex
index a966e374b..82fa3c23f 100644
--- a/tests/writer.latex
+++ b/tests/writer.latex
@@ -734,7 +734,7 @@ These shouldn't be math:
\begin{itemize}
\itemsep1pt\parskip0pt\parsep0pt
\item
- To get the famous equation, write \texttt{\$e = mc\^{}2\$}.
+ To get the famous equation, write \texttt{\$e\ =\ mc\^{}2\$}.
\item
\$22,000 is a \emph{lot} of money. So is \$34,000. (It worked if ``lot'' is
emphasized.)