aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Text/Pandoc/Shared.hs21
-rw-r--r--src/pandoc.hs27
2 files changed, 26 insertions, 22 deletions
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index 6854e5ae6..13eab9bdb 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -49,6 +49,7 @@ module Text.Pandoc.Shared (
wrapTeXIfNeeded,
BlockWrapper (..),
wrappedBlocksToDoc,
+ tabFilter,
-- * Parsing
(>>~),
anyLine,
@@ -285,6 +286,26 @@ wrappedBlocksToDoc = foldr addBlock empty
addBlock (Pad d) accum = d $$ text "" $$ accum
addBlock (Reg d) accum = d $$ accum
+-- | Convert tabs to spaces and filter out DOS line endings.
+-- Tabs will be preserved if tab stop is set to 0.
+tabFilter :: Int -- ^ Tab stop
+ -> String -- ^ Input
+ -> String
+tabFilter tabStop =
+ let go _ [] = ""
+ go _ ('\n':xs) = '\n' : go tabStop xs
+ go _ ('\r':'\n':xs) = '\n' : go tabStop xs
+ go _ ('\r':xs) = '\n' : go tabStop xs
+ go spsToNextStop ('\t':xs) =
+ if tabStop == 0
+ then '\t' : go tabStop xs
+ else replicate spsToNextStop ' ' ++ go tabStop xs
+ go 1 (x:xs) =
+ x : go tabStop xs
+ go spsToNextStop (x:xs) =
+ x : go (spsToNextStop - 1) xs
+ in go tabStop
+
--
-- Parsing
--
diff --git a/src/pandoc.hs b/src/pandoc.hs
index e498b3c0a..64b79619c 100644
--- a/src/pandoc.hs
+++ b/src/pandoc.hs
@@ -32,7 +32,7 @@ writers.
module Main where
import Text.Pandoc
import Text.Pandoc.ODT
-import Text.Pandoc.Shared ( HTMLMathMethod (..), splitBy, ObfuscationMethod (..) )
+import Text.Pandoc.Shared ( HTMLMathMethod (..), splitBy, tabFilter, ObfuscationMethod (..) )
import Text.Pandoc.Highlighting ( languages )
import System.Environment ( getArgs, getProgName, getEnvironment )
import System.Exit ( exitWith, ExitCode (..) )
@@ -131,8 +131,7 @@ writeDoc _ = prettyPandoc
-- | Data structure for command line options.
data Opt = Opt
- { optPreserveTabs :: Bool -- ^ Convert tabs to spaces
- , optTabStop :: Int -- ^ Number of spaces per tab
+ { optTabStop :: Int -- ^ Number of spaces per tab
, optStandalone :: Bool -- ^ Include header, footer
, optReader :: String -- ^ Reader format
, optWriter :: String -- ^ Writer format
@@ -167,8 +166,7 @@ data Opt = Opt
-- | Defaults for command-line options.
defaultOpts :: Opt
defaultOpts = Opt
- { optPreserveTabs = False
- , optTabStop = 4
+ { optTabStop = 4
, optStandalone = False
, optReader = "" -- null for default reader
, optWriter = "" -- null for default writer
@@ -229,7 +227,7 @@ options =
, Option "p" ["preserve-tabs"]
(NoArg
- (\opt -> return opt { optPreserveTabs = True }))
+ (\opt -> return opt { optTabStop = 0 }))
"" -- "Preserve tabs instead of converting to spaces"
, Option "" ["tab-stop"]
@@ -519,8 +517,7 @@ main = do
-- thread option data structure through all supplied option actions
opts <- foldl (>>=) (return defaultOpts') actions
- let Opt { optPreserveTabs = preserveTabs
- , optTabStop = tabStop
+ let Opt { optTabStop = tabStop
, optStandalone = standalone
, optReader = readerName
, optWriter = writerName
@@ -581,20 +578,6 @@ main = do
Just cols -> read cols
Nothing -> stateColumns defaultParserState
- let tabFilter _ [] = ""
- tabFilter _ ('\n':xs) = '\n' : tabFilter tabStop xs
- -- remove DOS line endings
- tabFilter _ ('\r':'\n':xs) = '\n' : tabFilter tabStop xs
- tabFilter _ ('\r':xs) = '\n' : tabFilter tabStop xs
- tabFilter spsToNextStop ('\t':xs) =
- if preserveTabs
- then '\t' : tabFilter tabStop xs
- else replicate spsToNextStop ' ' ++ tabFilter tabStop xs
- tabFilter 1 (x:xs) =
- x : tabFilter tabStop xs
- tabFilter spsToNextStop (x:xs) =
- x : tabFilter (spsToNextStop - 1) xs
-
let standalone' = (standalone && not strict) || isNonTextOutput writerName'
#ifdef _CITEPROC