diff options
author | Albert Krewinkel <albert@zeitkraut.de> | 2019-05-19 15:26:00 +0200 |
---|---|---|
committer | Albert Krewinkel <albert@zeitkraut.de> | 2019-05-29 10:07:43 +0200 |
commit | 505f5bf5d951a5c4342f7acce9bea5f260dc9d78 (patch) | |
tree | 3b201baedf4003cdb17fa58c444bbb158faf213d | |
parent | d07ed83d705df491bba7b295bd5e80629d971685 (diff) | |
download | pandoc-505f5bf5d951a5c4342f7acce9bea5f260dc9d78.tar.gz |
Lua: add Version type to simplify comparisons
Version specifiers like `PANDOC_VERSION` and `PANDOC_API_VERSION` are
turned into `Version` objects. The objects simplify version-appropriate
comparisons while maintaining backward-compatibility.
A function `pandoc.types.Version` is added as part of the newly
introduced module `pandoc.types`, allowing users to create version
objects in scripts.
-rw-r--r-- | doc/lua-filters.md | 51 | ||||
-rw-r--r-- | pandoc.cabal | 5 | ||||
-rw-r--r-- | src/Text/Pandoc/Lua/Global.hs | 5 | ||||
-rw-r--r-- | src/Text/Pandoc/Lua/Marshaling.hs | 1 | ||||
-rw-r--r-- | src/Text/Pandoc/Lua/Marshaling/Version.hs | 154 | ||||
-rw-r--r-- | src/Text/Pandoc/Lua/Module/Types.hs | 28 | ||||
-rw-r--r-- | src/Text/Pandoc/Lua/Module/Utils.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Lua/Packages.hs | 2 | ||||
-rw-r--r-- | test/Tests/Lua.hs | 13 | ||||
-rw-r--r-- | test/Tests/Lua/Module.hs | 3 | ||||
-rw-r--r-- | test/lua/module/pandoc-types.lua | 112 | ||||
-rw-r--r-- | test/lua/module/pandoc-utils.lua (renamed from test/lua/module/pandoc.utils.lua) | 0 |
12 files changed, 353 insertions, 23 deletions
diff --git a/doc/lua-filters.md b/doc/lua-filters.md index 3b3bb2f17..a5a7f2922 100644 --- a/doc/lua-filters.md +++ b/doc/lua-filters.md @@ -151,21 +151,21 @@ variables. : Table of the options which were provided to the parser. `PANDOC_VERSION` -: Contains the pandoc version as a numerically indexed table, - most significant number first. E.g., for pandoc 2.1.1, the - value of the variable is a table `{2, 1, 1}`. Use - `table.concat(PANDOC_VERSION, '.')` to produce a version - string. This variable is also set in custom writers. +: Contains the pandoc version as a [Version object] which + behaves like a numerically indexed table, most significant + number first. E.g., for pandoc 2.7.3, the value of the + variable is equivalent to a table `{2, 7, 3}`. Use + `tostring(PANDOC_VERSION)` to produce a version string. This + variable is also set in custom writers. `PANDOC_API_VERSION` : Contains the version of the pandoc-types API against which pandoc was compiled. It is given as a numerically indexed table, most significant number first. E.g., if pandoc was compiled against pandoc-types 1.17.3, then the value of the - variable will be a table `{1, 17, 3}`. Use - `table.concat(PANDOC_API_VERSION, '.')` to produce a version - string from this table. This variable is also set in custom - writers. + variable will behave like the table `{1, 17, 3}`. Use + `tostring(PANDOC_API_VERSION)` to produce a version string. + This variable is also set in custom writers. `PANDOC_SCRIPT_FILE` : The name used to involve the filter. This value can be used @@ -178,6 +178,8 @@ variables. variable is of type [CommonState](#type-ref-CommonState) and is read-only. +[Version object]: #type-ref-Version + # Pandoc Module The `pandoc` lua module is loaded into the filter's lua @@ -1353,6 +1355,32 @@ available to readers and writers. A pandoc log message. Object have no fields, but can be converted to a string via `tostring`. +## Version {#type-ref-Version} + +A version object. This represents a software version like +"2.7.3". The object behaves like a numerically indexed table, +i.e., if `version` represents the version `2.7.3`, then + + version[1] == 2 + version[2] == 7 + version[3] == 3 + #version == 3 -- length + +Comparisons are performed element-wise, i.e. + + Version '1.12' > Version '1.9' + +### `must_be_at_least` + +`must_be_at_least(actual, expected [, error_message])` + +Raise an error message if the actual version is older than the +expected version. + +Usage: + + PANDOC_VERSION:must_be_at_least('2.7.3') + [Block]: #type-ref-Block [List]: #module-pandoc.list [MetaValue]: #type-ref-MetaValue @@ -2726,3 +2754,8 @@ Parameters: Returns: - The result(s) of the call to `callback` + + +# Module pandoc.types + +Constructors for types which are not part of the pandoc AST. diff --git a/pandoc.cabal b/pandoc.cabal index 8bf09cdd1..25513d7db 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -339,8 +339,7 @@ extra-source-files: test/odt/markdown/*.md test/odt/native/*.native test/lua/*.lua - test/lua/module/pandoc.lua - test/lua/module/pandoc.utils.lua + test/lua/module/*.lua source-repository head type: git location: git://github.com/jgm/pandoc.git @@ -593,9 +592,11 @@ library Text.Pandoc.Lua.Marshaling.AnyValue, Text.Pandoc.Lua.Marshaling.CommonState, Text.Pandoc.Lua.Marshaling.ReaderOptions, + Text.Pandoc.Lua.Marshaling.Version, Text.Pandoc.Lua.Module.MediaBag, Text.Pandoc.Lua.Module.Pandoc, Text.Pandoc.Lua.Module.System, + Text.Pandoc.Lua.Module.Types, Text.Pandoc.Lua.Module.Utils, Text.Pandoc.Lua.Packages, Text.Pandoc.Lua.Util, diff --git a/src/Text/Pandoc/Lua/Global.hs b/src/Text/Pandoc/Lua/Global.hs index f303af6c5..b9b6c9cd9 100644 --- a/src/Text/Pandoc/Lua/Global.hs +++ b/src/Text/Pandoc/Lua/Global.hs @@ -17,7 +17,6 @@ module Text.Pandoc.Lua.Global import Prelude import Data.Data (Data) -import Data.Version (Version (versionBranch)) import Foreign.Lua (Lua, Peekable, Pushable) import Foreign.Lua.Userdata ( ensureUserdataMetatable, pushAnyWithMetatable , metatableName) @@ -52,7 +51,7 @@ setGlobal global = case global of Lua.push format Lua.setglobal "FORMAT" PANDOC_API_VERSION -> do - Lua.push (versionBranch pandocTypesVersion) + Lua.push pandocTypesVersion Lua.setglobal "PANDOC_API_VERSION" PANDOC_DOCUMENT doc -> do Lua.push (LazyPandoc doc) @@ -67,7 +66,7 @@ setGlobal global = case global of Lua.push commonState Lua.setglobal "PANDOC_STATE" PANDOC_VERSION -> do - Lua.push (versionBranch version) + Lua.push version Lua.setglobal "PANDOC_VERSION" -- | Readonly and lazy pandoc objects. diff --git a/src/Text/Pandoc/Lua/Marshaling.hs b/src/Text/Pandoc/Lua/Marshaling.hs index cc0451c09..8a1270ab7 100644 --- a/src/Text/Pandoc/Lua/Marshaling.hs +++ b/src/Text/Pandoc/Lua/Marshaling.hs @@ -14,3 +14,4 @@ module Text.Pandoc.Lua.Marshaling () where import Text.Pandoc.Lua.Marshaling.AST () import Text.Pandoc.Lua.Marshaling.CommonState () import Text.Pandoc.Lua.Marshaling.ReaderOptions () +import Text.Pandoc.Lua.Marshaling.Version () diff --git a/src/Text/Pandoc/Lua/Marshaling/Version.hs b/src/Text/Pandoc/Lua/Marshaling/Version.hs new file mode 100644 index 000000000..3c667cbc4 --- /dev/null +++ b/src/Text/Pandoc/Lua/Marshaling/Version.hs @@ -0,0 +1,154 @@ +{-# OPTIONS_GHC -fno-warn-orphans #-} +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE NoImplicitPrelude #-} +{- | + Module : Text.Pandoc.Lua.Marshaling.Version + Copyright : © 2019 Albert Krewinkel + License : GNU GPL, version 2 or above + + Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de> + Stability : alpha + +Marshaling of @'Version'@s. The marshaled elements can be compared using +default comparison operators (like @>@ and @<=@). +-} +module Text.Pandoc.Lua.Marshaling.Version + ( peekVersion + , pushVersion + ) + where + +import Prelude +import Data.Maybe (fromMaybe) +import Data.Version (Version (..), makeVersion, parseVersion, showVersion) +import Foreign.Lua (Lua, Optional (..), NumResults, + Peekable, Pushable, StackIndex) +import Foreign.Lua.Types.Peekable (reportValueOnFailure) +import Foreign.Lua.Userdata (ensureUserdataMetatable, pushAnyWithMetatable, + toAnyWithName) +import Safe (atMay, lastMay) +import Text.Pandoc.Lua.Marshaling.AnyValue (AnyValue (..)) +import Text.ParserCombinators.ReadP (readP_to_S) + +import qualified Foreign.Lua as Lua +import qualified Text.Pandoc.Lua.Util as LuaUtil + +-- | Push a @'Version'@ element to the Lua stack. +pushVersion :: Version -> Lua () +pushVersion version = pushAnyWithMetatable pushVersionMT version + where + pushVersionMT = ensureUserdataMetatable versionTypeName $ do + LuaUtil.addFunction "__eq" __eq + LuaUtil.addFunction "__le" __le + LuaUtil.addFunction "__lt" __lt + LuaUtil.addFunction "__len" __len + LuaUtil.addFunction "__index" __index + LuaUtil.addFunction "__pairs" __pairs + LuaUtil.addFunction "__tostring" __tostring + +instance Pushable Version where + push = pushVersion + +peekVersion :: StackIndex -> Lua Version +peekVersion idx = Lua.ltype idx >>= \case + Lua.TypeString -> do + versionStr <- Lua.peek idx + let parses = readP_to_S parseVersion versionStr + case lastMay parses of + Just (v, "") -> return v + _ -> Lua.throwException $ "could not parse as Version: " ++ versionStr + + Lua.TypeUserdata -> + reportValueOnFailure versionTypeName + (`toAnyWithName` versionTypeName) + idx + Lua.TypeNumber -> do + n <- Lua.peek idx + return (makeVersion [n]) + + Lua.TypeTable -> + makeVersion <$> Lua.peek idx + + _ -> + Lua.throwException "could not peek Version" + +instance Peekable Version where + peek = peekVersion + +-- | Name used by Lua for the @CommonState@ type. +versionTypeName :: String +versionTypeName = "HsLua Version" + +__eq :: Version -> Version -> Lua Bool +__eq v1 v2 = return (v1 == v2) + +__le :: Version -> Version -> Lua Bool +__le v1 v2 = return (v1 <= v2) + +__lt :: Version -> Version -> Lua Bool +__lt v1 v2 = return (v1 < v2) + +-- | Get number of version components. +__len :: Version -> Lua Int +__len = return . length . versionBranch + +-- | Access fields. +__index :: Version -> AnyValue -> Lua NumResults +__index v (AnyValue k) = do + ty <- Lua.ltype k + case ty of + Lua.TypeNumber -> do + n <- Lua.peek k + let versionPart = atMay (versionBranch v) (n - 1) + Lua.push (Lua.Optional versionPart) + return 1 + Lua.TypeString -> do + str <- Lua.peek k + if str == "must_be_at_least" + then 1 <$ Lua.pushHaskellFunction must_be_at_least + else 1 <$ Lua.pushnil + _ -> 1 <$ Lua.pushnil + +-- | Create iterator. +__pairs :: Version -> Lua NumResults +__pairs v = do + Lua.pushHaskellFunction nextFn + Lua.pushnil + Lua.pushnil + return 3 + where + nextFn :: AnyValue -> Optional Int -> Lua Lua.NumResults + nextFn _ (Optional key) = + case key of + Nothing -> case versionBranch v of + [] -> 2 <$ (Lua.pushnil *> Lua.pushnil) + n:_ -> 2 <$ (Lua.push (1 :: Int) *> Lua.push n) + Just n -> case atMay (versionBranch v) n of + Nothing -> 2 <$ (Lua.pushnil *> Lua.pushnil) + Just b -> 2 <$ (Lua.push (n + 1) *> Lua.push b) + +-- | Convert to string. +__tostring :: Version -> Lua String +__tostring v = return (showVersion v) + +-- | Default error message when a version is too old. This message is +-- formatted in Lua with the expected and actual versions as arguments. +versionTooOldMessage :: String +versionTooOldMessage = "version too old: expected version %s or newer, got %s" + +-- | Throw an error if this version is older than the given version. +-- FIXME: This function currently requires the string library to be +-- loaded. +must_be_at_least :: Version -> Version -> Optional String -> Lua NumResults +must_be_at_least actual expected optMsg = do + let msg = fromMaybe versionTooOldMessage (fromOptional optMsg) + if expected <= actual + then return 0 + else do + Lua.getglobal' "string.format" + Lua.push msg + Lua.push (showVersion expected) + Lua.push (showVersion actual) + Lua.call 3 1 + Lua.error + diff --git a/src/Text/Pandoc/Lua/Module/Types.hs b/src/Text/Pandoc/Lua/Module/Types.hs new file mode 100644 index 000000000..641bde7d6 --- /dev/null +++ b/src/Text/Pandoc/Lua/Module/Types.hs @@ -0,0 +1,28 @@ +{- | + Module : Text.Pandoc.Lua.Module.Types + Copyright : © 2019 Albert Krewinkel + License : GNU GPL, version 2 or above + + Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de> + Stability : alpha + +Pandoc data type constructors. +-} +module Text.Pandoc.Lua.Module.Types + ( pushModule + ) where + +import Prelude +import Data.Version (Version) +import Foreign.Lua (Lua, NumResults) +import Text.Pandoc.Lua.Marshaling.Version () +import Text.Pandoc.Lua.Util (addFunction) + +import qualified Foreign.Lua as Lua + +-- | Push the pandoc.system module on the Lua stack. +pushModule :: Lua NumResults +pushModule = do + Lua.newtable + addFunction "Version" (return :: Version -> Lua Version) + return 1 diff --git a/src/Text/Pandoc/Lua/Module/Utils.hs b/src/Text/Pandoc/Lua/Module/Utils.hs index 7f201a4b2..21e3f5674 100644 --- a/src/Text/Pandoc/Lua/Module/Utils.hs +++ b/src/Text/Pandoc/Lua/Module/Utils.hs @@ -17,6 +17,7 @@ import Prelude import Control.Applicative ((<|>)) import Data.Char (toLower) import Data.Default (def) +import Data.Version (Version) import Foreign.Lua (Peekable, Lua, NumResults) import Text.Pandoc.Class (runIO, setUserDataDir) import Text.Pandoc.Definition ( Pandoc, Meta, MetaValue (..), Block, Inline @@ -43,6 +44,7 @@ pushModule mbDatadir = do addFunction "sha1" sha1 addFunction "stringify" stringify addFunction "to_roman_numeral" toRomanNumeral + addFunction "Version" (return :: Version -> Lua Version) return 1 -- | Squashes a list of blocks into inlines. diff --git a/src/Text/Pandoc/Lua/Packages.hs b/src/Text/Pandoc/Lua/Packages.hs index 5f2751f52..ca1779e27 100644 --- a/src/Text/Pandoc/Lua/Packages.hs +++ b/src/Text/Pandoc/Lua/Packages.hs @@ -26,6 +26,7 @@ import qualified Foreign.Lua as Lua import Text.Pandoc.Lua.Module.Pandoc as Pandoc import Text.Pandoc.Lua.Module.MediaBag as MediaBag import Text.Pandoc.Lua.Module.System as System +import Text.Pandoc.Lua.Module.Types as Types import Text.Pandoc.Lua.Module.Utils as Utils -- | Parameters used to create lua packages/modules. @@ -54,6 +55,7 @@ pandocPackageSearcher pkgParams pkgName = in pushWrappedHsFun (Pandoc.pushModule datadir) "pandoc.mediabag" -> pushWrappedHsFun MediaBag.pushModule "pandoc.system" -> pushWrappedHsFun System.pushModule + "pandoc.types" -> pushWrappedHsFun Types.pushModule "pandoc.utils" -> let datadir = luaPkgDataDir pkgParams in pushWrappedHsFun (Utils.pushModule datadir) _ -> searchPureLuaLoader diff --git a/test/Tests/Lua.hs b/test/Tests/Lua.hs index c585182e4..7a1261eb2 100644 --- a/test/Tests/Lua.hs +++ b/test/Tests/Lua.hs @@ -15,7 +15,6 @@ module Tests.Lua ( runLuaTest, tests ) where import Prelude import Control.Monad (when) -import Data.Version (Version (versionBranch)) import System.FilePath ((</>)) import Test.Tasty (TestTree, localOption) import Test.Tasty.HUnit (Assertion, assertEqual, testCase) @@ -34,6 +33,7 @@ import Text.Pandoc.Options (def) import Text.Pandoc.Shared (pandocVersion) import qualified Foreign.Lua as Lua +import qualified Data.ByteString.Char8 as BS tests :: [TestTree] tests = map (localOption (QuickCheckTests 20)) @@ -135,17 +135,14 @@ tests = map (localOption (QuickCheckTests 20)) (doc $ para (str $ "lua" </> "script-name.lua")) , testCase "Pandoc version is set" . runLuaTest $ do - Lua.getglobal' "table.concat" Lua.getglobal "PANDOC_VERSION" - Lua.push ("." :: String) -- separator - Lua.call 2 1 - Lua.liftIO . assertEqual "pandoc version is wrong" pandocVersion - =<< Lua.peek Lua.stackTop + Lua.liftIO . + assertEqual "pandoc version is wrong" (BS.pack pandocVersion) + =<< Lua.tostring' Lua.stackTop , testCase "Pandoc types version is set" . runLuaTest $ do - let versionNums = versionBranch pandocTypesVersion Lua.getglobal "PANDOC_API_VERSION" - Lua.liftIO . assertEqual "pandoc-types version is wrong" versionNums + Lua.liftIO . assertEqual "pandoc-types version is wrong" pandocTypesVersion =<< Lua.peek Lua.stackTop , testCase "Allow singleton inline in constructors" . runLuaTest $ do diff --git a/test/Tests/Lua/Module.hs b/test/Tests/Lua/Module.hs index 82c9330e5..324acce04 100644 --- a/test/Tests/Lua/Module.hs +++ b/test/Tests/Lua/Module.hs @@ -20,7 +20,8 @@ import Tests.Lua (runLuaTest) tests :: [TestTree] tests = [ testPandocLua "pandoc" ("lua" </> "module" </> "pandoc.lua") - , testPandocLua "pandoc.util" ("lua" </> "module" </> "pandoc.utils.lua") + , testPandocLua "pandoc.types" ("lua" </> "module" </> "pandoc-types.lua") + , testPandocLua "pandoc.util" ("lua" </> "module" </> "pandoc-utils.lua") ] testPandocLua :: TestName -> FilePath -> TestTree diff --git a/test/lua/module/pandoc-types.lua b/test/lua/module/pandoc-types.lua new file mode 100644 index 000000000..8c8d903d9 --- /dev/null +++ b/test/lua/module/pandoc-types.lua @@ -0,0 +1,112 @@ +local tasty = require 'tasty' +local types = require 'pandoc.types' +local Version = types.Version + +local assert = tasty.assert +local test = tasty.test_case +local group = tasty.test_group + +return { + group 'Version' { + + group 'constructor' { + test('has type `userdata`', function () + assert.are_same(type(Version {2}), 'userdata') + end), + test('accepts list of integers', function () + assert.are_same(type(Version {2, 7, 3}), 'userdata') + end), + test('accepts a single integer', function () + assert.are_same(Version(5), Version {5}) + end), + test('accepts version as string', function () + assert.are_same( + Version '4.45.1', + Version {4, 45, 1} + ) + end), + test('non-version string is rejected', function () + assert.error_matches( + function () Version '11friends' end, + '11friends' + ) + end) + }, + + group 'comparison' { + test('smaller (equal) than', function () + assert.is_truthy(Version {2, 58, 3} < Version {2, 58, 4}) + assert.is_falsy(Version {2, 60, 1} < Version {2, 59, 2}) + assert.is_truthy(Version {0, 14, 3} < Version {0, 14, 3, 1}) + assert.is_truthy(Version {3, 58, 3} <= Version {4}) + assert.is_truthy(Version {0, 14, 3} <= Version {0, 14, 3, 1}) + end), + test('larger (equal) than', function () + assert.is_truthy(Version{2,58,3} > Version {2, 57, 4}) + assert.is_truthy(Version{2,58,3} > Version {2, 58, 2}) + assert.is_truthy(Version {0, 8} >= Version {0, 8}) + assert.is_falsy(Version {0, 8} >= Version {0, 8, 2}) + end), + test('equality', function () + assert.is_truthy(Version '8.8', Version {8, 8}) + end), + test('second argument can be a version string', function () + assert.is_truthy(Version '8' < '9.1') + assert.is_falsy(Version '8.8' < '8.7') + end), + }, + + group 'list-like behavior' { + test('can access version component numbers', function () + local version = Version '2.7.3' + assert.is_nil(version[0]) + assert.are_equal(version[1], 2) + assert.are_equal(version[2], 7) + assert.are_equal(version[3], 3) + end), + test('can be iterated over', function () + local version_list = {2, 7, 3} + local final_index = 0 + for i, v in pairs(Version(version_list)) do + assert.are_equal(v, version_list[i]) + final_index = i + end + assert.are_equal(final_index, 3) + end), + test('length is the number of components', function () + assert.are_equal(#(Version '0'), 1) + assert.are_equal(#(Version '1.6'), 2) + assert.are_equal(#(Version '8.7.5'), 3) + assert.are_equal(#(Version '2.9.1.5'), 4) + end) + }, + + group 'conversion to string' { + test('converting from and to string is a noop', function () + local version_string = '1.19.4' + assert.are_equal(tostring(Version(version_string)), version_string) + end) + }, + + group 'convenience functions' { + test('throws error if version is too old', function () + local actual = Version {2, 8} + local expected = Version {2, 9} + assert.error_matches( + function () actual:must_be_at_least(expected) end, + 'version too old: expected version 2.9 or newer, got 2.8' + ) + end), + test('does nothing if expected version is older than actual', function () + local actual = Version '2.9' + local expected = Version '2.8' + actual:must_be_at_least(expected) + end), + test('does nothing if expected version equals to actual', function () + local actual = Version '2.8' + local expected = Version '2.8' + actual:must_be_at_least(expected) + end) + } + } +} diff --git a/test/lua/module/pandoc.utils.lua b/test/lua/module/pandoc-utils.lua index dc37ec354..dc37ec354 100644 --- a/test/lua/module/pandoc.utils.lua +++ b/test/lua/module/pandoc-utils.lua |