diff options
Diffstat (limited to 'src/Text/Pandoc/Readers')
-rw-r--r-- | src/Text/Pandoc/Readers/LaTeX.hs | 57 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/LaTeX/Include.hs | 66 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/LaTeX/Inline.hs | 15 |
3 files changed, 52 insertions, 86 deletions
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index dd6c2a1fa..552411db8 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -38,8 +38,9 @@ import Text.Pandoc.BCP47 (renderLang) import Text.Pandoc.Builder as B import Text.Pandoc.Class.PandocPure (PandocPure) import Text.Pandoc.Class.PandocMonad (PandocMonad (..), getResourcePath, - report, setResourcePath) -import Text.Pandoc.Error (PandocError (PandocParsecError)) + readFileFromDirs, report, + setResourcePath) +import Text.Pandoc.Error (PandocError (PandocParseError, PandocParsecError)) import Text.Pandoc.Highlighting (languagesByExtension) import Text.Pandoc.ImageSize (numUnit, showFl) import Text.Pandoc.Logging @@ -60,8 +61,6 @@ import Text.Pandoc.Readers.LaTeX.Lang (inlineLanguageCommands, enquoteCommands, babelLangToBCP47, setDefaultLanguage) import Text.Pandoc.Readers.LaTeX.SIunitx (siunitxCommands) -import Text.Pandoc.Readers.LaTeX.Include (insertIncluded, - readFileFromTexinputs) import Text.Pandoc.Readers.LaTeX.Inline (acronymCommands, refCommands, nameCommands, charCommands, accentCommands, @@ -236,10 +235,19 @@ mkImage options (T.unpack -> src) = do _ -> return src return $ imageWith attr (T.pack src') "" alt +doxspace :: PandocMonad m => LP m Inlines +doxspace = + (space <$ lookAhead (satisfyTok startsWithLetter)) <|> return mempty + where startsWithLetter (Tok _ Word t) = + case T.uncons t of + Just (c, _) | isLetter c -> True + _ -> False + startsWithLetter _ = False + removeDoubleQuotes :: Text -> Text removeDoubleQuotes t = - fromMaybe t $ T.stripPrefix "\"" t >>= T.stripSuffix "\"" + Data.Maybe.fromMaybe t $ T.stripPrefix "\"" t >>= T.stripSuffix "\"" doubleQuote :: PandocMonad m => LP m Inlines doubleQuote = @@ -398,8 +406,8 @@ inlineCommands = M.unions link (unescapeURL $ untokenize url) "" <$> tok) , ("includegraphics", do options <- option [] keyvals src <- braced - mkImage options . unescapeURL . - removeDoubleQuotes $ untokenize src) + mkImage options . unescapeURL . removeDoubleQuotes $ + untokenize src) , ("hyperlink", hyperlink) , ("hypertarget", hypertargetInline) -- hyphenat @@ -409,6 +417,8 @@ inlineCommands = M.unions -- LaTeX colors , ("textcolor", coloredInline "color") , ("colorbox", coloredInline "background-color") + -- xspace + , ("xspace", doxspace) -- etoolbox , ("ifstrequal", ifstrequal) , ("newtoggle", braced >>= newToggle) @@ -688,6 +698,39 @@ include name = do mapM_ (insertIncluded defaultExt) fs return mempty +readFileFromTexinputs :: PandocMonad m => FilePath -> LP m (Maybe Text) +readFileFromTexinputs fp = do + fileContentsMap <- sFileContents <$> getState + case M.lookup (T.pack fp) fileContentsMap of + Just t -> return (Just t) + Nothing -> do + dirs <- map T.unpack . splitTextBy (==':') . fromMaybe "." + <$> lookupEnv "TEXINPUTS" + readFileFromDirs dirs fp + +insertIncluded :: PandocMonad m + => FilePath + -> FilePath + -> LP m () +insertIncluded defaultExtension f' = do + let f = case takeExtension f' of + ".tex" -> f' + ".sty" -> f' + _ -> addExtension f' defaultExtension + pos <- getPosition + containers <- getIncludeFiles <$> getState + when (T.pack f `elem` containers) $ + throwError $ PandocParseError $ T.pack $ "Include file loop at " ++ show pos + updateState $ addIncludeFile $ T.pack f + mbcontents <- readFileFromTexinputs f + contents <- case mbcontents of + Just s -> return s + Nothing -> do + report $ CouldNotLoadIncludeFile (T.pack f) pos + return "" + getInput >>= setInput . (tokenize f contents ++) + updateState dropLatestIncludeFile + authors :: PandocMonad m => LP m () authors = try $ do bgroup diff --git a/src/Text/Pandoc/Readers/LaTeX/Include.hs b/src/Text/Pandoc/Readers/LaTeX/Include.hs deleted file mode 100644 index 618a89284..000000000 --- a/src/Text/Pandoc/Readers/LaTeX/Include.hs +++ /dev/null @@ -1,66 +0,0 @@ -{-# LANGUAGE OverloadedStrings #-} -{- | - Module : Text.Pandoc.Readers.LaTeX.Include - Copyright : Copyright (C) 2006-2021 John MacFarlane - License : GNU GPL, version 2 or above - - Maintainer : John MacFarlane <jgm@berkeley.edu> - Stability : alpha - Portability : portable --} -module Text.Pandoc.Readers.LaTeX.Include - ( readFileFromTexinputs - , insertIncluded - ) -where - -import qualified Data.Map as M -import Data.Text (Text) -import qualified Data.Text as T -import Text.Pandoc.Shared (splitTextBy) -import System.FilePath (takeExtension, addExtension) -import Control.Monad (when) -import Control.Monad.Except (throwError) -import Text.Pandoc.Error (PandocError(PandocParseError)) -import Text.Pandoc.Logging (LogMessage(CouldNotLoadIncludeFile)) -import Text.Pandoc.Class (PandocMonad (..), readFileFromDirs, report) -import Text.Pandoc.Readers.LaTeX.Parsing -import Text.Pandoc.Parsing (updateState, getState, getInput, setInput, - getPosition, addIncludeFile, getIncludeFiles, - dropLatestIncludeFile) -import Data.Maybe (fromMaybe) - -readFileFromTexinputs :: PandocMonad m => FilePath -> LP m (Maybe Text) -readFileFromTexinputs fp = do - fileContentsMap <- sFileContents <$> getState - case M.lookup (T.pack fp) fileContentsMap of - Just t -> return (Just t) - Nothing -> do - dirs <- map T.unpack . splitTextBy (==':') . fromMaybe "." - <$> lookupEnv "TEXINPUTS" - readFileFromDirs dirs fp - -insertIncluded :: PandocMonad m - => FilePath - -> FilePath - -> LP m () -insertIncluded defaultExtension f' = do - let f = case takeExtension f' of - ".tex" -> f' - ".sty" -> f' - _ -> addExtension f' defaultExtension - pos <- getPosition - containers <- getIncludeFiles <$> getState - when (T.pack f `elem` containers) $ - throwError $ PandocParseError $ T.pack $ "Include file loop at " ++ show pos - updateState $ addIncludeFile $ T.pack f - mbcontents <- readFileFromTexinputs f - contents <- case mbcontents of - Just s -> return s - Nothing -> do - report $ CouldNotLoadIncludeFile (T.pack f) pos - return "" - getInput >>= setInput . (tokenize f contents ++) - updateState dropLatestIncludeFile - - diff --git a/src/Text/Pandoc/Readers/LaTeX/Inline.hs b/src/Text/Pandoc/Readers/LaTeX/Inline.hs index 3b37ee50e..7b8bca4af 100644 --- a/src/Text/Pandoc/Readers/LaTeX/Inline.hs +++ b/src/Text/Pandoc/Readers/LaTeX/Inline.hs @@ -35,8 +35,8 @@ import Text.Pandoc.Readers.LaTeX.Parsing import Text.Pandoc.Extensions (extensionEnabled, Extension(..)) import Text.Pandoc.Parsing (getOption, updateState, getState, notFollowedBy, manyTill, getInput, setInput, incSourceColumn, - option, many1, try, lookAhead) -import Data.Char (isDigit, isLetter) + option, many1, try) +import Data.Char (isDigit) import Text.Pandoc.Highlighting (fromListingsLanguage,) import Data.Maybe (maybeToList, fromMaybe) import Text.Pandoc.Options (ReaderOptions(..)) @@ -50,15 +50,6 @@ rawInlineOr name' fallback = do then rawInline "latex" <$> getRawCommand name' ("\\" <> name') else fallback -doxspace :: PandocMonad m => LP m Inlines -doxspace = - (space <$ lookAhead (satisfyTok startsWithLetter)) <|> return mempty - where startsWithLetter (Tok _ Word t) = - case T.uncons t of - Just (c, _) | isLetter c -> True - _ -> False - startsWithLetter _ = False - dolabel :: PandocMonad m => LP m Inlines dolabel = do v <- braced @@ -289,8 +280,6 @@ charCommands = M.fromList , ("dothyp", lit ".\173") , ("colonhyp", lit ":\173") , ("hyp", lit "-") - -- xspace - , ("xspace", doxspace) ] biblatexInlineCommands :: PandocMonad m |