diff options
author | John MacFarlane <jgm@berkeley.edu> | 2021-03-03 18:47:17 -0800 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2021-03-03 18:47:17 -0800 |
commit | b569b0226d4bd5e0699077089d54fb03d4394b7d (patch) | |
tree | 5ab2d3fb3c0f91854fc4a352b740852c1b57f2c4 /src/Text/Pandoc/Readers/LaTeX | |
parent | 33e4c8dd6c2bbc8109880f43b379d074ceb38391 (diff) | |
download | pandoc-b569b0226d4bd5e0699077089d54fb03d4394b7d.tar.gz |
Add T.P.Readers.LaTeX.Include.
Diffstat (limited to 'src/Text/Pandoc/Readers/LaTeX')
-rw-r--r-- | src/Text/Pandoc/Readers/LaTeX/Include.hs | 66 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/LaTeX/Inline.hs | 15 |
2 files changed, 79 insertions, 2 deletions
diff --git a/src/Text/Pandoc/Readers/LaTeX/Include.hs b/src/Text/Pandoc/Readers/LaTeX/Include.hs new file mode 100644 index 000000000..618a89284 --- /dev/null +++ b/src/Text/Pandoc/Readers/LaTeX/Include.hs @@ -0,0 +1,66 @@ +{-# 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 7b8bca4af..3b37ee50e 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) -import Data.Char (isDigit) + option, many1, try, lookAhead) +import Data.Char (isDigit, isLetter) import Text.Pandoc.Highlighting (fromListingsLanguage,) import Data.Maybe (maybeToList, fromMaybe) import Text.Pandoc.Options (ReaderOptions(..)) @@ -50,6 +50,15 @@ 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 @@ -280,6 +289,8 @@ charCommands = M.fromList , ("dothyp", lit ".\173") , ("colonhyp", lit ":\173") , ("hyp", lit "-") + -- xspace + , ("xspace", doxspace) ] biblatexInlineCommands :: PandocMonad m |