diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index ed2d5ae4d..f42fcfbc4 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -126,7 +126,8 @@ resolveRefs _ x = x -- res <- runIOorExplode (runParserT p defaultLaTeXState{ -- sOptions = def{ readerExtensions = -- enableExtension Ext_raw_tex $ --- getDefaultExtensions "latex" }} "source" (tokenize "source" t)) +-- getDefaultExtensions "latex" }} "source" +-- (tokenize (initialPos "source") t)) -- case res of -- Left e -> error (show e) -- Right r -> return r @@ -721,7 +722,7 @@ insertIncluded defaultExtension f' = do Nothing -> do report $ CouldNotLoadIncludeFile (T.pack f) pos return "" - getInput >>= setInput . (tokenize f contents ++) + getInput >>= setInput . (tokenize (initialPos f) contents ++) updateState dropLatestIncludeFile authors :: PandocMonad m => LP m () diff --git a/src/Text/Pandoc/Readers/LaTeX/Inline.hs b/src/Text/Pandoc/Readers/LaTeX/Inline.hs index 83a0215b5..bee2de66d 100644 --- a/src/Text/Pandoc/Readers/LaTeX/Inline.hs +++ b/src/Text/Pandoc/Readers/LaTeX/Inline.hs @@ -96,7 +96,7 @@ verbTok stopchar = do let (t1, t2) = T.splitAt i txt inp <- getInput setInput $ Tok (incSourceColumn pos i) Symbol (T.singleton stopchar) - : totoks (incSourceColumn pos (i + 1)) (T.drop 1 t2) ++ inp + : tokenize (incSourceColumn pos (i + 1)) (T.drop 1 t2) ++ inp return $ Tok pos toktype t1 listingsLanguage :: [(Text, Text)] -> Maybe Text diff --git a/src/Text/Pandoc/Readers/LaTeX/Parsing.hs b/src/Text/Pandoc/Readers/LaTeX/Parsing.hs index 0d1e551fc..852b99b4d 100644 --- a/src/Text/Pandoc/Readers/LaTeX/Parsing.hs +++ b/src/Text/Pandoc/Readers/LaTeX/Parsing.hs @@ -32,7 +32,6 @@ module Text.Pandoc.Readers.LaTeX.Parsing , getInputTokens , untokenize , untoken - , totoks , toksToString , satisfyTok , parseFromToks @@ -307,7 +306,7 @@ applyMacros s = (guardDisabled Ext_latex_macros >> return s) <|> pstate <- getState let lstate = def{ sOptions = extractReaderOptions pstate , sMacros = extractMacros pstate :| [] } - res <- runParserT retokenize lstate "math" (tokenize "math" s) + res <- runParserT retokenize lstate "math" (tokenize (initialPos "math") s) case res of Left e -> Prelude.fail (show e) Right s' -> return s' @@ -324,7 +323,7 @@ QuickCheck property: tokenizeSources :: Sources -> [Tok] tokenizeSources = concatMap tokenizeSource . unSources where - tokenizeSource (pos, t) = totoks pos t + tokenizeSource (pos, t) = tokenize pos t -- Return tokens from input sources. Ensure that starting position is -- correct. @@ -337,12 +336,11 @@ getInputTokens = do Sources [] -> [] Sources ((_,t):rest) -> tokenizeSources $ Sources ((pos,t):rest) -tokenize :: SourceName -> Text -> [Tok] -tokenize sourcename = totoks (initialPos sourcename) - -totoks :: SourcePos -> Text -> [Tok] -totoks pos t = - case T.uncons t of +tokenize :: SourcePos -> Text -> [Tok] +tokenize = totoks + where + totoks pos t = + case T.uncons t of Nothing -> [] Just (c, rest) | c == '\n' -> @@ -806,7 +804,7 @@ retokenizeComment = (do let updPos (Tok pos' toktype' txt') = Tok (incSourceColumn (incSourceLine pos' (sourceLine pos - 1)) (sourceColumn pos)) toktype' txt' - let newtoks = map updPos $ tokenize (sourceName pos) $ T.tail txt + let newtoks = map updPos $ tokenize pos $ T.tail txt getInput >>= setInput . ((Tok pos Symbol "%" : newtoks) ++)) <|> return ()