diff options
| author | Albert Krewinkel <[email protected]> | 2026-01-08 17:29:39 +0100 |
|---|---|---|
| committer | Albert Krewinkel <[email protected]> | 2026-01-08 17:55:04 +0100 |
| commit | cb8739f5b079ad5d73be6601eb7dd62c61c533a1 (patch) | |
| tree | 27b6c4ffba933c8f83ebd97cbde712276e3f020c /pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Structure.hs | |
| parent | 8123be654d6ece208df32afc26b4fe1629e78ffd (diff) | |
Lua: switch to HsLua 2.5
Diffstat (limited to 'pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Structure.hs')
| -rw-r--r-- | pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Structure.hs | 17 |
1 files changed, 6 insertions, 11 deletions
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" |
