+ Removed tabsToSpaces and tabsInLine from Text.Pandoc.Shared.

(They were used only in Main.)
+ Wrote new tabsToSpacesInLine function in Main that changes tabs
  to spaces and removes DOS line-endings in one pass, for a slight
  speed improvement.


git-svn-id: https://pandoc.googlecode.com/svn/trunk@942 788f1e2b-df1e-0410-8736-df70ead52e1b
This commit is contained in:
fiddlosopher 2007-08-28 19:33:47 +00:00
parent cda7e7ac21
commit 8fdf8c1d4c
2 changed files with 14 additions and 26 deletions

View file

@ -31,7 +31,7 @@ writers.
module Main where module Main where
import Text.Pandoc import Text.Pandoc
import Text.Pandoc.UTF8 import Text.Pandoc.UTF8
import Text.Pandoc.Shared ( joinWithSep, tabsToSpaces ) import Text.Pandoc.Shared ( joinWithSep )
import Text.Regex ( mkRegex, matchRegex ) import Text.Regex ( mkRegex, matchRegex )
import System.Environment ( getArgs, getProgName, getEnvironment ) import System.Environment ( getArgs, getProgName, getEnvironment )
import System.Exit ( exitWith, ExitCode (..) ) import System.Exit ( exitWith, ExitCode (..) )
@ -445,8 +445,18 @@ main = do
Just cols -> read cols Just cols -> read cols
Nothing -> stateColumns defaultParserState Nothing -> stateColumns defaultParserState
let tabFilter = if preserveTabs then id else (tabsToSpaces tabStop) let tabsToSpacesInLine _ [] = ""
let removeCRs str = filter (/= '\r') str -- remove DOS-style line endings 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 = let startParserState =
defaultParserState { stateParseRaw = parseRaw, defaultParserState { stateParseRaw = parseRaw,
stateTabStop = tabStop, stateTabStop = tabStop,
@ -484,7 +494,7 @@ main = do
(readSources sources) >>= (hPutStrLn output . toUTF8 . (readSources sources) >>= (hPutStrLn output . toUTF8 .
(writer writerOptions) . (writer writerOptions) .
(reader startParserState) . tabFilter . (reader startParserState) . tabFilter .
removeCRs . fromUTF8 . (joinWithSep "\n")) >> fromUTF8 . (joinWithSep "\n")) >>
hClose output hClose output
where where

View file

@ -34,7 +34,6 @@ module Text.Pandoc.Shared (
substitute, substitute,
joinWithSep, joinWithSep,
-- * Text processing -- * Text processing
tabsToSpaces,
backslashEscapes, backslashEscapes,
escapeStringUsing, escapeStringUsing,
stripTrailingNewlines, stripTrailingNewlines,
@ -143,27 +142,6 @@ joinWithSep sep lst = foldr1 (\a b -> a ++ sep ++ b) lst
-- Text processing -- 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 -- | Returns an association list of backslash escapes for the
-- designated characters. -- designated characters.
backslashEscapes :: [Char] -- ^ list of special characters to escape backslashEscapes :: [Char] -- ^ list of special characters to escape