aboutsummaryrefslogtreecommitdiff
path: root/pandoc-lua-engine
diff options
context:
space:
mode:
authorAlbert Krewinkel <[email protected]>2023-03-19 13:44:59 +0100
committerAlbert Krewinkel <[email protected]>2023-03-19 15:09:23 +0100
commit7743c5287a54abe71da8fb316a34cb9f1f37c358 (patch)
tree9f3859e6badf29a78bbbd5b85ee4efed62ab7789 /pandoc-lua-engine
parent07c56322c24062082b798961573f0dbb22c4937b (diff)
Lua: add info on when functions became available in pandoc
Diffstat (limited to 'pandoc-lua-engine')
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Init.hs9
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/CLI.hs4
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Format.hs4
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/JSON.hs12
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/MediaBag.hs18
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Structure.hs11
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/System.hs18
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Template.hs5
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Types.hs4
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Utils.hs19
10 files changed, 69 insertions, 35 deletions
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Init.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Init.hs
index 247b70add..f41206bdc 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Init.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Init.hs
@@ -21,6 +21,7 @@ import Control.Monad (forM, forM_, when)
import Control.Monad.Catch (throwM, try)
import Control.Monad.Trans (MonadIO (..))
import Data.Maybe (catMaybes)
+import Data.Version (makeVersion)
import HsLua as Lua hiding (status, try)
import Text.Pandoc.Class (PandocMonad (..))
import Text.Pandoc.Data (readDataFile)
@@ -95,10 +96,18 @@ loadedModules =
, Pandoc.Types.documentedModule
, Pandoc.Utils.documentedModule
, Module.Layout.documentedModule { moduleName = "pandoc.layout" }
+ `allSince` [2,18]
, Module.Path.documentedModule { moduleName = "pandoc.path" }
+ `allSince` [2,12]
, Module.Text.documentedModule
+ `allSince` [2,0,3]
, Module.Zip.documentedModule { moduleName = "pandoc.zip" }
+ `allSince` [3,0]
]
+ where
+ allSince mdl version = mdl
+ { moduleFunctions = map (`since` makeVersion version) $ moduleFunctions mdl
+ }
-- | Initialize the lua state with all required values
initLuaState :: PandocLua ()
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 37aa719f7..c126d5338 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/CLI.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/CLI.hs
@@ -13,6 +13,7 @@ module Text.Pandoc.Lua.Module.CLI
) where
import Control.Applicative ((<|>))
+import Data.Version (makeVersion)
import HsLua
import HsLua.REPL (defaultConfig, replWithEnv, setup)
import Text.Pandoc.App (defaultOpts, options, parseOptionsFromArgs)
@@ -47,8 +48,9 @@ documentedModule = Module
, "Typically this function will be used in stand-alone pandoc Lua"
, "scripts, taking the list of arguments from the global `arg`."
]
+ `since` makeVersion [3, 0]
- , repl
+ , repl `since` makeVersion [3, 1, 2]
]
, moduleOperations = []
, moduleTypeInitializers = []
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 2bc9910cd..b4397e2bc 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Format.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Format.hs
@@ -11,6 +11,7 @@ module Text.Pandoc.Lua.Module.Format
( documentedModule
) where
+import Data.Version (makeVersion)
import HsLua
import Text.Pandoc.Error (PandocError)
import Text.Pandoc.Extensions (getAllExtensions, getDefaultExtensions)
@@ -46,6 +47,7 @@ functions =
, "function does not check if the format is supported, it will return"
, "a fallback list of extensions even for unknown formats."
]
+ `since` makeVersion [3,0]
, defun "all_extensions"
### liftPure getAllExtensions
@@ -58,6 +60,7 @@ functions =
, "can have an effect when reading a format but not when"
, "writing it, or *vice versa*."
]
+ `since` makeVersion [3,0]
, defun "extensions"
### liftPure getExtensionsConfig
@@ -73,4 +76,5 @@ functions =
, "This function can be used to assign a value to the `Extensions`"
, "global in custom readers and writers."
]
+ `since` makeVersion [3,0]
]
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 a21635329..6b309fbd8 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/JSON.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/JSON.hs
@@ -22,7 +22,7 @@ where
import Prelude hiding (null)
import Data.Maybe (fromMaybe)
import Data.Monoid (Alt (..))
-import Data.Version (Version, makeVersion)
+import Data.Version (makeVersion)
import HsLua.Aeson
import HsLua.Core
import HsLua.Marshalling
@@ -70,8 +70,8 @@ null = Field
functions :: [DocumentedFunction PandocError]
functions =
- [ decode
- , encode
+ [ decode `since` makeVersion [3, 1, 1]
+ , encode `since` makeVersion [3, 1, 1]
]
-- | Decode a JSON string into a Lua object.
@@ -102,7 +102,6 @@ decode = defun "decode"
, "The special handling of AST elements can be disabled by setting"
, "`pandoc_types` to `false`."
]
- `since` initialVersion
-- | Encode a Lua object as JSON.
encode :: LuaError e => DocumentedFunction e
@@ -133,8 +132,3 @@ encode = defun "encode"
, "the sole argument. The result of that call is expected to be a"
, "valid JSON string, but this not checked."
]
- `since` initialVersion
-
--- | First published version of this library.
-initialVersion :: Version
-initialVersion = makeVersion [1,0,0]
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 3de86cc99..8336b6917 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/MediaBag.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/MediaBag.hs
@@ -42,15 +42,15 @@ documentedModule = Module
, moduleDescription = "mediabag access"
, moduleFields = []
, moduleFunctions =
- [ delete
- , empty
- , fetch
- , fill
- , insert
- , items
- , list
- , lookup
- , write
+ [ delete `since` makeVersion [2,7,3]
+ , empty `since` makeVersion [2,7,3]
+ , fetch `since` makeVersion [2,0]
+ , fill `since` makeVersion [2,19]
+ , insert `since` makeVersion [2,0]
+ , items `since` makeVersion [2,7,3]
+ , list `since` makeVersion [2,0]
+ , lookup `since` makeVersion [2,0]
+ , write `since` makeVersion [3,0]
]
, moduleOperations = []
, moduleTypeInitializers = []
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 73419633f..266e502c6 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Structure.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Structure.hs
@@ -15,11 +15,12 @@ module Text.Pandoc.Lua.Module.Structure
import Control.Applicative ((<|>), optional)
import Data.Default (Default (..))
import Data.Maybe (fromMaybe)
+import Data.Version (makeVersion)
import HsLua ( DocumentedFunction, LuaError, Module (..), Peeker
, (###), (<#>), (=#>), (#?)
, defun, functionResult, getfield, isnil, lastly, liftLua
, opt, liftPure, parameter , peekBool, peekIntegral
- , peekFieldRaw, peekText, pop, pushIntegral, top )
+ , peekFieldRaw, peekText, pop, pushIntegral, since, top )
import Text.Pandoc.Chunks ( ChunkedDoc (..), PathTemplate (..)
, tocToList, splitIntoChunks )
import Text.Pandoc.Definition (Pandoc (..), Block)
@@ -45,10 +46,10 @@ documentedModule = Module
"hierarchical sections and the table of contents."
, moduleFields = []
, moduleFunctions =
- [ make_sections
- , slide_level
- , split_into_chunks
- , table_of_contents
+ [ 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]
]
, moduleOperations = []
, moduleTypeInitializers = []
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 1d685e13e..367b74a33 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/System.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/System.hs
@@ -31,15 +31,17 @@ documentedModule = Module
]
, moduleFunctions =
[ cputime `since` makeVersion [3, 1, 1]
- , setName "environment" env
- , setName "get_working_directory" getwd
- , setName "list_directory" ls
- , setName "make_directory" mkdir
- , setName "remove_directory" rmdir
- , setName "with_environment" with_env
- , setName "with_temporary_directory" with_tmpdir
- , setName "with_working_directory" with_wd
+ , 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]
+ , setName "remove_directory" rmdir `since` v[2,19]
+ , 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]
]
, 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 87d9cebb5..203fbf1cf 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Template.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Template.hs
@@ -11,6 +11,7 @@ module Text.Pandoc.Lua.Module.Template
( documentedModule
) where
+import Data.Version (makeVersion)
import HsLua
import HsLua.Module.DocLayout (peekDoc, pushDoc)
import Text.Pandoc.Error (PandocError)
@@ -53,6 +54,7 @@ functions =
, "table as values, where the table can be either be a list of the"
, "aforementioned types, or a nested context."
]
+ `since` makeVersion [3,0]
, defun "compile"
### (\template mfilepath -> unPandocLua $
@@ -64,6 +66,7 @@ functions =
<#> opt (stringParam "templ_path" "template path")
=#> functionResult (either failLua pushTemplate) "pandoc Template"
"compiled template"
+ `since` makeVersion [2,17]
, defun "default"
### (\mformat -> unPandocLua $ do
@@ -76,6 +79,7 @@ functions =
"writer for which the template should be returned.")
=#> functionResult pushText "string"
"string representation of the writer's default template"
+ `since` makeVersion [2,17]
, defun "meta_to_context"
### (\meta blockWriterIdx inlineWriterIdx -> unPandocLua $ do
@@ -101,4 +105,5 @@ functions =
, "data, using the given functions to convert [Blocks] and [Inlines]"
, "to [Doc] values."
]
+ `since` makeVersion [3,0]
]
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 4f656ff3f..4b88c7662 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Types.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Types.hs
@@ -13,8 +13,9 @@ module Text.Pandoc.Lua.Module.Types
( documentedModule
) where
+import Data.Version (makeVersion)
import HsLua ( Module (..), (###), (<#>), (=#>)
- , defun, functionResult, parameter)
+ , defun, functionResult, parameter, since)
import HsLua.Module.Version (peekVersionFuzzy, pushVersion)
import Text.Pandoc.Error (PandocError)
import Text.Pandoc.Lua.PandocLua ()
@@ -37,6 +38,7 @@ documentedModule = Module
, "or a Version object"
])
=#> functionResult pushVersion "Version" "A 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 74e3cc4ec..b87efd756 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Utils.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Utils.hs
@@ -22,7 +22,7 @@ import Control.Monad ((<$!>))
import Data.Data (showConstr, toConstr)
import Data.Default (def)
import Data.Maybe (fromMaybe)
-import Data.Version (Version)
+import Data.Version (Version, makeVersion)
import HsLua as Lua
import HsLua.Module.Version (peekVersionFuzzy, pushVersion)
import Text.Pandoc.Citeproc (getReferences, processCitations)
@@ -59,6 +59,7 @@ documentedModule = Module
"blocks" ""
<#> opt (parameter (peekList peekInline) "Inlines" "sep" "")
=#> functionResult pushInlines "list of inlines" ""
+ `since` v[2,2,3]
, defun "citeproc"
### unPandocLua . processCitations
@@ -69,12 +70,14 @@ documentedModule = Module
, "rendered citations and adding a bibliography. "
, "See the manual section on citation rendering for details."
]
+ `since` v[2,19,1]
, defun "equals"
### equal
<#> parameter pure "AST element" "elem1" ""
<#> parameter pure "AST element" "elem2" ""
=#> functionResult pushBool "boolean" "true iff elem1 == elem2"
+ `since` v[2,5]
, defun "make_sections"
### liftPure3 Shared.makeSections
@@ -85,6 +88,7 @@ documentedModule = Module
"blocks" "document blocks to process"
=#> functionResult pushBlocks "list of Blocks"
"processes blocks"
+ `since` v[2,8]
, defun "normalize_date"
### liftPure Shared.normalizeDate
@@ -97,8 +101,10 @@ documentedModule = Module
, "or equal to 1583, but MS Word only accepts dates starting 1601)."
, "Returns nil instead of a string if the conversion failed."
]
+ `since` v [2,0,6]
, sha1
+ `since` v [2,0,6]
, defun "Version"
### liftPure (id @Version)
@@ -119,6 +125,7 @@ documentedModule = Module
, "document (either with a genuine citation or with `nocite`) are "
, "returned. URL variables are converted to links."
]
+ `since` v[2,17]
, defun "run_json_filter"
### (\doc filterPath margs -> do
@@ -134,28 +141,33 @@ documentedModule = Module
<#> opt (parameter (peekList peekString) "list of strings"
"args" "arguments to pass to the filter")
=#> functionResult pushPandoc "Pandoc" "filtered document"
+ `since` v[2,1,1]
, defun "stringify"
### stringify
<#> parameter pure "AST element" "elem" "some pandoc AST element"
=#> functionResult pushText "string" "stringified element"
+ `since` v [2,0,6]
, defun "from_simple_table"
### from_simple_table
<#> parameter peekSimpleTable "SimpleTable" "simple_tbl" ""
=?> "Simple table"
+ `since` v[2,11]
, defun "to_roman_numeral"
### liftPure Shared.toRomanNumeral
<#> parameter (peekIntegral @Int) "integer" "n" "number smaller than 4000"
=#> functionResult pushText "string" "roman numeral"
#? "Converts a number < 4000 to uppercase roman numeral."
+ `since` v[2,0,6]
, defun "to_simple_table"
### to_simple_table
<#> parameter peekTable "Block" "tbl" "a table"
=#> functionResult pushSimpleTable "SimpleTable" "SimpleTable object"
#? "Converts a table into an old/simple table."
+ `since` v[2,11]
, defun "type"
### (\idx -> getmetafield idx "__name" >>= \case
@@ -163,12 +175,15 @@ documentedModule = Module
_ -> ltype idx >>= typename)
<#> parameter pure "any" "object" ""
=#> functionResult pushByteString "string" "type of the given value"
- #? ("Pandoc-friendly version of Lua's default `type` function, " <>
+ #? ("Pandoc-friendly version of Lua's default `type` function, " <>
"returning the type of a value. If the argument has a " <>
"string-valued metafield `__name`, then it gives that string. " <>
"Otherwise it behaves just like the normal `type` function.")
+ `since` v[2,17]
]
}
+ where
+ v = makeVersion
-- | Documented Lua function to compute the hash of a string.
sha1 :: DocumentedFunction e