diff --git a/doc/lua-filters.md b/doc/lua-filters.md index 9ca1003f9..251b9fa85 100644 --- a/doc/lua-filters.md +++ b/doc/lua-filters.md @@ -3414,7 +3414,7 @@ retrieved from the other parsed input files. Parameters: `markup` -: the markup to be parsed (string) +: the markup to be parsed (string|Sources) `format` : format specification, defaults to `"markdown"` (string) diff --git a/src/Text/Pandoc/Lua/Marshal/Sources.hs b/src/Text/Pandoc/Lua/Marshal/Sources.hs index b65b605dd..3b3b58329 100644 --- a/src/Text/Pandoc/Lua/Marshal/Sources.hs +++ b/src/Text/Pandoc/Lua/Marshal/Sources.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} {-# OPTIONS_GHC -fno-warn-orphans #-} {- | @@ -9,13 +10,15 @@ Maintainer : Albert Krewinkel Marshal 'Sources'. -} module Text.Pandoc.Lua.Marshal.Sources - ( pushSources + ( peekSources + , pushSources ) where +import Control.Monad ((<$!>)) import Data.Text (Text) import HsLua as Lua import Text.Pandoc.Lua.Marshal.List (newListMetatable) -import Text.Pandoc.Sources (Sources (..)) +import Text.Pandoc.Sources (Sources (..), toSources) import Text.Parsec (SourcePos, sourceName) -- | Pushes the 'Sources' as a list of lazy Lua objects. @@ -31,6 +34,13 @@ pushSources (Sources srcs) = do rawset (nth 3) 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. typeSource :: LuaError e => DocumentedType e (SourcePos, Text) typeSource = deftype "pandoc input source" diff --git a/src/Text/Pandoc/Lua/Module/Pandoc.hs b/src/Text/Pandoc/Lua/Module/Pandoc.hs index 7d8a98bb1..3dacc48de 100644 --- a/src/Text/Pandoc/Lua/Module/Pandoc.hs +++ b/src/Text/Pandoc/Lua/Module/Pandoc.hs @@ -19,6 +19,7 @@ module Text.Pandoc.Lua.Module.Pandoc ) where import Prelude hiding (read) +import Control.Applicative ((<|>)) import Control.Monad (forM_, when) import Control.Monad.Catch (catch, throwM) 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.ReaderOptions ( peekReaderOptions , pushReaderOptions) +import Text.Pandoc.Lua.Marshal.Sources (peekSources) import Text.Pandoc.Lua.Marshal.WriterOptions ( peekWriterOptions , pushWriterOptions) import Text.Pandoc.Lua.Module.Utils (sha1) @@ -42,6 +44,7 @@ import Text.Pandoc.Options ( ReaderOptions (readerExtensions) , WriterOptions (writerExtensions) ) import Text.Pandoc.Process (pipeProcess) import Text.Pandoc.Readers (Reader (..), getReader) +import Text.Pandoc.Sources (toSources) import Text.Pandoc.Writers (Writer (..), getWriter) import qualified HsLua as Lua @@ -180,10 +183,17 @@ functions = let formatSpec = fromMaybe "markdown" mformatspec readerOpts = fromMaybe def mreaderOptions readAction = getReader formatSpec >>= \case - (TextReader r, es) -> - r readerOpts{readerExtensions = es} (UTF8.toText content) + (TextReader r, es) -> + r readerOpts{readerExtensions = es} + (case content of + Left bs -> toSources $ UTF8.toText bs + Right sources -> sources) (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 Right pd -> -- success, got a Pandoc document @@ -195,7 +205,9 @@ functions = "Extension " <> e <> " not supported for " <> f Left 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 (parameter peekReaderOptions "ReaderOptions" "reader_options" "reader options")