aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2012-09-29 17:09:34 -0400
committerJohn MacFarlane <jgm@berkeley.edu>2012-09-29 17:09:34 -0400
commit93e92a47169ee84e1a42c68f9b890314f8866de1 (patch)
tree6417dfea9a99c4ce3b1782fbed0ef7956b70661a /src/Text/Pandoc/Readers
parent487d01118fb55c351f61a58d2b5411ae6de30629 (diff)
downloadpandoc-93e92a47169ee84e1a42c68f9b890314f8866de1.tar.gz
Renamed removedLeadingTrailingSpace to trim.
Also removeLeadingSpace to triml, removeTrailingSpace to trimr.
Diffstat (limited to 'src/Text/Pandoc/Readers')
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs3
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs18
-rw-r--r--src/Text/Pandoc/Readers/RST.hs22
3 files changed, 20 insertions, 23 deletions
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index c3854bc3e..1f85c3d61 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -146,9 +146,6 @@ braced = bgroup *> (concat <$> manyTill
bracketed :: Monoid a => LP a -> LP a
bracketed parser = try $ char '[' *> (mconcat <$> manyTill parser (char ']'))
-trim :: String -> String
-trim = removeLeadingTrailingSpace
-
mathDisplay :: LP String -> LP Inlines
mathDisplay p = displayMath <$> (try p >>= applyMacros' . trim)
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index adf24588b..7ac68c856 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -239,7 +239,7 @@ referenceKey = try $ do
src <- try betweenAngles <|> sourceURL
tit <- option "" referenceTitle
blanklines
- let target = (escapeURI $ removeTrailingSpace src, tit)
+ let target = (escapeURI $ trimr src, tit)
st <- getState
let oldkeys = stateKeys st
updateState $ \s -> s { stateKeys = M.insert (toKey raw) target oldkeys }
@@ -848,7 +848,7 @@ simpleTableHeader headless = try $ do
else rawHeads
heads <- fmap sequence
$ mapM (parseFromString (mconcat <$> many plain))
- $ map removeLeadingTrailingSpace rawHeads'
+ $ map trim rawHeads'
return (heads, aligns, indices)
-- Returns an alignment type for a table, based on a list of strings
@@ -859,7 +859,7 @@ alignType :: [String]
-> Alignment
alignType [] _ = AlignDefault
alignType strLst len =
- let nonempties = filter (not . null) $ map removeTrailingSpace strLst
+ let nonempties = filter (not . null) $ map trimr strLst
(leftSpace, rightSpace) =
case sortBy (comparing length) nonempties of
(x:_) -> (head x `elem` " \t", length x < len)
@@ -884,7 +884,7 @@ rawTableLine :: [Int]
rawTableLine indices = do
notFollowedBy' (blanklines <|> tableFooter)
line <- many1Till anyChar newline
- return $ map removeLeadingTrailingSpace $ tail $
+ return $ map trim $ tail $
splitStringByIndices (init indices) line
-- Parse a table line and return a list of lists of blocks (columns).
@@ -957,7 +957,7 @@ multilineTableHeader headless = try $ do
else map (intercalate " ") rawHeadsList
heads <- fmap sequence $
mapM (parseFromString (mconcat <$> many plain)) $
- map removeLeadingTrailingSpace rawHeads
+ map trim rawHeads
return (heads, aligns, indices)
-- Parse a grid table: starts with row of '-' on top, then header
@@ -972,7 +972,7 @@ gridTable headless =
gridTableSplitLine :: [Int] -> String -> [String]
gridTableSplitLine indices line = map removeFinalBar $ tail $
- splitStringByIndices (init indices) $ removeTrailingSpace line
+ splitStringByIndices (init indices) $ trimr line
gridPart :: Char -> Parser [Char] st (Int, Int)
gridPart ch = do
@@ -1014,7 +1014,7 @@ gridTableHeader headless = try $ do
else map (intercalate " ") $ transpose
$ map (gridTableSplitLine indices) rawContent
heads <- fmap sequence $ mapM (parseFromString block) $
- map removeLeadingTrailingSpace rawHeads
+ map trim rawHeads
return (heads, aligns, indices)
gridTableRawLine :: [Int] -> Parser [Char] ParserState [String]
@@ -1228,7 +1228,7 @@ code = try $ do
notFollowedBy (char '`')))
attr <- option ([],[],[]) (try $ guardEnabled Ext_inline_code_attributes >>
optional whitespace >> attributes)
- return $ return $ B.codeWith attr $ removeLeadingTrailingSpace $ concat result
+ return $ return $ B.codeWith attr $ trim $ concat result
math :: Parser [Char] ParserState (F Inlines)
math = (return . B.displayMath <$> (mathDisplay >>= applyMacros'))
@@ -1416,7 +1416,7 @@ source' = do
tit <- option "" linkTitle
skipSpaces
eof
- return (escapeURI $ removeTrailingSpace src, tit)
+ return (escapeURI $ trimr src, tit)
linkTitle :: Parser [Char] ParserState String
linkTitle = try $ do
diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs
index 0b01d3b53..2dfdd5377 100644
--- a/src/Text/Pandoc/Readers/RST.hs
+++ b/src/Text/Pandoc/Readers/RST.hs
@@ -256,15 +256,15 @@ imageBlock = try $ do
imageDef :: Inlines -> RSTParser Inlines
imageDef defaultAlt = try $ do
string "image:: "
- src <- escapeURI . removeLeadingTrailingSpace <$> manyTill anyChar newline
+ src <- escapeURI . trim <$> manyTill anyChar newline
fields <- try $ do indent <- lookAhead $ many (oneOf " /t")
many $ rawFieldListItem indent
optional blanklines
- let alt = maybe defaultAlt (\x -> B.str $ removeTrailingSpace x)
+ let alt = maybe defaultAlt (\x -> B.str $ trimr x)
$ lookup "alt" fields
let img = B.image src "" alt
return $ case lookup "target" fields of
- Just t -> B.link (escapeURI $ removeLeadingTrailingSpace t)
+ Just t -> B.link (escapeURI $ trim t)
"" img
Nothing -> img
@@ -381,7 +381,7 @@ customCodeBlock = try $ do
figureBlock :: RSTParser Blocks
figureBlock = try $ do
string ".. figure::"
- src <- escapeURI . removeLeadingTrailingSpace <$> manyTill anyChar newline
+ src <- escapeURI . trim <$> manyTill anyChar newline
body <- indentedBlock
caption <- parseFromString extractCaption body
return $ B.para $ B.image src "" caption
@@ -540,7 +540,7 @@ defaultRoleBlock :: RSTParser Blocks
defaultRoleBlock = try $ do
string ".. default-role::"
-- doesn't enforce any restrictions on the role name; embedded spaces shouldn't be allowed, for one
- role <- manyTill anyChar newline >>= return . removeLeadingTrailingSpace
+ role <- manyTill anyChar newline >>= return . trim
updateState $ \s -> s { stateRstDefaultRole =
if null role
then stateRstDefaultRole defaultParserState
@@ -587,7 +587,7 @@ directive = try $ do
-- divide string by blanklines
toChunks :: String -> [String]
toChunks = dropWhile null
- . map (removeLeadingTrailingSpace . unlines)
+ . map (trim . unlines)
. splitBy (all (`elem` " \t")) . lines
---
@@ -674,7 +674,7 @@ targetURI = do
contents <- many1 (try (many spaceChar >> newline >>
many1 spaceChar >> noneOf " \t\n") <|> noneOf "\n")
blanklines
- return $ escapeURI $ removeLeadingTrailingSpace $ contents
+ return $ escapeURI $ trim $ contents
imageKey :: RSTParser ()
imageKey = try $ do
@@ -758,7 +758,7 @@ simpleTableRow indices = do
simpleTableSplitLine :: [Int] -> String -> [String]
simpleTableSplitLine indices line =
- map removeLeadingTrailingSpace
+ map trim
$ tail $ splitByIndices (init indices) line
simpleTableHeader :: Bool -- ^ Headerless table
@@ -777,7 +777,7 @@ simpleTableHeader headless = try $ do
then replicate (length dashes) ""
else simpleTableSplitLine indices rawContent
heads <- mapM (parseFromString (B.toList . mconcat <$> many plain)) $
- map removeLeadingTrailingSpace rawHeads
+ map trim rawHeads
return (heads, aligns, indices)
-- Parse a simple table.
@@ -845,7 +845,7 @@ code = try $ do
string "``"
result <- manyTill anyChar (try (string "``"))
return $ B.code
- $ removeLeadingTrailingSpace $ unwords $ lines result
+ $ trim $ unwords $ lines result
-- succeeds only if we're not right after a str (ie. in middle of word)
atStart :: RSTParser a -> RSTParser a
@@ -932,7 +932,7 @@ explicitLink = try $ do
src <- manyTill (noneOf ">\n") (char '>')
skipSpaces
string "`_"
- return $ B.link (escapeURI $ removeLeadingTrailingSpace src) "" label'
+ return $ B.link (escapeURI $ trim src) "" label'
referenceLink :: RSTParser Inlines
referenceLink = try $ do