aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorAlbert Krewinkel <[email protected]>2022-10-12 11:48:21 +0200
committerAlbert Krewinkel <[email protected]>2022-10-12 11:58:18 +0200
commit253d2e768a43c8ab3ad8e1c46b2bc4a02acec946 (patch)
tree591d2f32798cdcd5d6b841b162bbd6aa654ce4bb
parent543cb5d45d3ebc4c5a504be42efd6febb3a9ceaa (diff)
Lua: support extensions in custom readers.
Like custom readers, like writers, can define the set of supported extensions by setting a global. E.g.: ``` lua reader_extensions = { smart = true, citations = false, } ```
-rw-r--r--doc/custom-readers.md41
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Reader.hs14
-rw-r--r--pandoc-lua-engine/test/Tests/Lua/Reader.hs4
-rw-r--r--src/Text/Pandoc/App.hs6
-rw-r--r--src/Text/Pandoc/Scripting.hs2
5 files changed, 60 insertions, 7 deletions
diff --git a/doc/custom-readers.md b/doc/custom-readers.md
index 601d879dd..4d2009690 100644
--- a/doc/custom-readers.md
+++ b/doc/custom-readers.md
@@ -93,6 +93,47 @@ function ByteStringReader (input)
end
```
+# Format extensions
+
+Custom readers can be built such that their behavior is
+controllable through format extensions, such as `smart`,
+`citations`, or `hard-line-breaks`. Supported extensions are those
+that are present as a key in the global `reader_extensions` table.
+Fields of extensions that are enabled default have the value
+`true`, while those that are supported but disabled have value
+`false`.
+
+Example: A writer with the following global table supports the
+extensions `smart` and `citations`, with the former enabled and
+the latter disabled by default:
+
+``` lua
+reader_extensions = {
+ smart = true,
+ citations = false,
+}
+```
+
+The users control extensions as usual, e.g., `pandoc -f
+my-reader.lua+citations`. The extensions are accessible through
+the reader options' `extensions` field, e.g.:
+
+``` lua
+function Reader (input, opts)
+ print(
+ 'The citations extension is',
+ opts.extensions:includes 'citations' and 'enabled' or 'disabled'
+ )
+ -- ...
+end
+```
+
+Extensions that are neither enabled nor disabled in the
+`reader_extensions` field are treated as unsupported by the
+reader. Trying to modify such an extension via the command line
+will lead to an error.
+
+
# Example: plain text reader
This is a simple example using [lpeg] to parse the input
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Reader.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Reader.hs
index 6aeda526f..2c2dd369b 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Reader.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Reader.hs
@@ -1,6 +1,7 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}
+{-# LANGUAGE TupleSections #-}
{- |
Module : Text.Pandoc.Lua.Reader
Copyright : Copyright (C) 2021-2022 John MacFarlane
@@ -14,17 +15,19 @@ Supports custom parsers written in Lua which produce a Pandoc AST.
-}
module Text.Pandoc.Lua.Reader ( readCustom ) where
import Control.Exception
-import Control.Monad ((<=<), when)
+import Control.Monad ((<=<), (<$!>), when)
import Control.Monad.IO.Class (MonadIO)
import Data.Maybe (fromMaybe)
import HsLua as Lua hiding (Operation (Div))
import HsLua.Core.Run (GCManagedState, newGCManagedState, withGCManagedState)
import Text.Pandoc.Class (PandocMonad, findFileWithDataFallback, report)
import Text.Pandoc.Error (PandocError)
+import Text.Pandoc.Format (ExtensionsConfig (..))
import Text.Pandoc.Logging
import Text.Pandoc.Lua.Global (Global (..), setGlobals)
import Text.Pandoc.Lua.Init (runLuaWith)
import Text.Pandoc.Lua.PandocLua
+import Text.Pandoc.Lua.Marshal.Format (peekExtensionsConfig)
import Text.Pandoc.Lua.Marshal.Pandoc (peekPandoc)
import Text.Pandoc.Readers (Reader (..))
import Text.Pandoc.Sources (ToSources(..), sourcesToText)
@@ -32,7 +35,7 @@ import qualified Data.Text as T
-- | Convert custom markup to Pandoc.
readCustom :: (PandocMonad m, MonadIO m)
- => FilePath -> m (Reader m)
+ => FilePath -> m (Reader m, ExtensionsConfig)
readCustom luaFile = do
luaState <- liftIO newGCManagedState
luaFile' <- fromMaybe luaFile <$> findFileWithDataFallback "readers" luaFile
@@ -44,7 +47,12 @@ readCustom luaFile = do
-- to handle this more gracefully):
when (stat /= Lua.OK)
Lua.throwErrorAsException
- getCustomReader luaState
+
+ extsConf <- getglobal "reader_extensions" >>= \case
+ TypeNil -> pure $ ExtensionsConfig mempty mempty
+ _ -> forcePeek $ peekExtensionsConfig top `lastly` pop 1
+
+ (,extsConf) <$!> getCustomReader luaState
where
readerField = "PANDOC Reader function"
diff --git a/pandoc-lua-engine/test/Tests/Lua/Reader.hs b/pandoc-lua-engine/test/Tests/Lua/Reader.hs
index 16474bd91..15ad685b4 100644
--- a/pandoc-lua-engine/test/Tests/Lua/Reader.hs
+++ b/pandoc-lua-engine/test/Tests/Lua/Reader.hs
@@ -27,8 +27,8 @@ tests =
input <- BL.readFile "bytestring.bin"
doc <- runIOorExplode $
readCustom "bytestring-reader.lua" >>= \case
- ByteStringReader f -> f def input
- TextReader {} -> error "Expected a bytestring reader"
+ (ByteStringReader f, _) -> f def input
+ (TextReader {}, _) -> error "Expected a bytestring reader"
let bytes = mconcat $ map (B.str . T.singleton . chr) [0..255]
doc @?= B.doc (B.plain bytes)
]
diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs
index b4a9454e5..1290fc1c5 100644
--- a/src/Text/Pandoc/App.hs
+++ b/src/Text/Pandoc/App.hs
@@ -165,7 +165,11 @@ convertWithOpts' scriptingEngine istty datadir opts = do
(reader, readerExts) <-
if ".lua" `T.isSuffixOf` readerName
- then (,mempty) <$> engineReadCustom scriptingEngine (T.unpack readerName)
+ then do
+ let scriptPath = T.unpack readerNameBase
+ (r, extsConf) <- engineReadCustom scriptingEngine scriptPath
+ rexts <- Format.applyExtensionsDiff extsConf flvrd
+ return (r, rexts)
else if optSandbox opts
then case runPure (getReader flvrd) of
Left e -> throwError e
diff --git a/src/Text/Pandoc/Scripting.hs b/src/Text/Pandoc/Scripting.hs
index 0defa2f77..d4be7e377 100644
--- a/src/Text/Pandoc/Scripting.hs
+++ b/src/Text/Pandoc/Scripting.hs
@@ -36,7 +36,7 @@ data ScriptingEngine = ScriptingEngine
-- ^ Use the scripting engine to run a filter.
, engineReadCustom :: forall m. (PandocMonad m, MonadIO m)
- => FilePath -> m (Reader m)
+ => FilePath -> m (Reader m, ExtensionsConfig)
-- ^ Function to parse input into a 'Pandoc' document.
, engineWriteCustom :: forall m. (PandocMonad m, MonadIO m)