summaryrefslogtreecommitdiff
path: root/src/Text
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2014-07-12 22:57:22 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2014-07-12 22:57:22 -0700
commit4676bfdf825a2b5b205d6057462d317c00c6b354 (patch)
tree2d5e84a0ddec2b3c2102e6d4cec3cf03e69e1164 /src/Text
parent8bbcff0cfcd9923cdcf5024d13bb411d085715d0 (diff)
Removed space at ends of lines in source.
Diffstat (limited to 'src/Text')
-rw-r--r--src/Text/Pandoc.hs2
-rw-r--r--src/Text/Pandoc/Parsing.hs74
-rw-r--r--src/Text/Pandoc/Readers/Docx.hs18
-rw-r--r--src/Text/Pandoc/Readers/Docx/Lists.hs14
-rw-r--r--src/Text/Pandoc/Readers/Docx/Parse.hs48
-rw-r--r--src/Text/Pandoc/Readers/Docx/Reducible.hs8
-rw-r--r--src/Text/Pandoc/Readers/Docx/TexChar.hs2
-rw-r--r--src/Text/Pandoc/Shared.hs4
-rw-r--r--src/Text/Pandoc/Writers/AsciiDoc.hs8
-rw-r--r--src/Text/Pandoc/Writers/ICML.hs8
-rw-r--r--src/Text/Pandoc/Writers/OpenDocument.hs4
-rw-r--r--src/Text/Pandoc/Writers/RST.hs2
12 files changed, 96 insertions, 96 deletions
diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs
index 23b97e6c1..b303fa7d7 100644
--- a/src/Text/Pandoc.hs
+++ b/src/Text/Pandoc.hs
@@ -303,7 +303,7 @@ getReader :: String -> Either String Reader
getReader s =
case parseFormatSpec s of
Left e -> Left $ intercalate "\n" $ [m | Message m <- errorMessages e]
- Right (readerName, setExts) ->
+ Right (readerName, setExts) ->
case lookup readerName readers of
Nothing -> Left $ "Unknown reader: " ++ readerName
Just (StringReader r) -> Right $ StringReader $ \o ->
diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs
index d4d5295c0..d775b3f36 100644
--- a/src/Text/Pandoc/Parsing.hs
+++ b/src/Text/Pandoc/Parsing.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE
+{-# LANGUAGE
FlexibleContexts
, GeneralizedNewtypeDeriving
, TypeSynonymInstances
@@ -100,7 +100,7 @@ module Text.Pandoc.Parsing ( anyLine,
macro,
applyMacros',
Parser,
- ParserT,
+ ParserT,
F(..),
runF,
askF,
@@ -222,7 +222,7 @@ anyLine = do
_ -> mzero
-- | Like @manyTill@, but reads at least one item.
-many1Till :: Stream s m t
+many1Till :: Stream s m t
=> ParserT s st m a
-> ParserT s st m end
-> ParserT s st m [a]
@@ -501,7 +501,7 @@ mathInline =
-- displacement (the difference between the source column at the end
-- and the source column at the beginning). Vertical displacement
-- (source row) is ignored.
-withHorizDisplacement :: Stream s m Char
+withHorizDisplacement :: Stream s m Char
=> ParserT s st m a -- ^ Parser to apply
-> ParserT s st m (a, Int) -- ^ (result, displacement)
withHorizDisplacement parser = do
@@ -528,7 +528,7 @@ withRaw parser = do
return (result, raw)
-- | Parses backslash, then applies character parser.
-escaped :: Stream s m Char
+escaped :: Stream s m Char
=> ParserT s st m Char -- ^ Parser for character to escape
-> ParserT s st m Char
escaped parser = try $ char '\\' >> parser
@@ -564,7 +564,7 @@ decimal = do
-- returns (DefaultStyle, [next example number]). The next
-- example number is incremented in parser state, and the label
-- (if present) is added to the label table.
-exampleNum :: Stream s m Char
+exampleNum :: Stream s m Char
=> ParserT s ParserState m (ListNumberStyle, Int)
exampleNum = do
char '@'
@@ -609,7 +609,7 @@ anyOrderedListMarker = choice $
lowerAlpha, lowerRoman, upperAlpha, upperRoman]]
-- | Parses a list number (num) followed by a period, returns list attributes.
-inPeriod :: Stream s m Char
+inPeriod :: Stream s m Char
=> ParserT s st m (ListNumberStyle, Int)
-> ParserT s st m ListAttributes
inPeriod num = try $ do
@@ -621,7 +621,7 @@ inPeriod num = try $ do
return (start, style, delim)
-- | Parses a list number (num) followed by a paren, returns list attributes.
-inOneParen :: Stream s m Char
+inOneParen :: Stream s m Char
=> ParserT s st m (ListNumberStyle, Int)
-> ParserT s st m ListAttributes
inOneParen num = try $ do
@@ -630,7 +630,7 @@ inOneParen num = try $ do
return (start, style, OneParen)
-- | Parses a list number (num) enclosed in parens, returns list attributes.
-inTwoParens :: Stream s m Char
+inTwoParens :: Stream s m Char
=> ParserT s st m (ListNumberStyle, Int)
-> ParserT s st m ListAttributes
inTwoParens num = try $ do
@@ -641,7 +641,7 @@ inTwoParens num = try $ do
-- | Parses an ordered list marker with a given style and delimiter,
-- returns number.
-orderedListMarker :: Stream s m Char
+orderedListMarker :: Stream s m Char
=> ListNumberStyle
-> ListNumberDelim
-> ParserT s ParserState m Int
@@ -688,7 +688,7 @@ lineBlockLines = try $ do
-- | Parse a table using 'headerParser', 'rowParser',
-- 'lineParser', and 'footerParser'.
-tableWith :: Stream s m Char
+tableWith :: Stream s m Char
=> ParserT s ParserState m ([[Block]], [Alignment], [Int])
-> ([Int] -> ParserT s ParserState m [[Block]])
-> ParserT s ParserState m sep
@@ -735,7 +735,7 @@ widthsFromIndices numColumns' indices =
-- (which may be grid), then the rows,
-- which may be grid, separated by blank lines, and
-- ending with a footer (dashed line followed by blank line).
-gridTableWith :: Stream [Char] m Char
+gridTableWith :: Stream [Char] m Char
=> ParserT [Char] ParserState m [Block] -- ^ Block list parser
-> Bool -- ^ Headerless table
-> ParserT [Char] ParserState m Block
@@ -765,7 +765,7 @@ gridTableSep :: Stream s m Char => Char -> ParserT s ParserState m Char
gridTableSep ch = try $ gridDashedLines ch >> return '\n'
-- | Parse header for a grid table.
-gridTableHeader :: Stream [Char] m Char
+gridTableHeader :: Stream [Char] m Char
=> Bool -- ^ Headerless table
-> ParserT [Char] ParserState m [Block]
-> ParserT [Char] ParserState m ([[Block]], [Alignment], [Int])
@@ -798,7 +798,7 @@ gridTableRawLine indices = do
return (gridTableSplitLine indices line)
-- | Parse row of grid table.
-gridTableRow :: Stream [Char] m Char
+gridTableRow :: Stream [Char] m Char
=> ParserT [Char] ParserState m [Block]
-> [Int]
-> ParserT [Char] ParserState m [[Block]]
@@ -826,7 +826,7 @@ gridTableFooter = blanklines
---
-- | Parse a string with a given parser and state.
-readWith :: (Show s, Stream s Identity Char)
+readWith :: (Show s, Stream s Identity Char)
=> ParserT s st Identity a -- ^ parser
-> st -- ^ initial state
-> s -- ^ input
@@ -844,7 +844,7 @@ readWith parser state input =
Right result -> result
-- | Parse a string with @parser@ (for testing).
-testStringWith :: (Show s, Show a, Stream s Identity Char)
+testStringWith :: (Show s, Show a, Stream s Identity Char)
=> ParserT s ParserState Identity a
-> s
-> IO ()
@@ -1038,7 +1038,7 @@ registerHeader (ident,classes,kvs) header' = do
failUnlessSmart :: (Stream s m a, HasReaderOptions st) => ParserT s st m ()
failUnlessSmart = getOption readerSmart >>= guard
-smartPunctuation :: Stream s m Char
+smartPunctuation :: Stream s m Char
=> ParserT s ParserState m Inlines
-> ParserT s ParserState m Inlines
smartPunctuation inlineParser = do
@@ -1048,12 +1048,12 @@ smartPunctuation inlineParser = do
apostrophe :: Stream s m Char => ParserT s st m Inlines
apostrophe = (char '\'' <|> char '\8217') >> return (B.str "\x2019")
-quoted :: Stream s m Char
+quoted :: Stream s m Char
=> ParserT s ParserState m Inlines
-> ParserT s ParserState m Inlines
quoted inlineParser = doubleQuoted inlineParser <|> singleQuoted inlineParser
-withQuoteContext :: Stream s m t
+withQuoteContext :: Stream s m t
=> QuoteContext
-> ParserT s ParserState m a
-> ParserT s ParserState m a
@@ -1066,7 +1066,7 @@ withQuoteContext context parser = do
setState newState { stateQuoteContext = oldQuoteContext }
return result
-singleQuoted :: Stream s m Char
+singleQuoted :: Stream s m Char
=> ParserT s ParserState m Inlines
-> ParserT s ParserState m Inlines
singleQuoted inlineParser = try $ do
@@ -1074,7 +1074,7 @@ singleQuoted inlineParser = try $ do
withQuoteContext InSingleQuote $ many1Till inlineParser singleQuoteEnd >>=
return . B.singleQuoted . mconcat
-doubleQuoted :: Stream s m Char
+doubleQuoted :: Stream s m Char
=> ParserT s ParserState m Inlines
-> ParserT s ParserState m Inlines
doubleQuoted inlineParser = try $ do
@@ -1082,8 +1082,8 @@ doubleQuoted inlineParser = try $ do
withQuoteContext InDoubleQuote $ manyTill inlineParser doubleQuoteEnd >>=
return . B.doubleQuoted . mconcat
-failIfInQuoteContext :: Stream s m t
- => QuoteContext
+failIfInQuoteContext :: Stream s m t
+ => QuoteContext
-> ParserT s ParserState m ()
failIfInQuoteContext context = do
st <- getState
@@ -1097,7 +1097,7 @@ charOrRef cs =
guard (c `elem` cs)
return c)
-singleQuoteStart :: Stream s m Char
+singleQuoteStart :: Stream s m Char
=> ParserT s ParserState m ()
singleQuoteStart = do
failIfInQuoteContext InSingleQuote
@@ -1105,24 +1105,24 @@ singleQuoteStart = do
guard =<< notAfterString
() <$ charOrRef "'\8216\145"
-singleQuoteEnd :: Stream s m Char
+singleQuoteEnd :: Stream s m Char
=> ParserT s st m ()
singleQuoteEnd = try $ do
charOrRef "'\8217\146"
notFollowedBy alphaNum
-doubleQuoteStart :: Stream s m Char
+doubleQuoteStart :: Stream s m Char
=> ParserT s ParserState m ()
doubleQuoteStart = do
failIfInQuoteContext InDoubleQuote
try $ do charOrRef "\"\8220\147"
notFollowedBy . satisfy $ flip elem [' ', '\t', '\n']
-doubleQuoteEnd :: Stream s m Char
+doubleQuoteEnd :: Stream s m Char
=> ParserT s st m ()
doubleQuoteEnd = void (charOrRef "\"\8221\148")
-ellipses :: Stream s m Char
+ellipses :: Stream s m Char
=> ParserT s st m Inlines
ellipses = do
try (charOrRef "\8230\133") <|> try (string "..." >> return '…')
@@ -1136,32 +1136,32 @@ dash = do
else B.str <$> (hyphenDash <|> emDash <|> enDash)
-- Two hyphens = en-dash, three = em-dash
-hyphenDash :: Stream s m Char
+hyphenDash :: Stream s m Char
=> ParserT s st m String
hyphenDash = do
try $ string "--"
option "\8211" (char '-' >> return "\8212")
-emDash :: Stream s m Char
+emDash :: Stream s m Char
=> ParserT s st m String
emDash = do
try (charOrRef "\8212\151")
return "\8212"
-enDash :: Stream s m Char
+enDash :: Stream s m Char
=> ParserT s st m String
enDash = do
try (charOrRef "\8212\151")
return "\8211"
-enDashOld :: Stream s m Char
+enDashOld :: Stream s m Char
=> ParserT s st m Inlines
enDashOld = do
try (charOrRef "\8211\150") <|>
try (char '-' >> lookAhead (satisfy isDigit) >> return '–')
return (B.str "\8211")
-emDashOld :: Stream s m Char
+emDashOld :: Stream s m Char
=> ParserT s st m Inlines
emDashOld = do
try (charOrRef "\8212\151") <|> (try $ string "--" >> optional (char '-') >> return '-')
@@ -1169,7 +1169,7 @@ emDashOld = do
-- This is used to prevent exponential blowups for things like:
-- a**a*a**a*a**a*a**a*a**a*a**a*a**
-nested :: Stream s m a
+nested :: Stream s m a
=> ParserT s ParserState m a
-> ParserT s ParserState m a
nested p = do
@@ -1198,7 +1198,7 @@ citeKey = try $ do
--
-- | Parse a \newcommand or \renewcommand macro definition.
-macro :: (Stream [Char] m Char, HasMacros st, HasReaderOptions st)
+macro :: (Stream [Char] m Char, HasMacros st, HasReaderOptions st)
=> ParserT [Char] st m Blocks
macro = do
apply <- getOption readerApplyMacros
@@ -1214,8 +1214,8 @@ macro = do
else return $ rawBlock "latex" def'
-- | Apply current macros to string.
-applyMacros' :: Stream [Char] m Char
- => String
+applyMacros' :: Stream [Char] m Char
+ => String
-> ParserT [Char] ParserState m String
applyMacros' target = do
apply <- getOption readerApplyMacros
diff --git a/src/Text/Pandoc/Readers/Docx.hs b/src/Text/Pandoc/Readers/Docx.hs
index fe4c6b7e6..882e8d7d8 100644
--- a/src/Text/Pandoc/Readers/Docx.hs
+++ b/src/Text/Pandoc/Readers/Docx.hs
@@ -150,7 +150,7 @@ runStyleToContainers rPr =
classContainers = case rStyle rPr of
Nothing -> []
Just s -> spanClassToContainers s
-
+
formatters = map Container $ mapMaybe id
[ if isBold rPr then (Just Strong) else Nothing
, if isItalic rPr then (Just Emph) else Nothing
@@ -188,7 +188,7 @@ parStyleToContainers pPr | (c:cs) <- pStyle pPr, c `elem` blockQuoteDivs =
parStyleToContainers pPr | (_:cs) <- pStyle pPr =
let pPr' = pPr { pStyle = cs}
in
- parStyleToContainers pPr'
+ parStyleToContainers pPr'
parStyleToContainers pPr | null (pStyle pPr),
Just left <- indentation pPr >>= leftParIndent,
Just hang <- indentation pPr >>= hangingParIndent =
@@ -205,7 +205,7 @@ parStyleToContainers pPr | null (pStyle pPr),
True -> (Container BlockQuote) : (parStyleToContainers pPr')
False -> parStyleToContainers pPr'
parStyleToContainers _ = []
-
+
strToInlines :: String -> [Inline]
strToInlines = toList . text
@@ -258,9 +258,9 @@ runToInlines (Run rs runElems)
| otherwise =
return $
rebuild (runStyleToContainers rs) (concatMap runElemToInlines runElems)
-runToInlines (Footnote bps) =
+runToInlines (Footnote bps) =
concatMapM bodyPartToBlocks bps >>= (\blks -> return [Note blks])
-runToInlines (Endnote bps) =
+runToInlines (Endnote bps) =
concatMapM bodyPartToBlocks bps >>= (\blks -> return [Note blks])
makeDataUrl :: String -> B.ByteString -> Maybe String
@@ -343,7 +343,7 @@ oMathElemToTexString (Bar style base) = do
Top -> printf "\\overline{%s}" baseString
Bottom -> printf "\\underline{%s}" baseString
oMathElemToTexString (Box base) = baseToTexString base
-oMathElemToTexString (BorderBox base) =
+oMathElemToTexString (BorderBox base) =
baseToTexString base >>= (\s -> return $ printf "\\boxed{%s}" s)
oMathElemToTexString (Delimiter dPr bases) = do
let beg = fromMaybe '(' (delimBegChar dPr)
@@ -474,7 +474,7 @@ oMathElemToTexString (OMathRun _ run) = return $ stringToTex $ runToString run
baseToTexString :: Base -> DocxContext String
baseToTexString (Base mathElems) =
concatMapM oMathElemToTexString mathElems
-
+
isAnchorSpan :: Inline -> Bool
isAnchorSpan (Span (ident, classes, kvs) ils) =
@@ -535,7 +535,7 @@ bodyPartToBlocks (Paragraph pPr parparts)
let
otherConts = filter (not . isBlockCodeContainer) (parStyleToContainers pPr)
in
- return $
+ return $
rebuild
otherConts
[CodeBlock ("", [], []) (concatMap parPartToString parparts)]
@@ -582,7 +582,7 @@ bodyPartToBlocks (Tbl cap _ look (r:rs)) = do
hdrCells <- case hdr of
Just r' -> rowToBlocksList r'
Nothing -> return []
-
+
cells <- mapM rowToBlocksList rows
let size = case null hdrCells of
diff --git a/src/Text/Pandoc/Readers/Docx/Lists.hs b/src/Text/Pandoc/Readers/Docx/Lists.hs
index 1e37d0076..ea195c14a 100644
--- a/src/Text/Pandoc/Readers/Docx/Lists.hs
+++ b/src/Text/Pandoc/Readers/Docx/Lists.hs
@@ -121,7 +121,7 @@ handleListParagraphs (
in
handleListParagraphs ((Div attr1 (blks1 ++ [newDiv2])) : blks)
handleListParagraphs (blk:blks) = blk : (handleListParagraphs blks)
-
+
separateBlocks' :: Block -> [[Block]] -> [[Block]]
separateBlocks' blk ([] : []) = [[blk]]
separateBlocks' b@(BulletList _) acc = (init acc) ++ [(last acc) ++ [b]]
@@ -139,7 +139,7 @@ flatToBullets' :: Integer -> [Block] -> [Block]
flatToBullets' _ [] = []
flatToBullets' num xs@(b : elems)
| getLevelN b == num = b : (flatToBullets' num elems)
- | otherwise =
+ | otherwise =
let bNumId = getNumIdN b
bLevel = getLevelN b
(children, remaining) =
@@ -162,7 +162,7 @@ flatToBullets elems = flatToBullets' (-1) elems
blocksToBullets :: [Block] -> [Block]
blocksToBullets blks =
- bottomUp removeListDivs $
+ bottomUp removeListDivs $
flatToBullets $ (handleListParagraphs blks)
plainParaInlines :: Block -> [Inline]
@@ -216,12 +216,12 @@ removeListDivs' blk = [blk]
removeListDivs :: [Block] -> [Block]
removeListDivs = concatMap removeListDivs'
-
+
blocksToDefinitions :: [Block] -> [Block]
blocksToDefinitions = blocksToDefinitions' [] []
-
-
-
+
+
+
diff --git a/src/Text/Pandoc/Readers/Docx/Parse.hs b/src/Text/Pandoc/Readers/Docx/Parse.hs
index 4b5a11fa8..8541a1a3a 100644
--- a/src/Text/Pandoc/Readers/Docx/Parse.hs
+++ b/src/Text/Pandoc/Readers/Docx/Parse.hs
@@ -106,7 +106,7 @@ type NameSpaces = [(String, String)]
data Docx = Docx Document
deriving Show
-data Document = Document NameSpaces Body
+data Document = Document NameSpaces Body
deriving Show
data Body = Body [BodyPart]
@@ -276,7 +276,7 @@ defaultRunStyle = RunStyle { isBold = False
, isSubScript = False
, rUnderline = Nothing
, rStyle = Nothing
- }
+ }
type Target = String
@@ -286,7 +286,7 @@ type BookMarkId = String
type RelId = String
type ChangeId = String
type Author = String
-type ChangeDate = String
+type ChangeDate = String
attrToNSPair :: Attr -> Maybe (String, String)
attrToNSPair (Attr (QName s _ (Just "xmlns")) val) = Just (s, val)
@@ -301,18 +301,18 @@ archiveToDocx archive = do
rEnv = ReaderEnv notes numbering rels media
doc <- runD (archiveToDocument archive) rEnv
return $ Docx doc
-
+
archiveToDocument :: Archive -> D Document
archiveToDocument zf = do
entry <- maybeToD $ findEntryByPath "word/document.xml" zf
docElem <- maybeToD $ (parseXMLDoc . UTF8.toStringLazy . fromEntry) entry
- let namespaces = mapMaybe attrToNSPair (elAttribs docElem)
+ let namespaces = mapMaybe attrToNSPair (elAttribs docElem)
bodyElem <- maybeToD $ findChild (elemName namespaces "w" "body") docElem
body <- elemToBody namespaces bodyElem
return $ Document namespaces body
-elemToBody :: NameSpaces -> Element -> D Body
+elemToBody :: NameSpaces -> Element -> D Body
elemToBody ns element | isElem ns "w" "body" element =
mapD (elemToBodyPart ns) (elChildren element) >>=
(\bps -> return $ Body bps)
@@ -349,10 +349,10 @@ relElemToRelationship element | qName (elName element) == "Relationship" =
target <- findAttr (QName "Target" Nothing Nothing) element
return $ Relationship (relId, target)
relElemToRelationship _ = Nothing
-
+
archiveToRelationships :: Archive -> [Relationship]
-archiveToRelationships archive =
+archiveToRelationships archive =
let relPaths = filter filePathIsRel (filesInArchive archive)
entries = mapMaybe (\f -> findEntryByPath f archive) relPaths
relElems = mapMaybe (parseXMLDoc . UTF8.toStringLazy . fromEntry) entries
@@ -445,7 +445,7 @@ archiveToNumbering archive =
elemToNotes :: NameSpaces -> String -> Element -> Maybe (M.Map String Element)
elemToNotes ns notetype element
- | isElem ns "w" (notetype ++ "s") element =
+ | isElem ns "w" (notetype ++ "s") element =
let pairs = mapMaybe
(\e -> findAttr (elemName ns "w" "id") e >>=
(\a -> Just (a, e)))
@@ -478,7 +478,7 @@ elemToTblLook :: NameSpaces -> Element -> D TblLook
elemToTblLook ns element | isElem ns "w" "tblLook" element =
let firstRow = findAttr (elemName ns "w" "firstRow") element
val = findAttr (elemName ns "w" "val") element
- firstRowFmt =
+ firstRowFmt =
case firstRow of
Just "1" -> True
Just _ -> False
@@ -505,15 +505,15 @@ elemToCell ns element | isElem ns "w" "tc" element =
elemToCell _ _ = throwError WrongElem
elemToParIndentation :: NameSpaces -> Element -> Maybe ParIndentation
-elemToParIndentation ns element | isElem ns "w" "ind" element =
+elemToParIndentation ns element | isElem ns "w" "ind" element =
Just $ ParIndentation {
leftParIndent =
findAttr (QName "left" (lookup "w" ns) (Just "w")) element >>=
stringToInteger
- , rightParIndent =
+ , rightParIndent =
findAttr (QName "right" (lookup "w" ns) (Just "w")) element >>=
stringToInteger
- , hangingParIndent =
+ , hangingParIndent =
findAttr (QName "hanging" (lookup "w" ns) (Just "w")) element >>=
stringToInteger}
elemToParIndentation _ _ = Nothing
@@ -558,7 +558,7 @@ elemToBodyPart ns element
case lookupLevel numId lvl num of
Just levelInfo -> return $ ListItem parstyle numId lvl levelInfo parparts
Nothing -> throwError WrongElem
-elemToBodyPart ns element
+elemToBodyPart ns element
| isElem ns "w" "p" element = do
let parstyle = elemToParagraphStyle ns element
parparts <- mapD (elemToParPart ns) (elChildren element)
@@ -667,15 +667,15 @@ elemToMathElem ns element | isElem ns "m" "bar" element = do
base <-maybeToD (findChild (QName "e" (lookup "m" ns) (Just "m")) element) >>=
elemToBase ns
return $ Bar barPr base
-elemToMathElem ns element | isElem ns "m" "box" element =
+elemToMathElem ns element | isElem ns "m" "box" element =
maybeToD (findChild (elemName ns "m" "e") element) >>=
elemToBase ns >>=
(\b -> return $ Box b)
-elemToMathElem ns element | isElem ns "m" "borderBox" element =
+elemToMathElem ns element | isElem ns "m" "borderBox" element =
maybeToD (findChild (elemName ns "m" "e") element) >>=
elemToBase ns >>=
(\b -> return $ BorderBox b)
-elemToMathElem ns element | isElem ns "m" "d" element =
+elemToMathElem ns element | isElem ns "m" "d" element =
let style = elemToDelimStyle ns element
in
mapD (elemToBase ns) (elChildren element) >>=
@@ -684,8 +684,8 @@ elemToMathElem ns element | isElem ns "m" "eqArr" element =
mapD (elemToBase ns) (elChildren element) >>=
(\es -> return $ EquationArray es)
elemToMathElem ns element | isElem ns "m" "f" element = do
- num <- maybeToD $ findChild (elemName ns "m" "num") element
- den <- maybeToD $ findChild (elemName ns "m" "den") element
+ num <- maybeToD $ findChild (elemName ns "m" "num") element
+ den <- maybeToD $ findChild (elemName ns "m" "den") element
numElems <- mapD (elemToMathElem ns) (elChildren num)
denElems <- mapD (elemToMathElem ns) (elChildren den)
return $ Fraction numElems denElems
@@ -695,7 +695,7 @@ elemToMathElem ns element | isElem ns "m" "func" element = do
elemToBase ns
fnElems <- mapD (elemToMathElem ns) (elChildren fName)
return $ Function fnElems base
-elemToMathElem ns element | isElem ns "m" "groupChr" element =
+elemToMathElem ns element | isElem ns "m" "groupChr" element =
let style = elemToGroupStyle ns element
in
maybeToD (findChild (elemName ns "m" "e") element) >>=
@@ -920,11 +920,11 @@ elemToRunElems ns element
elemToRunElems _ _ = throwError WrongElem
-
-
-
-
+
+
+
+
diff --git a/src/Text/Pandoc/Readers/Docx/Reducible.hs b/src/Text/Pandoc/Readers/Docx/Reducible.hs
index 8c105d1f1..e8e407844 100644
--- a/src/Text/Pandoc/Readers/Docx/Reducible.hs
+++ b/src/Text/Pandoc/Readers/Docx/Reducible.hs
@@ -90,7 +90,7 @@ combineReducibles r s =
True -> case (not . null) rs && isSpace (last rs) of
True -> rebuild conts (init rs) ++ [last rs, s]
False -> [r,s]
- False -> rebuild
+ False -> rebuild
shared $
reduceList $
(rebuild remaining rs) ++ (rebuild remaining' ss)
@@ -145,7 +145,7 @@ instance Reducible Inline where
isSpace _ = False
instance Reducible Block where
- (Div (ident, classes, kvs) blks) <++> blk | "list-item" `elem` classes =
+ (Div (ident, classes, kvs) blks) <++> blk | "list-item" `elem` classes =
[Div (ident, classes, kvs) (reduceList blks), blk]
blk <++> blk' = combineReducibles blk blk'
@@ -177,5 +177,5 @@ rebuild :: [Container a] -> [a] -> [a]
rebuild [] xs = xs
rebuild ((Container f) : cs) xs = rebuild cs $ [f xs]
rebuild (NullContainer : cs) xs = rebuild cs $ xs
-
-
+
+
diff --git a/src/Text/Pandoc/Readers/Docx/TexChar.hs b/src/Text/Pandoc/Readers/Docx/TexChar.hs
index 1bef8d7da..eddcabecc 100644
--- a/src/Text/Pandoc/Readers/Docx/TexChar.hs
+++ b/src/Text/Pandoc/Readers/Docx/TexChar.hs
@@ -4382,5 +4382,5 @@ uniconvMap = M.fromList [ ('\8193', "\\quad")
-- , ('\120829', "\\mttseven")
-- , ('\120830', "\\mtteight")
-- , ('\120831', "\\mttnine")
-
+
-- ]
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index dacd4e104..5cb64c1e7 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -335,10 +335,10 @@ isSpaceOrEmpty (Str "") = True
isSpaceOrEmpty _ = False
-- | Extract the leading and trailing spaces from inside an inline element
--- and place them outside the element.
+-- and place them outside the element.
extractSpaces :: (Inlines -> Inlines) -> Inlines -> Inlines
-extractSpaces f is =
+extractSpaces f is =
let contents = B.unMany is
left = case viewl contents of
(Space :< _) -> B.space
diff --git a/src/Text/Pandoc/Writers/AsciiDoc.hs b/src/Text/Pandoc/Writers/AsciiDoc.hs
index 19112d8f5..8d36efeee 100644
--- a/src/Text/Pandoc/Writers/AsciiDoc.hs
+++ b/src/Text/Pandoc/Writers/AsciiDoc.hs
@@ -142,10 +142,10 @@ blockToAsciiDoc opts (Header level (ident,_,_) inlines) = do
let len = offset contents
-- ident seem to be empty most of the time and asciidoc will generate them automatically
-- so lets make them not show up when null
- let identifier = if (null ident) then empty else ("[[" <> text ident <> "]]")
+ let identifier = if (null ident) then empty else ("[[" <> text ident <> "]]")
let setext = writerSetextHeaders opts
- return $
- (if setext
+ return $
+ (if setext
then
identifier $$ contents $$
(case level of
@@ -155,7 +155,7 @@ blockToAsciiDoc opts (Header level (ident,_,_) inlines) = do
4 -> text $ replicate len '+'
_ -> empty) <> blankline
else
- identifier $$ text (replicate level '=') <> space <> contents <> blankline)
+ identifier $$ text (replicate level '=') <> space <> contents <> blankline)
blockToAsciiDoc _ (CodeBlock (_,classes,_) str) = return $
flush (attrs <> dashes <> space <> attrs <> cr <> text str <>
cr <> dashes) <> blankline
diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs
index 19d486b25..ae20efd4b 100644
--- a/src/Text/Pandoc/Writers/ICML.hs
+++ b/src/Text/Pandoc/Writers/ICML.hs
@@ -42,7 +42,7 @@ type WS a = State WriterState a
defaultWriterState :: WriterState
defaultWriterState = WriterState{
- blockStyles = Set.empty
+ blockStyles = Set.empty
, inlineStyles = Set.empty
, links = []
, listDepth = 1
@@ -267,7 +267,7 @@ hyperlinksToDoc (x:xs) = hyp x $$ hyperlinksToDoc xs
$ inTags False "BorderColor" [("type","enumeration")] (text "Black")
$$ (inTags False "Destination" [("type","object")]
$ text $ "HyperlinkURLDestination/"++(escapeStringForXML url))
-
+
-- | Convert a list of Pandoc blocks to ICML.
blocksToICML :: WriterOptions -> Style -> [Block] -> WS Doc
@@ -352,7 +352,7 @@ listItemsToICML opts listType style attribs (first:rest) = do
-- | Convert a list of blocks to ICML list items.
listItemToICML :: WriterOptions -> Style -> Bool-> Maybe ListAttributes -> [Block] -> WS Doc
listItemToICML opts style isFirst attribs item =
- let makeNumbStart (Just (beginsWith, numbStl, _)) =
+ let makeNumbStart (Just (beginsWith, numbStl, _)) =
let doN DefaultStyle = []
doN LowerRoman = [lowerRomanName]
doN UpperRoman = [upperRomanName]
@@ -467,7 +467,7 @@ parStyle opts style lst =
-- | Wrap a Doc in an ICML Character Style.
charStyle :: Style -> Doc -> WS Doc
-charStyle style content =
+charStyle style content =
let (stlStr, attrs) = styleToStrAttr style
doc = inTags True "CharacterStyleRange" attrs $ inTagsSimple "Content" $ flush content
in do
diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs
index b6da2694c..e2b9a68f1 100644
--- a/src/Text/Pandoc/Writers/OpenDocument.hs
+++ b/src/Text/Pandoc/Writers/OpenDocument.hs
@@ -504,7 +504,7 @@ paraStyle parent attrs = do
tight = if t then [ ("fo:margin-top" , "0in" )
, ("fo:margin-bottom" , "0in" )]
else []
- indent = if (i /= 0 || b)
+ indent = if (i /= 0 || b)
then [ ("fo:margin-left" , indentVal)
, ("fo:margin-right" , "0in" )
, ("fo:text-indent" , "0in" )
@@ -534,7 +534,7 @@ paraTableStyles t s (a:xs)
[ ("fo:text-align", x)
, ("style:justify-single-word", "false")]
-data TextStyle = Italic | Bold | Strike | Sub | Sup | SmallC | Pre
+data TextStyle = Italic | Bold | Strike | Sub | Sup | SmallC | Pre
deriving ( Eq,Ord )
textStyleAttr :: TextStyle -> [(String,String)]
diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs
index 31c97349b..5e97d2ac3 100644
--- a/src/Text/Pandoc/Writers/RST.hs
+++ b/src/Text/Pandoc/Writers/RST.hs
@@ -174,7 +174,7 @@ blockToRST (Para [Image txt (src,'f':'i':'g':':':tit)]) = do
let alt = ":alt: " <> if null tit then capt else text tit
return $ hang 3 ".. " $ fig $$ alt $+$ capt $$ blankline
blockToRST (Para inlines)
- | LineBreak `elem` inlines = do -- use line block if LineBreaks
+ | LineBreak `elem` inlines = do -- use line block if LineBreaks
lns <- mapM inlineListToRST $ splitBy (==LineBreak) inlines
return $ (vcat $ map (text "| " <>) lns) <> blankline
| otherwise = do