aboutsummaryrefslogtreecommitdiff
path: root/pandoc-lua-engine/src/Text/Pandoc/Lua/Module
diff options
context:
space:
mode:
Diffstat (limited to 'pandoc-lua-engine/src/Text/Pandoc/Lua/Module')
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/CLI.hs24
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Format.hs11
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Image.hs19
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/JSON.hs24
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Log.hs12
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/MediaBag.hs11
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Pandoc.hs69
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Path.hs12
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Scaffolding.hs25
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Structure.hs17
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/System.hs49
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Template.hs18
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Text.hs8
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Types.hs15
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Utils.hs13
15 files changed, 116 insertions, 211 deletions
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/CLI.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/CLI.hs
index 868112561..3d8ff2727 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/CLI.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/CLI.hs
@@ -23,20 +23,17 @@ import qualified Data.Text as T
-- | Push the pandoc.types module on the Lua stack.
documentedModule :: Module PandocError
-documentedModule = Module
- { moduleName = "pandoc.cli"
- , moduleDescription =
+documentedModule = defmodule "pandoc.cli"
+ `withDescription`
"Command line options and argument parsing."
- , moduleFields =
- [ Field
- { fieldName = "default_options"
- , fieldType = "table"
- , fieldDescription = "Default CLI options, using a JSON-like " <>
- "representation."
- , fieldPushValue = pushViaJSON defaultOpts
- }
+ `withFields`
+ [ deffield "default_options"
+ `withType` "table"
+ `withDescription`
+ "Default CLI options, using a JSON-like representation."
+ `withValue` pushViaJSON defaultOpts
]
- , moduleFunctions =
+ `withFunctions`
[ defun "parse_options"
### parseOptions
<#> parameter peekArgs "{string,...}" "args"
@@ -52,9 +49,6 @@ documentedModule = Module
, repl `since` makeVersion [3, 1, 2]
]
- , moduleOperations = []
- , moduleTypeInitializers = []
- }
where
peekArgs idx =
(,)
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Format.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Format.hs
index 1b539edfe..dbfaa93ac 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Format.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Format.hs
@@ -23,16 +23,11 @@ import qualified Data.Text as T
-- | The "pandoc.format" module.
documentedModule :: Module PandocError
-documentedModule = Module
- { moduleName = "pandoc.format"
- , moduleDescription = T.unlines
+documentedModule = defmodule "pandoc.format"
+ `withDescription` T.unlines
[ "Information about the formats supported by pandoc."
]
- , moduleFields = []
- , moduleOperations = []
- , moduleFunctions = functions
- , moduleTypeInitializers = []
- }
+ `withFunctions` functions
-- | Extension module functions.
functions :: [DocumentedFunction PandocError]
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Image.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Image.hs
index cf9f8e55d..05719994a 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Image.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Image.hs
@@ -34,22 +34,9 @@ import qualified Data.Text as T
-- | The @pandoc.image@ module specification.
documentedModule :: Module PandocError
-documentedModule = Module
- { moduleName = "pandoc.image"
- , moduleDescription = "Basic image querying functions."
- , moduleFields = fields
- , moduleFunctions = functions
- , moduleOperations = []
- , moduleTypeInitializers = []
- }
-
---
--- Fields
---
-
--- | Exported fields.
-fields :: LuaError e => [Field e]
-fields = []
+documentedModule = defmodule "pandoc.image"
+ `withDescription` "Basic image querying functions."
+ `withFunctions` functions
--
-- Functions
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/JSON.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/JSON.hs
index 2c58d0a48..0b69612b9 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/JSON.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/JSON.hs
@@ -35,15 +35,11 @@ import qualified Data.Text as T
-- | The @aeson@ module specification.
documentedModule :: Module PandocError
-documentedModule = Module
- { moduleName = "pandoc.json"
- , moduleDescription = "JSON module to work with JSON; " <>
- "based on the Aeson Haskell package."
- , moduleFields = fields
- , moduleFunctions = functions
- , moduleOperations = []
- , moduleTypeInitializers = []
- }
+documentedModule = defmodule "pandoc.json"
+ `withDescription`
+ "JSON module to work with JSON; based on the Aeson Haskell package."
+ `withFields` fields
+ `withFunctions` functions
--
-- Fields
@@ -57,12 +53,10 @@ fields =
-- | The value used to represent the JSON @null@.
null :: LuaError e => Field e
-null = Field
- { fieldName = "null"
- , fieldType = "light userdata"
- , fieldDescription = "Value used to represent the `null` JSON value."
- , fieldPushValue = pushValue Aeson.Null
- }
+null = deffield "null"
+ `withType` "light userdata"
+ `withDescription` "Value used to represent the `null` JSON value."
+ `withValue` pushValue Aeson.Null
--
-- Functions
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Log.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Log.hs
index b885cae74..f11d01640 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Log.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Log.hs
@@ -26,12 +26,11 @@ import qualified HsLua.Core.Utf8 as UTF8
-- | Push the pandoc.log module on the Lua stack.
documentedModule :: Module PandocError
-documentedModule = Module
- { moduleName = "pandoc.log"
- , moduleDescription =
+documentedModule = defmodule "pandoc.log"
+ `withDescription`
"Access to pandoc's logging system."
- , moduleFields = []
- , moduleFunctions =
+ `withFields` []
+ `withFunctions`
[ defun "info"
### (\msg -> do
-- reporting levels:
@@ -78,9 +77,6 @@ documentedModule = Module
]
`since` makeVersion [3, 2]
]
- , moduleOperations = []
- , moduleTypeInitializers = []
- }
-- | Calls the function given as the first argument, but suppresses logging.
-- Returns the list of generated log messages as the first result, and the other
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/MediaBag.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/MediaBag.hs
index 0e21c6340..412131560 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/MediaBag.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/MediaBag.hs
@@ -37,9 +37,8 @@ import qualified Text.Pandoc.MediaBag as MB
-- MediaBag submodule
--
documentedModule :: Module PandocError
-documentedModule = Module
- { moduleName = "pandoc.mediabag"
- , moduleDescription = T.unlines
+documentedModule = Lua.defmodule "pandoc.mediabag"
+ `Lua.withDescription` T.unlines
[ "The `pandoc.mediabag` module allows accessing pandoc's media"
, "storage. The \"media bag\" is used when pandoc is called with the"
, "`--extract-media` or (for HTML only) `--embed-resources` option."
@@ -50,8 +49,7 @@ documentedModule = Module
, ""
, " local mb = require 'pandoc.mediabag'"
]
- , moduleFields = []
- , moduleFunctions =
+ `Lua.withFunctions`
[ delete `since` makeVersion [2,7,3]
, empty `since` makeVersion [2,7,3]
, fetch `since` makeVersion [2,0]
@@ -63,9 +61,6 @@ documentedModule = Module
, make_data_uri `since` makeVersion [3,7,1]
, write `since` makeVersion [3,0]
]
- , moduleOperations = []
- , moduleTypeInitializers = []
- }
-- | Delete a single item from the media bag.
delete :: DocumentedFunction PandocError
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 9e6d033d4..cf4325b17 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Pandoc.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Pandoc.hs
@@ -63,17 +63,15 @@ import qualified Data.Text as T
import qualified Text.Pandoc.UTF8 as UTF8
documentedModule :: Module PandocError
-documentedModule = Module
- { moduleName = "pandoc"
- , moduleDescription = T.unlines
+documentedModule = defmodule "pandoc"
+ `withDescription` T.unlines
[ "Fields and functions for pandoc scripts; includes constructors for"
, "document tree elements, functions to parse text in a given"
, "format, and functions to filter and modify a subtree."
]
- , moduleFields = readersField : writersField :
+ `withFields` readersField : writersField :
stringConstants ++ [inlineField, blockField]
- , moduleOperations = []
- , moduleFunctions = mconcat
+ `withFunctions` mconcat
[ [mkPandoc, mkMeta]
, metaValueConstructors
, blockConstructors
@@ -83,25 +81,20 @@ documentedModule = Module
, otherConstructors
, functions
]
- , moduleTypeInitializers =
- [ initType typePandoc
- , initType typeBlock
- , initType typeInline
- ]
- }
+ `associateType` typePandoc
+ `associateType` typeBlock
+ `associateType` typeInline
-- | Set of input formats accepted by @read@.
readersField :: Field PandocError
-readersField = Field
- { fieldName = "readers"
- , fieldType = "table"
- , fieldDescription = T.unlines
+readersField = deffield "readers"
+ `withType` "table"
+ `withDescription` T.unlines
[ "Set of formats that pandoc can parse. All keys in this table can"
, "be used as the `format` value in `pandoc.read`."
]
- , fieldPushValue = pushKeyValuePairs pushText (pushText . readerType)
+ `withValue` pushKeyValuePairs pushText (pushText . readerType)
(readers @PandocLua)
- }
where
readerType = \case
TextReader {} -> "text"
@@ -109,16 +102,14 @@ readersField = Field
-- | Set of input formats accepted by @write@.
writersField :: Field PandocError
-writersField = Field
- { fieldName = "writers"
- , fieldType = "table"
- , fieldDescription = T.unlines
+writersField = deffield "writers"
+ `withType` "table"
+ `withDescription` T.unlines
[ "Set of formats that pandoc can generate. All keys in this table"
, "can be used as the `format` value in `pandoc.write`."
]
- , fieldPushValue = pushKeyValuePairs pushText (pushText . writerType)
+ `withValue` pushKeyValuePairs pushText (pushText . writerType)
(writers @PandocLua)
- }
where
writerType = \case
TextWriter {} -> "text"
@@ -126,25 +117,21 @@ writersField = Field
-- | Inline table field
inlineField :: Field PandocError
-inlineField = Field
- { fieldName = "Inline"
- , fieldType = "table"
- , fieldDescription = "Inline constructors, nested under 'constructors'."
+inlineField = deffield "Inline"
+ `withType` "table"
+ `withDescription` "Inline constructors, nested under 'constructors'."
-- the nesting happens for historical reasons and should probably be
-- changed.
- , fieldPushValue = pushWithConstructorsSubtable inlineConstructors
- }
+ `withValue` pushWithConstructorsSubtable inlineConstructors
-- | @Block@ module field
blockField :: Field PandocError
-blockField = Field
- { fieldName = "Block"
- , fieldType = "table"
- , fieldDescription = "Inline constructors, nested under 'constructors'."
+blockField = deffield "Block"
+ `withType` "table"
+ `withDescription` "Inline constructors, nested under 'constructors'."
-- the nesting happens for historical reasons and should probably be
-- changed.
- , fieldPushValue = pushWithConstructorsSubtable blockConstructors
- }
+ `withValue` pushWithConstructorsSubtable blockConstructors
pushWithConstructorsSubtable :: [DocumentedFunction PandocError]
-> LuaE PandocError ()
@@ -222,12 +209,10 @@ stringConstants =
, constrs (Proxy @Alignment)
, constrs (Proxy @CitationMode)
]
- toField s = Field
- { fieldName = T.pack s
- , fieldType = "string"
- , fieldDescription = T.pack s
- , fieldPushValue = pushString s
- }
+ toField s = deffield (Name $ UTF8.fromString s)
+ `withType` "string"
+ `withDescription` T.pack s
+ `withValue` pushString s
in map toField nullaryConstructors
functions :: [DocumentedFunction PandocError]
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Path.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Path.hs
index 1d2169976..efe00e03c 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Path.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Path.hs
@@ -22,14 +22,13 @@ import qualified HsLua.Module.System as MSystem
-- | Push the pandoc.system module on the Lua stack.
documentedModule :: forall e. LuaError e => Module e
-documentedModule = Module
- { moduleName = "pandoc.path"
- , moduleDescription = moduleDescription @e MPath.documentedModule
- , moduleFields =
+documentedModule = defmodule "pandoc.path"
+ `withDescription` moduleDescription @e MPath.documentedModule
+ `withFields`
[ MPath.separator
, MPath.search_path_separator
]
- , moduleFunctions =
+ `withFunctions`
[ MPath.directory `since` v[2,12]
, MSystem.exists `since` v[3,7,1]
, MPath.filename `since` v[2,12]
@@ -43,8 +42,5 @@ documentedModule = Module
, MPath.split_search_path `since` v[2,12]
, MPath.treat_strings_as_paths `since` v[2,12]
]
- , moduleOperations = []
- , moduleTypeInitializers = []
- }
where
v = makeVersion
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
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Structure.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Structure.hs
index a15b1fdc3..903c85a15 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Structure.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Structure.hs
@@ -2,7 +2,7 @@
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Lua.Module.Structure
- Copyright : © 2023-2025 Albert Krewinkel <[email protected]>
+ Copyright : © 2023-2026 Albert Krewinkel <[email protected]>
License : GPL-2.0-or-later
Maintainer : Albert Krewinkel <[email protected]>
@@ -17,11 +17,11 @@ import Data.Default (Default (..))
import Data.Maybe (fromMaybe)
import Data.Version (makeVersion)
import HsLua ( DocumentedFunction, LuaError, Module (..), Peeker
- , (###), (<#>), (=#>), (#?)
+ , (###), (<#>), (=#>), (#?), defmodule
, defun, functionResult, getfield, isnil, lastly, liftLua
, opt, liftPure, parameter , peekBool, peekIntegral
, peekFieldRaw, peekSet, peekText, pop, pushIntegral
- , pushText, since, top )
+ , pushText, since, top, withDescription, withFunctions )
import Text.Pandoc.Chunks ( ChunkedDoc (..), PathTemplate (..)
, tocToList, splitIntoChunks )
import Text.Pandoc.Definition (Pandoc (..), Block)
@@ -41,22 +41,17 @@ import qualified Text.Pandoc.Shared as Shared
-- | Push the pandoc.structure module on the Lua stack.
documentedModule :: Module PandocError
-documentedModule = Module
- { moduleName = "pandoc.structure"
- , moduleDescription =
+documentedModule = defmodule "pandoc.structure"
+ `withDescription`
"Access to the higher-level document structure, including " <>
"hierarchical sections and the table of contents."
- , moduleFields = []
- , moduleFunctions =
+ `withFunctions`
[ make_sections `since` makeVersion [3,0]
, slide_level `since` makeVersion [3,0]
, split_into_chunks `since` makeVersion [3,0]
, table_of_contents `since` makeVersion [3,0]
, unique_identifier `since` makeVersion [3,8]
]
- , moduleOperations = []
- , moduleTypeInitializers = []
- }
make_sections :: LuaError e => DocumentedFunction e
make_sections = defun "make_sections"
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/System.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/System.hs
index c6a124166..75d1ac3ba 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/System.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/System.hs
@@ -26,34 +26,27 @@ import qualified HsLua.Module.System as MSys
-- | Push the pandoc.system module on the Lua stack.
documentedModule :: forall e. LuaError e => Module e
-documentedModule = Module
- { moduleName = "pandoc.system"
- , moduleDescription = moduleDescription @e MSys.documentedModule
- , moduleFields =
- [ arch
- , os
+documentedModule = defmodule "pandoc.system"
+ `withDescription` moduleDescription @e MSys.documentedModule
+ `withFields` [arch, os]
+ `withFunctions`
+ [ cputime `since` v[3,1,1]
+ , setName cmd "command" `since` v[3,7,1]
+ , setName cp "copy" `since` v[3,7,1]
+ , setName env "environment" `since` v[2,7,3]
+ , setName getwd "get_working_directory" `since` v[2,8]
+ , setName ls "list_directory" `since` v[2,19]
+ , setName mkdir "make_directory" `since` v[2,19]
+ , read_file `since` v[3,7,1]
+ , rename `since` v[3,7,1]
+ , setName rm "remove" `since` v[3,7,1]
+ , setName rmdir "remove_directory" `since` v[2,19]
+ , times `since` v[3,7,1]
+ , setName with_env "with_environment" `since` v[2,7,3]
+ , setName with_tmpdir "with_temporary_directory" `since` v[2,8]
+ , setName with_wd "with_working_directory" `since` v[2,7,3]
+ , write_file `since` v[3,7,1]
+ , xdg `since` v[3,7,1]
]
- , moduleFunctions =
- [ cputime `since` v[3,1,1]
- , setName "command" cmd `since` v[3,7,1]
- , setName "copy" cp `since` v[3,7,1]
- , setName "environment" env `since` v[2,7,3]
- , setName "get_working_directory" getwd `since` v[2,8]
- , setName "list_directory" ls `since` v[2,19]
- , setName "make_directory" mkdir `since` v[2,19]
- , read_file `since` v[3,7,1]
- , rename `since` v[3,7,1]
- , setName "remove" rm `since` v[3,7,1]
- , setName "remove_directory" rmdir `since` v[2,19]
- , times `since` v[3,7,1]
- , setName "with_environment" with_env `since` v[2,7,3]
- , setName "with_temporary_directory" with_tmpdir `since` v[2,8]
- , setName "with_working_directory" with_wd `since` v[2,7,3]
- , write_file `since` v[3,7,1]
- , xdg `since` v[3,7,1]
- ]
- , moduleOperations = []
- , moduleTypeInitializers = []
- }
where
v = makeVersion
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 a9138bbb0..a1ff8da5d 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Template.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Template.hs
@@ -1,8 +1,8 @@
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Lua.Module.Template
- Copyright : Copyright © 2022-2024 Albert Krewinkel, John MacFarlane
- License : GNU GPL, version 2 or above
+ Copyright : Copyright © 2022-2026 Albert Krewinkel, John MacFarlane
+ License : GPL-2.0-or-later
Maintainer : Albert Krewinkel <[email protected]>
Lua module to handle pandoc templates.
@@ -28,16 +28,10 @@ import qualified Data.Text as T
-- | The "pandoc.template" module.
documentedModule :: Module PandocError
-documentedModule = Module
- { moduleName = "pandoc.template"
- , moduleDescription = T.unlines
- [ "Handle pandoc templates."
- ]
- , moduleFields = []
- , moduleOperations = []
- , moduleFunctions = functions
- , moduleTypeInitializers = [initType typeTemplate]
- }
+documentedModule = defmodule "pandoc.template"
+ `withDescription` "Handle pandoc templates."
+ `withFunctions` functions
+ `associateType` typeTemplate
-- | Template module functions.
functions :: [DocumentedFunction PandocError]
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Text.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Text.hs
index 8c43df526..f40cc001e 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Text.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Text.hs
@@ -22,9 +22,8 @@ import qualified HsLua.Module.Text as TM
-- | The @aeson@ module specification.
documentedModule :: Module PandocError
-documentedModule = TM.documentedModule
- { moduleName = "pandoc.text"
- , moduleFunctions =
+documentedModule = defmodule "pandoc.text"
+ `withFunctions`
[ TM.fromencoding `since` v[3,0]
, TM.len `since` v[2,0,3]
, TM.lower `since` v[2,0,3]
@@ -35,7 +34,7 @@ documentedModule = TM.documentedModule
, TM.toencoding `since` v[3,0]
, TM.upper `since` v[2,0,3]
]
- , moduleDescription = T.unlines
+ `withDescription` T.unlines
[ "UTF-8 aware text manipulation functions, implemented in Haskell."
, ""
, "The text module can also be loaded under the name `text`, although"
@@ -49,7 +48,6 @@ documentedModule = TM.documentedModule
, "end"
, "```"
]
- }
where
v = makeVersion
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Types.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Types.hs
index a9a29e869..c044685da 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Types.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Types.hs
@@ -15,19 +15,19 @@ module Text.Pandoc.Lua.Module.Types
import Data.Version (makeVersion)
import HsLua ( Module (..), (###), (<#>), (=#>)
- , defun, functionResult, parameter, since)
+ , defmodule, defun, functionResult, parameter, since
+ , withDescription, withFunctions
+ )
import HsLua.Module.Version (peekVersionFuzzy, pushVersion)
import Text.Pandoc.Error (PandocError)
import Text.Pandoc.Lua.PandocLua ()
-- | Push the pandoc.types module on the Lua stack.
documentedModule :: Module PandocError
-documentedModule = Module
- { moduleName = "pandoc.types"
- , moduleDescription =
+documentedModule = defmodule "pandoc.types"
+ `withDescription`
"Constructors for types that are not part of the pandoc AST."
- , moduleFields = []
- , moduleFunctions =
+ `withFunctions`
[ defun "Version"
### return
<#> parameter peekVersionFuzzy "string|number|{integer,...}|Version"
@@ -40,6 +40,3 @@ documentedModule = Module
=#> functionResult pushVersion "Version" "New Version object."
`since` makeVersion [2,7,3]
]
- , moduleOperations = []
- , moduleTypeInitializers = []
- }
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Utils.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Utils.hs
index a19f353b5..d4b7cea08 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Utils.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Utils.hs
@@ -4,7 +4,7 @@
{-# LANGUAGE TypeApplications #-}
{- |
Module : Text.Pandoc.Lua.Module.Utils
- Copyright : Copyright © 2017-2024 Albert Krewinkel
+ Copyright : Copyright © 2017-2026 Albert Krewinkel
License : GNU GPL, version 2 or above
Maintainer : Albert Krewinkel <[email protected]>
@@ -44,16 +44,12 @@ import qualified Text.Pandoc.Writers.Shared as Shared
-- | Push the "pandoc.utils" module to the Lua stack.
documentedModule :: Module PandocError
-documentedModule = Module
- { moduleName = "pandoc.utils"
- , moduleDescription = T.unlines
+documentedModule = defmodule "pandoc.utils"
+ `withDescription` T.unlines
[ "This module exposes internal pandoc functions and utility"
, "functions."
]
- , moduleFields = []
- , moduleOperations = []
- , moduleTypeInitializers = []
- , moduleFunctions =
+ `withFunctions`
[ blocks_to_inlines `since` v[2,2,3]
, citeproc `since` v[2,19,1]
, equals `since` v[2,5]
@@ -77,7 +73,6 @@ documentedModule = Module
=#> functionResult pushVersion "Version" "new Version object"
#? "Creates a Version object."
]
- }
where
v = makeVersion