Lua: add pandoc.template module

The module provides a `compile` function to use strings as templates.
This commit is contained in:
Albert Krewinkel 2022-01-04 10:38:02 +01:00 committed by John MacFarlane
parent 974a9d353a
commit 1f8638fb54
9 changed files with 187 additions and 2 deletions

View file

@ -2121,7 +2121,7 @@ Fields:
: Include table of contents (boolean)
`template`
: Template to use (pandoc Template|nil)
: Template to use ([Template](#type-template)|nil)
`toc_depth`
: Number of levels to include in TOC (integer)
@ -2231,6 +2231,10 @@ Fields:
: table rows ([List] of rows, where a row is a list of simple
cells, i.e., [List] of [Blocks][])
## Template {#type-template}
Opaque type holding a compiled template.
## Version {#type-version}
A version object. This represents a software version like
@ -4393,6 +4397,55 @@ Returns:
- The result(s) of the call to `callback`
# Module pandoc.template
Handle pandoc templates.
### compile {#pandoc.template.compile}
`compile (template[, templates_path])`
Compiles a template string into a [Template](#type-template)
object usable by pandoc.
If the `templates_path` parameter is specified, should be the
file path associated with the template. It is used when checking
for partials. Partials will be taken only from the default data
files if this parameter is omitted.
An error is raised if compilation fails.
Parameters:
`template`:
: template string (string)
`templates_path`:
: parameter to determine a default path and extension for
partials; uses the data files templates path by default.
(string)
Returns:
- compiled template (Template)
### default {#pandoc.template.default}
`default ([writer])`
Returns the default template for a given writer as a string. An
error if no such template can be found.
Parameters:
`writer`:
: name of the writer for which the template should be
retrieved; defaults to the global `FORMAT`.
Returns:
- raw template (string)
# Module pandoc.types
Constructors for types which are not part of the pandoc AST.

View file

@ -711,6 +711,7 @@ library
Text.Pandoc.Lua.Module.MediaBag,
Text.Pandoc.Lua.Module.Pandoc,
Text.Pandoc.Lua.Module.System,
Text.Pandoc.Lua.Module.Template,
Text.Pandoc.Lua.Module.Types,
Text.Pandoc.Lua.Module.Utils,
Text.Pandoc.Lua.Orphans,

View file

@ -48,6 +48,7 @@ loadedModules =
, ("pandoc.mediabag", "mediabag")
, ("pandoc.path", "path")
, ("pandoc.system", "system")
, ("pandoc.template", "template")
, ("pandoc.types", "types")
, ("pandoc.utils", "utils")
, ("text", "text")

View file

@ -29,6 +29,7 @@ import HsLua hiding (pushModule)
import HsLua.Class.Peekable (PeekError)
import System.Exit (ExitCode (..))
import Text.Pandoc.Definition
import Text.Pandoc.Error (PandocError (..))
import Text.Pandoc.Lua.Orphans ()
import Text.Pandoc.Lua.Marshal.AST
import Text.Pandoc.Lua.Marshal.Filter (peekFilter)
@ -50,7 +51,6 @@ import qualified Data.ByteString.Lazy.Char8 as BSL
import qualified Data.Text as T
import qualified Text.Pandoc.Lua.Util as LuaUtil
import qualified Text.Pandoc.UTF8 as UTF8
import Text.Pandoc.Error
-- | Push the "pandoc" package to the Lua stack. Requires the `List`
-- module to be loadable.

View file

@ -0,0 +1,61 @@
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Lua.Module.Template
Copyright : Copyright © 2022 Albert Krewinkel, John MacFarlane
License : GNU GPL, version 2 or above
Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
Lua module to handle pandoc templates.
-}
module Text.Pandoc.Lua.Module.Template
( documentedModule
) where
import HsLua
import Text.Pandoc.Error (PandocError)
import Text.Pandoc.Lua.Marshal.Template (pushTemplate)
import Text.Pandoc.Lua.PandocLua (PandocLua (unPandocLua), liftPandocLua)
import Text.Pandoc.Templates
(compileTemplate, getDefaultTemplate, runWithPartials, runWithDefaultPartials)
import qualified Data.Text as T
-- | The "pandoc.template" module.
documentedModule :: Module PandocError
documentedModule = Module
{ moduleName = "pandoc.template"
, moduleDescription = T.unlines
[ "Lua functions for pandoc templates."
]
, moduleFields = []
, moduleOperations = []
, moduleFunctions = functions
}
-- | Template module functions.
functions :: [DocumentedFunction PandocError]
functions =
[ defun "compile"
### (\template mfilepath -> unPandocLua $
case mfilepath of
Just fp -> runWithPartials (compileTemplate fp template)
Nothing -> runWithDefaultPartials
(compileTemplate "templates/default" template))
<#> parameter peekText "string" "template" "template string"
<#> optionalParameter peekString "string" "templ_path" "template path"
=#> functionResult (either failLua pushTemplate) "pandoc Template"
"compiled template"
, defun "default"
### (\mformat -> unPandocLua $ do
let getFORMAT = liftPandocLua $ do
getglobal "FORMAT"
forcePeek $ peekText top `lastly` pop 1
format <- maybe getFORMAT pure mformat
getDefaultTemplate format)
<#> optionalParameter peekText "string" "writer"
"writer for which the template should be returned."
=#> functionResult pushText "string"
"string representation of the writer's default template"
]

View file

@ -26,6 +26,7 @@ import qualified HsLua.Module.Text as Text
import qualified Text.Pandoc.Lua.Module.Pandoc as Pandoc
import qualified Text.Pandoc.Lua.Module.MediaBag as MediaBag
import qualified Text.Pandoc.Lua.Module.System as System
import qualified Text.Pandoc.Lua.Module.Template as Template
import qualified Text.Pandoc.Lua.Module.Types as Types
import qualified Text.Pandoc.Lua.Module.Utils as Utils
@ -50,6 +51,7 @@ pandocPackageSearcher pkgName =
"pandoc.mediabag" -> pushModuleLoader MediaBag.documentedModule
"pandoc.path" -> pushModuleLoader Path.documentedModule
"pandoc.system" -> pushModuleLoader System.documentedModule
"pandoc.template" -> pushModuleLoader Template.documentedModule
"pandoc.types" -> pushModuleLoader Types.documentedModule
"pandoc.utils" -> pushModuleLoader Utils.documentedModule
"text" -> pushModuleLoader Text.documentedModule

View file

@ -27,6 +27,8 @@ tests =
("lua" </> "module" </> "pandoc-mediabag.lua")
, testPandocLua "pandoc.path"
("lua" </> "module" </> "pandoc-path.lua")
, testPandocLua "pandoc.template"
("lua" </> "module" </> "pandoc-template.lua")
, testPandocLua "pandoc.types"
("lua" </> "module" </> "pandoc-types.lua")
, testPandocLua "pandoc.utils"

View file

@ -0,0 +1,65 @@
local tasty = require 'tasty'
local template = require 'pandoc.template'
local assert = tasty.assert
local test = tasty.test_case
local group = tasty.test_group
return {
test('is table', function ()
assert.are_equal(type(template), 'table')
end),
group 'default' {
test('is function', function ()
assert.are_equal(type(template.default), 'function')
end),
test('returns a string for known format', function ()
assert.are_equal(
pandoc.utils.type(template.default 'json'),
'string'
)
assert.are_equal(
pandoc.utils.type(template.default 'markdown'),
'string'
)
end),
test('fails on unknown format', function ()
local success, msg = pcall(function ()
return pandoc.utils.type(template.default 'nosuchformat')
end)
assert.is_falsy(success)
end),
},
group 'compile' {
test('is function', function ()
assert.are_equal(type(template.compile), 'function')
end),
test('returns a Template', function ()
assert.are_equal(
pandoc.utils.type(template.compile('$title$')),
'pandoc Template'
)
end),
test('returns a Template', function ()
local templ_path = pandoc.path.join{'lua', 'module', 'default.test'}
assert.are_equal(
pandoc.utils.type(template.compile('${ partial() }', templ_path)),
'pandoc Template'
)
end),
test('fails if template has non-existing partial', function ()
assert.error_matches(
function () return template.compile('${ nosuchpartial() }') end,
'PandocCouldNotFindDataFileError'
)
end),
test('works with default template that uses partials', function ()
local jats_template = template.default 'jats'
assert.are_equal(type(jats_template), 'string')
assert.are_equal(
pandoc.utils.type(template.compile(jats_template)),
'pandoc Template'
)
end),
},
}

View file