Renamed removedLeadingTrailingSpace to trim.

Also removeLeadingSpace to triml,
removeTrailingSpace to trimr.
This commit is contained in:
John MacFarlane 2012-09-29 17:09:34 -04:00
parent 487d01118f
commit 93e92a4716
9 changed files with 38 additions and 43 deletions

View file

@ -610,7 +610,7 @@ gridTableWith blocks 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
@ -652,8 +652,7 @@ gridTableHeader headless blocks = try $ do
then replicate (length dashes) ""
else map (intercalate " ") $ transpose
$ map (gridTableSplitLine indices) rawContent
heads <- mapM (parseFromString blocks) $
map removeLeadingTrailingSpace rawHeads
heads <- mapM (parseFromString blocks) $ map trim rawHeads
return (heads, aligns, indices)
gridTableRawLine :: [Int] -> Parser [Char] ParserState [String]

View file

@ -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)

View file

@ -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

View file

@ -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

View file

@ -38,9 +38,9 @@ module Text.Pandoc.Shared (
backslashEscapes,
escapeStringUsing,
stripTrailingNewlines,
removeLeadingTrailingSpace,
removeLeadingSpace,
removeTrailingSpace,
trim,
triml,
trimr,
stripFirstAndLast,
camelCaseToHyphenated,
toRomanNumeral,
@ -161,16 +161,16 @@ stripTrailingNewlines :: String -> String
stripTrailingNewlines = reverse . dropWhile (== '\n') . reverse
-- | Remove leading and trailing space (including newlines) from string.
removeLeadingTrailingSpace :: String -> String
removeLeadingTrailingSpace = removeLeadingSpace . removeTrailingSpace
trim :: String -> String
trim = triml . trimr
-- | Remove leading space (including newlines) from string.
removeLeadingSpace :: String -> String
removeLeadingSpace = dropWhile (`elem` " \r\n\t")
triml :: String -> String
triml = dropWhile (`elem` " \r\n\t")
-- | Remove trailing space (including newlines) from string.
removeTrailingSpace :: String -> String
removeTrailingSpace = reverse . removeLeadingSpace . reverse
trimr :: String -> String
trimr = reverse . triml . reverse
-- | Strip leading and trailing characters from string
stripFirstAndLast :: String -> String

View file

@ -49,7 +49,7 @@ authorToDocbook opts name' =
in if ',' `elem` name
then -- last name first
let (lastname, rest) = break (==',') name
firstname = removeLeadingSpace rest in
firstname = triml rest in
inTagsSimple "firstname" (text $ escapeStringForXML firstname) <>
inTagsSimple "surname" (text $ escapeStringForXML lastname)
else -- last name last
@ -74,7 +74,7 @@ writeDocbook opts (Pandoc (Meta tit auths dat) blocks) =
else Nothing
render' = render colwidth
opts' = if "/book>" `isSuffixOf`
(removeTrailingSpace $ writerTemplate opts)
(trimr $ writerTemplate opts)
then opts{ writerChapters = True }
else opts
startLvl = if writerChapters opts' then 0 else 1

View file

@ -151,7 +151,7 @@ writeEPUB opts doc@(Pandoc meta _) = do
[("id", takeBaseName $ eRelativePath ent),
("href", eRelativePath ent),
("media-type", maybe "" id $ getMimeType $ eRelativePath ent)] $ ()
let plainify t = removeTrailingSpace $
let plainify t = trimr $
writePlain opts'{ writerStandalone = False } $
Pandoc meta [Plain t]
let plainTitle = plainify $ docTitle meta
@ -289,7 +289,7 @@ transformInlines _ sourceDir picsRef (Image lab (src,tit) : xs) = do
return new
return $ Image lab (newsrc, tit) : xs
transformInlines (MathML _) _ _ (x@(Math _ _) : xs) = do
let writeHtmlInline opts z = removeTrailingSpace $
let writeHtmlInline opts z = trimr $
writeHtmlString opts $ Pandoc (Meta [] [] []) [Plain [z]]
mathml = writeHtmlInline def{writerHTMLMathMethod = MathML Nothing } x
fallback = writeHtmlInline def{writerHTMLMathMethod = PlainMath } x

View file

@ -63,8 +63,7 @@ pandocToMan opts (Pandoc (Meta title authors date) blocks) = do
(text (reverse xs), char d)
xs -> (text (reverse xs), doubleQuotes empty)
let description = hsep $
map (doubleQuotes . text . removeLeadingTrailingSpace) $
splitBy (== '|') rest
map (doubleQuotes . text . trim) $ splitBy (== '|') rest
body <- blockListToMan opts blocks
notes <- liftM stNotes get
notes' <- notesToMan opts (reverse notes)

View file

@ -17,7 +17,7 @@ import Test.Framework
import Test.Framework.Providers.HUnit
import Test.Framework.Providers.QuickCheck2
import Test.HUnit (assertBool)
import Text.Pandoc.Shared (normalize, removeTrailingSpace)
import Text.Pandoc.Shared (normalize, trimr)
import Text.Pandoc.Options
import Text.Pandoc.Writers.Native (writeNative)
import Language.Haskell.TH.Quote (QuasiQuoter(..))
@ -94,7 +94,7 @@ instance ToString Blocks where
toString = writeNative def . toPandoc
instance ToString Inlines where
toString = removeTrailingSpace . writeNative def . toPandoc
toString = trimr . writeNative def . toPandoc
instance ToString String where
toString = id