aboutsummaryrefslogtreecommitdiff
path: root/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Format.hs
diff options
context:
space:
mode:
authorAlbert Krewinkel <[email protected]>2022-10-04 17:30:12 +0200
committerJohn MacFarlane <[email protected]>2022-10-04 13:06:23 -0700
commit86e009b49547e7072cf099b7990cb7ff2b864979 (patch)
tree29b34f6931c3d174271b7788f0a37c04144a7247 /pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Format.hs
parenta50765b3e42de0295ffcb090f77f140070b57d0a (diff)
Lua: add new module `pandoc.format`.
The module provides functions to query the set of extensions supported by formats, and the set of extension enabled per default.
Diffstat (limited to 'pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Format.hs')
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Format.hs60
1 files changed, 60 insertions, 0 deletions
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Format.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Format.hs
new file mode 100644
index 000000000..8fa0485fc
--- /dev/null
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Format.hs
@@ -0,0 +1,60 @@
+{-# LANGUAGE OverloadedStrings #-}
+{- |
+ Module : Text.Pandoc.Lua.Module.Format
+ Copyright : © 2022 Albert Krewinkel
+ License : GPL-2.0-or-later
+ Maintainer : Albert Krewinkel <[email protected]>
+
+Lua module to handle pandoc templates.
+-}
+module Text.Pandoc.Lua.Module.Format
+ ( documentedModule
+ ) where
+
+import HsLua
+import Text.Pandoc.Error (PandocError)
+import Text.Pandoc.Extensions
+ ( getAllExtensions, getDefaultExtensions )
+import Text.Pandoc.Lua.ErrorConversion ()
+import Text.Pandoc.Lua.Marshal.Extensions (pushExtensions)
+
+import qualified Data.Text as T
+
+-- | The "pandoc.format" module.
+documentedModule :: Module PandocError
+documentedModule = Module
+ { moduleName = "pandoc.format"
+ , moduleDescription = T.unlines
+ [ "Pandoc formats and their extensions."
+ ]
+ , moduleFields = []
+ , moduleOperations = []
+ , moduleFunctions = functions
+ }
+
+-- | Extension module functions.
+functions :: [DocumentedFunction PandocError]
+functions =
+ [ defun "default_extensions"
+ ### liftPure getDefaultExtensions
+ <#> parameter peekText "string" "format" "format name"
+ =#> functionResult pushExtensions "FormatExtensions"
+ "default extensions enabled for `format`"
+ #? T.unlines
+ [ "Returns the list of default extensions of the given format; this"
+ , "function does not check if the format is supported, it will return"
+ , "a fallback list of extensions even for unknown formats."
+ ]
+
+ , defun "all_extensions"
+ ### liftPure getAllExtensions
+ <#> parameter peekText "string" "format" "format name"
+ =#> functionResult pushExtensions "FormatExtensions"
+ "all extensions supported for `format`"
+ #? T.unlines
+ [ "Returns the list of all valid extensions for a format."
+ , "No distinction is made between input and output, and an"
+ , "extension have an effect when reading a format but not when"
+ , "writing it, or *vice versa*."
+ ]
+ ]