aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
Diffstat (limited to 'src')
-rw-r--r--src/Main.hs18
-rw-r--r--src/Text/Pandoc/Shared.hs22
2 files changed, 14 insertions, 26 deletions
diff --git a/src/Main.hs b/src/Main.hs
index b1aa55982..4bd3982d2 100644
--- a/src/Main.hs
+++ b/src/Main.hs
@@ -31,7 +31,7 @@ writers.
module Main where
import Text.Pandoc
import Text.Pandoc.UTF8
-import Text.Pandoc.Shared ( joinWithSep, tabsToSpaces )
+import Text.Pandoc.Shared ( joinWithSep )
import Text.Regex ( mkRegex, matchRegex )
import System.Environment ( getArgs, getProgName, getEnvironment )
import System.Exit ( exitWith, ExitCode (..) )
@@ -445,8 +445,18 @@ main = do
Just cols -> read cols
Nothing -> stateColumns defaultParserState
- let tabFilter = if preserveTabs then id else (tabsToSpaces tabStop)
- let removeCRs str = filter (/= '\r') str -- remove DOS-style line endings
+ let tabsToSpacesInLine _ [] = ""
+ tabsToSpacesInLine _ ('\r':[]) = "" -- remove DOS line-endings
+ tabsToSpacesInLine spsToNextStop (x:xs) =
+ if x == '\t'
+ then if preserveTabs
+ then x:(tabsToSpacesInLine tabStop xs)
+ else replicate spsToNextStop ' ' ++
+ tabsToSpacesInLine tabStop xs
+ else x:(tabsToSpacesInLine (spsToNextStop - 1) xs)
+
+ let tabFilter = unlines . map (tabsToSpacesInLine tabStop) . lines
+
let startParserState =
defaultParserState { stateParseRaw = parseRaw,
stateTabStop = tabStop,
@@ -484,7 +494,7 @@ main = do
(readSources sources) >>= (hPutStrLn output . toUTF8 .
(writer writerOptions) .
(reader startParserState) . tabFilter .
- removeCRs . fromUTF8 . (joinWithSep "\n")) >>
+ fromUTF8 . (joinWithSep "\n")) >>
hClose output
where
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index 2958b4388..ddc325374 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -34,7 +34,6 @@ module Text.Pandoc.Shared (
substitute,
joinWithSep,
-- * Text processing
- tabsToSpaces,
backslashEscapes,
escapeStringUsing,
stripTrailingNewlines,
@@ -143,27 +142,6 @@ joinWithSep sep lst = foldr1 (\a b -> a ++ sep ++ b) lst
-- Text processing
--
--- | Convert tabs to spaces (with adjustable tab stop).
-tabsToSpaces :: Int -- ^ Tabstop
- -> String -- ^ String to convert
- -> String
-tabsToSpaces tabstop str =
- unlines $ map (tabsInLine tabstop tabstop) (lines str)
-
--- | Convert tabs to spaces in one line.
-tabsInLine :: Int -- ^ Number of spaces to next tab stop
- -> Int -- ^ Tabstop
- -> String -- ^ Line to convert
- -> String
-tabsInLine num tabstop [] = ""
-tabsInLine num tabstop (c:cs) =
- let (replacement, nextnum) = if c == '\t'
- then (replicate num ' ', tabstop)
- else if num > 1
- then ([c], num - 1)
- else ([c], tabstop)
- in replacement ++ tabsInLine nextnum tabstop cs
-
-- | Returns an association list of backslash escapes for the
-- designated characters.
backslashEscapes :: [Char] -- ^ list of special characters to escape