Lua: marshal Version values as userdata
This commit is contained in:
parent
6a03aca906
commit
c07005a095
7 changed files with 13 additions and 126 deletions
|
@ -556,6 +556,7 @@ library
|
||||||
hslua-module-path >= 1.0 && < 1.1,
|
hslua-module-path >= 1.0 && < 1.1,
|
||||||
hslua-module-system >= 1.0 && < 1.1,
|
hslua-module-system >= 1.0 && < 1.1,
|
||||||
hslua-module-text >= 1.0 && < 1.1,
|
hslua-module-text >= 1.0 && < 1.1,
|
||||||
|
hslua-module-version >= 1.0 && < 1.1,
|
||||||
http-client >= 0.4.30 && < 0.8,
|
http-client >= 0.4.30 && < 0.8,
|
||||||
http-client-tls >= 0.2.4 && < 0.4,
|
http-client-tls >= 0.2.4 && < 0.4,
|
||||||
http-types >= 0.8 && < 0.13,
|
http-types >= 0.8 && < 0.13,
|
||||||
|
@ -783,7 +784,6 @@ library
|
||||||
Text.Pandoc.Lua.Marshaling.PandocError,
|
Text.Pandoc.Lua.Marshaling.PandocError,
|
||||||
Text.Pandoc.Lua.Marshaling.ReaderOptions,
|
Text.Pandoc.Lua.Marshaling.ReaderOptions,
|
||||||
Text.Pandoc.Lua.Marshaling.SimpleTable,
|
Text.Pandoc.Lua.Marshaling.SimpleTable,
|
||||||
Text.Pandoc.Lua.Marshaling.Version,
|
|
||||||
Text.Pandoc.Lua.Module.MediaBag,
|
Text.Pandoc.Lua.Module.MediaBag,
|
||||||
Text.Pandoc.Lua.Module.Pandoc,
|
Text.Pandoc.Lua.Module.Pandoc,
|
||||||
Text.Pandoc.Lua.Module.System,
|
Text.Pandoc.Lua.Module.System,
|
||||||
|
|
|
@ -15,6 +15,7 @@ module Text.Pandoc.Lua.Global
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import HsLua as Lua
|
import HsLua as Lua
|
||||||
|
import HsLua.Module.Version (pushVersion)
|
||||||
import Paths_pandoc (version)
|
import Paths_pandoc (version)
|
||||||
import Text.Pandoc.Class.CommonState (CommonState)
|
import Text.Pandoc.Class.CommonState (CommonState)
|
||||||
import Text.Pandoc.Definition (Pandoc (Pandoc), pandocTypesVersion)
|
import Text.Pandoc.Definition (Pandoc (Pandoc), pandocTypesVersion)
|
||||||
|
@ -48,7 +49,7 @@ setGlobal global = case global of
|
||||||
Lua.push format
|
Lua.push format
|
||||||
Lua.setglobal "FORMAT"
|
Lua.setglobal "FORMAT"
|
||||||
PANDOC_API_VERSION -> do
|
PANDOC_API_VERSION -> do
|
||||||
Lua.push pandocTypesVersion
|
pushVersion pandocTypesVersion
|
||||||
Lua.setglobal "PANDOC_API_VERSION"
|
Lua.setglobal "PANDOC_API_VERSION"
|
||||||
PANDOC_DOCUMENT doc -> do
|
PANDOC_DOCUMENT doc -> do
|
||||||
pushUD typePandocLazy doc
|
pushUD typePandocLazy doc
|
||||||
|
@ -63,7 +64,7 @@ setGlobal global = case global of
|
||||||
pushCommonState commonState
|
pushCommonState commonState
|
||||||
Lua.setglobal "PANDOC_STATE"
|
Lua.setglobal "PANDOC_STATE"
|
||||||
PANDOC_VERSION -> do
|
PANDOC_VERSION -> do
|
||||||
Lua.push version
|
pushVersion version
|
||||||
Lua.setglobal "PANDOC_VERSION"
|
Lua.setglobal "PANDOC_VERSION"
|
||||||
|
|
||||||
-- | Readonly and lazy pandoc objects.
|
-- | Readonly and lazy pandoc objects.
|
||||||
|
|
|
@ -16,5 +16,4 @@ import Text.Pandoc.Lua.Marshaling.CommonState ()
|
||||||
import Text.Pandoc.Lua.Marshaling.Context ()
|
import Text.Pandoc.Lua.Marshaling.Context ()
|
||||||
import Text.Pandoc.Lua.Marshaling.PandocError()
|
import Text.Pandoc.Lua.Marshaling.PandocError()
|
||||||
import Text.Pandoc.Lua.Marshaling.ReaderOptions ()
|
import Text.Pandoc.Lua.Marshaling.ReaderOptions ()
|
||||||
import Text.Pandoc.Lua.Marshaling.Version ()
|
|
||||||
import Text.Pandoc.Lua.ErrorConversion ()
|
import Text.Pandoc.Lua.ErrorConversion ()
|
||||||
|
|
|
@ -48,7 +48,9 @@ import Control.Monad.Catch (throwM)
|
||||||
import Control.Monad ((<$!>), (>=>))
|
import Control.Monad ((<$!>), (>=>))
|
||||||
import Data.Data (showConstr, toConstr)
|
import Data.Data (showConstr, toConstr)
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
|
import Data.Version (Version)
|
||||||
import HsLua hiding (Operation (Div))
|
import HsLua hiding (Operation (Div))
|
||||||
|
import HsLua.Module.Version (peekVersionFuzzy)
|
||||||
import Text.Pandoc.Definition
|
import Text.Pandoc.Definition
|
||||||
import Text.Pandoc.Error (PandocError (PandocLuaError))
|
import Text.Pandoc.Error (PandocError (PandocLuaError))
|
||||||
import Text.Pandoc.Lua.Util (pushViaConstr', pushViaConstructor)
|
import Text.Pandoc.Lua.Util (pushViaConstr', pushViaConstructor)
|
||||||
|
@ -616,5 +618,8 @@ instance Peekable Meta where
|
||||||
instance Peekable Pandoc where
|
instance Peekable Pandoc where
|
||||||
peek = forcePeek . peekPandoc
|
peek = forcePeek . peekPandoc
|
||||||
|
|
||||||
|
instance Peekable Version where
|
||||||
|
peek = forcePeek . peekVersionFuzzy
|
||||||
|
|
||||||
instance {-# OVERLAPPING #-} Peekable Attr where
|
instance {-# OVERLAPPING #-} Peekable Attr where
|
||||||
peek = forcePeek . peekAttr
|
peek = forcePeek . peekAttr
|
||||||
|
|
|
@ -1,118 +0,0 @@
|
||||||
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
|
||||||
{-# LANGUAGE LambdaCase #-}
|
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
|
||||||
{- |
|
|
||||||
Module : Text.Pandoc.Lua.Marshaling.Version
|
|
||||||
Copyright : © 2019-2021 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
|
|
||||||
, peekVersionFuzzy
|
|
||||||
)
|
|
||||||
where
|
|
||||||
|
|
||||||
import Data.Maybe (fromMaybe)
|
|
||||||
import Data.Version (Version (..), makeVersion, parseVersion, showVersion)
|
|
||||||
import HsLua as Lua
|
|
||||||
import Safe (lastMay)
|
|
||||||
import Text.ParserCombinators.ReadP (readP_to_S)
|
|
||||||
import qualified Text.Pandoc.UTF8 as UTF8
|
|
||||||
|
|
||||||
instance Peekable Version where
|
|
||||||
peek = forcePeek . peekVersionFuzzy
|
|
||||||
|
|
||||||
instance Pushable Version where
|
|
||||||
push = pushVersion
|
|
||||||
|
|
||||||
-- | Push a @'Version'@ element to the Lua stack.
|
|
||||||
pushVersion :: LuaError e => Pusher e Version
|
|
||||||
pushVersion = pushUD typeVersion
|
|
||||||
|
|
||||||
peekVersionFuzzy :: LuaError e => Peeker e Version
|
|
||||||
peekVersionFuzzy idx = retrieving "Version" $ liftLua (Lua.ltype idx) >>= \case
|
|
||||||
Lua.TypeUserdata -> peekVersion idx
|
|
||||||
Lua.TypeString -> do
|
|
||||||
versionStr <- peekString idx
|
|
||||||
let parses = readP_to_S parseVersion versionStr
|
|
||||||
case lastMay parses of
|
|
||||||
Just (v, "") -> return v
|
|
||||||
_ -> Lua.failPeek $
|
|
||||||
UTF8.fromString $ "could not parse as Version: " ++ versionStr
|
|
||||||
|
|
||||||
Lua.TypeNumber -> do
|
|
||||||
(makeVersion . (:[])) <$> peekIntegral idx
|
|
||||||
|
|
||||||
Lua.TypeTable ->
|
|
||||||
makeVersion <$> peekList peekIntegral idx
|
|
||||||
|
|
||||||
_ ->
|
|
||||||
Lua.failPeek "could not peek Version"
|
|
||||||
|
|
||||||
peekVersion :: LuaError e => Peeker e Version
|
|
||||||
peekVersion = peekUD typeVersion
|
|
||||||
|
|
||||||
typeVersion :: LuaError e => DocumentedType e Version
|
|
||||||
typeVersion = deftype "Version"
|
|
||||||
[ operation Eq $ defun "__eq"
|
|
||||||
### liftPure2 (==)
|
|
||||||
<#> parameter peekVersionFuzzy "Version" "v1" ""
|
|
||||||
<#> parameter peekVersionFuzzy "Version" "v2" ""
|
|
||||||
=#> functionResult pushBool "boolean" "true iff v1 == v2"
|
|
||||||
, operation Lt $ defun "__lt"
|
|
||||||
### liftPure2 (<)
|
|
||||||
<#> parameter peekVersionFuzzy "Version" "v1" ""
|
|
||||||
<#> parameter peekVersionFuzzy "Version" "v2" ""
|
|
||||||
=#> functionResult pushBool "boolean" "true iff v1 < v2"
|
|
||||||
, operation Le $ defun "__le"
|
|
||||||
### liftPure2 (<=)
|
|
||||||
<#> parameter peekVersionFuzzy "Version" "v1" ""
|
|
||||||
<#> parameter peekVersionFuzzy "Version" "v2" ""
|
|
||||||
=#> functionResult pushBool "boolean" "true iff v1 <= v2"
|
|
||||||
, operation Len $ defun "__len"
|
|
||||||
### liftPure (length . versionBranch)
|
|
||||||
<#> parameter peekVersionFuzzy "Version" "v1" ""
|
|
||||||
=#> functionResult pushIntegral "integer" "number of version components"
|
|
||||||
, operation Tostring $ defun "__tostring"
|
|
||||||
### liftPure showVersion
|
|
||||||
<#> parameter peekVersionFuzzy "Version" "version" ""
|
|
||||||
=#> functionResult pushString "string" "stringified version"
|
|
||||||
]
|
|
||||||
[ method $ defun "must_be_at_least"
|
|
||||||
### must_be_at_least
|
|
||||||
<#> parameter peekVersionFuzzy "Version" "self" "version to check"
|
|
||||||
<#> parameter peekVersionFuzzy "Version" "reference" "minimum version"
|
|
||||||
<#> optionalParameter peekString "string" "msg" "alternative message"
|
|
||||||
=?> "Returns no result, and throws an error if this version is older than reference"
|
|
||||||
]
|
|
||||||
|
|
||||||
-- | 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 :: LuaError e
|
|
||||||
=> Version -> Version -> Maybe String
|
|
||||||
-> LuaE e NumResults
|
|
||||||
must_be_at_least actual expected mMsg = do
|
|
||||||
let msg = fromMaybe versionTooOldMessage mMsg
|
|
||||||
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
|
|
||||||
|
|
||||||
-- | 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 = "expected version %s or newer, got %s"
|
|
|
@ -13,21 +13,21 @@ module Text.Pandoc.Lua.Module.Types
|
||||||
( pushModule
|
( pushModule
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Data.Version (Version)
|
|
||||||
import HsLua (LuaE, NumResults, Peeker, Pusher)
|
import HsLua (LuaE, NumResults, Peeker, Pusher)
|
||||||
import Text.Pandoc.Error (PandocError)
|
import Text.Pandoc.Error (PandocError)
|
||||||
import Text.Pandoc.Lua.ErrorConversion ()
|
import Text.Pandoc.Lua.ErrorConversion ()
|
||||||
import Text.Pandoc.Lua.Marshaling.AST
|
import Text.Pandoc.Lua.Marshaling.AST
|
||||||
import Text.Pandoc.Lua.Marshaling.Version ()
|
|
||||||
import Text.Pandoc.Lua.Util (addFunction)
|
import Text.Pandoc.Lua.Util (addFunction)
|
||||||
|
|
||||||
import qualified HsLua as Lua
|
import qualified HsLua as Lua
|
||||||
|
import qualified HsLua.Module.Version as Version
|
||||||
|
|
||||||
-- | Push the pandoc.types module on the Lua stack.
|
-- | Push the pandoc.types module on the Lua stack.
|
||||||
pushModule :: LuaE PandocError NumResults
|
pushModule :: LuaE PandocError NumResults
|
||||||
pushModule = do
|
pushModule = do
|
||||||
Lua.newtable
|
Lua.newtable
|
||||||
addFunction "Version" (return :: Version -> LuaE PandocError Version)
|
Lua.pushName "Version" *> Lua.pushModule Version.documentedModule
|
||||||
|
*> Lua.rawset (Lua.nth 3)
|
||||||
pushCloneTable
|
pushCloneTable
|
||||||
Lua.setfield (Lua.nth 2) "clone"
|
Lua.setfield (Lua.nth 2) "clone"
|
||||||
return 1
|
return 1
|
||||||
|
|
|
@ -23,6 +23,7 @@ import Data.Default (def)
|
||||||
import Data.Version (Version)
|
import Data.Version (Version)
|
||||||
import HsLua as Lua hiding (pushModule)
|
import HsLua as Lua hiding (pushModule)
|
||||||
import HsLua.Class.Peekable (PeekError)
|
import HsLua.Class.Peekable (PeekError)
|
||||||
|
import HsLua.Module.Version (peekVersionFuzzy, pushVersion)
|
||||||
import Text.Pandoc.Definition
|
import Text.Pandoc.Definition
|
||||||
import Text.Pandoc.Error (PandocError)
|
import Text.Pandoc.Error (PandocError)
|
||||||
import Text.Pandoc.Lua.Marshaling ()
|
import Text.Pandoc.Lua.Marshaling ()
|
||||||
|
@ -32,7 +33,6 @@ import Text.Pandoc.Lua.Marshaling.AST
|
||||||
import Text.Pandoc.Lua.Marshaling.List (pushPandocList)
|
import Text.Pandoc.Lua.Marshaling.List (pushPandocList)
|
||||||
import Text.Pandoc.Lua.Marshaling.SimpleTable
|
import Text.Pandoc.Lua.Marshaling.SimpleTable
|
||||||
( SimpleTable (..), peekSimpleTable, pushSimpleTable )
|
( SimpleTable (..), peekSimpleTable, pushSimpleTable )
|
||||||
import Text.Pandoc.Lua.Marshaling.Version (peekVersionFuzzy, pushVersion)
|
|
||||||
import Text.Pandoc.Lua.PandocLua (PandocLua (unPandocLua))
|
import Text.Pandoc.Lua.PandocLua (PandocLua (unPandocLua))
|
||||||
|
|
||||||
import qualified Data.Digest.Pure.SHA as SHA
|
import qualified Data.Digest.Pure.SHA as SHA
|
||||||
|
|
Loading…
Add table
Reference in a new issue