diff --git a/README b/README
index c59f8880a..8a75d90da 100644
--- a/README
+++ b/README
@@ -349,17 +349,30 @@ Pandoc's markdown allows footnotes, using the following syntax:
 	[^longnote]: Here's the other note.  This one contains multiple
 	blocks.
 
-        Subsequent blocks are indented to show that they belong to
+        Subsequent paragraphs 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 whole paragraph can be indented, or just the first line.
+	    In this way, multi-paragraph footnotes work just like
+	    multi-paragraph list items in markdown.
+
+    This paragraph won't be part of the note.
 
 The identifiers in footnote references may not contain spaces, tabs,
-or newlines.
+or newlines.  These identifiers are used only to correlate the
+footnote reference with the note itself; in the output, footnotes
+will be numbered sequentially.
+
+Inline footnotes are also allowed (though, unlike regular notes,
+they cannot contain multiple paragraphs).  The syntax is as follows:
+
+    Here is an inline note.^[Inlines notes are easier to write, since
+    you don't have to pick an identifier and move down to type the
+    note.]
+
+Inline and regular footnotes may be mixed freely.
 
 ## Embedded HTML
 
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index b31f98ff7..a62ff7b94 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -550,8 +550,7 @@ link = try (do
   url <- manyTill anyChar (char '}')
   char '{'
   label <- manyTill inline (char '}') 
-  ref <- generateReference url ""
-  return (Link (normalizeSpaces label) ref))
+  return (Link (normalizeSpaces label) (Src url "")))
 
 image = try (do
   ("includegraphics", _, args) <- command
@@ -569,11 +568,11 @@ footnote = try (do
     else
       fail "not a footnote or thanks command"
   let contents' = stripFirstAndLast contents
-  let blocks = case runParser parseBlocks defaultParserState "footnote" contents of
+  state <- getState
+  let blocks = case runParser parseBlocks state "footnote" contents of
                  Left err -> error $ "Input:\n" ++ show contents' ++
                              "\nError:\n" ++ show err
                  Right result -> result
-  state <- getState
   let notes = stateNoteBlocks state
   let nextRef  = case notes of
                    []                   -> "1"
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index c47fd771a..51d70e700 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -3,6 +3,8 @@ module Text.Pandoc.Readers.Markdown (
                                      readMarkdown 
                                     ) where
 
+import Data.List ( findIndex, sortBy )
+import Data.Ord ( comparing )
 import Text.ParserCombinators.Pandoc
 import Text.Pandoc.Definition
 import Text.Pandoc.Readers.LaTeX ( rawLaTeXInline, rawLaTeXEnvironment )
@@ -108,13 +110,21 @@ titleBlock = try (do
   option "" blanklines
   return (title, author, date))
 
+-- | Returns the number assigned to a Note block
+numberOfNote :: Block -> Int
+numberOfNote (Note ref _) = (read ref) 
+numberOfNote _ = 0 
+
 parseMarkdown = do
   updateState (\state -> state { stateParseRaw = True }) -- need to parse raw HTML
   (title, author, date) <- option ([],[],"") titleBlock
   blocks <- parseBlocks
+  let blocks' = filter (/= Null) blocks
   state <- getState
   let keys = reverse $ stateKeyBlocks state
-  return (Pandoc (Meta title author date) (blocks ++ keys))
+  let notes = reverse $ stateNoteBlocks state
+  let sortedNotes = sortBy (comparing numberOfNote) notes
+  return (Pandoc (Meta title author date) (blocks' ++ sortedNotes ++ keys))
 
 --
 -- parsing blocks
@@ -202,6 +212,7 @@ codeBlock = do
 
 rawLine = try (do
     notFollowedBy' blankline
+    notFollowedBy' noteMarker
     contents <- many1 nonEndline
     end <- option "" (do
                         newline
@@ -214,7 +225,8 @@ rawLines = do
     return (concat lines)
 
 note = try (do
-    (NoteRef ref) <- noteRef 
+    ref <- noteMarker
+    char ':'
     char ':'
     skipSpaces
     skipEndline
@@ -225,7 +237,12 @@ note = try (do
     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 
-    return (Note ref parsed))
+    let identifiers = stateNoteIdentifiers state
+    case (findIndex (== ref) identifiers) of
+      Just n  -> updateState (\s -> s {stateNoteBlocks = 
+                 (Note (show (n+1)) parsed):(stateNoteBlocks s)})
+      Nothing -> updateState id 
+    return Null)
 
 --
 -- block quotes
@@ -410,7 +427,7 @@ text = choice [ math, strong, emph, code2, code1, str, linebreak, tabchar,
 
 inline = choice [ rawLaTeXInline, escapedChar, special, hyphens, text, ltSign, symbol ] <?> "inline"
 
-special = choice [ noteRef, link, referenceLink, rawHtmlInline, autoLink, 
+special = choice [ noteRef, inlineNote, link, referenceLink, rawHtmlInline, autoLink, 
                    image ] <?> "link, inline html, note, or image"
 
 escapedChar = escaped anyChar
@@ -587,9 +604,27 @@ image =
            (Link label src) <- link
            return (Image label src)) 
 
-noteRef = try (do
+noteMarker = try (do
     char labelStart
     char noteStart
-    ref <- manyTill (noneOf " \t\n") (char labelEnd)
+    manyTill (noneOf " \t\n") (char labelEnd))
+
+noteRef = try (do
+    ref <- noteMarker
+    state <- getState
+    let identifiers = (stateNoteIdentifiers state) ++ [ref] 
+    updateState (\st -> st {stateNoteIdentifiers = identifiers})
+    return (NoteRef (show (length identifiers))))
+
+inlineNote = try (do
+    char noteStart
+    char labelStart
+    contents <- manyTill inline (char labelEnd)
+    state <- getState
+    let identifiers = stateNoteIdentifiers state
+    let ref = show $ (length identifiers) + 1
+    let noteBlocks = stateNoteBlocks state
+    updateState (\st -> st {stateNoteIdentifiers = (identifiers ++ [ref]),
+                            stateNoteBlocks = (Note ref [Para contents]):noteBlocks})
     return (NoteRef ref))
 
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index b3261f02e..a420e3766 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -79,6 +79,7 @@ data ParserState = ParserState
       stateKeyBlocks             :: [Block],        -- ^ List of reference key blocks
       stateKeysUsed              :: [[Inline]],     -- ^ List of references used so far
       stateNoteBlocks            :: [Block],        -- ^ List of note blocks
+      stateNoteIdentifiers       :: [String],       -- ^ List of footnote identifiers, in order encountered
       stateTabStop               :: Int,            -- ^ Tab stop
       stateStandalone            :: Bool,           -- ^ If @True@, parse bibliographic info
       stateTitle                 :: [Inline],       -- ^ Title of document
@@ -90,17 +91,18 @@ data ParserState = ParserState
 
 defaultParserState :: ParserState
 defaultParserState = 
-    ParserState { stateParseRaw      = False,
-                  stateParserContext = NullState,
-                  stateKeyBlocks     = [],
-                  stateKeysUsed      = [],
-                  stateNoteBlocks    = [],
-                  stateTabStop       = 4,
-                  stateStandalone    = False,
-                  stateTitle         = [],
-                  stateAuthors       = [],
-                  stateDate          = [],
-                  stateHeaderTable   = [] }
+    ParserState { stateParseRaw        = False,
+                  stateParserContext   = NullState,
+                  stateKeyBlocks       = [],
+                  stateKeysUsed        = [],
+                  stateNoteBlocks      = [],
+                  stateNoteIdentifiers = [],
+                  stateTabStop         = 4,
+                  stateStandalone      = False,
+                  stateTitle           = [],
+                  stateAuthors         = [],
+                  stateDate            = [],
+                  stateHeaderTable     = [] }
 
 -- | Consolidate @Str@s and @Space@s in an inline list into one big @Str@.
 -- Collapse adjacent @Space@s.
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index d99b70bee..dadd45e39 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -8,7 +8,7 @@ import Text.Html ( stringToHtmlString )
 import Text.Regex ( mkRegex )
 import Numeric ( showHex )
 import Char ( ord )
-import List ( isPrefixOf )
+import Data.List ( isPrefixOf, partition )
 
 -- | Convert Pandoc document to string in HTML format.
 writeHtml :: WriterOptions -> Pandoc -> String
@@ -28,11 +28,23 @@ writeHtml options (Pandoc (Meta title authors date) blocks) =
                      else
                          []
         foot = if (writerStandalone options) then "</body>\n</html>\n" else "" 
+        blocks' = replaceReferenceLinks (titleBlocks ++ blocks)
+        (noteBlocks, blocks'') = partition isNoteBlock blocks' 
         body = (writerIncludeBefore options) ++ 
-               concatMap (blockToHtml options) (replaceReferenceLinks (titleBlocks ++ blocks)) ++
-                             (writerIncludeAfter options) in
+               concatMap (blockToHtml options) blocks'' ++
+               footnoteSection options noteBlocks ++
+               (writerIncludeAfter options) in
     head ++ body ++ foot
 
+-- | Convert list of Note blocks to a footnote <div>.  Assumes notes are sorted.
+footnoteSection :: WriterOptions -> [Block] -> String
+footnoteSection options notes =
+    if null notes 
+      then ""
+      else "<div class=\"footnotes\">\n<hr />\n<ol>\n" ++
+           concatMap (blockToHtml options) notes ++
+           "</ol>\n</div>\n"  
+
 -- | Obfuscate a "mailto:" link using Javascript.
 obfuscateLink :: WriterOptions -> [Inline] -> String -> String
 obfuscateLink options text src =
@@ -127,13 +139,10 @@ blockToHtml options (BlockQuote blocks) =
     else
         "<blockquote>\n" ++ (concatMap (blockToHtml options) blocks) ++ "</blockquote>\n"
 blockToHtml options (Note ref lst) = 
-    let marker = "<span class=\"pandocNoteMarker\"><a name=\"note_" ++ ref ++ 
-                 "\" href=\"#ref_" ++ ref ++ "\">(" ++ ref ++ ")</a></span> " in
     let contents = (concatMap (blockToHtml options) lst) in
-    let contents' = case contents of
-                      ('<':'p':'>':rest) -> "<p class=\"first\">" ++ marker ++ rest ++ "\n"
-                      otherwise -> marker ++ contents ++ "\n" in
-    "<div class=\"pandocNote\">\n" ++ contents' ++ "</div>\n"
+    "<li id=\"fn" ++ ref ++ "\">" ++ contents ++ " <a href=\"#fnref" ++ ref ++ 
+    "\" class=\"footnoteBacklink\" title=\"Jump back to footnote " ++ ref ++ 
+    "\">&#8617;</a></li>" 
 blockToHtml options (Key _ _) = ""
 blockToHtml options (CodeBlock str) = "<pre><code>" ++ (codeStringToHtml str) ++ 
                                       "\n</code></pre>\n"
@@ -196,6 +205,6 @@ inlineToHtml options (Image alternate (Ref [])) =
 inlineToHtml options (Image alternate (Ref ref)) = 
     "![" ++ (inlineListToHtml options alternate) ++ "][" ++ (inlineListToHtml options ref) ++ "]"
 inlineToHtml options (NoteRef ref) = 
-    "<span class=\"pandocNoteRef\"><a name=\"ref_" ++ ref ++ "\" href=\"#note_" ++ ref ++ 
-                                                       "\">(" ++ ref ++ ")</a></span>"
+    "<sup class=\"footnoteRef\" id=\"fnref" ++ ref ++ "\"><a href=\"#fn" ++ ref ++ 
+    "\">" ++ ref ++ "</a></sup>"
 
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index 18a904fac..55d0eb2e1 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -77,7 +77,7 @@ blockToMarkdown tabStop (Note ref lst) =
         let first = head lns
             rest = tail lns in
         text ("[^" ++ (escapeString ref) ++ "]: ") <> (text first) $$ (vcat $
-             map (\line -> (text "    ") <> (text line)) rest) <> (text "\n")
+             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) 
diff --git a/src/headers/HtmlHeader b/src/headers/HtmlHeader
index ac1be8d3a..26b0bad94 100644
--- a/src/headers/HtmlHeader
+++ b/src/headers/HtmlHeader
@@ -4,8 +4,3 @@
 <head>
 <meta http-equiv="Content-Type" content="text/html; charset=UTF-8" />
 <meta name="generator" content="pandoc" />
-<style type="text/css">
-div.pandocNote { border-left: 1px solid grey; padding-left: 1em; }
-span.pandocNoteRef { vertical-align: super; font-size: 80%; }
-span.pandocNoteMarker { }
-</style>
diff --git a/tests/s5.inserts.html b/tests/s5.inserts.html
index 4f998c573..7be33a2c8 100644
--- a/tests/s5.inserts.html
+++ b/tests/s5.inserts.html
@@ -4,11 +4,6 @@
 <head>
 <meta http-equiv="Content-Type" content="text/html; charset=UTF-8" />
 <meta name="generator" content="pandoc" />
-<style type="text/css">
-div.pandocNote { border-left: 1px solid grey; padding-left: 1em; }
-span.pandocNoteRef { vertical-align: super; font-size: 80%; }
-span.pandocNoteMarker { }
-</style>
 <link rel="stylesheet" href="main.css" type="text/css" media="all" />
 STUFF INSERTED
 <meta name="author" content="Sam Smith, Jen Jones" />
diff --git a/tests/testsuite.native b/tests/testsuite.native
index 340e11a5c..910de1f39 100644
--- a/tests/testsuite.native
+++ b/tests/testsuite.native
@@ -318,12 +318,16 @@ 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 "^",Str "my",Space,Str "note",Str "]",Str "."]
+, Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "footnote",Space,Str "reference,",NoteRef "1",Space,Str "and",Space,Str "another.",NoteRef "2",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.",NoteRef "3"]
+, 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."]
 , 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."] ]
+  [ 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."] ]
 
-, 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."]
+, Note "2"
+  [ Para [Str "Here'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."] ] ]
+  , 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."] ]
+, Note "3"
+  [ 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"] (Src "http://google.com" ""),Space,Str "and",Space,Code "]",Space,Str "verbatim",Space,Str "characters."] ]
+ ]
diff --git a/tests/testsuite.txt b/tests/testsuite.txt
index 1beb7aaac..9d6481126 100644
--- a/tests/testsuite.txt
+++ b/tests/testsuite.txt
@@ -590,14 +590,13 @@ 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]  Here is an inline note.^[This
+is *easier* to type.  Inline notes may contain
+[links](http://google.com) and `]` verbatim characters.]
 
-[^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 long note.  This one contains multiple
 blocks.  
 
     Subsequent blocks are indented to show that they belong to the
@@ -607,3 +606,8 @@ footnote (as with list items).
 
     If you want, you can indent every line, but you can also be
     lazy and just indent the first line of each block.
+
+This paragraph should not be part of the note, as it is not indented.
+
+[^1]: Here is the footnote.  It can go anywhere after the footnote
+reference.  It need not be placed at the end of the document.
diff --git a/tests/writer.html b/tests/writer.html
index 37920383b..e8d7c228f 100644
--- a/tests/writer.html
+++ b/tests/writer.html
@@ -4,11 +4,6 @@
 <head>
 <meta http-equiv="Content-Type" content="text/html; charset=UTF-8" />
 <meta name="generator" content="pandoc" />
-<style type="text/css">
-div.pandocNote { border-left: 1px solid grey; padding-left: 1em; }
-span.pandocNoteRef { vertical-align: super; font-size: 80%; }
-span.pandocNoteMarker { }
-</style>
 <meta name="author" content="John MacFarlane, Anonymous" />
 <meta name="date" content="July 17, 2006" />
 <title>Pandoc Test Suite</title>
@@ -438,18 +433,19 @@ 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>
-<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>Here is a footnote reference,<sup class="footnoteRef" id="fnref1"><a href="#fn1">1</a></sup> and another.<sup class="footnoteRef" id="fnref2"><a href="#fn2">2</a></sup> This should <em>not</em> be a footnote reference, because it contains a space.[^my note] Here is an inline note.<sup class="footnoteRef" id="fnref3"><a href="#fn3">3</a></sup></p>
+<p>This paragraph should not be part of the note, as it is not indented.</p>
+<div class="footnotes">
+<hr />
+<ol>
+<li id="fn1"><p>Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document.</p>
+ <a href="#fnref1" class="footnoteBacklink" title="Jump back to footnote 1">&#8617;</a></li><li id="fn2"><p>Here's the long note. This one contains multiple blocks.</p>
 <p>Subsequent blocks are indented to show that they belong to the footnote (as with list items).</p>
 <pre><code>  { &lt;code> }
 </code></pre>
 <p>If you want, you can indent every line, but you can also be lazy and just indent the first line of each block.</p>
-
+ <a href="#fnref2" class="footnoteBacklink" title="Jump back to footnote 2">&#8617;</a></li><li id="fn3"><p>This is <em>easier</em> to type. Inline notes may contain <a href="http://google.com">links</a> and <code>]</code> verbatim characters.</p>
+ <a href="#fnref3" class="footnoteBacklink" title="Jump back to footnote 3">&#8617;</a></li></ol>
 </div>
 </body>
 </html>
diff --git a/tests/writer.latex b/tests/writer.latex
index e892e12e6..c813f511d 100644
--- a/tests/writer.latex
+++ b/tests/writer.latex
@@ -567,14 +567,16 @@ Here is a movie \includegraphics{movie.jpg} icon.
 
 \section{Footnotes}
 
-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.
+Here is a footnote reference,\footnote{Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document.} and another.\footnote{Here's the long note. This one contains multiple blocks.
 
 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 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].
+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] Here is an inline note.\footnote{This is \emph{easier} to type. Inline notes may contain \href{http://google.com}{links} and \verb!]! verbatim characters.}
+
+This paragraph should not be part of the note, as it is not indented.
 
 
 \end{document}
diff --git a/tests/writer.markdown b/tests/writer.markdown
index f84372797..c91546aaa 100644
--- a/tests/writer.markdown
+++ b/tests/writer.markdown
@@ -607,14 +607,17 @@ Here is a movie ![movie](movie.jpg) icon.
 
 # Footnotes
 
-Here is a footnote reference[^1], and another[^longnote]. This
-should *not* be a footnote reference, because it contains a
-space[\^my note].
+Here is a footnote reference,[^1] and another.[^2] This should
+*not* be a footnote reference, because it contains a space.[\^my
+note] Here is an inline note.[^3]
 
-[^1]: Here is the footnote. It can go anywhere in the document, not just
-    at the end.
+This paragraph should not be part of the note, as it is not
+indented.
 
-[^longnote]: Here's the other note. This one contains multiple blocks.
+[^1]: Here is the footnote. It can go anywhere after the footnote
+    reference. It need not be placed at the end of the document.
+
+[^2]: Here's the long note. This one contains multiple blocks.
     
     Subsequent blocks are indented to show that they belong to the
     footnote (as with list items).
@@ -624,3 +627,6 @@ 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.
 
+[^3]: This is *easier* to type. Inline notes may contain
+    [links](http://google.com) and `]` verbatim characters.
+
diff --git a/tests/writer.native b/tests/writer.native
index 340e11a5c..910de1f39 100644
--- a/tests/writer.native
+++ b/tests/writer.native
@@ -318,12 +318,16 @@ 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 "^",Str "my",Space,Str "note",Str "]",Str "."]
+, Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "footnote",Space,Str "reference,",NoteRef "1",Space,Str "and",Space,Str "another.",NoteRef "2",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.",NoteRef "3"]
+, 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."]
 , 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."] ]
+  [ 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."] ]
 
-, 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."]
+, Note "2"
+  [ Para [Str "Here'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."] ] ]
+  , 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."] ]
+, Note "3"
+  [ 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"] (Src "http://google.com" ""),Space,Str "and",Space,Code "]",Space,Str "verbatim",Space,Str "characters."] ]
+ ]
diff --git a/tests/writer.rst b/tests/writer.rst
index 6a9f3b997..327b780ab 100644
--- a/tests/writer.rst
+++ b/tests/writer.rst
@@ -695,16 +695,19 @@ Here is a movie |movie| icon.
 Footnotes
 =========
 
-Here is a footnote reference [1]_, and another [longnote]_. This
-should *not* be a footnote reference, because it contains a
-space[^my note].
+Here is a footnote reference, [1]_ and another. [2]_ This should
+*not* be a footnote reference, because it contains a space.[^my
+note] Here is an inline note. [3]_
+
+This paragraph should not be part of the note, as it is not
+indented.
 
 .. [1] 
-   Here is the footnote. It can go anywhere in the document, not just
-   at the end.
+   Here is the footnote. It can go anywhere after the footnote
+   reference. It need not be placed at the end of the document.
 
-.. [longnote] 
-   Here's the other note. This one contains multiple blocks.
+.. [2] 
+   Here's the long note. This one contains multiple blocks.
 
    Subsequent blocks are indented to show that they belong to the
    footnote (as with list items).
@@ -716,6 +719,10 @@ 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.
 
+.. [3] 
+   This is *easier* to type. Inline notes may contain `links`_ and
+   ``]`` verbatim characters.
+
 
 .. _embedded link: /url
 .. _emphasized link: /url
@@ -740,4 +747,5 @@ space[^my note].
 .. _nobody@nowhere.net: mailto:nobody@nowhere.net
 .. |lalune| image:: lalune.jpg
 .. |movie| image:: movie.jpg
+.. _links: http://google.com
 
diff --git a/tests/writer.rtf b/tests/writer.rtf
index 0a1d4b5c8..073ec3054 100644
--- a/tests/writer.rtf
+++ b/tests/writer.rtf
@@ -367,11 +367,16 @@ http://example.com/
 {\pard \f0 \sa180 \li0 \fi0 Here is a movie {\cf1 [image: movie.jpg]\cf0} icon.\par}
 {\pard \f0 \sa180 \li0 \fi0 \qc \emdash\emdash\emdash\emdash\emdash\par}
 {\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 Here is a footnote reference,{\super\chftn}{\*\footnote\chftn\~\plain\pard {\pard \f0 \sa180 \li0 \fi0 Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document.\par}
+} and another.{\super\chftn}{\*\footnote\chftn\~\plain\pard {\pard \f0 \sa180 \li0 \fi0 Here's the long note. This one contains multiple blocks.\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 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}
+} This should {\i not}  be a footnote reference, because it contains a space.[^my note] Here is an inline note.{\super\chftn}{\*\footnote\chftn\~\plain\pard {\pard \f0 \sa180 \li0 \fi0 This is {\i easier}  to type. Inline notes may contain {\field{\*\fldinst{HYPERLINK "http://google.com"}}{\fldrslt{\ul
+links
+}}}
+ and {\f1 ]}  verbatim characters.\par}
+}\par}
+{\pard \f0 \sa180 \li0 \fi0 This paragraph should not be part of the note, as it is not indented.\par}
 
 }
diff --git a/tests/writer.smart.html b/tests/writer.smart.html
index a177b05cf..b63e78968 100644
--- a/tests/writer.smart.html
+++ b/tests/writer.smart.html
@@ -4,11 +4,6 @@
 <head>
 <meta http-equiv="Content-Type" content="text/html; charset=UTF-8" />
 <meta name="generator" content="pandoc" />
-<style type="text/css">
-div.pandocNote { border-left: 1px solid grey; padding-left: 1em; }
-span.pandocNoteRef { vertical-align: super; font-size: 80%; }
-span.pandocNoteMarker { }
-</style>
 <meta name="author" content="John MacFarlane, Anonymous" />
 <meta name="date" content="July 17, 2006" />
 <title>Pandoc Test Suite</title>
@@ -438,18 +433,19 @@ 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>
-<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>Here is a footnote reference,<sup class="footnoteRef" id="fnref1"><a href="#fn1">1</a></sup> and another.<sup class="footnoteRef" id="fnref2"><a href="#fn2">2</a></sup> This should <em>not</em> be a footnote reference, because it contains a space.[^my note] Here is an inline note.<sup class="footnoteRef" id="fnref3"><a href="#fn3">3</a></sup></p>
+<p>This paragraph should not be part of the note, as it is not indented.</p>
+<div class="footnotes">
+<hr />
+<ol>
+<li id="fn1"><p>Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document.</p>
+ <a href="#fnref1" class="footnoteBacklink" title="Jump back to footnote 1">&#8617;</a></li><li id="fn2"><p>Here&rsquo;s the long note. This one contains multiple blocks.</p>
 <p>Subsequent blocks are indented to show that they belong to the footnote (as with list items).</p>
 <pre><code>  { &lt;code> }
 </code></pre>
 <p>If you want, you can indent every line, but you can also be lazy and just indent the first line of each block.</p>
-
+ <a href="#fnref2" class="footnoteBacklink" title="Jump back to footnote 2">&#8617;</a></li><li id="fn3"><p>This is <em>easier</em> to type. Inline notes may contain <a href="http://google.com">links</a> and <code>]</code> verbatim characters.</p>
+ <a href="#fnref3" class="footnoteBacklink" title="Jump back to footnote 3">&#8617;</a></li></ol>
 </div>
 </body>
 </html>