aboutsummaryrefslogtreecommitdiff
path: root/pandoc-lua-engine/src/Text
diff options
context:
space:
mode:
authorAlbert Krewinkel <[email protected]>2022-10-12 21:37:47 +0200
committerJohn MacFarlane <[email protected]>2022-10-14 10:37:37 -0700
commit8900b0f953798b01087e0135a3a9708a95eb7fde (patch)
treeb7221db3118cff0d81daf9282aa33c05536631f6 /pandoc-lua-engine/src/Text
parent06ba4e9788eb5d53d566c01ad8e24aa91e104a74 (diff)
Lua: Support built-in default templates for custom writers
Custom writers can define a default template via a global `Template` function; the data directory is no longer searched for a default template. Writer authors can restore the old lookup behavior with ``` lua Template = function () local template return template.compile(template.default(PANDOC_SCRIPT_FILE)) end ```
Diffstat (limited to 'pandoc-lua-engine/src/Text')
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Writer.hs31
1 files changed, 24 insertions, 7 deletions
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Writer.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Writer.hs
index a9a044fe6..eeec9b6af 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Writer.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Writer.hs
@@ -21,21 +21,24 @@ import Control.Exception
import Control.Monad ((<=<))
import Data.Default (def)
import Data.Maybe (fromMaybe)
+import Data.Text (Text)
import HsLua
import HsLua.Core.Run (newGCManagedState, withGCManagedState)
import Control.Monad.IO.Class (MonadIO)
import Text.Pandoc.Class (PandocMonad, findFileWithDataFallback)
-import Text.Pandoc.Error (PandocError)
+import Text.Pandoc.Error (PandocError (..))
import Text.Pandoc.Format (ExtensionsConfig (..))
import Text.Pandoc.Lua.Global (Global (..), setGlobals)
import Text.Pandoc.Lua.Init (runLuaWith)
import Text.Pandoc.Lua.Marshal.Format (peekExtensionsConfig)
+import Text.Pandoc.Lua.Marshal.Template (peekTemplate)
+import Text.Pandoc.Templates (Template)
import Text.Pandoc.Writers (Writer (..))
import qualified Text.Pandoc.Lua.Writer.Classic as Classic
-- | Convert Pandoc to custom markup.
writeCustom :: (PandocMonad m, MonadIO m)
- => FilePath -> m (Writer m, ExtensionsConfig)
+ => FilePath -> m (Writer m, ExtensionsConfig, m (Template Text))
writeCustom luaFile = do
luaState <- liftIO newGCManagedState
luaFile' <- fromMaybe luaFile <$> findFileWithDataFallback "writers" luaFile
@@ -56,25 +59,39 @@ writeCustom luaFile = do
pushName x
rawget (nth 2) <* remove (nth 2) -- remove global table
- let writerField = "PANDOC Writer function"
+ let writerField = "Pandoc Writer function"
extsConf <- rawgetglobal "writer_extensions" >>= \case
- TypeNil -> pure $ ExtensionsConfig mempty mempty
+ TypeNil -> ExtensionsConfig mempty mempty <$ pop 1
_ -> forcePeek $ peekExtensionsConfig top `lastly` pop 1
+ -- Store template function in registry
+ let templateField = "Pandoc Writer Template"
+ rawgetglobal "Template" *> setfield registryindex templateField
+
+ let getTemplate = liftIO $ withGCManagedState @PandocError luaState $ do
+ getfield registryindex templateField >>= \case
+ TypeNil -> failLua $ "No default template for writer; " <>
+ "the global variable Template is undefined."
+ _ -> do
+ callTrace 0 1
+ forcePeek $ peekTemplate top `lastly` pop 1
+
+ let addProperties = (, extsConf, getTemplate)
+
rawgetglobal "Writer" >>= \case
TypeNil -> rawgetglobal "ByteStringWriter" >>= \case
TypeNil -> do
-- Neither `Writer` nor `BinaryWriter` are defined. Try to
-- use the file as a classic writer.
pop 1 -- remove nil
- pure $ (,extsConf) . TextWriter $ \opts doc ->
+ pure $ addProperties . TextWriter $ \opts doc ->
liftIO $ withGCManagedState luaState $ do
Classic.runCustom @PandocError opts doc
_ -> do
-- Binary writer. Writer function is on top of the stack.
setfield registryindex writerField
- pure $ (,extsConf) . ByteStringWriter $ \opts doc ->
+ pure $ addProperties . ByteStringWriter $ \opts doc ->
-- Call writer with document and writer options as arguments.
liftIO $ withGCManagedState luaState $ do
getfield registryindex writerField
@@ -85,7 +102,7 @@ writeCustom luaFile = do
_ -> do
-- New-type text writer. Writer function is on top of the stack.
setfield registryindex writerField
- pure $ (,extsConf) . TextWriter $ \opts doc ->
+ pure $ addProperties . TextWriter $ \opts doc ->
liftIO $ withGCManagedState luaState $ do
getfield registryindex writerField
push doc