aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorAlbert Krewinkel <[email protected]>2026-01-15 09:59:58 +0100
committerGitHub <[email protected]>2026-01-15 09:59:58 +0100
commit9219a313e986c43eabcfb12c78a900c4439a9937 (patch)
treec24c3293809b8c5ad21d714c76d5b0a9dfe60527
parentd14dee0dc2dd8d0d929d695feee18588aa4707a9 (diff)
Lua: add function `pandoc.utils.documentation` (#11383)
Closes #10999. This is now used to generate much of the Lua API documentation.
-rw-r--r--doc/lua-filters.md99
-rw-r--r--pandoc-lua-engine/pandoc-lua-engine.cabal1
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Documentation.hs187
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Init.hs2
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/MediaBag.hs5
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Path.hs2
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Utils.hs48
-rw-r--r--tools/update-lua-module-docs.lua49
8 files changed, 320 insertions, 73 deletions
diff --git a/doc/lua-filters.md b/doc/lua-filters.md
index 2c82447f9..39e5988fc 100644
--- a/doc/lua-filters.md
+++ b/doc/lua-filters.md
@@ -4163,7 +4163,7 @@ Parameters:
Returns:
-- ([Inlines])
+- ([Inlines])
*Since: 2.2.3*
@@ -4193,6 +4193,24 @@ Returns:
*Since: 2.19.1*
+### documentation {#pandoc.utils.documentation}
+
+`documentation (object[, format])`
+
+Parameters:
+
+`object`
+: Retrieve documentation for this object (any)
+
+`format`
+: result format (string\|table)
+
+Returns:
+
+- rendered documentation (string\|[Blocks])
+
+*Since: 3.8.4*
+
### equals {#pandoc.utils.equals}
`equals (element1, element2)`
@@ -4207,10 +4225,10 @@ operator instead.
Parameters:
`element1`
-: (any)
+: (any)
`element2`
-: (any)
+: (any)
Returns:
@@ -4237,7 +4255,7 @@ Usage:
Parameters:
`simple_tbl`
-: ([SimpleTable])
+: ([SimpleTable])
Returns:
@@ -4264,8 +4282,7 @@ Parameters:
attribute containing the section number. (boolean)
`baselevel`
-: shift top-level headings to this level
- ([integer]{unknown-type="integer"}\|nil)
+: shift top-level headings to this level (integer\|nil)
`blocks`
: list of blocks to process ([Blocks])
@@ -4292,8 +4309,7 @@ Parameters:
Returns:
-- normalized date, or nil if normalization failed. ([string or
- nil]{unknown-type="string or nil"})
+- normalized date, or nil if normalization failed. (string\|nil)
*Since: 2.0.6*
@@ -4389,7 +4405,7 @@ Computes the SHA1 hash of the given string input.
Parameters:
`input`
-: (string)
+: (string)
Returns:
@@ -4407,8 +4423,8 @@ string with all formatting removed.
Parameters:
`element`
-: some pandoc AST element ([AST
- element]{unknown-type="AST element"})
+: some pandoc AST element
+ ([Pandoc]\|[Block]\|[Inline]\|[Caption]\|[Cell]\|[MetaValue])
Returns:
@@ -4431,8 +4447,7 @@ Usage:
Parameters:
`n`
-: positive integer below 4000
- ([integer]{unknown-type="integer"})
+: positive integer below 4000 (integer)
Returns:
@@ -4509,8 +4524,8 @@ Creates a Version object.
Parameters:
`v`
-: version description ([version string, list of integers, or
- integer]{unknown-type="version string, list of integers, or integer"})
+: version description
+ ([Version]\|string\|{integer,\...}\|number)
Returns:
@@ -4583,6 +4598,7 @@ Returns:
- The entry's MIME type, or `nil` if the file was not found.
(string)
+
- Contents of the file, or `nil` if the file was not found.
(string)
@@ -4630,7 +4646,8 @@ Parameters:
: filename and path relative to the output folder. (string)
`mimetype`
-: the item's MIME type; omit if unknown or unavailable. (string)
+: the item's MIME type; use `nil` if the MIME type is unknown or
+ unavailable. (string\|nil)
`contents`
: the binary contents of the file. (string)
@@ -4714,6 +4731,7 @@ Returns:
- The entry's MIME type, or nil if the file was not found.
(string)
+
- Contents of the file, or nil if the file was not found. (string)
*Since: 2.0*
@@ -5044,8 +5062,7 @@ Parameters:
Returns:
-- all extensions supported for `format`
- ([FormatExtensions]{unknown-type="FormatExtensions"})
+- all extensions supported for `format` ([FormatExtensions])
*Since: 3.0*
@@ -5064,8 +5081,7 @@ Parameters:
Returns:
-- default extensions enabled for `format`
- ([FormatExtensions]{unknown-type="FormatExtensions"})
+- default extensions enabled for `format` ([FormatExtensions])
*Since: 3.0*
@@ -5516,6 +5532,7 @@ Parameters:
Returns:
- filepath without extension (string)
+
- extension or empty string (string)
*Since: 2.12*
@@ -5616,7 +5633,7 @@ Parameters:
Returns:
-- slide level ([integer]{unknown-type="integer"})
+- slide level (integer)
*Since: 3.0*
@@ -5665,7 +5682,7 @@ Parameters:
Returns:
-- ([ChunkedDoc])
+- ([ChunkedDoc])
*Since: 3.0*
@@ -5765,7 +5782,7 @@ versions and on different platforms.
Returns:
-- CPU time in picoseconds ([integer]{unknown-type="integer"})
+- CPU time in picoseconds (integer)
*Since: 3.1.1*
@@ -5793,8 +5810,10 @@ Parameters:
Returns:
- exit code -- `false` on success, an integer otherwise
- ([integer]{unknown-type="integer"}\|boolean)
+ (integer\|boolean)
+
- stdout (string)
+
- stderr (string)
*Since: 3.7.1*
@@ -5971,6 +5990,7 @@ Parameters:
Returns:
- time at which the file or directory was last modified (table)
+
- time at which the file or directory was last accessed (table)
*Since: 3.7.1*
@@ -6106,7 +6126,10 @@ Returns:
<!-- END: AUTOGENERATED CONTENT -->
-<!-- BEGIN: AUTOGENERATED CONTENT for module pandoc.layout -->
+<!-- Auto-generation temporarily disabled; needs updates in the documenation
+renderer and in `hslua-packaging`. -->
+
+<!-- BEGIN DISABLED: AUTOGENERATED CONTENT for module pandoc.layout -->
# Module pandoc.layout
@@ -6822,6 +6845,7 @@ Scaffolding for custom writers.
An object to be used as a `Writer` function; the construct handles
most of the boilerplate, expecting only render functions for all
AST elements (table)
+
<!-- END: AUTOGENERATED CONTENT -->
<!-- BEGIN: AUTOGENERATED CONTENT for module pandoc.text -->
@@ -6885,7 +6909,7 @@ Parameters:
Returns:
-- length ([integer]{unknown-type="integer"}\|string)
+- length (integer\|string)
*Since: 2.0.3*
@@ -6936,10 +6960,10 @@ Parameters:
: UTF-8 string (string)
`i`
-: substring start position ([integer]{unknown-type="integer"})
+: substring start position (integer)
`j`
-: substring end position ([integer]{unknown-type="integer"})
+: substring end position (integer)
Returns:
@@ -7165,7 +7189,7 @@ Returns:
## Types {#pandoc.template-types}
-### Template {#type-pandoc.Template}
+### Template {#type-pandoc.template.Template}
<!-- END: AUTOGENERATED CONTENT -->
@@ -7186,7 +7210,7 @@ Parameters:
`version_specifier`
: A version string like `'2.7.3'`, a Lua number like `2.0`, a
list of integers like `{2,7,3}`, or a Version object.
- (string\|number\|{[integer]{unknown-type="integer"},\...}\|[Version])
+ (string\|number\|{integer,\...}\|[Version])
Returns:
@@ -7196,7 +7220,9 @@ Returns:
<!-- END: AUTOGENERATED CONTENT -->
-<!-- BEGIN: AUTOGENERATED CONTENT for module pandoc.zip -->
+<!-- Disabled due to limitations in the current documentation
+ renderer. -->
+<!-- BEGIN DISABLED: AUTOGENERATED CONTENT for module pandoc.zip -->
# Module pandoc.zip
@@ -7255,7 +7281,7 @@ Parameters:
: uncompressed contents (string)
`modtime`
-: modification time ([integer]{unknown-type="integer"})
+: modification time (integer)
Returns:
@@ -7272,7 +7298,7 @@ Generates a ZipEntry from a file or directory.
Parameters:
`filepath`
-: (string)
+: (string)
`opts`
: zip options (table)
@@ -7399,7 +7425,9 @@ Returns:
- link target if entry represents a symbolic link (string\|nil)
-<!-- END: AUTOGENERATED CONTENT -->
+[zip.Entry]: #type-pandoc.zip.Entry
+[zip.Archive]: #type-pandoc.zip.Archive
+<!-- END DISABLED: AUTOGENERATED CONTENT -->
<!-- BEGIN: GENERATED REFERENCE LINKS -->
@@ -7428,6 +7456,7 @@ Returns:
[Table]: #type-table
[Version]: #type-version
[`list`]: #pandoc.mediabag.list
+ [FormatExtensions]: #FormatExtensions
[WriterOptions]: #type-writeroptions
[null]: #pandoc.json.null
[this blog post]: http://neilmitchell.blogspot.co.uk/2015/10/filepaths-are-subtle-symlinks-are-hard.html
@@ -7435,5 +7464,3 @@ Returns:
[XDG Base Directory Specification]: https://specifications.freedesktop.org/basedir-spec/latest/
[Doc]: #type-doc
[Template]: #type-template
- [zip.Entry]: #type-pandoc.zip.Entry
- [zip.Archive]: #type-pandoc.zip.Archive
diff --git a/pandoc-lua-engine/pandoc-lua-engine.cabal b/pandoc-lua-engine/pandoc-lua-engine.cabal
index 1086c2db8..cb35943f6 100644
--- a/pandoc-lua-engine/pandoc-lua-engine.cabal
+++ b/pandoc-lua-engine/pandoc-lua-engine.cabal
@@ -69,6 +69,7 @@ library
hs-source-dirs: src
exposed-modules: Text.Pandoc.Lua
other-modules: Text.Pandoc.Lua.Custom
+ , Text.Pandoc.Lua.Documentation
, Text.Pandoc.Lua.Engine
, Text.Pandoc.Lua.Filter
, Text.Pandoc.Lua.Global
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Documentation.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Documentation.hs
new file mode 100644
index 000000000..833d57603
--- /dev/null
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Documentation.hs
@@ -0,0 +1,187 @@
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE RankNTypes #-}
+{- |
+ Module : Text.Pandoc.Lua.Documentation
+ Copyright : Copyright © 2026 Albert Krewinkel
+ License : GPL-2.0-or-later
+ Maintainer : Albert Krewinkel <[email protected]>
+
+Render Lua documentation
+-}
+module Text.Pandoc.Lua.Documentation
+ ( renderDocumentation
+ ) where
+
+import Data.Default (def)
+import Data.List (intersperse)
+import Data.Sequence (Seq ((:|>)))
+import Data.Version (showVersion)
+import HsLua as Lua
+import Text.Pandoc.Class (runPure)
+import Text.Pandoc.Definition (Pandoc (Pandoc))
+import Text.Pandoc.Extensions (extensionsFromList, Extension (..))
+import Text.Pandoc.Options (ReaderOptions (readerExtensions))
+import Text.Pandoc.Readers (readCommonMark)
+import Text.Pandoc.Shared (compactify)
+import Text.Pandoc.Walk (walk)
+
+import qualified Data.Text as T
+import qualified Text.Pandoc.Builder as B
+import qualified Text.Pandoc.UTF8 as UTF8
+
+-- | Render the documentation object as pandoc Blocks
+renderDocumentation :: DocumentationObject -> B.Blocks
+renderDocumentation = \case
+ DocObjectFunction fn -> renderFunctionDoc Nothing fn
+ DocObjectModule mdl -> renderModuleDoc mdl
+ DocObjectType tp -> renderTypeDoc Nothing tp
+
+renderTypeDoc :: Maybe T.Text -> TypeDoc -> B.Blocks
+renderTypeDoc mbmodname td = mconcat
+ [ B.headerWith (ident, [], []) 1 (B.str $ typeDocName td)
+ , parseCommonMark $ typeDocDescription td
+ , if null $ typeDocMethods td
+ then mempty
+ else
+ B.header 2 "Methods" <>
+ (shiftHeadings 2 . mconcat . map (renderFunctionDoc Nothing) $
+ typeDocMethods td)
+ ]
+ where
+ ident = case mbmodname of
+ Just modname -> mconcat [ "type-", modname, ".", typeDocName td ]
+ Nothing -> mconcat [ "type-", typeDocName td ]
+
+-- Shift headings
+shiftHeadings :: Int -> B.Blocks -> B.Blocks
+shiftHeadings incr blks = flip walk blks $ \case
+ B.Header level attr inner -> B.Header (level + incr) attr inner
+ x -> x
+
+renderModuleDoc :: ModuleDoc -> B.Blocks
+renderModuleDoc moddoc =
+ let modname = moduleDocName moddoc
+ in mconcat
+ [ B.headerWith ("module-" <> modname, [], []) 1
+ (B.str $ "Module " <> modname)
+ , parseCommonMark (moduleDocDescription moddoc)
+ , if null (moduleDocFields moddoc)
+ then mempty
+ else
+ let ident = modname <> "-fields"
+ in B.headerWith (ident, [], []) 2 (B.str "Fields") <>
+ shiftHeadings 0 (mconcat (map (renderFieldDoc modname)
+ (moduleDocFields moddoc)))
+ , if null (moduleDocFunctions moddoc)
+ then mempty
+ else
+ let ident = modname <> "-functions"
+ in B.headerWith (ident, [], []) 2 (B.str "Functions") <>
+ (shiftHeadings 2 . mconcat . map (renderFunctionDoc $ Just modname) $
+ moduleDocFunctions moddoc)
+ , if null (moduleDocTypes moddoc)
+ then mempty
+ else
+ let ident = modname <> "-types"
+ in B.headerWith (ident, [], []) 2 (B.str "Types") <>
+ (shiftHeadings 2 . mconcat . map (renderTypeDoc $ Just modname) .
+ reverse $ moduleDocTypes moddoc)
+ ]
+
+parseCommonMark :: T.Text -> B.Blocks
+parseCommonMark txt =
+ let exts = extensionsFromList
+ [ Ext_wikilinks_title_after_pipe
+ , Ext_smart
+ ]
+ result = runPure $ do
+ Pandoc _ blks <- readCommonMark (def {readerExtensions = exts}) txt
+ return $ B.fromList blks
+ in either mempty id result
+
+appendInlines :: B.Blocks -> B.Inlines -> B.Blocks
+appendInlines blks inlns = case B.unMany blks of
+ front :|> (B.Para xs) -> B.Many front <> B.para (addTo xs)
+ front :|> (B.Plain xs) -> B.Many front <> B.plain (addTo xs)
+ _ -> blks <> B.para inlns
+ where addTo xs = B.fromList xs <> B.space <> inlns
+
+appendType :: B.Blocks -> TypeSpec -> B.Blocks
+appendType blks typespec =
+ appendInlines blks (B.str "(" <> typeToInlines typespec <> B.str ")")
+
+typeToInlines :: TypeSpec -> B.Inlines
+typeToInlines = \case
+ bt@BasicType{} -> builtin $ tystr bt
+ NamedType "integer" -> builtin "integer"
+ NamedType name -> B.linkWith ("", ["documented-type"], [])
+ ("#" <> n2t name) mempty $ B.str (n2t name)
+ SeqType itemtype -> "{" <> typeToInlines itemtype <> ",...}"
+ SumType summands -> mconcat . intersperse (B.str "|") $ map typeToInlines summands
+ AnyType -> "any"
+ x -> tystr x
+ where
+ tystr = B.str . T.pack . typeSpecToString
+ n2t = UTF8.toText . fromName
+ builtin = B.spanWith ("", ["builtin-lua-type"], [])
+
+renderFunctionDoc :: Maybe T.Text -> FunctionDoc -> B.Blocks
+renderFunctionDoc mbmodule fndoc =
+ let name = case mbmodule of
+ Just _ -> T.takeWhileEnd (/= '.') $ funDocName fndoc
+ Nothing -> funDocName fndoc
+ ident = funDocName fndoc
+ level = 1
+ argsString = argslist (funDocParameters fndoc)
+ paramToDefItem p = ( B.code $ parameterName p
+ , compactify
+ [ appendType
+ (parseCommonMark $ parameterDescription p)
+ (parameterType p)
+ ]
+ )
+ paramlist = B.definitionList . map paramToDefItem $
+ funDocParameters fndoc
+ in mconcat
+ [ B.headerWith (ident, [], []) level (B.str name)
+ , B.plain (B.code $ name <> " (" <> argsString <> ")")
+ , parseCommonMark (funDocDescription fndoc)
+ , if null (funDocParameters fndoc)
+ then mempty
+ else B.para "Parameters:" <> paramlist
+ , if funDocResults fndoc == ResultsDocList []
+ then mempty
+ else B.para "Returns:" <> renderResults (funDocResults fndoc)
+ , case funDocSince fndoc of
+ Nothing -> mempty
+ Just version ->
+ B.para $ B.emph $ "Since: " <> (B.str . T.pack $ showVersion version)
+ ]
+
+renderResults :: ResultsDoc -> B.Blocks
+renderResults (ResultsDocMult descr) = parseCommonMark descr
+renderResults (ResultsDocList rvd) = B.bulletList $ map renderResultVal rvd
+ where
+ renderResultVal (ResultValueDoc typespec descr) =
+ parseCommonMark descr `appendType` typespec
+
+argslist :: [ParameterDoc] -> T.Text
+argslist params =
+ -- Expect optional values to come after required values.
+ let (required, optional') = break parameterIsOptional params
+ reqs = map parameterName required
+ opts = map parameterName optional'
+ in if null opts
+ then T.intercalate ", " reqs
+ else T.intercalate ", " reqs <>
+ (if null required then "[" else "[, ") <>
+ T.intercalate "[, " opts <> T.replicate (length opts) "]"
+
+renderFieldDoc :: T.Text -> FieldDoc -> B.Blocks
+renderFieldDoc _modname fd =
+ B.headerWith (ident, [], []) 3 (B.str name) <>
+ appendType (parseCommonMark $ fieldDocDescription fd) (fieldDocType fd)
+ where
+ ident = fieldDocName fd
+ name = T.takeWhileEnd (/= '.') $ fieldDocName fd
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Init.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Init.hs
index 2756dc61b..546323761 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Init.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Init.hs
@@ -3,7 +3,7 @@
{-# LANGUAGE RankNTypes #-}
{- |
Module : Text.Pandoc.Lua.Init
- Copyright : © 2017-2024 Albert Krewinkel
+ Copyright : © 2017-2026 Albert Krewinkel
License : GPL-2.0-or-later
Maintainer : Albert Krewinkel <[email protected]>
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 412131560..7d0c76b80 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/MediaBag.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/MediaBag.hs
@@ -104,8 +104,9 @@ insert = defun "insert"
setMediaBag $ MB.insertMedia fp mmime contents mb
return (Lua.NumResults 0))
<#> stringParam "filepath" "filename and path relative to the output folder."
- <#> opt (textParam "mimetype"
- "the item's MIME type; omit if unknown or unavailable.")
+ <#> parameter (Lua.peekNilOr Lua.peekText) "string|nil" "mimetype"
+ "the item's MIME type; use `nil` if the MIME type is\
+ \ unknown or unavailable."
<#> parameter Lua.peekLazyByteString "string" "contents"
"the binary contents of the file."
=#> []
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 efe00e03c..9334a2252 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Path.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Path.hs
@@ -3,7 +3,7 @@
{-# LANGUAGE TypeApplications #-}
{- |
Module : Text.Pandoc.Lua.Module.Path
- Copyright : © 2019-2024 Albert Krewinkel
+ Copyright : © 2019-2026 Albert Krewinkel
License : GNU GPL, version 2 or above
Maintainer : Albert Krewinkel <[email protected]>
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 d4b7cea08..a5a6bde8b 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-2026 Albert Krewinkel
+ Copyright : © 2017-2026 Albert Krewinkel
License : GNU GPL, version 2 or above
Maintainer : Albert Krewinkel <[email protected]>
@@ -19,6 +19,7 @@ module Text.Pandoc.Lua.Module.Utils
import Control.Applicative ((<|>))
import Control.Monad ((<$!>))
+import Control.Monad.Except (MonadError (throwError))
import Crypto.Hash (hashWith, SHA1(SHA1))
import Data.Data (showConstr, toConstr)
import Data.Default (def)
@@ -28,12 +29,17 @@ import HsLua as Lua
import HsLua.Module.Version (peekVersionFuzzy, pushVersion)
import Text.Pandoc.Citeproc (getReferences, processCitations)
import Text.Pandoc.Definition
-import Text.Pandoc.Error (PandocError)
+import Text.Pandoc.Error (PandocError (PandocLuaError))
import Text.Pandoc.Filter (applyJSONFilter)
+import Text.Pandoc.Format (FlavoredFormat (formatName), parseFlavoredFormat)
+import Text.Pandoc.Lua.Documentation (renderDocumentation)
import Text.Pandoc.Lua.Filter (runFilterFile')
import Text.Pandoc.Lua.Marshal.AST
+import Text.Pandoc.Lua.Marshal.Format (peekFlavoredFormat)
import Text.Pandoc.Lua.Marshal.Reference
import Text.Pandoc.Lua.PandocLua (PandocLua (unPandocLua))
+import Text.Pandoc.Options (WriterOptions (writerExtensions))
+import Text.Pandoc.Writers (Writer (..), getWriter)
import qualified Data.Map as Map
import qualified Data.Text as T
@@ -52,6 +58,7 @@ documentedModule = defmodule "pandoc.utils"
`withFunctions`
[ blocks_to_inlines `since` v[2,2,3]
, citeproc `since` v[2,19,1]
+ , documentation `since` v[3,8,4]
, equals `since` v[2,5]
, from_simple_table `since` v[2,11]
, make_sections `since` v[2,8]
@@ -67,8 +74,7 @@ documentedModule = defmodule "pandoc.utils"
, defun "Version"
### liftPure (id @Version)
- <#> parameter peekVersionFuzzy
- "version string, list of integers, or integer"
+ <#> parameter peekVersionFuzzy "Version|string|{integer,...}|number"
"v" "version description"
=#> functionResult pushVersion "Version" "new Version object"
#? "Creates a Version object."
@@ -125,6 +131,35 @@ citeproc = defun "citeproc"
, " end"
]
+documentation :: DocumentedFunction PandocError
+documentation = defun "documentation"
+ ### (\idx mformat -> do
+ docobj <- getdocumentation idx >>= \case
+ TypeNil -> fail "Undocumented object"
+ _ -> forcePeek $ peekDocumentationObject top
+ let blocks = renderDocumentation docobj
+ if maybe mempty formatName mformat == "blocks"
+ then pure . Left $ B.toList blocks
+ else unPandocLua $ do
+ flvrd <- maybe (parseFlavoredFormat "ansi") pure mformat
+ getWriter flvrd >>= \case
+ (TextWriter w, es) -> Right <$>
+ w def{ writerExtensions = es } (B.doc blocks)
+ _ -> throwError $ PandocLuaError
+ "ByteString writers are not supported here.")
+ <#> parameter pure "any" "object" "Retrieve documentation for this object"
+ <#> opt (parameter peekFlavoredFormat "string|table" "format"
+ "result format; defaults to `'ansi'`")
+ =#> functionResult (either pushBlocks pushText) "string|Blocks"
+ "rendered documentation"
+ #? "Return the documentation for a function or module defined by pandoc.\
+ \ Throws an error if there is no documentation for the given object.\n\
+ \\n\
+ \The result format can be any textual format accepted by `pandoc.write`,\
+ \ and the documentation will be returned in that format.\
+ \ Additionally, the special format `blocks` is accepted, in which case\
+ \ the documentation is returned as [[Blocks]]."
+
equals :: LuaError e => DocumentedFunction e
equals = defun "equals"
### equal
@@ -205,7 +240,7 @@ normalize_date :: DocumentedFunction e
normalize_date = defun "normalize_date"
### liftPure Shared.normalizeDate
<#> parameter peekText "string" "date" "the date string"
- =#> functionResult (maybe pushnil pushText) "string or nil"
+ =#> functionResult (maybe pushnil pushText) "string|nil"
"normalized date, or nil if normalization failed."
#? T.unwords
[ "Parse a date and convert (if possible) to \"YYYY-MM-DD\" format. We"
@@ -320,7 +355,8 @@ stringify = defun "stringify"
, (fmap (const "") . peekAttr)
, (fmap (const "") . peekListAttributes)
] idx)
- <#> parameter pure "AST element" "element" "some pandoc AST element"
+ <#> parameter pure "Pandoc|Block|Inline|Caption|Cell|MetaValue"
+ "element" "some pandoc AST element"
=#> functionResult pushText "string"
"A plain string representation of the given element."
#? T.unlines
diff --git a/tools/update-lua-module-docs.lua b/tools/update-lua-module-docs.lua
index 3f80ee28d..e74fb22aa 100644
--- a/tools/update-lua-module-docs.lua
+++ b/tools/update-lua-module-docs.lua
@@ -24,7 +24,13 @@ local registry = debug.getregistry()
--- Retrieves the documentation object for the given value.
local function documentation (value)
- return registry['HsLua docs'][value]
+ local docobj = registry['HsLua docs'][value]
+ if type(docobj) == 'userdata' then
+ -- Get the table representation by calling the object
+ return docobj()
+ else
+ return docobj
+ end
end
--- Table containing all known modules
@@ -201,9 +207,8 @@ end
-- @param modulename name of the module that contains this function
-- @return Documentation rendered as list of Blocks
local function render_function (doc, level, modulename)
- local name = doc.name
+ local name = doc.name:match('[^%.]*$')
level = level or 1
- local id = modulename and modulename .. '.' .. doc.name or ''
local args = argslist(doc.parameters)
local paramlist = DefinitionList(
List(doc.parameters):map(
@@ -219,7 +224,7 @@ local function render_function (doc, level, modulename)
)
)
return Blocks{
- Header(level, name, {id}),
+ Header(level, name, {doc.name}),
Plain{Code(string.format('%s (%s)', name, args))},
} .. read_blocks(doc.description)
.. List(#doc.parameters > 0 and {Para 'Parameters:'} or {})
@@ -236,8 +241,8 @@ end
-- @param modulename name of the module that contains this function
-- @return {Block,...}
local function render_field (field, level, modulename)
- local id = modulename and modulename .. '.' .. field.name or ''
- return Blocks{Header(level, field.name, {id})} ..
+ local name = field.name:match('[^.]*$')
+ return Blocks{Header(level, name, {field.name})} ..
{Plain(read_inlines(field.description) .. type_to_inlines(field.type))}
end
@@ -346,7 +351,7 @@ local function render_main_pandoc_module (doc)
for _, field in ipairs(doc.fields) do
if tostring(field.type) == 'string' then
constants_section:extend(render_field(field, 2, "pandoc"))
- elseif field.name:match '^[A-Z]' then
+ elseif field.name:match '^pandoc%.[A-Z]' then
-- Ignore (these are the `Block` and `Inline` tables)
else
fields:insert(field)
@@ -360,7 +365,7 @@ local function render_main_pandoc_module (doc)
else
functions:insert(fn)
end
- if fn.name == 'SimpleTable' then
+ if fn.name == 'pandoc.SimpleTable' then
stop_rendering = true
end
end
@@ -392,10 +397,10 @@ local function process_document (input, blocks, start)
if mstart and mstop and module_name then
print('Generating docs for module ' .. module_name)
blocks:insert(rawmd(input:sub(start, mstop)))
- local object = modules[module_name] or modules[module_name:gsub('^pandoc%.', '')]
+ local object = require(module_name)
local docblocks = (object == pandoc)
and render_main_pandoc_module(documentation(object))
- or render_module(documentation(object))
+ or pandoc.utils.documentation(object, 'blocks')
blocks:extend(docblocks)
return process_document(input, blocks, input:find(autogen_end, mstop) or -1)
else
@@ -411,12 +416,15 @@ function Reader (inputs)
local blocks = process_document(tostring(inputs), Blocks{}, 1)
blocks = blocks:walk {
Link = function (link)
- if link.classes == pandoc.List{'wikilink'} then
+ if link.classes == pandoc.List{'documented-type'} or
+ link.classes == pandoc.List{'wikilink'} then
link.classes = {}
- if known_types[link.target] then
- link.target = '#' .. known_types[link.target]
+ local ident = link.target:gsub('^#', '')
+ if known_types[ident] then
+ link.target = '#' .. known_types[ident]
else
- warn('Unknown type: ' .. link.target)
+ link.target = '#' .. ident
+ warn('Unknown type: ' .. ident)
end
return link
end
@@ -432,16 +440,3 @@ function Reader (inputs)
}
return Pandoc(blocks)
end
-
--- For usage as a standalone script.
--- E.g.
---
--- pandoc lua module-docs.lua
---
--- Generate Markdown docs for the given module and writes them to stdout.
-if arg and arg[1] then
- local module_name = arg[1]
- local object = modules[module_name]
- local blocks = render_module(documentation(object))
- print(write(Pandoc(blocks), 'markdown'))
-end