Changed footnote syntax to conform to the de facto standard

for markdown footnotes.  References are now like this[^1]
rather than like this^(1).  There are corresponding changes
in the footnotes themselves.  See the updated README for
more details.


git-svn-id: https://pandoc.googlecode.com/svn/trunk@230 788f1e2b-df1e-0410-8736-df70ead52e1b
This commit is contained in:
fiddlosopher 2006-12-19 07:30:36 +00:00
parent a8bbd950e5
commit 3a6296acae
12 changed files with 89 additions and 77 deletions

26
README
View file

@ -341,23 +341,25 @@ appear as `[link]` if there's no reference for `link`. If you want
Pandoc's markdown allows footnotes, using the following syntax:
here is a footnote reference,^(1) and another.^(longnote)
Here is a footnote reference,[^1] and another.[^longnote]
^(1) Here is the footnote. It can go anywhere in the document,
[^1]: Here is the footnote. It can go anywhere in the document,
except in embedded contexts like block quotes or lists.
^(longnote) Here's the other note. This one contains multiple
[^longnote]: Here's the other note. This one contains multiple
blocks.
^
^ Caret characters are used to indicate that the blocks all belong
to a single footnote (as with block quotes).
^
^ If you want, you can use a caret at the beginning of every line,
^ as with blockquotes, but all that you need is a caret at the
^ beginning of the first line of the block and any preceding
^ blank lines.
Footnote references may not contain spaces, tabs, or newlines.
Subsequent blocks are indented to show that they belong to
the previous footnote.
{ some.code }
The whole block can be indented, or just the first line.
In this way, multi-block footnotes work just like multi-block
list items in markdown.
The identifiers in footnote references may not contain spaces, tabs,
or newlines.
## Embedded HTML

View file

@ -124,7 +124,7 @@ parseBlocks = do
result <- manyTill block eof
return result
block = choice [ codeBlock, referenceKey, note, header, hrule, list, blockQuote, rawHtmlBlocks,
block = choice [ codeBlock, note, referenceKey, header, hrule, list, blockQuote, rawHtmlBlocks,
rawLaTeXEnvironment, para, plain, blankBlock, nullBlock ] <?> "block"
--
@ -200,19 +200,31 @@ codeBlock = do
-- note block
--
rawLine = try (do
notFollowedBy' blankline
contents <- many1 nonEndline
end <- option "" (do
newline
option "" indentSpaces
return "\n")
return (contents ++ end))
rawLines = do
lines <- many1 rawLine
return (concat lines)
note = try (do
(NoteRef ref) <- noteRef
char ':'
skipSpaces
raw <- sepBy (many (choice [nonEndline,
(try (do {endline; notFollowedBy (char noteStart); return '\n'}))
])) (try (do {newline; char noteStart; option ' ' (char ' ')}))
newline
blanklines
-- parse the extracted block, which may contain various block elements:
skipEndline
raw <- sepBy rawLines (try (do {blankline; indentSpaces}))
option "" blanklines
-- parse the extracted text, which may contain various block elements:
state <- getState
let parsed = case runParser parseBlocks (state {stateParserContext = BlockQuoteState}) "block" ((joinWithSep "\n" raw) ++ "\n\n") of
Left err -> error $ "Raw block:\n" ++ show raw ++ "\nError:\n" ++ show err
Right result -> result
Right result -> result
return (Note ref parsed))
--
@ -398,8 +410,8 @@ text = choice [ math, strong, emph, code2, code1, str, linebreak, tabchar,
inline = choice [ rawLaTeXInline, escapedChar, special, hyphens, text, ltSign, symbol ] <?> "inline"
special = choice [ link, referenceLink, rawHtmlInline, autoLink,
image, noteRef ] <?> "link, inline html, note, or image"
special = choice [ noteRef, link, referenceLink, rawHtmlInline, autoLink,
image ] <?> "link, inline html, note, or image"
escapedChar = escaped anyChar
@ -505,6 +517,7 @@ endline =
-- a reference label for a link
reference = do
char labelStart
notFollowedBy (char noteStart)
label <- manyTill inline (char labelEnd)
return (normalizeSpaces label)
@ -575,7 +588,8 @@ image =
return (Image label src))
noteRef = try (do
char labelStart
char noteStart
ref <- between (char '(') (char ')') (many1 (noneOf " \t\n)"))
ref <- manyTill (noneOf " \t\n") (char labelEnd)
return (NoteRef ref))

View file

@ -76,8 +76,8 @@ blockToMarkdown tabStop (Note ref lst) =
else
let first = head lns
rest = tail lns in
text ("^(" ++ (escapeString ref) ++ ") ") <> (text first) $$ (vcat $
map (\line -> (text "^ ") <> (text line)) rest) <> (text "\n")
text ("[^" ++ (escapeString ref) ++ "]: ") <> (text first) $$ (vcat $
map (\line -> (text " ") <> (text line)) rest) <> (text "\n")
blockToMarkdown tabStop (Key txt (Src src tit)) =
text " " <> char '[' <> inlineListToMarkdown txt <> char ']' <> text ": " <> text src <>
(if tit /= "" then (text (" \"" ++ (escapeLinkTitle tit) ++ "\"")) else empty)
@ -145,4 +145,4 @@ inlineToMarkdown (Image alternate (Ref [])) =
inlineToMarkdown (Image alternate (Ref ref)) =
char '!' <> char '[' <> inlineListToMarkdown alternate <> char ']' <>
char '[' <> inlineListToMarkdown ref <> char ']'
inlineToMarkdown (NoteRef ref) = char '^' <> char '(' <> text (escapeString ref) <> char ')'
inlineToMarkdown (NoteRef ref) = text "[^" <> text (escapeString ref) <> char ']'

View file

@ -318,12 +318,12 @@ Pandoc (Meta [Str "Pandoc",Space,Str "Test",Space,Str "Suite"] ["John MacFarlane
, Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "movie",Space,Image [Str "movie"] (Src "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",NoteRef "1",Str ",",Space,Str "and",Space,Str "another",NoteRef "longnote",Str ".",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 "(my",Space,Str "note)."]
, Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "footnote",Space,Str "reference",NoteRef "1",Str ",",Space,Str "and",Space,Str "another",NoteRef "longnote",Str ".",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 "]",Str "."]
, Note "1"
[ 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 "in",Space,Str "the",Space,Str "document,",Space,Str "not",Space,Str "just",Space,Str "at",Space,Str "the",Space,Str "end."] ]
, Note "longnote"
[ Para [Str "Here's",Space,Str "the",Space,Str "other",Space,Str "note.",Space,Str "This",Space,Str "one",Space,Str "contains",Space,Str "multiple",Space,Str "blocks."]
, Para [Str "Caret",Space,Str "characters",Space,Str "are",Space,Str "used",Space,Str "to",Space,Str "indicate",Space,Str "that",Space,Str "the",Space,Str "blocks",Space,Str "all",Space,Str "belong",Space,Str "to",Space,Str "a",Space,Str "single",Space,Str "footnote",Space,Str "(as",Space,Str "with",Space,Str "block",Space,Str "quotes)."]
, 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 "use",Space,Str "a",Space,Str "caret",Space,Str "at",Space,Str "the",Space,Str "beginning",Space,Str "of",Space,Str "every",Space,Str "line,",Space,Str "as",Space,Str "with",Space,Str "blockquotes,",Space,Str "but",Space,Str "all",Space,Str "that",Space,Str "you",Space,Str "need",Space,Str "is",Space,Str "a",Space,Str "caret",Space,Str "at",Space,Str "the",Space,Str "beginning",Space,Str "of",Space,Str "the",Space,Str "first",Space,Str "line",Space,Str "of",Space,Str "the",Space,Str "block",Space,Str "and",Space,Str "any",Space,Str "preceding",Space,Str "blank",Space,Str "lines."] ] ]
, 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."] ] ]

View file

@ -590,22 +590,20 @@ Here is a movie ![movie](movie.jpg) icon.
# Footnotes
Here is a footnote reference^(1), and another^(longnote).
Here is a footnote reference[^1], and another[^longnote].
This should *not* be a footnote reference, because it
contains a space^(my note).
contains a space[^my note].
^(1) Here is the footnote. It can go anywhere in the document,
[^1]: Here is the footnote. It can go anywhere in the document,
not just at the end.
^(longnote) Here's the other note. This one contains multiple
[^longnote]: Here's the other note. This one contains multiple
blocks.
^
^ Caret characters are used to indicate that the blocks all belong
to a single footnote (as with block quotes).
^
^ { <code> }
^
^ If you want, you can use a caret at the beginning of every line,
^ as with blockquotes, but all that you need is a caret at the
^ beginning of the first line of the block and any preceding
^ blank lines.
Subsequent blocks are indented to show that they belong to the
footnote (as with list items).
{ <code> }
If you want, you can indent every line, but you can also be
lazy and just indent the first line of each block.

View file

@ -438,17 +438,17 @@ Cat &amp; 1 \\ \hline
<p>Here is a movie <img src="movie.jpg" alt="movie"> icon.</p>
<hr />
<h1>Footnotes</h1>
<p>Here is a footnote reference<span class="pandocNoteRef"><a name="ref_1" href="#note_1">(1)</a></span>, and another<span class="pandocNoteRef"><a name="ref_longnote" href="#note_longnote">(longnote)</a></span>. This should <em>not</em> be a footnote reference, because it contains a space^(my note).</p>
<p>Here is a footnote reference<span class="pandocNoteRef"><a name="ref_1" href="#note_1">(1)</a></span>, and another<span class="pandocNoteRef"><a name="ref_longnote" href="#note_longnote">(longnote)</a></span>. This should <em>not</em> be a footnote reference, because it contains a space[^my note].</p>
<div class="pandocNote">
<p class="first"><span class="pandocNoteMarker"><a name="note_1" href="#ref_1">(1)</a></span> Here is the footnote. It can go anywhere in the document, not just at the end.</p>
</div>
<div class="pandocNote">
<p class="first"><span class="pandocNoteMarker"><a name="note_longnote" href="#ref_longnote">(longnote)</a></span> Here's the other note. This one contains multiple blocks.</p>
<p>Caret characters are used to indicate that the blocks all belong to a single footnote (as with block quotes).</p>
<p>Subsequent blocks are indented to show that they belong to the footnote (as with list items).</p>
<pre><code> { &lt;code> }
</code></pre>
<p>If you want, you can use a caret at the beginning of every line, as with blockquotes, but all that you need is a caret at the beginning of the first line of the block and any preceding blank lines.</p>
<p>If you want, you can indent every line, but you can also be lazy and just indent the first line of each block.</p>
</div>
</body>

View file

@ -569,12 +569,12 @@ Here is a movie \includegraphics{movie.jpg} icon.
Here is a footnote reference\footnote{Here is the footnote. It can go anywhere in the document, not just at the end.}, and another\footnote{Here's the other note. This one contains multiple blocks.
Caret characters are used to indicate that the blocks all belong to a single footnote (as with block quotes).
Subsequent blocks are indented to show that they belong to the footnote (as with list items).
\begin{verbatim}
{ <code> }
\end{verbatim}
If you want, you can use a caret at the beginning of every line, as with blockquotes, but all that you need is a caret at the beginning of the first line of the block and any preceding blank lines.}. This should \emph{not} be a footnote reference, because it contains a space\^{}(my note).
If you want, you can indent every line, but you can also be lazy and just indent the first line of each block.}. This should \emph{not} be a footnote reference, because it contains a space[\^{}my note].
\end{document}

View file

@ -607,21 +607,20 @@ Here is a movie ![movie](movie.jpg) icon.
# Footnotes
Here is a footnote reference^(1), and another^(longnote). This
Here is a footnote reference[^1], and another[^longnote]. This
should *not* be a footnote reference, because it contains a
space\^(my note).
space[\^my note].
^(1) Here is the footnote. It can go anywhere in the document, not just
^ at the end.
[^1]: Here is the footnote. It can go anywhere in the document, not just
at the end.
^(longnote) Here's the other note. This one contains multiple blocks.
^
^ Caret characters are used to indicate that the blocks all belong to
^ a single footnote (as with block quotes).
^
^ { <code> }
^
^ If you want, you can use a caret at the beginning of every line, as
^ with blockquotes, but all that you need is a caret at the beginning
^ of the first line of the block and any preceding blank lines.
[^longnote]: Here's the other note. This one contains multiple blocks.
Subsequent blocks are indented to show that they belong to the
footnote (as with list items).
{ <code> }
If you want, you can indent every line, but you can also be lazy
and just indent the first line of each block.

View file

@ -318,12 +318,12 @@ Pandoc (Meta [Str "Pandoc",Space,Str "Test",Space,Str "Suite"] ["John MacFarlane
, Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "movie",Space,Image [Str "movie"] (Src "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",NoteRef "1",Str ",",Space,Str "and",Space,Str "another",NoteRef "longnote",Str ".",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 "(my",Space,Str "note)."]
, Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "footnote",Space,Str "reference",NoteRef "1",Str ",",Space,Str "and",Space,Str "another",NoteRef "longnote",Str ".",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 "]",Str "."]
, Note "1"
[ 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 "in",Space,Str "the",Space,Str "document,",Space,Str "not",Space,Str "just",Space,Str "at",Space,Str "the",Space,Str "end."] ]
, Note "longnote"
[ Para [Str "Here's",Space,Str "the",Space,Str "other",Space,Str "note.",Space,Str "This",Space,Str "one",Space,Str "contains",Space,Str "multiple",Space,Str "blocks."]
, Para [Str "Caret",Space,Str "characters",Space,Str "are",Space,Str "used",Space,Str "to",Space,Str "indicate",Space,Str "that",Space,Str "the",Space,Str "blocks",Space,Str "all",Space,Str "belong",Space,Str "to",Space,Str "a",Space,Str "single",Space,Str "footnote",Space,Str "(as",Space,Str "with",Space,Str "block",Space,Str "quotes)."]
, 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 "use",Space,Str "a",Space,Str "caret",Space,Str "at",Space,Str "the",Space,Str "beginning",Space,Str "of",Space,Str "every",Space,Str "line,",Space,Str "as",Space,Str "with",Space,Str "blockquotes,",Space,Str "but",Space,Str "all",Space,Str "that",Space,Str "you",Space,Str "need",Space,Str "is",Space,Str "a",Space,Str "caret",Space,Str "at",Space,Str "the",Space,Str "beginning",Space,Str "of",Space,Str "the",Space,Str "first",Space,Str "line",Space,Str "of",Space,Str "the",Space,Str "block",Space,Str "and",Space,Str "any",Space,Str "preceding",Space,Str "blank",Space,Str "lines."] ] ]
, 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."] ] ]

View file

@ -697,7 +697,7 @@ Footnotes
Here is a footnote reference [1]_, and another [longnote]_. This
should *not* be a footnote reference, because it contains a
space^(my note).
space[^my note].
.. [1]
Here is the footnote. It can go anywhere in the document, not just
@ -706,16 +706,15 @@ space^(my note).
.. [longnote]
Here's the other note. This one contains multiple blocks.
Caret characters are used to indicate that the blocks all belong to
a single footnote (as with block quotes).
Subsequent blocks are indented to show that they belong to the
footnote (as with list items).
::
{ <code> }
If you want, you can use a caret at the beginning of every line, as
with blockquotes, but all that you need is a caret at the beginning
of the first line of the block and any preceding blank lines.
If you want, you can indent every line, but you can also be lazy
and just indent the first line of each block.
.. _embedded link: /url

View file

@ -369,9 +369,9 @@ http://example.com/
{\pard \f0 \sa180 \li0 \fi0 \b \fs36 Footnotes\par}
{\pard \f0 \sa180 \li0 \fi0 Here is a footnote reference{\super\chftn}{\*\footnote\chftn\~\plain\pard {\pard \f0 \sa180 \li0 \fi0 Here is the footnote. It can go anywhere in the document, not just at the end.\par}
}, and another{\super\chftn}{\*\footnote\chftn\~\plain\pard {\pard \f0 \sa180 \li0 \fi0 Here's the other note. This one contains multiple blocks.\par}
{\pard \f0 \sa180 \li0 \fi0 Caret characters are used to indicate that the blocks all belong to a single footnote (as with block quotes).\par}
{\pard \f0 \sa180 \li0 \fi0 Subsequent blocks are indented to show that they belong to the footnote (as with list items).\par}
{\pard \f0 \sa180 \li0 \fi0 \f1 \{ <code> \}\par}
{\pard \f0 \sa180 \li0 \fi0 If you want, you can use a caret at the beginning of every line, as with blockquotes, but all that you need is a caret at the beginning of the first line of the block and any preceding blank lines.\par}
}. This should {\i not} be a footnote reference, because it contains a space^(my note).\par}
{\pard \f0 \sa180 \li0 \fi0 If you want, you can indent every line, but you can also be lazy and just indent the first line of each block.\par}
}. This should {\i not} be a footnote reference, because it contains a space[^my note].\par}
}

View file

@ -438,17 +438,17 @@ Cat &amp; 1 \\ \hline
<p>Here is a movie <img src="movie.jpg" alt="movie"> icon.</p>
<hr />
<h1>Footnotes</h1>
<p>Here is a footnote reference<span class="pandocNoteRef"><a name="ref_1" href="#note_1">(1)</a></span>, and another<span class="pandocNoteRef"><a name="ref_longnote" href="#note_longnote">(longnote)</a></span>. This should <em>not</em> be a footnote reference, because it contains a space^(my note).</p>
<p>Here is a footnote reference<span class="pandocNoteRef"><a name="ref_1" href="#note_1">(1)</a></span>, and another<span class="pandocNoteRef"><a name="ref_longnote" href="#note_longnote">(longnote)</a></span>. This should <em>not</em> be a footnote reference, because it contains a space[^my note].</p>
<div class="pandocNote">
<p class="first"><span class="pandocNoteMarker"><a name="note_1" href="#ref_1">(1)</a></span> Here is the footnote. It can go anywhere in the document, not just at the end.</p>
</div>
<div class="pandocNote">
<p class="first"><span class="pandocNoteMarker"><a name="note_longnote" href="#ref_longnote">(longnote)</a></span> Here&rsquo;s the other note. This one contains multiple blocks.</p>
<p>Caret characters are used to indicate that the blocks all belong to a single footnote (as with block quotes).</p>
<p>Subsequent blocks are indented to show that they belong to the footnote (as with list items).</p>
<pre><code> { &lt;code> }
</code></pre>
<p>If you want, you can use a caret at the beginning of every line, as with blockquotes, but all that you need is a caret at the beginning of the first line of the block and any preceding blank lines.</p>
<p>If you want, you can indent every line, but you can also be lazy and just indent the first line of each block.</p>
</div>
</body>