aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorfiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b>2006-12-19 23:13:03 +0000
committerfiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b>2006-12-19 23:13:03 +0000
commit661c7e7b1da0af7132767f5522c56fb8ae370ee9 (patch)
tree4ef0439ce3b478a240aa6a3a81e140ffa13fff56 /src
parent66da30cd7853854572192edc3e9ef0fda313bc5e (diff)
downloadpandoc-661c7e7b1da0af7132767f5522c56fb8ae370ee9.tar.gz
Merged changes to footnotes branch r219-r240.
git-svn-id: https://pandoc.googlecode.com/svn/trunk@241 788f1e2b-df1e-0410-8736-df70ead52e1b
Diffstat (limited to 'src')
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs7
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs47
-rw-r--r--src/Text/Pandoc/Shared.hs24
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs31
-rw-r--r--src/Text/Pandoc/Writers/Markdown.hs2
-rw-r--r--src/headers/HtmlHeader5
6 files changed, 78 insertions, 38 deletions
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>