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:
parent
d6e66b1f1d
commit
03054a33e8
2 changed files with 19 additions and 10 deletions
|
@ -3232,6 +3232,14 @@ Returns: the transformed inline element
|
|||
|
||||
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:
|
||||
|
||||
`markup`:
|
||||
|
@ -3246,7 +3254,7 @@ Parameters:
|
|||
ReaderOptions object; defaults to the default values
|
||||
documented in the manual. ([ReaderOptions]|table)
|
||||
|
||||
Returns: pandoc document
|
||||
Returns: pandoc document ([Pandoc](#type-pandoc))
|
||||
|
||||
Usage:
|
||||
|
||||
|
|
|
@ -28,7 +28,6 @@ import Data.Proxy (Proxy (Proxy))
|
|||
import HsLua hiding (pushModule)
|
||||
import HsLua.Class.Peekable (PeekError)
|
||||
import System.Exit (ExitCode (..))
|
||||
import Text.Pandoc.Class.PandocIO (runIO)
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Lua.Orphans ()
|
||||
import Text.Pandoc.Lua.Marshal.AST
|
||||
|
@ -36,7 +35,7 @@ import Text.Pandoc.Lua.Marshal.Filter (peekFilter)
|
|||
import Text.Pandoc.Lua.Marshal.ReaderOptions ( peekReaderOptions
|
||||
, pushReaderOptions)
|
||||
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.Process (pipeProcess)
|
||||
import Text.Pandoc.Readers (Reader (..), getReader)
|
||||
|
@ -171,13 +170,15 @@ functions =
|
|||
### (\content mformatspec mreaderOptions -> do
|
||||
let formatSpec = fromMaybe "markdown" mformatspec
|
||||
readerOpts = fromMaybe def mreaderOptions
|
||||
res <- Lua.liftIO . runIO $ getReader formatSpec >>= \case
|
||||
(TextReader r, es) ->
|
||||
r readerOpts{ readerExtensions = es } (UTF8.toText content)
|
||||
(ByteStringReader r, es) ->
|
||||
r readerOpts{ readerExtensions = es } (BSL.fromStrict content)
|
||||
case res of
|
||||
Right pd -> return pd -- success, got a Pandoc document
|
||||
readAction = getReader formatSpec >>= \case
|
||||
(TextReader r, es) ->
|
||||
r readerOpts{readerExtensions = es} (UTF8.toText content)
|
||||
(ByteStringReader r, es) ->
|
||||
r readerOpts{readerExtensions = es} (BSL.fromStrict content)
|
||||
try (unPandocLua readAction) >>= \case
|
||||
Right pd ->
|
||||
-- success, got a Pandoc document
|
||||
return pd
|
||||
Left (PandocUnknownReaderError f) ->
|
||||
Lua.failLua . T.unpack $ "Unknown reader: " <> f
|
||||
Left (PandocUnsupportedExtensionError e f) ->
|
||||
|
|
Loading…
Reference in a new issue