parent
1ce7db1fa6
commit
ea479bf28a
3 changed files with 65 additions and 6 deletions
|
@ -1219,6 +1219,7 @@ preamble :: PandocMonad m => LP m Blocks
|
||||||
preamble = mconcat <$> many preambleBlock
|
preamble = mconcat <$> many preambleBlock
|
||||||
where preambleBlock = (mempty <$ spaces1)
|
where preambleBlock = (mempty <$ spaces1)
|
||||||
<|> macroDef (rawBlock "latex")
|
<|> macroDef (rawBlock "latex")
|
||||||
|
<|> filecontents
|
||||||
<|> (mempty <$ blockCommand)
|
<|> (mempty <$ blockCommand)
|
||||||
<|> (mempty <$ braced)
|
<|> (mempty <$ braced)
|
||||||
<|> (do notFollowedBy (begin_ "document")
|
<|> (do notFollowedBy (begin_ "document")
|
||||||
|
@ -1272,6 +1273,16 @@ include name = do
|
||||||
mapM_ (insertIncluded defaultExt) fs
|
mapM_ (insertIncluded defaultExt) fs
|
||||||
return mempty
|
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
|
insertIncluded :: PandocMonad m
|
||||||
=> FilePath
|
=> FilePath
|
||||||
-> FilePath
|
-> FilePath
|
||||||
|
@ -1281,13 +1292,12 @@ insertIncluded defaultExtension f' = do
|
||||||
".tex" -> f'
|
".tex" -> f'
|
||||||
".sty" -> f'
|
".sty" -> f'
|
||||||
_ -> addExtension f' defaultExtension
|
_ -> addExtension f' defaultExtension
|
||||||
dirs <- map T.unpack . splitTextBy (==':') . fromMaybe "." <$> lookupEnv "TEXINPUTS"
|
|
||||||
pos <- getPosition
|
pos <- getPosition
|
||||||
containers <- getIncludeFiles <$> getState
|
containers <- getIncludeFiles <$> getState
|
||||||
when (T.pack f `elem` containers) $
|
when (T.pack f `elem` containers) $
|
||||||
throwError $ PandocParseError $ T.pack $ "Include file loop at " ++ show pos
|
throwError $ PandocParseError $ T.pack $ "Include file loop at " ++ show pos
|
||||||
updateState $ addIncludeFile $ T.pack f
|
updateState $ addIncludeFile $ T.pack f
|
||||||
mbcontents <- readFileFromDirs dirs f
|
mbcontents <- readFileFromTexinputs f
|
||||||
contents <- case mbcontents of
|
contents <- case mbcontents of
|
||||||
Just s -> return s
|
Just s -> return s
|
||||||
Nothing -> do
|
Nothing -> do
|
||||||
|
@ -1695,6 +1705,18 @@ environments = M.fromList
|
||||||
, ("iftoggle", try $ ifToggle >> block)
|
, ("iftoggle", try $ ifToggle >> block)
|
||||||
]
|
]
|
||||||
|
|
||||||
|
filecontents :: PandocMonad m => LP m Blocks
|
||||||
|
filecontents = try $ do
|
||||||
|
controlSeq "begin"
|
||||||
|
name <- untokenize <$> braced
|
||||||
|
guard $ name == "filecontents" || name == "filecontents*"
|
||||||
|
skipopts
|
||||||
|
fp <- untokenize <$> braced
|
||||||
|
txt <- verbEnv name
|
||||||
|
updateState $ \st ->
|
||||||
|
st{ sFileContents = M.insert fp txt (sFileContents st) }
|
||||||
|
return mempty
|
||||||
|
|
||||||
theoremstyle :: PandocMonad m => LP m Blocks
|
theoremstyle :: PandocMonad m => LP m Blocks
|
||||||
theoremstyle = do
|
theoremstyle = do
|
||||||
stylename <- untokenize <$> braced
|
stylename <- untokenize <$> braced
|
||||||
|
@ -1894,8 +1916,7 @@ inputMinted = do
|
||||||
pos <- getPosition
|
pos <- getPosition
|
||||||
attr <- mintedAttr
|
attr <- mintedAttr
|
||||||
f <- T.filter (/='"') . untokenize <$> braced
|
f <- T.filter (/='"') . untokenize <$> braced
|
||||||
dirs <- map T.unpack . splitTextBy (==':') . fromMaybe "." <$> lookupEnv "TEXINPUTS"
|
mbCode <- readFileFromTexinputs (T.unpack f)
|
||||||
mbCode <- readFileFromDirs dirs (T.unpack f)
|
|
||||||
rawcode <- case mbCode of
|
rawcode <- case mbCode of
|
||||||
Just s -> return s
|
Just s -> return s
|
||||||
Nothing -> do
|
Nothing -> do
|
||||||
|
@ -1981,8 +2002,7 @@ inputListing = do
|
||||||
pos <- getPosition
|
pos <- getPosition
|
||||||
options <- option [] keyvals
|
options <- option [] keyvals
|
||||||
f <- T.filter (/='"') . untokenize <$> braced
|
f <- T.filter (/='"') . untokenize <$> braced
|
||||||
dirs <- map T.unpack . splitTextBy (==':') . fromMaybe "." <$> lookupEnv "TEXINPUTS"
|
mbCode <- readFileFromTexinputs (T.unpack f)
|
||||||
mbCode <- readFileFromDirs dirs (T.unpack f)
|
|
||||||
codeLines <- case mbCode of
|
codeLines <- case mbCode of
|
||||||
Just s -> return $ T.lines s
|
Just s -> return $ T.lines s
|
||||||
Nothing -> do
|
Nothing -> do
|
||||||
|
|
|
@ -152,6 +152,7 @@ data LaTeXState = LaTeXState{ sOptions :: ReaderOptions
|
||||||
, sHasChapters :: Bool
|
, sHasChapters :: Bool
|
||||||
, sToggles :: M.Map Text Bool
|
, sToggles :: M.Map Text Bool
|
||||||
, sExpanded :: Bool
|
, sExpanded :: Bool
|
||||||
|
, sFileContents :: M.Map Text Text
|
||||||
}
|
}
|
||||||
deriving Show
|
deriving Show
|
||||||
|
|
||||||
|
@ -177,6 +178,7 @@ defaultLaTeXState = LaTeXState{ sOptions = def
|
||||||
, sHasChapters = False
|
, sHasChapters = False
|
||||||
, sToggles = M.empty
|
, sToggles = M.empty
|
||||||
, sExpanded = False
|
, sExpanded = False
|
||||||
|
, sFileContents = M.empty
|
||||||
}
|
}
|
||||||
|
|
||||||
instance PandocMonad m => HasQuoteContext LaTeXState m where
|
instance PandocMonad m => HasQuoteContext LaTeXState m where
|
||||||
|
|
37
test/command/7003.md
Normal file
37
test/command/7003.md
Normal file
|
@ -0,0 +1,37 @@
|
||||||
|
```
|
||||||
|
% pandoc -f latex -t native
|
||||||
|
\documentclass{article}
|
||||||
|
\usepackage{listings}
|
||||||
|
|
||||||
|
\lstset{basicstyle=\ttfamily}
|
||||||
|
|
||||||
|
\begin{filecontents*}[overwrite]{example.tex}
|
||||||
|
\documentclass{article}
|
||||||
|
\begin{document}
|
||||||
|
\section{Bar}
|
||||||
|
This a Bar section
|
||||||
|
\end{document}
|
||||||
|
\end{filecontents*}
|
||||||
|
|
||||||
|
\begin{document}
|
||||||
|
|
||||||
|
\section{With lstlisting environment}
|
||||||
|
|
||||||
|
\begin{lstlisting}
|
||||||
|
\documentclass{article}
|
||||||
|
\begin{document}
|
||||||
|
\section{Foo}
|
||||||
|
This a Foo section
|
||||||
|
\end{document}
|
||||||
|
\end{lstlisting}
|
||||||
|
|
||||||
|
\section{With lstinputlisting command}
|
||||||
|
|
||||||
|
\lstinputlisting{example.tex}
|
||||||
|
\end{document}
|
||||||
|
^D
|
||||||
|
[Header 1 ("with-lstlisting-environment",[],[]) [Str "With",Space,Str "lstlisting",Space,Str "environment"]
|
||||||
|
,CodeBlock ("",[],[]) "\\documentclass{article}\n\\begin{document}\n\\section{Foo}\nThis a Foo section\n\\end{document}"
|
||||||
|
,Header 1 ("with-lstinputlisting-command",[],[]) [Str "With",Space,Str "lstinputlisting",Space,Str "command"]
|
||||||
|
,CodeBlock ("",["latex"],[]) "\\documentclass{article}\n\\begin{document}\n\\section{Bar}\nThis a Bar section\n\\end{document}"]
|
||||||
|
```
|
Loading…
Reference in a new issue