diff options
| author | John MacFarlane <fiddlosopher@gmail.com> | 2012-07-25 12:31:16 -0700 | 
|---|---|---|
| committer | John MacFarlane <fiddlosopher@gmail.com> | 2012-07-25 12:31:16 -0700 | 
| commit | 335cd5de4d785f09ae1c14e961df8c4137300252 (patch) | |
| tree | 52810f2a87fb89571ad2036cc334bcda4c0c9f6e | |
| parent | 0d4424c21c7d3d6da068a77750db72f61ff0e0cd (diff) | |
| download | pandoc-335cd5de4d785f09ae1c14e961df8c4137300252.tar.gz | |
Moved stateTabStop to readerTabStop in ReaderOptions.
| -rw-r--r-- | src/Text/Pandoc/Options.hs | 2 | ||||
| -rw-r--r-- | src/Text/Pandoc/Parsing.hs | 3 | ||||
| -rw-r--r-- | src/Text/Pandoc/Readers/Markdown.hs | 13 | ||||
| -rw-r--r-- | src/Text/Pandoc/Readers/RST.hs | 4 | ||||
| -rw-r--r-- | src/pandoc.hs | 4 | 
5 files changed, 11 insertions, 15 deletions
| diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs index 28a962607..ab4dda388 100644 --- a/src/Text/Pandoc/Options.hs +++ b/src/Text/Pandoc/Options.hs @@ -56,6 +56,7 @@ data ReaderOptions = ReaderOptions{         , readerStrict         :: Bool  -- ^ FOR TRANSITION ONLY         , readerParseRaw       :: Bool  -- ^ Parse raw HTML, LaTeX         , readerColumns        :: Int   -- ^ Number of columns in terminal +       , readerTabStop        :: Int   -- ^ Tab stop         } deriving (Show, Read)  instance Default ReaderOptions @@ -65,4 +66,5 @@ instance Default ReaderOptions                 , readerStrict        = False                 , readerParseRaw      = False                 , readerColumns       = 80 +               , readerTabStop       = 4                 } diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs index 2d7c4eb81..3d7057936 100644 --- a/src/Text/Pandoc/Parsing.hs +++ b/src/Text/Pandoc/Parsing.hs @@ -544,7 +544,6 @@ tableWith headerParser rowParser lineParser footerParser = try $ do      (heads, aligns, indices) <- headerParser      lines' <- rowParser indices `sepEndBy1` lineParser      footerParser -    state <- getState      numColumns <- getOption readerColumns      let widths = if (indices == [])                      then replicate (length aligns) 0.0 @@ -696,7 +695,6 @@ data ParserState = ParserState        stateKeys            :: KeyTable,      -- ^ List of reference keys        stateCitations       :: [String],      -- ^ List of available citations        stateNotes           :: NoteTable,     -- ^ List of notes -      stateTabStop         :: Int,           -- ^ Tab stop        stateStandalone      :: Bool,          -- ^ Parse bibliographic info?        stateTitle           :: [Inline],      -- ^ Title of document        stateAuthors         :: [[Inline]],    -- ^ Authors of document @@ -729,7 +727,6 @@ defaultParserState =                    stateKeys            = M.empty,                    stateCitations       = [],                    stateNotes           = [], -                  stateTabStop         = 4,                    stateStandalone      = False,                    stateTitle           = [],                    stateAuthors         = [], diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 69faadd4a..4f1831baf 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -85,15 +85,13 @@ isBlank _    = False  indentSpaces :: Parser [Char] ParserState [Char]  indentSpaces = try $ do -  state <- getState -  let tabStop = stateTabStop state +  tabStop <- getOption readerTabStop    count tabStop (char ' ') <|>      string "\t" <?> "indentation"  nonindentSpaces :: Parser [Char] ParserState [Char]  nonindentSpaces = do -  state <- getState -  let tabStop = stateTabStop state +  tabStop <- getOption readerTabStop    sps <- many (char ' ')    if length sps < tabStop        then return sps @@ -101,8 +99,8 @@ nonindentSpaces = do  skipNonindentSpaces :: Parser [Char] ParserState ()  skipNonindentSpaces = do -  state <- getState -  atMostSpaces (stateTabStop state - 1) +  tabStop <- getOption readerTabStop +  atMostSpaces (tabStop - 1)  atMostSpaces :: Int -> Parser [Char] ParserState ()  atMostSpaces 0 = notFollowedBy (char ' ') @@ -627,8 +625,7 @@ defListMarker :: Parser [Char] ParserState ()  defListMarker = do    sps <- nonindentSpaces    char ':' <|> char '~' -  st <- getState -  let tabStop = stateTabStop st +  tabStop <- getOption readerTabStop    let remaining = tabStop - (length sps + 1)    if remaining > 0       then count remaining (char ' ') <|> string "\t" diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs index 675524443..b017b736b 100644 --- a/src/Text/Pandoc/Readers/RST.hs +++ b/src/Text/Pandoc/Readers/RST.hs @@ -33,6 +33,7 @@ module Text.Pandoc.Readers.RST (  import Text.Pandoc.Definition  import Text.Pandoc.Shared  import Text.Pandoc.Parsing +import Text.Pandoc.Options  import Control.Monad ( when, liftM, guard, mzero )  import Data.List ( findIndex, intercalate, transpose, sort, deleteFirstsBy )  import qualified Data.Map as M @@ -493,8 +494,7 @@ listLine markerLength = try $ do  -- indent by specified number of spaces (or equiv. tabs)  indentWith :: Int -> Parser [Char] ParserState [Char]  indentWith num = do -  state <- getState -  let tabStop = stateTabStop state +  tabStop <- getOption readerTabStop    if (num < tabStop)       then count num  (char ' ')       else choice [ try (count num (char ' ')),  diff --git a/src/pandoc.hs b/src/pandoc.hs index fe7b54f9d..a3c01133c 100644 --- a/src/pandoc.hs +++ b/src/pandoc.hs @@ -936,8 +936,7 @@ main = do                       then "."                       else takeDirectory (head sources) -  let startParserState = def{ stateTabStop         = tabStop, -                              stateLiterateHaskell = "+lhs" `isSuffixOf` readerName' || +  let startParserState = def{ stateLiterateHaskell = "+lhs" `isSuffixOf` readerName' ||                                                       lhsExtension sources,                                stateStandalone      = standalone',                                stateCitations       = map CSL.refId refs, @@ -948,6 +947,7 @@ main = do                                       (laTeXOutput || writerName' == "context"))                                   , readerParseRaw = parseRaw                                   , readerColumns = columns +                                 , readerTabStop = tabStop                                   },                                stateIndentedCodeClasses = codeBlockClasses,                                stateApplyMacros     = not laTeXOutput | 
