Textile reader: Implemented footnotes.

This commit is contained in:
John MacFarlane 2010-12-08 00:44:46 -08:00
parent 200ea33641
commit f02080b62d
3 changed files with 54 additions and 6 deletions

View file

@ -35,12 +35,12 @@ Implemented and parsed:
- blockquote
- Inlines : strong, emph, cite, code, deleted, superscript,
subscript, links
- footnotes
Implemented but discarded:
- HTML-specific and CSS-specific attributes
Left to be implemented:
- footnotes
- dimension sign
- all caps
- definition lists
@ -64,7 +64,7 @@ import Text.Pandoc.Readers.HTML ( htmlTag, htmlEndTag, -- find code blocks
-- import Text.Pandoc.Readers.Markdown (smartPunctuation)
import Text.ParserCombinators.Parsec
import Data.Char ( digitToInt, isLetter )
import Control.Monad ( guard )
import Control.Monad ( guard, liftM )
-- | Parse a Textile text and return a Pandoc document.
readTextile :: ParserState -- ^ Parser state, including options for parser
@ -87,8 +87,35 @@ parseTextile = do
-- textile allows raw HTML and does smart punctuation by default
updateState (\state -> state { stateParseRaw = True, stateSmart = True })
many blankline
blocks <- parseBlocks
return $ Pandoc (Meta [Str ""] [[Str ""]] [Str ""]) blocks -- FIXME
startPos <- getPosition
-- go through once just to get list of reference keys and notes
-- docMinusKeys is the raw document with blanks where the keys/notes were...
let firstPassParser = noteBlock <|> lineClump
manyTill firstPassParser eof >>= setInput . concat
setPosition startPos
st' <- getState
let reversedNotes = stateNotes st'
updateState $ \s -> s { stateNotes = reverse reversedNotes }
-- now parse it for real...
blocks <- parseBlocks
return $ Pandoc (Meta [] [] []) blocks -- FIXME
noteMarker :: GenParser Char ParserState [Char]
noteMarker = skipMany spaceChar >> string "fn" >> manyTill digit (char '.')
noteBlock :: GenParser Char ParserState [Char]
noteBlock = try $ do
startPos <- getPosition
ref <- noteMarker
optional blankline
contents <- liftM unlines $ many1Till anyLine (blanklines <|> noteBlock)
endPos <- getPosition
let newnote = (ref, contents ++ "\n")
st <- getState
let oldnotes = stateNotes st
updateState $ \s -> s { stateNotes = newnote : oldnotes }
-- return blanks so line count isn't affected
return $ replicate (sourceLine endPos - sourceLine startPos) '\n'
-- | Parse document blocks
parseBlocks :: GenParser Char ParserState [Block]
@ -306,6 +333,7 @@ inlines = manyTill inline newline
inlineParsers :: [GenParser Char ParserState Inline]
inlineParsers = [ autoLink
, mark
, note
, str
, htmlSpan
, whitespace
@ -349,6 +377,17 @@ copy = do
char ')'
return $ Str "\169"
note :: GenParser Char ParserState Inline
note = try $ do
char '['
ref <- many1 digit
char ']'
state <- getState
let notes = stateNotes state
case lookup ref notes of
Nothing -> fail "note not found"
Just raw -> liftM Note $ parseFromString parseBlocks raw
-- | Any string
str :: GenParser Char ParserState Inline
str = do

View file

@ -1,4 +1,4 @@
Pandoc (Meta {docTitle = [Str ""], docAuthors = [[Str ""]], docDate = [Str ""]})
Pandoc (Meta {docTitle = [], docAuthors = [], docDate = []})
[ 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 "Textile",Space,Str "Reader",Str ".",Space,Str "Part",Space,Str "of",Space,Str "it",Space,Str "comes",LineBreak,Str "from",Space,Str "John",Space,Str "Gruber",Apostrophe,Str "s",Space,Str "markdown",Space,Str "test",Space,Str "suite",Str "."]
, HorizontalRule
, Header 1 [Str "Headers"]
@ -131,4 +131,6 @@ Pandoc (Meta {docTitle = [Str ""], docAuthors = [[Str ""]], docDate = [Str ""]})
, Para [Str "Hi",Str "\8482"]
, Para [Str "Hi",Space,Str "\8482"]
, Para [Str "\174",Space,Str "Hi",Str "\174"]
, Para [Str "Hi",Str "\169",Str "2008",Space,Str "\169",Space,Str "2008"] ]
, Para [Str "Hi",Str "\169",Str "2008",Space,Str "\169",Space,Str "2008"]
, Header 1 [Str "Footnotes"]
, Para [Str "A",Space,Str "note",Str ".",Note [Para [Str "The",Space,Str "note",LineBreak,Str "is",Space,Str "here",Str "!"]]] ]

View file

@ -190,3 +190,10 @@ Hi (TM)
(r) Hi(r)
Hi(c)2008 (C) 2008
h1. Footnotes
A note.[1]
fn1. The note
is here!