summaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers
diff options
context:
space:
mode:
authorJohn MacFarlane <fiddlosopher@gmail.com>2012-07-26 22:32:53 -0700
committerJohn MacFarlane <fiddlosopher@gmail.com>2012-07-26 22:32:53 -0700
commit6d7f0a1b816c405fb48bcf9736db17a0a7d49995 (patch)
tree5459fb2318b0a6949e2aaf900667014d4f4f962c /src/Text/Pandoc/Readers
parente797ab9136115caab3d162162bf9d231afc514a0 (diff)
Fixed whitespace errors.
Diffstat (limited to 'src/Text/Pandoc/Readers')
-rw-r--r--src/Text/Pandoc/Readers/DocBook.hs10
-rw-r--r--src/Text/Pandoc/Readers/HTML.hs10
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs62
-rw-r--r--src/Text/Pandoc/Readers/Native.hs2
-rw-r--r--src/Text/Pandoc/Readers/RST.hs52
-rw-r--r--src/Text/Pandoc/Readers/TeXMath.hs2
-rw-r--r--src/Text/Pandoc/Readers/Textile.hs24
7 files changed, 81 insertions, 81 deletions
diff --git a/src/Text/Pandoc/Readers/DocBook.hs b/src/Text/Pandoc/Readers/DocBook.hs
index b8cddcab3..685fa1ee4 100644
--- a/src/Text/Pandoc/Readers/DocBook.hs
+++ b/src/Text/Pandoc/Readers/DocBook.hs
@@ -455,13 +455,13 @@ List of all DocBook tags, with [x] indicating implemented,
[x] tocfront - An entry in a table of contents for a front matter component
[x] toclevel1 - A top-level entry within a table of contents entry for a
chapter-like component
-[x] toclevel2 - A second-level entry within a table of contents entry for a
+[x] toclevel2 - A second-level entry within a table of contents entry for a
chapter-like component
-[x] toclevel3 - A third-level entry within a table of contents entry for a
+[x] toclevel3 - A third-level entry within a table of contents entry for a
chapter-like component
-[x] toclevel4 - A fourth-level entry within a table of contents entry for a
+[x] toclevel4 - A fourth-level entry within a table of contents entry for a
chapter-like component
-[x] toclevel5 - A fifth-level entry within a table of contents entry for a
+[x] toclevel5 - A fifth-level entry within a table of contents entry for a
chapter-like component
[x] tocpart - An entry in a table of contents for a part of a book
[ ] token - A unit of information
@@ -574,7 +574,7 @@ addToStart toadd bs =
(Para xs : rest) -> para (toadd <> fromList xs) <> fromList rest
_ -> bs
--- function that is used by both mediaobject (in parseBlock)
+-- function that is used by both mediaobject (in parseBlock)
-- and inlinemediaobject (in parseInline)
getImage :: Element -> DB Inlines
getImage e = do
diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs
index 515d8b008..33846286d 100644
--- a/src/Text/Pandoc/Readers/HTML.hs
+++ b/src/Text/Pandoc/Readers/HTML.hs
@@ -19,10 +19,10 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
{- |
Module : Text.Pandoc.Readers.HTML
Copyright : Copyright (C) 2006-2010 John MacFarlane
- License : GNU GPL, version 2 or above
+ License : GNU GPL, version 2 or above
Maintainer : John MacFarlane <jgm@berkeley.edu>
- Stability : alpha
+ Stability : alpha
Portability : portable
Conversion of HTML to 'Pandoc' document.
@@ -231,7 +231,7 @@ pSimpleTable = try $ do
rows <- pOptInTag "tbody"
$ many1 $ try $ skipMany pBlank >> pInTags "tr" (pCell "td")
skipMany pBlank
- TagClose _ <- pSatisfy (~== TagClose "table")
+ TagClose _ <- pSatisfy (~== TagClose "table")
let cols = maximum $ map length rows
let aligns = replicate cols AlignLeft
let widths = replicate cols 0
@@ -303,7 +303,7 @@ pLocation = do
pSat :: (Tag String -> Bool) -> TagParser (Tag String)
pSat f = do
pos <- getPosition
- token show (const pos) (\x -> if f x then Just x else Nothing)
+ token show (const pos) (\x -> if f x then Just x else Nothing)
pSatisfy :: (Tag String -> Bool) -> TagParser (Tag String)
pSatisfy f = try $ optional pLocation >> pSat f
@@ -608,7 +608,7 @@ htmlTag f = try $ do
count (length s + 4) anyChar
skipMany (satisfy (/='>'))
char '>'
- return (next, "<!--" ++ s ++ "-->")
+ return (next, "<!--" ++ s ++ "-->")
_ -> do
rendered <- manyTill anyChar (char '>')
return (next, rendered ++ ">")
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index 48807cbec..ae51fdd5a 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -20,7 +20,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
{- |
Module : Text.Pandoc.Readers.Markdown
Copyright : Copyright (C) 2006-2010 John MacFarlane
- License : GNU GPL, version 2 or above
+ License : GNU GPL, version 2 or above
Maintainer : John MacFarlane <jgm@berkeley.edu>
Stability : alpha
@@ -94,7 +94,7 @@ nonindentSpaces :: Parser [Char] ParserState [Char]
nonindentSpaces = do
tabStop <- getOption readerTabStop
sps <- many (char ' ')
- if length sps < tabStop
+ if length sps < tabStop
then return sps
else unexpected "indented line"
@@ -140,7 +140,7 @@ titleLine = try $ do
return $ normalizeSpaces res
authorsLine :: Parser [Char] ParserState [[Inline]]
-authorsLine = try $ do
+authorsLine = try $ do
char '%'
skipSpaces
authors <- sepEndBy (many (notFollowedBy (satisfy $ \c ->
@@ -166,7 +166,7 @@ titleBlock = try $ do
optional blanklines
return (title, author, date)
-parseMarkdown :: Parser [Char] ParserState Pandoc
+parseMarkdown :: Parser [Char] ParserState Pandoc
parseMarkdown = do
-- markdown allows raw HTML
updateState $ \state -> state { stateOptions =
@@ -202,7 +202,7 @@ parseMarkdown = do
then return doc
else return $ bottomUp handleExampleRef doc
---
+--
-- initial pass for references and notes
--
@@ -422,7 +422,7 @@ codeBlockDelimited = try $ do
codeBlockIndented :: Parser [Char] ParserState Block
codeBlockIndented = do
- contents <- many1 (indentedLine <|>
+ contents <- many1 (indentedLine <|>
try (do b <- blanklines
l <- indentedLine
return $ b ++ l))
@@ -483,7 +483,7 @@ emailBlockQuoteStart = try $ skipNonindentSpaces >> char '>' >>~ optional (char
emailBlockQuote :: Parser [Char] ParserState [[Char]]
emailBlockQuote = try $ do
emailBlockQuoteStart
- raw <- sepBy (many (nonEndline <|>
+ raw <- sepBy (many (nonEndline <|>
(try (endline >> notFollowedBy emailBlockQuoteStart >>
return '\n'))))
(try (newline >> emailBlockQuoteStart))
@@ -492,12 +492,12 @@ emailBlockQuote = try $ do
return raw
blockQuote :: Parser [Char] ParserState Block
-blockQuote = do
+blockQuote = do
raw <- emailBlockQuote
-- parse the extracted block, which may contain various block elements:
contents <- parseFromString parseBlocks $ (intercalate "\n" raw) ++ "\n\n"
return $ BlockQuote contents
-
+
--
-- list blocks
--
@@ -511,7 +511,7 @@ bulletListStart = try $ do
spaceChar
skipSpaces
-anyOrderedListStart :: Parser [Char] ParserState (Int, ListNumberStyle, ListNumberDelim)
+anyOrderedListStart :: Parser [Char] ParserState (Int, ListNumberStyle, ListNumberDelim)
anyOrderedListStart = try $ do
optional newline -- if preceded by a Plain block in a list context
skipNonindentSpaces
@@ -554,7 +554,7 @@ rawListItem start = try $ do
blanks <- many blankline
return $ concat (first:rest) ++ blanks
--- continuation of a list item - indented and separated by blankline
+-- continuation of a list item - indented and separated by blankline
-- or (in compact lists) endline.
-- note: nested lists are parsed as continuations
listContinuation :: Parser [Char] ParserState [Char]
@@ -672,7 +672,7 @@ isHtmlOrBlank (LineBreak) = True
isHtmlOrBlank _ = False
para :: Parser [Char] ParserState Block
-para = try $ do
+para = try $ do
result <- liftM normalizeSpaces $ many1 inline
guard $ not . all isHtmlOrBlank $ result
option (Plain result) $ try $ do
@@ -685,7 +685,7 @@ para = try $ do
plain :: Parser [Char] ParserState Block
plain = many1 inline >>~ spaces >>= return . Plain . normalizeSpaces
---
+--
-- raw html
--
@@ -741,20 +741,20 @@ rawHtmlBlocks = do
--
-- Tables
---
+--
-- Parse a dashed line with optional trailing spaces; return its length
-- and the length including trailing space.
-dashedLine :: Char
+dashedLine :: Char
-> Parser [Char] st (Int, Int)
dashedLine ch = do
dashes <- many1 (char ch)
sp <- many spaceChar
return $ (length dashes, length $ dashes ++ sp)
--- Parse a table header with dashed lines of '-' preceded by
+-- Parse a table header with dashed lines of '-' preceded by
-- one (or zero) line of text.
-simpleTableHeader :: Bool -- ^ Headerless table
+simpleTableHeader :: Bool -- ^ Headerless table
-> Parser [Char] ParserState ([[Block]], [Alignment], [Int])
simpleTableHeader headless = try $ do
rawContent <- if headless
@@ -768,12 +768,12 @@ simpleTableHeader headless = try $ do
-- If no header, calculate alignment on basis of first row of text
rawHeads <- liftM (tail . splitStringByIndices (init indices)) $
if headless
- then lookAhead anyLine
+ then lookAhead anyLine
else return rawContent
let aligns = zipWith alignType (map (\a -> [a]) rawHeads) lengths
let rawHeads' = if headless
then replicate (length dashes) ""
- else rawHeads
+ else rawHeads
heads <- mapM (parseFromString (many plain)) $
map removeLeadingTrailingSpace rawHeads'
return (heads, aligns, indices)
@@ -792,7 +792,7 @@ rawTableLine :: [Int]
rawTableLine indices = do
notFollowedBy' (blanklines <|> tableFooter)
line <- many1Till anyChar newline
- return $ map removeLeadingTrailingSpace $ tail $
+ return $ map removeLeadingTrailingSpace $ tail $
splitStringByIndices (init indices) line
-- Parse a table line and return a list of lists of blocks (columns).
@@ -845,7 +845,7 @@ multilineTableHeader headless = try $ do
then return '\n'
else tableSep >>~ notFollowedBy blankline
rawContent <- if headless
- then return $ repeat ""
+ then return $ repeat ""
else many1
(notFollowedBy tableSep >> many1Till anyChar newline)
initSp <- nonindentSpaces
@@ -856,7 +856,7 @@ multilineTableHeader headless = try $ do
rawHeadsList <- if headless
then liftM (map (:[]) . tail .
splitStringByIndices (init indices)) $ lookAhead anyLine
- else return $ transpose $ map
+ else return $ transpose $ map
(\ln -> tail $ splitStringByIndices (init indices) ln)
rawContent
let aligns = zipWith alignType rawHeadsList lengths
@@ -1026,7 +1026,7 @@ exampleRef = try $ do
return $ Str $ '@' : lab
symbol :: Parser [Char] ParserState Inline
-symbol = do
+symbol = do
result <- noneOf "<\\\n\t "
<|> try (do lookAhead $ char '\\'
notFollowedBy' rawTeXBlock
@@ -1035,12 +1035,12 @@ symbol = do
-- parses inline code, between n `s and n `s
code :: Parser [Char] ParserState Inline
-code = try $ do
+code = try $ do
starts <- many1 (char '`')
skipSpaces
result <- many1Till (many1 (noneOf "`\n") <|> many1 (char '`') <|>
(char '\n' >> notFollowedBy' blankline >> return " "))
- (try (skipSpaces >> count (length starts) (char '`') >>
+ (try (skipSpaces >> count (length starts) (char '`') >>
notFollowedBy (char '`')))
attr <- option ([],[],[]) (try $ optional whitespace >> attributes)
return $ Code attr $ removeLeadingTrailingSpace $ concat result
@@ -1058,7 +1058,7 @@ math :: Parser [Char] ParserState Inline
math = (mathDisplay >>= applyMacros' >>= return . Math DisplayMath)
<|> (mathInline >>= applyMacros' >>= return . Math InlineMath)
-mathDisplay :: Parser [Char] ParserState String
+mathDisplay :: Parser [Char] ParserState String
mathDisplay = try $ do
guardEnabled Ext_tex_math
string "$$"
@@ -1129,14 +1129,14 @@ strikeout = Strikeout `liftM`
strikeEnd = try $ string "~~"
superscript :: Parser [Char] ParserState Inline
-superscript = guardEnabled Ext_superscript >> enclosed (char '^') (char '^')
+superscript = guardEnabled Ext_superscript >> enclosed (char '^') (char '^')
(notFollowedBy spaceChar >> inline) >>= -- may not contain Space
return . Superscript
subscript :: Parser [Char] ParserState Inline
subscript = guardEnabled Ext_subscript >> enclosed (char '~') (char '~')
(notFollowedBy spaceChar >> inline) >>= -- may not contain Space
- return . Subscript
+ return . Subscript
whitespace :: Parser [Char] ParserState Inline
whitespace = spaceChar >>
@@ -1257,13 +1257,13 @@ delinkify = bottomUp $ concatMap go
referenceLink :: [Inline]
-> Parser [Char] ParserState (String, [Char])
referenceLink lab = do
- ref <- option [] (try (optional (char ' ') >>
+ ref <- option [] (try (optional (char ' ') >>
optional (newline >> skipSpaces) >> reference))
let ref' = if null ref then lab else ref
state <- getState
case lookupKeySrc (stateKeys state) (toKey ref') of
- Nothing -> fail "no corresponding key"
- Just target -> return target
+ Nothing -> fail "no corresponding key"
+ Just target -> return target
autoLink :: Parser [Char] ParserState Inline
autoLink = try $ do
diff --git a/src/Text/Pandoc/Readers/Native.hs b/src/Text/Pandoc/Readers/Native.hs
index 2c6fcc6e6..410c44a37 100644
--- a/src/Text/Pandoc/Readers/Native.hs
+++ b/src/Text/Pandoc/Readers/Native.hs
@@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
{- |
Module : Text.Pandoc.Readers.Native
Copyright : Copyright (C) 2011 John MacFarlane
- License : GNU GPL, version 2 or above
+ License : GNU GPL, version 2 or above
Maintainer : John MacFarlane <jgm@berkeley.edu>
Stability : alpha
diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs
index 7b52993f9..939de08e9 100644
--- a/src/Text/Pandoc/Readers/RST.hs
+++ b/src/Text/Pandoc/Readers/RST.hs
@@ -17,9 +17,9 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
-}
{- |
- Module : Text.Pandoc.Readers.RST
+ Module : Text.Pandoc.Readers.RST
Copyright : Copyright (C) 2006-2010 John MacFarlane
- License : GNU GPL, version 2 or above
+ License : GNU GPL, version 2 or above
Maintainer : John MacFarlane <jgm@berkeley.edu>
Stability : alpha
@@ -71,14 +71,14 @@ isHeader _ _ = False
-- | Promote all headers in a list of blocks. (Part of
-- title transformation for RST.)
promoteHeaders :: Int -> [Block] -> [Block]
-promoteHeaders num ((Header level text):rest) =
+promoteHeaders num ((Header level text):rest) =
(Header (level - num) text):(promoteHeaders num rest)
promoteHeaders num (other:rest) = other:(promoteHeaders num rest)
promoteHeaders _ [] = []
-- | If list of blocks starts with a header (or a header and subheader)
-- of level that are not found elsewhere, return it as a title and
--- promote all the other headers.
+-- promote all the other headers.
titleTransform :: [Block] -- ^ list of blocks
-> ([Block], [Inline]) -- ^ modified list of blocks, title
titleTransform ((Header 1 head1):(Header 2 head2):rest) |
@@ -238,14 +238,14 @@ paraBeforeCodeBlock = try $ do
-- regular paragraph
paraNormal :: Parser [Char] ParserState Block
-paraNormal = try $ do
+paraNormal = try $ do
result <- many1 inline
newline
blanklines
return $ Para $ normalizeSpaces result
plain :: Parser [Char] ParserState Block
-plain = many1 inline >>= return . Plain . normalizeSpaces
+plain = many1 inline >>= return . Plain . normalizeSpaces
--
-- image block
@@ -284,7 +284,7 @@ doubleHeader = try $ do
blankline -- spaces and newline
count lenTop (char c) -- the bottom line
blanklines
- -- check to see if we've had this kind of header before.
+ -- check to see if we've had this kind of header before.
-- if so, get appropriate level. if not, add to list.
state <- getState
let headerTable = stateHeaderTable state
@@ -296,7 +296,7 @@ doubleHeader = try $ do
-- a header with line on the bottom only
singleHeader :: Parser [Char] ParserState Block
-singleHeader = try $ do
+singleHeader = try $ do
notFollowedBy' whitespace
txt <- many1 (do {notFollowedBy blankline; inline})
pos <- getPosition
@@ -498,8 +498,8 @@ indentWith num = do
tabStop <- getOption readerTabStop
if (num < tabStop)
then count num (char ' ')
- else choice [ try (count num (char ' ')),
- (try (char '\t' >> count (num - tabStop) (char ' '))) ]
+ else choice [ try (count num (char ' ')),
+ (try (char '\t' >> count (num - tabStop) (char ' '))) ]
-- parse raw text for one list item, excluding start marker and continuations
rawListItem :: Parser [Char] ParserState Int
@@ -510,8 +510,8 @@ rawListItem start = try $ do
restLines <- many (listLine markerLength)
return (markerLength, (firstLine ++ "\n" ++ (concat restLines)))
--- continuation of a list item - indented and separated by blankline or
--- (in compact lists) endline.
+-- continuation of a list item - indented and separated by blankline or
+-- (in compact lists) endline.
-- Note: nested lists are parsed as continuations.
listContinuation :: Int -> Parser [Char] ParserState [Char]
listContinuation markerLength = try $ do
@@ -521,7 +521,7 @@ listContinuation markerLength = try $ do
listItem :: Parser [Char] ParserState Int
-> Parser [Char] ParserState [Block]
-listItem start = try $ do
+listItem start = try $ do
(markerLength, first) <- rawListItem start
rest <- many (listContinuation markerLength)
blanks <- choice [ try (many blankline >>~ lookAhead start),
@@ -545,7 +545,7 @@ orderedList = try $ do
return $ OrderedList (start, style, delim) items'
bulletList :: Parser [Char] ParserState Block
-bulletList = many1 (listItem bulletListStart) >>=
+bulletList = many1 (listItem bulletListStart) >>=
return . BulletList . compactify
--
@@ -617,7 +617,7 @@ noteMarker = do
quotedReferenceName :: Parser [Char] ParserState [Inline]
quotedReferenceName = try $ do
char '`' >> notFollowedBy (char '`') -- `` means inline code!
- label' <- many1Till inline (char '`')
+ label' <- many1Till inline (char '`')
return label'
unquotedReferenceName :: Parser [Char] ParserState [Inline]
@@ -662,7 +662,7 @@ targetURI :: Parser [Char] st [Char]
targetURI = do
skipSpaces
optional newline
- contents <- many1 (try (many spaceChar >> newline >>
+ contents <- many1 (try (many spaceChar >> newline >>
many1 spaceChar >> noneOf " \t\n") <|> noneOf "\n")
blanklines
return $ escapeURI $ removeLeadingTrailingSpace $ contents
@@ -702,7 +702,7 @@ regularKey = try $ do
-- Simple tables TODO:
-- - column spans
-- - multiline support
--- - ensure that rightmost column span does not need to reach end
+-- - ensure that rightmost column span does not need to reach end
-- - require at least 2 columns
--
-- Grid tables TODO:
@@ -745,7 +745,7 @@ simpleTableSplitLine indices line =
map removeLeadingTrailingSpace
$ tail $ splitByIndices (init indices) line
-simpleTableHeader :: Bool -- ^ Headerless table
+simpleTableHeader :: Bool -- ^ Headerless table
-> Parser [Char] ParserState ([[Block]], [Alignment], [Int])
simpleTableHeader headless = try $ do
optional blanklines
@@ -783,7 +783,7 @@ table = gridTable False <|> simpleTable False <|>
gridTable True <|> simpleTable True <?> "table"
- --
+ --
-- inline
--
@@ -808,7 +808,7 @@ inline = choice [ whitespace
hyphens :: Parser [Char] ParserState Inline
hyphens = do
result <- many1 (char '-')
- option Space endline
+ option Space endline
-- don't want to treat endline after hyphen or dash as a space
return $ Str result
@@ -819,13 +819,13 @@ escapedChar = do c <- escaped anyChar
else Str [c]
symbol :: Parser [Char] ParserState Inline
-symbol = do
+symbol = do
result <- oneOf specialChars
return $ Str [result]
-- parses inline code, between codeStart and codeEnd
code :: Parser [Char] ParserState Inline
-code = try $ do
+code = try $ do
string "``"
result <- manyTill anyChar (try (string "``"))
return $ Code nullAttr
@@ -841,11 +841,11 @@ atStart p = do
p
emph :: Parser [Char] ParserState Inline
-emph = enclosed (atStart $ char '*') (char '*') inline >>=
+emph = enclosed (atStart $ char '*') (char '*') inline >>=
return . Emph . normalizeSpaces
strong :: Parser [Char] ParserState Inline
-strong = enclosed (atStart $ string "**") (try $ string "**") inline >>=
+strong = enclosed (atStart $ string "**") (try $ string "**") inline >>=
return . Strong . normalizeSpaces
-- Parses inline interpreted text which is required to have the given role.
@@ -911,7 +911,7 @@ explicitLink :: Parser [Char] ParserState Inline
explicitLink = try $ do
char '`'
notFollowedBy (char '`') -- `` marks start of inline code
- label' <- manyTill (notFollowedBy (char '`') >> inline)
+ label' <- manyTill (notFollowedBy (char '`') >> inline)
(try (spaces >> char '<'))
src <- manyTill (noneOf ">\n") (char '>')
skipSpaces
@@ -938,7 +938,7 @@ referenceLink = try $ do
Just target -> return target
-- if anonymous link, remove key so it won't be used again
when (isAnonKey key) $ updateState $ \s -> s{ stateKeys = M.delete key keyTable }
- return $ Link (normalizeSpaces label') (src, tit)
+ return $ Link (normalizeSpaces label') (src, tit)
autoURI :: Parser [Char] ParserState Inline
autoURI = do
diff --git a/src/Text/Pandoc/Readers/TeXMath.hs b/src/Text/Pandoc/Readers/TeXMath.hs
index 67dfe6753..fe49a992e 100644
--- a/src/Text/Pandoc/Readers/TeXMath.hs
+++ b/src/Text/Pandoc/Readers/TeXMath.hs
@@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
{- |
Module : Text.Pandoc.Readers.TeXMath
Copyright : Copyright (C) 2007-2010 John MacFarlane
- License : GNU GPL, version 2 or above
+ License : GNU GPL, version 2 or above
Maintainer : John MacFarlane <jgm@berkeley.edu>
Stability : alpha
diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs
index 6e5ab2791..89f281ae8 100644
--- a/src/Text/Pandoc/Readers/Textile.hs
+++ b/src/Text/Pandoc/Readers/Textile.hs
@@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
{- |
Module : Text.Pandoc.Readers.Textile
Copyright : Copyright (C) 2010-2012 Paul Rivier and John MacFarlane
- License : GNU GPL, version 2 or above
+ License : GNU GPL, version 2 or above
Maintainer : Paul Rivier <paul*rivier#demotera*com>
Stability : alpha
@@ -232,9 +232,9 @@ genericListItemAtDepth c depth = try $ do
return ((Plain p):sublist)
-- | A definition list is a set of consecutive definition items
-definitionList :: Parser [Char] ParserState Block
+definitionList :: Parser [Char] ParserState Block
definitionList = try $ DefinitionList <$> many1 definitionListItem
-
+
-- | A definition list item in textile begins with '- ', followed by
-- the term defined, then spaces and ":=". The definition follows, on
-- the same single line, or spaned on multiple line, after a line
@@ -283,7 +283,7 @@ para = try $ Para . normalizeSpaces <$> manyTill inline blockBreak
-- Tables
-
+
-- | A table cell spans until a pipe |
tableCell :: Parser [Char] ParserState TableCell
tableCell = do
@@ -303,7 +303,7 @@ tableRows = many1 tableRow
tableHeaders :: Parser [Char] ParserState [TableCell]
tableHeaders = let separator = (try $ string "|_.") in
try $ ( separator *> (sepBy1 tableCell separator) <* char '|' <* newline )
-
+
-- | A table with an optional header. Current implementation can
-- handle tables with and without header, but will parse cells
-- alignment attributes as content.
@@ -313,12 +313,12 @@ table = try $ do
rows <- tableRows
blanklines
let nbOfCols = max (length headers) (length $ head rows)
- return $ Table []
+ return $ Table []
(replicate nbOfCols AlignDefault)
(replicate nbOfCols 0.0)
headers
rows
-
+
-- | Blocks like 'p' and 'table' do not need explicit block tag.
-- However, they can be used to set HTML/CSS attributes when needed.
@@ -326,7 +326,7 @@ maybeExplicitBlock :: String -- ^ block tag name
-> Parser [Char] ParserState Block -- ^ implicit block
-> Parser [Char] ParserState Block
maybeExplicitBlock name blk = try $ do
- optional $ try $ string name >> optional attributes >> char '.' >>
+ optional $ try $ string name >> optional attributes >> char '.' >>
((try whitespace) <|> endline)
blk
@@ -410,7 +410,7 @@ note = try $ do
Nothing -> fail "note not found"
Just raw -> liftM Note $ parseFromString parseBlocks raw
--- | Special chars
+-- | Special chars
markupChars :: [Char]
markupChars = "\\[]*#_@~-+^|%="
@@ -429,10 +429,10 @@ wordBoundaries = markupChars ++ stringBreakers
hyphenedWords :: Parser [Char] ParserState String
hyphenedWords = try $ do
hd <- noneOf wordBoundaries
- tl <- many ( (noneOf wordBoundaries) <|>
+ tl <- many ( (noneOf wordBoundaries) <|>
try (oneOf markupChars <* lookAhead (noneOf wordBoundaries) ) )
let wd = hd:tl
- option wd $ try $
+ option wd $ try $
(\r -> concat [wd, "-", r]) <$> (char '-' *> hyphenedWords)
-- | Any string
@@ -465,7 +465,7 @@ endline = try $ do
rawHtmlInline :: Parser [Char] ParserState Inline
rawHtmlInline = RawInline "html" . snd <$> htmlTag isInlineTag
--- | Raw LaTeX Inline
+-- | Raw LaTeX Inline
rawLaTeXInline' :: Parser [Char] ParserState Inline
rawLaTeXInline' = try $ do
guardEnabled Ext_raw_tex