summaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
Diffstat (limited to 'src')
-rw-r--r--src/Text/Pandoc/MIME.hs2
-rw-r--r--src/Text/Pandoc/Parsing.hs50
-rw-r--r--src/Text/Pandoc/Pretty.hs2
-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
-rw-r--r--src/Text/Pandoc/SelfContained.hs4
-rw-r--r--src/Text/Pandoc/Shared.hs18
-rw-r--r--src/Text/Pandoc/Templates.hs16
-rw-r--r--src/Text/Pandoc/UTF8.hs2
-rw-r--r--src/Text/Pandoc/Writers/ConTeXt.hs46
-rw-r--r--src/Text/Pandoc/Writers/Docbook.hs66
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs2
-rw-r--r--src/Text/Pandoc/Writers/Man.hs78
-rw-r--r--src/Text/Pandoc/Writers/Markdown.hs40
-rw-r--r--src/Text/Pandoc/Writers/MediaWiki.hs46
-rw-r--r--src/Text/Pandoc/Writers/Native.hs8
-rw-r--r--src/Text/Pandoc/Writers/Org.hs52
-rw-r--r--src/Text/Pandoc/Writers/RST.hs48
-rw-r--r--src/Text/Pandoc/Writers/RTF.hs80
-rw-r--r--src/Text/Pandoc/Writers/Texinfo.hs18
-rw-r--r--src/Text/Pandoc/Writers/Textile.hs30
26 files changed, 385 insertions, 385 deletions
diff --git a/src/Text/Pandoc/MIME.hs b/src/Text/Pandoc/MIME.hs
index f9749cece..9cde57e4d 100644
--- a/src/Text/Pandoc/MIME.hs
+++ b/src/Text/Pandoc/MIME.hs
@@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
{- |
Module : Text.Pandoc.MIME
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/Parsing.hs b/src/Text/Pandoc/Parsing.hs
index 16eee6de5..4bda4dc23 100644
--- a/src/Text/Pandoc/Parsing.hs
+++ b/src/Text/Pandoc/Parsing.hs
@@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
{- |
Module : Text.Pandoc.Parsing
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
@@ -167,7 +167,7 @@ many1Till p end = do
rest <- manyTill p end
return (first:rest)
--- | A more general form of @notFollowedBy@. This one allows any
+-- | A more general form of @notFollowedBy@. This one allows any
-- type of parser to be specified, and succeeds only if that parser fails.
-- It does not consume any input.
notFollowedBy' :: Show b => Parsec [a] st b -> Parsec [a] st ()
@@ -213,7 +213,7 @@ enclosed :: Parsec [Char] st t -- ^ start parser
-> Parsec [Char] st end -- ^ end parser
-> Parsec [Char] st a -- ^ content parser (to be used repeatedly)
-> Parsec [Char] st [a]
-enclosed start end parser = try $
+enclosed start end parser = try $
start >> notFollowedBy space >> many1Till parser end
-- | Parse string, case insensitive.
@@ -237,7 +237,7 @@ parseFromString parser str = do
-- | Parse raw line block up to and including blank lines.
lineClump :: Parsec [Char] st String
-lineClump = blanklines
+lineClump = blanklines
<|> (many1 (notFollowedBy blankline >> anyLine) >>= return . unlines)
-- | Parse a string of characters between an open character
@@ -273,11 +273,11 @@ uppercaseRomanDigits = map toUpper lowercaseRomanDigits
romanNumeral :: Bool -- ^ Uppercase if true
-> Parsec [Char] st Int
romanNumeral upperCase = do
- let romanDigits = if upperCase
- then uppercaseRomanDigits
+ let romanDigits = if upperCase
+ then uppercaseRomanDigits
else lowercaseRomanDigits
lookAhead $ oneOf romanDigits
- let [one, five, ten, fifty, hundred, fivehundred, thousand] =
+ let [one, five, ten, fifty, hundred, fivehundred, thousand] =
map char romanDigits
thousands <- many thousand >>= (return . (1000 *) . length)
ninehundreds <- option 0 $ try $ hundred >> thousand >> return 900
@@ -468,15 +468,15 @@ romanOne = (char 'i' >> return (LowerRoman, 1)) <|>
(char 'I' >> return (UpperRoman, 1))
-- | Parses an ordered list marker and returns list attributes.
-anyOrderedListMarker :: Parsec [Char] ParserState ListAttributes
-anyOrderedListMarker = choice $
+anyOrderedListMarker :: Parsec [Char] ParserState ListAttributes
+anyOrderedListMarker = choice $
[delimParser numParser | delimParser <- [inPeriod, inOneParen, inTwoParens],
numParser <- [decimal, exampleNum, defaultNum, romanOne,
lowerAlpha, lowerRoman, upperAlpha, upperRoman]]
-- | Parses a list number (num) followed by a period, returns list attributes.
inPeriod :: Parsec [Char] st (ListNumberStyle, Int)
- -> Parsec [Char] st ListAttributes
+ -> Parsec [Char] st ListAttributes
inPeriod num = try $ do
(style, start) <- num
char '.'
@@ -484,10 +484,10 @@ inPeriod num = try $ do
then DefaultDelim
else Period
return (start, style, delim)
-
+
-- | Parses a list number (num) followed by a paren, returns list attributes.
inOneParen :: Parsec [Char] st (ListNumberStyle, Int)
- -> Parsec [Char] st ListAttributes
+ -> Parsec [Char] st ListAttributes
inOneParen num = try $ do
(style, start) <- num
char ')'
@@ -495,7 +495,7 @@ inOneParen num = try $ do
-- | Parses a list number (num) enclosed in parens, returns list attributes.
inTwoParens :: Parsec [Char] st (ListNumberStyle, Int)
- -> Parsec [Char] st ListAttributes
+ -> Parsec [Char] st ListAttributes
inTwoParens num = try $ do
char '('
(style, start) <- num
@@ -504,8 +504,8 @@ inTwoParens num = try $ do
-- | Parses an ordered list marker with a given style and delimiter,
-- returns number.
-orderedListMarker :: ListNumberStyle
- -> ListNumberDelim
+orderedListMarker :: ListNumberStyle
+ -> ListNumberDelim
-> Parsec [Char] ParserState Int
orderedListMarker style delim = do
let num = defaultNum <|> -- # can continue any kind of list
@@ -552,8 +552,8 @@ tableWith headerParser rowParser lineParser footerParser = try $ do
widthsFromIndices :: Int -- Number of columns on terminal
-> [Int] -- Indices
-> [Double] -- Fractional relative sizes of columns
-widthsFromIndices _ [] = []
-widthsFromIndices numColumns' indices =
+widthsFromIndices _ [] = []
+widthsFromIndices numColumns' indices =
let numColumns = max numColumns' (if null indices then 0 else last indices)
lengths' = zipWith (-) indices (0:indices)
lengths = reverse $
@@ -614,7 +614,7 @@ gridTableHeader headless block = try $ do
optional blanklines
dashes <- gridDashedLines '-'
rawContent <- if headless
- then return $ repeat ""
+ then return $ repeat ""
else many1
(notFollowedBy (gridTableSep '=') >> char '|' >>
many1Till anyChar newline)
@@ -671,7 +671,7 @@ readWith :: Parsec [t] ParserState a -- ^ parser
-> ParserState -- ^ initial state
-> [t] -- ^ input
-> a
-readWith parser state input =
+readWith parser state input =
case runParser parser state "source" input of
Left err' -> error $ "\nError:\n" ++ show err'
Right result -> result
@@ -697,7 +697,7 @@ data ParserState = ParserState
stateDate :: [Inline], -- ^ Date of document
stateHeaderTable :: [HeaderType], -- ^ Ordered list of header types used
stateNextExample :: Int, -- ^ Number of next example
- stateExamples :: M.Map String Int, -- ^ Map from example labels to numbers
+ stateExamples :: M.Map String Int, -- ^ Map from example labels to numbers
stateHasChapters :: Bool, -- ^ True if \chapter encountered
stateMacros :: [Macro], -- ^ List of macros defined so far
stateRstDefaultRole :: String -- ^ Current rST default interpreted text role
@@ -708,7 +708,7 @@ instance Default ParserState where
def = defaultParserState
defaultParserState :: ParserState
-defaultParserState =
+defaultParserState =
ParserState { stateOptions = def,
stateParserContext = NullState,
stateQuoteContext = NoQuote,
@@ -737,12 +737,12 @@ guardEnabled ext = getOption readerExtensions >>= guard . Set.member ext
guardDisabled :: Extension -> Parser s ParserState ()
guardDisabled ext = getOption readerExtensions >>= guard . not . Set.member ext
-data HeaderType
+data HeaderType
= SingleHeader Char -- ^ Single line of characters underneath
| DoubleHeader Char -- ^ Lines of characters above and below
deriving (Eq, Show)
-data ParserContext
+data ParserContext
= ListItemState -- ^ Used when running parser on list item contents
| NullState -- ^ Default state
deriving (Eq, Show)
@@ -838,7 +838,7 @@ charOrRef cs =
return c)
updateLastStrPos :: Parsec [Char] ParserState ()
-updateLastStrPos = getPosition >>= \p ->
+updateLastStrPos = getPosition >>= \p ->
updateState $ \s -> s{ stateLastStrPos = Just p }
singleQuoteStart :: Parsec [Char] ParserState ()
@@ -852,7 +852,7 @@ singleQuoteStart = do
notFollowedBy (oneOf ")!],;:-? \t\n")
notFollowedBy (char '.') <|> lookAhead (string "..." >> return ())
notFollowedBy (try (oneOfStrings ["s","t","m","ve","ll","re"] >>
- satisfy (not . isAlphaNum)))
+ satisfy (not . isAlphaNum)))
-- possess/contraction
return ()
diff --git a/src/Text/Pandoc/Pretty.hs b/src/Text/Pandoc/Pretty.hs
index 0372dbe5d..6cb6bce18 100644
--- a/src/Text/Pandoc/Pretty.hs
+++ b/src/Text/Pandoc/Pretty.hs
@@ -20,7 +20,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111(-1)307 USA
{- |
Module : Text.Pandoc.Pretty
Copyright : Copyright (C) 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/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
diff --git a/src/Text/Pandoc/SelfContained.hs b/src/Text/Pandoc/SelfContained.hs
index a80ab0c63..675b8366e 100644
--- a/src/Text/Pandoc/SelfContained.hs
+++ b/src/Text/Pandoc/SelfContained.hs
@@ -102,14 +102,14 @@ convertTag userdata t@(TagOpen "script" as) =
src -> do
(raw, mime) <- getRaw userdata (fromAttrib "type" t) src
let enc = "data:" ++ mime ++ "," ++ escapeURIString isOk (toString raw)
- return $ TagOpen "script" (("src",enc) : [(x,y) | (x,y) <- as, x /= "src"])
+ return $ TagOpen "script" (("src",enc) : [(x,y) | (x,y) <- as, x /= "src"])
convertTag userdata t@(TagOpen "link" as) =
case fromAttrib "href" t of
[] -> return t
src -> do
(raw, mime) <- getRaw userdata (fromAttrib "type" t) src
let enc = "data:" ++ mime ++ "," ++ escapeURIString isOk (toString raw)
- return $ TagOpen "link" (("href",enc) : [(x,y) | (x,y) <- as, x /= "href"])
+ return $ TagOpen "link" (("href",enc) : [(x,y) | (x,y) <- as, x /= "href"])
convertTag _ t = return t
cssURLs :: Maybe FilePath -> FilePath -> ByteString -> IO ByteString
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index 0825a414d..724fa5cae 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -20,7 +20,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
{- |
Module : Text.Pandoc.Shared
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
@@ -150,7 +150,7 @@ backslashEscapes = map (\ch -> (ch, ['\\',ch]))
-- characters and strings.
escapeStringUsing :: [(Char, String)] -> String -> String
escapeStringUsing _ [] = ""
-escapeStringUsing escapeTable (x:xs) =
+escapeStringUsing escapeTable (x:xs) =
case (lookup x escapeTable) of
Just str -> str ++ rest
Nothing -> x:rest
@@ -177,7 +177,7 @@ stripFirstAndLast :: String -> String
stripFirstAndLast str =
drop 1 $ take ((length str) - 1) str
--- | Change CamelCase word to hyphenated lowercase (e.g., camel-case).
+-- | Change CamelCase word to hyphenated lowercase (e.g., camel-case).
camelCaseToHyphenated :: String -> String
camelCaseToHyphenated [] = ""
camelCaseToHyphenated (a:b:rest) | isLower a && isUpper b =
@@ -248,13 +248,13 @@ normalizeDate s = fmap (formatTime defaultTimeLocale "%F")
-- | Generate infinite lazy list of markers for an ordered list,
-- depending on list attributes.
orderedListMarkers :: (Int, ListNumberStyle, ListNumberDelim) -> [String]
-orderedListMarkers (start, numstyle, numdelim) =
+orderedListMarkers (start, numstyle, numdelim) =
let singleton c = [c]
nums = case numstyle of
DefaultStyle -> map show [start..]
Example -> map show [start..]
Decimal -> map show [start..]
- UpperAlpha -> drop (start - 1) $ cycle $
+ UpperAlpha -> drop (start - 1) $ cycle $
map singleton ['A'..'Z']
LowerAlpha -> drop (start - 1) $ cycle $
map singleton ['a'..'z']
@@ -386,7 +386,7 @@ isPara (Para _) = True
isPara _ = False
-- | Data structure for defining hierarchical Pandoc documents
-data Element = Blk Block
+data Element = Blk Block
| Sec Int [Int] String [Inline] [Element]
-- lvl num ident label contents
deriving (Eq, Read, Show, Typeable, Data)
@@ -414,7 +414,7 @@ hierarchicalizeWithIds ((Header level title'):xs) = do
let ident = uniqueIdent title' usedIdents
let lastnum' = take level lastnum
let newnum = if length lastnum' >= level
- then init lastnum' ++ [last lastnum' + 1]
+ then init lastnum' ++ [last lastnum' + 1]
else lastnum ++ replicate (level - length lastnum - 1) 0 ++ [1]
S.put (newnum, (ident : usedIdents))
let (sectionContents, rest) = break (headerLtEq level) xs
@@ -459,7 +459,7 @@ headerShift n = bottomUp shift
-- Writer options
--
-data HTMLMathMethod = PlainMath
+data HTMLMathMethod = PlainMath
| LaTeXMathML (Maybe String) -- url of LaTeXMathML.js
| JsMath (Maybe String) -- url of jsMath load script
| GladTeX
@@ -534,7 +534,7 @@ instance Default WriterOptions where
{-# DEPRECATED writerXeTeX "writerXeTeX no longer does anything" #-}
-- | Default writer options.
defaultWriterOptions :: WriterOptions
-defaultWriterOptions =
+defaultWriterOptions =
WriterOptions { writerStandalone = False
, writerTemplate = ""
, writerVariables = []
diff --git a/src/Text/Pandoc/Templates.hs b/src/Text/Pandoc/Templates.hs
index bd4cdcd86..061be29aa 100644
--- a/src/Text/Pandoc/Templates.hs
+++ b/src/Text/Pandoc/Templates.hs
@@ -30,7 +30,7 @@ A simple templating system with variable substitution and conditionals.
Example:
> renderTemplate [("name","Sam"),("salary","50,000")] $
-> "Hi, $name$. $if(salary)$You make $$$salary$.$else$No salary data.$endif$"
+> "Hi, $name$. $if(salary)$You make $$$salary$.$else$No salary data.$endif$"
> "Hi, John. You make $50,000."
A slot for an interpolated variable is a variable name surrounded
@@ -83,8 +83,8 @@ import Text.Pandoc.Shared (readDataFile)
import qualified Control.Exception.Extensible as E (try, IOException)
-- | Get default template for the specified writer.
-getDefaultTemplate :: (Maybe FilePath) -- ^ User data directory to search first
- -> String -- ^ Name of writer
+getDefaultTemplate :: (Maybe FilePath) -- ^ User data directory to search first
+ -> String -- ^ Name of writer
-> IO (Either E.IOException String)
getDefaultTemplate _ "native" = return $ Right ""
getDefaultTemplate _ "json" = return $ Right ""
@@ -108,18 +108,18 @@ adjustPosition str = do
return str
class TemplateTarget a where
- toTarget :: String -> a
+ toTarget :: String -> a
instance TemplateTarget String where
toTarget = id
-instance TemplateTarget ByteString where
+instance TemplateTarget ByteString where
toTarget = fromString
instance TemplateTarget Html where
toTarget = preEscapedString
--- | Renders a template
+-- | Renders a template
renderTemplate :: TemplateTarget a
=> [(String,String)] -- ^ Assoc. list of values for variables
-> String -- ^ Template
@@ -178,14 +178,14 @@ for = try $ do
string ")$"
-- if newline after the "for", then a newline after "endfor" will be swallowed
multiline <- option False $ try $ skipEndline >> return True
- let matches = filter (\(k,_) -> k == id') vars
+ let matches = filter (\(k,_) -> k == id') vars
let indent = replicate pos ' '
contents <- forM matches $ \m -> do
updateState $ \(TemplateState p v) -> TemplateState p (m:v)
raw <- liftM concat $ lookAhead parseTemplate
return $ intercalate ('\n':indent) $ lines $ raw ++ "\n"
parseTemplate
- sep <- option "" $ do try (string "$sep$")
+ sep <- option "" $ do try (string "$sep$")
when multiline $ optional skipEndline
liftM concat parseTemplate
string "$endfor$"
diff --git a/src/Text/Pandoc/UTF8.hs b/src/Text/Pandoc/UTF8.hs
index e2959eae7..508ad30a9 100644
--- a/src/Text/Pandoc/UTF8.hs
+++ b/src/Text/Pandoc/UTF8.hs
@@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
{- |
Module : Text.Pandoc.UTF8
Copyright : Copyright (C) 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/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs
index 964320eb2..fb832c7f5 100644
--- a/src/Text/Pandoc/Writers/ConTeXt.hs
+++ b/src/Text/Pandoc/Writers/ConTeXt.hs
@@ -20,10 +20,10 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
{- |
Module : Text.Pandoc.Writers.ConTeXt
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
+ Stability : alpha
Portability : portable
Conversion of 'Pandoc' format into ConTeXt.
@@ -39,23 +39,23 @@ import Text.Pandoc.Pretty
import Text.Pandoc.Templates ( renderTemplate )
import Network.URI ( isURI, unEscapeString )
-data WriterState =
+data WriterState =
WriterState { stNextRef :: Int -- number of next URL reference
, stOrderedListLevel :: Int -- level of ordered list
, stOptions :: WriterOptions -- writer options
}
orderedListStyles :: [[Char]]
-orderedListStyles = cycle ["[n]","[a]", "[r]", "[g]"]
+orderedListStyles = cycle ["[n]","[a]", "[r]", "[g]"]
-- | Convert Pandoc to ConTeXt.
writeConTeXt :: WriterOptions -> Pandoc -> String
-writeConTeXt options document =
+writeConTeXt options document =
let defaultWriterState = WriterState { stNextRef = 1
, stOrderedListLevel = 0
, stOptions = options
- }
- in evalState (pandocToConTeXt options document) defaultWriterState
+ }
+ in evalState (pandocToConTeXt options document) defaultWriterState
pandocToConTeXt :: WriterOptions -> Pandoc -> State WriterState String
pandocToConTeXt options (Pandoc (Meta title authors date) blocks) = do
@@ -120,7 +120,7 @@ elementToConTeXt opts (Sec level _ id' title' elements) = do
return $ vcat (header' : innerContents)
-- | Convert Pandoc block element to ConTeXt.
-blockToConTeXt :: Block
+blockToConTeXt :: Block
-> State WriterState Doc
blockToConTeXt Null = return empty
blockToConTeXt (Plain lst) = inlineListToConTeXt lst
@@ -128,7 +128,7 @@ blockToConTeXt (Para [Image txt (src,_)]) = do
capt <- inlineListToConTeXt txt
return $ blankline $$ "\\placefigure[here,nonumber]" <> braces capt <>
braces ("\\externalfigure" <> brackets (text src)) <> blankline
-blockToConTeXt (Para lst) = do
+blockToConTeXt (Para lst) = do
contents <- inlineListToConTeXt lst
return $ contents <> blankline
blockToConTeXt (BlockQuote lst) = do
@@ -147,18 +147,18 @@ blockToConTeXt (OrderedList (start, style', delim) lst) = do
let level = stOrderedListLevel st
put $ st {stOrderedListLevel = level + 1}
contents <- mapM listItemToConTeXt lst
- put $ st {stOrderedListLevel = level}
+ put $ st {stOrderedListLevel = level}
let start' = if start == 1 then "" else "start=" ++ show start
let delim' = case delim of
DefaultDelim -> ""
- Period -> "stopper=."
- OneParen -> "stopper=)"
+ Period -> "stopper=."
+ OneParen -> "stopper=)"
TwoParens -> "left=(,stopper=)"
- let width = maximum $ map length $ take (length contents)
+ let width = maximum $ map length $ take (length contents)
(orderedListMarkers (start, style', delim))
let width' = (toEnum width + 1) / 2
- let width'' = if width' > (1.5 :: Double)
- then "width=" ++ show width' ++ "em"
+ let width'' = if width' > (1.5 :: Double)
+ then "width=" ++ show width' ++ "em"
else ""
let specs2Items = filter (not . null) [start', delim', width'']
let specs2 = if null specs2Items
@@ -166,8 +166,8 @@ blockToConTeXt (OrderedList (start, style', delim) lst) = do
else "[" ++ intercalate "," specs2Items ++ "]"
let style'' = case style' of
DefaultStyle -> orderedListStyles !! level
- Decimal -> "[n]"
- Example -> "[n]"
+ Decimal -> "[n]"
+ Example -> "[n]"
LowerRoman -> "[r]"
UpperRoman -> "[R]"
LowerAlpha -> "[a]"
@@ -182,21 +182,21 @@ blockToConTeXt HorizontalRule = return $ "\\thinrule" <> blankline
blockToConTeXt (Header level lst) = sectionHeader "" level lst
blockToConTeXt (Table caption aligns widths heads rows) = do
let colDescriptor colWidth alignment = (case alignment of
- AlignLeft -> 'l'
+ AlignLeft -> 'l'
AlignRight -> 'r'
AlignCenter -> 'c'
AlignDefault -> 'l'):
if colWidth == 0
then "|"
else ("p(" ++ printf "%.2f" colWidth ++ "\\textwidth)|")
- let colDescriptors = "|" ++ (concat $
+ let colDescriptors = "|" ++ (concat $
zipWith colDescriptor widths aligns)
headers <- if all null heads
then return empty
- else liftM ($$ "\\HL") $ tableRowToConTeXt heads
- captionText <- inlineListToConTeXt caption
+ else liftM ($$ "\\HL") $ tableRowToConTeXt heads
+ captionText <- inlineListToConTeXt caption
let captionText' = if null caption then text "none" else captionText
- rows' <- mapM tableRowToConTeXt rows
+ rows' <- mapM tableRowToConTeXt rows
return $ "\\placetable[here]" <> braces captionText' $$
"\\starttable" <> brackets (text colDescriptors) $$
"\\HL" $$ headers $$
@@ -230,7 +230,7 @@ inlineListToConTeXt lst = liftM hcat $ mapM inlineToConTeXt lst
-- | Convert inline element to ConTeXt
inlineToConTeXt :: Inline -- ^ Inline to convert
-> State WriterState Doc
-inlineToConTeXt (Emph lst) = do
+inlineToConTeXt (Emph lst) = do
contents <- inlineListToConTeXt lst
return $ braces $ "\\em " <> contents
inlineToConTeXt (Strong lst) = do
diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs
index 1bcf99dcf..74bc0a366 100644
--- a/src/Text/Pandoc/Writers/Docbook.hs
+++ b/src/Text/Pandoc/Writers/Docbook.hs
@@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
{- |
Module : Text.Pandoc.Writers.Docbook
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
@@ -47,23 +47,23 @@ authorToDocbook opts name' =
let name = render Nothing $ inlinesToDocbook opts name'
in if ',' `elem` name
then -- last name first
- let (lastname, rest) = break (==',') name
+ let (lastname, rest) = break (==',') name
firstname = removeLeadingSpace rest in
- inTagsSimple "firstname" (text $ escapeStringForXML firstname) <>
- inTagsSimple "surname" (text $ escapeStringForXML lastname)
+ inTagsSimple "firstname" (text $ escapeStringForXML firstname) <>
+ inTagsSimple "surname" (text $ escapeStringForXML lastname)
else -- last name last
let namewords = words name
- lengthname = length namewords
+ lengthname = length namewords
(firstname, lastname) = case lengthname of
- 0 -> ("","")
+ 0 -> ("","")
1 -> ("", name)
n -> (intercalate " " (take (n-1) namewords), last namewords)
- in inTagsSimple "firstname" (text $ escapeStringForXML firstname) $$
- inTagsSimple "surname" (text $ escapeStringForXML lastname)
+ in inTagsSimple "firstname" (text $ escapeStringForXML firstname) $$
+ inTagsSimple "surname" (text $ escapeStringForXML lastname)
-- | Convert Pandoc document to string in Docbook format.
writeDocbook :: WriterOptions -> Pandoc -> String
-writeDocbook opts (Pandoc (Meta tit auths dat) blocks) =
+writeDocbook opts (Pandoc (Meta tit auths dat) blocks) =
let title = inlinesToDocbook opts tit
authors = map (authorToDocbook opts) auths
date = inlinesToDocbook opts dat
@@ -92,7 +92,7 @@ writeDocbook opts (Pandoc (Meta tit auths dat) blocks) =
-- | Convert an Element to Docbook.
elementToDocbook :: WriterOptions -> Int -> Element -> Doc
-elementToDocbook opts _ (Blk block) = blockToDocbook opts block
+elementToDocbook opts _ (Blk block) = blockToDocbook opts block
elementToDocbook opts lvl (Sec _ _num id' title elements) =
-- Docbook doesn't allow sections with no content, so insert some if needed
let elements' = if null elements
@@ -115,10 +115,10 @@ plainToPara :: Block -> Block
plainToPara (Plain x) = Para x
plainToPara x = x
--- | Convert a list of pairs of terms and definitions into a list of
+-- | Convert a list of pairs of terms and definitions into a list of
-- Docbook varlistentrys.
deflistItemsToDocbook :: WriterOptions -> [([Inline],[[Block]])] -> Doc
-deflistItemsToDocbook opts items =
+deflistItemsToDocbook opts items =
vcat $ map (\(term, defs) -> deflistItemToDocbook opts term defs) items
-- | Convert a term and a list of blocks into a Docbook varlistentry.
@@ -167,9 +167,9 @@ blockToDocbook _ (CodeBlock (_,classes,_) str) =
then [s]
else languagesByExtension . map toLower $ s
langs = concatMap langsFrom classes
-blockToDocbook opts (BulletList lst) =
- inTagsIndented "itemizedlist" $ listItemsToDocbook opts lst
-blockToDocbook _ (OrderedList _ []) = empty
+blockToDocbook opts (BulletList lst) =
+ inTagsIndented "itemizedlist" $ listItemsToDocbook opts lst
+blockToDocbook _ (OrderedList _ []) = empty
blockToDocbook opts (OrderedList (start, numstyle, _) (first:rest)) =
let attribs = case numstyle of
DefaultStyle -> []
@@ -182,12 +182,12 @@ blockToDocbook opts (OrderedList (start, numstyle, _) (first:rest)) =
items = if start == 1
then listItemsToDocbook opts (first:rest)
else (inTags True "listitem" [("override",show start)]
- (blocksToDocbook opts $ map plainToPara first)) $$
- listItemsToDocbook opts rest
+ (blocksToDocbook opts $ map plainToPara first)) $$
+ listItemsToDocbook opts rest
in inTags True "orderedlist" attribs items
-blockToDocbook opts (DefinitionList lst) =
- inTagsIndented "variablelist" $ deflistItemsToDocbook opts lst
-blockToDocbook _ (RawBlock "docbook" str) = text str -- raw XML block
+blockToDocbook opts (DefinitionList lst) =
+ inTagsIndented "variablelist" $ deflistItemsToDocbook opts lst
+blockToDocbook _ (RawBlock "docbook" str) = text str -- raw XML block
-- we allow html for compatibility with earlier versions of pandoc
blockToDocbook _ (RawBlock "html" str) = text str -- raw XML block
blockToDocbook _ (RawBlock _ _) = empty
@@ -237,26 +237,26 @@ inlinesToDocbook opts lst = hcat $ map (inlineToDocbook opts) lst
-- | Convert an inline element to Docbook.
inlineToDocbook :: WriterOptions -> Inline -> Doc
-inlineToDocbook _ (Str str) = text $ escapeStringForXML str
-inlineToDocbook opts (Emph lst) =
+inlineToDocbook _ (Str str) = text $ escapeStringForXML str
+inlineToDocbook opts (Emph lst) =
inTagsSimple "emphasis" $ inlinesToDocbook opts lst
-inlineToDocbook opts (Strong lst) =
+inlineToDocbook opts (Strong lst) =
inTags False "emphasis" [("role", "strong")] $ inlinesToDocbook opts lst
-inlineToDocbook opts (Strikeout lst) =
+inlineToDocbook opts (Strikeout lst) =
inTags False "emphasis" [("role", "strikethrough")] $
inlinesToDocbook opts lst
-inlineToDocbook opts (Superscript lst) =
+inlineToDocbook opts (Superscript lst) =
inTagsSimple "superscript" $ inlinesToDocbook opts lst
-inlineToDocbook opts (Subscript lst) =
+inlineToDocbook opts (Subscript lst) =
inTagsSimple "subscript" $ inlinesToDocbook opts lst
-inlineToDocbook opts (SmallCaps lst) =
+inlineToDocbook opts (SmallCaps lst) =
inTags False "emphasis" [("role", "smallcaps")] $
inlinesToDocbook opts lst
-inlineToDocbook opts (Quoted _ lst) =
+inlineToDocbook opts (Quoted _ lst) =
inTagsSimple "quote" $ inlinesToDocbook opts lst
inlineToDocbook opts (Cite _ lst) =
- inlinesToDocbook opts lst
-inlineToDocbook _ (Code _ str) =
+ inlinesToDocbook opts lst
+inlineToDocbook _ (Code _ str) =
inTagsSimple "literal" $ text (escapeStringForXML str)
inlineToDocbook opts (Math t str)
| isMathML (writerHTMLMathMethod opts) =
@@ -282,7 +282,7 @@ inlineToDocbook _ Space = space
inlineToDocbook opts (Link txt (src, _)) =
if isPrefixOf "mailto:" src
then let src' = drop 7 src
- emailLink = inTagsSimple "email" $ text $
+ emailLink = inTagsSimple "email" $ text $
escapeStringForXML $ src'
in case txt of
[Code _ s] | s == src' -> emailLink
@@ -292,14 +292,14 @@ inlineToDocbook opts (Link txt (src, _)) =
then inTags False "link" [("linkend", drop 1 src)]
else inTags False "ulink" [("url", src)]) $
inlinesToDocbook opts txt
-inlineToDocbook _ (Image _ (src, tit)) =
+inlineToDocbook _ (Image _ (src, tit)) =
let titleDoc = if null tit
then empty
else inTagsIndented "objectinfo" $
inTagsIndented "title" (text $ escapeStringForXML tit)
in inTagsIndented "inlinemediaobject" $ inTagsIndented "imageobject" $
titleDoc $$ selfClosingTag "imagedata" [("fileref", src)]
-inlineToDocbook opts (Note contents) =
+inlineToDocbook opts (Note contents) =
inTagsIndented "footnote" $ blocksToDocbook opts contents
isMathML :: HTMLMathMethod -> Bool
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index cafb6ca74..c7bab7260 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -618,7 +618,7 @@ inlineToHtml opts inline =
! A.src (toValue $ url ++ urlEncode str)
! A.alt (toValue str)
! A.title (toValue str)
- let brtag = if writerHtml5 opts then H5.br else H.br
+ let brtag = if writerHtml5 opts then H5.br else H.br
return $ case t of
InlineMath -> m
DisplayMath -> brtag >> m >> brtag
diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs
index c481e6c87..f6f570042 100644
--- a/src/Text/Pandoc/Writers/Man.hs
+++ b/src/Text/Pandoc/Writers/Man.hs
@@ -17,9 +17,9 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
-}
{- |
- Module : Text.Pandoc.Writers.Man
+ Module : Text.Pandoc.Writers.Man
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
@@ -44,21 +44,21 @@ data WriterState = WriterState { stNotes :: Notes
-- | Convert Pandoc to Man.
writeMan :: WriterOptions -> Pandoc -> String
-writeMan opts document = evalState (pandocToMan opts document) (WriterState [] False)
+writeMan opts document = evalState (pandocToMan opts document) (WriterState [] False)
-- | Return groff man representation of document.
pandocToMan :: WriterOptions -> Pandoc -> State WriterState String
pandocToMan opts (Pandoc (Meta title authors date) blocks) = do
titleText <- inlineListToMan opts title
authors' <- mapM (inlineListToMan opts) authors
- date' <- inlineListToMan opts date
+ date' <- inlineListToMan opts date
let colwidth = if writerWrapText opts
then Just $ writerColumns opts
else Nothing
let render' = render colwidth
let (cmdName, rest) = break (== ' ') $ render' titleText
let (title', section) = case reverse cmdName of
- (')':d:'(':xs) | d `elem` ['0'..'9'] ->
+ (')':d:'(':xs) | d `elem` ['0'..'9'] ->
(text (reverse xs), char d)
xs -> (text (reverse xs), doubleQuotes empty)
let description = hsep $
@@ -86,7 +86,7 @@ notesToMan :: WriterOptions -> [[Block]] -> State WriterState Doc
notesToMan opts notes =
if null notes
then return empty
- else mapM (\(num, note) -> noteToMan opts num note) (zip [1..] notes) >>=
+ else mapM (\(num, note) -> noteToMan opts num note) (zip [1..] notes) >>=
return . (text ".SH NOTES" $$) . vcat
-- | Return man representation of a note.
@@ -94,7 +94,7 @@ noteToMan :: WriterOptions -> Int -> [Block] -> State WriterState Doc
noteToMan opts num note = do
contents <- blockListToMan opts note
let marker = cr <> text ".SS " <> brackets (text (show num))
- return $ marker $$ contents
+ return $ marker $$ contents
-- | Association list of characters to escape.
manEscapes :: [(Char, String)]
@@ -113,7 +113,7 @@ escapeString = escapeStringUsing manEscapes
-- | Escape a literal (code) section for Man.
escapeCode :: String -> String
escapeCode = concat . intersperse "\n" . map escapeLine . lines where
- escapeLine codeline =
+ escapeLine codeline =
case escapeStringUsing (manEscapes ++ backslashEscapes "\t ") codeline of
a@('.':_) -> "\\&" ++ a
b -> b
@@ -150,14 +150,14 @@ splitSentences xs =
-- | Convert Pandoc block element to man.
blockToMan :: WriterOptions -- ^ Options
-> Block -- ^ Block element
- -> State WriterState Doc
+ -> State WriterState Doc
blockToMan _ Null = return empty
-blockToMan opts (Plain inlines) =
+blockToMan opts (Plain inlines) =
liftM vcat $ mapM (inlineListToMan opts) $ splitSentences inlines
blockToMan opts (Para inlines) = do
contents <- liftM vcat $ mapM (inlineListToMan opts) $
splitSentences inlines
- return $ text ".PP" $$ contents
+ return $ text ".PP" $$ contents
blockToMan _ (RawBlock "man" str) = return $ text str
blockToMan _ (RawBlock _ _) = return empty
blockToMan _ HorizontalRule = return $ text ".PP" $$ text " * * * * *"
@@ -166,7 +166,7 @@ blockToMan opts (Header level inlines) = do
let heading = case level of
1 -> ".SH "
_ -> ".SS "
- return $ text heading <> contents
+ return $ text heading <> contents
blockToMan _ (CodeBlock _ str) = return $
text ".IP" $$
text ".nf" $$
@@ -174,10 +174,10 @@ blockToMan _ (CodeBlock _ str) = return $
text (escapeCode str) $$
text "\\f[]" $$
text ".fi"
-blockToMan opts (BlockQuote blocks) = do
+blockToMan opts (BlockQuote blocks) = do
contents <- blockListToMan opts blocks
return $ text ".RS" $$ contents $$ text ".RE"
-blockToMan opts (Table caption alignments widths headers rows) =
+blockToMan opts (Table caption alignments widths headers rows) =
let aligncode AlignLeft = "l"
aligncode AlignRight = "r"
aligncode AlignCenter = "c"
@@ -190,53 +190,53 @@ blockToMan opts (Table caption alignments widths headers rows) =
else map (printf "w(%0.2fn)" . (70 *)) widths
-- 78n default width - 8n indent = 70n
let coldescriptions = text $ intercalate " "
- (zipWith (\align width -> aligncode align ++ width)
+ (zipWith (\align width -> aligncode align ++ width)
alignments iwidths) ++ "."
colheadings <- mapM (blockListToMan opts) headers
- let makeRow cols = text "T{" $$
- (vcat $ intersperse (text "T}@T{") cols) $$
+ let makeRow cols = text "T{" $$
+ (vcat $ intersperse (text "T}@T{") cols) $$
text "T}"
let colheadings' = if all null headers
then empty
else makeRow colheadings $$ char '_'
- body <- mapM (\row -> do
+ body <- mapM (\row -> do
cols <- mapM (blockListToMan opts) row
return $ makeRow cols) rows
- return $ text ".PP" $$ caption' $$
- text ".TS" $$ text "tab(@);" $$ coldescriptions $$
+ return $ text ".PP" $$ caption' $$
+ text ".TS" $$ text "tab(@);" $$ coldescriptions $$
colheadings' $$ vcat body $$ text ".TE"
blockToMan opts (BulletList items) = do
contents <- mapM (bulletListItemToMan opts) items
- return (vcat contents)
+ return (vcat contents)
blockToMan opts (OrderedList attribs items) = do
- let markers = take (length items) $ orderedListMarkers attribs
+ let markers = take (length items) $ orderedListMarkers attribs
let indent = 1 + (maximum $ map length markers)
contents <- mapM (\(num, item) -> orderedListItemToMan opts num indent item) $
- zip markers items
+ zip markers items
return (vcat contents)
-blockToMan opts (DefinitionList items) = do
+blockToMan opts (DefinitionList items) = do
contents <- mapM (definitionListItemToMan opts) items
return (vcat contents)
-- | Convert bullet list item (list of blocks) to man.
bulletListItemToMan :: WriterOptions -> [Block] -> State WriterState Doc
bulletListItemToMan _ [] = return empty
-bulletListItemToMan opts ((Para first):rest) =
+bulletListItemToMan opts ((Para first):rest) =
bulletListItemToMan opts ((Plain first):rest)
bulletListItemToMan opts ((Plain first):rest) = do
- first' <- blockToMan opts (Plain first)
+ first' <- blockToMan opts (Plain first)
rest' <- blockListToMan opts rest
let first'' = text ".IP \\[bu] 2" $$ first'
let rest'' = if null rest
then empty
else text ".RS 2" $$ rest' $$ text ".RE"
- return (first'' $$ rest'')
+ return (first'' $$ rest'')
bulletListItemToMan opts (first:rest) = do
first' <- blockToMan opts first
rest' <- blockListToMan opts rest
return $ text "\\[bu] .RS 2" $$ first' $$ rest' $$ text ".RE"
-
+
-- | Convert ordered list item (a list of blocks) to man.
orderedListItemToMan :: WriterOptions -- ^ options
-> String -- ^ order marker for list item
@@ -244,7 +244,7 @@ orderedListItemToMan :: WriterOptions -- ^ options
-> [Block] -- ^ list item (list of blocks)
-> State WriterState Doc
orderedListItemToMan _ _ _ [] = return empty
-orderedListItemToMan opts num indent ((Para first):rest) =
+orderedListItemToMan opts num indent ((Para first):rest) =
orderedListItemToMan opts num indent ((Plain first):rest)
orderedListItemToMan opts num indent (first:rest) = do
first' <- blockToMan opts first
@@ -254,17 +254,17 @@ orderedListItemToMan opts num indent (first:rest) = do
let rest'' = if null rest
then empty
else text ".RS 4" $$ rest' $$ text ".RE"
- return $ first'' $$ rest''
+ return $ first'' $$ rest''
-- | Convert definition list item (label, list of blocks) to man.
definitionListItemToMan :: WriterOptions
- -> ([Inline],[[Block]])
+ -> ([Inline],[[Block]])
-> State WriterState Doc
definitionListItemToMan opts (label, defs) = do
labelText <- inlineListToMan opts label
- contents <- if null defs
+ contents <- if null defs
then return empty
- else liftM vcat $ forM defs $ \blocks -> do
+ else liftM vcat $ forM defs $ \blocks -> do
let (first, rest) = case blocks of
((Para x):y) -> (Plain x,y)
(x:y) -> (x,y)
@@ -278,7 +278,7 @@ definitionListItemToMan opts (label, defs) = do
-- | Convert list of Pandoc block elements to man.
blockListToMan :: WriterOptions -- ^ Options
-> [Block] -- ^ List of block elements
- -> State WriterState Doc
+ -> State WriterState Doc
blockListToMan opts blocks =
mapM (blockToMan opts) blocks >>= (return . vcat)
@@ -292,7 +292,7 @@ inlineListToMan opts lst = mapM (inlineToMan opts) lst >>= (return . hcat)
-- | Convert Pandoc inline element to man.
inlineToMan :: WriterOptions -> Inline -> State WriterState Doc
-inlineToMan opts (Emph lst) = do
+inlineToMan opts (Emph lst) = do
contents <- inlineListToMan opts lst
return $ text "\\f[I]" <> contents <> text "\\f[]"
inlineToMan opts (Strong lst) = do
@@ -333,16 +333,16 @@ inlineToMan opts (Link txt (src, _)) = do
let srcSuffix = if isPrefixOf "mailto:" src then drop 7 src else src
return $ case txt of
[Code _ s]
- | s == srcSuffix -> char '<' <> text srcSuffix <> char '>'
+ | s == srcSuffix -> char '<' <> text srcSuffix <> char '>'
_ -> linktext <> text " (" <> text src <> char ')'
inlineToMan opts (Image alternate (source, tit)) = do
- let txt = if (null alternate) || (alternate == [Str ""]) ||
+ let txt = if (null alternate) || (alternate == [Str ""]) ||
(alternate == [Str source]) -- to prevent autolinks
then [Str "image"]
else alternate
- linkPart <- inlineToMan opts (Link txt (source, tit))
+ linkPart <- inlineToMan opts (Link txt (source, tit))
return $ char '[' <> text "IMAGE: " <> linkPart <> char ']'
-inlineToMan _ (Note contents) = do
+inlineToMan _ (Note contents) = do
-- add to notes in state
modify $ \st -> st{ stNotes = contents : stNotes st }
notes <- liftM stNotes get
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index 32b28a770..80f51dfc6 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -18,9 +18,9 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
-}
{- |
- Module : Text.Pandoc.Writers.Markdown
+ Module : Text.Pandoc.Writers.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
@@ -48,7 +48,7 @@ data WriterState = WriterState { stNotes :: Notes
-- | Convert Pandoc to Markdown.
writeMarkdown :: WriterOptions -> Pandoc -> String
-writeMarkdown opts document =
+writeMarkdown opts document =
evalState (pandocToMarkdown opts document) WriterState{ stNotes = []
, stRefs = []
, stPlain = False }
@@ -88,7 +88,7 @@ pandocToMarkdown opts (Pandoc (Meta title authors date) blocks) = do
date' <- inlineListToMarkdown opts date
let titleblock = not $ null title && null authors && null date
let headerBlocks = filter isHeaderBlock blocks
- let toc = if writerTableOfContents opts
+ let toc = if writerTableOfContents opts
then tableOfContents opts headerBlocks
else empty
body <- blockListToMarkdown opts blocks
@@ -118,9 +118,9 @@ pandocToMarkdown opts (Pandoc (Meta title authors date) blocks) = do
refsToMarkdown :: WriterOptions -> Refs -> State WriterState Doc
refsToMarkdown opts refs = mapM (keyToMarkdown opts) refs >>= return . vcat
--- | Return markdown representation of a reference key.
-keyToMarkdown :: WriterOptions
- -> ([Inline], (String, String))
+-- | Return markdown representation of a reference key.
+keyToMarkdown :: WriterOptions
+ -> ([Inline], (String, String))
-> State WriterState Doc
keyToMarkdown opts (label, (src, tit)) = do
label' <- inlineListToMarkdown opts label
@@ -132,7 +132,7 @@ keyToMarkdown opts (label, (src, tit)) = do
-- | Return markdown representation of notes.
notesToMarkdown :: WriterOptions -> [[Block]] -> State WriterState Doc
-notesToMarkdown opts notes =
+notesToMarkdown opts notes =
mapM (\(num, note) -> noteToMarkdown opts num note) (zip [1..] notes) >>=
return . vsep
@@ -154,7 +154,7 @@ escapeString = escapeStringUsing markdownEscapes
where markdownEscapes = backslashEscapes "\\`*_$<>#~^"
-- | Construct table of contents from list of header blocks.
-tableOfContents :: WriterOptions -> [Block] -> Doc
+tableOfContents :: WriterOptions -> [Block] -> Doc
tableOfContents opts headers =
let opts' = opts { writerIgnoreNotes = True }
contents = BulletList $ map elementToListItem $ hierarchicalize headers
@@ -165,7 +165,7 @@ tableOfContents opts headers =
-- | Converts an Element to a list item for a table of contents,
elementToListItem :: Element -> [Block]
elementToListItem (Blk _) = []
-elementToListItem (Sec _ _ _ headerText subsecs) = [Plain headerText] ++
+elementToListItem (Sec _ _ _ headerText subsecs) = [Plain headerText] ++
if null subsecs
then []
else [BulletList $ map elementToListItem subsecs]
@@ -189,7 +189,7 @@ attrsToMarkdown attribs = braces $ hsep [attribId, attribClasses, attribKeys]
-- | Ordered list start parser for use in Para below.
olMarker :: Parser [Char] ParserState Char
olMarker = do (start, style', delim) <- anyOrderedListMarker
- if delim == Period &&
+ if delim == Period &&
(style' == UpperAlpha || (style' == UpperRoman &&
start `elem` [1, 5, 10, 50, 100, 500, 1000]))
then spaceChar >> spaceChar
@@ -205,7 +205,7 @@ beginsWithOrderedListMarker str =
-- | Convert Pandoc block element to markdown.
blockToMarkdown :: WriterOptions -- ^ Options
-> Block -- ^ Block element
- -> State WriterState Doc
+ -> State WriterState Doc
blockToMarkdown _ Null = return empty
blockToMarkdown opts (Plain inlines) = do
contents <- inlineListToMarkdown opts inlines
@@ -348,7 +348,7 @@ orderedListItemToMarkdown opts marker items = do
-- | Convert definition list item (label, list of blocks) to markdown.
definitionListItemToMarkdown :: WriterOptions
- -> ([Inline],[[Block]])
+ -> ([Inline],[[Block]])
-> State WriterState Doc
definitionListItemToMarkdown opts (label, defs) = do
labelText <- inlineListToMarkdown opts label
@@ -365,7 +365,7 @@ definitionListItemToMarkdown opts (label, defs) = do
-- | Convert list of Pandoc block elements to markdown.
blockListToMarkdown :: WriterOptions -- ^ Options
-> [Block] -- ^ List of block elements
- -> State WriterState Doc
+ -> State WriterState Doc
blockListToMarkdown opts blocks =
mapM (blockToMarkdown opts) (fixBlocks blocks) >>= return . cat
-- insert comment between list and indented code block, or the
@@ -411,7 +411,7 @@ escapeSpaces x = x
-- | Convert Pandoc inline element to markdown.
inlineToMarkdown :: WriterOptions -> Inline -> State WriterState Doc
-inlineToMarkdown opts (Emph lst) = do
+inlineToMarkdown opts (Emph lst) = do
contents <- inlineListToMarkdown opts lst
return $ "*" <> contents <> "*"
inlineToMarkdown opts (Strong lst) = do
@@ -436,11 +436,11 @@ inlineToMarkdown opts (Quoted DoubleQuote lst) = do
contents <- inlineListToMarkdown opts lst
return $ "“" <> contents <> "”"
inlineToMarkdown opts (Code attr str) =
- let tickGroups = filter (\s -> '`' `elem` s) $ group str
+ let tickGroups = filter (\s -> '`' `elem` s) $ group str
longest = if null tickGroups
then 0
- else maximum $ map length tickGroups
- marker = replicate (longest + 1) '`'
+ else maximum $ map length tickGroups
+ marker = replicate (longest + 1) '`'
spacer = if (longest == 0) then "" else " "
attrs = if writerStrictMarkdown opts || attr == nullAttr
then empty
@@ -512,7 +512,7 @@ inlineToMarkdown opts (Link txt (src, tit)) = do
then "[]"
else "[" <> reftext <> "]"
in first <> second
- else "[" <> linktext <> "](" <>
+ else "[" <> linktext <> "](" <>
text src <> linktitle <> ")"
inlineToMarkdown opts (Image alternate (source, tit)) = do
let txt = if null alternate || alternate == [Str source]
@@ -521,7 +521,7 @@ inlineToMarkdown opts (Image alternate (source, tit)) = do
else alternate
linkPart <- inlineToMarkdown opts (Link txt (source, tit))
return $ "!" <> linkPart
-inlineToMarkdown _ (Note contents) = do
+inlineToMarkdown _ (Note contents) = do
modify (\st -> st{ stNotes = contents : stNotes st })
st <- get
let ref = show $ (length $ stNotes st)
diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs
index b32c5327d..a9e2a2c69 100644
--- a/src/Text/Pandoc/Writers/MediaWiki.hs
+++ b/src/Text/Pandoc/Writers/MediaWiki.hs
@@ -17,9 +17,9 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
-}
{- |
- Module : Text.Pandoc.Writers.MediaWiki
+ Module : Text.Pandoc.Writers.MediaWiki
Copyright : Copyright (C) 2008-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
@@ -31,7 +31,7 @@ MediaWiki: <http://www.mediawiki.org/wiki/MediaWiki>
-}
module Text.Pandoc.Writers.MediaWiki ( writeMediaWiki ) where
import Text.Pandoc.Definition
-import Text.Pandoc.Shared
+import Text.Pandoc.Shared
import Text.Pandoc.Templates (renderTemplate)
import Text.Pandoc.XML ( escapeStringForXML )
import Data.List ( intersect, intercalate )
@@ -46,9 +46,9 @@ data WriterState = WriterState {
-- | Convert Pandoc to MediaWiki.
writeMediaWiki :: WriterOptions -> Pandoc -> String
-writeMediaWiki opts document =
- evalState (pandocToMediaWiki opts document)
- (WriterState { stNotes = False, stListLevel = [], stUseTags = False })
+writeMediaWiki opts document =
+ evalState (pandocToMediaWiki opts document)
+ (WriterState { stNotes = False, stListLevel = [], stUseTags = False })
-- | Return MediaWiki representation of document.
pandocToMediaWiki :: WriterOptions -> Pandoc -> State WriterState String
@@ -57,7 +57,7 @@ pandocToMediaWiki opts (Pandoc _ blocks) = do
notesExist <- get >>= return . stNotes
let notes = if notesExist
then "\n<references />"
- else ""
+ else ""
let main = body ++ notes
let context = writerVariables opts ++
[ ("body", main) ] ++
@@ -70,18 +70,18 @@ pandocToMediaWiki opts (Pandoc _ blocks) = do
escapeString :: String -> String
escapeString = escapeStringForXML
--- | Convert Pandoc block element to MediaWiki.
+-- | Convert Pandoc block element to MediaWiki.
blockToMediaWiki :: WriterOptions -- ^ Options
-> Block -- ^ Block element
- -> State WriterState String
+ -> State WriterState String
blockToMediaWiki _ Null = return ""
-blockToMediaWiki opts (Plain inlines) =
+blockToMediaWiki opts (Plain inlines) =
inlineListToMediaWiki opts inlines
blockToMediaWiki opts (Para [Image txt (src,tit)]) = do
- capt <- inlineListToMediaWiki opts txt
+ capt <- inlineListToMediaWiki opts txt
let opt = if null txt
then ""
else "|alt=" ++ if null tit then capt else tit ++
@@ -115,7 +115,7 @@ blockToMediaWiki _ (CodeBlock (_,classes,_) str) = do
"javascript", "latex", "lisp", "lua", "matlab", "mirc", "mpasm", "mysql", "nsis", "objc",
"ocaml", "ocaml-brief", "oobas", "oracle8", "pascal", "perl", "php", "php-brief", "plsql",
"python", "qbasic", "rails", "reg", "robots", "ruby", "sas", "scheme", "sdlbasic",
- "smalltalk", "smarty", "sql", "tcl", "", "thinbasic", "tsql", "vb", "vbnet", "vhdl",
+ "smalltalk", "smarty", "sql", "tcl", "", "thinbasic", "tsql", "vb", "vbnet", "vhdl",
"visualfoxpro", "winbatch", "xml", "xpp", "z80"]
let (beg, end) = if null at
then ("<pre" ++ if null classes then ">" else " class=\"" ++ unwords classes ++ "\">", "</pre>")
@@ -124,7 +124,7 @@ blockToMediaWiki _ (CodeBlock (_,classes,_) str) = do
blockToMediaWiki opts (BlockQuote blocks) = do
contents <- blockListToMediaWiki opts blocks
- return $ "<blockquote>" ++ contents ++ "</blockquote>"
+ return $ "<blockquote>" ++ contents ++ "</blockquote>"
blockToMediaWiki opts (Table capt aligns widths headers rows') = do
let alignStrings = map alignmentToString aligns
@@ -221,7 +221,7 @@ listItemToMediaWiki opts items = do
-- | Convert definition list item (label, list of blocks) to MediaWiki.
definitionListItemToMediaWiki :: WriterOptions
- -> ([Inline],[[Block]])
+ -> ([Inline],[[Block]])
-> State WriterState String
definitionListItemToMediaWiki opts (label, items) = do
labelText <- inlineListToMediaWiki opts label
@@ -242,7 +242,7 @@ isSimpleList x =
BulletList items -> all isSimpleListItem items
OrderedList (num, sty, _) items -> all isSimpleListItem items &&
num == 1 && sty `elem` [DefaultStyle, Decimal]
- DefinitionList items -> all isSimpleListItem $ concatMap snd items
+ DefinitionList items -> all isSimpleListItem $ concatMap snd items
_ -> False
-- | True if list item can be handled with the simple wiki syntax. False if
@@ -287,8 +287,8 @@ tableRowToMediaWiki opts alignStrings rownum cols' = do
0 -> "header"
x | x `rem` 2 == 1 -> "odd"
_ -> "even"
- cols'' <- sequence $ zipWith
- (\alignment item -> tableItemToMediaWiki opts celltype alignment item)
+ cols'' <- sequence $ zipWith
+ (\alignment item -> tableItemToMediaWiki opts celltype alignment item)
alignStrings cols'
return $ "<tr class=\"" ++ rowclass ++ "\">\n" ++ unlines cols'' ++ "</tr>"
@@ -313,7 +313,7 @@ tableItemToMediaWiki opts celltype align' item = do
-- | Convert list of Pandoc block elements to MediaWiki.
blockListToMediaWiki :: WriterOptions -- ^ Options
-> [Block] -- ^ List of block elements
- -> State WriterState String
+ -> State WriterState String
blockListToMediaWiki opts blocks =
mapM (blockToMediaWiki opts) blocks >>= return . vcat
@@ -325,9 +325,9 @@ inlineListToMediaWiki opts lst =
-- | Convert Pandoc inline element to MediaWiki.
inlineToMediaWiki :: WriterOptions -> Inline -> State WriterState String
-inlineToMediaWiki opts (Emph lst) = do
+inlineToMediaWiki opts (Emph lst) = do
contents <- inlineListToMediaWiki opts lst
- return $ "''" ++ contents ++ "''"
+ return $ "''" ++ contents ++ "''"
inlineToMediaWiki opts (Strong lst) = do
contents <- inlineListToMediaWiki opts lst
@@ -365,8 +365,8 @@ inlineToMediaWiki _ (Str str) = return $ escapeString str
inlineToMediaWiki _ (Math _ str) = return $ "<math>" ++ str ++ "</math>"
-- note: str should NOT be escaped
-inlineToMediaWiki _ (RawInline "mediawiki" str) = return str
-inlineToMediaWiki _ (RawInline "html" str) = return str
+inlineToMediaWiki _ (RawInline "mediawiki" str) = return str
+inlineToMediaWiki _ (RawInline "html" str) = return str
inlineToMediaWiki _ (RawInline _ _) = return ""
inlineToMediaWiki _ (LineBreak) = return "<br />\n"
@@ -392,7 +392,7 @@ inlineToMediaWiki opts (Image alt (source, tit)) = do
else "|" ++ tit
return $ "[[Image:" ++ source ++ txt ++ "]]"
-inlineToMediaWiki opts (Note contents) = do
+inlineToMediaWiki opts (Note contents) = do
contents' <- blockListToMediaWiki opts contents
modify (\s -> s { stNotes = True })
return $ "<ref>" ++ contents' ++ "</ref>"
diff --git a/src/Text/Pandoc/Writers/Native.hs b/src/Text/Pandoc/Writers/Native.hs
index d2b56cd17..8b3148273 100644
--- a/src/Text/Pandoc/Writers/Native.hs
+++ b/src/Text/Pandoc/Writers/Native.hs
@@ -20,7 +20,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
{- |
Module : Text.Pandoc.Writers.Native
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
@@ -47,17 +47,17 @@ prettyList ds =
prettyBlock :: Block -> Doc
prettyBlock (BlockQuote blocks) =
"BlockQuote" $$ prettyList (map prettyBlock blocks)
-prettyBlock (OrderedList attribs blockLists) =
+prettyBlock (OrderedList attribs blockLists) =
"OrderedList" <> space <> text (show attribs) $$
(prettyList $ map (prettyList . map prettyBlock) blockLists)
-prettyBlock (BulletList blockLists) =
+prettyBlock (BulletList blockLists) =
"BulletList" $$
(prettyList $ map (prettyList . map prettyBlock) blockLists)
prettyBlock (DefinitionList items) = "DefinitionList" $$
(prettyList $ map deflistitem items)
where deflistitem (term, defs) = "(" <> text (show term) <> "," <> cr <>
nest 1 (prettyList $ map (prettyList . map prettyBlock) defs) <> ")"
-prettyBlock (Table caption aligns widths header rows) =
+prettyBlock (Table caption aligns widths header rows) =
"Table " <> text (show caption) <> " " <> text (show aligns) <> " " <>
text (show widths) $$
prettyRow header $$
diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs
index 7eb943a22..1bb4b5449 100644
--- a/src/Text/Pandoc/Writers/Org.hs
+++ b/src/Text/Pandoc/Writers/Org.hs
@@ -20,7 +20,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
{- |
Module : Text.Pandoc.Writers.Org
Copyright : Copyright (C) 2010 Puneeth Chaganti
- License : GNU GPL, version 2 or above
+ License : GNU GPL, version 2 or above
Maintainer : Puneeth Chaganti <punchagan@gmail.com>
Stability : alpha
@@ -32,14 +32,14 @@ Org-Mode: <http://orgmode.org>
-}
module Text.Pandoc.Writers.Org ( writeOrg) where
import Text.Pandoc.Definition
-import Text.Pandoc.Shared
+import Text.Pandoc.Shared
import Text.Pandoc.Pretty
import Text.Pandoc.Templates (renderTemplate)
import Data.List ( intersect, intersperse, transpose )
import Control.Monad.State
import Control.Applicative ( (<$>) )
-data WriterState =
+data WriterState =
WriterState { stNotes :: [[Block]]
, stLinks :: Bool
, stImages :: Bool
@@ -49,7 +49,7 @@ data WriterState =
-- | Convert Pandoc to Org.
writeOrg :: WriterOptions -> Pandoc -> String
-writeOrg opts document =
+writeOrg opts document =
let st = WriterState { stNotes = [], stLinks = False,
stImages = False, stHasMath = False,
stOptions = opts }
@@ -82,8 +82,8 @@ pandocToOrg (Pandoc (Meta tit auth dat) blocks) = do
-- | Return Org representation of notes.
notesToOrg :: [[Block]] -> State WriterState Doc
-notesToOrg notes =
- mapM (\(num, note) -> noteToOrg num note) (zip [1..] notes) >>=
+notesToOrg notes =
+ mapM (\(num, note) -> noteToOrg num note) (zip [1..] notes) >>=
return . vsep
-- | Return Org representation of a note.
@@ -106,11 +106,11 @@ titleToOrg :: [Inline] -> State WriterState Doc
titleToOrg [] = return empty
titleToOrg lst = do
contents <- inlineListToOrg lst
- return $ "#+TITLE: " <> contents
+ return $ "#+TITLE: " <> contents
--- | Convert Pandoc block element to Org.
+-- | Convert Pandoc block element to Org.
blockToOrg :: Block -- ^ Block element
- -> State WriterState Doc
+ -> State WriterState Doc
blockToOrg Null = return empty
blockToOrg (Plain inlines) = inlineListToOrg inlines
blockToOrg (Para [Image txt (src,tit)]) = do
@@ -120,7 +120,7 @@ blockToOrg (Para [Image txt (src,tit)]) = do
blockToOrg (Para inlines) = do
contents <- inlineListToOrg inlines
return $ contents <> blankline
-blockToOrg (RawBlock "html" str) =
+blockToOrg (RawBlock "html" str) =
return $ blankline $$ "#+BEGIN_HTML" $$
nest 2 (text str) $$ "#+END_HTML" $$ blankline
blockToOrg (RawBlock f str) | f == "org" || f == "latex" || f == "tex" =
@@ -134,17 +134,17 @@ blockToOrg (Header level inlines) = do
blockToOrg (CodeBlock (_,classes,_) str) = do
opts <- stOptions <$> get
let tabstop = writerTabStop opts
- let at = classes `intersect` ["asymptote", "C", "clojure", "css", "ditaa",
- "dot", "emacs-lisp", "gnuplot", "haskell", "js", "latex",
- "ledger", "lisp", "matlab", "mscgen", "ocaml", "octave",
- "oz", "perl", "plantuml", "python", "R", "ruby", "sass",
+ let at = classes `intersect` ["asymptote", "C", "clojure", "css", "ditaa",
+ "dot", "emacs-lisp", "gnuplot", "haskell", "js", "latex",
+ "ledger", "lisp", "matlab", "mscgen", "ocaml", "octave",
+ "oz", "perl", "plantuml", "python", "R", "ruby", "sass",
"scheme", "screen", "sh", "sql", "sqlite"]
let (beg, end) = case at of
[] -> ("#+BEGIN_EXAMPLE", "#+END_EXAMPLE")
(x:_) -> ("#+BEGIN_SRC " ++ x, "#+END_SRC")
return $ text beg $$ nest tabstop (text str) $$ text end $$ blankline
blockToOrg (BlockQuote blocks) = do
- contents <- blockListToOrg blocks
+ contents <- blockListToOrg blocks
return $ blankline $$ "#+BEGIN_QUOTE" $$
nest 2 contents $$ "#+END_QUOTE" $$ blankline
blockToOrg (Table caption' _ _ headers rows) = do
@@ -155,11 +155,11 @@ blockToOrg (Table caption' _ _ headers rows) = do
headers' <- mapM blockListToOrg headers
rawRows <- mapM (mapM blockListToOrg) rows
let numChars = maximum . map offset
- -- FIXME: width is not being used.
+ -- FIXME: width is not being used.
let widthsInChars =
map ((+2) . numChars) $ transpose (headers' : rawRows)
- -- FIXME: Org doesn't allow blocks with height more than 1.
- let hpipeBlocks blocks = hcat [beg, middle, end]
+ -- FIXME: Org doesn't allow blocks with height more than 1.
+ let hpipeBlocks blocks = hcat [beg, middle, end]
where h = maximum (map height blocks)
sep' = lblock 3 $ vcat (map text $ replicate h " | ")
beg = lblock 2 $ vcat (map text $ replicate h "| ")
@@ -170,7 +170,7 @@ blockToOrg (Table caption' _ _ headers rows) = do
rows' <- mapM (\row -> do cols <- mapM blockListToOrg row
return $ makeRow cols) rows
let border ch = char '|' <> char ch <>
- (hcat $ intersperse (char ch <> char '+' <> char ch) $
+ (hcat $ intersperse (char ch <> char '+' <> char ch) $
map (\l -> text $ replicate l ch) widthsInChars) <>
char ch <> char '|'
let body = vcat rows'
@@ -186,7 +186,7 @@ blockToOrg (OrderedList (start, _, delim) items) = do
let delim' = case delim of
TwoParens -> OneParen
x -> x
- let markers = take (length items) $ orderedListMarkers
+ let markers = take (length items) $ orderedListMarkers
(start, Decimal, delim')
let maxMarkerLength = maximum $ map length markers
let markers' = map (\m -> let s = maxMarkerLength - length m
@@ -222,7 +222,7 @@ definitionListItemToOrg (label, defs) = do
-- | Convert list of Pandoc block elements to Org.
blockListToOrg :: [Block] -- ^ List of block elements
- -> State WriterState Doc
+ -> State WriterState Doc
blockListToOrg blocks = mapM blockToOrg blocks >>= return . vcat
-- | Convert list of Pandoc inline elements to Org.
@@ -231,19 +231,19 @@ inlineListToOrg lst = mapM inlineToOrg lst >>= return . hcat
-- | Convert Pandoc inline element to Org.
inlineToOrg :: Inline -> State WriterState Doc
-inlineToOrg (Emph lst) = do
+inlineToOrg (Emph lst) = do
contents <- inlineListToOrg lst
return $ "/" <> contents <> "/"
inlineToOrg (Strong lst) = do
contents <- inlineListToOrg lst
return $ "*" <> contents <> "*"
-inlineToOrg (Strikeout lst) = do
+inlineToOrg (Strikeout lst) = do
contents <- inlineListToOrg lst
return $ "+" <> contents <> "+"
-inlineToOrg (Superscript lst) = do
+inlineToOrg (Superscript lst) = do
contents <- inlineListToOrg lst
return $ "^{" <> contents <> "}"
-inlineToOrg (Subscript lst) = do
+inlineToOrg (Subscript lst) = do
contents <- inlineListToOrg lst
return $ "_{" <> contents <> "}"
inlineToOrg (SmallCaps lst) = inlineListToOrg lst
@@ -276,7 +276,7 @@ inlineToOrg (Link txt (src, _)) = do
inlineToOrg (Image _ (source, _)) = do
modify $ \s -> s{ stImages = True }
return $ "[[" <> text source <> "]]"
-inlineToOrg (Note contents) = do
+inlineToOrg (Note contents) = do
-- add to notes in state
notes <- get >>= (return . stNotes)
modify $ \st -> st { stNotes = contents:notes }
diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs
index d98079940..d04fe4113 100644
--- a/src/Text/Pandoc/Writers/RST.hs
+++ b/src/Text/Pandoc/Writers/RST.hs
@@ -18,9 +18,9 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
-}
{- |
- Module : Text.Pandoc.Writers.RST
+ Module : Text.Pandoc.Writers.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
@@ -32,7 +32,7 @@ reStructuredText: <http://docutils.sourceforge.net/rst.html>
-}
module Text.Pandoc.Writers.RST ( writeRST) where
import Text.Pandoc.Definition
-import Text.Pandoc.Shared
+import Text.Pandoc.Shared
import Text.Pandoc.Templates (renderTemplate)
import Data.List ( isPrefixOf, intersperse, transpose )
import Text.Pandoc.Pretty
@@ -42,7 +42,7 @@ import Data.Char (isSpace)
type Refs = [([Inline], Target)]
-data WriterState =
+data WriterState =
WriterState { stNotes :: [[Block]]
, stLinks :: Refs
, stImages :: Refs
@@ -52,7 +52,7 @@ data WriterState =
-- | Convert Pandoc to RST.
writeRST :: WriterOptions -> Pandoc -> String
-writeRST opts document =
+writeRST opts document =
let st = WriterState { stNotes = [], stLinks = [],
stImages = [], stHasMath = False,
stOptions = opts }
@@ -89,8 +89,8 @@ pandocToRST (Pandoc (Meta tit auth dat) blocks) = do
refsToRST :: Refs -> State WriterState Doc
refsToRST refs = mapM keyToRST refs >>= return . vcat
--- | Return RST representation of a reference key.
-keyToRST :: ([Inline], (String, String))
+-- | Return RST representation of a reference key.
+keyToRST :: ([Inline], (String, String))
-> State WriterState Doc
keyToRST (label, (src, _)) = do
label' <- inlineListToRST label
@@ -101,7 +101,7 @@ keyToRST (label, (src, _)) = do
-- | Return RST representation of notes.
notesToRST :: [[Block]] -> State WriterState Doc
-notesToRST notes =
+notesToRST notes =
mapM (\(num, note) -> noteToRST num note) (zip [1..] notes) >>=
return . vsep
@@ -116,8 +116,8 @@ noteToRST num note = do
pictRefsToRST :: Refs -> State WriterState Doc
pictRefsToRST refs = mapM pictToRST refs >>= return . vcat
--- | Return RST representation of a picture substitution reference.
-pictToRST :: ([Inline], (String, String))
+-- | Return RST representation of a picture substitution reference.
+pictToRST :: ([Inline], (String, String))
-> State WriterState Doc
pictToRST (label, (src, _)) = do
label' <- inlineListToRST label
@@ -135,9 +135,9 @@ titleToRST lst = do
let border = text (replicate titleLength '=')
return $ border $$ contents $$ border
--- | Convert Pandoc block element to RST.
+-- | Convert Pandoc block element to RST.
blockToRST :: Block -- ^ Block element
- -> State WriterState Doc
+ -> State WriterState Doc
blockToRST Null = return empty
blockToRST (Plain inlines) = inlineListToRST inlines
blockToRST (Para [Image txt (src,tit)]) = do
@@ -168,7 +168,7 @@ blockToRST (CodeBlock (_,classes,_) str) = do
else return $ "::" $+$ nest tabstop (text str) $$ blankline
blockToRST (BlockQuote blocks) = do
tabstop <- get >>= (return . writerTabStop . stOptions)
- contents <- blockListToRST blocks
+ contents <- blockListToRST blocks
return $ (nest tabstop contents) <> blankline
blockToRST (Table caption _ widths headers rows) = do
caption' <- inlineListToRST caption
@@ -184,7 +184,7 @@ blockToRST (Table caption _ widths headers rows) = do
if isSimple
then map ((+2) . numChars) $ transpose (headers' : rawRows)
else map (floor . (fromIntegral (writerColumns opts) *)) widths
- let hpipeBlocks blocks = hcat [beg, middle, end]
+ let hpipeBlocks blocks = hcat [beg, middle, end]
where h = maximum (map height blocks)
sep' = lblock 3 $ vcat (map text $ replicate h " | ")
beg = lblock 2 $ vcat (map text $ replicate h "| ")
@@ -195,7 +195,7 @@ blockToRST (Table caption _ widths headers rows) = do
rows' <- mapM (\row -> do cols <- mapM blockListToRST row
return $ makeRow cols) rows
let border ch = char '+' <> char ch <>
- (hcat $ intersperse (char ch <> char '+' <> char ch) $
+ (hcat $ intersperse (char ch <> char '+' <> char ch) $
map (\l -> text $ replicate l ch) widthsInChars) <>
char ch <> char '+'
let body = vcat $ intersperse (border '-') rows'
@@ -208,9 +208,9 @@ blockToRST (BulletList items) = do
-- ensure that sublists have preceding blank line
return $ blankline $$ vcat contents $$ blankline
blockToRST (OrderedList (start, style', delim) items) = do
- let markers = if start == 1 && style' == DefaultStyle && delim == DefaultDelim
+ let markers = if start == 1 && style' == DefaultStyle && delim == DefaultDelim
then take (length items) $ repeat "#."
- else take (length items) $ orderedListMarkers
+ else take (length items) $ orderedListMarkers
(start, style', delim)
let maxMarkerLength = maximum $ map length markers
let markers' = map (\m -> let s = maxMarkerLength - length m
@@ -249,7 +249,7 @@ definitionListItemToRST (label, defs) = do
-- | Convert list of Pandoc block elements to RST.
blockListToRST :: [Block] -- ^ List of block elements
- -> State WriterState Doc
+ -> State WriterState Doc
blockListToRST blocks = mapM blockToRST blocks >>= return . vcat
-- | Convert list of Pandoc inline elements to RST.
@@ -303,19 +303,19 @@ inlineListToRST lst = mapM inlineToRST (insertBS lst) >>= return . hcat
-- | Convert Pandoc inline element to RST.
inlineToRST :: Inline -> State WriterState Doc
-inlineToRST (Emph lst) = do
+inlineToRST (Emph lst) = do
contents <- inlineListToRST lst
return $ "*" <> contents <> "*"
inlineToRST (Strong lst) = do
contents <- inlineListToRST lst
return $ "**" <> contents <> "**"
-inlineToRST (Strikeout lst) = do
+inlineToRST (Strikeout lst) = do
contents <- inlineListToRST lst
return $ "[STRIKEOUT:" <> contents <> "]"
-inlineToRST (Superscript lst) = do
+inlineToRST (Superscript lst) = do
contents <- inlineListToRST lst
return $ ":sup:`" <> contents <> "`"
-inlineToRST (Subscript lst) = do
+inlineToRST (Subscript lst) = do
contents <- inlineListToRST lst
return $ ":sub:`" <> contents <> "`"
inlineToRST (SmallCaps lst) = inlineListToRST lst
@@ -358,7 +358,7 @@ inlineToRST (Link txt (src, tit)) = do
else return $ "`" <> linktext <> " <" <> text src <> ">`_"
inlineToRST (Image alternate (source, tit)) = do
pics <- get >>= return . stImages
- let labelsUsed = map fst pics
+ let labelsUsed = map fst pics
let txt = if null alternate || alternate == [Str ""] ||
alternate `elem` labelsUsed
then [Str $ "image" ++ show (length pics)]
@@ -369,7 +369,7 @@ inlineToRST (Image alternate (source, tit)) = do
modify $ \st -> st { stImages = pics' }
label <- inlineListToRST txt
return $ "|" <> label <> "|"
-inlineToRST (Note contents) = do
+inlineToRST (Note contents) = do
-- add to notes in state
notes <- get >>= return . stNotes
modify $ \st -> st { stNotes = contents:notes }
diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs
index a571f2a0f..5ab71c8d6 100644
--- a/src/Text/Pandoc/Writers/RTF.hs
+++ b/src/Text/Pandoc/Writers/RTF.hs
@@ -19,10 +19,10 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
{- |
Module : Text.Pandoc.Writers.RTF
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 'Pandoc' documents to RTF (rich text format).
@@ -65,7 +65,7 @@ rtfEmbedImage x = return x
-- | Convert Pandoc to a string in rich text format.
writeRTF :: WriterOptions -> Pandoc -> String
-writeRTF options (Pandoc (Meta title authors date) blocks) =
+writeRTF options (Pandoc (Meta title authors date) blocks) =
let titletext = inlineListToRTF title
authorstext = map inlineListToRTF authors
datetext = inlineListToRTF date
@@ -84,11 +84,11 @@ writeRTF options (Pandoc (Meta title authors date) blocks) =
else body
-- | Construct table of contents from list of header blocks.
-tableOfContents :: [Block] -> String
+tableOfContents :: [Block] -> String
tableOfContents headers =
let contentsTree = hierarchicalize headers
- in concatMap (blockToRTF 0 AlignDefault) $
- [Header 1 [Str "Contents"],
+ in concatMap (blockToRTF 0 AlignDefault) $
+ [Header 1 [Str "Contents"],
BulletList (map elementToListItem contentsTree)]
elementToListItem :: Element -> [Block]
@@ -102,7 +102,7 @@ elementToListItem (Sec _ _ _ sectext subsecs) = [Plain sectext] ++
handleUnicode :: String -> String
handleUnicode [] = []
handleUnicode (c:cs) =
- if ord c > 127
+ if ord c > 127
then '\\':'u':(show (ord c)) ++ "?" ++ handleUnicode cs
else c:(handleUnicode cs)
@@ -132,32 +132,32 @@ rtfParSpaced :: Int -- ^ space after (in twips)
-> Int -- ^ first line indent (relative to block) (in twips)
-> Alignment -- ^ alignment
-> String -- ^ string with content
- -> String
-rtfParSpaced spaceAfter indent firstLineIndent alignment content =
+ -> String
+rtfParSpaced spaceAfter indent firstLineIndent alignment content =
let alignString = case alignment of
AlignLeft -> "\\ql "
AlignRight -> "\\qr "
AlignCenter -> "\\qc "
AlignDefault -> "\\ql "
in "{\\pard " ++ alignString ++
- "\\f0 \\sa" ++ (show spaceAfter) ++ " \\li" ++ (show indent) ++
+ "\\f0 \\sa" ++ (show spaceAfter) ++ " \\li" ++ (show indent) ++
" \\fi" ++ (show firstLineIndent) ++ " " ++ content ++ "\\par}\n"
--- | Default paragraph.
+-- | Default paragraph.
rtfPar :: Int -- ^ block indent (in twips)
-> Int -- ^ first line indent (relative to block) (in twips)
-> Alignment -- ^ alignment
-> String -- ^ string with content
- -> String
-rtfPar = rtfParSpaced 180
+ -> String
+rtfPar = rtfParSpaced 180
-- | Compact paragraph (e.g. for compact list items).
rtfCompact :: Int -- ^ block indent (in twips)
-> Int -- ^ first line indent (relative to block) (in twips)
-> Alignment -- ^ alignment
-> String -- ^ string with content
- -> String
-rtfCompact = rtfParSpaced 0
+ -> String
+rtfCompact = rtfParSpaced 0
-- number of twips to indent
indentIncrement :: Int
@@ -174,7 +174,7 @@ bulletMarker indent = case indent `mod` 720 of
-- | Returns appropriate (list of) ordered list markers for indent level.
orderedMarkers :: Int -> ListAttributes -> [String]
-orderedMarkers indent (start, style, delim) =
+orderedMarkers indent (start, style, delim) =
if style == DefaultStyle && delim == DefaultDelim
then case indent `mod` 720 of
0 -> orderedListMarkers (start, Decimal, Period)
@@ -187,30 +187,30 @@ blockToRTF :: Int -- ^ indent level
-> Block -- ^ block to convert
-> String
blockToRTF _ _ Null = ""
-blockToRTF indent alignment (Plain lst) =
+blockToRTF indent alignment (Plain lst) =
rtfCompact indent 0 alignment $ inlineListToRTF lst
-blockToRTF indent alignment (Para lst) =
+blockToRTF indent alignment (Para lst) =
rtfPar indent 0 alignment $ inlineListToRTF lst
-blockToRTF indent alignment (BlockQuote lst) =
- concatMap (blockToRTF (indent + indentIncrement) alignment) lst
+blockToRTF indent alignment (BlockQuote lst) =
+ concatMap (blockToRTF (indent + indentIncrement) alignment) lst
blockToRTF indent _ (CodeBlock _ str) =
rtfPar indent 0 AlignLeft ("\\f1 " ++ (codeStringToRTF str))
blockToRTF _ _ (RawBlock "rtf" str) = str
blockToRTF _ _ (RawBlock _ _) = ""
-blockToRTF indent alignment (BulletList lst) = spaceAtEnd $
+blockToRTF indent alignment (BulletList lst) = spaceAtEnd $
concatMap (listItemToRTF alignment indent (bulletMarker indent)) lst
-blockToRTF indent alignment (OrderedList attribs lst) = spaceAtEnd $ concat $
+blockToRTF indent alignment (OrderedList attribs lst) = spaceAtEnd $ concat $
zipWith (listItemToRTF alignment indent) (orderedMarkers indent attribs) lst
-blockToRTF indent alignment (DefinitionList lst) = spaceAtEnd $
+blockToRTF indent alignment (DefinitionList lst) = spaceAtEnd $
concatMap (definitionListItemToRTF alignment indent) lst
-blockToRTF indent _ HorizontalRule =
+blockToRTF indent _ HorizontalRule =
rtfPar indent 0 AlignCenter "\\emdash\\emdash\\emdash\\emdash\\emdash"
blockToRTF indent alignment (Header level lst) = rtfPar indent 0 alignment $
"\\b \\fs" ++ (show (40 - (level * 4))) ++ " " ++ inlineListToRTF lst
-blockToRTF indent alignment (Table caption aligns sizes headers rows) =
+blockToRTF indent alignment (Table caption aligns sizes headers rows) =
(if all null headers
then ""
- else tableRowToRTF True indent aligns sizes headers) ++
+ else tableRowToRTF True indent aligns sizes headers) ++
concatMap (tableRowToRTF False indent aligns sizes) rows ++
rtfPar indent 0 alignment (inlineListToRTF caption)
@@ -232,7 +232,7 @@ tableRowToRTF header indent aligns sizes' cols =
end = "}\n\\intbl\\row}\n"
in start ++ columns ++ end
-tableItemToRTF :: Int -> Alignment -> [Block] -> String
+tableItemToRTF :: Int -> Alignment -> [Block] -> String
tableItemToRTF indent alignment item =
let contents = concatMap (blockToRTF indent alignment) item
in "{\\intbl " ++ contents ++ "\\cell}\n"
@@ -240,7 +240,7 @@ tableItemToRTF indent alignment item =
-- | Ensure that there's the same amount of space after compact
-- lists as after regular lists.
spaceAtEnd :: String -> String
-spaceAtEnd str =
+spaceAtEnd str =
if isSuffixOf "\\par}\n" str
then (take ((length str) - 6) str) ++ "\\sa180\\par}\n"
else str
@@ -251,10 +251,10 @@ listItemToRTF :: Alignment -- ^ alignment
-> String -- ^ list start marker
-> [Block] -- ^ list item (list of blocks)
-> [Char]
-listItemToRTF alignment indent marker [] =
- rtfCompact (indent + listIncrement) (0 - listIncrement) alignment
- (marker ++ "\\tx" ++ (show listIncrement) ++ "\\tab ")
-listItemToRTF alignment indent marker list =
+listItemToRTF alignment indent marker [] =
+ rtfCompact (indent + listIncrement) (0 - listIncrement) alignment
+ (marker ++ "\\tx" ++ (show listIncrement) ++ "\\tab ")
+listItemToRTF alignment indent marker list =
let (first:rest) = map (blockToRTF (indent + listIncrement) alignment) list
listMarker = "\\fi" ++ show (0 - listIncrement) ++ " " ++ marker ++ "\\tx" ++
show listIncrement ++ "\\tab"
@@ -277,7 +277,7 @@ definitionListItemToRTF alignment indent (label, defs) =
let labelText = blockToRTF indent alignment (Plain label)
itemsText = concatMap (blockToRTF (indent + listIncrement) alignment) $
concat defs
- in labelText ++ itemsText
+ in labelText ++ itemsText
-- | Convert list of inline items to RTF.
inlineListToRTF :: [Inline] -- ^ list of inlines to convert
@@ -293,9 +293,9 @@ inlineToRTF (Strikeout lst) = "{\\strike " ++ (inlineListToRTF lst) ++ "}"
inlineToRTF (Superscript lst) = "{\\super " ++ (inlineListToRTF lst) ++ "}"
inlineToRTF (Subscript lst) = "{\\sub " ++ (inlineListToRTF lst) ++ "}"
inlineToRTF (SmallCaps lst) = "{\\scaps " ++ (inlineListToRTF lst) ++ "}"
-inlineToRTF (Quoted SingleQuote lst) =
+inlineToRTF (Quoted SingleQuote lst) =
"\\u8216'" ++ (inlineListToRTF lst) ++ "\\u8217'"
-inlineToRTF (Quoted DoubleQuote lst) =
+inlineToRTF (Quoted DoubleQuote lst) =
"\\u8220\"" ++ (inlineListToRTF lst) ++ "\\u8221\""
inlineToRTF (Code _ str) = "{\\f1 " ++ (codeStringToRTF str) ++ "}"
inlineToRTF (Str str) = stringToRTF str
@@ -305,11 +305,11 @@ inlineToRTF (RawInline "rtf" str) = str
inlineToRTF (RawInline _ _) = ""
inlineToRTF (LineBreak) = "\\line "
inlineToRTF Space = " "
-inlineToRTF (Link text (src, _)) =
- "{\\field{\\*\\fldinst{HYPERLINK \"" ++ (codeStringToRTF src) ++
+inlineToRTF (Link text (src, _)) =
+ "{\\field{\\*\\fldinst{HYPERLINK \"" ++ (codeStringToRTF src) ++
"\"}}{\\fldrslt{\\ul\n" ++ (inlineListToRTF text) ++ "\n}}}\n"
-inlineToRTF (Image _ (source, _)) =
- "{\\cf1 [image: " ++ source ++ "]\\cf0}"
+inlineToRTF (Image _ (source, _)) =
+ "{\\cf1 [image: " ++ source ++ "]\\cf0}"
inlineToRTF (Note contents) =
- "{\\super\\chftn}{\\*\\footnote\\chftn\\~\\plain\\pard " ++
+ "{\\super\\chftn}{\\*\\footnote\\chftn\\~\\plain\\pard " ++
(concatMap (blockToRTF 0 AlignDefault) contents) ++ "}"
diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs
index 6bb782899..e85013162 100644
--- a/src/Text/Pandoc/Writers/Texinfo.hs
+++ b/src/Text/Pandoc/Writers/Texinfo.hs
@@ -19,10 +19,10 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
{- |
Module : Text.Pandoc.Writers.Texinfo
Copyright : Copyright (C) 2008-2010 John MacFarlane and Peter Wang
- 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 'Pandoc' format into Texinfo.
@@ -40,7 +40,7 @@ import Text.Pandoc.Pretty
import Network.URI ( isAbsoluteURI, unEscapeString )
import System.FilePath
-data WriterState =
+data WriterState =
WriterState { stStrikeout :: Bool -- document contains strikeout
, stSuperscript :: Bool -- document contains superscript
, stSubscript :: Bool -- document contains subscript
@@ -53,8 +53,8 @@ data WriterState =
-- | Convert Pandoc to Texinfo.
writeTexinfo :: WriterOptions -> Pandoc -> String
-writeTexinfo options document =
- evalState (pandocToTexinfo options $ wrapTop document) $
+writeTexinfo options document =
+ evalState (pandocToTexinfo options $ wrapTop document) $
WriterState { stStrikeout = False, stSuperscript = False, stSubscript = False }
-- | Add a "Top" node around the document, needed by Texinfo.
@@ -217,7 +217,7 @@ blockToTexinfo (Table caption aligns widths heads rows) = do
else return $ "@columnfractions " ++ concatMap (printf "%.2f ") widths
let tableBody = text ("@multitable " ++ colDescriptors) $$
headers $$
- vcat rowsText $$
+ vcat rowsText $$
text "@end multitable"
return $ if isEmpty captionText
then tableBody <> blankline
@@ -241,7 +241,7 @@ tableAnyRowToTexinfo :: String
-> [[Block]]
-> State WriterState Doc
tableAnyRowToTexinfo itemtype aligns cols =
- zipWithM alignedBlock aligns cols >>=
+ zipWithM alignedBlock aligns cols >>=
return . (text itemtype $$) . foldl (\row item -> row $$
(if isEmpty row then empty else text " @tab ") <> item) empty
@@ -358,8 +358,8 @@ inlineToTexinfo :: Inline -- ^ Inline to convert
inlineToTexinfo (Emph lst) =
inlineListToTexinfo lst >>= return . inCmd "emph"
-inlineToTexinfo (Strong lst) =
- inlineListToTexinfo lst >>= return . inCmd "strong"
+inlineToTexinfo (Strong lst) =
+ inlineListToTexinfo lst >>= return . inCmd "strong"
inlineToTexinfo (Strikeout lst) = do
modify $ \st -> st{ stStrikeout = True }
diff --git a/src/Text/Pandoc/Writers/Textile.hs b/src/Text/Pandoc/Writers/Textile.hs
index 26d5ec6d7..e3711911b 100644
--- a/src/Text/Pandoc/Writers/Textile.hs
+++ b/src/Text/Pandoc/Writers/Textile.hs
@@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
{- |
Module : Text.Pandoc.Writers.Textile
Copyright : Copyright (C) 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
@@ -31,7 +31,7 @@ Textile: <http://thresholdstate.com/articles/4312/the-textile-reference-manual>
-}
module Text.Pandoc.Writers.Textile ( writeTextile ) where
import Text.Pandoc.Definition
-import Text.Pandoc.Shared
+import Text.Pandoc.Shared
import Text.Pandoc.Templates (renderTemplate)
import Text.Pandoc.XML ( escapeStringForXML )
import Data.List ( intercalate )
@@ -46,9 +46,9 @@ data WriterState = WriterState {
-- | Convert Pandoc to Textile.
writeTextile :: WriterOptions -> Pandoc -> String
-writeTextile opts document =
- evalState (pandocToTextile opts document)
- (WriterState { stNotes = [], stListLevel = [], stUseTags = False })
+writeTextile opts document =
+ evalState (pandocToTextile opts document)
+ (WriterState { stNotes = [], stListLevel = [], stUseTags = False })
-- | Return Textile representation of document.
pandocToTextile :: WriterOptions -> Pandoc -> State WriterState String
@@ -90,14 +90,14 @@ escapeCharForTextile x = case x of
escapeStringForTextile :: String -> String
escapeStringForTextile = concatMap escapeCharForTextile
--- | Convert Pandoc block element to Textile.
+-- | Convert Pandoc block element to Textile.
blockToTextile :: WriterOptions -- ^ Options
-> Block -- ^ Block element
- -> State WriterState String
+ -> State WriterState String
blockToTextile _ Null = return ""
-blockToTextile opts (Plain inlines) =
+blockToTextile opts (Plain inlines) =
inlineListToTextile opts inlines
blockToTextile opts (Para [Image txt (src,tit)]) = do
@@ -236,7 +236,7 @@ listItemToTextile opts items = do
-- | Convert definition list item (label, list of blocks) to Textile.
definitionListItemToTextile :: WriterOptions
- -> ([Inline],[[Block]])
+ -> ([Inline],[[Block]])
-> State WriterState String
definitionListItemToTextile opts (label, items) = do
labelText <- inlineListToTextile opts label
@@ -294,8 +294,8 @@ tableRowToTextile opts alignStrings rownum cols' = do
0 -> "header"
x | x `rem` 2 == 1 -> "odd"
_ -> "even"
- cols'' <- sequence $ zipWith
- (\alignment item -> tableItemToTextile opts celltype alignment item)
+ cols'' <- sequence $ zipWith
+ (\alignment item -> tableItemToTextile opts celltype alignment item)
alignStrings cols'
return $ "<tr class=\"" ++ rowclass ++ "\">\n" ++ unlines cols'' ++ "</tr>"
@@ -320,7 +320,7 @@ tableItemToTextile opts celltype align' item = do
-- | Convert list of Pandoc block elements to Textile.
blockListToTextile :: WriterOptions -- ^ Options
-> [Block] -- ^ List of block elements
- -> State WriterState String
+ -> State WriterState String
blockListToTextile opts blocks =
mapM (blockToTextile opts) blocks >>= return . vcat
@@ -332,11 +332,11 @@ inlineListToTextile opts lst =
-- | Convert Pandoc inline element to Textile.
inlineToTextile :: WriterOptions -> Inline -> State WriterState String
-inlineToTextile opts (Emph lst) = do
+inlineToTextile opts (Emph lst) = do
contents <- inlineListToTextile opts lst
return $ if '_' `elem` contents
then "<em>" ++ contents ++ "</em>"
- else "_" ++ contents ++ "_"
+ else "_" ++ contents ++ "_"
inlineToTextile opts (Strong lst) = do
contents <- inlineListToTextile opts lst
@@ -377,7 +377,7 @@ inlineToTextile opts (Cite _ lst) = inlineListToTextile opts lst
inlineToTextile _ (Code _ str) =
return $ if '@' `elem` str
then "<tt>" ++ escapeStringForXML str ++ "</tt>"
- else "@" ++ str ++ "@"
+ else "@" ++ str ++ "@"
inlineToTextile _ (Str str) = return $ escapeStringForTextile str