aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--doc/lua-filters.md42
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Structure.hs45
-rw-r--r--pandoc-lua-engine/test/lua/module/pandoc-structure.lua24
3 files changed, 107 insertions, 4 deletions
diff --git a/doc/lua-filters.md b/doc/lua-filters.md
index bddd98692..bb55c6efe 100644
--- a/doc/lua-filters.md
+++ b/doc/lua-filters.md
@@ -5671,6 +5671,48 @@ Returns:
*Since: 3.0*
+### unique_identifier {#pandoc.structure.unique_identifier}
+
+`unique_identifier (inlines[, used[, exts]])`
+
+Generates a unique identifier from a list of inlines, similar to
+what's generated by the `auto_identifiers` extension.
+
+The method used to generated identifiers can be modified through
+`ext`, which is a list of format extensions.
+
+It can be used to generate IDs similar to what the
+`auto_identifiers` extension provides.
+
+Example:
+
+ local used_ids = {}
+ function Header (h)
+ local id =
+ pandoc.structure.unique_identifier(h.content, used_ids)
+ used_ids[id] = true
+ h.identifier = id
+ return h
+ end
+
+Parameters:
+
+`inlines`
+: base for identifier ([Inlines])
+
+`used`
+: set of identifiers (string keys, boolean values) that have
+ already been used. (table)
+
+`exts`
+: list of format extensions ({string,\...})
+
+Returns:
+
+- unique identifier (string)
+
+*Since: 3.8*
+
<!-- END: AUTOGENERATED CONTENT -->
<!-- BEGIN: AUTOGENERATED CONTENT for module pandoc.system -->
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 afff459c5..a15b1fdc3 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 Albert Krewinkel
+ Copyright : © 2023-2025 Albert Krewinkel <[email protected]>
License : GPL-2.0-or-later
Maintainer : Albert Krewinkel <[email protected]>
@@ -20,15 +20,17 @@ import HsLua ( DocumentedFunction, LuaError, Module (..), Peeker
, (###), (<#>), (=#>), (#?)
, defun, functionResult, getfield, isnil, lastly, liftLua
, opt, liftPure, parameter , peekBool, peekIntegral
- , peekFieldRaw, peekText, pop, pushIntegral, since, top )
+ , peekFieldRaw, peekSet, peekText, pop, pushIntegral
+ , pushText, since, top )
import Text.Pandoc.Chunks ( ChunkedDoc (..), PathTemplate (..)
, tocToList, splitIntoChunks )
import Text.Pandoc.Definition (Pandoc (..), Block)
import Text.Pandoc.Error (PandocError)
import Text.Pandoc.Lua.PandocLua ()
-import Text.Pandoc.Lua.Marshal.AST ( peekBlocksFuzzy, peekPandoc
- , pushBlock, pushBlocks )
+import Text.Pandoc.Lua.Marshal.AST ( peekBlocksFuzzy, peekInlinesFuzzy
+ , peekPandoc, pushBlock, pushBlocks )
import Text.Pandoc.Lua.Marshal.Chunks
+import Text.Pandoc.Lua.Marshal.Format (peekExtensions)
import Text.Pandoc.Lua.Marshal.WriterOptions ( peekWriterOptions )
import Text.Pandoc.Options (WriterOptions (writerTOCDepth,
writerNumberSections))
@@ -50,6 +52,7 @@ documentedModule = Module
, 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 = []
@@ -198,6 +201,40 @@ table_of_contents = defun "table_of_contents"
(Left <$> peekBodyBlocks idx) <|>
(Right . chunkedTOC <$> peekChunkedDoc idx)
+-- | Generate a unique ID from a list of inlines.
+unique_identifier :: LuaError e => DocumentedFunction e
+unique_identifier = defun "unique_identifier"
+ ### (\inlns mUsedIdents mExts -> do
+ let usedIdents = fromMaybe mempty mUsedIdents
+ let exts = fromMaybe mempty mExts
+ pure $ Shared.uniqueIdent exts inlns usedIdents)
+ <#> parameter peekInlinesFuzzy "Inlines" "inlines" "base for identifier"
+ <#> opt (parameter (peekSet peekText) "table" "used"
+ "set of identifiers (string keys, boolean values) that\
+ \ have already been used.")
+ <#> opt (parameter peekExtensions "{string,...}" "exts"
+ "list of format extensions")
+ =#> functionResult pushText "string" "unique identifier"
+ #? "Generates a unique identifier from a list of inlines, similar to\
+ \ what's generated by the `auto_identifiers` extension.\n\
+ \\n\
+ \ The method used to generated identifiers can be modified through\
+ \ `ext`, which is a list of format extensions.\n\
+ \\n\
+ \ It can be used to generate IDs similar to what the `auto_identifiers`\
+ \ extension provides.\n\
+ \\n\
+ \ Example:\n\
+ \\n\
+ \ local used_ids = {}\n\
+ \ function Header (h)\n\
+ \ local id =\n\
+ \ pandoc.structure.unique_identifier(h.content, used_ids)\n\
+ \ used_ids[id] = true\n\
+ \ h.identifier = id\n\
+ \ return h\n\
+ \ end"
+
-- | Retrieves the body blocks of a 'Pandoc' object or from a list of
-- blocks.
peekBodyBlocks :: LuaError e => Peeker e [Block]
diff --git a/pandoc-lua-engine/test/lua/module/pandoc-structure.lua b/pandoc-lua-engine/test/lua/module/pandoc-structure.lua
index ff2abba22..159e6e27b 100644
--- a/pandoc-lua-engine/test/lua/module/pandoc-structure.lua
+++ b/pandoc-lua-engine/test/lua/module/pandoc-structure.lua
@@ -136,4 +136,28 @@ return {
)
end),
},
+ group 'unique_identifier' {
+ test('returns an identifier based on the input', function ()
+ local inlines = pandoc.Inlines{pandoc.Emph{'This'}, ' is nice'}
+ local id = structure.unique_identifier(inlines)
+ assert.are_equal('this-is-nice', id)
+ end),
+ test('respects the list of used IDs', function ()
+ local inlines = pandoc.Inlines('Hello, World!')
+ local used = {['hello-world'] = true}
+ local id = structure.unique_identifier(inlines, used)
+ assert.are_equal('hello-world-1', id)
+ end),
+ test('defaults to pandoc Markdown identifiers', function ()
+ local inlines = pandoc.Inlines('Mr. Jones')
+ local id = structure.unique_identifier(inlines, {})
+ assert.are_equal('mr.-jones', id)
+ end),
+ test('can generate gfm identifiers', function ()
+ local inlines = pandoc.Inlines('Mr. Jones')
+ local exts = {'gfm_auto_identifiers'}
+ local id = structure.unique_identifier(inlines, {}, exts)
+ assert.are_equal('mr-jones', id)
+ end),
+ }
}