Lua: allow to pass Sources to pandoc.read (#8002)

Sources, the data type passed to the `Reader` function in custom
readers, are now accepted as input to `pandoc.read`.
This commit is contained in:
Albert Krewinkel 2022-03-30 23:10:30 +02:00 committed by GitHub
parent 63de34481a
commit ad726953b9
No known key found for this signature in database
GPG key ID: 4AEE18F83AFDEB23
3 changed files with 29 additions and 7 deletions

View file

@ -3414,7 +3414,7 @@ retrieved from the other parsed input files.
Parameters: Parameters:
`markup` `markup`
: the markup to be parsed (string) : the markup to be parsed (string|Sources)
`format` `format`
: format specification, defaults to `"markdown"` (string) : format specification, defaults to `"markdown"` (string)

View file

@ -1,3 +1,4 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -fno-warn-orphans #-} {-# OPTIONS_GHC -fno-warn-orphans #-}
{- | {- |
@ -9,13 +10,15 @@ Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
Marshal 'Sources'. Marshal 'Sources'.
-} -}
module Text.Pandoc.Lua.Marshal.Sources module Text.Pandoc.Lua.Marshal.Sources
( pushSources ( peekSources
, pushSources
) where ) where
import Control.Monad ((<$!>))
import Data.Text (Text) import Data.Text (Text)
import HsLua as Lua import HsLua as Lua
import Text.Pandoc.Lua.Marshal.List (newListMetatable) import Text.Pandoc.Lua.Marshal.List (newListMetatable)
import Text.Pandoc.Sources (Sources (..)) import Text.Pandoc.Sources (Sources (..), toSources)
import Text.Parsec (SourcePos, sourceName) import Text.Parsec (SourcePos, sourceName)
-- | Pushes the 'Sources' as a list of lazy Lua objects. -- | Pushes the 'Sources' as a list of lazy Lua objects.
@ -31,6 +34,13 @@ pushSources (Sources srcs) = do
rawset (nth 3) rawset (nth 3)
setmetatable (nth 2) setmetatable (nth 2)
-- | Retrieves sources from the stack.
peekSources :: LuaError e => Peeker e Sources
peekSources idx = liftLua (ltype idx) >>= \case
TypeString -> toSources <$!> peekText idx
TypeTable -> Sources <$!> peekList (peekUD typeSource) idx
_ -> Sources . (:[]) <$!> peekUD typeSource idx
-- | Source object type. -- | Source object type.
typeSource :: LuaError e => DocumentedType e (SourcePos, Text) typeSource :: LuaError e => DocumentedType e (SourcePos, Text)
typeSource = deftype "pandoc input source" typeSource = deftype "pandoc input source"

View file

@ -19,6 +19,7 @@ module Text.Pandoc.Lua.Module.Pandoc
) where ) where
import Prelude hiding (read) import Prelude hiding (read)
import Control.Applicative ((<|>))
import Control.Monad (forM_, when) import Control.Monad (forM_, when)
import Control.Monad.Catch (catch, throwM) import Control.Monad.Catch (catch, throwM)
import Data.Data (Data, dataTypeConstrs, dataTypeOf, showConstr) import Data.Data (Data, dataTypeConstrs, dataTypeOf, showConstr)
@ -34,6 +35,7 @@ import Text.Pandoc.Lua.Marshal.AST
import Text.Pandoc.Lua.Marshal.Filter (peekFilter) 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.Marshal.Sources (peekSources)
import Text.Pandoc.Lua.Marshal.WriterOptions ( peekWriterOptions import Text.Pandoc.Lua.Marshal.WriterOptions ( peekWriterOptions
, pushWriterOptions) , pushWriterOptions)
import Text.Pandoc.Lua.Module.Utils (sha1) import Text.Pandoc.Lua.Module.Utils (sha1)
@ -42,6 +44,7 @@ import Text.Pandoc.Options ( ReaderOptions (readerExtensions)
, WriterOptions (writerExtensions) ) , WriterOptions (writerExtensions) )
import Text.Pandoc.Process (pipeProcess) import Text.Pandoc.Process (pipeProcess)
import Text.Pandoc.Readers (Reader (..), getReader) import Text.Pandoc.Readers (Reader (..), getReader)
import Text.Pandoc.Sources (toSources)
import Text.Pandoc.Writers (Writer (..), getWriter) import Text.Pandoc.Writers (Writer (..), getWriter)
import qualified HsLua as Lua import qualified HsLua as Lua
@ -180,10 +183,17 @@ functions =
let formatSpec = fromMaybe "markdown" mformatspec let formatSpec = fromMaybe "markdown" mformatspec
readerOpts = fromMaybe def mreaderOptions readerOpts = fromMaybe def mreaderOptions
readAction = getReader formatSpec >>= \case readAction = getReader formatSpec >>= \case
(TextReader r, es) -> (TextReader r, es) ->
r readerOpts{readerExtensions = es} (UTF8.toText content) r readerOpts{readerExtensions = es}
(case content of
Left bs -> toSources $ UTF8.toText bs
Right sources -> sources)
(ByteStringReader r, es) -> (ByteStringReader r, es) ->
r readerOpts{readerExtensions = es} (BSL.fromStrict content) case content of
Left bs -> r readerOpts{readerExtensions = es}
(BSL.fromStrict bs)
Right _ -> liftPandocLua $ Lua.failLua
"Cannot use bytestring reader with Sources"
try (unPandocLua readAction) >>= \case try (unPandocLua readAction) >>= \case
Right pd -> Right pd ->
-- success, got a Pandoc document -- success, got a Pandoc document
@ -195,7 +205,9 @@ functions =
"Extension " <> e <> " not supported for " <> f "Extension " <> e <> " not supported for " <> f
Left e -> Left e ->
throwM e) throwM e)
<#> parameter peekByteString "string" "content" "text to parse" <#> parameter (\idx -> (Left <$> peekByteString idx)
<|> (Right <$> peekSources idx))
"string|Sources" "content" "text to parse"
<#> opt (textParam "formatspec" "format and extensions") <#> opt (textParam "formatspec" "format and extensions")
<#> opt (parameter peekReaderOptions "ReaderOptions" "reader_options" <#> opt (parameter peekReaderOptions "ReaderOptions" "reader_options"
"reader options") "reader options")