aboutsummaryrefslogtreecommitdiff
path: root/pandoc-lua-engine/src
diff options
context:
space:
mode:
authorAlbert Krewinkel <[email protected]>2022-10-27 22:04:59 +0200
committerAlbert Krewinkel <[email protected]>2022-10-27 22:09:39 +0200
commit6c4d885bdaf8f31afafa5a785a3517a40b529408 (patch)
tree269792ebd45c72ec758a497c5e3039ed8c5391c7 /pandoc-lua-engine/src
parent91436ebbf45d8d0891053ebdfbb837c71c4bf33a (diff)
Lua: allow strings in place of compiled templates.
This allows to use a string as parameter to `pandoc.template.apply` and in the WriterOptions `template` field. Closes: #8321
Diffstat (limited to 'pandoc-lua-engine/src')
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Template.hs18
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/WriterOptions.hs12
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Pandoc.hs2
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Writer.hs5
4 files changed, 24 insertions, 13 deletions
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Template.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Template.hs
index 56878b109..5425a566c 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Template.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Template.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{- |
@@ -16,15 +17,26 @@ module Text.Pandoc.Lua.Marshal.Template
import Data.Text (Text)
import HsLua as Lua
-import Text.DocTemplates (Template)
+import HsLua.Core.Utf8 as Lua
+import Text.Pandoc.Error (PandocError)
+import Text.Pandoc.Lua.PandocLua (unPandocLua)
+import Text.Pandoc.Templates (Template, compileTemplate, runWithDefaultPartials)
-- | Pushes a 'Template' as a an opaque userdata value.
pushTemplate :: LuaError e => Pusher e (Template Text)
pushTemplate = pushUD typeTemplate
-- | Retrieves a 'Template' 'Text' value from the stack.
-peekTemplate :: LuaError e => Peeker e (Template Text)
-peekTemplate = peekUD typeTemplate
+peekTemplate :: Peeker PandocError (Template Text)
+peekTemplate idx = liftLua (ltype idx) >>= \case
+ TypeString -> do
+ let path = "templates/default.custom"
+ let liftPM = liftLua . unPandocLua
+ tmpl <- peekText idx
+ (liftPM $ runWithDefaultPartials (compileTemplate path tmpl)) >>= \case
+ Left e -> failPeek (Lua.fromString e)
+ Right t -> pure t
+ _ -> peekUD typeTemplate idx
-- | Template object type.
typeTemplate :: LuaError e => DocumentedType e (Template Text)
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/WriterOptions.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/WriterOptions.hs
index 48451457b..1b0a9ea1c 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/WriterOptions.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/WriterOptions.hs
@@ -21,6 +21,7 @@ module Text.Pandoc.Lua.Marshal.WriterOptions
import Control.Applicative (optional)
import Data.Default (def)
import HsLua as Lua
+import Text.Pandoc.Error (PandocError)
import Text.Pandoc.Lua.Marshal.Context (peekContext, pushContext)
import Text.Pandoc.Lua.Marshal.Format (peekExtensions, pushExtensions)
import Text.Pandoc.Lua.Marshal.List (pushPandocList)
@@ -34,7 +35,7 @@ import Text.Pandoc.Options (WriterOptions (..))
-- | Retrieve a WriterOptions value, either from a normal WriterOptions
-- value, from a read-only object, or from a table with the same
-- keys as a WriterOptions object.
-peekWriterOptions :: LuaError e => Peeker e WriterOptions
+peekWriterOptions :: Peeker PandocError WriterOptions
peekWriterOptions = retrieving "WriterOptions" . \idx ->
liftLua (ltype idx) >>= \case
TypeUserdata -> peekUD typeWriterOptions idx
@@ -43,11 +44,11 @@ peekWriterOptions = retrieving "WriterOptions" . \idx ->
typeMismatchMessage "WriterOptions userdata or table" idx
-- | Pushes a WriterOptions value as userdata object.
-pushWriterOptions :: LuaError e => Pusher e WriterOptions
+pushWriterOptions :: Pusher PandocError WriterOptions
pushWriterOptions = pushUD typeWriterOptions
-- | 'WriterOptions' object type.
-typeWriterOptions :: LuaError e => DocumentedType e WriterOptions
+typeWriterOptions :: DocumentedType PandocError WriterOptions
typeWriterOptions = deftype "WriterOptions"
[ operation Tostring $ lambda
### liftPure show
@@ -223,7 +224,7 @@ typeWriterOptions = deftype "WriterOptions"
-- key/value pair of the table in the userdata value, then retrieves the
-- object again. This will update all fields and complain about unknown
-- keys.
-peekWriterOptionsTable :: LuaError e => Peeker e WriterOptions
+peekWriterOptionsTable :: Peeker PandocError WriterOptions
peekWriterOptionsTable idx = retrieving "WriterOptions (table)" $ do
liftLua $ do
absidx <- absindex idx
@@ -238,6 +239,3 @@ peekWriterOptionsTable idx = retrieving "WriterOptions (table)" $ do
pushnil -- first key
setFields
peekUD typeWriterOptions top `lastly` pop 1
-
-instance Pushable WriterOptions where
- push = pushWriterOptions
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Pandoc.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Pandoc.hs
index b42bdc50f..aaca86b02 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Pandoc.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Pandoc.hs
@@ -131,7 +131,7 @@ pushWithConstructorsSubtable constructors = do
rawset (nth 3)
pop 1 -- pop constructor table
-otherConstructors :: LuaError e => [DocumentedFunction e]
+otherConstructors :: [DocumentedFunction PandocError]
otherConstructors =
[ mkPandoc
, mkMeta
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Writer.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Writer.hs
index e310b33c8..c5e3e2469 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Writer.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Writer.hs
@@ -32,6 +32,7 @@ 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.Lua.Marshal.WriterOptions (pushWriterOptions)
import Text.Pandoc.Templates (Template)
import Text.Pandoc.Writers (Writer (..))
import qualified Text.Pandoc.Lua.Writer.Classic as Classic
@@ -96,7 +97,7 @@ writeCustom luaFile = do
liftIO $ withGCManagedState luaState $ do
getfield registryindex writerField
push doc
- push opts
+ pushWriterOptions opts
callTrace 2 1
forcePeek @PandocError $ peekLazyByteString top
_ -> do
@@ -106,6 +107,6 @@ writeCustom luaFile = do
liftIO $ withGCManagedState luaState $ do
getfield registryindex writerField
push doc
- push opts
+ pushWriterOptions opts
callTrace 2 1
forcePeek @PandocError $ peekText top