diff options
| author | Albert Krewinkel <[email protected]> | 2022-10-11 21:40:21 +0200 |
|---|---|---|
| committer | John MacFarlane <[email protected]> | 2022-10-11 14:03:08 -0700 |
| commit | 78d7fc46febe3f2d5ebc1bea4761d115bb26f117 (patch) | |
| tree | ffb4bccbdc58ee339cfdd44879b8fb153f4dc3a1 /pandoc-lua-engine/src/Text/Pandoc/Lua | |
| parent | 3cac33bdd2b2b69ac585cc37498deea49763c665 (diff) | |
Lua: add function `pandoc.template.apply`
The new function applies a context, containing variable assignments, to
a template.
Diffstat (limited to 'pandoc-lua-engine/src/Text/Pandoc/Lua')
| -rw-r--r-- | pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Context.hs | 66 | ||||
| -rw-r--r-- | pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Template.hs | 22 |
2 files changed, 69 insertions, 19 deletions
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Context.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Context.hs index 126f3a82d..dfaa1ff87 100644 --- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Context.hs +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Context.hs @@ -1,3 +1,6 @@ +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE OverloadedStrings #-} {-# OPTIONS_GHC -fno-warn-orphans #-} {- | Module : Text.Pandoc.Lua.Marshaling.Context @@ -10,19 +13,50 @@ Marshaling instance for doctemplates Context and its components. -} -module Text.Pandoc.Lua.Marshal.Context () where - -import qualified HsLua as Lua -import HsLua (Pushable) -import Text.DocTemplates (Context(..), Val(..), TemplateTarget) -import Text.DocLayout (render) - -instance (TemplateTarget a, Pushable a) => Pushable (Context a) where - push (Context m) = Lua.push m - -instance (TemplateTarget a, Pushable a) => Pushable (Val a) where - push NullVal = Lua.push () - push (BoolVal b) = Lua.push b - push (MapVal ctx) = Lua.push ctx - push (ListVal xs) = Lua.push xs - push (SimpleVal d) = Lua.push $ render Nothing d +module Text.Pandoc.Lua.Marshal.Context + ( peekContext + , pushContext + ) where + +import Control.Monad ((<$!>)) +import Data.Text (Text) +import HsLua as Lua +import HsLua.Module.DocLayout (peekDoc, pushDoc) +import Text.DocTemplates (Context(..), Val(..)) + +instance Pushable (Context Text) where + push = pushContext + +instance Pushable (Val Text) where + push = pushVal + +-- | Retrieves a template context from the Lua stack. +peekContext :: LuaError e => Peeker e (Context Text) +peekContext idx = Context <$!> peekMap peekText peekVal idx + +-- | Pushes a template context to the Lua stack. +pushContext :: LuaError e => Pusher e (Context Text) +pushContext = pushMap pushText pushVal . unContext + +pushVal :: LuaError e => Pusher e (Val Text) +pushVal = \case + NullVal -> Lua.pushnil + BoolVal b -> Lua.pushBool b + MapVal ctx -> pushContext ctx + ListVal xs -> pushList pushVal xs + SimpleVal d -> pushDoc d + +peekVal :: LuaError e => Peeker e (Val Text) +peekVal idx = liftLua (ltype idx) >>= \case + TypeNil -> pure NullVal + TypeBoolean -> BoolVal <$!> peekBool idx + TypeNumber -> SimpleVal <$!> peekDoc idx + TypeString -> SimpleVal <$!> peekDoc idx + TypeTable -> do + len <- liftLua $ Lua.rawlen idx + if len <= 0 + then MapVal <$!> peekContext idx + else ListVal <$!> peekList peekVal idx + TypeUserdata -> SimpleVal <$!> peekDoc idx + _ -> failPeek =<< + typeMismatchMessage "Doc, string, boolean, table, or nil" idx diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Template.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Template.hs index 967fe31a8..be769e988 100644 --- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Template.hs +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Template.hs @@ -12,11 +12,14 @@ module Text.Pandoc.Lua.Module.Template ) where import HsLua +import HsLua.Module.DocLayout (pushDoc) import Text.Pandoc.Error (PandocError) -import Text.Pandoc.Lua.Marshal.Template (pushTemplate) +import Text.Pandoc.Lua.Marshal.Context (peekContext) +import Text.Pandoc.Lua.Marshal.Template (peekTemplate, pushTemplate) import Text.Pandoc.Lua.PandocLua (PandocLua (unPandocLua), liftPandocLua) import Text.Pandoc.Templates - (compileTemplate, getDefaultTemplate, runWithPartials, runWithDefaultPartials) + ( compileTemplate, getDefaultTemplate, renderTemplate + , runWithPartials, runWithDefaultPartials ) import qualified Data.Text as T @@ -35,7 +38,20 @@ documentedModule = Module -- | Template module functions. functions :: [DocumentedFunction PandocError] functions = - [ defun "compile" + [ defun "apply" + ### liftPure2 renderTemplate + <#> parameter peekTemplate "pandoc Template" "template" "template to apply" + <#> parameter peekContext "table" "context" "variable values" + =#> functionResult pushDoc "Doc" "rendered template" + #? T.unlines + [ "Applies a context with variable assignments to a template," + , "returning the rendered template. The `context` parameter must be a" + , "table with variable names as keys and [Doc], string, boolean, or" + , "table as values, where the table can be either be a list of the" + , "aforementioned types, or a nested context." + ] + + , defun "compile" ### (\template mfilepath -> unPandocLua $ case mfilepath of Just fp -> runWithPartials (compileTemplate fp template) |
