Lua: use global state when parsing documents in pandoc.read

The function `pandoc.read` is updated to use the same state that was
used while parsing the main input files. This ensures that log messages
are preserved and that images embedded in the input are added to the
mediabag.
This commit is contained in:
Albert Krewinkel 2021-12-31 10:23:32 +01:00 committed by John MacFarlane
parent d6e66b1f1d
commit 03054a33e8
2 changed files with 19 additions and 10 deletions

View file

@ -3232,6 +3232,14 @@ Returns: the transformed inline element
Parse the given string into a Pandoc document. Parse the given string into a Pandoc document.
The parser is run in the same environment that was used to read
the main input files; it has full access to the file-system and
the mediabag. This means that if the document specifies files to
be included, as is possible in formats like LaTeX,
reStructuredText, and Org, then these will be included in the
resulting document. Any media elements are added to those
retrieved from the other parsed input files.
Parameters: Parameters:
`markup`: `markup`:
@ -3246,7 +3254,7 @@ Parameters:
ReaderOptions object; defaults to the default values ReaderOptions object; defaults to the default values
documented in the manual. ([ReaderOptions]|table) documented in the manual. ([ReaderOptions]|table)
Returns: pandoc document Returns: pandoc document ([Pandoc](#type-pandoc))
Usage: Usage:

View file

@ -28,7 +28,6 @@ import Data.Proxy (Proxy (Proxy))
import HsLua hiding (pushModule) import HsLua hiding (pushModule)
import HsLua.Class.Peekable (PeekError) import HsLua.Class.Peekable (PeekError)
import System.Exit (ExitCode (..)) import System.Exit (ExitCode (..))
import Text.Pandoc.Class.PandocIO (runIO)
import Text.Pandoc.Definition import Text.Pandoc.Definition
import Text.Pandoc.Lua.Orphans () import Text.Pandoc.Lua.Orphans ()
import Text.Pandoc.Lua.Marshal.AST import Text.Pandoc.Lua.Marshal.AST
@ -36,7 +35,7 @@ import Text.Pandoc.Lua.Marshal.Filter (peekFilter)
import Text.Pandoc.Lua.Marshal.ReaderOptions ( peekReaderOptions import Text.Pandoc.Lua.Marshal.ReaderOptions ( peekReaderOptions
, pushReaderOptions) , pushReaderOptions)
import Text.Pandoc.Lua.Module.Utils (sha1) import Text.Pandoc.Lua.Module.Utils (sha1)
import Text.Pandoc.Lua.PandocLua (PandocLua, liftPandocLua) import Text.Pandoc.Lua.PandocLua (PandocLua (unPandocLua), liftPandocLua)
import Text.Pandoc.Options (ReaderOptions (readerExtensions)) import Text.Pandoc.Options (ReaderOptions (readerExtensions))
import Text.Pandoc.Process (pipeProcess) import Text.Pandoc.Process (pipeProcess)
import Text.Pandoc.Readers (Reader (..), getReader) import Text.Pandoc.Readers (Reader (..), getReader)
@ -171,13 +170,15 @@ functions =
### (\content mformatspec mreaderOptions -> do ### (\content mformatspec mreaderOptions -> do
let formatSpec = fromMaybe "markdown" mformatspec let formatSpec = fromMaybe "markdown" mformatspec
readerOpts = fromMaybe def mreaderOptions readerOpts = fromMaybe def mreaderOptions
res <- Lua.liftIO . runIO $ getReader formatSpec >>= \case readAction = getReader formatSpec >>= \case
(TextReader r, es) -> (TextReader r, es) ->
r readerOpts{ readerExtensions = es } (UTF8.toText content) r readerOpts{readerExtensions = es} (UTF8.toText content)
(ByteStringReader r, es) -> (ByteStringReader r, es) ->
r readerOpts{ readerExtensions = es } (BSL.fromStrict content) r readerOpts{readerExtensions = es} (BSL.fromStrict content)
case res of try (unPandocLua readAction) >>= \case
Right pd -> return pd -- success, got a Pandoc document Right pd ->
-- success, got a Pandoc document
return pd
Left (PandocUnknownReaderError f) -> Left (PandocUnknownReaderError f) ->
Lua.failLua . T.unpack $ "Unknown reader: " <> f Lua.failLua . T.unpack $ "Unknown reader: " <> f
Left (PandocUnsupportedExtensionError e f) -> Left (PandocUnsupportedExtensionError e f) ->