aboutsummaryrefslogtreecommitdiff
path: root/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Scaffolding.hs
diff options
context:
space:
mode:
authorAlbert Krewinkel <[email protected]>2026-01-08 17:29:39 +0100
committerAlbert Krewinkel <[email protected]>2026-01-08 17:55:04 +0100
commitcb8739f5b079ad5d73be6601eb7dd62c61c533a1 (patch)
tree27b6c4ffba933c8f83ebd97cbde712276e3f020c /pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Scaffolding.hs
parent8123be654d6ece208df32afc26b4fe1629e78ffd (diff)
Lua: switch to HsLua 2.5
Diffstat (limited to 'pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Scaffolding.hs')
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Scaffolding.hs25
1 files changed, 8 insertions, 17 deletions
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Scaffolding.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Scaffolding.hs
index 45a678832..64094fbee 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Scaffolding.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Scaffolding.hs
@@ -1,7 +1,7 @@
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Lua.Module.Scaffolding
- Copyright : Copyright © 2022-2024 Albert Krewinkel, John MacFarlane
+ Copyright : Copyright © 2022-2026 Albert Krewinkel, John MacFarlane
License : GNU GPL, version 2 or above
Maintainer : Albert Krewinkel <[email protected]>
@@ -18,28 +18,20 @@ import qualified Data.Text as T
-- | The "pandoc.template" module.
documentedModule :: Module PandocError
-documentedModule = Module
- { moduleName = "pandoc.scaffolding"
- , moduleDescription = T.unlines
- [ "Scaffolding for custom writers."
- ]
- , moduleFields = [writerScaffolding]
- , moduleOperations = []
- , moduleFunctions = []
- , moduleTypeInitializers = []
- }
+documentedModule = defmodule "pandoc.scaffolding"
+ `withDescription` "Scaffolding for custom writers."
+ `withFields` [writerScaffolding]
-- | Template module functions.
writerScaffolding :: Field PandocError
-writerScaffolding = Field
- { fieldName = "Writer"
- , fieldType = "table"
- , fieldDescription = T.unlines
+writerScaffolding = deffield "Writer"
+ `withType` "table"
+ `withDescription` T.unlines
[ "An object to be used as a `Writer` function; the construct handles"
, "most of the boilerplate, expecting only render functions for all"
, "AST elements"
]
- , fieldPushValue = do
+ `withValue` do
pushWriterScaffolding
-- pretend that it's a submodule so we get better error messages
getfield registryindex loaded
@@ -50,5 +42,4 @@ writerScaffolding = Field
getfield (nth 2) "Block" *> setfield (nth 2) (submod "Writer.Block")
pop 1 -- remove "LOADED_TABLE"
- }
where submod x = moduleName documentedModule <> "." <> x