From 86f82870fa36be7f92d992633616b8810510e87a Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Wed, 16 Nov 2022 19:02:33 +0100 Subject: [PATCH 001/373] Switch to Kupo for getDatumByHash and getDatumsByHashes --- src/Contract/PlutusData.purs | 46 +++++++++++++++++------------------ src/Internal/QueryM/Kupo.purs | 30 +++++++++++++++++++++-- test/Plutip/Contract.purs | 4 +-- 3 files changed, 52 insertions(+), 28 deletions(-) diff --git a/src/Contract/PlutusData.purs b/src/Contract/PlutusData.purs index e380955398..79da0d5409 100644 --- a/src/Contract/PlutusData.purs +++ b/src/Contract/PlutusData.purs @@ -5,7 +5,7 @@ module Contract.PlutusData ( getDatumByHash , getDatumsByHashes - , getDatumsByHashesWithErrors + , getDatumsByHashesWithError , module DataSchema , module Datum , module ExportQueryM @@ -73,11 +73,7 @@ import Ctl.Internal.QueryM , defaultDatumCacheWsConfig , mkDatumCacheWebSocketAff ) as ExportQueryM -import Ctl.Internal.QueryM - ( getDatumByHash - , getDatumsByHashes - , getDatumsByHashesWithErrors - ) as QueryM +import Ctl.Internal.QueryM.Kupo (getDatumByHash, getDatumsByHashes) as Kupo import Ctl.Internal.Serialization (serializeData) as Serialization import Ctl.Internal.ToData ( class ToData @@ -93,7 +89,7 @@ import Ctl.Internal.ToData , toDataWithSchema ) as ToData import Ctl.Internal.TypeLevel.Nat (Nat, S, Z) as Nat -import Ctl.Internal.Types.Datum (DataHash) +import Ctl.Internal.Types.Datum (DataHash, Datum) import Ctl.Internal.Types.Datum (DataHash(DataHash), Datum(Datum), unitDatum) as Datum import Ctl.Internal.Types.OutputDatum ( OutputDatum(NoOutputDatum, OutputDatumHash, OutputDatum) @@ -107,30 +103,32 @@ import Ctl.Internal.Types.Redeemer , redeemerHash , unitRedeemer ) as Redeemer -import Data.Either (Either) +import Data.Bifunctor (lmap) +import Data.Either (Either, hush) import Data.Map (Map) import Data.Maybe (Maybe) --- | Get a `PlutusData` given a `DatumHash`. -getDatumByHash - :: forall (r :: Row Type) - . DataHash - -> Contract r (Maybe Datum.Datum) -getDatumByHash = wrapContract <<< QueryM.getDatumByHash +-- | Retrieve the full resolved datum associated to a given datum hash. +getDatumByHash :: forall (r :: Row Type). DataHash -> Contract r (Maybe Datum) +getDatumByHash = wrapContract <<< map (join <<< hush) <<< Kupo.getDatumByHash --- | Get `PlutusData`s given an `Array` of `DataHash`. --- | This function discards all possible error getting a `DataHash`. +-- | Retrieve full resolved datums associated with given datum hashes. +-- | The resulting `Map` will only contain datums that have been successfully +-- | resolved. This function returns `Nothing` in case of an error during +-- | response processing (bad HTTP code or response parsing error). getDatumsByHashes :: forall (r :: Row Type) . Array DataHash - -> Contract r (Map DataHash Datum.Datum) -getDatumsByHashes = wrapContract <<< QueryM.getDatumsByHashes + -> Contract r (Maybe (Map DataHash Datum)) +getDatumsByHashes = wrapContract <<< map hush <<< Kupo.getDatumsByHashes --- | Get `PlutusData`s given an `Array` of `DataHash`. --- | In case of error, the returned string contains the needed information. -getDatumsByHashesWithErrors +-- | Retrieve full resolved datums associated with given datum hashes. +-- | The resulting `Map` will only contain datums that have been successfully +-- | resolved. +getDatumsByHashesWithError :: forall (r :: Row Type) . Array DataHash - -> Contract r (Map DataHash (Either String Datum.Datum)) -getDatumsByHashesWithErrors = wrapContract <<< - QueryM.getDatumsByHashesWithErrors + -> Contract r (Either String (Map DataHash Datum)) +getDatumsByHashesWithError = + wrapContract <<< map (lmap show) <<< Kupo.getDatumsByHashes + diff --git a/src/Internal/QueryM/Kupo.purs b/src/Internal/QueryM/Kupo.purs index 915dfd2406..ce3fd48a29 100644 --- a/src/Internal/QueryM/Kupo.purs +++ b/src/Internal/QueryM/Kupo.purs @@ -1,5 +1,10 @@ module Ctl.Internal.QueryM.Kupo - ( getUtxoByOref + ( getDatumByHash + , getDatumsByHashes + , getScriptByHash + , getScriptsByHashes + , getUtxoByOref + , isTxConfirmed , utxosAt ) where @@ -69,13 +74,14 @@ import Ctl.Internal.Types.Transaction ( TransactionHash(TransactionHash) , TransactionInput(TransactionInput) ) +import Data.Array (null) as Array import Data.BigInt (BigInt) import Data.Either (Either(Left, Right), note) import Data.Foldable (fold) import Data.Generic.Rep (class Generic) import Data.HTTP.Method (Method(GET)) import Data.Map (Map) -import Data.Map (fromFoldable, lookup) as Map +import Data.Map (catMaybes, fromFoldable, lookup) as Map import Data.Maybe (Maybe(Just, Nothing), fromMaybe) import Data.Newtype (class Newtype, unwrap, wrap) import Data.Show.Generic (genericShow) @@ -122,12 +128,32 @@ getDatumByHash (DataHash dataHashBytes) = do kupoGetRequest endpoint <#> map unwrapKupoDatum <<< handleAffjaxResponse +getDatumsByHashes + :: Array DataHash -> QueryM (Either ClientError (Map DataHash Datum)) +getDatumsByHashes = + runExceptT + <<< map (Map.catMaybes <<< Map.fromFoldable) + <<< parTraverse (\dh -> Tuple dh <$> ExceptT (getDatumByHash dh)) + getScriptByHash :: ScriptHash -> QueryM (Either ClientError (Maybe ScriptRef)) getScriptByHash scriptHash = do let endpoint = "/scripts/" <> rawBytesToHex (scriptHashToBytes scriptHash) kupoGetRequest endpoint <#> map unwrapKupoScriptRef <<< handleAffjaxResponse +getScriptsByHashes + :: Array ScriptHash -> QueryM (Either ClientError (Map ScriptHash ScriptRef)) +getScriptsByHashes = + runExceptT + <<< map (Map.catMaybes <<< Map.fromFoldable) + <<< parTraverse (\sh -> Tuple sh <$> ExceptT (getScriptByHash sh)) + +isTxConfirmed :: TransactionHash -> QueryM (Either ClientError Boolean) +isTxConfirmed (TransactionHash txHash) = do + let endpoint = "/matches/*@" <> byteArrayToHex txHash + kupoGetRequest endpoint + <#> map (not <<< Array.null :: Array Aeson -> _) <<< handleAffjaxResponse + -------------------------------------------------------------------------------- -- `utxosAt` response parsing -------------------------------------------------------------------------------- diff --git a/test/Plutip/Contract.purs b/test/Plutip/Contract.purs index 4887a8d967..943bd87b99 100644 --- a/test/Plutip/Contract.purs +++ b/test/Plutip/Contract.purs @@ -27,7 +27,7 @@ import Contract.PlutusData , Redeemer(Redeemer) , getDatumByHash , getDatumsByHashes - , getDatumsByHashesWithErrors + , getDatumsByHashesWithError ) import Contract.Prelude (mconcat) import Contract.Prim.ByteArray (byteArrayFromAscii, hexToByteArrayUnsafe) @@ -694,7 +694,7 @@ suite = do , mkDatumHash "e8cb7d18e81b0be160c114c563c020dcc7bf148a1994b73912db3ea1318d488b" ] - logInfo' <<< show =<< getDatumsByHashesWithErrors + logInfo' <<< show =<< getDatumsByHashesWithError [ mkDatumHash "777093fe6dfffdb3bd2033ad71745f5e2319589e36be4bc9c8cca65ac2bfeb8f" , mkDatumHash From 4cc3b7b51b01bc53a7236c47fafd6d5570078f4b Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Thu, 17 Nov 2022 12:13:51 +0100 Subject: [PATCH 002/373] Use Kupo for awaitTxConfirmed --- src/Internal/QueryM/AwaitTxConfirmed.purs | 28 ++++++++++++----------- 1 file changed, 15 insertions(+), 13 deletions(-) diff --git a/src/Internal/QueryM/AwaitTxConfirmed.purs b/src/Internal/QueryM/AwaitTxConfirmed.purs index 09b5f8c1ff..2240b56b6e 100644 --- a/src/Internal/QueryM/AwaitTxConfirmed.purs +++ b/src/Internal/QueryM/AwaitTxConfirmed.purs @@ -7,14 +7,15 @@ module Ctl.Internal.QueryM.AwaitTxConfirmed import Prelude import Control.Parallel (parOneOf) -import Ctl.Internal.QueryM (QueryM, getChainTip, mkDatumCacheRequest) -import Ctl.Internal.QueryM.DatumCacheWsp (getTxByHashCall) +import Ctl.Internal.QueryM (QueryM, getChainTip) +import Ctl.Internal.QueryM.Kupo (isTxConfirmed) as Kupo import Ctl.Internal.QueryM.Ogmios (TxHash) import Ctl.Internal.QueryM.WaitUntilSlot (waitUntilSlot) import Ctl.Internal.Serialization.Address (Slot) import Ctl.Internal.Types.BigNum as BigNum import Ctl.Internal.Types.Chain as Chain -import Data.Maybe (isJust, maybe) +import Data.Either (either) +import Data.Maybe (maybe) import Data.Newtype (unwrap, wrap) import Data.Number (infinity) import Data.Time.Duration (Milliseconds, Seconds(Seconds), fromDuration) @@ -40,12 +41,9 @@ awaitTxConfirmedWithTimeout timeoutSeconds txHash = -- Try to find the TX indefinitely, with a waiting period between each -- request findTx :: QueryM Boolean - findTx = do - isTxFound <- isJust <<< unwrap <$> mkDatumCacheRequest getTxByHashCall - _.getTxByHash - txHash - if isTxFound then pure true - else liftAff (delay delayTime) *> findTx + findTx = + isTxConfirmed txHash >>= \found -> + if found then pure true else liftAff (delay delayTime) *> findTx -- Wait until the timeout elapses and return false waitAndFail :: QueryM Boolean @@ -60,9 +58,8 @@ awaitTxConfirmedWithTimeout timeoutSeconds txHash = delayTime = wrap 1000.0 awaitTxConfirmedWithTimeoutSlots :: Int -> TxHash -> QueryM Unit -awaitTxConfirmedWithTimeoutSlots timeoutSlots txHash = do +awaitTxConfirmedWithTimeoutSlots timeoutSlots txHash = getCurrentSlot >>= addSlots timeoutSlots >>= go - where getCurrentSlot :: QueryM Slot getCurrentSlot = getChainTip >>= case _ of @@ -78,8 +75,8 @@ awaitTxConfirmedWithTimeoutSlots timeoutSlots txHash = do go :: Slot -> QueryM Unit go timeout = - mkDatumCacheRequest getTxByHashCall _.getTxByHash txHash >>= \found -> - unless (isJust $ unwrap found) do + isTxConfirmed txHash >>= \found -> + unless found do slot <- getCurrentSlot when (slot >= timeout) do liftEffect $ throw $ @@ -87,3 +84,8 @@ awaitTxConfirmedWithTimeoutSlots timeoutSlots txHash = do \ timeout exceeded, Transaction not confirmed" void $ addSlots 1 slot >>= waitUntilSlot go timeout + +isTxConfirmed :: TxHash -> QueryM Boolean +isTxConfirmed txHash = + Kupo.isTxConfirmed (wrap txHash) + >>= either (liftEffect <<< throw <<< show) pure From 1e106cde30f6b606ee07cf7449c4dd9374636030 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Thu, 17 Nov 2022 12:14:35 +0100 Subject: [PATCH 003/373] Fix formatting --- src/Internal/QueryM/AwaitTxConfirmed.purs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Internal/QueryM/AwaitTxConfirmed.purs b/src/Internal/QueryM/AwaitTxConfirmed.purs index 2240b56b6e..9a6264b543 100644 --- a/src/Internal/QueryM/AwaitTxConfirmed.purs +++ b/src/Internal/QueryM/AwaitTxConfirmed.purs @@ -75,7 +75,7 @@ awaitTxConfirmedWithTimeoutSlots timeoutSlots txHash = go :: Slot -> QueryM Unit go timeout = - isTxConfirmed txHash >>= \found -> + isTxConfirmed txHash >>= \found -> unless found do slot <- getCurrentSlot when (slot >= timeout) do @@ -87,5 +87,5 @@ awaitTxConfirmedWithTimeoutSlots timeoutSlots txHash = isTxConfirmed :: TxHash -> QueryM Boolean isTxConfirmed txHash = - Kupo.isTxConfirmed (wrap txHash) - >>= either (liftEffect <<< throw <<< show) pure + Kupo.isTxConfirmed (wrap txHash) + >>= either (liftEffect <<< throw <<< show) pure From 11b5591b165c6f6ff06552891a8692951e7a25f9 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Mon, 21 Nov 2022 18:24:10 +0100 Subject: [PATCH 004/373] WIP: Add QueryHandle and QueryBackend --- src/Contract/Monad.purs | 7 +++-- src/Contract/Utxos.purs | 6 ++-- src/Internal/Plutip/Server.purs | 4 ++- src/Internal/QueryM.purs | 26 ++++++++++++----- src/Internal/QueryM/Blockfrost.purs | 17 +++++++++++ src/Internal/QueryM/Config.purs | 4 ++- src/Internal/QueryM/Kupo.purs | 3 +- src/Internal/QueryM/QueryHandle.purs | 43 ++++++++++++++++++++++++++++ 8 files changed, 95 insertions(+), 15 deletions(-) create mode 100644 src/Internal/QueryM/Blockfrost.purs create mode 100644 src/Internal/QueryM/QueryHandle.purs diff --git a/src/Contract/Monad.purs b/src/Contract/Monad.purs index 34a2e8dfc2..7f01807ccc 100644 --- a/src/Contract/Monad.purs +++ b/src/Contract/Monad.purs @@ -110,6 +110,7 @@ import Effect.Aff.Class (class MonadAff, liftAff) import Effect.Class (class MonadEffect, liftEffect) import Effect.Exception (Error, throw) import Prim.TypeError (class Warn, Text) +import Undefined (undefined) -- | The `Contract` monad is a newtype wrapper over `QueryM` which is `ReaderT` -- | on `QueryConfig` over asynchronous effects, `Aff`. Throwing and catching @@ -307,7 +308,8 @@ mkContractEnv } = do let config = - { ctlServerConfig + { backend: undefined -- TODO: + , ctlServerConfig , ogmiosConfig , datumCacheConfig , kupoConfig @@ -366,7 +368,8 @@ withContractEnv let config :: QueryConfig config = - { ctlServerConfig + { backend: undefined -- TODO: + , ctlServerConfig , ogmiosConfig , datumCacheConfig , kupoConfig diff --git a/src/Contract/Utxos.purs b/src/Contract/Utxos.purs index 76bf4585f8..f60cc883fc 100644 --- a/src/Contract/Utxos.purs +++ b/src/Contract/Utxos.purs @@ -26,11 +26,10 @@ import Ctl.Internal.Plutus.Types.Transaction (UtxoMap) as X import Ctl.Internal.Plutus.Types.Value (Value) import Ctl.Internal.QueryM (getNetworkId) import Ctl.Internal.QueryM.Kupo (getUtxoByOref, utxosAt) as Kupo +import Ctl.Internal.QueryM.QueryHandle (getQueryHandle) import Ctl.Internal.QueryM.Utxos (getWalletBalance, getWalletUtxos) as Utxos import Data.Maybe (Maybe) --- | This module defines the functionality for requesting utxos via Kupo. - -- | Queries for utxos at the given Plutus `Address`. utxosAt :: forall (r :: Row Type) (address :: Type) @@ -40,7 +39,8 @@ utxosAt utxosAt address = do networkId <- wrapContract getNetworkId let cardanoAddr = fromPlutusAddress networkId (getAddress address) - cardanoUtxoMap <- liftedE $ wrapContract $ Kupo.utxosAt cardanoAddr + queryHandle <- wrapContract getQueryHandle + cardanoUtxoMap <- liftedE $ wrapContract $ queryHandle.utxosAt cardanoAddr toPlutusUtxoMap cardanoUtxoMap # liftContractM "utxosAt: failed to convert utxos" diff --git a/src/Internal/Plutip/Server.purs b/src/Internal/Plutip/Server.purs index 996c79a146..41417bfbb7 100644 --- a/src/Internal/Plutip/Server.purs +++ b/src/Internal/Plutip/Server.purs @@ -111,6 +111,7 @@ import Node.ChildProcess (defaultSpawnOptions) import Node.FS.Sync (exists, mkdir) as FSSync import Node.Path (FilePath, dirname) import Type.Prelude (Proxy(Proxy)) +import Undefined (undefined) -- | Run a single `Contract` in Plutip environment. runPlutipContract @@ -747,7 +748,8 @@ mkClusterContractEnv plutipCfg logger customLogger = do pparams <- QueryM.getProtocolParametersAff ogmiosWs logger pure $ ContractEnv { config: - { ctlServerConfig: plutipCfg.ctlServerConfig + { backend: undefined -- TODO: + , ctlServerConfig: plutipCfg.ctlServerConfig , ogmiosConfig: plutipCfg.ogmiosConfig , datumCacheConfig: plutipCfg.ogmiosDatumCacheConfig , kupoConfig: plutipCfg.kupoConfig diff --git a/src/Internal/QueryM.purs b/src/Internal/QueryM.purs index dff240290a..0debdbdb66 100644 --- a/src/Internal/QueryM.purs +++ b/src/Internal/QueryM.purs @@ -17,6 +17,7 @@ module Ctl.Internal.QueryM , Logger , OgmiosListeners , OgmiosWebSocket + , QueryBackend(BlockfrostBackend, CtlBackend) , QueryConfig , QueryM , ParQueryM @@ -277,6 +278,7 @@ import Effect.Class (class MonadEffect, liftEffect) import Effect.Exception (Error, error, throw, try) import Effect.Ref as Ref import Foreign.Object as Object +import Undefined (undefined) import Untagged.Union (asOneOf) -- This module defines an Aff interface for Ogmios Websocket Queries @@ -313,6 +315,15 @@ emptyHooks = , onError: Nothing } +data QueryBackend + = CtlBackend + { ogmiosConfig :: ServerConfig + , kupoConfig :: ServerConfig + } + | BlockfrostBackend + { blockfrostConfig :: ServerConfig + } + -- | `QueryConfig` contains a complete specification on how to initialize a -- | `QueryM` environment. -- | It includes: @@ -322,10 +333,11 @@ emptyHooks = -- | - wallet setup instructions -- | - optional custom logger type QueryConfig = - { ctlServerConfig :: Maybe ServerConfig - , ogmiosConfig :: ServerConfig - , datumCacheConfig :: ServerConfig - , kupoConfig :: ServerConfig + { backend :: QueryBackend + , ctlServerConfig :: Maybe ServerConfig + , datumCacheConfig :: ServerConfig -- TODO: make optional + , ogmiosConfig :: ServerConfig -- TODO: remove, use `QueryBackend` instead + , kupoConfig :: ServerConfig -- TODO: remove, use `QueryBackend` instead , networkId :: NetworkId , logLevel :: LogLevel , walletSpec :: Maybe WalletSpec @@ -343,11 +355,11 @@ type QueryConfig = -- | - A data structure to keep UTxOs that has already been spent -- | - Current protocol parameters type QueryRuntime = - { ogmiosWs :: OgmiosWebSocket - , datumCacheWs :: DatumCacheWebSocket + { ogmiosWs :: OgmiosWebSocket -- TODO: make optional + , datumCacheWs :: DatumCacheWebSocket -- TODO: make optional , wallet :: Maybe Wallet , usedTxOuts :: UsedTxOuts - , pparams :: Ogmios.ProtocolParameters + , pparams :: Ogmios.ProtocolParameters -- TODO: fetch using specified backend } -- | `QueryEnv` contains everything needed for `QueryM` to run. diff --git a/src/Internal/QueryM/Blockfrost.purs b/src/Internal/QueryM/Blockfrost.purs new file mode 100644 index 0000000000..96944d23dd --- /dev/null +++ b/src/Internal/QueryM/Blockfrost.purs @@ -0,0 +1,17 @@ +module Ctl.Internal.QueryM.Blockfrost where + +import Prelude + +import Ctl.Internal.Cardano.Types.Transaction (UtxoMap) +import Ctl.Internal.QueryM (ClientError, QueryM) +import Ctl.Internal.Serialization.Address (Address) +import Ctl.Internal.Types.Datum (DataHash, Datum) +import Data.Either (Either) +import Data.Maybe (Maybe) +import Undefined (undefined) + +utxosAt :: Address -> QueryM (Either ClientError UtxoMap) +utxosAt = undefined + +getDatumByHash :: DataHash -> QueryM (Either ClientError (Maybe Datum)) +getDatumByHash = undefined diff --git a/src/Internal/QueryM/Config.purs b/src/Internal/QueryM/Config.purs index 531441e216..14888caea8 100644 --- a/src/Internal/QueryM/Config.purs +++ b/src/Internal/QueryM/Config.purs @@ -13,10 +13,12 @@ import Ctl.Internal.QueryM.ServerConfig import Ctl.Internal.Serialization.Address (NetworkId(TestnetId)) import Data.Log.Level (LogLevel(Error, Trace)) import Data.Maybe (Maybe(Just, Nothing)) +import Undefined (undefined) testnetTraceQueryConfig :: QueryConfig testnetTraceQueryConfig = - { ctlServerConfig: Just defaultServerConfig + { backend: undefined -- TODO: + , ctlServerConfig: Just defaultServerConfig , ogmiosConfig: defaultOgmiosWsConfig , datumCacheConfig: defaultDatumCacheWsConfig , kupoConfig: defaultKupoServerConfig diff --git a/src/Internal/QueryM/Kupo.purs b/src/Internal/QueryM/Kupo.purs index 915dfd2406..669e9ef97d 100644 --- a/src/Internal/QueryM/Kupo.purs +++ b/src/Internal/QueryM/Kupo.purs @@ -1,5 +1,6 @@ module Ctl.Internal.QueryM.Kupo - ( getUtxoByOref + ( getDatumByHash + , getUtxoByOref , utxosAt ) where diff --git a/src/Internal/QueryM/QueryHandle.purs b/src/Internal/QueryM/QueryHandle.purs new file mode 100644 index 0000000000..66804be02e --- /dev/null +++ b/src/Internal/QueryM/QueryHandle.purs @@ -0,0 +1,43 @@ +module Ctl.Internal.QueryM.QueryHandle where + +import Prelude + +import Control.Monad.Reader.Class (asks) +import Ctl.Internal.Cardano.Types.ScriptRef (ScriptRef) +import Ctl.Internal.Cardano.Types.Transaction (UtxoMap) +import Ctl.Internal.QueryM + ( ClientError + , QueryBackend(BlockfrostBackend, CtlBackend) + , QueryM + ) +import Ctl.Internal.QueryM.Blockfrost (getDatumByHash, utxosAt) as Blockfrost +import Ctl.Internal.QueryM.Kupo (getDatumByHash, utxosAt) as Kupo +import Ctl.Internal.Serialization.Address (Address) +import Ctl.Internal.Serialization.Hash (ScriptHash) +import Ctl.Internal.Types.Datum (DataHash, Datum) +import Data.Either (Either) +import Data.Map (Map) +import Data.Maybe (Maybe) + +type QueryME (a :: Type) = QueryM (Either ClientError a) + +type QueryHandle = + { utxosAt :: Address -> QueryME UtxoMap + , getDatumByHash :: DataHash -> QueryME (Maybe Datum) + -- , getDatumByHashes :: Array DataHash -> QueryME (Map DataHash Datum) + -- , getScriptByHash :: ScriptHash -> QueryME (Maybe ScriptRef) + -- , getScriptsByHashes :: Array ScriptHash -> QueryME (Map ScriptHash ScriptRef) + } + +getQueryHandle :: QueryM QueryHandle +getQueryHandle = + asks (_.backend <<< _.config) <#> case _ of + CtlBackend _ -> + { utxosAt: Kupo.utxosAt + , getDatumByHash: Kupo.getDatumByHash + } + BlockfrostBackend _ -> + { utxosAt: Blockfrost.utxosAt + , getDatumByHash: Blockfrost.getDatumByHash + } + From 76cb19246d455faf76c04f4989ccb0590ff714f5 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Tue, 22 Nov 2022 10:27:52 +0100 Subject: [PATCH 005/373] WIP: Begin rewriting Contract monad to support multiple backends --- src/Contract/Monad.purs | 7 +- src/Contract/Utxos.purs | 4 +- src/Internal/Contract/Monad.purs | 162 +++++++++++++++++++++++++ src/Internal/Contract/QueryHandle.purs | 13 ++ src/Internal/Plutip/Server.purs | 4 +- src/Internal/QueryM.purs | 26 ++-- src/Internal/QueryM/Config.purs | 4 +- src/Internal/QueryM/QueryHandle.purs | 43 ------- 8 files changed, 187 insertions(+), 76 deletions(-) create mode 100644 src/Internal/Contract/Monad.purs create mode 100644 src/Internal/Contract/QueryHandle.purs delete mode 100644 src/Internal/QueryM/QueryHandle.purs diff --git a/src/Contract/Monad.purs b/src/Contract/Monad.purs index 7f01807ccc..34a2e8dfc2 100644 --- a/src/Contract/Monad.purs +++ b/src/Contract/Monad.purs @@ -110,7 +110,6 @@ import Effect.Aff.Class (class MonadAff, liftAff) import Effect.Class (class MonadEffect, liftEffect) import Effect.Exception (Error, throw) import Prim.TypeError (class Warn, Text) -import Undefined (undefined) -- | The `Contract` monad is a newtype wrapper over `QueryM` which is `ReaderT` -- | on `QueryConfig` over asynchronous effects, `Aff`. Throwing and catching @@ -308,8 +307,7 @@ mkContractEnv } = do let config = - { backend: undefined -- TODO: - , ctlServerConfig + { ctlServerConfig , ogmiosConfig , datumCacheConfig , kupoConfig @@ -368,8 +366,7 @@ withContractEnv let config :: QueryConfig config = - { backend: undefined -- TODO: - , ctlServerConfig + { ctlServerConfig , ogmiosConfig , datumCacheConfig , kupoConfig diff --git a/src/Contract/Utxos.purs b/src/Contract/Utxos.purs index f60cc883fc..54a635dda4 100644 --- a/src/Contract/Utxos.purs +++ b/src/Contract/Utxos.purs @@ -26,7 +26,6 @@ import Ctl.Internal.Plutus.Types.Transaction (UtxoMap) as X import Ctl.Internal.Plutus.Types.Value (Value) import Ctl.Internal.QueryM (getNetworkId) import Ctl.Internal.QueryM.Kupo (getUtxoByOref, utxosAt) as Kupo -import Ctl.Internal.QueryM.QueryHandle (getQueryHandle) import Ctl.Internal.QueryM.Utxos (getWalletBalance, getWalletUtxos) as Utxos import Data.Maybe (Maybe) @@ -39,8 +38,7 @@ utxosAt utxosAt address = do networkId <- wrapContract getNetworkId let cardanoAddr = fromPlutusAddress networkId (getAddress address) - queryHandle <- wrapContract getQueryHandle - cardanoUtxoMap <- liftedE $ wrapContract $ queryHandle.utxosAt cardanoAddr + cardanoUtxoMap <- liftedE $ wrapContract $ Kupo.utxosAt cardanoAddr toPlutusUtxoMap cardanoUtxoMap # liftContractM "utxosAt: failed to convert utxos" diff --git a/src/Internal/Contract/Monad.purs b/src/Internal/Contract/Monad.purs new file mode 100644 index 0000000000..c939f8e578 --- /dev/null +++ b/src/Internal/Contract/Monad.purs @@ -0,0 +1,162 @@ +module Ctl.Internal.Contract.Monad where + +import Prelude + +import Control.Monad.Error.Class (class MonadError, class MonadThrow) +import Control.Monad.Logger.Class (class MonadLogger) +import Control.Monad.Reader.Class (class MonadAsk, class MonadReader, ask) +import Control.Monad.Reader.Trans (ReaderT) +import Control.Monad.Rec.Class (class MonadRec) +import Ctl.Internal.Helpers (logWithLevel) +import Ctl.Internal.QueryM (DatumCacheWebSocket, OgmiosWebSocket, Hooks) +import Ctl.Internal.QueryM.Ogmios (ProtocolParameters) as Ogmios +import Ctl.Internal.QueryM.ServerConfig (ServerConfig) +import Ctl.Internal.Serialization.Address (NetworkId) +import Ctl.Internal.Types.UsedTxOuts (UsedTxOuts) +import Ctl.Internal.Wallet (Wallet) +import Ctl.Internal.Wallet.Spec (WalletSpec) +import Data.Log.Level (LogLevel) +import Data.Log.Message (Message) +import Data.Maybe (Maybe, fromMaybe) +import Data.Newtype (class Newtype) +import Effect.Aff (Aff) +import Effect.Aff.Class (liftAff) +import Effect.Class (class MonadEffect) +import Effect.Exception (Error) +import MedeaPrelude (class MonadAff) + +import Undefined (undefined) + +-------------------------------------------------------------------------------- +-- Contract +-------------------------------------------------------------------------------- + +newtype Contract (a :: Type) = Contract (ReaderT ContractEnv Aff a) + +-- Many of these derivations depend on the underlying `ReaderT` and +-- asychronous effects, `Aff`. +derive instance Newtype (Contract a) _ +derive newtype instance Functor Contract +derive newtype instance Apply Contract +derive newtype instance Applicative Contract +derive newtype instance Bind Contract +derive newtype instance Monad Contract +derive newtype instance MonadEffect Contract +derive newtype instance MonadAff Contract +derive newtype instance Semigroup a => Semigroup (Contract a) +derive newtype instance Monoid a => Monoid (Contract a) +derive newtype instance MonadRec Contract +derive newtype instance MonadAsk ContractEnv Contract +derive newtype instance MonadReader ContractEnv Contract +-- Utilise JavaScript's native `Error` via underlying `Aff` for flexibility: +derive newtype instance MonadThrow Error Contract +derive newtype instance MonadError Error Contract + +instance MonadLogger Contract where + log msg = do + config <- ask + let logFunction = fromMaybe logWithLevel config.customLogger + liftAff $ logFunction config.logLevel msg + +-------------------------------------------------------------------------------- +-- ContractEnv +-------------------------------------------------------------------------------- + +data QueryBackend + = CtlBackend + { ogmiosConfig :: ServerConfig + , ogmiosWs :: OgmiosWebSocket + , kupoConfig :: ServerConfig + } + | BlockfrostBackend + { blockfrostConfig :: ServerConfig + } + +type ContractEnv = + { backend :: QueryBackend + , ctlServerConfig :: Maybe ServerConfig + , datumCache :: { config :: ServerConfig, ws :: DatumCacheWebSocket } -- TODO: + -- , datumCache :: Maybe { config :: ServerConfig, ws :: DatumCacheWebSocket } + , networkId :: NetworkId + , logLevel :: LogLevel + , walletSpec :: Maybe WalletSpec + , customLogger :: Maybe (LogLevel -> Message -> Aff Unit) + , suppressLogs :: Boolean + , hooks :: Hooks + , wallet :: Maybe Wallet + , usedTxOuts :: UsedTxOuts + , pparams :: Ogmios.ProtocolParameters -- TODO: + } + +type ContractRuntime = + { ogmiosWs :: Maybe OgmiosWebSocket + , datumCacheWs :: DatumCacheWebSocket + , wallet :: Maybe Wallet + , usedTxOuts :: UsedTxOuts + , pparams :: Ogmios.ProtocolParameters -- TODO: + } + +{- +-- | Initializes a `Contract` environment. Does not ensure finalization. +-- | Consider using `withContractEnv` if possible - otherwise use +-- | `stopContractEnv` to properly finalize. +mkContractEnv + :: Warn + ( Text "Using `mkContractEnv` is not recommended: it does not ensure" + <> Text " `ContractEnv` finalization. Consider using `withContractEnv`" + ) + => ContractParams + -> Aff ContractEnv +mkContractEnv + params@ + { backendParams + , ctlServerConfig + , datumCacheConfig + , networkId + , logLevel + , walletSpec + , customLogger + , suppressLogs + , hooks + } = +-} + +{- mkContractRuntime :: ContractParams -> Aff ContractRuntime +mkContractRuntime params = do + for_ params.hooks.beforeInit (void <<< liftEffect <<< try) + usedTxOuts <- newUsedTxOuts +-} + +-------------------------------------------------------------------------------- +-- ContractParams +-------------------------------------------------------------------------------- + +data QueryBackendParams + = CtlBackendParams + { ogmiosConfig :: ServerConfig + , kupoConfig :: ServerConfig + } + | BlockfrostBackendParams + { blockfrostConfig :: ServerConfig + } + +-- | Options to construct a `ContractEnv` indirectly. +-- | +-- | Use `runContract` to run a `Contract` within an implicity constructed +-- | `ContractEnv` environment, or use `withContractEnv` if your application +-- | contains multiple contracts that can be run in parallel, reusing the same +-- | environment (see `withContractEnv`) +type ContractParams = + { backendParams :: QueryBackendParams + , ctlServerConfig :: Maybe ServerConfig + , datumCacheConfig :: ServerConfig -- TODO: + -- , datumCacheConfig :: Maybe ServerConfig + , networkId :: NetworkId + , logLevel :: LogLevel + , walletSpec :: Maybe WalletSpec + , customLogger :: Maybe (LogLevel -> Message -> Aff Unit) + -- | Suppress logs until an exception is thrown + , suppressLogs :: Boolean + , hooks :: Hooks + } + diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs new file mode 100644 index 0000000000..57eb81eeac --- /dev/null +++ b/src/Internal/Contract/QueryHandle.purs @@ -0,0 +1,13 @@ +module Ctl.Internal.Contract.QueryHandle where +{- +import + + +type QueryHandle (m :: Type -> Type) = + { utxosAt :: Address -> m UtxoMap + , getDatumByHash :: DataHash -> m (Maybe Datum) + , getDatumByHashes :: Array DataHash -> m (Map DataHash Datum) + , getScriptByHash :: ScriptHash -> m (Maybe ScriptRef) + , getScriptsByHashes :: Array ScriptHash -> m (Map ScriptHash ScriptRef) + } +-} diff --git a/src/Internal/Plutip/Server.purs b/src/Internal/Plutip/Server.purs index 41417bfbb7..996c79a146 100644 --- a/src/Internal/Plutip/Server.purs +++ b/src/Internal/Plutip/Server.purs @@ -111,7 +111,6 @@ import Node.ChildProcess (defaultSpawnOptions) import Node.FS.Sync (exists, mkdir) as FSSync import Node.Path (FilePath, dirname) import Type.Prelude (Proxy(Proxy)) -import Undefined (undefined) -- | Run a single `Contract` in Plutip environment. runPlutipContract @@ -748,8 +747,7 @@ mkClusterContractEnv plutipCfg logger customLogger = do pparams <- QueryM.getProtocolParametersAff ogmiosWs logger pure $ ContractEnv { config: - { backend: undefined -- TODO: - , ctlServerConfig: plutipCfg.ctlServerConfig + { ctlServerConfig: plutipCfg.ctlServerConfig , ogmiosConfig: plutipCfg.ogmiosConfig , datumCacheConfig: plutipCfg.ogmiosDatumCacheConfig , kupoConfig: plutipCfg.kupoConfig diff --git a/src/Internal/QueryM.purs b/src/Internal/QueryM.purs index 0debdbdb66..706d2b9f68 100644 --- a/src/Internal/QueryM.purs +++ b/src/Internal/QueryM.purs @@ -17,7 +17,6 @@ module Ctl.Internal.QueryM , Logger , OgmiosListeners , OgmiosWebSocket - , QueryBackend(BlockfrostBackend, CtlBackend) , QueryConfig , QueryM , ParQueryM @@ -278,7 +277,6 @@ import Effect.Class (class MonadEffect, liftEffect) import Effect.Exception (Error, error, throw, try) import Effect.Ref as Ref import Foreign.Object as Object -import Undefined (undefined) import Untagged.Union (asOneOf) -- This module defines an Aff interface for Ogmios Websocket Queries @@ -315,15 +313,6 @@ emptyHooks = , onError: Nothing } -data QueryBackend - = CtlBackend - { ogmiosConfig :: ServerConfig - , kupoConfig :: ServerConfig - } - | BlockfrostBackend - { blockfrostConfig :: ServerConfig - } - -- | `QueryConfig` contains a complete specification on how to initialize a -- | `QueryM` environment. -- | It includes: @@ -333,11 +322,10 @@ data QueryBackend -- | - wallet setup instructions -- | - optional custom logger type QueryConfig = - { backend :: QueryBackend - , ctlServerConfig :: Maybe ServerConfig - , datumCacheConfig :: ServerConfig -- TODO: make optional - , ogmiosConfig :: ServerConfig -- TODO: remove, use `QueryBackend` instead - , kupoConfig :: ServerConfig -- TODO: remove, use `QueryBackend` instead + { ctlServerConfig :: Maybe ServerConfig + , datumCacheConfig :: ServerConfig + , ogmiosConfig :: ServerConfig + , kupoConfig :: ServerConfig , networkId :: NetworkId , logLevel :: LogLevel , walletSpec :: Maybe WalletSpec @@ -355,11 +343,11 @@ type QueryConfig = -- | - A data structure to keep UTxOs that has already been spent -- | - Current protocol parameters type QueryRuntime = - { ogmiosWs :: OgmiosWebSocket -- TODO: make optional - , datumCacheWs :: DatumCacheWebSocket -- TODO: make optional + { ogmiosWs :: OgmiosWebSocket + , datumCacheWs :: DatumCacheWebSocket , wallet :: Maybe Wallet , usedTxOuts :: UsedTxOuts - , pparams :: Ogmios.ProtocolParameters -- TODO: fetch using specified backend + , pparams :: Ogmios.ProtocolParameters } -- | `QueryEnv` contains everything needed for `QueryM` to run. diff --git a/src/Internal/QueryM/Config.purs b/src/Internal/QueryM/Config.purs index 14888caea8..531441e216 100644 --- a/src/Internal/QueryM/Config.purs +++ b/src/Internal/QueryM/Config.purs @@ -13,12 +13,10 @@ import Ctl.Internal.QueryM.ServerConfig import Ctl.Internal.Serialization.Address (NetworkId(TestnetId)) import Data.Log.Level (LogLevel(Error, Trace)) import Data.Maybe (Maybe(Just, Nothing)) -import Undefined (undefined) testnetTraceQueryConfig :: QueryConfig testnetTraceQueryConfig = - { backend: undefined -- TODO: - , ctlServerConfig: Just defaultServerConfig + { ctlServerConfig: Just defaultServerConfig , ogmiosConfig: defaultOgmiosWsConfig , datumCacheConfig: defaultDatumCacheWsConfig , kupoConfig: defaultKupoServerConfig diff --git a/src/Internal/QueryM/QueryHandle.purs b/src/Internal/QueryM/QueryHandle.purs deleted file mode 100644 index 66804be02e..0000000000 --- a/src/Internal/QueryM/QueryHandle.purs +++ /dev/null @@ -1,43 +0,0 @@ -module Ctl.Internal.QueryM.QueryHandle where - -import Prelude - -import Control.Monad.Reader.Class (asks) -import Ctl.Internal.Cardano.Types.ScriptRef (ScriptRef) -import Ctl.Internal.Cardano.Types.Transaction (UtxoMap) -import Ctl.Internal.QueryM - ( ClientError - , QueryBackend(BlockfrostBackend, CtlBackend) - , QueryM - ) -import Ctl.Internal.QueryM.Blockfrost (getDatumByHash, utxosAt) as Blockfrost -import Ctl.Internal.QueryM.Kupo (getDatumByHash, utxosAt) as Kupo -import Ctl.Internal.Serialization.Address (Address) -import Ctl.Internal.Serialization.Hash (ScriptHash) -import Ctl.Internal.Types.Datum (DataHash, Datum) -import Data.Either (Either) -import Data.Map (Map) -import Data.Maybe (Maybe) - -type QueryME (a :: Type) = QueryM (Either ClientError a) - -type QueryHandle = - { utxosAt :: Address -> QueryME UtxoMap - , getDatumByHash :: DataHash -> QueryME (Maybe Datum) - -- , getDatumByHashes :: Array DataHash -> QueryME (Map DataHash Datum) - -- , getScriptByHash :: ScriptHash -> QueryME (Maybe ScriptRef) - -- , getScriptsByHashes :: Array ScriptHash -> QueryME (Map ScriptHash ScriptRef) - } - -getQueryHandle :: QueryM QueryHandle -getQueryHandle = - asks (_.backend <<< _.config) <#> case _ of - CtlBackend _ -> - { utxosAt: Kupo.utxosAt - , getDatumByHash: Kupo.getDatumByHash - } - BlockfrostBackend _ -> - { utxosAt: Blockfrost.utxosAt - , getDatumByHash: Blockfrost.getDatumByHash - } - From 763933110d534dfd71bfd90c1e52337fc5925867 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Tue, 22 Nov 2022 13:15:15 +0100 Subject: [PATCH 006/373] WIP: Rewrite Contract monad to support multiple backends --- src/Internal/Contract/Monad.purs | 180 +++++++++++++++++++------ src/Internal/Contract/QueryHandle.purs | 49 +++++-- 2 files changed, 177 insertions(+), 52 deletions(-) diff --git a/src/Internal/Contract/Monad.purs b/src/Internal/Contract/Monad.purs index c939f8e578..8ab51dd6fd 100644 --- a/src/Internal/Contract/Monad.purs +++ b/src/Internal/Contract/Monad.purs @@ -5,26 +5,41 @@ import Prelude import Control.Monad.Error.Class (class MonadError, class MonadThrow) import Control.Monad.Logger.Class (class MonadLogger) import Control.Monad.Reader.Class (class MonadAsk, class MonadReader, ask) -import Control.Monad.Reader.Trans (ReaderT) +import Control.Monad.Reader.Trans (ReaderT, runReaderT) import Control.Monad.Rec.Class (class MonadRec) +import Control.Parallel (parallel, sequential) import Ctl.Internal.Helpers (logWithLevel) -import Ctl.Internal.QueryM (DatumCacheWebSocket, OgmiosWebSocket, Hooks) +import Ctl.Internal.QueryM + ( DatumCacheWebSocket + , Hooks + , Logger + , OgmiosWebSocket + , QueryEnv + , QueryM + , mkDatumCacheWebSocketAff + , mkLogger + , mkOgmiosWebSocketAff + , mkWalletBySpec + ) import Ctl.Internal.QueryM.Ogmios (ProtocolParameters) as Ogmios import Ctl.Internal.QueryM.ServerConfig (ServerConfig) import Ctl.Internal.Serialization.Address (NetworkId) -import Ctl.Internal.Types.UsedTxOuts (UsedTxOuts) +import Ctl.Internal.Types.UsedTxOuts (UsedTxOuts, newUsedTxOuts) import Ctl.Internal.Wallet (Wallet) import Ctl.Internal.Wallet.Spec (WalletSpec) import Data.Log.Level (LogLevel) import Data.Log.Message (Message) -import Data.Maybe (Maybe, fromMaybe) -import Data.Newtype (class Newtype) +import Data.Maybe (Maybe(Just, Nothing), fromJust, fromMaybe) +import Data.Newtype (class Newtype, unwrap) +import Data.Traversable (for_, traverse) import Effect.Aff (Aff) import Effect.Aff.Class (liftAff) -import Effect.Class (class MonadEffect) -import Effect.Exception (Error) +import Effect.Class (class MonadEffect, liftEffect) +import Effect.Exception (Error, try) +import Effect.Ref (new) as Ref import MedeaPrelude (class MonadAff) - +import Partial.Unsafe (unsafePartial) +import Prim.TypeError (class Warn, Text) import Undefined (undefined) -------------------------------------------------------------------------------- @@ -62,15 +77,19 @@ instance MonadLogger Contract where -- ContractEnv -------------------------------------------------------------------------------- +type CtlBackend = + { ogmiosConfig :: ServerConfig + , ogmiosWs :: OgmiosWebSocket + , kupoConfig :: ServerConfig + } + +type BlockfrostBackend = + { blockfrostConfig :: ServerConfig + } + data QueryBackend - = CtlBackend - { ogmiosConfig :: ServerConfig - , ogmiosWs :: OgmiosWebSocket - , kupoConfig :: ServerConfig - } - | BlockfrostBackend - { blockfrostConfig :: ServerConfig - } + = CtlBackend CtlBackend + | BlockfrostBackend BlockfrostBackend type ContractEnv = { backend :: QueryBackend @@ -88,44 +107,87 @@ type ContractEnv = , pparams :: Ogmios.ProtocolParameters -- TODO: } -type ContractRuntime = - { ogmiosWs :: Maybe OgmiosWebSocket - , datumCacheWs :: DatumCacheWebSocket - , wallet :: Maybe Wallet - , usedTxOuts :: UsedTxOuts - , pparams :: Ogmios.ProtocolParameters -- TODO: - } - -{- -- | Initializes a `Contract` environment. Does not ensure finalization. -- | Consider using `withContractEnv` if possible - otherwise use -- | `stopContractEnv` to properly finalize. mkContractEnv :: Warn - ( Text "Using `mkContractEnv` is not recommended: it does not ensure" - <> Text " `ContractEnv` finalization. Consider using `withContractEnv`" + ( Text + "Using `mkContractEnv` is not recommended: it does not ensure `ContractEnv` finalization. Consider using `withContractEnv`" ) => ContractParams -> Aff ContractEnv -mkContractEnv - params@ - { backendParams - , ctlServerConfig - , datumCacheConfig - , networkId - , logLevel - , walletSpec - , customLogger - , suppressLogs - , hooks - } = --} - -{- mkContractRuntime :: ContractParams -> Aff ContractRuntime +mkContractEnv params = do + runtime <- mkContractRuntime params + pure + { backend: mkQueryBackend params.backendParams runtime + , ctlServerConfig: params.ctlServerConfig + , datumCache: { config: params.datumCacheConfig, ws: runtime.datumCacheWs } + , networkId: params.networkId + , logLevel: params.logLevel + , walletSpec: params.walletSpec + , customLogger: params.customLogger + , suppressLogs: params.suppressLogs + , hooks: params.hooks + , wallet: runtime.wallet + , usedTxOuts: runtime.usedTxOuts + , pparams: runtime.pparams + } + where + mkQueryBackend :: QueryBackendParams -> ContractRuntime -> QueryBackend + mkQueryBackend (BlockfrostBackendParams backend) _ = BlockfrostBackend backend + mkQueryBackend (CtlBackendParams { ogmiosConfig, kupoConfig }) runtime = + CtlBackend + { ogmiosConfig + , ogmiosWs: unsafePartial fromJust runtime.ogmiosWs + , kupoConfig + } + +-------------------------------------------------------------------------------- +-- ContractRuntime +-------------------------------------------------------------------------------- + +type ContractRuntime = + { ogmiosWs :: Maybe OgmiosWebSocket + , datumCacheWs :: DatumCacheWebSocket + , wallet :: Maybe Wallet + , usedTxOuts :: UsedTxOuts + , pparams :: Ogmios.ProtocolParameters -- TODO: + } + +-- | Used in `mkContractRuntime` only +data ContractRuntimeModel = ContractRuntimeModel + DatumCacheWebSocket + (Maybe OgmiosWebSocket) + (Maybe Wallet) + +mkContractRuntime :: ContractParams -> Aff ContractRuntime mkContractRuntime params = do for_ params.hooks.beforeInit (void <<< liftEffect <<< try) usedTxOuts <- newUsedTxOuts --} + datumCacheWsRef <- liftEffect $ Ref.new Nothing + ContractRuntimeModel datumCacheWs ogmiosWs wallet <- sequential $ + ContractRuntimeModel + <$> parallel + ( mkDatumCacheWebSocketAff datumCacheWsRef logger + params.datumCacheConfig + ) + <*> parallel + ( traverse (mkOgmiosWebSocketAff datumCacheWsRef logger) + mOgmiosConfig + ) + <*> parallel (traverse mkWalletBySpec params.walletSpec) + pparams <- undefined -- TODO: + pure { ogmiosWs, datumCacheWs, wallet, usedTxOuts, pparams } + where + logger :: Logger + logger = mkLogger params.logLevel params.customLogger + + mOgmiosConfig :: Maybe ServerConfig + mOgmiosConfig = + case params.backendParams of + CtlBackendParams { ogmiosConfig } -> Just ogmiosConfig + _ -> Nothing -------------------------------------------------------------------------------- -- ContractParams @@ -160,3 +222,35 @@ type ContractParams = , hooks :: Hooks } +-------------------------------------------------------------------------------- +-- QueryM +-------------------------------------------------------------------------------- + +runQueryM :: forall (a :: Type). ContractEnv -> CtlBackend -> QueryM a -> Aff a +runQueryM contractEnv ctlBackend = + flip runReaderT (mkQueryEnv contractEnv ctlBackend) <<< unwrap + +mkQueryEnv :: ContractEnv -> CtlBackend -> QueryEnv () +mkQueryEnv contractEnv ctlBackend = + { config: + { ctlServerConfig: contractEnv.ctlServerConfig + , datumCacheConfig: contractEnv.datumCache.config + , ogmiosConfig: ctlBackend.ogmiosConfig + , kupoConfig: ctlBackend.kupoConfig + , networkId: contractEnv.networkId + , logLevel: contractEnv.logLevel + , walletSpec: contractEnv.walletSpec + , customLogger: contractEnv.customLogger + , suppressLogs: contractEnv.suppressLogs + , hooks: contractEnv.hooks + } + , runtime: + { ogmiosWs: ctlBackend.ogmiosWs + , datumCacheWs: contractEnv.datumCache.ws + , wallet: contractEnv.wallet + , usedTxOuts: contractEnv.usedTxOuts + , pparams: contractEnv.pparams + } + , extraConfig: {} + } + diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs index 57eb81eeac..7bdbf9a78a 100644 --- a/src/Internal/Contract/QueryHandle.purs +++ b/src/Internal/Contract/QueryHandle.purs @@ -1,13 +1,44 @@ module Ctl.Internal.Contract.QueryHandle where -{- -import +import Prelude -type QueryHandle (m :: Type -> Type) = - { utxosAt :: Address -> m UtxoMap - , getDatumByHash :: DataHash -> m (Maybe Datum) - , getDatumByHashes :: Array DataHash -> m (Map DataHash Datum) - , getScriptByHash :: ScriptHash -> m (Maybe ScriptRef) - , getScriptsByHashes :: Array ScriptHash -> m (Map ScriptHash ScriptRef) +import Control.Monad.Reader.Class (ask) +import Ctl.Internal.Cardano.Types.Transaction (UtxoMap) +import Ctl.Internal.Contract.Monad + ( BlockfrostBackend + , Contract + , ContractEnv + , CtlBackend + , QueryBackend(BlockfrostBackend, CtlBackend) + , runQueryM + ) +import Ctl.Internal.QueryM (ClientError) +import Ctl.Internal.QueryM.Kupo (utxosAt) as Kupo +import Ctl.Internal.Serialization.Address (Address) +import Data.Either (Either) +import Effect.Aff (Aff) +import Undefined (undefined) + +type QueryHandle = + { utxosAt :: Address -> Aff (Either ClientError UtxoMap) + } + +getQueryHandle :: Contract QueryHandle +getQueryHandle = + ask <#> \contractEnv -> + case contractEnv.backend of + CtlBackend backend -> + queryHandleForCtlBackend contractEnv backend + BlockfrostBackend backend -> + queryHandleForBlockfrostBackend contractEnv backend + +queryHandleForCtlBackend :: ContractEnv -> CtlBackend -> QueryHandle +queryHandleForCtlBackend contractEnv backend = + { utxosAt: + runQueryM contractEnv backend <<< Kupo.utxosAt } --} + +queryHandleForBlockfrostBackend + :: ContractEnv -> BlockfrostBackend -> QueryHandle +queryHandleForBlockfrostBackend = undefined + From 3bafc8232f9e439d67806f05eebaa397632e14fb Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Wed, 23 Nov 2022 13:15:59 +0100 Subject: [PATCH 007/373] Contract: Support auxiliary backends for exclusive functionality --- src/Internal/Contract/Monad.purs | 46 ++++----- src/Internal/Contract/QueryBackend.purs | 121 ++++++++++++++++++++++++ src/Internal/Contract/QueryHandle.purs | 53 +++++++++-- 3 files changed, 180 insertions(+), 40 deletions(-) create mode 100644 src/Internal/Contract/QueryBackend.purs diff --git a/src/Internal/Contract/Monad.purs b/src/Internal/Contract/Monad.purs index 8ab51dd6fd..43a313eaba 100644 --- a/src/Internal/Contract/Monad.purs +++ b/src/Internal/Contract/Monad.purs @@ -8,6 +8,14 @@ import Control.Monad.Reader.Class (class MonadAsk, class MonadReader, ask) import Control.Monad.Reader.Trans (ReaderT, runReaderT) import Control.Monad.Rec.Class (class MonadRec) import Control.Parallel (parallel, sequential) +import Ctl.Internal.Contract.QueryBackend + ( CtlBackend + , QueryBackend(BlockfrostBackend, CtlBackend) + , QueryBackendLabel(CtlBackendLabel) + , QueryBackendParams(BlockfrostBackendParams, CtlBackendParams) + , QueryBackends + , lookupBackend + ) import Ctl.Internal.Helpers (logWithLevel) import Ctl.Internal.QueryM ( DatumCacheWebSocket @@ -77,22 +85,8 @@ instance MonadLogger Contract where -- ContractEnv -------------------------------------------------------------------------------- -type CtlBackend = - { ogmiosConfig :: ServerConfig - , ogmiosWs :: OgmiosWebSocket - , kupoConfig :: ServerConfig - } - -type BlockfrostBackend = - { blockfrostConfig :: ServerConfig - } - -data QueryBackend - = CtlBackend CtlBackend - | BlockfrostBackend BlockfrostBackend - type ContractEnv = - { backend :: QueryBackend + { backend :: QueryBackends QueryBackend , ctlServerConfig :: Maybe ServerConfig , datumCache :: { config :: ServerConfig, ws :: DatumCacheWebSocket } -- TODO: -- , datumCache :: Maybe { config :: ServerConfig, ws :: DatumCacheWebSocket } @@ -120,7 +114,7 @@ mkContractEnv mkContractEnv params = do runtime <- mkContractRuntime params pure - { backend: mkQueryBackend params.backendParams runtime + { backend: mkQueryBackend runtime <$> params.backendParams , ctlServerConfig: params.ctlServerConfig , datumCache: { config: params.datumCacheConfig, ws: runtime.datumCacheWs } , networkId: params.networkId @@ -134,9 +128,10 @@ mkContractEnv params = do , pparams: runtime.pparams } where - mkQueryBackend :: QueryBackendParams -> ContractRuntime -> QueryBackend - mkQueryBackend (BlockfrostBackendParams backend) _ = BlockfrostBackend backend - mkQueryBackend (CtlBackendParams { ogmiosConfig, kupoConfig }) runtime = + mkQueryBackend :: ContractRuntime -> QueryBackendParams -> QueryBackend + mkQueryBackend _ (BlockfrostBackendParams backend) = + BlockfrostBackend backend + mkQueryBackend runtime (CtlBackendParams { ogmiosConfig, kupoConfig }) = CtlBackend { ogmiosConfig , ogmiosWs: unsafePartial fromJust runtime.ogmiosWs @@ -185,7 +180,7 @@ mkContractRuntime params = do mOgmiosConfig :: Maybe ServerConfig mOgmiosConfig = - case params.backendParams of + lookupBackend CtlBackendLabel params.backendParams >>= case _ of CtlBackendParams { ogmiosConfig } -> Just ogmiosConfig _ -> Nothing @@ -193,15 +188,6 @@ mkContractRuntime params = do -- ContractParams -------------------------------------------------------------------------------- -data QueryBackendParams - = CtlBackendParams - { ogmiosConfig :: ServerConfig - , kupoConfig :: ServerConfig - } - | BlockfrostBackendParams - { blockfrostConfig :: ServerConfig - } - -- | Options to construct a `ContractEnv` indirectly. -- | -- | Use `runContract` to run a `Contract` within an implicity constructed @@ -209,7 +195,7 @@ data QueryBackendParams -- | contains multiple contracts that can be run in parallel, reusing the same -- | environment (see `withContractEnv`) type ContractParams = - { backendParams :: QueryBackendParams + { backendParams :: QueryBackends QueryBackendParams , ctlServerConfig :: Maybe ServerConfig , datumCacheConfig :: ServerConfig -- TODO: -- , datumCacheConfig :: Maybe ServerConfig diff --git a/src/Internal/Contract/QueryBackend.purs b/src/Internal/Contract/QueryBackend.purs new file mode 100644 index 0000000000..7b91c08212 --- /dev/null +++ b/src/Internal/Contract/QueryBackend.purs @@ -0,0 +1,121 @@ +module Ctl.Internal.Contract.QueryBackend + ( BlockfrostBackend + , CtlBackend + , QueryBackend(BlockfrostBackend, CtlBackend) + , QueryBackendLabel(BlockfrostBackendLabel, CtlBackendLabel) + , QueryBackendParams(BlockfrostBackendParams, CtlBackendParams) + , QueryBackends + , class HasQueryBackendLabel + , backendLabel + , defaultBackend + , lookupBackend + , mkBackendParams + , mkSingletonBackendParams + ) where + +import Prelude + +import Ctl.Internal.QueryM (OgmiosWebSocket) +import Ctl.Internal.QueryM.ServerConfig (ServerConfig) +import Data.Array (filter, nub) as Array +import Data.Array ((:)) +import Data.Foldable (foldl, length) +import Data.Map (Map) +import Data.Map (empty, insert, lookup, singleton) as Map +import Data.Maybe (Maybe(Just)) +import Effect (Effect) +import Effect.Exception (throw) + +-------------------------------------------------------------------------------- +-- QueryBackends +-------------------------------------------------------------------------------- + +data QueryBackends (backend :: Type) = + QueryBackends backend (Map QueryBackendLabel backend) + +derive instance Functor QueryBackends + +mkSingletonBackendParams + :: QueryBackendParams -> QueryBackends QueryBackendParams +mkSingletonBackendParams = flip QueryBackends Map.empty + +mkBackendParams + :: QueryBackendParams + -> Array QueryBackendParams + -> Effect (QueryBackends QueryBackendParams) +mkBackendParams defaultBackend backends = + case length backends + 1 /= numUniqueBackends of + true -> + throw "mkBackendParams: multiple configs for the same service" + false -> + pure $ QueryBackends defaultBackend $ + foldl (\mp b -> Map.insert (backendLabel b) b mp) Map.empty backends + where + numUniqueBackends :: Int + numUniqueBackends = + length $ Array.nub $ map backendLabel (defaultBackend : backends) + +defaultBackend :: forall (backend :: Type). QueryBackends backend -> backend +defaultBackend (QueryBackends backend _) = backend + +lookupBackend + :: forall (backend :: Type) + . HasQueryBackendLabel backend + => QueryBackendLabel + -> QueryBackends backend + -> Maybe backend +lookupBackend key (QueryBackends defaultBackend backends) + | key == backendLabel defaultBackend = Just defaultBackend + | otherwise = Map.lookup key backends + +-------------------------------------------------------------------------------- +-- QueryBackendLabel +-------------------------------------------------------------------------------- + +data QueryBackendLabel = CtlBackendLabel | BlockfrostBackendLabel + +derive instance Eq QueryBackendLabel +derive instance Ord QueryBackendLabel + +class HasQueryBackendLabel (t :: Type) where + backendLabel :: t -> QueryBackendLabel + +instance HasQueryBackendLabel QueryBackend where + backendLabel (CtlBackend _) = CtlBackendLabel + backendLabel (BlockfrostBackend _) = BlockfrostBackendLabel + +instance HasQueryBackendLabel QueryBackendParams where + backendLabel (CtlBackendParams _) = CtlBackendLabel + backendLabel (BlockfrostBackendParams _) = BlockfrostBackendLabel + +-------------------------------------------------------------------------------- +-- QueryBackend +-------------------------------------------------------------------------------- + +type CtlBackend = + { ogmiosConfig :: ServerConfig + , ogmiosWs :: OgmiosWebSocket + , kupoConfig :: ServerConfig + } + +type BlockfrostBackend = + { blockfrostConfig :: ServerConfig + } + +data QueryBackend + = CtlBackend CtlBackend + | BlockfrostBackend BlockfrostBackend + +-------------------------------------------------------------------------------- +-- QueryBackendParams +-------------------------------------------------------------------------------- + +data QueryBackendParams + = CtlBackendParams + { ogmiosConfig :: ServerConfig + , kupoConfig :: ServerConfig + } + | BlockfrostBackendParams + { blockfrostConfig :: ServerConfig + } + diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs index 7bdbf9a78a..35cccd00d6 100644 --- a/src/Internal/Contract/QueryHandle.purs +++ b/src/Internal/Contract/QueryHandle.purs @@ -3,30 +3,55 @@ module Ctl.Internal.Contract.QueryHandle where import Prelude import Control.Monad.Reader.Class (ask) -import Ctl.Internal.Cardano.Types.Transaction (UtxoMap) +import Ctl.Internal.Cardano.Types.ScriptRef (ScriptRef) +import Ctl.Internal.Cardano.Types.Transaction (TransactionOutput, UtxoMap) import Ctl.Internal.Contract.Monad - ( BlockfrostBackend - , Contract + ( Contract , ContractEnv + , runQueryM + ) +import Ctl.Internal.Contract.QueryBackend + ( BlockfrostBackend , CtlBackend , QueryBackend(BlockfrostBackend, CtlBackend) - , runQueryM + , defaultBackend ) -import Ctl.Internal.QueryM (ClientError) -import Ctl.Internal.QueryM.Kupo (utxosAt) as Kupo +import Ctl.Internal.QueryM (ClientError, QueryM) +import Ctl.Internal.QueryM.Kupo + ( getDatumByHash + , getDatumsByHashes + , getScriptByHash + , getScriptsByHashes + , getUtxoByOref + , isTxConfirmed + , utxosAt + ) as Kupo import Ctl.Internal.Serialization.Address (Address) +import Ctl.Internal.Serialization.Hash (ScriptHash) +import Ctl.Internal.Types.Datum (DataHash, Datum) +import Ctl.Internal.Types.Transaction (TransactionHash, TransactionInput) import Data.Either (Either) +import Data.Map (Map) +import Data.Maybe (Maybe) import Effect.Aff (Aff) import Undefined (undefined) +type AffE (a :: Type) = Aff (Either ClientError a) + type QueryHandle = - { utxosAt :: Address -> Aff (Either ClientError UtxoMap) + { getDatumByHash :: DataHash -> AffE (Maybe Datum) + , getDatumsByHashes :: Array DataHash -> AffE (Map DataHash Datum) + , getScriptByHash :: ScriptHash -> AffE (Maybe ScriptRef) + , getScriptsByHashes :: Array ScriptHash -> AffE (Map ScriptHash ScriptRef) + , getUtxoByOref :: TransactionInput -> AffE (Maybe TransactionOutput) + , isTxConfirmed :: TransactionHash -> AffE Boolean + , utxosAt :: Address -> AffE UtxoMap } getQueryHandle :: Contract QueryHandle getQueryHandle = ask <#> \contractEnv -> - case contractEnv.backend of + case defaultBackend contractEnv.backend of CtlBackend backend -> queryHandleForCtlBackend contractEnv backend BlockfrostBackend backend -> @@ -34,9 +59,17 @@ getQueryHandle = queryHandleForCtlBackend :: ContractEnv -> CtlBackend -> QueryHandle queryHandleForCtlBackend contractEnv backend = - { utxosAt: - runQueryM contractEnv backend <<< Kupo.utxosAt + { getDatumByHash: runQueryM' <<< Kupo.getDatumByHash + , getDatumsByHashes: runQueryM' <<< Kupo.getDatumsByHashes + , getScriptByHash: runQueryM' <<< Kupo.getScriptByHash + , getScriptsByHashes: runQueryM' <<< Kupo.getScriptsByHashes + , getUtxoByOref: runQueryM' <<< Kupo.getUtxoByOref + , isTxConfirmed: runQueryM' <<< Kupo.isTxConfirmed + , utxosAt: runQueryM' <<< Kupo.utxosAt } + where + runQueryM' :: forall (a :: Type). QueryM a -> Aff a + runQueryM' = runQueryM contractEnv backend queryHandleForBlockfrostBackend :: ContractEnv -> BlockfrostBackend -> QueryHandle From 63432990d856e4e1f91fffaf17d7fd7c93c128d4 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Wed, 23 Nov 2022 16:16:29 +0100 Subject: [PATCH 008/373] Adapt various functions for new Contract --- src/Internal/Contract/Monad.purs | 98 ++++++++++++++++++++++++++++++-- 1 file changed, 94 insertions(+), 4 deletions(-) diff --git a/src/Internal/Contract/Monad.purs b/src/Internal/Contract/Monad.purs index 43a313eaba..b0057e5aa1 100644 --- a/src/Internal/Contract/Monad.purs +++ b/src/Internal/Contract/Monad.purs @@ -1,8 +1,22 @@ -module Ctl.Internal.Contract.Monad where +module Ctl.Internal.Contract.Monad + ( Contract(Contract) + , ContractEnv + , ContractParams + , mkContractEnv + , runContract + , runContractInEnv + , runQueryM + , stopContractEnv + , withContractEnv + ) where import Prelude -import Control.Monad.Error.Class (class MonadError, class MonadThrow) +import Control.Monad.Error.Class + ( class MonadError + , class MonadThrow + , throwError + ) import Control.Monad.Logger.Class (class MonadLogger) import Control.Monad.Reader.Class (class MonadAsk, class MonadReader, ask) import Control.Monad.Reader.Trans (ReaderT, runReaderT) @@ -17,6 +31,7 @@ import Ctl.Internal.Contract.QueryBackend , lookupBackend ) import Ctl.Internal.Helpers (logWithLevel) +import Ctl.Internal.JsWebSocket (JsWebSocket, _wsClose, _wsFinalize) import Ctl.Internal.QueryM ( DatumCacheWebSocket , Hooks @@ -28,19 +43,23 @@ import Ctl.Internal.QueryM , mkLogger , mkOgmiosWebSocketAff , mkWalletBySpec + , underlyingWebSocket ) +import Ctl.Internal.QueryM.Logging (setupLogs) import Ctl.Internal.QueryM.Ogmios (ProtocolParameters) as Ogmios import Ctl.Internal.QueryM.ServerConfig (ServerConfig) import Ctl.Internal.Serialization.Address (NetworkId) import Ctl.Internal.Types.UsedTxOuts (UsedTxOuts, newUsedTxOuts) import Ctl.Internal.Wallet (Wallet) import Ctl.Internal.Wallet.Spec (WalletSpec) +import Data.Either (Either(Left, Right)) import Data.Log.Level (LogLevel) import Data.Log.Message (Message) import Data.Maybe (Maybe(Just, Nothing), fromJust, fromMaybe) import Data.Newtype (class Newtype, unwrap) import Data.Traversable (for_, traverse) -import Effect.Aff (Aff) +import Effect (Effect) +import Effect.Aff (Aff, attempt, finally, supervise) import Effect.Aff.Class (liftAff) import Effect.Class (class MonadEffect, liftEffect) import Effect.Exception (Error, try) @@ -81,6 +100,23 @@ instance MonadLogger Contract where let logFunction = fromMaybe logWithLevel config.customLogger liftAff $ logFunction config.logLevel msg +-- | Interprets a contract into an `Aff` context. +-- | Implicitly initializes and finalizes a new `ContractEnv` runtime. +-- | +-- | Use `withContractEnv` if your application contains multiple contracts that +-- | can be run in parallel, reusing the same environment (see +-- | `withContractEnv`) +runContract :: forall (a :: Type). ContractParams -> Contract a -> Aff a +runContract params contract = do + withContractEnv params \config -> + runContractInEnv config contract + +-- | Runs a contract in existing environment. Does not destroy the environment +-- | when contract execution ends. +runContractInEnv :: forall (a :: Type). ContractEnv -> Contract a -> Aff a +runContractInEnv contractEnv = + flip runReaderT contractEnv <<< unwrap + -------------------------------------------------------------------------------- -- ContractEnv -------------------------------------------------------------------------------- @@ -150,7 +186,7 @@ type ContractRuntime = , pparams :: Ogmios.ProtocolParameters -- TODO: } --- | Used in `mkContractRuntime` only +-- | Used in `mkContractRuntime` only. data ContractRuntimeModel = ContractRuntimeModel DatumCacheWebSocket (Maybe OgmiosWebSocket) @@ -184,6 +220,60 @@ mkContractRuntime params = do CtlBackendParams { ogmiosConfig } -> Just ogmiosConfig _ -> Nothing +-- | Finalizes a `Contract` environment. +-- | Closes the websockets in `ContractEnv`, effectively making it unusable. +stopContractEnv + :: Warn + ( Text + "Using `stopContractEnv` is not recommended: users should rely on `withContractEnv` to finalize the runtime environment instead" + ) + => ContractEnv + -> Effect Unit +stopContractEnv contractEnv = do + _wsFinalize datumCacheWs *> _wsClose datumCacheWs + for_ mOgmiosWs \ogmiosWs -> _wsFinalize ogmiosWs *> _wsClose ogmiosWs + where + datumCacheWs :: JsWebSocket + datumCacheWs = underlyingWebSocket contractEnv.datumCache.ws + + mOgmiosWs :: Maybe JsWebSocket + mOgmiosWs = + lookupBackend CtlBackendLabel contractEnv.backend >>= case _ of + CtlBackend { ogmiosWs } -> + Just $ underlyingWebSocket ogmiosWs + _ -> Nothing + +-- | Constructs and finalizes a contract environment that is usable inside a +-- | bracket callback. +-- | One environment can be used by multiple `Contract`s in parallel (see +-- | `runContractInEnv`). +-- | Make sure that `Aff` action does not end before all contracts that use the +-- | runtime terminate. Otherwise `WebSocket`s will be closed too early. +withContractEnv + :: forall (a :: Type). ContractParams -> (ContractEnv -> Aff a) -> Aff a +withContractEnv params action = do + { addLogEntry, printLogs } <- + liftEffect $ setupLogs params.logLevel params.customLogger + let + customLogger :: Maybe (LogLevel -> Message -> Aff Unit) + customLogger + | params.suppressLogs = Just $ map liftEffect <<< addLogEntry + | otherwise = params.customLogger + + contractEnv <- mkContractEnv params <#> _ { customLogger = customLogger } + eiRes <- + -- TODO: Adapt `networkIdCheck` from QueryM module + attempt $ supervise (action contractEnv) + `flip finally` liftEffect (stopContractEnv contractEnv) + liftEffect $ case eiRes of + Left err -> do + for_ contractEnv.hooks.onError \f -> void $ try $ f err + when contractEnv.suppressLogs printLogs + throwError err + Right res -> do + for_ contractEnv.hooks.onSuccess (void <<< try) + pure res + -------------------------------------------------------------------------------- -- ContractParams -------------------------------------------------------------------------------- From f592acbc3936ec20add4cddba71c807d3458c70b Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Thu, 24 Nov 2022 14:08:59 +0100 Subject: [PATCH 009/373] Re-export new Contract in Contract.Monad, Adapt Contract.PlutusData --- src/Contract/Monad.purs | 468 ++++--------------------------- src/Contract/PlutusData.purs | 28 +- src/Internal/Contract/Monad.purs | 5 + 3 files changed, 71 insertions(+), 430 deletions(-) diff --git a/src/Contract/Monad.purs b/src/Contract/Monad.purs index 34a2e8dfc2..1e0ca44a64 100644 --- a/src/Contract/Monad.purs +++ b/src/Contract/Monad.purs @@ -1,15 +1,8 @@ -- | A module defining the `Contract` monad. module Contract.Monad - ( Contract(Contract) - , ParContract - , ContractEnv(ContractEnv) - , ConfigParams - , DefaultContractEnv - , module Aff - , module QueryM - , module Log.Tag - , askConfig - , asksConfig + ( module ExportAff + , module ExportContract + , module ExportLogTag , liftContractAffM , liftContractE , liftContractE' @@ -17,80 +10,23 @@ module Contract.Monad , liftedE , liftedE' , liftedM - , mkContractEnv - , runContract - , runContractInEnv - , stopContractEnv , throwContractError - , withContractEnv - , wrapContract ) where import Prelude -import Control.Alt (class Alt) -import Control.Alternative (class Alternative) -import Control.Monad.Error.Class - ( class MonadError - , class MonadThrow - , catchError - ) -import Control.Monad.Except (throwError) -import Control.Monad.Logger.Class (class MonadLogger) -import Control.Monad.Reader.Class - ( class MonadAsk - , class MonadReader - , ask - , asks - , local - ) -import Control.Monad.Reader.Trans (runReaderT) -import Control.Monad.Rec.Class (class MonadRec) -import Control.Parallel (class Parallel, parallel, sequential) -import Control.Plus (class Plus, empty) -import Ctl.Internal.QueryM - ( DatumCacheListeners - , DatumCacheWebSocket - , Host - , ListenerSet - , Logger - , OgmiosListeners - , OgmiosWebSocket - , QueryConfig - , QueryEnv - , QueryM - , QueryMExtended - , QueryRuntime - , ServerConfig - , WebSocket - , defaultDatumCacheWsConfig - , defaultOgmiosWsConfig - , defaultServerConfig - , liftQueryM - , mkDatumCacheWebSocketAff - , mkHttpUrl - , mkLogger - , mkOgmiosWebSocketAff - , mkWsUrl - ) as QueryM -import Ctl.Internal.QueryM - ( Hooks - , QueryConfig - , QueryEnv - , QueryM - , QueryMExtended - , ServerConfig - , liftQueryM - , mkQueryRuntime - , stopQueryRuntime - , withQueryRuntime - ) -import Ctl.Internal.QueryM.Logging (setupLogs) -import Ctl.Internal.Serialization.Address (NetworkId) -import Ctl.Internal.Wallet.Spec (WalletSpec) -import Data.Either (Either(Left, Right), either, hush) -import Data.Log.Level (LogLevel) -import Data.Log.Message (Message) +import Ctl.Internal.Contract.Monad (Contract) +import Ctl.Internal.Contract.Monad + ( Contract(Contract) + , ContractEnv + , ContractParams + , mkContractEnv + , runContract + , runContractInEnv + , stopContractEnv + , withContractEnv + ) as ExportContract +import Data.Either (Either, either, hush) import Data.Log.Tag ( TagSet , booleanTag @@ -99,366 +35,64 @@ import Data.Log.Tag , numberTag , tag , tagSetTag - ) as Log.Tag -import Data.Maybe (Maybe(Just), maybe) -import Data.Newtype (class Newtype, unwrap, wrap) -import Data.Profunctor (dimap) -import Effect (Effect) -import Effect.Aff (Aff, ParAff, try) -import Effect.Aff (Aff, launchAff_) as Aff -import Effect.Aff.Class (class MonadAff, liftAff) -import Effect.Class (class MonadEffect, liftEffect) -import Effect.Exception (Error, throw) -import Prim.TypeError (class Warn, Text) - --- | The `Contract` monad is a newtype wrapper over `QueryM` which is `ReaderT` --- | on `QueryConfig` over asynchronous effects, `Aff`. Throwing and catching --- | errors can therefore be implemented with native JavaScript --- | `Effect.Exception.Error`s and `Effect.Class.Console.log` replaces the --- | `Writer` monad. `Aff` enables the user to make effectful calls inside this --- | `Contract` monad. --- | --- | The `Contract` has the same capabilities as the underlying `QueryM` but --- | `Contract` provides a seperation of intent. While the user may access --- | the underlying type alias, `QueryM`, we intend to keep the mentioned type --- | internal for all requests to wallets and servers. Although the user may --- | find the type in the `QueryM` module. --- | --- | The configuration for `Contract` is also a newtype wrapper over the --- | underlying `QueryConfig`, see `ContractEnv`. --- | --- | All useful functions written in `QueryM` should be lifted into the --- | `Contract` monad and available in the same namespace. If anything is --- | missing, please contact us. -newtype Contract (r :: Row Type) (a :: Type) = Contract (QueryMExtended r Aff a) - --- Many of these derivations of depending on the underlying `ReaderT` and --- asychronous effects,`Aff`. -derive instance Newtype (Contract r a) _ -derive newtype instance Functor (Contract r) -derive newtype instance Apply (Contract r) -derive newtype instance Applicative (Contract r) -derive newtype instance Bind (Contract r) -derive newtype instance Monad (Contract r) -derive newtype instance MonadEffect (Contract r) -derive newtype instance MonadAff (Contract r) -derive newtype instance Semigroup a => Semigroup (Contract r a) -derive newtype instance Monoid a => Monoid (Contract r a) --- Utilise JavaScript's native `Error` via underlying `Aff` for flexibility: -derive newtype instance MonadThrow Error (Contract r) -derive newtype instance MonadError Error (Contract r) -derive newtype instance MonadRec (Contract r) -derive newtype instance MonadLogger (Contract r) - -instance MonadAsk (ContractEnv r) (Contract r) where - -- Use the underlying `ask`: - ask = Contract $ ContractEnv <$> ask - -instance MonadReader (ContractEnv r) (Contract r) where - -- Use the underlying `local` after dimapping and unwrapping: - local f contract = Contract $ local (dimap wrap unwrap f) (unwrap contract) - -instance Parallel (ParContract r) (Contract r) where - parallel :: Contract r ~> ParContract r - parallel = ParContract <<< parallel <<< unwrap - sequential :: ParContract r ~> Contract r - sequential (ParContract a) = wrap $ sequential a - --- | The `ParContract` applicative is a newtype wrapper over `ParQueryM`, which --- | is a `ReaderT` on `QueryConfig` over _parallel_ asynchronous effects, --- | `ParAff`. As expected, it's `Applicative` instance combines effects in --- | parallel. It's similar in functionality to `Contract`, but it notably lacks --- | a `Monad` instance and all the associated monadic functionalities --- | (like `MonadThrow`, `MonadError`, etc). This datatype is a requirement for --- | the `Parallel` instance that `Contract` contains. As such, there is little --- | point in using it directly, since all the methods in `Control.Parallel` --- | can be run directly on `Contract`. Also, there are no functions for --- | directly executing a `ParContract`; all `ParContract`s must eventually --- | be converted to `Contract`s before execution. -newtype ParContract (r :: Row Type) (a :: Type) = ParContract - (QueryMExtended r ParAff a) - -derive newtype instance Functor (ParContract r) -derive newtype instance Apply (ParContract r) -derive newtype instance Applicative (ParContract r) -derive newtype instance Alt (ParContract r) -derive newtype instance Plus (ParContract r) -derive newtype instance Alternative (ParContract r) -derive newtype instance Semigroup a => Semigroup (ParContract r a) -derive newtype instance Monoid a => Monoid (ParContract r a) - --- | `ContractEnv` is a trivial wrapper over `QueryEnv`. -newtype ContractEnv (r :: Row Type) = ContractEnv (QueryEnv r) - --- | Contract's `Alt` instance piggie-backs on the underlying `Aff`'s `Alt` --- | instance, which uses `MonadError` capabilities. --- | You can use `alt` operator to provide an alternative contract in case --- | the first one fails with an error. -instance Alt (Contract r) where - alt a1 a2 = catchError a1 (const a2) - --- | Identity for `alt` - a.k.a. a contract that "always fails". -instance Plus (Contract r) where - empty = liftAff empty - -type DefaultContractEnv = ContractEnv () - -derive instance Newtype (ContractEnv r) _ - -wrapContract :: forall (r :: Row Type) (a :: Type). QueryM a -> Contract r a -wrapContract = wrap <<< liftQueryM - --- | Same as `ask`, but points to the user config record. -askConfig - :: forall (r :: Row Type) - . Warn - ( Text - "User-defined configs are deprecated - https://github.com/Plutonomicon/cardano-transaction-lib/issues/734" - ) - => Contract r { | r } -askConfig = do - asks $ unwrap >>> _.extraConfig - --- | Same as `asks`, but allows to apply a function to the user config record. -asksConfig - :: forall (r :: Row Type) (a :: Type) - . Warn - ( Text - "User-defined configs are deprecated - https://github.com/Plutonomicon/cardano-transaction-lib/issues/734" - ) - => ({ | r } -> a) - -> Contract r a -asksConfig f = do - asks $ unwrap >>> _.extraConfig >>> f - --- | Options to construct a `ContractEnv` indirectly. `extraConfig` --- | holds additional options that will extend the resulting `ContractEnv`. --- | --- | Use `runContract` to run a `Contract` within an implicity constructed --- | `ContractEnv` environment, or use `withContractEnv` if your application --- | contains multiple contracts that can be run in parallel, reusing the same --- | environment (see `withContractEnv`) -type ConfigParams (r :: Row Type) = - { ogmiosConfig :: ServerConfig - , datumCacheConfig :: ServerConfig - , ctlServerConfig :: Maybe ServerConfig - , kupoConfig :: ServerConfig - , networkId :: NetworkId - , logLevel :: LogLevel - , walletSpec :: Maybe WalletSpec - , customLogger :: Maybe (LogLevel -> Message -> Aff Unit) - -- | Suppress logs until an exception is thrown - , suppressLogs :: Boolean - -- | Additional config options to extend the `ContractEnv` - , extraConfig :: { | r } - , hooks :: Hooks - } - --- | Interprets a contract into an `Aff` context. --- | Implicitly initializes and finalizes a new `ContractEnv` runtime. --- | --- | Use `withContractEnv` if your application contains multiple contracts that --- | can be run in parallel, reusing the same environment (see --- | `withContractEnv`) -runContract - :: forall (r :: Row Type) (a :: Type) - . ConfigParams r - -> Contract r a - -> Aff a -runContract params contract = do - withContractEnv params \config -> - runContractInEnv config contract - --- | Runs a contract in existing environment. Does not destroy the environment --- | when contract execution ends. -runContractInEnv - :: forall (r :: Row Type) (a :: Type) - . ContractEnv r - -> Contract r a - -> Aff a -runContractInEnv env contract = - flip runReaderT (unwrap env) - $ unwrap - $ unwrap contract - --- | Initializes a `Contract` environment. Does not ensure finalization. --- | Consider using `withContractEnv` if possible - otherwise use --- | `stopContractEnv` to properly finalize. -mkContractEnv - :: forall (r :: Row Type) (a :: Type) - . Warn - ( Text - "Using `mkContractEnv` is not recommended: it does not ensure `ContractEnv` finalization. Consider using `withContractEnv`" - ) - => ConfigParams r - -> Aff (ContractEnv r) -mkContractEnv - params@ - { ctlServerConfig - , ogmiosConfig - , datumCacheConfig - , kupoConfig - , networkId - , logLevel - , walletSpec - , customLogger - , suppressLogs - , hooks - } = do - let - config = - { ctlServerConfig - , ogmiosConfig - , datumCacheConfig - , kupoConfig - , networkId - , logLevel - , walletSpec - , customLogger - , suppressLogs - , hooks - } - runtime <- mkQueryRuntime - config - let - contractEnv = wrap - { runtime, config, extraConfig: params.extraConfig } - pure contractEnv - --- | Finalizes a `Contract` environment. -stopContractEnv - :: forall (r :: Row Type) - . Warn - ( Text - "Using `stopContractEnv` is not recommended: users should rely on `withContractEnv` to finalize the runtime environment instead" - ) - => ContractEnv r - -> Effect Unit -stopContractEnv env = stopQueryRuntime (unwrap env).runtime - --- | Constructs and finalizes a contract environment that is usable inside a --- | bracket callback. --- | One environment can be used by multiple `Contract`s in parallel (see --- | `runContractInEnv`). --- | Make sure that `Aff` action does not end before all contracts that use the --- | runtime terminate. Otherwise `WebSocket`s will be closed too early. -withContractEnv - :: forall (r :: Row Type) (a :: Type) - . ConfigParams r - -> (ContractEnv r -> Aff a) - -> Aff a -withContractEnv - params@ - { ctlServerConfig - , ogmiosConfig - , datumCacheConfig - , kupoConfig - , networkId - , logLevel - , walletSpec - , customLogger - , suppressLogs - , hooks - } - action = do - { addLogEntry, printLogs } <- - liftEffect $ setupLogs params.logLevel params.customLogger - let - config :: QueryConfig - config = - { ctlServerConfig - , ogmiosConfig - , datumCacheConfig - , kupoConfig - , networkId - , logLevel - , walletSpec - , customLogger: - if suppressLogs then Just $ map liftEffect <<< addLogEntry - else customLogger - , suppressLogs - , hooks - } - - withQueryRuntime config \runtime -> do - let - contractEnv = wrap - { runtime, config, extraConfig: params.extraConfig } - res <- try $ action contractEnv - case res of - Left err -> liftEffect do - when suppressLogs printLogs - throwError err - Right result -> pure result - --- | Throws an `Error` for any showable error using `Effect.Exception.throw` --- | and lifting into the `Contract` monad. -throwContractError - :: forall (e :: Type) (r :: Row Type) (a :: Type). Show e => e -> Contract r a -throwContractError = liftEffect <<< throw <<< show - --- | Given a string error and `Maybe` value, if the latter is `Nothing`, throw --- | the error with the given string, otherwise, return the value. If using --- | using `runExceptT`, see `liftM` inside `Contract.Prelude`. This can be --- | thought of as `liftM` restricted to JavaScript's `Error` and without the --- | need to call `error :: String -> Error` each time. -liftContractM - :: forall (r :: Row Type) (a :: Type) - . String - -> Maybe a - -> Contract r a -liftContractM str = maybe (liftEffect $ throw str) pure - --- | Same as `liftContractM` but the `Maybe` value is already in the `Contract` --- | context. -liftedM - :: forall (r :: Row Type) (a :: Type) - . String - -> Contract r (Maybe a) - -> Contract r a -liftedM str cm = cm >>= liftContractM str + ) as ExportLogTag +import Data.Maybe (Maybe, maybe) +import Effect.Aff (Aff) +import Effect.Aff (Aff, launchAff_) as ExportAff +import Effect.Aff.Class (liftAff) +import Effect.Class (liftEffect) +import Effect.Exception (throw) -- | Same as `liftContractM` but the `Maybe` value is in the `Aff` context. -liftContractAffM - :: forall (r :: Row Type) (a :: Type) - . String - -> Aff (Maybe a) - -> Contract r a +liftContractAffM :: forall (a :: Type). String -> Aff (Maybe a) -> Contract a liftContractAffM str = liftedM str <<< liftAff -- | Similar to `liftContractE` except it directly throws the showable error -- | via `throwContractError` instead of an arbitrary string. liftContractE - :: forall (e :: Type) (r :: Row Type) (a :: Type) - . Show e - => Either e a - -> Contract r a + :: forall (e :: Type) (a :: Type). Show e => Either e a -> Contract a liftContractE = either throwContractError pure -- | Similar to `liftContractM`, throwing the string instead of the `Left` -- | value. For throwing the `Left` value, see `liftEither` in -- | `Contract.Prelude`. liftContractE' - :: forall (e :: Type) (r :: Row Type) (a :: Type) - . String - -> Either e a - -> Contract r a + :: forall (e :: Type) (a :: Type). String -> Either e a -> Contract a liftContractE' str = liftContractM str <<< hush +-- | Given a string error and `Maybe` value, if the latter is `Nothing`, throw +-- | the error with the given string, otherwise, return the value. If using +-- | using `runExceptT`, see `liftM` inside `Contract.Prelude`. This can be +-- | thought of as `liftM` restricted to JavaScript's `Error` and without the +-- | need to call `error :: String -> Error` each time. +liftContractM :: forall (a :: Type). String -> Maybe a -> Contract a +liftContractM str = maybe (liftEffect $ throw str) pure + -- | Similar to `liftedE` except it directly throws the showable error via -- | `throwContractError` instead of an arbitrary string. liftedE - :: forall (e :: Type) (r :: Row Type) (a :: Type) + :: forall (e :: Type) (a :: Type) . Show e - => Contract r (Either e a) - -> Contract r a + => Contract (Either e a) + -> Contract a liftedE = (=<<) liftContractE -- | Same as `liftContractE` but the `Either` value is already in the `Contract` -- | context. liftedE' - :: forall (e :: Type) (r :: Row Type) (a :: Type) + :: forall (e :: Type) (a :: Type) . String - -> Contract r (Either e a) - -> Contract r a -liftedE' str em = em >>= liftContractE' str + -> Contract (Either e a) + -> Contract a +liftedE' str = (=<<) (liftContractE' str) + +-- | Same as `liftContractM` but the `Maybe` value is already in the `Contract` +-- | context. +liftedM :: forall (a :: Type). String -> Contract (Maybe a) -> Contract a +liftedM str = (=<<) (liftContractM str) + +-- | Throws an `Error` for any showable error using `Effect.Exception.throw` +-- | and lifting into the `Contract` monad. +throwContractError :: forall (e :: Type) (a :: Type). Show e => e -> Contract a +throwContractError = liftEffect <<< throw <<< show + diff --git a/src/Contract/PlutusData.purs b/src/Contract/PlutusData.purs index 79da0d5409..eb69349533 100644 --- a/src/Contract/PlutusData.purs +++ b/src/Contract/PlutusData.purs @@ -23,7 +23,8 @@ module Contract.PlutusData import Prelude -import Contract.Monad (Contract, wrapContract) +import Contract.Monad (Contract) +import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.Deserialization.PlutusData (deserializeData) as Deserialization import Ctl.Internal.FromData ( class FromData @@ -107,28 +108,29 @@ import Data.Bifunctor (lmap) import Data.Either (Either, hush) import Data.Map (Map) import Data.Maybe (Maybe) +import Effect.Aff.Class (liftAff) -- | Retrieve the full resolved datum associated to a given datum hash. -getDatumByHash :: forall (r :: Row Type). DataHash -> Contract r (Maybe Datum) -getDatumByHash = wrapContract <<< map (join <<< hush) <<< Kupo.getDatumByHash +getDatumByHash :: DataHash -> Contract (Maybe Datum) +getDatumByHash dataHash = do + queryHandle <- getQueryHandle + liftAff $ join <<< hush <$> queryHandle.getDatumByHash dataHash -- | Retrieve full resolved datums associated with given datum hashes. -- | The resulting `Map` will only contain datums that have been successfully -- | resolved. This function returns `Nothing` in case of an error during -- | response processing (bad HTTP code or response parsing error). -getDatumsByHashes - :: forall (r :: Row Type) - . Array DataHash - -> Contract r (Maybe (Map DataHash Datum)) -getDatumsByHashes = wrapContract <<< map hush <<< Kupo.getDatumsByHashes +getDatumsByHashes :: Array DataHash -> Contract (Maybe (Map DataHash Datum)) +getDatumsByHashes hashes = do + queryHandle <- getQueryHandle + liftAff $ hush <$> queryHandle.getDatumsByHashes hashes -- | Retrieve full resolved datums associated with given datum hashes. -- | The resulting `Map` will only contain datums that have been successfully -- | resolved. getDatumsByHashesWithError - :: forall (r :: Row Type) - . Array DataHash - -> Contract r (Either String (Map DataHash Datum)) -getDatumsByHashesWithError = - wrapContract <<< map (lmap show) <<< Kupo.getDatumsByHashes + :: Array DataHash -> Contract (Either String (Map DataHash Datum)) +getDatumsByHashesWithError hashes = do + queryHandle <- getQueryHandle + liftAff $ lmap show <$> queryHandle.getDatumsByHashes hashes diff --git a/src/Internal/Contract/Monad.purs b/src/Internal/Contract/Monad.purs index b0057e5aa1..500cc5ce12 100644 --- a/src/Internal/Contract/Monad.purs +++ b/src/Internal/Contract/Monad.purs @@ -73,6 +73,11 @@ import Undefined (undefined) -- Contract -------------------------------------------------------------------------------- +-- | The `Contract` monad is a newtype wrapper over `ReaderT` on `ContractEnv` +-- | over asynchronous effects, `Aff`. Throwing and catching errors can +-- | therefore be implemented with native JavaScript `Effect.Exception.Error`s +-- | and `Effect.Class.Console.log` replaces the `Writer` monad. `Aff` enables +-- | the user to make effectful calls inside this `Contract` monad. newtype Contract (a :: Type) = Contract (ReaderT ContractEnv Aff a) -- Many of these derivations depend on the underlying `ReaderT` and From 3455be5050fff4a7e57d5146d2faac38a6fd033a Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Fri, 25 Nov 2022 22:16:53 +0000 Subject: [PATCH 010/373] WIP: Moved more functions to use the Contract abstraction. Improved contract env setup. Exploring what is needed for other functions which can use the abstraction --- src/Contract/Address.purs | 61 +++---- src/Internal/Contract/Monad.purs | 206 +++++++++++------------ src/Internal/Contract/QueryBackend.purs | 27 ++- src/Internal/Contract/QueryHandle.purs | 12 ++ src/Internal/Contract/WaitUntilSlot.purs | 178 ++++++++++++++++++++ src/Internal/Contract/Wallet.purs | 193 +++++++++++++++++++++ src/Internal/QueryM.purs | 20 +++ templates/ctl-scaffold/src/Scaffold.purs | 2 +- 8 files changed, 550 insertions(+), 149 deletions(-) create mode 100644 src/Internal/Contract/WaitUntilSlot.purs create mode 100644 src/Internal/Contract/Wallet.purs diff --git a/src/Contract/Address.purs b/src/Contract/Address.purs index 79f36e1dbc..c275f6e48e 100644 --- a/src/Contract/Address.purs +++ b/src/Contract/Address.purs @@ -38,7 +38,7 @@ module Contract.Address import Prelude -import Contract.Monad (Contract, liftContractM, liftedM, wrapContract) +import Contract.Monad (Contract, liftContractM, liftedM) import Contract.Prelude (liftM) import Control.Monad.Error.Class (throwError) import Ctl.Internal.Address @@ -68,13 +68,13 @@ import Ctl.Internal.Plutus.Types.Address import Ctl.Internal.Plutus.Types.TransactionUnspentOutput ( TransactionUnspentOutput ) -import Ctl.Internal.QueryM +import Ctl.Internal.Contract.Wallet ( getNetworkId , getWalletAddresses , ownPaymentPubKeyHashes , ownStakePubKeysHashes - ) as QueryM -import Ctl.Internal.QueryM.Utxos (getWalletCollateral) as QueryM + , getWalletCollateral + ) as Contract import Ctl.Internal.Scripts ( typedValidatorBaseAddress , typedValidatorEnterpriseAddress @@ -130,19 +130,17 @@ import Prim.TypeError (class Warn, Text) -- | Get an `Address` of the browser wallet. getWalletAddress - :: forall (r :: Row Type) - . Warn + :: Warn ( Text "This function returns only one `Adress` even in case multiple `Adress`es are available. Use `getWalletAdresses` instead" ) - => Contract r (Maybe Address) + => Contract (Maybe Address) getWalletAddress = head <$> getWalletAddresses -- | Get all the `Address`es of the browser wallet. -getWalletAddresses - :: forall (r :: Row Type). Contract r (Array Address) +getWalletAddresses :: Contract (Array Address) getWalletAddresses = do - addresses <- wrapContract QueryM.getWalletAddresses + addresses <- Contract.getWalletAddresses traverse ( liftM (error "getWalletAddresses: failed to deserialize `Address`") @@ -152,19 +150,17 @@ getWalletAddresses = do -- | Get an `AddressWithNetworkTag` of the browser wallet. getWalletAddressWithNetworkTag - :: forall (r :: Row Type) - . Warn + :: Warn ( Text "This function returns only one `AddressWithNetworkTag` even in case multiple `AddressWithNetworkTag` are available. Use `getWalletAddressesWithNetworkTag` instead" ) - => Contract r (Maybe AddressWithNetworkTag) + => Contract (Maybe AddressWithNetworkTag) getWalletAddressWithNetworkTag = head <$> getWalletAddressesWithNetworkTag -- | Get all the `AddressWithNetworkTag` of the browser wallet discarding errors. -getWalletAddressesWithNetworkTag - :: forall (r :: Row Type). Contract r (Array AddressWithNetworkTag) +getWalletAddressesWithNetworkTag :: Contract (Array AddressWithNetworkTag) getWalletAddressesWithNetworkTag = do - addresses <- wrapContract QueryM.getWalletAddresses + addresses <- Contract.getWalletAddresses traverse ( liftM ( error @@ -180,9 +176,9 @@ getWalletAddressesWithNetworkTag = do -- | Throws on `Promise` rejection by wallet, returns `Nothing` if no collateral -- | is available. getWalletCollateral - :: forall (r :: Row Type). Contract r (Maybe (Array TransactionUnspentOutput)) + :: Contract (Maybe (Array TransactionUnspentOutput)) getWalletCollateral = do - mtxUnspentOutput <- wrapContract QueryM.getWalletCollateral + mtxUnspentOutput <- Contract.getWalletCollateral for mtxUnspentOutput $ traverse $ liftedM "getWalletCollateral: failed to deserialize TransactionUnspentOutput" @@ -191,35 +187,30 @@ getWalletCollateral = do -- | Gets a wallet `PaymentPubKeyHash` via `getWalletAddresses`. ownPaymentPubKeyHash - :: forall (r :: Row Type) - . Warn + :: Warn ( Text "This function returns only one `PaymentPubKeyHash` even in case multiple `PaymentPubKeysHash`es are available. Use `ownPaymentPubKeysHashes` instead" ) - => Contract r (Maybe PaymentPubKeyHash) + => Contract (Maybe PaymentPubKeyHash) ownPaymentPubKeyHash = head <$> ownPaymentPubKeysHashes -- | Gets all wallet `PaymentPubKeyHash`es via `getWalletAddresses`. -ownPaymentPubKeysHashes - :: forall (r :: Row Type). Contract r (Array PaymentPubKeyHash) -ownPaymentPubKeysHashes = wrapContract QueryM.ownPaymentPubKeyHashes +ownPaymentPubKeysHashes :: Contract (Array PaymentPubKeyHash) +ownPaymentPubKeysHashes = Contract.ownPaymentPubKeyHashes ownStakePubKeyHash - :: forall (r :: Row Type) - . Warn + :: Warn ( Text "This function returns only one `StakePubKeyHash` even in case multiple `StakePubKeysHash`es are available. Use `ownStakePubKeysHashes` instead" ) - => Contract r (Maybe StakePubKeyHash) + => Contract (Maybe StakePubKeyHash) ownStakePubKeyHash = join <<< head <$> ownStakePubKeysHashes -ownStakePubKeysHashes - :: forall (r :: Row Type). Contract r (Array (Maybe StakePubKeyHash)) -ownStakePubKeysHashes = wrapContract QueryM.ownStakePubKeysHashes +ownStakePubKeysHashes :: Contract (Array (Maybe StakePubKeyHash)) +ownStakePubKeysHashes = Contract.ownStakePubKeysHashes -getNetworkId - :: forall (r :: Row Type). Contract r NetworkId -getNetworkId = wrapContract QueryM.getNetworkId +getNetworkId :: Contract NetworkId +getNetworkId = Contract.getNetworkId -------------------------------------------------------------------------------- -- Helpers via Cardano helpers, these are helpers from the CSL equivalent @@ -244,7 +235,7 @@ addressWithNetworkTagFromBech32 str = do -- | Convert `Address` to `Bech32String`, using current `NetworkId` provided by -- | `Contract` configuration to determine the network tag. -addressToBech32 :: forall (r :: Row Type). Address -> Contract r Bech32String +addressToBech32 :: Address -> Contract Bech32String addressToBech32 address = do networkId <- getNetworkId pure $ addressWithNetworkTagToBech32 @@ -253,7 +244,7 @@ addressToBech32 address = do -- | Convert `Bech32String` to `Address`, asserting that the address `networkId` -- | corresponds to the contract environment `networkId` addressFromBech32 - :: forall (r :: Row Type). Bech32String -> Contract r Address + :: Bech32String -> Contract Address addressFromBech32 str = do networkId <- getNetworkId cslAddress <- liftContractM "addressFromBech32: unable to read address" $ diff --git a/src/Internal/Contract/Monad.purs b/src/Internal/Contract/Monad.purs index 500cc5ce12..dfde67f58e 100644 --- a/src/Internal/Contract/Monad.purs +++ b/src/Internal/Contract/Monad.purs @@ -12,6 +12,12 @@ module Ctl.Internal.Contract.Monad import Prelude +import Effect.Aff (Aff, attempt, error, finally, supervise) +import Data.Array (head) +import Ctl.Internal.JsWebSocket (_wsClose, _wsFinalize) +import Ctl.Internal.QueryM (Hooks, Logger, QueryEnv, QueryM, WebSocket, getProtocolParametersAff, getSystemStartAff, getEraSummariesAff, mkDatumCacheWebSocketAff, mkLogger, mkOgmiosWebSocketAff, mkWalletBySpec, underlyingWebSocket) +import Record.Builder (build, merge) +import Control.Parallel (parTraverse, parallel, sequential) import Control.Monad.Error.Class ( class MonadError , class MonadThrow @@ -21,32 +27,16 @@ import Control.Monad.Logger.Class (class MonadLogger) import Control.Monad.Reader.Class (class MonadAsk, class MonadReader, ask) import Control.Monad.Reader.Trans (ReaderT, runReaderT) import Control.Monad.Rec.Class (class MonadRec) -import Control.Parallel (parallel, sequential) import Ctl.Internal.Contract.QueryBackend ( CtlBackend , QueryBackend(BlockfrostBackend, CtlBackend) - , QueryBackendLabel(CtlBackendLabel) , QueryBackendParams(BlockfrostBackendParams, CtlBackendParams) , QueryBackends - , lookupBackend - ) -import Ctl.Internal.Helpers (logWithLevel) -import Ctl.Internal.JsWebSocket (JsWebSocket, _wsClose, _wsFinalize) -import Ctl.Internal.QueryM - ( DatumCacheWebSocket - , Hooks - , Logger - , OgmiosWebSocket - , QueryEnv - , QueryM - , mkDatumCacheWebSocketAff - , mkLogger - , mkOgmiosWebSocketAff - , mkWalletBySpec - , underlyingWebSocket + , defaultBackend ) +import Ctl.Internal.Helpers (liftedM, logWithLevel) import Ctl.Internal.QueryM.Logging (setupLogs) -import Ctl.Internal.QueryM.Ogmios (ProtocolParameters) as Ogmios +import Ctl.Internal.QueryM.Ogmios (ProtocolParameters, SlotLength, SystemStart) as Ogmios import Ctl.Internal.QueryM.ServerConfig (ServerConfig) import Ctl.Internal.Serialization.Address (NetworkId) import Ctl.Internal.Types.UsedTxOuts (UsedTxOuts, newUsedTxOuts) @@ -55,17 +45,15 @@ import Ctl.Internal.Wallet.Spec (WalletSpec) import Data.Either (Either(Left, Right)) import Data.Log.Level (LogLevel) import Data.Log.Message (Message) -import Data.Maybe (Maybe(Just, Nothing), fromJust, fromMaybe) +import Data.Maybe (Maybe(Just, Nothing), fromMaybe) import Data.Newtype (class Newtype, unwrap) import Data.Traversable (for_, traverse) import Effect (Effect) -import Effect.Aff (Aff, attempt, finally, supervise) import Effect.Aff.Class (liftAff) import Effect.Class (class MonadEffect, liftEffect) import Effect.Exception (Error, try) import Effect.Ref (new) as Ref import MedeaPrelude (class MonadAff) -import Partial.Unsafe (unsafePartial) import Prim.TypeError (class Warn, Text) import Undefined (undefined) @@ -128,9 +116,8 @@ runContractInEnv contractEnv = type ContractEnv = { backend :: QueryBackends QueryBackend + -- ctlServer is currently used for applyArgs, which is needed for all backends. This will be removed later , ctlServerConfig :: Maybe ServerConfig - , datumCache :: { config :: ServerConfig, ws :: DatumCacheWebSocket } -- TODO: - -- , datumCache :: Maybe { config :: ServerConfig, ws :: DatumCacheWebSocket } , networkId :: NetworkId , logLevel :: LogLevel , walletSpec :: Maybe WalletSpec @@ -139,7 +126,12 @@ type ContractEnv = , hooks :: Hooks , wallet :: Maybe Wallet , usedTxOuts :: UsedTxOuts - , pparams :: Ogmios.ProtocolParameters -- TODO: + -- TODO: Duplicate types to Contract + , ledgerConstants :: + { pparams :: Ogmios.ProtocolParameters + , systemStart :: Ogmios.SystemStart + , slotLength :: Ogmios.SlotLength + } } -- | Initializes a `Contract` environment. Does not ensure finalization. @@ -153,80 +145,78 @@ mkContractEnv => ContractParams -> Aff ContractEnv mkContractEnv params = do - runtime <- mkContractRuntime params - pure - { backend: mkQueryBackend runtime <$> params.backendParams - , ctlServerConfig: params.ctlServerConfig - , datumCache: { config: params.datumCacheConfig, ws: runtime.datumCacheWs } - , networkId: params.networkId - , logLevel: params.logLevel - , walletSpec: params.walletSpec - , customLogger: params.customLogger - , suppressLogs: params.suppressLogs - , hooks: params.hooks - , wallet: runtime.wallet - , usedTxOuts: runtime.usedTxOuts - , pparams: runtime.pparams - } - where - mkQueryBackend :: ContractRuntime -> QueryBackendParams -> QueryBackend - mkQueryBackend _ (BlockfrostBackendParams backend) = - BlockfrostBackend backend - mkQueryBackend runtime (CtlBackendParams { ogmiosConfig, kupoConfig }) = - CtlBackend - { ogmiosConfig - , ogmiosWs: unsafePartial fromJust runtime.ogmiosWs - , kupoConfig - } - --------------------------------------------------------------------------------- --- ContractRuntime --------------------------------------------------------------------------------- + for_ params.hooks.beforeInit (void <<< liftEffect <<< try) -type ContractRuntime = - { ogmiosWs :: Maybe OgmiosWebSocket - , datumCacheWs :: DatumCacheWebSocket - , wallet :: Maybe Wallet - , usedTxOuts :: UsedTxOuts - , pparams :: Ogmios.ProtocolParameters -- TODO: - } + usedTxOuts <- newUsedTxOuts --- | Used in `mkContractRuntime` only. -data ContractRuntimeModel = ContractRuntimeModel - DatumCacheWebSocket - (Maybe OgmiosWebSocket) - (Maybe Wallet) + envBuilder <- sequential ado + b1 <- parallel do + backend <- buildBackend + -- Use the default backend to fetch ledger constants + ledgerConstants <- getLedgerConstants $ defaultBackend backend + pure $ merge { backend, ledgerConstants } + b2 <- parallel do + wallet <- buildWallet + pure $ merge { wallet } + -- compose the sub-builders together + in b1 >>> b2 >>> merge { usedTxOuts } -mkContractRuntime :: ContractParams -> Aff ContractRuntime -mkContractRuntime params = do - for_ params.hooks.beforeInit (void <<< liftEffect <<< try) - usedTxOuts <- newUsedTxOuts - datumCacheWsRef <- liftEffect $ Ref.new Nothing - ContractRuntimeModel datumCacheWs ogmiosWs wallet <- sequential $ - ContractRuntimeModel - <$> parallel - ( mkDatumCacheWebSocketAff datumCacheWsRef logger - params.datumCacheConfig - ) - <*> parallel - ( traverse (mkOgmiosWebSocketAff datumCacheWsRef logger) - mOgmiosConfig - ) - <*> parallel (traverse mkWalletBySpec params.walletSpec) - pparams <- undefined -- TODO: - pure { ogmiosWs, datumCacheWs, wallet, usedTxOuts, pparams } + pure $ build envBuilder constants where - logger :: Logger - logger = mkLogger params.logLevel params.customLogger + logger :: Logger + logger = mkLogger params.logLevel params.customLogger + + -- TODO Move CtlServer to a backend? Wouldn't make sense as a 'main' backend though + buildBackend :: Aff (QueryBackends QueryBackend) + buildBackend = flip parTraverse params.backendParams case _ of + CtlBackendParams { ogmiosConfig, kupoConfig, odcConfig } -> do + datumCacheWsRef <- liftEffect $ Ref.new Nothing + sequential ado + odcWs <- parallel $ mkDatumCacheWebSocketAff datumCacheWsRef logger odcConfig + ogmiosWs <- parallel $ mkOgmiosWebSocketAff datumCacheWsRef logger ogmiosConfig + in CtlBackend + { ogmios: + { config: ogmiosConfig + , ws: ogmiosWs + } + , odc: + { config: odcConfig + , ws: odcWs + } + , kupoConfig + } + BlockfrostBackendParams bf -> pure $ BlockfrostBackend bf - mOgmiosConfig :: Maybe ServerConfig - mOgmiosConfig = - lookupBackend CtlBackendLabel params.backendParams >>= case _ of - CtlBackendParams { ogmiosConfig } -> Just ogmiosConfig - _ -> Nothing + getLedgerConstants :: QueryBackend -> Aff + { pparams :: Ogmios.ProtocolParameters + , systemStart :: Ogmios.SystemStart + , slotLength :: Ogmios.SlotLength + } + getLedgerConstants backend = case backend of + CtlBackend { ogmios: { ws } } -> do + pparams <- getProtocolParametersAff ws logger + systemStart <- getSystemStartAff ws logger + slotLength <- liftedM (error "Could not get EraSummary") do + map (_.slotLength <<< unwrap <<< _.parameters <<< unwrap) <<< head <<< unwrap <$> getEraSummariesAff ws logger + pure { pparams, slotLength, systemStart } + BlockfrostBackend _ -> undefined + + buildWallet :: Aff (Maybe Wallet) + buildWallet = traverse mkWalletBySpec params.walletSpec + + constants = + { ctlServerConfig: params.ctlServerConfig + , networkId: params.networkId + , logLevel: params.logLevel + , walletSpec: params.walletSpec + , customLogger: params.customLogger + , suppressLogs: params.suppressLogs + , hooks: params.hooks + } -- | Finalizes a `Contract` environment. -- | Closes the websockets in `ContractEnv`, effectively making it unusable. +-- TODO Move to Aff? stopContractEnv :: Warn ( Text @@ -235,18 +225,14 @@ stopContractEnv => ContractEnv -> Effect Unit stopContractEnv contractEnv = do - _wsFinalize datumCacheWs *> _wsClose datumCacheWs - for_ mOgmiosWs \ogmiosWs -> _wsFinalize ogmiosWs *> _wsClose ogmiosWs - where - datumCacheWs :: JsWebSocket - datumCacheWs = underlyingWebSocket contractEnv.datumCache.ws - - mOgmiosWs :: Maybe JsWebSocket - mOgmiosWs = - lookupBackend CtlBackendLabel contractEnv.backend >>= case _ of - CtlBackend { ogmiosWs } -> - Just $ underlyingWebSocket ogmiosWs - _ -> Nothing + for_ contractEnv.backend case _ of + CtlBackend { ogmios, odc } -> do + let + stopWs :: forall (a :: Type). WebSocket a -> Effect Unit + stopWs = ((*>) <$> _wsFinalize <*> _wsClose) <<< underlyingWebSocket + stopWs odc.ws + stopWs ogmios.ws + BlockfrostBackend _ -> undefined -- | Constructs and finalizes a contract environment that is usable inside a -- | bracket callback. @@ -291,9 +277,8 @@ withContractEnv params action = do -- | environment (see `withContractEnv`) type ContractParams = { backendParams :: QueryBackends QueryBackendParams + -- TODO: Move CtlServer to a backend? , ctlServerConfig :: Maybe ServerConfig - , datumCacheConfig :: ServerConfig -- TODO: - -- , datumCacheConfig :: Maybe ServerConfig , networkId :: NetworkId , logLevel :: LogLevel , walletSpec :: Maybe WalletSpec @@ -315,8 +300,8 @@ mkQueryEnv :: ContractEnv -> CtlBackend -> QueryEnv () mkQueryEnv contractEnv ctlBackend = { config: { ctlServerConfig: contractEnv.ctlServerConfig - , datumCacheConfig: contractEnv.datumCache.config - , ogmiosConfig: ctlBackend.ogmiosConfig + , datumCacheConfig: ctlBackend.odc.config + , ogmiosConfig: ctlBackend.ogmios.config , kupoConfig: ctlBackend.kupoConfig , networkId: contractEnv.networkId , logLevel: contractEnv.logLevel @@ -326,11 +311,12 @@ mkQueryEnv contractEnv ctlBackend = , hooks: contractEnv.hooks } , runtime: - { ogmiosWs: ctlBackend.ogmiosWs - , datumCacheWs: contractEnv.datumCache.ws + { ogmiosWs: ctlBackend.ogmios.ws + , datumCacheWs: ctlBackend.odc.ws , wallet: contractEnv.wallet , usedTxOuts: contractEnv.usedTxOuts - , pparams: contractEnv.pparams + -- TODO: Make queryM use the new constants + , pparams: contractEnv.ledgerConstants.pparams } , extraConfig: {} } diff --git a/src/Internal/Contract/QueryBackend.purs b/src/Internal/Contract/QueryBackend.purs index 7b91c08212..846faa13be 100644 --- a/src/Internal/Contract/QueryBackend.purs +++ b/src/Internal/Contract/QueryBackend.purs @@ -15,10 +15,11 @@ module Ctl.Internal.Contract.QueryBackend import Prelude -import Ctl.Internal.QueryM (OgmiosWebSocket) +import Ctl.Internal.QueryM (OgmiosWebSocket, DatumCacheWebSocket) import Ctl.Internal.QueryM.ServerConfig (ServerConfig) import Data.Array (filter, nub) as Array import Data.Array ((:)) +import Data.Traversable import Data.Foldable (foldl, length) import Data.Map (Map) import Data.Map (empty, insert, lookup, singleton) as Map @@ -30,11 +31,24 @@ import Effect.Exception (throw) -- QueryBackends -------------------------------------------------------------------------------- +-- | A generic type to represent a choice of backend with a set of fallback +-- | backends when an operation is not supported by the default. +-- TODO Should this just be a list? +-- How do operations decide on what backend to use? data QueryBackends (backend :: Type) = QueryBackends backend (Map QueryBackendLabel backend) derive instance Functor QueryBackends +instance Foldable QueryBackends where + foldr f z (QueryBackends x xs) = f x (foldr f z xs) + foldl f z (QueryBackends x xs) = foldl f (f z x) xs + foldMap f (QueryBackends x xs) = f x <> foldMap f xs + +instance Traversable QueryBackends where + traverse f (QueryBackends x xs) = QueryBackends <$> f x <*> traverse f xs + sequence (QueryBackends x xs) = QueryBackends <$> x <*> sequence xs + mkSingletonBackendParams :: QueryBackendParams -> QueryBackends QueryBackendParams mkSingletonBackendParams = flip QueryBackends Map.empty @@ -93,8 +107,14 @@ instance HasQueryBackendLabel QueryBackendParams where -------------------------------------------------------------------------------- type CtlBackend = - { ogmiosConfig :: ServerConfig - , ogmiosWs :: OgmiosWebSocket + { ogmios :: + { config :: ServerConfig + , ws :: OgmiosWebSocket + } + , odc :: + { config :: ServerConfig + , ws :: DatumCacheWebSocket + } , kupoConfig :: ServerConfig } @@ -114,6 +134,7 @@ data QueryBackendParams = CtlBackendParams { ogmiosConfig :: ServerConfig , kupoConfig :: ServerConfig + , odcConfig :: ServerConfig } | BlockfrostBackendParams { blockfrostConfig :: ServerConfig diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs index 35cccd00d6..8107ee7411 100644 --- a/src/Internal/Contract/QueryHandle.purs +++ b/src/Internal/Contract/QueryHandle.purs @@ -36,6 +36,7 @@ import Data.Maybe (Maybe) import Effect.Aff (Aff) import Undefined (undefined) +-- Why ClientError? type AffE (a :: Type) = Aff (Either ClientError a) type QueryHandle = @@ -46,6 +47,17 @@ type QueryHandle = , getUtxoByOref :: TransactionInput -> AffE (Maybe TransactionOutput) , isTxConfirmed :: TransactionHash -> AffE Boolean , utxosAt :: Address -> AffE UtxoMap + -- submitTx + -- evaluateTx + -- chainTip + -- getProtocolParameters + -- this gets done early on + -- perhaps genesis/systemStart should be too + -- getConstantParameters + -- systemStart + -- currentEpoch + -- we need era summaries start + end, and the era summaries slot length + -- ogmios has eraSummaries, BF has epochs for start + end, and genesis for slot length (idk if this is safe) } getQueryHandle :: Contract QueryHandle diff --git a/src/Internal/Contract/WaitUntilSlot.purs b/src/Internal/Contract/WaitUntilSlot.purs new file mode 100644 index 0000000000..11b354208f --- /dev/null +++ b/src/Internal/Contract/WaitUntilSlot.purs @@ -0,0 +1,178 @@ +module Ctl.Internal.Contract.WaitUntilSlot + ( waitUntilSlot + , waitNSlots + , currentSlot + , currentTime + ) where + +import Prelude + +import Ctl.Internal.Contract.Monad(Contract) + +import Contract.Log (logTrace') +import Ctl.Internal.Helpers (liftEither, liftM) +import Ctl.Internal.QueryM (QueryM, getChainTip) +-- import Ctl.Internal.QueryM.EraSummaries (getEraSummaries) +import Ctl.Internal.QueryM.Ogmios (EraSummaries, SystemStart) +-- import Ctl.Internal.QueryM.SystemStart (getSystemStart) +import Ctl.Internal.Serialization.Address (Slot(Slot)) +import Ctl.Internal.Types.BigNum as BigNum +import Ctl.Internal.Types.Chain as Chain +import Ctl.Internal.Types.Interval + ( POSIXTime(POSIXTime) + , findSlotEraSummary + , getSlotLength + , slotToPosixTime + ) +import Ctl.Internal.Types.Natural (Natural) +import Ctl.Internal.Types.Natural as Natural +import Data.Bifunctor (lmap) +import Data.BigInt as BigInt +import Data.DateTime.Instant (unInstant) +import Data.Either (hush) +import Data.Int as Int +import Data.Newtype (unwrap, wrap) +import Data.Time.Duration (Milliseconds(Milliseconds), Seconds) +import Effect.Aff (Milliseconds, delay) +import Effect.Aff.Class (liftAff) +import Effect.Class (liftEffect) +import Effect.Exception (error) +import Effect.Now (now) + +-- | The returned slot will be no less than the slot provided as argument. +waitUntilSlot :: Slot -> Contract Chain.Tip +waitUntilSlot futureSlot = + getChainTip >>= case _ of + tip@(Chain.Tip (Chain.ChainTip { slot })) + | slot >= futureSlot -> pure tip + | otherwise -> do + -- TODO Read sysStart and slotLength(Ms) from env + eraSummaries <- getEraSummaries + sysStart <- getSystemStart + -- slotLengthMs <- map getSlotLength $ liftEither + -- $ lmap (const $ error "Unable to get current Era summary") + -- $ findSlotEraSummary eraSummaries slot + -- `timePadding` in slots + -- If there are less than `slotPadding` slots remaining, start querying for chainTip + -- repeatedly, because it's possible that at any given moment Ogmios suddenly + -- synchronizes with node that is also synchronized with global time. + getLag eraSummaries sysStart slot >>= logLag slotLengthMs + futureTime <- + liftEffect (slotToPosixTime eraSummaries sysStart futureSlot) + >>= hush >>> liftM (error "Unable to convert Slot to POSIXTime") + delayTime <- estimateDelayUntil futureTime + liftAff $ delay delayTime + let + -- Repeatedly check current slot until it's greater than or equal to futureAbsSlot + fetchRepeatedly :: Contract Chain.Tip + fetchRepeatedly = + getChainTip >>= case _ of + currentTip@(Chain.Tip (Chain.ChainTip { slot: currentSlot_ })) + | currentSlot_ >= futureSlot -> pure currentTip + | otherwise -> do + liftAff $ delay $ Milliseconds slotLengthMs + getLag eraSummaries sysStart currentSlot_ >>= logLag + slotLengthMs + fetchRepeatedly + Chain.TipAtGenesis -> do + liftAff $ delay retryDelay + fetchRepeatedly + fetchRepeatedly + Chain.TipAtGenesis -> do + -- We just retry until the tip moves from genesis + liftAff $ delay retryDelay + waitUntilSlot futureSlot + where + retryDelay :: Milliseconds + retryDelay = wrap 1000.0 + + logLag :: Number -> Milliseconds -> Contract Unit + logLag slotLengthMs (Milliseconds lag) = do + logTrace' $ + "waitUntilSlot: current lag: " <> show lag <> " ms, " + <> show (lag / slotLengthMs) + <> " slots." + +-- | Calculate difference between estimated POSIX time of given slot +-- | and current time. +getLag :: EraSummaries -> SystemStart -> Slot -> Contract Milliseconds +getLag eraSummaries sysStart nowSlot = do + nowPosixTime <- liftEffect (slotToPosixTime eraSummaries sysStart nowSlot) >>= + hush >>> liftM (error "Unable to convert Slot to POSIXTime") + nowMs <- unwrap <<< unInstant <$> liftEffect now + logTrace' $ + "getLag: current slot: " <> BigNum.toString (unwrap nowSlot) + <> ", slot time: " + <> BigInt.toString (unwrap nowPosixTime) + <> ", system time: " + <> show nowMs + nowMsBigInt <- liftM (error "Unable to convert Milliseconds to BigInt") $ + BigInt.fromNumber nowMs + pure $ wrap $ BigInt.toNumber $ nowMsBigInt - unwrap nowPosixTime + +-- | Estimate how long we want to wait if we want to wait until `timePadding` +-- | milliseconds before a given `POSIXTime`. +estimateDelayUntil :: POSIXTime -> Contract Milliseconds +estimateDelayUntil futureTimePosix = do + futureTimeSec <- posixTimeToSeconds futureTimePosix + nowMs <- unwrap <<< unInstant <$> liftEffect now + let + result = wrap $ mul 1000.0 $ nonNegative $ + unwrap futureTimeSec - nowMs / 1000.0 + logTrace' $ + "estimateDelayUntil: target time: " <> show (unwrap futureTimeSec * 1000.0) + <> ", system time: " + <> show nowMs + <> ", delay: " + <> show (unwrap result) + <> "ms" + pure result + where + nonNegative :: Number -> Number + nonNegative n + | n < 0.0 = 0.0 + | otherwise = n + +posixTimeToSeconds :: POSIXTime -> Contract Seconds +posixTimeToSeconds (POSIXTime futureTimeBigInt) = do + liftM (error "Unable to convert POSIXTIme to Number") + $ map (wrap <<< Int.toNumber) + $ BigInt.toInt + $ futureTimeBigInt / BigInt.fromInt 1000 + +-- | Wait at least `offset` number of slots. +waitNSlots :: Natural -> Contract Chain.Tip +waitNSlots offset = do + offsetBigNum <- liftM (error "Unable to convert BigInt to BigNum") + $ (BigNum.fromBigInt <<< Natural.toBigInt) offset + if offsetBigNum == BigNum.fromInt 0 then getChainTip + else do + slot <- currentSlot + newSlot <- liftM (error "Unable to advance slot") + $ wrap <$> BigNum.add (unwrap slot) offsetBigNum + waitUntilSlot newSlot + +currentSlot :: Contract Slot +currentSlot = getChainTip <#> case _ of + Chain.Tip (Chain.ChainTip { slot }) -> slot + Chain.TipAtGenesis -> (Slot <<< BigNum.fromInt) 0 + +-- | Get the latest POSIXTime of the current slot. +-- The plutus implementation relies on `slotToEndPOSIXTime` +-- https://github.com/input-output-hk/plutus-apps/blob/fb8a39645e532841b6e38d42ecb957f1945833a5/plutus-contract/src/Plutus/Contract/Trace.hs +currentTime :: Contract POSIXTime +currentTime = currentSlot >>= slotToEndPOSIXTime + +-- | Get the ending 'POSIXTime' of a 'Slot' related to +-- | our `Contract` configuration. +-- see https://github.com/input-output-hk/plutus-apps/blob/fb8a39645e532841b6e38d42ecb957f1945833a5/plutus-ledger/src/Ledger/TimeSlot.hs +slotToEndPOSIXTime :: Slot -> Contract POSIXTime +slotToEndPOSIXTime slot = do + futureSlot <- liftM (error "Unable to advance slot") + $ wrap <$> BigNum.add (unwrap slot) (BigNum.fromInt 1) + eraSummaries <- getEraSummaries + sysStart <- getSystemStart + futureTime <- liftEffect $ slotToPosixTime eraSummaries sysStart futureSlot + >>= hush >>> liftM (error "Unable to convert Slot to POSIXTime") + -- We assume that a slot is 1000 milliseconds here. + pure ((wrap <<< BigInt.fromInt $ -1) + futureTime) diff --git a/src/Internal/Contract/Wallet.purs b/src/Internal/Contract/Wallet.purs new file mode 100644 index 0000000000..7820211671 --- /dev/null +++ b/src/Internal/Contract/Wallet.purs @@ -0,0 +1,193 @@ +module Ctl.Internal.Contract.Wallet where + +import Prelude + +import Ctl.Internal.Contract.Monad (Contract) + +import Ctl.Internal.Contract.QueryHandle (getQueryHandle) +import Ctl.Internal.Helpers (liftM) +import Ctl.Internal.Serialization.Address + ( Address + , NetworkId + , addressPaymentCred + , baseAddressDelegationCred + , baseAddressFromAddress + , stakeCredentialToKeyHash + ) +import Ctl.Internal.Types.PubKeyHash + ( PaymentPubKeyHash + , PubKeyHash + , StakePubKeyHash + ) +import Ctl.Internal.Types.RawBytes (RawBytes) +import Ctl.Internal.Wallet + ( Cip30Connection + , Cip30Wallet + , KeyWallet + , Wallet(KeyWallet, Lode, Flint, Gero, Nami, Eternl) + ) +import Ctl.Internal.Wallet.Cip30 (DataSignature) +import Data.Array (catMaybes) +import Data.Foldable (fold) +import Data.Newtype (unwrap, wrap) +import Effect.Aff + ( Aff + ) +import Effect.Aff.Class (liftAff) +import Effect.Exception (error, throw) +import Control.Monad.Reader (withReaderT) +import Control.Monad.Reader.Trans (ReaderT, asks) +import Ctl.Internal.Cardano.Types.Transaction (UtxoMap) +import Ctl.Internal.Cardano.Types.TransactionUnspentOutput + ( TransactionUnspentOutput + ) +import Ctl.Internal.Helpers as Helpers +import Ctl.Internal.Types.UsedTxOuts (UsedTxOuts, isTxOutRefUsed) +import Data.Array as Array +import Data.Either (hush) +import Data.Map as Map +import Data.Maybe (Maybe(Nothing), fromMaybe, maybe) +import Data.Traversable (for_, traverse) +import Data.UInt as UInt +import Effect.Class (liftEffect) + +getUnusedAddresses :: Contract (Array Address) +getUnusedAddresses = fold <$> do + actionBasedOnWallet _.getUnusedAddresses + (\_ -> pure []) + +getChangeAddress :: Contract (Maybe Address) +getChangeAddress = do + networkId <- getNetworkId + actionBasedOnWallet _.getChangeAddress (\kw -> (unwrap kw).address networkId) + +getRewardAddresses :: Contract (Array Address) +getRewardAddresses = fold <$> do + networkId <- getNetworkId + actionBasedOnWallet _.getRewardAddresses + (\kw -> Array.singleton <$> (unwrap kw).address networkId) + +getWalletAddresses :: Contract (Array Address) +getWalletAddresses = fold <$> do + networkId <- getNetworkId + actionBasedOnWallet _.getWalletAddresses + (\kw -> Array.singleton <$> (unwrap kw).address networkId) + +actionBasedOnWallet + :: forall (a :: Type) + . (Cip30Wallet -> Cip30Connection -> Aff (Maybe a)) + -> (KeyWallet -> Aff a) + -> Contract (Maybe a) +actionBasedOnWallet walletAction keyWalletAction = + withMWalletAff case _ of + Eternl wallet -> callCip30Wallet wallet walletAction + Nami wallet -> callCip30Wallet wallet walletAction + Gero wallet -> callCip30Wallet wallet walletAction + Flint wallet -> callCip30Wallet wallet walletAction + Lode wallet -> callCip30Wallet wallet walletAction + KeyWallet kw -> pure <$> keyWalletAction kw + +signData :: Address -> RawBytes -> Contract (Maybe DataSignature) +signData address payload = do + networkId <- getNetworkId + actionBasedOnWallet + (\wallet conn -> wallet.signData conn address payload) + (\kw -> (unwrap kw).signData networkId payload) + +getWallet :: Contract (Maybe Wallet) +getWallet = asks (_.wallet) + +getNetworkId :: Contract NetworkId +getNetworkId = asks _.networkId + +ownPubKeyHashes :: Contract (Array PubKeyHash) +ownPubKeyHashes = catMaybes <$> do + getWalletAddresses >>= traverse \address -> do + paymentCred <- + liftM + ( error $ + "Unable to get payment credential from Address" + ) $ + addressPaymentCred address + pure $ stakeCredentialToKeyHash paymentCred <#> wrap + +ownPaymentPubKeyHashes :: Contract (Array PaymentPubKeyHash) +ownPaymentPubKeyHashes = map wrap <$> ownPubKeyHashes + +ownStakePubKeysHashes :: Contract (Array (Maybe StakePubKeyHash)) +ownStakePubKeysHashes = do + addresses <- getWalletAddresses + pure $ addressToMStakePubKeyHash <$> addresses + where + + addressToMStakePubKeyHash :: Address -> Maybe StakePubKeyHash + addressToMStakePubKeyHash address = do + baseAddress <- baseAddressFromAddress address + wrap <<< wrap <$> stakeCredentialToKeyHash + (baseAddressDelegationCred baseAddress) + +withMWalletAff + :: forall (a :: Type). (Wallet -> Aff (Maybe a)) -> Contract (Maybe a) +withMWalletAff act = withMWallet (liftAff <<< act) + +withMWallet + :: forall (a :: Type). (Wallet -> Contract (Maybe a)) -> Contract (Maybe a) +withMWallet act = asks _.wallet >>= maybe (pure Nothing) + act + +callCip30Wallet + :: forall (a :: Type) + . Cip30Wallet + -> (Cip30Wallet -> (Cip30Connection -> Aff a)) + -> Aff a +callCip30Wallet wallet act = act wallet wallet.connection + +filterLockedUtxos :: UtxoMap -> Contract UtxoMap +filterLockedUtxos utxos = + withTxRefsCache $ + flip Helpers.filterMapWithKeyM utxos + (\k _ -> not <$> isTxOutRefUsed (unwrap k)) + +withTxRefsCache + :: forall (m :: Type -> Type) (a :: Type) + . ReaderT UsedTxOuts Aff a + -> Contract a +withTxRefsCache = wrap <<< withReaderT _.usedTxOuts + +getWalletCollateral :: Contract (Maybe (Array TransactionUnspentOutput)) +getWalletCollateral = do + queryHandle <- getQueryHandle + mbCollateralUTxOs <- asks (_.wallet) >>= maybe (pure Nothing) + case _ of + Nami wallet -> liftAff $ callCip30Wallet wallet _.getCollateral + Gero wallet -> liftAff $ callCip30Wallet wallet _.getCollateral + Flint wallet -> liftAff $ callCip30Wallet wallet _.getCollateral + Lode wallet -> liftAff $ callCip30Wallet wallet _.getCollateral + Eternl wallet -> liftAff $ callCip30Wallet wallet _.getCollateral + KeyWallet kw -> do + networkId <- getNetworkId + addr <- liftAff $ (unwrap kw).address networkId + utxos <- (liftAff $ queryHandle.utxosAt addr) <#> hush >>> fromMaybe Map.empty + >>= filterLockedUtxos + pparams <- asks $ _.pparams <#> unwrap + let + coinsPerUtxoUnit = pparams.coinsPerUtxoUnit + maxCollateralInputs = UInt.toInt $ + pparams.maxCollateralInputs + liftEffect $ (unwrap kw).selectCollateral coinsPerUtxoUnit + maxCollateralInputs + utxos + for_ mbCollateralUTxOs \collateralUTxOs -> do + pparams <- asks $ _.pparams + let + tooManyCollateralUTxOs = + UInt.fromInt (Array.length collateralUTxOs) > + (unwrap pparams).maxCollateralInputs + when tooManyCollateralUTxOs do + liftEffect $ throw tooManyCollateralUTxOsError + pure mbCollateralUTxOs + where + tooManyCollateralUTxOsError = + "Wallet returned too many UTxOs as collateral. This is likely a bug in \ + \the wallet." + diff --git a/src/Internal/QueryM.purs b/src/Internal/QueryM.purs index f07ca20b9f..c59732782b 100644 --- a/src/Internal/QueryM.purs +++ b/src/Internal/QueryM.purs @@ -39,6 +39,8 @@ module Ctl.Internal.QueryM , getRewardAddresses , getProtocolParameters , getProtocolParametersAff + , getSystemStartAff + , getEraSummariesAff , getWalletAddresses , getWallet , handleAffjaxResponse @@ -574,6 +576,24 @@ getProtocolParametersAff ogmiosWs logger = _.getProtocolParameters unit +getSystemStartAff + :: OgmiosWebSocket + -> (LogLevel -> String -> Effect Unit) + -> Aff Ogmios.SystemStart +getSystemStartAff ogmiosWs logger = + mkOgmiosRequestAff ogmiosWs logger Ogmios.querySystemStartCall + _.systemStart + unit + +getEraSummariesAff + :: OgmiosWebSocket + -> (LogLevel -> String -> Effect Unit) + -> Aff Ogmios.EraSummaries +getEraSummariesAff ogmiosWs logger = + mkOgmiosRequestAff ogmiosWs logger Ogmios.queryEraSummariesCall + _.eraSummaries + unit + -------------------------------------------------------------------------------- -- Ogmios Local State Query Protocol -------------------------------------------------------------------------------- diff --git a/templates/ctl-scaffold/src/Scaffold.purs b/templates/ctl-scaffold/src/Scaffold.purs index f0e44c8fcc..f6241b4713 100644 --- a/templates/ctl-scaffold/src/Scaffold.purs +++ b/templates/ctl-scaffold/src/Scaffold.purs @@ -8,7 +8,7 @@ import Contract.Address (ownPaymentPubKeyHash) import Contract.Log (logInfo') import Contract.Monad (Contract) -contract :: Contract () Unit +contract :: Contract Unit contract = do logInfo' "Welcome to CTL! Your wallet's payment PubKey hash is:" logInfo' <<< show =<< ownPaymentPubKeyHash From 8000a457b49d24c85ffb45e8769aa7c0304f582c Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Sun, 27 Nov 2022 23:37:34 +0000 Subject: [PATCH 011/373] WIP: Move time related operations to Contract, with new abstractions. Added new handlers for chain tip and current epoch. --- examples/AlwaysMints.purs | 4 +- examples/AlwaysSucceeds.purs | 8 +- examples/AwaitTxConfirmedWithTimeout.purs | 2 +- examples/BalanceTxConstraints.purs | 2 +- examples/ByUrl.purs | 2 +- examples/Cip30.purs | 6 +- examples/ContractTestUtils.purs | 6 +- examples/Datums.purs | 6 +- examples/IncludeDatum.purs | 6 +- examples/KeyWallet/Cip30.purs | 6 +- .../KeyWallet/Internal/Cip30Contract.purs | 2 +- .../KeyWallet/Internal/Pkh2PkhContract.purs | 2 +- examples/Lose7Ada.purs | 6 +- examples/MintsMultipleTokens.purs | 8 +- examples/MultipleRedeemers.purs | 10 +- examples/NativeScriptMints.purs | 4 +- examples/OneShotMinting.purs | 12 +- examples/Pkh2Pkh.purs | 2 +- examples/PlutusV2/AlwaysSucceeds.purs | 2 +- examples/PlutusV2/InlineDatum.purs | 10 +- examples/PlutusV2/OneShotMinting.purs | 6 +- examples/PlutusV2/ReferenceInputs.purs | 2 +- .../PlutusV2/ReferenceInputsAndScripts.purs | 8 +- examples/PlutusV2/ReferenceScripts.purs | 6 +- examples/PlutusV2/Scripts/AlwaysMints.purs | 4 +- examples/PlutusV2/Scripts/AlwaysSucceeds.purs | 2 +- examples/SatisfiesAnyOf.purs | 2 +- examples/SendsToken.purs | 8 +- examples/SignMultiple.purs | 2 +- examples/TxChaining.purs | 2 +- examples/Utxos.purs | 2 +- examples/Wallet.purs | 2 +- src/Contract/Chain.purs | 28 +-- src/Contract/Config.purs | 43 +++-- src/Contract/ProtocolParameters.purs | 8 +- src/Contract/Scripts.purs | 16 +- src/Contract/Staking.purs | 28 ++- src/Contract/Time.purs | 30 +-- src/Contract/Transaction.purs | 15 +- src/Internal/Contract.purs | 20 ++ src/Internal/Contract/ApplyArgs.purs | 82 ++++++++ .../AwaitTxConfirmed.purs | 34 ++-- src/Internal/Contract/Monad.purs | 67 ++++++- src/Internal/Contract/QueryBackend.purs | 1 + src/Internal/Contract/QueryHandle.purs | 8 + src/Internal/Contract/WaitUntilSlot.purs | 28 +-- src/Internal/Contract/Wallet.purs | 4 +- src/Internal/QueryM/WaitUntilSlot.purs | 175 ------------------ src/Internal/Types/Interval.purs | 130 ++++++------- src/Internal/Types/ScriptLookups.purs | 25 +-- src/Internal/Types/TypedTxOut.purs | 15 +- test/AffInterface.purs | 2 +- 52 files changed, 457 insertions(+), 454 deletions(-) create mode 100644 src/Internal/Contract.purs create mode 100644 src/Internal/Contract/ApplyArgs.purs rename src/Internal/{QueryM => Contract}/AwaitTxConfirmed.purs (74%) delete mode 100644 src/Internal/QueryM/WaitUntilSlot.purs diff --git a/examples/AlwaysMints.purs b/examples/AlwaysMints.purs index 21c57746d0..81b9b9140d 100644 --- a/examples/AlwaysMints.purs +++ b/examples/AlwaysMints.purs @@ -35,7 +35,7 @@ import Effect.Exception (error) main :: Effect Unit main = example testnetNamiConfig -contract :: Contract () Unit +contract :: Contract Unit contract = do logInfo' "Running Examples.AlwaysMints" mp /\ cs <- Helpers.mkCurrencySymbol alwaysMintsPolicy @@ -65,7 +65,7 @@ alwaysMintsPolicyMaybe = do envelope <- decodeTextEnvelope alwaysMints PlutusMintingPolicy <$> plutusScriptV1FromEnvelope envelope -alwaysMintsPolicy :: Contract () MintingPolicy +alwaysMintsPolicy :: Contract MintingPolicy alwaysMintsPolicy = liftMaybe (error "Error decoding alwaysMintsPolicy") alwaysMintsPolicyMaybe diff --git a/examples/AlwaysSucceeds.purs b/examples/AlwaysSucceeds.purs index e1af946a94..7222c1d4bd 100644 --- a/examples/AlwaysSucceeds.purs +++ b/examples/AlwaysSucceeds.purs @@ -42,7 +42,7 @@ import Effect.Exception (error) main :: Effect Unit main = example testnetNamiConfig -contract :: Contract () Unit +contract :: Contract Unit contract = do logInfo' "Running Examples.AlwaysSucceeds" validator <- alwaysSucceedsScript @@ -57,7 +57,7 @@ example :: ConfigParams () -> Effect Unit example cfg = launchAff_ do runContract cfg contract -payToAlwaysSucceeds :: ValidatorHash -> Contract () TransactionHash +payToAlwaysSucceeds :: ValidatorHash -> Contract TransactionHash payToAlwaysSucceeds vhash = do -- Send to own stake credential. This is used to test mustPayToScriptAddress. mbStakeKeyHash <- join <<< head <$> ownStakePubKeysHashes @@ -87,7 +87,7 @@ spendFromAlwaysSucceeds :: ValidatorHash -> Validator -> TransactionHash - -> Contract () Unit + -> Contract Unit spendFromAlwaysSucceeds vhash validator txId = do -- Use own stake credential if available mbStakeKeyHash <- join <<< head <$> ownStakePubKeysHashes @@ -119,7 +119,7 @@ spendFromAlwaysSucceeds vhash validator txId = do foreign import alwaysSucceeds :: String -alwaysSucceedsScript :: Contract () Validator +alwaysSucceedsScript :: Contract Validator alwaysSucceedsScript = liftMaybe (error "Error decoding alwaysSucceeds") do envelope <- decodeTextEnvelope alwaysSucceeds diff --git a/examples/AwaitTxConfirmedWithTimeout.purs b/examples/AwaitTxConfirmedWithTimeout.purs index 06c8528dac..17c0844c83 100644 --- a/examples/AwaitTxConfirmedWithTimeout.purs +++ b/examples/AwaitTxConfirmedWithTimeout.purs @@ -27,7 +27,7 @@ example :: ConfigParams () -> Effect Unit example cfg = launchAff_ do runContract cfg contract -contract :: Contract () Unit +contract :: Contract Unit contract = do logInfo' "Running AwaitTxConfirmedWithTimeout" let diff --git a/examples/BalanceTxConstraints.purs b/examples/BalanceTxConstraints.purs index c41b61dc01..a877411aa1 100644 --- a/examples/BalanceTxConstraints.purs +++ b/examples/BalanceTxConstraints.purs @@ -107,7 +107,7 @@ assertions = , assertSelectedUtxoIsNotSpent ] -contract :: ContractParams -> Contract () Unit +contract :: ContractParams -> Contract Unit contract (ContractParams p) = do logInfo' "Examples.BalanceTxConstraints" diff --git a/examples/ByUrl.purs b/examples/ByUrl.purs index 131bc97b07..a73038839b 100644 --- a/examples/ByUrl.purs +++ b/examples/ByUrl.purs @@ -65,7 +65,7 @@ wallets = Map.fromFoldable , "plutip-lode-mock" /\ mainnetLodeConfig /\ Just MockLode ] -examples :: Map E2ETestName (Contract () Unit) +examples :: Map E2ETestName (Contract Unit) examples = Map.fromFoldable [ "AlwaysMints" /\ AlwaysMints.contract , "NativeScriptMints" /\ NativeScriptMints.contract diff --git a/examples/Cip30.purs b/examples/Cip30.purs index 8e273fc765..d310404bdc 100644 --- a/examples/Cip30.purs +++ b/examples/Cip30.purs @@ -60,7 +60,7 @@ nonConfigFunctions extensionWallet = do result <- f extensionWallet log $ msg <> ":" <> (show result) -contract :: Contract () Unit +contract :: Contract Unit contract = do logInfo' "Running Examples.Cip30" logInfo' "Funtions that depend on `Contract`" @@ -84,8 +84,8 @@ contract = do :: forall (a :: Type) . Show a => String - -> Contract () a - -> Contract () a + -> Contract a + -> Contract a performAndLog logMsg cont = do result <- cont logInfo' $ logMsg <> ": " <> show result diff --git a/examples/ContractTestUtils.purs b/examples/ContractTestUtils.purs index e45b056812..563140ffd5 100644 --- a/examples/ContractTestUtils.purs +++ b/examples/ContractTestUtils.purs @@ -78,7 +78,7 @@ type ContractResult = mkAssertions :: ContractParams - -> Contract () + -> Contract ( Array (ContractWrapAssertion () ContractResult) /\ Array (ContractBasicAssertion () ContractResult Unit) ) @@ -115,7 +115,7 @@ mkAssertions params@(ContractParams p) = do TestUtils.assertTxHasMetadata "CIP25 Metadata" txHash p.txMetadata ] -contract :: ContractParams -> Contract () Unit +contract :: ContractParams -> Contract Unit contract params@(ContractParams p) = do logInfo' "Running Examples.ContractTestUtils" ownPkh <- liftedM "Failed to get own PKH" $ head <$> ownPaymentPubKeysHashes @@ -181,7 +181,7 @@ contract params@(ContractParams p) = do OutputDatumHash _ -> true _ -> false -getReceiverAddress :: ContractParams -> Contract () (Maybe Address) +getReceiverAddress :: ContractParams -> Contract (Maybe Address) getReceiverAddress (ContractParams { receiverPkh, receiverSkh }) = getNetworkId <#> \networkId -> case receiverSkh of diff --git a/examples/Datums.purs b/examples/Datums.purs index 971ef55c05..b343cc5072 100644 --- a/examples/Datums.purs +++ b/examples/Datums.purs @@ -19,7 +19,7 @@ module Ctl.Examples.Datums (main, contract, example) where import Contract.Prelude -import Contract.Config (ConfigParams, testnetConfig) +import Contract.Config (ContractParams, testnetConfig) import Contract.Log (logInfo') import Contract.Monad (Contract, launchAff_, runContract) import Contract.PlutusData (DataHash, getDatumByHash, getDatumsByHashes) @@ -28,7 +28,7 @@ import Contract.Prim.ByteArray (hexToByteArrayUnsafe) main :: Effect Unit main = example testnetConfig -contract :: Contract () Unit +contract :: Contract Unit contract = do logInfo' "Running Examples.Datums" logInfo' <<< show =<< getDatumByHash @@ -45,6 +45,6 @@ contract = do mkDatumHash :: String -> DataHash mkDatumHash = wrap <<< hexToByteArrayUnsafe -example :: ConfigParams () -> Effect Unit +example :: ContractParams -> Effect Unit example cfg = launchAff_ $ do runContract cfg contract diff --git a/examples/IncludeDatum.purs b/examples/IncludeDatum.purs index 035342882d..cc339ee500 100644 --- a/examples/IncludeDatum.purs +++ b/examples/IncludeDatum.purs @@ -55,7 +55,7 @@ example cfg = launchAff_ do datum :: Datum datum = Datum $ Integer $ BigInt.fromInt 42 -payToIncludeDatum :: ValidatorHash -> Contract () TransactionHash +payToIncludeDatum :: ValidatorHash -> Contract TransactionHash payToIncludeDatum vhash = let constraints :: TxConstraints Unit Unit @@ -75,7 +75,7 @@ spendFromIncludeDatum :: ValidatorHash -> Validator -> TransactionHash - -> Contract () Unit + -> Contract Unit spendFromIncludeDatum vhash validator txId = do let scriptAddress = scriptHashAddress vhash Nothing utxos <- utxosAt scriptAddress @@ -97,7 +97,7 @@ spendFromIncludeDatum vhash validator txId = do foreign import includeDatum :: String -- | checks if the datum equals 42 -only42Script :: Contract () Validator +only42Script :: Contract Validator only42Script = liftMaybe (error "Error decoding includeDatum") do envelope <- decodeTextEnvelope includeDatum diff --git a/examples/KeyWallet/Cip30.purs b/examples/KeyWallet/Cip30.purs index 5334312b9b..b86911c352 100644 --- a/examples/KeyWallet/Cip30.purs +++ b/examples/KeyWallet/Cip30.purs @@ -24,7 +24,7 @@ import Effect.Exception (error) main :: Effect Unit main = runKeyWalletContract_ mkContract -mkContract :: RawBytes -> Contract () Unit +mkContract :: RawBytes -> Contract Unit mkContract dat = do logInfo' "Running Examples.KeyWallet.Cip30" logInfo' "Funtions that depend on `Contract`" @@ -44,8 +44,8 @@ mkContract dat = do :: forall (a :: Type) . Show a => String - -> Contract () a - -> Contract () a + -> Contract a + -> Contract a performAndLog logMsg cont = do result <- cont logInfo' $ logMsg <> ": " <> show result diff --git a/examples/KeyWallet/Internal/Cip30Contract.purs b/examples/KeyWallet/Internal/Cip30Contract.purs index 1fb8dd6873..6d8840cf08 100644 --- a/examples/KeyWallet/Internal/Cip30Contract.purs +++ b/examples/KeyWallet/Internal/Cip30Contract.purs @@ -27,7 +27,7 @@ import Effect.Class (class MonadEffect) import Effect.Exception (Error, error, message) runKeyWalletContract_ - :: (RawBytes -> Contract () Unit) -> Effect Unit + :: (RawBytes -> Contract Unit) -> Effect Unit runKeyWalletContract_ contract = HtmlForm.mkForm \input log' unlock -> launchAff_ $ flip catchError (errorHandler log' unlock) $ do diff --git a/examples/KeyWallet/Internal/Pkh2PkhContract.purs b/examples/KeyWallet/Internal/Pkh2PkhContract.purs index ff5fb99c23..0a1b98466e 100644 --- a/examples/KeyWallet/Internal/Pkh2PkhContract.purs +++ b/examples/KeyWallet/Internal/Pkh2PkhContract.purs @@ -31,7 +31,7 @@ import Effect.Class (class MonadEffect) import Effect.Exception (Error, error, message) runKeyWalletContract_ - :: (PaymentPubKeyHash -> BigInt -> Unlock -> Contract () Unit) -> Effect Unit + :: (PaymentPubKeyHash -> BigInt -> Unlock -> Contract Unit) -> Effect Unit runKeyWalletContract_ contract = HtmlForm.mkForm \input log' unlock -> launchAff_ $ flip catchError (errorHandler log' unlock) $ do diff --git a/examples/Lose7Ada.purs b/examples/Lose7Ada.purs index 3989393558..690712ec08 100644 --- a/examples/Lose7Ada.purs +++ b/examples/Lose7Ada.purs @@ -57,7 +57,7 @@ example cfg = launchAff_ do logInfo' "Tx submitted successfully, Try to spend locked values" spendFromAlwaysFails vhash validator txId -payToAlwaysFails :: ValidatorHash -> Contract () TransactionHash +payToAlwaysFails :: ValidatorHash -> Contract TransactionHash payToAlwaysFails vhash = do let constraints :: TxConstraints Unit Unit @@ -76,7 +76,7 @@ spendFromAlwaysFails :: ValidatorHash -> Validator -> TransactionHash - -> Contract () Unit + -> Contract Unit spendFromAlwaysFails vhash validator txId = do balanceBefore <- fold <$> getWalletBalance let scriptAddress = scriptHashAddress vhash Nothing @@ -116,7 +116,7 @@ spendFromAlwaysFails vhash validator txId = do foreign import alwaysFails :: String -alwaysFailsScript :: Contract () Validator +alwaysFailsScript :: Contract Validator alwaysFailsScript = liftMaybe (error "Error decoding alwaysFails") do envelope <- decodeTextEnvelope alwaysFails diff --git a/examples/MintsMultipleTokens.purs b/examples/MintsMultipleTokens.purs index 7840e90085..ff6d40a896 100644 --- a/examples/MintsMultipleTokens.purs +++ b/examples/MintsMultipleTokens.purs @@ -37,7 +37,7 @@ import Effect.Exception (error) main :: Effect Unit main = example testnetNamiConfig -contract :: Contract () Unit +contract :: Contract Unit contract = do logInfo' "Running Examples.MintsMultipleTokens" tn1 <- Helpers.mkTokenName "Token with a long name" @@ -79,19 +79,19 @@ foreign import redeemerInt1 :: String foreign import redeemerInt2 :: String foreign import redeemerInt3 :: String -mintingPolicyRdmrInt1 :: Contract () MintingPolicy +mintingPolicyRdmrInt1 :: Contract MintingPolicy mintingPolicyRdmrInt1 = liftMaybe (error "Error decoding redeemerInt1") do envelope <- decodeTextEnvelope redeemerInt3 PlutusMintingPolicy <$> plutusScriptV1FromEnvelope envelope -mintingPolicyRdmrInt2 :: Contract () MintingPolicy +mintingPolicyRdmrInt2 :: Contract MintingPolicy mintingPolicyRdmrInt2 = liftMaybe (error "Error decoding redeemerInt2") do envelope <- decodeTextEnvelope redeemerInt3 PlutusMintingPolicy <$> plutusScriptV1FromEnvelope envelope -mintingPolicyRdmrInt3 :: Contract () MintingPolicy +mintingPolicyRdmrInt3 :: Contract MintingPolicy mintingPolicyRdmrInt3 = liftMaybe (error "Error decoding redeemerInt3") do envelope <- decodeTextEnvelope redeemerInt3 diff --git a/examples/MultipleRedeemers.purs b/examples/MultipleRedeemers.purs index 9b0a55ff88..1b6e1cc1e4 100644 --- a/examples/MultipleRedeemers.purs +++ b/examples/MultipleRedeemers.purs @@ -44,7 +44,7 @@ import Data.Map as Map import Data.Traversable (sequence) import Effect.Exception (error) -contract :: Contract () Unit +contract :: Contract Unit contract = do tokenName <- mkTokenName "Token" validator1 <- redeemerIs1Validator @@ -69,7 +69,7 @@ contract = do constraints void $ awaitTxConfirmed txHash -contractWithMintRedeemers :: Contract () Unit +contractWithMintRedeemers :: Contract Unit contractWithMintRedeemers = do tokenName <- mkTokenName "Token" validator1 <- redeemerIs1Validator @@ -127,19 +127,19 @@ foreign import vredeemerInt2 :: String foreign import vredeemerInt3 :: String -- | checks whether redeemer is 1 -redeemerIs1Validator :: Contract () Validator +redeemerIs1Validator :: Contract Validator redeemerIs1Validator = liftMaybe (error "Error decoding vredeemerInt1") do envelope <- decodeTextEnvelope vredeemerInt1 Validator <$> plutusScriptV1FromEnvelope envelope -- | checks whether redeemer is 2 -redeemerIs2Validator :: Contract () Validator +redeemerIs2Validator :: Contract Validator redeemerIs2Validator = liftMaybe (error "Error decoding vredeemerInt2") do envelope <- decodeTextEnvelope vredeemerInt2 Validator <$> plutusScriptV1FromEnvelope envelope -- | checks whether redeemer is 3 -redeemerIs3Validator :: Contract () Validator +redeemerIs3Validator :: Contract Validator redeemerIs3Validator = liftMaybe (error "Error decoding vredeemerInt3") do envelope <- decodeTextEnvelope vredeemerInt3 Validator <$> plutusScriptV1FromEnvelope envelope diff --git a/examples/NativeScriptMints.purs b/examples/NativeScriptMints.purs index c2bea6a67f..2c0527694f 100644 --- a/examples/NativeScriptMints.purs +++ b/examples/NativeScriptMints.purs @@ -34,7 +34,7 @@ import Data.BigInt as BigInt main :: Effect Unit main = example testnetNamiConfig -contract :: Contract () Unit +contract :: Contract Unit contract = do logInfo' "Running Examples.NativeScriptMints" @@ -60,7 +60,7 @@ contract = do toSelfContract cs tn $ BigInt.fromInt 50 -toSelfContract :: CurrencySymbol -> TokenName -> BigInt -> Contract () Unit +toSelfContract :: CurrencySymbol -> TokenName -> BigInt -> Contract Unit toSelfContract cs tn amount = do pkh <- liftedM "Failed to get own PKH" $ head <$> ownPaymentPubKeysHashes skh <- join <<< head <$> ownStakePubKeysHashes diff --git a/examples/OneShotMinting.purs b/examples/OneShotMinting.purs index 65fdc0a298..05661aba0d 100644 --- a/examples/OneShotMinting.purs +++ b/examples/OneShotMinting.purs @@ -73,14 +73,14 @@ mkAssertions ownAddress nft = \{ txFinalFee } -> pure txFinalFee ] -contract :: Contract () Unit +contract :: Contract Unit contract = mkContractWithAssertions "Examples.OneShotMinting" oneShotMintingPolicy mkContractWithAssertions :: String - -> (TransactionInput -> Contract () MintingPolicy) - -> Contract () Unit + -> (TransactionInput -> Contract MintingPolicy) + -> Contract Unit mkContractWithAssertions exampleName mkMintingPolicy = do logInfo' ("Running " <> exampleName) @@ -116,11 +116,11 @@ mkContractWithAssertions exampleName mkMintingPolicy = do foreign import oneShotMinting :: String -oneShotMintingPolicy :: TransactionInput -> Contract () MintingPolicy +oneShotMintingPolicy :: TransactionInput -> Contract MintingPolicy oneShotMintingPolicy = map PlutusMintingPolicy <<< oneShotMintingPolicyScript -oneShotMintingPolicyScript :: TransactionInput -> Contract () PlutusScript +oneShotMintingPolicyScript :: TransactionInput -> Contract PlutusScript oneShotMintingPolicyScript txInput = do script <- liftMaybe (error "Error decoding oneShotMinting") do envelope <- decodeTextEnvelope oneShotMinting @@ -130,7 +130,7 @@ oneShotMintingPolicyScript txInput = do mkOneShotMintingPolicy :: PlutusScript -> TransactionInput - -> Contract () PlutusScript + -> Contract PlutusScript mkOneShotMintingPolicy unappliedMintingPolicy oref = let mintingPolicyArgs :: Array PlutusData diff --git a/examples/Pkh2Pkh.purs b/examples/Pkh2Pkh.purs index 4e511bbc8a..a154a30f71 100644 --- a/examples/Pkh2Pkh.purs +++ b/examples/Pkh2Pkh.purs @@ -20,7 +20,7 @@ import Data.BigInt as BigInt main :: Effect Unit main = example testnetNamiConfig -contract :: Contract () Unit +contract :: Contract Unit contract = do logInfo' "Running Examples.Pkh2Pkh" pkh <- liftedM "Failed to get own PKH" $ head <$> ownPaymentPubKeysHashes diff --git a/examples/PlutusV2/AlwaysSucceeds.purs b/examples/PlutusV2/AlwaysSucceeds.purs index 826ad8d754..9844c022c7 100644 --- a/examples/PlutusV2/AlwaysSucceeds.purs +++ b/examples/PlutusV2/AlwaysSucceeds.purs @@ -25,7 +25,7 @@ import Ctl.Examples.PlutusV2.Scripts.AlwaysSucceeds (alwaysSucceedsScriptV2) main :: Effect Unit main = example testnetNamiConfig -contract :: Contract () Unit +contract :: Contract Unit contract = do logInfo' "Running Examples.PlutusV2.AlwaysSucceeds" validator <- alwaysSucceedsScriptV2 diff --git a/examples/PlutusV2/InlineDatum.purs b/examples/PlutusV2/InlineDatum.purs index 01db393f88..dc4920de13 100644 --- a/examples/PlutusV2/InlineDatum.purs +++ b/examples/PlutusV2/InlineDatum.purs @@ -61,7 +61,7 @@ example cfg = launchAff_ do plutusData :: PlutusData plutusData = Integer $ BigInt.fromInt 31415927 -payToCheckDatumIsInline :: ValidatorHash -> Contract () TransactionHash +payToCheckDatumIsInline :: ValidatorHash -> Contract TransactionHash payToCheckDatumIsInline vhash = do let datum :: Datum @@ -83,7 +83,7 @@ spendFromCheckDatumIsInline :: ValidatorHash -> Validator -> TransactionHash - -> Contract () Unit + -> Contract Unit spendFromCheckDatumIsInline vhash validator txId = do let scriptAddress = scriptHashAddress vhash Nothing utxos <- utxosAt scriptAddress @@ -118,7 +118,7 @@ spendFromCheckDatumIsInline vhash validator txId = do hasTransactionId (TransactionInput tx /\ _) = tx.transactionId == txId -payToCheckDatumIsInlineWrong :: ValidatorHash -> Contract () TransactionHash +payToCheckDatumIsInlineWrong :: ValidatorHash -> Contract TransactionHash payToCheckDatumIsInlineWrong vhash = do let datum :: Datum @@ -139,7 +139,7 @@ payToCheckDatumIsInlineWrong vhash = do readFromCheckDatumIsInline :: ValidatorHash -> TransactionHash - -> Contract () Unit + -> Contract Unit readFromCheckDatumIsInline vhash txId = do let scriptAddress = scriptHashAddress vhash Nothing utxos <- utxosAt scriptAddress @@ -163,7 +163,7 @@ readFromCheckDatumIsInline vhash txId = do foreign import checkDatumIsInline :: String -checkDatumIsInlineScript :: Contract () Validator +checkDatumIsInlineScript :: Contract Validator checkDatumIsInlineScript = liftMaybe (error "Error decoding checkDatumIsInline") do envelope <- decodeTextEnvelope checkDatumIsInline diff --git a/examples/PlutusV2/OneShotMinting.purs b/examples/PlutusV2/OneShotMinting.purs index 4f2a23d93e..ad4716b9ca 100644 --- a/examples/PlutusV2/OneShotMinting.purs +++ b/examples/PlutusV2/OneShotMinting.purs @@ -33,18 +33,18 @@ example :: ConfigParams () -> Effect Unit example cfg = launchAff_ do runContract cfg contract -contract :: Contract () Unit +contract :: Contract Unit contract = mkContractWithAssertions "Examples.PlutusV2.OneShotMinting" oneShotMintingPolicyV2 foreign import oneShotMinting :: String -oneShotMintingPolicyV2 :: TransactionInput -> Contract () MintingPolicy +oneShotMintingPolicyV2 :: TransactionInput -> Contract MintingPolicy oneShotMintingPolicyV2 = map PlutusMintingPolicy <<< oneShotMintingPolicyScriptV2 -oneShotMintingPolicyScriptV2 :: TransactionInput -> Contract () PlutusScript +oneShotMintingPolicyScriptV2 :: TransactionInput -> Contract PlutusScript oneShotMintingPolicyScriptV2 txInput = do script <- liftMaybe (error "Error decoding oneShotMinting") do envelope <- decodeTextEnvelope oneShotMinting diff --git a/examples/PlutusV2/ReferenceInputs.purs b/examples/PlutusV2/ReferenceInputs.purs index 7e5645955a..39fd1e45e8 100644 --- a/examples/PlutusV2/ReferenceInputs.purs +++ b/examples/PlutusV2/ReferenceInputs.purs @@ -51,7 +51,7 @@ main = example testnetNamiConfig example :: ConfigParams () -> Effect Unit example = launchAff_ <<< flip runContract contract -contract :: Contract () Unit +contract :: Contract Unit contract = do logInfo' "Running Examples.PlutusV2.ReferenceInputs" diff --git a/examples/PlutusV2/ReferenceInputsAndScripts.purs b/examples/PlutusV2/ReferenceInputsAndScripts.purs index 11fc06d576..596b14dd75 100644 --- a/examples/PlutusV2/ReferenceInputsAndScripts.purs +++ b/examples/PlutusV2/ReferenceInputsAndScripts.purs @@ -69,7 +69,7 @@ example :: ConfigParams () -> Effect Unit example cfg = launchAff_ do runContract cfg contract -contract :: Contract () Unit +contract :: Contract Unit contract = do logInfo' "Running Examples.PlutusV2.ReferenceInputsAndScripts" validator <- alwaysSucceedsScriptV2 @@ -93,7 +93,7 @@ contract = do tokenName payToAlwaysSucceedsAndCreateScriptRefOutput - :: ValidatorHash -> ScriptRef -> ScriptRef -> Contract () TransactionHash + :: ValidatorHash -> ScriptRef -> ScriptRef -> Contract TransactionHash payToAlwaysSucceedsAndCreateScriptRefOutput vhash validatorRef mpRef = do pkh <- liftedM "Failed to get own PKH" $ head <$> ownPaymentPubKeysHashes skh <- join <<< head <$> ownStakePubKeysHashes @@ -122,7 +122,7 @@ spendFromAlwaysSucceeds -> PlutusScript -> PlutusScript -> TokenName - -> Contract () Unit + -> Contract Unit spendFromAlwaysSucceeds vhash txId validator mp tokenName = do let scriptAddress = scriptHashAddress vhash Nothing ownAddress <- liftedM "Failed to get own address" $ head <$> @@ -184,7 +184,7 @@ mustPayToPubKeyStakeAddressWithScriptRef pkh (Just skh) = Constraints.mustPayToPubKeyAddressWithScriptRef pkh skh mintAlwaysMintsV2ToTheScript - :: TokenName -> Validator -> Int -> Contract () Unit + :: TokenName -> Validator -> Int -> Contract Unit mintAlwaysMintsV2ToTheScript tokenName validator sum = do mp <- alwaysMintsPolicyV2 cs <- liftContractM "Cannot get cs" $ Value.scriptCurrencySymbol mp diff --git a/examples/PlutusV2/ReferenceScripts.purs b/examples/PlutusV2/ReferenceScripts.purs index 731db274b4..983192e476 100644 --- a/examples/PlutusV2/ReferenceScripts.purs +++ b/examples/PlutusV2/ReferenceScripts.purs @@ -42,7 +42,7 @@ example :: ConfigParams () -> Effect Unit example cfg = launchAff_ do runContract cfg contract -contract :: Contract () Unit +contract :: Contract Unit contract = do logInfo' "Running Examples.PlutusV2.ReferenceScripts" validator <- alwaysSucceedsScriptV2 @@ -60,7 +60,7 @@ contract = do spendFromAlwaysSucceeds vhash txId payWithScriptRefToAlwaysSucceeds - :: ValidatorHash -> ScriptRef -> Contract () TransactionHash + :: ValidatorHash -> ScriptRef -> Contract TransactionHash payWithScriptRefToAlwaysSucceeds vhash scriptRef = do -- Send to own stake credential. This is used to test -- `mustPayToScriptAddressWithScriptRef` @@ -87,7 +87,7 @@ payWithScriptRefToAlwaysSucceeds vhash scriptRef = do Helpers.buildBalanceSignAndSubmitTx lookups constraints -spendFromAlwaysSucceeds :: ValidatorHash -> TransactionHash -> Contract () Unit +spendFromAlwaysSucceeds :: ValidatorHash -> TransactionHash -> Contract Unit spendFromAlwaysSucceeds vhash txId = do -- Send to own stake credential. This is used to test -- `mustPayToScriptAddressWithScriptRef` diff --git a/examples/PlutusV2/Scripts/AlwaysMints.purs b/examples/PlutusV2/Scripts/AlwaysMints.purs index aee3d6bfa2..8f89cc3d2a 100644 --- a/examples/PlutusV2/Scripts/AlwaysMints.purs +++ b/examples/PlutusV2/Scripts/AlwaysMints.purs @@ -13,10 +13,10 @@ import Effect.Exception (error) foreign import alwaysMintsV2 :: String -alwaysMintsPolicyV2 :: Contract () MintingPolicy +alwaysMintsPolicyV2 :: Contract MintingPolicy alwaysMintsPolicyV2 = PlutusMintingPolicy <$> alwaysMintsPolicyScriptV2 -alwaysMintsPolicyScriptV2 :: Contract () PlutusScript +alwaysMintsPolicyScriptV2 :: Contract PlutusScript alwaysMintsPolicyScriptV2 = liftMaybe (error "Error decoding alwaysMintsV2") do envelope <- decodeTextEnvelope alwaysMintsV2 diff --git a/examples/PlutusV2/Scripts/AlwaysSucceeds.purs b/examples/PlutusV2/Scripts/AlwaysSucceeds.purs index e06ef58766..5b9f273f60 100644 --- a/examples/PlutusV2/Scripts/AlwaysSucceeds.purs +++ b/examples/PlutusV2/Scripts/AlwaysSucceeds.purs @@ -12,7 +12,7 @@ import Effect.Exception (error) foreign import alwaysSucceedsV2 :: String -alwaysSucceedsScriptV2 :: Contract () Validator +alwaysSucceedsScriptV2 :: Contract Validator alwaysSucceedsScriptV2 = liftMaybe (error "Error decoding alwaysSucceeds") do envelope <- decodeTextEnvelope alwaysSucceedsV2 diff --git a/examples/SatisfiesAnyOf.purs b/examples/SatisfiesAnyOf.purs index 34175cf53b..07efebee64 100644 --- a/examples/SatisfiesAnyOf.purs +++ b/examples/SatisfiesAnyOf.purs @@ -38,7 +38,7 @@ example cfg = launchAff_ do wrongDatum :: Datum wrongDatum = Datum $ Integer $ BigInt.fromInt 42 -testMustSatisfyAnyOf :: Contract () Unit +testMustSatisfyAnyOf :: Contract Unit testMustSatisfyAnyOf = do wrongDatumHash <- liftMaybe (error "Cannot get DatumHash") $ Hashing.datumHash wrongDatum diff --git a/examples/SendsToken.purs b/examples/SendsToken.purs index cecb8af0ea..d8534897df 100644 --- a/examples/SendsToken.purs +++ b/examples/SendsToken.purs @@ -32,7 +32,7 @@ example :: ConfigParams () -> Effect Unit example cfg = launchAff_ do runContract cfg contract -contract :: Contract () Unit +contract :: Contract Unit contract = do logInfo' "Running Examples.SendsToken" @@ -42,7 +42,7 @@ contract = do sendToken >>= awaitTxConfirmed logInfo' "Tx submitted successfully!" -mintToken :: Contract () TransactionHash +mintToken :: Contract TransactionHash mintToken = do mp /\ value <- tokenValue let @@ -54,7 +54,7 @@ mintToken = do Helpers.buildBalanceSignAndSubmitTx lookups constraints -sendToken :: Contract () TransactionHash +sendToken :: Contract TransactionHash sendToken = do pkh <- liftedM "Failed to get own PKH" $ head <$> ownPaymentPubKeysHashes skh <- join <<< head <$> ownStakePubKeysHashes @@ -68,7 +68,7 @@ sendToken = do Helpers.buildBalanceSignAndSubmitTx lookups constraints -tokenValue :: Contract () (MintingPolicy /\ Value) +tokenValue :: Contract (MintingPolicy /\ Value) tokenValue = do mp /\ cs <- Helpers.mkCurrencySymbol alwaysMintsPolicy tn <- Helpers.mkTokenName "TheToken" diff --git a/examples/SignMultiple.purs b/examples/SignMultiple.purs index 58d50f52ff..c7d3eb1768 100644 --- a/examples/SignMultiple.purs +++ b/examples/SignMultiple.purs @@ -44,7 +44,7 @@ getLockedInputs = do main :: Effect Unit main = example testnetNamiConfig -contract :: Contract () Unit +contract :: Contract Unit contract = do logInfo' "Running Examples.SignMultiple" pkh <- liftedM "Failed to get own PKH" $ head <$> ownPaymentPubKeysHashes diff --git a/examples/TxChaining.purs b/examples/TxChaining.purs index 9a8fd893dc..0537398140 100644 --- a/examples/TxChaining.purs +++ b/examples/TxChaining.purs @@ -41,7 +41,7 @@ example :: ConfigParams () -> Effect Unit example cfg = launchAff_ do runContract cfg contract -contract :: Contract () Unit +contract :: Contract Unit contract = do pkh <- liftedM "Failed to get PKH" $ head <$> ownPaymentPubKeysHashes let diff --git a/examples/Utxos.purs b/examples/Utxos.purs index e95f8c5dd4..de949ef54c 100644 --- a/examples/Utxos.purs +++ b/examples/Utxos.purs @@ -49,7 +49,7 @@ main = example testnetNamiConfig example :: ConfigParams () -> Effect Unit example = launchAff_ <<< flip runContract contract -contract :: Contract () Unit +contract :: Contract Unit contract = do logInfo' "Running Examples.Utxos" pkh <- liftedM "Failed to get own PKH" ownPaymentPubKeyHash diff --git a/examples/Wallet.purs b/examples/Wallet.purs index dc21124e58..212a6377c4 100644 --- a/examples/Wallet.purs +++ b/examples/Wallet.purs @@ -7,7 +7,7 @@ import Contract.Config (ConfigParams) import Contract.Monad (Contract, launchAff_, runContract) import Contract.Utxos (getWalletBalance, getWalletUtxos) -contract :: Contract () Unit +contract :: Contract Unit contract = do log "Address:" log <<< show =<< getWalletAddresses diff --git a/src/Contract/Chain.purs b/src/Contract/Chain.purs index 16e7fdd0ba..e1f072d2b1 100644 --- a/src/Contract/Chain.purs +++ b/src/Contract/Chain.purs @@ -10,14 +10,14 @@ module Contract.Chain import Prelude -import Contract.Monad (Contract, wrapContract) -import Ctl.Internal.QueryM (getChainTip) as QueryM -import Ctl.Internal.QueryM.WaitUntilSlot +import Contract.Monad (Contract) +import Ctl.Internal.Contract (getChainTip) as Contract +import Ctl.Internal.Contract.WaitUntilSlot ( currentSlot , currentTime , waitNSlots , waitUntilSlot - ) as QueryM + ) as Contract import Ctl.Internal.Serialization.Address (Slot) import Ctl.Internal.Types.Chain ( BlockHeaderHash(BlockHeaderHash) @@ -27,17 +27,17 @@ import Ctl.Internal.Types.Chain import Ctl.Internal.Types.Interval (POSIXTime) import Ctl.Internal.Types.Natural (Natural) -getTip :: forall (r :: Row Type). Contract r Chain.Tip -getTip = wrapContract QueryM.getChainTip +getTip :: Contract Chain.Tip +getTip = Contract.getChainTip -waitUntilSlot :: forall (r :: Row Type). Slot -> Contract r Chain.Tip -waitUntilSlot = wrapContract <<< QueryM.waitUntilSlot +waitUntilSlot :: Slot -> Contract Chain.Tip +waitUntilSlot = Contract.waitUntilSlot -waitNSlots :: forall (r :: Row Type). Natural -> Contract r Chain.Tip -waitNSlots = wrapContract <<< QueryM.waitNSlots +waitNSlots :: Natural -> Contract Chain.Tip +waitNSlots = Contract.waitNSlots -currentTime :: forall (r :: Row Type). Contract r POSIXTime -currentTime = wrapContract QueryM.currentTime +currentTime :: Contract POSIXTime +currentTime = Contract.currentTime -currentSlot :: forall (r :: Row Type). Contract r Slot -currentSlot = wrapContract QueryM.currentSlot +currentSlot :: Contract Slot +currentSlot = Contract.currentSlot diff --git a/src/Contract/Config.purs b/src/Contract/Config.purs index 57188cd19a..ab0ecfefb0 100644 --- a/src/Contract/Config.purs +++ b/src/Contract/Config.purs @@ -1,4 +1,4 @@ --- | Exposes some pre-defined Contract configurations. Re-exports all modules needed to modify `ConfigParams`. +-- | Exposes some pre-defined Contract configurations. Re-exports all modules needed to modify `ContractParams`. module Contract.Config ( testnetConfig , testnetNamiConfig @@ -13,7 +13,8 @@ module Contract.Config , mainnetEternlConfig , mainnetLodeConfig , module Contract.Address - , module Contract.Monad + , module Ctl.Internal.Contract.Monad + , module Ctl.Internal.Contract.QueryBackend , module Data.Log.Level , module Data.Log.Message , module Ctl.Internal.Deserialization.Keys @@ -23,8 +24,11 @@ module Contract.Config , module X ) where +import Prelude + import Contract.Address (NetworkId(MainnetId, TestnetId)) -import Contract.Monad (ConfigParams) +import Ctl.Internal.Contract.Monad (ContractParams) +import Ctl.Internal.Contract.QueryBackend (QueryBackendParams(CtlBackendParams, BlockfrostBackendParams), mkSingletonBackendParams) import Ctl.Internal.Deserialization.Keys (privateKeyFromBytes) import Ctl.Internal.QueryM (emptyHooks) import Ctl.Internal.QueryM (emptyHooks) as X @@ -56,14 +60,15 @@ import Data.Log.Level (LogLevel(Trace, Debug, Info, Warn, Error)) import Data.Log.Message (Message) import Data.Maybe (Maybe(Just, Nothing)) -testnetConfig :: ConfigParams () +testnetConfig :: ContractParams testnetConfig = - { ogmiosConfig: defaultOgmiosWsConfig - , datumCacheConfig: defaultDatumCacheWsConfig + { backendParams: mkSingletonBackendParams $ CtlBackendParams + { ogmiosConfig: defaultOgmiosWsConfig + , odcConfig: defaultDatumCacheWsConfig + , kupoConfig: defaultKupoServerConfig + } , ctlServerConfig: Just defaultServerConfig - , kupoConfig: defaultKupoServerConfig , networkId: TestnetId - , extraConfig: {} , walletSpec: Nothing , logLevel: Trace , customLogger: Nothing @@ -71,35 +76,35 @@ testnetConfig = , hooks: emptyHooks } -testnetNamiConfig :: ConfigParams () +testnetNamiConfig :: ContractParams testnetNamiConfig = testnetConfig { walletSpec = Just ConnectToNami } -testnetGeroConfig :: ConfigParams () +testnetGeroConfig :: ContractParams testnetGeroConfig = testnetConfig { walletSpec = Just ConnectToGero } -testnetFlintConfig :: ConfigParams () +testnetFlintConfig :: ContractParams testnetFlintConfig = testnetConfig { walletSpec = Just ConnectToFlint } -testnetEternlConfig :: ConfigParams () +testnetEternlConfig :: ContractParams testnetEternlConfig = testnetConfig { walletSpec = Just ConnectToEternl } -testnetLodeConfig :: ConfigParams () +testnetLodeConfig :: ContractParams testnetLodeConfig = testnetConfig { walletSpec = Just ConnectToLode } -mainnetConfig :: ConfigParams () +mainnetConfig :: ContractParams mainnetConfig = testnetConfig { networkId = MainnetId } -mainnetNamiConfig :: ConfigParams () +mainnetNamiConfig :: ContractParams mainnetNamiConfig = mainnetConfig { walletSpec = Just ConnectToNami } -mainnetGeroConfig :: ConfigParams () +mainnetGeroConfig :: ContractParams mainnetGeroConfig = mainnetConfig { walletSpec = Just ConnectToGero } -mainnetFlintConfig :: ConfigParams () +mainnetFlintConfig :: ContractParams mainnetFlintConfig = mainnetConfig { walletSpec = Just ConnectToFlint } -mainnetEternlConfig :: ConfigParams () +mainnetEternlConfig :: ContractParams mainnetEternlConfig = mainnetConfig { walletSpec = Just ConnectToEternl } -mainnetLodeConfig :: ConfigParams () +mainnetLodeConfig :: ContractParams mainnetLodeConfig = mainnetConfig { walletSpec = Just ConnectToLode } diff --git a/src/Contract/ProtocolParameters.purs b/src/Contract/ProtocolParameters.purs index b0782931b7..80ef6e3172 100644 --- a/src/Contract/ProtocolParameters.purs +++ b/src/Contract/ProtocolParameters.purs @@ -2,11 +2,11 @@ module Contract.ProtocolParameters ( getProtocolParameters ) where -import Contract.Monad (Contract, wrapContract) -import Ctl.Internal.QueryM (getProtocolParameters) as QueryM +import Contract.Monad (Contract) +import Ctl.Internal.Contract (getProtocolParameters) as Contract import Ctl.Internal.QueryM.Ogmios (ProtocolParameters) -- | Returns the `ProtocolParameters` from the `Contract` environment. -- | Note that this is not necessarily the current value from the ledger. -getProtocolParameters :: forall (r :: Row Type). Contract r ProtocolParameters -getProtocolParameters = wrapContract QueryM.getProtocolParameters +getProtocolParameters :: Contract ProtocolParameters +getProtocolParameters = Contract.getProtocolParameters diff --git a/src/Contract/Scripts.purs b/src/Contract/Scripts.purs index 50d4d976da..b4558b3bb7 100644 --- a/src/Contract/Scripts.purs +++ b/src/Contract/Scripts.purs @@ -15,7 +15,7 @@ module Contract.Scripts import Prelude -import Contract.Monad (Contract, wrapContract) +import Contract.Monad (Contract) import Ctl.Internal.Cardano.Types.NativeScript ( NativeScript ( ScriptPubkey @@ -34,7 +34,7 @@ import Ctl.Internal.QueryM , ClientEncodingError ) ) as ExportQueryM -import Ctl.Internal.QueryM (applyArgs) as QueryM +import Ctl.Internal.Contract.ApplyArgs (applyArgs) as Contract import Ctl.Internal.Scripts ( mintingPolicyHash , nativeScriptStakeValidatorHash @@ -72,16 +72,14 @@ import Data.Maybe (Maybe) -- | Apply `PlutusData` arguments to any type isomorphic to `PlutusScript`, -- | returning an updated script with the provided arguments applied applyArgs - :: forall (r :: Row Type) - . PlutusScript + :: PlutusScript -> Array PlutusData - -> Contract r (Either ExportQueryM.ClientError PlutusScript) -applyArgs a = wrapContract <<< QueryM.applyArgs a + -> Contract (Either ExportQueryM.ClientError PlutusScript) +applyArgs = Contract.applyArgs -- | Same as `applyArgs` with arguments hushed. applyArgsM - :: forall (r :: Row Type) - . PlutusScript + :: PlutusScript -> Array PlutusData - -> Contract r (Maybe PlutusScript) + -> Contract (Maybe PlutusScript) applyArgsM a = map hush <<< applyArgs a diff --git a/src/Contract/Staking.purs b/src/Contract/Staking.purs index 0ceb835b70..8dacdb8e4e 100644 --- a/src/Contract/Staking.purs +++ b/src/Contract/Staking.purs @@ -7,7 +7,8 @@ module Contract.Staking import Prelude -import Contract.Monad (Contract, wrapContract) +import Ctl.Internal.Contract.Monad (wrapQueryM) +import Contract.Monad (Contract) import Ctl.Internal.Cardano.Types.Transaction ( PoolPubKeyHash , PoolRegistrationParams @@ -18,25 +19,22 @@ import Ctl.Internal.Types.PubKeyHash (StakePubKeyHash) import Ctl.Internal.Types.Scripts (StakeValidatorHash) import Data.Maybe (Maybe) -getPoolIds :: forall (r :: Row Type). Contract r (Array PoolPubKeyHash) -getPoolIds = wrapContract QueryM.getPoolIds +getPoolIds :: Contract (Array PoolPubKeyHash) +getPoolIds = wrapQueryM QueryM.getPoolIds getPoolParameters - :: forall (r :: Row Type) - . PoolPubKeyHash - -> Contract r PoolRegistrationParams -getPoolParameters poolId = wrapContract $ QueryM.getPoolParameters poolId + :: PoolPubKeyHash + -> Contract PoolRegistrationParams +getPoolParameters poolId = wrapQueryM $ QueryM.getPoolParameters poolId getPubKeyHashDelegationsAndRewards - :: forall (r :: Row Type) - . StakePubKeyHash - -> Contract r (Maybe DelegationsAndRewards) + :: StakePubKeyHash + -> Contract (Maybe DelegationsAndRewards) getPubKeyHashDelegationsAndRewards = - wrapContract <<< QueryM.getPubKeyHashDelegationsAndRewards + wrapQueryM <<< QueryM.getPubKeyHashDelegationsAndRewards getValidatorHashDelegationsAndRewards - :: forall (r :: Row Type) - . StakeValidatorHash - -> Contract r (Maybe DelegationsAndRewards) + :: StakeValidatorHash + -> Contract (Maybe DelegationsAndRewards) getValidatorHashDelegationsAndRewards = - wrapContract <<< QueryM.getValidatorHashDelegationsAndRewards + wrapQueryM <<< QueryM.getValidatorHashDelegationsAndRewards diff --git a/src/Contract/Time.purs b/src/Contract/Time.purs index b425acdcf7..8f251e1b89 100644 --- a/src/Contract/Time.purs +++ b/src/Contract/Time.purs @@ -11,13 +11,17 @@ module Contract.Time import Prelude +import Effect.Aff.Class (liftAff) +import Ctl.Internal.Contract.QueryHandle (getQueryHandle) +import Control.Monad.Reader.Class (asks) +import Ctl.Internal.Contract.Monad (wrapQueryM) import Contract.Chain ( BlockHeaderHash(BlockHeaderHash) , ChainTip(ChainTip) , Tip(Tip, TipAtGenesis) , getTip ) as Chain -import Contract.Monad (Contract, wrapContract) +import Contract.Monad (Contract) import Ctl.Internal.Cardano.Types.Transaction (Epoch(Epoch)) import Ctl.Internal.Helpers (liftM) import Ctl.Internal.QueryM.CurrentEpoch (getCurrentEpoch) as CurrentEpoch @@ -99,21 +103,21 @@ import Data.BigInt as BigInt import Data.UInt as UInt import Effect.Exception (error) --- | Get the current Epoch. Details can be found https://ogmios.dev/api/ under --- | "currentEpoch" query -getCurrentEpoch :: forall (r :: Row Type). Contract r Epoch +-- | Get the current Epoch. +getCurrentEpoch :: Contract Epoch getCurrentEpoch = do - CurrentEpoch bigInt <- wrapContract CurrentEpoch.getCurrentEpoch + queryHandle <- getQueryHandle + CurrentEpoch bigInt <- liftAff $ queryHandle.getCurrentEpoch map Epoch $ liftM (error "Unable to convert CurrentEpoch") $ UInt.fromString $ BigInt.toString (bigInt :: BigInt.BigInt) --- | Get `EraSummaries` as used for Slot arithemetic. Details can be found --- | https://ogmios.dev/api/ under "eraSummaries" query -getEraSummaries :: forall (r :: Row Type). Contract r EraSummaries -getEraSummaries = wrapContract EraSummaries.getEraSummaries +-- | Get `EraSummaries` as used for Slot arithemetic. Ogmios only. +-- | Details can be found https://ogmios.dev/api/ under "eraSummaries" query +getEraSummaries :: Contract EraSummaries +getEraSummaries = wrapQueryM EraSummaries.getEraSummaries --- | Get the current system start time. Details can be found --- | https://ogmios.dev/api/ under "systemStart" query -getSystemStart :: forall (r :: Row Type). Contract r SystemStart -getSystemStart = wrapContract SystemStart.getSystemStart +-- | Get the current system start time. +getSystemStart :: Contract SystemStart +getSystemStart = do + asks $ _.ledgerConstants >>> _.systemStart diff --git a/src/Contract/Transaction.purs b/src/Contract/Transaction.purs index dc0c61d744..c4d88874aa 100644 --- a/src/Contract/Transaction.purs +++ b/src/Contract/Transaction.purs @@ -174,11 +174,11 @@ import Ctl.Internal.QueryM ) ) as ExportQueryM import Ctl.Internal.QueryM (submitTxOgmios) as QueryM -import Ctl.Internal.QueryM.AwaitTxConfirmed +import Ctl.Internal.Contract.AwaitTxConfirmed ( awaitTxConfirmed , awaitTxConfirmedWithTimeout , awaitTxConfirmedWithTimeoutSlots - ) as AwaitTx + ) as Contract import Ctl.Internal.QueryM.GetTxByHash (getTxByHash) as QueryM import Ctl.Internal.QueryM.MinFee (calculateMinFee) as QueryM import Ctl.Internal.QueryM.Ogmios (SubmitTxR(SubmitTxSuccess, SubmitFail)) @@ -548,7 +548,7 @@ awaitTxConfirmed :: forall (r :: Row Type) . TransactionHash -> Contract r Unit -awaitTxConfirmed = wrapContract <<< AwaitTx.awaitTxConfirmed <<< unwrap +awaitTxConfirmed = Contract.awaitTxConfirmed -- | Same as `awaitTxConfirmed`, but allows to specify a timeout in seconds for waiting. -- | Throws an exception on timeout. @@ -557,9 +557,7 @@ awaitTxConfirmedWithTimeout . Seconds -> TransactionHash -> Contract r Unit -awaitTxConfirmedWithTimeout timeout = wrapContract - <<< AwaitTx.awaitTxConfirmedWithTimeout timeout - <<< unwrap +awaitTxConfirmedWithTimeout = Contract.awaitTxConfirmedWithTimeout -- | Same as `awaitTxConfirmed`, but allows to specify a timeout in slots for waiting. -- | Throws an exception on timeout. @@ -568,9 +566,8 @@ awaitTxConfirmedWithTimeoutSlots . Int -> TransactionHash -> Contract r Unit -awaitTxConfirmedWithTimeoutSlots timeout = wrapContract - <<< AwaitTx.awaitTxConfirmedWithTimeoutSlots timeout - <<< unwrap +awaitTxConfirmedWithTimeoutSlots = + Contract.awaitTxConfirmedWithTimeoutSlots -- | Builds an expected utxo set from transaction outputs. Predicts output -- | references (`TransactionInput`s) for each output by calculating the diff --git a/src/Internal/Contract.purs b/src/Internal/Contract.purs new file mode 100644 index 0000000000..a31ea57262 --- /dev/null +++ b/src/Internal/Contract.purs @@ -0,0 +1,20 @@ +module Ctl.Internal.Contract where + +import Prelude + +import Control.Monad.Reader.Class (asks) +import Ctl.Internal.Contract.Monad (Contract) +import Ctl.Internal.Contract.QueryHandle (getQueryHandle) +import Effect.Aff.Class (liftAff) +import Ctl.Internal.QueryM.Ogmios (ProtocolParameters) as Ogmios + +getChainTip = do + queryHandle <- getQueryHandle + liftAff $ queryHandle.getChainTip + +-- | Returns the `ProtocolParameters` from the `QueryM` environment. +-- | Note that this is not necessarily the current value from the ledger. +getProtocolParameters :: Contract Ogmios.ProtocolParameters +getProtocolParameters = + asks $ _.ledgerConstants >>> _.pparams + diff --git a/src/Internal/Contract/ApplyArgs.purs b/src/Internal/Contract/ApplyArgs.purs new file mode 100644 index 0000000000..454dbace65 --- /dev/null +++ b/src/Internal/Contract/ApplyArgs.purs @@ -0,0 +1,82 @@ +module Ctl.Internal.Contract.ApplyArgs + ( applyArgs + ) where + +import Prelude + +import Ctl.Internal.QueryM (ClientError(..), scriptToAeson, postAeson, handleAffjaxResponse) +import Ctl.Internal.Contract.Monad(Contract) +import Aeson + ( Aeson + , encodeAeson + ) +import Control.Monad.Reader.Trans + ( asks + ) +import Ctl.Internal.Helpers ((<>)) +import Ctl.Internal.QueryM.ServerConfig + ( mkHttpUrl + ) +import Ctl.Internal.Serialization (toBytes) as Serialization +import Ctl.Internal.Serialization.PlutusData (convertPlutusData) as Serialization +import Ctl.Internal.Types.ByteArray (byteArrayToHex) +import Ctl.Internal.Types.PlutusData (PlutusData) +import Ctl.Internal.Types.Scripts (Language, PlutusScript(PlutusScript)) +import Data.Either (Either(Left)) +import Data.Maybe (Maybe(Just, Nothing)) +import Data.Newtype (unwrap) +import Data.Traversable (traverse) +import Data.Tuple (Tuple(Tuple), snd) +import Data.Tuple.Nested ((/\)) +import Effect.Aff.Class (liftAff) +import Foreign.Object as Object +import Untagged.Union (asOneOf) + +-- | Apply `PlutusData` arguments to any type isomorphic to `PlutusScript`, +-- | returning an updated script with the provided arguments applied +applyArgs + :: PlutusScript + -> Array PlutusData + -> Contract (Either ClientError PlutusScript) +applyArgs script args = + asks _.ctlServerConfig >>= case _ of + Nothing -> pure + $ Left + $ + ClientOtherError + "The `ctl-server` service is required to call `applyArgs`. Please \ + \provide a `Just` value in `ConfigParams.ctlServerConfig` and make \ + \sure that the `ctl-server` service is running and available at the \ + \provided host and port. The `ctl-server` packages can be obtained \ + \from `overlays.ctl-server` defined in CTL's flake. Please see \ + \`doc/runtime.md` in the CTL repository for more information" + Just config -> case traverse plutusDataToAeson args of + Nothing -> pure $ Left $ ClientEncodingError + "Failed to convert script args" + Just ps -> do + let + language :: Language + language = snd $ unwrap script + + url :: String + url = mkHttpUrl config <> "apply-args" + + reqBody :: Aeson + reqBody = encodeAeson + $ Object.fromFoldable + [ "script" /\ scriptToAeson script + , "args" /\ encodeAeson ps + ] + liftAff (postAeson url reqBody) + <#> map (PlutusScript <<< flip Tuple language) <<< + handleAffjaxResponse + where + plutusDataToAeson :: PlutusData -> Maybe Aeson + plutusDataToAeson = + map + ( encodeAeson + <<< byteArrayToHex + <<< Serialization.toBytes + <<< asOneOf + ) + <<< Serialization.convertPlutusData diff --git a/src/Internal/QueryM/AwaitTxConfirmed.purs b/src/Internal/Contract/AwaitTxConfirmed.purs similarity index 74% rename from src/Internal/QueryM/AwaitTxConfirmed.purs rename to src/Internal/Contract/AwaitTxConfirmed.purs index 9a6264b543..e83f712709 100644 --- a/src/Internal/QueryM/AwaitTxConfirmed.purs +++ b/src/Internal/Contract/AwaitTxConfirmed.purs @@ -1,4 +1,4 @@ -module Ctl.Internal.QueryM.AwaitTxConfirmed +module Ctl.Internal.Contract.AwaitTxConfirmed ( awaitTxConfirmed , awaitTxConfirmedWithTimeout , awaitTxConfirmedWithTimeoutSlots @@ -7,10 +7,12 @@ module Ctl.Internal.QueryM.AwaitTxConfirmed import Prelude import Control.Parallel (parOneOf) -import Ctl.Internal.QueryM (QueryM, getChainTip) -import Ctl.Internal.QueryM.Kupo (isTxConfirmed) as Kupo +import Ctl.Internal.Contract (getChainTip) +import Ctl.Internal.Contract.Monad (Contract) +import Ctl.Internal.Contract.QueryHandle (getQueryHandle) +-- import Ctl.Internal.QueryM.Kupo (isTxConfirmed) as Kupo import Ctl.Internal.QueryM.Ogmios (TxHash) -import Ctl.Internal.QueryM.WaitUntilSlot (waitUntilSlot) +import Ctl.Internal.Contract.WaitUntilSlot (waitUntilSlot) import Ctl.Internal.Serialization.Address (Slot) import Ctl.Internal.Types.BigNum as BigNum import Ctl.Internal.Types.Chain as Chain @@ -24,10 +26,10 @@ import Effect.Aff.Class (liftAff) import Effect.Class (liftEffect) import Effect.Exception (throw) -awaitTxConfirmed :: TxHash -> QueryM Unit +awaitTxConfirmed :: TxHash -> Contract Unit awaitTxConfirmed = awaitTxConfirmedWithTimeout (Seconds infinity) -awaitTxConfirmedWithTimeout :: Seconds -> TxHash -> QueryM Unit +awaitTxConfirmedWithTimeout :: Seconds -> TxHash -> Contract Unit awaitTxConfirmedWithTimeout timeoutSeconds txHash = -- If timeout is infinity, do not use a timeout at all if unwrap timeoutSeconds == infinity then void findTx @@ -40,13 +42,13 @@ awaitTxConfirmedWithTimeout timeoutSeconds txHash = where -- Try to find the TX indefinitely, with a waiting period between each -- request - findTx :: QueryM Boolean + findTx :: Contract Boolean findTx = isTxConfirmed txHash >>= \found -> if found then pure true else liftAff (delay delayTime) *> findTx -- Wait until the timeout elapses and return false - waitAndFail :: QueryM Boolean + waitAndFail :: Contract Boolean waitAndFail = do liftAff $ delay $ timeout pure false @@ -57,23 +59,23 @@ awaitTxConfirmedWithTimeout timeoutSeconds txHash = delayTime :: Milliseconds delayTime = wrap 1000.0 -awaitTxConfirmedWithTimeoutSlots :: Int -> TxHash -> QueryM Unit +awaitTxConfirmedWithTimeoutSlots :: Int -> TxHash -> Contract Unit awaitTxConfirmedWithTimeoutSlots timeoutSlots txHash = getCurrentSlot >>= addSlots timeoutSlots >>= go where - getCurrentSlot :: QueryM Slot + getCurrentSlot :: Contract Slot getCurrentSlot = getChainTip >>= case _ of Chain.TipAtGenesis -> do liftAff $ delay $ wrap 1000.0 getCurrentSlot Chain.Tip (Chain.ChainTip { slot }) -> pure slot - addSlots :: Int -> Slot -> QueryM Slot + addSlots :: Int -> Slot -> Contract Slot addSlots n slot = maybe (liftEffect $ throw "Cannot determine next slot") (pure <<< wrap) $ unwrap slot `BigNum.add` BigNum.fromInt n - go :: Slot -> QueryM Unit + go :: Slot -> Contract Unit go timeout = isTxConfirmed txHash >>= \found -> unless found do @@ -85,7 +87,9 @@ awaitTxConfirmedWithTimeoutSlots timeoutSlots txHash = void $ addSlots 1 slot >>= waitUntilSlot go timeout -isTxConfirmed :: TxHash -> QueryM Boolean -isTxConfirmed txHash = - Kupo.isTxConfirmed (wrap txHash) +isTxConfirmed :: TxHash -> Contract Boolean +isTxConfirmed txHash = do + queryHandle <- getQueryHandle + liftAff $ queryHandle.isTxConfirmed (wrap txHash) >>= either (liftEffect <<< throw <<< show) pure + diff --git a/src/Internal/Contract/Monad.purs b/src/Internal/Contract/Monad.purs index dfde67f58e..fb9f51cfcb 100644 --- a/src/Internal/Contract/Monad.purs +++ b/src/Internal/Contract/Monad.purs @@ -1,19 +1,23 @@ module Ctl.Internal.Contract.Monad ( Contract(Contract) + , ParContract(ParContract) , ContractEnv , ContractParams , mkContractEnv , runContract , runContractInEnv , runQueryM + , wrapQueryM , stopContractEnv , withContractEnv ) where import Prelude -import Effect.Aff (Aff, attempt, error, finally, supervise) -import Data.Array (head) +import Data.Function (on) +import Data.Foldable (maximumBy) +import Ctl.Internal.Serialization.Address (Slot) +import Effect.Aff (Aff, ParAff, attempt, error, finally, supervise) import Ctl.Internal.JsWebSocket (_wsClose, _wsFinalize) import Ctl.Internal.QueryM (Hooks, Logger, QueryEnv, QueryM, WebSocket, getProtocolParametersAff, getSystemStartAff, getEraSummariesAff, mkDatumCacheWebSocketAff, mkLogger, mkOgmiosWebSocketAff, mkWalletBySpec, underlyingWebSocket) import Record.Builder (build, merge) @@ -24,19 +28,21 @@ import Control.Monad.Error.Class , throwError ) import Control.Monad.Logger.Class (class MonadLogger) -import Control.Monad.Reader.Class (class MonadAsk, class MonadReader, ask) -import Control.Monad.Reader.Trans (ReaderT, runReaderT) +import Control.Monad.Reader.Class (class MonadAsk, class MonadReader, ask, asks) +import Control.Monad.Reader.Trans (ReaderT(ReaderT), runReaderT) import Control.Monad.Rec.Class (class MonadRec) import Ctl.Internal.Contract.QueryBackend ( CtlBackend , QueryBackend(BlockfrostBackend, CtlBackend) , QueryBackendParams(BlockfrostBackendParams, CtlBackendParams) , QueryBackends + , QueryBackendLabel(CtlBackendLabel) , defaultBackend + , lookupBackend ) -import Ctl.Internal.Helpers (liftedM, logWithLevel) +import Ctl.Internal.Helpers (liftM, liftedM, logWithLevel) import Ctl.Internal.QueryM.Logging (setupLogs) -import Ctl.Internal.QueryM.Ogmios (ProtocolParameters, SlotLength, SystemStart) as Ogmios +import Ctl.Internal.QueryM.Ogmios (ProtocolParameters, SlotLength, SystemStart, RelativeTime) as Ogmios import Ctl.Internal.QueryM.ServerConfig (ServerConfig) import Ctl.Internal.Serialization.Address (NetworkId) import Ctl.Internal.Types.UsedTxOuts (UsedTxOuts, newUsedTxOuts) @@ -56,6 +62,10 @@ import Effect.Ref (new) as Ref import MedeaPrelude (class MonadAff) import Prim.TypeError (class Warn, Text) import Undefined (undefined) +import Control.Parallel (class Parallel, parallel, sequential) +import Control.Alt (class Alt) +import Control.Alternative (class Alternative) +import Control.Plus (class Plus) -------------------------------------------------------------------------------- -- Contract @@ -93,6 +103,24 @@ instance MonadLogger Contract where let logFunction = fromMaybe logWithLevel config.customLogger liftAff $ logFunction config.logLevel msg +instance Parallel ParContract Contract where + parallel :: Contract ~> ParContract + parallel (Contract a) = ParContract $ parallel a + sequential :: ParContract ~> Contract + sequential (ParContract a) = Contract $ sequential a + +newtype ParContract (a :: Type) = ParContract + (ReaderT ContractEnv ParAff a) + +derive newtype instance Functor ParContract +derive newtype instance Apply ParContract +derive newtype instance Applicative ParContract +derive newtype instance Alt ParContract +derive newtype instance Plus ParContract +derive newtype instance Alternative ParContract +derive newtype instance Semigroup a => Semigroup (ParContract a) +derive newtype instance Monoid a => Monoid (ParContract a) + -- | Interprets a contract into an `Aff` context. -- | Implicitly initializes and finalizes a new `ContractEnv` runtime. -- | @@ -127,10 +155,17 @@ type ContractEnv = , wallet :: Maybe Wallet , usedTxOuts :: UsedTxOuts -- TODO: Duplicate types to Contract + -- We don't support changing protocol parameters, so supporting a HFC is even less unlikely + -- slotLength can only change with a HFC. , ledgerConstants :: { pparams :: Ogmios.ProtocolParameters , systemStart :: Ogmios.SystemStart + -- Why not use Duration? , slotLength :: Ogmios.SlotLength + -- A reference point in which the slotLength is assumed to be constant from + -- then until now, not including HFC which occur during contract evaluation + -- TODO: Drop systemStart and just normalize time AOT + , slotReference :: { slot :: Slot, time :: Ogmios.RelativeTime } } } @@ -191,14 +226,20 @@ mkContractEnv params = do { pparams :: Ogmios.ProtocolParameters , systemStart :: Ogmios.SystemStart , slotLength :: Ogmios.SlotLength + , slotReference :: { slot :: Slot, time :: Ogmios.RelativeTime } } getLedgerConstants backend = case backend of CtlBackend { ogmios: { ws } } -> do pparams <- getProtocolParametersAff ws logger systemStart <- getSystemStartAff ws logger - slotLength <- liftedM (error "Could not get EraSummary") do - map (_.slotLength <<< unwrap <<< _.parameters <<< unwrap) <<< head <<< unwrap <$> getEraSummariesAff ws logger - pure { pparams, slotLength, systemStart } + -- Do we ever recieve an eraSummary ahead of schedule? + -- Maybe search for the chainTip's era + latestEraSummary <- liftedM (error "Could not get EraSummary") do + map unwrap <<< (maximumBy (compare `on` (unwrap >>> _.start >>> unwrap >>> _.slot))) <<< unwrap <$> getEraSummariesAff ws logger + let + slotLength = _.slotLength $ unwrap $ _.parameters $ latestEraSummary + slotReference = (\{slot, time} -> {slot, time}) $ unwrap $ _.start $ latestEraSummary + pure { pparams, slotLength, systemStart, slotReference } BlockfrostBackend _ -> undefined buildWallet :: Aff (Maybe Wallet) @@ -292,6 +333,14 @@ type ContractParams = -- QueryM -------------------------------------------------------------------------------- +wrapQueryM :: forall a. QueryM a -> Contract a +wrapQueryM qm = do + backend <- asks _.backend + ctlBackend <- liftM (error "Operation only supported on CTL backend") $ lookupBackend CtlBackendLabel backend >>= case _ of + CtlBackend b -> Just b + _ -> Nothing + Contract $ ReaderT \contractEnv -> runQueryM contractEnv ctlBackend qm + runQueryM :: forall (a :: Type). ContractEnv -> CtlBackend -> QueryM a -> Aff a runQueryM contractEnv ctlBackend = flip runReaderT (mkQueryEnv contractEnv ctlBackend) <<< unwrap diff --git a/src/Internal/Contract/QueryBackend.purs b/src/Internal/Contract/QueryBackend.purs index 846faa13be..0cd498c99a 100644 --- a/src/Internal/Contract/QueryBackend.purs +++ b/src/Internal/Contract/QueryBackend.purs @@ -72,6 +72,7 @@ mkBackendParams defaultBackend backends = defaultBackend :: forall (backend :: Type). QueryBackends backend -> backend defaultBackend (QueryBackends backend _) = backend +-- Still requires a match on the backend constructor... lookupBackend :: forall (backend :: Type) . HasQueryBackendLabel backend diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs index 8107ee7411..94f2d2e7bc 100644 --- a/src/Internal/Contract/QueryHandle.purs +++ b/src/Internal/Contract/QueryHandle.purs @@ -5,6 +5,7 @@ import Prelude import Control.Monad.Reader.Class (ask) import Ctl.Internal.Cardano.Types.ScriptRef (ScriptRef) import Ctl.Internal.Cardano.Types.Transaction (TransactionOutput, UtxoMap) +import Ctl.Internal.QueryM.CurrentEpoch(getCurrentEpoch) as QueryM import Ctl.Internal.Contract.Monad ( Contract , ContractEnv @@ -16,6 +17,7 @@ import Ctl.Internal.Contract.QueryBackend , QueryBackend(BlockfrostBackend, CtlBackend) , defaultBackend ) +import Ctl.Internal.QueryM (getChainTip) as QueryM import Ctl.Internal.QueryM (ClientError, QueryM) import Ctl.Internal.QueryM.Kupo ( getDatumByHash @@ -35,6 +37,8 @@ import Data.Map (Map) import Data.Maybe (Maybe) import Effect.Aff (Aff) import Undefined (undefined) +import Ctl.Internal.Types.Chain as Chain +import Ctl.Internal.QueryM.Ogmios (CurrentEpoch) as Ogmios -- Why ClientError? type AffE (a :: Type) = Aff (Either ClientError a) @@ -47,6 +51,8 @@ type QueryHandle = , getUtxoByOref :: TransactionInput -> AffE (Maybe TransactionOutput) , isTxConfirmed :: TransactionHash -> AffE Boolean , utxosAt :: Address -> AffE UtxoMap + , getChainTip :: Aff Chain.Tip + , getCurrentEpoch :: Aff Ogmios.CurrentEpoch -- submitTx -- evaluateTx -- chainTip @@ -78,6 +84,8 @@ queryHandleForCtlBackend contractEnv backend = , getUtxoByOref: runQueryM' <<< Kupo.getUtxoByOref , isTxConfirmed: runQueryM' <<< Kupo.isTxConfirmed , utxosAt: runQueryM' <<< Kupo.utxosAt + , getChainTip: runQueryM' QueryM.getChainTip + , getCurrentEpoch: runQueryM' QueryM.getCurrentEpoch } where runQueryM' :: forall (a :: Type). QueryM a -> Aff a diff --git a/src/Internal/Contract/WaitUntilSlot.purs b/src/Internal/Contract/WaitUntilSlot.purs index 11b354208f..ac152efb8d 100644 --- a/src/Internal/Contract/WaitUntilSlot.purs +++ b/src/Internal/Contract/WaitUntilSlot.purs @@ -8,12 +8,12 @@ module Ctl.Internal.Contract.WaitUntilSlot import Prelude import Ctl.Internal.Contract.Monad(Contract) +import Control.Monad.Reader.Class (asks) import Contract.Log (logTrace') import Ctl.Internal.Helpers (liftEither, liftM) -import Ctl.Internal.QueryM (QueryM, getChainTip) -- import Ctl.Internal.QueryM.EraSummaries (getEraSummaries) -import Ctl.Internal.QueryM.Ogmios (EraSummaries, SystemStart) +import Ctl.Internal.QueryM.Ogmios (EraSummaries, SystemStart, RelativeTime, SlotLength) -- import Ctl.Internal.QueryM.SystemStart (getSystemStart) import Ctl.Internal.Serialization.Address (Slot(Slot)) import Ctl.Internal.Types.BigNum as BigNum @@ -38,6 +38,7 @@ import Effect.Aff.Class (liftAff) import Effect.Class (liftEffect) import Effect.Exception (error) import Effect.Now (now) +import Ctl.Internal.Contract (getChainTip) -- | The returned slot will be no less than the slot provided as argument. waitUntilSlot :: Slot -> Contract Chain.Tip @@ -46,9 +47,8 @@ waitUntilSlot futureSlot = tip@(Chain.Tip (Chain.ChainTip { slot })) | slot >= futureSlot -> pure tip | otherwise -> do - -- TODO Read sysStart and slotLength(Ms) from env - eraSummaries <- getEraSummaries - sysStart <- getSystemStart + { systemStart, slotLength, slotReference } <- asks _.ledgerConstants + let slotLengthMs = unwrap slotLength * 1000.0 -- slotLengthMs <- map getSlotLength $ liftEither -- $ lmap (const $ error "Unable to get current Era summary") -- $ findSlotEraSummary eraSummaries slot @@ -56,9 +56,9 @@ waitUntilSlot futureSlot = -- If there are less than `slotPadding` slots remaining, start querying for chainTip -- repeatedly, because it's possible that at any given moment Ogmios suddenly -- synchronizes with node that is also synchronized with global time. - getLag eraSummaries sysStart slot >>= logLag slotLengthMs + getLag slotReference slotLength systemStart slot >>= logLag slotLengthMs futureTime <- - liftEffect (slotToPosixTime eraSummaries sysStart futureSlot) + liftEffect (slotToPosixTime slotReference slotLength systemStart futureSlot) >>= hush >>> liftM (error "Unable to convert Slot to POSIXTime") delayTime <- estimateDelayUntil futureTime liftAff $ delay delayTime @@ -71,7 +71,7 @@ waitUntilSlot futureSlot = | currentSlot_ >= futureSlot -> pure currentTip | otherwise -> do liftAff $ delay $ Milliseconds slotLengthMs - getLag eraSummaries sysStart currentSlot_ >>= logLag + getLag slotReference slotLength systemStart currentSlot_ >>= logLag slotLengthMs fetchRepeatedly Chain.TipAtGenesis -> do @@ -95,9 +95,9 @@ waitUntilSlot futureSlot = -- | Calculate difference between estimated POSIX time of given slot -- | and current time. -getLag :: EraSummaries -> SystemStart -> Slot -> Contract Milliseconds -getLag eraSummaries sysStart nowSlot = do - nowPosixTime <- liftEffect (slotToPosixTime eraSummaries sysStart nowSlot) >>= +getLag :: { slot :: Slot, time :: RelativeTime } -> SlotLength -> SystemStart -> Slot -> Contract Milliseconds +getLag slotReference slotLength sysStart nowSlot = do + nowPosixTime <- liftEffect (slotToPosixTime slotReference slotLength sysStart nowSlot) >>= hush >>> liftM (error "Unable to convert Slot to POSIXTime") nowMs <- unwrap <<< unInstant <$> liftEffect now logTrace' $ @@ -170,9 +170,9 @@ slotToEndPOSIXTime :: Slot -> Contract POSIXTime slotToEndPOSIXTime slot = do futureSlot <- liftM (error "Unable to advance slot") $ wrap <$> BigNum.add (unwrap slot) (BigNum.fromInt 1) - eraSummaries <- getEraSummaries - sysStart <- getSystemStart - futureTime <- liftEffect $ slotToPosixTime eraSummaries sysStart futureSlot + { systemStart, slotLength, slotReference } <- asks _.ledgerConstants + futureTime <- liftEffect $ slotToPosixTime slotReference slotLength systemStart futureSlot >>= hush >>> liftM (error "Unable to convert Slot to POSIXTime") -- We assume that a slot is 1000 milliseconds here. + -- TODO Don't pure ((wrap <<< BigInt.fromInt $ -1) + futureTime) diff --git a/src/Internal/Contract/Wallet.purs b/src/Internal/Contract/Wallet.purs index 7820211671..b92c3ddc8c 100644 --- a/src/Internal/Contract/Wallet.purs +++ b/src/Internal/Contract/Wallet.purs @@ -169,7 +169,7 @@ getWalletCollateral = do addr <- liftAff $ (unwrap kw).address networkId utxos <- (liftAff $ queryHandle.utxosAt addr) <#> hush >>> fromMaybe Map.empty >>= filterLockedUtxos - pparams <- asks $ _.pparams <#> unwrap + pparams <- asks $ _.ledgerConstants >>> _.pparams <#> unwrap let coinsPerUtxoUnit = pparams.coinsPerUtxoUnit maxCollateralInputs = UInt.toInt $ @@ -178,7 +178,7 @@ getWalletCollateral = do maxCollateralInputs utxos for_ mbCollateralUTxOs \collateralUTxOs -> do - pparams <- asks $ _.pparams + pparams <- asks $ _.ledgerConstants >>> _.pparams let tooManyCollateralUTxOs = UInt.fromInt (Array.length collateralUTxOs) > diff --git a/src/Internal/QueryM/WaitUntilSlot.purs b/src/Internal/QueryM/WaitUntilSlot.purs deleted file mode 100644 index 0d18877c4c..0000000000 --- a/src/Internal/QueryM/WaitUntilSlot.purs +++ /dev/null @@ -1,175 +0,0 @@ -module Ctl.Internal.QueryM.WaitUntilSlot - ( waitUntilSlot - , waitNSlots - , currentSlot - , currentTime - ) where - -import Prelude - -import Contract.Log (logTrace') -import Ctl.Internal.Helpers (liftEither, liftM) -import Ctl.Internal.QueryM (QueryM, getChainTip) -import Ctl.Internal.QueryM.EraSummaries (getEraSummaries) -import Ctl.Internal.QueryM.Ogmios (EraSummaries, SystemStart) -import Ctl.Internal.QueryM.SystemStart (getSystemStart) -import Ctl.Internal.Serialization.Address (Slot(Slot)) -import Ctl.Internal.Types.BigNum as BigNum -import Ctl.Internal.Types.Chain as Chain -import Ctl.Internal.Types.Interval - ( POSIXTime(POSIXTime) - , findSlotEraSummary - , getSlotLength - , slotToPosixTime - ) -import Ctl.Internal.Types.Natural (Natural) -import Ctl.Internal.Types.Natural as Natural -import Data.Bifunctor (lmap) -import Data.BigInt as BigInt -import Data.DateTime.Instant (unInstant) -import Data.Either (hush) -import Data.Int as Int -import Data.Newtype (unwrap, wrap) -import Data.Time.Duration (Milliseconds(Milliseconds), Seconds) -import Effect.Aff (Milliseconds, delay) -import Effect.Aff.Class (liftAff) -import Effect.Class (liftEffect) -import Effect.Exception (error) -import Effect.Now (now) - --- | The returned slot will be no less than the slot provided as argument. -waitUntilSlot :: Slot -> QueryM Chain.Tip -waitUntilSlot futureSlot = - getChainTip >>= case _ of - tip@(Chain.Tip (Chain.ChainTip { slot })) - | slot >= futureSlot -> pure tip - | otherwise -> do - eraSummaries <- getEraSummaries - sysStart <- getSystemStart - slotLengthMs <- map getSlotLength $ liftEither - $ lmap (const $ error "Unable to get current Era summary") - $ findSlotEraSummary eraSummaries slot - -- `timePadding` in slots - -- If there are less than `slotPadding` slots remaining, start querying for chainTip - -- repeatedly, because it's possible that at any given moment Ogmios suddenly - -- synchronizes with node that is also synchronized with global time. - getLag eraSummaries sysStart slot >>= logLag slotLengthMs - futureTime <- - liftEffect (slotToPosixTime eraSummaries sysStart futureSlot) - >>= hush >>> liftM (error "Unable to convert Slot to POSIXTime") - delayTime <- estimateDelayUntil futureTime - liftAff $ delay delayTime - let - -- Repeatedly check current slot until it's greater than or equal to futureAbsSlot - fetchRepeatedly :: QueryM Chain.Tip - fetchRepeatedly = - getChainTip >>= case _ of - currentTip@(Chain.Tip (Chain.ChainTip { slot: currentSlot_ })) - | currentSlot_ >= futureSlot -> pure currentTip - | otherwise -> do - liftAff $ delay $ Milliseconds slotLengthMs - getLag eraSummaries sysStart currentSlot_ >>= logLag - slotLengthMs - fetchRepeatedly - Chain.TipAtGenesis -> do - liftAff $ delay retryDelay - fetchRepeatedly - fetchRepeatedly - Chain.TipAtGenesis -> do - -- We just retry until the tip moves from genesis - liftAff $ delay retryDelay - waitUntilSlot futureSlot - where - retryDelay :: Milliseconds - retryDelay = wrap 1000.0 - - logLag :: Number -> Milliseconds -> QueryM Unit - logLag slotLengthMs (Milliseconds lag) = do - logTrace' $ - "waitUntilSlot: current lag: " <> show lag <> " ms, " - <> show (lag / slotLengthMs) - <> " slots." - --- | Calculate difference between estimated POSIX time of given slot --- | and current time. -getLag :: EraSummaries -> SystemStart -> Slot -> QueryM Milliseconds -getLag eraSummaries sysStart nowSlot = do - nowPosixTime <- liftEffect (slotToPosixTime eraSummaries sysStart nowSlot) >>= - hush >>> liftM (error "Unable to convert Slot to POSIXTime") - nowMs <- unwrap <<< unInstant <$> liftEffect now - logTrace' $ - "getLag: current slot: " <> BigNum.toString (unwrap nowSlot) - <> ", slot time: " - <> BigInt.toString (unwrap nowPosixTime) - <> ", system time: " - <> show nowMs - nowMsBigInt <- liftM (error "Unable to convert Milliseconds to BigInt") $ - BigInt.fromNumber nowMs - pure $ wrap $ BigInt.toNumber $ nowMsBigInt - unwrap nowPosixTime - --- | Estimate how long we want to wait if we want to wait until `timePadding` --- | milliseconds before a given `POSIXTime`. -estimateDelayUntil :: POSIXTime -> QueryM Milliseconds -estimateDelayUntil futureTimePosix = do - futureTimeSec <- posixTimeToSeconds futureTimePosix - nowMs <- unwrap <<< unInstant <$> liftEffect now - let - result = wrap $ mul 1000.0 $ nonNegative $ - unwrap futureTimeSec - nowMs / 1000.0 - logTrace' $ - "estimateDelayUntil: target time: " <> show (unwrap futureTimeSec * 1000.0) - <> ", system time: " - <> show nowMs - <> ", delay: " - <> show (unwrap result) - <> "ms" - pure result - where - nonNegative :: Number -> Number - nonNegative n - | n < 0.0 = 0.0 - | otherwise = n - -posixTimeToSeconds :: POSIXTime -> QueryM Seconds -posixTimeToSeconds (POSIXTime futureTimeBigInt) = do - liftM (error "Unable to convert POSIXTIme to Number") - $ map (wrap <<< Int.toNumber) - $ BigInt.toInt - $ futureTimeBigInt / BigInt.fromInt 1000 - --- | Wait at least `offset` number of slots. -waitNSlots :: Natural -> QueryM Chain.Tip -waitNSlots offset = do - offsetBigNum <- liftM (error "Unable to convert BigInt to BigNum") - $ (BigNum.fromBigInt <<< Natural.toBigInt) offset - if offsetBigNum == BigNum.fromInt 0 then getChainTip - else do - slot <- currentSlot - newSlot <- liftM (error "Unable to advance slot") - $ wrap <$> BigNum.add (unwrap slot) offsetBigNum - waitUntilSlot newSlot - -currentSlot :: QueryM Slot -currentSlot = getChainTip <#> case _ of - Chain.Tip (Chain.ChainTip { slot }) -> slot - Chain.TipAtGenesis -> (Slot <<< BigNum.fromInt) 0 - --- | Get the latest POSIXTime of the current slot. --- The plutus implementation relies on `slotToEndPOSIXTime` --- https://github.com/input-output-hk/plutus-apps/blob/fb8a39645e532841b6e38d42ecb957f1945833a5/plutus-contract/src/Plutus/Contract/Trace.hs -currentTime :: QueryM POSIXTime -currentTime = currentSlot >>= slotToEndPOSIXTime - --- | Get the ending 'POSIXTime' of a 'Slot' related to --- | our `QueryM` configuration. --- see https://github.com/input-output-hk/plutus-apps/blob/fb8a39645e532841b6e38d42ecb957f1945833a5/plutus-ledger/src/Ledger/TimeSlot.hs -slotToEndPOSIXTime :: Slot -> QueryM POSIXTime -slotToEndPOSIXTime slot = do - futureSlot <- liftM (error "Unable to advance slot") - $ wrap <$> BigNum.add (unwrap slot) (BigNum.fromInt 1) - eraSummaries <- getEraSummaries - sysStart <- getSystemStart - futureTime <- liftEffect $ slotToPosixTime eraSummaries sysStart futureSlot - >>= hush >>> liftM (error "Unable to convert Slot to POSIXTime") - -- We assume that a slot is 1000 milliseconds here. - pure ((wrap <<< BigInt.fromInt $ -1) + futureTime) diff --git a/src/Internal/Types/Interval.purs b/src/Internal/Types/Interval.purs index 3034b151de..7c7a966cf4 100644 --- a/src/Internal/Types/Interval.purs +++ b/src/Internal/Types/Interval.purs @@ -97,6 +97,8 @@ import Ctl.Internal.QueryM.Ogmios ( EraSummaries(EraSummaries) , EraSummary(EraSummary) , SystemStart + , RelativeTime + , SlotLength , aesonObject , slotLengthFactor ) @@ -697,21 +699,22 @@ extractArg o = do -- | Start, then add any excess for a UNIX Epoch time. Recall that POSIXTime -- | is in milliseconds for Protocol Version >= 6. slotToPosixTime - :: EraSummaries + :: { slot :: Slot, time :: RelativeTime } + -> SlotLength -> SystemStart -> Slot -> Effect (Either SlotToPosixTimeError POSIXTime) -slotToPosixTime eraSummaries sysStart slot = runExceptT do +slotToPosixTime slotReference slotLength sysStart slot = runExceptT do -- Get JSDate: sysStartD <- liftEffect $ parse $ unwrap sysStart -- Find current era: - currentEra <- liftEither $ findSlotEraSummary eraSummaries slot + -- currentEra <- liftEither $ findSlotEraSummary eraSummaries slot -- Convert absolute slot (relative to System start) to relative slot of era - relSlot <- liftEither $ relSlotFromSlot currentEra slot + relSlot <- liftEither $ relSlotFromSlot slotReference.slot slot -- Convert relative slot to relative time for that era - relTime <- liftM CannotGetBigIntFromNumber $ relTimeFromRelSlot currentEra + relTime <- liftM CannotGetBigIntFromNumber $ relTimeFromRelSlot slotLength relSlot - absTime <- liftEither $ absTimeFromRelTime currentEra relTime + absTime <- liftEither $ absTimeFromRelTime slotReference.time relTime -- Get POSIX time for system start sysStartPosix <- liftM CannotGetBigIntFromNumber $ BigInt.fromNumber @@ -806,29 +809,26 @@ instance Show AbsTime where -- | in conjunction with `findSlotEraSummary`. However, we choose to make the -- | function more general, guarding against a larger `start`ing slot relSlotFromSlot - :: EraSummary -> Slot -> Either SlotToPosixTimeError RelSlot -relSlotFromSlot (EraSummary { start }) s@(Slot slot) = do + :: Slot -> Slot -> Either SlotToPosixTimeError RelSlot +relSlotFromSlot start s@(Slot slot) = do let - startSlot = BigNum.toBigIntUnsafe $ unwrap (unwrap start).slot + startSlot = BigNum.toBigIntUnsafe $ unwrap start biSlot = BigNum.toBigIntUnsafe slot unless (startSlot <= biSlot) (throwError $ StartingSlotGreaterThanSlot s) pure $ wrap $ biSlot - startSlot -relTimeFromRelSlot :: EraSummary -> RelSlot -> Maybe RelTime -relTimeFromRelSlot eraSummary (RelSlot relSlot) = - let - slotLength = getSlotLength eraSummary - in - (<$>) wrap <<< BigInt.fromNumber $ (BigInt.toNumber relSlot) * slotLength +relTimeFromRelSlot :: SlotLength -> RelSlot -> Maybe RelTime +relTimeFromRelSlot slotLength (RelSlot relSlot) = + (<$>) wrap <<< BigInt.fromNumber $ (BigInt.toNumber relSlot) * (unwrap slotLength) -- As justified in https://github.com/input-output-hk/ouroboros-network/blob/bd9e5653647c3489567e02789b0ec5b75c726db2/ouroboros-consensus/src/Ouroboros/Consensus/HardFork/History/Qry.hs#L461-L481 -- Treat the upperbound as inclusive. -- | Returns the absolute time relative to some system start, not UNIX epoch. absTimeFromRelTime - :: EraSummary -> RelTime -> Either SlotToPosixTimeError AbsTime -absTimeFromRelTime (EraSummary { start, end }) (RelTime relTime) = do + :: RelativeTime -> RelTime -> Either SlotToPosixTimeError AbsTime +absTimeFromRelTime start (RelTime relTime) = do let - startTime = unwrap (unwrap start).time * slotLengthFactor + startTime = unwrap start * slotLengthFactor absTime = startTime + BigInt.toNumber relTime -- relative to System Start, not UNIX Epoch. -- If `EraSummary` doesn't have an end, the condition is automatically -- satisfied. We use `<=` as justified by the source code. @@ -836,12 +836,12 @@ absTimeFromRelTime (EraSummary { start, end }) (RelTime relTime) = do -- here could be issues going far into the future. But certain contracts are -- required to be in the distant future. Onchain, this uses POSIXTime which -- is stable, unlike Slots. - endTime = maybe (absTime + one) - ((*) slotLengthFactor <<< unwrap <<< _.time <<< unwrap) - end - unless - (absTime <= endTime) - (throwError $ EndTimeLessThanTime absTime) + -- endTime = maybe (absTime + one) + -- ((*) slotLengthFactor <<< unwrap <<< _.time <<< unwrap) + -- end + -- unless + -- (absTime <= endTime) + -- (throwError $ EndTimeLessThanTime absTime) wrap <$> (liftM CannotGetBigIntFromNumber $ BigInt.fromNumber absTime) @@ -938,11 +938,12 @@ instance DecodeAeson PosixTimeToSlotError where -- | Converts a `POSIXTime` to `Slot` given an `EraSummaries` and -- | `SystemStart` queried from Ogmios. posixTimeToSlot - :: EraSummaries + :: { slot :: Slot, time :: RelativeTime } + -> SlotLength -> SystemStart -> POSIXTime -> Effect (Either PosixTimeToSlotError Slot) -posixTimeToSlot eraSummaries sysStart pt'@(POSIXTime pt) = runExceptT do +posixTimeToSlot slotReference slotLength sysStart pt'@(POSIXTime pt) = runExceptT do -- Get JSDate: sysStartD <- liftEffect $ parse $ unwrap sysStart -- Get POSIX time for system start @@ -957,14 +958,14 @@ posixTimeToSlot eraSummaries sysStart pt'@(POSIXTime pt) = runExceptT do -- Keep as milliseconds: let absTime = wrap $ pt - sysStartPosix -- Find current era: - currentEra <- liftEither $ findTimeEraSummary eraSummaries absTime + -- currentEra <- liftEither $ findTimeEraSummary eraSummaries absTime -- Get relative time from absolute time w.r.t. current era - relTime <- liftEither $ relTimeFromAbsTime currentEra absTime + relTime <- liftEither $ relTimeFromAbsTime slotReference.time absTime -- Convert to relative slot - relSlotMod <- liftM CannotGetBigIntFromNumber' $ relSlotFromRelTime currentEra + relSlotMod <- liftM CannotGetBigIntFromNumber' $ relSlotFromRelTime slotLength relTime -- Get absolute slot relative to system start - liftEither $ slotFromRelSlot currentEra relSlotMod + liftEither $ slotFromRelSlot slotReference.slot relSlotMod -- | Finds the `EraSummary` an `AbsTime` lies inside (if any). findTimeEraSummary @@ -987,9 +988,9 @@ findTimeEraSummary (EraSummaries eraSummaries) absTime@(AbsTime at) = end relTimeFromAbsTime - :: EraSummary -> AbsTime -> Either PosixTimeToSlotError RelTime -relTimeFromAbsTime (EraSummary { start }) at@(AbsTime absTime) = do - let startTime = unwrap (unwrap start).time * slotLengthFactor + :: RelativeTime -> AbsTime -> Either PosixTimeToSlotError RelTime +relTimeFromAbsTime start at@(AbsTime absTime) = do + let startTime = unwrap start * slotLengthFactor unless (startTime <= BigInt.toNumber absTime) (throwError $ StartTimeGreaterThanTime at) let @@ -1003,24 +1004,23 @@ relTimeFromAbsTime (EraSummary { start }) at@(AbsTime absTime) = do -- | Converts relative time to relative slot (using Euclidean division) and -- | modulus for any leftover. relSlotFromRelTime - :: EraSummary -> RelTime -> Maybe (RelSlot /\ ModTime) -relSlotFromRelTime eraSummary (RelTime relTime) = + :: SlotLength -> RelTime -> Maybe (RelSlot /\ ModTime) +relSlotFromRelTime slotLength (RelTime relTime) = let - slotLength = getSlotLength eraSummary relSlot = wrap <$> - (BigInt.fromNumber <<< Math.trunc) (BigInt.toNumber relTime / slotLength) + (BigInt.fromNumber <<< Math.trunc) (BigInt.toNumber relTime / unwrap slotLength) modTime = wrap <$> - BigInt.fromNumber (BigInt.toNumber relTime Math.% slotLength) + BigInt.fromNumber (BigInt.toNumber relTime Math.% unwrap slotLength) in (/\) <$> relSlot <*> modTime slotFromRelSlot - :: EraSummary -> RelSlot /\ ModTime -> Either PosixTimeToSlotError Slot + :: Slot -> RelSlot /\ ModTime -> Either PosixTimeToSlotError Slot slotFromRelSlot - (EraSummary { start, end }) + start -- (EraSummary { start, end }) (RelSlot relSlot /\ mt@(ModTime modTime)) = do let - startSlot = BigNum.toBigIntUnsafe $ unwrap (unwrap start).slot + startSlot = BigNum.toBigIntUnsafe $ unwrap start -- Round down to the nearest Slot to accept Milliseconds as input. slot = startSlot + relSlot -- relative to system start -- If `EraSummary` doesn't have an end, the condition is automatically @@ -1029,13 +1029,13 @@ slotFromRelSlot -- here could be issues going far into the future. But certain contracts are -- required to be in the distant future. Onchain, this uses POSIXTime which -- is stable, unlike Slots. - endSlot = maybe (slot + one) - (BigNum.toBigIntUnsafe <<< unwrap <<< _.slot <<< unwrap) - end + -- endSlot = maybe (slot + one) + -- (BigNum.toBigIntUnsafe <<< unwrap <<< _.slot <<< unwrap) + -- end bnSlot <- liftM CannotGetBigNumFromBigInt' $ BigNum.fromBigInt slot -- Check we are less than the end slot, or if equal, there is no excess: - unless (slot < endSlot || slot == endSlot && modTime == zero) - (throwError $ EndSlotLessThanSlotOrModNonZero (wrap bnSlot) mt) + -- unless (slot < endSlot || slot == endSlot && modTime == zero) + -- (throwError $ EndSlotLessThanSlotOrModNonZero (wrap bnSlot) mt) pure $ wrap bnSlot -- | Get SlotLength in Milliseconds @@ -1059,28 +1059,32 @@ sequenceInterval AlwaysInterval = pure AlwaysInterval -- | Converts a `POSIXTimeRange` to `SlotRange` given an `EraSummaries` and -- | `SystemStart` queried from Ogmios. posixTimeRangeToSlotRange - :: EraSummaries + :: { slot :: Slot, time :: RelativeTime } + -> SlotLength -> SystemStart -> POSIXTimeRange -> Effect (Either PosixTimeToSlotError SlotRange) posixTimeRangeToSlotRange - eraSummaries + slotReference + slotLength sysStart range = sequenceInterval <$> - sequenceInterval (posixTimeToSlot eraSummaries sysStart <$> range) + sequenceInterval (posixTimeToSlot slotReference slotLength sysStart <$> range) -- | Converts a `SlotRange` to `POSIXTimeRange` given an `EraSummaries` and -- | `SystemStart` queried from Ogmios. slotRangeToPosixTimeRange - :: EraSummaries + :: { slot :: Slot, time :: RelativeTime } + -> SlotLength -> SystemStart -> SlotRange -> Effect (Either SlotToPosixTimeError POSIXTimeRange) slotRangeToPosixTimeRange - eraSummaries + slotReference + slotLength sysStart range = sequenceInterval <$> - sequenceInterval (slotToPosixTime eraSummaries sysStart <$> range) + sequenceInterval (slotToPosixTime slotReference slotLength sysStart <$> range) type TransactionValiditySlot = { validityStartInterval :: Maybe Slot, timeToLive :: Maybe Slot } @@ -1112,12 +1116,13 @@ slotRangeToTransactionValidity EmptyInterval = -- | Converts a `POSIXTimeRange` to a transaction validity interval via a -- | `SlotRange` to be used when building a CSL transaction body posixTimeRangeToTransactionValidity - :: EraSummaries + :: { slot :: Slot, time :: RelativeTime } + -> SlotLength -> SystemStart -> POSIXTimeRange -> Effect (Either PosixTimeToSlotError TransactionValiditySlot) -posixTimeRangeToTransactionValidity es ss = - map (map slotRangeToTransactionValidity) <<< posixTimeRangeToSlotRange es ss +posixTimeRangeToTransactionValidity sr sl ss = + map (map slotRangeToTransactionValidity) <<< posixTimeRangeToSlotRange sr sl ss data ToOnChainPosixTimeRangeError = PosixTimeToSlotError' PosixTimeToSlotError @@ -1290,21 +1295,22 @@ haskIntervalToInterval (HaskInterval { ivFrom, ivTo }) = case ivFrom, ivTo of -- | `OnchainPOSIXTimeRange` is intended to equal the validity range found in -- | the on-chain `ScriptContext` toOnchainPosixTimeRange - :: EraSummaries + :: { slot :: Slot, time :: RelativeTime } + -> SlotLength -> SystemStart -> POSIXTimeRange -> Effect (Either ToOnChainPosixTimeRangeError OnchainPOSIXTimeRange) -toOnchainPosixTimeRange es ss ptr = runExceptT do +toOnchainPosixTimeRange sr sl ss ptr = runExceptT do { validityStartInterval, timeToLive } <- - ExceptT $ posixTimeRangeToTransactionValidity es ss ptr + ExceptT $ posixTimeRangeToTransactionValidity sr sl ss ptr <#> lmap PosixTimeToSlotError' case validityStartInterval, timeToLive of Nothing, Nothing -> liftEither $ Right $ wrap always - Just s, Nothing -> ExceptT $ slotToPosixTime es ss s + Just s, Nothing -> ExceptT $ slotToPosixTime sr sl ss s <#> bimap SlotToPosixTimeError' (from >>> wrap) - Nothing, Just s -> ExceptT $ slotToPosixTime es ss s + Nothing, Just s -> ExceptT $ slotToPosixTime sr sl ss s <#> bimap SlotToPosixTimeError' (to >>> wrap) Just s1, Just s2 -> do - t1 <- ExceptT $ slotToPosixTime es ss s1 <#> lmap SlotToPosixTimeError' - t2 <- ExceptT $ slotToPosixTime es ss s2 <#> lmap SlotToPosixTimeError' + t1 <- ExceptT $ slotToPosixTime sr sl ss s1 <#> lmap SlotToPosixTimeError' + t2 <- ExceptT $ slotToPosixTime sr sl ss s2 <#> lmap SlotToPosixTimeError' liftEither $ Right $ wrap $ mkFiniteInterval t1 t2 diff --git a/src/Internal/Types/ScriptLookups.purs b/src/Internal/Types/ScriptLookups.purs index a7ffb0f682..0143d46462 100644 --- a/src/Internal/Types/ScriptLookups.purs +++ b/src/Internal/Types/ScriptLookups.purs @@ -54,10 +54,14 @@ module Ctl.Internal.Types.ScriptLookups import Prelude hiding (join) +import Effect.Aff.Class (liftAff) +import Ctl.Internal.Contract.QueryHandle (getQueryHandle) +import Ctl.Internal.Contract.Monad (Contract) import Aeson (class EncodeAeson) import Contract.Hashing (plutusScriptStakeValidatorHash) import Control.Monad.Error.Class (catchError, liftMaybe, throwError) import Control.Monad.Except.Trans (ExceptT(ExceptT), except, runExceptT) +import Control.Monad.Reader.Class (asks) import Control.Monad.State.Trans (StateT, get, gets, put, runStateT) import Control.Monad.Trans.Class (lift) import Ctl.Internal.Address (addressPaymentValidatorHash) @@ -253,7 +257,7 @@ import Data.Array (cons, filter, mapWithIndex, partition, toUnfoldable, zip) import Data.Array (singleton, union, (:)) as Array import Data.Bifunctor (lmap) import Data.BigInt (BigInt, fromInt) -import Data.Either (Either(Left, Right), either, isRight, note) +import Data.Either (Either(Left, Right), either, isRight, note, hush) import Data.Foldable (foldM) import Data.Generic.Rep (class Generic) import Data.Lattice (join) @@ -572,7 +576,7 @@ requireValue required = ValueSpentBalances { required, provided: mempty } -- We write `ReaderT QueryConfig Aff` below since type synonyms need to be fully -- applied. type ConstraintsM (a :: Type) (b :: Type) = - StateT (ConstraintProcessingState a) (QueryMExtended () Aff) b + StateT (ConstraintProcessingState a) Contract b -- The constraints don't precisely match those of Plutus: -- `forall v. (FromData (DatumType v), ToData (DatumType v), ToData (RedeemerType v))` @@ -817,7 +821,7 @@ addOwnInput -> InputConstraint redeemer -> ConstraintsM validator (Either MkUnbalancedTxError Unit) addOwnInput _pd (InputConstraint { txOutRef }) = do - networkId <- getNetworkId + networkId <- asks _.networkId runExceptT do ScriptLookups { txOutputs, typedValidator } <- use _lookups -- Convert to Cardano type @@ -842,7 +846,8 @@ addOwnOutput => OutputConstraint datum -> ConstraintsM validator (Either MkUnbalancedTxError Unit) addOwnOutput (OutputConstraint { datum: d, value }) = do - networkId <- getNetworkId + queryHandle <- getQueryHandle + networkId <- asks _.networkId runExceptT do ScriptLookups { typedValidator } <- use _lookups inst <- liftM TypedValidatorMissing typedValidator @@ -854,7 +859,8 @@ addOwnOutput (OutputConstraint { datum: d, value }) = do -- in the `OutputConstraint`: dHash <- liftM TypedTxOutHasNoDatumHash (typedTxOutDatumHash typedTxOut) dat <- - ExceptT $ lift $ getDatumByHash dHash <#> note (CannotQueryDatum dHash) + -- TODO fix + ExceptT $ liftAff $ (queryHandle.getDatumByHash dHash <#> hush >>> join >>> note (CannotQueryDatum dHash)) _cpsToTxBody <<< _outputs %= Array.(:) txOut ExceptT $ addDatum dat _valueSpentBalancesOutputs <>= provideValue value' @@ -1054,13 +1060,10 @@ processConstraint mpsMap osMap = do case _ of MustIncludeDatum dat -> addDatum dat MustValidateIn posixTimeRange -> do - -- Potential improvement: bring these out so we have one source of truth - -- although they should be static in a single contract call - es <- lift getEraSummaries - ss <- lift getSystemStart + { slotReference, slotLength, systemStart } <- asks _.ledgerConstants runExceptT do ({ timeToLive, validityStartInterval }) <- ExceptT $ liftEffect $ - posixTimeRangeToTransactionValidity es ss posixTimeRange + posixTimeRangeToTransactionValidity slotReference slotLength systemStart posixTimeRange <#> lmap (CannotConvertPOSIXTimeRange posixTimeRange) _cpsToTxBody <<< _Newtype %= _ @@ -1511,4 +1514,4 @@ getNetworkId :: forall (a :: Type) . ConstraintsM a NetworkId getNetworkId = use (_cpsToTxBody <<< _networkId) - >>= maybe (lift $ QueryM.getNetworkId) pure + >>= maybe (asks _.networkId) pure diff --git a/src/Internal/Types/TypedTxOut.purs b/src/Internal/Types/TypedTxOut.purs index bfd07798a3..b32b21af27 100644 --- a/src/Internal/Types/TypedTxOut.purs +++ b/src/Internal/Types/TypedTxOut.purs @@ -34,6 +34,8 @@ import Prelude import Control.Monad.Error.Class (throwError) import Control.Monad.Except.Trans (ExceptT(ExceptT), except, runExceptT) +import Effect.Aff.Class (liftAff) +import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.Cardano.Types.Transaction ( TransactionOutput(TransactionOutput) ) @@ -42,7 +44,6 @@ import Ctl.Internal.FromData (class FromData, fromData) import Ctl.Internal.Hashing (datumHash) as Hashing import Ctl.Internal.Helpers (liftM) import Ctl.Internal.IsData (class IsData) -import Ctl.Internal.QueryM (QueryM, getDatumByHash) import Ctl.Internal.Scripts (typedValidatorEnterpriseAddress) import Ctl.Internal.Serialization.Address (Address, NetworkId) import Ctl.Internal.ToData (class ToData, toData) @@ -54,11 +55,12 @@ import Ctl.Internal.Types.OutputDatum import Ctl.Internal.Types.PlutusData (PlutusData) import Ctl.Internal.Types.Transaction (TransactionInput) import Ctl.Internal.Types.TypedValidator (class DatumType, TypedValidator) -import Data.Either (Either, note) +import Data.Either (Either, hush, note) import Data.Generic.Rep (class Generic) import Data.Maybe (Maybe(Just, Nothing)) import Data.Newtype (unwrap, wrap) import Data.Show.Generic (genericShow) +import Ctl.Internal.Contract.Monad (Contract) -- | A `TransactionInput` tagged by a phantom type: and the -- | connection type of the output. @@ -263,16 +265,17 @@ typeTxOut => NetworkId -> TypedValidator validator -> TransactionOutput - -> QueryM (Either TypeCheckError (TypedTxOut validator datum)) + -> Contract (Either TypeCheckError (TypedTxOut validator datum)) typeTxOut networkId typedVal - (TransactionOutput { address, amount, datum }) = + (TransactionOutput { address, amount, datum }) = do + queryHandle <- getQueryHandle runExceptT do -- Assume `Nothing` is a public key. dHash <- liftM ExpectedScriptGotPubkey $ outputDatumDataHash datum void $ checkValidatorAddress networkId typedVal address - pd <- ExceptT $ getDatumByHash dHash <#> note (CannotQueryDatum dHash) + pd <- ExceptT $ liftAff $ queryHandle.getDatumByHash dHash <#> hush >>> join >>> note (CannotQueryDatum dHash) dtOut <- ExceptT $ checkDatum typedVal pd except $ note CannotMakeTypedTxOut (mkTypedTxOut networkId typedVal dtOut amount) @@ -289,7 +292,7 @@ typeTxOutRef -> (TransactionInput -> Maybe TransactionOutput) -> TypedValidator validator -> TransactionInput - -> QueryM (Either TypeCheckError (TypedTxOutRef validator datum)) + -> Contract (Either TypeCheckError (TypedTxOutRef validator datum)) typeTxOutRef networkId lookupRef typedVal txOutRef = runExceptT do out <- liftM UnknownRef (lookupRef txOutRef) typedTxOut <- ExceptT $ typeTxOut networkId typedVal out diff --git a/test/AffInterface.purs b/test/AffInterface.purs index 22fb7d9953..59edf1c321 100644 --- a/test/AffInterface.purs +++ b/test/AffInterface.purs @@ -19,7 +19,7 @@ import Ctl.Internal.QueryM.GetTxByHash (getTxByHash) import Ctl.Internal.QueryM.Ogmios (OgmiosAddress) import Ctl.Internal.QueryM.SystemStart (getSystemStart) import Ctl.Internal.QueryM.Utxos (utxosAt) -import Ctl.Internal.QueryM.WaitUntilSlot (waitUntilSlot) +import Ctl.Internal.Contract.WaitUntilSlot (waitUntilSlot) import Ctl.Internal.Serialization.Address (Slot(Slot)) import Ctl.Internal.Test.TestPlanM (TestPlanM) import Ctl.Internal.Types.BigNum (add, fromInt) as BigNum From 23df11d67826bfddfd44dadcf61d23f842b7dc85 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Sat, 1 Oct 2022 18:15:55 +0200 Subject: [PATCH 012/373] First draft of multi-asset coin selection algorithm (cherry picked from commit 8a8e7651bf31af678dfa8a28c44ea87ad7739ffe) --- src/Internal/BalanceTx/CoinSelection.purs | 371 ++++++++++++++++++++++ src/Internal/BalanceTx/Error.purs | 8 +- 2 files changed, 377 insertions(+), 2 deletions(-) create mode 100644 src/Internal/BalanceTx/CoinSelection.purs diff --git a/src/Internal/BalanceTx/CoinSelection.purs b/src/Internal/BalanceTx/CoinSelection.purs new file mode 100644 index 0000000000..35db11e15e --- /dev/null +++ b/src/Internal/BalanceTx/CoinSelection.purs @@ -0,0 +1,371 @@ +module Ctl.Internal.BalanceTx.CoinSelection where + +import Prelude + +import Control.Bind (bindFlipped) +import Control.Monad.Error.Class (class MonadThrow, throwError) +import Ctl.Internal.BalanceTx.Error (BalanceTxError(CoinSelectionFailed)) +import Ctl.Internal.Cardano.Types.Transaction (TransactionOutput, UtxoMap) +import Ctl.Internal.Cardano.Types.Value (Coin, CurrencySymbol, Value(Value)) +import Ctl.Internal.Cardano.Types.Value + ( flattenNonAdaValue + , valueOf + , valueToCoin + , valueToCoin' + ) as Value +import Ctl.Internal.Types.TokenName (TokenName) +import Ctl.Internal.Types.Transaction (TransactionInput) +import Data.Array (fromFoldable, snoc, uncons) as Array +import Data.Array ((!!)) +import Data.Array.NonEmpty (NonEmptyArray) +import Data.Array.NonEmpty (cons', fromArray, singleton, uncons) as NEArray +import Data.BigInt (BigInt) +import Data.BigInt (abs, fromInt) as BigInt +import Data.Foldable (foldMap) as Foldable +import Data.Function (applyFlipped) +import Data.Lens (Lens') +import Data.Lens.Getter (view, (^.)) +import Data.Lens.Iso.Newtype (_Newtype) +import Data.Lens.Record (prop) +import Data.Lens.Setter (over) +import Data.Map (Map) +import Data.Map as Map +import Data.Maybe (Maybe(Just, Nothing), maybe, maybe') +import Data.Newtype (class Newtype, unwrap, wrap) +import Data.Set (Set) +import Data.Set (fromFoldable, isEmpty, member, singleton, size) as Set +import Data.Tuple (fst) as Tuple +import Data.Tuple.Nested (type (/\), (/\)) +import Effect.Class (class MonadEffect, liftEffect) +import Effect.Random (randomInt) as Random +import Type.Proxy (Proxy(Proxy)) + +-------------------------------------------------------------------------------- +-- CoinSelection +-------------------------------------------------------------------------------- + +data MultiAssetSelection = MultiAssetSelection SelectionStrategy + +-- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L325 +data SelectionStrategy = SelectionStrategyMinimal | SelectionStrategyOptimal + +performMultiAssetSelection + :: forall (m :: Type -> Type) + . MonadEffect m + => MonadThrow BalanceTxError m + => MultiAssetSelection + -> UtxoMap + -> Value + -> m (Set TransactionInput) +performMultiAssetSelection (MultiAssetSelection strategy) utxos requiredValue = + selectedInputs <$> runRoundRobinM (mkSelectionState utxos) selectors + where + selectors + :: Array (SelectionState -> m (Maybe SelectionState)) + selectors = + map assetSelector (valueAssets requiredValue) `Array.snoc` coinSelector + where + assetSelector + :: AssetClass /\ BigInt -> SelectionState -> m (Maybe SelectionState) + assetSelector = runSelectionStep <<< assetSelectionLens strategy + + coinSelector :: SelectionState -> m (Maybe SelectionState) + coinSelector = + runSelectionStep $ + coinSelectionLens strategy (Value.valueToCoin requiredValue) + +-- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/Primitive/Types/UTxOSelection.hs#L145 +newtype SelectionState = SelectionState + { leftoverUtxos :: UtxoMap + , selectedUtxos :: UtxoMap + } + +derive instance Newtype SelectionState _ + +_leftoverUtxos :: Lens' SelectionState UtxoMap +_leftoverUtxos = _Newtype <<< prop (Proxy :: Proxy "leftoverUtxos") + +_selectedUtxos :: Lens' SelectionState UtxoMap +_selectedUtxos = _Newtype <<< prop (Proxy :: Proxy "selectedUtxos") + +-- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/Primitive/Types/UTxOSelection.hs#L192 +mkSelectionState :: UtxoMap -> SelectionState +mkSelectionState = wrap <<< { leftoverUtxos: _, selectedUtxos: Map.empty } + +-- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/Primitive/Types/UTxOSelection.hs#L426 +selectUtxo :: TxUnspentOutput -> SelectionState -> SelectionState +selectUtxo (oref /\ out) = + over _selectedUtxos (Map.insert oref out) + <<< over _leftoverUtxos (Map.delete oref) + +balance :: UtxoMap -> Value +balance = Foldable.foldMap (_.amount <<< unwrap) + +-- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/Primitive/Types/UTxOSelection.hs#L375 +selectedBalance :: SelectionState -> Value +selectedBalance = balance <<< _.selectedUtxos <<< unwrap + +-- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L2169 +selectedAssetQuantity :: AssetClass -> SelectionState -> BigInt +selectedAssetQuantity assetClass = + getAssetQuantity assetClass <<< selectedBalance + +-- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L2175 +selectedCoinQuantity :: SelectionState -> BigInt +selectedCoinQuantity = Value.valueToCoin' <<< selectedBalance + +selectedInputs :: SelectionState -> Set TransactionInput +selectedInputs = Set.fromFoldable <<< Map.keys <<< view _selectedUtxos + +-- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L1254 +type SelectionLens (m :: Type -> Type) = + { currentQuantity :: SelectionState -> BigInt + , requiredQuantity :: BigInt + , selectQuantityCover :: SelectionState -> m (Maybe SelectionState) + , selectQuantityImprove :: SelectionState -> m (Maybe SelectionState) + , selectionStrategy :: SelectionStrategy + } + +-- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L1159 +assetSelectionLens + :: forall (m :: Type -> Type) + . MonadEffect m + => SelectionStrategy + -> AssetClass /\ BigInt + -> SelectionLens m +assetSelectionLens selectionStrategy (assetClass /\ requiredQuantity) = + { currentQuantity: selectedAssetQuantity assetClass + , requiredQuantity + , selectQuantityCover: + selectQuantityOf assetClass SelectionPriorityCover + , selectQuantityImprove: + selectQuantityOf assetClass SelectionPriorityImprove + , selectionStrategy + } + +-- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L1173 +coinSelectionLens + :: forall (m :: Type -> Type) + . MonadEffect m + => SelectionStrategy + -> Coin + -> SelectionLens m +coinSelectionLens selectionStrategy coin = + { currentQuantity: selectedCoinQuantity + , requiredQuantity: unwrap coin + , selectQuantityCover: + selectQuantityOf coin SelectionPriorityCover + , selectQuantityImprove: + selectQuantityOf coin SelectionPriorityImprove + , selectionStrategy + } + +-- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L1217 +selectQuantityOf + :: forall (m :: Type -> Type) (asset :: Type) + . MonadEffect m + => ApplySelectionFilter asset + => asset + -> SelectionPriority + -> SelectionState + -> m (Maybe SelectionState) +selectQuantityOf asset priority state = + map updateState <$> + selectRandomWithPriority (state ^. _leftoverUtxos) filters + where + filters :: NonEmptyArray (SelectionFilter asset) + filters = filtersForAssetWithPriority asset priority + + updateState :: TxUnspentOutput /\ UtxoMap -> SelectionState + updateState = flip selectUtxo state <<< Tuple.fst + +-- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L1284 +runSelectionStep + :: forall (m :: Type -> Type) + . MonadThrow BalanceTxError m + => SelectionLens m + -> SelectionState + -> m (Maybe SelectionState) +runSelectionStep lens state + | lens.currentQuantity state < lens.requiredQuantity = + lens.selectQuantityCover state + >>= maybe (throwError CoinSelectionFailed) (pure <<< Just) + | otherwise = + bindFlipped requireImprovement <$> lens.selectQuantityImprove state + where + requireImprovement :: SelectionState -> Maybe SelectionState + requireImprovement state' + | distanceFromTarget state' < distanceFromTarget state = Just state' + | otherwise = Nothing + + distanceFromTarget :: SelectionState -> BigInt + distanceFromTarget = + BigInt.abs <<< sub targetQuantity <<< lens.currentQuantity + + targetMultiplier :: Int + targetMultiplier = + case lens.selectionStrategy of + SelectionStrategyMinimal -> 1 + SelectionStrategyOptimal -> 2 + + targetQuantity :: BigInt + targetQuantity = + lens.requiredQuantity * (BigInt.fromInt targetMultiplier) + +-------------------------------------------------------------------------------- +-- Round-robin processing +-------------------------------------------------------------------------------- + +type Processor (m :: Type -> Type) (s :: Type) (s' :: Type) = s -> m (Maybe s') + +runRoundRobinM + :: forall (m :: Type -> Type) (s :: Type) + . Monad m + => s + -> Array (Processor m s s) + -> m s +runRoundRobinM state = runRoundRobinM' state identity + +-- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L2155 +runRoundRobinM' + :: forall (m :: Type -> Type) (s :: Type) (s' :: Type) + . Monad m + => s + -> (s' -> s) + -> Array (Processor m s s') + -> m s +runRoundRobinM' state demote processors = go state processors [] + where + go :: s -> Array (Processor m s s') -> Array (Processor m s s') -> m s + go s [] [] = pure s + go s ps qs = + case Array.uncons ps of + Nothing -> go s qs [] + Just { head: p, tail: ps' } -> + p s >>= case _ of + Nothing -> go s ps' qs + Just s' -> go (demote s') ps' (Array.snoc qs p) + +-------------------------------------------------------------------------------- +-- SelectionPriority +-------------------------------------------------------------------------------- + +data SelectionPriority = SelectionPriorityCover | SelectionPriorityImprove + +filtersForAssetWithPriority + :: forall (asset :: Type) + . asset + -> SelectionPriority + -> NonEmptyArray (SelectionFilter asset) +filtersForAssetWithPriority asset priority = + case priority of + SelectionPriorityCover -> + applyFlipped asset <$> + NEArray.cons' SelectSingleton [ SelectPairWith, SelectAnyWith ] + SelectionPriorityImprove -> + NEArray.singleton (SelectSingleton asset) + +-- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L460 +selectRandomWithPriority + :: forall (m :: Type -> Type) (asset :: Type) + . MonadEffect m + => ApplySelectionFilter asset + => UtxoMap + -> NonEmptyArray (SelectionFilter asset) + -> m (Maybe (TxUnspentOutput /\ UtxoMap)) +selectRandomWithPriority utxos filters = + NEArray.uncons filters # \{ head: filter, tail } -> + case NEArray.fromArray tail of + Nothing -> + selectRandomWithFilter utxos filter + Just xs -> + maybe' (\_ -> selectRandomWithPriority utxos xs) (pure <<< Just) + =<< selectRandomWithFilter utxos filter + +-------------------------------------------------------------------------------- +-- SelectionFilter, ApplySelectionFilter +-------------------------------------------------------------------------------- + +-- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L399 +data SelectionFilter (asset :: Type) + = SelectSingleton asset + | SelectPairWith asset + | SelectAnyWith asset + +class ApplySelectionFilter (asset :: Type) where + applySelectionFilter :: UtxoMap -> SelectionFilter asset -> UtxoMap + +instance ApplySelectionFilter AssetClass where + applySelectionFilter utxos filter = + flip Map.filter utxos $ + case filter of + SelectSingleton asset -> + eq (Set.singleton asset) <<< txOutputAssetClasses + SelectPairWith asset -> + (\assets -> Set.member asset assets && Set.size assets == 2) + <<< txOutputAssetClasses + SelectAnyWith asset -> + Set.member asset <<< txOutputAssetClasses + +instance ApplySelectionFilter Coin where + applySelectionFilter utxos filter = + case filter of + SelectSingleton _ -> + Map.filter (Set.isEmpty <<< txOutputAssetClasses) utxos + SelectPairWith _ -> + Map.filter (eq one <<< Set.size <<< txOutputAssetClasses) utxos + SelectAnyWith _ -> utxos + +type TxUnspentOutput = TransactionInput /\ TransactionOutput + +-- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L418 +selectRandomWithFilter + :: forall (m :: Type -> Type) (asset :: Type) + . MonadEffect m + => ApplySelectionFilter asset + => UtxoMap + -> SelectionFilter asset + -> m (Maybe (TxUnspentOutput /\ UtxoMap)) +selectRandomWithFilter utxos filter = + selectRandomMapMember (applySelectionFilter utxos filter) + <#> map (\utxo@(oref /\ _) -> utxo /\ Map.delete oref utxos) + +-------------------------------------------------------------------------------- +-- Helpers +-------------------------------------------------------------------------------- + +-- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L598 +selectRandomMapMember + :: forall (m :: Type -> Type) (k :: Type) (v :: Type) + . MonadEffect m + => Map k v + -> m (Maybe (k /\ v)) +selectRandomMapMember m + | Map.isEmpty m = pure Nothing + | otherwise = liftEffect do + idx <- Random.randomInt zero (Map.size m - one) + pure $ Map.toUnfoldable m !! idx + +-------------------------------------------------------------------------------- +-- AssetClass +-------------------------------------------------------------------------------- + +data AssetClass = AssetClass CurrencySymbol TokenName + +derive instance Eq AssetClass +derive instance Ord AssetClass + +valueAssets :: Value -> Array (AssetClass /\ BigInt) +valueAssets (Value _ assets) = + Array.fromFoldable (Value.flattenNonAdaValue assets) + <#> \(cs /\ tn /\ quantity) -> AssetClass cs tn /\ quantity + +valueAssetClasses :: Value -> Set AssetClass +valueAssetClasses = Set.fromFoldable <<< map Tuple.fst <<< valueAssets + +getAssetQuantity :: AssetClass -> Value -> BigInt +getAssetQuantity (AssetClass cs tn) value = Value.valueOf value cs tn + +txOutputAssetClasses :: TransactionOutput -> Set AssetClass +txOutputAssetClasses = valueAssetClasses <<< _.amount <<< unwrap + diff --git a/src/Internal/BalanceTx/Error.purs b/src/Internal/BalanceTx/Error.purs index aff59d0ec3..6999b70c72 100644 --- a/src/Internal/BalanceTx/Error.purs +++ b/src/Internal/BalanceTx/Error.purs @@ -4,7 +4,9 @@ module Ctl.Internal.BalanceTx.Error ( Actual(Actual) , BalanceTxError - ( CouldNotConvertScriptOutputToTxInput + ( BalanceInsufficientError + , CoinSelectionFailed + , CouldNotConvertScriptOutputToTxInput , CouldNotGetChangeAddress , CouldNotGetCollateral , CouldNotGetUtxos @@ -65,7 +67,9 @@ import Data.Tuple.Nested (type (/\), (/\)) -- | Errors conditions that may possibly arise during transaction balancing data BalanceTxError - = CouldNotConvertScriptOutputToTxInput + = BalanceInsufficientError Expected Actual + | CoinSelectionFailed + | CouldNotConvertScriptOutputToTxInput | CouldNotGetChangeAddress | CouldNotGetCollateral | CouldNotGetUtxos From 71c2c7769387f19ad73d4e2186fa829fd077802c Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Mon, 3 Oct 2022 14:21:52 +0200 Subject: [PATCH 013/373] CoinSelection: Improve err messages, Extract AssetClass to Cardano.Value (cherry picked from commit ca83764680b22d217d3a515e98ffdcfd83c63820) --- src/Internal/BalanceTx/CoinSelection.purs | 115 ++++++++++++++-------- src/Internal/BalanceTx/Error.purs | 4 +- src/Internal/Cardano/Types/Value.purs | 31 +++++- 3 files changed, 106 insertions(+), 44 deletions(-) diff --git a/src/Internal/BalanceTx/CoinSelection.purs b/src/Internal/BalanceTx/CoinSelection.purs index 35db11e15e..1670f0e904 100644 --- a/src/Internal/BalanceTx/CoinSelection.purs +++ b/src/Internal/BalanceTx/CoinSelection.purs @@ -1,30 +1,46 @@ -module Ctl.Internal.BalanceTx.CoinSelection where +module Ctl.Internal.BalanceTx.CoinSelection + ( MultiAssetSelection(MultiAssetSelection) + , SelectionState(SelectionState) + , SelectionStrategy(SelectionStrategyMinimal, SelectionStrategyOptimal) + , performMultiAssetSelection + ) where import Prelude import Control.Bind (bindFlipped) import Control.Monad.Error.Class (class MonadThrow, throwError) -import Ctl.Internal.BalanceTx.Error (BalanceTxError(CoinSelectionFailed)) +import Ctl.Internal.BalanceTx.Error + ( Actual(Actual) + , BalanceTxError + ( BalanceInsufficientError + , InsufficientUtxoBalanceToCoverAsset + ) + , Expected(Expected) + ) import Ctl.Internal.Cardano.Types.Transaction (TransactionOutput, UtxoMap) -import Ctl.Internal.Cardano.Types.Value (Coin, CurrencySymbol, Value(Value)) +import Ctl.Internal.Cardano.Types.Value (AssetClass(AssetClass), Coin, Value) import Ctl.Internal.Cardano.Types.Value - ( flattenNonAdaValue - , valueOf + ( getAssetQuantity + , getCurrencySymbol + , lt + , valueAssetClasses + , valueAssets , valueToCoin , valueToCoin' ) as Value -import Ctl.Internal.Types.TokenName (TokenName) +import Ctl.Internal.Types.ByteArray (byteArrayToHex) +import Ctl.Internal.Types.TokenName (getTokenName) as TokenName import Ctl.Internal.Types.Transaction (TransactionInput) -import Data.Array (fromFoldable, snoc, uncons) as Array +import Data.Array (snoc, uncons) as Array import Data.Array ((!!)) import Data.Array.NonEmpty (NonEmptyArray) import Data.Array.NonEmpty (cons', fromArray, singleton, uncons) as NEArray import Data.BigInt (BigInt) -import Data.BigInt (abs, fromInt) as BigInt +import Data.BigInt (abs, fromInt, toString) as BigInt import Data.Foldable (foldMap) as Foldable import Data.Function (applyFlipped) import Data.Lens (Lens') -import Data.Lens.Getter (view, (^.)) +import Data.Lens.Getter ((^.)) import Data.Lens.Iso.Newtype (_Newtype) import Data.Lens.Record (prop) import Data.Lens.Setter (over) @@ -56,15 +72,28 @@ performMultiAssetSelection => MultiAssetSelection -> UtxoMap -> Value - -> m (Set TransactionInput) + -> m SelectionState performMultiAssetSelection (MultiAssetSelection strategy) utxos requiredValue = - selectedInputs <$> runRoundRobinM (mkSelectionState utxos) selectors + case availableValue `Value.lt` requiredValue of + true -> + throwError balanceInsufficientError + false -> + runRoundRobinM (mkSelectionState utxos) selectors where + balanceInsufficientError :: BalanceTxError + balanceInsufficientError = + BalanceInsufficientError (Expected requiredValue) (Actual availableValue) + + availableValue :: Value + availableValue = balance utxos + selectors :: Array (SelectionState -> m (Maybe SelectionState)) - selectors = - map assetSelector (valueAssets requiredValue) `Array.snoc` coinSelector + selectors = map assetSelector assets `Array.snoc` coinSelector where + assets :: Array (AssetClass /\ BigInt) + assets = Value.valueAssets requiredValue + assetSelector :: AssetClass /\ BigInt -> SelectionState -> m (Maybe SelectionState) assetSelector = runSelectionStep <<< assetSelectionLens strategy @@ -108,18 +137,16 @@ selectedBalance = balance <<< _.selectedUtxos <<< unwrap -- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L2169 selectedAssetQuantity :: AssetClass -> SelectionState -> BigInt selectedAssetQuantity assetClass = - getAssetQuantity assetClass <<< selectedBalance + Value.getAssetQuantity assetClass <<< selectedBalance -- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L2175 selectedCoinQuantity :: SelectionState -> BigInt selectedCoinQuantity = Value.valueToCoin' <<< selectedBalance -selectedInputs :: SelectionState -> Set TransactionInput -selectedInputs = Set.fromFoldable <<< Map.keys <<< view _selectedUtxos - -- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L1254 type SelectionLens (m :: Type -> Type) = - { currentQuantity :: SelectionState -> BigInt + { assetDisplayString :: String + , currentQuantity :: SelectionState -> BigInt , requiredQuantity :: BigInt , selectQuantityCover :: SelectionState -> m (Maybe SelectionState) , selectQuantityImprove :: SelectionState -> m (Maybe SelectionState) @@ -134,7 +161,10 @@ assetSelectionLens -> AssetClass /\ BigInt -> SelectionLens m assetSelectionLens selectionStrategy (assetClass /\ requiredQuantity) = - { currentQuantity: selectedAssetQuantity assetClass + { assetDisplayString: + showAssetClassWithQuantity assetClass requiredQuantity + , currentQuantity: + selectedAssetQuantity assetClass , requiredQuantity , selectQuantityCover: selectQuantityOf assetClass SelectionPriorityCover @@ -151,7 +181,8 @@ coinSelectionLens -> Coin -> SelectionLens m coinSelectionLens selectionStrategy coin = - { currentQuantity: selectedCoinQuantity + { assetDisplayString: show coin + , currentQuantity: selectedCoinQuantity , requiredQuantity: unwrap coin , selectQuantityCover: selectQuantityOf coin SelectionPriorityCover @@ -188,8 +219,13 @@ runSelectionStep -> m (Maybe SelectionState) runSelectionStep lens state | lens.currentQuantity state < lens.requiredQuantity = - lens.selectQuantityCover state - >>= maybe (throwError CoinSelectionFailed) (pure <<< Just) + let + balanceInsufficientError :: BalanceTxError + balanceInsufficientError = + InsufficientUtxoBalanceToCoverAsset lens.assetDisplayString + in + lens.selectQuantityCover state + >>= maybe (throwError balanceInsufficientError) (pure <<< Just) | otherwise = bindFlipped requireImprovement <$> lens.selectQuantityImprove state where @@ -346,26 +382,23 @@ selectRandomMapMember m idx <- Random.randomInt zero (Map.size m - one) pure $ Map.toUnfoldable m !! idx --------------------------------------------------------------------------------- --- AssetClass --------------------------------------------------------------------------------- - -data AssetClass = AssetClass CurrencySymbol TokenName - -derive instance Eq AssetClass -derive instance Ord AssetClass - -valueAssets :: Value -> Array (AssetClass /\ BigInt) -valueAssets (Value _ assets) = - Array.fromFoldable (Value.flattenNonAdaValue assets) - <#> \(cs /\ tn /\ quantity) -> AssetClass cs tn /\ quantity +txOutputAssetClasses :: TransactionOutput -> Set AssetClass +txOutputAssetClasses = + Set.fromFoldable <<< Value.valueAssetClasses <<< _.amount <<< unwrap -valueAssetClasses :: Value -> Set AssetClass -valueAssetClasses = Set.fromFoldable <<< map Tuple.fst <<< valueAssets +showAssetClassWithQuantity :: AssetClass -> BigInt -> String +showAssetClassWithQuantity (AssetClass cs tn) quantity = + "(Asset (" <> displayCurrencySymbol <> displayTokenName <> displayQuantity + where + displayCurrencySymbol :: String + displayCurrencySymbol = + "cs: " <> byteArrayToHex (Value.getCurrencySymbol cs) <> ", " -getAssetQuantity :: AssetClass -> Value -> BigInt -getAssetQuantity (AssetClass cs tn) value = Value.valueOf value cs tn + displayTokenName :: String + displayTokenName = + "tn: " <> byteArrayToHex (TokenName.getTokenName tn) <> ", " -txOutputAssetClasses :: TransactionOutput -> Set AssetClass -txOutputAssetClasses = valueAssetClasses <<< _.amount <<< unwrap + displayQuantity :: String + displayQuantity = + "quantity: " <> BigInt.toString quantity <> "))" diff --git a/src/Internal/BalanceTx/Error.purs b/src/Internal/BalanceTx/Error.purs index 6999b70c72..91055d6990 100644 --- a/src/Internal/BalanceTx/Error.purs +++ b/src/Internal/BalanceTx/Error.purs @@ -5,7 +5,6 @@ module Ctl.Internal.BalanceTx.Error ( Actual(Actual) , BalanceTxError ( BalanceInsufficientError - , CoinSelectionFailed , CouldNotConvertScriptOutputToTxInput , CouldNotGetChangeAddress , CouldNotGetCollateral @@ -14,6 +13,7 @@ module Ctl.Internal.BalanceTx.Error , CollateralReturnMinAdaValueCalcError , ExUnitsEvaluationFailed , InsufficientTxInputs + , InsufficientUtxoBalanceToCoverAsset , ReindexRedeemersError , UtxoLookupFailedFor , UtxoMinAdaValueCalculationFailed @@ -68,7 +68,6 @@ import Data.Tuple.Nested (type (/\), (/\)) -- | Errors conditions that may possibly arise during transaction balancing data BalanceTxError = BalanceInsufficientError Expected Actual - | CoinSelectionFailed | CouldNotConvertScriptOutputToTxInput | CouldNotGetChangeAddress | CouldNotGetCollateral @@ -77,6 +76,7 @@ data BalanceTxError | CollateralReturnMinAdaValueCalcError | ExUnitsEvaluationFailed UnattachedUnbalancedTx Ogmios.TxEvaluationFailure | InsufficientTxInputs Expected Actual + | InsufficientUtxoBalanceToCoverAsset String | ReindexRedeemersError ReindexErrors | UtxoLookupFailedFor TransactionInput | UtxoMinAdaValueCalculationFailed diff --git a/src/Internal/Cardano/Types/Value.purs b/src/Internal/Cardano/Types/Value.purs index f64621d938..70a5240426 100644 --- a/src/Internal/Cardano/Types/Value.purs +++ b/src/Internal/Cardano/Types/Value.purs @@ -1,5 +1,6 @@ module Ctl.Internal.Cardano.Types.Value - ( Coin(Coin) + ( AssetClass(AssetClass) + , Coin(Coin) , CurrencySymbol , NonAdaAsset , Value(Value) @@ -12,6 +13,7 @@ module Ctl.Internal.Cardano.Types.Value , filterNonAda , flattenNonAdaValue , geq + , getAssetQuantity , getCurrencySymbol , getLovelace , getNonAdaAsset @@ -46,6 +48,8 @@ module Ctl.Internal.Cardano.Types.Value , unionWith , unionWithNonAda , unwrapNonAdaAsset + , valueAssetClasses + , valueAssets , valueOf , valueToCoin , valueToCoin' @@ -89,6 +93,7 @@ import Ctl.Internal.Types.TokenName , mkTokenNames ) import Data.Array (cons, filter) +import Data.Array (fromFoldable) as Array import Data.Array.NonEmpty (NonEmptyArray) import Data.Array.NonEmpty (replicate, singleton, zipWith) as NEArray import Data.Bifunctor (bimap) @@ -491,6 +496,30 @@ mkSingletonValue' curSymbol tokenName amount = do if isAdaCs then Value (Coin amount) mempty else Value mempty $ mkSingletonNonAdaAsset curSymbol tokenName amount +-------------------------------------------------------------------------------- +-- AssetClass +-------------------------------------------------------------------------------- + +data AssetClass = AssetClass CurrencySymbol TokenName + +derive instance Generic AssetClass _ +derive instance Eq AssetClass +derive instance Ord AssetClass + +instance Show AssetClass where + show = genericShow + +getAssetQuantity :: AssetClass -> Value -> BigInt +getAssetQuantity (AssetClass cs tn) value = valueOf value cs tn + +valueAssets :: Value -> Array (AssetClass /\ BigInt) +valueAssets (Value _ assets) = + Array.fromFoldable (flattenNonAdaValue assets) + <#> \(cs /\ tn /\ quantity) -> AssetClass cs tn /\ quantity + +valueAssetClasses :: Value -> Array AssetClass +valueAssetClasses = map fst <<< valueAssets + -------------------------------------------------------------------------------- -- Helpers -------------------------------------------------------------------------------- From 53d25e65c6ff03cb610ac3dbff8a511521e02846 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Wed, 5 Oct 2022 12:52:12 +0200 Subject: [PATCH 014/373] Rewrite balancing algorithm to support multi-asset coin selection (cherry picked from commit 45f77bf56f0b211880b2fc7f158c6510074c750a) --- spago.dhall | 1 + src/Internal/BalanceTx/BalanceTx.purs | 474 ++++++++-------------- src/Internal/BalanceTx/CoinSelection.purs | 11 +- 3 files changed, 183 insertions(+), 303 deletions(-) diff --git a/spago.dhall b/spago.dhall index 62fe612aae..43c4af9313 100644 --- a/spago.dhall +++ b/spago.dhall @@ -70,6 +70,7 @@ You can edit this file as you like. , "quickcheck" , "quickcheck-combinators" , "quickcheck-laws" + , "random" , "rationals" , "record" , "refs" diff --git a/src/Internal/BalanceTx/BalanceTx.purs b/src/Internal/BalanceTx/BalanceTx.purs index 3f50bd7edd..ea11aa122e 100644 --- a/src/Internal/BalanceTx/BalanceTx.purs +++ b/src/Internal/BalanceTx/BalanceTx.purs @@ -8,8 +8,13 @@ import Prelude import Control.Monad.Error.Class (liftMaybe) import Control.Monad.Except.Trans (ExceptT(ExceptT), except, runExceptT) -import Control.Monad.Logger.Class (class MonadLogger) -import Control.Monad.Logger.Class as Logger +import Ctl.Internal.BalanceTx.CoinSelection + ( SelectionState + , SelectionStrategy(SelectionStrategyOptimal) + , _leftoverUtxos + , performMultiAssetSelection + , selectedInputs + ) import Ctl.Internal.BalanceTx.Collateral ( addTxCollateral , addTxCollateralReturn @@ -24,8 +29,7 @@ import Ctl.Internal.BalanceTx.Constraints import Ctl.Internal.BalanceTx.Error ( Actual(Actual) , BalanceTxError - ( CouldNotConvertScriptOutputToTxInput - , CouldNotGetChangeAddress + ( CouldNotGetChangeAddress , CouldNotGetCollateral , CouldNotGetUtxos , ExUnitsEvaluationFailed @@ -38,17 +42,13 @@ import Ctl.Internal.BalanceTx.Error , printTxEvaluationFailure ) as BalanceTxErrorExport import Ctl.Internal.BalanceTx.Error - ( Actual(Actual) - , BalanceTxError - ( CouldNotConvertScriptOutputToTxInput - , CouldNotGetChangeAddress + ( BalanceTxError + ( CouldNotGetChangeAddress , CouldNotGetCollateral , CouldNotGetUtxos - , InsufficientTxInputs , UtxoLookupFailedFor , UtxoMinAdaValueCalculationFailed ) - , Expected(Expected) ) import Ctl.Internal.BalanceTx.ExUnitsAndMinFee ( evalExUnitsAndMinFee @@ -63,7 +63,7 @@ import Ctl.Internal.BalanceTx.Helpers import Ctl.Internal.BalanceTx.Types ( BalanceTxM , FinalizedTransaction - , PrebalancedTransaction(PrebalancedTransaction) + , PrebalancedTransaction , askCip30Wallet , askCoinsPerUtxoUnit , askNetworkId @@ -78,7 +78,7 @@ import Ctl.Internal.Cardano.Types.Transaction ( Certificate(StakeRegistration, StakeDeregistration) , Transaction(Transaction) , TransactionOutput(TransactionOutput) - , TxBody(TxBody) + , TxBody , UtxoMap , _body , _certs @@ -95,11 +95,9 @@ import Ctl.Internal.Cardano.Types.Value , Value , coinToValue , equipartitionValueWithTokenQuantityUpperBound - , geq , getNonAdaAsset , minus , mkValue - , posNonAdaAsset , valueToCoin' ) import Ctl.Internal.QueryM (QueryM, getProtocolParameters) @@ -109,11 +107,7 @@ import Ctl.Internal.QueryM.Utxos , getWalletCollateral , utxosAt ) -import Ctl.Internal.Serialization.Address - ( Address - , addressPaymentCred - , withStakeCredential - ) +import Ctl.Internal.Serialization.Address (Address) import Ctl.Internal.Types.OutputDatum (OutputDatum(NoOutputDatum)) import Ctl.Internal.Types.ScriptLookups (UnattachedUnbalancedTx) import Ctl.Internal.Types.Transaction (TransactionInput) @@ -122,19 +116,18 @@ import Data.Array as Array import Data.Array.NonEmpty (NonEmptyArray) import Data.Array.NonEmpty (toArray) as NEArray import Data.BigInt (BigInt) -import Data.Either (Either(Left, Right), hush, note) -import Data.Foldable (fold, foldMap, foldl, foldr, sum) +import Data.Either (Either, note) +import Data.Foldable (fold, foldMap, foldr, sum) import Data.Lens.Getter ((^.)) import Data.Lens.Setter ((%~), (.~), (?~)) -import Data.Log.Tag (tag) -import Data.Map (empty, filterKeys, lookup, toUnfoldable, union) as Map +import Data.Map (empty, lookup, union) as Map import Data.Maybe (Maybe(Nothing, Just), fromMaybe, isJust, maybe) import Data.Newtype (unwrap, wrap) import Data.Set (Set) import Data.Set as Set -import Data.Traversable (traverse, traverse_) -import Data.Tuple.Nested (type (/\), (/\)) -import Effect.Class (class MonadEffect, liftEffect) +import Data.Traversable (for, traverse) +import Data.Tuple.Nested ((/\)) +import Effect.Class (liftEffect) -- | Balances an unbalanced transaction using the specified balancer -- | constraints. @@ -178,8 +171,6 @@ balanceTxWithConstraints unbalancedTx constraintsBuilder = do availableUtxos <- liftQueryM $ filterLockedUtxos allUtxos - logTx "unbalancedCollTx" availableUtxos unbalancedCollTx - -- Balance and finalize the transaction: runBalancer allUtxos availableUtxos changeAddr certsFee (unbalancedTx # _transaction' .~ unbalancedCollTx) @@ -210,72 +201,149 @@ balanceTxWithConstraints unbalancedTx constraintsBuilder = do -- Balancing Algorithm -------------------------------------------------------------------------------- -type ChangeAddress = Address -type TransactionChangeOutput = TransactionOutput -type MinFee = BigInt -type Iteration = Int +type BalanceTxState = + { unbalancedTx :: UnattachedUnbalancedTx + , changeOutputs :: Array TransactionOutput + , leftoverUtxos :: UtxoMap + } runBalancer :: UtxoMap -> UtxoMap - -> ChangeAddress + -> Address -> Coin -> UnattachedUnbalancedTx -> BalanceTxM FinalizedTransaction runBalancer allUtxos utxos changeAddress certsFee = - mainLoop one zero <=< addLovelacesToTransactionOutputs + ( prebalanceTx + <<< { unbalancedTx: _, changeOutputs: mempty, leftoverUtxos: utxos } + ) + <=< addLovelacesToTransactionOutputs where - mainLoop - :: Iteration - -> MinFee - -> UnattachedUnbalancedTx - -> BalanceTxM FinalizedTransaction - mainLoop iteration minFee unbalancedTx = do + prebalanceTx :: BalanceTxState -> BalanceTxM FinalizedTransaction + prebalanceTx { unbalancedTx, changeOutputs, leftoverUtxos } = do + selectionState <- + performCoinSelection + (setTxChangeOutputs changeOutputs unbalancedTx ^. _body') let - unbalancedTxWithMinFee = - setTransactionMinFee minFee unbalancedTx - - unbalancedTxWithInputs <- - addTransactionInputs changeAddress utxos certsFee unbalancedTxWithMinFee + leftoverUtxos' :: UtxoMap + leftoverUtxos' = selectionState ^. _leftoverUtxos - traceMainLoop "added transaction inputs" "unbalancedTxWithInputs" - unbalancedTxWithInputs + selectedInputs' :: Set TransactionInput + selectedInputs' = selectedInputs selectionState - prebalancedTx <- - addTransactionChangeOutputs changeAddress utxos certsFee - unbalancedTxWithInputs + unbalancedTxWithInputs :: UnattachedUnbalancedTx + unbalancedTxWithInputs = + unbalancedTx # _body' <<< _inputs %~ Set.union selectedInputs' - traceMainLoop "added transaction change output" "prebalancedTx" - prebalancedTx + changeOutputs' <- + genTransactionChangeOutputs certsFee (unbalancedTxWithInputs ^. _body') - balancedTx /\ newMinFee <- evalExUnitsAndMinFee prebalancedTx allUtxos + requiredValue <- + except $ getRequiredValue certsFee utxos + (setTxChangeOutputs changeOutputs' unbalancedTxWithInputs ^. _body') - traceMainLoop "calculated ex units and min fee" "balancedTx" balancedTx - - case newMinFee == minFee of - true -> do - finalizedTransaction <- finalizeTransaction balancedTx allUtxos - - traceMainLoop "finalized transaction" "finalizedTransaction" - finalizedTransaction + let + updatedState :: BalanceTxState + updatedState = + { unbalancedTx: unbalancedTxWithInputs + , changeOutputs: changeOutputs' + , leftoverUtxos: leftoverUtxos' + } - pure finalizedTransaction + case requiredValue == mempty of + true -> + balanceChangeAndMinFee updatedState false -> - mainLoop (iteration + one) newMinFee unbalancedTxWithInputs + prebalanceTx updatedState where - traceMainLoop - :: forall (a :: Type). Show a => String -> String -> a -> BalanceTxM Unit - traceMainLoop meta message object = - let - tagMessage :: String - tagMessage = - "mainLoop (iteration " <> show iteration <> "): " <> meta - in - Logger.trace (tag tagMessage "^") $ message <> ": " <> show object - -setTransactionMinFee - :: MinFee -> UnattachedUnbalancedTx -> UnattachedUnbalancedTx -setTransactionMinFee minFee = _body' <<< _fee .~ Coin minFee + performCoinSelection :: TxBody -> BalanceTxM SelectionState + performCoinSelection txBody = + except (getRequiredValue certsFee utxos txBody) + >>= performMultiAssetSelection SelectionStrategyOptimal leftoverUtxos + + balanceChangeAndMinFee :: BalanceTxState -> BalanceTxM FinalizedTransaction + balanceChangeAndMinFee state@{ unbalancedTx, changeOutputs } = do + let + prebalancedTx :: PrebalancedTransaction + prebalancedTx = + wrap (setTxChangeOutputs changeOutputs unbalancedTx) + + balancedTx /\ minFee <- evalExUnitsAndMinFee prebalancedTx allUtxos + + case Coin minFee <= unbalancedTx ^. _body' <<< _fee of + true -> + finalizeTransaction balancedTx allUtxos + false -> do + let + unbalancedTxWithMinFee :: UnattachedUnbalancedTx + unbalancedTxWithMinFee = + unbalancedTx # _body' <<< _fee .~ Coin minFee + + changeOutputs' <- genTransactionChangeOutputs certsFee + (unbalancedTxWithMinFee ^. _body') + + requiredValue <- + except $ getRequiredValue certsFee utxos + (setTxChangeOutputs changeOutputs' unbalancedTxWithMinFee ^. _body') + + let + updatedState :: BalanceTxState + updatedState = state + { unbalancedTx = unbalancedTxWithMinFee + , changeOutputs = changeOutputs' + } + + case requiredValue == mempty of + true -> + balanceChangeAndMinFee updatedState + false -> + prebalanceTx updatedState + + -- | Generates change outputs to return all excess `Value` back to the owner's + -- | address. If necessary, adds lovelaces to the generated change outputs to + -- | cover the utxo min-ada-value requirement. + -- | + -- | If the `maxChangeOutputTokenQuantity` constraint is set, partitions the + -- | change `Value` into smaller `Value`s (where the Ada amount and the quantity + -- | of each token is equipartitioned across the resultant `Value`s; and no + -- | token quantity in any of the resultant `Value`s exceeds the given upper + -- | bound). Then builds `TransactionChangeOutput`s using those `Value`s. + genTransactionChangeOutputs + :: Coin -> TxBody -> BalanceTxM (Array TransactionOutput) + genTransactionChangeOutputs certsFee txBody = do + inputValue <- except $ getInputValue utxos txBody + let + changeValue :: Value + changeValue = + (inputValue <> mintValue txBody) `minus` + (outputValue txBody <> minFeeValue txBody <> coinToValue certsFee) + + mkChangeOutput :: Value -> TransactionOutput + mkChangeOutput amount = + TransactionOutput + { address: changeAddress + , amount + , datum: NoOutputDatum + , scriptRef: Nothing + } + + if changeValue == mempty then pure mempty + else + asksConstraints Constraints._maxChangeOutputTokenQuantity >>= case _ of + Nothing -> + Array.singleton <$> + addLovelacesToTransactionOutput (mkChangeOutput changeValue) + + Just maxChangeOutputTokenQuantity -> + let + values :: NonEmptyArray Value + values = + equipartitionValueWithTokenQuantityUpperBound changeValue + maxChangeOutputTokenQuantity + in + traverse (addLovelacesToTransactionOutput <<< mkChangeOutput) + (NEArray.toArray values) -- | For each transaction output, if necessary, adds some number of lovelaces -- | to cover the utxo min-ada-value requirement. @@ -290,8 +358,8 @@ addLovelacesToTransactionOutput :: TransactionOutput -> BalanceTxM TransactionOutput addLovelacesToTransactionOutput txOutput = do coinsPerUtxoUnit <- askCoinsPerUtxoUnit - txOutputMinAda <- ExceptT $ liftEffect $ - utxoMinAdaValue coinsPerUtxoUnit txOutput + txOutputMinAda <- + ExceptT $ liftEffect $ utxoMinAdaValue coinsPerUtxoUnit txOutput <#> note UtxoMinAdaValueCalculationFailed let txOutputRec = unwrap txOutput @@ -305,6 +373,34 @@ addLovelacesToTransactionOutput txOutput = do pure $ wrap txOutputRec { amount = mkValue newCoin (getNonAdaAsset txOutputValue) } +setTxChangeOutputs + :: Array TransactionOutput -> UnattachedUnbalancedTx -> UnattachedUnbalancedTx +setTxChangeOutputs outputs = _body' <<< _outputs %~ flip append outputs + +getRequiredValue :: Coin -> UtxoMap -> TxBody -> Either BalanceTxError Value +getRequiredValue certsFee utxos txBody = + getInputValue utxos txBody <#> \inputValue -> + (outputValue txBody <> minFeeValue txBody <> coinToValue certsFee) + `minus` (inputValue <> mintValue txBody) + +getAmount :: TransactionOutput -> Value +getAmount = _.amount <<< unwrap + +getInputValue :: UtxoMap -> TxBody -> Either BalanceTxError Value +getInputValue utxos txBody = + foldMap getAmount <$> + for (Array.fromFoldable $ txBody ^. _inputs) \oref -> + note (UtxoLookupFailedFor oref) (Map.lookup oref utxos) + +outputValue :: TxBody -> Value +outputValue txBody = foldMap getAmount (txBody ^. _outputs) + +minFeeValue :: TxBody -> Value +minFeeValue txBody = mkValue (txBody ^. _fee) mempty + +mintValue :: TxBody -> Value +mintValue txBody = maybe mempty (mkValue mempty <<< unwrap) (txBody ^. _mint) + -- | Accounts for: -- | -- | - stake registration deposit @@ -329,225 +425,3 @@ getStakingBalance tx depositLovelacesPerCert = in Coin fee --- | Generates change outputs to return all excess `Value` back to the owner's --- | address. If necessary, adds lovelaces to the generated change outputs to --- | cover the utxo min-ada-value requirement. --- | --- | If the `maxChangeOutputTokenQuantity` constraint is set, partitions the --- | change `Value` into smaller `Value`s (where the Ada amount and the quantity --- | of each token is equipartitioned across the resultant `Value`s; and no --- | token quantity in any of the resultant `Value`s exceeds the given upper --- | bound). Then builds `TransactionChangeOutput`s using those `Value`s. -genTransactionChangeOutputs - :: ChangeAddress - -> UtxoMap - -> Coin - -> UnattachedUnbalancedTx - -> BalanceTxM (Array TransactionChangeOutput) -genTransactionChangeOutputs changeAddress utxos certsFee tx = do - let - txBody :: TxBody - txBody = tx ^. _body' - - totalInputValue :: Value - totalInputValue = getInputValue utxos txBody - - changeValue :: Value - changeValue = posValue $ - (totalInputValue <> mintValue txBody) - `minus` - ( totalOutputValue txBody <> minFeeValue txBody <> coinToValue - certsFee - ) - - mkChangeOutput :: Value -> TransactionChangeOutput - mkChangeOutput amount = - TransactionOutput - { address: changeAddress - , amount - , datum: NoOutputDatum - , scriptRef: Nothing - } - - asksConstraints Constraints._maxChangeOutputTokenQuantity >>= case _ of - Nothing -> - Array.singleton <$> - addLovelacesToTransactionOutput (mkChangeOutput changeValue) - - Just maxChangeOutputTokenQuantity -> - let - values :: NonEmptyArray Value - values = - equipartitionValueWithTokenQuantityUpperBound changeValue - maxChangeOutputTokenQuantity - in - traverse (addLovelacesToTransactionOutput <<< mkChangeOutput) - (NEArray.toArray values) - -addTransactionChangeOutputs - :: ChangeAddress - -> UtxoMap - -> Coin - -> UnattachedUnbalancedTx - -> BalanceTxM PrebalancedTransaction -addTransactionChangeOutputs changeAddress utxos certsFee unbalancedTx = do - changeOutputs <- genTransactionChangeOutputs changeAddress utxos certsFee - unbalancedTx - pure $ PrebalancedTransaction $ - unbalancedTx # _body' <<< _outputs %~ flip append changeOutputs - --- | Selects a combination of unspent transaction outputs from the wallet's --- | utxo set so that the total input value is sufficient to cover all --- | transaction outputs, including the change that will be generated --- | when using that particular combination of inputs. --- | --- | Prerequisites: --- | 1. Must be called with a transaction with no change output. --- | 2. The `fee` field of a transaction body must be set. -addTransactionInputs - :: ChangeAddress - -> UtxoMap - -> Coin - -> UnattachedUnbalancedTx - -> BalanceTxM UnattachedUnbalancedTx -addTransactionInputs changeAddress utxos certsFee unbalancedTx = do - let - txBody :: TxBody - txBody = unbalancedTx ^. _body' - - txInputs :: Set TransactionInput - txInputs = txBody ^. _inputs - - nonMintedValue :: Value - nonMintedValue = totalOutputValue txBody `minus` mintValue txBody - - txChangeOutputs <- - genTransactionChangeOutputs changeAddress utxos certsFee unbalancedTx - - nonSpendableInputs <- asksConstraints Constraints._nonSpendableInputs - - let - changeValue :: Value - changeValue = foldMap getAmount txChangeOutputs - - requiredInputValue :: Value - requiredInputValue = nonMintedValue <> minFeeValue txBody <> changeValue <> - coinToValue certsFee - - spendableUtxos :: UtxoMap - spendableUtxos = - flip Map.filterKeys utxos \oref -> not $ - Set.member oref nonSpendableInputs - || Set.member oref (txBody ^. _referenceInputs) - - newTxInputs <- - except $ collectTransactionInputs txInputs spendableUtxos requiredInputValue - - case newTxInputs == txInputs of - true -> - pure unbalancedTx - false -> - addTransactionInputs changeAddress utxos certsFee - (unbalancedTx # _body' <<< _inputs %~ Set.union newTxInputs) - -collectTransactionInputs - :: Set TransactionInput - -> UtxoMap - -> Value - -> Either BalanceTxError (Set TransactionInput) -collectTransactionInputs originalTxIns utxos value = do - txInsValue <- updatedInputs >>= getTxInsValue utxos - updatedInputs' <- updatedInputs - case isSufficient updatedInputs' txInsValue of - true -> - pure $ Set.fromFoldable updatedInputs' - false -> - Left $ InsufficientTxInputs (Expected value) (Actual txInsValue) - where - updatedInputs :: Either BalanceTxError (Array TransactionInput) - updatedInputs = - foldl - ( \newTxIns txIn -> do - txIns <- newTxIns - txInsValue <- getTxInsValue utxos txIns - case Array.elem txIn txIns || isSufficient txIns txInsValue of - true -> newTxIns - false -> - Right $ Array.insert txIn txIns -- treat as a set. - ) - (Right $ Array.fromFoldable originalTxIns) - $ utxosToTransactionInput utxos - - isSufficient :: Array TransactionInput -> Value -> Boolean - isSufficient txIns' txInsValue = - not (Array.null txIns') && txInsValue `geq` value - - getTxInsValue - :: UtxoMap -> Array TransactionInput -> Either BalanceTxError Value - getTxInsValue utxos' = - map (Array.foldMap getAmount) <<< - traverse (\x -> note (UtxoLookupFailedFor x) $ Map.lookup x utxos') - - utxosToTransactionInput :: UtxoMap -> Array TransactionInput - utxosToTransactionInput = - Array.mapMaybe (hush <<< getPublicKeyTransactionInput) <<< Map.toUnfoldable - -getAmount :: TransactionOutput -> Value -getAmount = _.amount <<< unwrap - -totalOutputValue :: TxBody -> Value -totalOutputValue txBody = foldMap getAmount (txBody ^. _outputs) - -mintValue :: TxBody -> Value -mintValue txBody = maybe mempty (mkValue mempty <<< unwrap) (txBody ^. _mint) - -minFeeValue :: TxBody -> Value -minFeeValue txBody = mkValue (txBody ^. _fee) mempty - -posValue :: Value -> Value -posValue value = mkValue - (Coin $ max (valueToCoin' value) zero) - (posNonAdaAsset $ getNonAdaAsset value) - --- | Get `TransactionInput` such that it is associated to `PaymentCredentialKey` --- | and not `PaymentCredentialScript`, i.e. we want wallets only -getPublicKeyTransactionInput - :: TransactionInput /\ TransactionOutput - -> Either BalanceTxError TransactionInput -getPublicKeyTransactionInput (txOutRef /\ txOut) = - note CouldNotConvertScriptOutputToTxInput $ do - paymentCred <- unwrap txOut # (_.address >>> addressPaymentCred) - -- TEST ME: using StakeCredential to determine whether wallet or script - paymentCred # withStakeCredential - { onKeyHash: const $ pure txOutRef - , onScriptHash: const Nothing - } - -getInputValue :: UtxoMap -> TxBody -> Value -getInputValue utxos (TxBody txBody) = - Array.foldMap - getAmount - ( Array.mapMaybe (flip Map.lookup utxos) - <<< Array.fromFoldable - <<< _.inputs $ txBody - ) - --------------------------------------------------------------------------------- --- Logging Helpers --------------------------------------------------------------------------------- - --- Logging for Transaction type without returning Transaction -logTx - :: forall (m :: Type -> Type) - . MonadEffect m - => MonadLogger m - => String - -> UtxoMap - -> Transaction - -> m Unit -logTx msg utxos (Transaction { body: body'@(TxBody body) }) = - traverse_ (Logger.trace (tag msg mempty)) - [ "Input Value: " <> show (getInputValue utxos body') - , "Output Value: " <> show (Array.foldMap getAmount body.outputs) - , "Fees: " <> show body.fee - ] diff --git a/src/Internal/BalanceTx/CoinSelection.purs b/src/Internal/BalanceTx/CoinSelection.purs index 1670f0e904..91edde5e26 100644 --- a/src/Internal/BalanceTx/CoinSelection.purs +++ b/src/Internal/BalanceTx/CoinSelection.purs @@ -2,7 +2,9 @@ module Ctl.Internal.BalanceTx.CoinSelection ( MultiAssetSelection(MultiAssetSelection) , SelectionState(SelectionState) , SelectionStrategy(SelectionStrategyMinimal, SelectionStrategyOptimal) + , _leftoverUtxos , performMultiAssetSelection + , selectedInputs ) where import Prelude @@ -40,7 +42,7 @@ import Data.BigInt (abs, fromInt, toString) as BigInt import Data.Foldable (foldMap) as Foldable import Data.Function (applyFlipped) import Data.Lens (Lens') -import Data.Lens.Getter ((^.)) +import Data.Lens.Getter (view, (^.)) import Data.Lens.Iso.Newtype (_Newtype) import Data.Lens.Record (prop) import Data.Lens.Setter (over) @@ -69,11 +71,11 @@ performMultiAssetSelection :: forall (m :: Type -> Type) . MonadEffect m => MonadThrow BalanceTxError m - => MultiAssetSelection + => SelectionStrategy -> UtxoMap -> Value -> m SelectionState -performMultiAssetSelection (MultiAssetSelection strategy) utxos requiredValue = +performMultiAssetSelection strategy utxos requiredValue = case availableValue `Value.lt` requiredValue of true -> throwError balanceInsufficientError @@ -143,6 +145,9 @@ selectedAssetQuantity assetClass = selectedCoinQuantity :: SelectionState -> BigInt selectedCoinQuantity = Value.valueToCoin' <<< selectedBalance +selectedInputs :: SelectionState -> Set TransactionInput +selectedInputs = Set.fromFoldable <<< Map.keys <<< view _selectedUtxos + -- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L1254 type SelectionLens (m :: Type -> Type) = { assetDisplayString :: String From 8c40bf534f3f98e8dd4c64963acdd8aac509263a Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Wed, 5 Oct 2022 13:37:15 +0200 Subject: [PATCH 015/373] Check non-spendable inputs, Fix Plutip tests (cherry picked from commit ed51ed0eb42bed0d2956b144f497dd50a997bfda) --- src/Internal/BalanceTx/BalanceTx.purs | 49 +++++++++++++++++---------- 1 file changed, 32 insertions(+), 17 deletions(-) diff --git a/src/Internal/BalanceTx/BalanceTx.purs b/src/Internal/BalanceTx/BalanceTx.purs index ea11aa122e..d0a5471828 100644 --- a/src/Internal/BalanceTx/BalanceTx.purs +++ b/src/Internal/BalanceTx/BalanceTx.purs @@ -92,12 +92,13 @@ import Ctl.Internal.Cardano.Types.Transaction ) import Ctl.Internal.Cardano.Types.Value ( Coin(Coin) - , Value + , Value(Value) , coinToValue , equipartitionValueWithTokenQuantityUpperBound , getNonAdaAsset , minus , mkValue + , posNonAdaAsset , valueToCoin' ) import Ctl.Internal.QueryM (QueryM, getProtocolParameters) @@ -120,7 +121,7 @@ import Data.Either (Either, note) import Data.Foldable (fold, foldMap, foldr, sum) import Data.Lens.Getter ((^.)) import Data.Lens.Setter ((%~), (.~), (?~)) -import Data.Map (empty, lookup, union) as Map +import Data.Map (empty, filterKeys, lookup, union) as Map import Data.Maybe (Maybe(Nothing, Just), fromMaybe, isJust, maybe) import Data.Newtype (unwrap, wrap) import Data.Set (Set) @@ -201,12 +202,20 @@ balanceTxWithConstraints unbalancedTx constraintsBuilder = do -- Balancing Algorithm -------------------------------------------------------------------------------- -type BalanceTxState = +type BalancerState = { unbalancedTx :: UnattachedUnbalancedTx , changeOutputs :: Array TransactionOutput , leftoverUtxos :: UtxoMap } +mkBalancerState + :: UnattachedUnbalancedTx + -> Array TransactionOutput + -> UtxoMap + -> BalancerState +mkBalancerState unbalancedTx changeOutputs leftoverUtxos = + { unbalancedTx, changeOutputs, leftoverUtxos } + runBalancer :: UtxoMap -> UtxoMap @@ -214,13 +223,18 @@ runBalancer -> Coin -> UnattachedUnbalancedTx -> BalanceTxM FinalizedTransaction -runBalancer allUtxos utxos changeAddress certsFee = - ( prebalanceTx - <<< { unbalancedTx: _, changeOutputs: mempty, leftoverUtxos: utxos } - ) - <=< addLovelacesToTransactionOutputs +runBalancer allUtxos utxos changeAddress certsFee unbalancedTx' = do + spendableUtxos <- getSpendableUtxos + addLovelacesToTransactionOutputs unbalancedTx' + >>= ((\tx -> mkBalancerState tx mempty spendableUtxos) >>> prebalanceTx) where - prebalanceTx :: BalanceTxState -> BalanceTxM FinalizedTransaction + getSpendableUtxos :: BalanceTxM UtxoMap + getSpendableUtxos = + asksConstraints Constraints._nonSpendableInputs <#> + \nonSpendableInputs -> + Map.filterKeys (not <<< flip Set.member nonSpendableInputs) utxos + + prebalanceTx :: BalancerState -> BalanceTxM FinalizedTransaction prebalanceTx { unbalancedTx, changeOutputs, leftoverUtxos } = do selectionState <- performCoinSelection @@ -244,12 +258,9 @@ runBalancer allUtxos utxos changeAddress certsFee = (setTxChangeOutputs changeOutputs' unbalancedTxWithInputs ^. _body') let - updatedState :: BalanceTxState + updatedState :: BalancerState updatedState = - { unbalancedTx: unbalancedTxWithInputs - , changeOutputs: changeOutputs' - , leftoverUtxos: leftoverUtxos' - } + mkBalancerState unbalancedTxWithInputs changeOutputs' leftoverUtxos' case requiredValue == mempty of true -> @@ -262,7 +273,7 @@ runBalancer allUtxos utxos changeAddress certsFee = except (getRequiredValue certsFee utxos txBody) >>= performMultiAssetSelection SelectionStrategyOptimal leftoverUtxos - balanceChangeAndMinFee :: BalanceTxState -> BalanceTxM FinalizedTransaction + balanceChangeAndMinFee :: BalancerState -> BalanceTxM FinalizedTransaction balanceChangeAndMinFee state@{ unbalancedTx, changeOutputs } = do let prebalancedTx :: PrebalancedTransaction @@ -288,7 +299,7 @@ runBalancer allUtxos utxos changeAddress certsFee = (setTxChangeOutputs changeOutputs' unbalancedTxWithMinFee ^. _body') let - updatedState :: BalanceTxState + updatedState :: BalancerState updatedState = state { unbalancedTx = unbalancedTxWithMinFee , changeOutputs = changeOutputs' @@ -314,8 +325,12 @@ runBalancer allUtxos utxos changeAddress certsFee = genTransactionChangeOutputs certsFee txBody = do inputValue <- except $ getInputValue utxos txBody let + posValue :: Value -> Value + posValue (Value (Coin coin) nonAdaAsset) = + mkValue (Coin $ max coin zero) (posNonAdaAsset nonAdaAsset) + changeValue :: Value - changeValue = + changeValue = posValue $ (inputValue <> mintValue txBody) `minus` (outputValue txBody <> minFeeValue txBody <> coinToValue certsFee) From 73ada65ca127c995353a08cdad9092fa69b1993f Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Wed, 5 Oct 2022 17:03:34 +0200 Subject: [PATCH 016/373] BalanceTx: Improve progress logging, Minor refactorings (cherry picked from commit bd5c6aea502f04216aabc992f1d7536985551a16) --- src/Internal/BalanceTx/BalanceTx.purs | 145 ++++++++++++++++---------- 1 file changed, 92 insertions(+), 53 deletions(-) diff --git a/src/Internal/BalanceTx/BalanceTx.purs b/src/Internal/BalanceTx/BalanceTx.purs index d0a5471828..1c5e3c6f40 100644 --- a/src/Internal/BalanceTx/BalanceTx.purs +++ b/src/Internal/BalanceTx/BalanceTx.purs @@ -8,6 +8,7 @@ import Prelude import Control.Monad.Error.Class (liftMaybe) import Control.Monad.Except.Trans (ExceptT(ExceptT), except, runExceptT) +import Control.Monad.Logger.Class (trace) as Logger import Ctl.Internal.BalanceTx.CoinSelection ( SelectionState , SelectionStrategy(SelectionStrategyOptimal) @@ -121,6 +122,8 @@ import Data.Either (Either, note) import Data.Foldable (fold, foldMap, foldr, sum) import Data.Lens.Getter ((^.)) import Data.Lens.Setter ((%~), (.~), (?~)) +import Data.Log.Tag (TagSet) +import Data.Log.Tag (fromArray, tag) as TagSet import Data.Map (empty, filterKeys, lookup, union) as Map import Data.Maybe (Maybe(Nothing, Just), fromMaybe, isJust, maybe) import Data.Newtype (unwrap, wrap) @@ -208,14 +211,6 @@ type BalancerState = , leftoverUtxos :: UtxoMap } -mkBalancerState - :: UnattachedUnbalancedTx - -> Array TransactionOutput - -> UtxoMap - -> BalancerState -mkBalancerState unbalancedTx changeOutputs leftoverUtxos = - { unbalancedTx, changeOutputs, leftoverUtxos } - runBalancer :: UtxoMap -> UtxoMap @@ -234,8 +229,23 @@ runBalancer allUtxos utxos changeAddress certsFee unbalancedTx' = do \nonSpendableInputs -> Map.filterKeys (not <<< flip Set.member nonSpendableInputs) utxos + runNextBalancingStep + :: UnattachedUnbalancedTx -> UtxoMap -> BalanceTxM FinalizedTransaction + runNextBalancingStep unbalancedTx leftoverUtxos = do + changeOutputs <- + genTransactionChangeOutputs certsFee (unbalancedTx ^. _body') + + requiredValue <- + except $ getRequiredValue certsFee utxos + (setTxChangeOutputs changeOutputs unbalancedTx ^. _body') + + { unbalancedTx, changeOutputs, leftoverUtxos } # + if requiredValue == mempty then balanceChangeAndMinFee else prebalanceTx + prebalanceTx :: BalancerState -> BalanceTxM FinalizedTransaction - prebalanceTx { unbalancedTx, changeOutputs, leftoverUtxos } = do + prebalanceTx state@{ unbalancedTx, changeOutputs, leftoverUtxos } = do + logBalancerState "Pre-balancing (Stage 1)" utxos state + selectionState <- performCoinSelection (setTxChangeOutputs changeOutputs unbalancedTx ^. _body') @@ -250,23 +260,7 @@ runBalancer allUtxos utxos changeAddress certsFee unbalancedTx' = do unbalancedTxWithInputs = unbalancedTx # _body' <<< _inputs %~ Set.union selectedInputs' - changeOutputs' <- - genTransactionChangeOutputs certsFee (unbalancedTxWithInputs ^. _body') - - requiredValue <- - except $ getRequiredValue certsFee utxos - (setTxChangeOutputs changeOutputs' unbalancedTxWithInputs ^. _body') - - let - updatedState :: BalancerState - updatedState = - mkBalancerState unbalancedTxWithInputs changeOutputs' leftoverUtxos' - - case requiredValue == mempty of - true -> - balanceChangeAndMinFee updatedState - false -> - prebalanceTx updatedState + runNextBalancingStep unbalancedTxWithInputs leftoverUtxos' where performCoinSelection :: TxBody -> BalanceTxM SelectionState performCoinSelection txBody = @@ -274,42 +268,29 @@ runBalancer allUtxos utxos changeAddress certsFee unbalancedTx' = do >>= performMultiAssetSelection SelectionStrategyOptimal leftoverUtxos balanceChangeAndMinFee :: BalancerState -> BalanceTxM FinalizedTransaction - balanceChangeAndMinFee state@{ unbalancedTx, changeOutputs } = do + balanceChangeAndMinFee + state@{ unbalancedTx, changeOutputs, leftoverUtxos } = do + logBalancerState "Balancing change and fees (Stage 2)" utxos state let prebalancedTx :: PrebalancedTransaction - prebalancedTx = - wrap (setTxChangeOutputs changeOutputs unbalancedTx) + prebalancedTx = wrap $ setTxChangeOutputs changeOutputs unbalancedTx + + minFee :: BigInt + minFee = unwrap $ unbalancedTx ^. _body' <<< _fee - balancedTx /\ minFee <- evalExUnitsAndMinFee prebalancedTx allUtxos + balancedTx /\ newMinFee <- evalExUnitsAndMinFee prebalancedTx allUtxos - case Coin minFee <= unbalancedTx ^. _body' <<< _fee of + case newMinFee <= minFee of true -> finalizeTransaction balancedTx allUtxos - false -> do + <* logTransaction "Balanced transaction (Done)" utxos balancedTx + false -> let unbalancedTxWithMinFee :: UnattachedUnbalancedTx unbalancedTxWithMinFee = - unbalancedTx # _body' <<< _fee .~ Coin minFee - - changeOutputs' <- genTransactionChangeOutputs certsFee - (unbalancedTxWithMinFee ^. _body') - - requiredValue <- - except $ getRequiredValue certsFee utxos - (setTxChangeOutputs changeOutputs' unbalancedTxWithMinFee ^. _body') - - let - updatedState :: BalancerState - updatedState = state - { unbalancedTx = unbalancedTxWithMinFee - , changeOutputs = changeOutputs' - } - - case requiredValue == mempty of - true -> - balanceChangeAndMinFee updatedState - false -> - prebalanceTx updatedState + unbalancedTx # _body' <<< _fee .~ Coin newMinFee + in + runNextBalancingStep unbalancedTxWithMinFee leftoverUtxos -- | Generates change outputs to return all excess `Value` back to the owner's -- | address. If necessary, adds lovelaces to the generated change outputs to @@ -392,6 +373,10 @@ setTxChangeOutputs :: Array TransactionOutput -> UnattachedUnbalancedTx -> UnattachedUnbalancedTx setTxChangeOutputs outputs = _body' <<< _outputs %~ flip append outputs +-------------------------------------------------------------------------------- +-- Getters for various `Value`s +-------------------------------------------------------------------------------- + getRequiredValue :: Coin -> UtxoMap -> TxBody -> Either BalanceTxError Value getRequiredValue certsFee utxos txBody = getInputValue utxos txBody <#> \inputValue -> @@ -440,3 +425,57 @@ getStakingBalance tx depositLovelacesPerCert = in Coin fee +-------------------------------------------------------------------------------- +-- Helpers +-------------------------------------------------------------------------------- + +mkBalancerState + :: UnattachedUnbalancedTx + -> Array TransactionOutput + -> UtxoMap + -> BalancerState +mkBalancerState unbalancedTx changeOutputs leftoverUtxos = + { unbalancedTx, changeOutputs, leftoverUtxos } + +logBalancerState :: String -> UtxoMap -> BalancerState -> BalanceTxM Unit +logBalancerState message utxos { unbalancedTx, changeOutputs } = + logTransactionWithChange message utxos (Just changeOutputs) unbalancedTx + +logTransaction + :: String -> UtxoMap -> UnattachedUnbalancedTx -> BalanceTxM Unit +logTransaction message utxos = + logTransactionWithChange message utxos Nothing + +logTransactionWithChange + :: String + -> UtxoMap + -> Maybe (Array TransactionOutput) + -> UnattachedUnbalancedTx + -> BalanceTxM Unit +logTransactionWithChange message utxos mChangeOutputs unbalancedTx = + let + txBody :: TxBody + txBody = unbalancedTx ^. _body' + + tag :: forall (a :: Type). Show a => String -> a -> TagSet + tag title = TagSet.tag title <<< show + + outputValuesTagSet :: Maybe (Array TransactionOutput) -> Array TagSet + outputValuesTagSet Nothing = + [ "Output Value" `tag` outputValue txBody ] + outputValuesTagSet (Just changeOutputs) = + [ "Output Value without change" `tag` outputValue txBody + , "Change Value" `tag` foldMap getAmount changeOutputs + ] + + transactionInfo :: Value -> TagSet + transactionInfo inputValue = + TagSet.fromArray $ + [ "Input Value" `tag` inputValue + , "Mint Value" `tag` mintValue txBody + , "Fees" `tag` (txBody ^. _fee) + ] <> outputValuesTagSet mChangeOutputs + in + except (getInputValue utxos txBody) + >>= (flip Logger.trace (message <> ":") <<< transactionInfo) + From 5ea13a5cb904a7eb269b23db99aea35f3c2b715e Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Mon, 17 Oct 2022 18:37:45 +0200 Subject: [PATCH 017/373] Provide Partition instance for BigInt (cherry picked from commit e5318a17a60894dc9abb503ec665b98d29c378e7) --- src/Internal/Cardano/Types/Value.purs | 2 +- src/Internal/Partition.purs | 106 ++++++++++++++++++++++++++ test/Equipartition.purs | 2 +- 3 files changed, 108 insertions(+), 2 deletions(-) create mode 100644 src/Internal/Partition.purs diff --git a/src/Internal/Cardano/Types/Value.purs b/src/Internal/Cardano/Types/Value.purs index 70a5240426..36ecaa564c 100644 --- a/src/Internal/Cardano/Types/Value.purs +++ b/src/Internal/Cardano/Types/Value.purs @@ -67,11 +67,11 @@ import Aeson ) import Control.Alt ((<|>)) import Control.Alternative (guard) -import Ctl.Internal.Equipartition (class Equipartition, equipartition) import Ctl.Internal.FromData (class FromData) import Ctl.Internal.Helpers (encodeMap, showWithParens) import Ctl.Internal.Metadata.FromMetadata (class FromMetadata) import Ctl.Internal.Metadata.ToMetadata (class ToMetadata) +import Ctl.Internal.Partition (class Equipartition, equipartition) import Ctl.Internal.Serialization.Hash ( ScriptHash , scriptHashFromBytes diff --git a/src/Internal/Partition.purs b/src/Internal/Partition.purs new file mode 100644 index 0000000000..634bf2ce0c --- /dev/null +++ b/src/Internal/Partition.purs @@ -0,0 +1,106 @@ +module Ctl.Internal.Partition + ( class Equipartition + , class Partition + , equipartition + , partition + ) where + +import Prelude + +import Data.Array (replicate) +import Data.Array.NonEmpty (NonEmptyArray) +import Data.Array.NonEmpty + ( appendArray + , range + , replicate + , singleton + , sortBy + , zip + , zipWith + ) as NEArray +import Data.BigInt (BigInt) +import Data.BigInt (fromInt, toInt) as BigInt +import Data.Foldable (any, length, sum) +import Data.Function (on) +import Data.Maybe (Maybe(Just, Nothing), fromJust) +import Data.Newtype (class Newtype, unwrap) +import Data.Ordering (invert) as Ordering +import Data.Tuple (fst, snd) +import Data.Tuple.Nested (type (/\), (/\)) +import Partial.Unsafe (unsafePartial) + +class Partition (a :: Type) where + partition :: a -> NonEmptyArray a -> Maybe (NonEmptyArray a) + +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/14e0f1c2a457f85b8ea470661e7bec5e6bcf93e0/lib/numeric/src/Cardano/Numeric/Util.hs#L175 +instance Partition BigInt where + partition target weights + | any (\w -> w < zero) weights = Nothing + | sum weights == zero = Nothing + | otherwise = Just portionsRounded + where + portionsRounded :: NonEmptyArray BigInt + portionsRounded = portionsUnrounded + # map QuotRem + # NEArray.zip (NEArray.range 1 $ length portionsUnrounded) + # NEArray.sortBy ((\x -> Ordering.invert <<< compare x) `on` snd) + # round + # NEArray.sortBy (comparing fst) + # map snd + + round + :: NonEmptyArray (Int /\ QuotRem BigInt) + -> NonEmptyArray (Int /\ BigInt) + round portions = + NEArray.zipWith (+) + (map (fst <<< unwrap) <$> portions) + ( NEArray.replicate shortfall one + <> NEArray.replicate (length portions - shortfall) zero + ) + + shortfall :: Int + shortfall = toIntUnsafe $ target - sum (map fst portionsUnrounded) + + portionsUnrounded :: NonEmptyArray (BigInt /\ BigInt) + portionsUnrounded = weights <#> \w -> (target * w) `quotRem` sumWeights + + sumWeights :: BigInt + sumWeights = sum weights + +-- | Represents types whose values can be equally divided into several parts. +class Equipartition (a :: Type) where + equipartition :: a -> Int -> NonEmptyArray a + +-- | Computes the equipartition of a `BigInt` into `numParts` smaller `BigInt`s +-- | whose values differ by no more than 1. The resultant array is sorted in +-- | ascending order. +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/d4b30de073f2b5eddb25bf12c2453abb42e8b352/lib/numeric/src/Cardano/Numeric/Util.hs#L127 +instance Equipartition BigInt where + equipartition bi numParts + | numParts <= one = + NEArray.singleton bi + | otherwise = + let + quot /\ rem = toIntUnsafe <$> (bi `quotRem` BigInt.fromInt numParts) + in + NEArray.replicate (numParts - rem) quot + `NEArray.appendArray` replicate rem (quot + one) + +toIntUnsafe :: BigInt -> Int +toIntUnsafe = unsafePartial fromJust <<< BigInt.toInt + +quotRem :: forall (a :: Type). EuclideanRing a => a -> a -> (a /\ a) +quotRem a b = (a `div` b) /\ (a `mod` b) + +newtype QuotRem (a :: Type) = QuotRem (a /\ a) + +derive instance Newtype (QuotRem a) _ +derive newtype instance Eq a => Eq (QuotRem a) + +instance Ord a => Ord (QuotRem a) where + compare (QuotRem (quot0 /\ rem0)) (QuotRem (quot1 /\ rem1)) = + case compare rem0 rem1 of + EQ -> compare quot0 quot1 + ordering -> ordering diff --git a/test/Equipartition.purs b/test/Equipartition.purs index a844e8bbf3..6a2107fe76 100644 --- a/test/Equipartition.purs +++ b/test/Equipartition.purs @@ -2,7 +2,7 @@ module Test.Ctl.Equipartition (suite) where import Prelude -import Ctl.Internal.Equipartition (class Equipartition, equipartition) +import Ctl.Internal.Partition (class Equipartition, equipartition) import Ctl.Internal.Test.TestPlanM (TestPlanM) import Data.Array (elem) as Array import Data.Array.NonEmpty (NonEmptyArray) From e46d58cf4241328bb20a24ec24170cf4de5d5d76 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Tue, 18 Oct 2022 18:30:50 +0200 Subject: [PATCH 018/373] First draft of new change generation logic (cherry picked from commit 1b8bd8bbe804c3a6f9381d0efd01819fa927c772) --- src/Internal/BalanceTx/BalanceTx.purs | 220 +++++++++++++++++++------- src/Internal/Cardano/Types/Value.purs | 5 + src/Internal/Helpers.purs | 7 + src/Internal/Partition.purs | 9 +- 4 files changed, 182 insertions(+), 59 deletions(-) diff --git a/src/Internal/BalanceTx/BalanceTx.purs b/src/Internal/BalanceTx/BalanceTx.purs index 1c5e3c6f40..1be8d2b398 100644 --- a/src/Internal/BalanceTx/BalanceTx.purs +++ b/src/Internal/BalanceTx/BalanceTx.purs @@ -92,16 +92,25 @@ import Ctl.Internal.Cardano.Types.Transaction , _withdrawals ) import Ctl.Internal.Cardano.Types.Value - ( Coin(Coin) + ( AssetClass + , Coin(Coin) , Value(Value) , coinToValue , equipartitionValueWithTokenQuantityUpperBound , getNonAdaAsset + , lovelaceValueOf , minus , mkValue , posNonAdaAsset , valueToCoin' ) +import Ctl.Internal.Cardano.Types.Value + ( assetToValue + , getAssetQuantity + , valueAssets + ) as Value +import Ctl.Internal.Helpers ((??)) +import Ctl.Internal.Partition (equipartition, partition) import Ctl.Internal.QueryM (QueryM, getProtocolParameters) import Ctl.Internal.QueryM (getChangeAddress, getWalletAddresses) as QueryM import Ctl.Internal.QueryM.Utxos @@ -116,22 +125,35 @@ import Ctl.Internal.Types.Transaction (TransactionInput) import Ctl.Internal.Types.UnbalancedTransaction (_utxoIndex) import Data.Array as Array import Data.Array.NonEmpty (NonEmptyArray) -import Data.Array.NonEmpty (toArray) as NEArray +import Data.Array.NonEmpty + ( cons' + , fromArray + , replicate + , singleton + , sortWith + , toArray + , uncons + , zip + , zipWith + ) as NEArray import Data.BigInt (BigInt) import Data.Either (Either, note) -import Data.Foldable (fold, foldMap, foldr, sum) +import Data.Foldable (fold, foldMap, foldr, length, sum) +import Data.Function (on) import Data.Lens.Getter ((^.)) import Data.Lens.Setter ((%~), (.~), (?~)) import Data.Log.Tag (TagSet) import Data.Log.Tag (fromArray, tag) as TagSet import Data.Map (empty, filterKeys, lookup, union) as Map -import Data.Maybe (Maybe(Nothing, Just), fromMaybe, isJust, maybe) -import Data.Newtype (unwrap, wrap) +import Data.Maybe (Maybe(Nothing, Just), fromJust, fromMaybe, isJust, maybe) +import Data.Newtype (class Newtype, unwrap, wrap) import Data.Set (Set) import Data.Set as Set import Data.Traversable (for, traverse) -import Data.Tuple.Nested ((/\)) +import Data.Tuple (fst, snd) +import Data.Tuple.Nested (type (/\), (/\)) import Effect.Class (liftEffect) +import Partial.Unsafe (unsafePartial) -- | Balances an unbalanced transaction using the specified balancer -- | constraints. @@ -232,8 +254,9 @@ runBalancer allUtxos utxos changeAddress certsFee unbalancedTx' = do runNextBalancingStep :: UnattachedUnbalancedTx -> UtxoMap -> BalanceTxM FinalizedTransaction runNextBalancingStep unbalancedTx leftoverUtxos = do - changeOutputs <- - genTransactionChangeOutputs certsFee (unbalancedTx ^. _body') + let txBody = unbalancedTx ^. _body' + inputValue <- except $ getInputValue allUtxos txBody + changeOutputs <- makeChange changeAddress inputValue certsFee txBody requiredValue <- except $ getRequiredValue certsFee utxos @@ -292,55 +315,6 @@ runBalancer allUtxos utxos changeAddress certsFee unbalancedTx' = do in runNextBalancingStep unbalancedTxWithMinFee leftoverUtxos - -- | Generates change outputs to return all excess `Value` back to the owner's - -- | address. If necessary, adds lovelaces to the generated change outputs to - -- | cover the utxo min-ada-value requirement. - -- | - -- | If the `maxChangeOutputTokenQuantity` constraint is set, partitions the - -- | change `Value` into smaller `Value`s (where the Ada amount and the quantity - -- | of each token is equipartitioned across the resultant `Value`s; and no - -- | token quantity in any of the resultant `Value`s exceeds the given upper - -- | bound). Then builds `TransactionChangeOutput`s using those `Value`s. - genTransactionChangeOutputs - :: Coin -> TxBody -> BalanceTxM (Array TransactionOutput) - genTransactionChangeOutputs certsFee txBody = do - inputValue <- except $ getInputValue utxos txBody - let - posValue :: Value -> Value - posValue (Value (Coin coin) nonAdaAsset) = - mkValue (Coin $ max coin zero) (posNonAdaAsset nonAdaAsset) - - changeValue :: Value - changeValue = posValue $ - (inputValue <> mintValue txBody) `minus` - (outputValue txBody <> minFeeValue txBody <> coinToValue certsFee) - - mkChangeOutput :: Value -> TransactionOutput - mkChangeOutput amount = - TransactionOutput - { address: changeAddress - , amount - , datum: NoOutputDatum - , scriptRef: Nothing - } - - if changeValue == mempty then pure mempty - else - asksConstraints Constraints._maxChangeOutputTokenQuantity >>= case _ of - Nothing -> - Array.singleton <$> - addLovelacesToTransactionOutput (mkChangeOutput changeValue) - - Just maxChangeOutputTokenQuantity -> - let - values :: NonEmptyArray Value - values = - equipartitionValueWithTokenQuantityUpperBound changeValue - maxChangeOutputTokenQuantity - in - traverse (addLovelacesToTransactionOutput <<< mkChangeOutput) - (NEArray.toArray values) - -- | For each transaction output, if necessary, adds some number of lovelaces -- | to cover the utxo min-ada-value requirement. addLovelacesToTransactionOutputs @@ -373,6 +347,138 @@ setTxChangeOutputs :: Array TransactionOutput -> UnattachedUnbalancedTx -> UnattachedUnbalancedTx setTxChangeOutputs outputs = _body' <<< _outputs %~ flip append outputs +-------------------------------------------------------------------------------- +-- Making change +-------------------------------------------------------------------------------- + +makeChange + :: Address -> Value -> Coin -> TxBody -> BalanceTxM (Array TransactionOutput) +makeChange changeAddress inputValue certsFee txBody = + map (mkChangeOutput changeAddress) <$> + assignCoinsToChangeValues changeAddress excessCoin + changeValueOutputCoinPairs + where + changeValueOutputCoinPairs :: NonEmptyArray (Value /\ BigInt) + changeValueOutputCoinPairs = outputCoins + # NEArray.zip changeForAssets + # NEArray.sortWith (AssetCount <<< fst) + + changeForAssets :: NonEmptyArray Value + changeForAssets = foldr + (NEArray.zipWith (<>) <<< makeChangeForAsset txOutputs) + (NEArray.replicate (length txOutputs) mempty) + excessAssets + + outputCoins :: NonEmptyArray BigInt + outputCoins = + NEArray.fromArray (valueToCoin' <<< _.amount <<< unwrap <$> txOutputs) + ?? NEArray.singleton zero + + txOutputs :: Array TransactionOutput + txOutputs = txBody ^. _outputs + + excessAssets :: Array (AssetClass /\ BigInt) + excessAssets = Value.valueAssets excessValue + + excessCoin :: BigInt + excessCoin = valueToCoin' excessValue + + excessValue :: Value + excessValue = posValue $ + (inputValue <> mintValue txBody) `minus` + (outputValue txBody <> minFeeValue txBody <> coinToValue certsFee) + + posValue :: Value -> Value + posValue (Value (Coin coin) nonAdaAsset) = + mkValue (Coin $ max coin zero) (posNonAdaAsset nonAdaAsset) + +makeChangeForAsset + :: Array TransactionOutput -> (AssetClass /\ BigInt) -> NonEmptyArray Value +makeChangeForAsset txOutputs (assetClass /\ excess) = + Value.assetToValue assetClass <$> + partition excess weights ?? equipartition excess (length weights) + where + weights :: NonEmptyArray BigInt + weights = NEArray.fromArray assetQuantities ?? NEArray.singleton one + + assetQuantities :: Array BigInt + assetQuantities = + txOutputs <#> Value.getAssetQuantity assetClass <<< _.amount <<< unwrap + +makeChangeForCoin :: NonEmptyArray BigInt -> BigInt -> NonEmptyArray Value +makeChangeForCoin weights excess = + (map lovelaceValueOf <$> partition excess weights) + ?? NEArray.singleton (lovelaceValueOf excess) + +assignCoinsToChangeValues + :: Address + -> BigInt + -> NonEmptyArray (Value /\ BigInt) + -> BalanceTxM (Array Value) +assignCoinsToChangeValues changeAddress adaAvailable pairsAtStart = + flip worker pairsAtStart =<< adaRequiredAtStart + where + worker + :: BigInt + -> NonEmptyArray (Value /\ BigInt) + -> BalanceTxM (Array Value) + worker adaRequired = NEArray.uncons >>> case _ of + { head: pair, tail: [] } | noTokens pair && adaAvailable < adaRequired -> + pure mempty + + { head: pair, tail: pairs } | noTokens pair && adaAvailable < adaRequired -> + minCoinFor (fst pair) >>= \minCoin -> + worker (adaRequired - minCoin) (fromArrayUnsafe pairs) + + { head, tail } -> do + let + pairs :: NonEmptyArray (Value /\ BigInt) + pairs = NEArray.cons' head tail + + adaRemaining :: BigInt + adaRemaining = adaAvailable - adaRequired + + changeValuesForOutputCoins :: NonEmptyArray Value + changeValuesForOutputCoins = + makeChangeForCoin (snd <$> pairs) adaRemaining + + changeValuesWithMinCoins <- traverse (assignMinimumCoin <<< fst) pairs + pure $ NEArray.toArray $ + NEArray.zipWith (<>) changeValuesWithMinCoins changeValuesForOutputCoins + where + assignMinimumCoin :: Value -> BalanceTxM Value + assignMinimumCoin value@(Value _ assets) = + flip mkValue assets <<< wrap <$> minCoinFor value + + fromArrayUnsafe :: forall (a :: Type). Array a -> NonEmptyArray a + fromArrayUnsafe = unsafePartial fromJust <<< NEArray.fromArray + + noTokens :: Value /\ BigInt -> Boolean + noTokens = Array.null <<< Value.valueAssets <<< fst + + adaRequiredAtStart :: BalanceTxM BigInt + adaRequiredAtStart = + foldr (+) zero <$> traverse (minCoinFor <<< fst) pairsAtStart + + minCoinFor :: Value -> BalanceTxM BigInt + minCoinFor value = do + let txOutput = mkChangeOutput changeAddress value + coinsPerUtxoUnit <- askCoinsPerUtxoUnit + ExceptT $ liftEffect $ utxoMinAdaValue coinsPerUtxoUnit txOutput + <#> note UtxoMinAdaValueCalculationFailed + +newtype AssetCount = AssetCount Value + +derive instance Newtype AssetCount _ +derive newtype instance Eq AssetCount + +instance Ord AssetCount where + compare = compare `on` (Array.length <<< Value.valueAssets <<< unwrap) + +mkChangeOutput :: Address -> Value -> TransactionOutput +mkChangeOutput changeAddress amount = wrap + { address: changeAddress, amount, datum: NoOutputDatum, scriptRef: Nothing } + -------------------------------------------------------------------------------- -- Getters for various `Value`s -------------------------------------------------------------------------------- diff --git a/src/Internal/Cardano/Types/Value.purs b/src/Internal/Cardano/Types/Value.purs index 36ecaa564c..c9d483c9b1 100644 --- a/src/Internal/Cardano/Types/Value.purs +++ b/src/Internal/Cardano/Types/Value.purs @@ -6,6 +6,7 @@ module Ctl.Internal.Cardano.Types.Value , Value(Value) , class Negate , class Split + , assetToValue , coinToValue , currencyMPSHash , eq @@ -509,6 +510,10 @@ derive instance Ord AssetClass instance Show AssetClass where show = genericShow +assetToValue :: AssetClass -> BigInt -> Value +assetToValue (AssetClass cs tn) quantity = + mkValue mempty (mkSingletonNonAdaAsset cs tn quantity) + getAssetQuantity :: AssetClass -> Value -> BigInt getAssetQuantity (AssetClass cs tn) value = valueOf value cs tn diff --git a/src/Internal/Helpers.purs b/src/Internal/Helpers.purs index 253d4f2d06..e13436e3a7 100644 --- a/src/Internal/Helpers.purs +++ b/src/Internal/Helpers.purs @@ -3,6 +3,7 @@ module Ctl.Internal.Helpers , (<<>>) , (<\>) , (<>) + , (??) , appendFirstMaybe , appendLastMaybe , appendMap @@ -12,6 +13,7 @@ module Ctl.Internal.Helpers , filterMapM , filterMapWithKeyM , fromJustEff + , fromMaybeFlipped , fromRightEff , liftEither , liftM @@ -262,3 +264,8 @@ concatPaths a b = right = fromMaybe b (stripPrefix (Pattern "/") b) infixr 5 concatPaths as <> -- is taken + +fromMaybeFlipped :: forall (a :: Type). Maybe a -> a -> a +fromMaybeFlipped = flip fromMaybe + +infixl 5 fromMaybeFlipped as ?? diff --git a/src/Internal/Partition.purs b/src/Internal/Partition.purs index 634bf2ce0c..3f1eeb567b 100644 --- a/src/Internal/Partition.purs +++ b/src/Internal/Partition.purs @@ -11,6 +11,7 @@ import Data.Array (replicate) import Data.Array.NonEmpty (NonEmptyArray) import Data.Array.NonEmpty ( appendArray + , fromArray , range , replicate , singleton @@ -55,8 +56,9 @@ instance Partition BigInt where round portions = NEArray.zipWith (+) (map (fst <<< unwrap) <$> portions) - ( NEArray.replicate shortfall one - <> NEArray.replicate (length portions - shortfall) zero + ( fromArrayUnsafe $ + replicate shortfall one + <> replicate (length portions - shortfall) zero ) shortfall :: Int @@ -91,6 +93,9 @@ instance Equipartition BigInt where toIntUnsafe :: BigInt -> Int toIntUnsafe = unsafePartial fromJust <<< BigInt.toInt +fromArrayUnsafe :: forall (a :: Type). Array a -> NonEmptyArray a +fromArrayUnsafe = unsafePartial fromJust <<< NEArray.fromArray + quotRem :: forall (a :: Type). EuclideanRing a => a -> a -> (a /\ a) quotRem a b = (a `div` b) /\ (a `mod` b) From d88d3ea1eda7060c33cb489c388a31e799ed06ba Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Wed, 19 Oct 2022 14:47:10 +0200 Subject: [PATCH 019/373] Split oversized change outputs, Fix Plutip tests (cherry picked from commit fc635d70b4d748405fe345affce2b3cbb822e259) --- src/Internal/BalanceTx/BalanceTx.purs | 29 ++++++++++++++++++++++----- src/Internal/Cardano/Types/Value.purs | 4 ++-- 2 files changed, 26 insertions(+), 7 deletions(-) diff --git a/src/Internal/BalanceTx/BalanceTx.purs b/src/Internal/BalanceTx/BalanceTx.purs index 1be8d2b398..36e2a36685 100644 --- a/src/Internal/BalanceTx/BalanceTx.purs +++ b/src/Internal/BalanceTx/BalanceTx.purs @@ -355,14 +355,33 @@ makeChange :: Address -> Value -> Coin -> TxBody -> BalanceTxM (Array TransactionOutput) makeChange changeAddress inputValue certsFee txBody = map (mkChangeOutput changeAddress) <$> - assignCoinsToChangeValues changeAddress excessCoin - changeValueOutputCoinPairs + ( assignCoinsToChangeValues changeAddress excessCoin + =<< splitOversizedValues changeValueOutputCoinPairs + ) where changeValueOutputCoinPairs :: NonEmptyArray (Value /\ BigInt) changeValueOutputCoinPairs = outputCoins # NEArray.zip changeForAssets # NEArray.sortWith (AssetCount <<< fst) + splitOversizedValues + :: NonEmptyArray (Value /\ BigInt) + -> BalanceTxM (NonEmptyArray (Value /\ BigInt)) + splitOversizedValues pairs = + asksConstraints Constraints._maxChangeOutputTokenQuantity <#> case _ of + Nothing -> pairs + Just maxTokenQuantity -> + unbundle <$> + ( equipartitionValueWithTokenQuantityUpperBound maxTokenQuantity + =<< map bundle pairs + ) + where + bundle :: Value /\ BigInt -> Value + bundle (Value _ assets /\ coin) = mkValue (wrap coin) assets + + unbundle :: Value -> Value /\ BigInt + unbundle (Value coin assets) = mkValue mempty assets /\ unwrap coin + changeForAssets :: NonEmptyArray Value changeForAssets = foldr (NEArray.zipWith (<>) <<< makeChangeForAsset txOutputs) @@ -407,8 +426,8 @@ makeChangeForAsset txOutputs (assetClass /\ excess) = makeChangeForCoin :: NonEmptyArray BigInt -> BigInt -> NonEmptyArray Value makeChangeForCoin weights excess = - (map lovelaceValueOf <$> partition excess weights) - ?? NEArray.singleton (lovelaceValueOf excess) + lovelaceValueOf <$> + partition excess weights ?? equipartition excess (length weights) assignCoinsToChangeValues :: Address @@ -436,7 +455,7 @@ assignCoinsToChangeValues changeAddress adaAvailable pairsAtStart = pairs = NEArray.cons' head tail adaRemaining :: BigInt - adaRemaining = adaAvailable - adaRequired + adaRemaining = max zero (adaAvailable - adaRequired) changeValuesForOutputCoins :: NonEmptyArray Value changeValuesForOutputCoins = diff --git a/src/Internal/Cardano/Types/Value.purs b/src/Internal/Cardano/Types/Value.purs index c9d483c9b1..c6244af595 100644 --- a/src/Internal/Cardano/Types/Value.purs +++ b/src/Internal/Cardano/Types/Value.purs @@ -460,8 +460,8 @@ instance Equipartition Value where -- | Taken from cardano-wallet: -- | https://github.com/input-output-hk/cardano-wallet/blob/d4b30de073f2b5eddb25bf12c2453abb42e8b352/lib/wallet/src/Cardano/Wallet/Primitive/Types/TokenBundle.hs#L381 equipartitionValueWithTokenQuantityUpperBound - :: Value -> BigInt -> NonEmptyArray Value -equipartitionValueWithTokenQuantityUpperBound value maxTokenQuantity = + :: BigInt -> Value -> NonEmptyArray Value +equipartitionValueWithTokenQuantityUpperBound maxTokenQuantity value = let Value coin nonAdaAssets = value ms /\ numParts = From 01078e77a5ef0a439399b6ff248ebd1c30205df3 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Wed, 19 Oct 2022 17:23:56 +0200 Subject: [PATCH 020/373] Add unit tests for partitionBigInt (cherry picked from commit 7075559e159412cb52dd97f9782191877702d9f9) --- test/Partition.purs | 186 ++++++++++++++++++++++++++++++++++++++++++++ test/Unit.purs | 4 +- 2 files changed, 188 insertions(+), 2 deletions(-) create mode 100644 test/Partition.purs diff --git a/test/Partition.purs b/test/Partition.purs new file mode 100644 index 0000000000..77b86eb1ab --- /dev/null +++ b/test/Partition.purs @@ -0,0 +1,186 @@ +module Test.Ctl.Partition (suite) where + +import Prelude + +import Ctl.Internal.Partition + ( class Equipartition + , class Partition + , equipartition + , partition + ) +import Ctl.Internal.Test.TestPlanM (TestPlanM) +import Data.Array (elem) as Array +import Data.Array.NonEmpty (NonEmptyArray, (:)) +import Data.Array.NonEmpty (length, singleton, sort, zip) as NEArray +import Data.BigInt (BigInt) +import Data.BigInt (fromInt) as BigInt +import Data.Foldable (all, foldMap, sum) +import Data.Maybe (Maybe(Just, Nothing), isNothing) +import Data.Newtype (class Newtype, unwrap) +import Data.Ord.Max (Max(Max)) +import Data.Ord.Min (Min(Min)) +import Data.Tuple.Nested ((/\)) +import Effect.Aff (Aff) +import Mote (group, test) +import Test.QuickCheck.Arbitrary (class Arbitrary, arbitrary) +import Test.QuickCheck.Gen (suchThat) +import Test.Spec.QuickCheck (quickCheck) + +suite :: TestPlanM (Aff Unit) Unit +suite = + group "Partition" do + group "partitionBigInt" do + test "prop_partitionBigInt_pos_weights" + (quickCheck prop_partitionBigInt_pos_weights) + + test "prop_partitionBigInt_sum_weights" + (quickCheck prop_partitionBigInt_sum_weights) + + test "prop_partitionBigInt_length" + (quickCheck prop_partitionBigInt_length) + + test "prop_partitionBigInt_sum" + (quickCheck prop_partitionBigInt_sum) + + test "prop_partitionBigInt_fair" + (quickCheck prop_partitionBigInt_fair) + + group "equipartitionBigInt" do + test "prop_equipartitionBigInt_trivial" + (quickCheck prop_equipartitionBigInt_trivial) + + test "prop_equipartitionBigInt_length" + (quickCheck prop_equipartitionBigInt_length) + + test "prop_equipartitionBigInt_sum" + (quickCheck prop_equipartitionBigInt_sum) + + test "prop_equipartitionBigInt_order" + (quickCheck prop_equipartitionBigInt_order) + + test "prop_equipartitionBigInt_fair" + (quickCheck prop_equipartitionBigInt_fair) + +prop_partitionBigInt_pos_weights + :: BigInt' -> BigIntNeg -> NonEmptyArray BigIntGeqOne -> Boolean +prop_partitionBigInt_pos_weights bi negWeight weights = + isNothing $ partition bi (unwrap negWeight : map unwrap weights) + +prop_partitionBigInt_sum_weights :: BigInt' -> NonEmptyArray BigInt' -> Boolean +prop_partitionBigInt_sum_weights bi = + isNothing <<< partition bi <<< map (const (zero :: BigInt')) + +-- Taken from cardano-wallet: +-- https://github.com/input-output-hk/cardano-wallet/blob/cacdb55a5de6857ef666c4a6eac662de6952b5a6/lib/numeric/test/unit/Cardano/Numeric/UtilSpec.hs#L142 +prop_partitionBigInt_length :: BigInt' -> NonEmptyArray BigIntGeqOne -> Boolean +prop_partitionBigInt_length bi weights = + map NEArray.length (partition bi $ map unwrap weights) + == Just (NEArray.length weights) + +-- Taken from cardano-wallet: +-- https://github.com/input-output-hk/cardano-wallet/blob/cacdb55a5de6857ef666c4a6eac662de6952b5a6/lib/numeric/test/unit/Cardano/Numeric/UtilSpec.hs#L151 +prop_partitionBigInt_sum :: BigInt' -> NonEmptyArray BigIntGeqOne -> Boolean +prop_partitionBigInt_sum bi weights = + map sum (partition bi $ map unwrap weights) == Just bi + +-- Taken from cardano-wallet: +-- https://github.com/input-output-hk/cardano-wallet/blob/cacdb55a5de6857ef666c4a6eac662de6952b5a6/lib/numeric/test/unit/Cardano/Numeric/UtilSpec.hs#L162 +prop_partitionBigInt_fair :: BigInt' -> NonEmptyArray BigIntGeqOne -> Boolean +prop_partitionBigInt_fair bi weights' = + case partition bi weights of + Nothing -> false + Just portions -> + all (\(x /\ a) -> x >= a) (NEArray.zip portions portionsLowerBounds) + && all (\(x /\ b) -> x <= b) (NEArray.zip portions portionsUpperBounds) + where + portionsUpperBounds :: NonEmptyArray BigInt' + portionsUpperBounds = add one <$> portionsLowerBounds + + portionsLowerBounds :: NonEmptyArray BigInt' + portionsLowerBounds = weights <#> \w -> (bi * w) `div` sum weights + + weights :: NonEmptyArray BigInt' + weights = unwrap <$> weights' + +prop_equipartitionBigInt_trivial :: BigInt' -> IntLeqOne -> Boolean +prop_equipartitionBigInt_trivial bi (IntLeqOne numParts) = + equipartition bi numParts == NEArray.singleton bi + +-- Taken from cardano-wallet: +-- https://github.com/input-output-hk/cardano-wallet/blob/7b0192110fe226f992bca6198b8ee83fa4a37f46/lib/numeric/test/unit/Cardano/Numeric/UtilSpec.hs#L124 +prop_equipartitionBigInt_length :: BigInt' -> IntGeqOne -> Boolean +prop_equipartitionBigInt_length bi (IntGeqOne numParts) = + NEArray.length (equipartition bi numParts) == numParts + +-- Taken from cardano-wallet: +-- https://github.com/input-output-hk/cardano-wallet/blob/7b0192110fe226f992bca6198b8ee83fa4a37f46/lib/numeric/test/unit/Cardano/Numeric/UtilSpec.hs#L134 +prop_equipartitionBigInt_sum :: BigInt' -> Int -> Boolean +prop_equipartitionBigInt_sum bi numParts = sum (equipartition bi numParts) == bi + +-- Taken from cardano-wallet: +-- https://github.com/input-output-hk/cardano-wallet/blob/7b0192110fe226f992bca6198b8ee83fa4a37f46/lib/numeric/test/unit/Cardano/Numeric/UtilSpec.hs#L128 +prop_equipartitionBigInt_order :: BigInt' -> Int -> Boolean +prop_equipartitionBigInt_order bi numParts = + let + results :: NonEmptyArray BigInt' + results = equipartition bi numParts + in + NEArray.sort results == results + +-- Taken from cardano-wallet: +-- https://github.com/input-output-hk/cardano-wallet/blob/7b0192110fe226f992bca6198b8ee83fa4a37f46/lib/numeric/test/unit/Cardano/Numeric/UtilSpec.hs#L112 +prop_equipartitionBigInt_fair :: BigInt' -> Int -> Boolean +prop_equipartitionBigInt_fair bi numParts = + let + results :: NonEmptyArray BigInt' + results = equipartition bi numParts + in + flip Array.elem [ zero, one ] $ + unwrap (foldMap Max results) - unwrap (foldMap Min results) + +newtype BigInt' = BigInt' BigInt + +derive newtype instance Eq BigInt' +derive newtype instance Ord BigInt' +derive newtype instance Semiring BigInt' +derive newtype instance Ring BigInt' +derive newtype instance CommutativeRing BigInt' +derive newtype instance EuclideanRing BigInt' +derive newtype instance Equipartition BigInt' +derive newtype instance Partition BigInt' + +instance Bounded BigInt' where + top = BigInt' (BigInt.fromInt top) + bottom = BigInt' (BigInt.fromInt bottom) + +instance Arbitrary BigInt' where + arbitrary = BigInt' <<< BigInt.fromInt <$> arbitrary + +newtype BigIntNeg = BigIntNeg BigInt' + +derive instance Newtype BigIntNeg _ + +instance Arbitrary BigIntNeg where + arbitrary = BigIntNeg <$> suchThat arbitrary (_ < zero) + +newtype BigIntGeqOne = BigIntGeqOne BigInt' + +derive instance Newtype BigIntGeqOne _ + +instance Arbitrary BigIntGeqOne where + arbitrary = BigIntGeqOne <$> suchThat arbitrary (_ >= one) + +newtype IntLeqOne = IntLeqOne Int + +derive instance Newtype IntLeqOne _ + +instance Arbitrary IntLeqOne where + arbitrary = IntLeqOne <$> suchThat arbitrary (_ <= one) + +newtype IntGeqOne = IntGeqOne Int + +derive instance Newtype IntGeqOne _ + +instance Arbitrary IntGeqOne where + arbitrary = IntGeqOne <$> suchThat arbitrary (_ >= one) + diff --git a/test/Unit.purs b/test/Unit.purs index c714aa9e45..8ac64084a3 100644 --- a/test/Unit.purs +++ b/test/Unit.purs @@ -13,7 +13,6 @@ import Test.Ctl.Data as Data import Test.Ctl.Data.Interval as Ctl.Data.Interval import Test.Ctl.Deserialization as Deserialization import Test.Ctl.E2E.Route as E2E.Route -import Test.Ctl.Equipartition as Equipartition import Test.Ctl.Hashing as Hashing import Test.Ctl.Internal.Plutus.Conversion.Address as Plutus.Conversion.Address import Test.Ctl.Internal.Plutus.Conversion.Value as Plutus.Conversion.Value @@ -26,6 +25,7 @@ import Test.Ctl.Ogmios.Aeson as Ogmios.Aeson import Test.Ctl.Ogmios.EvaluateTx as Ogmios.EvaluateTx import Test.Ctl.OgmiosDatumCache as OgmiosDatumCache import Test.Ctl.Parser as Parser +import Test.Ctl.Partition as Partition import Test.Ctl.ProtocolParams as ProtocolParams import Test.Ctl.Serialization as Serialization import Test.Ctl.Serialization.Address as Serialization.Address @@ -54,9 +54,9 @@ testPlan = do Cip30SignData.suite Data.suite Deserialization.suite - Equipartition.suite Hashing.suite Parser.suite + Partition.suite Plutus.Conversion.Address.suite Plutus.Conversion.Value.suite Plutus.Time.suite From 4de704334db0faa5b74ede0b1212a63ba84c00b6 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Wed, 19 Oct 2022 19:24:49 +0200 Subject: [PATCH 021/373] Provide Arbitrary instances for Cardano.Value and related types (cherry picked from commit abee84b2541158932e654776248fb71962723669) --- src/Internal/Cardano/Types/Value.purs | 26 ++++++++++++++++++++++++++ src/Internal/Types/TokenName.purs | 8 +++++++- 2 files changed, 33 insertions(+), 1 deletion(-) diff --git a/src/Internal/Cardano/Types/Value.purs b/src/Internal/Cardano/Types/Value.purs index c6244af595..9745dd1eb1 100644 --- a/src/Internal/Cardano/Types/Value.purs +++ b/src/Internal/Cardano/Types/Value.purs @@ -81,6 +81,7 @@ import Ctl.Internal.Serialization.Hash import Ctl.Internal.ToData (class ToData) import Ctl.Internal.Types.ByteArray ( ByteArray + , byteArrayFromIntArrayUnsafe , byteArrayToHex , byteLength , hexToByteArray @@ -111,6 +112,7 @@ import Data.List (List(Nil), all, (:)) import Data.List (nubByEq) as List import Data.Map (Map, keys, lookup, toUnfoldable, unions, values) import Data.Map as Map +import Data.Map.Gen (genMap) import Data.Maybe (Maybe(Just, Nothing), fromJust) import Data.Newtype (class Newtype, unwrap, wrap) import Data.Set (Set) @@ -120,6 +122,8 @@ import Data.Traversable (class Traversable, traverse) import Data.Tuple (fst) import Data.Tuple.Nested (type (/\), (/\)) import Partial.Unsafe (unsafePartial) +import Test.QuickCheck.Arbitrary (class Arbitrary, arbitrary) +import Test.QuickCheck.Gen (Gen, chooseInt, suchThat, vectorOf) -- `Negate` and `Split` seem a bit too contrived, and their purpose is to -- combine similar behaviour without satisfying any useful laws. I wonder @@ -157,6 +161,9 @@ derive newtype instance DecodeAeson Coin derive newtype instance EncodeAeson Coin derive newtype instance Equipartition Coin +instance Arbitrary Coin where + arbitrary = Coin <<< fromInt <$> suchThat arbitrary (_ >= zero) + instance Show Coin where show (Coin c) = showWithParens "Coin" c @@ -220,6 +227,11 @@ derive newtype instance Ord CurrencySymbol derive newtype instance ToData CurrencySymbol derive newtype instance ToMetadata CurrencySymbol +instance Arbitrary CurrencySymbol where + arbitrary = + unsafePartial fromJust <<< mkCurrencySymbol <<< byteArrayFromIntArrayUnsafe + <$> vectorOf 28 (chooseInt 0 255) + instance Show CurrencySymbol where show (CurrencySymbol cs) = "(CurrencySymbol " <> show cs <> ")" @@ -263,6 +275,17 @@ newtype NonAdaAsset = NonAdaAsset (Map CurrencySymbol (Map TokenName BigInt)) derive newtype instance Eq NonAdaAsset +instance Arbitrary NonAdaAsset where + arbitrary = + NonAdaAsset <$> + genMap + (arbitrary :: Gen CurrencySymbol) + ( flip suchThat (not Map.isEmpty) $ + genMap + (arbitrary :: Gen TokenName) + (fromInt <$> suchThat arbitrary (_ >= one) :: Gen BigInt) + ) + instance Show NonAdaAsset where show (NonAdaAsset nonAdaAsset) = "(NonAdaAsset " <> show nonAdaAsset <> ")" @@ -417,6 +440,9 @@ data Value = Value Coin NonAdaAsset derive instance Generic Value _ derive instance Eq Value +instance Arbitrary Value where + arbitrary = Value <$> arbitrary <*> arbitrary + instance Show Value where show = genericShow diff --git a/src/Internal/Types/TokenName.purs b/src/Internal/Types/TokenName.purs index 0bcc5ccbad..40034a7a9f 100644 --- a/src/Internal/Types/TokenName.purs +++ b/src/Internal/Types/TokenName.purs @@ -32,12 +32,15 @@ import Data.Bitraversable (ltraverse) import Data.Either (Either(Right, Left), either, note) import Data.Map (Map) import Data.Map (fromFoldable) as Map -import Data.Maybe (Maybe(Nothing)) +import Data.Maybe (Maybe(Nothing), fromJust) import Data.Newtype (unwrap, wrap) import Data.String.CodePoints (drop, take) import Data.TextEncoding (encodeUtf8) import Data.Traversable (class Traversable, traverse) import Data.Tuple.Nested (type (/\)) +import Partial.Unsafe (unsafePartial) +import Test.QuickCheck.Arbitrary (class Arbitrary, arbitrary) +import Test.QuickCheck.Gen (resize) newtype TokenName = TokenName RawBytes @@ -48,6 +51,9 @@ derive newtype instance ToMetadata TokenName derive newtype instance Ord TokenName derive newtype instance ToData TokenName +instance Arbitrary TokenName where + arbitrary = unsafePartial fromJust <<< mkTokenName <$> resize 32 arbitrary + foreign import _decodeUtf8 :: forall (r :: Type). Uint8Array -> (String -> r) -> (String -> r) -> r From a5b8ca2789824fd4dd5cadf10e47f3db6f9fbfa1 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Fri, 21 Oct 2022 15:53:33 +0200 Subject: [PATCH 022/373] Add docstrings for CoinSelection module, Logic fixes (cherry picked from commit 3a1eef25031c77fb97120612fde39af8a084a29a) --- src/Contract/BalanceTxConstraints.purs | 1 + src/Internal/BalanceTx/BalanceTx.purs | 48 ++++--- src/Internal/BalanceTx/CoinSelection.purs | 149 +++++++++++++++++----- src/Internal/BalanceTx/Constraints.purs | 15 +++ src/Internal/BalanceTx/Error.purs | 11 +- 5 files changed, 173 insertions(+), 51 deletions(-) diff --git a/src/Contract/BalanceTxConstraints.purs b/src/Contract/BalanceTxConstraints.purs index f58d346051..ca6afa0075 100644 --- a/src/Contract/BalanceTxConstraints.purs +++ b/src/Contract/BalanceTxConstraints.purs @@ -9,6 +9,7 @@ import Ctl.Internal.BalanceTx.Constraints , mustNotSpendUtxosWithOutRefs , mustSendChangeToAddress , mustUseAdditionalUtxos + , mustUseCoinSelectionStrategy , mustUseUtxosAtAddress , mustUseUtxosAtAddresses ) as BalanceTxConstraints diff --git a/src/Internal/BalanceTx/BalanceTx.purs b/src/Internal/BalanceTx/BalanceTx.purs index 36e2a36685..03eef6eb45 100644 --- a/src/Internal/BalanceTx/BalanceTx.purs +++ b/src/Internal/BalanceTx/BalanceTx.purs @@ -11,7 +11,7 @@ import Control.Monad.Except.Trans (ExceptT(ExceptT), except, runExceptT) import Control.Monad.Logger.Class (trace) as Logger import Ctl.Internal.BalanceTx.CoinSelection ( SelectionState - , SelectionStrategy(SelectionStrategyOptimal) + , SelectionStrategy , _leftoverUtxos , performMultiAssetSelection , selectedInputs @@ -25,6 +25,7 @@ import Ctl.Internal.BalanceTx.Constraints ( _changeAddress , _maxChangeOutputTokenQuantity , _nonSpendableInputs + , _selectionStrategy , _srcAddresses ) as Constraints import Ctl.Internal.BalanceTx.Error @@ -197,8 +198,10 @@ balanceTxWithConstraints unbalancedTx constraintsBuilder = do availableUtxos <- liftQueryM $ filterLockedUtxos allUtxos + selectionStrategy <- asksConstraints Constraints._selectionStrategy + -- Balance and finalize the transaction: - runBalancer allUtxos availableUtxos changeAddr certsFee + runBalancer selectionStrategy allUtxos availableUtxos changeAddr certsFee (unbalancedTx # _transaction' .~ unbalancedCollTx) where getChangeAddress :: BalanceTxM Address @@ -234,13 +237,14 @@ type BalancerState = } runBalancer - :: UtxoMap + :: SelectionStrategy + -> UtxoMap -> UtxoMap -> Address -> Coin -> UnattachedUnbalancedTx -> BalanceTxM FinalizedTransaction -runBalancer allUtxos utxos changeAddress certsFee unbalancedTx' = do +runBalancer strategy allUtxos utxos changeAddress certsFee unbalancedTx' = do spendableUtxos <- getSpendableUtxos addLovelacesToTransactionOutputs unbalancedTx' >>= ((\tx -> mkBalancerState tx mempty spendableUtxos) >>> prebalanceTx) @@ -269,26 +273,28 @@ runBalancer allUtxos utxos changeAddress certsFee unbalancedTx' = do prebalanceTx state@{ unbalancedTx, changeOutputs, leftoverUtxos } = do logBalancerState "Pre-balancing (Stage 1)" utxos state - selectionState <- - performCoinSelection - (setTxChangeOutputs changeOutputs unbalancedTx ^. _body') - let - leftoverUtxos' :: UtxoMap - leftoverUtxos' = selectionState ^. _leftoverUtxos - - selectedInputs' :: Set TransactionInput - selectedInputs' = selectedInputs selectionState + performCoinSelection >>= \selectionState -> + let + leftoverUtxos' :: UtxoMap + leftoverUtxos' = selectionState ^. _leftoverUtxos - unbalancedTxWithInputs :: UnattachedUnbalancedTx - unbalancedTxWithInputs = - unbalancedTx # _body' <<< _inputs %~ Set.union selectedInputs' + selectedInputs' :: Set TransactionInput + selectedInputs' = selectedInputs selectionState - runNextBalancingStep unbalancedTxWithInputs leftoverUtxos' + unbalancedTxWithInputs :: UnattachedUnbalancedTx + unbalancedTxWithInputs = + unbalancedTx # _body' <<< _inputs %~ Set.union selectedInputs' + in + runNextBalancingStep unbalancedTxWithInputs leftoverUtxos' where - performCoinSelection :: TxBody -> BalanceTxM SelectionState - performCoinSelection txBody = - except (getRequiredValue certsFee utxos txBody) - >>= performMultiAssetSelection SelectionStrategyOptimal leftoverUtxos + performCoinSelection :: BalanceTxM SelectionState + performCoinSelection = + let + txBody :: TxBody + txBody = setTxChangeOutputs changeOutputs unbalancedTx ^. _body' + in + except (getRequiredValue certsFee utxos txBody) + >>= performMultiAssetSelection strategy leftoverUtxos balanceChangeAndMinFee :: BalancerState -> BalanceTxM FinalizedTransaction balanceChangeAndMinFee diff --git a/src/Internal/BalanceTx/CoinSelection.purs b/src/Internal/BalanceTx/CoinSelection.purs index 91edde5e26..90dd83afef 100644 --- a/src/Internal/BalanceTx/CoinSelection.purs +++ b/src/Internal/BalanceTx/CoinSelection.purs @@ -1,6 +1,9 @@ +-- | This module provides a multi-asset coin selection algorithm replicated from +-- | cardano-wallet (https://github.com/input-output-hk/cardano-wallet/blob/master/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs). The algorithm supports two selection +-- | strategies (optimal and minimal) and uses priority ordering and round-robin +-- | processing to handle the problem of over-selection. module Ctl.Internal.BalanceTx.CoinSelection - ( MultiAssetSelection(MultiAssetSelection) - , SelectionState(SelectionState) + ( SelectionState(SelectionState) , SelectionStrategy(SelectionStrategyMinimal, SelectionStrategyOptimal) , _leftoverUtxos , performMultiAssetSelection @@ -18,13 +21,14 @@ import Ctl.Internal.BalanceTx.Error , InsufficientUtxoBalanceToCoverAsset ) , Expected(Expected) + , ImpossibleError(Impossible) ) import Ctl.Internal.Cardano.Types.Transaction (TransactionOutput, UtxoMap) import Ctl.Internal.Cardano.Types.Value (AssetClass(AssetClass), Coin, Value) import Ctl.Internal.Cardano.Types.Value ( getAssetQuantity , getCurrencySymbol - , lt + , leq , valueAssetClasses , valueAssets , valueToCoin @@ -59,14 +63,39 @@ import Effect.Random (randomInt) as Random import Type.Proxy (Proxy(Proxy)) -------------------------------------------------------------------------------- --- CoinSelection +-- Coin Selection -------------------------------------------------------------------------------- -data MultiAssetSelection = MultiAssetSelection SelectionStrategy - --- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L325 -data SelectionStrategy = SelectionStrategyMinimal | SelectionStrategyOptimal - +-- | A `SelectionStrategy` determines how much of each asset the selection +-- | algorithm will attempt to select from the available utxo set. +-- | +-- | Specifying `SelectionStrategyOptimal` will cause the selection algorithm to +-- | attempt to select around twice the required amount of each asset from the +-- | available utxo set, making it possible to generate change outputs that are +-- | roughly the same sizes and shapes as the user-specified outputs. Using this +-- | strategy will help to ensure that a wallet's utxo distribution can evolve +-- | over time to resemble the typical distribution of payments made by the +-- | wallet owner. +-- | +-- | Specifying `SelectionStrategyMinimal` will cause the selection algorithm to +-- | only select just enough of each asset from the available utxo set to meet +-- | the required amount. It is advised to use this strategy only when +-- | necessary, as it increases the likelihood of generating change outputs that +-- | are much smaller than user-specified outputs. If this strategy is used +-- | regularly, the utxo set can evolve to a state where the distribution no +-- | longer resembles the typical distribution of payments made by the user. +-- | +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/a61d37f2557b8cb5c47b57da79375afad698eed4/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L325 +data SelectionStrategy = SelectionStrategyOptimal | SelectionStrategyMinimal + +-- | Performs a coin selection using the specified selection strategy. +-- | +-- | Throws a `BalanceInsufficientError` if the balance of the provided utxo +-- | set is insufficient to cover the balance required. +-- | +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/a61d37f2557b8cb5c47b57da79375afad698eed4/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L1128 performMultiAssetSelection :: forall (m :: Type -> Type) . MonadEffect m @@ -76,11 +105,11 @@ performMultiAssetSelection -> Value -> m SelectionState performMultiAssetSelection strategy utxos requiredValue = - case availableValue `Value.lt` requiredValue of + case requiredValue `Value.leq` availableValue of true -> - throwError balanceInsufficientError - false -> runRoundRobinM (mkSelectionState utxos) selectors + false -> + throwError balanceInsufficientError where balanceInsufficientError :: BalanceTxError balanceInsufficientError = @@ -105,7 +134,10 @@ performMultiAssetSelection strategy utxos requiredValue = runSelectionStep $ coinSelectionLens strategy (Value.valueToCoin requiredValue) --- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/Primitive/Types/UTxOSelection.hs#L145 +-- | Represents the internal state of a selection. +-- | +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/a61d37f2557b8cb5c47b57da79375afad698eed4/lib/wallet/src/Cardano/Wallet/Primitive/Types/UTxOSelection.hs#L145 newtype SelectionState = SelectionState { leftoverUtxos :: UtxoMap , selectedUtxos :: UtxoMap @@ -119,36 +151,58 @@ _leftoverUtxos = _Newtype <<< prop (Proxy :: Proxy "leftoverUtxos") _selectedUtxos :: Lens' SelectionState UtxoMap _selectedUtxos = _Newtype <<< prop (Proxy :: Proxy "selectedUtxos") --- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/Primitive/Types/UTxOSelection.hs#L192 +-- | Creates an initial `SelectionState` where none of the utxos are selected. +-- | +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/a61d37f2557b8cb5c47b57da79375afad698eed4/lib/wallet/src/Cardano/Wallet/Primitive/Types/UTxOSelection.hs#L192 mkSelectionState :: UtxoMap -> SelectionState mkSelectionState = wrap <<< { leftoverUtxos: _, selectedUtxos: Map.empty } --- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/Primitive/Types/UTxOSelection.hs#L426 +-- | Moves a single utxo entry from the leftover set to the selected set. +-- | +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/a61d37f2557b8cb5c47b57da79375afad698eed4/lib/wallet/src/Cardano/Wallet/Primitive/Types/UTxOSelection.hs#L426 selectUtxo :: TxUnspentOutput -> SelectionState -> SelectionState selectUtxo (oref /\ out) = over _selectedUtxos (Map.insert oref out) <<< over _leftoverUtxos (Map.delete oref) +-- | Returns the balance of the given utxo set. balance :: UtxoMap -> Value balance = Foldable.foldMap (_.amount <<< unwrap) --- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/Primitive/Types/UTxOSelection.hs#L375 +-- | Returns the balance of selected utxos. +-- | +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/a61d37f2557b8cb5c47b57da79375afad698eed4/lib/wallet/src/Cardano/Wallet/Primitive/Types/UTxOSelection.hs#L375 selectedBalance :: SelectionState -> Value selectedBalance = balance <<< _.selectedUtxos <<< unwrap --- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L2169 +-- | Returns the quantity of the given asset in the selected `Value`. +-- | +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/a61d37f2557b8cb5c47b57da79375afad698eed4/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L2169 selectedAssetQuantity :: AssetClass -> SelectionState -> BigInt selectedAssetQuantity assetClass = Value.getAssetQuantity assetClass <<< selectedBalance --- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L2175 +-- | Returns the selected amount of Ada. +-- | +-- | Taken from cardano-wallet: +-- |https://github.com/input-output-hk/cardano-wallet/blob/a61d37f2557b8cb5c47b57da79375afad698eed4/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L2175 selectedCoinQuantity :: SelectionState -> BigInt selectedCoinQuantity = Value.valueToCoin' <<< selectedBalance +-- | Returns the output references of the selected utxos. selectedInputs :: SelectionState -> Set TransactionInput selectedInputs = Set.fromFoldable <<< Map.keys <<< view _selectedUtxos --- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L1254 +-- | A `SelectionLens` gives `runSelectionStep` the information on the current +-- | selection state along with the functions required to transition to the next +-- | state. +-- | +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/a61d37f2557b8cb5c47b57da79375afad698eed4/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L1254 type SelectionLens (m :: Type -> Type) = { assetDisplayString :: String , currentQuantity :: SelectionState -> BigInt @@ -158,7 +212,8 @@ type SelectionLens (m :: Type -> Type) = , selectionStrategy :: SelectionStrategy } --- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L1159 +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/a61d37f2557b8cb5c47b57da79375afad698eed4/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L1159 assetSelectionLens :: forall (m :: Type -> Type) . MonadEffect m @@ -178,7 +233,8 @@ assetSelectionLens selectionStrategy (assetClass /\ requiredQuantity) = , selectionStrategy } --- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L1173 +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/a61d37f2557b8cb5c47b57da79375afad698eed4/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L1173 coinSelectionLens :: forall (m :: Type -> Type) . MonadEffect m @@ -196,7 +252,15 @@ coinSelectionLens selectionStrategy coin = , selectionStrategy } --- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L1217 +-- | Selects an utxo entry that matches one of the filters derived from the +-- | given `SelectionPriority`. This function traverses the list of filters from +-- | left to right, in descending order of priority. +-- | +-- | Returns `Nothing` if it traverses the entire list of filters without +-- | successfully selecting an utxo entry. +-- | +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/a61d37f2557b8cb5c47b57da79375afad698eed4/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L1217 selectQuantityOf :: forall (m :: Type -> Type) (asset :: Type) . MonadEffect m @@ -215,7 +279,25 @@ selectQuantityOf asset priority state = updateState :: TxUnspentOutput /\ UtxoMap -> SelectionState updateState = flip selectUtxo state <<< Tuple.fst --- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L1284 +-- | Runs just a single step of a coin selection. +-- | +-- | It returns an updated state if (and only if) the updated selection +-- | represents an improvement over the selection in the previous state. +-- | +-- | An improvement, for a given asset quantity, is defined as follows: +-- | +-- | - If the total selected asset quantity of the previous selection had +-- | not yet reached 100% of the output asset quantity, any additional +-- | selection is considered to be an improvement. +-- | +-- | - If the total selected asset quantity of the previous selection had +-- | already reached or surpassed 100% of the output asset quantity, any +-- | additional selection is considered to be an improvement if and only +-- | if it takes the total selected asset quantity closer to the target +-- | asset quantity, but not further away. +-- | +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L1284 runSelectionStep :: forall (m :: Type -> Type) . MonadThrow BalanceTxError m @@ -227,11 +309,15 @@ runSelectionStep lens state let balanceInsufficientError :: BalanceTxError balanceInsufficientError = - InsufficientUtxoBalanceToCoverAsset lens.assetDisplayString + InsufficientUtxoBalanceToCoverAsset Impossible lens.assetDisplayString in lens.selectQuantityCover state >>= maybe (throwError balanceInsufficientError) (pure <<< Just) | otherwise = + -- Note that if the required asset quantity has already been reached, + -- we attempt to improve the selection using `SelectionPriorityImprove`, + -- which allows us to select only utxos containing the given asset and no + -- other asset, i.e. we select from the "singleton" subset of utxos. bindFlipped requireImprovement <$> lens.selectQuantityImprove state where requireImprovement :: SelectionState -> Maybe SelectionState @@ -267,7 +353,8 @@ runRoundRobinM -> m s runRoundRobinM state = runRoundRobinM' state identity --- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L2155 +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/a61d37f2557b8cb5c47b57da79375afad698eed4/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L2155 runRoundRobinM' :: forall (m :: Type -> Type) (s :: Type) (s' :: Type) . Monad m @@ -306,7 +393,8 @@ filtersForAssetWithPriority asset priority = SelectionPriorityImprove -> NEArray.singleton (SelectSingleton asset) --- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L460 +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L460 selectRandomWithPriority :: forall (m :: Type -> Type) (asset :: Type) . MonadEffect m @@ -327,7 +415,8 @@ selectRandomWithPriority utxos filters = -- SelectionFilter, ApplySelectionFilter -------------------------------------------------------------------------------- --- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L399 +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L399 data SelectionFilter (asset :: Type) = SelectSingleton asset | SelectPairWith asset @@ -359,7 +448,8 @@ instance ApplySelectionFilter Coin where type TxUnspentOutput = TransactionInput /\ TransactionOutput --- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L418 +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L418 selectRandomWithFilter :: forall (m :: Type -> Type) (asset :: Type) . MonadEffect m @@ -375,7 +465,8 @@ selectRandomWithFilter utxos filter = -- Helpers -------------------------------------------------------------------------------- --- https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L598 +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L598 selectRandomMapMember :: forall (m :: Type -> Type) (k :: Type) (v :: Type) . MonadEffect m diff --git a/src/Internal/BalanceTx/Constraints.purs b/src/Internal/BalanceTx/Constraints.purs index b6e16beb09..c110233906 100644 --- a/src/Internal/BalanceTx/Constraints.purs +++ b/src/Internal/BalanceTx/Constraints.purs @@ -7,17 +7,22 @@ module Ctl.Internal.BalanceTx.Constraints , mustNotSpendUtxoWithOutRef , mustSendChangeToAddress , mustUseAdditionalUtxos + , mustUseCoinSelectionStrategy , mustUseUtxosAtAddress , mustUseUtxosAtAddresses , _additionalUtxos , _changeAddress , _maxChangeOutputTokenQuantity , _nonSpendableInputs + , _selectionStrategy , _srcAddresses ) where import Prelude +import Ctl.Internal.BalanceTx.CoinSelection + ( SelectionStrategy(SelectionStrategyOptimal) + ) import Ctl.Internal.Plutus.Conversion ( fromPlutusAddress , fromPlutusAddressWithNetworkTag @@ -49,6 +54,7 @@ newtype BalanceTxConstraints = BalanceTxConstraints , nonSpendableInputs :: Set TransactionInput , srcAddresses :: Maybe (Array Address) , changeAddress :: Maybe Address + , selectionStrategy :: SelectionStrategy } derive instance Newtype BalanceTxConstraints _ @@ -69,6 +75,9 @@ _srcAddresses = _Newtype <<< prop (Proxy :: Proxy "srcAddresses") _changeAddress :: Lens' BalanceTxConstraints (Maybe Address) _changeAddress = _Newtype <<< prop (Proxy :: Proxy "changeAddress") +_selectionStrategy :: Lens' BalanceTxConstraints SelectionStrategy +_selectionStrategy = _Newtype <<< prop (Proxy :: Proxy "selectionStrategy") + newtype BalanceTxConstraintsBuilder = BalanceTxConstraintsBuilder (BalanceTxConstraints -> BalanceTxConstraints) @@ -90,6 +99,7 @@ buildBalanceTxConstraints = applyFlipped defaultConstraints <<< unwrap , nonSpendableInputs: mempty , srcAddresses: Nothing , changeAddress: Nothing + , selectionStrategy: SelectionStrategyOptimal } -- | Tells the balancer to send all generated change to a given address. @@ -148,3 +158,8 @@ mustNotSpendUtxoWithOutRef = mustNotSpendUtxosWithOutRefs <<< Set.singleton -- | spendable by the transaction (see `Examples.TxChaining` for reference). mustUseAdditionalUtxos :: Plutus.UtxoMap -> BalanceTxConstraintsBuilder mustUseAdditionalUtxos = wrap <<< set _additionalUtxos + +-- | Tells the balancer to use the given strategy for coin selection. +mustUseCoinSelectionStrategy :: SelectionStrategy -> BalanceTxConstraintsBuilder +mustUseCoinSelectionStrategy = wrap <<< set _selectionStrategy + diff --git a/src/Internal/BalanceTx/Error.purs b/src/Internal/BalanceTx/Error.purs index 91055d6990..0d139c37f6 100644 --- a/src/Internal/BalanceTx/Error.purs +++ b/src/Internal/BalanceTx/Error.purs @@ -19,6 +19,7 @@ module Ctl.Internal.BalanceTx.Error , UtxoMinAdaValueCalculationFailed ) , Expected(Expected) + , ImpossibleError(Impossible) , printTxEvaluationFailure ) where @@ -76,7 +77,7 @@ data BalanceTxError | CollateralReturnMinAdaValueCalcError | ExUnitsEvaluationFailed UnattachedUnbalancedTx Ogmios.TxEvaluationFailure | InsufficientTxInputs Expected Actual - | InsufficientUtxoBalanceToCoverAsset String + | InsufficientUtxoBalanceToCoverAsset ImpossibleError String | ReindexRedeemersError ReindexErrors | UtxoLookupFailedFor TransactionInput | UtxoMinAdaValueCalculationFailed @@ -104,6 +105,14 @@ derive instance Newtype Expected _ instance Show Expected where show = genericShow +-- | Indicates that an error should be impossible. +data ImpossibleError = Impossible + +derive instance Generic ImpossibleError _ + +instance Show ImpossibleError where + show = genericShow + -------------------------------------------------------------------------------- -- Failure parsing for Ogmios.EvaluateTx -------------------------------------------------------------------------------- From c4e59ccc7c51504d6173e1ba611cfd70359795da Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Mon, 24 Oct 2022 14:48:54 +0200 Subject: [PATCH 023/373] More documentation on balancing and change generation (cherry picked from commit 18cb489300a43560a2c4e87b49a7530cfe3e46c8) --- src/Internal/BalanceTx/BalanceTx.purs | 89 +++++++++++++++++++++++++-- 1 file changed, 85 insertions(+), 4 deletions(-) diff --git a/src/Internal/BalanceTx/BalanceTx.purs b/src/Internal/BalanceTx/BalanceTx.purs index 03eef6eb45..ab3953495b 100644 --- a/src/Internal/BalanceTx/BalanceTx.purs +++ b/src/Internal/BalanceTx/BalanceTx.purs @@ -255,6 +255,11 @@ runBalancer strategy allUtxos utxos changeAddress certsFee unbalancedTx' = do \nonSpendableInputs -> Map.filterKeys (not <<< flip Set.member nonSpendableInputs) utxos + -- | Determines which balancing step will be performed next. + -- | + -- | If the transaction remains unbalanced (i.e. `requiredValue != mempty`) + -- | after generation of change, the first balancing step (`prebalanceTx`) + -- | is performed, otherwise we proceed to `balanceChangeAndMinFee`. runNextBalancingStep :: UnattachedUnbalancedTx -> UtxoMap -> BalanceTxM FinalizedTransaction runNextBalancingStep unbalancedTx leftoverUtxos = do @@ -269,6 +274,9 @@ runBalancer strategy allUtxos utxos changeAddress certsFee unbalancedTx' = do { unbalancedTx, changeOutputs, leftoverUtxos } # if requiredValue == mempty then balanceChangeAndMinFee else prebalanceTx + -- | Selects a combination of unspent transaction outputs from the wallet's + -- | utxo set so that the total input value is sufficient to cover all + -- | transaction outputs, including generated change and min fee. prebalanceTx :: BalancerState -> BalanceTxM FinalizedTransaction prebalanceTx state@{ unbalancedTx, changeOutputs, leftoverUtxos } = do logBalancerState "Pre-balancing (Stage 1)" utxos state @@ -296,6 +304,12 @@ runBalancer strategy allUtxos utxos changeAddress certsFee unbalancedTx' = do except (getRequiredValue certsFee utxos txBody) >>= performMultiAssetSelection strategy leftoverUtxos + -- | Calculates execution units for each script in the transaction and sets + -- | min fee. + -- | + -- | The transaction must be pre-balanced before evaluating execution units, + -- | since this pre-condition is sometimes required for successfull script + -- | execution during transaction evaluation. balanceChangeAndMinFee :: BalancerState -> BalanceTxM FinalizedTransaction balanceChangeAndMinFee state@{ unbalancedTx, changeOutputs, leftoverUtxos } = do @@ -357,14 +371,34 @@ setTxChangeOutputs outputs = _body' <<< _outputs %~ flip append outputs -- Making change -------------------------------------------------------------------------------- +-- | Constructs change outputs to return all excess `Value` back to the owner's +-- | address. +-- | +-- | Returns an array of change outputs even if the transaction becomes +-- | unbalanced after attaching them (which can be the case if the specified +-- | inputs do not provide enough ada to satisfy minimum ada quantites of the +-- | change outputs generated). +-- | +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/4c2eb651d79212157a749d8e69a48fff30862e93/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L1396 makeChange :: Address -> Value -> Coin -> TxBody -> BalanceTxM (Array TransactionOutput) makeChange changeAddress inputValue certsFee txBody = - map (mkChangeOutput changeAddress) <$> - ( assignCoinsToChangeValues changeAddress excessCoin - =<< splitOversizedValues changeValueOutputCoinPairs - ) + if excessValue == mempty then pure mempty + else + map (mkChangeOutput changeAddress) <$> + ( assignCoinsToChangeValues changeAddress excessCoin + =<< splitOversizedValues changeValueOutputCoinPairs + ) where + -- | Change `Value`s for all assets, where each change map is paired with a + -- | corresponding coin from the original outputs. + -- | + -- | This array is sorted into ascending order of asset count, where empty + -- | change `Value`s are all located at the start of the list. + -- | + -- | Taken from cardano-wallet: + -- | https://github.com/input-output-hk/cardano-wallet/blob/4c2eb651d79212157a749d8e69a48fff30862e93/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L1447 changeValueOutputCoinPairs :: NonEmptyArray (Value /\ BigInt) changeValueOutputCoinPairs = outputCoins # NEArray.zip changeForAssets @@ -417,6 +451,19 @@ makeChange changeAddress inputValue certsFee txBody = posValue (Value (Coin coin) nonAdaAsset) = mkValue (Coin $ max coin zero) (posNonAdaAsset nonAdaAsset) +-- | Constructs change outputs for an asset. +-- | +-- | The given asset quantity is partitioned into a list of `Value`s that are +-- | proportional to the weights withing the given distribution. If the given +-- | asset quantity does not appear in the distribution, then it is equally +-- | partitioned into a list of the same length. +-- | +-- | The length of the output list is always the same as the length of the input +-- | list, and the sum of quantities is exactly equal to the asset quantity in +-- | the second argument. +-- | +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/4c2eb651d79212157a749d8e69a48fff30862e93/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L1729 makeChangeForAsset :: Array TransactionOutput -> (AssetClass /\ BigInt) -> NonEmptyArray Value makeChangeForAsset txOutputs (assetClass /\ excess) = @@ -430,11 +477,45 @@ makeChangeForAsset txOutputs (assetClass /\ excess) = assetQuantities = txOutputs <#> Value.getAssetQuantity assetClass <<< _.amount <<< unwrap +-- | Constructs an array of ada change outputs based on the given distribution. +-- | +-- | The given ada amount is partitioned into a list of `Value`s that are +-- | proportional to the weights withing the given distribution. If the sum of +-- | weights in the given distribution is equal to zero, then the given excess +-- | coin is equally partitioned into a list of the same length. +-- | +-- | The length of the output list is always the same as the length of the input +-- | list, and the sum of its quantities is always exactly equal to the excess +-- | ada amount given as the second argument. +-- | +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/4c2eb651d79212157a749d8e69a48fff30862e93/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L1799 makeChangeForCoin :: NonEmptyArray BigInt -> BigInt -> NonEmptyArray Value makeChangeForCoin weights excess = lovelaceValueOf <$> partition excess weights ?? equipartition excess (length weights) +-- | Assigns coin quantities to a list of pre-computed change `Value`s. +-- | +-- | Each pre-computed change `Value` must be paired with the original coin +-- | value of its corresponding output. +-- | +-- | This function: +-- | - expects the list of pre-computed change `Value`s to be sorted in an +-- | order that ensures all empty `Value`s are at the start of the list. +-- | +-- | - attempts to assign a minimum ada quantity to every change `Value`, but +-- | iteratively drops empty change `Value`s from the start of the list if +-- | the amount of ada is insufficient to cover them all. +-- | +-- | - continues dropping empty change maps from the start of the list until +-- | it is possible to assign a minimum ada value to all remaining entries. +-- | +-- | - assigns the minimum ada quantity to all non-empty change `Value`s, even +-- | if `adaAvailable` is insufficient, does not fail. +-- | +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/4c2eb651d79212157a749d8e69a48fff30862e93/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L1631 assignCoinsToChangeValues :: Address -> BigInt From bfe315e7d04718d836265aa6249340098168d4f3 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Wed, 26 Oct 2022 13:38:57 +0200 Subject: [PATCH 024/373] Apply suggestions, Fix warnings (cherry picked from commit 966fcb9a8931dc6b1612c7a70d41e1e98554b65b) --- src/Internal/BalanceTx/BalanceTx.purs | 33 ++++++++++++++------------- 1 file changed, 17 insertions(+), 16 deletions(-) diff --git a/src/Internal/BalanceTx/BalanceTx.purs b/src/Internal/BalanceTx/BalanceTx.purs index ab3953495b..9f7a0fadb7 100644 --- a/src/Internal/BalanceTx/BalanceTx.purs +++ b/src/Internal/BalanceTx/BalanceTx.purs @@ -78,8 +78,8 @@ import Ctl.Internal.BalanceTx.Types (FinalizedTransaction(FinalizedTransaction)) import Ctl.Internal.BalanceTx.UtxoMinAda (utxoMinAdaValue) import Ctl.Internal.Cardano.Types.Transaction ( Certificate(StakeRegistration, StakeDeregistration) - , Transaction(Transaction) - , TransactionOutput(TransactionOutput) + , Transaction + , TransactionOutput , TxBody , UtxoMap , _body @@ -253,7 +253,9 @@ runBalancer strategy allUtxos utxos changeAddress certsFee unbalancedTx' = do getSpendableUtxos = asksConstraints Constraints._nonSpendableInputs <#> \nonSpendableInputs -> - Map.filterKeys (not <<< flip Set.member nonSpendableInputs) utxos + flip Map.filterKeys utxos \oref -> not $ + Set.member oref nonSpendableInputs + || Set.member oref (unbalancedTx' ^. _body' <<< _referenceInputs) -- | Determines which balancing step will be performed next. -- | @@ -281,19 +283,19 @@ runBalancer strategy allUtxos utxos changeAddress certsFee unbalancedTx' = do prebalanceTx state@{ unbalancedTx, changeOutputs, leftoverUtxos } = do logBalancerState "Pre-balancing (Stage 1)" utxos state - performCoinSelection >>= \selectionState -> - let - leftoverUtxos' :: UtxoMap - leftoverUtxos' = selectionState ^. _leftoverUtxos + selectionState <- performCoinSelection + let + leftoverUtxos' :: UtxoMap + leftoverUtxos' = selectionState ^. _leftoverUtxos - selectedInputs' :: Set TransactionInput - selectedInputs' = selectedInputs selectionState + selectedInputs' :: Set TransactionInput + selectedInputs' = selectedInputs selectionState - unbalancedTxWithInputs :: UnattachedUnbalancedTx - unbalancedTxWithInputs = - unbalancedTx # _body' <<< _inputs %~ Set.union selectedInputs' - in - runNextBalancingStep unbalancedTxWithInputs leftoverUtxos' + unbalancedTxWithInputs :: UnattachedUnbalancedTx + unbalancedTxWithInputs = + unbalancedTx # _body' <<< _inputs %~ Set.union selectedInputs' + + runNextBalancingStep unbalancedTxWithInputs leftoverUtxos' where performCoinSelection :: BalanceTxM SelectionState performCoinSelection = @@ -563,8 +565,7 @@ assignCoinsToChangeValues changeAddress adaAvailable pairsAtStart = noTokens = Array.null <<< Value.valueAssets <<< fst adaRequiredAtStart :: BalanceTxM BigInt - adaRequiredAtStart = - foldr (+) zero <$> traverse (minCoinFor <<< fst) pairsAtStart + adaRequiredAtStart = sum <$> traverse (minCoinFor <<< fst) pairsAtStart minCoinFor :: Value -> BalanceTxM BigInt minCoinFor value = do From 5caba50b5ee4d2e73f5a2b747ab26cbad15cbfda Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Mon, 28 Nov 2022 21:01:41 +0000 Subject: [PATCH 025/373] WIP --- examples/AlwaysMints.purs | 4 +- examples/AlwaysSucceeds.purs | 4 +- examples/AwaitTxConfirmedWithTimeout.purs | 4 +- examples/BalanceTxConstraints.purs | 6 +- examples/ByUrl.purs | 4 +- examples/Cip30.purs | 4 +- examples/ContractTestUtils.purs | 4 +- examples/Helpers.purs | 17 +- examples/IncludeDatum.purs | 4 +- examples/KeyWallet/SignMultiple.purs | 9 +- examples/Lose7Ada.purs | 4 +- examples/MintsMultipleTokens.purs | 4 +- examples/MultipleRedeemers.purs | 5 +- examples/NativeScriptMints.purs | 4 +- examples/OneShotMinting.purs | 6 +- examples/Pkh2Pkh.purs | 4 +- examples/PlutusV2/AlwaysSucceeds.purs | 4 +- examples/PlutusV2/InlineDatum.purs | 4 +- examples/PlutusV2/OneShotMinting.purs | 4 +- examples/PlutusV2/ReferenceInputs.purs | 10 +- .../PlutusV2/ReferenceInputsAndScripts.purs | 4 +- examples/PlutusV2/ReferenceScripts.purs | 4 +- examples/SatisfiesAnyOf.purs | 4 +- examples/SendsToken.purs | 4 +- examples/SignMultiple.purs | 13 +- examples/TxChaining.purs | 4 +- examples/Utxos.purs | 4 +- examples/Wallet.purs | 4 +- src/Contract/AuxiliaryData.purs | 14 +- src/Contract/Monad.purs | 34 ++- src/Contract/ScriptLookups.purs | 12 +- src/Contract/Test/Utils.purs | 203 ++++++++--------- src/Contract/Time.purs | 15 +- src/Contract/Transaction.purs | 212 +++++++----------- src/Contract/Utxos.purs | 36 +-- src/Contract/Wallet.purs | 56 ++--- src/Internal/BalanceTx/BalanceTx.purs | 33 +-- src/Internal/BalanceTx/ExUnitsAndMinFee.purs | 30 +-- src/Internal/BalanceTx/Types.purs | 34 +-- src/Internal/Contract/MinFee.purs | 123 ++++++++++ src/Internal/Contract/Monad.purs | 101 ++++----- src/Internal/Contract/QueryBackend.purs | 1 + src/Internal/Contract/QueryHandle.purs | 51 ++++- src/Internal/Contract/Sign.purs | 103 +++++++++ src/Internal/Contract/Wallet.purs | 82 +++++-- src/Internal/Plutip/Server.purs | 96 ++++---- src/Internal/Plutip/UtxoDistribution.purs | 9 +- src/Internal/ReindexRedeemers.purs | 18 +- src/Internal/Test/E2E/Route.purs | 25 ++- src/Internal/Test/E2E/Runner.purs | 16 +- src/Internal/Types/ScriptLookups.purs | 48 ++-- src/Internal/Wallet/Cip30Mock.purs | 61 +++-- templates/ctl-scaffold/test/E2E.purs | 6 +- test/AffInterface.purs | 164 +++++++------- test/BalanceTx/Collateral.purs | 10 +- test/BalanceTx/Time.purs | 29 +-- test/Integration.purs | 21 +- test/Ogmios/GenerateFixtures.purs | 2 +- test/Plutip/Contract.purs | 20 +- test/Plutip/Staking.purs | 4 +- test/Plutip/Utils.purs | 6 +- test/Plutip/UtxoDistribution.purs | 17 +- test/Types/Interval.purs | 90 +++++--- test/Unit.purs | 3 +- 64 files changed, 1099 insertions(+), 836 deletions(-) create mode 100644 src/Internal/Contract/MinFee.purs create mode 100644 src/Internal/Contract/Sign.purs diff --git a/examples/AlwaysMints.purs b/examples/AlwaysMints.purs index 81b9b9140d..3989614c8b 100644 --- a/examples/AlwaysMints.purs +++ b/examples/AlwaysMints.purs @@ -11,7 +11,7 @@ module Ctl.Examples.AlwaysMints import Contract.Prelude -import Contract.Config (ConfigParams, testnetNamiConfig) +import Contract.Config (ContractParams, testnetNamiConfig) import Contract.Log (logInfo') import Contract.Monad (Contract, launchAff_, runContract) import Contract.ScriptLookups as Lookups @@ -54,7 +54,7 @@ contract = do awaitTxConfirmed txId logInfo' "Tx submitted successfully!" -example :: ConfigParams () -> Effect Unit +example :: ContractParams -> Effect Unit example cfg = launchAff_ $ do runContract cfg contract diff --git a/examples/AlwaysSucceeds.purs b/examples/AlwaysSucceeds.purs index 7222c1d4bd..c6c791d89b 100644 --- a/examples/AlwaysSucceeds.purs +++ b/examples/AlwaysSucceeds.purs @@ -14,7 +14,7 @@ module Ctl.Examples.AlwaysSucceeds import Contract.Prelude import Contract.Address (ownStakePubKeysHashes, scriptHashAddress) -import Contract.Config (ConfigParams, testnetNamiConfig) +import Contract.Config (ContractParams, testnetNamiConfig) import Contract.Credential (Credential(PubKeyCredential)) import Contract.Log (logInfo') import Contract.Monad (Contract, launchAff_, runContract) @@ -53,7 +53,7 @@ contract = do logInfo' "Tx submitted successfully, Try to spend locked values" spendFromAlwaysSucceeds vhash validator txId -example :: ConfigParams () -> Effect Unit +example :: ContractParams -> Effect Unit example cfg = launchAff_ do runContract cfg contract diff --git a/examples/AwaitTxConfirmedWithTimeout.purs b/examples/AwaitTxConfirmedWithTimeout.purs index 17c0844c83..401328c886 100644 --- a/examples/AwaitTxConfirmedWithTimeout.purs +++ b/examples/AwaitTxConfirmedWithTimeout.purs @@ -10,7 +10,7 @@ module Ctl.Examples.AwaitTxConfirmedWithTimeout import Contract.Prelude -import Contract.Config (ConfigParams, testnetNamiConfig) +import Contract.Config (ContractParams, testnetNamiConfig) import Contract.Log (logInfo') import Contract.Monad (Contract, launchAff_, runContract, throwContractError) import Contract.Prim.ByteArray (hexToByteArrayUnsafe) @@ -23,7 +23,7 @@ import Control.Monad.Error.Class (try) main :: Effect Unit main = example testnetNamiConfig -example :: ConfigParams () -> Effect Unit +example :: ContractParams -> Effect Unit example cfg = launchAff_ do runContract cfg contract diff --git a/examples/BalanceTxConstraints.purs b/examples/BalanceTxConstraints.purs index a877411aa1..9702b6fe89 100644 --- a/examples/BalanceTxConstraints.purs +++ b/examples/BalanceTxConstraints.purs @@ -63,7 +63,7 @@ type ContractResult = -- | correctly, i.e. their token quantities do not exceed the specified upper -- | limit of 4 tokens per change output. assertChangeOutputsPartitionedCorrectly - :: ContractBasicAssertion () ContractResult Unit + :: ContractBasicAssertion ContractResult Unit assertChangeOutputsPartitionedCorrectly { txHash, changeAddress: addr, mintedToken: cs /\ tn } = do let labeledAddr = label addr "changeAddress" @@ -89,7 +89,7 @@ assertChangeOutputsPartitionedCorrectly -- | Checks that the utxo with the specified output reference -- | (`nonSpendableOref`) is not consumed during transaction balancing. assertSelectedUtxoIsNotSpent - :: ContractBasicAssertion () ContractResult Unit + :: ContractBasicAssertion ContractResult Unit assertSelectedUtxoIsNotSpent { changeAddress, nonSpendableOref } = TestUtils.runContractAssertionM' do utxos <- TestUtils.utxosAtAddress (label changeAddress "changeAddress") @@ -101,7 +101,7 @@ assertSelectedUtxoIsNotSpent { changeAddress, nonSpendableOref } = TestUtils.assertContract assertionFailure $ Map.member nonSpendableOref utxos -assertions :: Array (ContractBasicAssertion () ContractResult Unit) +assertions :: Array (ContractBasicAssertion ContractResult Unit) assertions = [ assertChangeOutputsPartitionedCorrectly , assertSelectedUtxoIsNotSpent diff --git a/examples/ByUrl.purs b/examples/ByUrl.purs index a73038839b..aeff4b3d23 100644 --- a/examples/ByUrl.purs +++ b/examples/ByUrl.purs @@ -3,7 +3,7 @@ module Ctl.Examples.ByUrl (main) where import Prelude import Contract.Config - ( ConfigParams + ( ContractParams , mainnetFlintConfig , mainnetGeroConfig , mainnetLodeConfig @@ -47,7 +47,7 @@ main = do addLinks wallets examples route wallets examples -wallets :: Map E2EConfigName (ConfigParams () /\ Maybe WalletMock) +wallets :: Map E2EConfigName (ContractParams /\ Maybe WalletMock) wallets = Map.fromFoldable [ "nami" /\ testnetNamiConfig /\ Nothing , "gero" /\ testnetGeroConfig /\ Nothing diff --git a/examples/Cip30.purs b/examples/Cip30.purs index d310404bdc..8d882fb4fc 100644 --- a/examples/Cip30.purs +++ b/examples/Cip30.purs @@ -8,7 +8,7 @@ module Ctl.Examples.Cip30 import Contract.Prelude -import Contract.Config (ConfigParams, testnetNamiConfig) +import Contract.Config (ContractParams, testnetNamiConfig) import Contract.Log (logInfo') import Contract.Monad (Contract, launchAff_, liftContractAffM, runContract) import Contract.Prim.ByteArray (rawBytesFromAscii) @@ -34,7 +34,7 @@ import Effect.Exception (error) main :: Effect Unit main = example testnetNamiConfig -example :: ConfigParams () -> Effect Unit +example :: ContractParams -> Effect Unit example cfg = launchAff_ do mWallet <- runContract cfg getWallet let mSupportWallet = walletToWalletExtension =<< mWallet diff --git a/examples/ContractTestUtils.purs b/examples/ContractTestUtils.purs index 563140ffd5..5aa441b7a9 100644 --- a/examples/ContractTestUtils.purs +++ b/examples/ContractTestUtils.purs @@ -79,8 +79,8 @@ type ContractResult = mkAssertions :: ContractParams -> Contract - ( Array (ContractWrapAssertion () ContractResult) - /\ Array (ContractBasicAssertion () ContractResult Unit) + ( Array (ContractWrapAssertion ContractResult) + /\ Array (ContractBasicAssertion ContractResult Unit) ) mkAssertions params@(ContractParams p) = do senderAddress <- diff --git a/examples/Helpers.purs b/examples/Helpers.purs index c556ef2da4..a552623529 100644 --- a/examples/Helpers.purs +++ b/examples/Helpers.purs @@ -33,14 +33,14 @@ import Data.BigInt (BigInt) import Effect.Exception (throw) buildBalanceSignAndSubmitTx' - :: forall (r :: Row Type) (validator :: Type) (datum :: Type) + :: forall (validator :: Type) (datum :: Type) (redeemer :: Type) . ValidatorTypes validator datum redeemer => IsData datum => IsData redeemer => Lookups.ScriptLookups validator -> Constraints.TxConstraints redeemer datum - -> Contract r { txHash :: TransactionHash, txFinalFee :: BigInt } + -> Contract { txHash :: TransactionHash, txFinalFee :: BigInt } buildBalanceSignAndSubmitTx' lookups constraints = do unbalancedTx <- liftedE $ Lookups.mkUnbalancedTx lookups constraints balancedTx <- liftedE $ balanceTx unbalancedTx @@ -50,27 +50,26 @@ buildBalanceSignAndSubmitTx' lookups constraints = do pure { txHash, txFinalFee: getTxFinalFee balancedSignedTx } buildBalanceSignAndSubmitTx - :: forall (r :: Row Type) (validator :: Type) (datum :: Type) + :: forall (validator :: Type) (datum :: Type) (redeemer :: Type) . ValidatorTypes validator datum redeemer => IsData datum => IsData redeemer => Lookups.ScriptLookups validator -> Constraints.TxConstraints redeemer datum - -> Contract r TransactionHash + -> Contract TransactionHash buildBalanceSignAndSubmitTx lookups constraints = _.txHash <$> buildBalanceSignAndSubmitTx' lookups constraints mkCurrencySymbol - :: forall (r :: Row Type) - . Contract r MintingPolicy - -> Contract r (MintingPolicy /\ CurrencySymbol) + :: Contract MintingPolicy + -> Contract (MintingPolicy /\ CurrencySymbol) mkCurrencySymbol mintingPolicy = do mp <- mintingPolicy cs <- liftContractM "Cannot get cs" $ Value.scriptCurrencySymbol mp pure (mp /\ cs) -mkTokenName :: forall (r :: Row Type). String -> Contract r TokenName +mkTokenName :: String -> Contract TokenName mkTokenName = liftContractM "Cannot make token name" <<< (Value.mkTokenName <=< byteArrayFromAscii) @@ -87,7 +86,7 @@ mustPayToPubKeyStakeAddress pkh (Just skh) = Constraints.mustPayToPubKeyAddress pkh skh submitAndLog - :: forall (r :: Row Type). BalancedSignedTransaction -> Contract r Unit + :: BalancedSignedTransaction -> Contract Unit submitAndLog bsTx = do txId <- submit bsTx logInfo' $ "Tx ID: " <> show txId diff --git a/examples/IncludeDatum.purs b/examples/IncludeDatum.purs index cc339ee500..258100b0d5 100644 --- a/examples/IncludeDatum.purs +++ b/examples/IncludeDatum.purs @@ -13,7 +13,7 @@ module Ctl.Examples.IncludeDatum import Contract.Prelude import Contract.Address (scriptHashAddress) -import Contract.Config (ConfigParams, testnetNamiConfig) +import Contract.Config (ContractParams, testnetNamiConfig) import Contract.Log (logInfo') import Contract.Monad (Contract, launchAff_, liftContractM, runContract) import Contract.PlutusData (Datum(Datum), PlutusData(Integer), unitRedeemer) @@ -40,7 +40,7 @@ import Effect.Exception (error) main :: Effect Unit main = example testnetNamiConfig -example :: ConfigParams () -> Effect Unit +example :: ContractParams -> Effect Unit example cfg = launchAff_ do runContract cfg do logInfo' "Running Examples.IncludeDatum" diff --git a/examples/KeyWallet/SignMultiple.purs b/examples/KeyWallet/SignMultiple.purs index 27c351da2d..0713da495e 100644 --- a/examples/KeyWallet/SignMultiple.purs +++ b/examples/KeyWallet/SignMultiple.purs @@ -24,9 +24,9 @@ import Data.UInt (UInt) import Effect.Ref (read) as Ref getLockedInputs - :: forall (r :: Row Type). Contract r (Map TransactionHash (Set UInt)) + :: Contract (Map TransactionHash (Set UInt)) getLockedInputs = do - cache <- asks (_.usedTxOuts <<< _.runtime <<< unwrap) + cache <- asks _.usedTxOuts liftEffect $ Ref.read $ unwrap cache main :: Effect Unit @@ -64,9 +64,8 @@ main = runKeyWalletContract_ \pkh lovelace unlock -> do liftEffect unlock where submitAndLog - :: forall (r :: Row Type) - . BalancedSignedTransaction - -> Contract r TransactionHash + :: BalancedSignedTransaction + -> Contract TransactionHash submitAndLog bsTx = do txId <- submit bsTx logInfo' $ "Tx ID: " <> show txId diff --git a/examples/Lose7Ada.purs b/examples/Lose7Ada.purs index 690712ec08..95d8f0ba94 100644 --- a/examples/Lose7Ada.purs +++ b/examples/Lose7Ada.purs @@ -14,7 +14,7 @@ module Ctl.Examples.Lose7Ada import Contract.Prelude import Contract.Address (scriptHashAddress) -import Contract.Config (ConfigParams, testnetNamiConfig) +import Contract.Config (ContractParams, testnetNamiConfig) import Contract.Log (logInfo') import Contract.Monad (Contract, launchAff_, runContract) import Contract.PlutusData (PlutusData, unitDatum, unitRedeemer) @@ -45,7 +45,7 @@ import Test.Spec.Assertions (shouldEqual) main :: Effect Unit main = example testnetNamiConfig -example :: ConfigParams () -> Effect Unit +example :: ContractParams -> Effect Unit example cfg = launchAff_ do runContract cfg do logInfo' "Running Examples.AlwaysFails" diff --git a/examples/MintsMultipleTokens.purs b/examples/MintsMultipleTokens.purs index ff6d40a896..8428325c50 100644 --- a/examples/MintsMultipleTokens.purs +++ b/examples/MintsMultipleTokens.purs @@ -12,7 +12,7 @@ module Ctl.Examples.MintsMultipleTokens import Contract.Prelude -import Contract.Config (ConfigParams, testnetNamiConfig) +import Contract.Config (ContractParams, testnetNamiConfig) import Contract.Log (logInfo') import Contract.Monad (Contract, launchAff_, runContract) import Contract.PlutusData (PlutusData(Integer), Redeemer(Redeemer)) @@ -71,7 +71,7 @@ contract = do awaitTxConfirmed txId logInfo' $ "Tx submitted successfully!" -example :: ConfigParams () -> Effect Unit +example :: ContractParams -> Effect Unit example cfg = launchAff_ do runContract cfg contract diff --git a/examples/MultipleRedeemers.purs b/examples/MultipleRedeemers.purs index 1b6e1cc1e4..6a3445e65c 100644 --- a/examples/MultipleRedeemers.purs +++ b/examples/MultipleRedeemers.purs @@ -99,9 +99,8 @@ contractWithMintRedeemers = do void $ awaitTxConfirmed txHash spendLockedByIntOutputParams - :: forall x - . Tuple Validator Int - -> Contract x + :: Tuple Validator Int + -> Contract ( Tuple (Constraints.TxConstraints Void Void) (Lookups.ScriptLookups Void) ) diff --git a/examples/NativeScriptMints.purs b/examples/NativeScriptMints.purs index 2c0527694f..87bae89ea7 100644 --- a/examples/NativeScriptMints.purs +++ b/examples/NativeScriptMints.purs @@ -9,7 +9,7 @@ import Contract.Address , ownPaymentPubKeysHashes , ownStakePubKeysHashes ) -import Contract.Config (ConfigParams, testnetNamiConfig) +import Contract.Config (ContractParams, testnetNamiConfig) import Contract.Log (logInfo') import Contract.Monad (Contract, launchAff_, liftedM, runContract) import Contract.ScriptLookups as Lookups @@ -79,7 +79,7 @@ toSelfContract cs tn amount = do awaitTxConfirmed txId logInfo' $ "Moved " <> show (BigInt.fromInt 50) <> " to self successfully" -example :: ConfigParams () -> Effect Unit +example :: ContractParams -> Effect Unit example cfg = launchAff_ $ do runContract cfg contract diff --git a/examples/OneShotMinting.purs b/examples/OneShotMinting.purs index 05661aba0d..dc1535e4d0 100644 --- a/examples/OneShotMinting.purs +++ b/examples/OneShotMinting.purs @@ -14,7 +14,7 @@ module Ctl.Examples.OneShotMinting import Contract.Prelude import Contract.Address (Address, getWalletAddresses) -import Contract.Config (ConfigParams, testnetNamiConfig) +import Contract.Config (ContractParams, testnetNamiConfig) import Contract.Log (logInfo') import Contract.Monad ( Contract @@ -54,14 +54,14 @@ import Effect.Exception (error) main :: Effect Unit main = example testnetNamiConfig -example :: ConfigParams () -> Effect Unit +example :: ContractParams -> Effect Unit example cfg = launchAff_ do runContract cfg contract mkAssertions :: Address -> (CurrencySymbol /\ TokenName /\ BigInt) - -> Array (ContractWrapAssertion () { txFinalFee :: BigInt }) + -> Array (ContractWrapAssertion { txFinalFee :: BigInt }) mkAssertions ownAddress nft = let labeledOwnAddress :: Labeled Address diff --git a/examples/Pkh2Pkh.purs b/examples/Pkh2Pkh.purs index a154a30f71..a2a1d756a4 100644 --- a/examples/Pkh2Pkh.purs +++ b/examples/Pkh2Pkh.purs @@ -6,7 +6,7 @@ module Ctl.Examples.Pkh2Pkh (main, contract, example) where import Contract.Prelude import Contract.Address (ownPaymentPubKeysHashes, ownStakePubKeysHashes) -import Contract.Config (ConfigParams, testnetNamiConfig) +import Contract.Config (ContractParams, testnetNamiConfig) import Contract.Log (logInfo') import Contract.Monad (Contract, launchAff_, liftedM, runContract) import Contract.ScriptLookups as Lookups @@ -41,6 +41,6 @@ contract = do awaitTxConfirmedWithTimeout (wrap 100.0) txId logInfo' $ "Tx submitted successfully!" -example :: ConfigParams () -> Effect Unit +example :: ContractParams -> Effect Unit example cfg = launchAff_ do runContract cfg contract diff --git a/examples/PlutusV2/AlwaysSucceeds.purs b/examples/PlutusV2/AlwaysSucceeds.purs index 9844c022c7..70122b3f72 100644 --- a/examples/PlutusV2/AlwaysSucceeds.purs +++ b/examples/PlutusV2/AlwaysSucceeds.purs @@ -5,7 +5,7 @@ module Ctl.Examples.PlutusV2.AlwaysSucceeds (main, example, contract) where import Contract.Prelude -import Contract.Config (ConfigParams, testnetNamiConfig) +import Contract.Config (ContractParams, testnetNamiConfig) import Contract.Log (logInfo') import Contract.Monad ( Contract @@ -36,7 +36,7 @@ contract = do logInfo' "Tx submitted successfully, Try to spend locked values" spendFromAlwaysSucceeds vhash validator txId -example :: ConfigParams () -> Effect Unit +example :: ContractParams -> Effect Unit example cfg = launchAff_ do runContract cfg contract diff --git a/examples/PlutusV2/InlineDatum.purs b/examples/PlutusV2/InlineDatum.purs index dc4920de13..ca6ad6da27 100644 --- a/examples/PlutusV2/InlineDatum.purs +++ b/examples/PlutusV2/InlineDatum.purs @@ -14,7 +14,7 @@ module Ctl.Examples.PlutusV2.InlineDatum import Contract.Prelude import Contract.Address (scriptHashAddress) -import Contract.Config (ConfigParams, testnetNamiConfig) +import Contract.Config (ContractParams, testnetNamiConfig) import Contract.Log (logInfo') import Contract.Monad (Contract, launchAff_, runContract) import Contract.PlutusData @@ -46,7 +46,7 @@ import Test.Spec.Assertions (shouldEqual) main :: Effect Unit main = example testnetNamiConfig -example :: ConfigParams () -> Effect Unit +example :: ContractParams -> Effect Unit example cfg = launchAff_ do runContract cfg do logInfo' "Running Examples.PlutusV2.InlineDatum" diff --git a/examples/PlutusV2/OneShotMinting.purs b/examples/PlutusV2/OneShotMinting.purs index ad4716b9ca..d520c401de 100644 --- a/examples/PlutusV2/OneShotMinting.purs +++ b/examples/PlutusV2/OneShotMinting.purs @@ -11,7 +11,7 @@ module Ctl.Examples.PlutusV2.OneShotMinting import Contract.Prelude -import Contract.Config (ConfigParams, testnetNamiConfig) +import Contract.Config (ContractParams, testnetNamiConfig) import Contract.Monad (Contract, launchAff_, runContract) import Contract.Scripts (MintingPolicy(PlutusMintingPolicy), PlutusScript) import Contract.TextEnvelope @@ -29,7 +29,7 @@ import Effect.Exception (error) main :: Effect Unit main = example testnetNamiConfig -example :: ConfigParams () -> Effect Unit +example :: ContractParams -> Effect Unit example cfg = launchAff_ do runContract cfg contract diff --git a/examples/PlutusV2/ReferenceInputs.purs b/examples/PlutusV2/ReferenceInputs.purs index 39fd1e45e8..a4852b68c3 100644 --- a/examples/PlutusV2/ReferenceInputs.purs +++ b/examples/PlutusV2/ReferenceInputs.purs @@ -8,7 +8,7 @@ import Contract.Address , ownPaymentPubKeysHashes , ownStakePubKeysHashes ) -import Contract.Config (ConfigParams, testnetNamiConfig) +import Contract.Config (ContractParams, testnetNamiConfig) import Contract.Log (logInfo') import Contract.Monad ( Contract @@ -48,7 +48,7 @@ import Data.Set (member) as Set main :: Effect Unit main = example testnetNamiConfig -example :: ConfigParams () -> Effect Unit +example :: ContractParams -> Effect Unit example = launchAff_ <<< flip runContract contract contract :: Contract Unit @@ -93,7 +93,7 @@ type ContractResult = , balancedSignedTx :: BalancedSignedTransaction } -assertTxContainsReferenceInput :: ContractBasicAssertion () ContractResult Unit +assertTxContainsReferenceInput :: ContractBasicAssertion ContractResult Unit assertTxContainsReferenceInput { balancedSignedTx, referenceInput } = let assertionFailure :: ContractAssertionFailure @@ -105,7 +105,7 @@ assertTxContainsReferenceInput { balancedSignedTx, referenceInput } = Set.member referenceInput (unwrap balancedSignedTx ^. _body <<< _referenceInputs) -assertReferenceInputNotSpent :: ContractBasicAssertion () ContractResult Unit +assertReferenceInputNotSpent :: ContractBasicAssertion ContractResult Unit assertReferenceInputNotSpent { ownAddress, referenceInput } = let assertionFailure :: ContractAssertionFailure @@ -117,7 +117,7 @@ assertReferenceInputNotSpent { ownAddress, referenceInput } = TestUtils.assertContract assertionFailure do Map.member referenceInput utxos -assertions :: Array (ContractBasicAssertion () ContractResult Unit) +assertions :: Array (ContractBasicAssertion ContractResult Unit) assertions = [ assertTxContainsReferenceInput , assertReferenceInputNotSpent diff --git a/examples/PlutusV2/ReferenceInputsAndScripts.purs b/examples/PlutusV2/ReferenceInputsAndScripts.purs index 596b14dd75..18a627d4de 100644 --- a/examples/PlutusV2/ReferenceInputsAndScripts.purs +++ b/examples/PlutusV2/ReferenceInputsAndScripts.purs @@ -15,7 +15,7 @@ import Contract.Address , ownStakePubKeysHashes , scriptHashAddress ) -import Contract.Config (ConfigParams, testnetNamiConfig) +import Contract.Config (ContractParams, testnetNamiConfig) import Contract.Log (logInfo') import Contract.Monad ( Contract @@ -65,7 +65,7 @@ import Data.Map (toUnfoldable) as Map main :: Effect Unit main = example testnetNamiConfig -example :: ConfigParams () -> Effect Unit +example :: ContractParams -> Effect Unit example cfg = launchAff_ do runContract cfg contract diff --git a/examples/PlutusV2/ReferenceScripts.purs b/examples/PlutusV2/ReferenceScripts.purs index 983192e476..fd9f3bb7c7 100644 --- a/examples/PlutusV2/ReferenceScripts.purs +++ b/examples/PlutusV2/ReferenceScripts.purs @@ -7,7 +7,7 @@ module Ctl.Examples.PlutusV2.ReferenceScripts import Contract.Prelude import Contract.Address (ownStakePubKeysHashes, scriptHashAddress) -import Contract.Config (ConfigParams, testnetNamiConfig) +import Contract.Config (ContractParams, testnetNamiConfig) import Contract.Credential (Credential(PubKeyCredential)) import Contract.Log (logInfo') import Contract.Monad (Contract, launchAff_, liftContractM, runContract) @@ -38,7 +38,7 @@ import Data.Map (toUnfoldable) as Map main :: Effect Unit main = example testnetNamiConfig -example :: ConfigParams () -> Effect Unit +example :: ContractParams -> Effect Unit example cfg = launchAff_ do runContract cfg contract diff --git a/examples/SatisfiesAnyOf.purs b/examples/SatisfiesAnyOf.purs index 07efebee64..03267b8fa4 100644 --- a/examples/SatisfiesAnyOf.purs +++ b/examples/SatisfiesAnyOf.purs @@ -10,7 +10,7 @@ module Ctl.Examples.SatisfiesAnyOf import Contract.Prelude -import Contract.Config (ConfigParams, testnetNamiConfig) +import Contract.Config (ContractParams, testnetNamiConfig) import Contract.Hashing (datumHash) as Hashing import Contract.Log (logInfo') import Contract.Monad (Contract, launchAff_, liftedE, runContract) @@ -29,7 +29,7 @@ import Effect.Exception (error) main :: Effect Unit main = example testnetNamiConfig -example :: ConfigParams () -> Effect Unit +example :: ContractParams -> Effect Unit example cfg = launchAff_ do runContract cfg do logInfo' "Running Examples.SatisfiesAnyOf" diff --git a/examples/SendsToken.purs b/examples/SendsToken.purs index d8534897df..2f14400aae 100644 --- a/examples/SendsToken.purs +++ b/examples/SendsToken.purs @@ -7,7 +7,7 @@ module Ctl.Examples.SendsToken (main, example, contract) where import Contract.Prelude import Contract.Address (ownPaymentPubKeysHashes, ownStakePubKeysHashes) -import Contract.Config (ConfigParams, testnetNamiConfig) +import Contract.Config (ContractParams, testnetNamiConfig) import Contract.Log (logInfo') import Contract.Monad (Contract, launchAff_, liftedM, runContract) import Contract.ScriptLookups as Lookups @@ -28,7 +28,7 @@ import Data.Array (head) main :: Effect Unit main = example testnetNamiConfig -example :: ConfigParams () -> Effect Unit +example :: ContractParams -> Effect Unit example cfg = launchAff_ do runContract cfg contract diff --git a/examples/SignMultiple.purs b/examples/SignMultiple.purs index c7d3eb1768..f42582258e 100644 --- a/examples/SignMultiple.purs +++ b/examples/SignMultiple.purs @@ -6,7 +6,7 @@ module Ctl.Examples.SignMultiple (example, contract, main) where import Contract.Prelude import Contract.Address (ownPaymentPubKeysHashes, ownStakePubKeysHashes) -import Contract.Config (ConfigParams, testnetNamiConfig) +import Contract.Config (ContractParams, testnetNamiConfig) import Contract.Log (logInfo') import Contract.Monad ( Contract @@ -36,9 +36,9 @@ import Data.UInt (UInt) import Effect.Ref as Ref getLockedInputs - :: forall (r :: Row Type). Contract r (Map TransactionHash (Set UInt)) + :: Contract (Map TransactionHash (Set UInt)) getLockedInputs = do - cache <- asks (_.usedTxOuts <<< _.runtime <<< unwrap) + cache <- asks _.usedTxOuts liftEffect $ Ref.read $ unwrap cache main :: Effect Unit @@ -82,14 +82,13 @@ contract = do where submitAndLog - :: forall (r :: Row Type) - . BalancedSignedTransaction - -> Contract r TransactionHash + :: BalancedSignedTransaction + -> Contract TransactionHash submitAndLog bsTx = do txId <- submit bsTx logInfo' $ "Tx ID: " <> show txId pure txId -example :: ConfigParams () -> Effect Unit +example :: ContractParams -> Effect Unit example cfg = launchAff_ do runContract cfg contract diff --git a/examples/TxChaining.purs b/examples/TxChaining.purs index 0537398140..dfb68f9d20 100644 --- a/examples/TxChaining.purs +++ b/examples/TxChaining.purs @@ -15,7 +15,7 @@ import Contract.BalanceTxConstraints ( BalanceTxConstraintsBuilder , mustUseAdditionalUtxos ) as BalanceTxConstraints -import Contract.Config (ConfigParams, testnetNamiConfig) +import Contract.Config (ContractParams, testnetNamiConfig) import Contract.Log (logInfo') import Contract.Monad (Contract, launchAff_, liftedE, liftedM, runContract) import Contract.PlutusData (PlutusData) @@ -37,7 +37,7 @@ import Data.BigInt as BigInt main :: Effect Unit main = example testnetNamiConfig -example :: ConfigParams () -> Effect Unit +example :: ContractParams -> Effect Unit example cfg = launchAff_ do runContract cfg contract diff --git a/examples/Utxos.purs b/examples/Utxos.purs index de949ef54c..e0254e7792 100644 --- a/examples/Utxos.purs +++ b/examples/Utxos.purs @@ -9,7 +9,7 @@ import Contract.Address , ownPaymentPubKeyHash , ownStakePubKeyHash ) -import Contract.Config (ConfigParams, testnetNamiConfig) +import Contract.Config (ContractParams, testnetNamiConfig) import Contract.Log (logInfo, logInfo') import Contract.Monad ( Contract @@ -46,7 +46,7 @@ import Test.QuickCheck.Gen (randomSampleOne) main :: Effect Unit main = example testnetNamiConfig -example :: ConfigParams () -> Effect Unit +example :: ContractParams -> Effect Unit example = launchAff_ <<< flip runContract contract contract :: Contract Unit diff --git a/examples/Wallet.purs b/examples/Wallet.purs index 212a6377c4..18e7a072da 100644 --- a/examples/Wallet.purs +++ b/examples/Wallet.purs @@ -3,7 +3,7 @@ module Ctl.Examples.Wallet (example, contract) where import Contract.Prelude import Contract.Address (getWalletAddresses, getWalletCollateral) -import Contract.Config (ConfigParams) +import Contract.Config (ContractParams) import Contract.Monad (Contract, launchAff_, runContract) import Contract.Utxos (getWalletBalance, getWalletUtxos) @@ -18,6 +18,6 @@ contract = do log "UTxOs:" log <<< show =<< getWalletUtxos -example :: ConfigParams () -> Effect Unit +example :: ContractParams -> Effect Unit example cfg = launchAff_ $ do runContract cfg contract diff --git a/src/Contract/AuxiliaryData.purs b/src/Contract/AuxiliaryData.purs index 106b6b4a1a..63eaf976db 100644 --- a/src/Contract/AuxiliaryData.purs +++ b/src/Contract/AuxiliaryData.purs @@ -42,19 +42,17 @@ import Effect.Class (liftEffect) -- later on - see Types.ScriptLookups for more detail. setAuxiliaryData - :: forall (r :: Row Type) - . UnattachedUnbalancedTx + :: UnattachedUnbalancedTx -> AuxiliaryData - -> Contract r UnattachedUnbalancedTx + -> Contract UnattachedUnbalancedTx setAuxiliaryData tx auxData = liftEffect do auxDataHash <- hashAuxiliaryData auxData pure (tx # _auxiliaryData ?~ auxData # _auxiliaryDataHash ?~ auxDataHash) setGeneralTxMetadata - :: forall (r :: Row Type) - . UnattachedUnbalancedTx + :: UnattachedUnbalancedTx -> GeneralTransactionMetadata - -> Contract r UnattachedUnbalancedTx + -> Contract UnattachedUnbalancedTx setGeneralTxMetadata tx generalMetadata = let auxData = fromMaybe mempty (view _auxiliaryData tx) @@ -62,11 +60,11 @@ setGeneralTxMetadata tx generalMetadata = setAuxiliaryData tx (auxData # _metadata ?~ generalMetadata) setTxMetadata - :: forall (r :: Row Type) (m :: Type) + :: forall (m :: Type) . MetadataType m => UnattachedUnbalancedTx -> m - -> Contract r UnattachedUnbalancedTx + -> Contract UnattachedUnbalancedTx setTxMetadata tx = setGeneralTxMetadata tx <<< toGeneralTxMetadata diff --git a/src/Contract/Monad.purs b/src/Contract/Monad.purs index 1e0ca44a64..e2032855d7 100644 --- a/src/Contract/Monad.purs +++ b/src/Contract/Monad.purs @@ -11,19 +11,23 @@ module Contract.Monad , liftedE' , liftedM , throwContractError + , mkContractEnv + , stopContractEnv ) where import Prelude import Ctl.Internal.Contract.Monad (Contract) +import Ctl.Internal.Contract.Monad + ( mkContractEnv + , stopContractEnv + ) as Contract import Ctl.Internal.Contract.Monad ( Contract(Contract) , ContractEnv , ContractParams - , mkContractEnv , runContract , runContractInEnv - , stopContractEnv , withContractEnv ) as ExportContract import Data.Either (Either, either, hush) @@ -41,7 +45,33 @@ import Effect.Aff (Aff) import Effect.Aff (Aff, launchAff_) as ExportAff import Effect.Aff.Class (liftAff) import Effect.Class (liftEffect) +import Effect (Effect) import Effect.Exception (throw) +import Prim.TypeError (class Warn, Text) +import Ctl.Internal.Contract.Monad (ContractParams, ContractEnv) + +-- | Initializes a `Contract` environment. Does not ensure finalization. +-- | Consider using `withContractEnv` if possible - otherwise use +-- | `stopContractEnv` to properly finalize. +mkContractEnv + :: Warn + ( Text + "Using `mkContractEnv` is not recommended: it does not ensure `ContractEnv` finalization. Consider using `withContractEnv`" + ) + => ContractParams + -> Aff ContractEnv +mkContractEnv = Contract.mkContractEnv + +-- | Finalizes a `Contract` environment. +-- | Closes the websockets in `ContractEnv`, effectively making it unusable. +stopContractEnv + :: Warn + ( Text + "Using `stopContractEnv` is not recommended: users should rely on `withContractEnv` to finalize the runtime environment instead" + ) + => ContractEnv + -> Effect Unit +stopContractEnv = Contract.stopContractEnv -- | Same as `liftContractM` but the `Maybe` value is in the `Aff` context. liftContractAffM :: forall (a :: Type). String -> Aff (Maybe a) -> Contract a diff --git a/src/Contract/ScriptLookups.purs b/src/Contract/ScriptLookups.purs index 3d34b333bf..1401ada05d 100644 --- a/src/Contract/ScriptLookups.purs +++ b/src/Contract/ScriptLookups.purs @@ -16,7 +16,7 @@ module Contract.ScriptLookups import Prelude -import Contract.Monad (Contract, wrapContract) +import Contract.Monad (Contract) import Ctl.Internal.IsData (class IsData) import Ctl.Internal.Types.ScriptLookups ( MkUnbalancedTxError @@ -75,28 +75,28 @@ import Data.Maybe (Maybe) -- | a separate call. In particular, this should be called in conjuction with -- | `balanceTx` and `signTransaction`. mkUnbalancedTx - :: forall (r :: Row Type) (validator :: Type) (datum :: Type) + :: forall (validator :: Type) (datum :: Type) (redeemer :: Type) . ValidatorTypes validator datum redeemer => IsData datum => IsData redeemer => ScriptLookups.ScriptLookups validator -> TxConstraints redeemer datum - -> Contract r + -> Contract ( Either ScriptLookups.MkUnbalancedTxError ScriptLookups.UnattachedUnbalancedTx ) -mkUnbalancedTx lookups = wrapContract <<< SL.mkUnbalancedTx lookups +mkUnbalancedTx = SL.mkUnbalancedTx -- | Same as `mkUnbalancedTx` but hushes the error. mkUnbalancedTxM - :: forall (r :: Row Type) (validator :: Type) (datum :: Type) + :: forall (validator :: Type) (datum :: Type) (redeemer :: Type) . ValidatorTypes validator datum redeemer => IsData datum => IsData redeemer => ScriptLookups.ScriptLookups validator -> TxConstraints redeemer datum - -> Contract r (Maybe ScriptLookups.UnattachedUnbalancedTx) + -> Contract (Maybe ScriptLookups.UnattachedUnbalancedTx) mkUnbalancedTxM lookups = map hush <<< mkUnbalancedTx lookups diff --git a/src/Contract/Test/Utils.purs b/src/Contract/Test/Utils.purs index 6d636cca94..6f6309e23d 100644 --- a/src/Contract/Test/Utils.purs +++ b/src/Contract/Test/Utils.purs @@ -106,8 +106,8 @@ import Type.Proxy (Proxy(Proxy)) -- | Monad allowing for accumulation of assertion failures. Should be used in -- | conjunction with `ContractAssertionM`. -type ContractTestM (r :: Row Type) (a :: Type) = - WriterT (Array ContractAssertionFailure) (Contract r) a +type ContractTestM (a :: Type) = + WriterT (Array ContractAssertionFailure) Contract a -- | Represents computations which may fail with `ContractAssertionFailure`, -- | with the capability of storing some intermediate result, usually the result @@ -117,20 +117,20 @@ type ContractTestM (r :: Row Type) (a :: Type) = -- | run (`ContractWrapAssertion`s). So in case of a failure after the contract -- | has already been executed, we can return the result of the contract, thus -- | preventing the failure of subsequent assertions. -type ContractAssertionM (r :: Row Type) (w :: Type) (a :: Type) = +type ContractAssertionM (w :: Type) (a :: Type) = -- ExceptT ContractAssertionFailure - -- (Writer (Maybe (Last w)) (ContractTestM r)) a + -- (Writer (Maybe (Last w)) (ContractTestM)) a ExceptT ContractAssertionFailure ( WriterT (Maybe (Last w)) - (WriterT (Array ContractAssertionFailure) (Contract r)) + (WriterT (Array ContractAssertionFailure) (Contract)) ) a runContractAssertionM - :: forall (r :: Row Type) (a :: Type) - . ContractTestM r a - -> ContractAssertionM r a a - -> ContractTestM r a + :: forall (a :: Type) + . ContractTestM a + -> ContractAssertionM a a + -> ContractTestM a runContractAssertionM contract wrappedContract = runWriterT (runExceptT wrappedContract) >>= case _ of Right result /\ _ -> @@ -139,15 +139,14 @@ runContractAssertionM contract wrappedContract = tell [ failure ] *> maybe contract (pure <<< unwrap) result runContractAssertionM' - :: forall (r :: Row Type) - . ContractAssertionM r Unit Unit - -> ContractTestM r Unit + :: ContractAssertionM Unit Unit + -> ContractTestM Unit runContractAssertionM' = runContractAssertionM (pure unit) liftContractTestM - :: forall (r :: Row Type) (w :: Type) (a :: Type) - . ContractTestM r a - -> ContractAssertionM r w a + :: forall (w :: Type) (a :: Type) + . ContractTestM a + -> ContractAssertionM w a liftContractTestM = lift <<< lift -------------------------------------------------------------------------------- @@ -243,88 +242,88 @@ instance Show a => Show (ExpectedActual a) where -------------------------------------------------------------------------------- -- | An assertion that only needs the result of the contract. -type ContractBasicAssertion (r :: Row Type) (a :: Type) (b :: Type) = - a -> ContractTestM r b +type ContractBasicAssertion (a :: Type) (b :: Type) = + a -> ContractTestM b -- | An assertion that can control when the contract is run. The assertion -- | inhabiting this type should not call the contract more than once, as other -- | assertions need to be able to make this assumption to succesfully compose. -type ContractWrapAssertion (r :: Row Type) (a :: Type) = - ContractTestM r a -> ContractTestM r a +type ContractWrapAssertion (a :: Type) = + ContractTestM a -> ContractTestM a -- | Class to unify different methods of making assertions about a contract -- | under a single interface. Note that the typechecker may need some help when -- | using this class; try providing type annotations for your assertions using -- | the type aliases for the instances of this class. -class ContractAssertions (f :: Type) (r :: Row Type) (a :: Type) where +class ContractAssertions (f :: Type) (a :: Type) where -- | Wrap a contract in an assertion. The wrapped contract itself becomes a -- | contract which can be wrapped, allowing for composition of assertions. -- | -- | No guarantees are made about the order in which assertions are made. -- | Assertions with side effects should not be used. - wrapAndAssert :: ContractTestM r a -> f -> ContractTestM r a + wrapAndAssert :: ContractTestM a -> f -> ContractTestM a -instance ContractAssertions (ContractWrapAssertion r a) r a where +instance ContractAssertions (ContractWrapAssertion a) a where wrapAndAssert contract assertion = assertion contract -else instance ContractAssertions (ContractBasicAssertion r a b) r a where +else instance ContractAssertions (ContractBasicAssertion a b) a where wrapAndAssert contract assertion = contract >>= \r -> assertion r *> pure r -instance ContractAssertions (Array (ContractWrapAssertion r a)) r a where +instance ContractAssertions (Array (ContractWrapAssertion a)) a where wrapAndAssert contract assertions = ala Endo foldMap assertions contract else instance - ContractAssertions (Array (ContractBasicAssertion r a b)) r a where + ContractAssertions (Array (ContractBasicAssertion a b)) a where wrapAndAssert contract assertions = contract >>= \r -> traverse_ (_ $ r) assertions *> pure r instance - ( ContractAssertions f r a - , ContractAssertions g r a + ( ContractAssertions f a + , ContractAssertions g a ) => - ContractAssertions (f /\ g) r a where + ContractAssertions (f /\ g) a where wrapAndAssert contract (assertionsX /\ assertionsY) = wrapAndAssert (wrapAndAssert contract assertionsX) assertionsY assertContract - :: forall (r :: Row Type) (w :: Type) + :: forall (w :: Type) . ContractAssertionFailure -> Boolean - -> ContractAssertionM r w Unit + -> ContractAssertionM w Unit assertContract failure cond | cond = pure unit | otherwise = except (Left failure) assertContractM' - :: forall (r :: Row Type) (w :: Type) (a :: Type) + :: forall (w :: Type) (a :: Type) . ContractAssertionFailure -> Maybe a - -> ContractAssertionM r w a + -> ContractAssertionM w a assertContractM' msg = maybe (except $ Left msg) pure assertContractM - :: forall (r :: Row Type) (w :: Type) (a :: Type) + :: forall (w :: Type) (a :: Type) . ContractAssertionFailure - -> Contract r (Maybe a) - -> ContractAssertionM r w a + -> Contract (Maybe a) + -> ContractAssertionM w a assertContractM msg cm = liftContractTestM (lift cm) >>= assertContractM' msg assertContractExpectedActual - :: forall (r :: Row Type) (w :: Type) (a :: Type) + :: forall (w :: Type) (a :: Type) . Eq a => (ExpectedActual a -> ContractAssertionFailure) -> a -> a - -> ContractAssertionM r w Unit + -> ContractAssertionM w Unit assertContractExpectedActual mkAssertionFailure expected actual = assertContract (mkAssertionFailure $ ExpectedActual expected actual) (expected == actual) withAssertions - :: forall (r :: Row Type) (a :: Type) (assertions :: Type) - . ContractAssertions assertions r a + :: forall (a :: Type) (assertions :: Type) + . ContractAssertions assertions a => assertions - -> Contract r a - -> Contract r a + -> Contract a + -> Contract a withAssertions assertions contract = do result /\ failures <- runWriterT $ wrapAndAssert (lift contract) assertions @@ -332,9 +331,9 @@ withAssertions assertions contract = do else throwContractError (ContractAssertionFailures failures) mkCheckFromAssertion - :: forall (r :: Row Type) (w :: Type) (a :: Type) - . ContractAssertionM r w a - -> Contract r Boolean + :: forall (w :: Type) (a :: Type) + . ContractAssertionM w a + -> Contract Boolean mkCheckFromAssertion = map (fst <<< fst) <<< runWriterT <<< runWriterT <<< map isRight <<< runExceptT @@ -343,24 +342,24 @@ mkCheckFromAssertion = -------------------------------------------------------------------------------- utxosAtAddress - :: forall (r :: Row Type) (w :: Type) + :: forall (w :: Type) . Labeled Address - -> ContractAssertionM r w UtxoMap + -> ContractAssertionM w UtxoMap utxosAtAddress = liftContractTestM <<< lift <<< utxosAt <<< unlabel valueAtAddress - :: forall (r :: Row Type) (w :: Type) + :: forall (w :: Type) . Labeled Address - -> ContractAssertionM r w Value + -> ContractAssertionM w Value valueAtAddress = map (foldMap (view (_output <<< _amount))) <<< utxosAtAddress checkBalanceDeltaAtAddress - :: forall (r :: Row Type) (w :: Type) (a :: Type) + :: forall (w :: Type) (a :: Type) . Labeled Address - -> ContractTestM r w - -> (w -> Value -> Value -> ContractAssertionM r w a) - -> ContractAssertionM r w a + -> ContractTestM w + -> (w -> Value -> Value -> ContractAssertionM w a) + -> ContractAssertionM w a checkBalanceDeltaAtAddress addr contract check = do valueBefore <- valueAtAddress addr res <- liftContractTestM contract @@ -369,22 +368,22 @@ checkBalanceDeltaAtAddress addr contract check = do check res valueBefore valueAfter checkNewUtxosAtAddress - :: forall (r :: Row Type) (w :: Type) (a :: Type) + :: forall (w :: Type) (a :: Type) . Labeled Address -> TransactionHash - -> (Array TransactionOutputWithRefScript -> ContractAssertionM r w a) - -> ContractAssertionM r w a + -> (Array TransactionOutputWithRefScript -> ContractAssertionM w a) + -> ContractAssertionM w a checkNewUtxosAtAddress addr txHash check = utxosAtAddress addr >>= \utxos -> check $ Array.fromFoldable $ Map.values $ Map.filterKeys (\oref -> (unwrap oref).transactionId == txHash) utxos assertLovelaceDeltaAtAddress - :: forall (r :: Row Type) (a :: Type) + :: forall (a :: Type) . Labeled Address - -> (a -> Contract r BigInt) + -> (a -> Contract BigInt) -> (BigInt -> BigInt -> Boolean) - -> ContractWrapAssertion r a + -> ContractWrapAssertion a assertLovelaceDeltaAtAddress addr getExpected comp contract = runContractAssertionM contract $ checkBalanceDeltaAtAddress addr contract @@ -404,50 +403,50 @@ assertLovelaceDeltaAtAddress addr getExpected comp contract = -- | Requires that the computed amount of lovelace was gained at the address -- | by calling the contract. assertGainAtAddress - :: forall (r :: Row Type) (a :: Type) + :: forall (a :: Type) . Labeled Address - -> (a -> Contract r BigInt) - -> ContractWrapAssertion r a + -> (a -> Contract BigInt) + -> ContractWrapAssertion a assertGainAtAddress addr getMinGain = assertLovelaceDeltaAtAddress addr getMinGain eq -- | Requires that the passed amount of lovelace was gained at the address -- | by calling the contract. assertGainAtAddress' - :: forall (r :: Row Type) (a :: Type) + :: forall (a :: Type) . Labeled Address -> BigInt - -> ContractWrapAssertion r a + -> ContractWrapAssertion a assertGainAtAddress' addr minGain = assertGainAtAddress addr (const $ pure minGain) -- | Requires that the computed amount of lovelace was lost at the address -- | by calling the contract. assertLossAtAddress - :: forall (r :: Row Type) (a :: Type) + :: forall (a :: Type) . Labeled Address - -> (a -> Contract r BigInt) - -> ContractWrapAssertion r a + -> (a -> Contract BigInt) + -> ContractWrapAssertion a assertLossAtAddress addr getMinLoss = assertLovelaceDeltaAtAddress addr (map negate <<< getMinLoss) eq -- | Requires that the passed amount of lovelace was lost at the address -- | by calling the contract. assertLossAtAddress' - :: forall (r :: Row Type) (a :: Type) + :: forall (a :: Type) . Labeled Address -> BigInt - -> ContractWrapAssertion r a + -> ContractWrapAssertion a assertLossAtAddress' addr minLoss = assertLossAtAddress addr (const $ pure minLoss) assertTokenDeltaAtAddress - :: forall (r :: Row Type) (a :: Type) + :: forall (a :: Type) . Labeled Address -> (CurrencySymbol /\ TokenName) - -> (a -> Contract r BigInt) + -> (a -> Contract BigInt) -> (BigInt -> BigInt -> Boolean) - -> ContractWrapAssertion r a + -> ContractWrapAssertion a assertTokenDeltaAtAddress addr (cs /\ tn) getExpected comp contract = runContractAssertionM contract $ checkBalanceDeltaAtAddress addr contract @@ -467,50 +466,49 @@ assertTokenDeltaAtAddress addr (cs /\ tn) getExpected comp contract = -- | Requires that the computed number of tokens was gained at the address -- | by calling the contract. assertTokenGainAtAddress - :: forall (r :: Row Type) (a :: Type) + :: forall (a :: Type) . Labeled Address -> (CurrencySymbol /\ TokenName) - -> (a -> Contract r BigInt) - -> ContractWrapAssertion r a + -> (a -> Contract BigInt) + -> ContractWrapAssertion a assertTokenGainAtAddress addr token getMinGain = assertTokenDeltaAtAddress addr token getMinGain eq -- | Requires that the passed number of tokens was gained at the address -- | by calling the contract. assertTokenGainAtAddress' - :: forall (r :: Row Type) (a :: Type) + :: forall (a :: Type) . Labeled Address -> (CurrencySymbol /\ TokenName /\ BigInt) - -> ContractWrapAssertion r a + -> ContractWrapAssertion a assertTokenGainAtAddress' addr (cs /\ tn /\ minGain) = assertTokenGainAtAddress addr (cs /\ tn) (const $ pure minGain) -- | Requires that the computed number of tokens was lost at the address -- | by calling the contract. assertTokenLossAtAddress - :: forall (r :: Row Type) (a :: Type) + :: forall (a :: Type) . Labeled Address -> (CurrencySymbol /\ TokenName) - -> (a -> Contract r BigInt) - -> ContractWrapAssertion r a + -> (a -> Contract BigInt) + -> ContractWrapAssertion a assertTokenLossAtAddress addr token getMinLoss = assertTokenDeltaAtAddress addr token (map negate <<< getMinLoss) eq -- | Requires that the passed number of tokens was lost at the address -- | by calling the contract. assertTokenLossAtAddress' - :: forall (r :: Row Type) (a :: Type) + :: forall (a :: Type) . Labeled Address -> (CurrencySymbol /\ TokenName /\ BigInt) - -> ContractWrapAssertion r a + -> ContractWrapAssertion a assertTokenLossAtAddress' addr (cs /\ tn /\ minLoss) = assertTokenLossAtAddress addr (cs /\ tn) (const $ pure minLoss) assertOutputHasDatumImpl - :: forall (r :: Row Type) - . OutputDatum + :: OutputDatum -> Labeled TransactionOutputWithRefScript - -> ContractAssertionM r Unit Unit + -> ContractAssertionM Unit Unit assertOutputHasDatumImpl expectedDatum txOutput = do let actualDatum = unlabel txOutput ^. _output <<< _datum assertContractExpectedActual (UnexpectedDatumInOutput txOutput) @@ -520,29 +518,26 @@ assertOutputHasDatumImpl expectedDatum txOutput = do -- | Requires that the transaction output contains the specified datum or -- | datum hash. assertOutputHasDatum - :: forall (r :: Row Type) - . OutputDatum + :: OutputDatum -> Labeled TransactionOutputWithRefScript - -> ContractTestM r Unit + -> ContractTestM Unit assertOutputHasDatum expectedDatum = runContractAssertionM' <<< assertOutputHasDatumImpl expectedDatum -- | Checks whether the transaction output contains the specified datum or -- | datum hash. checkOutputHasDatum - :: forall (r :: Row Type) - . OutputDatum + :: OutputDatum -> TransactionOutputWithRefScript - -> Contract r Boolean + -> Contract Boolean checkOutputHasDatum expectedDatum txOutput = mkCheckFromAssertion $ assertOutputHasDatumImpl expectedDatum (noLabel txOutput) assertOutputHasRefScriptImpl - :: forall (r :: Row Type) - . ScriptRef + :: ScriptRef -> Labeled TransactionOutputWithRefScript - -> ContractAssertionM r Unit Unit + -> ContractAssertionM Unit Unit assertOutputHasRefScriptImpl expectedRefScript txOutput = do let actualRefScript = unlabel txOutput ^. _scriptRef assertContractExpectedActual (UnexpectedRefScriptInOutput txOutput) @@ -552,33 +547,31 @@ assertOutputHasRefScriptImpl expectedRefScript txOutput = do -- | Requires that the transaction output contains the specified reference -- | script. assertOutputHasRefScript - :: forall (r :: Row Type) - . ScriptRef + :: ScriptRef -> Labeled TransactionOutputWithRefScript - -> ContractTestM r Unit + -> ContractTestM Unit assertOutputHasRefScript expectedRefScript = runContractAssertionM' <<< assertOutputHasRefScriptImpl expectedRefScript -- | Checks whether the transaction output contains the specified reference -- | script. checkOutputHasRefScript - :: forall (r :: Row Type) - . ScriptRef + :: ScriptRef -> TransactionOutputWithRefScript - -> Contract r Boolean + -> Contract Boolean checkOutputHasRefScript expectedRefScript txOutput = mkCheckFromAssertion $ assertOutputHasRefScriptImpl expectedRefScript (noLabel txOutput) assertTxHasMetadataImpl - :: forall (r :: Row Type) (a :: Type) + :: forall (a :: Type) . MetadataType a => Eq a => Show a => Label -> TransactionHash -> a - -> ContractAssertionM r Unit Unit + -> ContractAssertionM Unit Unit assertTxHasMetadataImpl mdLabel txHash expectedMetadata = do Transaction { auxiliaryData } <- assertContractM (CouldNotGetTxByHash txHash) (getTxByHash txHash) @@ -601,25 +594,25 @@ assertTxHasMetadataImpl mdLabel txHash expectedMetadata = do -- | Requires that the transaction contains the specified metadata. assertTxHasMetadata - :: forall (r :: Row Type) (a :: Type) + :: forall (a :: Type) . MetadataType a => Eq a => Show a => Label -> TransactionHash -> a - -> ContractTestM r Unit + -> ContractTestM Unit assertTxHasMetadata mdLabel txHash = runContractAssertionM' <<< assertTxHasMetadataImpl mdLabel txHash -- | Checks whether the transaction contains the specified metadata. checkTxHasMetadata - :: forall (r :: Row Type) (a :: Type) + :: forall (a :: Type) . MetadataType a => Eq a => Show a => TransactionHash -> a - -> Contract r Boolean + -> Contract Boolean checkTxHasMetadata txHash = mkCheckFromAssertion <<< assertTxHasMetadataImpl mempty txHash diff --git a/src/Contract/Time.purs b/src/Contract/Time.purs index 8f251e1b89..6d978614ad 100644 --- a/src/Contract/Time.purs +++ b/src/Contract/Time.purs @@ -3,6 +3,8 @@ module Contract.Time ( getCurrentEpoch , getEraSummaries , getSystemStart + , getSlotLength + , getSlotReference , module Chain , module ExportOgmios , module Interval @@ -24,7 +26,6 @@ import Contract.Chain import Contract.Monad (Contract) import Ctl.Internal.Cardano.Types.Transaction (Epoch(Epoch)) import Ctl.Internal.Helpers (liftM) -import Ctl.Internal.QueryM.CurrentEpoch (getCurrentEpoch) as CurrentEpoch import Ctl.Internal.QueryM.EraSummaries (getEraSummaries) as EraSummaries import Ctl.Internal.QueryM.Ogmios ( CurrentEpoch(CurrentEpoch) @@ -41,8 +42,10 @@ import Ctl.Internal.QueryM.Ogmios ( CurrentEpoch(CurrentEpoch) , EraSummaries , SystemStart + , SlotLength + , RelativeTime ) -import Ctl.Internal.QueryM.SystemStart (getSystemStart) as SystemStart +import Ctl.Internal.Serialization.Address (Slot) import Ctl.Internal.Serialization.Address (BlockId(BlockId), Slot(Slot)) as SerializationAddress import Ctl.Internal.Types.Interval ( AbsTime(AbsTime) @@ -121,3 +124,11 @@ getEraSummaries = wrapQueryM EraSummaries.getEraSummaries getSystemStart :: Contract SystemStart getSystemStart = do asks $ _.ledgerConstants >>> _.systemStart + +getSlotLength :: Contract SlotLength +getSlotLength = do + asks $ _.ledgerConstants >>> _.slotLength + +getSlotReference :: Contract { slot :: Slot, time :: RelativeTime } +getSlotReference = do + asks $ _.ledgerConstants >>> _.slotReference diff --git a/src/Contract/Transaction.purs b/src/Contract/Transaction.purs index c4d88874aa..0a486338ae 100644 --- a/src/Contract/Transaction.purs +++ b/src/Contract/Transaction.purs @@ -11,7 +11,6 @@ module Contract.Transaction , balanceTxsWithConstraints , balanceTxM , calculateMinFee - , calculateMinFeeM , createAdditionalUtxos , getTxByHash , getTxFinalFee @@ -41,15 +40,15 @@ module Contract.Transaction import Prelude +import Contract.Prelude (undefined) import Aeson (class EncodeAeson, Aeson) -import Contract.Log (logDebug') +import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Contract.Monad ( Contract , liftContractM , liftedE , liftedM , runContractInEnv - , wrapContract ) import Control.Monad.Error.Class (catchError, throwError) import Control.Monad.Reader (ReaderT, asks, runReaderT) @@ -173,22 +172,18 @@ import Ctl.Internal.QueryM , ClientOtherError ) ) as ExportQueryM -import Ctl.Internal.QueryM (submitTxOgmios) as QueryM import Ctl.Internal.Contract.AwaitTxConfirmed ( awaitTxConfirmed , awaitTxConfirmedWithTimeout , awaitTxConfirmedWithTimeoutSlots ) as Contract -import Ctl.Internal.QueryM.GetTxByHash (getTxByHash) as QueryM -import Ctl.Internal.QueryM.MinFee (calculateMinFee) as QueryM -import Ctl.Internal.QueryM.Ogmios (SubmitTxR(SubmitTxSuccess, SubmitFail)) -import Ctl.Internal.QueryM.Sign (signTransaction) as QueryM +import Ctl.Internal.Contract.MinFee (calculateMinFee) as Contract +import Ctl.Internal.Contract.Sign (signTransaction) as Contract import Ctl.Internal.ReindexRedeemers ( ReindexErrors(CannotGetTxOutRefIndexForRedeemer) ) as ReindexRedeemersExport import Ctl.Internal.ReindexRedeemers (reindexSpentScriptRedeemers) as ReindexRedeemers import Ctl.Internal.Serialization (convertTransaction) -import Ctl.Internal.Serialization (convertTransaction, toBytes) as Serialization import Ctl.Internal.Types.OutputDatum ( OutputDatum(NoOutputDatum, OutputDatumHash, OutputDatum) , outputDatumDataHash @@ -262,13 +257,13 @@ import Ctl.Internal.Types.VRFKeyHash ) as X import Data.Array.NonEmpty as NonEmptyArray import Data.BigInt (BigInt) -import Data.Either (Either(Left, Right), hush) +import Data.Either (Either, hush) import Data.Foldable (foldl, length) import Data.Generic.Rep (class Generic) import Data.Lens.Getter (view) import Data.Map (empty, insert) as Map import Data.Maybe (Maybe) -import Data.Newtype (class Newtype, unwrap, wrap) +import Data.Newtype (class Newtype, unwrap) import Data.Show.Generic (genericShow) import Data.Time.Duration (Seconds) import Data.Traversable (class Traversable, for_, traverse) @@ -278,90 +273,65 @@ import Data.UInt (UInt) import Effect.Aff (bracket) import Effect.Aff.Class (liftAff) import Effect.Class (liftEffect) -import Effect.Exception (throw) -import Untagged.Union (asOneOf) -- | Signs a transaction with potential failure. signTransaction - :: forall (tx :: Type) (r :: Row Type) + :: forall (tx :: Type) . Newtype tx Transaction => tx - -> Contract r BalancedSignedTransaction + -> Contract BalancedSignedTransaction signTransaction = map BalancedSignedTransaction <<< liftedM "Error signing the transaction" - <<< wrapContract - <<< QueryM.signTransaction + <<< Contract.signTransaction <<< unwrap -- | Submits a `BalancedSignedTransaction`, which is the output of -- | `signTransaction`. submit - :: forall (r :: Row Type) - . BalancedSignedTransaction - -> Contract r TransactionHash + :: BalancedSignedTransaction + -> Contract TransactionHash submit tx = do - result <- submitE tx - case result of - Right th -> pure th - Left json -> liftEffect $ throw $ - "`submit` call failed. Error from Ogmios: " <> show json + queryHandle <- getQueryHandle + liftedM "Failed to submit tx" $ liftAff $ queryHandle.submitTx $ unwrap tx -- | Like `submit` except when Ogmios sends a SubmitFail the error is returned -- | as an Array of Aesons. submitE - :: forall (r :: Row Type) - . BalancedSignedTransaction - -> Contract r (Either (Array Aeson) TransactionHash) -submitE tx = do - cslTx <- liftEffect $ Serialization.convertTransaction (unwrap tx) - let txHash = Hashing.transactionHash cslTx - logDebug' $ "Pre-calculated tx hash: " <> show txHash - let txCborBytes = wrap $ Serialization.toBytes $ asOneOf cslTx - result <- wrapContract $ - QueryM.submitTxOgmios (unwrap txHash) txCborBytes - pure $ case result of - SubmitTxSuccess th -> Right $ wrap th - SubmitFail json -> Left json - --- | Query the Haskell server for the minimum transaction fee. + :: BalancedSignedTransaction + -> Contract (Either (Array Aeson) TransactionHash) +submitE tx = -- TODO + undefined + +-- | Calculate the minimum transaction fee. calculateMinFee - :: forall (r :: Row Type) - . Transaction + :: Transaction -> UtxoMap - -> Contract r (Either ExportQueryM.ClientError Coin) + -> Contract Coin calculateMinFee tx additionalUtxos = do - networkId <- asks $ unwrap >>> _.config >>> _.networkId + networkId <- asks _.networkId let additionalUtxos' = fromPlutusUtxoMap networkId additionalUtxos - map (pure <<< toPlutusCoin) - (wrapContract $ QueryM.calculateMinFee tx additionalUtxos') - --- | Same as `calculateMinFee` hushing the error. -calculateMinFeeM - :: forall (r :: Row Type). Transaction -> UtxoMap -> Contract r (Maybe Coin) -calculateMinFeeM tx additionalUtxos = - map hush $ calculateMinFee tx additionalUtxos + toPlutusCoin <$> Contract.calculateMinFee tx additionalUtxos' -- | Helper to adapt to UsedTxOuts. withUsedTxOuts - :: forall (r :: Row Type) (a :: Type) - . ReaderT UsedTxOuts (Contract r) a - -> Contract r a -withUsedTxOuts f = asks (_.usedTxOuts <<< _.runtime <<< unwrap) >>= runReaderT f + :: forall (a :: Type) + . ReaderT UsedTxOuts Contract a + -> Contract a +withUsedTxOuts f = asks _.usedTxOuts >>= runReaderT f -- Helper to avoid repetition. withTransactions :: forall (a :: Type) (t :: Type -> Type) - (r :: Row Type) (ubtx :: Type) (tx :: Type) . Traversable t - => (t ubtx -> Contract r (t tx)) + => (t ubtx -> Contract (t tx)) -> (tx -> Transaction) -> t ubtx - -> (t tx -> Contract r a) - -> Contract r a + -> (t tx -> Contract a) + -> Contract a withTransactions prepare extract utxs action = do env <- ask let @@ -376,12 +346,12 @@ withTransactions prepare extract utxs action = do (withUsedTxOuts <<< unlockTransactionInputs <<< extract) withSingleTransaction - :: forall (a :: Type) (ubtx :: Type) (tx :: Type) (r :: Row Type) - . (ubtx -> Contract r tx) + :: forall (a :: Type) (ubtx :: Type) (tx :: Type) + . (ubtx -> Contract tx) -> (tx -> Transaction) -> ubtx - -> (tx -> Contract r a) - -> Contract r a + -> (tx -> Contract a) + -> Contract a withSingleTransaction prepare extract utx action = withTransactions (traverse prepare) extract (NonEmptyArray.singleton utx) (action <<< NonEmptyArray.head) @@ -394,20 +364,20 @@ withSingleTransaction prepare extract utx action = -- | After the function completes, the locks will be removed. -- | Errors will be thrown. withBalancedTxsWithConstraints - :: forall (a :: Type) (r :: Row Type) + :: forall (a :: Type) . Array (UnattachedUnbalancedTx /\ BalanceTxConstraintsBuilder) - -> (Array FinalizedTransaction -> Contract r a) - -> Contract r a + -> (Array FinalizedTransaction -> Contract a) + -> Contract a withBalancedTxsWithConstraints = withTransactions balanceTxsWithConstraints unwrap -- | Same as `withBalancedTxsWithConstraints`, but uses the default balancer -- | constraints. withBalancedTxs - :: forall (a :: Type) (r :: Row Type) + :: forall (a :: Type) . Array UnattachedUnbalancedTx - -> (Array FinalizedTransaction -> Contract r a) - -> Contract r a + -> (Array FinalizedTransaction -> Contract a) + -> Contract a withBalancedTxs = withTransactions balanceTxs unwrap -- | Execute an action on a balanced transaction (`balanceTx` will @@ -417,11 +387,11 @@ withBalancedTxs = withTransactions balanceTxs unwrap -- | After the function completes, the locks will be removed. -- | Errors will be thrown. withBalancedTxWithConstraints - :: forall (a :: Type) (r :: Row Type) + :: forall (a :: Type) . UnattachedUnbalancedTx -> BalanceTxConstraintsBuilder - -> (FinalizedTransaction -> Contract r a) - -> Contract r a + -> (FinalizedTransaction -> Contract a) + -> Contract a withBalancedTxWithConstraints unbalancedTx = withSingleTransaction balanceAndLockWithConstraints unwrap <<< Tuple unbalancedTx @@ -429,42 +399,40 @@ withBalancedTxWithConstraints unbalancedTx = -- | Same as `withBalancedTxWithConstraints`, but uses the default balancer -- | constraints. withBalancedTx - :: forall (a :: Type) (r :: Row Type) + :: forall (a :: Type) . UnattachedUnbalancedTx - -> (FinalizedTransaction -> Contract r a) - -> Contract r a + -> (FinalizedTransaction -> Contract a) + -> Contract a withBalancedTx = withSingleTransaction balanceAndLock unwrap -- | Attempts to balance an `UnattachedUnbalancedTx` using the specified -- | balancer constraints. balanceTxWithConstraints - :: forall (r :: Row Type) - . UnattachedUnbalancedTx + :: UnattachedUnbalancedTx -> BalanceTxConstraintsBuilder - -> Contract r (Either BalanceTxError.BalanceTxError FinalizedTransaction) -balanceTxWithConstraints unbalancedTx = - wrapContract <<< BalanceTx.balanceTxWithConstraints unbalancedTx + -> Contract (Either BalanceTxError.BalanceTxError FinalizedTransaction) +balanceTxWithConstraints = + BalanceTx.balanceTxWithConstraints -- | Same as `balanceTxWithConstraints`, but uses the default balancer -- | constraints. balanceTx - :: forall (r :: Row Type) - . UnattachedUnbalancedTx - -> Contract r (Either BalanceTxError.BalanceTxError FinalizedTransaction) + :: UnattachedUnbalancedTx + -> Contract (Either BalanceTxError.BalanceTxError FinalizedTransaction) balanceTx = flip balanceTxWithConstraints mempty -- | Balances each transaction using specified balancer constraint sets and -- | locks the used inputs so that they cannot be reused by subsequent -- | transactions. balanceTxsWithConstraints - :: forall (r :: Row Type) (t :: Type -> Type) + :: forall (t :: Type -> Type) . Traversable t => t (UnattachedUnbalancedTx /\ BalanceTxConstraintsBuilder) - -> Contract r (t FinalizedTransaction) + -> Contract (t FinalizedTransaction) balanceTxsWithConstraints unbalancedTxs = unlockAllOnError $ traverse balanceAndLockWithConstraints unbalancedTxs where - unlockAllOnError :: forall (a :: Type). Contract r a -> Contract r a + unlockAllOnError :: forall (a :: Type). Contract a -> Contract a unlockAllOnError f = catchError f $ \e -> do for_ unbalancedTxs $ withUsedTxOuts <<< unlockTransactionInputs <<< uutxToTx <<< fst @@ -476,23 +444,21 @@ balanceTxsWithConstraints unbalancedTxs = -- | Same as `balanceTxsWithConstraints`, but uses the default balancer -- | constraints. balanceTxs - :: forall (r :: Row Type) (t :: Type -> Type) + :: forall (t :: Type -> Type) . Traversable t => t UnattachedUnbalancedTx - -> Contract r (t FinalizedTransaction) + -> Contract (t FinalizedTransaction) balanceTxs = balanceTxsWithConstraints <<< map (flip Tuple mempty) -- | Attempts to balance an `UnattachedUnbalancedTx` hushing the error. balanceTxM - :: forall (r :: Row Type) - . UnattachedUnbalancedTx - -> Contract r (Maybe FinalizedTransaction) + :: UnattachedUnbalancedTx + -> Contract (Maybe FinalizedTransaction) balanceTxM = map hush <<< balanceTx balanceAndLockWithConstraints - :: forall (r :: Row Type) - . UnattachedUnbalancedTx /\ BalanceTxConstraintsBuilder - -> Contract r FinalizedTransaction + :: UnattachedUnbalancedTx /\ BalanceTxConstraintsBuilder + -> Contract FinalizedTransaction balanceAndLockWithConstraints (unbalancedTx /\ constraints) = do balancedTx <- liftedE $ balanceTxWithConstraints unbalancedTx constraints @@ -501,25 +467,21 @@ balanceAndLockWithConstraints (unbalancedTx /\ constraints) = do pure balancedTx balanceAndLock - :: forall (r :: Row Type) - . UnattachedUnbalancedTx - -> Contract r FinalizedTransaction + :: UnattachedUnbalancedTx + -> Contract FinalizedTransaction balanceAndLock = balanceAndLockWithConstraints <<< flip Tuple mempty -- | Reindex the `Spend` redeemers. Since we insert to an ordered array, we must -- | reindex the redeemers with such inputs. This must be crucially called after -- | balancing when all inputs are in place so they cannot be reordered. reindexSpentScriptRedeemers - :: forall (r :: Row Type) - . Array Transaction.TransactionInput + :: Array Transaction.TransactionInput -> Array (Transaction.Redeemer /\ Maybe Transaction.TransactionInput) - -> Contract r - ( Either - ReindexRedeemersExport.ReindexErrors - (Array Transaction.Redeemer) - ) -reindexSpentScriptRedeemers balancedTx = - wrapContract <<< ReindexRedeemers.reindexSpentScriptRedeemers balancedTx + -> Either + ReindexRedeemersExport.ReindexErrors + (Array Transaction.Redeemer) +reindexSpentScriptRedeemers = + ReindexRedeemers.reindexSpentScriptRedeemers newtype BalancedSignedTransaction = BalancedSignedTransaction Transaction @@ -537,37 +499,35 @@ getTxFinalFee = -- | Get `Transaction` contents by hash getTxByHash - :: forall (r :: Row Type) - . TransactionHash - -> Contract r (Maybe Transaction) -getTxByHash = wrapContract <<< QueryM.getTxByHash <<< unwrap + :: TransactionHash + -> Contract (Maybe Transaction) +getTxByHash th = do + queryHandle <- getQueryHandle + liftAff $ queryHandle.getTxByHash th -- | Wait until a transaction with given hash is confirmed. -- | Use `awaitTxConfirmedWithTimeout` if you want to limit the time of waiting. awaitTxConfirmed - :: forall (r :: Row Type) - . TransactionHash - -> Contract r Unit -awaitTxConfirmed = Contract.awaitTxConfirmed + :: TransactionHash + -> Contract Unit +awaitTxConfirmed = Contract.awaitTxConfirmed <<< unwrap -- | Same as `awaitTxConfirmed`, but allows to specify a timeout in seconds for waiting. -- | Throws an exception on timeout. awaitTxConfirmedWithTimeout - :: forall (r :: Row Type) - . Seconds + :: Seconds -> TransactionHash - -> Contract r Unit -awaitTxConfirmedWithTimeout = Contract.awaitTxConfirmedWithTimeout + -> Contract Unit +awaitTxConfirmedWithTimeout timeout = Contract.awaitTxConfirmedWithTimeout timeout <<< unwrap -- | Same as `awaitTxConfirmed`, but allows to specify a timeout in slots for waiting. -- | Throws an exception on timeout. awaitTxConfirmedWithTimeoutSlots - :: forall (r :: Row Type) - . Int + :: Int -> TransactionHash - -> Contract r Unit -awaitTxConfirmedWithTimeoutSlots = - Contract.awaitTxConfirmedWithTimeoutSlots + -> Contract Unit +awaitTxConfirmedWithTimeoutSlots timeout = + Contract.awaitTxConfirmedWithTimeoutSlots timeout <<< unwrap -- | Builds an expected utxo set from transaction outputs. Predicts output -- | references (`TransactionInput`s) for each output by calculating the @@ -576,10 +536,10 @@ awaitTxConfirmedWithTimeoutSlots = -- | in conjunction with `mustUseAdditionalUtxos` balancer constraint. -- | Throws an exception if conversion to Plutus outputs fails. createAdditionalUtxos - :: forall (tx :: Type) (r :: Row Type) + :: forall (tx :: Type) . Newtype tx Transaction => tx - -> Contract r UtxoMap + -> Contract UtxoMap createAdditionalUtxos tx = do transactionId <- liftEffect $ Hashing.transactionHash <$> convertTransaction (unwrap tx) diff --git a/src/Contract/Utxos.purs b/src/Contract/Utxos.purs index 54a635dda4..47a7427b75 100644 --- a/src/Contract/Utxos.purs +++ b/src/Contract/Utxos.purs @@ -11,9 +11,12 @@ module Contract.Utxos import Prelude -import Contract.Monad (Contract, liftContractM, liftedE, wrapContract) +import Contract.Monad (Contract, liftContractM, liftedE) import Contract.Prelude (for) import Contract.Transaction (TransactionInput, TransactionOutput) +import Control.Monad.Reader.Class (asks) +import Ctl.Internal.Contract.QueryHandle (getQueryHandle) +import Effect.Aff.Class (liftAff) import Ctl.Internal.Plutus.Conversion ( fromPlutusAddress , toPlutusTxOutput @@ -24,39 +27,37 @@ import Ctl.Internal.Plutus.Types.Address (class PlutusAddress, getAddress) import Ctl.Internal.Plutus.Types.Transaction (UtxoMap) import Ctl.Internal.Plutus.Types.Transaction (UtxoMap) as X import Ctl.Internal.Plutus.Types.Value (Value) -import Ctl.Internal.QueryM (getNetworkId) -import Ctl.Internal.QueryM.Kupo (getUtxoByOref, utxosAt) as Kupo -import Ctl.Internal.QueryM.Utxos (getWalletBalance, getWalletUtxos) as Utxos +import Ctl.Internal.Contract.Wallet (getWalletBalance, getWalletUtxos) as Utxos import Data.Maybe (Maybe) -- | Queries for utxos at the given Plutus `Address`. utxosAt - :: forall (r :: Row Type) (address :: Type) + :: forall (address :: Type) . PlutusAddress address => address - -> Contract r UtxoMap + -> Contract UtxoMap utxosAt address = do - networkId <- wrapContract getNetworkId + networkId <- asks _.networkId + queryHandle <- getQueryHandle let cardanoAddr = fromPlutusAddress networkId (getAddress address) - cardanoUtxoMap <- liftedE $ wrapContract $ Kupo.utxosAt cardanoAddr + cardanoUtxoMap <- liftedE $ liftAff $ queryHandle.utxosAt cardanoAddr toPlutusUtxoMap cardanoUtxoMap # liftContractM "utxosAt: failed to convert utxos" -- | Queries for an utxo given a transaction input. -- | Returns `Nothing` if the output has already been spent. getUtxo - :: forall (r :: Row Type) - . TransactionInput - -> Contract r (Maybe TransactionOutput) + :: TransactionInput + -> Contract (Maybe TransactionOutput) getUtxo oref = do - cardanoTxOutput <- liftedE $ wrapContract $ Kupo.getUtxoByOref oref + queryHandle <- getQueryHandle + cardanoTxOutput <- liftedE $ liftAff $ queryHandle.getUtxoByOref oref for cardanoTxOutput (liftContractM "getUtxo: failed to convert tx output" <<< toPlutusTxOutput) getWalletBalance - :: forall (r :: Row Type) - . Contract r (Maybe Value) -getWalletBalance = wrapContract (Utxos.getWalletBalance <#> map toPlutusValue) + :: Contract (Maybe Value) +getWalletBalance = Utxos.getWalletBalance <#> map toPlutusValue -- | Similar to `utxosAt` called on own address, except that it uses CIP-30 -- | wallet state and not query layer state. @@ -65,10 +66,9 @@ getWalletBalance = wrapContract (Utxos.getWalletBalance <#> map toPlutusValue) -- | This function is expected to be more performant than `utxosAt` when there -- | is a large number of assets. getWalletUtxos - :: forall (r :: Row Type) - . Contract r (Maybe UtxoMap) + :: Contract (Maybe UtxoMap) getWalletUtxos = do - mCardanoUtxos <- wrapContract Utxos.getWalletUtxos + mCardanoUtxos <- Utxos.getWalletUtxos for mCardanoUtxos $ liftContractM "getWalletUtxos: unable to deserialize UTxOs" <<< toPlutusUtxoMap diff --git a/src/Contract/Wallet.purs b/src/Contract/Wallet.purs index a9920338fd..e7157dc3e7 100644 --- a/src/Contract/Wallet.purs +++ b/src/Contract/Wallet.purs @@ -20,18 +20,18 @@ module Contract.Wallet import Prelude import Contract.Address (getWalletAddress, getWalletCollateral) -import Contract.Monad (Contract, ContractEnv, wrapContract) +import Contract.Monad (Contract, ContractEnv) import Contract.Utxos (getWalletUtxos) as Contract.Utxos import Control.Monad.Reader (local) +import Control.Monad.Reader.Class (asks) import Ctl.Internal.Deserialization.Keys (privateKeyFromBytes) as Deserialization.Keys -import Ctl.Internal.QueryM +import Ctl.Internal.Contract.Wallet ( getChangeAddress - , getNetworkId , getRewardAddresses , getUnusedAddresses , getWallet , signData - ) as QueryM + ) as Contract import Ctl.Internal.Serialization.Address (Address, NetworkId) import Ctl.Internal.Types.RawBytes (RawBytes) import Ctl.Internal.Wallet @@ -76,48 +76,34 @@ import Data.Lens.Record (prop) import Data.Maybe (Maybe(Just)) import Type.Proxy (Proxy(Proxy)) -getNetworkId :: forall (r :: Row Type). Contract r NetworkId -getNetworkId = wrapContract QueryM.getNetworkId +getNetworkId :: Contract NetworkId +getNetworkId = asks _.networkId -getUnusedAddresses :: forall (r :: Row Type). Contract r (Array Address) -getUnusedAddresses = wrapContract QueryM.getUnusedAddresses +getUnusedAddresses :: Contract (Array Address) +getUnusedAddresses = Contract.getUnusedAddresses -getChangeAddress :: forall (r :: Row Type). Contract r (Maybe Address) -getChangeAddress = wrapContract QueryM.getChangeAddress +getChangeAddress :: Contract (Maybe Address) +getChangeAddress = Contract.getChangeAddress -getRewardAddresses :: forall (r :: Row Type). Contract r (Array Address) -getRewardAddresses = wrapContract QueryM.getRewardAddresses +getRewardAddresses :: Contract (Array Address) +getRewardAddresses = Contract.getRewardAddresses signData - :: forall (r :: Row Type) - . Address + :: Address -> RawBytes - -> Contract r (Maybe DataSignature) -signData address dat = wrapContract (QueryM.signData address dat) + -> Contract (Maybe DataSignature) +signData address dat = Contract.signData address dat -getWallet :: forall (r :: Row Type). Contract r (Maybe Wallet) -getWallet = wrapContract QueryM.getWallet +getWallet :: Contract (Maybe Wallet) +getWallet = Contract.getWallet withKeyWallet - :: forall (r :: Row Type) (a :: Type) + :: forall (a :: Type) . Wallet.KeyWallet - -> Contract r a - -> Contract r a + -> Contract a + -> Contract a withKeyWallet wallet action = do - let - setUpdatedWallet :: ContractEnv r -> ContractEnv r - setUpdatedWallet = - simple _Newtype <<< _runtime <<< _wallet .~ - (Just (KeyWallet wallet)) - local setUpdatedWallet action - where - _wallet - :: forall x rest. Lens { wallet :: x | rest } { wallet :: x | rest } x x - _wallet = prop (Proxy :: Proxy "wallet") - - _runtime - :: forall x rest. Lens { runtime :: x | rest } { runtime :: x | rest } x x - _runtime = prop (Proxy :: Proxy "runtime") + local _ { wallet = Just $ KeyWallet wallet } action mkKeyWalletFromPrivateKeys :: PrivatePaymentKey -> Maybe PrivateStakeKey -> Wallet diff --git a/src/Internal/BalanceTx/BalanceTx.purs b/src/Internal/BalanceTx/BalanceTx.purs index 3f50bd7edd..bf67c6db1d 100644 --- a/src/Internal/BalanceTx/BalanceTx.purs +++ b/src/Internal/BalanceTx/BalanceTx.purs @@ -10,6 +10,9 @@ import Control.Monad.Error.Class (liftMaybe) import Control.Monad.Except.Trans (ExceptT(ExceptT), except, runExceptT) import Control.Monad.Logger.Class (class MonadLogger) import Control.Monad.Logger.Class as Logger +import Control.Monad.Reader.Class (asks) +import Effect.Aff.Class (liftAff) +import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.BalanceTx.Collateral ( addTxCollateral , addTxCollateralReturn @@ -68,8 +71,8 @@ import Ctl.Internal.BalanceTx.Types , askCoinsPerUtxoUnit , askNetworkId , asksConstraints - , liftEitherQueryM - , liftQueryM + , liftEitherContract + , liftContract , withBalanceTxConstraints ) import Ctl.Internal.BalanceTx.Types (FinalizedTransaction(FinalizedTransaction)) as FinalizedTransaction @@ -102,12 +105,11 @@ import Ctl.Internal.Cardano.Types.Value , posNonAdaAsset , valueToCoin' ) -import Ctl.Internal.QueryM (QueryM, getProtocolParameters) -import Ctl.Internal.QueryM (getChangeAddress, getWalletAddresses) as QueryM -import Ctl.Internal.QueryM.Utxos - ( filterLockedUtxos - , getWalletCollateral - , utxosAt +import Ctl.Internal.Contract.Monad (Contract) +import Ctl.Internal.Contract.Wallet (getChangeAddress, getWalletAddresses) as Contract +import Ctl.Internal.Contract.Wallet + ( getWalletCollateral + , filterLockedUtxos ) import Ctl.Internal.Serialization.Address ( Address @@ -141,9 +143,10 @@ import Effect.Class (class MonadEffect, liftEffect) balanceTxWithConstraints :: UnattachedUnbalancedTx -> BalanceTxConstraintsBuilder - -> QueryM (Either BalanceTxError FinalizedTransaction) + -> Contract (Either BalanceTxError FinalizedTransaction) balanceTxWithConstraints unbalancedTx constraintsBuilder = do - pparams <- getProtocolParameters + pparams <- asks $ _.ledgerConstants >>> _.pparams + queryHandle <- getQueryHandle withBalanceTxConstraints constraintsBuilder $ runExceptT do let @@ -153,11 +156,11 @@ balanceTxWithConstraints unbalancedTx constraintsBuilder = do srcAddrs <- asksConstraints Constraints._srcAddresses - >>= maybe (liftQueryM QueryM.getWalletAddresses) pure + >>= maybe (liftContract Contract.getWalletAddresses) pure changeAddr <- getChangeAddress - utxos <- liftEitherQueryM $ traverse utxosAt srcAddrs <#> + utxos <- liftEitherContract $ traverse (queryHandle.utxosAt >>> liftAff >>> map hush) srcAddrs <#> traverse (note CouldNotGetUtxos) -- Maybe -> Either and unwrap UtxoM >>> map (foldr Map.union Map.empty) -- merge all utxos into one map @@ -176,7 +179,7 @@ balanceTxWithConstraints unbalancedTx constraintsBuilder = do -- involved with the contract in the unbalanced transaction: utxos `Map.union` (unbalancedTx ^. _unbalancedTx <<< _utxoIndex) - availableUtxos <- liftQueryM $ filterLockedUtxos allUtxos + availableUtxos <- liftContract $ filterLockedUtxos allUtxos logTx "unbalancedCollTx" availableUtxos unbalancedCollTx @@ -187,7 +190,7 @@ balanceTxWithConstraints unbalancedTx constraintsBuilder = do getChangeAddress :: BalanceTxM Address getChangeAddress = liftMaybe CouldNotGetChangeAddress - =<< maybe (liftQueryM QueryM.getChangeAddress) (pure <<< Just) + =<< maybe (liftContract Contract.getChangeAddress) (pure <<< Just) =<< asksConstraints Constraints._changeAddress unbalancedTxWithNetworkId :: BalanceTxM Transaction @@ -199,7 +202,7 @@ balanceTxWithConstraints unbalancedTx constraintsBuilder = do setTransactionCollateral :: Address -> Transaction -> BalanceTxM Transaction setTransactionCollateral changeAddr transaction = do collateral <- - liftEitherQueryM $ note CouldNotGetCollateral <$> getWalletCollateral + liftEitherContract $ note CouldNotGetCollateral <$> getWalletCollateral let collaterisedTx = addTxCollateral collateral transaction -- Don't mess with Cip30 collateral isCip30 <- isJust <$> askCip30Wallet diff --git a/src/Internal/BalanceTx/ExUnitsAndMinFee.purs b/src/Internal/BalanceTx/ExUnitsAndMinFee.purs index c8128b8b70..b0947e4d6d 100644 --- a/src/Internal/BalanceTx/ExUnitsAndMinFee.purs +++ b/src/Internal/BalanceTx/ExUnitsAndMinFee.purs @@ -5,7 +5,9 @@ module Ctl.Internal.BalanceTx.ExUnitsAndMinFee import Prelude -import Control.Monad.Error.Class (throwError) +import Control.Monad.Error.Class (liftEither, throwError) +import Effect.Aff.Class (liftAff) +import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Control.Monad.Except.Trans (except) import Ctl.Internal.BalanceTx.Constraints (_additionalUtxos) as Constraints import Ctl.Internal.BalanceTx.Error @@ -23,8 +25,7 @@ import Ctl.Internal.BalanceTx.Types , askCostModelsForLanguages , askNetworkId , asksConstraints - , liftEitherQueryM - , liftQueryM + , liftContract ) import Ctl.Internal.Cardano.Types.ScriptRef as ScriptRef import Ctl.Internal.Cardano.Types.Transaction @@ -43,9 +44,7 @@ import Ctl.Internal.Cardano.Types.Transaction , _witnessSet ) import Ctl.Internal.Plutus.Conversion (fromPlutusUtxoMap) -import Ctl.Internal.QueryM (QueryM) -import Ctl.Internal.QueryM (evaluateTxOgmios) as QueryM -import Ctl.Internal.QueryM.MinFee (calculateMinFee) as QueryM +import Ctl.Internal.Contract.MinFee (calculateMinFee) as Contract import Ctl.Internal.QueryM.Ogmios ( AdditionalUtxoSet , TxEvaluationResult(TxEvaluationResult) @@ -54,7 +53,6 @@ import Ctl.Internal.ReindexRedeemers ( ReindexErrors , reindexSpentScriptRedeemers' ) -import Ctl.Internal.Serialization (convertTransaction, toBytes) as Serialization import Ctl.Internal.Transaction (setScriptDataHash) import Ctl.Internal.TxOutput ( transactionInputToTxOutRef @@ -85,20 +83,16 @@ import Data.Traversable (for) import Data.Tuple (fst, snd) import Data.Tuple.Nested (type (/\), (/\)) import Effect.Class (liftEffect) -import Untagged.Union (asOneOf) evalTxExecutionUnits :: Transaction -> UnattachedUnbalancedTx -> BalanceTxM Ogmios.TxEvaluationResult evalTxExecutionUnits tx unattachedTx = do - txBytes <- liftEffect - ( wrap <<< Serialization.toBytes <<< asOneOf <$> - Serialization.convertTransaction tx - ) + queryHandle <- liftContract getQueryHandle additionalUtxos <- getOgmiosAdditionalUtxoSet evalResult <- - unwrap <$> liftQueryM (QueryM.evaluateTxOgmios txBytes additionalUtxos) + unwrap <$> liftContract (liftAff $ queryHandle.evaluateTx tx additionalUtxos) case evalResult of Right a -> pure a @@ -127,8 +121,8 @@ evalExUnitsAndMinFee -> BalanceTxM (UnattachedUnbalancedTx /\ BigInt) evalExUnitsAndMinFee (PrebalancedTransaction unattachedTx) allUtxos = do -- Reindex `Spent` script redeemers: - reindexedUnattachedTx <- liftEitherQueryM $ - reindexRedeemers unattachedTx <#> lmap ReindexRedeemersError + reindexedUnattachedTx <- liftEither $ + reindexRedeemers unattachedTx # lmap ReindexRedeemersError -- Reattach datums and redeemers before evaluating ex units: let attachedTx = reattachDatumsAndRedeemers reindexedUnattachedTx -- Evaluate transaction ex units: @@ -145,7 +139,7 @@ evalExUnitsAndMinFee (PrebalancedTransaction unattachedTx) allUtxos = do additionalUtxos <- fromPlutusUtxoMap networkId <$> asksConstraints Constraints._additionalUtxos - minFee <- liftQueryM $ QueryM.calculateMinFee finalizedTx additionalUtxos + minFee <- liftContract $ Contract.calculateMinFee finalizedTx additionalUtxos pure $ reindexedUnattachedTxWithExUnits /\ unwrap minFee -- | Attaches datums and redeemers, sets the script integrity hash, @@ -201,13 +195,13 @@ finalizeTransaction reindexedUnattachedTxWithExUnits utxos = do reindexRedeemers :: UnattachedUnbalancedTx - -> QueryM (Either ReindexErrors UnattachedUnbalancedTx) + -> Either ReindexErrors UnattachedUnbalancedTx reindexRedeemers unattachedTx@(UnattachedUnbalancedTx { redeemersTxIns }) = let inputs = Array.fromFoldable $ unattachedTx ^. _body' <<< _inputs in - reindexSpentScriptRedeemers' inputs redeemersTxIns <#> + reindexSpentScriptRedeemers' inputs redeemersTxIns # map \redeemersTxInsReindexed -> unattachedTx # _redeemersTxIns .~ redeemersTxInsReindexed diff --git a/src/Internal/BalanceTx/Types.purs b/src/Internal/BalanceTx/Types.purs index 43a7b59bc7..4a7d0c7219 100644 --- a/src/Internal/BalanceTx/Types.purs +++ b/src/Internal/BalanceTx/Types.purs @@ -8,8 +8,8 @@ module Ctl.Internal.BalanceTx.Types , askCostModelsForLanguages , askNetworkId , asksConstraints - , liftEitherQueryM - , liftQueryM + , liftEitherContract + , liftContract , withBalanceTxConstraints ) where @@ -28,7 +28,7 @@ import Ctl.Internal.BalanceTx.Constraints ) as Constraints import Ctl.Internal.BalanceTx.Error (BalanceTxError) import Ctl.Internal.Cardano.Types.Transaction (Costmdls(Costmdls), Transaction) -import Ctl.Internal.QueryM (QueryEnv, QueryM) +import Ctl.Internal.Contract.Monad (ContractEnv, Contract) import Ctl.Internal.QueryM.Ogmios (CoinsPerUtxoUnit) import Ctl.Internal.Serialization.Address (NetworkId) import Ctl.Internal.Types.ScriptLookups (UnattachedUnbalancedTx) @@ -48,37 +48,37 @@ import Data.Show.Generic (genericShow) type BalanceTxMContext = { constraints :: BalanceTxConstraints } type BalanceTxM (a :: Type) = - ExceptT BalanceTxError (ReaderT BalanceTxMContext QueryM) a + ExceptT BalanceTxError (ReaderT BalanceTxMContext Contract) a -liftQueryM :: forall (a :: Type). QueryM a -> BalanceTxM a -liftQueryM = lift <<< lift +liftContract :: forall (a :: Type). Contract a -> BalanceTxM a +liftContract = lift <<< lift -liftEitherQueryM - :: forall (a :: Type). QueryM (Either BalanceTxError a) -> BalanceTxM a -liftEitherQueryM = ExceptT <<< lift +liftEitherContract + :: forall (a :: Type). Contract (Either BalanceTxError a) -> BalanceTxM a +liftEitherContract = ExceptT <<< lift asksConstraints :: forall (a :: Type). Lens' BalanceTxConstraints a -> BalanceTxM a asksConstraints l = asks (view l <<< _.constraints) -asksQueryEnv :: forall (a :: Type). (QueryEnv () -> a) -> BalanceTxM a -asksQueryEnv = lift <<< lift <<< asks +asksContractEnv :: forall (a :: Type). (ContractEnv -> a) -> BalanceTxM a +asksContractEnv = lift <<< lift <<< asks askCoinsPerUtxoUnit :: BalanceTxM CoinsPerUtxoUnit askCoinsPerUtxoUnit = - asksQueryEnv (_.coinsPerUtxoUnit <<< unwrap <<< _.pparams <<< _.runtime) + asksContractEnv (_.coinsPerUtxoUnit <<< unwrap <<< _.pparams <<< _.ledgerConstants) askCip30Wallet :: BalanceTxM (Maybe Cip30Wallet) -askCip30Wallet = asksQueryEnv (cip30Wallet <=< _.wallet <<< _.runtime) +askCip30Wallet = asksContractEnv (cip30Wallet <=< _.wallet) askNetworkId :: BalanceTxM NetworkId -askNetworkId = asksQueryEnv (_.networkId <<< _.config) +askNetworkId = asksContractEnv _.networkId withBalanceTxConstraints :: forall (a :: Type) . BalanceTxConstraintsBuilder - -> ReaderT BalanceTxMContext QueryM a - -> QueryM a + -> ReaderT BalanceTxMContext Contract a + -> Contract a withBalanceTxConstraints constraintsBuilder = flip runReaderT { constraints } where @@ -87,7 +87,7 @@ withBalanceTxConstraints constraintsBuilder = askCostModelsForLanguages :: Set Language -> BalanceTxM Costmdls askCostModelsForLanguages languages = - asksQueryEnv (_.costModels <<< unwrap <<< _.pparams <<< _.runtime) + asksContractEnv (_.costModels <<< unwrap <<< _.pparams <<< _.ledgerConstants) <#> over Costmdls (Map.filterKeys (flip Set.member languages)) newtype FinalizedTransaction = FinalizedTransaction Transaction diff --git a/src/Internal/Contract/MinFee.purs b/src/Internal/Contract/MinFee.purs new file mode 100644 index 0000000000..589a7a1e31 --- /dev/null +++ b/src/Internal/Contract/MinFee.purs @@ -0,0 +1,123 @@ +module Ctl.Internal.Contract.MinFee (calculateMinFee) where + +import Prelude + +import Control.Monad.Reader.Class (asks) +import Data.Either (hush) +import Effect.Aff.Class (liftAff) +import Ctl.Internal.Contract.QueryHandle (getQueryHandle) +import Ctl.Internal.Cardano.Types.Transaction + ( Transaction + , UtxoMap + , _body + , _collateral + , _inputs + ) +import Ctl.Internal.Cardano.Types.TransactionUnspentOutput + ( TransactionUnspentOutput + ) +import Ctl.Internal.Cardano.Types.Value (Coin) +import Ctl.Internal.Helpers (liftM, liftedM) +import Ctl.Internal.Contract.Monad (Contract) +import Ctl.Internal.Contract.Wallet (getWalletAddresses, getWalletCollateral) +import Ctl.Internal.Serialization.Address + ( Address + , addressPaymentCred + , addressStakeCred + , stakeCredentialToKeyHash + ) +import Ctl.Internal.Serialization.Hash (Ed25519KeyHash) +import Ctl.Internal.Serialization.MinFee (calculateMinFeeCsl) +import Ctl.Internal.Types.Transaction (TransactionInput) +import Data.Array (fromFoldable, mapMaybe) +import Data.Array as Array +import Data.Lens.Getter ((^.)) +import Data.Map (empty, fromFoldable, keys, lookup, values) as Map +import Data.Maybe (fromMaybe, maybe) +import Data.Newtype (unwrap) +import Data.Set (Set) +import Data.Set (difference, fromFoldable, intersection, mapMaybe, union) as Set +import Data.Traversable (for) +import Data.Tuple.Nested ((/\)) +import Effect.Aff (error) + +-- | Calculate `min_fee` using CSL with protocol parameters from Ogmios. +calculateMinFee :: Transaction -> UtxoMap -> Contract Coin +calculateMinFee tx additionalUtxos = do + selfSigners <- getSelfSigners tx additionalUtxos + pparams <- asks $ _.ledgerConstants >>> _.pparams + calculateMinFeeCsl pparams selfSigners tx + +getSelfSigners :: Transaction -> UtxoMap -> Contract (Set Ed25519KeyHash) +getSelfSigners tx additionalUtxos = do + queryHandle <- getQueryHandle + + -- Get all tx inputs and remove the additional ones. + let + txInputs :: Set TransactionInput + txInputs = + Set.difference + (tx ^. _body <<< _inputs) + (Map.keys additionalUtxos) + + additionalUtxosAddrs :: Set Address + additionalUtxosAddrs = Set.fromFoldable $ + (_.address <<< unwrap) <$> Map.values additionalUtxos + + (inUtxosAddrs :: Set Address) <- setFor txInputs $ \txInput -> + liftedM (error $ "Couldn't get tx output for " <> show txInput) $ + (map <<< map) (_.address <<< unwrap) (liftAff $ queryHandle.getUtxoByOref txInput <#> hush >>> join) + + -- Get all tx output addressses + let + txCollats :: Set TransactionInput + txCollats = Set.fromFoldable <<< fromMaybe [] $ tx ^. _body <<< _collateral + + walletCollats <- maybe Map.empty toUtxoMap <$> getWalletCollateral + + (inCollatAddrs :: Set Address) <- setFor txCollats + ( \txCollat -> + liftM (error $ "Couldn't get tx output for " <> show txCollat) + $ (map (_.address <<< unwrap) <<< Map.lookup txCollat) + $ walletCollats + ) + + -- Get own addressses + (ownAddrs :: Set Address) <- Set.fromFoldable <$> getWalletAddresses + + -- Combine to get all self tx input addresses + let + txOwnAddrs = ownAddrs `Set.intersection` + (additionalUtxosAddrs `Set.union` inUtxosAddrs `Set.union` inCollatAddrs) + + -- Extract payment pub key hashes from addresses. + paymentPkhs <- map (Set.mapMaybe identity) $ setFor txOwnAddrs $ \addr -> do + paymentCred <- + liftM + ( error $ "Could not extract payment credential from Address: " <> show + addr + ) $ addressPaymentCred addr + pure $ stakeCredentialToKeyHash paymentCred + + -- Extract stake pub key hashes from addresses + let + stakePkhs = Set.fromFoldable $ + (stakeCredentialToKeyHash <=< addressStakeCred) `mapMaybe` + Array.fromFoldable txOwnAddrs + + pure $ paymentPkhs <> stakePkhs + where + setFor + :: forall (a :: Type) (b :: Type) (m :: Type -> Type) + . Monad m + => Ord a + => Ord b + => Set a + -> (a -> m b) + -> m (Set b) + setFor txIns f = Set.fromFoldable <$> for (fromFoldable txIns) f + + toUtxoMap :: Array TransactionUnspentOutput -> UtxoMap + toUtxoMap = Map.fromFoldable <<< map + (unwrap >>> \({ input, output }) -> input /\ output) + diff --git a/src/Internal/Contract/Monad.purs b/src/Internal/Contract/Monad.purs index fb9f51cfcb..a17fb01bf2 100644 --- a/src/Internal/Contract/Monad.purs +++ b/src/Internal/Contract/Monad.purs @@ -10,6 +10,8 @@ module Ctl.Internal.Contract.Monad , wrapQueryM , stopContractEnv , withContractEnv + , buildBackend + , getLedgerConstants ) where import Prelude @@ -60,7 +62,6 @@ import Effect.Class (class MonadEffect, liftEffect) import Effect.Exception (Error, try) import Effect.Ref (new) as Ref import MedeaPrelude (class MonadAff) -import Prim.TypeError (class Warn, Text) import Undefined (undefined) import Control.Parallel (class Parallel, parallel, sequential) import Control.Alt (class Alt) @@ -173,11 +174,7 @@ type ContractEnv = -- | Consider using `withContractEnv` if possible - otherwise use -- | `stopContractEnv` to properly finalize. mkContractEnv - :: Warn - ( Text - "Using `mkContractEnv` is not recommended: it does not ensure `ContractEnv` finalization. Consider using `withContractEnv`" - ) - => ContractParams + :: ContractParams -> Aff ContractEnv mkContractEnv params = do for_ params.hooks.beforeInit (void <<< liftEffect <<< try) @@ -186,9 +183,9 @@ mkContractEnv params = do envBuilder <- sequential ado b1 <- parallel do - backend <- buildBackend + backend <- buildBackend logger params.backendParams -- Use the default backend to fetch ledger constants - ledgerConstants <- getLedgerConstants $ defaultBackend backend + ledgerConstants <- getLedgerConstants logger $ defaultBackend backend pure $ merge { backend, ledgerConstants } b2 <- parallel do wallet <- buildWallet @@ -201,47 +198,6 @@ mkContractEnv params = do logger :: Logger logger = mkLogger params.logLevel params.customLogger - -- TODO Move CtlServer to a backend? Wouldn't make sense as a 'main' backend though - buildBackend :: Aff (QueryBackends QueryBackend) - buildBackend = flip parTraverse params.backendParams case _ of - CtlBackendParams { ogmiosConfig, kupoConfig, odcConfig } -> do - datumCacheWsRef <- liftEffect $ Ref.new Nothing - sequential ado - odcWs <- parallel $ mkDatumCacheWebSocketAff datumCacheWsRef logger odcConfig - ogmiosWs <- parallel $ mkOgmiosWebSocketAff datumCacheWsRef logger ogmiosConfig - in CtlBackend - { ogmios: - { config: ogmiosConfig - , ws: ogmiosWs - } - , odc: - { config: odcConfig - , ws: odcWs - } - , kupoConfig - } - BlockfrostBackendParams bf -> pure $ BlockfrostBackend bf - - getLedgerConstants :: QueryBackend -> Aff - { pparams :: Ogmios.ProtocolParameters - , systemStart :: Ogmios.SystemStart - , slotLength :: Ogmios.SlotLength - , slotReference :: { slot :: Slot, time :: Ogmios.RelativeTime } - } - getLedgerConstants backend = case backend of - CtlBackend { ogmios: { ws } } -> do - pparams <- getProtocolParametersAff ws logger - systemStart <- getSystemStartAff ws logger - -- Do we ever recieve an eraSummary ahead of schedule? - -- Maybe search for the chainTip's era - latestEraSummary <- liftedM (error "Could not get EraSummary") do - map unwrap <<< (maximumBy (compare `on` (unwrap >>> _.start >>> unwrap >>> _.slot))) <<< unwrap <$> getEraSummariesAff ws logger - let - slotLength = _.slotLength $ unwrap $ _.parameters $ latestEraSummary - slotReference = (\{slot, time} -> {slot, time}) $ unwrap $ _.start $ latestEraSummary - pure { pparams, slotLength, systemStart, slotReference } - BlockfrostBackend _ -> undefined - buildWallet :: Aff (Maybe Wallet) buildWallet = traverse mkWalletBySpec params.walletSpec @@ -255,15 +211,52 @@ mkContractEnv params = do , hooks: params.hooks } +-- TODO Move CtlServer to a backend? Wouldn't make sense as a 'main' backend though +buildBackend :: Logger -> QueryBackends QueryBackendParams -> Aff (QueryBackends QueryBackend) +buildBackend logger = parTraverse case _ of + CtlBackendParams { ogmiosConfig, kupoConfig, odcConfig } -> do + datumCacheWsRef <- liftEffect $ Ref.new Nothing + sequential ado + odcWs <- parallel $ mkDatumCacheWebSocketAff datumCacheWsRef logger odcConfig + ogmiosWs <- parallel $ mkOgmiosWebSocketAff datumCacheWsRef logger ogmiosConfig + in CtlBackend + { ogmios: + { config: ogmiosConfig + , ws: ogmiosWs + } + , odc: + { config: odcConfig + , ws: odcWs + } + , kupoConfig + } + BlockfrostBackendParams bf -> pure $ BlockfrostBackend bf + +getLedgerConstants :: Logger -> QueryBackend -> Aff + { pparams :: Ogmios.ProtocolParameters + , systemStart :: Ogmios.SystemStart + , slotLength :: Ogmios.SlotLength + , slotReference :: { slot :: Slot, time :: Ogmios.RelativeTime } + } +getLedgerConstants logger backend = case backend of + CtlBackend { ogmios: { ws } } -> do + pparams <- getProtocolParametersAff ws logger + systemStart <- getSystemStartAff ws logger + -- Do we ever recieve an eraSummary ahead of schedule? + -- Maybe search for the chainTip's era + latestEraSummary <- liftedM (error "Could not get EraSummary") do + map unwrap <<< (maximumBy (compare `on` (unwrap >>> _.start >>> unwrap >>> _.slot))) <<< unwrap <$> getEraSummariesAff ws logger + let + slotLength = _.slotLength $ unwrap $ _.parameters $ latestEraSummary + slotReference = (\{slot, time} -> {slot, time}) $ unwrap $ _.start $ latestEraSummary + pure { pparams, slotLength, systemStart, slotReference } + BlockfrostBackend _ -> undefined + -- | Finalizes a `Contract` environment. -- | Closes the websockets in `ContractEnv`, effectively making it unusable. -- TODO Move to Aff? stopContractEnv - :: Warn - ( Text - "Using `stopContractEnv` is not recommended: users should rely on `withContractEnv` to finalize the runtime environment instead" - ) - => ContractEnv + :: ContractEnv -> Effect Unit stopContractEnv contractEnv = do for_ contractEnv.backend case _ of diff --git a/src/Internal/Contract/QueryBackend.purs b/src/Internal/Contract/QueryBackend.purs index 0cd498c99a..09813e37c5 100644 --- a/src/Internal/Contract/QueryBackend.purs +++ b/src/Internal/Contract/QueryBackend.purs @@ -38,6 +38,7 @@ import Effect.Exception (throw) data QueryBackends (backend :: Type) = QueryBackends backend (Map QueryBackendLabel backend) +-- Functor breaks this datatype... derive instance Functor QueryBackends instance Foldable QueryBackends where diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs index 94f2d2e7bc..d6fc15870f 100644 --- a/src/Internal/Contract/QueryHandle.purs +++ b/src/Internal/Contract/QueryHandle.purs @@ -2,10 +2,18 @@ module Ctl.Internal.Contract.QueryHandle where import Prelude +import Contract.Log (logDebug') +import Ctl.Internal.QueryM.Ogmios (SubmitTxR(SubmitTxSuccess), TxEvaluationR) +import Data.Either (Either) +import Untagged.Union (asOneOf) +import Data.Newtype (unwrap, wrap) +import Ctl.Internal.Hashing (transactionHash) as Hashing +import Effect.Class (liftEffect) +import Ctl.Internal.Cardano.Types.Transaction (Transaction, TransactionOutput, UtxoMap) import Control.Monad.Reader.Class (ask) import Ctl.Internal.Cardano.Types.ScriptRef (ScriptRef) -import Ctl.Internal.Cardano.Types.Transaction (TransactionOutput, UtxoMap) import Ctl.Internal.QueryM.CurrentEpoch(getCurrentEpoch) as QueryM +import Ctl.Internal.QueryM.GetTxByHash (getTxByHash) as QueryM import Ctl.Internal.Contract.Monad ( Contract , ContractEnv @@ -17,7 +25,7 @@ import Ctl.Internal.Contract.QueryBackend , QueryBackend(BlockfrostBackend, CtlBackend) , defaultBackend ) -import Ctl.Internal.QueryM (getChainTip) as QueryM +import Ctl.Internal.QueryM (getChainTip, submitTxOgmios, evaluateTxOgmios) as QueryM import Ctl.Internal.QueryM (ClientError, QueryM) import Ctl.Internal.QueryM.Kupo ( getDatumByHash @@ -28,17 +36,17 @@ import Ctl.Internal.QueryM.Kupo , isTxConfirmed , utxosAt ) as Kupo +import Ctl.Internal.Serialization (convertTransaction, toBytes) as Serialization import Ctl.Internal.Serialization.Address (Address) import Ctl.Internal.Serialization.Hash (ScriptHash) import Ctl.Internal.Types.Datum (DataHash, Datum) import Ctl.Internal.Types.Transaction (TransactionHash, TransactionInput) -import Data.Either (Either) import Data.Map (Map) -import Data.Maybe (Maybe) +import Data.Maybe (Maybe(Just, Nothing)) import Effect.Aff (Aff) import Undefined (undefined) import Ctl.Internal.Types.Chain as Chain -import Ctl.Internal.QueryM.Ogmios (CurrentEpoch) as Ogmios +import Ctl.Internal.QueryM.Ogmios (CurrentEpoch, AdditionalUtxoSet) as Ogmios -- Why ClientError? type AffE (a :: Type) = Aff (Either ClientError a) @@ -53,6 +61,15 @@ type QueryHandle = , utxosAt :: Address -> AffE UtxoMap , getChainTip :: Aff Chain.Tip , getCurrentEpoch :: Aff Ogmios.CurrentEpoch + -- TODO Capture errors from all backends + , submitTx :: Transaction -> Aff (Maybe TransactionHash) + , getTxByHash :: TransactionHash -> Aff (Maybe Transaction) + , evaluateTx :: Transaction -> Ogmios.AdditionalUtxoSet -> Aff TxEvaluationR + + -- getTxByHash + -- bf: /txs/{hash} + -- ctl: requires ODC + -- Not a problem for now -- submitTx -- evaluateTx -- chainTip @@ -75,6 +92,14 @@ getQueryHandle = BlockfrostBackend backend -> queryHandleForBlockfrostBackend contractEnv backend +getQueryHandle' :: ContractEnv -> QueryHandle +getQueryHandle' contractEnv = + case defaultBackend contractEnv.backend of + CtlBackend backend -> + queryHandleForCtlBackend contractEnv backend + BlockfrostBackend backend -> + queryHandleForBlockfrostBackend contractEnv backend + queryHandleForCtlBackend :: ContractEnv -> CtlBackend -> QueryHandle queryHandleForCtlBackend contractEnv backend = { getDatumByHash: runQueryM' <<< Kupo.getDatumByHash @@ -86,6 +111,22 @@ queryHandleForCtlBackend contractEnv backend = , utxosAt: runQueryM' <<< Kupo.utxosAt , getChainTip: runQueryM' QueryM.getChainTip , getCurrentEpoch: runQueryM' QueryM.getCurrentEpoch + , submitTx: \tx -> runQueryM' do + cslTx <- liftEffect $ Serialization.convertTransaction tx + let txHash = Hashing.transactionHash cslTx + logDebug' $ "Pre-calculated tx hash: " <> show txHash + let txCborBytes = wrap $ Serialization.toBytes $ asOneOf cslTx + result <- QueryM.submitTxOgmios (unwrap txHash) txCborBytes + case result of + SubmitTxSuccess a -> pure $ Just $ wrap a + _ -> pure Nothing + , getTxByHash: runQueryM' <<< QueryM.getTxByHash <<< unwrap + , evaluateTx: \tx additionalUtxos -> runQueryM' do + txBytes <- liftEffect + ( wrap <<< Serialization.toBytes <<< asOneOf <$> + Serialization.convertTransaction tx + ) + QueryM.evaluateTxOgmios txBytes additionalUtxos } where runQueryM' :: forall (a :: Type). QueryM a -> Aff a diff --git a/src/Internal/Contract/Sign.purs b/src/Internal/Contract/Sign.purs new file mode 100644 index 0000000000..f3cc95d6d2 --- /dev/null +++ b/src/Internal/Contract/Sign.purs @@ -0,0 +1,103 @@ +module Ctl.Internal.Contract.Sign + ( signTransaction + ) where + +import Prelude + +import Control.Monad.Reader (asks) +import Ctl.Internal.Cardano.Types.Transaction (_body, _inputs, _witnessSet) +import Ctl.Internal.Cardano.Types.Transaction as Transaction +import Ctl.Internal.Contract.QueryHandle (getQueryHandle) +import Ctl.Internal.Helpers (liftedM) +import Ctl.Internal.Contract.Monad (Contract) +import Ctl.Internal.Contract.Wallet + ( callCip30Wallet + , getWalletAddresses + , getWalletUtxos + , withMWallet + ) +import Ctl.Internal.Types.Transaction (TransactionInput) +import Ctl.Internal.Wallet (Wallet(KeyWallet, Lode, Eternl, Flint, Gero, Nami)) +import Data.Array (elem, fromFoldable) +import Data.Lens ((<>~)) +import Data.Lens.Getter ((^.)) +import Data.Map as Map +import Data.Maybe (Maybe(Just), fromMaybe) +import Data.Newtype (unwrap, wrap) +import Data.Traversable (for_, traverse) +import Data.Tuple.Nested ((/\)) +import Effect.Aff (delay, error) +import Effect.Aff.Class (liftAff) +import Effect.Class (liftEffect) +import Effect.Exception (throw, try) +import Data.Either (hush) + +signTransaction + :: Transaction.Transaction -> Contract (Maybe Transaction.Transaction) +signTransaction tx = do + hooks <- asks _.hooks + let + runHook = + for_ hooks.beforeSign (void <<< liftEffect <<< try) + runHook + withMWallet case _ of + Nami nami -> liftAff $ callCip30Wallet nami \nw -> flip nw.signTx tx + Gero gero -> liftAff $ callCip30Wallet gero \nw -> flip nw.signTx tx + Flint flint -> liftAff $ callCip30Wallet flint \nw -> flip nw.signTx tx + Eternl eternl -> do + let + txInputs :: Array TransactionInput + txInputs = fromFoldable $ tx ^. _body <<< _inputs + walletWaitForInputs txInputs + liftAff $ callCip30Wallet eternl \nw -> flip nw.signTx tx + Lode lode -> liftAff $ callCip30Wallet lode \nw -> flip nw.signTx tx + KeyWallet kw -> liftAff do + witnessSet <- (unwrap kw).signTx tx + pure $ Just (tx # _witnessSet <>~ witnessSet) + +-- | Waits till all provided inputs of a given transaction appear in the UTxO +-- | set provided by the wallet. +-- | This is a hacky solution to the problem of Eternl not seeing UTxOs that +-- | hasn't been fully confirmed at the moment of a `sign()` call. +-- | Since it can't detect UTxO origin, it can't decide which of the private +-- | keys to use for signing. As a result, we get `MissingVKeyWitnesses`. +walletWaitForInputs :: Array TransactionInput -> Contract Unit +walletWaitForInputs txInputs = do + queryHandle <- getQueryHandle + ownAddrs <- getWalletAddresses + ownInputUtxos :: Map.Map TransactionInput _ + <- txInputs # + traverse + ( \txInput -> do + utxo <- liftedM (error "Could not get utxo") $ liftAff $ join <<< hush <$> queryHandle.getUtxoByOref txInput + pure (txInput /\ utxo) + ) >>> map + ( Map.fromFoldable >>> Map.filter + ( flip elem ownAddrs + <<< _.address + <<< unwrap + ) + ) + let + go attempts = do + walletUtxos <- getWalletUtxos <#> fromMaybe Map.empty + unless (ownInputUtxos `Map.isSubmap` walletUtxos) do + when (attempts == 0) do + liftEffect $ throw $ + "walletWaitForInputs: timeout while waiting for wallet" + <> " UTxO set and CTL query layer UTxO set to synchronize. UTxOs" + <> " from Ogmios: " + <> show ownInputUtxos + <> ", UTxOs from wallet: " + <> show walletUtxos + <> ", UTxOs that didn't appear in the wallet: " + <> + show (Map.difference ownInputUtxos walletUtxos) + liftAff $ delay $ wrap $ 1000.0 + go (attempts - 1) + -- As clarified in Eternl discord, they synchronize with the server every 2 + -- minutes, so 150 seconds would probably be enough to also account for + -- possible network latency. + go 150 + + diff --git a/src/Internal/Contract/Wallet.purs b/src/Internal/Contract/Wallet.purs index b92c3ddc8c..bd1c582a48 100644 --- a/src/Internal/Contract/Wallet.purs +++ b/src/Internal/Contract/Wallet.purs @@ -4,6 +4,31 @@ import Prelude import Ctl.Internal.Contract.Monad (Contract) +import Control.Monad.Reader (withReaderT) +import Control.Monad.Reader.Trans (ReaderT, asks) +import Ctl.Internal.Cardano.Types.Transaction (UtxoMap) +import Ctl.Internal.Cardano.Types.TransactionUnspentOutput + ( TransactionUnspentOutput + ) +import Ctl.Internal.Cardano.Types.Value (Value) +import Ctl.Internal.Helpers as Helpers +import Ctl.Internal.Serialization.Address (Address) +import Ctl.Internal.Types.UsedTxOuts (UsedTxOuts, isTxOutRefUsed) +import Ctl.Internal.Wallet (Wallet(Gero, Nami, Flint, Lode, Eternl, KeyWallet)) +import Data.Array (head) +import Data.Array as Array +import Data.Either (hush) +import Data.Foldable (fold) +import Data.Map as Map +import Data.Maybe (Maybe(Nothing), fromMaybe, maybe) +import Data.Newtype (unwrap, wrap) +import Data.Traversable (for, for_, traverse) +import Data.Tuple.Nested ((/\)) +import Data.UInt as UInt +import Effect.Aff (Aff) +import Effect.Aff.Class (liftAff) +import Effect.Class (liftEffect) +import Effect.Exception (throw) import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.Helpers (liftM) import Ctl.Internal.Serialization.Address @@ -28,28 +53,8 @@ import Ctl.Internal.Wallet ) import Ctl.Internal.Wallet.Cip30 (DataSignature) import Data.Array (catMaybes) -import Data.Foldable (fold) -import Data.Newtype (unwrap, wrap) -import Effect.Aff - ( Aff - ) -import Effect.Aff.Class (liftAff) import Effect.Exception (error, throw) -import Control.Monad.Reader (withReaderT) -import Control.Monad.Reader.Trans (ReaderT, asks) -import Ctl.Internal.Cardano.Types.Transaction (UtxoMap) -import Ctl.Internal.Cardano.Types.TransactionUnspentOutput - ( TransactionUnspentOutput - ) -import Ctl.Internal.Helpers as Helpers -import Ctl.Internal.Types.UsedTxOuts (UsedTxOuts, isTxOutRefUsed) -import Data.Array as Array -import Data.Either (hush) -import Data.Map as Map -import Data.Maybe (Maybe(Nothing), fromMaybe, maybe) import Data.Traversable (for_, traverse) -import Data.UInt as UInt -import Effect.Class (liftEffect) getUnusedAddresses :: Contract (Array Address) getUnusedAddresses = fold <$> do @@ -142,6 +147,7 @@ callCip30Wallet -> Aff a callCip30Wallet wallet act = act wallet wallet.connection +-- TODO Move filterLockedUtxos :: UtxoMap -> Contract UtxoMap filterLockedUtxos utxos = withTxRefsCache $ @@ -191,3 +197,39 @@ getWalletCollateral = do "Wallet returned too many UTxOs as collateral. This is likely a bug in \ \the wallet." +getWalletBalance + :: Contract (Maybe Value) +getWalletBalance = do + queryHandle <- getQueryHandle + asks _.wallet >>= map join <<< traverse case _ of + Nami wallet -> liftAff $ wallet.getBalance wallet.connection + Gero wallet -> liftAff $ wallet.getBalance wallet.connection + Eternl wallet -> liftAff $ wallet.getBalance wallet.connection + Flint wallet -> liftAff $ wallet.getBalance wallet.connection + Lode wallet -> liftAff $ wallet.getBalance wallet.connection + KeyWallet _ -> do + -- Implement via `utxosAt` + addresses <- getWalletAddresses + fold <$> for addresses \address -> do + liftAff $ queryHandle.utxosAt address <#> hush >>> map + -- Combine `Value`s + (fold <<< map _.amount <<< map unwrap <<< Map.values) + +getWalletUtxos :: Contract (Maybe UtxoMap) +getWalletUtxos = do + queryHandle <- getQueryHandle + asks _.wallet >>= map join <<< traverse case _ of + Nami wallet -> liftAff $ wallet.getUtxos wallet.connection <#> map toUtxoMap + Gero wallet -> liftAff $ wallet.getUtxos wallet.connection <#> map toUtxoMap + Flint wallet -> liftAff $ wallet.getUtxos wallet.connection <#> map + toUtxoMap + Eternl wallet -> liftAff $ wallet.getUtxos wallet.connection <#> map + toUtxoMap + Lode wallet -> liftAff $ wallet.getUtxos wallet.connection <#> map toUtxoMap + KeyWallet _ -> do + mbAddress <- getWalletAddresses <#> head + map join $ for mbAddress $ map hush <<< liftAff <<< queryHandle.utxosAt + where + toUtxoMap :: Array TransactionUnspentOutput -> UtxoMap + toUtxoMap = Map.fromFoldable <<< map + (unwrap >>> \({ input, output }) -> input /\ output) diff --git a/src/Internal/Plutip/Server.purs b/src/Internal/Plutip/Server.purs index fdca358280..ac33c6a76a 100644 --- a/src/Internal/Plutip/Server.purs +++ b/src/Internal/Plutip/Server.purs @@ -20,9 +20,13 @@ import Affjax.RequestBody as RequestBody import Affjax.RequestHeader as Header import Affjax.ResponseFormat as Affjax.ResponseFormat import Contract.Address (NetworkId(MainnetId)) +import Contract.Config (QueryBackendParams(CtlBackendParams)) +import Ctl.Internal.Contract.QueryBackend (defaultBackend, mkSingletonBackendParams) +import Ctl.Internal.Contract.Monad (buildBackend, getLedgerConstants) +import Ctl.Internal.Contract.Monad (stopContractEnv) as Contract import Contract.Monad ( Contract - , ContractEnv(ContractEnv) + , ContractEnv , liftContractM , runContractInEnv ) @@ -30,7 +34,6 @@ import Control.Monad.Error.Class (liftEither) import Control.Monad.State (State, execState, modify_) import Control.Monad.Trans.Class (lift) import Control.Monad.Writer (censor, execWriterT, tell) -import Control.Parallel (parallel, sequential) import Ctl.Internal.Helpers ((<>)) import Ctl.Internal.Plutip.PortCheck (isPortAvailable) import Ctl.Internal.Plutip.Spawn @@ -66,9 +69,7 @@ import Ctl.Internal.QueryM , Logger , emptyHooks , mkLogger - , stopQueryRuntime ) -import Ctl.Internal.QueryM as QueryM import Ctl.Internal.QueryM.Logging (setupLogs) import Ctl.Internal.QueryM.UniqueId (uniqueId) import Ctl.Internal.Test.TestPlanM (TestPlanM) @@ -83,11 +84,11 @@ import Data.HTTP.Method as Method import Data.Log.Level (LogLevel) import Data.Log.Message (Message) import Data.Maybe (Maybe(Just, Nothing), maybe) -import Data.Newtype (over, unwrap, wrap) +import Data.Newtype (over, wrap) import Data.String.CodeUnits as String import Data.String.Pattern (Pattern(Pattern)) import Data.Traversable (foldMap, for, for_, sequence_, traverse_) -import Data.Tuple (Tuple(Tuple), fst, snd) +import Data.Tuple (fst, snd) import Data.Tuple.Nested (type (/\), (/\)) import Data.UInt (UInt) import Data.UInt as UInt @@ -119,7 +120,7 @@ runPlutipContract . UtxoDistribution distr wallets => PlutipConfig -> distr - -> (wallets -> Contract () a) + -> (wallets -> Contract a) -> Aff a runPlutipContract cfg distr cont = withPlutipContractEnv cfg distr \env wallets -> @@ -132,7 +133,7 @@ withPlutipContractEnv . UtxoDistribution distr wallets => PlutipConfig -> distr - -> (ContractEnv () -> wallets -> Aff a) + -> (ContractEnv -> wallets -> Aff a) -> Aff a withPlutipContractEnv plutipCfg distr cont = do cleanupRef <- liftEffect $ Ref.new mempty @@ -204,19 +205,19 @@ newtype PlutipTest = PlutipTest type PlutipTestHandler :: Type -> Type -> Type -> Type type PlutipTestHandler distr wallets r = - UtxoDistribution distr wallets => distr -> (wallets -> Contract () Unit) -> r + UtxoDistribution distr wallets => distr -> (wallets -> Contract Unit) -> r -- | Store a wallet `UtxoDistribution` and a `Contract` that depends on those wallets withWallets :: forall (distr :: Type) (wallets :: Type) . UtxoDistribution distr wallets => distr - -> (wallets -> Contract () Unit) + -> (wallets -> Contract Unit) -> PlutipTest withWallets distr tests = PlutipTest \h -> h distr tests -- | Lift a `Contract` into `PlutipTest` -noWallet :: Contract () Unit -> PlutipTest +noWallet :: Contract Unit -> PlutipTest noWallet = withWallets unit <<< const -- | Represents `Contract`s in `TestPlanM` that depend on *some* wallet `UtxoDistribution` @@ -232,7 +233,7 @@ type PlutipTestPlanHandler :: Type -> Type -> Type -> Type type PlutipTestPlanHandler distr wallets r = UtxoDistribution distr wallets => distr - -> TestPlanM (wallets -> Contract () Unit) Unit + -> TestPlanM (wallets -> Contract Unit) Unit -> r -- | Lifts the utxo distributions of each test out of Mote, into a combined @@ -281,7 +282,7 @@ startPlutipContractEnv -> distr -> Ref (Array (Aff Unit)) -> Aff - { env :: ContractEnv () + { env :: ContractEnv , wallets :: wallets , printLogs :: Aff Unit , clearLogs :: Aff Unit @@ -378,13 +379,13 @@ startPlutipContractEnv plutipCfg distr cleanupRef = do $ const (pure unit) mkWallets' - :: ContractEnv () + :: ContractEnv -> PrivatePaymentKey -> ClusterStartupParameters -> Aff wallets mkWallets' env ourKey response = do runContractInEnv - (over wrap (_ { config { customLogger = Just (\_ _ -> pure unit) } }) env) + ((_ { customLogger = Just (\_ _ -> pure unit) }) env) do wallets <- liftContractM @@ -396,7 +397,7 @@ startPlutipContractEnv plutipCfg distr cleanupRef = do mkContractEnv' :: Aff - { env :: ContractEnv () + { env :: ContractEnv , printLogs :: Aff Unit , clearLogs :: Aff Unit } @@ -430,8 +431,8 @@ startPlutipContractEnv plutipCfg distr cleanupRef = do } -- a version of Contract.Monad.stopContractEnv without a compile-time warning - stopContractEnv :: ContractEnv () -> Effect Unit - stopContractEnv env = stopQueryRuntime (unwrap env).runtime + stopContractEnv :: ContractEnv -> Effect Unit + stopContractEnv env = Contract.stopContractEnv env -- | Throw an exception if `PlutipConfig` contains ports that are occupied. configCheck :: PlutipConfig -> Aff Unit @@ -731,48 +732,27 @@ mkClusterContractEnv :: PlutipConfig -> Logger -> Maybe (LogLevel -> Message -> Aff Unit) - -> Aff (ContractEnv ()) + -> Aff ContractEnv mkClusterContractEnv plutipCfg logger customLogger = do - datumCacheWsRef <- liftEffect $ Ref.new Nothing - datumCacheWs /\ ogmiosWs <- sequential $ - Tuple - <$> parallel - ( QueryM.mkDatumCacheWebSocketAff datumCacheWsRef logger - QueryM.defaultDatumCacheWsConfig - { port = plutipCfg.ogmiosDatumCacheConfig.port - , host = plutipCfg.ogmiosDatumCacheConfig.host - } - ) - <*> parallel - ( QueryM.mkOgmiosWebSocketAff datumCacheWsRef logger - QueryM.defaultOgmiosWsConfig - { port = plutipCfg.ogmiosConfig.port - , host = plutipCfg.ogmiosConfig.host - } - ) usedTxOuts <- newUsedTxOuts - pparams <- QueryM.getProtocolParametersAff ogmiosWs logger - pure $ ContractEnv - { config: - { ctlServerConfig: plutipCfg.ctlServerConfig - , ogmiosConfig: plutipCfg.ogmiosConfig - , datumCacheConfig: plutipCfg.ogmiosDatumCacheConfig - , kupoConfig: plutipCfg.kupoConfig - , networkId: MainnetId - , logLevel: plutipCfg.logLevel - , walletSpec: Nothing - , customLogger: customLogger - , suppressLogs: plutipCfg.suppressLogs - , hooks: emptyHooks - } - , runtime: - { ogmiosWs - , datumCacheWs - , wallet: Nothing - , usedTxOuts - , pparams - } - , extraConfig: {} + backend <- buildBackend logger $ mkSingletonBackendParams $ CtlBackendParams + { ogmiosConfig: plutipCfg.ogmiosConfig + , odcConfig: plutipCfg.ogmiosDatumCacheConfig + , kupoConfig: plutipCfg.kupoConfig + } + ledgerConstants <- getLedgerConstants logger $ defaultBackend backend + pure + { backend + , ctlServerConfig: plutipCfg.ctlServerConfig + , networkId: MainnetId + , logLevel: plutipCfg.logLevel + , walletSpec: Nothing + , customLogger: customLogger + , suppressLogs: plutipCfg.suppressLogs + , hooks: emptyHooks + , wallet: Nothing + , usedTxOuts + , ledgerConstants } startCtlServer :: UInt -> Aff ManagedProcess diff --git a/src/Internal/Plutip/UtxoDistribution.purs b/src/Internal/Plutip/UtxoDistribution.purs index e8fe0215f7..a3ba803eda 100644 --- a/src/Internal/Plutip/UtxoDistribution.purs +++ b/src/Internal/Plutip/UtxoDistribution.purs @@ -172,10 +172,9 @@ type WalletInfo = -- | be cleared (this function is intended to be used only on plutip -- | startup). transferFundsFromEnterpriseToBase - :: forall (r :: Row Type) - . PrivatePaymentKey + :: PrivatePaymentKey -> Array KeyWallet - -> Contract r Unit + -> Contract Unit transferFundsFromEnterpriseToBase ourKey wallets = do -- Get all utxos and key hashes at all wallets containing a stake key walletsInfo <- foldM addStakeKeyWalletInfo mempty wallets @@ -207,7 +206,7 @@ transferFundsFromEnterpriseToBase ourKey wallets = do -- Clear the used txouts cache because we know the state of these -- utxos is settled, see here: -- https://github.com/Plutonomicon/cardano-transaction-lib/pull/838#discussion_r941592493 - cache <- asks (unwrap <<< _.usedTxOuts <<< _.runtime <<< unwrap) + cache <- asks (unwrap <<< _.usedTxOuts) liftEffect $ Ref.write Map.empty cache where constraintsForWallet :: WalletInfo -> Constraints.TxConstraints Void Void @@ -227,7 +226,7 @@ transferFundsFromEnterpriseToBase ourKey wallets = do addStakeKeyWalletInfo :: List WalletInfo -> KeyWallet - -> Contract r (List WalletInfo) + -> Contract (List WalletInfo) addStakeKeyWalletInfo walletsInfo wallet = withKeyWallet wallet $ join <<< head <$> ownStakePubKeysHashes >>= case _ of Nothing -> pure walletsInfo diff --git a/src/Internal/ReindexRedeemers.purs b/src/Internal/ReindexRedeemers.purs index cee63dde06..1264ff95fb 100644 --- a/src/Internal/ReindexRedeemers.purs +++ b/src/Internal/ReindexRedeemers.purs @@ -8,10 +8,7 @@ module Ctl.Internal.ReindexRedeemers import Prelude -import Control.Monad.Except.Trans (ExceptT(ExceptT), except, runExceptT) import Ctl.Internal.Cardano.Types.Transaction (Redeemer(Redeemer)) as T -import Ctl.Internal.Helpers (liftEither) -import Ctl.Internal.QueryM (QueryM) import Ctl.Internal.Types.RedeemerTag (RedeemerTag(Spend)) import Ctl.Internal.Types.Transaction (TransactionInput) import Data.Array (elemIndex) @@ -42,19 +39,18 @@ type RedeemersTxIn = T.Redeemer /\ Maybe TransactionInput reindexSpentScriptRedeemers :: Array TransactionInput -> Array RedeemersTxIn - -> QueryM (Either ReindexErrors (Array T.Redeemer)) -reindexSpentScriptRedeemers inputs redeemersTxIns = runExceptT do - redeemersTxInsReindexed <- ExceptT $ + -> Either ReindexErrors (Array T.Redeemer) +reindexSpentScriptRedeemers inputs redeemersTxIns = do + redeemersTxInsReindexed <- reindexSpentScriptRedeemers' inputs redeemersTxIns - except <<< Right $ - map fst redeemersTxInsReindexed + Right $ map fst redeemersTxInsReindexed reindexSpentScriptRedeemers' :: Array TransactionInput -> Array RedeemersTxIn - -> QueryM (Either ReindexErrors (Array RedeemersTxIn)) -reindexSpentScriptRedeemers' inputs redeemersTxIns = runExceptT do - liftEither $ traverse (reindex inputs) redeemersTxIns + -> Either ReindexErrors (Array RedeemersTxIn) +reindexSpentScriptRedeemers' inputs redeemersTxIns = do + traverse (reindex inputs) redeemersTxIns where reindex :: Array TransactionInput diff --git a/src/Internal/Test/E2E/Route.purs b/src/Internal/Test/E2E/Route.purs index 2cd00bba96..c713246479 100644 --- a/src/Internal/Test/E2E/Route.purs +++ b/src/Internal/Test/E2E/Route.purs @@ -9,9 +9,10 @@ module Ctl.Internal.E2E.Route import Prelude -import Contract.Config (ConfigParams) +import Contract.Config (ContractParams) import Contract.Monad (Contract, runContract) import Contract.Test.Cip30Mock (WalletMock, withCip30Mock) +import Ctl.Internal.Contract.QueryBackend (QueryBackendParams(CtlBackendParams), mkSingletonBackendParams) import Contract.Wallet ( PrivatePaymentKey(PrivatePaymentKey) , PrivateStakeKey(PrivateStakeKey) @@ -102,8 +103,8 @@ parseRoute queryString = mkPrivateKey str <#> PrivateStakeKey addLinks - :: Map E2EConfigName (ConfigParams () /\ Maybe WalletMock) - -> Map E2ETestName (Contract () Unit) + :: Map E2EConfigName (ContractParams /\ Maybe WalletMock) + -> Map E2ETestName (Contract Unit) -> Effect Unit addLinks configMaps testMaps = do let @@ -133,8 +134,8 @@ addLinks configMaps testMaps = do -- | from the cluster should be used. If there's no local cluster, an error -- | will be thrown. route - :: Map E2EConfigName (ConfigParams () /\ Maybe WalletMock) - -> Map E2ETestName (Contract () Unit) + :: Map E2EConfigName (ContractParams /\ Maybe WalletMock) + -> Map E2ETestName (Contract Unit) -> Effect Unit route configs tests = do queryString <- fold <<< last <<< split (Pattern "?") <$> _queryString @@ -176,7 +177,7 @@ route configs tests = do test where -- Eternl does not initialize instantly. We have to add a small delay. - delayIfEternl :: forall (r :: Row Type). ConfigParams r -> Aff Unit + delayIfEternl :: ContractParams -> Aff Unit delayIfEternl config = case config.walletSpec of Just ConnectToEternl -> @@ -201,7 +202,7 @@ route configs tests = do -- Override config values with parameters from cluster setup setClusterOptions - :: forall (r :: Row Type). ClusterSetup -> ConfigParams r -> ConfigParams r + :: ClusterSetup -> ContractParams -> ContractParams setClusterOptions { ctlServerConfig , ogmiosConfig @@ -210,10 +211,12 @@ route configs tests = do } config = config - { ctlServerConfig = ctlServerConfig - , ogmiosConfig = ogmiosConfig - , datumCacheConfig = datumCacheConfig - , kupoConfig = kupoConfig + { backendParams = mkSingletonBackendParams $ CtlBackendParams + { ogmiosConfig: ogmiosConfig + , odcConfig: datumCacheConfig + , kupoConfig: kupoConfig + } + , ctlServerConfig = ctlServerConfig } foreign import _queryString :: Effect String diff --git a/src/Internal/Test/E2E/Runner.purs b/src/Internal/Test/E2E/Runner.purs index 5e071ad87f..2f6703d5fd 100644 --- a/src/Internal/Test/E2E/Runner.purs +++ b/src/Internal/Test/E2E/Runner.purs @@ -12,6 +12,7 @@ import Affjax.ResponseFormat as Affjax.ResponseFormat import Control.Alt ((<|>)) import Control.Monad.Error.Class (liftMaybe) import Control.Promise (Promise, toAffE) +import Ctl.Internal.Contract.QueryBackend (QueryBackend(CtlBackend), defaultBackend) import Ctl.Internal.Deserialization.Keys (privateKeyFromBytes) import Ctl.Internal.Helpers (liftedM, (<>)) import Ctl.Internal.Plutip.Server (withPlutipContractEnv) @@ -84,7 +85,7 @@ import Data.List (intercalate) import Data.Log.Level (LogLevel(Trace)) import Data.Map as Map import Data.Maybe (Maybe(Just, Nothing), fromJust, fromMaybe, maybe) -import Data.Newtype (unwrap, wrap) +import Data.Newtype (wrap) import Data.Posix.Signal (Signal(SIGINT)) import Data.String (Pattern(Pattern)) import Data.String (contains, null, split, toLower, toUpper, trim) as String @@ -260,17 +261,18 @@ testPlan opts@{ tests } rt@{ wallets } = -- https://github.com/Plutonomicon/cardano-transaction-lib/issues/1197 liftAff $ withPlutipContractEnv (buildPlutipConfig opts) distr \env wallet -> do - let - (clusterSetup :: ClusterSetup) = - { ctlServerConfig: (unwrap env).config.ctlServerConfig - , ogmiosConfig: (unwrap env).config.ogmiosConfig - , datumCacheConfig: (unwrap env).config.datumCacheConfig - , kupoConfig: (unwrap env).config.kupoConfig + (clusterSetup :: ClusterSetup) <- case defaultBackend env.backend of + CtlBackend backend -> pure + { ctlServerConfig: env.ctlServerConfig + , ogmiosConfig: backend.ogmios.config + , datumCacheConfig: backend.odc.config + , kupoConfig: backend.kupoConfig , keys: { payment: keyWalletPrivatePaymentKey wallet , stake: keyWalletPrivateStakeKey wallet } } + _ -> liftEffect $ throw "Unsupported backend" withBrowser opts.noHeadless opts.extraBrowserArgs rt Nothing \browser -> do withE2ETest opts.skipJQuery (wrap url) browser \{ page } -> do diff --git a/src/Internal/Types/ScriptLookups.purs b/src/Internal/Types/ScriptLookups.purs index 0143d46462..31035ea9c7 100644 --- a/src/Internal/Types/ScriptLookups.purs +++ b/src/Internal/Types/ScriptLookups.purs @@ -53,10 +53,11 @@ module Ctl.Internal.Types.ScriptLookups ) where import Prelude hiding (join) +import Prelude (join) as Bind +import Ctl.Internal.Contract.Monad (Contract, wrapQueryM) import Effect.Aff.Class (liftAff) import Ctl.Internal.Contract.QueryHandle (getQueryHandle) -import Ctl.Internal.Contract.Monad (Contract) import Aeson (class EncodeAeson) import Contract.Hashing (plutusScriptStakeValidatorHash) import Control.Monad.Error.Class (catchError, liftMaybe, throwError) @@ -119,19 +120,10 @@ import Ctl.Internal.Plutus.Types.Transaction (TransactionOutputWithRefScript) as import Ctl.Internal.Plutus.Types.TransactionUnspentOutput ( TransactionUnspentOutput(TransactionUnspentOutput) ) -import Ctl.Internal.QueryM - ( QueryM - , QueryMExtended - , getDatumByHash - , getProtocolParameters - ) -import Ctl.Internal.QueryM (getNetworkId) as QueryM -import Ctl.Internal.QueryM.EraSummaries (getEraSummaries) import Ctl.Internal.QueryM.Pools ( getPubKeyHashDelegationsAndRewards , getValidatorHashDelegationsAndRewards ) -import Ctl.Internal.QueryM.SystemStart (getSystemStart) import Ctl.Internal.Scripts ( mintingPolicyHash , nativeScriptStakeValidatorHash @@ -278,7 +270,6 @@ import Data.Traversable (for, traverse_) import Data.Tuple (fst, snd) import Data.Tuple.Nested (type (/\), (/\)) import Effect (Effect) -import Effect.Aff (Aff) import Effect.Class (liftEffect) import MedeaPrelude (mapMaybe) import Type.Proxy (Proxy(Proxy)) @@ -647,9 +638,9 @@ runConstraintsM => IsData redeemer => ScriptLookups validator -> TxConstraints redeemer datum - -> QueryM (Either MkUnbalancedTxError (ConstraintProcessingState validator)) + -> Contract (Either MkUnbalancedTxError (ConstraintProcessingState validator)) runConstraintsM lookups txConstraints = do - costModels <- getProtocolParameters <#> unwrap >>> _.costModels + costModels <- asks $ _.ledgerConstants >>> _.pparams >>> unwrap >>> _.costModels let initCps :: ConstraintProcessingState validator initCps = @@ -684,7 +675,7 @@ mkUnbalancedTx' => IsData redeemer => ScriptLookups validator -> TxConstraints redeemer datum - -> QueryM (Either MkUnbalancedTxError UnbalancedTx) + -> Contract (Either MkUnbalancedTxError UnbalancedTx) mkUnbalancedTx' scriptLookups txConstraints = runConstraintsM scriptLookups txConstraints <#> map _.unbalancedTx @@ -722,7 +713,7 @@ mkUnbalancedTx => IsData redeemer => ScriptLookups validator -> TxConstraints redeemer datum - -> QueryM (Either MkUnbalancedTxError UnattachedUnbalancedTx) + -> Contract (Either MkUnbalancedTxError UnattachedUnbalancedTx) mkUnbalancedTx scriptLookups txConstraints = runConstraintsM scriptLookups txConstraints <#> map \{ unbalancedTx, datums, redeemersTxIns } -> @@ -846,7 +837,7 @@ addOwnOutput => OutputConstraint datum -> ConstraintsM validator (Either MkUnbalancedTxError Unit) addOwnOutput (OutputConstraint { datum: d, value }) = do - queryHandle <- getQueryHandle + queryHandle <- lift $ getQueryHandle networkId <- asks _.networkId runExceptT do ScriptLookups { typedValidator } <- use _lookups @@ -858,9 +849,7 @@ addOwnOutput (OutputConstraint { datum: d, value }) = do -- We are erroring if we don't have a datumhash given the polymorphic datum -- in the `OutputConstraint`: dHash <- liftM TypedTxOutHasNoDatumHash (typedTxOutDatumHash typedTxOut) - dat <- - -- TODO fix - ExceptT $ liftAff $ (queryHandle.getDatumByHash dHash <#> hush >>> join >>> note (CannotQueryDatum dHash)) + dat <- ExceptT $ liftAff $ queryHandle.getDatumByHash dHash <#> hush >>> Bind.join >>> note (CannotQueryDatum dHash) _cpsToTxBody <<< _outputs %= Array.(:) txOut ExceptT $ addDatum dat _valueSpentBalancesOutputs <>= provideValue value' @@ -1056,8 +1045,9 @@ processConstraint -> Map ValidatorHash Validator -> TxConstraint -> ConstraintsM a (Either MkUnbalancedTxError Unit) -processConstraint mpsMap osMap = do - case _ of +processConstraint mpsMap osMap c = do + queryHandle <- lift $ getQueryHandle + case c of MustIncludeDatum dat -> addDatum dat MustValidateIn posixTimeRange -> do { slotReference, slotLength, systemStart } <- asks _.ledgerConstants @@ -1125,7 +1115,7 @@ processConstraint mpsMap osMap = do if isRight mDatumLookup then pure mDatumLookup else - lift $ getDatumByHash dHash <#> note + liftAff $ queryHandle.getDatumByHash dHash <#> hush >>> Bind.join >>> note (CannotQueryDatum dHash) ExceptT $ addDatum dat OutputDatum _ -> pure unit @@ -1379,8 +1369,8 @@ processConstraint mpsMap osMap = do poolKeyHash attachToCps attachNativeScript (unwrap stakeValidator) MustWithdrawStakePubKey spkh -> runExceptT do - networkId <- lift getNetworkId - mbRewards <- lift $ lift $ getPubKeyHashDelegationsAndRewards spkh + networkId <- asks _.networkId + mbRewards <- lift $ lift $ wrapQueryM $ getPubKeyHashDelegationsAndRewards spkh ({ rewards }) <- ExceptT $ pure $ note (CannotWithdrawRewardsPubKey spkh) mbRewards let @@ -1390,8 +1380,8 @@ processConstraint mpsMap osMap = do Map.union (Map.singleton rewardAddress (fromMaybe (Coin zero) rewards)) MustWithdrawStakePlutusScript stakeValidator redeemerData -> runExceptT do let hash = plutusScriptStakeValidatorHash stakeValidator - networkId <- lift getNetworkId - mbRewards <- lift $ lift $ getValidatorHashDelegationsAndRewards hash + networkId <- asks _.networkId + mbRewards <- lift $ lift $ wrapQueryM $ getValidatorHashDelegationsAndRewards hash let rewardAddress = RewardAddress.stakeValidatorHashRewardAddress networkId hash @@ -1412,8 +1402,8 @@ processConstraint mpsMap osMap = do _redeemersTxIns <>= Array.singleton (redeemer /\ Nothing) MustWithdrawStakeNativeScript stakeValidator -> runExceptT do let hash = nativeScriptStakeValidatorHash stakeValidator - networkId <- lift getNetworkId - mbRewards <- lift $ lift $ getValidatorHashDelegationsAndRewards hash + networkId <- asks _.networkId + mbRewards <- lift $ lift $ wrapQueryM $ getValidatorHashDelegationsAndRewards hash let rewardAddress = RewardAddress.stakeValidatorHashRewardAddress networkId hash @@ -1458,7 +1448,7 @@ processConstraint mpsMap osMap = do -> DatumPresence -> ExceptT MkUnbalancedTxError - (StateT (ConstraintProcessingState a) (QueryMExtended () Aff)) + (StateT (ConstraintProcessingState a) Contract) OutputDatum outputDatum dat = case _ of DatumInline -> pure $ OutputDatum dat diff --git a/src/Internal/Wallet/Cip30Mock.purs b/src/Internal/Wallet/Cip30Mock.purs index 5b6d5d0c7e..d180450652 100644 --- a/src/Internal/Wallet/Cip30Mock.purs +++ b/src/Internal/Wallet/Cip30Mock.purs @@ -2,18 +2,17 @@ module Ctl.Internal.Wallet.Cip30Mock where import Prelude -import Contract.Monad (Contract, ContractEnv, wrapContract) +import Contract.Monad (Contract) import Control.Monad.Error.Class (liftMaybe, try) import Control.Monad.Reader (ask) import Control.Monad.Reader.Class (local) import Control.Promise (Promise, fromAff) +import Ctl.Internal.Contract.QueryHandle (getQueryHandle') import Ctl.Internal.Cardano.Types.TransactionUnspentOutput ( TransactionUnspentOutput(TransactionUnspentOutput) ) import Ctl.Internal.Deserialization.Transaction (deserializeTransaction) import Ctl.Internal.Helpers (liftEither) -import Ctl.Internal.QueryM (QueryM, runQueryMInRuntime) -import Ctl.Internal.QueryM.Utxos (utxosAt) import Ctl.Internal.Serialization ( convertTransactionUnspentOutput , convertValue @@ -39,10 +38,6 @@ import Data.Array as Array import Data.Either (hush) import Data.Foldable (fold, foldMap) import Data.Function.Uncurried (Fn2, mkFn2) -import Data.Lens ((.~)) -import Data.Lens.Common (simple) -import Data.Lens.Iso.Newtype (_Newtype) -import Data.Lens.Record (prop) import Data.Map as Map import Data.Maybe (Maybe(Just)) import Data.Newtype (unwrap, wrap) @@ -55,7 +50,6 @@ import Effect.Aff.Class (liftAff) import Effect.Class (liftEffect) import Effect.Exception (error) import Effect.Unsafe (unsafePerformEffect) -import Type.Proxy (Proxy(Proxy)) import Untagged.Union (asOneOf) data WalletMock = MockFlint | MockGero | MockNami | MockLode @@ -74,23 +68,17 @@ data WalletMock = MockFlint | MockGero | MockNami | MockLode -- | it will have to be changed a lot to successfully mimic the behavior of -- | multi-address wallets, like Eternl. withCip30Mock - :: forall (r :: Row Type) (a :: Type) + :: forall (a :: Type) . KeyWallet -> WalletMock - -> Contract r a - -> Contract r a + -> Contract a + -> Contract a withCip30Mock (KeyWallet keyWallet) mock contract = do - cip30Mock <- wrapContract $ mkCip30Mock keyWallet.paymentKey + cip30Mock <- mkCip30Mock keyWallet.paymentKey keyWallet.stakeKey deleteMock <- liftEffect $ injectCip30Mock mockString cip30Mock wallet <- liftAff mkWalletAff' - let - setUpdatedWallet :: ContractEnv r -> ContractEnv r - setUpdatedWallet = - simple _Newtype <<< prop (Proxy :: Proxy "runtime") <<< prop - (Proxy :: Proxy "wallet") .~ - (Just wallet) - res <- try $ local setUpdatedWallet contract + res <- try $ local _ { wallet = Just wallet } contract liftEffect deleteMock liftEither res where @@ -122,13 +110,13 @@ type Cip30Mock = } mkCip30Mock - :: PrivatePaymentKey -> Maybe PrivateStakeKey -> QueryM Cip30Mock + :: PrivatePaymentKey -> Maybe PrivateStakeKey -> Contract Cip30Mock mkCip30Mock pKey mSKey = do - { config, runtime } <- ask + env <- ask let getCollateralUtxos utxos = do let - pparams = unwrap $ runtime.pparams + pparams = unwrap $ env.ledgerConstants.pparams coinsPerUtxoUnit = pparams.coinsPerUtxoUnit maxCollateralInputs = UInt.toInt $ pparams.maxCollateralInputs @@ -138,15 +126,18 @@ mkCip30Mock pKey mSKey = do utxos <#> fold + utxosAt address = liftMaybe (error "No UTxOs at address") <<< hush =<< do + let queryHandle = getQueryHandle' env + queryHandle.utxosAt address + pure $ { getNetworkId: fromAff $ pure $ - case config.networkId of + case env.networkId of TestnetId -> 0 MainnetId -> 1 , getUtxos: fromAff do - ownAddress <- (unwrap keyWallet).address config.networkId - utxos <- liftMaybe (error "No UTxOs at address") =<< - runQueryMInRuntime config runtime (utxosAt ownAddress) + ownAddress <- (unwrap keyWallet).address env.networkId + utxos <- utxosAt ownAddress collateralUtxos <- getCollateralUtxos utxos let -- filter UTxOs that will be used as collateral @@ -160,31 +151,29 @@ mkCip30Mock pKey mSKey = do TransactionUnspentOutput { input, output } pure $ (byteArrayToHex <<< toBytes <<< asOneOf) <$> cslUtxos , getCollateral: fromAff do - ownAddress <- (unwrap keyWallet).address config.networkId - utxos <- liftMaybe (error "No UTxOs at address") =<< - runQueryMInRuntime config runtime (utxosAt ownAddress) + ownAddress <- (unwrap keyWallet).address env.networkId + utxos <- utxosAt ownAddress collateralUtxos <- getCollateralUtxos utxos cslUnspentOutput <- liftEffect $ traverse convertTransactionUnspentOutput collateralUtxos pure $ (byteArrayToHex <<< toBytes <<< asOneOf) <$> cslUnspentOutput , getBalance: fromAff do - ownAddress <- (unwrap keyWallet).address config.networkId - utxos <- liftMaybe (error "No UTxOs at address") =<< - runQueryMInRuntime config runtime (utxosAt ownAddress) + ownAddress <- (unwrap keyWallet).address env.networkId + utxos <- utxosAt ownAddress value <- liftEffect $ convertValue $ (foldMap (_.amount <<< unwrap) <<< Map.values) utxos pure $ byteArrayToHex $ toBytes $ asOneOf value , getUsedAddresses: fromAff do - (unwrap keyWallet).address config.networkId <#> \address -> + (unwrap keyWallet).address env.networkId <#> \address -> [ (byteArrayToHex <<< toBytes <<< asOneOf) address ] , getUnusedAddresses: fromAff $ pure [] , getChangeAddress: fromAff do - (unwrap keyWallet).address config.networkId <#> + (unwrap keyWallet).address env.networkId <#> (byteArrayToHex <<< toBytes <<< asOneOf) , getRewardAddresses: fromAff do - (unwrap keyWallet).address config.networkId <#> \address -> + (unwrap keyWallet).address env.networkId <#> \address -> [ (byteArrayToHex <<< toBytes <<< asOneOf) address ] , signTx: \str -> unsafePerformEffect $ fromAff do txBytes <- liftMaybe (error "Unable to convert CBOR") $ hexToByteArray @@ -199,7 +188,7 @@ mkCip30Mock pKey mSKey = do , signData: mkFn2 \_addr msg -> unsafePerformEffect $ fromAff do msgBytes <- liftMaybe (error "Unable to convert CBOR") (hexToByteArray msg) - (unwrap keyWallet).signData config.networkId (wrap msgBytes) + (unwrap keyWallet).signData env.networkId (wrap msgBytes) } where keyWallet = privateKeysToKeyWallet pKey mSKey diff --git a/templates/ctl-scaffold/test/E2E.purs b/templates/ctl-scaffold/test/E2E.purs index 71d782f338..6293691a6d 100644 --- a/templates/ctl-scaffold/test/E2E.purs +++ b/templates/ctl-scaffold/test/E2E.purs @@ -4,7 +4,7 @@ module Scaffold.Test.E2E.Serve where import Contract.Prelude import Contract.Config - ( ConfigParams + ( ContractParams , mainnetFlintConfig , mainnetGeroConfig , mainnetLodeConfig @@ -29,7 +29,7 @@ main = do addLinks configs tests route configs tests -configs :: Map E2EConfigName (ConfigParams () /\ Maybe WalletMock) +configs :: Map E2EConfigName (ContractParams /\ Maybe WalletMock) configs = Map.fromFoldable [ "nami" /\ testnetNamiConfig /\ Nothing , "gero" /\ testnetGeroConfig /\ Nothing @@ -47,7 +47,7 @@ configs = Map.fromFoldable , "plutip-lode-mock" /\ mainnetLodeConfig /\ Just MockLode ] -tests :: Map E2ETestName (Contract () Unit) +tests :: Map E2ETestName (Contract Unit) tests = Map.fromFoldable [ "Contract" /\ Scaffold.contract -- Add more `Contract`s here diff --git a/test/AffInterface.purs b/test/AffInterface.purs index 59edf1c321..659750bb0e 100644 --- a/test/AffInterface.purs +++ b/test/AffInterface.purs @@ -49,84 +49,86 @@ addr1 = -- state, and ogmios itself. suite :: TestPlanM (QueryM Unit) Unit suite = do - group "Aff Interface" do - test "UtxosAt Testnet" $ testUtxosAt testnet_addr1 - test "UtxosAt Mainnet" $ testUtxosAt addr1 - test "Get ChainTip" testGetChainTip - test "Get waitUntilSlot" testWaitUntilSlot - test "Get EraSummaries" testGetEraSummaries - test "Get CurrentEpoch" testGetCurrentEpoch - test "Get SystemStart" testGetSystemStart - group "Ogmios error" do - test "Ogmios fails with user-friendly message" do - try testSubmitTxFailure >>= case _ of - Right _ -> do - void $ throwError $ error $ - "Unexpected success in testSubmitTxFailure" - Left error -> do - (Pattern "Server responded with `fault`" `indexOf` show error) - `shouldSatisfy` isJust - group "Ogmios datum cache" do - test "Can process GetDatumByHash" do - testOgmiosDatumCacheGetDatumByHash - test "Can process GetDatumsByHashes" do - testOgmiosDatumCacheGetDatumsByHashes - test "Can process GetDatumsByHashesWithErrors" do - testOgmiosDatumCacheGetDatumsByHashesWithErrors - test "Can process GetTxByHash" do - testOgmiosGetTxByHash - -testOgmiosDatumCacheGetDatumByHash :: QueryM Unit -testOgmiosDatumCacheGetDatumByHash = do - void $ getDatumByHash $ DataHash $ hexToByteArrayUnsafe - "f7c47c65216f7057569111d962a74de807de57e79f7efa86b4e454d42c875e4e" - -testOgmiosDatumCacheGetDatumsByHashes :: QueryM Unit -testOgmiosDatumCacheGetDatumsByHashes = do - void $ getDatumsByHashes $ pure $ DataHash $ hexToByteArrayUnsafe - "f7c47c65216f7057569111d962a74de807de57e79f7efa86b4e454d42c875e4e" - -testOgmiosDatumCacheGetDatumsByHashesWithErrors :: QueryM Unit -testOgmiosDatumCacheGetDatumsByHashesWithErrors = do - void $ getDatumsByHashesWithErrors $ pure $ DataHash $ hexToByteArrayUnsafe - "f7c47c65216f7057569111d962a74de807de57e79f7efa86b4e454d42c875e4e" - -testOgmiosGetTxByHash :: QueryM Unit -testOgmiosGetTxByHash = do - void $ getTxByHash $ hexToByteArrayUnsafe - "f7c47c65216f7057569111d962a74de807de57e79f7efa86b4e454d42c875e4e" - -testUtxosAt :: OgmiosAddress -> QueryM Unit -testUtxosAt testAddr = case ogmiosAddressToAddress testAddr of - Nothing -> throwError (error "Failed UtxosAt") - Just addr -> void $ utxosAt addr - -testGetChainTip :: QueryM Unit -testGetChainTip = do - void getChainTip - -testWaitUntilSlot :: QueryM Unit -testWaitUntilSlot = do - void $ getChainTip >>= case _ of - TipAtGenesis -> throwError $ error "Tip is at genesis" - Tip (ChainTip { slot }) -> do - waitUntilSlot $ over Slot - (fromMaybe (BigNum.fromInt 0) <<< BigNum.add (BigNum.fromInt 10)) - slot - -testGetEraSummaries :: QueryM Unit -testGetEraSummaries = do - void getEraSummaries - -testSubmitTxFailure :: QueryM Unit -testSubmitTxFailure = do - let bytes = hexToByteArrayUnsafe "00" - void $ submitTxOgmios bytes (wrap bytes) - -testGetCurrentEpoch :: QueryM Unit -testGetCurrentEpoch = do - void getCurrentEpoch - -testGetSystemStart :: QueryM Unit -testGetSystemStart = do - void getSystemStart + pure unit +-- +-- group "Aff Interface" do +-- test "UtxosAt Testnet" $ testUtxosAt testnet_addr1 +-- test "UtxosAt Mainnet" $ testUtxosAt addr1 +-- test "Get ChainTip" testGetChainTip +-- test "Get waitUntilSlot" testWaitUntilSlot +-- test "Get EraSummaries" testGetEraSummaries +-- test "Get CurrentEpoch" testGetCurrentEpoch +-- test "Get SystemStart" testGetSystemStart +-- group "Ogmios error" do +-- test "Ogmios fails with user-friendly message" do +-- try testSubmitTxFailure >>= case _ of +-- Right _ -> do +-- void $ throwError $ error $ +-- "Unexpected success in testSubmitTxFailure" +-- Left error -> do +-- (Pattern "Server responded with `fault`" `indexOf` show error) +-- `shouldSatisfy` isJust +-- group "Ogmios datum cache" do +-- test "Can process GetDatumByHash" do +-- testOgmiosDatumCacheGetDatumByHash +-- test "Can process GetDatumsByHashes" do +-- testOgmiosDatumCacheGetDatumsByHashes +-- test "Can process GetDatumsByHashesWithErrors" do +-- testOgmiosDatumCacheGetDatumsByHashesWithErrors +-- test "Can process GetTxByHash" do +-- testOgmiosGetTxByHash +-- +-- testOgmiosDatumCacheGetDatumByHash :: QueryM Unit +-- testOgmiosDatumCacheGetDatumByHash = do +-- void $ getDatumByHash $ DataHash $ hexToByteArrayUnsafe +-- "f7c47c65216f7057569111d962a74de807de57e79f7efa86b4e454d42c875e4e" +-- +-- testOgmiosDatumCacheGetDatumsByHashes :: QueryM Unit +-- testOgmiosDatumCacheGetDatumsByHashes = do +-- void $ getDatumsByHashes $ pure $ DataHash $ hexToByteArrayUnsafe +-- "f7c47c65216f7057569111d962a74de807de57e79f7efa86b4e454d42c875e4e" +-- +-- testOgmiosDatumCacheGetDatumsByHashesWithErrors :: QueryM Unit +-- testOgmiosDatumCacheGetDatumsByHashesWithErrors = do +-- void $ getDatumsByHashesWithErrors $ pure $ DataHash $ hexToByteArrayUnsafe +-- "f7c47c65216f7057569111d962a74de807de57e79f7efa86b4e454d42c875e4e" +-- +-- testOgmiosGetTxByHash :: QueryM Unit +-- testOgmiosGetTxByHash = do +-- void $ getTxByHash $ hexToByteArrayUnsafe +-- "f7c47c65216f7057569111d962a74de807de57e79f7efa86b4e454d42c875e4e" +-- +-- testUtxosAt :: OgmiosAddress -> QueryM Unit +-- testUtxosAt testAddr = case ogmiosAddressToAddress testAddr of +-- Nothing -> throwError (error "Failed UtxosAt") +-- Just addr -> void $ utxosAt addr +-- +-- testGetChainTip :: QueryM Unit +-- testGetChainTip = do +-- void getChainTip +-- +-- testWaitUntilSlot :: QueryM Unit +-- testWaitUntilSlot = do +-- void $ getChainTip >>= case _ of +-- TipAtGenesis -> throwError $ error "Tip is at genesis" +-- Tip (ChainTip { slot }) -> do +-- waitUntilSlot $ over Slot +-- (fromMaybe (BigNum.fromInt 0) <<< BigNum.add (BigNum.fromInt 10)) +-- slot +-- +-- testGetEraSummaries :: QueryM Unit +-- testGetEraSummaries = do +-- void getEraSummaries +-- +-- testSubmitTxFailure :: QueryM Unit +-- testSubmitTxFailure = do +-- let bytes = hexToByteArrayUnsafe "00" +-- void $ submitTxOgmios bytes (wrap bytes) +-- +-- testGetCurrentEpoch :: QueryM Unit +-- testGetCurrentEpoch = do +-- void getCurrentEpoch +-- +-- testGetSystemStart :: QueryM Unit +-- testGetSystemStart = do +-- void getSystemStart diff --git a/test/BalanceTx/Collateral.purs b/test/BalanceTx/Collateral.purs index 45f2ae693b..44c3adb2a4 100644 --- a/test/BalanceTx/Collateral.purs +++ b/test/BalanceTx/Collateral.purs @@ -78,19 +78,19 @@ suite = do utxosFixture3 ) -withParams :: (CoinsPerUtxoUnit -> Int -> Contract () Unit) -> Aff Unit +withParams :: (CoinsPerUtxoUnit -> Int -> Contract Unit) -> Aff Unit withParams test = runContract testnetConfig { suppressLogs = true } (join (test <$> getCoinsPerUtxoUnit <*> getMaxCollateralInputs)) where - getMaxCollateralInputs :: Contract () Int + getMaxCollateralInputs :: Contract Int getMaxCollateralInputs = - asks $ unwrap >>> _.runtime >>> _.pparams <#> + asks $ _.ledgerConstants >>> _.pparams <#> UInt.toInt <<< _.maxCollateralInputs <<< unwrap - getCoinsPerUtxoUnit :: Contract () CoinsPerUtxoUnit + getCoinsPerUtxoUnit :: Contract CoinsPerUtxoUnit getCoinsPerUtxoUnit = - asks (unwrap >>> _.runtime >>> _.pparams) <#> unwrap >>> + asks (_.ledgerConstants >>> _.pparams) <#> unwrap >>> _.coinsPerUtxoUnit -- | Ada-only tx output sufficient to cover `minRequiredCollateral`. diff --git a/test/BalanceTx/Time.purs b/test/BalanceTx/Time.purs index f6fa7feaf7..fac0994279 100644 --- a/test/BalanceTx/Time.purs +++ b/test/BalanceTx/Time.purs @@ -14,8 +14,9 @@ import Contract.Time , Slot , always , from - , getEraSummaries , getSystemStart + , getSlotLength + , getSlotReference , maxSlot , mkFiniteInterval , never @@ -81,7 +82,7 @@ suite = do where run = runContract testnetConfig { suppressLogs = true } -mkTestFromSingleInterval :: Interval POSIXTime -> Contract () Unit +mkTestFromSingleInterval :: Interval POSIXTime -> Contract Unit mkTestFromSingleInterval interval = do let constraint = mustValidateIn interval @@ -93,7 +94,7 @@ mkTestFromSingleInterval interval = do returnedInterval <- getTimeFromUnbalanced utx returnedInterval `shouldEqual` interval -testEmptyInterval :: Contract () Unit +testEmptyInterval :: Contract Unit testEmptyInterval = do let constraint = mustValidateIn never @@ -102,7 +103,7 @@ testEmptyInterval = do Left _ -> pure unit Right utx -> fail $ "Empty interval must fail : " <> show utx -testEmptyMultipleIntervals :: Contract () Unit +testEmptyMultipleIntervals :: Contract Unit testEmptyMultipleIntervals = do let intervals = @@ -116,7 +117,7 @@ testEmptyMultipleIntervals = do Right utx -> fail $ "Empty interval must fail : " <> show utx mkTestMultipleInterval - :: Array (Interval POSIXTime) -> Interval POSIXTime -> Contract () Unit + :: Array (Interval POSIXTime) -> Interval POSIXTime -> Contract Unit mkTestMultipleInterval intervals expected = do let constraint = foldMap mustValidateIn intervals @@ -149,26 +150,28 @@ unsafeSubtractOne value = wrap <<< fromJust -------------------------------------------------------------------------------- getTimeFromUnbalanced - :: UnattachedUnbalancedTx -> Contract () (Interval POSIXTime) + :: UnattachedUnbalancedTx -> Contract (Interval POSIXTime) getTimeFromUnbalanced utx = validityToPosixTime $ unwrap body where body = (_transaction <<< _body) `view` (unwrap utx).unbalancedTx -toPosixTime :: Slot -> Contract () POSIXTime +toPosixTime :: Slot -> Contract POSIXTime toPosixTime time = do - eraSummaries <- getEraSummaries + slotReference <- getSlotReference + slotLength <- getSlotLength systemStart <- getSystemStart - eitherTime <- liftEffect $ slotToPosixTime eraSummaries systemStart time + eitherTime <- liftEffect $ slotToPosixTime slotReference slotLength systemStart time case eitherTime of Left e -> (throwError <<< error <<< show) e Right value -> pure value -toPosixTimeRange :: Interval Slot -> Contract () (Interval POSIXTime) +toPosixTimeRange :: Interval Slot -> Contract (Interval POSIXTime) toPosixTimeRange range = do - eraSummaries <- getEraSummaries + slotReference <- getSlotReference + slotLength <- getSlotLength systemStart <- getSystemStart eitherRange <- liftEffect $ - slotRangeToPosixTimeRange eraSummaries systemStart range + slotRangeToPosixTimeRange slotReference slotLength systemStart range case eitherRange of Left e -> (throwError <<< error <<< show) e Right value -> pure value @@ -176,7 +179,7 @@ toPosixTimeRange range = do validityToPosixTime :: forall (r :: Row Type) . { validityStartInterval :: Maybe Slot, ttl :: Maybe Slot | r } - -> Contract () (Interval POSIXTime) + -> Contract (Interval POSIXTime) validityToPosixTime { validityStartInterval, ttl: timeToLive } = case validityStartInterval of Just start -> diff --git a/test/Integration.purs b/test/Integration.purs index 1dd7ae6d74..29c8550131 100644 --- a/test/Integration.purs +++ b/test/Integration.purs @@ -2,12 +2,10 @@ module Test.Ctl.Integration (main, testPlan) where import Prelude +import Contract.Monad (runContract) +import Contract.Time (getSlotReference, getSystemStart, getSlotLength) import Contract.Config (testnetConfig) -import Contract.Monad (runContract, wrapContract) -import Ctl.Internal.QueryM (runQueryM) -import Ctl.Internal.QueryM.Config (testnetTraceQueryConfig) -import Ctl.Internal.QueryM.EraSummaries (getEraSummaries) -import Ctl.Internal.QueryM.SystemStart (getSystemStart) +import Ctl.Internal.Contract.Monad (wrapQueryM) import Ctl.Internal.Test.TestPlanM (TestPlanM, interpret) import Effect (Effect) import Effect.Aff (Aff, launchAff_) @@ -33,16 +31,17 @@ testPlan = do -- These tests depend on assumptions about testnet history. -- We disabled them during transition from `testnet` to `preprod` networks. -- https://github.com/Plutonomicon/cardano-transaction-lib/issues/945 - skip $ flip mapTest Types.Interval.suite \f -> runQueryM - testnetTraceQueryConfig { suppressLogs = true } + skip $ flip mapTest Types.Interval.suite \f -> runContract testnetConfig { suppressLogs = true } do - eraSummaries <- getEraSummaries - sysStart <- getSystemStart - liftEffect $ f eraSummaries sysStart + slotReference <- getSlotReference + slotLength <- getSlotLength + systemStart <- getSystemStart + liftEffect $ f { slotReference, slotLength, systemStart } Collateral.suite PrivateKey.suite Logging.suite BalanceTx.Time.suite where + -- TODO Don't use wrapQueryM runQueryM' = - runContract (testnetConfig { suppressLogs = true }) <<< wrapContract + runContract (testnetConfig { suppressLogs = true }) <<< wrapQueryM diff --git a/test/Ogmios/GenerateFixtures.purs b/test/Ogmios/GenerateFixtures.purs index db039b3dc1..aa05f52293 100644 --- a/test/Ogmios/GenerateFixtures.purs +++ b/test/Ogmios/GenerateFixtures.purs @@ -5,7 +5,6 @@ module Test.Ctl.Ogmios.GenerateFixtures import Prelude import Aeson (class DecodeAeson, class EncodeAeson, Aeson, stringifyAeson) -import Contract.Monad (ListenerSet) import Control.Parallel (parTraverse) import Ctl.Internal.Helpers (logString) import Ctl.Internal.JsWebSocket @@ -19,6 +18,7 @@ import Ctl.Internal.JsWebSocket import Ctl.Internal.QueryM ( WebSocket(WebSocket) , WebsocketDispatch + , ListenerSet , defaultMessageListener , defaultOgmiosWsConfig , mkListenerSet diff --git a/test/Plutip/Contract.purs b/test/Plutip/Contract.purs index 489bb384f5..dd7722e47e 100644 --- a/test/Plutip/Contract.purs +++ b/test/Plutip/Contract.purs @@ -4,12 +4,14 @@ module Test.Ctl.Plutip.Contract import Prelude +import Ctl.Internal.Contract.Monad (wrapQueryM) import Contract.Address ( PaymentPubKeyHash(PaymentPubKeyHash) , PubKeyHash(PubKeyHash) , StakePubKeyHash , getWalletAddresses , getWalletCollateral + , getNetworkId , ownPaymentPubKeysHashes , ownStakePubKeysHashes ) @@ -20,7 +22,7 @@ import Contract.BalanceTxConstraints import Contract.Chain (currentTime) import Contract.Hashing (datumHash, nativeScriptHash) import Contract.Log (logInfo') -import Contract.Monad (Contract, liftContractM, liftedE, liftedM, wrapContract) +import Contract.Monad (Contract, liftContractM, liftedE, liftedM) import Contract.PlutusData ( Datum(Datum) , PlutusData(Bytes, Integer, List) @@ -68,7 +70,6 @@ import Contract.Value (Coin(Coin), coinToValue) import Contract.Value as Value import Contract.Wallet (getWalletUtxos, isWalletAvailable, withKeyWallet) import Control.Monad.Error.Class (try) -import Control.Monad.Reader (asks) import Control.Parallel (parallel, sequential) import Ctl.Examples.AlwaysMints (alwaysMintsPolicy) import Ctl.Examples.AlwaysSucceeds as AlwaysSucceeds @@ -161,7 +162,7 @@ suite :: TestPlanM PlutipTest Unit suite = do group "Contract" do flip mapTest AffInterface.suite - (noWallet <<< wrapContract) + (noWallet <<< wrapQueryM) NetworkId.suite @@ -348,7 +349,7 @@ suite = do -- Bob attempts to unlock and send Ada to Charlie withKeyWallet bob do -- First, he should find the transaction input where Ada is locked - networkId <- asks $ unwrap >>> _.config >>> _.networkId + networkId <- getNetworkId let nsAddr = nativeScriptHashEnterpriseAddress networkId nsHash nsAddrPlutus <- liftContractM "Unable to convert to Plutus address" @@ -446,7 +447,7 @@ suite = do -- Bob attempts to unlock and send Ada to Charlie withKeyWallet bob do -- First, he should find the transaction input where Ada is locked - networkId <- asks $ unwrap >>> _.config >>> _.networkId + networkId <- getNetworkId let nsAddr = nativeScriptHashEnterpriseAddress networkId nsHash nsAddrPlutus <- liftContractM "Unable to convert to Plutus address" @@ -725,7 +726,7 @@ suite = do datums = [ datum2, datum1 ] let - payToTest :: ValidatorHash -> Contract () TransactionHash + payToTest :: ValidatorHash -> Contract TransactionHash payToTest vhash = do let constraints = @@ -1591,7 +1592,7 @@ suite = do getWalletBalance >>= flip shouldSatisfy (eq $ Just $ coinToValue $ Coin $ BigInt.fromInt 8_000_000) -signMultipleContract :: forall (r :: Row Type). Contract r Unit +signMultipleContract :: Contract Unit signMultipleContract = do pkh <- liftedM "Failed to get own PKH" $ head <$> ownPaymentPubKeysHashes stakePkh <- join <<< head <$> ownStakePubKeysHashes @@ -1620,10 +1621,9 @@ signMultipleContract = do liftEffect $ throw "locked inputs map is not empty" pkh2PkhContract - :: forall (r :: Row Type) - . PaymentPubKeyHash + :: PaymentPubKeyHash -> Maybe StakePubKeyHash - -> Contract r Unit + -> Contract Unit pkh2PkhContract pkh stakePkh = do let constraints :: Constraints.TxConstraints Void Void diff --git a/test/Plutip/Staking.purs b/test/Plutip/Staking.purs index a2704cbd98..8dee5929d6 100644 --- a/test/Plutip/Staking.purs +++ b/test/Plutip/Staking.purs @@ -255,7 +255,7 @@ suite = do privateStakeKey <- liftM (error "Failed to get private stake key") $ keyWalletPrivateStakeKey alice - networkId <- asks $ unwrap >>> _.config >>> _.networkId + networkId <- asks _.networkId let poolOperator = PoolPubKeyHash $ publicKeyHash $ publicKeyFromPrivateKey (unwrap privateStakeKey) @@ -335,7 +335,7 @@ suite = do liftedE (balanceTx ubTx) >>= signTransaction >>= submitAndLog let - waitEpoch :: forall (r :: Row Type). Epoch -> Contract r Epoch + waitEpoch :: Epoch -> Contract Epoch waitEpoch epoch = do epochNow <- getCurrentEpoch if unwrap epochNow >= unwrap epoch then pure epochNow diff --git a/test/Plutip/Utils.purs b/test/Plutip/Utils.purs index 35f07ab24e..a023f571d3 100644 --- a/test/Plutip/Utils.purs +++ b/test/Plutip/Utils.purs @@ -22,7 +22,7 @@ import Effect.Exception (throw) import Effect.Ref as Ref submitAndLog - :: forall (r :: Row Type). BalancedSignedTransaction -> Contract r Unit + :: BalancedSignedTransaction -> Contract Unit submitAndLog bsTx = do txId <- submit bsTx logInfo' $ "Tx ID: " <> show txId @@ -34,7 +34,7 @@ submitAndLog bsTx = do when (mbTransaction /= Just (unwrap bsTx)) do throw "Tx contents do not match" -getLockedInputs :: forall (r :: Row Type). Contract r TxOutRefCache +getLockedInputs :: Contract TxOutRefCache getLockedInputs = do - cache <- asks (_.usedTxOuts <<< _.runtime <<< unwrap) + cache <- asks _.usedTxOuts liftEffect $ Ref.read $ unwrap cache diff --git a/test/Plutip/UtxoDistribution.purs b/test/Plutip/UtxoDistribution.purs index e0c5aed974..81ffac3dc1 100644 --- a/test/Plutip/UtxoDistribution.purs +++ b/test/Plutip/UtxoDistribution.purs @@ -115,11 +115,11 @@ suite = group "UtxoDistribution" do checkUtxoDistribution randDistr checkUtxoDistribution - :: forall distr wallet (r :: Row Type) + :: forall (distr :: Type) (wallet :: Type) . UtxoDistribution distr wallet => distr -> wallet - -> Contract r Unit + -> Contract Unit checkUtxoDistribution distr wallets = do let walletsArray = keyWallets (Proxy :: Proxy distr) wallets @@ -188,7 +188,7 @@ withArbUtxoDistr d f = case d of UDTuple x y -> withArbUtxoDistr x (\d1 -> withArbUtxoDistr y (f <<< (d1 /\ _))) -assertContract :: forall (r :: Row Type). String -> Boolean -> Contract r Unit +assertContract :: String -> Boolean -> Contract Unit assertContract msg cond = if cond then pure unit else liftEffect $ throw msg -- | For a plutip test wallet, assert that any utxos held by the @@ -197,13 +197,13 @@ assertContract msg cond = if cond then pure unit else liftEffect $ throw msg -- | address, otherwise it assumes the expected address is the -- | enterprise address. assertUtxosAtPlutipWalletAddress - :: forall (r :: Row Type). KeyWallet -> Contract r Unit + :: KeyWallet -> Contract Unit assertUtxosAtPlutipWalletAddress wallet = withKeyWallet wallet do maybeStake <- join <<< head <$> ownStakePubKeysHashes when (isJust maybeStake) $ assertNoUtxosAtEnterpriseAddress wallet assertNoUtxosAtEnterpriseAddress - :: forall (r :: Row Type). KeyWallet -> Contract r Unit + :: KeyWallet -> Contract Unit assertNoUtxosAtEnterpriseAddress wallet = withKeyWallet wallet $ assertNoUtxosAtAddress =<< liftedM "Could not get wallet address" ( payPubKeyHashEnterpriseAddress @@ -212,7 +212,7 @@ assertNoUtxosAtEnterpriseAddress wallet = withKeyWallet wallet $ (head <$> ownPaymentPubKeysHashes) ) -assertNoUtxosAtAddress :: forall (r :: Row Type). Address -> Contract r Unit +assertNoUtxosAtAddress :: Address -> Contract Unit assertNoUtxosAtAddress addr = do utxos <- utxosAt addr assertContract "Expected address to not hold utxos" $ Map.isEmpty utxos @@ -220,9 +220,8 @@ assertNoUtxosAtAddress addr = do -- | For each wallet, assert that there is a one-to-one correspondance -- | between its utxo set and its expected utxo amounts. assertCorrectDistribution - :: forall (r :: Row Type) - . Array (KeyWallet /\ InitialUTxOs) - -> Contract r Unit + :: Array (KeyWallet /\ InitialUTxOs) + -> Contract Unit assertCorrectDistribution wallets = for_ wallets \(wallet /\ expectedAmounts) -> withKeyWallet wallet do addr <- liftedM "Could not get wallet address" $ head <$> getWalletAddresses diff --git a/test/Types/Interval.purs b/test/Types/Interval.purs index 61f901fc45..d89cfc4cb3 100644 --- a/test/Types/Interval.purs +++ b/test/Types/Interval.purs @@ -2,6 +2,9 @@ module Test.Ctl.Types.Interval ( suite , eraSummariesFixture , systemStartFixture + , slotLengthFixture + , slotReferenceFixture + , contextFixture ) where import Prelude @@ -9,10 +12,14 @@ import Prelude import Aeson (class DecodeAeson, decodeJsonString, printJsonDecodeError) import Control.Monad.Error.Class (liftEither) import Control.Monad.Except (throwError) -import Ctl.Internal.QueryM.Ogmios (EraSummaries, SystemStart) +import Ctl.Internal.Helpers (liftedM) +import Ctl.Internal.QueryM.Ogmios (EraSummaries, SystemStart, RelativeTime, SlotLength) import Ctl.Internal.Serialization.Address (Slot(Slot)) import Ctl.Internal.Test.TestPlanM (TestPlanM) import Ctl.Internal.Types.BigNum (fromInt) as BigNum +import Data.Function (on) +import Data.Foldable (maximumBy) +import Data.Newtype (unwrap) import Ctl.Internal.Types.Interval ( Interval , POSIXTime(POSIXTime) @@ -46,7 +53,13 @@ import Test.QuickCheck (Result(Success, Failed), quickCheck, ()) import Test.QuickCheck.Combinators ((&=&)) import Test.Spec.Assertions (shouldEqual) -suite :: TestPlanM (EraSummaries -> SystemStart -> Effect Unit) Unit +type Context = + { slotReference :: { slot :: Slot, time :: RelativeTime } + , slotLength :: SlotLength + , systemStart :: SystemStart + } + +suite :: TestPlanM (Context -> Effect Unit) Unit suite = do group "Interval" do group "EraSumaries related" do @@ -84,12 +97,31 @@ eraSummariesFixture :: Effect EraSummaries eraSummariesFixture = loadOgmiosFixture "eraSummaries" "bbf8b1d7d2487e750104ec2b5a31fa86" +slotLengthFixture :: Effect SlotLength +slotLengthFixture = do + latestEraSummary <- liftedM (error "Could not get EraSummary") do + map unwrap <<< (maximumBy (compare `on` (unwrap >>> _.start >>> unwrap >>> _.slot))) <<< unwrap <$> eraSummariesFixture + pure $ _.slotLength $ unwrap $ _.parameters $ latestEraSummary + +slotReferenceFixture :: Effect { slot :: Slot, time :: RelativeTime } +slotReferenceFixture = do + latestEraSummary <- liftedM (error "Could not get EraSummary") do + map unwrap <<< (maximumBy (compare `on` (unwrap >>> _.start >>> unwrap >>> _.slot))) <<< unwrap <$> eraSummariesFixture + pure $ (\{slot, time} -> {slot, time}) $ unwrap $ _.start $ latestEraSummary + systemStartFixture :: Effect SystemStart systemStartFixture = loadOgmiosFixture "systemStart" "ed0caad81f6936e0c122ef6f3c7de5e8" -testPosixTimeToSlot :: EraSummaries -> SystemStart -> Effect Unit -testPosixTimeToSlot eraSummaries sysStart = do +contextFixture :: Effect Context +contextFixture = do + slotReference <- slotReferenceFixture + slotLength <- slotLengthFixture + systemStart <- systemStartFixture + pure { slotReference, slotLength, systemStart } + +testPosixTimeToSlot :: Context -> Effect Unit +testPosixTimeToSlot ctx = do let -- Tests currently pass "exactly" for seconds precision, which makes sense -- given converting to a Slot will round down to the near slot length @@ -139,35 +171,33 @@ testPosixTimeToSlot eraSummaries sysStart = do [ "1603636353000" , "1613636755000" ] - traverse_ (idTest eraSummaries sysStart identity) posixTimes + traverse_ (idTest identity) posixTimes -- With Milliseconds, we generally round down, provided the aren't at the -- end with non-zero excess: - idTest eraSummaries sysStart + idTest (const $ mkPosixTime "1613636754000") (mkPosixTime "1613636754999") - idTest eraSummaries sysStart + idTest (const $ mkPosixTime "1613636754000") (mkPosixTime "1613636754500") - idTest eraSummaries sysStart + idTest (const $ mkPosixTime "1613636754000") (mkPosixTime "1613636754499") where idTest - :: EraSummaries - -> SystemStart - -> (POSIXTime -> POSIXTime) + :: (POSIXTime -> POSIXTime) -> POSIXTime -> Effect Unit - idTest es ss transf posixTime = do - posixTimeToSlot es ss posixTime >>= case _ of + idTest transf posixTime = do + posixTimeToSlot ctx.slotReference ctx.slotLength ctx.systemStart posixTime >>= case _ of Left err -> throwError $ error $ show err Right slot -> do - ePosixTime <- slotToPosixTime es ss slot + ePosixTime <- slotToPosixTime ctx.slotReference ctx.slotLength ctx.systemStart slot either (throwError <<< error <<< show) (shouldEqual $ transf posixTime) ePosixTime -testSlotToPosixTime :: EraSummaries -> SystemStart -> Effect Unit -testSlotToPosixTime eraSummaries sysStart = do +testSlotToPosixTime :: Context -> Effect Unit +testSlotToPosixTime ctx = do -- See *Testing far into the future note during hardforks:* for details on -- how far into the future we test with slots when a hardfork occurs. let @@ -181,36 +211,34 @@ testSlotToPosixTime eraSummaries sysStart = do , 232 , 1 ] - traverse_ (idTest eraSummaries sysStart) slots + traverse_ idTest slots where - idTest :: EraSummaries -> SystemStart -> Slot -> Effect Unit - idTest es ss slot = do - slotToPosixTime es ss slot >>= case _ of + idTest :: Slot -> Effect Unit + idTest slot = do + slotToPosixTime ctx.slotReference ctx.slotLength ctx.systemStart slot >>= case _ of Left err -> throwError $ error $ show err Right posixTime -> do - eSlot <- posixTimeToSlot es ss posixTime + eSlot <- posixTimeToSlot ctx.slotReference ctx.slotLength ctx.systemStart posixTime either (throwError <<< error <<< show) (shouldEqual slot) eSlot mkSlot :: Int -> Slot mkSlot = Slot <<< BigNum.fromInt -testPosixTimeToSlotError :: EraSummaries -> SystemStart -> Effect Unit -testPosixTimeToSlotError eraSummaries sysStart = do +testPosixTimeToSlotError :: Context -> Effect Unit +testPosixTimeToSlotError ctx = do let posixTime = mkPosixTime "1000" -- Some difficulty reproducing all the errors - errTest eraSummaries sysStart + errTest posixTime (PosixTimeBeforeSystemStart posixTime) where errTest - :: EraSummaries - -> SystemStart - -> POSIXTime + :: POSIXTime -> PosixTimeToSlotError -> Effect Unit - errTest es ss posixTime expectedErr = do - posixTimeToSlot es ss posixTime >>= case _ of + errTest posixTime expectedErr = do + posixTimeToSlot ctx.slotReference ctx.slotLength ctx.systemStart posixTime >>= case _ of Left err -> err `shouldEqual` expectedErr Right _ -> throwError $ error $ "Test should have failed giving: " <> show @@ -387,8 +415,8 @@ testIntersection = quickCheck test -- Helpers -------------------------------------------------------------------------------- -liftToTest :: Effect Unit -> (EraSummaries -> SystemStart -> Effect Unit) -liftToTest = pure <<< pure +liftToTest :: Effect Unit -> (Context -> Effect Unit) +liftToTest = pure withMsg :: String -> Result -> Result withMsg _ Success = Success diff --git a/test/Unit.purs b/test/Unit.purs index c714aa9e45..285a35cbd0 100644 --- a/test/Unit.purs +++ b/test/Unit.purs @@ -75,7 +75,6 @@ testPlan = do Types.Transaction.suite Ctl.Data.Interval.suite flip mapTest Types.Interval.suite \f -> liftEffect $ join $ - f <$> Types.Interval.eraSummariesFixture - <*> Types.Interval.systemStartFixture + f <$> Types.Interval.contextFixture E2E.Route.suite MustSpendTotal.suite From b1b6db64a5ef2a144af4cfb8b40daf9e517b6c37 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Tue, 29 Nov 2022 14:49:50 +0000 Subject: [PATCH 026/373] WIP: Strip out more QueryM. Move QueryM's wallet code into Internal.Wallet. KeyWallet now holds a networkId. Added wallet networkId check to Contract env creation --- src/Contract/Wallet.purs | 16 +- src/Contract/Wallet/KeyFile.purs | 13 +- src/Internal/Contract/Monad.purs | 31 +- src/Internal/Contract/Sign.purs | 4 +- src/Internal/Contract/Wallet.purs | 59 ++-- src/Internal/Plutip/UtxoDistribution.purs | 9 +- src/Internal/QueryM.purs | 336 +--------------------- src/Internal/QueryM/Blockfrost.purs | 17 -- src/Internal/QueryM/MinFee.purs | 117 -------- src/Internal/QueryM/Sign.purs | 97 ------- src/Internal/QueryM/SystemStart.purs | 15 - src/Internal/QueryM/Utxos.purs | 172 ----------- src/Internal/Test/E2E/Route.purs | 2 +- src/Internal/Wallet.purs | 128 ++++++++- src/Internal/Wallet/Cip30Mock.purs | 26 +- src/Internal/Wallet/Key.purs | 44 +-- test/AffInterface.purs | 10 +- test/Wallet/Cip30/SignData.purs | 5 +- 18 files changed, 245 insertions(+), 856 deletions(-) delete mode 100644 src/Internal/QueryM/Blockfrost.purs delete mode 100644 src/Internal/QueryM/MinFee.purs delete mode 100644 src/Internal/QueryM/Sign.purs delete mode 100644 src/Internal/QueryM/SystemStart.purs delete mode 100644 src/Internal/QueryM/Utxos.purs diff --git a/src/Contract/Wallet.purs b/src/Contract/Wallet.purs index e7157dc3e7..aa0d23f51b 100644 --- a/src/Contract/Wallet.purs +++ b/src/Contract/Wallet.purs @@ -20,7 +20,7 @@ module Contract.Wallet import Prelude import Contract.Address (getWalletAddress, getWalletCollateral) -import Contract.Monad (Contract, ContractEnv) +import Contract.Monad (Contract) import Contract.Utxos (getWalletUtxos) as Contract.Utxos import Control.Monad.Reader (local) import Control.Monad.Reader.Class (asks) @@ -49,12 +49,13 @@ import Ctl.Internal.Wallet , name , walletToWalletExtension ) as Wallet -import Ctl.Internal.Wallet (Wallet(KeyWallet), mkKeyWallet) +import Ctl.Internal.Wallet (Wallet(KeyWallet)) import Ctl.Internal.Wallet.Cip30 (DataSignature) import Ctl.Internal.Wallet.Key (KeyWallet, privateKeysToKeyWallet) as Wallet import Ctl.Internal.Wallet.Key ( PrivatePaymentKey(PrivatePaymentKey) , PrivateStakeKey(PrivateStakeKey) + , privateKeysToKeyWallet ) import Ctl.Internal.Wallet.KeyFile (formatPaymentKey, formatStakeKey) import Ctl.Internal.Wallet.Spec @@ -69,12 +70,7 @@ import Ctl.Internal.Wallet.Spec , ConnectToEternl ) ) -import Data.Lens (Lens, (.~)) -import Data.Lens.Common (simple) -import Data.Lens.Iso.Newtype (_Newtype) -import Data.Lens.Record (prop) import Data.Maybe (Maybe(Just)) -import Type.Proxy (Proxy(Proxy)) getNetworkId :: Contract NetworkId getNetworkId = asks _.networkId @@ -106,5 +102,7 @@ withKeyWallet wallet action = do local _ { wallet = Just $ KeyWallet wallet } action mkKeyWalletFromPrivateKeys - :: PrivatePaymentKey -> Maybe PrivateStakeKey -> Wallet -mkKeyWalletFromPrivateKeys = mkKeyWallet + :: PrivatePaymentKey -> Maybe PrivateStakeKey -> Contract Wallet.KeyWallet +mkKeyWalletFromPrivateKeys payment mbStake = do + networkId <- getNetworkId + pure $ privateKeysToKeyWallet networkId payment mbStake diff --git a/src/Contract/Wallet/KeyFile.purs b/src/Contract/Wallet/KeyFile.purs index 439e866398..9920409e5a 100644 --- a/src/Contract/Wallet/KeyFile.purs +++ b/src/Contract/Wallet/KeyFile.purs @@ -6,8 +6,11 @@ module Contract.Wallet.KeyFile import Prelude -import Ctl.Internal.Wallet (Wallet) as Wallet -import Ctl.Internal.Wallet (mkKeyWallet) +import Control.Monad.Reader.Class (asks) +import Effect.Aff.Class (liftAff) +import Ctl.Internal.Contract.Monad (Contract) +import Ctl.Internal.Wallet.Key (KeyWallet) as Wallet +import Ctl.Internal.Wallet.Key (privateKeysToKeyWallet) import Ctl.Internal.Wallet.KeyFile ( privatePaymentKeyFromFile , privatePaymentKeyFromTextEnvelope @@ -18,7 +21,6 @@ import Ctl.Internal.Wallet.KeyFile ) import Data.Maybe (Maybe) import Data.Traversable (traverse) -import Effect.Aff (Aff) import Node.Path (FilePath) -- | Load `PrivateKey`s from `skey` files (the files should be in JSON format as @@ -29,8 +31,9 @@ import Node.Path (FilePath) -- | -- | **NodeJS only** mkKeyWalletFromFiles - :: FilePath -> Maybe FilePath -> Aff Wallet.Wallet + :: FilePath -> Maybe FilePath -> Contract Wallet.KeyWallet mkKeyWalletFromFiles paymentKeyFile mbStakeKeyFile = do - mkKeyWallet + networkId <- asks _.networkId + liftAff $ privateKeysToKeyWallet networkId <$> privatePaymentKeyFromFile paymentKeyFile <*> traverse privateStakeKeyFromFile mbStakeKeyFile diff --git a/src/Internal/Contract/Monad.purs b/src/Internal/Contract/Monad.purs index a17fb01bf2..8dc5e8e576 100644 --- a/src/Internal/Contract/Monad.purs +++ b/src/Internal/Contract/Monad.purs @@ -18,12 +18,12 @@ import Prelude import Data.Function (on) import Data.Foldable (maximumBy) -import Ctl.Internal.Serialization.Address (Slot) +import Ctl.Internal.Serialization.Address (NetworkId, Slot) import Effect.Aff (Aff, ParAff, attempt, error, finally, supervise) import Ctl.Internal.JsWebSocket (_wsClose, _wsFinalize) import Ctl.Internal.QueryM (Hooks, Logger, QueryEnv, QueryM, WebSocket, getProtocolParametersAff, getSystemStartAff, getEraSummariesAff, mkDatumCacheWebSocketAff, mkLogger, mkOgmiosWebSocketAff, mkWalletBySpec, underlyingWebSocket) import Record.Builder (build, merge) -import Control.Parallel (parTraverse, parallel, sequential) +import Control.Parallel (class Parallel, parTraverse, parallel, sequential) import Control.Monad.Error.Class ( class MonadError , class MonadThrow @@ -46,9 +46,9 @@ import Ctl.Internal.Helpers (liftM, liftedM, logWithLevel) import Ctl.Internal.QueryM.Logging (setupLogs) import Ctl.Internal.QueryM.Ogmios (ProtocolParameters, SlotLength, SystemStart, RelativeTime) as Ogmios import Ctl.Internal.QueryM.ServerConfig (ServerConfig) -import Ctl.Internal.Serialization.Address (NetworkId) import Ctl.Internal.Types.UsedTxOuts (UsedTxOuts, newUsedTxOuts) import Ctl.Internal.Wallet (Wallet) +import Ctl.Internal.Wallet (getNetworkId) as Wallet import Ctl.Internal.Wallet.Spec (WalletSpec) import Data.Either (Either(Left, Right)) import Data.Log.Level (LogLevel) @@ -59,11 +59,10 @@ import Data.Traversable (for_, traverse) import Effect (Effect) import Effect.Aff.Class (liftAff) import Effect.Class (class MonadEffect, liftEffect) -import Effect.Exception (Error, try) +import Effect.Exception (Error, try, throw) import Effect.Ref (new) as Ref import MedeaPrelude (class MonadAff) import Undefined (undefined) -import Control.Parallel (class Parallel, parallel, sequential) import Control.Alt (class Alt) import Control.Alternative (class Alternative) import Control.Plus (class Plus) @@ -199,7 +198,7 @@ mkContractEnv params = do logger = mkLogger params.logLevel params.customLogger buildWallet :: Aff (Maybe Wallet) - buildWallet = traverse mkWalletBySpec params.walletSpec + buildWallet = traverse (mkWalletBySpec params.networkId) params.walletSpec constants = { ctlServerConfig: params.ctlServerConfig @@ -216,6 +215,8 @@ buildBackend :: Logger -> QueryBackends QueryBackendParams -> Aff (QueryBackends buildBackend logger = parTraverse case _ of CtlBackendParams { ogmiosConfig, kupoConfig, odcConfig } -> do datumCacheWsRef <- liftEffect $ Ref.new Nothing + -- TODO Check the network in env matches up with the network of odc, ogmios and kupo + -- Need to pass in the networkid sequential ado odcWs <- parallel $ mkDatumCacheWebSocketAff datumCacheWsRef logger odcConfig ogmiosWs <- parallel $ mkOgmiosWebSocketAff datumCacheWsRef logger ogmiosConfig @@ -238,7 +239,7 @@ getLedgerConstants :: Logger -> QueryBackend -> Aff , slotLength :: Ogmios.SlotLength , slotReference :: { slot :: Slot, time :: Ogmios.RelativeTime } } -getLedgerConstants logger backend = case backend of +getLedgerConstants logger = case _ of CtlBackend { ogmios: { ws } } -> do pparams <- getProtocolParametersAff ws logger systemStart <- getSystemStartAff ws logger @@ -252,6 +253,20 @@ getLedgerConstants logger backend = case backend of pure { pparams, slotLength, systemStart, slotReference } BlockfrostBackend _ -> undefined +-- | Ensure that `NetworkId` from wallet is the same as specified in the +-- | `ContractEnv`. +walletNetworkCheck :: NetworkId -> Wallet -> Aff Unit +walletNetworkCheck envNetworkId wallet = do + networkId <- Wallet.getNetworkId wallet + unless (envNetworkId == networkId) do + liftEffect $ throw $ + "The networkId that is specified is not equal to the one from wallet." + <> " The wallet is using " + <> show networkId + <> " while " + <> show envNetworkId + <> " is specified in the config." + -- | Finalizes a `Contract` environment. -- | Closes the websockets in `ContractEnv`, effectively making it unusable. -- TODO Move to Aff? @@ -286,8 +301,8 @@ withContractEnv params action = do | otherwise = params.customLogger contractEnv <- mkContractEnv params <#> _ { customLogger = customLogger } + for_ contractEnv.wallet $ walletNetworkCheck contractEnv.networkId eiRes <- - -- TODO: Adapt `networkIdCheck` from QueryM module attempt $ supervise (action contractEnv) `flip finally` liftEffect (stopContractEnv contractEnv) liftEffect $ case eiRes of diff --git a/src/Internal/Contract/Sign.purs b/src/Internal/Contract/Sign.purs index f3cc95d6d2..9bd82fd86d 100644 --- a/src/Internal/Contract/Sign.purs +++ b/src/Internal/Contract/Sign.purs @@ -14,7 +14,7 @@ import Ctl.Internal.Contract.Wallet ( callCip30Wallet , getWalletAddresses , getWalletUtxos - , withMWallet + , withWallet ) import Ctl.Internal.Types.Transaction (TransactionInput) import Ctl.Internal.Wallet (Wallet(KeyWallet, Lode, Eternl, Flint, Gero, Nami)) @@ -40,7 +40,7 @@ signTransaction tx = do runHook = for_ hooks.beforeSign (void <<< liftEffect <<< try) runHook - withMWallet case _ of + withWallet case _ of Nami nami -> liftAff $ callCip30Wallet nami \nw -> flip nw.signTx tx Gero gero -> liftAff $ callCip30Wallet gero \nw -> flip nw.signTx tx Flint flint -> liftAff $ callCip30Wallet flint \nw -> flip nw.signTx tx diff --git a/src/Internal/Contract/Wallet.purs b/src/Internal/Contract/Wallet.purs index bd1c582a48..9dbe51e7d4 100644 --- a/src/Internal/Contract/Wallet.purs +++ b/src/Internal/Contract/Wallet.purs @@ -30,7 +30,7 @@ import Effect.Aff.Class (liftAff) import Effect.Class (liftEffect) import Effect.Exception (throw) import Ctl.Internal.Contract.QueryHandle (getQueryHandle) -import Ctl.Internal.Helpers (liftM) +import Ctl.Internal.Helpers (liftM, liftedM) import Ctl.Internal.Serialization.Address ( Address , NetworkId @@ -51,53 +51,26 @@ import Ctl.Internal.Wallet , KeyWallet , Wallet(KeyWallet, Lode, Flint, Gero, Nami, Eternl) ) +import Ctl.Internal.Wallet (getChangeAddress, getRewardAddresses, getUnusedAddresses, getWalletAddresses, signData) as Aff import Ctl.Internal.Wallet.Cip30 (DataSignature) import Data.Array (catMaybes) import Effect.Exception (error, throw) import Data.Traversable (for_, traverse) getUnusedAddresses :: Contract (Array Address) -getUnusedAddresses = fold <$> do - actionBasedOnWallet _.getUnusedAddresses - (\_ -> pure []) +getUnusedAddresses = withWalletAff Aff.getUnusedAddresses getChangeAddress :: Contract (Maybe Address) -getChangeAddress = do - networkId <- getNetworkId - actionBasedOnWallet _.getChangeAddress (\kw -> (unwrap kw).address networkId) +getChangeAddress = withWalletAff Aff.getChangeAddress getRewardAddresses :: Contract (Array Address) -getRewardAddresses = fold <$> do - networkId <- getNetworkId - actionBasedOnWallet _.getRewardAddresses - (\kw -> Array.singleton <$> (unwrap kw).address networkId) +getRewardAddresses = withWalletAff Aff.getRewardAddresses getWalletAddresses :: Contract (Array Address) -getWalletAddresses = fold <$> do - networkId <- getNetworkId - actionBasedOnWallet _.getWalletAddresses - (\kw -> Array.singleton <$> (unwrap kw).address networkId) - -actionBasedOnWallet - :: forall (a :: Type) - . (Cip30Wallet -> Cip30Connection -> Aff (Maybe a)) - -> (KeyWallet -> Aff a) - -> Contract (Maybe a) -actionBasedOnWallet walletAction keyWalletAction = - withMWalletAff case _ of - Eternl wallet -> callCip30Wallet wallet walletAction - Nami wallet -> callCip30Wallet wallet walletAction - Gero wallet -> callCip30Wallet wallet walletAction - Flint wallet -> callCip30Wallet wallet walletAction - Lode wallet -> callCip30Wallet wallet walletAction - KeyWallet kw -> pure <$> keyWalletAction kw +getWalletAddresses = withWalletAff Aff.getWalletAddresses signData :: Address -> RawBytes -> Contract (Maybe DataSignature) -signData address payload = do - networkId <- getNetworkId - actionBasedOnWallet - (\wallet conn -> wallet.signData conn address payload) - (\kw -> (unwrap kw).signData networkId payload) +signData address payload = withWalletAff (Aff.signData address payload) getWallet :: Contract (Maybe Wallet) getWallet = asks (_.wallet) @@ -131,14 +104,15 @@ ownStakePubKeysHashes = do wrap <<< wrap <$> stakeCredentialToKeyHash (baseAddressDelegationCred baseAddress) -withMWalletAff - :: forall (a :: Type). (Wallet -> Aff (Maybe a)) -> Contract (Maybe a) -withMWalletAff act = withMWallet (liftAff <<< act) +withWalletAff + :: forall (a :: Type). (Wallet -> Aff a) -> Contract a +withWalletAff act = withWallet (liftAff <<< act) -withMWallet - :: forall (a :: Type). (Wallet -> Contract (Maybe a)) -> Contract (Maybe a) -withMWallet act = asks _.wallet >>= maybe (pure Nothing) - act +withWallet + :: forall (a :: Type). (Wallet -> Contract a) -> Contract a +withWallet act = do + wallet <- liftedM (error "No wallet set") $ asks _.wallet + act wallet callCip30Wallet :: forall (a :: Type) @@ -171,8 +145,7 @@ getWalletCollateral = do Lode wallet -> liftAff $ callCip30Wallet wallet _.getCollateral Eternl wallet -> liftAff $ callCip30Wallet wallet _.getCollateral KeyWallet kw -> do - networkId <- getNetworkId - addr <- liftAff $ (unwrap kw).address networkId + let addr = (unwrap kw).address utxos <- (liftAff $ queryHandle.utxosAt addr) <#> hush >>> fromMaybe Map.empty >>= filterLockedUtxos pparams <- asks $ _.ledgerConstants >>> _.pparams <#> unwrap diff --git a/src/Internal/Plutip/UtxoDistribution.purs b/src/Internal/Plutip/UtxoDistribution.purs index a3ba803eda..2786c25138 100644 --- a/src/Internal/Plutip/UtxoDistribution.purs +++ b/src/Internal/Plutip/UtxoDistribution.purs @@ -10,6 +10,8 @@ module Ctl.Internal.Plutip.UtxoDistribution import Prelude +import Ctl.Internal.Serialization.Address (NetworkId(MainnetId)) +import Contract.Wallet (mkKeyWalletFromPrivateKeys, withKeyWallet) import Contract.Address ( PaymentPubKeyHash , StakePubKeyHash @@ -31,7 +33,6 @@ import Contract.Transaction ) import Contract.TxConstraints as Constraints import Contract.Utxos (utxosAt) -import Contract.Wallet (withKeyWallet) import Control.Alternative (guard) import Control.Monad.Reader (asks) import Control.Monad.State.Trans (StateT(StateT), runStateT) @@ -85,7 +86,7 @@ instance UtxoDistribution InitialUTxOs KeyWallet where decodeWallets d p = decodeWalletsDefault d p decodeWallets' _ pks = Array.uncons pks <#> \{ head: PrivateKeyResponse key, tail } -> - (privateKeysToKeyWallet (PrivatePaymentKey key) Nothing) /\ tail + (privateKeysToKeyWallet MainnetId (PrivatePaymentKey key) Nothing) /\ tail keyWallets _ wallet = [ wallet ] instance UtxoDistribution InitialUTxOsWithStakeKey KeyWallet where @@ -93,7 +94,7 @@ instance UtxoDistribution InitialUTxOsWithStakeKey KeyWallet where decodeWallets d p = decodeWalletsDefault d p decodeWallets' (InitialUTxOsWithStakeKey stake _) pks = Array.uncons pks <#> \{ head: PrivateKeyResponse key, tail } -> - privateKeysToKeyWallet (PrivatePaymentKey key) (Just stake) /\ + privateKeysToKeyWallet MainnetId (PrivatePaymentKey key) (Just stake) /\ tail keyWallets _ wallet = [ wallet ] @@ -179,7 +180,7 @@ transferFundsFromEnterpriseToBase ourKey wallets = do -- Get all utxos and key hashes at all wallets containing a stake key walletsInfo <- foldM addStakeKeyWalletInfo mempty wallets unless (null walletsInfo) do - let ourWallet = privateKeysToKeyWallet ourKey Nothing + ourWallet <- mkKeyWalletFromPrivateKeys ourKey Nothing ourAddr <- liftedM "Could not get our address" $ head <$> withKeyWallet ourWallet getWalletAddresses ourUtxos <- utxosAt ourAddr diff --git a/src/Internal/QueryM.purs b/src/Internal/QueryM.purs index c59732782b..53ea3f5933 100644 --- a/src/Internal/QueryM.purs +++ b/src/Internal/QueryM.purs @@ -27,24 +27,13 @@ module Ctl.Internal.QueryM , WebSocket(WebSocket) , Hooks , allowError - , applyArgs , evaluateTxOgmios , getChainTip - , getDatumByHash - , getDatumsByHashes - , getDatumsByHashesWithErrors , getLogger - , getUnusedAddresses - , getChangeAddress - , getRewardAddresses - , getProtocolParameters , getProtocolParametersAff , getSystemStartAff , getEraSummariesAff - , getWalletAddresses - , getWallet , handleAffjaxResponse - , liftQueryM , listeners , postAeson , mkDatumCacheWebSocketAff @@ -58,22 +47,11 @@ module Ctl.Internal.QueryM , mkQueryRuntime , mkRequest , mkRequestAff + -- TODO Move mkWalletBySpec into Contract once import cycles are resolved , mkWalletBySpec - , ownPaymentPubKeyHashes - , ownStakePubKeysHashes - , runQueryM - , runQueryMWithSettings - , runQueryMInRuntime , scriptToAeson - , signData - , stopQueryRuntime , submitTxOgmios , underlyingWebSocket - , withMWalletAff - , withMWallet - , withQueryRuntime - , callCip30Wallet - , getNetworkId , emptyHooks ) where @@ -107,14 +85,12 @@ import Control.Monad.Reader.Class (class MonadAsk, class MonadReader) import Control.Monad.Reader.Trans ( ReaderT(ReaderT) , asks - , runReaderT - , withReaderT ) import Control.Monad.Rec.Class (class MonadRec) import Control.Parallel (class Parallel, parallel, sequential) import Control.Plus (class Plus) import Ctl.Internal.Cardano.Types.Transaction (PoolPubKeyHash) -import Ctl.Internal.Helpers (liftM, logString, logWithLevel, (<>)) +import Ctl.Internal.Helpers (logString, logWithLevel) import Ctl.Internal.JsWebSocket ( JsWebSocket , Url @@ -182,40 +158,20 @@ import Ctl.Internal.QueryM.ServerConfig ) as ExportServerConfig import Ctl.Internal.QueryM.ServerConfig ( ServerConfig - , mkHttpUrl , mkOgmiosDatumCacheWsUrl , mkWsUrl ) import Ctl.Internal.QueryM.UniqueId (ListenerId) -import Ctl.Internal.Serialization (toBytes) as Serialization -import Ctl.Internal.Serialization.Address - ( Address - , NetworkId(TestnetId, MainnetId) - , addressPaymentCred - , baseAddressDelegationCred - , baseAddressFromAddress - , stakeCredentialToKeyHash - ) -import Ctl.Internal.Serialization.PlutusData (convertPlutusData) as Serialization +import Ctl.Internal.Serialization.Address (NetworkId) import Ctl.Internal.Types.ByteArray (byteArrayToHex) import Ctl.Internal.Types.CborBytes (CborBytes) import Ctl.Internal.Types.Chain as Chain -import Ctl.Internal.Types.Datum (DataHash, Datum) -import Ctl.Internal.Types.PlutusData (PlutusData) -import Ctl.Internal.Types.PubKeyHash - ( PaymentPubKeyHash - , PubKeyHash - , StakePubKeyHash - ) -import Ctl.Internal.Types.RawBytes (RawBytes) -import Ctl.Internal.Types.Scripts (Language, PlutusScript(PlutusScript)) +import Ctl.Internal.Types.Datum (DataHash) +import Ctl.Internal.Types.Scripts (PlutusScript) import Ctl.Internal.Types.Transaction (TransactionInput) import Ctl.Internal.Types.UsedTxOuts (UsedTxOuts, newUsedTxOuts) import Ctl.Internal.Wallet - ( Cip30Connection - , Cip30Wallet - , KeyWallet - , Wallet(KeyWallet, Lode, Flint, Gero, Nami, Eternl) + ( Wallet , WalletExtension ( LodeWallet , EternlWallet @@ -226,7 +182,6 @@ import Ctl.Internal.Wallet , mkKeyWallet , mkWalletAff ) -import Ctl.Internal.Wallet.Cip30 (DataSignature) import Ctl.Internal.Wallet.Key (PrivatePaymentKey, PrivateStakeKey) import Ctl.Internal.Wallet.KeyFile ( privatePaymentKeyFromFile @@ -244,43 +199,35 @@ import Ctl.Internal.Wallet.Spec , ConnectToLode ) ) -import Data.Array (catMaybes) -import Data.Array (singleton) as Array import Data.Bifunctor (lmap) -import Data.Either (Either(Left, Right), either, hush, isRight) -import Data.Foldable (fold, foldl) +import Data.Either (Either(Left, Right), either, isRight) +import Data.Foldable (foldl) import Data.HTTP.Method (Method(POST)) import Data.JSDate (now) import Data.Log.Level (LogLevel(Error, Debug)) import Data.Log.Message (Message) -import Data.Map (Map) import Data.Map as Map import Data.Maybe (Maybe(Just, Nothing), fromMaybe, isJust, maybe) import Data.MediaType.Common (applicationJSON) import Data.Newtype (class Newtype, unwrap, wrap) -import Data.Traversable (for, for_, traverse, traverse_) -import Data.Tuple (Tuple(Tuple), fst, snd) +import Data.Traversable (for, for_, traverse_) +import Data.Tuple (fst) import Data.Tuple.Nested (type (/\), (/\)) import Effect (Effect) import Effect.Aff ( Aff , Canceler(Canceler) , ParAff - , attempt , delay - , finally , launchAff_ , makeAff , runAff_ - , supervise ) import Effect.Aff.Class (class MonadAff, liftAff) import Effect.Class (class MonadEffect, liftEffect) import Effect.Exception (Error, error, throw, try) import Effect.Ref (Ref) import Effect.Ref as Ref -import Foreign.Object as Object -import Untagged.Union (asOneOf) -- This module defines an Aff interface for Ogmios Websocket Queries -- Since WebSockets do not define a mechanism for linking request/response @@ -415,78 +362,6 @@ instance Parallel (QueryMExtended r ParAff) (QueryMExtended r Aff) where sequential :: QueryMExtended r ParAff ~> QueryMExtended r Aff sequential = wrap <<< sequential <<< unwrap -liftQueryM - :: forall (r :: Row Type) (a :: Type). QueryM a -> QueryMExtended r Aff a -liftQueryM = unwrap >>> withReaderT toDefaultQueryEnv >>> wrap - where - toDefaultQueryEnv :: QueryEnv r -> DefaultQueryEnv - toDefaultQueryEnv c = c { extraConfig = {} } - --- | Constructs and finalizes a contract environment that is usable inside a --- | bracket callback. --- | Make sure that `Aff` action does not end before all contracts that use the --- | runtime terminate. Otherwise `WebSocket`s will be closed too early. -withQueryRuntime - :: forall a - . QueryConfig - -> (QueryRuntime -> Aff a) - -> Aff a -withQueryRuntime config action = do - eiRes <- attempt do - runtime <- mkQueryRuntime config - supervise (networkIdCheck config runtime *> action runtime) - `flip finally` liftEffect do - stopQueryRuntime runtime - case eiRes of - Right res -> do - liftEffect $ for_ config.hooks.onSuccess (void <<< try) - pure res - Left err -> do - for_ config.hooks.onError \f -> do - void $ liftEffect $ try $ f err - liftEffect $ throwError err - --- | Ensure that `NetworkId` from wallet is the same as specified in the --- | `QueryConfig`. -networkIdCheck :: QueryConfig -> QueryRuntime -> Aff Unit -networkIdCheck config runtime = do - mbNetworkId <- runQueryMInRuntime config runtime getWalletNetworkId - for_ mbNetworkId \networkId -> - unless (networkToInt config.networkId == networkId) do - liftEffect $ throw $ - "The networkId that is specified is not equal to the one from wallet." - <> " The wallet is using " - <> printNetworkIdName networkId - <> " while " - <> printNetworkIdName (networkToInt config.networkId) - <> " is specified in the config." - where - networkToInt :: NetworkId -> Int - networkToInt = case _ of - TestnetId -> 0 - MainnetId -> 1 - - printNetworkIdName :: Int -> String - printNetworkIdName = case _ of - 0 -> "Testnet" - _ -> "Mainnet" - - getWalletNetworkId :: QueryM (Maybe Int) - getWalletNetworkId = do - join <$> actionBasedOnWallet - (\w -> map (Just <<< Just) <<< _.getNetworkId w) - (\_ -> pure Nothing) - --- | Close the websockets in `QueryRuntime`, effectively making it unusable -stopQueryRuntime - :: QueryRuntime - -> Effect Unit -stopQueryRuntime runtime = do - _wsFinalize $ underlyingWebSocket runtime.ogmiosWs - _wsClose $ underlyingWebSocket runtime.ogmiosWs - _wsFinalize $ underlyingWebSocket runtime.datumCacheWs - _wsClose $ underlyingWebSocket runtime.datumCacheWs - -- | Used in `mkQueryRuntime` only data QueryRuntimeModel = QueryRuntimeModel DatumCacheWebSocket @@ -511,7 +386,7 @@ mkQueryRuntime config = do mkOgmiosWebSocketAff datumCacheWsRef logger config.ogmiosConfig pparams <- getProtocolParametersAff ogmiosWs logger pure $ ogmiosWs /\ pparams - <*> parallel (for config.walletSpec mkWalletBySpec) + <*> parallel (for config.walletSpec $ mkWalletBySpec config.networkId) pure { ogmiosWs , datumCacheWs @@ -522,8 +397,8 @@ mkQueryRuntime config = do where logger = mkLogger config.logLevel config.customLogger -mkWalletBySpec :: WalletSpec -> Aff Wallet -mkWalletBySpec = case _ of +mkWalletBySpec :: NetworkId -> WalletSpec -> Aff Wallet +mkWalletBySpec networkId = case _ of UseKeys paymentKeySpec mbStakeKeySpec -> do privatePaymentKey <- case paymentKeySpec of PrivatePaymentKeyFile filePath -> @@ -532,41 +407,13 @@ mkWalletBySpec = case _ of mbPrivateStakeKey <- for mbStakeKeySpec case _ of PrivateStakeKeyFile filePath -> privateStakeKeyFromFile filePath PrivateStakeKeyValue key -> pure key - pure $ mkKeyWallet privatePaymentKey mbPrivateStakeKey + pure $ mkKeyWallet networkId privatePaymentKey mbPrivateStakeKey ConnectToNami -> mkWalletAff NamiWallet ConnectToGero -> mkWalletAff GeroWallet ConnectToFlint -> mkWalletAff FlintWallet ConnectToEternl -> mkWalletAff EternlWallet ConnectToLode -> mkWalletAff LodeWallet -runQueryM :: forall (a :: Type). QueryConfig -> QueryM a -> Aff a -runQueryM config action = do - withQueryRuntime config \runtime -> - runQueryMInRuntime config runtime action - -runQueryMWithSettings - :: forall (r :: Row Type) (a :: Type) - . QueryEnv r - -> QueryM a - -> Aff a -runQueryMWithSettings settings action = do - runQueryMInRuntime settings.config settings.runtime action - -runQueryMInRuntime - :: forall (r :: Row Type) (a :: Type) - . QueryConfig - -> QueryRuntime - -> QueryM a - -> Aff a -runQueryMInRuntime config runtime = do - flip runReaderT { config, runtime, extraConfig: {} } <<< unwrap - --- | Returns the `ProtocolParameters` from the `QueryM` environment. --- | Note that this is not necessarily the current value from the ledger. -getProtocolParameters :: QueryM Ogmios.ProtocolParameters -getProtocolParameters = - asks $ _.runtime >>> _.pparams - getProtocolParametersAff :: OgmiosWebSocket -> (LogLevel -> String -> Effect Unit) @@ -673,19 +520,6 @@ mempoolSnapshotHasTxAff ogmiosWs logger ms = -- Datum Cache Queries -------------------------------------------------------------------------------- -getDatumByHash :: DataHash -> QueryM (Maybe Datum) -getDatumByHash hash = unwrap <$> do - mkDatumCacheRequest DcWsp.getDatumByHashCall _.getDatumByHash hash - -getDatumsByHashes :: Array DataHash -> QueryM (Map DataHash Datum) -getDatumsByHashes hashes = Map.mapMaybe hush <$> getDatumsByHashesWithErrors - hashes - -getDatumsByHashesWithErrors - :: Array DataHash -> QueryM (Map DataHash (Either String Datum)) -getDatumsByHashesWithErrors hashes = unwrap <$> do - mkDatumCacheRequest DcWsp.getDatumsByHashesCall _.getDatumsByHashes hashes - checkTxByHashAff :: DatumCacheWebSocket -> Logger -> TxHash -> Aff Boolean checkTxByHashAff datumCacheWs logger = mkDatumCacheRequestAff datumCacheWs logger DcWsp.getTxByHashCall _.getTxByHash @@ -696,100 +530,9 @@ allowError allowError func = func <<< Right -------------------------------------------------------------------------------- --- Wallet +-- Affjax -------------------------------------------------------------------------------- -getUnusedAddresses :: QueryM (Array Address) -getUnusedAddresses = fold <$> do - actionBasedOnWallet _.getUnusedAddresses - (\_ -> pure []) - -getChangeAddress :: QueryM (Maybe Address) -getChangeAddress = do - networkId <- getNetworkId - actionBasedOnWallet _.getChangeAddress (\kw -> (unwrap kw).address networkId) - -getRewardAddresses :: QueryM (Array Address) -getRewardAddresses = fold <$> do - networkId <- getNetworkId - actionBasedOnWallet _.getRewardAddresses - (\kw -> Array.singleton <$> (unwrap kw).address networkId) - -getWalletAddresses :: QueryM (Array Address) -getWalletAddresses = fold <$> do - networkId <- getNetworkId - actionBasedOnWallet _.getWalletAddresses - (\kw -> Array.singleton <$> (unwrap kw).address networkId) - -actionBasedOnWallet - :: forall (a :: Type) - . (Cip30Wallet -> Cip30Connection -> Aff (Maybe a)) - -> (KeyWallet -> Aff a) - -> QueryM (Maybe a) -actionBasedOnWallet walletAction keyWalletAction = - withMWalletAff case _ of - Eternl wallet -> callCip30Wallet wallet walletAction - Nami wallet -> callCip30Wallet wallet walletAction - Gero wallet -> callCip30Wallet wallet walletAction - Flint wallet -> callCip30Wallet wallet walletAction - Lode wallet -> callCip30Wallet wallet walletAction - KeyWallet kw -> pure <$> keyWalletAction kw - -signData :: Address -> RawBytes -> QueryM (Maybe DataSignature) -signData address payload = do - networkId <- getNetworkId - actionBasedOnWallet - (\wallet conn -> wallet.signData conn address payload) - (\kw -> (unwrap kw).signData networkId payload) - -getWallet :: QueryM (Maybe Wallet) -getWallet = asks (_.runtime >>> _.wallet) - -getNetworkId :: QueryM NetworkId -getNetworkId = asks $ _.config >>> _.networkId - -ownPubKeyHashes :: QueryM (Array PubKeyHash) -ownPubKeyHashes = catMaybes <$> do - getWalletAddresses >>= traverse \address -> do - paymentCred <- - liftM - ( error $ - "Unable to get payment credential from Address" - ) $ - addressPaymentCred address - pure $ stakeCredentialToKeyHash paymentCred <#> wrap - -ownPaymentPubKeyHashes :: QueryM (Array PaymentPubKeyHash) -ownPaymentPubKeyHashes = map wrap <$> ownPubKeyHashes - -ownStakePubKeysHashes :: QueryM (Array (Maybe StakePubKeyHash)) -ownStakePubKeysHashes = do - addresses <- getWalletAddresses - pure $ addressToMStakePubKeyHash <$> addresses - where - - addressToMStakePubKeyHash :: Address -> Maybe StakePubKeyHash - addressToMStakePubKeyHash address = do - baseAddress <- baseAddressFromAddress address - wrap <<< wrap <$> stakeCredentialToKeyHash - (baseAddressDelegationCred baseAddress) - -withMWalletAff - :: forall (a :: Type). (Wallet -> Aff (Maybe a)) -> QueryM (Maybe a) -withMWalletAff act = withMWallet (liftAff <<< act) - -withMWallet - :: forall (a :: Type). (Wallet -> QueryM (Maybe a)) -> QueryM (Maybe a) -withMWallet act = asks (_.runtime >>> _.wallet) >>= maybe (pure Nothing) - act - -callCip30Wallet - :: forall (a :: Type) - . Cip30Wallet - -> (Cip30Wallet -> (Cip30Connection -> Aff a)) - -> Aff a -callCip30Wallet wallet act = act wallet wallet.connection - data ClientError = ClientHttpError Affjax.Error | ClientHttpResponseError String @@ -820,55 +563,6 @@ instance Show ClientError where <> err <> ")" --- | Apply `PlutusData` arguments to any type isomorphic to `PlutusScript`, --- | returning an updated script with the provided arguments applied -applyArgs - :: PlutusScript - -> Array PlutusData - -> QueryM (Either ClientError PlutusScript) -applyArgs script args = - asks (_.ctlServerConfig <<< _.config) >>= case _ of - Nothing -> pure - $ Left - $ - ClientOtherError - "The `ctl-server` service is required to call `applyArgs`. Please \ - \provide a `Just` value in `ConfigParams.ctlServerConfig` and make \ - \sure that the `ctl-server` service is running and available at the \ - \provided host and port. The `ctl-server` packages can be obtained \ - \from `overlays.ctl-server` defined in CTL's flake. Please see \ - \`doc/runtime.md` in the CTL repository for more information" - Just config -> case traverse plutusDataToAeson args of - Nothing -> pure $ Left $ ClientEncodingError - "Failed to convert script args" - Just ps -> do - let - language :: Language - language = snd $ unwrap script - - url :: String - url = mkHttpUrl config <> "apply-args" - - reqBody :: Aeson - reqBody = encodeAeson - $ Object.fromFoldable - [ "script" /\ scriptToAeson script - , "args" /\ encodeAeson ps - ] - liftAff (postAeson url reqBody) - <#> map (PlutusScript <<< flip Tuple language) <<< - handleAffjaxResponse - where - plutusDataToAeson :: PlutusData -> Maybe Aeson - plutusDataToAeson = - map - ( encodeAeson - <<< byteArrayToHex - <<< Serialization.toBytes - <<< asOneOf - ) - <<< Serialization.convertPlutusData - -- Checks response status code and returns `ClientError` in case of failure, -- otherwise attempts to decode the result. -- diff --git a/src/Internal/QueryM/Blockfrost.purs b/src/Internal/QueryM/Blockfrost.purs deleted file mode 100644 index 96944d23dd..0000000000 --- a/src/Internal/QueryM/Blockfrost.purs +++ /dev/null @@ -1,17 +0,0 @@ -module Ctl.Internal.QueryM.Blockfrost where - -import Prelude - -import Ctl.Internal.Cardano.Types.Transaction (UtxoMap) -import Ctl.Internal.QueryM (ClientError, QueryM) -import Ctl.Internal.Serialization.Address (Address) -import Ctl.Internal.Types.Datum (DataHash, Datum) -import Data.Either (Either) -import Data.Maybe (Maybe) -import Undefined (undefined) - -utxosAt :: Address -> QueryM (Either ClientError UtxoMap) -utxosAt = undefined - -getDatumByHash :: DataHash -> QueryM (Either ClientError (Maybe Datum)) -getDatumByHash = undefined diff --git a/src/Internal/QueryM/MinFee.purs b/src/Internal/QueryM/MinFee.purs deleted file mode 100644 index ee9efc51e0..0000000000 --- a/src/Internal/QueryM/MinFee.purs +++ /dev/null @@ -1,117 +0,0 @@ -module Ctl.Internal.QueryM.MinFee (calculateMinFee) where - -import Prelude - -import Ctl.Internal.Cardano.Types.Transaction - ( Transaction - , UtxoMap - , _body - , _collateral - , _inputs - ) -import Ctl.Internal.Cardano.Types.TransactionUnspentOutput - ( TransactionUnspentOutput - ) -import Ctl.Internal.Cardano.Types.Value (Coin) -import Ctl.Internal.Helpers (liftM, liftedM) -import Ctl.Internal.QueryM (QueryM, getProtocolParameters, getWalletAddresses) -import Ctl.Internal.QueryM.Utxos (getUtxo, getWalletCollateral) -import Ctl.Internal.Serialization.Address - ( Address - , addressPaymentCred - , addressStakeCred - , stakeCredentialToKeyHash - ) -import Ctl.Internal.Serialization.Hash (Ed25519KeyHash) -import Ctl.Internal.Serialization.MinFee (calculateMinFeeCsl) -import Ctl.Internal.Types.Transaction (TransactionInput) -import Data.Array (fromFoldable, mapMaybe) -import Data.Array as Array -import Data.Lens.Getter ((^.)) -import Data.Map (empty, fromFoldable, keys, lookup, values) as Map -import Data.Maybe (fromMaybe, maybe) -import Data.Newtype (unwrap) -import Data.Set (Set) -import Data.Set (difference, fromFoldable, intersection, mapMaybe, union) as Set -import Data.Traversable (for) -import Data.Tuple.Nested ((/\)) -import Effect.Aff (error) - --- | Calculate `min_fee` using CSL with protocol parameters from Ogmios. -calculateMinFee :: Transaction -> UtxoMap -> QueryM Coin -calculateMinFee tx additionalUtxos = do - selfSigners <- getSelfSigners tx additionalUtxos - pparams <- getProtocolParameters - calculateMinFeeCsl pparams selfSigners tx - -getSelfSigners :: Transaction -> UtxoMap -> QueryM (Set Ed25519KeyHash) -getSelfSigners tx additionalUtxos = do - - -- Get all tx inputs and remove the additional ones. - let - txInputs :: Set TransactionInput - txInputs = - Set.difference - (tx ^. _body <<< _inputs) - (Map.keys additionalUtxos) - - additionalUtxosAddrs :: Set Address - additionalUtxosAddrs = Set.fromFoldable $ - (_.address <<< unwrap) <$> Map.values additionalUtxos - - (inUtxosAddrs :: Set Address) <- setFor txInputs $ \txInput -> - liftedM (error $ "Couldn't get tx output for " <> show txInput) $ - (map <<< map) (_.address <<< unwrap) (getUtxo txInput) - - -- Get all tx output addressses - let - txCollats :: Set TransactionInput - txCollats = Set.fromFoldable <<< fromMaybe [] $ tx ^. _body <<< _collateral - - walletCollats <- maybe Map.empty toUtxoMap <$> getWalletCollateral - - (inCollatAddrs :: Set Address) <- setFor txCollats - ( \txCollat -> - liftM (error $ "Couldn't get tx output for " <> show txCollat) - $ (map (_.address <<< unwrap) <<< Map.lookup txCollat) - $ walletCollats - ) - - -- Get own addressses - (ownAddrs :: Set Address) <- Set.fromFoldable <$> getWalletAddresses - - -- Combine to get all self tx input addresses - let - txOwnAddrs = ownAddrs `Set.intersection` - (additionalUtxosAddrs `Set.union` inUtxosAddrs `Set.union` inCollatAddrs) - - -- Extract payment pub key hashes from addresses. - paymentPkhs <- map (Set.mapMaybe identity) $ setFor txOwnAddrs $ \addr -> do - paymentCred <- - liftM - ( error $ "Could not extract payment credential from Address: " <> show - addr - ) $ addressPaymentCred addr - pure $ stakeCredentialToKeyHash paymentCred - - -- Extract stake pub key hashes from addresses - let - stakePkhs = Set.fromFoldable $ - (stakeCredentialToKeyHash <=< addressStakeCred) `mapMaybe` - Array.fromFoldable txOwnAddrs - - pure $ paymentPkhs <> stakePkhs - where - setFor - :: forall (a :: Type) (b :: Type) (m :: Type -> Type) - . Monad m - => Ord a - => Ord b - => Set a - -> (a -> m b) - -> m (Set b) - setFor txIns f = Set.fromFoldable <$> for (fromFoldable txIns) f - - toUtxoMap :: Array TransactionUnspentOutput -> UtxoMap - toUtxoMap = Map.fromFoldable <<< map - (unwrap >>> \({ input, output }) -> input /\ output) diff --git a/src/Internal/QueryM/Sign.purs b/src/Internal/QueryM/Sign.purs deleted file mode 100644 index f6e3daa3df..0000000000 --- a/src/Internal/QueryM/Sign.purs +++ /dev/null @@ -1,97 +0,0 @@ -module Ctl.Internal.QueryM.Sign - ( signTransaction - ) where - -import Prelude - -import Control.Monad.Reader (asks) -import Ctl.Internal.Cardano.Types.Transaction (_body, _inputs, _witnessSet) -import Ctl.Internal.Cardano.Types.Transaction as Transaction -import Ctl.Internal.Helpers (liftedM) -import Ctl.Internal.QueryM - ( QueryM - , callCip30Wallet - , getWalletAddresses - , withMWallet - ) -import Ctl.Internal.QueryM.Utxos (getUtxo, getWalletUtxos) -import Ctl.Internal.Types.Transaction (TransactionInput) -import Ctl.Internal.Wallet (Wallet(KeyWallet, Lode, Eternl, Flint, Gero, Nami)) -import Data.Array (elem, fromFoldable) -import Data.Lens ((<>~)) -import Data.Lens.Getter ((^.)) -import Data.Map as Map -import Data.Maybe (Maybe(Just), fromMaybe) -import Data.Newtype (unwrap, wrap) -import Data.Traversable (for_, traverse) -import Data.Tuple.Nested ((/\)) -import Effect.Aff (delay, error) -import Effect.Aff.Class (liftAff) -import Effect.Class (liftEffect) -import Effect.Exception (throw, try) - -signTransaction - :: Transaction.Transaction -> QueryM (Maybe Transaction.Transaction) -signTransaction tx = do - config <- asks (_.config) - let - runHook = - for_ config.hooks.beforeSign (void <<< liftEffect <<< try) - runHook - withMWallet case _ of - Nami nami -> liftAff $ callCip30Wallet nami \nw -> flip nw.signTx tx - Gero gero -> liftAff $ callCip30Wallet gero \nw -> flip nw.signTx tx - Flint flint -> liftAff $ callCip30Wallet flint \nw -> flip nw.signTx tx - Eternl eternl -> do - let - txInputs :: Array TransactionInput - txInputs = fromFoldable $ tx ^. _body <<< _inputs - walletWaitForInputs txInputs - liftAff $ callCip30Wallet eternl \nw -> flip nw.signTx tx - Lode lode -> liftAff $ callCip30Wallet lode \nw -> flip nw.signTx tx - KeyWallet kw -> liftAff do - witnessSet <- (unwrap kw).signTx tx - pure $ Just (tx # _witnessSet <>~ witnessSet) - --- | Waits till all provided inputs of a given transaction appear in the UTxO --- | set provided by the wallet. --- | This is a hacky solution to the problem of Eternl not seeing UTxOs that --- | hasn't been fully confirmed at the moment of a `sign()` call. --- | Since it can't detect UTxO origin, it can't decide which of the private --- | keys to use for signing. As a result, we get `MissingVKeyWitnesses`. -walletWaitForInputs :: Array TransactionInput -> QueryM Unit -walletWaitForInputs txInputs = do - ownAddrs <- getWalletAddresses - ownInputUtxos <- txInputs # - traverse - ( \txInput -> do - utxo <- liftedM (error "Could not get utxo") $ getUtxo txInput - pure (txInput /\ utxo) - ) >>> map - ( Map.fromFoldable >>> Map.filter - ( flip elem ownAddrs - <<< _.address - <<< unwrap - ) - ) - let - go attempts = do - walletUtxos <- getWalletUtxos <#> fromMaybe Map.empty - unless (ownInputUtxos `Map.isSubmap` walletUtxos) do - when (attempts == 0) do - liftEffect $ throw $ - "walletWaitForInputs: timeout while waiting for wallet" - <> " UTxO set and CTL query layer UTxO set to synchronize. UTxOs" - <> " from Ogmios: " - <> show ownInputUtxos - <> ", UTxOs from wallet: " - <> show walletUtxos - <> ", UTxOs that didn't appear in the wallet: " - <> - show (Map.difference ownInputUtxos walletUtxos) - liftAff $ delay $ wrap $ 1000.0 - go (attempts - 1) - -- As clarified in Eternl discord, they synchronize with the server every 2 - -- minutes, so 150 seconds would probably be enough to also account for - -- possible network latency. - go 150 diff --git a/src/Internal/QueryM/SystemStart.purs b/src/Internal/QueryM/SystemStart.purs deleted file mode 100644 index ddeffe6bd4..0000000000 --- a/src/Internal/QueryM/SystemStart.purs +++ /dev/null @@ -1,15 +0,0 @@ --- | A module to get "systemStart" via an Ogmios request. -module Ctl.Internal.QueryM.SystemStart - ( getSystemStart - ) where - -import Prelude - -import Ctl.Internal.QueryM (QueryM, mkOgmiosRequest) -import Ctl.Internal.QueryM.Ogmios (SystemStart, querySystemStartCall) as Ogmios - --- | Get the current system start time. Details can be found --- | https://ogmios.dev/api/ under "systemStart" query -getSystemStart :: QueryM Ogmios.SystemStart -getSystemStart = - mkOgmiosRequest Ogmios.querySystemStartCall _.systemStart unit diff --git a/src/Internal/QueryM/Utxos.purs b/src/Internal/QueryM/Utxos.purs deleted file mode 100644 index 178e29937b..0000000000 --- a/src/Internal/QueryM/Utxos.purs +++ /dev/null @@ -1,172 +0,0 @@ --- | A module for `QueryM` queries related to utxos. -module Ctl.Internal.QueryM.Utxos - ( filterLockedUtxos - , getUtxo - , getWalletBalance - , utxosAt - , getWalletCollateral - , getWalletUtxos - ) where - -import Prelude - -import Control.Monad.Reader (withReaderT) -import Control.Monad.Reader.Trans (ReaderT, asks) -import Ctl.Internal.Cardano.Types.Transaction (TransactionOutput, UtxoMap) -import Ctl.Internal.Cardano.Types.TransactionUnspentOutput - ( TransactionUnspentOutput - ) -import Ctl.Internal.Cardano.Types.Value (Value) -import Ctl.Internal.Helpers as Helpers -import Ctl.Internal.QueryM - ( QueryM - , callCip30Wallet - , getNetworkId - , getWalletAddresses - ) -import Ctl.Internal.QueryM.Kupo (getUtxoByOref, utxosAt) as Kupo -import Ctl.Internal.Serialization.Address (Address) -import Ctl.Internal.Types.Transaction (TransactionInput) -import Ctl.Internal.Types.UsedTxOuts (UsedTxOuts, isTxOutRefUsed) -import Ctl.Internal.Wallet (Wallet(Gero, Nami, Flint, Lode, Eternl, KeyWallet)) -import Data.Array (head) -import Data.Array as Array -import Data.Either (hush) -import Data.Foldable (fold, foldr) -import Data.Map as Map -import Data.Maybe (Maybe(Nothing), fromMaybe, maybe) -import Data.Newtype (unwrap, wrap) -import Data.Traversable (for, for_, traverse) -import Data.Tuple.Nested ((/\)) -import Data.UInt as UInt -import Effect.Aff (Aff) -import Effect.Aff.Class (liftAff) -import Effect.Class (liftEffect) -import Effect.Exception (throw) - --------------------------------------------------------------------------------- --- UtxosAt --------------------------------------------------------------------------------- - --- If required, we can change to `Either` with more granular error handling. --- | Gets utxos at an (internal) `Address` in terms of (internal) `Cardano.Transaction.Types`. --- | Results may vary depending on `Wallet` type. -utxosAt :: Address -> QueryM (Maybe UtxoMap) -utxosAt address = mkUtxoQuery (hush <$> Kupo.utxosAt address) - --- | Queries for an utxo given a transaction input. -getUtxo :: TransactionInput -> QueryM (Maybe TransactionOutput) -getUtxo = map (join <<< hush) <<< Kupo.getUtxoByOref - -mkUtxoQuery :: QueryM (Maybe UtxoMap) -> QueryM (Maybe UtxoMap) -mkUtxoQuery allUtxosAt = - maybe allUtxosAt utxosAtByWallet =<< asks (_.wallet <<< _.runtime) - where - -- Add more wallet types here: - utxosAtByWallet :: Wallet -> QueryM (Maybe UtxoMap) - utxosAtByWallet = case _ of - Nami _ -> cip30UtxosAt - Gero _ -> cip30UtxosAt - Flint _ -> cip30UtxosAt - Eternl _ -> cip30UtxosAt - Lode _ -> cip30UtxosAt - KeyWallet _ -> allUtxosAt - - cip30UtxosAt :: QueryM (Maybe UtxoMap) - cip30UtxosAt = getWalletCollateral >>= maybe - (liftEffect $ throw "CIP-30 wallet missing collateral") - \collateralUtxos -> - allUtxosAt <#> \utxos' -> - foldr - ( \collateralUtxo utxoAcc -> - (Map.delete (unwrap collateralUtxo).input) <$> utxoAcc - ) - utxos' - collateralUtxos - --------------------------------------------------------------------------------- --- Used Utxos helpers --------------------------------------------------------------------------------- - -filterLockedUtxos :: UtxoMap -> QueryM UtxoMap -filterLockedUtxos utxos = - withTxRefsCache $ - flip Helpers.filterMapWithKeyM utxos - (\k _ -> not <$> isTxOutRefUsed (unwrap k)) - -withTxRefsCache - :: forall (m :: Type -> Type) (a :: Type) - . ReaderT UsedTxOuts Aff a - -> QueryM a -withTxRefsCache = wrap <<< withReaderT (_.runtime >>> _.usedTxOuts) - -getWalletBalance - :: QueryM (Maybe Value) -getWalletBalance = do - asks (_.runtime >>> _.wallet) >>= map join <<< traverse case _ of - Nami wallet -> liftAff $ wallet.getBalance wallet.connection - Gero wallet -> liftAff $ wallet.getBalance wallet.connection - Eternl wallet -> liftAff $ wallet.getBalance wallet.connection - Flint wallet -> liftAff $ wallet.getBalance wallet.connection - Lode wallet -> liftAff $ wallet.getBalance wallet.connection - KeyWallet _ -> do - -- Implement via `utxosAt` - addresses <- getWalletAddresses - fold <$> for addresses \address -> do - utxosAt address <#> map - -- Combine `Value`s - (fold <<< map _.amount <<< map unwrap <<< Map.values) - -getWalletUtxos :: QueryM (Maybe UtxoMap) -getWalletUtxos = do - asks (_.runtime >>> _.wallet) >>= map join <<< traverse case _ of - Nami wallet -> liftAff $ wallet.getUtxos wallet.connection <#> map toUtxoMap - Gero wallet -> liftAff $ wallet.getUtxos wallet.connection <#> map toUtxoMap - Flint wallet -> liftAff $ wallet.getUtxos wallet.connection <#> map - toUtxoMap - Eternl wallet -> liftAff $ wallet.getUtxos wallet.connection <#> map - toUtxoMap - Lode wallet -> liftAff $ wallet.getUtxos wallet.connection <#> map toUtxoMap - KeyWallet _ -> do - mbAddress <- getWalletAddresses <#> head - map join $ for mbAddress utxosAt - where - toUtxoMap :: Array TransactionUnspentOutput -> UtxoMap - toUtxoMap = Map.fromFoldable <<< map - (unwrap >>> \({ input, output }) -> input /\ output) - -getWalletCollateral :: QueryM (Maybe (Array TransactionUnspentOutput)) -getWalletCollateral = do - mbCollateralUTxOs <- asks (_.runtime >>> _.wallet) >>= maybe (pure Nothing) - case _ of - Nami wallet -> liftAff $ callCip30Wallet wallet _.getCollateral - Gero wallet -> liftAff $ callCip30Wallet wallet _.getCollateral - Flint wallet -> liftAff $ callCip30Wallet wallet _.getCollateral - Lode wallet -> liftAff $ callCip30Wallet wallet _.getCollateral - Eternl wallet -> liftAff $ callCip30Wallet wallet _.getCollateral - KeyWallet kw -> do - networkId <- getNetworkId - addr <- liftAff $ (unwrap kw).address networkId - utxos <- utxosAt addr <#> fromMaybe Map.empty - >>= filterLockedUtxos - pparams <- asks $ _.runtime >>> _.pparams <#> unwrap - let - coinsPerUtxoUnit = pparams.coinsPerUtxoUnit - maxCollateralInputs = UInt.toInt $ - pparams.maxCollateralInputs - liftEffect $ (unwrap kw).selectCollateral coinsPerUtxoUnit - maxCollateralInputs - utxos - for_ mbCollateralUTxOs \collateralUTxOs -> do - pparams <- asks $ _.runtime >>> _.pparams - let - tooManyCollateralUTxOs = - UInt.fromInt (Array.length collateralUTxOs) > - (unwrap pparams).maxCollateralInputs - when tooManyCollateralUTxOs do - liftEffect $ throw tooManyCollateralUTxOsError - pure mbCollateralUTxOs - where - tooManyCollateralUTxOsError = - "Wallet returned too many UTxOs as collateral. This is likely a bug in \ - \the wallet." diff --git a/src/Internal/Test/E2E/Route.purs b/src/Internal/Test/E2E/Route.purs index c713246479..a2bee1dff5 100644 --- a/src/Internal/Test/E2E/Route.purs +++ b/src/Internal/Test/E2E/Route.purs @@ -173,7 +173,7 @@ route configs tests = do # maybe identity setClusterOptions mbClusterSetup do runContract configWithHooks - $ withCip30Mock (privateKeysToKeyWallet paymentKey stakeKey) mock + $ withCip30Mock (privateKeysToKeyWallet config.networkId paymentKey stakeKey) mock test where -- Eternl does not initialize instantly. We have to add a small delay. diff --git a/src/Internal/Wallet.purs b/src/Internal/Wallet.purs index ad6c34c3ba..4fb766e55f 100644 --- a/src/Internal/Wallet.purs +++ b/src/Internal/Wallet.purs @@ -29,6 +29,16 @@ module Ctl.Internal.Wallet , apiVersion , name , icon + , getNetworkId + , getUnusedAddresses + , getChangeAddress + , getRewardAddresses + , getWalletAddresses + , actionBasedOnWalletAff + , signData + , ownPubKeyHashes + , ownPaymentPubKeyHashes + , ownStakePubKeysHashes ) where import Prelude @@ -49,6 +59,7 @@ import Ctl.Internal.Wallet.Cip30 (Cip30Connection, Cip30Wallet) as Cip30Wallet import Ctl.Internal.Wallet.Cip30 ( Cip30Connection , Cip30Wallet + , DataSignature , mkCip30WalletAff ) import Ctl.Internal.Wallet.Key @@ -60,13 +71,32 @@ import Ctl.Internal.Wallet.Key import Ctl.Internal.Wallet.Key (KeyWallet, privateKeysToKeyWallet) as KeyWallet import Data.Int (toNumber) import Data.Maybe (Maybe(Just, Nothing), fromJust) -import Data.Newtype (over, wrap) +import Data.Newtype (over, wrap, unwrap) import Data.Tuple.Nested ((/\)) import Effect (Effect) import Effect.Aff (Aff, delay, error) import Effect.Class (liftEffect) import Partial.Unsafe (unsafePartial) import Prim.TypeError (class Warn, Text) +import Ctl.Internal.Helpers as Helpers +import Data.Array as Array +import Data.Foldable (fold) +import Data.Traversable (traverse) +import Effect.Exception (throw) +import Ctl.Internal.Serialization.Address + ( Address + , NetworkId(TestnetId, MainnetId) + , addressPaymentCred + , baseAddressDelegationCred + , baseAddressFromAddress + , stakeCredentialToKeyHash + ) +import Ctl.Internal.Types.PubKeyHash + ( PaymentPubKeyHash + , PubKeyHash + , StakePubKeyHash + ) +import Ctl.Internal.Types.RawBytes (RawBytes) data Wallet = Nami Cip30Wallet @@ -83,9 +113,8 @@ data WalletExtension | EternlWallet | LodeWallet -mkKeyWallet :: PrivatePaymentKey -> Maybe PrivateStakeKey -> Wallet -mkKeyWallet payKey mbStakeKey = KeyWallet $ privateKeysToKeyWallet payKey - mbStakeKey +mkKeyWallet :: NetworkId -> PrivatePaymentKey -> Maybe PrivateStakeKey -> Wallet +mkKeyWallet network payKey mbStakeKey = KeyWallet $ privateKeysToKeyWallet network payKey mbStakeKey foreign import _enableWallet :: String -> Effect (Promise Cip30Connection) foreign import _isWalletAvailable :: String -> Effect Boolean @@ -273,3 +302,94 @@ dummySign tx@(Transaction { witnessSet: tws@(TransactionWitnessSet ws) }) = "ed25519_sig1ynufn5umzl746ekpjtzt2rf58ep0wg6mxpgyezh8vx0e8jpgm3kuu3tgm453wlz4rq5yjtth0fnj0ltxctaue0dgc2hwmysr9jvhjzswt86uk" ) ) + +getNetworkId :: Wallet -> Aff NetworkId +getNetworkId wallet = do + actionBasedOnWalletAff + (\w -> intToNetworkId <=< _.getNetworkId w) + (\kw -> pure (unwrap kw).networkId) + wallet + where + intToNetworkId :: Int -> Aff NetworkId + intToNetworkId = case _ of + 0 -> pure TestnetId + 1 -> pure MainnetId + _ -> liftEffect $ throw "Unknown network id" + +getUnusedAddresses :: Wallet -> Aff (Array Address) +getUnusedAddresses wallet = fold <$> do + actionBasedOnWalletAff _.getUnusedAddresses + (\_ -> pure $ pure []) + wallet + +getChangeAddress :: Wallet -> Aff (Maybe Address) +getChangeAddress wallet = do + actionBasedOnWalletAff _.getChangeAddress (\kw -> pure $ pure (unwrap kw).address) + wallet + +getRewardAddresses :: Wallet -> Aff (Array Address) +getRewardAddresses wallet = fold <$> do + actionBasedOnWalletAff _.getRewardAddresses + (\kw -> pure $ pure $ pure (unwrap kw).address) + wallet + +getWalletAddresses :: Wallet -> Aff (Array Address) +getWalletAddresses wallet = fold <$> do + actionBasedOnWalletAff _.getWalletAddresses + (\kw -> pure $ pure $ Array.singleton (unwrap kw).address) + wallet + +signData :: Address -> RawBytes -> Wallet -> Aff (Maybe DataSignature) +signData address payload wallet = do + actionBasedOnWalletAff + (\w conn -> w.signData conn address payload) + (\kw -> pure <$> (unwrap kw).signData payload) + wallet + +actionBasedOnWalletAff + :: forall (a :: Type) + . (Cip30Wallet -> Cip30Connection -> Aff a) + -> (KeyWallet -> Aff a) + -> Wallet + -> Aff a +actionBasedOnWalletAff walletAction keyWalletAction = + case _ of + Eternl wallet -> callCip30Wallet wallet walletAction + Nami wallet -> callCip30Wallet wallet walletAction + Gero wallet -> callCip30Wallet wallet walletAction + Flint wallet -> callCip30Wallet wallet walletAction + Lode wallet -> callCip30Wallet wallet walletAction + KeyWallet kw -> keyWalletAction kw + +ownPubKeyHashes :: Wallet -> Aff (Array PubKeyHash) +ownPubKeyHashes wallet = Array.catMaybes <$> do + getWalletAddresses wallet >>= traverse \address -> do + paymentCred <- + Helpers.liftM + ( error $ + "Unable to get payment credential from Address" + ) $ + addressPaymentCred address + pure $ stakeCredentialToKeyHash paymentCred <#> wrap + +ownPaymentPubKeyHashes :: Wallet -> Aff (Array PaymentPubKeyHash) +ownPaymentPubKeyHashes wallet = map wrap <$> ownPubKeyHashes wallet + +ownStakePubKeysHashes :: Wallet -> Aff (Array (Maybe StakePubKeyHash)) +ownStakePubKeysHashes wallet = do + addresses <- getWalletAddresses wallet + pure $ addressToMStakePubKeyHash <$> addresses + where + + addressToMStakePubKeyHash :: Address -> Maybe StakePubKeyHash + addressToMStakePubKeyHash address = do + baseAddress <- baseAddressFromAddress address + wrap <<< wrap <$> stakeCredentialToKeyHash + (baseAddressDelegationCred baseAddress) + +callCip30Wallet + :: forall (a :: Type) + . Cip30Wallet + -> (Cip30Wallet -> (Cip30Connection -> Aff a)) + -> Aff a +callCip30Wallet wallet act = act wallet wallet.connection diff --git a/src/Internal/Wallet/Cip30Mock.purs b/src/Internal/Wallet/Cip30Mock.purs index d180450652..aa80be604b 100644 --- a/src/Internal/Wallet/Cip30Mock.purs +++ b/src/Internal/Wallet/Cip30Mock.purs @@ -18,7 +18,7 @@ import Ctl.Internal.Serialization , convertValue , toBytes ) -import Ctl.Internal.Serialization.Address (NetworkId(TestnetId, MainnetId)) +import Ctl.Internal.Serialization.Address (Address, NetworkId(TestnetId, MainnetId)) import Ctl.Internal.Serialization.WitnessSet (convertWitnessSet) import Ctl.Internal.Types.ByteArray (byteArrayToHex, hexToByteArray) import Ctl.Internal.Types.CborBytes (cborBytesFromByteArray) @@ -130,13 +130,18 @@ mkCip30Mock pKey mSKey = do let queryHandle = getQueryHandle' env queryHandle.utxosAt address + keyWallet = privateKeysToKeyWallet env.networkId pKey mSKey + + addressHex = + byteArrayToHex $ toBytes $ asOneOf ((unwrap keyWallet).address :: Address) + pure $ { getNetworkId: fromAff $ pure $ case env.networkId of TestnetId -> 0 MainnetId -> 1 , getUtxos: fromAff do - ownAddress <- (unwrap keyWallet).address env.networkId + let ownAddress = (unwrap keyWallet).address utxos <- utxosAt ownAddress collateralUtxos <- getCollateralUtxos utxos let @@ -151,7 +156,7 @@ mkCip30Mock pKey mSKey = do TransactionUnspentOutput { input, output } pure $ (byteArrayToHex <<< toBytes <<< asOneOf) <$> cslUtxos , getCollateral: fromAff do - ownAddress <- (unwrap keyWallet).address env.networkId + let ownAddress = (unwrap keyWallet).address utxos <- utxosAt ownAddress collateralUtxos <- getCollateralUtxos utxos cslUnspentOutput <- liftEffect $ traverse @@ -159,22 +164,19 @@ mkCip30Mock pKey mSKey = do collateralUtxos pure $ (byteArrayToHex <<< toBytes <<< asOneOf) <$> cslUnspentOutput , getBalance: fromAff do - ownAddress <- (unwrap keyWallet).address env.networkId + let ownAddress = (unwrap keyWallet).address utxos <- utxosAt ownAddress value <- liftEffect $ convertValue $ (foldMap (_.amount <<< unwrap) <<< Map.values) utxos pure $ byteArrayToHex $ toBytes $ asOneOf value , getUsedAddresses: fromAff do - (unwrap keyWallet).address env.networkId <#> \address -> - [ (byteArrayToHex <<< toBytes <<< asOneOf) address ] + pure [addressHex] , getUnusedAddresses: fromAff $ pure [] , getChangeAddress: fromAff do - (unwrap keyWallet).address env.networkId <#> - (byteArrayToHex <<< toBytes <<< asOneOf) + pure addressHex , getRewardAddresses: fromAff do - (unwrap keyWallet).address env.networkId <#> \address -> - [ (byteArrayToHex <<< toBytes <<< asOneOf) address ] + pure [addressHex] , signTx: \str -> unsafePerformEffect $ fromAff do txBytes <- liftMaybe (error "Unable to convert CBOR") $ hexToByteArray str @@ -188,10 +190,8 @@ mkCip30Mock pKey mSKey = do , signData: mkFn2 \_addr msg -> unsafePerformEffect $ fromAff do msgBytes <- liftMaybe (error "Unable to convert CBOR") (hexToByteArray msg) - (unwrap keyWallet).signData env.networkId (wrap msgBytes) + (unwrap keyWallet).signData (wrap msgBytes) } - where - keyWallet = privateKeysToKeyWallet pKey mSKey -- returns an action that removes the mock. foreign import injectCip30Mock :: String -> Cip30Mock -> Effect (Effect Unit) diff --git a/src/Internal/Wallet/Key.purs b/src/Internal/Wallet/Key.purs index d50bf5090b..6a1bea56df 100644 --- a/src/Internal/Wallet/Key.purs +++ b/src/Internal/Wallet/Key.purs @@ -67,16 +67,17 @@ import Effect.Class (liftEffect) -- Key backend ------------------------------------------------------------------------------- newtype KeyWallet = KeyWallet - { address :: NetworkId -> Aff Address + { address :: Address , selectCollateral :: CoinsPerUtxoUnit -> Int -> UtxoMap -> Effect (Maybe (Array TransactionUnspentOutput)) , signTx :: Transaction -> Aff TransactionWitnessSet - , signData :: NetworkId -> RawBytes -> Aff DataSignature + , signData :: RawBytes -> Aff DataSignature , paymentKey :: PrivatePaymentKey , stakeKey :: Maybe PrivateStakeKey + , networkId :: NetworkId } derive instance Newtype KeyWallet _ @@ -122,38 +123,40 @@ keyWalletPrivateStakeKey :: KeyWallet -> Maybe PrivateStakeKey keyWalletPrivateStakeKey = unwrap >>> _.stakeKey privateKeysToAddress - :: PrivatePaymentKey -> Maybe PrivateStakeKey -> NetworkId -> Aff Address + :: PrivatePaymentKey -> Maybe PrivateStakeKey -> NetworkId -> Address privateKeysToAddress payKey mbStakeKey network = do let pubPayKey = publicKeyFromPrivateKey (unwrap payKey) case mbStakeKey of - Just stakeKey -> do - pubStakeKey <- pure $ publicKeyFromPrivateKey (unwrap stakeKey) - pure $ baseAddressToAddress $ + Just stakeKey -> + let pubStakeKey = publicKeyFromPrivateKey (unwrap stakeKey) + in baseAddressToAddress $ baseAddress { network , paymentCred: keyHashCredential $ publicKeyHash $ pubPayKey , delegationCred: keyHashCredential $ publicKeyHash $ pubStakeKey } - Nothing -> pure $ pubPayKey # publicKeyHash + Nothing -> pubPayKey # publicKeyHash >>> keyHashCredential >>> { network, paymentCred: _ } >>> enterpriseAddress >>> enterpriseAddressToAddress privateKeysToKeyWallet - :: PrivatePaymentKey -> Maybe PrivateStakeKey -> KeyWallet -privateKeysToKeyWallet payKey mbStakeKey = KeyWallet - { address - , selectCollateral - , signTx - , signData - , paymentKey: payKey - , stakeKey: mbStakeKey - } + :: NetworkId -> PrivatePaymentKey -> Maybe PrivateStakeKey -> KeyWallet +privateKeysToKeyWallet networkId payKey mbStakeKey = + KeyWallet + { address + , selectCollateral + , signTx + , signData: signData address + , paymentKey: payKey + , stakeKey: mbStakeKey + , networkId + } where - address :: NetworkId -> Aff Address - address = privateKeysToAddress payKey mbStakeKey + address :: Address + address = privateKeysToAddress payKey mbStakeKey networkId selectCollateral :: CoinsPerUtxoUnit @@ -178,7 +181,6 @@ privateKeysToKeyWallet payKey mbStakeKey = KeyWallet mempty pure witnessSet' - signData :: NetworkId -> RawBytes -> Aff DataSignature - signData networkId payload = do - addr <- address networkId + signData :: Address -> RawBytes -> Aff DataSignature + signData addr payload = do liftEffect $ Cip30SignData.signData (unwrap payKey) addr payload diff --git a/test/AffInterface.purs b/test/AffInterface.purs index 659750bb0e..35df2e8aa3 100644 --- a/test/AffInterface.purs +++ b/test/AffInterface.purs @@ -8,17 +8,17 @@ import Ctl.Internal.Address (ogmiosAddressToAddress) import Ctl.Internal.QueryM ( QueryM , getChainTip - , getDatumByHash - , getDatumsByHashes - , getDatumsByHashesWithErrors +-- , getDatumByHash +-- , getDatumsByHashes +-- , getDatumsByHashesWithErrors , submitTxOgmios ) import Ctl.Internal.QueryM.CurrentEpoch (getCurrentEpoch) import Ctl.Internal.QueryM.EraSummaries (getEraSummaries) import Ctl.Internal.QueryM.GetTxByHash (getTxByHash) import Ctl.Internal.QueryM.Ogmios (OgmiosAddress) -import Ctl.Internal.QueryM.SystemStart (getSystemStart) -import Ctl.Internal.QueryM.Utxos (utxosAt) +-- import Ctl.Internal.QueryM.SystemStart (getSystemStart) +-- import Ctl.Internal.QueryM.Utxos (utxosAt) import Ctl.Internal.Contract.WaitUntilSlot (waitUntilSlot) import Ctl.Internal.Serialization.Address (Slot(Slot)) import Ctl.Internal.Test.TestPlanM (TestPlanM) diff --git a/test/Wallet/Cip30/SignData.purs b/test/Wallet/Cip30/SignData.purs index c9648142b9..6c817f10ef 100644 --- a/test/Wallet/Cip30/SignData.purs +++ b/test/Wallet/Cip30/SignData.purs @@ -56,8 +56,9 @@ type TestInput = testCip30SignData :: TestInput -> Aff Unit testCip30SignData { privateKey, privateStakeKey, payload, networkId } = do - address <- - privateKeysToAddress (unwrap privateKey) (unwrap <$> privateStakeKey) + let + address = privateKeysToAddress (unwrap privateKey) + (unwrap <$> privateStakeKey) (unwrap networkId) { key, signature } <- liftEffect $ signData privatePaymentKey address payload From 05c2d1f8b85299e413d73efb35bf2d700eed17ce Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Tue, 29 Nov 2022 18:05:18 +0100 Subject: [PATCH 027/373] CoinSelection: Index utxos by asset to improve performance --- spago.dhall | 1 + src/Internal/BalanceTx/CoinSelection.purs | 255 ++++++++++++++++------ src/Internal/Cardano/Types/Value.purs | 5 + src/Internal/Types/ByteArray.purs | 9 +- src/Internal/Types/CborBytes.purs | 2 + src/Internal/Types/RawBytes.purs | 2 + src/Internal/Types/TokenName.purs | 2 + 7 files changed, 203 insertions(+), 73 deletions(-) diff --git a/spago.dhall b/spago.dhall index 43c4af9313..26bfd276f7 100644 --- a/spago.dhall +++ b/spago.dhall @@ -89,6 +89,7 @@ You can edit this file as you like. , "uint" , "undefined" , "unfoldable" + , "unordered-collections" , "untagged-union" , "variant" ] diff --git a/src/Internal/BalanceTx/CoinSelection.purs b/src/Internal/BalanceTx/CoinSelection.purs index 90dd83afef..dc94c3be76 100644 --- a/src/Internal/BalanceTx/CoinSelection.purs +++ b/src/Internal/BalanceTx/CoinSelection.purs @@ -3,8 +3,10 @@ -- | strategies (optimal and minimal) and uses priority ordering and round-robin -- | processing to handle the problem of over-selection. module Ctl.Internal.BalanceTx.CoinSelection - ( SelectionState(SelectionState) + ( Asset + , SelectionState(SelectionState) , SelectionStrategy(SelectionStrategyMinimal, SelectionStrategyOptimal) + , UtxoIndex(UtxoIndex) , _leftoverUtxos , performMultiAssetSelection , selectedInputs @@ -44,18 +46,22 @@ import Data.Array.NonEmpty (cons', fromArray, singleton, uncons) as NEArray import Data.BigInt (BigInt) import Data.BigInt (abs, fromInt, toString) as BigInt import Data.Foldable (foldMap) as Foldable +import Data.Foldable (foldl) import Data.Function (applyFlipped) +import Data.HashMap (HashMap) +import Data.HashMap (alter, empty, lookup, update) as HashMap +import Data.Hashable (class Hashable, hash) import Data.Lens (Lens') import Data.Lens.Getter (view, (^.)) import Data.Lens.Iso.Newtype (_Newtype) import Data.Lens.Record (prop) -import Data.Lens.Setter (over) +import Data.Lens.Setter (over, (%~)) import Data.Map (Map) import Data.Map as Map -import Data.Maybe (Maybe(Just, Nothing), maybe, maybe') +import Data.Maybe (Maybe(Just, Nothing), fromMaybe, maybe, maybe') import Data.Newtype (class Newtype, unwrap, wrap) import Data.Set (Set) -import Data.Set (fromFoldable, isEmpty, member, singleton, size) as Set +import Data.Set (fromFoldable, toUnfoldable) as Set import Data.Tuple (fst) as Tuple import Data.Tuple.Nested (type (/\), (/\)) import Effect.Class (class MonadEffect, liftEffect) @@ -139,14 +145,17 @@ performMultiAssetSelection strategy utxos requiredValue = -- | Taken from cardano-wallet: -- | https://github.com/input-output-hk/cardano-wallet/blob/a61d37f2557b8cb5c47b57da79375afad698eed4/lib/wallet/src/Cardano/Wallet/Primitive/Types/UTxOSelection.hs#L145 newtype SelectionState = SelectionState - { leftoverUtxos :: UtxoMap + { leftoverUtxos :: UtxoIndex , selectedUtxos :: UtxoMap } derive instance Newtype SelectionState _ _leftoverUtxos :: Lens' SelectionState UtxoMap -_leftoverUtxos = _Newtype <<< prop (Proxy :: Proxy "leftoverUtxos") +_leftoverUtxos = _leftoverUtxoIndex <<< _utxos + +_leftoverUtxoIndex :: Lens' SelectionState UtxoIndex +_leftoverUtxoIndex = _Newtype <<< prop (Proxy :: Proxy "leftoverUtxos") _selectedUtxos :: Lens' SelectionState UtxoMap _selectedUtxos = _Newtype <<< prop (Proxy :: Proxy "selectedUtxos") @@ -156,16 +165,17 @@ _selectedUtxos = _Newtype <<< prop (Proxy :: Proxy "selectedUtxos") -- | Taken from cardano-wallet: -- | https://github.com/input-output-hk/cardano-wallet/blob/a61d37f2557b8cb5c47b57da79375afad698eed4/lib/wallet/src/Cardano/Wallet/Primitive/Types/UTxOSelection.hs#L192 mkSelectionState :: UtxoMap -> SelectionState -mkSelectionState = wrap <<< { leftoverUtxos: _, selectedUtxos: Map.empty } +mkSelectionState = + wrap <<< { leftoverUtxos: _, selectedUtxos: Map.empty } <<< buildUtxoIndex -- | Moves a single utxo entry from the leftover set to the selected set. -- | -- | Taken from cardano-wallet: -- | https://github.com/input-output-hk/cardano-wallet/blob/a61d37f2557b8cb5c47b57da79375afad698eed4/lib/wallet/src/Cardano/Wallet/Primitive/Types/UTxOSelection.hs#L426 selectUtxo :: TxUnspentOutput -> SelectionState -> SelectionState -selectUtxo (oref /\ out) = +selectUtxo utxo@(oref /\ out) = over _selectedUtxos (Map.insert oref out) - <<< over _leftoverUtxos (Map.delete oref) + <<< over _leftoverUtxoIndex (utxoIndexDeleteEntry utxo) -- | Returns the balance of the given utxo set. balance :: UtxoMap -> Value @@ -227,9 +237,9 @@ assetSelectionLens selectionStrategy (assetClass /\ requiredQuantity) = selectedAssetQuantity assetClass , requiredQuantity , selectQuantityCover: - selectQuantityOf assetClass SelectionPriorityCover + selectQuantityOf (Asset assetClass) SelectionPriorityCover , selectQuantityImprove: - selectQuantityOf assetClass SelectionPriorityImprove + selectQuantityOf (Asset assetClass) SelectionPriorityImprove , selectionStrategy } @@ -246,9 +256,9 @@ coinSelectionLens selectionStrategy coin = , currentQuantity: selectedCoinQuantity , requiredQuantity: unwrap coin , selectQuantityCover: - selectQuantityOf coin SelectionPriorityCover + selectQuantityOf AssetLovelace SelectionPriorityCover , selectQuantityImprove: - selectQuantityOf coin SelectionPriorityImprove + selectQuantityOf AssetLovelace SelectionPriorityImprove , selectionStrategy } @@ -262,21 +272,20 @@ coinSelectionLens selectionStrategy coin = -- | Taken from cardano-wallet: -- | https://github.com/input-output-hk/cardano-wallet/blob/a61d37f2557b8cb5c47b57da79375afad698eed4/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L1217 selectQuantityOf - :: forall (m :: Type -> Type) (asset :: Type) + :: forall (m :: Type -> Type) . MonadEffect m - => ApplySelectionFilter asset - => asset + => Asset -> SelectionPriority -> SelectionState -> m (Maybe SelectionState) selectQuantityOf asset priority state = map updateState <$> - selectRandomWithPriority (state ^. _leftoverUtxos) filters + selectRandomWithPriority (state ^. _leftoverUtxoIndex) filters where - filters :: NonEmptyArray (SelectionFilter asset) + filters :: NonEmptyArray SelectionFilter filters = filtersForAssetWithPriority asset priority - updateState :: TxUnspentOutput /\ UtxoMap -> SelectionState + updateState :: TxUnspentOutput /\ UtxoIndex -> SelectionState updateState = flip selectUtxo state <<< Tuple.fst -- | Runs just a single step of a coin selection. @@ -381,10 +390,9 @@ runRoundRobinM' state demote processors = go state processors [] data SelectionPriority = SelectionPriorityCover | SelectionPriorityImprove filtersForAssetWithPriority - :: forall (asset :: Type) - . asset + :: Asset -> SelectionPriority - -> NonEmptyArray (SelectionFilter asset) + -> NonEmptyArray SelectionFilter filtersForAssetWithPriority asset priority = case priority of SelectionPriorityCover -> @@ -396,70 +404,179 @@ filtersForAssetWithPriority asset priority = -- | Taken from cardano-wallet: -- | https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L460 selectRandomWithPriority - :: forall (m :: Type -> Type) (asset :: Type) + :: forall (m :: Type -> Type) . MonadEffect m - => ApplySelectionFilter asset - => UtxoMap - -> NonEmptyArray (SelectionFilter asset) - -> m (Maybe (TxUnspentOutput /\ UtxoMap)) -selectRandomWithPriority utxos filters = + => UtxoIndex + -> NonEmptyArray SelectionFilter + -> m (Maybe (TxUnspentOutput /\ UtxoIndex)) +selectRandomWithPriority utxoIndex filters = NEArray.uncons filters # \{ head: filter, tail } -> case NEArray.fromArray tail of Nothing -> - selectRandomWithFilter utxos filter + selectRandomWithFilter utxoIndex filter Just xs -> - maybe' (\_ -> selectRandomWithPriority utxos xs) (pure <<< Just) - =<< selectRandomWithFilter utxos filter + maybe' (\_ -> selectRandomWithPriority utxoIndex xs) (pure <<< Just) + =<< selectRandomWithFilter utxoIndex filter + +-------------------------------------------------------------------------------- +-- Asset +-------------------------------------------------------------------------------- + +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/791541da69b9b3f434bb9ead43de406cc18b0373/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L485 +data Asset = AssetLovelace | Asset AssetClass + +derive instance Eq Asset + +instance Hashable Asset where + hash AssetLovelace = hash (Nothing :: Maybe AssetClass) + hash (Asset asset) = hash (Just asset) -------------------------------------------------------------------------------- --- SelectionFilter, ApplySelectionFilter +-- SelectionFilter -------------------------------------------------------------------------------- -- | Taken from cardano-wallet: -- | https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L399 -data SelectionFilter (asset :: Type) - = SelectSingleton asset - | SelectPairWith asset - | SelectAnyWith asset - -class ApplySelectionFilter (asset :: Type) where - applySelectionFilter :: UtxoMap -> SelectionFilter asset -> UtxoMap - -instance ApplySelectionFilter AssetClass where - applySelectionFilter utxos filter = - flip Map.filter utxos $ - case filter of - SelectSingleton asset -> - eq (Set.singleton asset) <<< txOutputAssetClasses - SelectPairWith asset -> - (\assets -> Set.member asset assets && Set.size assets == 2) - <<< txOutputAssetClasses - SelectAnyWith asset -> - Set.member asset <<< txOutputAssetClasses - -instance ApplySelectionFilter Coin where - applySelectionFilter utxos filter = - case filter of - SelectSingleton _ -> - Map.filter (Set.isEmpty <<< txOutputAssetClasses) utxos - SelectPairWith _ -> - Map.filter (eq one <<< Set.size <<< txOutputAssetClasses) utxos - SelectAnyWith _ -> utxos +data SelectionFilter + = SelectSingleton Asset + | SelectPairWith Asset + | SelectAnyWith Asset type TxUnspentOutput = TransactionInput /\ TransactionOutput +-------------------------------------------------------------------------------- +-- UtxoIndex +-------------------------------------------------------------------------------- + +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/791541da69b9b3f434bb9ead43de406cc18b0373/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L537 +data BundleCategory + = BundleWithNoAssets + | BundleWithOneAsset AssetClass + | BundleWithTwoAssets AssetClass AssetClass + | BundleWithMultipleAssets (Set AssetClass) + +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/791541da69b9b3f434bb9ead43de406cc18b0373/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L546 +categorizeUtxoEntry :: TransactionOutput -> BundleCategory +categorizeUtxoEntry txOutput = case Set.toUnfoldable bundleAssets of + [] -> BundleWithNoAssets + [ a ] -> BundleWithOneAsset a + [ a, b ] -> BundleWithTwoAssets a b + _ -> BundleWithMultipleAssets bundleAssets + where + bundleAssets :: Set AssetClass + bundleAssets = txOutputAssetClasses txOutput + +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/791541da69b9b3f434bb9ead43de406cc18b0373/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L176 +newtype UtxoIndex = UtxoIndex + { indexAnyWith :: HashMap Asset UtxoMap + -- ^ An index of all utxos that contain the given asset. + , indexSingletons :: HashMap Asset UtxoMap + -- ^ An index of all utxos that contain the given asset and no other assets. + , indexPairs :: HashMap Asset UtxoMap + -- ^ An index of all utxos that contain the given asset and exactly one + -- other asset. + , utxos :: UtxoMap + -- ^ The complete set of all utxos. + } + +derive instance Newtype UtxoIndex _ + +_indexAnyWith :: Lens' UtxoIndex (HashMap Asset UtxoMap) +_indexAnyWith = _Newtype <<< prop (Proxy :: Proxy "indexAnyWith") + +_indexSingletons :: Lens' UtxoIndex (HashMap Asset UtxoMap) +_indexSingletons = _Newtype <<< prop (Proxy :: Proxy "indexSingletons") + +_indexPairs :: Lens' UtxoIndex (HashMap Asset UtxoMap) +_indexPairs = _Newtype <<< prop (Proxy :: Proxy "indexPairs") + +_utxos :: Lens' UtxoIndex UtxoMap +_utxos = _Newtype <<< prop (Proxy :: Proxy "utxos") + +buildUtxoIndex :: UtxoMap -> UtxoIndex +buildUtxoIndex utxos = + foldl (flip utxoIndexInsertEntry) emptyUtxoIndex utxos' + where + utxos' :: Array TxUnspentOutput + utxos' = Map.toUnfoldable utxos + + emptyUtxoIndex :: UtxoIndex + emptyUtxoIndex = UtxoIndex + { indexAnyWith: HashMap.empty + , indexSingletons: HashMap.empty + , indexPairs: HashMap.empty + , utxos: Map.empty + } + -- | Taken from cardano-wallet: --- | https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L418 +-- | https://github.com/input-output-hk/cardano-wallet/blob/791541da69b9b3f434bb9ead43de406cc18b0373/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L561 +utxoIndexInsertEntry :: TxUnspentOutput -> UtxoIndex -> UtxoIndex +utxoIndexInsertEntry (oref /\ out) = + (_utxos %~ Map.insert oref out) <<< updateUtxoIndex out insertEntry + where + insertEntry :: Asset -> HashMap Asset UtxoMap -> HashMap Asset UtxoMap + insertEntry = + HashMap.alter + (Just <<< maybe (Map.singleton oref out) (Map.insert oref out)) + +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/791541da69b9b3f434bb9ead43de406cc18b0373/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L295 +utxoIndexDeleteEntry :: TxUnspentOutput -> UtxoIndex -> UtxoIndex +utxoIndexDeleteEntry (inp /\ out) = + (_utxos %~ Map.delete inp) <<< updateUtxoIndex out deleteEntry + where + deleteEntry :: Asset -> HashMap Asset UtxoMap -> HashMap Asset UtxoMap + deleteEntry = HashMap.update (Just <<< Map.delete inp) + +updateUtxoIndex + :: TransactionOutput + -> (Asset -> HashMap Asset UtxoMap -> HashMap Asset UtxoMap) + -> UtxoIndex + -> UtxoIndex +updateUtxoIndex out manageEntry = + case categorizeUtxoEntry out of + BundleWithNoAssets -> + _indexSingletons %~ manageEntry AssetLovelace + BundleWithOneAsset asset -> + (_indexPairs %~ manageEntry AssetLovelace) + <<< (_indexSingletons %~ manageEntry (Asset asset)) + BundleWithTwoAssets asset0 asset1 -> + (_indexAnyWith %~ manageEntry AssetLovelace) + <<< (_indexPairs %~ manageEntry (Asset asset0)) + <<< (_indexPairs %~ manageEntry (Asset asset1)) + BundleWithMultipleAssets assets -> + (_indexAnyWith %~ flip (foldl (flip (manageEntry <<< Asset))) assets) + <<< (_indexAnyWith %~ manageEntry AssetLovelace) + +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/791541da69b9b3f434bb9ead43de406cc18b0373/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L418 selectRandomWithFilter - :: forall (m :: Type -> Type) (asset :: Type) + :: forall (m :: Type -> Type) . MonadEffect m - => ApplySelectionFilter asset - => UtxoMap - -> SelectionFilter asset - -> m (Maybe (TxUnspentOutput /\ UtxoMap)) -selectRandomWithFilter utxos filter = - selectRandomMapMember (applySelectionFilter utxos filter) - <#> map (\utxo@(oref /\ _) -> utxo /\ Map.delete oref utxos) + => UtxoIndex + -> SelectionFilter + -> m (Maybe (TxUnspentOutput /\ UtxoIndex)) +selectRandomWithFilter utxoIndex selectionFilter = + selectRandomMapMember selectionUtxoMap + <#> map (\utxo -> utxo /\ utxoIndexDeleteEntry utxo utxoIndex) + where + selectionUtxoMap :: UtxoMap + selectionUtxoMap = + case selectionFilter of + SelectSingleton asset -> + asset `lookupWith` _indexSingletons + SelectPairWith asset -> + asset `lookupWith` _indexPairs + SelectAnyWith asset -> + asset `lookupWith` _indexAnyWith + where + lookupWith :: Asset -> Lens' UtxoIndex (HashMap Asset UtxoMap) -> UtxoMap + lookupWith asset getter = + fromMaybe Map.empty $ HashMap.lookup asset (utxoIndex ^. getter) -------------------------------------------------------------------------------- -- Helpers diff --git a/src/Internal/Cardano/Types/Value.purs b/src/Internal/Cardano/Types/Value.purs index 9745dd1eb1..dbb7b5e247 100644 --- a/src/Internal/Cardano/Types/Value.purs +++ b/src/Internal/Cardano/Types/Value.purs @@ -106,6 +106,7 @@ import Data.Foldable (any, fold, foldl, length) import Data.FoldableWithIndex (foldrWithIndex) import Data.Function (on) import Data.Generic.Rep (class Generic) +import Data.Hashable (class Hashable, hash) import Data.Int (ceil) as Int import Data.Lattice (class JoinSemilattice, class MeetSemilattice, join, meet) import Data.List (List(Nil), all, (:)) @@ -223,6 +224,7 @@ newtype CurrencySymbol = CurrencySymbol ByteArray derive newtype instance Eq CurrencySymbol derive newtype instance FromData CurrencySymbol derive newtype instance FromMetadata CurrencySymbol +derive newtype instance Hashable CurrencySymbol derive newtype instance Ord CurrencySymbol derive newtype instance ToData CurrencySymbol derive newtype instance ToMetadata CurrencySymbol @@ -536,6 +538,9 @@ derive instance Ord AssetClass instance Show AssetClass where show = genericShow +instance Hashable AssetClass where + hash (AssetClass cs tn) = hash (cs /\ tn) + assetToValue :: AssetClass -> BigInt -> Value assetToValue (AssetClass cs tn) quantity = mkValue mempty (mkSingletonNonAdaAsset cs tn quantity) diff --git a/src/Internal/Types/ByteArray.purs b/src/Internal/Types/ByteArray.purs index 379626f69b..9996aa2519 100644 --- a/src/Internal/Types/ByteArray.purs +++ b/src/Internal/Types/ByteArray.purs @@ -19,10 +19,7 @@ import Prelude import Aeson ( class DecodeAeson , class EncodeAeson - , JsonDecodeError - ( TypeMismatch - , UnexpectedValue - ) + , JsonDecodeError(TypeMismatch, UnexpectedValue) , caseAesonString , encodeAeson' , toStringifiedNumbersJson @@ -30,6 +27,7 @@ import Aeson import Data.ArrayBuffer.Types (Uint8Array) import Data.Char (toCharCode) import Data.Either (Either(Left), note) +import Data.Hashable (class Hashable, hash) import Data.Maybe (Maybe(Just, Nothing)) import Data.Newtype (class Newtype) import Data.String.CodeUnits (toCharArray) @@ -56,6 +54,9 @@ instance Ord ByteArray where LT -> 1 GT -> -1 +instance Hashable ByteArray where + hash = hash <<< byteArrayToIntArray + instance Semigroup ByteArray where append = concat_ diff --git a/src/Internal/Types/CborBytes.purs b/src/Internal/Types/CborBytes.purs index 36137e7ffa..c816fd0259 100644 --- a/src/Internal/Types/CborBytes.purs +++ b/src/Internal/Types/CborBytes.purs @@ -22,6 +22,7 @@ import Ctl.Internal.Metadata.ToMetadata (class ToMetadata) import Ctl.Internal.Types.ByteArray (ByteArray) import Ctl.Internal.Types.ByteArray as ByteArray import Ctl.Internal.Types.RawBytes (RawBytes) +import Data.Hashable (class Hashable) import Data.Maybe (Maybe) import Data.Newtype (class Newtype, unwrap, wrap) import Test.QuickCheck.Arbitrary (class Arbitrary) @@ -37,6 +38,7 @@ derive instance Newtype CborBytes _ derive newtype instance Eq CborBytes derive newtype instance Ord CborBytes +derive newtype instance Hashable CborBytes derive newtype instance Semigroup CborBytes derive newtype instance Monoid CborBytes derive newtype instance EncodeAeson CborBytes diff --git a/src/Internal/Types/RawBytes.purs b/src/Internal/Types/RawBytes.purs index 9be49b1c37..dc0235fb4b 100644 --- a/src/Internal/Types/RawBytes.purs +++ b/src/Internal/Types/RawBytes.purs @@ -21,6 +21,7 @@ import Ctl.Internal.Metadata.FromMetadata (class FromMetadata) import Ctl.Internal.Metadata.ToMetadata (class ToMetadata) import Ctl.Internal.Types.ByteArray (ByteArray) import Ctl.Internal.Types.ByteArray as BytesArray +import Data.Hashable (class Hashable) import Data.Maybe (Maybe) import Data.Newtype (class Newtype, unwrap, wrap) import Test.QuickCheck.Arbitrary (class Arbitrary) @@ -35,6 +36,7 @@ derive instance Newtype RawBytes _ derive newtype instance Eq RawBytes derive newtype instance Ord RawBytes +derive newtype instance Hashable RawBytes derive newtype instance Semigroup RawBytes derive newtype instance Monoid RawBytes derive newtype instance EncodeAeson RawBytes diff --git a/src/Internal/Types/TokenName.purs b/src/Internal/Types/TokenName.purs index 40034a7a9f..c01cc9839c 100644 --- a/src/Internal/Types/TokenName.purs +++ b/src/Internal/Types/TokenName.purs @@ -30,6 +30,7 @@ import Data.ArrayBuffer.Types (Uint8Array) import Data.BigInt (BigInt) import Data.Bitraversable (ltraverse) import Data.Either (Either(Right, Left), either, note) +import Data.Hashable (class Hashable) import Data.Map (Map) import Data.Map (fromFoldable) as Map import Data.Maybe (Maybe(Nothing), fromJust) @@ -47,6 +48,7 @@ newtype TokenName = TokenName RawBytes derive newtype instance Eq TokenName derive newtype instance FromData TokenName derive newtype instance FromMetadata TokenName +derive newtype instance Hashable TokenName derive newtype instance ToMetadata TokenName derive newtype instance Ord TokenName derive newtype instance ToData TokenName From b5808e6b020ba83555cfd1c43c23a6708b78dd38 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Tue, 29 Nov 2022 19:46:49 +0000 Subject: [PATCH 028/373] WIP: Cleaning imports and tests --- src/Contract/Chain.purs | 2 - src/Contract/Monad.purs | 8 +- src/Contract/PlutusData.purs | 1 - src/Contract/Transaction.purs | 2 +- src/Internal/Contract.purs | 4 +- src/Internal/Contract/Monad.purs | 25 +++-- src/Internal/Contract/QueryBackend.purs | 18 +-- src/Internal/Contract/WaitUntilSlot.purs | 12 +- src/Internal/Contract/Wallet.purs | 8 +- src/Internal/Plutip/Server.purs | 12 +- src/Internal/Types/Interval.purs | 2 +- test/AffInterface.purs | 134 ----------------------- test/Integration.purs | 4 +- test/Plutip/Contract.purs | 4 +- test/QueryM/AffInterface.purs | 81 ++++++++++++++ 15 files changed, 122 insertions(+), 195 deletions(-) delete mode 100644 test/AffInterface.purs create mode 100644 test/QueryM/AffInterface.purs diff --git a/src/Contract/Chain.purs b/src/Contract/Chain.purs index e1f072d2b1..580d3626dd 100644 --- a/src/Contract/Chain.purs +++ b/src/Contract/Chain.purs @@ -8,8 +8,6 @@ module Contract.Chain , module Chain ) where -import Prelude - import Contract.Monad (Contract) import Ctl.Internal.Contract (getChainTip) as Contract import Ctl.Internal.Contract.WaitUntilSlot diff --git a/src/Contract/Monad.purs b/src/Contract/Monad.purs index e2032855d7..cbdcd8d683 100644 --- a/src/Contract/Monad.purs +++ b/src/Contract/Monad.purs @@ -17,7 +17,6 @@ module Contract.Monad import Prelude -import Ctl.Internal.Contract.Monad (Contract) import Ctl.Internal.Contract.Monad ( mkContractEnv , stopContractEnv @@ -45,10 +44,9 @@ import Effect.Aff (Aff) import Effect.Aff (Aff, launchAff_) as ExportAff import Effect.Aff.Class (liftAff) import Effect.Class (liftEffect) -import Effect (Effect) import Effect.Exception (throw) import Prim.TypeError (class Warn, Text) -import Ctl.Internal.Contract.Monad (ContractParams, ContractEnv) +import Ctl.Internal.Contract.Monad (ContractParams, ContractEnv, Contract) -- | Initializes a `Contract` environment. Does not ensure finalization. -- | Consider using `withContractEnv` if possible - otherwise use @@ -63,14 +61,14 @@ mkContractEnv mkContractEnv = Contract.mkContractEnv -- | Finalizes a `Contract` environment. --- | Closes the websockets in `ContractEnv`, effectively making it unusable. +-- | Closes the connections in `ContractEnv`, effectively making it unusable. stopContractEnv :: Warn ( Text "Using `stopContractEnv` is not recommended: users should rely on `withContractEnv` to finalize the runtime environment instead" ) => ContractEnv - -> Effect Unit + -> Aff Unit stopContractEnv = Contract.stopContractEnv -- | Same as `liftContractM` but the `Maybe` value is in the `Aff` context. diff --git a/src/Contract/PlutusData.purs b/src/Contract/PlutusData.purs index eb69349533..246d145f62 100644 --- a/src/Contract/PlutusData.purs +++ b/src/Contract/PlutusData.purs @@ -74,7 +74,6 @@ import Ctl.Internal.QueryM , defaultDatumCacheWsConfig , mkDatumCacheWebSocketAff ) as ExportQueryM -import Ctl.Internal.QueryM.Kupo (getDatumByHash, getDatumsByHashes) as Kupo import Ctl.Internal.Serialization (serializeData) as Serialization import Ctl.Internal.ToData ( class ToData diff --git a/src/Contract/Transaction.purs b/src/Contract/Transaction.purs index 0a486338ae..95c97d5200 100644 --- a/src/Contract/Transaction.purs +++ b/src/Contract/Transaction.purs @@ -300,7 +300,7 @@ submit tx = do submitE :: BalancedSignedTransaction -> Contract (Either (Array Aeson) TransactionHash) -submitE tx = -- TODO +submitE = -- TODO undefined -- | Calculate the minimum transaction fee. diff --git a/src/Internal/Contract.purs b/src/Internal/Contract.purs index a31ea57262..986a561ced 100644 --- a/src/Internal/Contract.purs +++ b/src/Internal/Contract.purs @@ -5,9 +5,11 @@ import Prelude import Control.Monad.Reader.Class (asks) import Ctl.Internal.Contract.Monad (Contract) import Ctl.Internal.Contract.QueryHandle (getQueryHandle) -import Effect.Aff.Class (liftAff) import Ctl.Internal.QueryM.Ogmios (ProtocolParameters) as Ogmios +import Ctl.Internal.Types.Chain (Tip) +import Effect.Aff.Class (liftAff) +getChainTip :: Contract Tip getChainTip = do queryHandle <- getQueryHandle liftAff $ queryHandle.getChainTip diff --git a/src/Internal/Contract/Monad.purs b/src/Internal/Contract/Monad.purs index 8dc5e8e576..d748b68a81 100644 --- a/src/Internal/Contract/Monad.purs +++ b/src/Internal/Contract/Monad.purs @@ -23,7 +23,7 @@ import Effect.Aff (Aff, ParAff, attempt, error, finally, supervise) import Ctl.Internal.JsWebSocket (_wsClose, _wsFinalize) import Ctl.Internal.QueryM (Hooks, Logger, QueryEnv, QueryM, WebSocket, getProtocolParametersAff, getSystemStartAff, getEraSummariesAff, mkDatumCacheWebSocketAff, mkLogger, mkOgmiosWebSocketAff, mkWalletBySpec, underlyingWebSocket) import Record.Builder (build, merge) -import Control.Parallel (class Parallel, parTraverse, parallel, sequential) +import Control.Parallel (class Parallel, parTraverse, parTraverse_, parallel, sequential) import Control.Monad.Error.Class ( class MonadError , class MonadThrow @@ -31,7 +31,7 @@ import Control.Monad.Error.Class ) import Control.Monad.Logger.Class (class MonadLogger) import Control.Monad.Reader.Class (class MonadAsk, class MonadReader, ask, asks) -import Control.Monad.Reader.Trans (ReaderT(ReaderT), runReaderT) +import Control.Monad.Reader.Trans (ReaderT, runReaderT) import Control.Monad.Rec.Class (class MonadRec) import Ctl.Internal.Contract.QueryBackend ( CtlBackend @@ -165,6 +165,9 @@ type ContractEnv = -- A reference point in which the slotLength is assumed to be constant from -- then until now, not including HFC which occur during contract evaluation -- TODO: Drop systemStart and just normalize time AOT + -- Maybe not drop it, we export it in Contract. I'm not sure why though + -- TODO: We need to indicate that calculations in the past may be inaccurate + -- Or enforce slot reference to be as 'relatively old' , slotReference :: { slot :: Slot, time :: Ogmios.RelativeTime } } } @@ -268,19 +271,18 @@ walletNetworkCheck envNetworkId wallet = do <> " is specified in the config." -- | Finalizes a `Contract` environment. --- | Closes the websockets in `ContractEnv`, effectively making it unusable. --- TODO Move to Aff? +-- | Closes the connections in `ContractEnv`, effectively making it unusable. stopContractEnv :: ContractEnv - -> Effect Unit + -> Aff Unit stopContractEnv contractEnv = do - for_ contractEnv.backend case _ of + flip parTraverse_ contractEnv.backend case _ of CtlBackend { ogmios, odc } -> do let stopWs :: forall (a :: Type). WebSocket a -> Effect Unit stopWs = ((*>) <$> _wsFinalize <*> _wsClose) <<< underlyingWebSocket - stopWs odc.ws - stopWs ogmios.ws + liftEffect $ stopWs odc.ws + liftEffect $ stopWs ogmios.ws BlockfrostBackend _ -> undefined -- | Constructs and finalizes a contract environment that is usable inside a @@ -304,7 +306,7 @@ withContractEnv params action = do for_ contractEnv.wallet $ walletNetworkCheck contractEnv.networkId eiRes <- attempt $ supervise (action contractEnv) - `flip finally` liftEffect (stopContractEnv contractEnv) + `flip finally` stopContractEnv contractEnv liftEffect $ case eiRes of Left err -> do for_ contractEnv.hooks.onError \f -> void $ try $ f err @@ -341,13 +343,14 @@ type ContractParams = -- QueryM -------------------------------------------------------------------------------- -wrapQueryM :: forall a. QueryM a -> Contract a +wrapQueryM :: forall (a :: Type). QueryM a -> Contract a wrapQueryM qm = do backend <- asks _.backend ctlBackend <- liftM (error "Operation only supported on CTL backend") $ lookupBackend CtlBackendLabel backend >>= case _ of CtlBackend b -> Just b _ -> Nothing - Contract $ ReaderT \contractEnv -> runQueryM contractEnv ctlBackend qm + contractEnv <- ask + liftAff $ runQueryM contractEnv ctlBackend qm runQueryM :: forall (a :: Type). ContractEnv -> CtlBackend -> QueryM a -> Aff a runQueryM contractEnv ctlBackend = diff --git a/src/Internal/Contract/QueryBackend.purs b/src/Internal/Contract/QueryBackend.purs index 09813e37c5..d034f25276 100644 --- a/src/Internal/Contract/QueryBackend.purs +++ b/src/Internal/Contract/QueryBackend.purs @@ -17,12 +17,12 @@ import Prelude import Ctl.Internal.QueryM (OgmiosWebSocket, DatumCacheWebSocket) import Ctl.Internal.QueryM.ServerConfig (ServerConfig) -import Data.Array (filter, nub) as Array +import Data.Array (nub) as Array import Data.Array ((:)) -import Data.Traversable -import Data.Foldable (foldl, length) +import Data.Traversable (class Traversable, traverse, sequence) +import Data.Foldable (class Foldable, foldl, foldr, foldMap, length) import Data.Map (Map) -import Data.Map (empty, insert, lookup, singleton) as Map +import Data.Map (empty, insert, lookup) as Map import Data.Maybe (Maybe(Just)) import Effect (Effect) import Effect.Exception (throw) @@ -58,17 +58,17 @@ mkBackendParams :: QueryBackendParams -> Array QueryBackendParams -> Effect (QueryBackends QueryBackendParams) -mkBackendParams defaultBackend backends = +mkBackendParams defaultBackend' backends = case length backends + 1 /= numUniqueBackends of true -> throw "mkBackendParams: multiple configs for the same service" false -> - pure $ QueryBackends defaultBackend $ + pure $ QueryBackends defaultBackend' $ foldl (\mp b -> Map.insert (backendLabel b) b mp) Map.empty backends where numUniqueBackends :: Int numUniqueBackends = - length $ Array.nub $ map backendLabel (defaultBackend : backends) + length $ Array.nub $ map backendLabel (defaultBackend' : backends) defaultBackend :: forall (backend :: Type). QueryBackends backend -> backend defaultBackend (QueryBackends backend _) = backend @@ -80,8 +80,8 @@ lookupBackend => QueryBackendLabel -> QueryBackends backend -> Maybe backend -lookupBackend key (QueryBackends defaultBackend backends) - | key == backendLabel defaultBackend = Just defaultBackend +lookupBackend key (QueryBackends defaultBackend' backends) + | key == backendLabel defaultBackend' = Just defaultBackend' | otherwise = Map.lookup key backends -------------------------------------------------------------------------------- diff --git a/src/Internal/Contract/WaitUntilSlot.purs b/src/Internal/Contract/WaitUntilSlot.purs index ac152efb8d..d922902038 100644 --- a/src/Internal/Contract/WaitUntilSlot.purs +++ b/src/Internal/Contract/WaitUntilSlot.purs @@ -11,22 +11,17 @@ import Ctl.Internal.Contract.Monad(Contract) import Control.Monad.Reader.Class (asks) import Contract.Log (logTrace') -import Ctl.Internal.Helpers (liftEither, liftM) --- import Ctl.Internal.QueryM.EraSummaries (getEraSummaries) -import Ctl.Internal.QueryM.Ogmios (EraSummaries, SystemStart, RelativeTime, SlotLength) --- import Ctl.Internal.QueryM.SystemStart (getSystemStart) +import Ctl.Internal.Helpers (liftM) +import Ctl.Internal.QueryM.Ogmios (SystemStart, RelativeTime, SlotLength) import Ctl.Internal.Serialization.Address (Slot(Slot)) import Ctl.Internal.Types.BigNum as BigNum import Ctl.Internal.Types.Chain as Chain import Ctl.Internal.Types.Interval ( POSIXTime(POSIXTime) - , findSlotEraSummary - , getSlotLength , slotToPosixTime ) import Ctl.Internal.Types.Natural (Natural) import Ctl.Internal.Types.Natural as Natural -import Data.Bifunctor (lmap) import Data.BigInt as BigInt import Data.DateTime.Instant (unInstant) import Data.Either (hush) @@ -49,9 +44,6 @@ waitUntilSlot futureSlot = | otherwise -> do { systemStart, slotLength, slotReference } <- asks _.ledgerConstants let slotLengthMs = unwrap slotLength * 1000.0 - -- slotLengthMs <- map getSlotLength $ liftEither - -- $ lmap (const $ error "Unable to get current Era summary") - -- $ findSlotEraSummary eraSummaries slot -- `timePadding` in slots -- If there are less than `slotPadding` slots remaining, start querying for chainTip -- repeatedly, because it's possible that at any given moment Ogmios suddenly diff --git a/src/Internal/Contract/Wallet.purs b/src/Internal/Contract/Wallet.purs index 9dbe51e7d4..f14a9a4e66 100644 --- a/src/Internal/Contract/Wallet.purs +++ b/src/Internal/Contract/Wallet.purs @@ -12,10 +12,8 @@ import Ctl.Internal.Cardano.Types.TransactionUnspentOutput ) import Ctl.Internal.Cardano.Types.Value (Value) import Ctl.Internal.Helpers as Helpers -import Ctl.Internal.Serialization.Address (Address) import Ctl.Internal.Types.UsedTxOuts (UsedTxOuts, isTxOutRefUsed) -import Ctl.Internal.Wallet (Wallet(Gero, Nami, Flint, Lode, Eternl, KeyWallet)) -import Data.Array (head) +import Data.Array (head, catMaybes) import Data.Array as Array import Data.Either (hush) import Data.Foldable (fold) @@ -28,7 +26,6 @@ import Data.UInt as UInt import Effect.Aff (Aff) import Effect.Aff.Class (liftAff) import Effect.Class (liftEffect) -import Effect.Exception (throw) import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.Helpers (liftM, liftedM) import Ctl.Internal.Serialization.Address @@ -48,14 +45,11 @@ import Ctl.Internal.Types.RawBytes (RawBytes) import Ctl.Internal.Wallet ( Cip30Connection , Cip30Wallet - , KeyWallet , Wallet(KeyWallet, Lode, Flint, Gero, Nami, Eternl) ) import Ctl.Internal.Wallet (getChangeAddress, getRewardAddresses, getUnusedAddresses, getWalletAddresses, signData) as Aff import Ctl.Internal.Wallet.Cip30 (DataSignature) -import Data.Array (catMaybes) import Effect.Exception (error, throw) -import Data.Traversable (for_, traverse) getUnusedAddresses :: Contract (Array Address) getUnusedAddresses = withWalletAff Aff.getUnusedAddresses diff --git a/src/Internal/Plutip/Server.purs b/src/Internal/Plutip/Server.purs index ac33c6a76a..36c4464c0f 100644 --- a/src/Internal/Plutip/Server.purs +++ b/src/Internal/Plutip/Server.purs @@ -22,8 +22,7 @@ import Affjax.ResponseFormat as Affjax.ResponseFormat import Contract.Address (NetworkId(MainnetId)) import Contract.Config (QueryBackendParams(CtlBackendParams)) import Ctl.Internal.Contract.QueryBackend (defaultBackend, mkSingletonBackendParams) -import Ctl.Internal.Contract.Monad (buildBackend, getLedgerConstants) -import Ctl.Internal.Contract.Monad (stopContractEnv) as Contract +import Ctl.Internal.Contract.Monad (buildBackend, getLedgerConstants, stopContractEnv) import Contract.Monad ( Contract , ContractEnv @@ -92,7 +91,6 @@ import Data.Tuple (fst, snd) import Data.Tuple.Nested (type (/\), (/\)) import Data.UInt (UInt) import Data.UInt as UInt -import Effect (Effect) import Effect.Aff (Aff, Milliseconds(Milliseconds), try) import Effect.Aff (bracket) as Aff import Effect.Aff.Class (liftAff) @@ -410,7 +408,7 @@ startPlutipContractEnv plutipCfg distr cleanupRef = do configLogger = Just $ map liftEffect <<< addLogEntry bracket (mkClusterContractEnv plutipCfg suppressedLogger configLogger) - (liftEffect <<< stopContractEnv) + stopContractEnv \env -> pure { env , printLogs: liftEffect printLogs @@ -423,17 +421,13 @@ startPlutipContractEnv plutipCfg distr cleanupRef = do (mkLogger plutipCfg.logLevel plutipCfg.customLogger) plutipCfg.customLogger ) - (liftEffect <<< stopContractEnv) + stopContractEnv \env -> pure { env , printLogs: pure unit , clearLogs: pure unit } - -- a version of Contract.Monad.stopContractEnv without a compile-time warning - stopContractEnv :: ContractEnv -> Effect Unit - stopContractEnv env = Contract.stopContractEnv env - -- | Throw an exception if `PlutipConfig` contains ports that are occupied. configCheck :: PlutipConfig -> Aff Unit configCheck cfg = do diff --git a/src/Internal/Types/Interval.purs b/src/Internal/Types/Interval.purs index 7c7a966cf4..f16b7022e1 100644 --- a/src/Internal/Types/Interval.purs +++ b/src/Internal/Types/Interval.purs @@ -1018,7 +1018,7 @@ slotFromRelSlot :: Slot -> RelSlot /\ ModTime -> Either PosixTimeToSlotError Slot slotFromRelSlot start -- (EraSummary { start, end }) - (RelSlot relSlot /\ mt@(ModTime modTime)) = do + (RelSlot relSlot /\ _) = do let startSlot = BigNum.toBigIntUnsafe $ unwrap start -- Round down to the nearest Slot to accept Milliseconds as input. diff --git a/test/AffInterface.purs b/test/AffInterface.purs deleted file mode 100644 index 35df2e8aa3..0000000000 --- a/test/AffInterface.purs +++ /dev/null @@ -1,134 +0,0 @@ -module Test.Ctl.AffInterface (suite) where - -import Prelude - -import Contract.Chain (ChainTip(ChainTip), Tip(Tip, TipAtGenesis)) -import Control.Monad.Except (throwError) -import Ctl.Internal.Address (ogmiosAddressToAddress) -import Ctl.Internal.QueryM - ( QueryM - , getChainTip --- , getDatumByHash --- , getDatumsByHashes --- , getDatumsByHashesWithErrors - , submitTxOgmios - ) -import Ctl.Internal.QueryM.CurrentEpoch (getCurrentEpoch) -import Ctl.Internal.QueryM.EraSummaries (getEraSummaries) -import Ctl.Internal.QueryM.GetTxByHash (getTxByHash) -import Ctl.Internal.QueryM.Ogmios (OgmiosAddress) --- import Ctl.Internal.QueryM.SystemStart (getSystemStart) --- import Ctl.Internal.QueryM.Utxos (utxosAt) -import Ctl.Internal.Contract.WaitUntilSlot (waitUntilSlot) -import Ctl.Internal.Serialization.Address (Slot(Slot)) -import Ctl.Internal.Test.TestPlanM (TestPlanM) -import Ctl.Internal.Types.BigNum (add, fromInt) as BigNum -import Ctl.Internal.Types.ByteArray (hexToByteArrayUnsafe) -import Ctl.Internal.Types.Transaction (DataHash(DataHash)) -import Data.Either (Either(Left, Right)) -import Data.Maybe (Maybe(Just, Nothing), fromMaybe, isJust) -import Data.Newtype (over, wrap) -import Data.String.CodeUnits (indexOf) -import Data.String.Pattern (Pattern(Pattern)) -import Effect.Aff (error, try) -import Mote (group, test) -import Test.Spec.Assertions (shouldSatisfy) - -testnet_addr1 :: OgmiosAddress -testnet_addr1 = - "addr_test1qr7g8nrv76fc7k4ueqwecljxx9jfwvsgawhl55hck3n8uwaz26mpcwu58zdkhpdnc6nuq3fa8vylc8ak9qvns7r2dsysp7ll4d" - -addr1 :: OgmiosAddress -addr1 = - "addr1qyc0kwu98x23ufhsxjgs5k3h7gktn8v5682qna5amwh2juguztcrc8hjay66es67ctn0jmr9plfmlw37je2s2px4xdssgvxerq" - --- note: currently this suite relies on Ogmios being open and running against the --- testnet, and does not directly test outputs, as this suite is intended to --- help verify that the Aff interface for websockets itself works, --- not that the data represents expected values, as that would depend on chain --- state, and ogmios itself. -suite :: TestPlanM (QueryM Unit) Unit -suite = do - pure unit --- --- group "Aff Interface" do --- test "UtxosAt Testnet" $ testUtxosAt testnet_addr1 --- test "UtxosAt Mainnet" $ testUtxosAt addr1 --- test "Get ChainTip" testGetChainTip --- test "Get waitUntilSlot" testWaitUntilSlot --- test "Get EraSummaries" testGetEraSummaries --- test "Get CurrentEpoch" testGetCurrentEpoch --- test "Get SystemStart" testGetSystemStart --- group "Ogmios error" do --- test "Ogmios fails with user-friendly message" do --- try testSubmitTxFailure >>= case _ of --- Right _ -> do --- void $ throwError $ error $ --- "Unexpected success in testSubmitTxFailure" --- Left error -> do --- (Pattern "Server responded with `fault`" `indexOf` show error) --- `shouldSatisfy` isJust --- group "Ogmios datum cache" do --- test "Can process GetDatumByHash" do --- testOgmiosDatumCacheGetDatumByHash --- test "Can process GetDatumsByHashes" do --- testOgmiosDatumCacheGetDatumsByHashes --- test "Can process GetDatumsByHashesWithErrors" do --- testOgmiosDatumCacheGetDatumsByHashesWithErrors --- test "Can process GetTxByHash" do --- testOgmiosGetTxByHash --- --- testOgmiosDatumCacheGetDatumByHash :: QueryM Unit --- testOgmiosDatumCacheGetDatumByHash = do --- void $ getDatumByHash $ DataHash $ hexToByteArrayUnsafe --- "f7c47c65216f7057569111d962a74de807de57e79f7efa86b4e454d42c875e4e" --- --- testOgmiosDatumCacheGetDatumsByHashes :: QueryM Unit --- testOgmiosDatumCacheGetDatumsByHashes = do --- void $ getDatumsByHashes $ pure $ DataHash $ hexToByteArrayUnsafe --- "f7c47c65216f7057569111d962a74de807de57e79f7efa86b4e454d42c875e4e" --- --- testOgmiosDatumCacheGetDatumsByHashesWithErrors :: QueryM Unit --- testOgmiosDatumCacheGetDatumsByHashesWithErrors = do --- void $ getDatumsByHashesWithErrors $ pure $ DataHash $ hexToByteArrayUnsafe --- "f7c47c65216f7057569111d962a74de807de57e79f7efa86b4e454d42c875e4e" --- --- testOgmiosGetTxByHash :: QueryM Unit --- testOgmiosGetTxByHash = do --- void $ getTxByHash $ hexToByteArrayUnsafe --- "f7c47c65216f7057569111d962a74de807de57e79f7efa86b4e454d42c875e4e" --- --- testUtxosAt :: OgmiosAddress -> QueryM Unit --- testUtxosAt testAddr = case ogmiosAddressToAddress testAddr of --- Nothing -> throwError (error "Failed UtxosAt") --- Just addr -> void $ utxosAt addr --- --- testGetChainTip :: QueryM Unit --- testGetChainTip = do --- void getChainTip --- --- testWaitUntilSlot :: QueryM Unit --- testWaitUntilSlot = do --- void $ getChainTip >>= case _ of --- TipAtGenesis -> throwError $ error "Tip is at genesis" --- Tip (ChainTip { slot }) -> do --- waitUntilSlot $ over Slot --- (fromMaybe (BigNum.fromInt 0) <<< BigNum.add (BigNum.fromInt 10)) --- slot --- --- testGetEraSummaries :: QueryM Unit --- testGetEraSummaries = do --- void getEraSummaries --- --- testSubmitTxFailure :: QueryM Unit --- testSubmitTxFailure = do --- let bytes = hexToByteArrayUnsafe "00" --- void $ submitTxOgmios bytes (wrap bytes) --- --- testGetCurrentEpoch :: QueryM Unit --- testGetCurrentEpoch = do --- void getCurrentEpoch --- --- testGetSystemStart :: QueryM Unit --- testGetSystemStart = do --- void getSystemStart diff --git a/test/Integration.purs b/test/Integration.purs index 29c8550131..763319fb42 100644 --- a/test/Integration.purs +++ b/test/Integration.purs @@ -12,7 +12,7 @@ import Effect.Aff (Aff, launchAff_) import Effect.Class (liftEffect) import Mote (skip) import Mote.Monad (mapTest) -import Test.Ctl.AffInterface as AffInterface +import Test.Ctl.QueryM.AffInterface as QueryM.AffInterface import Test.Ctl.BalanceTx.Collateral as Collateral import Test.Ctl.BalanceTx.Time as BalanceTx.Time import Test.Ctl.Logging as Logging @@ -27,7 +27,7 @@ main = launchAff_ do -- Requires external services listed in README.md testPlan :: TestPlanM (Aff Unit) Unit testPlan = do - mapTest runQueryM' AffInterface.suite + mapTest runQueryM' QueryM.AffInterface.suite -- These tests depend on assumptions about testnet history. -- We disabled them during transition from `testnet` to `preprod` networks. -- https://github.com/Plutonomicon/cardano-transaction-lib/issues/945 diff --git a/test/Plutip/Contract.purs b/test/Plutip/Contract.purs index dd7722e47e..500fe33949 100644 --- a/test/Plutip/Contract.purs +++ b/test/Plutip/Contract.purs @@ -138,7 +138,7 @@ import Effect.Exception (error, throw) import Mote (group, skip, test) import Mote.Monad (mapTest) import Safe.Coerce (coerce) -import Test.Ctl.AffInterface as AffInterface +import Test.Ctl.QueryM.AffInterface as QueryM.AffInterface import Test.Ctl.Fixtures ( cip25MetadataFixture1 , fullyAppliedScriptFixture @@ -161,7 +161,7 @@ import Test.Spec.Assertions (shouldEqual, shouldNotEqual, shouldSatisfy) suite :: TestPlanM PlutipTest Unit suite = do group "Contract" do - flip mapTest AffInterface.suite + flip mapTest QueryM.AffInterface.suite (noWallet <<< wrapQueryM) NetworkId.suite diff --git a/test/QueryM/AffInterface.purs b/test/QueryM/AffInterface.purs new file mode 100644 index 0000000000..3d9e6d4330 --- /dev/null +++ b/test/QueryM/AffInterface.purs @@ -0,0 +1,81 @@ +module Test.Ctl.QueryM.AffInterface (suite) where + +import Prelude + +import Control.Monad.Except (throwError) +import Ctl.Internal.QueryM + ( QueryM + , getChainTip + , submitTxOgmios + ) +import Ctl.Internal.QueryM.CurrentEpoch (getCurrentEpoch) +import Ctl.Internal.QueryM.EraSummaries (getEraSummaries) +import Ctl.Internal.QueryM.GetTxByHash (getTxByHash) +import Ctl.Internal.Test.TestPlanM (TestPlanM) +import Ctl.Internal.Types.ByteArray (hexToByteArrayUnsafe) +import Data.Either (Either(Left, Right)) +import Data.Maybe (isJust) +import Data.Newtype (wrap) +import Data.String.CodeUnits (indexOf) +import Data.String.Pattern (Pattern(Pattern)) +import Effect.Aff (error, try) +import Mote (group, test) +import Test.Spec.Assertions (shouldSatisfy) + +-- note: currently this suite relies on Ogmios being open and running against the +-- testnet, and does not directly test outputs, as this suite is intended to +-- help verify that the Aff interface for websockets itself works, +-- not that the data represents expected values, as that would depend on chain +-- state, and ogmios itself. +suite :: TestPlanM (QueryM Unit) Unit +suite = do + group "QueryM" do + group "Aff Interface" do + test "Get ChainTip" testGetChainTip + test "Get CurrentEpoch" testGetCurrentEpoch + test "Get EraSummaries" testGetEraSummaries + group "Ogmios error" do + test "Ogmios fails with user-friendly message" do + try testSubmitTxFailure >>= case _ of + Right _ -> do + void $ throwError $ error $ + "Unexpected success in testSubmitTxFailure" + Left error -> do + (Pattern "Server responded with `fault`" `indexOf` show error) + `shouldSatisfy` isJust + group "Ogmios datum cache" do + test "Can process GetTxByHash" do + testOgmiosGetTxByHash + +testOgmiosGetTxByHash :: QueryM Unit +testOgmiosGetTxByHash = do + void $ getTxByHash $ hexToByteArrayUnsafe + "f7c47c65216f7057569111d962a74de807de57e79f7efa86b4e454d42c875e4e" + +testGetChainTip :: QueryM Unit +testGetChainTip = do + void getChainTip + +-- TODO Move this. Or put it in contract tests (maybe it already is) +-- testWaitUntilSlot :: QueryM Unit +-- testWaitUntilSlot = do +-- void $ getChainTip >>= case _ of +-- TipAtGenesis -> throwError $ error "Tip is at genesis" +-- Tip (ChainTip { slot }) -> do +-- waitUntilSlot $ over Slot +-- (fromMaybe (BigNum.fromInt 0) <<< BigNum.add (BigNum.fromInt 10)) +-- slot + +-- Remove eraSummaries from queryM? +testGetEraSummaries :: QueryM Unit +testGetEraSummaries = do + void getEraSummaries + +testSubmitTxFailure :: QueryM Unit +testSubmitTxFailure = do + let bytes = hexToByteArrayUnsafe "00" + void $ submitTxOgmios bytes (wrap bytes) + +testGetCurrentEpoch :: QueryM Unit +testGetCurrentEpoch = do + void getCurrentEpoch From 277eee0ad55139419c7b45fe9e5da72414631353 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Tue, 29 Nov 2022 19:49:28 +0000 Subject: [PATCH 029/373] Formatting --- src/Contract/Address.purs | 14 +- src/Contract/Config.purs | 13 +- src/Contract/Monad.purs | 10 +- src/Contract/Scripts.purs | 2 +- src/Contract/Staking.purs | 2 +- src/Contract/Time.purs | 14 +- src/Contract/Transaction.purs | 21 +-- src/Contract/Utxos.purs | 4 +- src/Contract/Wallet.purs | 2 +- src/Contract/Wallet/KeyFile.purs | 2 +- src/Internal/BalanceTx/BalanceTx.purs | 19 ++- src/Internal/BalanceTx/ExUnitsAndMinFee.purs | 9 +- src/Internal/BalanceTx/Types.purs | 5 +- src/Internal/Contract/ApplyArgs.purs | 9 +- src/Internal/Contract/AwaitTxConfirmed.purs | 2 +- src/Internal/Contract/MinFee.purs | 11 +- src/Internal/Contract/Monad.purs | 169 ++++++++++++------- src/Internal/Contract/QueryBackend.purs | 18 +- src/Internal/Contract/QueryHandle.purs | 34 ++-- src/Internal/Contract/Sign.purs | 33 ++-- src/Internal/Contract/WaitUntilSlot.purs | 37 ++-- src/Internal/Contract/Wallet.purs | 44 ++--- src/Internal/Plutip/Server.purs | 11 +- src/Internal/Plutip/UtxoDistribution.purs | 4 +- src/Internal/ReindexRedeemers.purs | 2 +- src/Internal/Test/E2E/Route.purs | 17 +- src/Internal/Test/E2E/Runner.purs | 5 +- src/Internal/Types/Interval.purs | 95 ++++++----- src/Internal/Types/ScriptLookups.purs | 36 ++-- src/Internal/Types/TypedTxOut.purs | 9 +- src/Internal/Wallet.purs | 48 +++--- src/Internal/Wallet/Cip30Mock.purs | 13 +- src/Internal/Wallet/Key.purs | 16 +- test/BalanceTx/Time.purs | 6 +- test/Integration.purs | 9 +- test/Ogmios/GenerateFixtures.purs | 4 +- test/Plutip/Contract.purs | 6 +- test/Types/Interval.purs | 66 +++++--- 38 files changed, 476 insertions(+), 345 deletions(-) diff --git a/src/Contract/Address.purs b/src/Contract/Address.purs index c275f6e48e..1a46e92dd3 100644 --- a/src/Contract/Address.purs +++ b/src/Contract/Address.purs @@ -45,6 +45,13 @@ import Ctl.Internal.Address ( addressPaymentValidatorHash , addressStakeValidatorHash ) as Address +import Ctl.Internal.Contract.Wallet + ( getNetworkId + , getWalletAddresses + , getWalletCollateral + , ownPaymentPubKeyHashes + , ownStakePubKeysHashes + ) as Contract import Ctl.Internal.Plutus.Conversion ( fromPlutusAddress , fromPlutusAddressWithNetworkTag @@ -68,13 +75,6 @@ import Ctl.Internal.Plutus.Types.Address import Ctl.Internal.Plutus.Types.TransactionUnspentOutput ( TransactionUnspentOutput ) -import Ctl.Internal.Contract.Wallet - ( getNetworkId - , getWalletAddresses - , ownPaymentPubKeyHashes - , ownStakePubKeysHashes - , getWalletCollateral - ) as Contract import Ctl.Internal.Scripts ( typedValidatorBaseAddress , typedValidatorEnterpriseAddress diff --git a/src/Contract/Config.purs b/src/Contract/Config.purs index ab0ecfefb0..94fe255646 100644 --- a/src/Contract/Config.purs +++ b/src/Contract/Config.purs @@ -28,7 +28,10 @@ import Prelude import Contract.Address (NetworkId(MainnetId, TestnetId)) import Ctl.Internal.Contract.Monad (ContractParams) -import Ctl.Internal.Contract.QueryBackend (QueryBackendParams(CtlBackendParams, BlockfrostBackendParams), mkSingletonBackendParams) +import Ctl.Internal.Contract.QueryBackend + ( QueryBackendParams(CtlBackendParams, BlockfrostBackendParams) + , mkSingletonBackendParams + ) import Ctl.Internal.Deserialization.Keys (privateKeyFromBytes) import Ctl.Internal.QueryM (emptyHooks) import Ctl.Internal.QueryM (emptyHooks) as X @@ -63,10 +66,10 @@ import Data.Maybe (Maybe(Just, Nothing)) testnetConfig :: ContractParams testnetConfig = { backendParams: mkSingletonBackendParams $ CtlBackendParams - { ogmiosConfig: defaultOgmiosWsConfig - , odcConfig: defaultDatumCacheWsConfig - , kupoConfig: defaultKupoServerConfig - } + { ogmiosConfig: defaultOgmiosWsConfig + , odcConfig: defaultDatumCacheWsConfig + , kupoConfig: defaultKupoServerConfig + } , ctlServerConfig: Just defaultServerConfig , networkId: TestnetId , walletSpec: Nothing diff --git a/src/Contract/Monad.purs b/src/Contract/Monad.purs index cbdcd8d683..daf702b4d0 100644 --- a/src/Contract/Monad.purs +++ b/src/Contract/Monad.purs @@ -17,10 +17,7 @@ module Contract.Monad import Prelude -import Ctl.Internal.Contract.Monad - ( mkContractEnv - , stopContractEnv - ) as Contract +import Ctl.Internal.Contract.Monad (Contract, ContractEnv, ContractParams) import Ctl.Internal.Contract.Monad ( Contract(Contract) , ContractEnv @@ -29,6 +26,10 @@ import Ctl.Internal.Contract.Monad , runContractInEnv , withContractEnv ) as ExportContract +import Ctl.Internal.Contract.Monad + ( mkContractEnv + , stopContractEnv + ) as Contract import Data.Either (Either, either, hush) import Data.Log.Tag ( TagSet @@ -46,7 +47,6 @@ import Effect.Aff.Class (liftAff) import Effect.Class (liftEffect) import Effect.Exception (throw) import Prim.TypeError (class Warn, Text) -import Ctl.Internal.Contract.Monad (ContractParams, ContractEnv, Contract) -- | Initializes a `Contract` environment. Does not ensure finalization. -- | Consider using `withContractEnv` if possible - otherwise use diff --git a/src/Contract/Scripts.purs b/src/Contract/Scripts.purs index b4558b3bb7..fb1f6cae39 100644 --- a/src/Contract/Scripts.purs +++ b/src/Contract/Scripts.purs @@ -26,6 +26,7 @@ import Ctl.Internal.Cardano.Types.NativeScript , TimelockExpiry ) ) as NativeScript +import Ctl.Internal.Contract.ApplyArgs (applyArgs) as Contract import Ctl.Internal.NativeScripts (NativeScriptHash(NativeScriptHash)) as X import Ctl.Internal.QueryM ( ClientError @@ -34,7 +35,6 @@ import Ctl.Internal.QueryM , ClientEncodingError ) ) as ExportQueryM -import Ctl.Internal.Contract.ApplyArgs (applyArgs) as Contract import Ctl.Internal.Scripts ( mintingPolicyHash , nativeScriptStakeValidatorHash diff --git a/src/Contract/Staking.purs b/src/Contract/Staking.purs index 8dacdb8e4e..b253213c86 100644 --- a/src/Contract/Staking.purs +++ b/src/Contract/Staking.purs @@ -7,12 +7,12 @@ module Contract.Staking import Prelude -import Ctl.Internal.Contract.Monad (wrapQueryM) import Contract.Monad (Contract) import Ctl.Internal.Cardano.Types.Transaction ( PoolPubKeyHash , PoolRegistrationParams ) +import Ctl.Internal.Contract.Monad (wrapQueryM) import Ctl.Internal.QueryM.Pools (DelegationsAndRewards) import Ctl.Internal.QueryM.Pools as QueryM import Ctl.Internal.Types.PubKeyHash (StakePubKeyHash) diff --git a/src/Contract/Time.purs b/src/Contract/Time.purs index 6d978614ad..8fb8b87a64 100644 --- a/src/Contract/Time.purs +++ b/src/Contract/Time.purs @@ -13,10 +13,6 @@ module Contract.Time import Prelude -import Effect.Aff.Class (liftAff) -import Ctl.Internal.Contract.QueryHandle (getQueryHandle) -import Control.Monad.Reader.Class (asks) -import Ctl.Internal.Contract.Monad (wrapQueryM) import Contract.Chain ( BlockHeaderHash(BlockHeaderHash) , ChainTip(ChainTip) @@ -24,7 +20,10 @@ import Contract.Chain , getTip ) as Chain import Contract.Monad (Contract) +import Control.Monad.Reader.Class (asks) import Ctl.Internal.Cardano.Types.Transaction (Epoch(Epoch)) +import Ctl.Internal.Contract.Monad (wrapQueryM) +import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.Helpers (liftM) import Ctl.Internal.QueryM.EraSummaries (getEraSummaries) as EraSummaries import Ctl.Internal.QueryM.Ogmios @@ -41,12 +40,12 @@ import Ctl.Internal.QueryM.Ogmios import Ctl.Internal.QueryM.Ogmios ( CurrentEpoch(CurrentEpoch) , EraSummaries - , SystemStart - , SlotLength , RelativeTime + , SlotLength + , SystemStart ) -import Ctl.Internal.Serialization.Address (Slot) import Ctl.Internal.Serialization.Address (BlockId(BlockId), Slot(Slot)) as SerializationAddress +import Ctl.Internal.Serialization.Address (Slot) import Ctl.Internal.Types.Interval ( AbsTime(AbsTime) , Closure @@ -104,6 +103,7 @@ import Ctl.Internal.Types.Interval ) as Interval import Data.BigInt as BigInt import Data.UInt as UInt +import Effect.Aff.Class (liftAff) import Effect.Exception (error) -- | Get the current Epoch. diff --git a/src/Contract/Transaction.purs b/src/Contract/Transaction.purs index 95c97d5200..5b8a1c0beb 100644 --- a/src/Contract/Transaction.purs +++ b/src/Contract/Transaction.purs @@ -40,9 +40,7 @@ module Contract.Transaction import Prelude -import Contract.Prelude (undefined) import Aeson (class EncodeAeson, Aeson) -import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Contract.Monad ( Contract , liftContractM @@ -50,6 +48,7 @@ import Contract.Monad , liftedM , runContractInEnv ) +import Contract.Prelude (undefined) import Control.Monad.Error.Class (catchError, throwError) import Control.Monad.Reader (ReaderT, asks, runReaderT) import Control.Monad.Reader.Class (ask) @@ -144,6 +143,14 @@ import Ctl.Internal.Cardano.Types.Transaction , _body , _outputs ) +import Ctl.Internal.Contract.AwaitTxConfirmed + ( awaitTxConfirmed + , awaitTxConfirmedWithTimeout + , awaitTxConfirmedWithTimeoutSlots + ) as Contract +import Ctl.Internal.Contract.MinFee (calculateMinFee) as Contract +import Ctl.Internal.Contract.QueryHandle (getQueryHandle) +import Ctl.Internal.Contract.Sign (signTransaction) as Contract import Ctl.Internal.Hashing (transactionHash) as Hashing import Ctl.Internal.Plutus.Conversion ( fromPlutusUtxoMap @@ -172,13 +179,6 @@ import Ctl.Internal.QueryM , ClientOtherError ) ) as ExportQueryM -import Ctl.Internal.Contract.AwaitTxConfirmed - ( awaitTxConfirmed - , awaitTxConfirmedWithTimeout - , awaitTxConfirmedWithTimeoutSlots - ) as Contract -import Ctl.Internal.Contract.MinFee (calculateMinFee) as Contract -import Ctl.Internal.Contract.Sign (signTransaction) as Contract import Ctl.Internal.ReindexRedeemers ( ReindexErrors(CannotGetTxOutRefIndexForRedeemer) ) as ReindexRedeemersExport @@ -518,7 +518,8 @@ awaitTxConfirmedWithTimeout :: Seconds -> TransactionHash -> Contract Unit -awaitTxConfirmedWithTimeout timeout = Contract.awaitTxConfirmedWithTimeout timeout <<< unwrap +awaitTxConfirmedWithTimeout timeout = + Contract.awaitTxConfirmedWithTimeout timeout <<< unwrap -- | Same as `awaitTxConfirmed`, but allows to specify a timeout in slots for waiting. -- | Throws an exception on timeout. diff --git a/src/Contract/Utxos.purs b/src/Contract/Utxos.purs index 47a7427b75..ef6741150e 100644 --- a/src/Contract/Utxos.purs +++ b/src/Contract/Utxos.purs @@ -16,7 +16,7 @@ import Contract.Prelude (for) import Contract.Transaction (TransactionInput, TransactionOutput) import Control.Monad.Reader.Class (asks) import Ctl.Internal.Contract.QueryHandle (getQueryHandle) -import Effect.Aff.Class (liftAff) +import Ctl.Internal.Contract.Wallet (getWalletBalance, getWalletUtxos) as Utxos import Ctl.Internal.Plutus.Conversion ( fromPlutusAddress , toPlutusTxOutput @@ -27,8 +27,8 @@ import Ctl.Internal.Plutus.Types.Address (class PlutusAddress, getAddress) import Ctl.Internal.Plutus.Types.Transaction (UtxoMap) import Ctl.Internal.Plutus.Types.Transaction (UtxoMap) as X import Ctl.Internal.Plutus.Types.Value (Value) -import Ctl.Internal.Contract.Wallet (getWalletBalance, getWalletUtxos) as Utxos import Data.Maybe (Maybe) +import Effect.Aff.Class (liftAff) -- | Queries for utxos at the given Plutus `Address`. utxosAt diff --git a/src/Contract/Wallet.purs b/src/Contract/Wallet.purs index aa0d23f51b..f39cc02684 100644 --- a/src/Contract/Wallet.purs +++ b/src/Contract/Wallet.purs @@ -24,7 +24,6 @@ import Contract.Monad (Contract) import Contract.Utxos (getWalletUtxos) as Contract.Utxos import Control.Monad.Reader (local) import Control.Monad.Reader.Class (asks) -import Ctl.Internal.Deserialization.Keys (privateKeyFromBytes) as Deserialization.Keys import Ctl.Internal.Contract.Wallet ( getChangeAddress , getRewardAddresses @@ -32,6 +31,7 @@ import Ctl.Internal.Contract.Wallet , getWallet , signData ) as Contract +import Ctl.Internal.Deserialization.Keys (privateKeyFromBytes) as Deserialization.Keys import Ctl.Internal.Serialization.Address (Address, NetworkId) import Ctl.Internal.Types.RawBytes (RawBytes) import Ctl.Internal.Wallet diff --git a/src/Contract/Wallet/KeyFile.purs b/src/Contract/Wallet/KeyFile.purs index 9920409e5a..6eb4aafadc 100644 --- a/src/Contract/Wallet/KeyFile.purs +++ b/src/Contract/Wallet/KeyFile.purs @@ -7,7 +7,6 @@ module Contract.Wallet.KeyFile import Prelude import Control.Monad.Reader.Class (asks) -import Effect.Aff.Class (liftAff) import Ctl.Internal.Contract.Monad (Contract) import Ctl.Internal.Wallet.Key (KeyWallet) as Wallet import Ctl.Internal.Wallet.Key (privateKeysToKeyWallet) @@ -21,6 +20,7 @@ import Ctl.Internal.Wallet.KeyFile ) import Data.Maybe (Maybe) import Data.Traversable (traverse) +import Effect.Aff.Class (liftAff) import Node.Path (FilePath) -- | Load `PrivateKey`s from `skey` files (the files should be in JSON format as diff --git a/src/Internal/BalanceTx/BalanceTx.purs b/src/Internal/BalanceTx/BalanceTx.purs index bf67c6db1d..5644291feb 100644 --- a/src/Internal/BalanceTx/BalanceTx.purs +++ b/src/Internal/BalanceTx/BalanceTx.purs @@ -11,8 +11,6 @@ import Control.Monad.Except.Trans (ExceptT(ExceptT), except, runExceptT) import Control.Monad.Logger.Class (class MonadLogger) import Control.Monad.Logger.Class as Logger import Control.Monad.Reader.Class (asks) -import Effect.Aff.Class (liftAff) -import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.BalanceTx.Collateral ( addTxCollateral , addTxCollateralReturn @@ -71,8 +69,8 @@ import Ctl.Internal.BalanceTx.Types , askCoinsPerUtxoUnit , askNetworkId , asksConstraints - , liftEitherContract , liftContract + , liftEitherContract , withBalanceTxConstraints ) import Ctl.Internal.BalanceTx.Types (FinalizedTransaction(FinalizedTransaction)) as FinalizedTransaction @@ -106,11 +104,12 @@ import Ctl.Internal.Cardano.Types.Value , valueToCoin' ) import Ctl.Internal.Contract.Monad (Contract) -import Ctl.Internal.Contract.Wallet (getChangeAddress, getWalletAddresses) as Contract +import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.Contract.Wallet - ( getWalletCollateral - , filterLockedUtxos + ( filterLockedUtxos + , getWalletCollateral ) +import Ctl.Internal.Contract.Wallet (getChangeAddress, getWalletAddresses) as Contract import Ctl.Internal.Serialization.Address ( Address , addressPaymentCred @@ -136,6 +135,7 @@ import Data.Set (Set) import Data.Set as Set import Data.Traversable (traverse, traverse_) import Data.Tuple.Nested (type (/\), (/\)) +import Effect.Aff.Class (liftAff) import Effect.Class (class MonadEffect, liftEffect) -- | Balances an unbalanced transaction using the specified balancer @@ -160,10 +160,11 @@ balanceTxWithConstraints unbalancedTx constraintsBuilder = do changeAddr <- getChangeAddress - utxos <- liftEitherContract $ traverse (queryHandle.utxosAt >>> liftAff >>> map hush) srcAddrs <#> - traverse (note CouldNotGetUtxos) -- Maybe -> Either and unwrap UtxoM + utxos <- liftEitherContract $ + traverse (queryHandle.utxosAt >>> liftAff >>> map hush) srcAddrs <#> + traverse (note CouldNotGetUtxos) -- Maybe -> Either and unwrap UtxoM - >>> map (foldr Map.union Map.empty) -- merge all utxos into one map + >>> map (foldr Map.union Map.empty) -- merge all utxos into one map unbalancedCollTx <- case Array.null (unbalancedTx ^. _redeemersTxIns) of diff --git a/src/Internal/BalanceTx/ExUnitsAndMinFee.purs b/src/Internal/BalanceTx/ExUnitsAndMinFee.purs index b0947e4d6d..18af77b886 100644 --- a/src/Internal/BalanceTx/ExUnitsAndMinFee.purs +++ b/src/Internal/BalanceTx/ExUnitsAndMinFee.purs @@ -6,8 +6,6 @@ module Ctl.Internal.BalanceTx.ExUnitsAndMinFee import Prelude import Control.Monad.Error.Class (liftEither, throwError) -import Effect.Aff.Class (liftAff) -import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Control.Monad.Except.Trans (except) import Ctl.Internal.BalanceTx.Constraints (_additionalUtxos) as Constraints import Ctl.Internal.BalanceTx.Error @@ -43,8 +41,9 @@ import Ctl.Internal.Cardano.Types.Transaction , _redeemers , _witnessSet ) -import Ctl.Internal.Plutus.Conversion (fromPlutusUtxoMap) import Ctl.Internal.Contract.MinFee (calculateMinFee) as Contract +import Ctl.Internal.Contract.QueryHandle (getQueryHandle) +import Ctl.Internal.Plutus.Conversion (fromPlutusUtxoMap) import Ctl.Internal.QueryM.Ogmios ( AdditionalUtxoSet , TxEvaluationResult(TxEvaluationResult) @@ -82,6 +81,7 @@ import Data.Set as Set import Data.Traversable (for) import Data.Tuple (fst, snd) import Data.Tuple.Nested (type (/\), (/\)) +import Effect.Aff.Class (liftAff) import Effect.Class (liftEffect) evalTxExecutionUnits @@ -92,7 +92,8 @@ evalTxExecutionUnits tx unattachedTx = do queryHandle <- liftContract getQueryHandle additionalUtxos <- getOgmiosAdditionalUtxoSet evalResult <- - unwrap <$> liftContract (liftAff $ queryHandle.evaluateTx tx additionalUtxos) + unwrap <$> liftContract + (liftAff $ queryHandle.evaluateTx tx additionalUtxos) case evalResult of Right a -> pure a diff --git a/src/Internal/BalanceTx/Types.purs b/src/Internal/BalanceTx/Types.purs index 4a7d0c7219..7490424e2f 100644 --- a/src/Internal/BalanceTx/Types.purs +++ b/src/Internal/BalanceTx/Types.purs @@ -28,7 +28,7 @@ import Ctl.Internal.BalanceTx.Constraints ) as Constraints import Ctl.Internal.BalanceTx.Error (BalanceTxError) import Ctl.Internal.Cardano.Types.Transaction (Costmdls(Costmdls), Transaction) -import Ctl.Internal.Contract.Monad (ContractEnv, Contract) +import Ctl.Internal.Contract.Monad (Contract, ContractEnv) import Ctl.Internal.QueryM.Ogmios (CoinsPerUtxoUnit) import Ctl.Internal.Serialization.Address (NetworkId) import Ctl.Internal.Types.ScriptLookups (UnattachedUnbalancedTx) @@ -66,7 +66,8 @@ asksContractEnv = lift <<< lift <<< asks askCoinsPerUtxoUnit :: BalanceTxM CoinsPerUtxoUnit askCoinsPerUtxoUnit = - asksContractEnv (_.coinsPerUtxoUnit <<< unwrap <<< _.pparams <<< _.ledgerConstants) + asksContractEnv + (_.coinsPerUtxoUnit <<< unwrap <<< _.pparams <<< _.ledgerConstants) askCip30Wallet :: BalanceTxM (Maybe Cip30Wallet) askCip30Wallet = asksContractEnv (cip30Wallet <=< _.wallet) diff --git a/src/Internal/Contract/ApplyArgs.purs b/src/Internal/Contract/ApplyArgs.purs index 454dbace65..b4d5567c94 100644 --- a/src/Internal/Contract/ApplyArgs.purs +++ b/src/Internal/Contract/ApplyArgs.purs @@ -4,8 +4,6 @@ module Ctl.Internal.Contract.ApplyArgs import Prelude -import Ctl.Internal.QueryM (ClientError(..), scriptToAeson, postAeson, handleAffjaxResponse) -import Ctl.Internal.Contract.Monad(Contract) import Aeson ( Aeson , encodeAeson @@ -13,7 +11,14 @@ import Aeson import Control.Monad.Reader.Trans ( asks ) +import Ctl.Internal.Contract.Monad (Contract) import Ctl.Internal.Helpers ((<>)) +import Ctl.Internal.QueryM + ( ClientError(ClientOtherError, ClientEncodingError) + , handleAffjaxResponse + , postAeson + , scriptToAeson + ) import Ctl.Internal.QueryM.ServerConfig ( mkHttpUrl ) diff --git a/src/Internal/Contract/AwaitTxConfirmed.purs b/src/Internal/Contract/AwaitTxConfirmed.purs index e83f712709..959e2dcf53 100644 --- a/src/Internal/Contract/AwaitTxConfirmed.purs +++ b/src/Internal/Contract/AwaitTxConfirmed.purs @@ -10,9 +10,9 @@ import Control.Parallel (parOneOf) import Ctl.Internal.Contract (getChainTip) import Ctl.Internal.Contract.Monad (Contract) import Ctl.Internal.Contract.QueryHandle (getQueryHandle) +import Ctl.Internal.Contract.WaitUntilSlot (waitUntilSlot) -- import Ctl.Internal.QueryM.Kupo (isTxConfirmed) as Kupo import Ctl.Internal.QueryM.Ogmios (TxHash) -import Ctl.Internal.Contract.WaitUntilSlot (waitUntilSlot) import Ctl.Internal.Serialization.Address (Slot) import Ctl.Internal.Types.BigNum as BigNum import Ctl.Internal.Types.Chain as Chain diff --git a/src/Internal/Contract/MinFee.purs b/src/Internal/Contract/MinFee.purs index 589a7a1e31..39a5d06eed 100644 --- a/src/Internal/Contract/MinFee.purs +++ b/src/Internal/Contract/MinFee.purs @@ -3,9 +3,6 @@ module Ctl.Internal.Contract.MinFee (calculateMinFee) where import Prelude import Control.Monad.Reader.Class (asks) -import Data.Either (hush) -import Effect.Aff.Class (liftAff) -import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.Cardano.Types.Transaction ( Transaction , UtxoMap @@ -17,9 +14,10 @@ import Ctl.Internal.Cardano.Types.TransactionUnspentOutput ( TransactionUnspentOutput ) import Ctl.Internal.Cardano.Types.Value (Coin) -import Ctl.Internal.Helpers (liftM, liftedM) import Ctl.Internal.Contract.Monad (Contract) +import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.Contract.Wallet (getWalletAddresses, getWalletCollateral) +import Ctl.Internal.Helpers (liftM, liftedM) import Ctl.Internal.Serialization.Address ( Address , addressPaymentCred @@ -31,6 +29,7 @@ import Ctl.Internal.Serialization.MinFee (calculateMinFeeCsl) import Ctl.Internal.Types.Transaction (TransactionInput) import Data.Array (fromFoldable, mapMaybe) import Data.Array as Array +import Data.Either (hush) import Data.Lens.Getter ((^.)) import Data.Map (empty, fromFoldable, keys, lookup, values) as Map import Data.Maybe (fromMaybe, maybe) @@ -40,6 +39,7 @@ import Data.Set (difference, fromFoldable, intersection, mapMaybe, union) as Set import Data.Traversable (for) import Data.Tuple.Nested ((/\)) import Effect.Aff (error) +import Effect.Aff.Class (liftAff) -- | Calculate `min_fee` using CSL with protocol parameters from Ogmios. calculateMinFee :: Transaction -> UtxoMap -> Contract Coin @@ -66,7 +66,8 @@ getSelfSigners tx additionalUtxos = do (inUtxosAddrs :: Set Address) <- setFor txInputs $ \txInput -> liftedM (error $ "Couldn't get tx output for " <> show txInput) $ - (map <<< map) (_.address <<< unwrap) (liftAff $ queryHandle.getUtxoByOref txInput <#> hush >>> join) + (map <<< map) (_.address <<< unwrap) + (liftAff $ queryHandle.getUtxoByOref txInput <#> hush >>> join) -- Get all tx output addressses let diff --git a/src/Internal/Contract/Monad.purs b/src/Internal/Contract/Monad.purs index d748b68a81..3dff7b529b 100644 --- a/src/Internal/Contract/Monad.purs +++ b/src/Internal/Contract/Monad.purs @@ -16,14 +16,8 @@ module Ctl.Internal.Contract.Monad import Prelude -import Data.Function (on) -import Data.Foldable (maximumBy) -import Ctl.Internal.Serialization.Address (NetworkId, Slot) -import Effect.Aff (Aff, ParAff, attempt, error, finally, supervise) -import Ctl.Internal.JsWebSocket (_wsClose, _wsFinalize) -import Ctl.Internal.QueryM (Hooks, Logger, QueryEnv, QueryM, WebSocket, getProtocolParametersAff, getSystemStartAff, getEraSummariesAff, mkDatumCacheWebSocketAff, mkLogger, mkOgmiosWebSocketAff, mkWalletBySpec, underlyingWebSocket) -import Record.Builder (build, merge) -import Control.Parallel (class Parallel, parTraverse, parTraverse_, parallel, sequential) +import Control.Alt (class Alt) +import Control.Alternative (class Alternative) import Control.Monad.Error.Class ( class MonadError , class MonadThrow @@ -33,39 +27,70 @@ import Control.Monad.Logger.Class (class MonadLogger) import Control.Monad.Reader.Class (class MonadAsk, class MonadReader, ask, asks) import Control.Monad.Reader.Trans (ReaderT, runReaderT) import Control.Monad.Rec.Class (class MonadRec) +import Control.Parallel + ( class Parallel + , parTraverse + , parTraverse_ + , parallel + , sequential + ) +import Control.Plus (class Plus) import Ctl.Internal.Contract.QueryBackend ( CtlBackend , QueryBackend(BlockfrostBackend, CtlBackend) + , QueryBackendLabel(CtlBackendLabel) , QueryBackendParams(BlockfrostBackendParams, CtlBackendParams) , QueryBackends - , QueryBackendLabel(CtlBackendLabel) , defaultBackend , lookupBackend ) import Ctl.Internal.Helpers (liftM, liftedM, logWithLevel) +import Ctl.Internal.JsWebSocket (_wsClose, _wsFinalize) +import Ctl.Internal.QueryM + ( Hooks + , Logger + , QueryEnv + , QueryM + , WebSocket + , getEraSummariesAff + , getProtocolParametersAff + , getSystemStartAff + , mkDatumCacheWebSocketAff + , mkLogger + , mkOgmiosWebSocketAff + , mkWalletBySpec + , underlyingWebSocket + ) import Ctl.Internal.QueryM.Logging (setupLogs) -import Ctl.Internal.QueryM.Ogmios (ProtocolParameters, SlotLength, SystemStart, RelativeTime) as Ogmios +import Ctl.Internal.QueryM.Ogmios + ( ProtocolParameters + , RelativeTime + , SlotLength + , SystemStart + ) as Ogmios import Ctl.Internal.QueryM.ServerConfig (ServerConfig) +import Ctl.Internal.Serialization.Address (NetworkId, Slot) import Ctl.Internal.Types.UsedTxOuts (UsedTxOuts, newUsedTxOuts) import Ctl.Internal.Wallet (Wallet) import Ctl.Internal.Wallet (getNetworkId) as Wallet import Ctl.Internal.Wallet.Spec (WalletSpec) import Data.Either (Either(Left, Right)) +import Data.Foldable (maximumBy) +import Data.Function (on) import Data.Log.Level (LogLevel) import Data.Log.Message (Message) import Data.Maybe (Maybe(Just, Nothing), fromMaybe) import Data.Newtype (class Newtype, unwrap) import Data.Traversable (for_, traverse) import Effect (Effect) +import Effect.Aff (Aff, ParAff, attempt, error, finally, supervise) import Effect.Aff.Class (liftAff) import Effect.Class (class MonadEffect, liftEffect) -import Effect.Exception (Error, try, throw) +import Effect.Exception (Error, throw, try) import Effect.Ref (new) as Ref import MedeaPrelude (class MonadAff) +import Record.Builder (build, merge) import Undefined (undefined) -import Control.Alt (class Alt) -import Control.Alternative (class Alternative) -import Control.Plus (class Plus) -------------------------------------------------------------------------------- -- Contract @@ -158,18 +183,18 @@ type ContractEnv = -- We don't support changing protocol parameters, so supporting a HFC is even less unlikely -- slotLength can only change with a HFC. , ledgerConstants :: - { pparams :: Ogmios.ProtocolParameters - , systemStart :: Ogmios.SystemStart - -- Why not use Duration? - , slotLength :: Ogmios.SlotLength - -- A reference point in which the slotLength is assumed to be constant from - -- then until now, not including HFC which occur during contract evaluation - -- TODO: Drop systemStart and just normalize time AOT - -- Maybe not drop it, we export it in Contract. I'm not sure why though - -- TODO: We need to indicate that calculations in the past may be inaccurate - -- Or enforce slot reference to be as 'relatively old' - , slotReference :: { slot :: Slot, time :: Ogmios.RelativeTime } - } + { pparams :: Ogmios.ProtocolParameters + , systemStart :: Ogmios.SystemStart + -- Why not use Duration? + , slotLength :: Ogmios.SlotLength + -- A reference point in which the slotLength is assumed to be constant from + -- then until now, not including HFC which occur during contract evaluation + -- TODO: Drop systemStart and just normalize time AOT + -- Maybe not drop it, we export it in Contract. I'm not sure why though + -- TODO: We need to indicate that calculations in the past may be inaccurate + -- Or enforce slot reference to be as 'relatively old' + , slotReference :: { slot :: Slot, time :: Ogmios.RelativeTime } + } } -- | Initializes a `Contract` environment. Does not ensure finalization. @@ -197,51 +222,60 @@ mkContractEnv params = do pure $ build envBuilder constants where - logger :: Logger - logger = mkLogger params.logLevel params.customLogger - - buildWallet :: Aff (Maybe Wallet) - buildWallet = traverse (mkWalletBySpec params.networkId) params.walletSpec - - constants = - { ctlServerConfig: params.ctlServerConfig - , networkId: params.networkId - , logLevel: params.logLevel - , walletSpec: params.walletSpec - , customLogger: params.customLogger - , suppressLogs: params.suppressLogs - , hooks: params.hooks - } + logger :: Logger + logger = mkLogger params.logLevel params.customLogger + + buildWallet :: Aff (Maybe Wallet) + buildWallet = traverse (mkWalletBySpec params.networkId) params.walletSpec + + constants = + { ctlServerConfig: params.ctlServerConfig + , networkId: params.networkId + , logLevel: params.logLevel + , walletSpec: params.walletSpec + , customLogger: params.customLogger + , suppressLogs: params.suppressLogs + , hooks: params.hooks + } -- TODO Move CtlServer to a backend? Wouldn't make sense as a 'main' backend though -buildBackend :: Logger -> QueryBackends QueryBackendParams -> Aff (QueryBackends QueryBackend) +buildBackend + :: Logger + -> QueryBackends QueryBackendParams + -> Aff (QueryBackends QueryBackend) buildBackend logger = parTraverse case _ of CtlBackendParams { ogmiosConfig, kupoConfig, odcConfig } -> do datumCacheWsRef <- liftEffect $ Ref.new Nothing -- TODO Check the network in env matches up with the network of odc, ogmios and kupo -- Need to pass in the networkid sequential ado - odcWs <- parallel $ mkDatumCacheWebSocketAff datumCacheWsRef logger odcConfig - ogmiosWs <- parallel $ mkOgmiosWebSocketAff datumCacheWsRef logger ogmiosConfig - in CtlBackend - { ogmios: - { config: ogmiosConfig - , ws: ogmiosWs - } - , odc: - { config: odcConfig - , ws: odcWs + odcWs <- parallel $ mkDatumCacheWebSocketAff datumCacheWsRef logger + odcConfig + ogmiosWs <- parallel $ mkOgmiosWebSocketAff datumCacheWsRef logger + ogmiosConfig + in + CtlBackend + { ogmios: + { config: ogmiosConfig + , ws: ogmiosWs + } + , odc: + { config: odcConfig + , ws: odcWs + } + , kupoConfig } - , kupoConfig - } BlockfrostBackendParams bf -> pure $ BlockfrostBackend bf -getLedgerConstants :: Logger -> QueryBackend -> Aff - { pparams :: Ogmios.ProtocolParameters - , systemStart :: Ogmios.SystemStart - , slotLength :: Ogmios.SlotLength - , slotReference :: { slot :: Slot, time :: Ogmios.RelativeTime } - } +getLedgerConstants + :: Logger + -> QueryBackend + -> Aff + { pparams :: Ogmios.ProtocolParameters + , systemStart :: Ogmios.SystemStart + , slotLength :: Ogmios.SlotLength + , slotReference :: { slot :: Slot, time :: Ogmios.RelativeTime } + } getLedgerConstants logger = case _ of CtlBackend { ogmios: { ws } } -> do pparams <- getProtocolParametersAff ws logger @@ -249,10 +283,14 @@ getLedgerConstants logger = case _ of -- Do we ever recieve an eraSummary ahead of schedule? -- Maybe search for the chainTip's era latestEraSummary <- liftedM (error "Could not get EraSummary") do - map unwrap <<< (maximumBy (compare `on` (unwrap >>> _.start >>> unwrap >>> _.slot))) <<< unwrap <$> getEraSummariesAff ws logger + map unwrap + <<< + (maximumBy (compare `on` (unwrap >>> _.start >>> unwrap >>> _.slot))) + <<< unwrap <$> getEraSummariesAff ws logger let slotLength = _.slotLength $ unwrap $ _.parameters $ latestEraSummary - slotReference = (\{slot, time} -> {slot, time}) $ unwrap $ _.start $ latestEraSummary + slotReference = (\{ slot, time } -> { slot, time }) $ unwrap $ _.start $ + latestEraSummary pure { pparams, slotLength, systemStart, slotReference } BlockfrostBackend _ -> undefined @@ -346,9 +384,10 @@ type ContractParams = wrapQueryM :: forall (a :: Type). QueryM a -> Contract a wrapQueryM qm = do backend <- asks _.backend - ctlBackend <- liftM (error "Operation only supported on CTL backend") $ lookupBackend CtlBackendLabel backend >>= case _ of - CtlBackend b -> Just b - _ -> Nothing + ctlBackend <- liftM (error "Operation only supported on CTL backend") $ + lookupBackend CtlBackendLabel backend >>= case _ of + CtlBackend b -> Just b + _ -> Nothing contractEnv <- ask liftAff $ runQueryM contractEnv ctlBackend qm diff --git a/src/Internal/Contract/QueryBackend.purs b/src/Internal/Contract/QueryBackend.purs index d034f25276..249014896f 100644 --- a/src/Internal/Contract/QueryBackend.purs +++ b/src/Internal/Contract/QueryBackend.purs @@ -15,15 +15,15 @@ module Ctl.Internal.Contract.QueryBackend import Prelude -import Ctl.Internal.QueryM (OgmiosWebSocket, DatumCacheWebSocket) +import Ctl.Internal.QueryM (DatumCacheWebSocket, OgmiosWebSocket) import Ctl.Internal.QueryM.ServerConfig (ServerConfig) import Data.Array (nub) as Array import Data.Array ((:)) -import Data.Traversable (class Traversable, traverse, sequence) -import Data.Foldable (class Foldable, foldl, foldr, foldMap, length) +import Data.Foldable (class Foldable, foldMap, foldl, foldr, length) import Data.Map (Map) import Data.Map (empty, insert, lookup) as Map import Data.Maybe (Maybe(Just)) +import Data.Traversable (class Traversable, sequence, traverse) import Effect (Effect) import Effect.Exception (throw) @@ -110,13 +110,13 @@ instance HasQueryBackendLabel QueryBackendParams where type CtlBackend = { ogmios :: - { config :: ServerConfig - , ws :: OgmiosWebSocket - } + { config :: ServerConfig + , ws :: OgmiosWebSocket + } , odc :: - { config :: ServerConfig - , ws :: DatumCacheWebSocket - } + { config :: ServerConfig + , ws :: DatumCacheWebSocket + } , kupoConfig :: ServerConfig } diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs index d6fc15870f..656a6d39eb 100644 --- a/src/Internal/Contract/QueryHandle.purs +++ b/src/Internal/Contract/QueryHandle.purs @@ -3,17 +3,13 @@ module Ctl.Internal.Contract.QueryHandle where import Prelude import Contract.Log (logDebug') -import Ctl.Internal.QueryM.Ogmios (SubmitTxR(SubmitTxSuccess), TxEvaluationR) -import Data.Either (Either) -import Untagged.Union (asOneOf) -import Data.Newtype (unwrap, wrap) -import Ctl.Internal.Hashing (transactionHash) as Hashing -import Effect.Class (liftEffect) -import Ctl.Internal.Cardano.Types.Transaction (Transaction, TransactionOutput, UtxoMap) import Control.Monad.Reader.Class (ask) import Ctl.Internal.Cardano.Types.ScriptRef (ScriptRef) -import Ctl.Internal.QueryM.CurrentEpoch(getCurrentEpoch) as QueryM -import Ctl.Internal.QueryM.GetTxByHash (getTxByHash) as QueryM +import Ctl.Internal.Cardano.Types.Transaction + ( Transaction + , TransactionOutput + , UtxoMap + ) import Ctl.Internal.Contract.Monad ( Contract , ContractEnv @@ -25,8 +21,11 @@ import Ctl.Internal.Contract.QueryBackend , QueryBackend(BlockfrostBackend, CtlBackend) , defaultBackend ) -import Ctl.Internal.QueryM (getChainTip, submitTxOgmios, evaluateTxOgmios) as QueryM +import Ctl.Internal.Hashing (transactionHash) as Hashing import Ctl.Internal.QueryM (ClientError, QueryM) +import Ctl.Internal.QueryM (evaluateTxOgmios, getChainTip, submitTxOgmios) as QueryM +import Ctl.Internal.QueryM.CurrentEpoch (getCurrentEpoch) as QueryM +import Ctl.Internal.QueryM.GetTxByHash (getTxByHash) as QueryM import Ctl.Internal.QueryM.Kupo ( getDatumByHash , getDatumsByHashes @@ -36,17 +35,22 @@ import Ctl.Internal.QueryM.Kupo , isTxConfirmed , utxosAt ) as Kupo +import Ctl.Internal.QueryM.Ogmios (AdditionalUtxoSet, CurrentEpoch) as Ogmios +import Ctl.Internal.QueryM.Ogmios (SubmitTxR(SubmitTxSuccess), TxEvaluationR) import Ctl.Internal.Serialization (convertTransaction, toBytes) as Serialization import Ctl.Internal.Serialization.Address (Address) import Ctl.Internal.Serialization.Hash (ScriptHash) +import Ctl.Internal.Types.Chain as Chain import Ctl.Internal.Types.Datum (DataHash, Datum) import Ctl.Internal.Types.Transaction (TransactionHash, TransactionInput) +import Data.Either (Either) import Data.Map (Map) import Data.Maybe (Maybe(Just, Nothing)) +import Data.Newtype (unwrap, wrap) import Effect.Aff (Aff) +import Effect.Class (liftEffect) import Undefined (undefined) -import Ctl.Internal.Types.Chain as Chain -import Ctl.Internal.QueryM.Ogmios (CurrentEpoch, AdditionalUtxoSet) as Ogmios +import Untagged.Union (asOneOf) -- Why ClientError? type AffE (a :: Type) = Aff (Either ClientError a) @@ -74,9 +78,9 @@ type QueryHandle = -- evaluateTx -- chainTip -- getProtocolParameters - -- this gets done early on - -- perhaps genesis/systemStart should be too - -- getConstantParameters + -- this gets done early on + -- perhaps genesis/systemStart should be too + -- getConstantParameters -- systemStart -- currentEpoch -- we need era summaries start + end, and the era summaries slot length diff --git a/src/Internal/Contract/Sign.purs b/src/Internal/Contract/Sign.purs index 9bd82fd86d..84483556ec 100644 --- a/src/Internal/Contract/Sign.purs +++ b/src/Internal/Contract/Sign.purs @@ -7,18 +7,19 @@ import Prelude import Control.Monad.Reader (asks) import Ctl.Internal.Cardano.Types.Transaction (_body, _inputs, _witnessSet) import Ctl.Internal.Cardano.Types.Transaction as Transaction -import Ctl.Internal.Contract.QueryHandle (getQueryHandle) -import Ctl.Internal.Helpers (liftedM) import Ctl.Internal.Contract.Monad (Contract) +import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.Contract.Wallet ( callCip30Wallet , getWalletAddresses , getWalletUtxos , withWallet ) +import Ctl.Internal.Helpers (liftedM) import Ctl.Internal.Types.Transaction (TransactionInput) import Ctl.Internal.Wallet (Wallet(KeyWallet, Lode, Eternl, Flint, Gero, Nami)) import Data.Array (elem, fromFoldable) +import Data.Either (hush) import Data.Lens ((<>~)) import Data.Lens.Getter ((^.)) import Data.Map as Map @@ -30,7 +31,6 @@ import Effect.Aff (delay, error) import Effect.Aff.Class (liftAff) import Effect.Class (liftEffect) import Effect.Exception (throw, try) -import Data.Either (hush) signTransaction :: Transaction.Transaction -> Contract (Maybe Transaction.Transaction) @@ -65,19 +65,19 @@ walletWaitForInputs :: Array TransactionInput -> Contract Unit walletWaitForInputs txInputs = do queryHandle <- getQueryHandle ownAddrs <- getWalletAddresses - ownInputUtxos :: Map.Map TransactionInput _ - <- txInputs # - traverse - ( \txInput -> do - utxo <- liftedM (error "Could not get utxo") $ liftAff $ join <<< hush <$> queryHandle.getUtxoByOref txInput - pure (txInput /\ utxo) - ) >>> map - ( Map.fromFoldable >>> Map.filter - ( flip elem ownAddrs - <<< _.address - <<< unwrap - ) - ) + ownInputUtxos :: Map.Map TransactionInput _ <- txInputs # + traverse + ( \txInput -> do + utxo <- liftedM (error "Could not get utxo") $ liftAff $ join <<< hush + <$> queryHandle.getUtxoByOref txInput + pure (txInput /\ utxo) + ) >>> map + ( Map.fromFoldable >>> Map.filter + ( flip elem ownAddrs + <<< _.address + <<< unwrap + ) + ) let go attempts = do walletUtxos <- getWalletUtxos <#> fromMaybe Map.empty @@ -100,4 +100,3 @@ walletWaitForInputs txInputs = do -- possible network latency. go 150 - diff --git a/src/Internal/Contract/WaitUntilSlot.purs b/src/Internal/Contract/WaitUntilSlot.purs index d922902038..d273e9e6cc 100644 --- a/src/Internal/Contract/WaitUntilSlot.purs +++ b/src/Internal/Contract/WaitUntilSlot.purs @@ -7,12 +7,12 @@ module Ctl.Internal.Contract.WaitUntilSlot import Prelude -import Ctl.Internal.Contract.Monad(Contract) -import Control.Monad.Reader.Class (asks) - import Contract.Log (logTrace') +import Control.Monad.Reader.Class (asks) +import Ctl.Internal.Contract (getChainTip) +import Ctl.Internal.Contract.Monad (Contract) import Ctl.Internal.Helpers (liftM) -import Ctl.Internal.QueryM.Ogmios (SystemStart, RelativeTime, SlotLength) +import Ctl.Internal.QueryM.Ogmios (RelativeTime, SlotLength, SystemStart) import Ctl.Internal.Serialization.Address (Slot(Slot)) import Ctl.Internal.Types.BigNum as BigNum import Ctl.Internal.Types.Chain as Chain @@ -33,7 +33,6 @@ import Effect.Aff.Class (liftAff) import Effect.Class (liftEffect) import Effect.Exception (error) import Effect.Now (now) -import Ctl.Internal.Contract (getChainTip) -- | The returned slot will be no less than the slot provided as argument. waitUntilSlot :: Slot -> Contract Chain.Tip @@ -48,9 +47,11 @@ waitUntilSlot futureSlot = -- If there are less than `slotPadding` slots remaining, start querying for chainTip -- repeatedly, because it's possible that at any given moment Ogmios suddenly -- synchronizes with node that is also synchronized with global time. - getLag slotReference slotLength systemStart slot >>= logLag slotLengthMs + getLag slotReference slotLength systemStart slot >>= logLag + slotLengthMs futureTime <- - liftEffect (slotToPosixTime slotReference slotLength systemStart futureSlot) + liftEffect + (slotToPosixTime slotReference slotLength systemStart futureSlot) >>= hush >>> liftM (error "Unable to convert Slot to POSIXTime") delayTime <- estimateDelayUntil futureTime liftAff $ delay delayTime @@ -63,8 +64,9 @@ waitUntilSlot futureSlot = | currentSlot_ >= futureSlot -> pure currentTip | otherwise -> do liftAff $ delay $ Milliseconds slotLengthMs - getLag slotReference slotLength systemStart currentSlot_ >>= logLag - slotLengthMs + getLag slotReference slotLength systemStart currentSlot_ + >>= logLag + slotLengthMs fetchRepeatedly Chain.TipAtGenesis -> do liftAff $ delay retryDelay @@ -87,10 +89,16 @@ waitUntilSlot futureSlot = -- | Calculate difference between estimated POSIX time of given slot -- | and current time. -getLag :: { slot :: Slot, time :: RelativeTime } -> SlotLength -> SystemStart -> Slot -> Contract Milliseconds +getLag + :: { slot :: Slot, time :: RelativeTime } + -> SlotLength + -> SystemStart + -> Slot + -> Contract Milliseconds getLag slotReference slotLength sysStart nowSlot = do - nowPosixTime <- liftEffect (slotToPosixTime slotReference slotLength sysStart nowSlot) >>= - hush >>> liftM (error "Unable to convert Slot to POSIXTime") + nowPosixTime <- + liftEffect (slotToPosixTime slotReference slotLength sysStart nowSlot) >>= + hush >>> liftM (error "Unable to convert Slot to POSIXTime") nowMs <- unwrap <<< unInstant <$> liftEffect now logTrace' $ "getLag: current slot: " <> BigNum.toString (unwrap nowSlot) @@ -163,8 +171,9 @@ slotToEndPOSIXTime slot = do futureSlot <- liftM (error "Unable to advance slot") $ wrap <$> BigNum.add (unwrap slot) (BigNum.fromInt 1) { systemStart, slotLength, slotReference } <- asks _.ledgerConstants - futureTime <- liftEffect $ slotToPosixTime slotReference slotLength systemStart futureSlot - >>= hush >>> liftM (error "Unable to convert Slot to POSIXTime") + futureTime <- liftEffect $ + slotToPosixTime slotReference slotLength systemStart futureSlot + >>= hush >>> liftM (error "Unable to convert Slot to POSIXTime") -- We assume that a slot is 1000 milliseconds here. -- TODO Don't pure ((wrap <<< BigInt.fromInt $ -1) + futureTime) diff --git a/src/Internal/Contract/Wallet.purs b/src/Internal/Contract/Wallet.purs index f14a9a4e66..ff990cc41d 100644 --- a/src/Internal/Contract/Wallet.purs +++ b/src/Internal/Contract/Wallet.purs @@ -2,8 +2,6 @@ module Ctl.Internal.Contract.Wallet where import Prelude -import Ctl.Internal.Contract.Monad (Contract) - import Control.Monad.Reader (withReaderT) import Control.Monad.Reader.Trans (ReaderT, asks) import Ctl.Internal.Cardano.Types.Transaction (UtxoMap) @@ -11,23 +9,10 @@ import Ctl.Internal.Cardano.Types.TransactionUnspentOutput ( TransactionUnspentOutput ) import Ctl.Internal.Cardano.Types.Value (Value) -import Ctl.Internal.Helpers as Helpers -import Ctl.Internal.Types.UsedTxOuts (UsedTxOuts, isTxOutRefUsed) -import Data.Array (head, catMaybes) -import Data.Array as Array -import Data.Either (hush) -import Data.Foldable (fold) -import Data.Map as Map -import Data.Maybe (Maybe(Nothing), fromMaybe, maybe) -import Data.Newtype (unwrap, wrap) -import Data.Traversable (for, for_, traverse) -import Data.Tuple.Nested ((/\)) -import Data.UInt as UInt -import Effect.Aff (Aff) -import Effect.Aff.Class (liftAff) -import Effect.Class (liftEffect) +import Ctl.Internal.Contract.Monad (Contract) import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.Helpers (liftM, liftedM) +import Ctl.Internal.Helpers as Helpers import Ctl.Internal.Serialization.Address ( Address , NetworkId @@ -42,13 +27,33 @@ import Ctl.Internal.Types.PubKeyHash , StakePubKeyHash ) import Ctl.Internal.Types.RawBytes (RawBytes) +import Ctl.Internal.Types.UsedTxOuts (UsedTxOuts, isTxOutRefUsed) import Ctl.Internal.Wallet ( Cip30Connection , Cip30Wallet , Wallet(KeyWallet, Lode, Flint, Gero, Nami, Eternl) ) -import Ctl.Internal.Wallet (getChangeAddress, getRewardAddresses, getUnusedAddresses, getWalletAddresses, signData) as Aff +import Ctl.Internal.Wallet + ( getChangeAddress + , getRewardAddresses + , getUnusedAddresses + , getWalletAddresses + , signData + ) as Aff import Ctl.Internal.Wallet.Cip30 (DataSignature) +import Data.Array (catMaybes, head) +import Data.Array as Array +import Data.Either (hush) +import Data.Foldable (fold) +import Data.Map as Map +import Data.Maybe (Maybe(Nothing), fromMaybe, maybe) +import Data.Newtype (unwrap, wrap) +import Data.Traversable (for, for_, traverse) +import Data.Tuple.Nested ((/\)) +import Data.UInt as UInt +import Effect.Aff (Aff) +import Effect.Aff.Class (liftAff) +import Effect.Class (liftEffect) import Effect.Exception (error, throw) getUnusedAddresses :: Contract (Array Address) @@ -140,7 +145,8 @@ getWalletCollateral = do Eternl wallet -> liftAff $ callCip30Wallet wallet _.getCollateral KeyWallet kw -> do let addr = (unwrap kw).address - utxos <- (liftAff $ queryHandle.utxosAt addr) <#> hush >>> fromMaybe Map.empty + utxos <- (liftAff $ queryHandle.utxosAt addr) + <#> hush >>> fromMaybe Map.empty >>= filterLockedUtxos pparams <- asks $ _.ledgerConstants >>> _.pparams <#> unwrap let diff --git a/src/Internal/Plutip/Server.purs b/src/Internal/Plutip/Server.purs index 36c4464c0f..165ce3c851 100644 --- a/src/Internal/Plutip/Server.purs +++ b/src/Internal/Plutip/Server.purs @@ -21,8 +21,6 @@ import Affjax.RequestHeader as Header import Affjax.ResponseFormat as Affjax.ResponseFormat import Contract.Address (NetworkId(MainnetId)) import Contract.Config (QueryBackendParams(CtlBackendParams)) -import Ctl.Internal.Contract.QueryBackend (defaultBackend, mkSingletonBackendParams) -import Ctl.Internal.Contract.Monad (buildBackend, getLedgerConstants, stopContractEnv) import Contract.Monad ( Contract , ContractEnv @@ -33,6 +31,15 @@ import Control.Monad.Error.Class (liftEither) import Control.Monad.State (State, execState, modify_) import Control.Monad.Trans.Class (lift) import Control.Monad.Writer (censor, execWriterT, tell) +import Ctl.Internal.Contract.Monad + ( buildBackend + , getLedgerConstants + , stopContractEnv + ) +import Ctl.Internal.Contract.QueryBackend + ( defaultBackend + , mkSingletonBackendParams + ) import Ctl.Internal.Helpers ((<>)) import Ctl.Internal.Plutip.PortCheck (isPortAvailable) import Ctl.Internal.Plutip.Spawn diff --git a/src/Internal/Plutip/UtxoDistribution.purs b/src/Internal/Plutip/UtxoDistribution.purs index 2786c25138..40dee249fb 100644 --- a/src/Internal/Plutip/UtxoDistribution.purs +++ b/src/Internal/Plutip/UtxoDistribution.purs @@ -10,8 +10,6 @@ module Ctl.Internal.Plutip.UtxoDistribution import Prelude -import Ctl.Internal.Serialization.Address (NetworkId(MainnetId)) -import Contract.Wallet (mkKeyWalletFromPrivateKeys, withKeyWallet) import Contract.Address ( PaymentPubKeyHash , StakePubKeyHash @@ -33,6 +31,7 @@ import Contract.Transaction ) import Contract.TxConstraints as Constraints import Contract.Utxos (utxosAt) +import Contract.Wallet (mkKeyWalletFromPrivateKeys, withKeyWallet) import Control.Alternative (guard) import Control.Monad.Reader (asks) import Control.Monad.State.Trans (StateT(StateT), runStateT) @@ -43,6 +42,7 @@ import Ctl.Internal.Plutip.Types , UtxoAmount ) import Ctl.Internal.Plutus.Types.Transaction (UtxoMap) +import Ctl.Internal.Serialization.Address (NetworkId(MainnetId)) import Ctl.Internal.Wallet.Key ( KeyWallet , PrivatePaymentKey(PrivatePaymentKey) diff --git a/src/Internal/ReindexRedeemers.purs b/src/Internal/ReindexRedeemers.purs index 1264ff95fb..df8abf62a8 100644 --- a/src/Internal/ReindexRedeemers.purs +++ b/src/Internal/ReindexRedeemers.purs @@ -41,7 +41,7 @@ reindexSpentScriptRedeemers -> Array RedeemersTxIn -> Either ReindexErrors (Array T.Redeemer) reindexSpentScriptRedeemers inputs redeemersTxIns = do - redeemersTxInsReindexed <- + redeemersTxInsReindexed <- reindexSpentScriptRedeemers' inputs redeemersTxIns Right $ map fst redeemersTxInsReindexed diff --git a/src/Internal/Test/E2E/Route.purs b/src/Internal/Test/E2E/Route.purs index a2bee1dff5..be5274c84a 100644 --- a/src/Internal/Test/E2E/Route.purs +++ b/src/Internal/Test/E2E/Route.purs @@ -12,7 +12,6 @@ import Prelude import Contract.Config (ContractParams) import Contract.Monad (Contract, runContract) import Contract.Test.Cip30Mock (WalletMock, withCip30Mock) -import Ctl.Internal.Contract.QueryBackend (QueryBackendParams(CtlBackendParams), mkSingletonBackendParams) import Contract.Wallet ( PrivatePaymentKey(PrivatePaymentKey) , PrivateStakeKey(PrivateStakeKey) @@ -21,6 +20,10 @@ import Contract.Wallet import Contract.Wallet.Key (privateKeysToKeyWallet) import Control.Alt ((<|>)) import Control.Monad.Error.Class (liftMaybe) +import Ctl.Internal.Contract.QueryBackend + ( QueryBackendParams(CtlBackendParams) + , mkSingletonBackendParams + ) import Ctl.Internal.Helpers (liftEither) import Ctl.Internal.QueryM (ClusterSetup) import Ctl.Internal.Serialization.Address (NetworkId(MainnetId)) @@ -173,7 +176,9 @@ route configs tests = do # maybe identity setClusterOptions mbClusterSetup do runContract configWithHooks - $ withCip30Mock (privateKeysToKeyWallet config.networkId paymentKey stakeKey) mock + $ withCip30Mock + (privateKeysToKeyWallet config.networkId paymentKey stakeKey) + mock test where -- Eternl does not initialize instantly. We have to add a small delay. @@ -212,10 +217,10 @@ route configs tests = do config = config { backendParams = mkSingletonBackendParams $ CtlBackendParams - { ogmiosConfig: ogmiosConfig - , odcConfig: datumCacheConfig - , kupoConfig: kupoConfig - } + { ogmiosConfig: ogmiosConfig + , odcConfig: datumCacheConfig + , kupoConfig: kupoConfig + } , ctlServerConfig = ctlServerConfig } diff --git a/src/Internal/Test/E2E/Runner.purs b/src/Internal/Test/E2E/Runner.purs index 2f6703d5fd..990103b3f0 100644 --- a/src/Internal/Test/E2E/Runner.purs +++ b/src/Internal/Test/E2E/Runner.purs @@ -12,7 +12,10 @@ import Affjax.ResponseFormat as Affjax.ResponseFormat import Control.Alt ((<|>)) import Control.Monad.Error.Class (liftMaybe) import Control.Promise (Promise, toAffE) -import Ctl.Internal.Contract.QueryBackend (QueryBackend(CtlBackend), defaultBackend) +import Ctl.Internal.Contract.QueryBackend + ( QueryBackend(CtlBackend) + , defaultBackend + ) import Ctl.Internal.Deserialization.Keys (privateKeyFromBytes) import Ctl.Internal.Helpers (liftedM, (<>)) import Ctl.Internal.Plutip.Server (withPlutipContractEnv) diff --git a/src/Internal/Types/Interval.purs b/src/Internal/Types/Interval.purs index f16b7022e1..c71d532890 100644 --- a/src/Internal/Types/Interval.purs +++ b/src/Internal/Types/Interval.purs @@ -96,9 +96,9 @@ import Ctl.Internal.Plutus.Types.DataSchema import Ctl.Internal.QueryM.Ogmios ( EraSummaries(EraSummaries) , EraSummary(EraSummary) - , SystemStart , RelativeTime , SlotLength + , SystemStart , aesonObject , slotLengthFactor ) @@ -819,7 +819,8 @@ relSlotFromSlot start s@(Slot slot) = do relTimeFromRelSlot :: SlotLength -> RelSlot -> Maybe RelTime relTimeFromRelSlot slotLength (RelSlot relSlot) = - (<$>) wrap <<< BigInt.fromNumber $ (BigInt.toNumber relSlot) * (unwrap slotLength) + (<$>) wrap <<< BigInt.fromNumber $ (BigInt.toNumber relSlot) * + (unwrap slotLength) -- As justified in https://github.com/input-output-hk/ouroboros-network/blob/bd9e5653647c3489567e02789b0ec5b75c726db2/ouroboros-consensus/src/Ouroboros/Consensus/HardFork/History/Qry.hs#L461-L481 -- Treat the upperbound as inclusive. @@ -830,15 +831,15 @@ absTimeFromRelTime start (RelTime relTime) = do let startTime = unwrap start * slotLengthFactor absTime = startTime + BigInt.toNumber relTime -- relative to System Start, not UNIX Epoch. - -- If `EraSummary` doesn't have an end, the condition is automatically - -- satisfied. We use `<=` as justified by the source code. - -- Note the hack that we don't have `end` for the current era, if we did not - -- here could be issues going far into the future. But certain contracts are - -- required to be in the distant future. Onchain, this uses POSIXTime which - -- is stable, unlike Slots. - -- endTime = maybe (absTime + one) - -- ((*) slotLengthFactor <<< unwrap <<< _.time <<< unwrap) - -- end + -- If `EraSummary` doesn't have an end, the condition is automatically + -- satisfied. We use `<=` as justified by the source code. + -- Note the hack that we don't have `end` for the current era, if we did not + -- here could be issues going far into the future. But certain contracts are + -- required to be in the distant future. Onchain, this uses POSIXTime which + -- is stable, unlike Slots. + -- endTime = maybe (absTime + one) + -- ((*) slotLengthFactor <<< unwrap <<< _.time <<< unwrap) + -- end -- unless -- (absTime <= endTime) -- (throwError $ EndTimeLessThanTime absTime) @@ -943,29 +944,31 @@ posixTimeToSlot -> SystemStart -> POSIXTime -> Effect (Either PosixTimeToSlotError Slot) -posixTimeToSlot slotReference slotLength sysStart pt'@(POSIXTime pt) = runExceptT do - -- Get JSDate: - sysStartD <- liftEffect $ parse $ unwrap sysStart - -- Get POSIX time for system start - sysStartPosix <- liftM CannotGetBigIntFromNumber' - $ BigInt.fromNumber - $ getTime sysStartD - -- Ensure the time we are converting is after the system start, otherwise - -- we have negative slots. - unless (sysStartPosix <= pt) - $ throwError - $ PosixTimeBeforeSystemStart pt' - -- Keep as milliseconds: - let absTime = wrap $ pt - sysStartPosix - -- Find current era: - -- currentEra <- liftEither $ findTimeEraSummary eraSummaries absTime - -- Get relative time from absolute time w.r.t. current era - relTime <- liftEither $ relTimeFromAbsTime slotReference.time absTime - -- Convert to relative slot - relSlotMod <- liftM CannotGetBigIntFromNumber' $ relSlotFromRelTime slotLength - relTime - -- Get absolute slot relative to system start - liftEither $ slotFromRelSlot slotReference.slot relSlotMod +posixTimeToSlot slotReference slotLength sysStart pt'@(POSIXTime pt) = + runExceptT do + -- Get JSDate: + sysStartD <- liftEffect $ parse $ unwrap sysStart + -- Get POSIX time for system start + sysStartPosix <- liftM CannotGetBigIntFromNumber' + $ BigInt.fromNumber + $ getTime sysStartD + -- Ensure the time we are converting is after the system start, otherwise + -- we have negative slots. + unless (sysStartPosix <= pt) + $ throwError + $ PosixTimeBeforeSystemStart pt' + -- Keep as milliseconds: + let absTime = wrap $ pt - sysStartPosix + -- Find current era: + -- currentEra <- liftEither $ findTimeEraSummary eraSummaries absTime + -- Get relative time from absolute time w.r.t. current era + relTime <- liftEither $ relTimeFromAbsTime slotReference.time absTime + -- Convert to relative slot + relSlotMod <- liftM CannotGetBigIntFromNumber' $ relSlotFromRelTime + slotLength + relTime + -- Get absolute slot relative to system start + liftEither $ slotFromRelSlot slotReference.slot relSlotMod -- | Finds the `EraSummary` an `AbsTime` lies inside (if any). findTimeEraSummary @@ -1008,7 +1011,8 @@ relSlotFromRelTime relSlotFromRelTime slotLength (RelTime relTime) = let relSlot = wrap <$> - (BigInt.fromNumber <<< Math.trunc) (BigInt.toNumber relTime / unwrap slotLength) + (BigInt.fromNumber <<< Math.trunc) + (BigInt.toNumber relTime / unwrap slotLength) modTime = wrap <$> BigInt.fromNumber (BigInt.toNumber relTime Math.% unwrap slotLength) in @@ -1023,15 +1027,15 @@ slotFromRelSlot startSlot = BigNum.toBigIntUnsafe $ unwrap start -- Round down to the nearest Slot to accept Milliseconds as input. slot = startSlot + relSlot -- relative to system start - -- If `EraSummary` doesn't have an end, the condition is automatically - -- satisfied. We use `<=` as justified by the source code. - -- Note the hack that we don't have `end` for the current era, if we did not - -- here could be issues going far into the future. But certain contracts are - -- required to be in the distant future. Onchain, this uses POSIXTime which - -- is stable, unlike Slots. - -- endSlot = maybe (slot + one) - -- (BigNum.toBigIntUnsafe <<< unwrap <<< _.slot <<< unwrap) - -- end + -- If `EraSummary` doesn't have an end, the condition is automatically + -- satisfied. We use `<=` as justified by the source code. + -- Note the hack that we don't have `end` for the current era, if we did not + -- here could be issues going far into the future. But certain contracts are + -- required to be in the distant future. Onchain, this uses POSIXTime which + -- is stable, unlike Slots. + -- endSlot = maybe (slot + one) + -- (BigNum.toBigIntUnsafe <<< unwrap <<< _.slot <<< unwrap) + -- end bnSlot <- liftM CannotGetBigNumFromBigInt' $ BigNum.fromBigInt slot -- Check we are less than the end slot, or if equal, there is no excess: -- unless (slot < endSlot || slot == endSlot && modTime == zero) @@ -1122,7 +1126,8 @@ posixTimeRangeToTransactionValidity -> POSIXTimeRange -> Effect (Either PosixTimeToSlotError TransactionValiditySlot) posixTimeRangeToTransactionValidity sr sl ss = - map (map slotRangeToTransactionValidity) <<< posixTimeRangeToSlotRange sr sl ss + map (map slotRangeToTransactionValidity) <<< posixTimeRangeToSlotRange sr sl + ss data ToOnChainPosixTimeRangeError = PosixTimeToSlotError' PosixTimeToSlotError diff --git a/src/Internal/Types/ScriptLookups.purs b/src/Internal/Types/ScriptLookups.purs index 31035ea9c7..527426ec86 100644 --- a/src/Internal/Types/ScriptLookups.purs +++ b/src/Internal/Types/ScriptLookups.purs @@ -53,11 +53,7 @@ module Ctl.Internal.Types.ScriptLookups ) where import Prelude hiding (join) -import Prelude (join) as Bind -import Ctl.Internal.Contract.Monad (Contract, wrapQueryM) -import Effect.Aff.Class (liftAff) -import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Aeson (class EncodeAeson) import Contract.Hashing (plutusScriptStakeValidatorHash) import Control.Monad.Error.Class (catchError, liftMaybe, throwError) @@ -105,6 +101,8 @@ import Ctl.Internal.Cardano.Types.Value , negation , split ) +import Ctl.Internal.Contract.Monad (Contract, wrapQueryM) +import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.Hashing (datumHash) as Hashing import Ctl.Internal.Helpers (liftM, (<\>)) import Ctl.Internal.IsData (class IsData) @@ -249,7 +247,7 @@ import Data.Array (cons, filter, mapWithIndex, partition, toUnfoldable, zip) import Data.Array (singleton, union, (:)) as Array import Data.Bifunctor (lmap) import Data.BigInt (BigInt, fromInt) -import Data.Either (Either(Left, Right), either, isRight, note, hush) +import Data.Either (Either(Left, Right), either, hush, isRight, note) import Data.Foldable (foldM) import Data.Generic.Rep (class Generic) import Data.Lattice (join) @@ -270,8 +268,10 @@ import Data.Traversable (for, traverse_) import Data.Tuple (fst, snd) import Data.Tuple.Nested (type (/\), (/\)) import Effect (Effect) +import Effect.Aff.Class (liftAff) import Effect.Class (liftEffect) import MedeaPrelude (mapMaybe) +import Prelude (join) as Bind import Type.Proxy (Proxy(Proxy)) -- Taken mainly from https://playground.plutus.iohkdev.io/doc/haddock/plutus-ledger-constraints/html/Ledger-Constraints-OffChain.html @@ -640,7 +640,8 @@ runConstraintsM -> TxConstraints redeemer datum -> Contract (Either MkUnbalancedTxError (ConstraintProcessingState validator)) runConstraintsM lookups txConstraints = do - costModels <- asks $ _.ledgerConstants >>> _.pparams >>> unwrap >>> _.costModels + costModels <- asks $ _.ledgerConstants >>> _.pparams >>> unwrap >>> + _.costModels let initCps :: ConstraintProcessingState validator initCps = @@ -849,7 +850,9 @@ addOwnOutput (OutputConstraint { datum: d, value }) = do -- We are erroring if we don't have a datumhash given the polymorphic datum -- in the `OutputConstraint`: dHash <- liftM TypedTxOutHasNoDatumHash (typedTxOutDatumHash typedTxOut) - dat <- ExceptT $ liftAff $ queryHandle.getDatumByHash dHash <#> hush >>> Bind.join >>> note (CannotQueryDatum dHash) + dat <- ExceptT $ liftAff $ queryHandle.getDatumByHash dHash <#> hush + >>> Bind.join + >>> note (CannotQueryDatum dHash) _cpsToTxBody <<< _outputs %= Array.(:) txOut ExceptT $ addDatum dat _valueSpentBalancesOutputs <>= provideValue value' @@ -1053,7 +1056,9 @@ processConstraint mpsMap osMap c = do { slotReference, slotLength, systemStart } <- asks _.ledgerConstants runExceptT do ({ timeToLive, validityStartInterval }) <- ExceptT $ liftEffect $ - posixTimeRangeToTransactionValidity slotReference slotLength systemStart posixTimeRange + posixTimeRangeToTransactionValidity slotReference slotLength + systemStart + posixTimeRange <#> lmap (CannotConvertPOSIXTimeRange posixTimeRange) _cpsToTxBody <<< _Newtype %= _ @@ -1115,8 +1120,10 @@ processConstraint mpsMap osMap c = do if isRight mDatumLookup then pure mDatumLookup else - liftAff $ queryHandle.getDatumByHash dHash <#> hush >>> Bind.join >>> note - (CannotQueryDatum dHash) + liftAff $ queryHandle.getDatumByHash dHash <#> hush + >>> Bind.join + >>> note + (CannotQueryDatum dHash) ExceptT $ addDatum dat OutputDatum _ -> pure unit NoOutputDatum -> throwError CannotFindDatum @@ -1370,7 +1377,8 @@ processConstraint mpsMap osMap c = do attachToCps attachNativeScript (unwrap stakeValidator) MustWithdrawStakePubKey spkh -> runExceptT do networkId <- asks _.networkId - mbRewards <- lift $ lift $ wrapQueryM $ getPubKeyHashDelegationsAndRewards spkh + mbRewards <- lift $ lift $ wrapQueryM $ getPubKeyHashDelegationsAndRewards + spkh ({ rewards }) <- ExceptT $ pure $ note (CannotWithdrawRewardsPubKey spkh) mbRewards let @@ -1381,7 +1389,8 @@ processConstraint mpsMap osMap c = do MustWithdrawStakePlutusScript stakeValidator redeemerData -> runExceptT do let hash = plutusScriptStakeValidatorHash stakeValidator networkId <- asks _.networkId - mbRewards <- lift $ lift $ wrapQueryM $ getValidatorHashDelegationsAndRewards hash + mbRewards <- lift $ lift $ wrapQueryM $ + getValidatorHashDelegationsAndRewards hash let rewardAddress = RewardAddress.stakeValidatorHashRewardAddress networkId hash @@ -1403,7 +1412,8 @@ processConstraint mpsMap osMap c = do MustWithdrawStakeNativeScript stakeValidator -> runExceptT do let hash = nativeScriptStakeValidatorHash stakeValidator networkId <- asks _.networkId - mbRewards <- lift $ lift $ wrapQueryM $ getValidatorHashDelegationsAndRewards hash + mbRewards <- lift $ lift $ wrapQueryM $ + getValidatorHashDelegationsAndRewards hash let rewardAddress = RewardAddress.stakeValidatorHashRewardAddress networkId hash diff --git a/src/Internal/Types/TypedTxOut.purs b/src/Internal/Types/TypedTxOut.purs index b32b21af27..44df9b2cab 100644 --- a/src/Internal/Types/TypedTxOut.purs +++ b/src/Internal/Types/TypedTxOut.purs @@ -34,12 +34,12 @@ import Prelude import Control.Monad.Error.Class (throwError) import Control.Monad.Except.Trans (ExceptT(ExceptT), except, runExceptT) -import Effect.Aff.Class (liftAff) -import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.Cardano.Types.Transaction ( TransactionOutput(TransactionOutput) ) import Ctl.Internal.Cardano.Types.Value (Value) +import Ctl.Internal.Contract.Monad (Contract) +import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.FromData (class FromData, fromData) import Ctl.Internal.Hashing (datumHash) as Hashing import Ctl.Internal.Helpers (liftM) @@ -60,7 +60,7 @@ import Data.Generic.Rep (class Generic) import Data.Maybe (Maybe(Just, Nothing)) import Data.Newtype (unwrap, wrap) import Data.Show.Generic (genericShow) -import Ctl.Internal.Contract.Monad (Contract) +import Effect.Aff.Class (liftAff) -- | A `TransactionInput` tagged by a phantom type: and the -- | connection type of the output. @@ -275,7 +275,8 @@ typeTxOut -- Assume `Nothing` is a public key. dHash <- liftM ExpectedScriptGotPubkey $ outputDatumDataHash datum void $ checkValidatorAddress networkId typedVal address - pd <- ExceptT $ liftAff $ queryHandle.getDatumByHash dHash <#> hush >>> join >>> note (CannotQueryDatum dHash) + pd <- ExceptT $ liftAff $ queryHandle.getDatumByHash dHash <#> hush >>> join + >>> note (CannotQueryDatum dHash) dtOut <- ExceptT $ checkDatum typedVal pd except $ note CannotMakeTypedTxOut (mkTypedTxOut networkId typedVal dtOut amount) diff --git a/src/Internal/Wallet.purs b/src/Internal/Wallet.purs index 4fb766e55f..d4b5582bec 100644 --- a/src/Internal/Wallet.purs +++ b/src/Internal/Wallet.purs @@ -54,7 +54,22 @@ import Ctl.Internal.Cardano.Types.Transaction , mkPublicKey ) import Ctl.Internal.Helpers ((<<>>)) +import Ctl.Internal.Helpers as Helpers +import Ctl.Internal.Serialization.Address + ( Address + , NetworkId(TestnetId, MainnetId) + , addressPaymentCred + , baseAddressDelegationCred + , baseAddressFromAddress + , stakeCredentialToKeyHash + ) import Ctl.Internal.Types.Natural (fromInt', minus) +import Ctl.Internal.Types.PubKeyHash + ( PaymentPubKeyHash + , PubKeyHash + , StakePubKeyHash + ) +import Ctl.Internal.Types.RawBytes (RawBytes) import Ctl.Internal.Wallet.Cip30 (Cip30Connection, Cip30Wallet) as Cip30Wallet import Ctl.Internal.Wallet.Cip30 ( Cip30Connection @@ -69,34 +84,19 @@ import Ctl.Internal.Wallet.Key , privateKeysToKeyWallet ) import Ctl.Internal.Wallet.Key (KeyWallet, privateKeysToKeyWallet) as KeyWallet +import Data.Array as Array +import Data.Foldable (fold) import Data.Int (toNumber) import Data.Maybe (Maybe(Just, Nothing), fromJust) -import Data.Newtype (over, wrap, unwrap) +import Data.Newtype (over, unwrap, wrap) +import Data.Traversable (traverse) import Data.Tuple.Nested ((/\)) import Effect (Effect) import Effect.Aff (Aff, delay, error) import Effect.Class (liftEffect) +import Effect.Exception (throw) import Partial.Unsafe (unsafePartial) import Prim.TypeError (class Warn, Text) -import Ctl.Internal.Helpers as Helpers -import Data.Array as Array -import Data.Foldable (fold) -import Data.Traversable (traverse) -import Effect.Exception (throw) -import Ctl.Internal.Serialization.Address - ( Address - , NetworkId(TestnetId, MainnetId) - , addressPaymentCred - , baseAddressDelegationCred - , baseAddressFromAddress - , stakeCredentialToKeyHash - ) -import Ctl.Internal.Types.PubKeyHash - ( PaymentPubKeyHash - , PubKeyHash - , StakePubKeyHash - ) -import Ctl.Internal.Types.RawBytes (RawBytes) data Wallet = Nami Cip30Wallet @@ -114,7 +114,10 @@ data WalletExtension | LodeWallet mkKeyWallet :: NetworkId -> PrivatePaymentKey -> Maybe PrivateStakeKey -> Wallet -mkKeyWallet network payKey mbStakeKey = KeyWallet $ privateKeysToKeyWallet network payKey mbStakeKey +mkKeyWallet network payKey mbStakeKey = KeyWallet $ privateKeysToKeyWallet + network + payKey + mbStakeKey foreign import _enableWallet :: String -> Effect (Promise Cip30Connection) foreign import _isWalletAvailable :: String -> Effect Boolean @@ -324,7 +327,8 @@ getUnusedAddresses wallet = fold <$> do getChangeAddress :: Wallet -> Aff (Maybe Address) getChangeAddress wallet = do - actionBasedOnWalletAff _.getChangeAddress (\kw -> pure $ pure (unwrap kw).address) + actionBasedOnWalletAff _.getChangeAddress + (\kw -> pure $ pure (unwrap kw).address) wallet getRewardAddresses :: Wallet -> Aff (Array Address) diff --git a/src/Internal/Wallet/Cip30Mock.purs b/src/Internal/Wallet/Cip30Mock.purs index aa80be604b..5540ef17ed 100644 --- a/src/Internal/Wallet/Cip30Mock.purs +++ b/src/Internal/Wallet/Cip30Mock.purs @@ -7,10 +7,10 @@ import Control.Monad.Error.Class (liftMaybe, try) import Control.Monad.Reader (ask) import Control.Monad.Reader.Class (local) import Control.Promise (Promise, fromAff) -import Ctl.Internal.Contract.QueryHandle (getQueryHandle') import Ctl.Internal.Cardano.Types.TransactionUnspentOutput ( TransactionUnspentOutput(TransactionUnspentOutput) ) +import Ctl.Internal.Contract.QueryHandle (getQueryHandle') import Ctl.Internal.Deserialization.Transaction (deserializeTransaction) import Ctl.Internal.Helpers (liftEither) import Ctl.Internal.Serialization @@ -18,7 +18,10 @@ import Ctl.Internal.Serialization , convertValue , toBytes ) -import Ctl.Internal.Serialization.Address (Address, NetworkId(TestnetId, MainnetId)) +import Ctl.Internal.Serialization.Address + ( Address + , NetworkId(TestnetId, MainnetId) + ) import Ctl.Internal.Serialization.WitnessSet (convertWitnessSet) import Ctl.Internal.Types.ByteArray (byteArrayToHex, hexToByteArray) import Ctl.Internal.Types.CborBytes (cborBytesFromByteArray) @@ -132,7 +135,7 @@ mkCip30Mock pKey mSKey = do keyWallet = privateKeysToKeyWallet env.networkId pKey mSKey - addressHex = + addressHex = byteArrayToHex $ toBytes $ asOneOf ((unwrap keyWallet).address :: Address) pure $ @@ -171,12 +174,12 @@ mkCip30Mock pKey mSKey = do utxos pure $ byteArrayToHex $ toBytes $ asOneOf value , getUsedAddresses: fromAff do - pure [addressHex] + pure [ addressHex ] , getUnusedAddresses: fromAff $ pure [] , getChangeAddress: fromAff do pure addressHex , getRewardAddresses: fromAff do - pure [addressHex] + pure [ addressHex ] , signTx: \str -> unsafePerformEffect $ fromAff do txBytes <- liftMaybe (error "Unable to convert CBOR") $ hexToByteArray str diff --git a/src/Internal/Wallet/Key.purs b/src/Internal/Wallet/Key.purs index 6a1bea56df..85af994b6a 100644 --- a/src/Internal/Wallet/Key.purs +++ b/src/Internal/Wallet/Key.purs @@ -128,13 +128,15 @@ privateKeysToAddress payKey mbStakeKey network = do let pubPayKey = publicKeyFromPrivateKey (unwrap payKey) case mbStakeKey of Just stakeKey -> - let pubStakeKey = publicKeyFromPrivateKey (unwrap stakeKey) - in baseAddressToAddress $ - baseAddress - { network - , paymentCred: keyHashCredential $ publicKeyHash $ pubPayKey - , delegationCred: keyHashCredential $ publicKeyHash $ pubStakeKey - } + let + pubStakeKey = publicKeyFromPrivateKey (unwrap stakeKey) + in + baseAddressToAddress $ + baseAddress + { network + , paymentCred: keyHashCredential $ publicKeyHash $ pubPayKey + , delegationCred: keyHashCredential $ publicKeyHash $ pubStakeKey + } Nothing -> pubPayKey # publicKeyHash >>> keyHashCredential diff --git a/test/BalanceTx/Time.purs b/test/BalanceTx/Time.purs index fac0994279..20d44ac2ef 100644 --- a/test/BalanceTx/Time.purs +++ b/test/BalanceTx/Time.purs @@ -14,9 +14,9 @@ import Contract.Time , Slot , always , from - , getSystemStart , getSlotLength , getSlotReference + , getSystemStart , maxSlot , mkFiniteInterval , never @@ -160,7 +160,9 @@ toPosixTime time = do slotReference <- getSlotReference slotLength <- getSlotLength systemStart <- getSystemStart - eitherTime <- liftEffect $ slotToPosixTime slotReference slotLength systemStart time + eitherTime <- liftEffect $ slotToPosixTime slotReference slotLength + systemStart + time case eitherTime of Left e -> (throwError <<< error <<< show) e Right value -> pure value diff --git a/test/Integration.purs b/test/Integration.purs index 763319fb42..8e0689a1b4 100644 --- a/test/Integration.purs +++ b/test/Integration.purs @@ -2,9 +2,9 @@ module Test.Ctl.Integration (main, testPlan) where import Prelude -import Contract.Monad (runContract) -import Contract.Time (getSlotReference, getSystemStart, getSlotLength) import Contract.Config (testnetConfig) +import Contract.Monad (runContract) +import Contract.Time (getSlotLength, getSlotReference, getSystemStart) import Ctl.Internal.Contract.Monad (wrapQueryM) import Ctl.Internal.Test.TestPlanM (TestPlanM, interpret) import Effect (Effect) @@ -12,11 +12,11 @@ import Effect.Aff (Aff, launchAff_) import Effect.Class (liftEffect) import Mote (skip) import Mote.Monad (mapTest) -import Test.Ctl.QueryM.AffInterface as QueryM.AffInterface import Test.Ctl.BalanceTx.Collateral as Collateral import Test.Ctl.BalanceTx.Time as BalanceTx.Time import Test.Ctl.Logging as Logging import Test.Ctl.PrivateKey as PrivateKey +import Test.Ctl.QueryM.AffInterface as QueryM.AffInterface import Test.Ctl.Types.Interval as Types.Interval -- Run with `spago test --main Test.Ctl.Integration` @@ -31,7 +31,8 @@ testPlan = do -- These tests depend on assumptions about testnet history. -- We disabled them during transition from `testnet` to `preprod` networks. -- https://github.com/Plutonomicon/cardano-transaction-lib/issues/945 - skip $ flip mapTest Types.Interval.suite \f -> runContract testnetConfig { suppressLogs = true } + skip $ flip mapTest Types.Interval.suite \f -> runContract + testnetConfig { suppressLogs = true } do slotReference <- getSlotReference slotLength <- getSlotLength diff --git a/test/Ogmios/GenerateFixtures.purs b/test/Ogmios/GenerateFixtures.purs index aa05f52293..5bcb89f49c 100644 --- a/test/Ogmios/GenerateFixtures.purs +++ b/test/Ogmios/GenerateFixtures.purs @@ -16,9 +16,9 @@ import Ctl.Internal.JsWebSocket , _wsSend ) import Ctl.Internal.QueryM - ( WebSocket(WebSocket) + ( ListenerSet + , WebSocket(WebSocket) , WebsocketDispatch - , ListenerSet , defaultMessageListener , defaultOgmiosWsConfig , mkListenerSet diff --git a/test/Plutip/Contract.purs b/test/Plutip/Contract.purs index 500fe33949..73e00bfb21 100644 --- a/test/Plutip/Contract.purs +++ b/test/Plutip/Contract.purs @@ -4,14 +4,13 @@ module Test.Ctl.Plutip.Contract import Prelude -import Ctl.Internal.Contract.Monad (wrapQueryM) import Contract.Address ( PaymentPubKeyHash(PaymentPubKeyHash) , PubKeyHash(PubKeyHash) , StakePubKeyHash + , getNetworkId , getWalletAddresses , getWalletCollateral - , getNetworkId , ownPaymentPubKeysHashes , ownStakePubKeysHashes ) @@ -103,6 +102,7 @@ import Ctl.Examples.PlutusV2.Scripts.AlwaysMints (alwaysMintsPolicyV2) import Ctl.Examples.PlutusV2.Scripts.AlwaysSucceeds (alwaysSucceedsScriptV2) import Ctl.Examples.SendsToken (contract) as SendsToken import Ctl.Examples.TxChaining (contract) as TxChaining +import Ctl.Internal.Contract.Monad (wrapQueryM) import Ctl.Internal.Plutus.Conversion.Address (toPlutusAddress) import Ctl.Internal.Plutus.Types.Transaction ( TransactionOutputWithRefScript(TransactionOutputWithRefScript) @@ -138,7 +138,6 @@ import Effect.Exception (error, throw) import Mote (group, skip, test) import Mote.Monad (mapTest) import Safe.Coerce (coerce) -import Test.Ctl.QueryM.AffInterface as QueryM.AffInterface import Test.Ctl.Fixtures ( cip25MetadataFixture1 , fullyAppliedScriptFixture @@ -156,6 +155,7 @@ import Test.Ctl.Plutip.Common (privateStakeKey) import Test.Ctl.Plutip.Contract.NetworkId as NetworkId import Test.Ctl.Plutip.Utils (getLockedInputs, submitAndLog) import Test.Ctl.Plutip.UtxoDistribution (checkUtxoDistribution) +import Test.Ctl.QueryM.AffInterface as QueryM.AffInterface import Test.Spec.Assertions (shouldEqual, shouldNotEqual, shouldSatisfy) suite :: TestPlanM PlutipTest Unit diff --git a/test/Types/Interval.purs b/test/Types/Interval.purs index d89cfc4cb3..b00da46ee4 100644 --- a/test/Types/Interval.purs +++ b/test/Types/Interval.purs @@ -13,13 +13,15 @@ import Aeson (class DecodeAeson, decodeJsonString, printJsonDecodeError) import Control.Monad.Error.Class (liftEither) import Control.Monad.Except (throwError) import Ctl.Internal.Helpers (liftedM) -import Ctl.Internal.QueryM.Ogmios (EraSummaries, SystemStart, RelativeTime, SlotLength) +import Ctl.Internal.QueryM.Ogmios + ( EraSummaries + , RelativeTime + , SlotLength + , SystemStart + ) import Ctl.Internal.Serialization.Address (Slot(Slot)) import Ctl.Internal.Test.TestPlanM (TestPlanM) import Ctl.Internal.Types.BigNum (fromInt) as BigNum -import Data.Function (on) -import Data.Foldable (maximumBy) -import Data.Newtype (unwrap) import Ctl.Internal.Types.Interval ( Interval , POSIXTime(POSIXTime) @@ -40,7 +42,10 @@ import Ctl.Internal.Types.Interval import Data.Bifunctor (lmap) import Data.BigInt (fromInt, fromString) as BigInt import Data.Either (Either(Left, Right), either) +import Data.Foldable (maximumBy) +import Data.Function (on) import Data.Maybe (fromJust) +import Data.Newtype (unwrap) import Data.Traversable (traverse_) import Effect (Effect) import Effect.Exception (error) @@ -53,7 +58,7 @@ import Test.QuickCheck (Result(Success, Failed), quickCheck, ()) import Test.QuickCheck.Combinators ((&=&)) import Test.Spec.Assertions (shouldEqual) -type Context = +type Context = { slotReference :: { slot :: Slot, time :: RelativeTime } , slotLength :: SlotLength , systemStart :: SystemStart @@ -100,14 +105,19 @@ eraSummariesFixture = slotLengthFixture :: Effect SlotLength slotLengthFixture = do latestEraSummary <- liftedM (error "Could not get EraSummary") do - map unwrap <<< (maximumBy (compare `on` (unwrap >>> _.start >>> unwrap >>> _.slot))) <<< unwrap <$> eraSummariesFixture + map unwrap + <<< (maximumBy (compare `on` (unwrap >>> _.start >>> unwrap >>> _.slot))) + <<< unwrap <$> eraSummariesFixture pure $ _.slotLength $ unwrap $ _.parameters $ latestEraSummary slotReferenceFixture :: Effect { slot :: Slot, time :: RelativeTime } slotReferenceFixture = do latestEraSummary <- liftedM (error "Could not get EraSummary") do - map unwrap <<< (maximumBy (compare `on` (unwrap >>> _.start >>> unwrap >>> _.slot))) <<< unwrap <$> eraSummariesFixture - pure $ (\{slot, time} -> {slot, time}) $ unwrap $ _.start $ latestEraSummary + map unwrap + <<< (maximumBy (compare `on` (unwrap >>> _.start >>> unwrap >>> _.slot))) + <<< unwrap <$> eraSummariesFixture + pure $ (\{ slot, time } -> { slot, time }) $ unwrap $ _.start $ + latestEraSummary systemStartFixture :: Effect SystemStart systemStartFixture = @@ -189,12 +199,16 @@ testPosixTimeToSlot ctx = do -> POSIXTime -> Effect Unit idTest transf posixTime = do - posixTimeToSlot ctx.slotReference ctx.slotLength ctx.systemStart posixTime >>= case _ of - Left err -> throwError $ error $ show err - Right slot -> do - ePosixTime <- slotToPosixTime ctx.slotReference ctx.slotLength ctx.systemStart slot - either (throwError <<< error <<< show) (shouldEqual $ transf posixTime) - ePosixTime + posixTimeToSlot ctx.slotReference ctx.slotLength ctx.systemStart posixTime + >>= case _ of + Left err -> throwError $ error $ show err + Right slot -> do + ePosixTime <- slotToPosixTime ctx.slotReference ctx.slotLength + ctx.systemStart + slot + either (throwError <<< error <<< show) + (shouldEqual $ transf posixTime) + ePosixTime testSlotToPosixTime :: Context -> Effect Unit testSlotToPosixTime ctx = do @@ -215,11 +229,14 @@ testSlotToPosixTime ctx = do where idTest :: Slot -> Effect Unit idTest slot = do - slotToPosixTime ctx.slotReference ctx.slotLength ctx.systemStart slot >>= case _ of - Left err -> throwError $ error $ show err - Right posixTime -> do - eSlot <- posixTimeToSlot ctx.slotReference ctx.slotLength ctx.systemStart posixTime - either (throwError <<< error <<< show) (shouldEqual slot) eSlot + slotToPosixTime ctx.slotReference ctx.slotLength ctx.systemStart slot >>= + case _ of + Left err -> throwError $ error $ show err + Right posixTime -> do + eSlot <- posixTimeToSlot ctx.slotReference ctx.slotLength + ctx.systemStart + posixTime + either (throwError <<< error <<< show) (shouldEqual slot) eSlot mkSlot :: Int -> Slot mkSlot = Slot <<< BigNum.fromInt @@ -238,11 +255,12 @@ testPosixTimeToSlotError ctx = do -> PosixTimeToSlotError -> Effect Unit errTest posixTime expectedErr = do - posixTimeToSlot ctx.slotReference ctx.slotLength ctx.systemStart posixTime >>= case _ of - Left err -> err `shouldEqual` expectedErr - Right _ -> - throwError $ error $ "Test should have failed giving: " <> show - expectedErr + posixTimeToSlot ctx.slotReference ctx.slotLength ctx.systemStart posixTime + >>= case _ of + Left err -> err `shouldEqual` expectedErr + Right _ -> + throwError $ error $ "Test should have failed giving: " <> show + expectedErr -- All this test can be generalized to use : -- forall (a::Type) . Arbitrary a => Ord a => Ring a From 69d73c19628ce62ed75b0bcc08bd7f1080902d9b Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Thu, 1 Dec 2022 11:50:57 +0000 Subject: [PATCH 030/373] Remove references to ConfigParams --- src/Internal/Contract/ApplyArgs.purs | 2 +- src/Internal/Test/E2E/Route.purs | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Internal/Contract/ApplyArgs.purs b/src/Internal/Contract/ApplyArgs.purs index b4d5567c94..7f6caa744e 100644 --- a/src/Internal/Contract/ApplyArgs.purs +++ b/src/Internal/Contract/ApplyArgs.purs @@ -50,7 +50,7 @@ applyArgs script args = $ ClientOtherError "The `ctl-server` service is required to call `applyArgs`. Please \ - \provide a `Just` value in `ConfigParams.ctlServerConfig` and make \ + \provide a `Just` value in `ContractParams.ctlServerConfig` and make \ \sure that the `ctl-server` service is running and available at the \ \provided host and port. The `ctl-server` packages can be obtained \ \from `overlays.ctl-server` defined in CTL's flake. Please see \ diff --git a/src/Internal/Test/E2E/Route.purs b/src/Internal/Test/E2E/Route.purs index be5274c84a..723307e8a9 100644 --- a/src/Internal/Test/E2E/Route.purs +++ b/src/Internal/Test/E2E/Route.purs @@ -54,7 +54,7 @@ import Effect.Exception (error, throw) -- | A name of some particular test. Used in the URL type E2ETestName = String --- | A name of some particular E2E test environment (`ConfigParams` and possible +-- | A name of some particular E2E test environment (`ContractParams` and possible -- | CIP-30 mock). Used in the URL for routing type E2EConfigName = String From cc92ac1dda23219db596983e2814b62c2c12a76d Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Thu, 1 Dec 2022 14:22:12 +0000 Subject: [PATCH 031/373] Cleanup queryHandle, use getNetworkId in staking test --- src/Internal/Contract/QueryHandle.purs | 16 ---------------- test/Plutip/Staking.purs | 4 ++-- 2 files changed, 2 insertions(+), 18 deletions(-) diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs index 656a6d39eb..16b125b927 100644 --- a/src/Internal/Contract/QueryHandle.purs +++ b/src/Internal/Contract/QueryHandle.purs @@ -69,22 +69,6 @@ type QueryHandle = , submitTx :: Transaction -> Aff (Maybe TransactionHash) , getTxByHash :: TransactionHash -> Aff (Maybe Transaction) , evaluateTx :: Transaction -> Ogmios.AdditionalUtxoSet -> Aff TxEvaluationR - - -- getTxByHash - -- bf: /txs/{hash} - -- ctl: requires ODC - -- Not a problem for now - -- submitTx - -- evaluateTx - -- chainTip - -- getProtocolParameters - -- this gets done early on - -- perhaps genesis/systemStart should be too - -- getConstantParameters - -- systemStart - -- currentEpoch - -- we need era summaries start + end, and the era summaries slot length - -- ogmios has eraSummaries, BF has epochs for start + end, and genesis for slot length (idk if this is safe) } getQueryHandle :: Contract QueryHandle diff --git a/test/Plutip/Staking.purs b/test/Plutip/Staking.purs index 8dee5929d6..e99e7f298f 100644 --- a/test/Plutip/Staking.purs +++ b/test/Plutip/Staking.purs @@ -10,6 +10,7 @@ import Contract.Address , PubKeyHash(PubKeyHash) , ownPaymentPubKeysHashes , ownStakePubKeysHashes + , getNetworkId ) import Contract.Credential (Credential(ScriptCredential)) import Contract.Hashing (plutusScriptStakeValidatorHash, publicKeyHash) @@ -65,7 +66,6 @@ import Contract.TxConstraints import Contract.Value (lovelaceValueOf) import Contract.Wallet (withKeyWallet) import Contract.Wallet.Key (keyWalletPrivateStakeKey, publicKeyFromPrivateKey) -import Control.Monad.Reader (asks) import Ctl.Examples.AlwaysSucceeds (alwaysSucceedsScript) import Ctl.Internal.Test.TestPlanM (TestPlanM, interpretWithConfig) import Data.Array (head) @@ -255,7 +255,7 @@ suite = do privateStakeKey <- liftM (error "Failed to get private stake key") $ keyWalletPrivateStakeKey alice - networkId <- asks _.networkId + networkId <- getNetworkId let poolOperator = PoolPubKeyHash $ publicKeyHash $ publicKeyFromPrivateKey (unwrap privateStakeKey) From 3731e7991ecf574ba5ca6eadbf43d9b0068a17fc Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Thu, 1 Dec 2022 21:45:33 +0000 Subject: [PATCH 032/373] Update docs to not reference old types, and to mention the possibility of multiple backends. Remove dead code --- doc/e2e-testing.md | 8 +- doc/faq.md | 2 + doc/getting-started.md | 33 +++---- doc/importing-scripts.md | 2 +- doc/plutip-testing.md | 6 +- doc/plutus-comparison.md | 8 +- doc/runtime.md | 19 ++-- doc/side-by-side-ctl-plutus-comparison.md | 75 +++++----------- doc/test-plan.md | 13 ++- src/Internal/QueryM.purs | 24 ++---- src/Internal/QueryM/DatumCacheWsp.purs | 100 ++-------------------- src/Internal/QueryM/Ogmios.purs | 34 +------- test/Ogmios/Aeson.purs | 2 - test/OgmiosDatumCache.purs | 26 +----- 14 files changed, 79 insertions(+), 273 deletions(-) diff --git a/doc/e2e-testing.md b/doc/e2e-testing.md index b3c866f69d..cd6bd78304 100644 --- a/doc/e2e-testing.md +++ b/doc/e2e-testing.md @@ -212,7 +212,7 @@ main = do -- Serves the appropriate `Contract` with e2eTestHooks route configs tests -configs :: Map E2EConfigName (ConfigParams () /\ Maybe WalletMock) +configs :: Map E2EConfigName (ContractParams /\ Maybe WalletMock) configs = Map.fromFoldable [ "nami" /\ testnetNamiConfig /\ Nothing , "gero" /\ testnetGeroConfig /\ Nothing @@ -225,7 +225,7 @@ configs = Map.fromFoldable , "lode-mock" /\ testnetLodeConfig /\ Just MockLode ] -tests :: Map E2ETestName (Contract () Unit) +tests :: Map E2ETestName (Contract Unit) tests = Map.fromFoldable [ "Contract" /\ Scaffold.contract -- Add more `Contract`s here @@ -282,13 +282,13 @@ It's possible to run headless browser tests on top of a temporary plutip cluster To do that, it's enough to define a config name that: -- uses a `ConfigParams` value with `networkId` set to `MainnetId`. +- uses a `ContractParams` value with `networkId` set to `MainnetId`. - Specifies a wallet mock (e.g. `MockNami`) E.g.: ```purescript -wallets :: Map E2EConfigName (ConfigParams () /\ Maybe WalletMock) +wallets :: Map E2EConfigName (ContractParams /\ Maybe WalletMock) wallets = Map.fromFoldable [ "plutip-nami-mock" /\ mainnetNamiConfig /\ Just MockNami , "plutip-gero-mock" /\ mainnetGeroConfig /\ Just MockGero diff --git a/doc/faq.md b/doc/faq.md index 141d38f47b..f764cea75e 100644 --- a/doc/faq.md +++ b/doc/faq.md @@ -31,6 +31,8 @@ Local `cardano-node` lags behind the global network time, so when using time con To do anything time-related, it's best to rely on local node chain tip time, instead of using `Date.now()` as a source of truth. This is often a requirement when using `mustValidateIn`, because the node will reject the transaction if it appears too early. +TODO Rethink these Time related questions + ### Q: Time/slot conversion functions return `Nothing`. Why is that? Time/slot conversion functions depend on `eraSummaries` [Ogmios local state query](https://ogmios.dev/mini-protocols/local-state-query/), that returns era bounds and slotting parameters details, required for proper slot arithmetic. The most common source of the problem is that Ogmios does not return enough epochs into the future. diff --git a/doc/getting-started.md b/doc/getting-started.md index e9848e7a76..eabfc3e100 100644 --- a/doc/getting-started.md +++ b/doc/getting-started.md @@ -104,43 +104,36 @@ main = Contract.Monad.launchAff_ do ### Making the `ContractEnv` -The `ContractEnv` type contains configuration values and websocket connections that are required to execute contracts written in CTL. The users should not construct it directly - `Contract.Config.ConfigParams` should be used instead. +The `ContractEnv` type contains configuration values and websocket connections that are required to execute contracts written in CTL. The users should not construct it directly - `Contract.Config.ContractParams` should be used instead. For local development and testing, we provide `Contract.Config.testnetConfig` where all service hosts are set to `localhost` and the `logLevel` is set to `Trace`. -It is **not recommended to directly construct or manipulate a `ContractEnv` yourself** as the process of making a new config initializes websockets. Instead, use `Contract.Monad.ConfigParams` with `runContract`. - -As explained in the [Plutus/PAB comparison](plutus-comparison.md#the-contract-type), the `ContractEnv` environment uses Purescript's extensible records. This can also be done via `ConfigParams`, which holds an `extraConfig` field corresponding to the `Row Type` argument to `ContractEnv` (and by extension, `Contract`). +It is **not recommended to directly construct or manipulate a `ContractEnv` yourself** as the process of making a new config initializes websockets. Instead, use `Contract.Monad.ContractParams` with `runContract`. A special `Contract.Config.WalletSpec` type is used to specify which wallet to use during the `Contract` lifetime. -An example of building a `Contract` via `ConfigParams` is as follows: +An example of building a `Contract` via `ContractParams` is as follows: ```purescript main :: Effect Unit main = Contract.Monad.launchAff_ do -- we re-export this for you let - (config :: ConfigParams (apiKey :: String)) = - { ogmiosConfig: defaultOgmiosWsConfig - , datumCacheConfig: defaultDatumCacheWsConfig + (config :: ContractParams) = + { backendParams: mkSingletonBackendParams $ CtlBackendParams + { ogmiosConfig: defaultOgmiosWsConfig + , odcConfig: defaultDatumCacheWsConfig + , kupoConfig: defaultKupoServerConfig + } , ctlServerConfig: defaultServerConfig , networkId: TestnetId , logLevel: Trace - , extraConfig: { apiKey: "foo" } , walletSpec: Just ConnectToNami , customLogger: Nothing } - runContract config someContractWithApiKeyInEnv - --- As we provided `(apiKey :: String)` to the `extraConfig` above, we can now --- access it in the reader environment of any `Contract` actions call using --- `askConfig`. -someContractWithApiKeyInEnv - :: forall. Contract (apiKey :: String) Unit - -- We can also retain polymorphism by adding `| r` to the row type: - -- :: forall (r :: Row Type). Contract (apiKey :: String | r) Unit -someContractWithApiKeyInEnv = do - { apiKey } <- askConfig + runContract config someContract + +someContract :: Contract Unit +someContract = do ... ``` diff --git a/doc/importing-scripts.md b/doc/importing-scripts.md index 7f07787957..8b02dbe5a6 100644 --- a/doc/importing-scripts.md +++ b/doc/importing-scripts.md @@ -62,7 +62,7 @@ And on the purescript side, the script can be loaded like so: ```purescript foreign import myscript :: String -parseValidator :: Contract () Validator +parseValidator :: Contract Validator parseValidator = liftMaybe (error "Error decoding myscript") do envelope <- decodeTextEnvelope myscript Validator <$> Contract.TextEnvelope.plutusScriptV1FromEnvelope envelope diff --git a/doc/plutip-testing.md b/doc/plutip-testing.md index af5c93a343..98c9adf36b 100644 --- a/doc/plutip-testing.md +++ b/doc/plutip-testing.md @@ -43,7 +43,7 @@ runPlutipContract . UtxoDistribution distr wallets => PlutipConfig -> distr - -> (wallets -> Contract () a) + -> (wallets -> Contract a) -> Aff a ``` @@ -111,10 +111,10 @@ withWallets :: forall (distr :: Type) (wallets :: Type) . UtxoDistribution distr wallets => distr - -> (wallets -> Contract () Unit) + -> (wallets -> Contract Unit) -> PlutipTest -noWallet :: Contract () Unit -> PlutipTest +noWallet :: Contract Unit -> PlutipTest noWallet test = withWallets unit (const test) ``` diff --git a/doc/plutus-comparison.md b/doc/plutus-comparison.md index 4608b6c75e..9b237fd2d8 100644 --- a/doc/plutus-comparison.md +++ b/doc/plutus-comparison.md @@ -32,13 +32,13 @@ Both CTL and Plutus define `Contract` monads for constructing, balancing, and su **CTL**: ```purescript -newtype Contract (r :: Row Type) (a :: Type) = Contract (QueryMExtended r a) +newtype Contract (a :: Type) = Contract (ReaderT ContractEnv Aff a) ``` where -- `QueryMExtended` is an internal monad transformer stack based on `ReaderT` over `Aff` (Purescript's monad for asynchronous effects, with no Haskell analogue). -- `r` extends the record serving as the reader environment +- `ContractEnv` is an internal type containing references to various backend services, configurations and ledger constants +- `Aff` (Purescript's monad for asynchronous effects, with no Haskell analogue, the closest being IO). **Plutus**: @@ -54,7 +54,7 @@ where As this direct comparison illustrates, CTL's `Contract` is significantly simpler than Plutus'. Importantly, CTL's `Contract` **allows for arbitrary effects**. This makes `Writer` capabilities redundant in CTL, for instance, as all communication between `Contract`s can be done in a more direct manner (e.g. logging or HTTP calls). -CTL also has no concept of a "schema" for `Contract`s as there is no equivalent of an endpoint as in PAB. That is, effects written in `Contract` are not activated in some way and can instead be called normally from Purescript code. Note that despite the similar appearance of the kind signatures above, where `Row Type` appears in the signature of both `Contract`s, they are practically and conceptually unrelated. The extensible record contained in CTL's `Contract` allows users to easily extend the reader environment in which their contracts execute. For instance, you may wish to expose some global state across all of your contracts, perhaps a unique `CurrencySymbol` that will be created in one contract and read by several others. Instead of threading this state throughout as parameters, you could use a `Ref (Maybe CurrencySymbol)` (`Ref`s are analogous to Haskell's `IORef`) and write your contracts with types signatures similar to `forall (r :: Row Type). Contract (cs :: Ref (Maybe CurrencySymbol) | r) Unit`. `cs` would then be accessible from your contracts using normal `MonadReader` methods (or more precisely those of `MonadAsk` in the case of Purescript). +CTL also has no concept of a "schema" for `Contract`s as there is no equivalent of an endpoint as in PAB. That is, effects written in `Contract` are not activated in some way and can instead be called normally from Purescript code. For library users, CTL's `Contract` is less opaque than Plutus'. The `Contract` newtype can be unwrapped to expose the inner monad transformer stack, whose internal structure will be immediately recognizable to developers familiar `transformers`-style stacks. `Contract` also has instances for various typeclasses, making it possible to write `mtl`-style effects. diff --git a/doc/runtime.md b/doc/runtime.md index cd9ec2dd13..ddbab0a648 100644 --- a/doc/runtime.md +++ b/doc/runtime.md @@ -1,16 +1,17 @@ # CTL's Runtime Dependencies -In order to run CTL's `Contract` effects, several services are required. These can be configured through a `ContractEnv` that holds websocket connections, information about server hosts/ports, and other requisite information. +In order to run CTL's `Contract` effects, several services are required. These can be configured through a `ContractEnv` that holds websocket connections, information about server hosts/ports, and other requisite information. Which services are required depends on which backend you are using. **Table of Contents** -- [Current services](#current-services) -- [Using NixOS module](#using-nixos-module) -- [Using CTL's `runtime` overlay](#using-ctl-s--runtime--overlay) -- [Changing network configurations](#changing-network-configurations) +- [CTL Backend](#ctl-backend) + + [Using NixOS module](#using-nixos-module) + + [Using CTL's `runtime` overlay](#using-ctl-s--runtime--overlay) + + [Changing network configurations](#changing-network-configurations) +- [Blockfrost Backend](#blockfrost-backend) - [Wallet requirements](#wallet-requirements) -### Current services +## CTL Backend The services that are currently **required** are: @@ -58,7 +59,11 @@ inputs.cardano-transaction-lib.inputs.cardano-configurations.follows = "..."; When changing networks, make sure that `network.magic` is correctly synchronized with value in config (see `protocolConsts.protocolMagic` in `byron.json`). -### Wallet requirements +## Blockfrost Backend + +TODO + +## Wallet requirements In order to run most `Contract` actions in the browser, **you must use one of the supported wallets**. The following steps must be taken to ensure that you can run CTL contracts: diff --git a/doc/side-by-side-ctl-plutus-comparison.md b/doc/side-by-side-ctl-plutus-comparison.md index 204fb7da0c..fe0beaedc0 100644 --- a/doc/side-by-side-ctl-plutus-comparison.md +++ b/doc/side-by-side-ctl-plutus-comparison.md @@ -12,45 +12,16 @@ both of them. The current definition of `Contract` in CTL is : ```PureScript -type QueryConfig = - { -- configuration options used on initialization to construct `QueryRuntime` +type ContractEnv = + { -- Internal type holding holding connections to backend services, ledger + -- constants which are fixed during contract evaluation, and user defined + -- values like the choice of wallet and logger. } -type QueryRuntime = - { -- Part of `QueryEnv` that is reusable between contracts (internal type) - } - --- | `QueryEnv` contains everything needed for `QueryM` to run. -type QueryEnv (r :: Row Type) = - { config :: QueryConfig - , runtime :: QueryRuntime - , extraConfig :: { | r } - } - -type DefaultQueryEnv = QueryEnv () - -type QueryM (a :: Type) = ReaderT DefaultQueryEnv (LoggerT Aff) a - -type QueryMExtended (r :: Row Type) (a :: Type) = ReaderT (QueryEnv r) - (LoggerT Aff) - a - -newtype Contract (r :: Row Type) (a :: Type) = Contract (QueryMExtended r a) -``` - -In CTL we have a general environment type - -```PureScript -newtype ContractEnv (r :: Row Type) = ContractEnv (QueryEnv r) +newtype Contract (a :: Type) = Contract (ReaderT ContractEnv Aff a) ``` -it stores the needed parameters to connect to an `Ogmios` server, -wallets and more things, this configuration uses the PureScript native -[row polymorphism](https://en.wikipedia.org/wiki/Row_polymorphism) to make it extensible for both CTL developers and users. -You can find a little discussion about row polymorphism [here](https://hgiasac.github.io/posts/2018-11-18-Record-Row-Type-and-Row-Polymorphism.html). - -The parameter `a` as in `Plutus` refers to a return value wrapped by `Contract`. - +The parameter `a`, as in `Plutus` also, refers to a return value wrapped by `Contract`. Note that in Plutus right now we have the following definition for `Contract`: @@ -73,18 +44,11 @@ The Plutus `Contract` environment is specialized to just two values and is fixed Also, Plutus `Contract` uses a phantom type `s` to contract schema and parameters `w` for a writer and `e` for errors. In the case of CTL we don't have the contract schema parameter or the writer -parameter since CTL definition allows performing arbitrary effects. -This is possible since the definition of `LoggerT` is: - -```PureScript -newtype LoggerT m a = LoggerT ((Message -> m Unit) -> m a) -``` - -The use of `Aff` inside `LoggerT` allows us to use asynchronous effects -inside the logger. In particular, this has a similar effect as using `IO` -in Haskell, although isn't the same. Of course we can log to console -using just `Aff` but `LoggerT` provide us with structured logging. - +parameter since CTL definition allows performing arbitrary effects, from the +use of `Aff`. `Aff` allows us to use asynchronous effects, which has a similar +effect as using `IO` in Haskell, although isn't the same. While most effectful +actions are defined directly in terms of those provided by `Aff`, logging is +provided by a configurable logger stored in `ContractEnv`. ## Contract comparison @@ -120,7 +84,7 @@ import Contract.TxConstraints (TxConstraints) buildBalanceSignAndSubmitTx :: ScriptLookups PlutusData -> TxConstraints Unit Unit - -> Contract () TransactionHash + -> Contract TransactionHash buildBalanceSignAndSubmitTx lookups constraints = do ubTx <- liftedE $ mkUnbalancedTx lookups constraints bsTx <- signTransaction =<< liftedE (balanceTx ubTx) @@ -236,7 +200,7 @@ import Contract.TxConstraints as Constraints import Contract.Prelude import Data.BigInt as BigInt -give :: ValidatorHash -> Contract () TransactionHash +give :: ValidatorHash -> Contract TransactionHash give vhash = do let constraints :: Constraints.TxConstraints Unit Unit @@ -291,11 +255,12 @@ module Contract.Utxos ... . . . --- | This module defines query functionality via Ogmios to get utxos. --- | Gets utxos at an (internal) `Address` in terms of a Plutus Address`. --- | Results may vary depending on `Wallet` type. See `QueryM` for more details --- | on wallet variance. -utxosAt :: forall (r :: Row Type). Address -> Contract r (Maybe UtxoMap) +-- | Queries for utxos at the given Plutus `Address`. +utxosAt + :: forall (address :: Type) + . PlutusAddress address + => address + -> Contract UtxoMap ``` @@ -313,7 +278,7 @@ grab :: ValidatorHash -> Validator -> TransactionHash - -> Contract () Unit + -> Contract Unit grab vhash validator txId = do let scriptAddress = scriptHashAddress vhash Nothing utxos <- fromMaybe Map.empty <$> utxosAt scriptAddress diff --git a/doc/test-plan.md b/doc/test-plan.md index 35b48bd48c..71b1f4d2aa 100644 --- a/doc/test-plan.md +++ b/doc/test-plan.md @@ -144,7 +144,7 @@ In the case of CTL's constraints/lookups API, in order to be qualified as "cover - **Note**: For implemented transaction features _not_ supported by our current constraints/lookups implementation, such as the features introduced by CIPs 31-33 (inline datums, etc...), modifying the transaction directly is also acceptable - balance the transaction while calculating sufficient fees/execution units - sign the transaction using the attached wallet (either a browser-based light wallet or our own `KeyWallet`) -- submit the transaction to the node via Ogmios +- submit the transaction to the node The functionality to achieve the above **must** be taken from our public API. That is, we must consume the public interface directly in all example contracts rather than importing internal CTL modules (anything outside of `Contract.*`). @@ -173,11 +173,11 @@ module Examples.MintsToken import Contract.Prelude -import Contract.Config (ConfigParams) +import Contract.Config (ContractParams) import Contract.Log (logInfo') import Contract.Monad (launchAff_) -example :: ConfigParams () -> Effect Unit +example :: ContractParams -> Effect Unit example cfg = launchAff_ do runContract cfg do logInfo' "Running Examples.MintsToken" @@ -204,7 +204,7 @@ Although such parsers are included implicitly in the example contracts defined a - **Integration tests** - These tests are run against a full runtime and make real requests to different components - These are intended to augment the unit tests described above and are a step below our full example contracts - - These can either call effects from the `Contract` interface or its underlying `QueryM` monad stack + - These can be effects from the `Contract` interface and the underlying backends #### Required parsing tests @@ -212,7 +212,6 @@ Currently, we require parsing tests for the following data structures, organized - Ogmios - [x] `ChainTipQR` - - [x] `UtxoQR` - [x] `CurrentEpoch` - [x] `SystemStart` - [x] `EraSummaries` @@ -220,8 +219,6 @@ Currently, we require parsing tests for the following data structures, organized - [x] `TxEvaluationR` - [x] `SubmitTxR` - `ogmios-datum-cache` - - [x] `GetDatumByHashR` - - [x] `GetDatumsByHashesR` - [x] `GetTxByHashR` - `cardano-serialization-lib` - `Transaction` @@ -233,3 +230,5 @@ Currently, we require parsing tests for the following data structures, organized - `TransactionWitnessSet` - [x] Serialization - [x] Deserialization + +TODO: Kupo and Blockfrost diff --git a/src/Internal/QueryM.purs b/src/Internal/QueryM.purs index 53ea3f5933..90fc8c3d67 100644 --- a/src/Internal/QueryM.purs +++ b/src/Internal/QueryM.purs @@ -104,9 +104,7 @@ import Ctl.Internal.JsWebSocket , _wsSend ) import Ctl.Internal.QueryM.DatumCacheWsp - ( GetDatumByHashR - , GetDatumsByHashesR - , GetTxByHashR + ( GetTxByHashR ) import Ctl.Internal.QueryM.DatumCacheWsp as DcWsp import Ctl.Internal.QueryM.Dispatcher @@ -166,9 +164,7 @@ import Ctl.Internal.Serialization.Address (NetworkId) import Ctl.Internal.Types.ByteArray (byteArrayToHex) import Ctl.Internal.Types.CborBytes (CborBytes) import Ctl.Internal.Types.Chain as Chain -import Ctl.Internal.Types.Datum (DataHash) import Ctl.Internal.Types.Scripts (PlutusScript) -import Ctl.Internal.Types.Transaction (TransactionInput) import Ctl.Internal.Types.UsedTxOuts (UsedTxOuts, newUsedTxOuts) import Ctl.Internal.Wallet ( Wallet @@ -784,9 +780,7 @@ mkDatumCacheWebSocketLens logger = do let datumCacheWebSocket :: JsWebSocket -> DatumCacheWebSocket datumCacheWebSocket ws = WebSocket ws - { getDatumByHash: mkListenerSet dispatcher pendingRequests - , getDatumsByHashes: mkListenerSet dispatcher pendingRequests - , getTxByHash: mkListenerSet dispatcher pendingRequests + { getTxByHash: mkListenerSet dispatcher pendingRequests } resendPendingRequests :: JsWebSocket -> Effect Unit @@ -812,11 +806,7 @@ mkOgmiosWebSocketLens logger datumCacheWebSocketRef = do let ogmiosWebSocket :: JsWebSocket -> OgmiosWebSocket ogmiosWebSocket ws = WebSocket ws - { utxo: - mkListenerSet dispatcher pendingRequests - , utxosAt: - mkListenerSet dispatcher pendingRequests - , chainTip: + { chainTip: mkListenerSet dispatcher pendingRequests , evaluate: mkListenerSet dispatcher pendingRequests @@ -864,9 +854,7 @@ mkOgmiosWebSocketLens logger datumCacheWebSocketRef = do -------------------------------------------------------------------------------- type OgmiosListeners = - { utxo :: ListenerSet TransactionInput Ogmios.UtxoQR - , utxosAt :: ListenerSet Ogmios.OgmiosAddress Ogmios.UtxoQR - , chainTip :: ListenerSet Unit Ogmios.ChainTipQR + { chainTip :: ListenerSet Unit Ogmios.ChainTipQR , submit :: SubmitTxListenerSet , evaluate :: ListenerSet (CborBytes /\ AdditionalUtxoSet) Ogmios.TxEvaluationR @@ -882,9 +870,7 @@ type OgmiosListeners = } type DatumCacheListeners = - { getDatumByHash :: ListenerSet DataHash GetDatumByHashR - , getDatumsByHashes :: ListenerSet (Array DataHash) GetDatumsByHashesR - , getTxByHash :: ListenerSet TxHash GetTxByHashR + { getTxByHash :: ListenerSet TxHash GetTxByHashR } -- convenience type for adding additional query types later diff --git a/src/Internal/QueryM/DatumCacheWsp.purs b/src/Internal/QueryM/DatumCacheWsp.purs index a91654eabf..eb5ac13bc6 100644 --- a/src/Internal/QueryM/DatumCacheWsp.purs +++ b/src/Internal/QueryM/DatumCacheWsp.purs @@ -1,16 +1,10 @@ module Ctl.Internal.QueryM.DatumCacheWsp ( DatumCacheMethod - ( GetDatumByHash - , GetDatumsByHashes - , GetTxByHash + ( GetTxByHash ) - , GetDatumByHashR(GetDatumByHashR) - , GetDatumsByHashesR(GetDatumsByHashesR) , GetTxByHashR(GetTxByHashR) , WspFault(WspFault) , faultToString - , getDatumByHashCall - , getDatumsByHashesCall , getTxByHashCall , JsonWspRequest , JsonWspResponse @@ -22,29 +16,21 @@ import Aeson ( class DecodeAeson , class EncodeAeson , Aeson - , JsonDecodeError(TypeMismatch) - , caseAesonArray - , caseAesonObject + , JsonDecodeError , decodeAeson , getNestedAeson , stringifyAeson - , (.:) ) import Control.Alt ((<|>)) import Ctl.Internal.Base64 (Base64String) import Ctl.Internal.QueryM.JsonWsp (JsonWspCall, mkCallType) import Ctl.Internal.QueryM.UniqueId (ListenerId) import Ctl.Internal.Types.ByteArray (ByteArray, byteArrayToHex) -import Ctl.Internal.Types.Datum (DataHash, Datum) -import Data.Either (Either(Left, Right)) +import Data.Either (Either) import Data.Generic.Rep (class Generic) -import Data.Map (Map) -import Data.Map as Map -import Data.Maybe (Maybe(Nothing, Just)) -import Data.Newtype (class Newtype, unwrap, wrap) +import Data.Maybe (Maybe(Nothing)) +import Data.Newtype (class Newtype) import Data.Show.Generic (genericShow) -import Data.Traversable (traverse) -import Data.Tuple.Nested (type (/\), (/\)) newtype WspFault = WspFault Aeson @@ -70,66 +56,6 @@ type JsonWspResponse = , reflection :: ListenerId } -newtype GetDatumByHashR = GetDatumByHashR (Maybe Datum) - -derive instance Newtype GetDatumByHashR _ -derive instance Generic GetDatumByHashR _ - -instance Show GetDatumByHashR where - show = genericShow - -instance DecodeAeson GetDatumByHashR where - decodeAeson r = GetDatumByHashR <$> - let - datumFound :: Either JsonDecodeError (Maybe Datum) - datumFound = - Just <$> (decodeAeson =<< getNestedAeson r [ "DatumFound", "value" ]) - - datumNotFound :: Either JsonDecodeError (Maybe Datum) - datumNotFound = - Nothing <$ getNestedAeson r [ "DatumNotFound" ] - in - datumFound <|> datumNotFound - -newtype GetDatumsByHashesR = GetDatumsByHashesR - (Map DataHash (Either String Datum)) - -derive instance Newtype GetDatumsByHashesR _ -derive instance Generic GetDatumsByHashesR _ - -instance Show GetDatumsByHashesR where - show = genericShow - -instance DecodeAeson GetDatumsByHashesR where - decodeAeson r = - let - decodeDatumArray - :: Aeson -> Either JsonDecodeError (Map DataHash (Either String Datum)) - decodeDatumArray = - caseAesonArray (Left $ TypeMismatch "Array") - $ (map Map.fromFoldable) <<< traverse decodeDatum - - decodeDatum - :: Aeson -> Either JsonDecodeError (DataHash /\ Either String Datum) - decodeDatum obj = caseAesonObject (Left $ TypeMismatch "Object") - (\o -> (/\) <$> map wrap (o .: "hash") <*> decodeValueOption obj) - obj - - decodeValueOption - :: Aeson -> Either JsonDecodeError (Either String Datum) - decodeValueOption aes = - do - options <- (pure <$> getNestedAeson aes [ "value", "Right" ]) - <|> (Left <$> getNestedAeson aes [ "value", "Left", "error" ]) - case options of - Left x -> pure $ Left $ show x - Right x -> pure <$> decodeAeson x - - in - map GetDatumsByHashesR <<< decodeDatumArray =<< getNestedAeson - r - [ "value" ] - -- TODO -- This should be changed to `GetTxByHashR Transaction` once we support `getTxById` -- @@ -157,9 +83,7 @@ instance DecodeAeson GetTxByHashR where -- TODO: delete data DatumCacheMethod - = GetDatumByHash - | GetDatumsByHashes - | GetTxByHash + = GetTxByHash derive instance Eq DatumCacheMethod @@ -168,20 +92,8 @@ instance Show DatumCacheMethod where datumCacheMethodToString :: DatumCacheMethod -> String datumCacheMethodToString = case _ of - GetDatumByHash -> "GetDatumByHash" - GetDatumsByHashes -> "GetDatumsByHashes" GetTxByHash -> "GetTxByHash" -getDatumByHashCall :: JsonWspCall DataHash GetDatumByHashR -getDatumByHashCall = mkDatumCacheCallType - GetDatumByHash - ({ hash: _ } <<< byteArrayToHex <<< unwrap) - -getDatumsByHashesCall :: JsonWspCall (Array DataHash) GetDatumsByHashesR -getDatumsByHashesCall = mkDatumCacheCallType - GetDatumsByHashes - ({ hashes: _ } <<< map (byteArrayToHex <<< unwrap)) - type TxHash = ByteArray getTxByHashCall :: JsonWspCall TxHash GetTxByHashR diff --git a/src/Internal/QueryM/Ogmios.purs b/src/Internal/QueryM/Ogmios.purs index bed7448c0f..961d535c00 100644 --- a/src/Internal/QueryM/Ogmios.purs +++ b/src/Internal/QueryM/Ogmios.purs @@ -66,9 +66,6 @@ module Ctl.Internal.QueryM.Ogmios , queryEraSummariesCall , queryProtocolParametersCall , querySystemStartCall - , queryUtxoCall - , queryUtxosAtCall - , queryUtxosCall , queryPoolParameters , queryDelegationsAndRewards , submitTxCall @@ -173,9 +170,8 @@ import Ctl.Internal.Types.Scripts , PlutusScript(PlutusScript) ) import Ctl.Internal.Types.TokenName (TokenName, getTokenName, mkTokenName) -import Ctl.Internal.Types.Transaction (TransactionHash, TransactionInput) import Ctl.Internal.Types.VRFKeyHash (VRFKeyHash(VRFKeyHash)) -import Data.Array (catMaybes, index, reverse, singleton) +import Data.Array (catMaybes, index, reverse) import Data.Array (head, length, replicate) as Array import Data.BigInt (BigInt) import Data.BigInt as BigInt @@ -276,34 +272,6 @@ queryDelegationsAndRewards = mkOgmiosCallType } } --- | Queries Ogmios for utxos at given addresses. --- | NOTE. querying for utxos by address is deprecated, should use output reference instead -queryUtxosCall :: JsonWspCall { utxo :: Array OgmiosAddress } UtxoQR -queryUtxosCall = mkOgmiosCallType - { methodname: "Query" - , args: { query: _ } - } - --- | Queries Ogmios for utxos at given address. --- | NOTE. querying for utxos by address is deprecated, should use output reference instead -queryUtxosAtCall :: JsonWspCall OgmiosAddress UtxoQR -queryUtxosAtCall = mkOgmiosCallType - { methodname: "Query" - , args: { query: _ } <<< { utxo: _ } <<< singleton - } - --- | Queries Ogmios for the utxo with the given output reference. -queryUtxoCall :: JsonWspCall TransactionInput UtxoQR -queryUtxoCall = mkOgmiosCallType - { methodname: "Query" - , args: { query: _ } <<< { utxo: _ } <<< singleton <<< renameFields <<< unwrap - } - where - renameFields - :: { transactionId :: TransactionHash, index :: UInt } - -> { txId :: TransactionHash, index :: UInt } - renameFields { transactionId: txId, index } = { txId, index } - type OgmiosAddress = String -------------------------------------------------------------------------------- diff --git a/test/Ogmios/Aeson.purs b/test/Ogmios/Aeson.purs index 66b9320b9a..a499f6a1bf 100644 --- a/test/Ogmios/Aeson.purs +++ b/test/Ogmios/Aeson.purs @@ -42,7 +42,6 @@ import Type.Proxy (Proxy(Proxy)) supported :: Array String supported = [ "chainTip" - , "utxo" , "currentEpoch" , "systemStart" , "eraSummaries" @@ -163,7 +162,6 @@ suite = group "Ogmios Aeson tests" do (Aeson.decodeAeson aeson :: _ a) case query of "chainTip" -> handle (Proxy :: _ O.ChainTipQR) - "utxo" -> handle (Proxy :: _ O.UtxoQR) "currentEpoch" -> handle (Proxy :: _ O.CurrentEpoch) "systemStart" -> handle (Proxy :: _ O.SystemStart) "eraSummaries" -> handle (Proxy :: _ O.EraSummaries) diff --git a/test/OgmiosDatumCache.purs b/test/OgmiosDatumCache.purs index d08d2b1b58..3a9077109e 100644 --- a/test/OgmiosDatumCache.purs +++ b/test/OgmiosDatumCache.purs @@ -8,16 +8,12 @@ import Aeson (caseAesonArray, decodeAeson, encodeAeson) import Contract.Address (ByteArray) import Control.Monad.Error.Class (class MonadThrow) import Ctl.Internal.Hashing (datumHash) -import Ctl.Internal.QueryM.DatumCacheWsp (GetDatumsByHashesR) import Ctl.Internal.Test.TestPlanM (TestPlanM) import Ctl.Internal.Types.Datum (Datum(Datum)) import Ctl.Internal.Types.PlutusData (PlutusData) import Data.Either (Either(Left, Right)) -import Data.Map as Map -import Data.Maybe (Maybe(Just)) import Data.Newtype (unwrap) import Data.Traversable (for_) -import Data.Tuple.Nested ((/\)) import Effect.Aff (Aff) import Effect.Class (class MonadEffect) import Effect.Exception (Error) @@ -27,31 +23,13 @@ import Test.Spec.Assertions (shouldEqual) suite :: TestPlanM (Aff Unit) Unit suite = group "Ogmios Datum Cache tests" $ do + -- TODO Move skip $ test "Plutus data samples should satisfy the Aeson roundtrip test (FIXME: \ \https://github.com/mlabs-haskell/purescript-aeson/issues/7)" plutusDataToFromAesonTest test "Plutus data samples should have a compatible hash" plutusDataHashingTest - test "GetDatumsByHashesR fixture parses and hashes properly" - getDatumsByHashesHashingTest - -readGetDatumsByHashesSample - :: forall (m :: Type -> Type) - . MonadEffect m - => m GetDatumsByHashesR -readGetDatumsByHashesSample = do - errEither <<< decodeAeson =<< readAeson - "./fixtures/test/ogmios-datum-cache/get-datums-by-hashes-samples.json" - -getDatumsByHashesHashingTest - :: forall (m :: Type -> Type) - . MonadEffect m - => MonadThrow Error m - => m Unit -getDatumsByHashesHashingTest = do - datums <- Map.toUnfoldable <<< unwrap <$> readGetDatumsByHashesSample - for_ (datums :: Array _) \(hash /\ datum) -> do - (datumHash <$> datum) `shouldEqual` Right (Just hash) + -- TODO Add GetTxByHash readPlutusDataSamples :: forall (m :: Type -> Type) From f48d0397de7d16665de480cf63017857dfa6bccd Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Thu, 1 Dec 2022 22:31:01 +0000 Subject: [PATCH 033/373] Formatting --- src/Internal/BalanceTx/BalanceTx.purs | 1 - src/Internal/QueryM/DatumCacheWsp.purs | 3 +-- test/OgmiosDatumCache.purs | 3 ++- test/Plutip/Staking.purs | 2 +- 4 files changed, 4 insertions(+), 5 deletions(-) diff --git a/src/Internal/BalanceTx/BalanceTx.purs b/src/Internal/BalanceTx/BalanceTx.purs index 1dffa88c08..2b7313ad93 100644 --- a/src/Internal/BalanceTx/BalanceTx.purs +++ b/src/Internal/BalanceTx/BalanceTx.purs @@ -164,7 +164,6 @@ balanceTxWithConstraints unbalancedTx constraintsBuilder = do utxos <- liftEitherContract $ parTraverse (queryHandle.utxosAt >>> liftAff >>> map hush) srcAddrs <#> traverse (note CouldNotGetUtxos) - >>> map (foldr Map.union Map.empty) -- merge all utxos into one map unbalancedCollTx <- diff --git a/src/Internal/QueryM/DatumCacheWsp.purs b/src/Internal/QueryM/DatumCacheWsp.purs index eb5ac13bc6..b6f9db8a45 100644 --- a/src/Internal/QueryM/DatumCacheWsp.purs +++ b/src/Internal/QueryM/DatumCacheWsp.purs @@ -82,8 +82,7 @@ instance DecodeAeson GetTxByHashR where txFound <|> txNotFound -- TODO: delete -data DatumCacheMethod - = GetTxByHash +data DatumCacheMethod = GetTxByHash derive instance Eq DatumCacheMethod diff --git a/test/OgmiosDatumCache.purs b/test/OgmiosDatumCache.purs index 3a9077109e..b763b26b74 100644 --- a/test/OgmiosDatumCache.purs +++ b/test/OgmiosDatumCache.purs @@ -29,7 +29,8 @@ suite = group "Ogmios Datum Cache tests" $ do \https://github.com/mlabs-haskell/purescript-aeson/issues/7)" plutusDataToFromAesonTest test "Plutus data samples should have a compatible hash" plutusDataHashingTest - -- TODO Add GetTxByHash + +-- TODO Add GetTxByHash readPlutusDataSamples :: forall (m :: Type -> Type) diff --git a/test/Plutip/Staking.purs b/test/Plutip/Staking.purs index e99e7f298f..eb528f7a43 100644 --- a/test/Plutip/Staking.purs +++ b/test/Plutip/Staking.purs @@ -8,9 +8,9 @@ import Prelude import Contract.Address ( PaymentPubKeyHash(PaymentPubKeyHash) , PubKeyHash(PubKeyHash) + , getNetworkId , ownPaymentPubKeysHashes , ownStakePubKeysHashes - , getNetworkId ) import Contract.Credential (Credential(ScriptCredential)) import Contract.Hashing (plutusScriptStakeValidatorHash, publicKeyHash) From 8ed023487fe855aeb63cb744a77d62f7ec93a706 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Thu, 1 Dec 2022 22:49:26 +0000 Subject: [PATCH 034/373] Update comment --- src/Internal/Contract.purs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Internal/Contract.purs b/src/Internal/Contract.purs index 986a561ced..a90d6d6244 100644 --- a/src/Internal/Contract.purs +++ b/src/Internal/Contract.purs @@ -14,7 +14,7 @@ getChainTip = do queryHandle <- getQueryHandle liftAff $ queryHandle.getChainTip --- | Returns the `ProtocolParameters` from the `QueryM` environment. +-- | Returns the `ProtocolParameters` from the environment. -- | Note that this is not necessarily the current value from the ledger. getProtocolParameters :: Contract Ogmios.ProtocolParameters getProtocolParameters = From 3eb0540a2173da5912b0d979f648564fc13fed72 Mon Sep 17 00:00:00 2001 From: Calum Sieppert Date: Thu, 1 Dec 2022 22:54:20 -0700 Subject: [PATCH 035/373] [WIP] Adding changes from #1073 on top of develop --- src/Contract/Transaction.purs | 1 + src/Internal/BalanceTx/ExUnitsAndMinFee.purs | 1 + src/Internal/Cardano/Types/Value.purs | 11 +- src/Internal/Deserialization/Error.purs | 24 ++- src/Internal/Deserialization/FromBytes.js | 17 +- src/Internal/Deserialization/FromBytes.purs | 148 ++++++---------- src/Internal/QueryM.purs | 3 +- src/Internal/QueryM/Ogmios.purs | 3 +- src/Internal/Serialization.js | 20 +-- src/Internal/Serialization.purs | 79 +++++---- src/Internal/Serialization/Address.purs | 1 + src/Internal/Serialization/AuxiliaryData.js | 2 +- src/Internal/Serialization/AuxiliaryData.purs | 9 +- src/Internal/Serialization/Hash.js | 38 ++-- src/Internal/Serialization/Hash.purs | 163 +++++++++--------- src/Internal/Serialization/Types.purs | 4 +- src/Internal/Transaction.purs | 3 +- src/Internal/TxOutput.purs | 6 +- src/Internal/Types/Redeemer.purs | 5 +- src/Internal/Types/Transaction.purs | 2 +- src/Internal/Types/VRFKeyHash.purs | 3 +- src/Internal/Wallet/Cip30.purs | 14 +- src/Internal/Wallet/Cip30Mock.purs | 15 +- 23 files changed, 263 insertions(+), 309 deletions(-) diff --git a/src/Contract/Transaction.purs b/src/Contract/Transaction.purs index dc0c61d744..54f412ebd9 100644 --- a/src/Contract/Transaction.purs +++ b/src/Contract/Transaction.purs @@ -279,6 +279,7 @@ import Effect.Aff (bracket) import Effect.Aff.Class (liftAff) import Effect.Class (liftEffect) import Effect.Exception (throw) +-- TODO: Remove once toBytes is switched to Castable import Untagged.Union (asOneOf) -- | Signs a transaction with potential failure. diff --git a/src/Internal/BalanceTx/ExUnitsAndMinFee.purs b/src/Internal/BalanceTx/ExUnitsAndMinFee.purs index c8128b8b70..2ef303193f 100644 --- a/src/Internal/BalanceTx/ExUnitsAndMinFee.purs +++ b/src/Internal/BalanceTx/ExUnitsAndMinFee.purs @@ -85,6 +85,7 @@ import Data.Traversable (for) import Data.Tuple (fst, snd) import Data.Tuple.Nested (type (/\), (/\)) import Effect.Class (liftEffect) +-- TODO: Remove once toBytes is switched to Castable import Untagged.Union (asOneOf) evalTxExecutionUnits diff --git a/src/Internal/Cardano/Types/Value.purs b/src/Internal/Cardano/Types/Value.purs index f64621d938..4db914f3c7 100644 --- a/src/Internal/Cardano/Types/Value.purs +++ b/src/Internal/Cardano/Types/Value.purs @@ -71,8 +71,8 @@ import Ctl.Internal.Metadata.ToMetadata (class ToMetadata) import Ctl.Internal.Serialization.Hash ( ScriptHash , scriptHashFromBytes - , scriptHashToBytes ) +import Ctl.Internal.Serialization.ToBytes (toBytes) import Ctl.Internal.ToData (class ToData) import Ctl.Internal.Types.ByteArray ( ByteArray @@ -242,7 +242,7 @@ unsafeAdaSymbol = CurrencySymbol mempty -- | constructor is not exported mkCurrencySymbol :: ByteArray -> Maybe CurrencySymbol mkCurrencySymbol byteArr = - scriptHashFromBytes (wrap byteArr) *> pure (CurrencySymbol byteArr) + scriptHashFromBytes byteArr *> pure (CurrencySymbol byteArr) -- Do not export. Create an Ada `CurrencySymbol` from a `ByteArray` mkUnsafeAdaSymbol :: ByteArray -> Maybe CurrencySymbol @@ -778,10 +778,10 @@ filterNonAda (Value _ nonAda) = Value mempty nonAda -- already know is a valid CurrencySymbol currencyScriptHash :: CurrencySymbol -> ScriptHash currencyScriptHash (CurrencySymbol byteArray) = - unsafePartial fromJust $ scriptHashFromBytes (wrap byteArray) + unsafePartial fromJust $ scriptHashFromBytes byteArray scriptHashAsCurrencySymbol :: ScriptHash -> CurrencySymbol -scriptHashAsCurrencySymbol = CurrencySymbol <<< unwrap <<< scriptHashToBytes +scriptHashAsCurrencySymbol = CurrencySymbol <<< unwrap <<< toBytes -- | The minting policy hash of a currency symbol currencyMPSHash :: CurrencySymbol -> MintingPolicyHash @@ -792,8 +792,7 @@ currencyMPSHash = MintingPolicyHash <<< currencyScriptHash -- Plutus doesn't use Maybe here. -- | The currency symbol of a monetary policy hash mpsSymbol :: MintingPolicyHash -> Maybe CurrencySymbol -mpsSymbol (MintingPolicyHash h) = mkCurrencySymbol <<< unwrap $ - scriptHashToBytes h +mpsSymbol (MintingPolicyHash h) = mkCurrencySymbol $ unwrap $ toBytes h -- Like `mapEither` that works with 'These'. mapThese diff --git a/src/Internal/Deserialization/Error.purs b/src/Internal/Deserialization/Error.purs index 8fdb2193a4..21f2709437 100644 --- a/src/Internal/Deserialization/Error.purs +++ b/src/Internal/Deserialization/Error.purs @@ -1,18 +1,21 @@ -- | Error-centered types and functions used by Deserialization modules. module Ctl.Internal.Deserialization.Error ( Err + , FromBytesError , FromCslRepError , _fromCslRepError , addErrTrace , cslErr + , fromBytesErrorHelper + , fromBytesError , fromCslRepError , toError ) where import Prelude -import Ctl.Internal.Deserialization.FromBytes (FromBytesError, _fromBytesError) import Ctl.Internal.Error (E, NotImplementedError, _notImplementedError, noteE) +import Ctl.Internal.FfiHelpers (ErrorFfiHelper, errorHelper) import Data.Either (Either(Left)) import Data.Maybe (Maybe) import Data.Variant (Variant, default, inj, match, onMatch) @@ -66,3 +69,22 @@ toError = error <<< match , fromBytesError: \err -> "FromBytesError: " <> err , notImplementedError: \err -> "NotImplementedError: " <> err } + +-- | FromBytesError row alias +type FromBytesError r = (fromBytesError :: String | r) + +-- | Needed to craate a variant type +_fromBytesError = Proxy :: Proxy "fromBytesError" + +-- | An error to use +fromBytesError + :: forall (r :: Row Type) (a :: Type) + . String + -> E (FromBytesError + r) a +fromBytesError = Left <<< inj _fromBytesError + +-- | An internal helper to shorten code +fromBytesErrorHelper + :: forall (r :: Row Type) + . ErrorFfiHelper (FromBytesError + r) +fromBytesErrorHelper = errorHelper (inj _fromBytesError) diff --git a/src/Internal/Deserialization/FromBytes.js b/src/Internal/Deserialization/FromBytes.js index 7a66a5e20b..461cf900d3 100644 --- a/src/Internal/Deserialization/FromBytes.js +++ b/src/Internal/Deserialization/FromBytes.js @@ -7,25 +7,10 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } -const fromBytes = name => helper => bytes => { +exports._fromBytes = name => helper => bytes => { try { return helper.valid(lib[name].from_bytes(bytes)); } catch (e) { return helper.error(name + ".from_bytes() raised " + e); } }; - -exports._fromBytesDataHash = fromBytes("DataHash"); -exports._fromBytesTransaction = fromBytes("Transaction"); -exports._fromBytesTransactionHash = fromBytes("TransactionHash"); -exports._fromBytesPlutusData = fromBytes("PlutusData"); -exports._fromBytesTransactionUnspentOutput = fromBytes( - "TransactionUnspentOutput" -); -exports._fromBytesTransactionWitnessSet = fromBytes("TransactionWitnessSet"); -exports._fromBytesNativeScript = fromBytes("NativeScript"); -exports._fromBytesMint = fromBytes("Mint"); -exports._fromBytesVRFKeyHash = fromBytes("VRFKeyHash"); -exports._fromBytesValue = fromBytes("Value"); -exports._fromBytesPublicKey = fromBytes("PublicKey"); -exports._fromBytesEd25519Signature = fromBytes("Ed25519Signature"); diff --git a/src/Internal/Deserialization/FromBytes.purs b/src/Internal/Deserialization/FromBytes.purs index 0b63165778..943b77d9d6 100644 --- a/src/Internal/Deserialization/FromBytes.purs +++ b/src/Internal/Deserialization/FromBytes.purs @@ -1,8 +1,5 @@ module Ctl.Internal.Deserialization.FromBytes ( class FromBytes - , FromBytesError - , _fromBytesError - , fromBytesError , fromBytes' , fromBytes , fromBytesEffect @@ -10,146 +7,107 @@ module Ctl.Internal.Deserialization.FromBytes import Prelude +import Ctl.Internal.Deserialization.Error (FromBytesError, fromBytesErrorHelper) import Ctl.Internal.Error (E) -import Ctl.Internal.FfiHelpers (ErrorFfiHelper, errorHelper) +import Ctl.Internal.FfiHelpers (ErrorFfiHelper) +import Ctl.Internal.Serialization.Hash (VRFKeyHash) import Ctl.Internal.Serialization.Types - ( DataHash + ( AuxiliaryDataHash + , DataHash , Ed25519Signature + , GenesisDelegateHash + , GenesisHash , Mint , NativeScript , PlutusData + , PoolMetadataHash , PublicKey + , ScriptDataHash , Transaction , TransactionHash , TransactionUnspentOutput , TransactionWitnessSet - , VRFKeyHash , Value ) import Ctl.Internal.Types.ByteArray (ByteArray) -import Data.Either (Either(Left), hush) +import Ctl.Internal.Types.CborBytes (CborBytes) +import Data.Either (hush) import Data.Maybe (Maybe(Just, Nothing)) -import Data.Variant (inj) +import Data.Newtype (unwrap) import Effect (Effect) import Effect.Exception (throw) -import Type.Prelude (Proxy(Proxy)) import Type.Row (type (+)) -- | Calls `from_bytes` method for the appropriate type class FromBytes a where fromBytes' :: forall (r :: Row Type). ByteArray -> E (FromBytesError + r) a +instance FromBytes AuxiliaryDataHash where + fromBytes' = _fromBytes "AuxiliaryDataHash" fromBytesErrorHelper + instance FromBytes DataHash where - fromBytes' = _fromBytesDataHash eh + fromBytes' = _fromBytes "DataHash" fromBytesErrorHelper -instance FromBytes Transaction where - fromBytes' = _fromBytesTransaction eh +instance FromBytes GenesisDelegateHash where + fromBytes' = _fromBytes "GenesisDelegateHash" fromBytesErrorHelper -instance FromBytes TransactionHash where - fromBytes' = _fromBytesTransactionHash eh +instance FromBytes GenesisHash where + fromBytes' = _fromBytes "GenesisHash" fromBytesErrorHelper + +instance FromBytes Mint where + fromBytes' = _fromBytes "Mint" fromBytesErrorHelper + +instance FromBytes NativeScript where + fromBytes' = _fromBytes "NativeScript" fromBytesErrorHelper instance FromBytes PlutusData where - fromBytes' = _fromBytesPlutusData eh + fromBytes' = _fromBytes "PlutusData" fromBytesErrorHelper -instance FromBytes TransactionUnspentOutput where - fromBytes' = _fromBytesTransactionUnspentOutput eh +instance FromBytes PoolMetadataHash where + fromBytes' = _fromBytes "PoolMetadataHash" fromBytesErrorHelper -instance FromBytes TransactionWitnessSet where - fromBytes' = _fromBytesTransactionWitnessSet eh +instance FromBytes ScriptDataHash where + fromBytes' = _fromBytes "ScriptDataHash" fromBytesErrorHelper -instance FromBytes NativeScript where - fromBytes' = _fromBytesNativeScript eh +instance FromBytes Transaction where + fromBytes' = _fromBytes "Transaction" fromBytesErrorHelper -instance FromBytes Mint where - fromBytes' = _fromBytesMint eh +instance FromBytes TransactionHash where + fromBytes' = _fromBytes "TransactionHash" fromBytesErrorHelper -instance FromBytes VRFKeyHash where - fromBytes' = _fromBytesVRFKeyHash eh +instance FromBytes TransactionUnspentOutput where + fromBytes' = _fromBytes "TransactionUnspentOutput" fromBytesErrorHelper + +instance FromBytes TransactionWitnessSet where + fromBytes' = _fromBytes "TransactionWitnessSet" fromBytesErrorHelper instance FromBytes Value where - fromBytes' = _fromBytesValue eh + fromBytes' = _fromBytes "Value" fromBytesErrorHelper instance FromBytes PublicKey where - fromBytes' = _fromBytesPublicKey eh + fromBytes' = _fromBytes "PublicKey" fromBytesErrorHelper instance FromBytes Ed25519Signature where - fromBytes' = _fromBytesEd25519Signature eh + fromBytes' = _fromBytes "Ed25519Signature" fromBytesErrorHelper + +instance FromBytes VRFKeyHash where + fromBytes' = _fromBytes "VRFKeyHash" fromBytesErrorHelper -- for backward compatibility until `Maybe` is abandoned. Then to be renamed. -fromBytes :: forall (a :: Type). FromBytes a => ByteArray -> Maybe a -fromBytes = fromBytes' >>> hush +fromBytes :: forall (a :: Type). FromBytes a => CborBytes -> Maybe a +fromBytes = unwrap >>> fromBytes' >>> hush -fromBytesEffect :: forall (a :: Type). FromBytes a => ByteArray -> Effect a +fromBytesEffect :: forall (a :: Type). FromBytes a => CborBytes -> Effect a fromBytesEffect bytes = case fromBytes bytes of Nothing -> throw "from_bytes() call failed" Just a -> pure a ----- Error types - --- | FromBytesError row alias -type FromBytesError r = (fromBytesError :: String | r) - --- | Needed to craate a variant type -_fromBytesError = Proxy :: Proxy "fromBytesError" +---- Foreign imports --- | An error to use -fromBytesError +foreign import _fromBytes :: forall (r :: Row Type) (a :: Type) . String - -> E (FromBytesError + r) a -fromBytesError = Left <<< inj _fromBytesError - --- | A local helper to shorten code -eh :: forall (r :: Row Type). ErrorFfiHelper (FromBytesError + r) -eh = errorHelper (inj _fromBytesError) - ----- Foreign imports - -foreign import _fromBytesDataHash - :: forall (r :: Row Type). ErrorFfiHelper r -> ByteArray -> E r DataHash - -foreign import _fromBytesTransactionHash - :: forall (r :: Row Type) - . ErrorFfiHelper r - -> ByteArray - -> E r TransactionHash - -foreign import _fromBytesPlutusData - :: forall (r :: Row Type). ErrorFfiHelper r -> ByteArray -> E r PlutusData - -foreign import _fromBytesTransaction - :: forall (r :: Row Type). ErrorFfiHelper r -> ByteArray -> E r Transaction - -foreign import _fromBytesTransactionUnspentOutput - :: forall (r :: Row Type) - . ErrorFfiHelper r - -> ByteArray - -> E r TransactionUnspentOutput - -foreign import _fromBytesTransactionWitnessSet - :: forall (r :: Row Type) - . ErrorFfiHelper r - -> ByteArray - -> E r TransactionWitnessSet - -foreign import _fromBytesNativeScript - :: forall (r :: Row Type). ErrorFfiHelper r -> ByteArray -> E r NativeScript - -foreign import _fromBytesMint - :: forall (r :: Row Type). ErrorFfiHelper r -> ByteArray -> E r Mint - -foreign import _fromBytesVRFKeyHash - :: forall (r :: Row Type). ErrorFfiHelper r -> ByteArray -> E r VRFKeyHash - -foreign import _fromBytesValue - :: forall (r :: Row Type). ErrorFfiHelper r -> ByteArray -> E r Value - -foreign import _fromBytesPublicKey - :: forall (r :: Row Type). ErrorFfiHelper r -> ByteArray -> E r PublicKey - -foreign import _fromBytesEd25519Signature - :: forall (r :: Row Type) - . ErrorFfiHelper r + -> ErrorFfiHelper r -> ByteArray - -> E r Ed25519Signature + -> E r a diff --git a/src/Internal/QueryM.purs b/src/Internal/QueryM.purs index 8da676b621..1afe925134 100644 --- a/src/Internal/QueryM.purs +++ b/src/Internal/QueryM.purs @@ -278,7 +278,6 @@ import Effect.Exception (Error, error, throw, try) import Effect.Ref (Ref) import Effect.Ref as Ref import Foreign.Object as Object -import Untagged.Union (asOneOf) -- This module defines an Aff interface for Ogmios Websocket Queries -- Since WebSockets do not define a mechanism for linking request/response @@ -844,8 +843,8 @@ applyArgs script args = map ( encodeAeson <<< byteArrayToHex + <<< unwrap <<< Serialization.toBytes - <<< asOneOf ) <<< Serialization.convertPlutusData diff --git a/src/Internal/QueryM/Ogmios.purs b/src/Internal/QueryM/Ogmios.purs index bed7448c0f..29854c4961 100644 --- a/src/Internal/QueryM/Ogmios.purs +++ b/src/Internal/QueryM/Ogmios.purs @@ -164,7 +164,6 @@ import Ctl.Internal.Types.Natural (Natural) import Ctl.Internal.Types.Natural (fromString) as Natural import Ctl.Internal.Types.Rational (Rational, (%)) import Ctl.Internal.Types.Rational as Rational -import Ctl.Internal.Types.RawBytes (hexToRawBytes) import Ctl.Internal.Types.RedeemerTag (RedeemerTag) import Ctl.Internal.Types.RedeemerTag (fromString) as RedeemerTag import Ctl.Internal.Types.RewardAddress (RewardAddress) @@ -1573,7 +1572,7 @@ parseScript outer = pubKeyHashHex = unsafePartial fromJust $ toString aeson ScriptPubkey <$> note pubKeyHashTypeMismatch - (ed25519KeyHashFromBytes =<< hexToRawBytes pubKeyHashHex) + (ed25519KeyHashFromBytes =<< hexToByteArray pubKeyHashHex) | otherwise = aeson # aesonObject \obj -> do let diff --git a/src/Internal/Serialization.js b/src/Internal/Serialization.js index 1764d25b00..ec88e383c1 100644 --- a/src/Internal/Serialization.js +++ b/src/Internal/Serialization.js @@ -43,15 +43,9 @@ exports.newTransaction = body => witness_set => auxiliary_data => () => exports.newTransaction_ = body => witness_set => () => lib.Transaction.new(body, witness_set); -exports.newTransactionUnspentOutputFromBytes = bytes => () => - lib.TransactionUnspentOutput.from_bytes(bytes); - exports.newTransactionUnspentOutput = input => output => () => lib.TransactionUnspentOutput.new(input, output); -exports.newTransactionWitnessSetFromBytes = bytes => () => - lib.TransactionWitnessSet.from_bytes(bytes); - exports.newMultiAsset = () => lib.MultiAsset.new(); exports.insertMultiAsset = multiasset => key => value => () => @@ -122,9 +116,6 @@ exports.addRedeemer = rs => r => () => rs.add(r); exports.setTxBodyReferenceInputs = txBody => referenceInputs => () => txBody.set_reference_inputs(referenceInputs); -exports.newScriptDataHashFromBytes = bytes => () => - lib.ScriptDataHash.from_bytes(bytes); - exports.setTxBodyScriptDataHash = setter("script_data_hash"); exports.setTxBodyMint = setter("mint"); @@ -244,8 +235,8 @@ exports.transactionBodySetValidityStartInterval = setter( "validity_start_interval_bignum" ); -exports.transactionBodySetAuxiliaryDataHash = txBody => hashBytes => () => - txBody.set_auxiliary_data_hash(lib.AuxiliaryDataHash.from_bytes(hashBytes)); +exports.transactionBodySetAuxiliaryDataHash = txBody => hash => () => + txBody.set_auxiliary_data_hash(hash); exports.convertPoolOwners = containerHelper => keyHashes => () => containerHelper.pack(lib.Ed25519KeyHashes, keyHashes); @@ -271,12 +262,7 @@ exports.newMultiHostName = dnsName => () => ); exports.newPoolMetadata = url => hash => () => - lib.PoolMetadata.new(lib.URL.new(url), lib.PoolMetadataHash.from_bytes(hash)); - -exports.newGenesisHash = bytes => () => lib.GenesisHash.from_bytes(bytes); - -exports.newGenesisDelegateHash = bytes => () => - lib.GenesisDelegateHash.from_bytes(bytes); + lib.PoolMetadata.new(lib.URL.new(url), hash); exports.newMoveInstantaneousRewardToOtherPot = pot => amount => () => lib.MoveInstantaneousReward.new_to_other_pot(pot, amount); diff --git a/src/Internal/Serialization.purs b/src/Internal/Serialization.purs index 1d8eddb043..a5c474ee36 100644 --- a/src/Internal/Serialization.purs +++ b/src/Internal/Serialization.purs @@ -8,8 +8,6 @@ module Ctl.Internal.Serialization , convertTransactionUnspentOutput , convertValue , serializeData - , newTransactionUnspentOutputFromBytes - , newTransactionWitnessSetFromBytes , hashScriptData , hashTransaction , publicKeyHash @@ -76,6 +74,7 @@ import Ctl.Internal.Serialization.BigInt as Serialization import Ctl.Internal.Serialization.Hash ( Ed25519KeyHash , ScriptHash + , VRFKeyHash , scriptHashFromBytes ) import Ctl.Internal.Serialization.NativeScript (convertNativeScript) @@ -111,6 +110,7 @@ import Ctl.Internal.Serialization.Types , PlutusData , PlutusScript , PoolMetadata + , PoolMetadataHash , PrivateKey , ProposedProtocolParameterUpdates , ProtocolParamUpdate @@ -133,7 +133,6 @@ import Ctl.Internal.Serialization.Types , TransactionWitnessSet , UnitInterval , Update - , VRFKeyHash , Value , Vkey , Vkeywitness @@ -172,7 +171,7 @@ import Data.Tuple.Nested (type (/\), (/\)) import Data.UInt (UInt) import Data.UInt as UInt import Effect (Effect) -import Untagged.Union (UndefinedOr, asOneOf, maybeToUor) +import Untagged.Union (UndefinedOr, maybeToUor) foreign import hashTransaction :: TransactionBody -> Effect TransactionHash @@ -210,12 +209,6 @@ foreign import newTransaction_ -> TransactionWitnessSet -> Effect Transaction -foreign import newTransactionWitnessSetFromBytes - :: CborBytes -> Effect TransactionWitnessSet - -foreign import newTransactionUnspentOutputFromBytes - :: CborBytes -> Effect TransactionUnspentOutput - foreign import newTransactionUnspentOutput :: TransactionInput -> TransactionOutput -> Effect TransactionUnspentOutput @@ -277,7 +270,6 @@ foreign import setTxBodyReferenceInputs -> TransactionInputs -> Effect Unit -foreign import newScriptDataHashFromBytes :: CborBytes -> Effect ScriptDataHash foreign import setTxBodyScriptDataHash :: TransactionBody -> ScriptDataHash -> Effect Unit @@ -347,9 +339,9 @@ foreign import newSingleHostAddr foreign import newSingleHostName :: UndefinedOr Int -> String -> Effect Relay foreign import newMultiHostName :: String -> Effect Relay -foreign import newPoolMetadata :: String -> ByteArray -> Effect PoolMetadata -foreign import newGenesisHash :: ByteArray -> Effect GenesisHash -foreign import newGenesisDelegateHash :: ByteArray -> Effect GenesisDelegateHash +foreign import newPoolMetadata + :: String -> PoolMetadataHash -> Effect PoolMetadata + foreign import newMoveInstantaneousRewardToOtherPot :: Number -> BigNum -> Effect MoveInstantaneousReward @@ -374,7 +366,7 @@ foreign import transactionBodySetValidityStartInterval :: TransactionBody -> BigNum -> Effect Unit foreign import transactionBodySetAuxiliaryDataHash - :: TransactionBody -> ByteArray -> Effect Unit + :: TransactionBody -> AuxiliaryDataHash -> Effect Unit foreign import newWithdrawals :: ContainerHelper @@ -488,9 +480,10 @@ convertTxBody (T.TxBody body) = do for_ body.certs $ convertCerts >=> setTxBodyCerts txBody for_ body.withdrawals $ convertWithdrawals >=> setTxBodyWithdrawals txBody for_ body.update $ convertUpdate >=> setTxBodyUpdate txBody - for_ body.auxiliaryDataHash - $ unwrap - >>> transactionBodySetAuxiliaryDataHash txBody + for_ body.auxiliaryDataHash $ + unwrap >>> wrap >>> fromBytes >>> fromJustEff + "Failed to convert auxiliary data hash" + >=> transactionBodySetAuxiliaryDataHash txBody for_ body.validityStartInterval $ unwrap >>> BigNum.toString @@ -500,15 +493,12 @@ convertTxBody (T.TxBody body) = do for_ body.requiredSigners $ map unwrap >>> transactionBodySetRequiredSigners containerHelper txBody - for_ body.auxiliaryDataHash - $ unwrap - >>> transactionBodySetAuxiliaryDataHash txBody for_ body.networkId $ convertNetworkId >=> setTxBodyNetworkId txBody for_ body.mint $ convertMint >=> setTxBodyMint txBody - for_ body.scriptDataHash - ( unwrap >>> wrap >>> newScriptDataHashFromBytes >=> - setTxBodyScriptDataHash txBody - ) + for_ body.scriptDataHash $ + unwrap >>> wrap >>> fromBytes >>> fromJustEff + "Failed to convert script data hash" + >=> setTxBodyScriptDataHash txBody for_ body.collateral $ convertTxInputs >=> setTxBodyCollateral txBody for_ body.requiredSigners $ map unwrap @@ -554,8 +544,13 @@ convertProposedProtocolParameterUpdates convertProposedProtocolParameterUpdates ppus = newProposedProtocolParameterUpdates containerHelper =<< for (Map.toUnfoldable $ unwrap ppus) \(genesisHash /\ ppu) -> do - Tuple <$> newGenesisHash (unwrap genesisHash) <*> - convertProtocolParamUpdate ppu + Tuple + <$> + ( fromJustEff "Failed to convert genesis hash" $ fromBytes + (wrap $ unwrap genesisHash) + ) + <*> + convertProtocolParamUpdate ppu convertProtocolParamUpdate :: T.ProtocolParamUpdate -> Effect ProtocolParamUpdate @@ -695,9 +690,18 @@ convertCert = case _ of , vrfKeyhash: T.VRFKeyHash vrfKeyhash } -> do join $ newGenesisKeyDelegationCertificate - <$> newGenesisHash genesisHash - <*> newGenesisDelegateHash genesisDelegateHash - <*> pure vrfKeyhash + <$> + ( fromJustEff "Failed to convert genesis hash" + $ fromBytes + $ wrap genesisHash + ) + <*> + ( fromJustEff "Failed to convert genesis delegate hash" + $ fromBytes + $ wrap genesisDelegateHash + ) + <*> + pure vrfKeyhash T.MoveInstantaneousRewardsCert mir -> do newMoveInstantaneousRewardsCertificate =<< convertMoveInstantaneousReward mir @@ -718,7 +722,9 @@ convertMoveInstantaneousReward (T.ToStakeCreds { pot, amounts }) = convertPoolMetadata :: T.PoolMetadata -> Effect PoolMetadata convertPoolMetadata (T.PoolMetadata { url: T.URL url, hash: T.PoolMetadataHash hash }) = - newPoolMetadata url hash + ( (fromJustEff "Failed to convert script data hash" <<< fromBytes <<< wrap) + >=> (newPoolMetadata url) + ) hash convertRelays :: Array T.Relay -> Effect Relays convertRelays relays = do @@ -743,7 +749,7 @@ convertMint (T.Mint nonAdaAssets) = do mint <- newMint forWithIndex_ m \scriptHashBytes' values -> do let - mScripthash = scriptHashFromBytes $ wrap $ Value.getCurrencySymbol + mScripthash = scriptHashFromBytes $ Value.getCurrencySymbol scriptHashBytes' scripthash <- fromJustEff "scriptHashFromBytes failed while converting value" @@ -772,7 +778,7 @@ convertTxInputs fInputs = do convertTxInput :: T.TransactionInput -> Effect TransactionInput convertTxInput (T.TransactionInput { transactionId, index }) = do - tx_hash <- fromBytesEffect (unwrap transactionId) + tx_hash <- fromBytesEffect (wrap $ unwrap transactionId) newTransactionInput tx_hash index convertTxOutputs :: Array T.TransactionOutput -> Effect TransactionOutputs @@ -789,7 +795,7 @@ convertTxOutput case datum of NoOutputDatum -> pure unit OutputDatumHash dataHash -> do - for_ (fromBytes $ unwrap dataHash) $ + for_ (fromBytes $ wrap $ unwrap dataHash) $ transactionOutputSetDataHash txo OutputDatum datumValue -> do transactionOutputSetPlutusData txo @@ -813,7 +819,7 @@ convertValue val = do multiasset <- newMultiAsset forWithIndex_ m \scriptHashBytes' values -> do let - mScripthash = scriptHashFromBytes $ wrap $ Value.getCurrencySymbol + mScripthash = scriptHashFromBytes $ Value.getCurrencySymbol scriptHashBytes' scripthash <- fromJustEff "scriptHashFromBytes failed while converting value" @@ -875,5 +881,4 @@ hashScriptData cms rs ps = do (traverse convertPlutusData ps) serializeData :: forall (a :: Type). ToData a => a -> Maybe CborBytes -serializeData = map (wrap <<< toBytes <<< asOneOf) <<< convertPlutusData <<< - toData +serializeData = map toBytes <<< convertPlutusData <<< toData diff --git a/src/Internal/Serialization/Address.purs b/src/Internal/Serialization/Address.purs index 8b2e32f348..7de32661f3 100644 --- a/src/Internal/Serialization/Address.purs +++ b/src/Internal/Serialization/Address.purs @@ -326,6 +326,7 @@ instance EncodeAeson StakeCredential where foreign import _addressFromBech32 :: MaybeFfiHelper -> Bech32String -> Maybe Address +-- We can't use FromBytes class here, because of cyclic dependencies foreign import _addressFromBytes :: MaybeFfiHelper -> CborBytes -> Maybe Address foreign import addressBytes :: Address -> CborBytes foreign import addressBech32 :: Address -> Bech32String diff --git a/src/Internal/Serialization/AuxiliaryData.js b/src/Internal/Serialization/AuxiliaryData.js index c34b6f8f4f..24f8da79fe 100644 --- a/src/Internal/Serialization/AuxiliaryData.js +++ b/src/Internal/Serialization/AuxiliaryData.js @@ -12,7 +12,7 @@ const setter = prop => obj => value => () => obj["set_" + prop](value); exports.newAuxiliaryData = () => lib.AuxiliaryData.new(); exports._hashAuxiliaryData = auxiliaryData => - lib.hash_auxiliary_data(auxiliaryData).to_bytes(); + lib.hash_auxiliary_data(auxiliaryData); exports.setAuxiliaryDataNativeScripts = setter("native_scripts"); diff --git a/src/Internal/Serialization/AuxiliaryData.purs b/src/Internal/Serialization/AuxiliaryData.purs index 1a11b22995..de2bf5873d 100644 --- a/src/Internal/Serialization/AuxiliaryData.purs +++ b/src/Internal/Serialization/AuxiliaryData.purs @@ -13,8 +13,10 @@ import Ctl.Internal.FfiHelpers (ContainerHelper, containerHelper) import Ctl.Internal.Helpers (fromJustEff) import Ctl.Internal.Serialization.NativeScript (convertNativeScripts) import Ctl.Internal.Serialization.PlutusScript (convertPlutusScript) +import Ctl.Internal.Serialization.ToBytes (toBytes) import Ctl.Internal.Serialization.Types ( AuxiliaryData + , AuxiliaryDataHash , GeneralTransactionMetadata , NativeScripts , PlutusScripts @@ -31,7 +33,7 @@ import Ctl.Internal.Types.TransactionMetadata , TransactionMetadatumLabel(TransactionMetadatumLabel) ) as T import Data.Map as Map -import Data.Newtype (wrap) +import Data.Newtype (unwrap, wrap) import Data.Traversable (for, for_, traverse) import Data.Tuple (Tuple(Tuple)) import Data.Tuple.Nested (type (/\), (/\)) @@ -73,11 +75,12 @@ foreign import newMetadataText :: String -> Effect TransactionMetadatum foreign import _hashAuxiliaryData - :: AuxiliaryData -> ByteArray + :: AuxiliaryData -> AuxiliaryDataHash hashAuxiliaryData :: T.AuxiliaryData -> Effect T.AuxiliaryDataHash hashAuxiliaryData = - map (wrap <<< _hashAuxiliaryData) <<< convertAuxiliaryData + map (wrap <<< unwrap <<< toBytes <<< _hashAuxiliaryData) <<< + convertAuxiliaryData convertAuxiliaryData :: T.AuxiliaryData -> Effect AuxiliaryData convertAuxiliaryData diff --git a/src/Internal/Serialization/Hash.js b/src/Internal/Serialization/Hash.js index aea712486c..709461736c 100644 --- a/src/Internal/Serialization/Hash.js +++ b/src/Internal/Serialization/Hash.js @@ -7,6 +7,18 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } +exports.hashToBytes = hash => { + return hash.to_bytes(); +}; + +exports.hashFromBytes = name => maybe => bytes => { + return hashFromImpl(lib[name].from_bytes)(maybe)(bytes); +}; + +exports.hashToBech32Unsafe = prefix => hash => { + return hash.to_bech32(prefix); +}; + const hashFromImpl = hashClassFrom => maybe => input => { let ret = null; try { @@ -20,15 +32,7 @@ const hashFromImpl = hashClassFrom => maybe => input => { return maybe.just(ret); }; -const hashToBytes = hash => { - return hash.to_bytes(); -}; - -const hashToBech32Unsafe = prefix => hash => { - return hash.to_bech32(prefix); -}; - -const hashToBech32Impl = maybe => prefix => hash => { +exports.hashToBech32Impl = maybe => prefix => hash => { let ret = null; try { ret = hash.to_bech32(prefix); @@ -45,24 +49,8 @@ exports._ed25519KeyHashFromBech32Impl = maybe => bech32str => { return hashFromImpl(lib.Ed25519KeyHash.from_bech32)(maybe)(bech32str); }; -exports._ed25519KeyHashFromBytesImpl = maybe => bytes => { - return hashFromImpl(lib.Ed25519KeyHash.from_bytes)(maybe)(bytes); -}; - -exports._scriptHashFromBytesImpl = maybe => bytes => { - return hashFromImpl(lib.ScriptHash.from_bytes)(maybe)(bytes); -}; - exports._scriptHashFromBech32Impl = maybe => bech32str => { return hashFromImpl(lib.ScriptHash.from_bech32)(maybe)(bech32str); }; -exports.ed25519KeyHashToBytes = hashToBytes; -exports.ed25519KeyHashToBech32Unsafe = hashToBech32Unsafe; -exports._ed25519KeyHashToBech32Impl = hashToBech32Impl; - -exports.scriptHashToBytes = hashToBytes; -exports.scriptHashToBech32Unsafe = hashToBech32Unsafe; -exports._scriptHashToBech32Impl = hashToBech32Impl; - exports.nativeScriptHash = script => script.hash(); diff --git a/src/Internal/Serialization/Hash.purs b/src/Internal/Serialization/Hash.purs index b4f20ae727..6938a80c4c 100644 --- a/src/Internal/Serialization/Hash.purs +++ b/src/Internal/Serialization/Hash.purs @@ -1,17 +1,16 @@ module Ctl.Internal.Serialization.Hash ( Ed25519KeyHash , ScriptHash - , ed25519KeyHashToBytes - , ed25519KeyHashFromBytes + , VRFKeyHash , ed25519KeyHashFromBech32 + , ed25519KeyHashFromBytes , ed25519KeyHashToBech32 , ed25519KeyHashToBech32Unsafe - , scriptHashToBytes - , scriptHashToBech32Unsafe - , scriptHashFromBytes + , nativeScriptHash , scriptHashFromBech32 + , scriptHashFromBytes , scriptHashToBech32 - , nativeScriptHash + , scriptHashToBech32Unsafe ) where import Prelude @@ -30,40 +29,77 @@ import Ctl.Internal.Metadata.ToMetadata (class ToMetadata, toMetadata) import Ctl.Internal.Serialization.Types (NativeScript) import Ctl.Internal.ToData (class ToData, toData) import Ctl.Internal.Types.Aliases (Bech32String) +import Ctl.Internal.Types.ByteArray (ByteArray, byteArrayToHex, hexToByteArray) import Ctl.Internal.Types.PlutusData (PlutusData(Bytes)) -import Ctl.Internal.Types.RawBytes (RawBytes, hexToRawBytes, rawBytesToHex) import Ctl.Internal.Types.TransactionMetadata (TransactionMetadatum(Bytes)) as Metadata import Data.Either (Either(Left, Right), note) import Data.Function (on) import Data.Maybe (Maybe(Nothing, Just), maybe) -import Data.Newtype (unwrap, wrap) + +-- We can't use ToBytes class here, because of cyclic dependencies +-- | Encodes the hash to `CborBytes` +foreign import hashToBytes :: forall (a :: Type). a -> ByteArray + +-- We can't use FromBytes class here, because of cyclic dependencies +-- | Decodes `CborBytes` to the hash +foreign import hashFromBytes + :: forall (a :: Type) + . String + -> MaybeFfiHelper + -> ByteArray + -> Maybe a + +foreign import nativeScriptHash :: NativeScript -> ScriptHash + +foreign import hashToBech32Unsafe + :: forall (a :: Type) + . String + -> a + -> Bech32String + +foreign import hashToBech32Impl + :: forall (a :: Type) + . MaybeFfiHelper + -> String + -> a + -> Maybe Bech32String + +foreign import _ed25519KeyHashFromBech32Impl + :: MaybeFfiHelper + -> Bech32String + -> Maybe Ed25519KeyHash + +foreign import _scriptHashFromBech32Impl + :: MaybeFfiHelper + -> Bech32String + -> Maybe ScriptHash -- | PubKeyHash and StakeKeyHash refers to blake2b-224 hash digests of Ed25519 -- | verification keys foreign import data Ed25519KeyHash :: Type instance Eq Ed25519KeyHash where - eq = eq `on` ed25519KeyHashToBytes + eq = eq `on` hashToBytes instance Ord Ed25519KeyHash where - compare = compare `on` ed25519KeyHashToBytes + compare = compare `on` hashToBytes instance Show Ed25519KeyHash where - show edkh = "(Ed25519KeyHash " <> rawBytesToHex (ed25519KeyHashToBytes edkh) + show edkh = "(Ed25519KeyHash " <> byteArrayToHex (hashToBytes edkh) <> ")" instance ToData Ed25519KeyHash where - toData = toData <<< unwrap <<< ed25519KeyHashToBytes + toData = toData <<< hashToBytes instance FromData Ed25519KeyHash where - fromData (Bytes kh) = ed25519KeyHashFromBytes $ wrap kh + fromData (Bytes kh) = ed25519KeyHashFromBytes kh fromData _ = Nothing instance ToMetadata Ed25519KeyHash where - toMetadata = toMetadata <<< ed25519KeyHashToBytes + toMetadata = toMetadata <<< hashToBytes instance FromMetadata Ed25519KeyHash where - fromMetadata (Metadata.Bytes kh) = ed25519KeyHashFromBytes $ wrap kh + fromMetadata (Metadata.Bytes kh) = ed25519KeyHashFromBytes kh fromMetadata _ = Nothing -- This is needed for `ApplyArgs`. @@ -73,40 +109,23 @@ instance DecodeAeson Ed25519KeyHash where decodeAeson = caseAesonString (Left $ TypeMismatch "Expected Plutus BuiltinByteString") ( note (TypeMismatch "Invalid Ed25519KeyHash") <<< ed25519KeyHashFromBytes - <=< note (TypeMismatch "Invalid ByteArray") <<< hexToRawBytes + <=< note (TypeMismatch "Invalid ByteArray") <<< hexToByteArray ) instance EncodeAeson Ed25519KeyHash where - encodeAeson' = encodeAeson' <<< rawBytesToHex <<< ed25519KeyHashToBytes - -foreign import _ed25519KeyHashFromBytesImpl - :: MaybeFfiHelper - -> RawBytes - -> Maybe Ed25519KeyHash - -foreign import _ed25519KeyHashFromBech32Impl - :: MaybeFfiHelper - -> Bech32String - -> Maybe Ed25519KeyHash - -foreign import ed25519KeyHashToBytes :: Ed25519KeyHash -> RawBytes + encodeAeson' = encodeAeson' <<< byteArrayToHex <<< hashToBytes -- | Convert ed25519KeyHash to Bech32 representation with given prefix. -- | Will crash if prefix is invalid (length, mixed-case, etc) -- | More on prefixes: https://cips.cardano.org/cips/cip5 -foreign import ed25519KeyHashToBech32Unsafe - :: String - -> Ed25519KeyHash - -> Bech32String +ed25519KeyHashToBech32Unsafe ∷ String → Ed25519KeyHash → Bech32String +ed25519KeyHashToBech32Unsafe = hashToBech32Unsafe -foreign import _ed25519KeyHashToBech32Impl - :: MaybeFfiHelper - -> String - -> Ed25519KeyHash - -> Maybe Bech32String +scriptHashToBech32Unsafe ∷ String → ScriptHash → Bech32String +scriptHashToBech32Unsafe = hashToBech32Unsafe -ed25519KeyHashFromBytes :: RawBytes -> Maybe Ed25519KeyHash -ed25519KeyHashFromBytes = _ed25519KeyHashFromBytesImpl maybeFfiHelper +ed25519KeyHashFromBytes :: ByteArray -> Maybe Ed25519KeyHash +ed25519KeyHashFromBytes = hashFromBytes "Ed25519KeyHash" maybeFfiHelper ed25519KeyHashFromBech32 :: Bech32String -> Maybe Ed25519KeyHash ed25519KeyHashFromBech32 = _ed25519KeyHashFromBech32Impl maybeFfiHelper @@ -121,68 +140,49 @@ ed25519KeyHashToBech32 = _ed25519KeyHashToBech32Impl maybeFfiHelper foreign import data ScriptHash :: Type instance Eq ScriptHash where - eq = eq `on` scriptHashToBytes + eq = eq `on` hashToBytes instance Ord ScriptHash where - compare = compare `on` scriptHashToBytes + compare = compare `on` hashToBytes instance Show ScriptHash where - show edkh = "(ScriptHash " <> rawBytesToHex (scriptHashToBytes edkh) <> ")" + show edkh = "(ScriptHash " <> byteArrayToHex (hashToBytes edkh) <> ")" instance ToData ScriptHash where - toData = toData <<< unwrap <<< scriptHashToBytes + toData = toData <<< hashToBytes instance FromData ScriptHash where - fromData (Bytes bytes) = scriptHashFromBytes $ wrap bytes + fromData (Bytes bytes) = scriptHashFromBytes bytes fromData _ = Nothing instance ToMetadata ScriptHash where - toMetadata = toMetadata <<< scriptHashToBytes + toMetadata = toMetadata <<< hashToBytes instance FromMetadata ScriptHash where - fromMetadata (Metadata.Bytes bytes) = scriptHashFromBytes $ wrap bytes + fromMetadata (Metadata.Bytes bytes) = scriptHashFromBytes bytes fromMetadata _ = Nothing -- Corresponds to Plutus' `Plutus.V1.Ledger.Api.Script` Aeson instances instance DecodeAeson ScriptHash where decodeAeson = do maybe (Left $ TypeMismatch "Expected hex-encoded script hash") Right <<< - caseAesonString Nothing (Just <=< scriptHashFromBytes <=< hexToRawBytes) + caseAesonString Nothing (Just <=< scriptHashFromBytes <=< hexToByteArray) instance EncodeAeson ScriptHash where - encodeAeson' sh = encodeAeson' $ scriptHashToBytes sh - -foreign import _scriptHashFromBytesImpl - :: MaybeFfiHelper - -> RawBytes - -> Maybe ScriptHash - -foreign import _scriptHashFromBech32Impl - :: MaybeFfiHelper - -> Bech32String - -> Maybe ScriptHash + encodeAeson' sh = encodeAeson' $ hashToBytes sh --- | Encodes the hash to Cbor bytes -foreign import scriptHashToBytes :: ScriptHash -> RawBytes +_ed25519KeyHashToBech32Impl + ∷ MaybeFfiHelper → String → Ed25519KeyHash → Maybe Bech32String +_ed25519KeyHashToBech32Impl = hashToBech32Impl --- | Convert scriptHash to Bech32 representation with given prefix. --- | Will crash if prefix is invalid (length, mixed-case, etc) --- | More on prefixes: https://cips.cardano.org/cips/cip5 -foreign import scriptHashToBech32Unsafe - :: String - -> ScriptHash - -> Bech32String - -foreign import _scriptHashToBech32Impl - :: MaybeFfiHelper - -> String - -> ScriptHash - -> Maybe Bech32String +_scriptHashToBech32Impl + ∷ MaybeFfiHelper → String → ScriptHash → Maybe Bech32String +_scriptHashToBech32Impl = hashToBech32Impl -- | Decodes a script hash from its CBOR bytes encoding -- | NOTE. It does _not_ compute hash of given bytes. -scriptHashFromBytes :: RawBytes -> Maybe ScriptHash -scriptHashFromBytes = _scriptHashFromBytesImpl maybeFfiHelper +scriptHashFromBytes :: ByteArray -> Maybe ScriptHash +scriptHashFromBytes = hashFromBytes "ScriptHash" maybeFfiHelper -- | Decodes a script hash from its Bech32 representation scriptHashFromBech32 :: Bech32String -> Maybe ScriptHash @@ -194,4 +194,13 @@ scriptHashFromBech32 = _scriptHashFromBech32Impl maybeFfiHelper scriptHashToBech32 :: String -> ScriptHash -> Maybe Bech32String scriptHashToBech32 = _scriptHashToBech32Impl maybeFfiHelper -foreign import nativeScriptHash :: NativeScript -> ScriptHash +foreign import data VRFKeyHash :: Type + +instance Show VRFKeyHash where + show = hashToBytes >>> byteArrayToHex + +instance Eq VRFKeyHash where + eq = eq `on` show + +instance EncodeAeson VRFKeyHash where + encodeAeson' = hashToBytes >>> byteArrayToHex >>> encodeAeson' diff --git a/src/Internal/Serialization/Types.purs b/src/Internal/Serialization/Types.purs index 453e4d0716..9cafb8706b 100644 --- a/src/Internal/Serialization/Types.purs +++ b/src/Internal/Serialization/Types.purs @@ -43,6 +43,7 @@ module Ctl.Internal.Serialization.Types , PlutusScript , PlutusScripts , PoolMetadata + , PoolMetadataHash , PoolParams , PrivateKey , ProposedProtocolParameterUpdates @@ -76,7 +77,6 @@ module Ctl.Internal.Serialization.Types , TransactionWitnessSet , UnitInterval , Update - , VRFKeyHash , Value , Vkey , Vkeywitness @@ -128,6 +128,7 @@ foreign import data PlutusMap :: Type foreign import data PlutusScript :: Type foreign import data PlutusScripts :: Type foreign import data PoolMetadata :: Type +foreign import data PoolMetadataHash :: Type foreign import data PoolParams :: Type foreign import data ProposedProtocolParameterUpdates :: Type foreign import data ProtocolParamUpdate :: Type @@ -161,7 +162,6 @@ foreign import data TransactionUnspentOutput :: Type foreign import data TransactionWitnessSet :: Type foreign import data UnitInterval :: Type foreign import data Update :: Type -foreign import data VRFKeyHash :: Type foreign import data Value :: Type foreign import data Vkey :: Type foreign import data Vkeywitness :: Type diff --git a/src/Internal/Transaction.purs b/src/Internal/Transaction.purs index 56745dba93..deb9d2254e 100644 --- a/src/Internal/Transaction.purs +++ b/src/Internal/Transaction.purs @@ -38,7 +38,6 @@ import Data.Show.Generic (genericShow) import Data.Traversable (traverse) import Effect (Effect) import Effect.Class (liftEffect) -import Untagged.Union (asOneOf) data ModifyTxError = ConvertWitnessesError @@ -69,7 +68,7 @@ setScriptDataHash costModels rs ds tx@(Transaction { body, witnessSet }) , null rs , null ds = pure tx | otherwise = do - scriptDataHash <- ScriptDataHash <<< toBytes <<< asOneOf + scriptDataHash <- ScriptDataHash <<< unwrap <<< toBytes <$> hashScriptData costModels rs (unwrap <$> ds) pure $ over Transaction _ diff --git a/src/Internal/TxOutput.purs b/src/Internal/TxOutput.purs index c5ba5bbd69..d093fa63ca 100644 --- a/src/Internal/TxOutput.purs +++ b/src/Internal/TxOutput.purs @@ -24,6 +24,7 @@ import Ctl.Internal.QueryM.Ogmios as Ogmios import Ctl.Internal.Serialization (toBytes) import Ctl.Internal.Serialization.PlutusData as Serialization import Ctl.Internal.Types.ByteArray (byteArrayToHex, hexToByteArray) +import Ctl.Internal.Types.CborBytes (hexToCborBytes) import Ctl.Internal.Types.Datum (DataHash, Datum(Datum)) import Ctl.Internal.Types.OutputDatum ( OutputDatum(OutputDatum, OutputDatumHash, NoOutputDatum) @@ -34,7 +35,6 @@ import Ctl.Internal.Types.Transaction (TransactionInput(TransactionInput)) as Tr import Data.Maybe (Maybe, fromMaybe, isNothing) import Data.Newtype (unwrap, wrap) import Data.Traversable (traverse) -import Untagged.Union (asOneOf) -- | A module for helpers of the various transaction output types. @@ -104,7 +104,7 @@ ogmiosDatumHashToDatumHash str = hexToByteArray str <#> wrap -- | Converts an Ogmios datum `String` to an internal `Datum` ogmiosDatumToDatum :: String -> Maybe Datum ogmiosDatumToDatum = - hexToByteArray + hexToCborBytes >=> fromBytes >=> Deserialization.convertPlutusData >>> map Datum @@ -117,7 +117,7 @@ datumHashToOgmiosDatumHash = byteArrayToHex <<< unwrap datumToOgmiosDatum :: Datum -> Maybe String datumToOgmiosDatum (Datum plutusData) = Serialization.convertPlutusData plutusData <#> - (asOneOf >>> toBytes >>> byteArrayToHex) + (toBytes >>> unwrap >>> byteArrayToHex) toOutputDatum :: Maybe Datum -> Maybe DataHash -> OutputDatum toOutputDatum d dh = diff --git a/src/Internal/Types/Redeemer.purs b/src/Internal/Types/Redeemer.purs index 149dbc46e4..6b466d53f1 100644 --- a/src/Internal/Types/Redeemer.purs +++ b/src/Internal/Types/Redeemer.purs @@ -11,13 +11,12 @@ import Ctl.Internal.FromData (class FromData) import Ctl.Internal.Serialization (toBytes) import Ctl.Internal.Serialization.PlutusData (convertPlutusData) import Ctl.Internal.ToData (class ToData, toData) -import Ctl.Internal.Types.ByteArray (ByteArray) +import Ctl.Internal.Types.ByteArray (ByteArray(ByteArray)) import Ctl.Internal.Types.PlutusData (PlutusData) import Data.Generic.Rep (class Generic) import Data.Maybe (Maybe) import Data.Newtype (class Newtype, unwrap, wrap) import Data.Show.Generic (genericShow) -import Untagged.Union (asOneOf) newtype Redeemer = Redeemer PlutusData @@ -51,4 +50,4 @@ instance Show RedeemerHash where -- | This is a duplicate of `datumHash`. redeemerHash :: Redeemer -> Maybe RedeemerHash redeemerHash = - map (wrap <<< toBytes <<< asOneOf) <<< convertPlutusData <<< unwrap + map (wrap <<< unwrap <<< toBytes) <<< convertPlutusData <<< unwrap diff --git a/src/Internal/Types/Transaction.purs b/src/Internal/Types/Transaction.purs index 3fc654a3a0..5b398fb619 100644 --- a/src/Internal/Types/Transaction.purs +++ b/src/Internal/Types/Transaction.purs @@ -11,7 +11,7 @@ import Prelude import Aeson (class DecodeAeson, class EncodeAeson) import Ctl.Internal.FromData (class FromData, fromData) import Ctl.Internal.ToData (class ToData, toData) -import Ctl.Internal.Types.ByteArray (ByteArray, byteArrayToHex) +import Ctl.Internal.Types.ByteArray (ByteArray(ByteArray), byteArrayToHex) import Ctl.Internal.Types.PlutusData (PlutusData(Constr)) import Data.Generic.Rep (class Generic) import Data.Maybe (Maybe(Nothing)) diff --git a/src/Internal/Types/VRFKeyHash.purs b/src/Internal/Types/VRFKeyHash.purs index 265324f3c5..f8b82355df 100644 --- a/src/Internal/Types/VRFKeyHash.purs +++ b/src/Internal/Types/VRFKeyHash.purs @@ -10,10 +10,11 @@ import Prelude import Aeson (class EncodeAeson, encodeAeson') import Ctl.Internal.Deserialization.FromBytes (fromBytes) import Ctl.Internal.Serialization.ToBytes (toBytes) -import Ctl.Internal.Serialization.Types as Serialization +import Ctl.Internal.Serialization.Hash as Serialization import Ctl.Internal.Types.ByteArray (ByteArray, byteArrayToHex) import Data.Function (on) import Data.Maybe (Maybe) +-- TODO: Remove once toBytes is switched to Castable import Untagged.Union (asOneOf) newtype VRFKeyHash = VRFKeyHash Serialization.VRFKeyHash diff --git a/src/Internal/Wallet/Cip30.purs b/src/Internal/Wallet/Cip30.purs index a3c17a6e13..599c699b29 100644 --- a/src/Internal/Wallet/Cip30.purs +++ b/src/Internal/Wallet/Cip30.purs @@ -24,7 +24,7 @@ import Ctl.Internal.Deserialization.UnspentOutput (convertValue) import Ctl.Internal.Deserialization.UnspentOutput as Deserialization.UnspentOuput import Ctl.Internal.Deserialization.WitnessSet as Deserialization.WitnessSet import Ctl.Internal.FfiHelpers (MaybeFfiHelper, maybeFfiHelper) -import Ctl.Internal.Serialization as Serialization +import Ctl.Internal.Serialization (convertTransaction, toBytes) as Serialization import Ctl.Internal.Serialization.Address ( Address , addressFromBytes @@ -42,6 +42,7 @@ import Ctl.Internal.Types.CborBytes ( CborBytes , cborBytesToHex , rawBytesAsCborBytes + , hexToCborBytes ) import Ctl.Internal.Types.RawBytes ( RawBytes @@ -55,7 +56,6 @@ import Effect (Effect) import Effect.Aff (Aff) import Effect.Class (liftEffect) import Effect.Exception (error, throw) -import Untagged.Union (asOneOf) type DataSignature = { key :: CborBytes @@ -126,7 +126,7 @@ mkCip30WalletAff walletName enableWallet = do txToHex :: Transaction -> Aff String txToHex = liftEffect - <<< map (byteArrayToHex <<< Serialization.toBytes <<< asOneOf) + <<< map (byteArrayToHex <<< unwrap <<< Serialization.toBytes) <<< Serialization.convertTransaction getNetworkId :: Cip30Connection -> Aff Int @@ -165,14 +165,14 @@ getCollateral conn = do for collateralUtxos \bytes -> do maybe (throw "Unable to convert UTxO") pure =<< Deserialization.UnspentOuput.convertUnspentOutput - <$> fromBytesEffect (unwrap bytes) + <$> fromBytesEffect (rawBytesAsCborBytes bytes) getUtxos :: Cip30Connection -> Aff (Maybe (Array TransactionUnspentOutput)) getUtxos conn = do mArrayStr <- toAffE $ _getUtxos maybeFfiHelper conn liftEffect $ for mArrayStr $ traverse \str -> do liftMaybe (error "Unable to convert UTxO") $ - hexToRawBytes str >>= unwrap >>> fromBytes >>= + hexToCborBytes str >>= fromBytes >>= Deserialization.UnspentOuput.convertUnspentOutput signTx :: Cip30Connection -> Transaction -> Aff (Maybe Transaction) @@ -182,7 +182,7 @@ signTx conn tx = do Nothing -> pure Nothing Just bytes -> map (combineWitnessSet tx) <$> liftEffect ( Deserialization.WitnessSet.convertWitnessSet - <$> fromBytesEffect (unwrap bytes) + <$> fromBytesEffect (rawBytesAsCborBytes bytes) ) where -- We have to combine the newly returned witness set with the existing one @@ -224,7 +224,7 @@ getBalance :: Cip30Connection -> Aff (Maybe Value) getBalance wallet = do fromHexString _getBalance wallet <#> \mbBytes -> do bytes <- mbBytes - fromBytes (unwrap bytes) >>= convertValue + fromBytes (rawBytesAsCborBytes bytes) >>= convertValue fromHexString :: (Cip30Connection -> Effect (Promise String)) diff --git a/src/Internal/Wallet/Cip30Mock.purs b/src/Internal/Wallet/Cip30Mock.purs index 5b6d5d0c7e..ebb9df69b3 100644 --- a/src/Internal/Wallet/Cip30Mock.purs +++ b/src/Internal/Wallet/Cip30Mock.purs @@ -56,7 +56,6 @@ import Effect.Class (liftEffect) import Effect.Exception (error) import Effect.Unsafe (unsafePerformEffect) import Type.Proxy (Proxy(Proxy)) -import Untagged.Union (asOneOf) data WalletMock = MockFlint | MockGero | MockNami | MockLode @@ -158,7 +157,7 @@ mkCip30Mock pKey mSKey = do cslUtxos <- traverse (liftEffect <<< convertTransactionUnspentOutput) $ Map.toUnfoldable nonCollateralUtxos <#> \(input /\ output) -> TransactionUnspentOutput { input, output } - pure $ (byteArrayToHex <<< toBytes <<< asOneOf) <$> cslUtxos + pure $ (byteArrayToHex <<< unwrap <<< toBytes) <$> cslUtxos , getCollateral: fromAff do ownAddress <- (unwrap keyWallet).address config.networkId utxos <- liftMaybe (error "No UTxOs at address") =<< @@ -167,7 +166,7 @@ mkCip30Mock pKey mSKey = do cslUnspentOutput <- liftEffect $ traverse convertTransactionUnspentOutput collateralUtxos - pure $ (byteArrayToHex <<< toBytes <<< asOneOf) <$> cslUnspentOutput + pure $ (byteArrayToHex <<< unwrap <<< toBytes) <$> cslUnspentOutput , getBalance: fromAff do ownAddress <- (unwrap keyWallet).address config.networkId utxos <- liftMaybe (error "No UTxOs at address") =<< @@ -175,17 +174,17 @@ mkCip30Mock pKey mSKey = do value <- liftEffect $ convertValue $ (foldMap (_.amount <<< unwrap) <<< Map.values) utxos - pure $ byteArrayToHex $ toBytes $ asOneOf value + pure $ byteArrayToHex $ unwrap $ toBytes value , getUsedAddresses: fromAff do (unwrap keyWallet).address config.networkId <#> \address -> - [ (byteArrayToHex <<< toBytes <<< asOneOf) address ] + [ (byteArrayToHex <<< unwrap <<< toBytes) address ] , getUnusedAddresses: fromAff $ pure [] , getChangeAddress: fromAff do (unwrap keyWallet).address config.networkId <#> - (byteArrayToHex <<< toBytes <<< asOneOf) + (byteArrayToHex <<< unwrap <<< toBytes) , getRewardAddresses: fromAff do (unwrap keyWallet).address config.networkId <#> \address -> - [ (byteArrayToHex <<< toBytes <<< asOneOf) address ] + [ (byteArrayToHex <<< unwrap <<< toBytes) address ] , signTx: \str -> unsafePerformEffect $ fromAff do txBytes <- liftMaybe (error "Unable to convert CBOR") $ hexToByteArray str @@ -195,7 +194,7 @@ mkCip30Mock pKey mSKey = do $ cborBytesFromByteArray txBytes witness <- (unwrap keyWallet).signTx tx cslWitnessSet <- liftEffect $ convertWitnessSet witness - pure $ byteArrayToHex $ toBytes $ asOneOf cslWitnessSet + pure $ byteArrayToHex $ unwrap $ toBytes cslWitnessSet , signData: mkFn2 \_addr msg -> unsafePerformEffect $ fromAff do msgBytes <- liftMaybe (error "Unable to convert CBOR") (hexToByteArray msg) From 77d054a20b9129f28bbdf702f5b38eee545a1ae6 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Fri, 2 Dec 2022 14:10:03 +0100 Subject: [PATCH 036/373] Apply suggestions --- src/Internal/BalanceTx/CoinSelection.purs | 45 +++++----- src/Internal/Partition.purs | 24 ++++- test/Equipartition.purs | 105 ---------------------- 3 files changed, 47 insertions(+), 127 deletions(-) delete mode 100644 test/Equipartition.purs diff --git a/src/Internal/BalanceTx/CoinSelection.purs b/src/Internal/BalanceTx/CoinSelection.purs index dc94c3be76..2ba1fe12f3 100644 --- a/src/Internal/BalanceTx/CoinSelection.purs +++ b/src/Internal/BalanceTx/CoinSelection.purs @@ -1,7 +1,10 @@ -- | This module provides a multi-asset coin selection algorithm replicated from --- | cardano-wallet (https://github.com/input-output-hk/cardano-wallet/blob/master/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs). The algorithm supports two selection --- | strategies (optimal and minimal) and uses priority ordering and round-robin --- | processing to handle the problem of over-selection. +-- | cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/3395b6e4749544d552125dfd0e060437b5c18d5c/lib/coin-selection/lib/Cardano/CoinSelection/Balance.hs +-- | +-- | The algorithm supports two selection strategies (optimal and minimal) and +-- | uses priority ordering and round-robin processing to handle the problem +-- | of over-selection. module Ctl.Internal.BalanceTx.CoinSelection ( Asset , SelectionState(SelectionState) @@ -327,7 +330,7 @@ runSelectionStep lens state -- we attempt to improve the selection using `SelectionPriorityImprove`, -- which allows us to select only utxos containing the given asset and no -- other asset, i.e. we select from the "singleton" subset of utxos. - bindFlipped requireImprovement <$> lens.selectQuantityImprove state + (requireImprovement =<< _) <$> lens.selectQuantityImprove state where requireImprovement :: SelectionState -> Maybe SelectionState requireImprovement state' @@ -352,28 +355,30 @@ runSelectionStep lens state -- Round-robin processing -------------------------------------------------------------------------------- -type Processor (m :: Type -> Type) (s :: Type) (s' :: Type) = s -> m (Maybe s') +type Processor (m :: Type -> Type) (s :: Type) = s -> m (Maybe s) +-- | Uses given processors to update the state sequentially. +-- | Removes the processor from the list if applying it to the state returns +-- | `Nothing`. Each processor can only be applied once per round and is +-- | carried over to the next round if it has successfully updated the state. +-- | +-- | We use Round-robin processing to perform coin selection in multiple rounds, +-- | where a `Processor` runs a single selection step (`runSelectionStep`) for +-- | an asset from the set of all assets present in `requiredValue`. +-- | It returns `Nothing` in case the selection for a particular asset is +-- | already optimal and cannot be improved further. +-- | +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/3395b6e4749544d552125dfd0e060437b5c18d5c/lib/coin-selection/lib/Cardano/CoinSelection/Balance.hs#L2155 runRoundRobinM :: forall (m :: Type -> Type) (s :: Type) . Monad m => s - -> Array (Processor m s s) - -> m s -runRoundRobinM state = runRoundRobinM' state identity - --- | Taken from cardano-wallet: --- | https://github.com/input-output-hk/cardano-wallet/blob/a61d37f2557b8cb5c47b57da79375afad698eed4/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L2155 -runRoundRobinM' - :: forall (m :: Type -> Type) (s :: Type) (s' :: Type) - . Monad m - => s - -> (s' -> s) - -> Array (Processor m s s') + -> Array (Processor m s) -> m s -runRoundRobinM' state demote processors = go state processors [] +runRoundRobinM state processors = go state processors [] where - go :: s -> Array (Processor m s s') -> Array (Processor m s s') -> m s + go :: s -> Array (Processor m s) -> Array (Processor m s) -> m s go s [] [] = pure s go s ps qs = case Array.uncons ps of @@ -381,7 +386,7 @@ runRoundRobinM' state demote processors = go state processors [] Just { head: p, tail: ps' } -> p s >>= case _ of Nothing -> go s ps' qs - Just s' -> go (demote s') ps' (Array.snoc qs p) + Just s' -> go s' ps' (Array.snoc qs p) -------------------------------------------------------------------------------- -- SelectionPriority diff --git a/src/Internal/Partition.purs b/src/Internal/Partition.purs index 3f1eeb567b..134b8ca9f8 100644 --- a/src/Internal/Partition.purs +++ b/src/Internal/Partition.purs @@ -33,21 +33,41 @@ import Partial.Unsafe (unsafePartial) class Partition (a :: Type) where partition :: a -> NonEmptyArray a -> Maybe (NonEmptyArray a) +-- | Partitions a `BigInt` into a number of parts, where the size of each part +-- | is proportional to the size of its corresponding element in the given +-- | list of weights, and the number of parts is equal to the number of weights. +-- | -- | Taken from cardano-wallet: -- | https://github.com/input-output-hk/cardano-wallet/blob/14e0f1c2a457f85b8ea470661e7bec5e6bcf93e0/lib/numeric/src/Cardano/Numeric/Util.hs#L175 instance Partition BigInt where partition target weights - | any (\w -> w < zero) weights = Nothing + | any (_ < zero) weights = Nothing | sum weights == zero = Nothing | otherwise = Just portionsRounded where portionsRounded :: NonEmptyArray BigInt - portionsRounded = portionsUnrounded + portionsRounded + -- 1. Start with the list of unrounded portions: + = portionsUnrounded # map QuotRem + -- 2. Attach an index to each portion, so that we can remember the + -- original order: # NEArray.zip (NEArray.range 1 $ length portionsUnrounded) + -- 3. Sort the portions in descending order of their remainders, and + -- then sort each subsequence with equal remainders into descending + -- order of their integral parts: + -- + -- NOTE: We sort unrounded portions by comparing their remainders + -- and not their fractional parts, as implemented in cardano-wallet. + -- This serves the same purpose, namely to distribute the `shortfall` + -- fairly between the portions, rounding *up* those portions that + -- have a larger remainder (i.e. larger fractional part). # NEArray.sortBy ((\x -> Ordering.invert <<< compare x) `on` snd) + -- 4. Apply pre-computed roundings to each portion: # round + -- 5. Restore the original order: # NEArray.sortBy (comparing fst) + -- 6. Strip away the indices: # map snd round diff --git a/test/Equipartition.purs b/test/Equipartition.purs deleted file mode 100644 index 6a2107fe76..0000000000 --- a/test/Equipartition.purs +++ /dev/null @@ -1,105 +0,0 @@ -module Test.Ctl.Equipartition (suite) where - -import Prelude - -import Ctl.Internal.Partition (class Equipartition, equipartition) -import Ctl.Internal.Test.TestPlanM (TestPlanM) -import Data.Array (elem) as Array -import Data.Array.NonEmpty (NonEmptyArray) -import Data.Array.NonEmpty (length, singleton, sort) as NEArray -import Data.BigInt (BigInt) -import Data.BigInt (fromInt) as BigInt -import Data.Foldable (foldMap, sum) -import Data.Newtype (class Newtype, unwrap) -import Data.Ord.Max (Max(Max)) -import Data.Ord.Min (Min(Min)) -import Effect.Aff (Aff) -import Mote (group, test) -import Test.QuickCheck.Arbitrary (class Arbitrary, arbitrary) -import Test.QuickCheck.Gen (suchThat) -import Test.Spec.QuickCheck (quickCheck) - -suite :: TestPlanM (Aff Unit) Unit -suite = - group "Equipartition" do - group "equipartitionBigInt" do - test "returns an arr containing only the input value if `numParts` leq 1" - (quickCheck prop_equipartitionBigInt_trivial) - - test "returns an arr containing `numParts` elements if `numParts` geq 1" - (quickCheck prop_equipartitionBigInt_length) - - test "returns an arr with the sum of elements equal to the input value" - (quickCheck prop_equipartitionBigInt_sum) - - test "returns an arr sorted in ascending order" - (quickCheck prop_equipartitionBigInt_order) - - test "returns an arr containing fairly equipartitioned portions" - (quickCheck prop_equipartitionBigInt_fair) - -prop_equipartitionBigInt_trivial :: BigInt' -> IntLeqOne -> Boolean -prop_equipartitionBigInt_trivial bi (IntLeqOne numParts) = - equipartition bi numParts == NEArray.singleton bi - --- Taken from cardano-wallet: --- https://github.com/input-output-hk/cardano-wallet/blob/7b0192110fe226f992bca6198b8ee83fa4a37f46/lib/numeric/test/unit/Cardano/Numeric/UtilSpec.hs#L124 -prop_equipartitionBigInt_length :: BigInt' -> IntGeqOne -> Boolean -prop_equipartitionBigInt_length bi (IntGeqOne numParts) = - NEArray.length (equipartition bi numParts) == numParts - --- Taken from cardano-wallet: --- https://github.com/input-output-hk/cardano-wallet/blob/7b0192110fe226f992bca6198b8ee83fa4a37f46/lib/numeric/test/unit/Cardano/Numeric/UtilSpec.hs#L134 -prop_equipartitionBigInt_sum :: BigInt' -> Int -> Boolean -prop_equipartitionBigInt_sum bi numParts = - sum (equipartition bi numParts) == bi - --- Taken from cardano-wallet: --- https://github.com/input-output-hk/cardano-wallet/blob/7b0192110fe226f992bca6198b8ee83fa4a37f46/lib/numeric/test/unit/Cardano/Numeric/UtilSpec.hs#L128 -prop_equipartitionBigInt_order :: BigInt' -> Int -> Boolean -prop_equipartitionBigInt_order bi numParts = - let - results :: NonEmptyArray BigInt' - results = equipartition bi numParts - in - NEArray.sort results == results - --- Taken from cardano-wallet: --- https://github.com/input-output-hk/cardano-wallet/blob/7b0192110fe226f992bca6198b8ee83fa4a37f46/lib/numeric/test/unit/Cardano/Numeric/UtilSpec.hs#L112 -prop_equipartitionBigInt_fair :: BigInt' -> Int -> Boolean -prop_equipartitionBigInt_fair bi numParts = - let - results :: NonEmptyArray BigInt' - results = equipartition bi numParts - in - flip Array.elem [ zero, one ] $ - unwrap (foldMap Max results) - unwrap (foldMap Min results) - -newtype BigInt' = BigInt' BigInt - -derive newtype instance Eq BigInt' -derive newtype instance Ord BigInt' -derive newtype instance Semiring BigInt' -derive newtype instance Ring BigInt' -derive newtype instance Equipartition BigInt' - -instance Bounded BigInt' where - top = BigInt' (BigInt.fromInt top) - bottom = BigInt' (BigInt.fromInt bottom) - -instance Arbitrary BigInt' where - arbitrary = BigInt' <<< BigInt.fromInt <$> arbitrary - -newtype IntLeqOne = IntLeqOne Int - -derive instance Newtype IntLeqOne _ - -instance Arbitrary IntLeqOne where - arbitrary = IntLeqOne <$> suchThat arbitrary (_ <= one) - -newtype IntGeqOne = IntGeqOne Int - -derive instance Newtype IntGeqOne _ - -instance Arbitrary IntGeqOne where - arbitrary = IntGeqOne <$> suchThat arbitrary (_ >= one) From 757ffd512a69e516e8aff31dea831a7017011749 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Fri, 2 Dec 2022 16:27:29 +0100 Subject: [PATCH 037/373] BalanceTx: Construct UtxoIndex only once --- src/Internal/BalanceTx/BalanceTx.purs | 12 ++++++----- src/Internal/BalanceTx/CoinSelection.purs | 25 ++++++++++------------- 2 files changed, 18 insertions(+), 19 deletions(-) diff --git a/src/Internal/BalanceTx/BalanceTx.purs b/src/Internal/BalanceTx/BalanceTx.purs index 9f7a0fadb7..e910430094 100644 --- a/src/Internal/BalanceTx/BalanceTx.purs +++ b/src/Internal/BalanceTx/BalanceTx.purs @@ -12,7 +12,9 @@ import Control.Monad.Logger.Class (trace) as Logger import Ctl.Internal.BalanceTx.CoinSelection ( SelectionState , SelectionStrategy + , UtxoIndex , _leftoverUtxos + , buildUtxoIndex , performMultiAssetSelection , selectedInputs ) @@ -233,7 +235,7 @@ balanceTxWithConstraints unbalancedTx constraintsBuilder = do type BalancerState = { unbalancedTx :: UnattachedUnbalancedTx , changeOutputs :: Array TransactionOutput - , leftoverUtxos :: UtxoMap + , leftoverUtxos :: UtxoIndex } runBalancer @@ -263,7 +265,7 @@ runBalancer strategy allUtxos utxos changeAddress certsFee unbalancedTx' = do -- | after generation of change, the first balancing step (`prebalanceTx`) -- | is performed, otherwise we proceed to `balanceChangeAndMinFee`. runNextBalancingStep - :: UnattachedUnbalancedTx -> UtxoMap -> BalanceTxM FinalizedTransaction + :: UnattachedUnbalancedTx -> UtxoIndex -> BalanceTxM FinalizedTransaction runNextBalancingStep unbalancedTx leftoverUtxos = do let txBody = unbalancedTx ^. _body' inputValue <- except $ getInputValue allUtxos txBody @@ -285,7 +287,7 @@ runBalancer strategy allUtxos utxos changeAddress certsFee unbalancedTx' = do selectionState <- performCoinSelection let - leftoverUtxos' :: UtxoMap + leftoverUtxos' :: UtxoIndex leftoverUtxos' = selectionState ^. _leftoverUtxos selectedInputs' :: Set TransactionInput @@ -647,8 +649,8 @@ mkBalancerState -> Array TransactionOutput -> UtxoMap -> BalancerState -mkBalancerState unbalancedTx changeOutputs leftoverUtxos = - { unbalancedTx, changeOutputs, leftoverUtxos } +mkBalancerState unbalancedTx changeOutputs = + { unbalancedTx, changeOutputs, leftoverUtxos: _ } <<< buildUtxoIndex logBalancerState :: String -> UtxoMap -> BalancerState -> BalanceTxM Unit logBalancerState message utxos { unbalancedTx, changeOutputs } = diff --git a/src/Internal/BalanceTx/CoinSelection.purs b/src/Internal/BalanceTx/CoinSelection.purs index 2ba1fe12f3..66d0d6877f 100644 --- a/src/Internal/BalanceTx/CoinSelection.purs +++ b/src/Internal/BalanceTx/CoinSelection.purs @@ -11,6 +11,7 @@ module Ctl.Internal.BalanceTx.CoinSelection , SelectionStrategy(SelectionStrategyMinimal, SelectionStrategyOptimal) , UtxoIndex(UtxoIndex) , _leftoverUtxos + , buildUtxoIndex , performMultiAssetSelection , selectedInputs ) where @@ -110,13 +111,13 @@ performMultiAssetSelection . MonadEffect m => MonadThrow BalanceTxError m => SelectionStrategy - -> UtxoMap + -> UtxoIndex -> Value -> m SelectionState -performMultiAssetSelection strategy utxos requiredValue = +performMultiAssetSelection strategy utxoIndex requiredValue = case requiredValue `Value.leq` availableValue of true -> - runRoundRobinM (mkSelectionState utxos) selectors + runRoundRobinM (mkSelectionState utxoIndex) selectors false -> throwError balanceInsufficientError where @@ -125,7 +126,7 @@ performMultiAssetSelection strategy utxos requiredValue = BalanceInsufficientError (Expected requiredValue) (Actual availableValue) availableValue :: Value - availableValue = balance utxos + availableValue = balance (utxoIndex ^. _utxos) selectors :: Array (SelectionState -> m (Maybe SelectionState)) @@ -154,11 +155,8 @@ newtype SelectionState = SelectionState derive instance Newtype SelectionState _ -_leftoverUtxos :: Lens' SelectionState UtxoMap -_leftoverUtxos = _leftoverUtxoIndex <<< _utxos - -_leftoverUtxoIndex :: Lens' SelectionState UtxoIndex -_leftoverUtxoIndex = _Newtype <<< prop (Proxy :: Proxy "leftoverUtxos") +_leftoverUtxos :: Lens' SelectionState UtxoIndex +_leftoverUtxos = _Newtype <<< prop (Proxy :: Proxy "leftoverUtxos") _selectedUtxos :: Lens' SelectionState UtxoMap _selectedUtxos = _Newtype <<< prop (Proxy :: Proxy "selectedUtxos") @@ -167,9 +165,8 @@ _selectedUtxos = _Newtype <<< prop (Proxy :: Proxy "selectedUtxos") -- | -- | Taken from cardano-wallet: -- | https://github.com/input-output-hk/cardano-wallet/blob/a61d37f2557b8cb5c47b57da79375afad698eed4/lib/wallet/src/Cardano/Wallet/Primitive/Types/UTxOSelection.hs#L192 -mkSelectionState :: UtxoMap -> SelectionState -mkSelectionState = - wrap <<< { leftoverUtxos: _, selectedUtxos: Map.empty } <<< buildUtxoIndex +mkSelectionState :: UtxoIndex -> SelectionState +mkSelectionState = wrap <<< { leftoverUtxos: _, selectedUtxos: Map.empty } -- | Moves a single utxo entry from the leftover set to the selected set. -- | @@ -178,7 +175,7 @@ mkSelectionState = selectUtxo :: TxUnspentOutput -> SelectionState -> SelectionState selectUtxo utxo@(oref /\ out) = over _selectedUtxos (Map.insert oref out) - <<< over _leftoverUtxoIndex (utxoIndexDeleteEntry utxo) + <<< over _leftoverUtxos (utxoIndexDeleteEntry utxo) -- | Returns the balance of the given utxo set. balance :: UtxoMap -> Value @@ -283,7 +280,7 @@ selectQuantityOf -> m (Maybe SelectionState) selectQuantityOf asset priority state = map updateState <$> - selectRandomWithPriority (state ^. _leftoverUtxoIndex) filters + selectRandomWithPriority (state ^. _leftoverUtxos) filters where filters :: NonEmptyArray SelectionFilter filters = filtersForAssetWithPriority asset priority From 1b5b3ff3a4623b594c19d2984271c3788ff28af9 Mon Sep 17 00:00:00 2001 From: Calum Sieppert Date: Fri, 2 Dec 2022 09:47:20 -0700 Subject: [PATCH 038/373] [WIP] Finish applying changes from #1073, doesn't type check yet --- src/Internal/Deserialization/PlutusData.purs | 3 +- src/Internal/Deserialization/Transaction.js | 2 +- src/Internal/Deserialization/Transaction.purs | 23 +++++----- src/Internal/Deserialization/UnspentOutput.js | 7 --- .../Deserialization/UnspentOutput.purs | 21 +++------ src/Internal/Deserialization/WitnessSet.js | 16 ------- src/Internal/Deserialization/WitnessSet.purs | 6 --- src/Internal/Hashing.js | 2 +- src/Internal/Hashing.purs | 12 ++--- src/Internal/Metadata/Cip25/V2.purs | 4 +- src/Internal/Plutus/Types/CurrencySymbol.purs | 18 +++----- test/Data.purs | 7 ++- test/Deserialization.purs | 31 ++++++------- test/Fixtures.purs | 44 ++++++++----------- test/Hashing.purs | 9 ++-- test/NativeScript.purs | 22 ++++++---- test/Serialization.purs | 22 +++++----- test/Serialization/Address.purs | 4 +- test/Serialization/Hash.purs | 16 +++---- 19 files changed, 108 insertions(+), 161 deletions(-) diff --git a/src/Internal/Deserialization/PlutusData.purs b/src/Internal/Deserialization/PlutusData.purs index f30cd52c5d..a01182f2db 100644 --- a/src/Internal/Deserialization/PlutusData.purs +++ b/src/Internal/Deserialization/PlutusData.purs @@ -30,7 +30,6 @@ import Ctl.Internal.Types.PlutusData ( PlutusData(Constr, Map, List, Integer, Bytes) ) as T import Data.Maybe (Maybe) -import Data.Newtype (unwrap) import Data.Traversable (traverse) import Data.Tuple (Tuple(Tuple)) import Data.Tuple.Nested (type (/\), (/\)) @@ -76,7 +75,7 @@ convertPlutusBytes :: PlutusData -> Maybe T.PlutusData convertPlutusBytes pd = T.Bytes <$> _PlutusData_bytes maybeFfiHelper pd deserializeData :: forall (a :: Type). FromData a => CborBytes -> Maybe a -deserializeData = (fromData <=< convertPlutusData <=< fromBytes) <<< unwrap +deserializeData = fromData <=< convertPlutusData <=< fromBytes foreign import _PlutusData_constr :: MaybeFfiHelper -> PlutusData -> Maybe ConstrPlutusData diff --git a/src/Internal/Deserialization/Transaction.js b/src/Internal/Deserialization/Transaction.js index d5c99090d9..93066ba99b 100644 --- a/src/Internal/Deserialization/Transaction.js +++ b/src/Internal/Deserialization/Transaction.js @@ -337,4 +337,4 @@ exports.unpackMIRToStakeCredentials_ = containerHelper.unpackKeyIndexed(mirToStakeCredentials); exports.convertPoolMetadata_ = cont => poolMetadata => - cont(poolMetadata.url().url())(poolMetadata.pool_metadata_hash().to_bytes()); + cont(poolMetadata.url().url())(poolMetadata.pool_metadata_hash()); diff --git a/src/Internal/Deserialization/Transaction.purs b/src/Internal/Deserialization/Transaction.purs index 578b3f96c9..eb5bc41cc1 100644 --- a/src/Internal/Deserialization/Transaction.purs +++ b/src/Internal/Deserialization/Transaction.purs @@ -138,7 +138,7 @@ import Ctl.Internal.Serialization.Address , StakeCredential ) as Csl import Ctl.Internal.Serialization.Address (Slot(Slot)) -import Ctl.Internal.Serialization.Hash (Ed25519KeyHash, ScriptHash) +import Ctl.Internal.Serialization.Hash (Ed25519KeyHash, ScriptHash, VRFKeyHash) import Ctl.Internal.Serialization.Types ( AssetName , AuxiliaryData @@ -164,6 +164,7 @@ import Ctl.Internal.Serialization.Types , Nonce , PlutusScripts , PoolMetadata + , PoolMetadataHash , PoolParams , ProtocolParamUpdate , ProtocolVersion @@ -179,7 +180,6 @@ import Ctl.Internal.Serialization.Types , TransactionWitnessSet , UnitInterval , Update - , VRFKeyHash , Withdrawals ) as Csl import Ctl.Internal.Types.BigNum (BigNum) as Csl @@ -212,7 +212,6 @@ import Data.UInt (UInt) import Data.UInt as UInt import Data.Variant (Variant) import Type.Row (type (+)) -import Untagged.Union (asOneOf) -- | Deserializes CBOR encoded transaction to a CTL's native type. deserializeTransaction @@ -300,7 +299,7 @@ convertTxBody txBody = do , withdrawals , update , auxiliaryDataHash: - T.AuxiliaryDataHash <<< toBytes <<< asOneOf <$> + T.AuxiliaryDataHash <<< unwrap <<< toBytes <$> _txBodyAuxiliaryDataHash maybeFfiHelper txBody , validityStartInterval: Slot <$> _txBodyValidityStartInterval maybeFfiHelper txBody @@ -325,7 +324,7 @@ convertUpdate u = do epoch <- map T.Epoch $ cslNumberToUInt "convertUpdate: epoch" e ppus <- traverse ( bitraverse - (pure <<< T.GenesisHash <<< toBytes <<< asOneOf) + (pure <<< T.GenesisHash <<< unwrap <<< toBytes) convertProtocolParamUpdate ) paramUpdates @@ -348,9 +347,9 @@ convertCertificate = _convertCert certConvHelper , poolRetirement: convertPoolRetirement , genesisKeyDelegation: \genesisHash genesisDelegateHash vrfKeyhash -> do pure $ T.GenesisKeyDelegation - { genesisHash: T.GenesisHash $ toBytes $ asOneOf genesisHash + { genesisHash: T.GenesisHash $ unwrap $ toBytes genesisHash , genesisDelegateHash: T.GenesisDelegateHash - (toBytes $ asOneOf genesisDelegateHash) + (unwrap $ toBytes genesisDelegateHash) , vrfKeyhash: VRFKeyHash vrfKeyhash } , moveInstantaneousRewardsToOtherPotCert: \pot amount -> do @@ -385,7 +384,7 @@ convertPoolRegistration params = do , poolMetadata: poolParamsPoolMetadata maybeFfiHelper params <#> convertPoolMetadata_ \url hash -> T.PoolMetadata - { url: T.URL url, hash: T.PoolMetadataHash hash } + { url: T.URL url, hash: T.PoolMetadataHash $ unwrap $ toBytes hash } } type ConvertRelayHelper a = @@ -659,7 +658,7 @@ convertExUnits nm cslExunits = <*> BigNum.toBigInt' (nm <> " steps") steps convertScriptDataHash :: Csl.ScriptDataHash -> T.ScriptDataHash -convertScriptDataHash = asOneOf >>> toBytes >>> T.ScriptDataHash +convertScriptDataHash = toBytes >>> unwrap >>> T.ScriptDataHash convertProtocolVersion :: forall (r :: Row Type) @@ -893,7 +892,7 @@ type CertConvHelper (r :: Type) = , genesisKeyDelegation :: Csl.GenesisHash -> Csl.GenesisDelegateHash - -> Csl.VRFKeyHash + -> VRFKeyHash -> r , moveInstantaneousRewardsToOtherPotCert :: Number -> Csl.BigNum -> r @@ -908,7 +907,7 @@ foreign import _convertCert -> Err r T.Certificate foreign import poolParamsOperator :: Csl.PoolParams -> Ed25519KeyHash -foreign import poolParamsVrfKeyhash :: Csl.PoolParams -> Csl.VRFKeyHash +foreign import poolParamsVrfKeyhash :: Csl.PoolParams -> VRFKeyHash foreign import poolParamsPledge :: Csl.PoolParams -> Csl.BigNum foreign import poolParamsCost :: Csl.PoolParams -> Csl.BigNum foreign import poolParamsMargin :: Csl.PoolParams -> Csl.UnitInterval @@ -928,4 +927,4 @@ foreign import unpackMIRToStakeCredentials_ -> Array (Csl.StakeCredential /\ Csl.Int) foreign import convertPoolMetadata_ - :: forall a. (String -> ByteArray -> a) -> Csl.PoolMetadata -> a + :: forall a. (String -> Csl.PoolMetadataHash -> a) -> Csl.PoolMetadata -> a diff --git a/src/Internal/Deserialization/UnspentOutput.js b/src/Internal/Deserialization/UnspentOutput.js index 9663769a61..a6a9eee072 100644 --- a/src/Internal/Deserialization/UnspentOutput.js +++ b/src/Internal/Deserialization/UnspentOutput.js @@ -64,10 +64,3 @@ exports.extractAssets = extractDict; exports.getDataHash = callMaybe("data_hash"); exports.mkTransactionUnspentOutput = input => output => lib.TransactionUnspentOutput.new(input, output); -exports._newTransactionUnspentOutputFromBytes = maybe => bytes => { - try { - return maybe.just(lib.TransactionUnspentOutput.from_bytes(bytes)); - } catch (_) { - return maybe.nothing; - } -}; diff --git a/src/Internal/Deserialization/UnspentOutput.purs b/src/Internal/Deserialization/UnspentOutput.purs index 5cc4f8fd84..b2e820fc5e 100644 --- a/src/Internal/Deserialization/UnspentOutput.purs +++ b/src/Internal/Deserialization/UnspentOutput.purs @@ -1,7 +1,6 @@ module Ctl.Internal.Deserialization.UnspentOutput ( convertUnspentOutput , mkTransactionUnspentOutput - , newTransactionUnspentOutputFromBytes , convertInput , convertOutput , convertValue @@ -32,7 +31,7 @@ import Ctl.Internal.Deserialization.WitnessSet (convertPlutusScript) import Ctl.Internal.FfiHelpers (MaybeFfiHelper, maybeFfiHelper) import Ctl.Internal.Serialization (toBytes) import Ctl.Internal.Serialization.Address (Address) -import Ctl.Internal.Serialization.Hash (ScriptHash, scriptHashToBytes) +import Ctl.Internal.Serialization.Hash (ScriptHash) import Ctl.Internal.Serialization.Types ( AssetName , Assets @@ -50,7 +49,6 @@ import Ctl.Internal.Serialization.Types ) import Ctl.Internal.Types.BigNum (BigNum) import Ctl.Internal.Types.BigNum (toBigInt) as BigNum -import Ctl.Internal.Types.ByteArray (ByteArray) import Ctl.Internal.Types.OutputDatum ( OutputDatum(NoOutputDatum, OutputDatumHash, OutputDatum) ) @@ -69,7 +67,6 @@ import Data.Traversable (for, traverse) import Data.Tuple (Tuple(Tuple)) import Data.Tuple.Nested (type (/\)) import Data.UInt as UInt -import Untagged.Union (asOneOf) convertUnspentOutput :: TransactionUnspentOutput -> Maybe T.TransactionUnspentOutput @@ -82,8 +79,8 @@ convertInput :: TransactionInput -> Maybe T.TransactionInput convertInput input = do index <- UInt.fromInt' $ getTransactionIndex input pure $ T.TransactionInput - { transactionId: T.TransactionHash $ toBytes - (asOneOf $ getTransactionHash input) + { transactionId: T.TransactionHash $ unwrap $ toBytes + (getTransactionHash input) , index } @@ -94,7 +91,7 @@ convertOutput output = do address = getAddress output mbDataHash = getDataHash maybeFfiHelper output <#> - asOneOf >>> toBytes >>> T.DataHash + toBytes >>> unwrap >>> T.DataHash mbDatum = getPlutusData maybeFfiHelper output datum <- case mbDatum, mbDataHash of Just _, Just _ -> Nothing -- impossible, so it's better to fail @@ -129,7 +126,7 @@ convertValue value = do ( traverse ( bitraverse -- scripthash to currency symbol - (scriptHashToBytes >>> unwrap >>> T.mkCurrencySymbol) + (toBytes >>> unwrap >>> T.mkCurrencySymbol) -- nested assetname to tokenname (traverse (ltraverse (T.assetNameName >>> T.mkTokenName))) ) @@ -182,11 +179,3 @@ foreign import getDataHash foreign import mkTransactionUnspentOutput :: TransactionInput -> TransactionOutput -> TransactionUnspentOutput - -foreign import _newTransactionUnspentOutputFromBytes - :: MaybeFfiHelper -> ByteArray -> Maybe TransactionUnspentOutput - -newTransactionUnspentOutputFromBytes - :: ByteArray -> Maybe TransactionUnspentOutput -newTransactionUnspentOutputFromBytes = _newTransactionUnspentOutputFromBytes - maybeFfiHelper diff --git a/src/Internal/Deserialization/WitnessSet.js b/src/Internal/Deserialization/WitnessSet.js index 5357786244..752cc47bc0 100644 --- a/src/Internal/Deserialization/WitnessSet.js +++ b/src/Internal/Deserialization/WitnessSet.js @@ -1,12 +1,3 @@ -/* global BROWSER_RUNTIME */ - -let lib; -if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { - lib = require("@emurgo/cardano-serialization-lib-browser"); -} else { - lib = require("@emurgo/cardano-serialization-lib-nodejs"); -} - const call = property => object => object[property](); const callMaybe = property => maybe => object => { @@ -59,10 +50,3 @@ exports.getRedeemerPlutusData = call("data"); exports.getExUnits = call("ex_units"); exports.getExUnitsMem = call("mem"); exports.getExUnitsSteps = call("steps"); -exports._deserializeWitnessSet = maybe => bytes => { - try { - return maybe.just(lib.TransactionWitnessSet.from_bytes(bytes)); - } catch (_) { - return maybe.nothing; - } -}; diff --git a/src/Internal/Deserialization/WitnessSet.purs b/src/Internal/Deserialization/WitnessSet.purs index 3597fa467b..f758c236cc 100644 --- a/src/Internal/Deserialization/WitnessSet.purs +++ b/src/Internal/Deserialization/WitnessSet.purs @@ -5,7 +5,6 @@ module Ctl.Internal.Deserialization.WitnessSet , convertVkeyWitnesses , convertVkeyWitness , convertWitnessSet - , deserializeWitnessSet , plutusScriptBytes ) where @@ -59,9 +58,6 @@ import Data.Traversable (for, traverse) import Data.Tuple (curry) import Data.Tuple.Nested ((/\)) -deserializeWitnessSet :: ByteArray -> Maybe TransactionWitnessSet -deserializeWitnessSet = _deserializeWitnessSet maybeFfiHelper - convertWitnessSet :: TransactionWitnessSet -> Maybe T.TransactionWitnessSet convertWitnessSet ws = do nativeScripts <- for (getNativeScripts maybeFfiHelper ws) convertNativeScripts @@ -197,5 +193,3 @@ foreign import getRedeemerPlutusData :: Redeemer -> PlutusData foreign import getExUnits :: Redeemer -> ExUnits foreign import getExUnitsMem :: ExUnits -> BigNum foreign import getExUnitsSteps :: ExUnits -> BigNum -foreign import _deserializeWitnessSet - :: MaybeFfiHelper -> ByteArray -> Maybe TransactionWitnessSet diff --git a/src/Internal/Hashing.js b/src/Internal/Hashing.js index 29c2080bd7..ce9c3f5c9d 100644 --- a/src/Internal/Hashing.js +++ b/src/Internal/Hashing.js @@ -20,7 +20,7 @@ exports.blake2b256HashHex = bytesToHash => { }; exports.hashPlutusData = plutusData => { - return lib.hash_plutus_data(plutusData).to_bytes(); + return lib.hash_plutus_data(plutusData); }; exports.hashPlutusScript = script => script.hash(); diff --git a/src/Internal/Hashing.purs b/src/Internal/Hashing.purs index f1b4cd6fbe..8b4e7debea 100644 --- a/src/Internal/Hashing.purs +++ b/src/Internal/Hashing.purs @@ -23,7 +23,8 @@ import Ctl.Internal.Serialization.NativeScript (convertNativeScript) import Ctl.Internal.Serialization.PlutusData (convertPlutusData) import Ctl.Internal.Serialization.PlutusScript (convertPlutusScript) import Ctl.Internal.Serialization.Types - ( PlutusData + ( DataHash + , PlutusData , PlutusScript , Transaction ) as Serialization @@ -33,13 +34,13 @@ import Ctl.Internal.Types.Scripts (PlutusScript) import Ctl.Internal.Types.Transaction (DataHash, TransactionHash) import Data.Maybe (Maybe) import Data.Newtype (unwrap, wrap) -import Untagged.Union (asOneOf) foreign import blake2b256Hash :: ByteArray -> ByteArray foreign import blake2b256HashHex :: ByteArray -> String -foreign import hashPlutusData :: Serialization.PlutusData -> ByteArray +foreign import hashPlutusData + :: Serialization.PlutusData -> Serialization.DataHash foreign import hashPlutusScript :: Serialization.PlutusScript -> ScriptHash @@ -53,13 +54,14 @@ foreign import sha3_256HashHex :: ByteArray -> String datumHash :: Datum -> Maybe DataHash datumHash = - map (wrap <<< hashPlutusData) <<< convertPlutusData <<< unwrap + map (wrap <<< unwrap <<< toBytes <<< hashPlutusData) <<< convertPlutusData <<< + unwrap -- | Calculates the hash of the transaction by applying `blake2b256Hash` to -- | the cbor-encoded transaction body. transactionHash :: Serialization.Transaction -> TransactionHash transactionHash = - wrap <<< blake2b256Hash <<< toBytes <<< asOneOf <<< _txBody + wrap <<< blake2b256Hash <<< unwrap <<< toBytes <<< _txBody plutusScriptHash :: PlutusScript -> ScriptHash plutusScriptHash = hashPlutusScript <<< convertPlutusScript diff --git a/src/Internal/Metadata/Cip25/V2.purs b/src/Internal/Metadata/Cip25/V2.purs index f9eee5726e..65b820f59a 100644 --- a/src/Internal/Metadata/Cip25/V2.purs +++ b/src/Internal/Metadata/Cip25/V2.purs @@ -54,9 +54,9 @@ import Ctl.Internal.Metadata.ToMetadata import Ctl.Internal.Plutus.Types.AssocMap (Map(Map), singleton) as AssocMap import Ctl.Internal.Serialization.Hash (scriptHashFromBytes) import Ctl.Internal.ToData (class ToData, toData) +import Ctl.Internal.Types.ByteArray (hexToByteArray) import Ctl.Internal.Types.Int as Int import Ctl.Internal.Types.PlutusData (PlutusData(Map, Integer)) -import Ctl.Internal.Types.RawBytes (hexToRawBytes) import Ctl.Internal.Types.Scripts (MintingPolicyHash) import Ctl.Internal.Types.TokenName (mkTokenName) import Ctl.Internal.Types.TransactionMetadata @@ -346,7 +346,7 @@ instance DecodeAeson Cip25Metadata where decodePolicyId = note (TypeMismatch "Expected hex-encoded policy id") <<< map wrap - <<< (scriptHashFromBytes <=< hexToRawBytes) + <<< (scriptHashFromBytes <=< hexToByteArray) decodeAssetName :: String -> Either JsonDecodeError Cip25TokenName decodeAssetName = diff --git a/src/Internal/Plutus/Types/CurrencySymbol.purs b/src/Internal/Plutus/Types/CurrencySymbol.purs index 7d7e7bda49..0d3911dde8 100644 --- a/src/Internal/Plutus/Types/CurrencySymbol.purs +++ b/src/Internal/Plutus/Types/CurrencySymbol.purs @@ -23,11 +23,8 @@ import Control.Monad.Gen as Gen import Ctl.Internal.FromData (class FromData) import Ctl.Internal.Metadata.FromMetadata (class FromMetadata) import Ctl.Internal.Metadata.ToMetadata (class ToMetadata) -import Ctl.Internal.Serialization.Hash - ( ScriptHash - , scriptHashFromBytes - , scriptHashToBytes - ) +import Ctl.Internal.Serialization.Hash (ScriptHash, scriptHashFromBytes) +import Ctl.Internal.Serialization.ToBytes (toBytes) import Ctl.Internal.ToData (class ToData) import Ctl.Internal.Types.ByteArray (ByteArray) import Ctl.Internal.Types.RawBytes @@ -37,7 +34,7 @@ import Ctl.Internal.Types.Scripts (MintingPolicyHash(MintingPolicyHash)) import Data.Array.NonEmpty (fromArray) import Data.Either (Either(Left)) import Data.Maybe (Maybe, fromJust) -import Data.Newtype (unwrap, wrap) +import Data.Newtype (unwrap) import Partial.Unsafe (unsafePartial) import Test.QuickCheck.Arbitrary (class Arbitrary) @@ -80,7 +77,7 @@ adaSymbol :: CurrencySymbol adaSymbol = CurrencySymbol mempty scriptHashAsCurrencySymbol :: ScriptHash -> CurrencySymbol -scriptHashAsCurrencySymbol = CurrencySymbol <<< unwrap <<< scriptHashToBytes +scriptHashAsCurrencySymbol = CurrencySymbol <<< unwrap <<< toBytes -- | The minting policy hash of a currency symbol. currencyMPSHash :: CurrencySymbol -> MintingPolicyHash @@ -88,8 +85,7 @@ currencyMPSHash = MintingPolicyHash <<< currencyScriptHash -- | The currency symbol of a monetary policy hash. mpsSymbol :: MintingPolicyHash -> Maybe CurrencySymbol -mpsSymbol (MintingPolicyHash h) = mkCurrencySymbol <<< unwrap $ - scriptHashToBytes h +mpsSymbol (MintingPolicyHash h) = mkCurrencySymbol $ unwrap $ toBytes h getCurrencySymbol :: CurrencySymbol -> ByteArray getCurrencySymbol (CurrencySymbol curSymbol) = curSymbol @@ -99,7 +95,7 @@ mkCurrencySymbol byteArr | byteArr == mempty = pure adaSymbol | otherwise = - scriptHashFromBytes (wrap byteArr) $> CurrencySymbol byteArr + scriptHashFromBytes byteArr $> CurrencySymbol byteArr -------------------------------------------------------------------------------- -- Internal @@ -108,5 +104,5 @@ mkCurrencySymbol byteArr -- This must be safe to use as long as we always construct a -- `CurrencySymbol` with the smart-constructors. currencyScriptHash :: CurrencySymbol -> ScriptHash -currencyScriptHash = unsafePartial $ fromJust <<< scriptHashFromBytes <<< wrap +currencyScriptHash = unsafePartial $ fromJust <<< scriptHashFromBytes <<< getCurrencySymbol diff --git a/test/Data.purs b/test/Data.purs index 2af9f7a4fc..7586fb5fc0 100644 --- a/test/Data.purs +++ b/test/Data.purs @@ -56,7 +56,6 @@ import Test.Spec.Assertions (shouldEqual) import Test.Spec.QuickCheck (quickCheck) import Type.Proxy (Proxy(Proxy)) import Type.RowList (Cons, Nil) -import Untagged.Union (asOneOf) plutusDataAesonRoundTrip :: forall (a :: Type). ToData a => FromData a => a -> Either JsonDecodeError a @@ -553,7 +552,7 @@ instance (FromData a) => FromData (Tree a) where fromBytesFromData :: forall a. FromData a => String -> Maybe a fromBytesFromData binary = fromData =<< PDD.convertPlutusData =<< fromBytes - (hexToByteArrayUnsafe binary) + (wrap $ hexToByteArrayUnsafe binary) testBinaryFixture :: forall a @@ -568,9 +567,9 @@ testBinaryFixture value binaryFixture = do test ("Deserialization: " <> show value) do fromBytesFromData binaryFixture `shouldEqual` Just value test ("Serialization: " <> show value) do - map (toBytes <<< asOneOf) (PDS.convertPlutusData (toData value)) + map toBytes (PDS.convertPlutusData (toData value)) `shouldEqual` Just - (hexToByteArrayUnsafe binaryFixture) + (wrap $ hexToByteArrayUnsafe binaryFixture) -- | Poor man's type level tests tests :: Array String diff --git a/test/Deserialization.purs b/test/Deserialization.purs index af0eb196aa..99d2a35db7 100644 --- a/test/Deserialization.purs +++ b/test/Deserialization.purs @@ -23,18 +23,16 @@ import Ctl.Internal.Deserialization.Transaction (convertTransaction) as TD import Ctl.Internal.Deserialization.UnspentOutput ( convertUnspentOutput , mkTransactionUnspentOutput - , newTransactionUnspentOutputFromBytes ) import Ctl.Internal.Deserialization.WitnessSet ( convertWitnessSet - , deserializeWitnessSet ) import Ctl.Internal.Serialization (convertTransaction) as TS -import Ctl.Internal.Serialization (toBytes) -import Ctl.Internal.Serialization as Serialization +import Ctl.Internal.Serialization (convertTxInput, convertTxOutput) as Serialization import Ctl.Internal.Serialization.BigInt as SB import Ctl.Internal.Serialization.NativeScript (convertNativeScript) as NSS import Ctl.Internal.Serialization.PlutusData as SPD +import Ctl.Internal.Serialization.ToBytes (toBytes) as Serialization import Ctl.Internal.Serialization.Types (TransactionUnspentOutput) import Ctl.Internal.Serialization.WitnessSet as SW import Ctl.Internal.Test.TestPlanM (TestPlanM) @@ -44,7 +42,7 @@ import Data.Array as Array import Data.BigInt as BigInt import Data.Either (hush) import Data.Maybe (isJust, isNothing) -import Data.Newtype (unwrap) +import Data.Newtype (unwrap, wrap) import Effect (Effect) import Effect.Aff (Aff) import Effect.Class (class MonadEffect, liftEffect) @@ -87,7 +85,6 @@ import Test.Ctl.Fixtures ) import Test.Ctl.Utils (errMaybe) import Test.Spec.Assertions (expectError, shouldEqual, shouldSatisfy) -import Untagged.Union (asOneOf) suite :: TestPlanM (Aff Unit) Unit suite = do @@ -110,7 +107,7 @@ suite = do cslPd <- errMaybe "Failed to convert from CTL PlutusData to CSL PlutusData" $ SPD.convertPlutusData ctlPd - let pdBytes = toBytes (asOneOf cslPd) + let pdBytes = Serialization.toBytes cslPd cslPd' <- errMaybe "Failed to fromBytes PlutusData" $ fromBytes pdBytes ctlPd' <- @@ -129,14 +126,14 @@ suite = do "fixture #8 different Cbor bytes encodings (compact vs general Constr tag encodings)" $ do cslPd' <- errMaybe "Failed to fromBytes PlutusData" $ fromBytes - plutusDataFixture8Bytes + $ wrap plutusDataFixture8Bytes ctlPd' <- errMaybe "Failed to convert from CSL PlutusData to CTL PlutusData" $ DPD.convertPlutusData cslPd' ctlPd' `shouldEqual` plutusDataFixture8 cslPdWp' <- errMaybe "Failed to fromBytes PlutusData" $ fromBytes - plutusDataFixture8Bytes' + $ wrap plutusDataFixture8Bytes' ctlPdWp' <- errMaybe "Failed to convert from CSL PlutusData to CTL PlutusData" $ @@ -153,7 +150,7 @@ suite = do output `shouldEqual` txOutputFixture1 test "fixture #1" do res <- errMaybe "Failed deserialization 4" do - newTransactionUnspentOutputFromBytes utxoFixture1 >>= + (fromBytes $ wrap utxoFixture1) >>= convertUnspentOutput res `shouldEqual` utxoFixture1' group "Transaction Roundtrips" do @@ -166,7 +163,7 @@ suite = do group "WitnessSet - deserialization" do group "fixture #1" do res <- errMaybe "Failed deserialization 5" do - deserializeWitnessSet witnessSetFixture1 >>= convertWitnessSet + (fromBytes $ wrap witnessSetFixture1) >>= convertWitnessSet test "has vkeys" do (unwrap res).vkeys `shouldSatisfy` isJust test "has plutusData" do @@ -181,15 +178,15 @@ suite = do (unwrap res).nativeScripts `shouldSatisfy` isNothing test "fixture #2" do res <- errMaybe "Failed deserialization 6" do - deserializeWitnessSet witnessSetFixture2 >>= convertWitnessSet + (fromBytes $ wrap witnessSetFixture2) >>= convertWitnessSet res `shouldEqual` witnessSetFixture2Value test "fixture #3" do res <- errMaybe "Failed deserialization 7" do - deserializeWitnessSet witnessSetFixture3 >>= convertWitnessSet + (fromBytes $ wrap witnessSetFixture3) >>= convertWitnessSet res `shouldEqual` witnessSetFixture3Value group "fixture #4" do res <- errMaybe "Failed deserialization 8" $ - deserializeWitnessSet witnessSetFixture4 >>= convertWitnessSet + (fromBytes $ wrap witnessSetFixture4) >>= convertWitnessSet test "has nativeScripts" do (unwrap res).nativeScripts `shouldSatisfy` isJust group "NativeScript - deserializaton is inverse to serialization" do @@ -227,11 +224,11 @@ suite = do -> m Unit witnessSetRoundTrip fixture = do ws0 <- errMaybe "Failed deserialization" $ - deserializeWitnessSet fixture >>= convertWitnessSet + (fromBytes $ wrap fixture) >>= convertWitnessSet ws1 <- liftEffect $ SW.convertWitnessSet ws0 ws2 <- errMaybe "Failed deserialization" $ convertWitnessSet ws1 ws0 `shouldEqual` ws2 -- value representation - let wsBytes = Serialization.toBytes (asOneOf ws1) + let wsBytes = unwrap $ Serialization.toBytes ws1 wsBytes `shouldEqual` fixture -- byte representation test "fixture #1" $ witnessSetRoundTrip witnessSetFixture1 test "fixture #2" $ witnessSetRoundTrip witnessSetFixture2 @@ -262,7 +259,7 @@ testNativeScript input = do purescript to handle it correctly. -} - let bytes = Serialization.toBytes (asOneOf serialized) + let bytes = Serialization.toBytes serialized res <- errMaybe "Failed deserialization" $ fromBytes bytes res' <- errMaybe "Failed deserialization" $ NSD.convertNativeScript res res' `shouldEqual` input diff --git a/test/Fixtures.purs b/test/Fixtures.purs index 0015e5f31b..47e0c05536 100644 --- a/test/Fixtures.purs +++ b/test/Fixtures.purs @@ -176,10 +176,6 @@ import Ctl.Internal.Types.ByteArray import Ctl.Internal.Types.Int as Int import Ctl.Internal.Types.OutputDatum (OutputDatum(NoOutputDatum, OutputDatum)) import Ctl.Internal.Types.PlutusData as PD -import Ctl.Internal.Types.RawBytes - ( hexToRawBytesUnsafe - , rawBytesFromIntArrayUnsafe - ) import Ctl.Internal.Types.RedeemerTag (RedeemerTag(Spend)) import Ctl.Internal.Types.RewardAddress (RewardAddress(RewardAddress)) import Ctl.Internal.Types.Scripts @@ -224,13 +220,13 @@ txOutputFixture1 = keyHashCredential $ unsafePartial $ fromJust $ ed25519KeyHashFromBytes -- $ T.Bech32 "hstk_1rsf0q0q77t5nttxrtmpwd7tvv58a80a686t92pgy65ekz0s8ncu" - $ hexToRawBytesUnsafe + $ hexToByteArrayUnsafe "1c12f03c1ef2e935acc35ec2e6f96c650fd3bfba3e96550504d53361" , paymentCred: keyHashCredential $ unsafePartial $ fromJust $ ed25519KeyHashFromBytes -- "hbas_1xranhpfej50zdup5jy995dlj9juem9x36syld8wm465hz92acfp" - $ hexToRawBytesUnsafe + $ hexToByteArrayUnsafe "30fb3b8539951e26f034910a5a37f22cb99d94d1d409f69ddbaea971" } , amount: Value (Coin $ BigInt.fromInt 0) mempty @@ -573,10 +569,9 @@ txFixture4 = , StakeDelegation stake1 (wrap ed25519KeyHash1) , PoolRegistration { operator: wrap ed25519KeyHash1 - , vrfKeyhash: unsafePartial $ fromJust $ + , vrfKeyhash: unsafePartial $ fromJust $ (fromBytes <<< wrap) =<< hexToByteArray "fbf6d41985670b9041c5bf362b5262cf34add5d265975de176d613ca05f37096" - >>= vrfKeyHashFromBytes , pledge: bigNumOne , cost: bigNumOne , margin: { numerator: bigNumOne, denominator: bigNumOne } @@ -609,16 +604,15 @@ txFixture4 = , epoch: Epoch one } , GenesisKeyDelegation - { genesisHash: GenesisHash $ - hexToByteArrayUnsafe - "5d677265fa5bb21ce6d8c7502aca70b9316d10e958611f3c6b758f65" - , genesisDelegateHash: GenesisDelegateHash $ - hexToByteArrayUnsafe - "5d677265fa5bb21ce6d8c7502aca70b9316d10e958611f3c6b758f65" - , vrfKeyhash: unsafePartial $ fromJust $ + { genesisHash: GenesisHash + $ hexToByteArrayUnsafe + "5d677265fa5bb21ce6d8c7502aca70b9316d10e958611f3c6b758f65" + , genesisDelegateHash: GenesisDelegateHash + $ hexToByteArrayUnsafe + "5d677265fa5bb21ce6d8c7502aca70b9316d10e958611f3c6b758f65" + , vrfKeyhash: unsafePartial $ fromJust $ (fromBytes <<< wrap) =<< hexToByteArray "fbf6d41985670b9041c5bf362b5262cf34add5d265975de176d613ca05f37096" - >>= vrfKeyHashFromBytes } , MoveInstantaneousRewardsCert $ ToOtherPot { pot: one @@ -917,7 +911,7 @@ utxoFixture1' = , paymentCred: keyHashCredential $ unsafePartial $ fromJust $ ed25519KeyHashFromBytes $ - rawBytesFromIntArrayUnsafe + byteArrayFromIntArrayUnsafe [ 243 , 63 , 250 @@ -950,7 +944,7 @@ utxoFixture1' = , delegationCred: keyHashCredential $ unsafePartial $ fromJust $ ed25519KeyHashFromBytes $ - ( rawBytesFromIntArrayUnsafe + ( byteArrayFromIntArrayUnsafe [ 57 , 3 , 16 @@ -1175,8 +1169,8 @@ addressString1 = mkTxInput :: { txId :: String, ix :: Int } -> TransactionInput mkTxInput { txId, ix } = TransactionInput - { transactionId: TransactionHash $ - hexToByteArrayUnsafe txId + { transactionId: TransactionHash + $ hexToByteArrayUnsafe txId , index: UInt.fromInt ix } @@ -1191,7 +1185,7 @@ ed25519KeyHashFixture1 = -- $ Bech32 "hstk_1rsf0q0q77t5nttxrtmpwd7tvv58a80a686t92pgy65ekz0s8ncu" unsafePartial $ fromJust $ ed25519KeyHashFromBytes - $ hexToRawBytesUnsafe + $ hexToByteArrayUnsafe "1c12f03c1ef2e935acc35ec2e6f96c650fd3bfba3e96550504d53361" ed25519KeyHashFixture2 :: Ed25519KeyHash @@ -1199,7 +1193,7 @@ ed25519KeyHashFixture2 = -- "hbas_1xranhpfej50zdup5jy995dlj9juem9x36syld8wm465hz92acfp" unsafePartial $ fromJust $ ed25519KeyHashFromBytes - $ hexToRawBytesUnsafe + $ hexToByteArrayUnsafe "30fb3b8539951e26f034910a5a37f22cb99d94d1d409f69ddbaea971" nativeScriptFixture1 :: NativeScript @@ -1230,11 +1224,11 @@ keyHashBaseAddress { payment, stake } = baseAddressToAddress $ baseAddress , delegationCred: keyHashCredential $ unsafePartial $ fromJust $ ed25519KeyHashFromBytes -- $ T.Bech32 "hstk_1rsf0q0q77t5nttxrtmpwd7tvv58a80a686t92pgy65ekz0s8ncu" - $ hexToRawBytesUnsafe stake + $ hexToByteArrayUnsafe stake , paymentCred: keyHashCredential $ unsafePartial $ fromJust $ ed25519KeyHashFromBytes -- "hbas_1xranhpfej50zdup5jy995dlj9juem9x36syld8wm465hz92acfp" - $ hexToRawBytesUnsafe payment + $ hexToByteArrayUnsafe payment } plutusDataFixture1 :: PD.PlutusData @@ -1307,7 +1301,7 @@ plutusDataFixture8Bytes' = hexToByteArrayUnsafe scriptHash1 :: ScriptHash scriptHash1 = unsafePartial $ fromJust $ scriptHashFromBytes $ - hexToRawBytesUnsafe + hexToByteArrayUnsafe "5d677265fa5bb21ce6d8c7502aca70b9316d10e958611f3c6b758f65" policyId :: MintingPolicyHash diff --git a/test/Hashing.purs b/test/Hashing.purs index ddd95070ab..32baea24f6 100644 --- a/test/Hashing.purs +++ b/test/Hashing.purs @@ -20,7 +20,6 @@ import Ctl.Internal.Types.ByteArray , hexToByteArrayUnsafe ) import Ctl.Internal.Types.PlutusData (PlutusData(Integer)) -import Ctl.Internal.Types.RawBytes (hexToRawBytesUnsafe) import Ctl.Internal.Types.Scripts (PlutusScript, plutusV1Script, plutusV2Script) import Ctl.Internal.Types.Transaction (DataHash) import Data.BigInt (fromInt) @@ -114,16 +113,16 @@ plutusV1ScriptFixture = plutusV1ScriptHashFixture :: ScriptHash plutusV1ScriptHashFixture = unsafePartial $ fromJust $ scriptHashFromBytes $ - hexToRawBytesUnsafe + hexToByteArrayUnsafe "67f33146617a5e61936081db3b2117cbf59bd2123748f58ac9678656" plutusV2ScriptFixture :: PlutusScript plutusV2ScriptFixture = - plutusV2Script $ - hexToByteArrayUnsafe "4d01000033222220051200120011" + plutusV2Script + $ hexToByteArrayUnsafe "4d01000033222220051200120011" plutusV2ScriptHashFixture :: ScriptHash plutusV2ScriptHashFixture = unsafePartial $ fromJust $ scriptHashFromBytes $ - hexToRawBytesUnsafe + hexToByteArrayUnsafe "793f8c8cffba081b2a56462fc219cc8fe652d6a338b62c7b134876e7" diff --git a/test/NativeScript.purs b/test/NativeScript.purs index ca5b848783..29b90adf79 100644 --- a/test/NativeScript.purs +++ b/test/NativeScript.purs @@ -13,7 +13,7 @@ import Ctl.Internal.Serialization.Hash , ed25519KeyHashFromBytes ) import Ctl.Internal.Test.TestPlanM (TestPlanM) -import Ctl.Internal.Types.RawBytes (hexToRawBytesUnsafe) +import Ctl.Internal.Types.ByteArray (hexToByteArrayUnsafe) import Data.Either (Either(Right)) import Data.Maybe (fromJust) import Data.Set as Set @@ -222,12 +222,14 @@ suite = do decodeAeson (encodeAeson script) === Right script pk1 :: Ed25519KeyHash -pk1 = unsafePartial $ fromJust $ ed25519KeyHashFromBytes $ hexToRawBytesUnsafe - "1c12f03c1ef2e935acc35ec2e6f96c650fd3bfba3e96550504d53361" +pk1 = unsafePartial $ fromJust $ ed25519KeyHashFromBytes $ + hexToByteArrayUnsafe + "1c12f03c1ef2e935acc35ec2e6f96c650fd3bfba3e96550504d53361" pk2 :: Ed25519KeyHash -pk2 = unsafePartial $ fromJust $ ed25519KeyHashFromBytes $ hexToRawBytesUnsafe - "30fb3b8539951e26f034910a5a37f22cb99d94d1d409f69ddbaea971" +pk2 = unsafePartial $ fromJust $ ed25519KeyHashFromBytes $ + hexToByteArrayUnsafe + "30fb3b8539951e26f034910a5a37f22cb99d94d1d409f69ddbaea971" pk3 :: Ed25519KeyHash pk3 = unsafePartial $ fromJust do @@ -235,9 +237,11 @@ pk3 = unsafePartial $ fromJust do "addr_vkh1zuctrdcq6ctd29242w8g84nlz0q38t2lnv3zzfcrfqktx0c9tzp" pk4 :: Ed25519KeyHash -pk4 = unsafePartial $ fromJust $ ed25519KeyHashFromBytes $ hexToRawBytesUnsafe - "30fb3b8529951e26f034910a5a37f22cb99d94d1d409f69ddbaea971" +pk4 = unsafePartial $ fromJust $ ed25519KeyHashFromBytes $ + hexToByteArrayUnsafe + "30fb3b8529951e26f034910a5a37f22cb99d94d1d409f69ddbaea971" pk5 :: Ed25519KeyHash -pk5 = unsafePartial $ fromJust $ ed25519KeyHashFromBytes $ hexToRawBytesUnsafe - "30fb3b8529951e26f034919a5a37f22cb99d94d1d409f69ddbaea971" +pk5 = unsafePartial $ fromJust $ ed25519KeyHashFromBytes $ + hexToByteArrayUnsafe + "30fb3b8529951e26f034919a5a37f22cb99d94d1d409f69ddbaea971" diff --git a/test/Serialization.purs b/test/Serialization.purs index 90842e92a7..fa71b05359 100644 --- a/test/Serialization.purs +++ b/test/Serialization.purs @@ -24,7 +24,7 @@ import Ctl.Internal.Types.PlutusData as PD import Data.BigInt as BigInt import Data.Either (hush) import Data.Maybe (Maybe, isJust, isNothing) -import Data.Newtype (unwrap) +import Data.Newtype (unwrap, wrap) import Data.Tuple.Nested ((/\)) import Effect.Aff (Aff) import Effect.Class (liftEffect) @@ -48,7 +48,6 @@ import Test.Ctl.Fixtures ) import Test.Ctl.Utils (errMaybe) import Test.Spec.Assertions (shouldEqual, shouldSatisfy) -import Untagged.Union (asOneOf) suite :: TestPlanM (Aff Unit) Unit suite = do @@ -74,7 +73,7 @@ suite = do let txString = "5d677265fa5bb21ce6d8c7502aca70b9316d10e958611f3c6b758f65ad959996" - txBytes = hexToByteArrayUnsafe txString + txBytes = wrap $ hexToByteArrayUnsafe txString _txHash :: TransactionHash <- liftEffect $ fromBytesEffect txBytes pure unit test "PlutusData #1 - Constr" $ do @@ -112,12 +111,12 @@ suite = do datum = PD.Integer (BigInt.fromInt 0) datum' <- errMaybe "Cannot convertPlutusData" $ convertPlutusData datum - let bytes = toBytes (asOneOf datum') - byteArrayToHex bytes `shouldEqual` "00" + let bytes = toBytes datum' + byteArrayToHex (unwrap bytes) `shouldEqual` "00" test "TransactionOutput serialization" $ liftEffect do txo <- convertTxOutput txOutputFixture1 - let bytes = toBytes (asOneOf txo) - byteArrayToHex bytes `shouldEqual` txOutputBinaryFixture1 + let bytes = toBytes txo + byteArrayToHex (unwrap bytes) `shouldEqual` txOutputBinaryFixture1 test "Transaction serialization #1" $ serializeTX txFixture1 txBinaryFixture1 test "Transaction serialization #2 - tokens" $ @@ -158,15 +157,14 @@ serializeTX :: Transaction -> String -> Aff Unit serializeTX tx fixture = liftEffect $ do cslTX <- TS.convertTransaction $ tx - let bytes = toBytes (asOneOf cslTX) - byteArrayToHex bytes `shouldEqual` fixture + let bytes = toBytes cslTX + byteArrayToHex (unwrap bytes) `shouldEqual` fixture txSerializedRoundtrip :: Transaction -> Aff Unit txSerializedRoundtrip tx = do cslTX <- liftEffect $ TS.convertTransaction tx - let serialized = toBytes (asOneOf cslTX) - deserialized <- errMaybe "Cannot deserialize bytes" $ fromBytes - serialized + let serialized = toBytes cslTX + deserialized <- errMaybe "Cannot deserialize bytes" $ fromBytes serialized expected <- errMaybe "Cannot convert TX from CSL to CTL" $ hush $ TD.convertTransaction deserialized tx `shouldEqual` expected diff --git a/test/Serialization/Address.purs b/test/Serialization/Address.purs index a4bcd0bee9..7a08b17fb6 100644 --- a/test/Serialization/Address.purs +++ b/test/Serialization/Address.purs @@ -44,7 +44,7 @@ import Ctl.Internal.Serialization.Hash import Ctl.Internal.Test.TestPlanM (TestPlanM) import Ctl.Internal.Types.Aliases (Bech32String) import Ctl.Internal.Types.BigNum (fromInt, fromStringUnsafe) as BigNum -import Ctl.Internal.Types.RawBytes (hexToRawBytesUnsafe) +import Ctl.Internal.Types.ByteArray (hexToByteArrayUnsafe) import Data.Maybe (Maybe(Nothing)) import Data.Newtype (unwrap, wrap) import Effect.Aff (Aff) @@ -68,7 +68,7 @@ mPkh :: Maybe Ed25519KeyHash mPkh = ed25519KeyHashFromBech32 pkhBech32 mScriptHash :: Maybe ScriptHash -mScriptHash = scriptHashFromBytes $ hexToRawBytesUnsafe scriptHashHex +mScriptHash = scriptHashFromBytes $ hexToByteArrayUnsafe scriptHashHex addressFunctionsTest :: TestPlanM (Aff Unit) Unit addressFunctionsTest = test "Address tests" $ do diff --git a/test/Serialization/Hash.purs b/test/Serialization/Hash.purs index 9f48f1bd1c..05638f255b 100644 --- a/test/Serialization/Hash.purs +++ b/test/Serialization/Hash.purs @@ -6,20 +6,19 @@ import Ctl.Internal.Serialization.Hash , ed25519KeyHashFromBytes , ed25519KeyHashToBech32 , ed25519KeyHashToBech32Unsafe - , ed25519KeyHashToBytes , scriptHashFromBech32 , scriptHashFromBytes , scriptHashToBech32 , scriptHashToBech32Unsafe - , scriptHashToBytes ) +import Ctl.Internal.Serialization.ToBytes (toBytes) import Ctl.Internal.Test.TestPlanM (TestPlanM) import Ctl.Internal.Types.Aliases (Bech32String) import Ctl.Internal.Types.ByteArray (hexToByteArrayUnsafe) import Data.Eq ((==)) import Data.Function (($)) import Data.Maybe (Maybe(Just, Nothing), isNothing) -import Data.Newtype (wrap) +import Data.Newtype (unwrap) import Data.Unit (Unit) import Effect.Aff (Aff) import Test.Ctl.Utils (assertTrue, errMaybe) @@ -43,8 +42,9 @@ suite = do let pkhB32 = ed25519KeyHashToBech32Unsafe "addr_vkh" pkh mPkhB32 = ed25519KeyHashToBech32 "addr_vkh" pkh - pkhBts = ed25519KeyHashToBytes pkh - pkh2 = ed25519KeyHashFromBytes pkhBts + pkhBts = toBytes pkh + -- TODO: use fromBytes instead? + pkh2 = ed25519KeyHashFromBytes $ unwrap pkhBts assertTrue "Safe ed25519KeyHashToBech32 should produce Just when unsafe version works" @@ -67,14 +67,14 @@ suite = do (isNothing $ scriptHashFromBech32 invalidBech32) scrh <- errMaybe "scriptHashFromBytes failed" $ scriptHashFromBytes - $ wrap $ hexToByteArrayUnsafe scriptHashHex let scrhB32 = scriptHashToBech32Unsafe "stake_vkh" scrh mScrhB32 = scriptHashToBech32 "stake_vkh" scrh - scrhBts = scriptHashToBytes scrh - scrhFromBytes = scriptHashFromBytes scrhBts + scrhBts = toBytes scrh + -- TODO: use fromBytes instead? + scrhFromBytes = scriptHashFromBytes $ unwrap scrhBts scrhFromBech = scriptHashFromBech32 scrhB32 assertTrue "Safe scriptHashToBech32 should produce Just when unsafe works" From 8867687fd92a3169e257b15c5901c306d696a704 Mon Sep 17 00:00:00 2001 From: Calum Sieppert Date: Fri, 2 Dec 2022 16:33:47 -0700 Subject: [PATCH 039/373] Get #1073 changes type checking --- src/Contract/Transaction.purs | 4 +- src/Internal/BalanceTx/ExUnitsAndMinFee.purs | 6 +- src/Internal/Cardano/Types/NativeScript.purs | 4 +- src/Internal/Cardano/Types/Transaction.purs | 10 +- src/Internal/Cardano/Types/Value.purs | 5 +- src/Internal/Deserialization/Transaction.purs | 20 ++-- src/Internal/Plutus/Types/CurrencySymbol.purs | 7 +- src/Internal/QueryM/Kupo.purs | 8 +- src/Internal/QueryM/Ogmios.purs | 2 +- src/Internal/QueryM/Pools.purs | 7 +- src/Internal/Serialization.purs | 1 + src/Internal/Serialization/ToBytes.js | 2 +- src/Internal/Serialization/ToBytes.purs | 105 +++++++++++++----- src/Internal/Types/VRFKeyHash.purs | 13 +-- src/Internal/Wallet/Cip30.purs | 2 +- test/Fixtures.purs | 21 ++-- test/Serialization.purs | 2 +- 17 files changed, 132 insertions(+), 87 deletions(-) diff --git a/src/Contract/Transaction.purs b/src/Contract/Transaction.purs index 54f412ebd9..a0cf4066b6 100644 --- a/src/Contract/Transaction.purs +++ b/src/Contract/Transaction.purs @@ -279,8 +279,6 @@ import Effect.Aff (bracket) import Effect.Aff.Class (liftAff) import Effect.Class (liftEffect) import Effect.Exception (throw) --- TODO: Remove once toBytes is switched to Castable -import Untagged.Union (asOneOf) -- | Signs a transaction with potential failure. signTransaction @@ -318,7 +316,7 @@ submitE tx = do cslTx <- liftEffect $ Serialization.convertTransaction (unwrap tx) let txHash = Hashing.transactionHash cslTx logDebug' $ "Pre-calculated tx hash: " <> show txHash - let txCborBytes = wrap $ Serialization.toBytes $ asOneOf cslTx + let txCborBytes = Serialization.toBytes cslTx result <- wrapContract $ QueryM.submitTxOgmios (unwrap txHash) txCborBytes pure $ case result of diff --git a/src/Internal/BalanceTx/ExUnitsAndMinFee.purs b/src/Internal/BalanceTx/ExUnitsAndMinFee.purs index 2ef303193f..b80c90f5e4 100644 --- a/src/Internal/BalanceTx/ExUnitsAndMinFee.purs +++ b/src/Internal/BalanceTx/ExUnitsAndMinFee.purs @@ -85,8 +85,6 @@ import Data.Traversable (for) import Data.Tuple (fst, snd) import Data.Tuple.Nested (type (/\), (/\)) import Effect.Class (liftEffect) --- TODO: Remove once toBytes is switched to Castable -import Untagged.Union (asOneOf) evalTxExecutionUnits :: Transaction @@ -94,9 +92,7 @@ evalTxExecutionUnits -> BalanceTxM Ogmios.TxEvaluationResult evalTxExecutionUnits tx unattachedTx = do txBytes <- liftEffect - ( wrap <<< Serialization.toBytes <<< asOneOf <$> - Serialization.convertTransaction tx - ) + $ Serialization.toBytes <$> Serialization.convertTransaction tx additionalUtxos <- getOgmiosAdditionalUtxoSet evalResult <- unwrap <$> liftQueryM (QueryM.evaluateTxOgmios txBytes additionalUtxos) diff --git a/src/Internal/Cardano/Types/NativeScript.purs b/src/Internal/Cardano/Types/NativeScript.purs index 2cae15101b..000d3f43a8 100644 --- a/src/Internal/Cardano/Types/NativeScript.purs +++ b/src/Internal/Cardano/Types/NativeScript.purs @@ -26,7 +26,7 @@ import Ctl.Internal.Metadata.Helpers (errExpectedObject) import Ctl.Internal.Serialization.Address (Slot) import Ctl.Internal.Serialization.Hash (Ed25519KeyHash, ed25519KeyHashFromBytes) import Ctl.Internal.Types.BigNum (fromString) -import Ctl.Internal.Types.RawBytes (hexToRawBytesUnsafe) +import Ctl.Internal.Types.ByteArray (hexToByteArrayUnsafe) import Data.Array.NonEmpty (fromFoldable) import Data.Either (Either(Left)) import Data.Generic.Rep (class Generic) @@ -68,7 +68,7 @@ instance Arbitrary NativeScript where where pk :: Ed25519KeyHash pk = unsafePartial $ fromJust $ ed25519KeyHashFromBytes $ - hexToRawBytesUnsafe + hexToByteArrayUnsafe "1c12f03c1ef2e935acc35ec2e6f96c650fd3bfba3e96550504d53361" instance DecodeAeson NativeScript where diff --git a/src/Internal/Cardano/Types/Transaction.purs b/src/Internal/Cardano/Types/Transaction.purs index 9859afea20..a7ff112a9d 100644 --- a/src/Internal/Cardano/Types/Transaction.purs +++ b/src/Internal/Cardano/Types/Transaction.purs @@ -165,7 +165,6 @@ import Data.Tuple (Tuple(Tuple)) import Data.Tuple.Nested (type (/\)) import Data.UInt (UInt) import Partial.Unsafe (unsafePartial) -import Untagged.Union (asOneOf) -------------------------------------------------------------------------------- -- `Transaction` @@ -852,7 +851,8 @@ mkFromCslPubKey :: Serialization.PublicKey -> PublicKey mkFromCslPubKey = PublicKey <<< bytesFromPublicKey convertPubKey :: PublicKey -> Serialization.PublicKey -convertPubKey (PublicKey bs) = unsafePartial $ fromJust <<< fromBytes <<< unwrap +convertPubKey (PublicKey bs) = unsafePartial + $ fromJust <<< fromBytes <<< wrap <<< unwrap $ bs derive newtype instance Eq PublicKey @@ -871,15 +871,15 @@ instance Show PublicKey where newtype Ed25519Signature = Ed25519Signature RawBytes mkEd25519Signature :: Bech32String -> Maybe Ed25519Signature -mkEd25519Signature = map (Ed25519Signature <<< wrap <<< toBytes <<< asOneOf) <<< +mkEd25519Signature = map (Ed25519Signature <<< wrap <<< unwrap <<< toBytes) <<< ed25519SignatureFromBech32 mkFromCslEd25519Signature :: Serialization.Ed25519Signature -> Ed25519Signature -mkFromCslEd25519Signature = Ed25519Signature <<< wrap <<< toBytes <<< asOneOf +mkFromCslEd25519Signature = Ed25519Signature <<< wrap <<< unwrap <<< toBytes convertEd25519Signature :: Ed25519Signature -> Serialization.Ed25519Signature convertEd25519Signature (Ed25519Signature bs) = unsafePartial - $ fromJust <<< fromBytes <<< unwrap + $ fromJust <<< fromBytes <<< wrap <<< unwrap $ bs derive newtype instance Eq Ed25519Signature diff --git a/src/Internal/Cardano/Types/Value.purs b/src/Internal/Cardano/Types/Value.purs index 4db914f3c7..59abe88837 100644 --- a/src/Internal/Cardano/Types/Value.purs +++ b/src/Internal/Cardano/Types/Value.purs @@ -68,10 +68,7 @@ import Ctl.Internal.FromData (class FromData) import Ctl.Internal.Helpers (encodeMap, showWithParens) import Ctl.Internal.Metadata.FromMetadata (class FromMetadata) import Ctl.Internal.Metadata.ToMetadata (class ToMetadata) -import Ctl.Internal.Serialization.Hash - ( ScriptHash - , scriptHashFromBytes - ) +import Ctl.Internal.Serialization.Hash (ScriptHash, scriptHashFromBytes) import Ctl.Internal.Serialization.ToBytes (toBytes) import Ctl.Internal.ToData (class ToData) import Ctl.Internal.Types.ByteArray diff --git a/src/Internal/Deserialization/Transaction.purs b/src/Internal/Deserialization/Transaction.purs index eb5bc41cc1..2cfc2e9157 100644 --- a/src/Internal/Deserialization/Transaction.purs +++ b/src/Internal/Deserialization/Transaction.purs @@ -138,7 +138,7 @@ import Ctl.Internal.Serialization.Address , StakeCredential ) as Csl import Ctl.Internal.Serialization.Address (Slot(Slot)) -import Ctl.Internal.Serialization.Hash (Ed25519KeyHash, ScriptHash, VRFKeyHash) +import Ctl.Internal.Serialization.Hash (Ed25519KeyHash, ScriptHash, VRFKeyHash) as Csl import Ctl.Internal.Serialization.Types ( AssetName , AuxiliaryData @@ -441,7 +441,7 @@ foreign import convertMultiHostName_ convertPoolRetirement :: forall (r :: Row Type) - . Ed25519KeyHash + . Csl.Ed25519KeyHash -> Int -> Err r T.Certificate convertPoolRetirement poolKeyHash epochInt = do @@ -842,7 +842,7 @@ foreign import _txBodyRequiredSigners :: ContainerHelper -> MaybeFfiHelper -> Csl.TransactionBody - -> Maybe (Array Ed25519KeyHash) + -> Maybe (Array Csl.Ed25519KeyHash) -- network_id(): NetworkId | void foreign import _txBodyNetworkId @@ -877,7 +877,7 @@ foreign import _unpackUpdate } foreign import _unpackMint - :: ContainerHelper -> Csl.Mint -> Array (ScriptHash /\ Csl.MintAssets) + :: ContainerHelper -> Csl.Mint -> Array (Csl.ScriptHash /\ Csl.MintAssets) foreign import _unpackMintAssets :: ContainerHelper -> Csl.MintAssets -> Array (Csl.AssetName /\ Csl.Int) @@ -886,13 +886,13 @@ type CertConvHelper (r :: Type) = { stakeDeregistration :: Csl.StakeCredential -> r , stakeRegistration :: Csl.StakeCredential -> r , stakeDelegation :: - Csl.StakeCredential -> Ed25519KeyHash -> r + Csl.StakeCredential -> Csl.Ed25519KeyHash -> r , poolRegistration :: Csl.PoolParams -> r - , poolRetirement :: Ed25519KeyHash -> Int -> r + , poolRetirement :: Csl.Ed25519KeyHash -> Int -> r , genesisKeyDelegation :: Csl.GenesisHash -> Csl.GenesisDelegateHash - -> VRFKeyHash + -> Csl.VRFKeyHash -> r , moveInstantaneousRewardsToOtherPotCert :: Number -> Csl.BigNum -> r @@ -906,14 +906,14 @@ foreign import _convertCert -> Csl.Certificate -> Err r T.Certificate -foreign import poolParamsOperator :: Csl.PoolParams -> Ed25519KeyHash -foreign import poolParamsVrfKeyhash :: Csl.PoolParams -> VRFKeyHash +foreign import poolParamsOperator :: Csl.PoolParams -> Csl.Ed25519KeyHash +foreign import poolParamsVrfKeyhash :: Csl.PoolParams -> Csl.VRFKeyHash foreign import poolParamsPledge :: Csl.PoolParams -> Csl.BigNum foreign import poolParamsCost :: Csl.PoolParams -> Csl.BigNum foreign import poolParamsMargin :: Csl.PoolParams -> Csl.UnitInterval foreign import poolParamsRewardAccount :: Csl.PoolParams -> Csl.RewardAddress foreign import poolParamsPoolOwners - :: ContainerHelper -> Csl.PoolParams -> Array Ed25519KeyHash + :: ContainerHelper -> Csl.PoolParams -> Array Csl.Ed25519KeyHash foreign import poolParamsRelays :: ContainerHelper -> Csl.PoolParams -> Array Csl.Relay diff --git a/src/Internal/Plutus/Types/CurrencySymbol.purs b/src/Internal/Plutus/Types/CurrencySymbol.purs index 0d3911dde8..ba17b0a2a5 100644 --- a/src/Internal/Plutus/Types/CurrencySymbol.purs +++ b/src/Internal/Plutus/Types/CurrencySymbol.purs @@ -26,10 +26,7 @@ import Ctl.Internal.Metadata.ToMetadata (class ToMetadata) import Ctl.Internal.Serialization.Hash (ScriptHash, scriptHashFromBytes) import Ctl.Internal.Serialization.ToBytes (toBytes) import Ctl.Internal.ToData (class ToData) -import Ctl.Internal.Types.ByteArray (ByteArray) -import Ctl.Internal.Types.RawBytes - ( hexToRawBytesUnsafe - ) +import Ctl.Internal.Types.ByteArray (ByteArray, hexToByteArrayUnsafe) import Ctl.Internal.Types.Scripts (MintingPolicyHash(MintingPolicyHash)) import Data.Array.NonEmpty (fromArray) import Data.Either (Either(Left)) @@ -71,7 +68,7 @@ instance Arbitrary CurrencySymbol where translate x = scriptHashAsCurrencySymbol $ unsafePartial $ fromJust $ scriptHashFromBytes - $ hexToRawBytesUnsafe x + $ hexToByteArrayUnsafe x adaSymbol :: CurrencySymbol adaSymbol = CurrencySymbol mempty diff --git a/src/Internal/QueryM/Kupo.purs b/src/Internal/QueryM/Kupo.purs index 915dfd2406..94483228fc 100644 --- a/src/Internal/QueryM/Kupo.purs +++ b/src/Internal/QueryM/Kupo.purs @@ -49,13 +49,14 @@ import Ctl.Internal.QueryM , handleAffjaxResponse ) import Ctl.Internal.QueryM.ServerConfig (mkHttpUrl) +import Ctl.Internal.Serialization (toBytes) import Ctl.Internal.Serialization.Address ( Address , addressBech32 , addressFromBech32 , addressFromBytes ) -import Ctl.Internal.Serialization.Hash (ScriptHash, scriptHashToBytes) +import Ctl.Internal.Serialization.Hash (ScriptHash) import Ctl.Internal.Types.ByteArray (ByteArray, byteArrayToHex, hexToByteArray) import Ctl.Internal.Types.CborBytes (hexToCborBytes) import Ctl.Internal.Types.Datum (DataHash(DataHash), Datum) @@ -124,7 +125,8 @@ getDatumByHash (DataHash dataHashBytes) = do getScriptByHash :: ScriptHash -> QueryM (Either ClientError (Maybe ScriptRef)) getScriptByHash scriptHash = do - let endpoint = "/scripts/" <> rawBytesToHex (scriptHashToBytes scriptHash) + let + endpoint = "/scripts/" <> rawBytesToHex (wrap $ unwrap $ toBytes scriptHash) kupoGetRequest endpoint <#> map unwrapKupoScriptRef <<< handleAffjaxResponse @@ -350,7 +352,7 @@ instance DecodeAeson KupoScriptRef where decodeNativeScript :: ByteArray -> Either JsonDecodeError NativeScript decodeNativeScript scriptBytes = do nativeScript <- - flip note (fromBytes scriptBytes) $ + flip note (fromBytes $ wrap scriptBytes) $ TypeMismatch "decodeNativeScript: from_bytes() call failed" flip note (convertNativeScript nativeScript) $ TypeMismatch "decodeNativeScript: failed to convert native script" diff --git a/src/Internal/QueryM/Ogmios.purs b/src/Internal/QueryM/Ogmios.purs index 29854c4961..5d47b1408e 100644 --- a/src/Internal/QueryM/Ogmios.purs +++ b/src/Internal/QueryM/Ogmios.purs @@ -674,7 +674,7 @@ instance DecodeAeson PoolParametersR where vrfKeyhashBytes <- note (TypeMismatch "VRFKeyHash") $ hexToByteArray vrfKeyhashHex vrfKeyhash <- note (TypeMismatch "VRFKeyHash") $ VRFKeyHash <$> fromBytes - vrfKeyhashBytes + (wrap vrfKeyhashBytes) pledge <- objParams .: "pledge" cost <- objParams .: "cost" margin <- decodeUnitInterval =<< objParams .: "margin" diff --git a/src/Internal/QueryM/Pools.purs b/src/Internal/QueryM/Pools.purs index b76cb0e511..9a8f2f788b 100644 --- a/src/Internal/QueryM/Pools.purs +++ b/src/Internal/QueryM/Pools.purs @@ -20,12 +20,11 @@ import Ctl.Internal.QueryM.Ogmios , PoolParametersR(PoolParametersR) ) import Ctl.Internal.QueryM.Ogmios as Ogmios +import Ctl.Internal.Serialization (toBytes) import Ctl.Internal.Serialization.Hash ( ed25519KeyHashToBech32 , ed25519KeyHashToBech32Unsafe - , ed25519KeyHashToBytes , scriptHashToBech32Unsafe - , scriptHashToBytes ) import Ctl.Internal.Types.ByteArray (byteArrayToHex) import Ctl.Internal.Types.PubKeyHash (StakePubKeyHash) @@ -81,7 +80,7 @@ getValidatorHashDelegationsAndRewards skh = do byteHex :: String byteHex = - byteArrayToHex <<< unwrap <<< scriptHashToBytes <<< unwrap $ + byteArrayToHex <<< unwrap <<< toBytes <<< unwrap $ skh -- TODO: batched variant @@ -99,6 +98,6 @@ getPubKeyHashDelegationsAndRewards pkh = do byteHex :: String byteHex = - byteArrayToHex <<< unwrap <<< ed25519KeyHashToBytes <<< unwrap $ + byteArrayToHex <<< unwrap <<< toBytes <<< unwrap $ unwrap pkh diff --git a/src/Internal/Serialization.purs b/src/Internal/Serialization.purs index a5c474ee36..e536817090 100644 --- a/src/Internal/Serialization.purs +++ b/src/Internal/Serialization.purs @@ -85,6 +85,7 @@ import Ctl.Internal.Serialization.Types ( AssetName , Assets , AuxiliaryData + , AuxiliaryDataHash , BigInt , Certificate , Certificates diff --git a/src/Internal/Serialization/ToBytes.js b/src/Internal/Serialization/ToBytes.js index 7b7280740f..6107d0d2ad 100644 --- a/src/Internal/Serialization/ToBytes.js +++ b/src/Internal/Serialization/ToBytes.js @@ -1 +1 @@ -exports.toBytes = sth => sth.to_bytes(); +exports._toBytes = sth => sth.to_bytes(); diff --git a/src/Internal/Serialization/ToBytes.purs b/src/Internal/Serialization/ToBytes.purs index c3caa22ffc..2634bd5bd7 100644 --- a/src/Internal/Serialization/ToBytes.purs +++ b/src/Internal/Serialization/ToBytes.purs @@ -1,6 +1,13 @@ -module Ctl.Internal.Serialization.ToBytes (toBytes) where +module Ctl.Internal.Serialization.ToBytes + ( class ToBytes + , toBytes + , toBytes' + ) where + +import Prelude import Ctl.Internal.Serialization.Address (Address) +import Ctl.Internal.Serialization.Hash (Ed25519KeyHash, ScriptHash, VRFKeyHash) import Ctl.Internal.Serialization.Types ( AuxiliaryDataHash , DataHash @@ -9,6 +16,7 @@ import Ctl.Internal.Serialization.Types , GenesisHash , NativeScript , PlutusData + , PoolMetadataHash , Redeemers , ScriptDataHash , Transaction @@ -17,32 +25,79 @@ import Ctl.Internal.Serialization.Types , TransactionOutput , TransactionUnspentOutput , TransactionWitnessSet - , VRFKeyHash , Value ) import Ctl.Internal.Types.ByteArray (ByteArray) -import Untagged.Union (type (|+|)) +import Ctl.Internal.Types.CborBytes (CborBytes(CborBytes)) -- NOTE returns cbor encoding for all but hash types, for which it returns raw bytes -foreign import toBytes - :: ( Transaction - |+| TransactionBody - |+| TransactionOutput - |+| TransactionUnspentOutput - |+| TransactionHash - |+| DataHash - |+| PlutusData - |+| TransactionWitnessSet - |+| NativeScript - |+| ScriptDataHash - |+| Redeemers - |+| GenesisHash - |+| GenesisDelegateHash - |+| AuxiliaryDataHash - |+| Address - |+| Value - |+| Ed25519Signature - |+| VRFKeyHash - -- Add more as needed. - ) - -> ByteArray +foreign import _toBytes :: forall (a :: Type). a -> ByteArray + +class ToBytes a where + toBytes' :: a -> ByteArray + +instance ToBytes Address where + toBytes' = _toBytes + +instance ToBytes AuxiliaryDataHash where + toBytes' = _toBytes + +instance ToBytes DataHash where + toBytes' = _toBytes + +instance ToBytes Ed25519KeyHash where + toBytes' = _toBytes + +instance ToBytes Ed25519Signature where + toBytes' = _toBytes + +instance ToBytes GenesisDelegateHash where + toBytes' = _toBytes + +instance ToBytes GenesisHash where + toBytes' = _toBytes + +instance ToBytes NativeScript where + toBytes' = _toBytes + +instance ToBytes PlutusData where + toBytes' = _toBytes + +instance ToBytes PoolMetadataHash where + toBytes' = _toBytes + +instance ToBytes Redeemers where + toBytes' = _toBytes + +instance ToBytes ScriptDataHash where + toBytes' = _toBytes + +instance ToBytes ScriptHash where + toBytes' = _toBytes + +instance ToBytes Transaction where + toBytes' = _toBytes + +instance ToBytes TransactionBody where + toBytes' = _toBytes + +instance ToBytes TransactionHash where + toBytes' = _toBytes + +instance ToBytes TransactionOutput where + toBytes' = _toBytes + +instance ToBytes TransactionUnspentOutput where + toBytes' = _toBytes + +instance ToBytes TransactionWitnessSet where + toBytes' = _toBytes + +instance ToBytes Value where + toBytes' = _toBytes + +instance ToBytes VRFKeyHash where + toBytes' = _toBytes + +toBytes :: forall (a :: Type). ToBytes a => a -> CborBytes +toBytes = CborBytes <<< toBytes' diff --git a/src/Internal/Types/VRFKeyHash.purs b/src/Internal/Types/VRFKeyHash.purs index f8b82355df..069e1009e0 100644 --- a/src/Internal/Types/VRFKeyHash.purs +++ b/src/Internal/Types/VRFKeyHash.purs @@ -9,32 +9,31 @@ import Prelude import Aeson (class EncodeAeson, encodeAeson') import Ctl.Internal.Deserialization.FromBytes (fromBytes) -import Ctl.Internal.Serialization.ToBytes (toBytes) import Ctl.Internal.Serialization.Hash as Serialization +import Ctl.Internal.Serialization.ToBytes (toBytes) import Ctl.Internal.Types.ByteArray (ByteArray, byteArrayToHex) import Data.Function (on) import Data.Maybe (Maybe) --- TODO: Remove once toBytes is switched to Castable -import Untagged.Union (asOneOf) +import Data.Newtype (unwrap, wrap) newtype VRFKeyHash = VRFKeyHash Serialization.VRFKeyHash instance Show VRFKeyHash where show (VRFKeyHash kh) = - "(VRFKeyHash " <> show (byteArrayToHex $ toBytes $ asOneOf kh) <> ")" + "(VRFKeyHash " <> show (byteArrayToHex $ unwrap $ toBytes kh) <> ")" instance Eq VRFKeyHash where eq = eq `on` vrfKeyHashToBytes instance EncodeAeson VRFKeyHash where encodeAeson' (VRFKeyHash kh) = - asOneOf kh # toBytes >>> byteArrayToHex >>> encodeAeson' + toBytes kh # unwrap >>> byteArrayToHex >>> encodeAeson' unVRFKeyHash :: VRFKeyHash -> Serialization.VRFKeyHash unVRFKeyHash (VRFKeyHash kh) = kh vrfKeyHashFromBytes :: ByteArray -> Maybe VRFKeyHash -vrfKeyHashFromBytes = fromBytes >>> map VRFKeyHash +vrfKeyHashFromBytes = wrap >>> fromBytes >>> map VRFKeyHash vrfKeyHashToBytes :: VRFKeyHash -> ByteArray -vrfKeyHashToBytes (VRFKeyHash kh) = toBytes $ asOneOf kh +vrfKeyHashToBytes (VRFKeyHash kh) = unwrap $ toBytes kh diff --git a/src/Internal/Wallet/Cip30.purs b/src/Internal/Wallet/Cip30.purs index 599c699b29..e79984a4ef 100644 --- a/src/Internal/Wallet/Cip30.purs +++ b/src/Internal/Wallet/Cip30.purs @@ -41,8 +41,8 @@ import Ctl.Internal.Types.ByteArray (byteArrayToHex) import Ctl.Internal.Types.CborBytes ( CborBytes , cborBytesToHex - , rawBytesAsCborBytes , hexToCborBytes + , rawBytesAsCborBytes ) import Ctl.Internal.Types.RawBytes ( RawBytes diff --git a/test/Fixtures.purs b/test/Fixtures.purs index 47e0c05536..b558620a77 100644 --- a/test/Fixtures.purs +++ b/test/Fixtures.purs @@ -78,10 +78,7 @@ import Prelude import Aeson (Aeson, aesonNull, decodeAeson, fromString, parseJsonStringToAeson) import Contract.Numeric.BigNum (BigNum) import Contract.Numeric.BigNum (fromBigInt, fromInt) as BigNum -import Contract.Transaction - ( PoolPubKeyHash(PoolPubKeyHash) - , vrfKeyHashFromBytes - ) +import Contract.Transaction (PoolPubKeyHash(PoolPubKeyHash)) import Ctl.Internal.Cardano.Types.NativeScript ( NativeScript ( ScriptPubkey @@ -142,6 +139,7 @@ import Ctl.Internal.Cardano.Types.Value , mkNonAdaAsset , mkSingletonNonAdaAsset ) +import Ctl.Internal.Deserialization.FromBytes (fromBytes) import Ctl.Internal.Metadata.Cip25.Cip25String (Cip25String, mkCip25String) import Ctl.Internal.Metadata.Cip25.Common (Cip25TokenName(Cip25TokenName)) import Ctl.Internal.Metadata.Cip25.V2 @@ -195,6 +193,7 @@ import Ctl.Internal.Types.TransactionMetadata , TransactionMetadatum(Text) , TransactionMetadatumLabel(TransactionMetadatumLabel) ) +import Ctl.Internal.Types.VRFKeyHash (VRFKeyHash(VRFKeyHash)) import Data.Array as Array import Data.BigInt as BigInt import Data.Either (fromRight, hush) @@ -569,9 +568,10 @@ txFixture4 = , StakeDelegation stake1 (wrap ed25519KeyHash1) , PoolRegistration { operator: wrap ed25519KeyHash1 - , vrfKeyhash: unsafePartial $ fromJust $ (fromBytes <<< wrap) =<< - hexToByteArray - "fbf6d41985670b9041c5bf362b5262cf34add5d265975de176d613ca05f37096" + , vrfKeyhash: unsafePartial $ VRFKeyHash $ fromJust $ + (fromBytes <<< wrap) =<< + hexToByteArray + "fbf6d41985670b9041c5bf362b5262cf34add5d265975de176d613ca05f37096" , pledge: bigNumOne , cost: bigNumOne , margin: { numerator: bigNumOne, denominator: bigNumOne } @@ -610,9 +610,10 @@ txFixture4 = , genesisDelegateHash: GenesisDelegateHash $ hexToByteArrayUnsafe "5d677265fa5bb21ce6d8c7502aca70b9316d10e958611f3c6b758f65" - , vrfKeyhash: unsafePartial $ fromJust $ (fromBytes <<< wrap) =<< - hexToByteArray - "fbf6d41985670b9041c5bf362b5262cf34add5d265975de176d613ca05f37096" + , vrfKeyhash: unsafePartial $ VRFKeyHash $ fromJust $ + (fromBytes <<< wrap) =<< + hexToByteArray + "fbf6d41985670b9041c5bf362b5262cf34add5d265975de176d613ca05f37096" } , MoveInstantaneousRewardsCert $ ToOtherPot { pot: one diff --git a/test/Serialization.purs b/test/Serialization.purs index fa71b05359..91dd1cc6d7 100644 --- a/test/Serialization.purs +++ b/test/Serialization.purs @@ -66,7 +66,7 @@ suite = do let pkBytes = bytesFromPublicKey $ convertPubKey pk (pk'' :: Maybe PublicKey) = mkFromCslPubKey <$> fromBytes - (unwrap pkBytes) + (wrap $ unwrap pkBytes) pk'' `shouldSatisfy` isJust test "newTransactionHash" do From ef13e13902453525099473cee74541e7c573698e Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Sat, 3 Dec 2022 14:21:01 +0100 Subject: [PATCH 040/373] BalanceTx: Code refactoring --- src/Internal/BalanceTx/BalanceTx.purs | 217 ++++++++++++++------------ 1 file changed, 116 insertions(+), 101 deletions(-) diff --git a/src/Internal/BalanceTx/BalanceTx.purs b/src/Internal/BalanceTx/BalanceTx.purs index 338eb096ea..9fce0e0d01 100644 --- a/src/Internal/BalanceTx/BalanceTx.purs +++ b/src/Internal/BalanceTx/BalanceTx.purs @@ -203,8 +203,14 @@ balanceTxWithConstraints unbalancedTx constraintsBuilder = do selectionStrategy <- asksConstraints Constraints._selectionStrategy -- Balance and finalize the transaction: - runBalancer selectionStrategy allUtxos availableUtxos changeAddr certsFee - (unbalancedTx # _transaction' .~ unbalancedCollTx) + runBalancer + { strategy: selectionStrategy + , unbalancedTx: unbalancedTx # _transaction' .~ unbalancedCollTx + , changeAddress: changeAddr + , allUtxos + , utxos: availableUtxos + , certsFee + } where getChangeAddress :: BalanceTxM Address getChangeAddress = @@ -232,112 +238,129 @@ balanceTxWithConstraints unbalancedTx constraintsBuilder = do -- Balancing Algorithm -------------------------------------------------------------------------------- +type BalancerParams = + { strategy :: SelectionStrategy + , unbalancedTx :: UnattachedUnbalancedTx + , changeAddress :: Address + , allUtxos :: UtxoMap + , utxos :: UtxoMap + , certsFee :: Coin + } + type BalancerState = - { unbalancedTx :: UnattachedUnbalancedTx - , changeOutputs :: Array TransactionOutput + { transaction :: UnattachedUnbalancedTx , leftoverUtxos :: UtxoIndex + , changeOutputs :: Array TransactionOutput + , minFee :: BigInt } -runBalancer - :: SelectionStrategy - -> UtxoMap +initBalancerState + :: UnattachedUnbalancedTx -> UtxoMap - -> Address - -> Coin - -> UnattachedUnbalancedTx - -> BalanceTxM FinalizedTransaction -runBalancer strategy allUtxos utxos changeAddress certsFee unbalancedTx' = do + -> BalancerState +initBalancerState transaction = + buildUtxoIndex >>> + { transaction, leftoverUtxos: _, changeOutputs: mempty, minFee: zero } + +data BalancerStep + = PrebalanceTx BalancerState + | BalanceChangeAndMinFee BalancerState + +runBalancer :: BalancerParams -> BalanceTxM FinalizedTransaction +runBalancer p = do spendableUtxos <- getSpendableUtxos - addLovelacesToTransactionOutputs unbalancedTx' - >>= ((\tx -> mkBalancerState tx mempty spendableUtxos) >>> prebalanceTx) + unbalancedTx <- addLovelacesToTransactionOutputs p.unbalancedTx + mainLoop (initBalancerState unbalancedTx spendableUtxos) where getSpendableUtxos :: BalanceTxM UtxoMap getSpendableUtxos = asksConstraints Constraints._nonSpendableInputs <#> \nonSpendableInputs -> - flip Map.filterKeys utxos \oref -> not $ + flip Map.filterKeys p.utxos \oref -> not $ Set.member oref nonSpendableInputs - || Set.member oref (unbalancedTx' ^. _body' <<< _referenceInputs) - - -- | Determines which balancing step will be performed next. - -- | - -- | If the transaction remains unbalanced (i.e. `requiredValue != mempty`) - -- | after generation of change, the first balancing step (`prebalanceTx`) - -- | is performed, otherwise we proceed to `balanceChangeAndMinFee`. - runNextBalancingStep - :: UnattachedUnbalancedTx -> UtxoIndex -> BalanceTxM FinalizedTransaction - runNextBalancingStep unbalancedTx leftoverUtxos = do - let txBody = unbalancedTx ^. _body' - inputValue <- except $ getInputValue allUtxos txBody - changeOutputs <- makeChange changeAddress inputValue certsFee txBody - - requiredValue <- - except $ getRequiredValue certsFee utxos - (setTxChangeOutputs changeOutputs unbalancedTx ^. _body') - - { unbalancedTx, changeOutputs, leftoverUtxos } # - if requiredValue == mempty then balanceChangeAndMinFee else prebalanceTx - - -- | Selects a combination of unspent transaction outputs from the wallet's - -- | utxo set so that the total input value is sufficient to cover all - -- | transaction outputs, including generated change and min fee. - prebalanceTx :: BalancerState -> BalanceTxM FinalizedTransaction - prebalanceTx state@{ unbalancedTx, changeOutputs, leftoverUtxos } = do - logBalancerState "Pre-balancing (Stage 1)" utxos state - - selectionState <- performCoinSelection - let - leftoverUtxos' :: UtxoIndex - leftoverUtxos' = selectionState ^. _leftoverUtxos - - selectedInputs' :: Set TransactionInput - selectedInputs' = selectedInputs selectionState + || Set.member oref (p.unbalancedTx ^. _body' <<< _referenceInputs) - unbalancedTxWithInputs :: UnattachedUnbalancedTx - unbalancedTxWithInputs = - unbalancedTx # _body' <<< _inputs %~ Set.union selectedInputs' - - runNextBalancingStep unbalancedTxWithInputs leftoverUtxos' + mainLoop :: BalancerState -> BalanceTxM FinalizedTransaction + mainLoop = worker <<< PrebalanceTx where - performCoinSelection :: BalanceTxM SelectionState - performCoinSelection = + worker :: BalancerStep -> BalanceTxM FinalizedTransaction + worker (PrebalanceTx state) = do + logBalancerState "Pre-balancing (Stage 1)" p.allUtxos state + prebalanceTx state >>= runNextBalancerStep + worker (BalanceChangeAndMinFee state@{ transaction, minFee }) = do + logBalancerState "Balancing change and fees (Stage 2)" p.allUtxos state + { transaction: balancedTx, minFee: newMinFee } <- evaluateTx state + case newMinFee <= minFee of + true -> + logTransaction "Balanced transaction (Done)" p.allUtxos balancedTx + *> finalizeTransaction balancedTx p.allUtxos + false -> + runNextBalancerStep $ state + { transaction = transaction # _body' <<< _fee .~ Coin newMinFee + , minFee = newMinFee + } + + -- | Determines which balancing step will be performed next. + -- | + -- | If the transaction remains unbalanced (i.e. `requiredValue != mempty`) + -- | after generation of change, the first balancing step `PrebalanceTx` + -- | is performed, otherwise we proceed to `BalanceChangeAndMinFee`. + runNextBalancerStep :: BalancerState -> BalanceTxM FinalizedTransaction + runNextBalancerStep state@{ transaction, leftoverUtxos } = do + let txBody = transaction ^. _body' + inputValue <- except $ getInputValue p.allUtxos txBody + changeOutputs <- makeChange p.changeAddress inputValue p.certsFee txBody + + requiredValue <- + except $ getRequiredValue p.certsFee p.allUtxos + (setTxChangeOutputs changeOutputs transaction ^. _body') + + worker $ state { changeOutputs = changeOutputs } # + if requiredValue == mempty then BalanceChangeAndMinFee else PrebalanceTx + + -- | Selects a combination of unspent transaction outputs from the wallet's + -- | utxo set so that the total input value is sufficient to cover all + -- | transaction outputs, including generated change and min fee. + prebalanceTx :: BalancerState -> BalanceTxM BalancerState + prebalanceTx state@{ transaction, changeOutputs, leftoverUtxos } = do + + selectionState <- performCoinSelection let - txBody :: TxBody - txBody = setTxChangeOutputs changeOutputs unbalancedTx ^. _body' - in - except (getRequiredValue certsFee utxos txBody) - >>= performMultiAssetSelection strategy leftoverUtxos - - -- | Calculates execution units for each script in the transaction and sets - -- | min fee. - -- | - -- | The transaction must be pre-balanced before evaluating execution units, - -- | since this pre-condition is sometimes required for successfull script - -- | execution during transaction evaluation. - balanceChangeAndMinFee :: BalancerState -> BalanceTxM FinalizedTransaction - balanceChangeAndMinFee - state@{ unbalancedTx, changeOutputs, leftoverUtxos } = do - logBalancerState "Balancing change and fees (Stage 2)" utxos state - let - prebalancedTx :: PrebalancedTransaction - prebalancedTx = wrap $ setTxChangeOutputs changeOutputs unbalancedTx - - minFee :: BigInt - minFee = unwrap $ unbalancedTx ^. _body' <<< _fee - - balancedTx /\ newMinFee <- evalExUnitsAndMinFee prebalancedTx allUtxos - - case newMinFee <= minFee of - true -> - finalizeTransaction balancedTx allUtxos - <* logTransaction "Balanced transaction (Done)" utxos balancedTx - false -> + selectedInputs' :: Set TransactionInput + selectedInputs' = selectedInputs selectionState + + unbalancedTxWithInputs :: UnattachedUnbalancedTx + unbalancedTxWithInputs = + transaction # _body' <<< _inputs %~ Set.union selectedInputs' + + pure $ state + { transaction = unbalancedTxWithInputs + , leftoverUtxos = selectionState ^. _leftoverUtxos + } + where + performCoinSelection :: BalanceTxM SelectionState + performCoinSelection = let - unbalancedTxWithMinFee :: UnattachedUnbalancedTx - unbalancedTxWithMinFee = - unbalancedTx # _body' <<< _fee .~ Coin newMinFee + txBody :: TxBody + txBody = setTxChangeOutputs changeOutputs transaction ^. _body' in - runNextBalancingStep unbalancedTxWithMinFee leftoverUtxos + except (getRequiredValue p.certsFee p.allUtxos txBody) + >>= performMultiAssetSelection p.strategy leftoverUtxos + + -- | Calculates execution units for each script in the transaction and sets + -- | min fee. + -- | + -- | The transaction must be pre-balanced before evaluating execution units, + -- | since this pre-condition is sometimes required for successfull script + -- | execution during transaction evaluation. + evaluateTx :: BalancerState -> BalanceTxM BalancerState + evaluateTx state@{ transaction, changeOutputs, leftoverUtxos } = do + let + prebalancedTx :: PrebalancedTransaction + prebalancedTx = wrap $ setTxChangeOutputs changeOutputs transaction + + transaction' /\ minFee <- evalExUnitsAndMinFee prebalancedTx p.allUtxos + pure $ state { transaction = transaction', minFee = minFee } -- | For each transaction output, if necessary, adds some number of lovelaces -- | to cover the utxo min-ada-value requirement. @@ -644,17 +667,9 @@ getStakingBalance tx depositLovelacesPerCert = -- Helpers -------------------------------------------------------------------------------- -mkBalancerState - :: UnattachedUnbalancedTx - -> Array TransactionOutput - -> UtxoMap - -> BalancerState -mkBalancerState unbalancedTx changeOutputs = - { unbalancedTx, changeOutputs, leftoverUtxos: _ } <<< buildUtxoIndex - logBalancerState :: String -> UtxoMap -> BalancerState -> BalanceTxM Unit -logBalancerState message utxos { unbalancedTx, changeOutputs } = - logTransactionWithChange message utxos (Just changeOutputs) unbalancedTx +logBalancerState message utxos { transaction, changeOutputs } = + logTransactionWithChange message utxos (Just changeOutputs) transaction logTransaction :: String -> UtxoMap -> UnattachedUnbalancedTx -> BalanceTxM Unit From e0bdbc4d8040952cf9fcae91c882a8dc935160f3 Mon Sep 17 00:00:00 2001 From: peter Date: Sun, 4 Dec 2022 09:53:36 +0100 Subject: [PATCH 041/373] .. --- src/Internal/Serialization/ToBytes.purs | 122 ++++++++++++++---------- 1 file changed, 74 insertions(+), 48 deletions(-) diff --git a/src/Internal/Serialization/ToBytes.purs b/src/Internal/Serialization/ToBytes.purs index 2634bd5bd7..d042578734 100644 --- a/src/Internal/Serialization/ToBytes.purs +++ b/src/Internal/Serialization/ToBytes.purs @@ -1,7 +1,7 @@ module Ctl.Internal.Serialization.ToBytes - ( class ToBytes - , toBytes - , toBytes' +-- ( class ToBytes + ( toBytes +-- , toBytes' ) where import Prelude @@ -30,74 +30,100 @@ import Ctl.Internal.Serialization.Types import Ctl.Internal.Types.ByteArray (ByteArray) import Ctl.Internal.Types.CborBytes (CborBytes(CborBytes)) +import Untagged.Union (type (|+|)) + +-- NOTE returns cbor encoding for all but hash types, for which it returns raw bytes +foreign import _toBytes + :: ( Transaction + |+| TransactionBody + |+| TransactionOutput + |+| TransactionUnspentOutput + |+| TransactionHash + |+| DataHash + |+| PlutusData + |+| TransactionWitnessSet + |+| NativeScript + |+| ScriptDataHash + |+| Redeemers + |+| GenesisHash + |+| GenesisDelegateHash + |+| AuxiliaryDataHash + |+| Address + |+| Value + |+| Ed25519Signature + |+| VRFKeyHash + -- Add more as needed. + ) + -> ByteArray -- NOTE returns cbor encoding for all but hash types, for which it returns raw bytes -foreign import _toBytes :: forall (a :: Type). a -> ByteArray -class ToBytes a where - toBytes' :: a -> ByteArray +-- foreign import _toBytes :: forall (a :: Type). a -> ByteArray + +-- class ToBytes a where +-- toBytes' :: a -> ByteArray -instance ToBytes Address where - toBytes' = _toBytes +-- instance ToBytes Address where +-- toBytes' = _toBytes -instance ToBytes AuxiliaryDataHash where - toBytes' = _toBytes +-- instance ToBytes AuxiliaryDataHash where +-- toBytes' = _toBytes -instance ToBytes DataHash where - toBytes' = _toBytes +-- instance ToBytes DataHash where +-- toBytes' = _toBytes -instance ToBytes Ed25519KeyHash where - toBytes' = _toBytes +-- instance ToBytes Ed25519KeyHash where +-- toBytes' = _toBytes -instance ToBytes Ed25519Signature where - toBytes' = _toBytes +-- instance ToBytes Ed25519Signature where +-- toBytes' = _toBytes -instance ToBytes GenesisDelegateHash where - toBytes' = _toBytes +-- instance ToBytes GenesisDelegateHash where +-- toBytes' = _toBytes -instance ToBytes GenesisHash where - toBytes' = _toBytes +-- instance ToBytes GenesisHash where +-- toBytes' = _toBytes -instance ToBytes NativeScript where - toBytes' = _toBytes +-- instance ToBytes NativeScript where +-- toBytes' = _toBytes -instance ToBytes PlutusData where - toBytes' = _toBytes +-- instance ToBytes PlutusData where +-- toBytes' = _toBytes -instance ToBytes PoolMetadataHash where - toBytes' = _toBytes +-- instance ToBytes PoolMetadataHash where +-- toBytes' = _toBytes -instance ToBytes Redeemers where - toBytes' = _toBytes +-- instance ToBytes Redeemers where +-- toBytes' = _toBytes -instance ToBytes ScriptDataHash where - toBytes' = _toBytes +-- instance ToBytes ScriptDataHash where +-- toBytes' = _toBytes -instance ToBytes ScriptHash where - toBytes' = _toBytes +-- instance ToBytes ScriptHash where +-- toBytes' = _toBytes -instance ToBytes Transaction where - toBytes' = _toBytes +-- instance ToBytes Transaction where +-- toBytes' = _toBytes -instance ToBytes TransactionBody where - toBytes' = _toBytes +-- instance ToBytes TransactionBody where +-- toBytes' = _toBytes -instance ToBytes TransactionHash where - toBytes' = _toBytes +-- instance ToBytes TransactionHash where +-- toBytes' = _toBytes -instance ToBytes TransactionOutput where - toBytes' = _toBytes +-- instance ToBytes TransactionOutput where +-- toBytes' = _toBytes -instance ToBytes TransactionUnspentOutput where - toBytes' = _toBytes +-- instance ToBytes TransactionUnspentOutput where +-- toBytes' = _toBytes -instance ToBytes TransactionWitnessSet where - toBytes' = _toBytes +-- instance ToBytes TransactionWitnessSet where +-- toBytes' = _toBytes -instance ToBytes Value where - toBytes' = _toBytes +-- instance ToBytes Value where +-- toBytes' = _toBytes -instance ToBytes VRFKeyHash where - toBytes' = _toBytes +-- instance ToBytes VRFKeyHash where +-- toBytes' = _toBytes toBytes :: forall (a :: Type). ToBytes a => a -> CborBytes toBytes = CborBytes <<< toBytes' From e9284ce68782e2cbf4429d45f33f3c7072f4c6b4 Mon Sep 17 00:00:00 2001 From: peter Date: Sun, 4 Dec 2022 10:12:46 +0100 Subject: [PATCH 042/373] ... --- src/Internal/Cardano/Types/Value.purs | 27 +++++------------------- src/Internal/Serialization/ToBytes.purs | 28 +++++++++++++++++++++++-- 2 files changed, 31 insertions(+), 24 deletions(-) diff --git a/src/Internal/Cardano/Types/Value.purs b/src/Internal/Cardano/Types/Value.purs index 59abe88837..edeffabec8 100644 --- a/src/Internal/Cardano/Types/Value.purs +++ b/src/Internal/Cardano/Types/Value.purs @@ -53,14 +53,7 @@ module Ctl.Internal.Cardano.Types.Value import Prelude hiding (join) -import Aeson - ( class DecodeAeson - , class EncodeAeson - , JsonDecodeError(TypeMismatch) - , caseAesonObject - , encodeAeson' - , getField - ) +import Aeson (class DecodeAeson, class EncodeAeson, JsonDecodeError(TypeMismatch), caseAesonObject, encodeAeson', getField) import Control.Alt ((<|>)) import Control.Alternative (guard) import Ctl.Internal.Equipartition (class Equipartition, equipartition) @@ -71,20 +64,9 @@ import Ctl.Internal.Metadata.ToMetadata (class ToMetadata) import Ctl.Internal.Serialization.Hash (ScriptHash, scriptHashFromBytes) import Ctl.Internal.Serialization.ToBytes (toBytes) import Ctl.Internal.ToData (class ToData) -import Ctl.Internal.Types.ByteArray - ( ByteArray - , byteArrayToHex - , byteLength - , hexToByteArray - ) +import Ctl.Internal.Types.ByteArray (ByteArray, byteArrayToHex, byteLength, hexToByteArray) import Ctl.Internal.Types.Scripts (MintingPolicyHash(MintingPolicyHash)) -import Ctl.Internal.Types.TokenName - ( TokenName - , adaToken - , getTokenName - , mkTokenName - , mkTokenNames - ) +import Ctl.Internal.Types.TokenName (TokenName, adaToken, getTokenName, mkTokenName, mkTokenNames) import Data.Array (cons, filter) import Data.Array.NonEmpty (NonEmptyArray) import Data.Array.NonEmpty (replicate, singleton, zipWith) as NEArray @@ -111,6 +93,7 @@ import Data.Traversable (class Traversable, traverse) import Data.Tuple (fst) import Data.Tuple.Nested (type (/\), (/\)) import Partial.Unsafe (unsafePartial) +import Untagged.Union (asOneOf) -- `Negate` and `Split` seem a bit too contrived, and their purpose is to -- combine similar behaviour without satisfying any useful laws. I wonder @@ -778,7 +761,7 @@ currencyScriptHash (CurrencySymbol byteArray) = unsafePartial fromJust $ scriptHashFromBytes byteArray scriptHashAsCurrencySymbol :: ScriptHash -> CurrencySymbol -scriptHashAsCurrencySymbol = CurrencySymbol <<< unwrap <<< toBytes +scriptHashAsCurrencySymbol = CurrencySymbol <<< unwrap <<< toBytes <<< asOneOf -- | The minting policy hash of a currency symbol currencyMPSHash :: CurrencySymbol -> MintingPolicyHash diff --git a/src/Internal/Serialization/ToBytes.purs b/src/Internal/Serialization/ToBytes.purs index d042578734..eabc19d46c 100644 --- a/src/Internal/Serialization/ToBytes.purs +++ b/src/Internal/Serialization/ToBytes.purs @@ -32,6 +32,8 @@ import Ctl.Internal.Types.CborBytes (CborBytes(CborBytes)) import Untagged.Union (type (|+|)) +-- data MyTypes = Transaction |+| TransactionBody + -- NOTE returns cbor encoding for all but hash types, for which it returns raw bytes foreign import _toBytes :: ( Transaction @@ -52,6 +54,7 @@ foreign import _toBytes |+| Value |+| Ed25519Signature |+| VRFKeyHash + |+| ScriptHash -- Add more as needed. ) -> ByteArray @@ -125,5 +128,26 @@ foreign import _toBytes -- instance ToBytes VRFKeyHash where -- toBytes' = _toBytes -toBytes :: forall (a :: Type). ToBytes a => a -> CborBytes -toBytes = CborBytes <<< toBytes' +toBytes :: + ( Transaction + |+| TransactionBody + |+| TransactionOutput + |+| TransactionUnspentOutput + |+| TransactionHash + |+| DataHash + |+| PlutusData + |+| TransactionWitnessSet + |+| NativeScript + |+| ScriptDataHash + |+| Redeemers + |+| GenesisHash + |+| GenesisDelegateHash + |+| AuxiliaryDataHash + |+| Address + |+| Value + |+| Ed25519Signature + |+| VRFKeyHash + |+| ScriptHash + -- Add more as needed. + ) -> CborBytes +toBytes = CborBytes <<< _toBytes From e31f634d58647f76bef5b899bc6115c57134c845 Mon Sep 17 00:00:00 2001 From: peter Date: Mon, 5 Dec 2022 11:48:47 +0100 Subject: [PATCH 043/373] with SerializationData type --- src/Contract/Transaction.purs | 7 +- src/Internal/BalanceTx/ExUnitsAndMinFee.purs | 3 +- src/Internal/Cardano/Types/Transaction.purs | 9 +- src/Internal/Cardano/Types/Value.purs | 30 +++- src/Internal/Deserialization/Transaction.purs | 15 +- .../Deserialization/UnspentOutput.purs | 7 +- src/Internal/Hashing.purs | 9 +- src/Internal/Plutus/Types/CurrencySymbol.purs | 5 +- src/Internal/QueryM.purs | 2 + src/Internal/QueryM/Kupo.purs | 4 +- src/Internal/QueryM/Pools.purs | 28 ++-- src/Internal/Serialization.purs | 3 +- src/Internal/Serialization/AuxiliaryData.purs | 3 +- src/Internal/Serialization/ToBytes.purs | 143 ++++-------------- src/Internal/Transaction.purs | 3 +- src/Internal/TxOutput.purs | 8 +- src/Internal/Types/Redeemer.purs | 3 +- src/Internal/Types/VRFKeyHash.purs | 7 +- src/Internal/Wallet/Cip30.purs | 9 +- src/Internal/Wallet/Cip30Mock.purs | 16 +- test/Data.purs | 3 +- test/Deserialization.purs | 11 +- test/Serialization.purs | 9 +- test/Serialization/Hash.purs | 5 +- 24 files changed, 150 insertions(+), 192 deletions(-) diff --git a/src/Contract/Transaction.purs b/src/Contract/Transaction.purs index a0cf4066b6..5b004ba7d3 100644 --- a/src/Contract/Transaction.purs +++ b/src/Contract/Transaction.purs @@ -56,9 +56,7 @@ import Control.Monad.Reader (ReaderT, asks, runReaderT) import Control.Monad.Reader.Class (ask) import Ctl.Internal.BalanceTx (BalanceTxError) as BalanceTxError import Ctl.Internal.BalanceTx (FinalizedTransaction) -import Ctl.Internal.BalanceTx - ( FinalizedTransaction(FinalizedTransaction) - ) as FinalizedTransaction +import Ctl.Internal.BalanceTx (FinalizedTransaction(FinalizedTransaction)) as FinalizedTransaction import Ctl.Internal.BalanceTx (balanceTxWithConstraints) as BalanceTx import Ctl.Internal.BalanceTx.Constraints (BalanceTxConstraintsBuilder) import Ctl.Internal.Cardano.Types.NativeScript @@ -279,6 +277,7 @@ import Effect.Aff (bracket) import Effect.Aff.Class (liftAff) import Effect.Class (liftEffect) import Effect.Exception (throw) +import Untagged.Castable (cast) -- | Signs a transaction with potential failure. signTransaction @@ -316,7 +315,7 @@ submitE tx = do cslTx <- liftEffect $ Serialization.convertTransaction (unwrap tx) let txHash = Hashing.transactionHash cslTx logDebug' $ "Pre-calculated tx hash: " <> show txHash - let txCborBytes = Serialization.toBytes cslTx + let txCborBytes = Serialization.toBytes $ cast cslTx result <- wrapContract $ QueryM.submitTxOgmios (unwrap txHash) txCborBytes pure $ case result of diff --git a/src/Internal/BalanceTx/ExUnitsAndMinFee.purs b/src/Internal/BalanceTx/ExUnitsAndMinFee.purs index b80c90f5e4..ead3264ca5 100644 --- a/src/Internal/BalanceTx/ExUnitsAndMinFee.purs +++ b/src/Internal/BalanceTx/ExUnitsAndMinFee.purs @@ -85,6 +85,7 @@ import Data.Traversable (for) import Data.Tuple (fst, snd) import Data.Tuple.Nested (type (/\), (/\)) import Effect.Class (liftEffect) +import Untagged.Castable (cast) evalTxExecutionUnits :: Transaction @@ -92,7 +93,7 @@ evalTxExecutionUnits -> BalanceTxM Ogmios.TxEvaluationResult evalTxExecutionUnits tx unattachedTx = do txBytes <- liftEffect - $ Serialization.toBytes <$> Serialization.convertTransaction tx + $ Serialization.toBytes <<< cast <$> Serialization.convertTransaction tx additionalUtxos <- getOgmiosAdditionalUtxoSet evalResult <- unwrap <$> liftQueryM (QueryM.evaluateTxOgmios txBytes additionalUtxos) diff --git a/src/Internal/Cardano/Types/Transaction.purs b/src/Internal/Cardano/Types/Transaction.purs index a7ff112a9d..a4300c6171 100644 --- a/src/Internal/Cardano/Types/Transaction.purs +++ b/src/Internal/Cardano/Types/Transaction.purs @@ -165,6 +165,7 @@ import Data.Tuple (Tuple(Tuple)) import Data.Tuple.Nested (type (/\)) import Data.UInt (UInt) import Partial.Unsafe (unsafePartial) +import Untagged.Castable (cast) -------------------------------------------------------------------------------- -- `Transaction` @@ -871,11 +872,13 @@ instance Show PublicKey where newtype Ed25519Signature = Ed25519Signature RawBytes mkEd25519Signature :: Bech32String -> Maybe Ed25519Signature -mkEd25519Signature = map (Ed25519Signature <<< wrap <<< unwrap <<< toBytes) <<< - ed25519SignatureFromBech32 +mkEd25519Signature = + map (Ed25519Signature <<< wrap <<< unwrap <<< toBytes <<< cast) <<< + ed25519SignatureFromBech32 mkFromCslEd25519Signature :: Serialization.Ed25519Signature -> Ed25519Signature -mkFromCslEd25519Signature = Ed25519Signature <<< wrap <<< unwrap <<< toBytes +mkFromCslEd25519Signature = Ed25519Signature <<< wrap <<< unwrap <<< toBytes <<< + cast convertEd25519Signature :: Ed25519Signature -> Serialization.Ed25519Signature convertEd25519Signature (Ed25519Signature bs) = unsafePartial diff --git a/src/Internal/Cardano/Types/Value.purs b/src/Internal/Cardano/Types/Value.purs index edeffabec8..6e584125c5 100644 --- a/src/Internal/Cardano/Types/Value.purs +++ b/src/Internal/Cardano/Types/Value.purs @@ -53,7 +53,14 @@ module Ctl.Internal.Cardano.Types.Value import Prelude hiding (join) -import Aeson (class DecodeAeson, class EncodeAeson, JsonDecodeError(TypeMismatch), caseAesonObject, encodeAeson', getField) +import Aeson + ( class DecodeAeson + , class EncodeAeson + , JsonDecodeError(TypeMismatch) + , caseAesonObject + , encodeAeson' + , getField + ) import Control.Alt ((<|>)) import Control.Alternative (guard) import Ctl.Internal.Equipartition (class Equipartition, equipartition) @@ -64,9 +71,20 @@ import Ctl.Internal.Metadata.ToMetadata (class ToMetadata) import Ctl.Internal.Serialization.Hash (ScriptHash, scriptHashFromBytes) import Ctl.Internal.Serialization.ToBytes (toBytes) import Ctl.Internal.ToData (class ToData) -import Ctl.Internal.Types.ByteArray (ByteArray, byteArrayToHex, byteLength, hexToByteArray) +import Ctl.Internal.Types.ByteArray + ( ByteArray + , byteArrayToHex + , byteLength + , hexToByteArray + ) import Ctl.Internal.Types.Scripts (MintingPolicyHash(MintingPolicyHash)) -import Ctl.Internal.Types.TokenName (TokenName, adaToken, getTokenName, mkTokenName, mkTokenNames) +import Ctl.Internal.Types.TokenName + ( TokenName + , adaToken + , getTokenName + , mkTokenName + , mkTokenNames + ) import Data.Array (cons, filter) import Data.Array.NonEmpty (NonEmptyArray) import Data.Array.NonEmpty (replicate, singleton, zipWith) as NEArray @@ -93,7 +111,7 @@ import Data.Traversable (class Traversable, traverse) import Data.Tuple (fst) import Data.Tuple.Nested (type (/\), (/\)) import Partial.Unsafe (unsafePartial) -import Untagged.Union (asOneOf) +import Untagged.Castable (cast) -- `Negate` and `Split` seem a bit too contrived, and their purpose is to -- combine similar behaviour without satisfying any useful laws. I wonder @@ -761,7 +779,7 @@ currencyScriptHash (CurrencySymbol byteArray) = unsafePartial fromJust $ scriptHashFromBytes byteArray scriptHashAsCurrencySymbol :: ScriptHash -> CurrencySymbol -scriptHashAsCurrencySymbol = CurrencySymbol <<< unwrap <<< toBytes <<< asOneOf +scriptHashAsCurrencySymbol = CurrencySymbol <<< unwrap <<< toBytes <<< cast -- | The minting policy hash of a currency symbol currencyMPSHash :: CurrencySymbol -> MintingPolicyHash @@ -772,7 +790,7 @@ currencyMPSHash = MintingPolicyHash <<< currencyScriptHash -- Plutus doesn't use Maybe here. -- | The currency symbol of a monetary policy hash mpsSymbol :: MintingPolicyHash -> Maybe CurrencySymbol -mpsSymbol (MintingPolicyHash h) = mkCurrencySymbol $ unwrap $ toBytes h +mpsSymbol (MintingPolicyHash h) = mkCurrencySymbol $ unwrap $ toBytes $ cast h -- Like `mapEither` that works with 'These'. mapThese diff --git a/src/Internal/Deserialization/Transaction.purs b/src/Internal/Deserialization/Transaction.purs index 2cfc2e9157..97a997f3fa 100644 --- a/src/Internal/Deserialization/Transaction.purs +++ b/src/Internal/Deserialization/Transaction.purs @@ -212,6 +212,7 @@ import Data.UInt (UInt) import Data.UInt as UInt import Data.Variant (Variant) import Type.Row (type (+)) +import Untagged.Castable (cast) -- | Deserializes CBOR encoded transaction to a CTL's native type. deserializeTransaction @@ -299,7 +300,7 @@ convertTxBody txBody = do , withdrawals , update , auxiliaryDataHash: - T.AuxiliaryDataHash <<< unwrap <<< toBytes <$> + T.AuxiliaryDataHash <<< unwrap <<< (toBytes <<< cast) <$> _txBodyAuxiliaryDataHash maybeFfiHelper txBody , validityStartInterval: Slot <$> _txBodyValidityStartInterval maybeFfiHelper txBody @@ -324,7 +325,7 @@ convertUpdate u = do epoch <- map T.Epoch $ cslNumberToUInt "convertUpdate: epoch" e ppus <- traverse ( bitraverse - (pure <<< T.GenesisHash <<< unwrap <<< toBytes) + (pure <<< T.GenesisHash <<< unwrap <<< toBytes <<< cast) convertProtocolParamUpdate ) paramUpdates @@ -347,9 +348,9 @@ convertCertificate = _convertCert certConvHelper , poolRetirement: convertPoolRetirement , genesisKeyDelegation: \genesisHash genesisDelegateHash vrfKeyhash -> do pure $ T.GenesisKeyDelegation - { genesisHash: T.GenesisHash $ unwrap $ toBytes genesisHash + { genesisHash: T.GenesisHash $ unwrap $ toBytes $ cast genesisHash , genesisDelegateHash: T.GenesisDelegateHash - (unwrap $ toBytes genesisDelegateHash) + (unwrap $ toBytes $ cast genesisDelegateHash) , vrfKeyhash: VRFKeyHash vrfKeyhash } , moveInstantaneousRewardsToOtherPotCert: \pot amount -> do @@ -384,7 +385,9 @@ convertPoolRegistration params = do , poolMetadata: poolParamsPoolMetadata maybeFfiHelper params <#> convertPoolMetadata_ \url hash -> T.PoolMetadata - { url: T.URL url, hash: T.PoolMetadataHash $ unwrap $ toBytes hash } + { url: T.URL url + , hash: T.PoolMetadataHash $ unwrap $ toBytes $ cast hash + } } type ConvertRelayHelper a = @@ -658,7 +661,7 @@ convertExUnits nm cslExunits = <*> BigNum.toBigInt' (nm <> " steps") steps convertScriptDataHash :: Csl.ScriptDataHash -> T.ScriptDataHash -convertScriptDataHash = toBytes >>> unwrap >>> T.ScriptDataHash +convertScriptDataHash = cast >>> toBytes >>> unwrap >>> T.ScriptDataHash convertProtocolVersion :: forall (r :: Row Type) diff --git a/src/Internal/Deserialization/UnspentOutput.purs b/src/Internal/Deserialization/UnspentOutput.purs index b2e820fc5e..c554916d8e 100644 --- a/src/Internal/Deserialization/UnspentOutput.purs +++ b/src/Internal/Deserialization/UnspentOutput.purs @@ -67,6 +67,7 @@ import Data.Traversable (for, traverse) import Data.Tuple (Tuple(Tuple)) import Data.Tuple.Nested (type (/\)) import Data.UInt as UInt +import Untagged.Castable (cast) convertUnspentOutput :: TransactionUnspentOutput -> Maybe T.TransactionUnspentOutput @@ -79,7 +80,7 @@ convertInput :: TransactionInput -> Maybe T.TransactionInput convertInput input = do index <- UInt.fromInt' $ getTransactionIndex input pure $ T.TransactionInput - { transactionId: T.TransactionHash $ unwrap $ toBytes + { transactionId: T.TransactionHash $ unwrap $ toBytes $ cast (getTransactionHash input) , index } @@ -91,7 +92,7 @@ convertOutput output = do address = getAddress output mbDataHash = getDataHash maybeFfiHelper output <#> - toBytes >>> unwrap >>> T.DataHash + cast >>> toBytes >>> unwrap >>> T.DataHash mbDatum = getPlutusData maybeFfiHelper output datum <- case mbDatum, mbDataHash of Just _, Just _ -> Nothing -- impossible, so it's better to fail @@ -126,7 +127,7 @@ convertValue value = do ( traverse ( bitraverse -- scripthash to currency symbol - (toBytes >>> unwrap >>> T.mkCurrencySymbol) + (cast >>> toBytes >>> unwrap >>> T.mkCurrencySymbol) -- nested assetname to tokenname (traverse (ltraverse (T.assetNameName >>> T.mkTokenName))) ) diff --git a/src/Internal/Hashing.purs b/src/Internal/Hashing.purs index 8b4e7debea..fc0b33a886 100644 --- a/src/Internal/Hashing.purs +++ b/src/Internal/Hashing.purs @@ -34,6 +34,7 @@ import Ctl.Internal.Types.Scripts (PlutusScript) import Ctl.Internal.Types.Transaction (DataHash, TransactionHash) import Data.Maybe (Maybe) import Data.Newtype (unwrap, wrap) +import Untagged.Castable (cast) foreign import blake2b256Hash :: ByteArray -> ByteArray @@ -54,14 +55,16 @@ foreign import sha3_256HashHex :: ByteArray -> String datumHash :: Datum -> Maybe DataHash datumHash = - map (wrap <<< unwrap <<< toBytes <<< hashPlutusData) <<< convertPlutusData <<< - unwrap + map (wrap <<< unwrap <<< toBytes <<< cast <<< hashPlutusData) + <<< convertPlutusData + <<< + unwrap -- | Calculates the hash of the transaction by applying `blake2b256Hash` to -- | the cbor-encoded transaction body. transactionHash :: Serialization.Transaction -> TransactionHash transactionHash = - wrap <<< blake2b256Hash <<< unwrap <<< toBytes <<< _txBody + wrap <<< blake2b256Hash <<< unwrap <<< toBytes <<< cast <<< _txBody plutusScriptHash :: PlutusScript -> ScriptHash plutusScriptHash = hashPlutusScript <<< convertPlutusScript diff --git a/src/Internal/Plutus/Types/CurrencySymbol.purs b/src/Internal/Plutus/Types/CurrencySymbol.purs index ba17b0a2a5..4d1ca03763 100644 --- a/src/Internal/Plutus/Types/CurrencySymbol.purs +++ b/src/Internal/Plutus/Types/CurrencySymbol.purs @@ -34,6 +34,7 @@ import Data.Maybe (Maybe, fromJust) import Data.Newtype (unwrap) import Partial.Unsafe (unsafePartial) import Test.QuickCheck.Arbitrary (class Arbitrary) +import Untagged.Castable (cast) newtype CurrencySymbol = CurrencySymbol ByteArray @@ -74,7 +75,7 @@ adaSymbol :: CurrencySymbol adaSymbol = CurrencySymbol mempty scriptHashAsCurrencySymbol :: ScriptHash -> CurrencySymbol -scriptHashAsCurrencySymbol = CurrencySymbol <<< unwrap <<< toBytes +scriptHashAsCurrencySymbol = CurrencySymbol <<< unwrap <<< toBytes <<< cast -- | The minting policy hash of a currency symbol. currencyMPSHash :: CurrencySymbol -> MintingPolicyHash @@ -82,7 +83,7 @@ currencyMPSHash = MintingPolicyHash <<< currencyScriptHash -- | The currency symbol of a monetary policy hash. mpsSymbol :: MintingPolicyHash -> Maybe CurrencySymbol -mpsSymbol (MintingPolicyHash h) = mkCurrencySymbol $ unwrap $ toBytes h +mpsSymbol (MintingPolicyHash h) = mkCurrencySymbol $ unwrap $ toBytes $ cast h getCurrencySymbol :: CurrencySymbol -> ByteArray getCurrencySymbol (CurrencySymbol curSymbol) = curSymbol diff --git a/src/Internal/QueryM.purs b/src/Internal/QueryM.purs index 1afe925134..d5d0dc5a9d 100644 --- a/src/Internal/QueryM.purs +++ b/src/Internal/QueryM.purs @@ -278,6 +278,7 @@ import Effect.Exception (Error, error, throw, try) import Effect.Ref (Ref) import Effect.Ref as Ref import Foreign.Object as Object +import Untagged.Castable (cast) -- This module defines an Aff interface for Ogmios Websocket Queries -- Since WebSockets do not define a mechanism for linking request/response @@ -845,6 +846,7 @@ applyArgs script args = <<< byteArrayToHex <<< unwrap <<< Serialization.toBytes + <<< cast ) <<< Serialization.convertPlutusData diff --git a/src/Internal/QueryM/Kupo.purs b/src/Internal/QueryM/Kupo.purs index 94483228fc..1ead112415 100644 --- a/src/Internal/QueryM/Kupo.purs +++ b/src/Internal/QueryM/Kupo.purs @@ -88,6 +88,7 @@ import Data.UInt (toString) as UInt import Effect.Aff.Class (liftAff) import Foreign.Object (Object) import Foreign.Object (toUnfoldable) as Object +import Untagged.Castable (cast) -------------------------------------------------------------------------------- -- Requests @@ -126,7 +127,8 @@ getDatumByHash (DataHash dataHashBytes) = do getScriptByHash :: ScriptHash -> QueryM (Either ClientError (Maybe ScriptRef)) getScriptByHash scriptHash = do let - endpoint = "/scripts/" <> rawBytesToHex (wrap $ unwrap $ toBytes scriptHash) + endpoint = "/scripts/" <> rawBytesToHex + (wrap $ unwrap $ toBytes $ cast scriptHash) kupoGetRequest endpoint <#> map unwrapKupoScriptRef <<< handleAffjaxResponse diff --git a/src/Internal/QueryM/Pools.purs b/src/Internal/QueryM/Pools.purs index 9a8f2f788b..28042d1517 100644 --- a/src/Internal/QueryM/Pools.purs +++ b/src/Internal/QueryM/Pools.purs @@ -8,6 +8,7 @@ module Ctl.Internal.QueryM.Pools import Prelude +import Contract.Scripts (ScriptHash) import Ctl.Internal.Cardano.Types.Transaction ( PoolPubKeyHash , PoolRegistrationParams @@ -20,12 +21,13 @@ import Ctl.Internal.QueryM.Ogmios , PoolParametersR(PoolParametersR) ) import Ctl.Internal.QueryM.Ogmios as Ogmios -import Ctl.Internal.Serialization (toBytes) import Ctl.Internal.Serialization.Hash - ( ed25519KeyHashToBech32 + ( Ed25519KeyHash + , ed25519KeyHashToBech32 , ed25519KeyHashToBech32Unsafe , scriptHashToBech32Unsafe ) +import Ctl.Internal.Serialization.ToBytes (toBytes) import Ctl.Internal.Types.ByteArray (byteArrayToHex) import Ctl.Internal.Types.PubKeyHash (StakePubKeyHash) import Ctl.Internal.Types.Scripts (StakeValidatorHash) @@ -34,6 +36,7 @@ import Data.Maybe (Maybe) import Data.Newtype (unwrap, wrap) import Effect.Exception (error) import Record.Builder (build, merge) +import Untagged.Castable (cast) getPoolIds :: QueryM (Array PoolPubKeyHash) getPoolIds = mkOgmiosRequest Ogmios.queryPoolIdsCall @@ -78,10 +81,14 @@ getValidatorHashDelegationsAndRewards skh = do stringRep :: String stringRep = scriptHashToBech32Unsafe "script" $ unwrap skh + -- byteHex :: String + -- byteHex = byteArrayToHex $ unwrap $ toBytes $ cast $ unwrap skh + + sh :: ScriptHash + sh = unwrap skh + byteHex :: String - byteHex = - byteArrayToHex <<< unwrap <<< toBytes <<< unwrap $ - skh + byteHex = byteArrayToHex $ unwrap $ toBytes $ cast sh -- TODO: batched variant getPubKeyHashDelegationsAndRewards @@ -96,8 +103,11 @@ getPubKeyHashDelegationsAndRewards pkh = do stringRep = ed25519KeyHashToBech32Unsafe "stake_vkh" $ unwrap $ unwrap pkh + -- byteHex :: String + -- byteHex = byteArrayToHex $ unwrap $ toBytes $ cast $ unwrap $ unwrap pkh + + ed :: Ed25519KeyHash + ed = unwrap $ unwrap pkh + byteHex :: String - byteHex = - byteArrayToHex <<< unwrap <<< toBytes <<< unwrap $ - unwrap - pkh + byteHex = byteArrayToHex $ unwrap $ toBytes $ cast ed diff --git a/src/Internal/Serialization.purs b/src/Internal/Serialization.purs index e536817090..62f1123594 100644 --- a/src/Internal/Serialization.purs +++ b/src/Internal/Serialization.purs @@ -172,6 +172,7 @@ import Data.Tuple.Nested (type (/\), (/\)) import Data.UInt (UInt) import Data.UInt as UInt import Effect (Effect) +import Untagged.Castable (cast) import Untagged.Union (UndefinedOr, maybeToUor) foreign import hashTransaction :: TransactionBody -> Effect TransactionHash @@ -882,4 +883,4 @@ hashScriptData cms rs ps = do (traverse convertPlutusData ps) serializeData :: forall (a :: Type). ToData a => a -> Maybe CborBytes -serializeData = map toBytes <<< convertPlutusData <<< toData +serializeData = map (toBytes <<< cast) <<< convertPlutusData <<< toData diff --git a/src/Internal/Serialization/AuxiliaryData.purs b/src/Internal/Serialization/AuxiliaryData.purs index de2bf5873d..49dd6f6c53 100644 --- a/src/Internal/Serialization/AuxiliaryData.purs +++ b/src/Internal/Serialization/AuxiliaryData.purs @@ -38,6 +38,7 @@ import Data.Traversable (for, for_, traverse) import Data.Tuple (Tuple(Tuple)) import Data.Tuple.Nested (type (/\), (/\)) import Effect (Effect) +import Untagged.Castable (cast) foreign import newAuxiliaryData :: Effect AuxiliaryData @@ -79,7 +80,7 @@ foreign import _hashAuxiliaryData hashAuxiliaryData :: T.AuxiliaryData -> Effect T.AuxiliaryDataHash hashAuxiliaryData = - map (wrap <<< unwrap <<< toBytes <<< _hashAuxiliaryData) <<< + map (wrap <<< unwrap <<< toBytes <<< cast <<< _hashAuxiliaryData) <<< convertAuxiliaryData convertAuxiliaryData :: T.AuxiliaryData -> Effect AuxiliaryData diff --git a/src/Internal/Serialization/ToBytes.purs b/src/Internal/Serialization/ToBytes.purs index eabc19d46c..595544955c 100644 --- a/src/Internal/Serialization/ToBytes.purs +++ b/src/Internal/Serialization/ToBytes.purs @@ -1,7 +1,5 @@ module Ctl.Internal.Serialization.ToBytes --- ( class ToBytes ( toBytes --- , toBytes' ) where import Prelude @@ -29,125 +27,38 @@ import Ctl.Internal.Serialization.Types ) import Ctl.Internal.Types.ByteArray (ByteArray) import Ctl.Internal.Types.CborBytes (CborBytes(CborBytes)) - import Untagged.Union (type (|+|)) --- data MyTypes = Transaction |+| TransactionBody +type SerializationData = Address + |+| AuxiliaryDataHash + |+| DataHash + |+| Ed25519KeyHash + |+| Ed25519Signature + |+| GenesisDelegateHash + |+| GenesisHash + |+| NativeScript + |+| PlutusData + |+| PoolMetadataHash + |+| Redeemers + |+| ScriptDataHash + |+| ScriptHash + |+| Transaction + |+| TransactionBody + |+| TransactionHash + |+| TransactionOutput + |+| TransactionUnspentOutput + |+| TransactionWitnessSet + |+| Value + |+| VRFKeyHash + +-- and more as needed -- NOTE returns cbor encoding for all but hash types, for which it returns raw bytes foreign import _toBytes - :: ( Transaction - |+| TransactionBody - |+| TransactionOutput - |+| TransactionUnspentOutput - |+| TransactionHash - |+| DataHash - |+| PlutusData - |+| TransactionWitnessSet - |+| NativeScript - |+| ScriptDataHash - |+| Redeemers - |+| GenesisHash - |+| GenesisDelegateHash - |+| AuxiliaryDataHash - |+| Address - |+| Value - |+| Ed25519Signature - |+| VRFKeyHash - |+| ScriptHash - -- Add more as needed. - ) + :: SerializationData -> ByteArray --- NOTE returns cbor encoding for all but hash types, for which it returns raw bytes - --- foreign import _toBytes :: forall (a :: Type). a -> ByteArray - --- class ToBytes a where --- toBytes' :: a -> ByteArray - --- instance ToBytes Address where --- toBytes' = _toBytes - --- instance ToBytes AuxiliaryDataHash where --- toBytes' = _toBytes - --- instance ToBytes DataHash where --- toBytes' = _toBytes - --- instance ToBytes Ed25519KeyHash where --- toBytes' = _toBytes - --- instance ToBytes Ed25519Signature where --- toBytes' = _toBytes - --- instance ToBytes GenesisDelegateHash where --- toBytes' = _toBytes - --- instance ToBytes GenesisHash where --- toBytes' = _toBytes - --- instance ToBytes NativeScript where --- toBytes' = _toBytes - --- instance ToBytes PlutusData where --- toBytes' = _toBytes - --- instance ToBytes PoolMetadataHash where --- toBytes' = _toBytes - --- instance ToBytes Redeemers where --- toBytes' = _toBytes - --- instance ToBytes ScriptDataHash where --- toBytes' = _toBytes - --- instance ToBytes ScriptHash where --- toBytes' = _toBytes - --- instance ToBytes Transaction where --- toBytes' = _toBytes - --- instance ToBytes TransactionBody where --- toBytes' = _toBytes - --- instance ToBytes TransactionHash where --- toBytes' = _toBytes - --- instance ToBytes TransactionOutput where --- toBytes' = _toBytes - --- instance ToBytes TransactionUnspentOutput where --- toBytes' = _toBytes - --- instance ToBytes TransactionWitnessSet where --- toBytes' = _toBytes - --- instance ToBytes Value where --- toBytes' = _toBytes - --- instance ToBytes VRFKeyHash where --- toBytes' = _toBytes -toBytes :: - ( Transaction - |+| TransactionBody - |+| TransactionOutput - |+| TransactionUnspentOutput - |+| TransactionHash - |+| DataHash - |+| PlutusData - |+| TransactionWitnessSet - |+| NativeScript - |+| ScriptDataHash - |+| Redeemers - |+| GenesisHash - |+| GenesisDelegateHash - |+| AuxiliaryDataHash - |+| Address - |+| Value - |+| Ed25519Signature - |+| VRFKeyHash - |+| ScriptHash - -- Add more as needed. - ) -> CborBytes +toBytes + :: SerializationData + -> CborBytes toBytes = CborBytes <<< _toBytes diff --git a/src/Internal/Transaction.purs b/src/Internal/Transaction.purs index deb9d2254e..502d68d39e 100644 --- a/src/Internal/Transaction.purs +++ b/src/Internal/Transaction.purs @@ -38,6 +38,7 @@ import Data.Show.Generic (genericShow) import Data.Traversable (traverse) import Effect (Effect) import Effect.Class (liftEffect) +import Untagged.Castable (cast) data ModifyTxError = ConvertWitnessesError @@ -68,7 +69,7 @@ setScriptDataHash costModels rs ds tx@(Transaction { body, witnessSet }) , null rs , null ds = pure tx | otherwise = do - scriptDataHash <- ScriptDataHash <<< unwrap <<< toBytes + scriptDataHash <- ScriptDataHash <<< unwrap <<< toBytes <<< cast <$> hashScriptData costModels rs (unwrap <$> ds) pure $ over Transaction _ diff --git a/src/Internal/TxOutput.purs b/src/Internal/TxOutput.purs index d093fa63ca..69c9ff3bc9 100644 --- a/src/Internal/TxOutput.purs +++ b/src/Internal/TxOutput.purs @@ -11,10 +11,7 @@ import Prelude import Control.Alt ((<|>)) import Control.Alternative (guard) -import Ctl.Internal.Address - ( addressToOgmiosAddress - , ogmiosAddressToAddress - ) +import Ctl.Internal.Address (addressToOgmiosAddress, ogmiosAddressToAddress) import Ctl.Internal.Cardano.Types.Transaction ( TransactionOutput(TransactionOutput) ) as Transaction @@ -35,6 +32,7 @@ import Ctl.Internal.Types.Transaction (TransactionInput(TransactionInput)) as Tr import Data.Maybe (Maybe, fromMaybe, isNothing) import Data.Newtype (unwrap, wrap) import Data.Traversable (traverse) +import Untagged.Castable (cast) -- | A module for helpers of the various transaction output types. @@ -117,7 +115,7 @@ datumHashToOgmiosDatumHash = byteArrayToHex <<< unwrap datumToOgmiosDatum :: Datum -> Maybe String datumToOgmiosDatum (Datum plutusData) = Serialization.convertPlutusData plutusData <#> - (toBytes >>> unwrap >>> byteArrayToHex) + (cast >>> toBytes >>> unwrap >>> byteArrayToHex) toOutputDatum :: Maybe Datum -> Maybe DataHash -> OutputDatum toOutputDatum d dh = diff --git a/src/Internal/Types/Redeemer.purs b/src/Internal/Types/Redeemer.purs index 6b466d53f1..310459000f 100644 --- a/src/Internal/Types/Redeemer.purs +++ b/src/Internal/Types/Redeemer.purs @@ -17,6 +17,7 @@ import Data.Generic.Rep (class Generic) import Data.Maybe (Maybe) import Data.Newtype (class Newtype, unwrap, wrap) import Data.Show.Generic (genericShow) +import Untagged.Castable (cast) newtype Redeemer = Redeemer PlutusData @@ -50,4 +51,4 @@ instance Show RedeemerHash where -- | This is a duplicate of `datumHash`. redeemerHash :: Redeemer -> Maybe RedeemerHash redeemerHash = - map (wrap <<< unwrap <<< toBytes) <<< convertPlutusData <<< unwrap + map (wrap <<< unwrap <<< toBytes <<< cast) <<< convertPlutusData <<< unwrap diff --git a/src/Internal/Types/VRFKeyHash.purs b/src/Internal/Types/VRFKeyHash.purs index 069e1009e0..f8c7822756 100644 --- a/src/Internal/Types/VRFKeyHash.purs +++ b/src/Internal/Types/VRFKeyHash.purs @@ -15,19 +15,20 @@ import Ctl.Internal.Types.ByteArray (ByteArray, byteArrayToHex) import Data.Function (on) import Data.Maybe (Maybe) import Data.Newtype (unwrap, wrap) +import Untagged.Castable (cast) newtype VRFKeyHash = VRFKeyHash Serialization.VRFKeyHash instance Show VRFKeyHash where show (VRFKeyHash kh) = - "(VRFKeyHash " <> show (byteArrayToHex $ unwrap $ toBytes kh) <> ")" + "(VRFKeyHash " <> show (byteArrayToHex $ unwrap $ toBytes $ cast kh) <> ")" instance Eq VRFKeyHash where eq = eq `on` vrfKeyHashToBytes instance EncodeAeson VRFKeyHash where encodeAeson' (VRFKeyHash kh) = - toBytes kh # unwrap >>> byteArrayToHex >>> encodeAeson' + toBytes (cast kh) # unwrap >>> byteArrayToHex >>> encodeAeson' unVRFKeyHash :: VRFKeyHash -> Serialization.VRFKeyHash unVRFKeyHash (VRFKeyHash kh) = kh @@ -36,4 +37,4 @@ vrfKeyHashFromBytes :: ByteArray -> Maybe VRFKeyHash vrfKeyHashFromBytes = wrap >>> fromBytes >>> map VRFKeyHash vrfKeyHashToBytes :: VRFKeyHash -> ByteArray -vrfKeyHashToBytes (VRFKeyHash kh) = unwrap $ toBytes kh +vrfKeyHashToBytes (VRFKeyHash kh) = unwrap $ toBytes $ cast kh diff --git a/src/Internal/Wallet/Cip30.purs b/src/Internal/Wallet/Cip30.purs index e79984a4ef..fef7b6a165 100644 --- a/src/Internal/Wallet/Cip30.purs +++ b/src/Internal/Wallet/Cip30.purs @@ -44,11 +44,7 @@ import Ctl.Internal.Types.CborBytes , hexToCborBytes , rawBytesAsCborBytes ) -import Ctl.Internal.Types.RawBytes - ( RawBytes - , hexToRawBytes - , rawBytesToHex - ) +import Ctl.Internal.Types.RawBytes (RawBytes, hexToRawBytes, rawBytesToHex) import Data.Maybe (Maybe(Just, Nothing), isNothing, maybe) import Data.Newtype (unwrap) import Data.Traversable (for, traverse) @@ -56,6 +52,7 @@ import Effect (Effect) import Effect.Aff (Aff) import Effect.Class (liftEffect) import Effect.Exception (error, throw) +import Untagged.Castable (cast) type DataSignature = { key :: CborBytes @@ -126,7 +123,7 @@ mkCip30WalletAff walletName enableWallet = do txToHex :: Transaction -> Aff String txToHex = liftEffect - <<< map (byteArrayToHex <<< unwrap <<< Serialization.toBytes) + <<< map (byteArrayToHex <<< unwrap <<< Serialization.toBytes <<< cast) <<< Serialization.convertTransaction getNetworkId :: Cip30Connection -> Aff Int diff --git a/src/Internal/Wallet/Cip30Mock.purs b/src/Internal/Wallet/Cip30Mock.purs index ebb9df69b3..9d1a5a75ed 100644 --- a/src/Internal/Wallet/Cip30Mock.purs +++ b/src/Internal/Wallet/Cip30Mock.purs @@ -56,6 +56,7 @@ import Effect.Class (liftEffect) import Effect.Exception (error) import Effect.Unsafe (unsafePerformEffect) import Type.Proxy (Proxy(Proxy)) +import Untagged.Castable (cast) data WalletMock = MockFlint | MockGero | MockNami | MockLode @@ -157,7 +158,7 @@ mkCip30Mock pKey mSKey = do cslUtxos <- traverse (liftEffect <<< convertTransactionUnspentOutput) $ Map.toUnfoldable nonCollateralUtxos <#> \(input /\ output) -> TransactionUnspentOutput { input, output } - pure $ (byteArrayToHex <<< unwrap <<< toBytes) <$> cslUtxos + pure $ (byteArrayToHex <<< unwrap <<< toBytes <<< cast) <$> cslUtxos , getCollateral: fromAff do ownAddress <- (unwrap keyWallet).address config.networkId utxos <- liftMaybe (error "No UTxOs at address") =<< @@ -166,7 +167,8 @@ mkCip30Mock pKey mSKey = do cslUnspentOutput <- liftEffect $ traverse convertTransactionUnspentOutput collateralUtxos - pure $ (byteArrayToHex <<< unwrap <<< toBytes) <$> cslUnspentOutput + pure $ (byteArrayToHex <<< unwrap <<< toBytes <<< cast) <$> + cslUnspentOutput , getBalance: fromAff do ownAddress <- (unwrap keyWallet).address config.networkId utxos <- liftMaybe (error "No UTxOs at address") =<< @@ -174,17 +176,17 @@ mkCip30Mock pKey mSKey = do value <- liftEffect $ convertValue $ (foldMap (_.amount <<< unwrap) <<< Map.values) utxos - pure $ byteArrayToHex $ unwrap $ toBytes value + pure $ byteArrayToHex $ unwrap $ toBytes $ cast value , getUsedAddresses: fromAff do (unwrap keyWallet).address config.networkId <#> \address -> - [ (byteArrayToHex <<< unwrap <<< toBytes) address ] + [ (byteArrayToHex <<< unwrap <<< toBytes <<< cast) address ] , getUnusedAddresses: fromAff $ pure [] , getChangeAddress: fromAff do (unwrap keyWallet).address config.networkId <#> - (byteArrayToHex <<< unwrap <<< toBytes) + (byteArrayToHex <<< unwrap <<< toBytes <<< cast) , getRewardAddresses: fromAff do (unwrap keyWallet).address config.networkId <#> \address -> - [ (byteArrayToHex <<< unwrap <<< toBytes) address ] + [ (byteArrayToHex <<< unwrap <<< toBytes <<< cast) address ] , signTx: \str -> unsafePerformEffect $ fromAff do txBytes <- liftMaybe (error "Unable to convert CBOR") $ hexToByteArray str @@ -194,7 +196,7 @@ mkCip30Mock pKey mSKey = do $ cborBytesFromByteArray txBytes witness <- (unwrap keyWallet).signTx tx cslWitnessSet <- liftEffect $ convertWitnessSet witness - pure $ byteArrayToHex $ unwrap $ toBytes cslWitnessSet + pure $ byteArrayToHex $ unwrap $ toBytes $ cast cslWitnessSet , signData: mkFn2 \_addr msg -> unsafePerformEffect $ fromAff do msgBytes <- liftMaybe (error "Unable to convert CBOR") (hexToByteArray msg) diff --git a/test/Data.purs b/test/Data.purs index 7586fb5fc0..84ba769c15 100644 --- a/test/Data.purs +++ b/test/Data.purs @@ -56,6 +56,7 @@ import Test.Spec.Assertions (shouldEqual) import Test.Spec.QuickCheck (quickCheck) import Type.Proxy (Proxy(Proxy)) import Type.RowList (Cons, Nil) +import Untagged.Castable (cast) plutusDataAesonRoundTrip :: forall (a :: Type). ToData a => FromData a => a -> Either JsonDecodeError a @@ -567,7 +568,7 @@ testBinaryFixture value binaryFixture = do test ("Deserialization: " <> show value) do fromBytesFromData binaryFixture `shouldEqual` Just value test ("Serialization: " <> show value) do - map toBytes (PDS.convertPlutusData (toData value)) + map (toBytes <<< cast) (PDS.convertPlutusData (toData value)) `shouldEqual` Just (wrap $ hexToByteArrayUnsafe binaryFixture) diff --git a/test/Deserialization.purs b/test/Deserialization.purs index 99d2a35db7..79f5703364 100644 --- a/test/Deserialization.purs +++ b/test/Deserialization.purs @@ -24,9 +24,7 @@ import Ctl.Internal.Deserialization.UnspentOutput ( convertUnspentOutput , mkTransactionUnspentOutput ) -import Ctl.Internal.Deserialization.WitnessSet - ( convertWitnessSet - ) +import Ctl.Internal.Deserialization.WitnessSet (convertWitnessSet) import Ctl.Internal.Serialization (convertTransaction) as TS import Ctl.Internal.Serialization (convertTxInput, convertTxOutput) as Serialization import Ctl.Internal.Serialization.BigInt as SB @@ -85,6 +83,7 @@ import Test.Ctl.Fixtures ) import Test.Ctl.Utils (errMaybe) import Test.Spec.Assertions (expectError, shouldEqual, shouldSatisfy) +import Untagged.Castable (cast) suite :: TestPlanM (Aff Unit) Unit suite = do @@ -107,7 +106,7 @@ suite = do cslPd <- errMaybe "Failed to convert from CTL PlutusData to CSL PlutusData" $ SPD.convertPlutusData ctlPd - let pdBytes = Serialization.toBytes cslPd + let pdBytes = Serialization.toBytes $ cast cslPd cslPd' <- errMaybe "Failed to fromBytes PlutusData" $ fromBytes pdBytes ctlPd' <- @@ -228,7 +227,7 @@ suite = do ws1 <- liftEffect $ SW.convertWitnessSet ws0 ws2 <- errMaybe "Failed deserialization" $ convertWitnessSet ws1 ws0 `shouldEqual` ws2 -- value representation - let wsBytes = unwrap $ Serialization.toBytes ws1 + let wsBytes = unwrap $ Serialization.toBytes $ cast ws1 wsBytes `shouldEqual` fixture -- byte representation test "fixture #1" $ witnessSetRoundTrip witnessSetFixture1 test "fixture #2" $ witnessSetRoundTrip witnessSetFixture2 @@ -259,7 +258,7 @@ testNativeScript input = do purescript to handle it correctly. -} - let bytes = Serialization.toBytes serialized + let bytes = Serialization.toBytes $ cast serialized res <- errMaybe "Failed deserialization" $ fromBytes bytes res' <- errMaybe "Failed deserialization" $ NSD.convertNativeScript res res' `shouldEqual` input diff --git a/test/Serialization.purs b/test/Serialization.purs index 91dd1cc6d7..4020370bd5 100644 --- a/test/Serialization.purs +++ b/test/Serialization.purs @@ -48,6 +48,7 @@ import Test.Ctl.Fixtures ) import Test.Ctl.Utils (errMaybe) import Test.Spec.Assertions (shouldEqual, shouldSatisfy) +import Untagged.Castable (cast) suite :: TestPlanM (Aff Unit) Unit suite = do @@ -111,11 +112,11 @@ suite = do datum = PD.Integer (BigInt.fromInt 0) datum' <- errMaybe "Cannot convertPlutusData" $ convertPlutusData datum - let bytes = toBytes datum' + let bytes = toBytes $ cast datum' byteArrayToHex (unwrap bytes) `shouldEqual` "00" test "TransactionOutput serialization" $ liftEffect do txo <- convertTxOutput txOutputFixture1 - let bytes = toBytes txo + let bytes = toBytes $ cast txo byteArrayToHex (unwrap bytes) `shouldEqual` txOutputBinaryFixture1 test "Transaction serialization #1" $ serializeTX txFixture1 txBinaryFixture1 @@ -157,13 +158,13 @@ serializeTX :: Transaction -> String -> Aff Unit serializeTX tx fixture = liftEffect $ do cslTX <- TS.convertTransaction $ tx - let bytes = toBytes cslTX + let bytes = toBytes $ cast cslTX byteArrayToHex (unwrap bytes) `shouldEqual` fixture txSerializedRoundtrip :: Transaction -> Aff Unit txSerializedRoundtrip tx = do cslTX <- liftEffect $ TS.convertTransaction tx - let serialized = toBytes cslTX + let serialized = toBytes $ cast cslTX deserialized <- errMaybe "Cannot deserialize bytes" $ fromBytes serialized expected <- errMaybe "Cannot convert TX from CSL to CTL" $ hush $ TD.convertTransaction deserialized diff --git a/test/Serialization/Hash.purs b/test/Serialization/Hash.purs index 05638f255b..03c920f36e 100644 --- a/test/Serialization/Hash.purs +++ b/test/Serialization/Hash.purs @@ -22,6 +22,7 @@ import Data.Newtype (unwrap) import Data.Unit (Unit) import Effect.Aff (Aff) import Test.Ctl.Utils (assertTrue, errMaybe) +import Untagged.Castable (cast) pkhBech32 :: Bech32String pkhBech32 = "addr_vkh1zuctrdcq6ctd29242w8g84nlz0q38t2lnv3zzfcrfqktx0c9tzp" @@ -42,7 +43,7 @@ suite = do let pkhB32 = ed25519KeyHashToBech32Unsafe "addr_vkh" pkh mPkhB32 = ed25519KeyHashToBech32 "addr_vkh" pkh - pkhBts = toBytes pkh + pkhBts = toBytes $ cast pkh -- TODO: use fromBytes instead? pkh2 = ed25519KeyHashFromBytes $ unwrap pkhBts @@ -72,7 +73,7 @@ suite = do let scrhB32 = scriptHashToBech32Unsafe "stake_vkh" scrh mScrhB32 = scriptHashToBech32 "stake_vkh" scrh - scrhBts = toBytes scrh + scrhBts = toBytes $ cast scrh -- TODO: use fromBytes instead? scrhFromBytes = scriptHashFromBytes $ unwrap scrhBts scrhFromBech = scriptHashFromBech32 scrhB32 From 571252abaa578b64c9a9f7c84c2509467c988e93 Mon Sep 17 00:00:00 2001 From: uhbif19 Date: Mon, 5 Dec 2022 11:52:41 +0300 Subject: [PATCH 044/373] Remove `Maybe` from `convertPlutusData` in `(De)serialization` modules --- examples/ContractTestUtils.purs | 2 +- examples/SatisfiesAnyOf.purs | 6 +-- src/Internal/Deserialization/PlutusData.purs | 29 +++++----- .../Deserialization/UnspentOutput.purs | 4 +- src/Internal/Deserialization/WitnessSet.purs | 11 ++-- src/Internal/Hashing.purs | 4 +- src/Internal/QueryM.purs | 54 +++++++++---------- src/Internal/Serialization.purs | 13 +++-- src/Internal/Serialization/PlutusData.purs | 45 ++++++++-------- src/Internal/Serialization/WitnessSet.purs | 4 +- src/Internal/Transaction.purs | 8 +-- src/Internal/TxOutput.purs | 10 ++-- src/Internal/Types/Redeemer.purs | 5 +- src/Internal/Types/ScriptLookups.purs | 11 ++-- src/Internal/Types/TypedTxOut.purs | 23 ++++---- test/Data.purs | 9 ++-- test/Deserialization.purs | 18 ++----- test/Hashing.purs | 6 +-- test/OgmiosDatumCache.purs | 5 +- test/Plutip/Contract.purs | 12 ++--- test/Serialization.purs | 21 ++++---- 21 files changed, 140 insertions(+), 160 deletions(-) diff --git a/examples/ContractTestUtils.purs b/examples/ContractTestUtils.purs index e45b056812..0ce8e0263f 100644 --- a/examples/ContractTestUtils.purs +++ b/examples/ContractTestUtils.purs @@ -87,7 +87,7 @@ mkAssertions params@(ContractParams p) = do liftedM "Failed to get sender address" $ head <$> getWalletAddresses receiverAddress <- liftedM "Failed to get receiver address" (getReceiverAddress params) - dhash <- liftContractM "Failed to hash datum" $ datumHash $ p.datumToAttach + let dhash = datumHash $ p.datumToAttach pure $ [ TestUtils.assertGainAtAddress' (label receiverAddress "Receiver") diff --git a/examples/SatisfiesAnyOf.purs b/examples/SatisfiesAnyOf.purs index 34175cf53b..d6168d2345 100644 --- a/examples/SatisfiesAnyOf.purs +++ b/examples/SatisfiesAnyOf.purs @@ -40,10 +40,8 @@ wrongDatum = Datum $ Integer $ BigInt.fromInt 42 testMustSatisfyAnyOf :: Contract () Unit testMustSatisfyAnyOf = do - wrongDatumHash <- liftMaybe (error "Cannot get DatumHash") $ Hashing.datumHash - wrongDatum - correctDatumHash <- liftMaybe (error "Cannot get DatumHash") $ - Hashing.datumHash unitDatum + let wrongDatumHash = Hashing.datumHash wrongDatum + let correctDatumHash = Hashing.datumHash unitDatum let constraints :: TxConstraints Unit Unit constraints = Constraints.mustSatisfyAnyOf diff --git a/src/Internal/Deserialization/PlutusData.purs b/src/Internal/Deserialization/PlutusData.purs index f30cd52c5d..b5acb4671f 100644 --- a/src/Internal/Deserialization/PlutusData.purs +++ b/src/Internal/Deserialization/PlutusData.purs @@ -29,14 +29,17 @@ import Ctl.Internal.Types.CborBytes (CborBytes) import Ctl.Internal.Types.PlutusData ( PlutusData(Constr, Map, List, Integer, Bytes) ) as T -import Data.Maybe (Maybe) +import Data.Maybe (Maybe(Just), fromJust) import Data.Newtype (unwrap) import Data.Traversable (traverse) import Data.Tuple (Tuple(Tuple)) import Data.Tuple.Nested (type (/\), (/\)) +import Partial.Unsafe (unsafePartial) -convertPlutusData :: PlutusData -> Maybe T.PlutusData -convertPlutusData pd = +convertPlutusData :: PlutusData -> T.PlutusData +-- Unsafe fromJust here is correct, because we cover every PlutusData +-- constructor, and Just will be returned by one of functions +convertPlutusData pd = unsafePartial $ fromJust $ convertPlutusConstr pd <|> convertPlutusMap pd <|> convertPlutusList pd @@ -46,9 +49,9 @@ convertPlutusData pd = convertPlutusConstr :: PlutusData -> Maybe T.PlutusData convertPlutusConstr pd = do constr <- _PlutusData_constr maybeFfiHelper pd - data' <- traverse convertPlutusData - $ _unpackPlutusList containerHelper - $ _ConstrPlutusData_data constr + let + data' = convertPlutusData <$> + (_unpackPlutusList containerHelper $ _ConstrPlutusData_data constr) alt <- BigNum.toBigInt $ _ConstrPlutusData_alternative constr pure $ T.Constr alt data' @@ -57,16 +60,17 @@ convertPlutusMap pd = do entries <- _PlutusData_map maybeFfiHelper pd >>= _unpackPlutusMap containerHelper Tuple >>> traverse \(k /\ v) -> do - k' <- convertPlutusData k - v' <- convertPlutusData v + let k' = convertPlutusData k + let v' = convertPlutusData v pure (k' /\ v') pure $ T.Map entries convertPlutusList :: PlutusData -> Maybe T.PlutusData convertPlutusList pd = T.List <$> do - _PlutusData_list maybeFfiHelper pd >>= - _unpackPlutusList containerHelper >>> - traverse convertPlutusData + _PlutusData_list maybeFfiHelper pd <#> + ( _unpackPlutusList containerHelper >>> + map convertPlutusData + ) convertPlutusInteger :: PlutusData -> Maybe T.PlutusData convertPlutusInteger pd = T.Integer <$> do @@ -76,7 +80,8 @@ convertPlutusBytes :: PlutusData -> Maybe T.PlutusData convertPlutusBytes pd = T.Bytes <$> _PlutusData_bytes maybeFfiHelper pd deserializeData :: forall (a :: Type). FromData a => CborBytes -> Maybe a -deserializeData = (fromData <=< convertPlutusData <=< fromBytes) <<< unwrap +deserializeData = (fromData <=< (Just <<< convertPlutusData) <=< fromBytes) <<< + unwrap foreign import _PlutusData_constr :: MaybeFfiHelper -> PlutusData -> Maybe ConstrPlutusData diff --git a/src/Internal/Deserialization/UnspentOutput.purs b/src/Internal/Deserialization/UnspentOutput.purs index 5cc4f8fd84..25b05fb0ba 100644 --- a/src/Internal/Deserialization/UnspentOutput.purs +++ b/src/Internal/Deserialization/UnspentOutput.purs @@ -98,8 +98,8 @@ convertOutput output = do mbDatum = getPlutusData maybeFfiHelper output datum <- case mbDatum, mbDataHash of Just _, Just _ -> Nothing -- impossible, so it's better to fail - Just datumValue, Nothing -> OutputDatum <<< wrap <$> convertPlutusData - datumValue + Just datumValue, Nothing -> pure <<< OutputDatum <<< wrap $ + convertPlutusData datumValue Nothing, Just datumHash -> pure $ OutputDatumHash datumHash Nothing, Nothing -> pure NoOutputDatum scriptRef <- getScriptRef maybeFfiHelper output # traverse convertScriptRef diff --git a/src/Internal/Deserialization/WitnessSet.purs b/src/Internal/Deserialization/WitnessSet.purs index 3597fa467b..b00d50dbfe 100644 --- a/src/Internal/Deserialization/WitnessSet.purs +++ b/src/Internal/Deserialization/WitnessSet.purs @@ -66,8 +66,9 @@ convertWitnessSet :: TransactionWitnessSet -> Maybe T.TransactionWitnessSet convertWitnessSet ws = do nativeScripts <- for (getNativeScripts maybeFfiHelper ws) convertNativeScripts redeemers <- for (getRedeemers maybeFfiHelper ws) convertRedeemers - plutusData <- for (getWitnessSetPlutusData maybeFfiHelper ws) - convertPlutusList + let + plutusData = map convertPlutusList + (getWitnessSetPlutusData maybeFfiHelper ws) plutusScripts <- for (getPlutusScripts maybeFfiHelper ws) convertPlutusScripts pure $ T.TransactionWitnessSet { vkeys: getVkeywitnesses maybeFfiHelper ws <#> convertVkeyWitnesses @@ -115,8 +116,8 @@ convertPlutusScript plutusScript = language <- convertLanguage $ plutusScriptVersion plutusScript pure $ curry S.PlutusScript (plutusScriptBytes plutusScript) language -convertPlutusList :: PlutusList -> Maybe (Array T.PlutusData) -convertPlutusList = extractPlutusData >>> traverse convertPlutusData +convertPlutusList :: PlutusList -> Array T.PlutusData +convertPlutusList = extractPlutusData >>> map convertPlutusData convertRedeemers :: Redeemers -> Maybe (Array T.Redeemer) convertRedeemers = extractRedeemers >>> traverse convertRedeemer @@ -126,7 +127,7 @@ convertRedeemer redeemer = do tag <- convertRedeemerTag $ getRedeemerTag redeemer index <- BigNum.toBigInt $ getRedeemerIndex redeemer exUnits <- convertExUnits $ getExUnits redeemer - data_ <- convertPlutusData $ getRedeemerPlutusData redeemer + let data_ = convertPlutusData $ getRedeemerPlutusData redeemer pure $ T.Redeemer { tag , index diff --git a/src/Internal/Hashing.purs b/src/Internal/Hashing.purs index f1b4cd6fbe..86a7a1dbf2 100644 --- a/src/Internal/Hashing.purs +++ b/src/Internal/Hashing.purs @@ -51,9 +51,9 @@ foreign import sha3_256Hash :: ByteArray -> ByteArray foreign import sha3_256HashHex :: ByteArray -> String -datumHash :: Datum -> Maybe DataHash +datumHash :: Datum -> DataHash datumHash = - map (wrap <<< hashPlutusData) <<< convertPlutusData <<< unwrap + wrap <<< hashPlutusData <<< convertPlutusData <<< unwrap -- | Calculates the hash of the transaction by applying `blake2b256Hash` to -- | the cbor-encoded transaction body. diff --git a/src/Internal/QueryM.purs b/src/Internal/QueryM.purs index 8da676b621..5c22d06f68 100644 --- a/src/Internal/QueryM.purs +++ b/src/Internal/QueryM.purs @@ -818,35 +818,35 @@ applyArgs script args = \provided host and port. The `ctl-server` packages can be obtained \ \from `overlays.ctl-server` defined in CTL's flake. Please see \ \`doc/runtime.md` in the CTL repository for more information" - Just config -> case traverse plutusDataToAeson args of - Nothing -> pure $ Left $ ClientEncodingError - "Failed to convert script args" - Just ps -> do - let - language :: Language - language = snd $ unwrap script - - url :: String - url = mkHttpUrl config <> "apply-args" - - reqBody :: Aeson - reqBody = encodeAeson - $ Object.fromFoldable - [ "script" /\ scriptToAeson script - , "args" /\ encodeAeson ps - ] - liftAff (postAeson url reqBody) - <#> map (PlutusScript <<< flip Tuple language) <<< - handleAffjaxResponse + Just config -> + let + ps = map plutusDataToAeson args + in + do + let + language :: Language + language = snd $ unwrap script + + url :: String + url = mkHttpUrl config <> "apply-args" + + reqBody :: Aeson + reqBody = encodeAeson + $ Object.fromFoldable + [ "script" /\ scriptToAeson script + , "args" /\ encodeAeson ps + ] + liftAff (postAeson url reqBody) + <#> map (PlutusScript <<< flip Tuple language) <<< + handleAffjaxResponse where - plutusDataToAeson :: PlutusData -> Maybe Aeson + plutusDataToAeson :: PlutusData -> Aeson plutusDataToAeson = - map - ( encodeAeson - <<< byteArrayToHex - <<< Serialization.toBytes - <<< asOneOf - ) + ( encodeAeson + <<< byteArrayToHex + <<< Serialization.toBytes + <<< asOneOf + ) <<< Serialization.convertPlutusData -- Checks response status code and returns `ClientError` in case of failure, diff --git a/src/Internal/Serialization.purs b/src/Internal/Serialization.purs index 1d8eddb043..13abf86762 100644 --- a/src/Internal/Serialization.purs +++ b/src/Internal/Serialization.purs @@ -166,7 +166,7 @@ import Data.FoldableWithIndex (forWithIndex_) import Data.Map as Map import Data.Maybe (Maybe(Just, Nothing)) import Data.Newtype (unwrap, wrap) -import Data.Traversable (for, for_, traverse, traverse_) +import Data.Traversable (for, for_, traverse_) import Data.Tuple (Tuple(Tuple)) import Data.Tuple.Nested (type (/\), (/\)) import Data.UInt (UInt) @@ -793,8 +793,7 @@ convertTxOutput transactionOutputSetDataHash txo OutputDatum datumValue -> do transactionOutputSetPlutusData txo - =<< fromJustEff "convertTxOutput" - (convertPlutusData $ unwrap datumValue) + =<< pure (convertPlutusData $ unwrap datumValue) for_ scriptRef $ convertScriptRef >>> transactionOutputSetScriptRef txo pure txo @@ -871,9 +870,9 @@ hashScriptData cms rs ps = do -- function, the resulting hash will be wrong case ps of [] -> _hashScriptDataNoDatums rs' cms' - _ -> _hashScriptData rs' cms' =<< fromJustEff "failed to convert datums" - (traverse convertPlutusData ps) + _ -> _hashScriptData rs' cms' =<< + pure (map convertPlutusData ps) -serializeData :: forall (a :: Type). ToData a => a -> Maybe CborBytes -serializeData = map (wrap <<< toBytes <<< asOneOf) <<< convertPlutusData <<< +serializeData :: forall (a :: Type). ToData a => a -> CborBytes +serializeData = wrap <<< toBytes <<< asOneOf <<< convertPlutusData <<< toData diff --git a/src/Internal/Serialization/PlutusData.purs b/src/Internal/Serialization/PlutusData.purs index 773bcd609c..b4fbf01cd6 100644 --- a/src/Internal/Serialization/PlutusData.purs +++ b/src/Internal/Serialization/PlutusData.purs @@ -23,38 +23,39 @@ import Ctl.Internal.Types.BigNum (fromBigInt) as BigNum import Ctl.Internal.Types.ByteArray (ByteArray) import Ctl.Internal.Types.PlutusData as T import Data.BigInt as BigInt -import Data.Maybe (Maybe) -import Data.Traversable (for, traverse) +import Data.Maybe (Maybe(Just), fromJust) import Data.Tuple (Tuple, fst, snd) import Data.Tuple.Nested (type (/\), (/\)) +import Partial.Unsafe (unsafePartial) -convertPlutusData :: T.PlutusData -> Maybe PlutusData -convertPlutusData = case _ of +convertPlutusData :: T.PlutusData -> PlutusData +-- Unsafe fromJust here is correct, because we cover every PlutusData +-- constructor, and Just will be returned by one of functions +convertPlutusData x = unsafePartial $ fromJust $ case x of T.Constr alt list -> convertConstr alt list - T.Map mp -> convertPlutusMap mp - T.List lst -> convertPlutusList lst + T.Map mp -> Just $ convertPlutusMap mp + T.List lst -> Just $ convertPlutusList lst T.Integer n -> convertPlutusInteger n T.Bytes b -> pure $ _mkPlutusData_bytes b convertConstr :: BigInt.BigInt -> Array T.PlutusData -> Maybe PlutusData convertConstr alt list = map _mkPlutusData_constr $ _mkConstrPlutusData - <$> BigNum.fromBigInt alt - <*> (_packPlutusList containerHelper <$> for list convertPlutusData) + <$> (BigNum.fromBigInt alt) + <*> Just (_packPlutusList containerHelper $ map convertPlutusData list) -convertPlutusList :: Array T.PlutusData -> Maybe PlutusData +convertPlutusList :: Array T.PlutusData -> PlutusData convertPlutusList x = - _mkPlutusData_list <<< _packPlutusList containerHelper <$> traverse - convertPlutusData - x + (_mkPlutusData_list <<< (_packPlutusList containerHelper)) $ + (map convertPlutusData x) -convertPlutusMap :: Array (T.PlutusData /\ T.PlutusData) -> Maybe PlutusData -convertPlutusMap mp = do - entries <- for mp \(k /\ v) -> do - k' <- convertPlutusData k - v' <- convertPlutusData v - pure $ k' /\ v' - pure $ _mkPlutusData_map $ _packMap fst snd entries +convertPlutusMap :: Array (T.PlutusData /\ T.PlutusData) -> PlutusData +convertPlutusMap mp = + let + entries :: Array (PlutusData /\ PlutusData) + entries = mp <#> \(k /\ v) -> (convertPlutusData k /\ convertPlutusData v) + in + _mkPlutusData_map $ _packMap fst snd entries convertPlutusInteger :: BigInt.BigInt -> Maybe PlutusData convertPlutusInteger n = @@ -63,9 +64,9 @@ convertPlutusInteger n = convertBigInt :: BigInt.BigInt -> Maybe BigInt convertBigInt n = _bigIntFromString maybeFfiHelper (BigInt.toString n) -packPlutusList :: Array T.PlutusData -> Maybe PlutusList -packPlutusList = map (_packPlutusList containerHelper) - <<< traverse convertPlutusData +packPlutusList :: Array T.PlutusData -> PlutusList +packPlutusList = (_packPlutusList containerHelper) + <<< map convertPlutusData foreign import _mkPlutusData_bytes :: ByteArray -> PlutusData foreign import _mkPlutusData_list :: PlutusList -> PlutusData diff --git a/src/Internal/Serialization/WitnessSet.purs b/src/Internal/Serialization/WitnessSet.purs index f6682277c9..260710c3f0 100644 --- a/src/Internal/Serialization/WitnessSet.purs +++ b/src/Internal/Serialization/WitnessSet.purs @@ -129,9 +129,7 @@ convertRedeemer (T.Redeemer { tag, index, "data": data_, exUnits }) = do newRedeemer tag' index' data' exUnits' convertPlutusDataEffect :: PD.PlutusData -> Effect PDS.PlutusData -convertPlutusDataEffect pd = maybe (throw "Failed to convert PlutusData") pure $ - convertPlutusData - pd +convertPlutusDataEffect pd = pure $ convertPlutusData pd convertRedeemerTag :: Tag.RedeemerTag -> Effect RedeemerTag convertRedeemerTag = _newRedeemerTag <<< case _ of diff --git a/src/Internal/Transaction.purs b/src/Internal/Transaction.purs index 56745dba93..831a04d132 100644 --- a/src/Internal/Transaction.purs +++ b/src/Internal/Transaction.purs @@ -87,13 +87,7 @@ attachDatums :: Array Datum -> Transaction -> ExceptT ModifyTxError Effect Transaction attachDatums [] tx = liftEither $ Right tx attachDatums datums tx@(Transaction { witnessSet: ws }) = do - ds <- traverse - ( liftEither - <<< note ConvertDatumError - <<< Serialization.PlutusData.convertPlutusData - <<< unwrap - ) - datums + let ds = map (Serialization.PlutusData.convertPlutusData <<< unwrap) datums updateTxWithWitnesses tx =<< convertWitnessesWith ws (Serialization.WitnessSet.setPlutusData ds) diff --git a/src/Internal/TxOutput.purs b/src/Internal/TxOutput.purs index c5ba5bbd69..34a5406ede 100644 --- a/src/Internal/TxOutput.purs +++ b/src/Internal/TxOutput.purs @@ -31,7 +31,7 @@ import Ctl.Internal.Types.OutputDatum , outputDatumDatum ) import Ctl.Internal.Types.Transaction (TransactionInput(TransactionInput)) as Transaction -import Data.Maybe (Maybe, fromMaybe, isNothing) +import Data.Maybe (Maybe(Just), fromMaybe, isNothing) import Data.Newtype (unwrap, wrap) import Data.Traversable (traverse) import Untagged.Union (asOneOf) @@ -90,7 +90,7 @@ transactionOutputToOgmiosTxOut { address: addressToOgmiosAddress address , value , datumHash: datumHashToOgmiosDatumHash <$> outputDatumDataHash datum - , datum: datumToOgmiosDatum =<< outputDatumDatum datum + , datum: datumToOgmiosDatum <$> outputDatumDatum datum , script: scriptRef } @@ -106,7 +106,7 @@ ogmiosDatumToDatum :: String -> Maybe Datum ogmiosDatumToDatum = hexToByteArray >=> fromBytes - >=> Deserialization.convertPlutusData + >=> (Deserialization.convertPlutusData >>> Just) >>> map Datum -- | Converts an internal `DataHash` to an Ogmios datumhash `String` @@ -114,9 +114,9 @@ datumHashToOgmiosDatumHash :: DataHash -> String datumHashToOgmiosDatumHash = byteArrayToHex <<< unwrap -- | Converts an internal `Datum` to an Ogmios datum `String` -datumToOgmiosDatum :: Datum -> Maybe String +datumToOgmiosDatum :: Datum -> String datumToOgmiosDatum (Datum plutusData) = - Serialization.convertPlutusData plutusData <#> + Serialization.convertPlutusData plutusData # (asOneOf >>> toBytes >>> byteArrayToHex) toOutputDatum :: Maybe Datum -> Maybe DataHash -> OutputDatum diff --git a/src/Internal/Types/Redeemer.purs b/src/Internal/Types/Redeemer.purs index 149dbc46e4..b5776f92cf 100644 --- a/src/Internal/Types/Redeemer.purs +++ b/src/Internal/Types/Redeemer.purs @@ -14,7 +14,6 @@ import Ctl.Internal.ToData (class ToData, toData) import Ctl.Internal.Types.ByteArray (ByteArray) import Ctl.Internal.Types.PlutusData (PlutusData) import Data.Generic.Rep (class Generic) -import Data.Maybe (Maybe) import Data.Newtype (class Newtype, unwrap, wrap) import Data.Show.Generic (genericShow) import Untagged.Union (asOneOf) @@ -49,6 +48,6 @@ instance Show RedeemerHash where -- | Converts Plutus-style `Redeemer` to internal (non-CSL) `RedeemerHash`. -- | This is a duplicate of `datumHash`. -redeemerHash :: Redeemer -> Maybe RedeemerHash +redeemerHash :: Redeemer -> RedeemerHash redeemerHash = - map (wrap <<< toBytes <<< asOneOf) <<< convertPlutusData <<< unwrap + wrap <<< toBytes <<< asOneOf <<< convertPlutusData <<< unwrap diff --git a/src/Internal/Types/ScriptLookups.purs b/src/Internal/Types/ScriptLookups.purs index a7ffb0f682..413519b925 100644 --- a/src/Internal/Types/ScriptLookups.purs +++ b/src/Internal/Types/ScriptLookups.purs @@ -422,10 +422,10 @@ validatorM :: forall (a :: Type). Validator -> Maybe (ScriptLookups a) validatorM = pure <<< validator -- | A script lookups value with a datum. -datum :: forall (a :: Type). Datum -> Maybe (ScriptLookups a) +datum :: forall (a :: Type). Datum -> ScriptLookups a datum dt = Hashing.datumHash dt - <#> \dh -> over ScriptLookups _ { datums = singleton dh dt } mempty + # \dh -> over ScriptLookups _ { datums = singleton dh dt } mempty -- | Add your own `PaymentPubKeyHash` to the lookup. ownPaymentPubKeyHash :: forall (a :: Type). PaymentPubKeyHash -> ScriptLookups a @@ -1299,8 +1299,8 @@ processConstraint mpsMap osMap = do _cpsToTxBody <<< _outputs %= Array.(:) txOut _valueSpentBalancesOutputs <>= provideValue amount MustHashDatum dh dt -> do - let mdh = Hashing.datumHash dt - if mdh == Just dh then addDatum dt + let dh' = Hashing.datumHash dt + if dh' == dh then addDatum dt else pure $ throwError $ DatumWrongHash dh dt MustRegisterStakePubKey skh -> runExceptT do lift $ addCertificate @@ -1459,8 +1459,7 @@ processConstraint mpsMap osMap = do OutputDatum outputDatum dat = case _ of DatumInline -> pure $ OutputDatum dat - DatumWitness -> OutputDatumHash <$> liftMaybe (CannotHashDatum dat) - (Hashing.datumHash dat) + DatumWitness -> pure $ OutputDatumHash $ Hashing.datumHash dat credentialToStakeCredential :: Credential -> StakeCredential credentialToStakeCredential cred = case cred of diff --git a/src/Internal/Types/TypedTxOut.purs b/src/Internal/Types/TypedTxOut.purs index bfd07798a3..a516374d4f 100644 --- a/src/Internal/Types/TypedTxOut.purs +++ b/src/Internal/Types/TypedTxOut.purs @@ -175,23 +175,20 @@ mkTypedTxOut -> Maybe (TypedTxOut validator datum) mkTypedTxOut networkId typedVal dt amount = let - mDHash = Hashing.datumHash $ Datum $ toData dt + dHash = Hashing.datumHash $ Datum $ toData dt -- FIX ME: This is hardcoded to enterprise address, it seems like Plutus' -- "validatorAddress" also currently doesn't account for staking. address = typedValidatorEnterpriseAddress networkId typedVal in - case mDHash of - Nothing -> Nothing - Just dHash -> - Just <<< mkTypedTxOut' dt $ - wrap - { address - , amount - -- TODO: populate properly - -- https://github.com/Plutonomicon/cardano-transaction-lib/issues/691 - , datum: OutputDatumHash dHash - , scriptRef: Nothing - } + Just <<< mkTypedTxOut' dt $ + wrap + { address + , amount + -- TODO: populate properly + -- https://github.com/Plutonomicon/cardano-transaction-lib/issues/691 + , datum: OutputDatumHash dHash + , scriptRef: Nothing + } where mkTypedTxOut' :: datum -- Data diff --git a/test/Data.purs b/test/Data.purs index 2af9f7a4fc..bd64858e18 100644 --- a/test/Data.purs +++ b/test/Data.purs @@ -552,8 +552,9 @@ instance (FromData a) => FromData (Tree a) where fromData x = genericFromData x fromBytesFromData :: forall a. FromData a => String -> Maybe a -fromBytesFromData binary = fromData =<< PDD.convertPlutusData =<< fromBytes - (hexToByteArrayUnsafe binary) +fromBytesFromData binary = fromData =<< (Just <<< PDD.convertPlutusData) =<< + fromBytes + (hexToByteArrayUnsafe binary) testBinaryFixture :: forall a @@ -568,8 +569,8 @@ testBinaryFixture value binaryFixture = do test ("Deserialization: " <> show value) do fromBytesFromData binaryFixture `shouldEqual` Just value test ("Serialization: " <> show value) do - map (toBytes <<< asOneOf) (PDS.convertPlutusData (toData value)) - `shouldEqual` Just + (toBytes <<< asOneOf) (PDS.convertPlutusData (toData value)) + `shouldEqual` (hexToByteArrayUnsafe binaryFixture) -- | Poor man's type level tests diff --git a/test/Deserialization.purs b/test/Deserialization.purs index af0eb196aa..3402ed5807 100644 --- a/test/Deserialization.purs +++ b/test/Deserialization.purs @@ -107,15 +107,11 @@ suite = do group "CSL <-> CTL PlutusData roundtrip tests" do let pdRoundTripTest ctlPd = do - cslPd <- - errMaybe "Failed to convert from CTL PlutusData to CSL PlutusData" $ - SPD.convertPlutusData ctlPd + let cslPd = SPD.convertPlutusData ctlPd let pdBytes = toBytes (asOneOf cslPd) cslPd' <- errMaybe "Failed to fromBytes PlutusData" $ fromBytes pdBytes - ctlPd' <- - errMaybe "Failed to convert from CSL PlutusData to CTL PlutusData" $ - DPD.convertPlutusData cslPd' + let ctlPd' = DPD.convertPlutusData cslPd' ctlPd' `shouldEqual` ctlPd test "fixture #1" $ pdRoundTripTest plutusDataFixture1 test "fixture #2" $ pdRoundTripTest plutusDataFixture2 @@ -130,17 +126,11 @@ suite = do $ do cslPd' <- errMaybe "Failed to fromBytes PlutusData" $ fromBytes plutusDataFixture8Bytes - ctlPd' <- - errMaybe "Failed to convert from CSL PlutusData to CTL PlutusData" - $ - DPD.convertPlutusData cslPd' + let ctlPd' = DPD.convertPlutusData cslPd' ctlPd' `shouldEqual` plutusDataFixture8 cslPdWp' <- errMaybe "Failed to fromBytes PlutusData" $ fromBytes plutusDataFixture8Bytes' - ctlPdWp' <- - errMaybe "Failed to convert from CSL PlutusData to CTL PlutusData" - $ - DPD.convertPlutusData cslPdWp' + let ctlPdWp' = DPD.convertPlutusData cslPdWp' ctlPdWp' `shouldEqual` plutusDataFixture8 group "UnspentTransactionOutput" do test "deserialization is inverse to serialization" do diff --git a/test/Hashing.purs b/test/Hashing.purs index ddd95070ab..269fd04800 100644 --- a/test/Hashing.purs +++ b/test/Hashing.purs @@ -24,7 +24,7 @@ import Ctl.Internal.Types.RawBytes (hexToRawBytesUnsafe) import Ctl.Internal.Types.Scripts (PlutusScript, plutusV1Script, plutusV2Script) import Ctl.Internal.Types.Transaction (DataHash) import Data.BigInt (fromInt) -import Data.Maybe (Maybe(Just), fromJust) +import Data.Maybe (fromJust) import Data.Newtype (wrap) import Effect.Aff (Aff) import Mote (group, test) @@ -53,13 +53,13 @@ suite = test "blake2b256 hash of Plutus data" do Hashing.datumHash (wrap plutusDataFixture7) - `shouldEqual` Just datumHashFixture + `shouldEqual` datumHashFixture test "blake2b256 hash of Plutus data - Integer 0 (regression to \ \https://github.com/Plutonomicon/cardano-transaction-lib/issues/488 ?)" do Hashing.datumHash (wrap $ Integer (fromInt 0)) - `shouldEqual` Just zeroIntDatumHashFixture + `shouldEqual` zeroIntDatumHashFixture test "sha256 hash of an arbitrary byte array" do Hashing.sha256Hash inputDataFixture diff --git a/test/OgmiosDatumCache.purs b/test/OgmiosDatumCache.purs index d08d2b1b58..8e4ef11601 100644 --- a/test/OgmiosDatumCache.purs +++ b/test/OgmiosDatumCache.purs @@ -14,7 +14,6 @@ import Ctl.Internal.Types.Datum (Datum(Datum)) import Ctl.Internal.Types.PlutusData (PlutusData) import Data.Either (Either(Left, Right)) import Data.Map as Map -import Data.Maybe (Maybe(Just)) import Data.Newtype (unwrap) import Data.Traversable (for_) import Data.Tuple.Nested ((/\)) @@ -51,7 +50,7 @@ getDatumsByHashesHashingTest getDatumsByHashesHashingTest = do datums <- Map.toUnfoldable <<< unwrap <$> readGetDatumsByHashesSample for_ (datums :: Array _) \(hash /\ datum) -> do - (datumHash <$> datum) `shouldEqual` Right (Just hash) + (datumHash <$> datum) `shouldEqual` Right (hash) readPlutusDataSamples :: forall (m :: Type -> Type) @@ -80,5 +79,5 @@ plutusDataHashingTest = do plutusDataSamples <- readPlutusDataSamples let elems = plutusDataSamples for_ elems \{ hash, plutusData } -> do - hash' <- errMaybe "Couldn't hash the datum" <<< datumHash $ Datum plutusData + let hash' = datumHash $ Datum plutusData hash `shouldEqual` unwrap hash' diff --git a/test/Plutip/Contract.purs b/test/Plutip/Contract.purs index cc67b512a2..cc35473c96 100644 --- a/test/Plutip/Contract.purs +++ b/test/Plutip/Contract.purs @@ -753,12 +753,9 @@ suite = do awaitTxConfirmed txId logInfo' "Tx submitted successfully, trying to fetch datum from ODC" - hash1 <- liftM (error "Couldn't get hash for datums 1") $ - datumHash datum1 - hash2 <- liftM (error "Couldn't get hash for datums 2") $ - datumHash datum2 - hashes <- liftM (error "Couldn't get hashes for datums [1,2]") $ - traverse datumHash datums + let hash1 = datumHash datum1 + let hash2 = datumHash datum2 + let hashes = map datumHash datums actualDatums1 <- getDatumsByHashes hashes actualDatums1 `shouldEqual` Map.fromFoldable @@ -1380,8 +1377,7 @@ suite = do tn (BigInt.fromInt 50) - datumLookup <- liftContractM "Unable to create datum lookup" $ - Lookups.datum datum' + let datumLookup = Lookups.datum datum' let lookups0 :: Lookups.ScriptLookups PlutusData diff --git a/test/Serialization.purs b/test/Serialization.purs index 90842e92a7..b3eecaaa2b 100644 --- a/test/Serialization.purs +++ b/test/Serialization.purs @@ -83,7 +83,8 @@ suite = do [ PD.Integer (BigInt.fromInt 1) , PD.Integer (BigInt.fromInt 2) ] - (convertPlutusData datum $> unit) `shouldSatisfy` isJust + let _ = convertPlutusData datum -- Checking no exception raised + pure unit test "PlutusData #2 - Map" $ do let datum = @@ -91,28 +92,30 @@ suite = do [ PD.Integer (BigInt.fromInt 1) /\ PD.Integer (BigInt.fromInt 2) , PD.Integer (BigInt.fromInt 3) /\ PD.Integer (BigInt.fromInt 4) ] - (convertPlutusData datum $> unit) `shouldSatisfy` isJust + let _ = convertPlutusData datum -- Checking no exception raised + pure unit test "PlutusData #3 - List" $ do let datum = PD.List [ PD.Integer (BigInt.fromInt 1), PD.Integer (BigInt.fromInt 2) ] - (convertPlutusData datum $> unit) `shouldSatisfy` isJust + let _ = convertPlutusData datum -- Checking no exception raised + pure unit test "PlutusData #4 - List" $ do let datum = PD.List [ PD.Integer (BigInt.fromInt 1), PD.Integer (BigInt.fromInt 2) ] - (convertPlutusData datum $> unit) `shouldSatisfy` isJust + let _ = convertPlutusData datum -- Checking no exception raised + pure unit test "PlutusData #5 - Bytes" $ do let datum = PD.Bytes $ hexToByteArrayUnsafe "00ff" - (convertPlutusData datum $> unit) `shouldSatisfy` isJust + let _ = convertPlutusData datum -- Checking no exception raised + pure unit test "PlutusData #6 - Integer 0 (regression to https://github.com/Plutonomicon/cardano-transaction-lib/issues/488 ?)" $ do let - datum = PD.Integer (BigInt.fromInt 0) - datum' <- errMaybe "Cannot convertPlutusData" $ convertPlutusData - datum - let bytes = toBytes (asOneOf datum') + datum = convertPlutusData $ PD.Integer (BigInt.fromInt 0) + let bytes = toBytes (asOneOf datum) byteArrayToHex bytes `shouldEqual` "00" test "TransactionOutput serialization" $ liftEffect do txo <- convertTxOutput txOutputFixture1 From 20df1ee4c59efb27728b868c66035f235469f724 Mon Sep 17 00:00:00 2001 From: peter Date: Mon, 5 Dec 2022 16:46:14 +0100 Subject: [PATCH 045/373] with Castable constraint --- src/Contract/Transaction.purs | 3 +-- src/Internal/BalanceTx/ExUnitsAndMinFee.purs | 3 +-- src/Internal/Cardano/Types/Transaction.purs | 6 ++---- src/Internal/Cardano/Types/Value.purs | 5 ++--- src/Internal/Deserialization/Transaction.purs | 13 ++++++------- src/Internal/Deserialization/UnspentOutput.purs | 7 +++---- src/Internal/Hashing.purs | 5 ++--- src/Internal/Plutus/Types/CurrencySymbol.purs | 5 ++--- src/Internal/QueryM.purs | 2 -- src/Internal/QueryM/Kupo.purs | 3 +-- src/Internal/QueryM/Pools.purs | 9 ++++----- src/Internal/Serialization.purs | 3 +-- src/Internal/Serialization/AuxiliaryData.purs | 3 +-- src/Internal/Serialization/ToBytes.purs | 8 +++++--- src/Internal/Transaction.purs | 3 +-- src/Internal/TxOutput.purs | 3 +-- src/Internal/Types/Redeemer.purs | 3 +-- src/Internal/Types/VRFKeyHash.purs | 7 +++---- src/Internal/Wallet/Cip30.purs | 3 +-- src/Internal/Wallet/Cip30Mock.purs | 15 +++++++-------- test/Data.purs | 3 +-- test/Deserialization.purs | 7 +++---- test/Serialization.purs | 9 ++++----- test/Serialization/Hash.purs | 5 ++--- 24 files changed, 55 insertions(+), 78 deletions(-) diff --git a/src/Contract/Transaction.purs b/src/Contract/Transaction.purs index 5b004ba7d3..2f9d730b38 100644 --- a/src/Contract/Transaction.purs +++ b/src/Contract/Transaction.purs @@ -277,7 +277,6 @@ import Effect.Aff (bracket) import Effect.Aff.Class (liftAff) import Effect.Class (liftEffect) import Effect.Exception (throw) -import Untagged.Castable (cast) -- | Signs a transaction with potential failure. signTransaction @@ -315,7 +314,7 @@ submitE tx = do cslTx <- liftEffect $ Serialization.convertTransaction (unwrap tx) let txHash = Hashing.transactionHash cslTx logDebug' $ "Pre-calculated tx hash: " <> show txHash - let txCborBytes = Serialization.toBytes $ cast cslTx + let txCborBytes = Serialization.toBytes cslTx result <- wrapContract $ QueryM.submitTxOgmios (unwrap txHash) txCborBytes pure $ case result of diff --git a/src/Internal/BalanceTx/ExUnitsAndMinFee.purs b/src/Internal/BalanceTx/ExUnitsAndMinFee.purs index ead3264ca5..b80c90f5e4 100644 --- a/src/Internal/BalanceTx/ExUnitsAndMinFee.purs +++ b/src/Internal/BalanceTx/ExUnitsAndMinFee.purs @@ -85,7 +85,6 @@ import Data.Traversable (for) import Data.Tuple (fst, snd) import Data.Tuple.Nested (type (/\), (/\)) import Effect.Class (liftEffect) -import Untagged.Castable (cast) evalTxExecutionUnits :: Transaction @@ -93,7 +92,7 @@ evalTxExecutionUnits -> BalanceTxM Ogmios.TxEvaluationResult evalTxExecutionUnits tx unattachedTx = do txBytes <- liftEffect - $ Serialization.toBytes <<< cast <$> Serialization.convertTransaction tx + $ Serialization.toBytes <$> Serialization.convertTransaction tx additionalUtxos <- getOgmiosAdditionalUtxoSet evalResult <- unwrap <$> liftQueryM (QueryM.evaluateTxOgmios txBytes additionalUtxos) diff --git a/src/Internal/Cardano/Types/Transaction.purs b/src/Internal/Cardano/Types/Transaction.purs index a4300c6171..b6706eff43 100644 --- a/src/Internal/Cardano/Types/Transaction.purs +++ b/src/Internal/Cardano/Types/Transaction.purs @@ -165,7 +165,6 @@ import Data.Tuple (Tuple(Tuple)) import Data.Tuple.Nested (type (/\)) import Data.UInt (UInt) import Partial.Unsafe (unsafePartial) -import Untagged.Castable (cast) -------------------------------------------------------------------------------- -- `Transaction` @@ -873,12 +872,11 @@ newtype Ed25519Signature = Ed25519Signature RawBytes mkEd25519Signature :: Bech32String -> Maybe Ed25519Signature mkEd25519Signature = - map (Ed25519Signature <<< wrap <<< unwrap <<< toBytes <<< cast) <<< + map (Ed25519Signature <<< wrap <<< unwrap <<< toBytes) <<< ed25519SignatureFromBech32 mkFromCslEd25519Signature :: Serialization.Ed25519Signature -> Ed25519Signature -mkFromCslEd25519Signature = Ed25519Signature <<< wrap <<< unwrap <<< toBytes <<< - cast +mkFromCslEd25519Signature = Ed25519Signature <<< wrap <<< unwrap <<< toBytes convertEd25519Signature :: Ed25519Signature -> Serialization.Ed25519Signature convertEd25519Signature (Ed25519Signature bs) = unsafePartial diff --git a/src/Internal/Cardano/Types/Value.purs b/src/Internal/Cardano/Types/Value.purs index 6e584125c5..59abe88837 100644 --- a/src/Internal/Cardano/Types/Value.purs +++ b/src/Internal/Cardano/Types/Value.purs @@ -111,7 +111,6 @@ import Data.Traversable (class Traversable, traverse) import Data.Tuple (fst) import Data.Tuple.Nested (type (/\), (/\)) import Partial.Unsafe (unsafePartial) -import Untagged.Castable (cast) -- `Negate` and `Split` seem a bit too contrived, and their purpose is to -- combine similar behaviour without satisfying any useful laws. I wonder @@ -779,7 +778,7 @@ currencyScriptHash (CurrencySymbol byteArray) = unsafePartial fromJust $ scriptHashFromBytes byteArray scriptHashAsCurrencySymbol :: ScriptHash -> CurrencySymbol -scriptHashAsCurrencySymbol = CurrencySymbol <<< unwrap <<< toBytes <<< cast +scriptHashAsCurrencySymbol = CurrencySymbol <<< unwrap <<< toBytes -- | The minting policy hash of a currency symbol currencyMPSHash :: CurrencySymbol -> MintingPolicyHash @@ -790,7 +789,7 @@ currencyMPSHash = MintingPolicyHash <<< currencyScriptHash -- Plutus doesn't use Maybe here. -- | The currency symbol of a monetary policy hash mpsSymbol :: MintingPolicyHash -> Maybe CurrencySymbol -mpsSymbol (MintingPolicyHash h) = mkCurrencySymbol $ unwrap $ toBytes $ cast h +mpsSymbol (MintingPolicyHash h) = mkCurrencySymbol $ unwrap $ toBytes h -- Like `mapEither` that works with 'These'. mapThese diff --git a/src/Internal/Deserialization/Transaction.purs b/src/Internal/Deserialization/Transaction.purs index 97a997f3fa..c62389be79 100644 --- a/src/Internal/Deserialization/Transaction.purs +++ b/src/Internal/Deserialization/Transaction.purs @@ -212,7 +212,6 @@ import Data.UInt (UInt) import Data.UInt as UInt import Data.Variant (Variant) import Type.Row (type (+)) -import Untagged.Castable (cast) -- | Deserializes CBOR encoded transaction to a CTL's native type. deserializeTransaction @@ -300,7 +299,7 @@ convertTxBody txBody = do , withdrawals , update , auxiliaryDataHash: - T.AuxiliaryDataHash <<< unwrap <<< (toBytes <<< cast) <$> + T.AuxiliaryDataHash <<< unwrap <<< toBytes <$> _txBodyAuxiliaryDataHash maybeFfiHelper txBody , validityStartInterval: Slot <$> _txBodyValidityStartInterval maybeFfiHelper txBody @@ -325,7 +324,7 @@ convertUpdate u = do epoch <- map T.Epoch $ cslNumberToUInt "convertUpdate: epoch" e ppus <- traverse ( bitraverse - (pure <<< T.GenesisHash <<< unwrap <<< toBytes <<< cast) + (pure <<< T.GenesisHash <<< unwrap <<< toBytes) convertProtocolParamUpdate ) paramUpdates @@ -348,9 +347,9 @@ convertCertificate = _convertCert certConvHelper , poolRetirement: convertPoolRetirement , genesisKeyDelegation: \genesisHash genesisDelegateHash vrfKeyhash -> do pure $ T.GenesisKeyDelegation - { genesisHash: T.GenesisHash $ unwrap $ toBytes $ cast genesisHash + { genesisHash: T.GenesisHash $ unwrap $ toBytes genesisHash , genesisDelegateHash: T.GenesisDelegateHash - (unwrap $ toBytes $ cast genesisDelegateHash) + (unwrap $ toBytes genesisDelegateHash) , vrfKeyhash: VRFKeyHash vrfKeyhash } , moveInstantaneousRewardsToOtherPotCert: \pot amount -> do @@ -386,7 +385,7 @@ convertPoolRegistration params = do convertPoolMetadata_ \url hash -> T.PoolMetadata { url: T.URL url - , hash: T.PoolMetadataHash $ unwrap $ toBytes $ cast hash + , hash: T.PoolMetadataHash $ unwrap $ toBytes hash } } @@ -661,7 +660,7 @@ convertExUnits nm cslExunits = <*> BigNum.toBigInt' (nm <> " steps") steps convertScriptDataHash :: Csl.ScriptDataHash -> T.ScriptDataHash -convertScriptDataHash = cast >>> toBytes >>> unwrap >>> T.ScriptDataHash +convertScriptDataHash = toBytes >>> unwrap >>> T.ScriptDataHash convertProtocolVersion :: forall (r :: Row Type) diff --git a/src/Internal/Deserialization/UnspentOutput.purs b/src/Internal/Deserialization/UnspentOutput.purs index c554916d8e..b2e820fc5e 100644 --- a/src/Internal/Deserialization/UnspentOutput.purs +++ b/src/Internal/Deserialization/UnspentOutput.purs @@ -67,7 +67,6 @@ import Data.Traversable (for, traverse) import Data.Tuple (Tuple(Tuple)) import Data.Tuple.Nested (type (/\)) import Data.UInt as UInt -import Untagged.Castable (cast) convertUnspentOutput :: TransactionUnspentOutput -> Maybe T.TransactionUnspentOutput @@ -80,7 +79,7 @@ convertInput :: TransactionInput -> Maybe T.TransactionInput convertInput input = do index <- UInt.fromInt' $ getTransactionIndex input pure $ T.TransactionInput - { transactionId: T.TransactionHash $ unwrap $ toBytes $ cast + { transactionId: T.TransactionHash $ unwrap $ toBytes (getTransactionHash input) , index } @@ -92,7 +91,7 @@ convertOutput output = do address = getAddress output mbDataHash = getDataHash maybeFfiHelper output <#> - cast >>> toBytes >>> unwrap >>> T.DataHash + toBytes >>> unwrap >>> T.DataHash mbDatum = getPlutusData maybeFfiHelper output datum <- case mbDatum, mbDataHash of Just _, Just _ -> Nothing -- impossible, so it's better to fail @@ -127,7 +126,7 @@ convertValue value = do ( traverse ( bitraverse -- scripthash to currency symbol - (cast >>> toBytes >>> unwrap >>> T.mkCurrencySymbol) + (toBytes >>> unwrap >>> T.mkCurrencySymbol) -- nested assetname to tokenname (traverse (ltraverse (T.assetNameName >>> T.mkTokenName))) ) diff --git a/src/Internal/Hashing.purs b/src/Internal/Hashing.purs index fc0b33a886..79add6ac1b 100644 --- a/src/Internal/Hashing.purs +++ b/src/Internal/Hashing.purs @@ -34,7 +34,6 @@ import Ctl.Internal.Types.Scripts (PlutusScript) import Ctl.Internal.Types.Transaction (DataHash, TransactionHash) import Data.Maybe (Maybe) import Data.Newtype (unwrap, wrap) -import Untagged.Castable (cast) foreign import blake2b256Hash :: ByteArray -> ByteArray @@ -55,7 +54,7 @@ foreign import sha3_256HashHex :: ByteArray -> String datumHash :: Datum -> Maybe DataHash datumHash = - map (wrap <<< unwrap <<< toBytes <<< cast <<< hashPlutusData) + map (wrap <<< unwrap <<< toBytes <<< hashPlutusData) <<< convertPlutusData <<< unwrap @@ -64,7 +63,7 @@ datumHash = -- | the cbor-encoded transaction body. transactionHash :: Serialization.Transaction -> TransactionHash transactionHash = - wrap <<< blake2b256Hash <<< unwrap <<< toBytes <<< cast <<< _txBody + wrap <<< blake2b256Hash <<< unwrap <<< toBytes <<< _txBody plutusScriptHash :: PlutusScript -> ScriptHash plutusScriptHash = hashPlutusScript <<< convertPlutusScript diff --git a/src/Internal/Plutus/Types/CurrencySymbol.purs b/src/Internal/Plutus/Types/CurrencySymbol.purs index 4d1ca03763..ba17b0a2a5 100644 --- a/src/Internal/Plutus/Types/CurrencySymbol.purs +++ b/src/Internal/Plutus/Types/CurrencySymbol.purs @@ -34,7 +34,6 @@ import Data.Maybe (Maybe, fromJust) import Data.Newtype (unwrap) import Partial.Unsafe (unsafePartial) import Test.QuickCheck.Arbitrary (class Arbitrary) -import Untagged.Castable (cast) newtype CurrencySymbol = CurrencySymbol ByteArray @@ -75,7 +74,7 @@ adaSymbol :: CurrencySymbol adaSymbol = CurrencySymbol mempty scriptHashAsCurrencySymbol :: ScriptHash -> CurrencySymbol -scriptHashAsCurrencySymbol = CurrencySymbol <<< unwrap <<< toBytes <<< cast +scriptHashAsCurrencySymbol = CurrencySymbol <<< unwrap <<< toBytes -- | The minting policy hash of a currency symbol. currencyMPSHash :: CurrencySymbol -> MintingPolicyHash @@ -83,7 +82,7 @@ currencyMPSHash = MintingPolicyHash <<< currencyScriptHash -- | The currency symbol of a monetary policy hash. mpsSymbol :: MintingPolicyHash -> Maybe CurrencySymbol -mpsSymbol (MintingPolicyHash h) = mkCurrencySymbol $ unwrap $ toBytes $ cast h +mpsSymbol (MintingPolicyHash h) = mkCurrencySymbol $ unwrap $ toBytes h getCurrencySymbol :: CurrencySymbol -> ByteArray getCurrencySymbol (CurrencySymbol curSymbol) = curSymbol diff --git a/src/Internal/QueryM.purs b/src/Internal/QueryM.purs index d5d0dc5a9d..1afe925134 100644 --- a/src/Internal/QueryM.purs +++ b/src/Internal/QueryM.purs @@ -278,7 +278,6 @@ import Effect.Exception (Error, error, throw, try) import Effect.Ref (Ref) import Effect.Ref as Ref import Foreign.Object as Object -import Untagged.Castable (cast) -- This module defines an Aff interface for Ogmios Websocket Queries -- Since WebSockets do not define a mechanism for linking request/response @@ -846,7 +845,6 @@ applyArgs script args = <<< byteArrayToHex <<< unwrap <<< Serialization.toBytes - <<< cast ) <<< Serialization.convertPlutusData diff --git a/src/Internal/QueryM/Kupo.purs b/src/Internal/QueryM/Kupo.purs index 1ead112415..fb7a26bb8f 100644 --- a/src/Internal/QueryM/Kupo.purs +++ b/src/Internal/QueryM/Kupo.purs @@ -88,7 +88,6 @@ import Data.UInt (toString) as UInt import Effect.Aff.Class (liftAff) import Foreign.Object (Object) import Foreign.Object (toUnfoldable) as Object -import Untagged.Castable (cast) -------------------------------------------------------------------------------- -- Requests @@ -128,7 +127,7 @@ getScriptByHash :: ScriptHash -> QueryM (Either ClientError (Maybe ScriptRef)) getScriptByHash scriptHash = do let endpoint = "/scripts/" <> rawBytesToHex - (wrap $ unwrap $ toBytes $ cast scriptHash) + (wrap $ unwrap $ toBytes scriptHash) kupoGetRequest endpoint <#> map unwrapKupoScriptRef <<< handleAffjaxResponse diff --git a/src/Internal/QueryM/Pools.purs b/src/Internal/QueryM/Pools.purs index 28042d1517..df5400fbe8 100644 --- a/src/Internal/QueryM/Pools.purs +++ b/src/Internal/QueryM/Pools.purs @@ -36,7 +36,6 @@ import Data.Maybe (Maybe) import Data.Newtype (unwrap, wrap) import Effect.Exception (error) import Record.Builder (build, merge) -import Untagged.Castable (cast) getPoolIds :: QueryM (Array PoolPubKeyHash) getPoolIds = mkOgmiosRequest Ogmios.queryPoolIdsCall @@ -82,13 +81,13 @@ getValidatorHashDelegationsAndRewards skh = do stringRep = scriptHashToBech32Unsafe "script" $ unwrap skh -- byteHex :: String - -- byteHex = byteArrayToHex $ unwrap $ toBytes $ cast $ unwrap skh + -- byteHex = byteArrayToHex $ unwrap $ toBytes $ unwrap skh sh :: ScriptHash sh = unwrap skh byteHex :: String - byteHex = byteArrayToHex $ unwrap $ toBytes $ cast sh + byteHex = byteArrayToHex $ unwrap $ toBytes sh -- TODO: batched variant getPubKeyHashDelegationsAndRewards @@ -104,10 +103,10 @@ getPubKeyHashDelegationsAndRewards pkh = do ed25519KeyHashToBech32Unsafe "stake_vkh" $ unwrap $ unwrap pkh -- byteHex :: String - -- byteHex = byteArrayToHex $ unwrap $ toBytes $ cast $ unwrap $ unwrap pkh + -- byteHex = byteArrayToHex $ unwrap $ toBytes $ unwrap $ unwrap pkh ed :: Ed25519KeyHash ed = unwrap $ unwrap pkh byteHex :: String - byteHex = byteArrayToHex $ unwrap $ toBytes $ cast ed + byteHex = byteArrayToHex $ unwrap $ toBytes ed diff --git a/src/Internal/Serialization.purs b/src/Internal/Serialization.purs index 62f1123594..e536817090 100644 --- a/src/Internal/Serialization.purs +++ b/src/Internal/Serialization.purs @@ -172,7 +172,6 @@ import Data.Tuple.Nested (type (/\), (/\)) import Data.UInt (UInt) import Data.UInt as UInt import Effect (Effect) -import Untagged.Castable (cast) import Untagged.Union (UndefinedOr, maybeToUor) foreign import hashTransaction :: TransactionBody -> Effect TransactionHash @@ -883,4 +882,4 @@ hashScriptData cms rs ps = do (traverse convertPlutusData ps) serializeData :: forall (a :: Type). ToData a => a -> Maybe CborBytes -serializeData = map (toBytes <<< cast) <<< convertPlutusData <<< toData +serializeData = map toBytes <<< convertPlutusData <<< toData diff --git a/src/Internal/Serialization/AuxiliaryData.purs b/src/Internal/Serialization/AuxiliaryData.purs index 49dd6f6c53..de2bf5873d 100644 --- a/src/Internal/Serialization/AuxiliaryData.purs +++ b/src/Internal/Serialization/AuxiliaryData.purs @@ -38,7 +38,6 @@ import Data.Traversable (for, for_, traverse) import Data.Tuple (Tuple(Tuple)) import Data.Tuple.Nested (type (/\), (/\)) import Effect (Effect) -import Untagged.Castable (cast) foreign import newAuxiliaryData :: Effect AuxiliaryData @@ -80,7 +79,7 @@ foreign import _hashAuxiliaryData hashAuxiliaryData :: T.AuxiliaryData -> Effect T.AuxiliaryDataHash hashAuxiliaryData = - map (wrap <<< unwrap <<< toBytes <<< cast <<< _hashAuxiliaryData) <<< + map (wrap <<< unwrap <<< toBytes <<< _hashAuxiliaryData) <<< convertAuxiliaryData convertAuxiliaryData :: T.AuxiliaryData -> Effect AuxiliaryData diff --git a/src/Internal/Serialization/ToBytes.purs b/src/Internal/Serialization/ToBytes.purs index 595544955c..f3721c06a7 100644 --- a/src/Internal/Serialization/ToBytes.purs +++ b/src/Internal/Serialization/ToBytes.purs @@ -27,6 +27,7 @@ import Ctl.Internal.Serialization.Types ) import Ctl.Internal.Types.ByteArray (ByteArray) import Ctl.Internal.Types.CborBytes (CborBytes(CborBytes)) +import Untagged.Castable (class Castable) import Untagged.Union (type (|+|)) type SerializationData = Address @@ -55,10 +56,11 @@ type SerializationData = Address -- NOTE returns cbor encoding for all but hash types, for which it returns raw bytes foreign import _toBytes - :: SerializationData - -> ByteArray + :: forall a. a -> ByteArray toBytes - :: SerializationData + :: forall a + . Castable a SerializationData + => a -> CborBytes toBytes = CborBytes <<< _toBytes diff --git a/src/Internal/Transaction.purs b/src/Internal/Transaction.purs index 502d68d39e..deb9d2254e 100644 --- a/src/Internal/Transaction.purs +++ b/src/Internal/Transaction.purs @@ -38,7 +38,6 @@ import Data.Show.Generic (genericShow) import Data.Traversable (traverse) import Effect (Effect) import Effect.Class (liftEffect) -import Untagged.Castable (cast) data ModifyTxError = ConvertWitnessesError @@ -69,7 +68,7 @@ setScriptDataHash costModels rs ds tx@(Transaction { body, witnessSet }) , null rs , null ds = pure tx | otherwise = do - scriptDataHash <- ScriptDataHash <<< unwrap <<< toBytes <<< cast + scriptDataHash <- ScriptDataHash <<< unwrap <<< toBytes <$> hashScriptData costModels rs (unwrap <$> ds) pure $ over Transaction _ diff --git a/src/Internal/TxOutput.purs b/src/Internal/TxOutput.purs index 69c9ff3bc9..efaba0be0e 100644 --- a/src/Internal/TxOutput.purs +++ b/src/Internal/TxOutput.purs @@ -32,7 +32,6 @@ import Ctl.Internal.Types.Transaction (TransactionInput(TransactionInput)) as Tr import Data.Maybe (Maybe, fromMaybe, isNothing) import Data.Newtype (unwrap, wrap) import Data.Traversable (traverse) -import Untagged.Castable (cast) -- | A module for helpers of the various transaction output types. @@ -115,7 +114,7 @@ datumHashToOgmiosDatumHash = byteArrayToHex <<< unwrap datumToOgmiosDatum :: Datum -> Maybe String datumToOgmiosDatum (Datum plutusData) = Serialization.convertPlutusData plutusData <#> - (cast >>> toBytes >>> unwrap >>> byteArrayToHex) + (toBytes >>> unwrap >>> byteArrayToHex) toOutputDatum :: Maybe Datum -> Maybe DataHash -> OutputDatum toOutputDatum d dh = diff --git a/src/Internal/Types/Redeemer.purs b/src/Internal/Types/Redeemer.purs index 310459000f..6b466d53f1 100644 --- a/src/Internal/Types/Redeemer.purs +++ b/src/Internal/Types/Redeemer.purs @@ -17,7 +17,6 @@ import Data.Generic.Rep (class Generic) import Data.Maybe (Maybe) import Data.Newtype (class Newtype, unwrap, wrap) import Data.Show.Generic (genericShow) -import Untagged.Castable (cast) newtype Redeemer = Redeemer PlutusData @@ -51,4 +50,4 @@ instance Show RedeemerHash where -- | This is a duplicate of `datumHash`. redeemerHash :: Redeemer -> Maybe RedeemerHash redeemerHash = - map (wrap <<< unwrap <<< toBytes <<< cast) <<< convertPlutusData <<< unwrap + map (wrap <<< unwrap <<< toBytes) <<< convertPlutusData <<< unwrap diff --git a/src/Internal/Types/VRFKeyHash.purs b/src/Internal/Types/VRFKeyHash.purs index f8c7822756..069e1009e0 100644 --- a/src/Internal/Types/VRFKeyHash.purs +++ b/src/Internal/Types/VRFKeyHash.purs @@ -15,20 +15,19 @@ import Ctl.Internal.Types.ByteArray (ByteArray, byteArrayToHex) import Data.Function (on) import Data.Maybe (Maybe) import Data.Newtype (unwrap, wrap) -import Untagged.Castable (cast) newtype VRFKeyHash = VRFKeyHash Serialization.VRFKeyHash instance Show VRFKeyHash where show (VRFKeyHash kh) = - "(VRFKeyHash " <> show (byteArrayToHex $ unwrap $ toBytes $ cast kh) <> ")" + "(VRFKeyHash " <> show (byteArrayToHex $ unwrap $ toBytes kh) <> ")" instance Eq VRFKeyHash where eq = eq `on` vrfKeyHashToBytes instance EncodeAeson VRFKeyHash where encodeAeson' (VRFKeyHash kh) = - toBytes (cast kh) # unwrap >>> byteArrayToHex >>> encodeAeson' + toBytes kh # unwrap >>> byteArrayToHex >>> encodeAeson' unVRFKeyHash :: VRFKeyHash -> Serialization.VRFKeyHash unVRFKeyHash (VRFKeyHash kh) = kh @@ -37,4 +36,4 @@ vrfKeyHashFromBytes :: ByteArray -> Maybe VRFKeyHash vrfKeyHashFromBytes = wrap >>> fromBytes >>> map VRFKeyHash vrfKeyHashToBytes :: VRFKeyHash -> ByteArray -vrfKeyHashToBytes (VRFKeyHash kh) = unwrap $ toBytes $ cast kh +vrfKeyHashToBytes (VRFKeyHash kh) = unwrap $ toBytes kh diff --git a/src/Internal/Wallet/Cip30.purs b/src/Internal/Wallet/Cip30.purs index fef7b6a165..fc08eb1c80 100644 --- a/src/Internal/Wallet/Cip30.purs +++ b/src/Internal/Wallet/Cip30.purs @@ -52,7 +52,6 @@ import Effect (Effect) import Effect.Aff (Aff) import Effect.Class (liftEffect) import Effect.Exception (error, throw) -import Untagged.Castable (cast) type DataSignature = { key :: CborBytes @@ -123,7 +122,7 @@ mkCip30WalletAff walletName enableWallet = do txToHex :: Transaction -> Aff String txToHex = liftEffect - <<< map (byteArrayToHex <<< unwrap <<< Serialization.toBytes <<< cast) + <<< map (byteArrayToHex <<< unwrap <<< Serialization.toBytes) <<< Serialization.convertTransaction getNetworkId :: Cip30Connection -> Aff Int diff --git a/src/Internal/Wallet/Cip30Mock.purs b/src/Internal/Wallet/Cip30Mock.purs index 9d1a5a75ed..7513629604 100644 --- a/src/Internal/Wallet/Cip30Mock.purs +++ b/src/Internal/Wallet/Cip30Mock.purs @@ -56,7 +56,6 @@ import Effect.Class (liftEffect) import Effect.Exception (error) import Effect.Unsafe (unsafePerformEffect) import Type.Proxy (Proxy(Proxy)) -import Untagged.Castable (cast) data WalletMock = MockFlint | MockGero | MockNami | MockLode @@ -158,7 +157,7 @@ mkCip30Mock pKey mSKey = do cslUtxos <- traverse (liftEffect <<< convertTransactionUnspentOutput) $ Map.toUnfoldable nonCollateralUtxos <#> \(input /\ output) -> TransactionUnspentOutput { input, output } - pure $ (byteArrayToHex <<< unwrap <<< toBytes <<< cast) <$> cslUtxos + pure $ (byteArrayToHex <<< unwrap <<< toBytes) <$> cslUtxos , getCollateral: fromAff do ownAddress <- (unwrap keyWallet).address config.networkId utxos <- liftMaybe (error "No UTxOs at address") =<< @@ -167,7 +166,7 @@ mkCip30Mock pKey mSKey = do cslUnspentOutput <- liftEffect $ traverse convertTransactionUnspentOutput collateralUtxos - pure $ (byteArrayToHex <<< unwrap <<< toBytes <<< cast) <$> + pure $ (byteArrayToHex <<< unwrap <<< toBytes) <$> cslUnspentOutput , getBalance: fromAff do ownAddress <- (unwrap keyWallet).address config.networkId @@ -176,17 +175,17 @@ mkCip30Mock pKey mSKey = do value <- liftEffect $ convertValue $ (foldMap (_.amount <<< unwrap) <<< Map.values) utxos - pure $ byteArrayToHex $ unwrap $ toBytes $ cast value + pure $ byteArrayToHex $ unwrap $ toBytes value , getUsedAddresses: fromAff do (unwrap keyWallet).address config.networkId <#> \address -> - [ (byteArrayToHex <<< unwrap <<< toBytes <<< cast) address ] + [ (byteArrayToHex <<< unwrap <<< toBytes) address ] , getUnusedAddresses: fromAff $ pure [] , getChangeAddress: fromAff do (unwrap keyWallet).address config.networkId <#> - (byteArrayToHex <<< unwrap <<< toBytes <<< cast) + (byteArrayToHex <<< unwrap <<< toBytes) , getRewardAddresses: fromAff do (unwrap keyWallet).address config.networkId <#> \address -> - [ (byteArrayToHex <<< unwrap <<< toBytes <<< cast) address ] + [ (byteArrayToHex <<< unwrap <<< toBytes) address ] , signTx: \str -> unsafePerformEffect $ fromAff do txBytes <- liftMaybe (error "Unable to convert CBOR") $ hexToByteArray str @@ -196,7 +195,7 @@ mkCip30Mock pKey mSKey = do $ cborBytesFromByteArray txBytes witness <- (unwrap keyWallet).signTx tx cslWitnessSet <- liftEffect $ convertWitnessSet witness - pure $ byteArrayToHex $ unwrap $ toBytes $ cast cslWitnessSet + pure $ byteArrayToHex $ unwrap $ toBytes cslWitnessSet , signData: mkFn2 \_addr msg -> unsafePerformEffect $ fromAff do msgBytes <- liftMaybe (error "Unable to convert CBOR") (hexToByteArray msg) diff --git a/test/Data.purs b/test/Data.purs index 84ba769c15..7586fb5fc0 100644 --- a/test/Data.purs +++ b/test/Data.purs @@ -56,7 +56,6 @@ import Test.Spec.Assertions (shouldEqual) import Test.Spec.QuickCheck (quickCheck) import Type.Proxy (Proxy(Proxy)) import Type.RowList (Cons, Nil) -import Untagged.Castable (cast) plutusDataAesonRoundTrip :: forall (a :: Type). ToData a => FromData a => a -> Either JsonDecodeError a @@ -568,7 +567,7 @@ testBinaryFixture value binaryFixture = do test ("Deserialization: " <> show value) do fromBytesFromData binaryFixture `shouldEqual` Just value test ("Serialization: " <> show value) do - map (toBytes <<< cast) (PDS.convertPlutusData (toData value)) + map toBytes (PDS.convertPlutusData (toData value)) `shouldEqual` Just (wrap $ hexToByteArrayUnsafe binaryFixture) diff --git a/test/Deserialization.purs b/test/Deserialization.purs index 79f5703364..29f4a46d90 100644 --- a/test/Deserialization.purs +++ b/test/Deserialization.purs @@ -83,7 +83,6 @@ import Test.Ctl.Fixtures ) import Test.Ctl.Utils (errMaybe) import Test.Spec.Assertions (expectError, shouldEqual, shouldSatisfy) -import Untagged.Castable (cast) suite :: TestPlanM (Aff Unit) Unit suite = do @@ -106,7 +105,7 @@ suite = do cslPd <- errMaybe "Failed to convert from CTL PlutusData to CSL PlutusData" $ SPD.convertPlutusData ctlPd - let pdBytes = Serialization.toBytes $ cast cslPd + let pdBytes = Serialization.toBytes cslPd cslPd' <- errMaybe "Failed to fromBytes PlutusData" $ fromBytes pdBytes ctlPd' <- @@ -227,7 +226,7 @@ suite = do ws1 <- liftEffect $ SW.convertWitnessSet ws0 ws2 <- errMaybe "Failed deserialization" $ convertWitnessSet ws1 ws0 `shouldEqual` ws2 -- value representation - let wsBytes = unwrap $ Serialization.toBytes $ cast ws1 + let wsBytes = unwrap $ Serialization.toBytes ws1 wsBytes `shouldEqual` fixture -- byte representation test "fixture #1" $ witnessSetRoundTrip witnessSetFixture1 test "fixture #2" $ witnessSetRoundTrip witnessSetFixture2 @@ -258,7 +257,7 @@ testNativeScript input = do purescript to handle it correctly. -} - let bytes = Serialization.toBytes $ cast serialized + let bytes = Serialization.toBytes serialized res <- errMaybe "Failed deserialization" $ fromBytes bytes res' <- errMaybe "Failed deserialization" $ NSD.convertNativeScript res res' `shouldEqual` input diff --git a/test/Serialization.purs b/test/Serialization.purs index 4020370bd5..91dd1cc6d7 100644 --- a/test/Serialization.purs +++ b/test/Serialization.purs @@ -48,7 +48,6 @@ import Test.Ctl.Fixtures ) import Test.Ctl.Utils (errMaybe) import Test.Spec.Assertions (shouldEqual, shouldSatisfy) -import Untagged.Castable (cast) suite :: TestPlanM (Aff Unit) Unit suite = do @@ -112,11 +111,11 @@ suite = do datum = PD.Integer (BigInt.fromInt 0) datum' <- errMaybe "Cannot convertPlutusData" $ convertPlutusData datum - let bytes = toBytes $ cast datum' + let bytes = toBytes datum' byteArrayToHex (unwrap bytes) `shouldEqual` "00" test "TransactionOutput serialization" $ liftEffect do txo <- convertTxOutput txOutputFixture1 - let bytes = toBytes $ cast txo + let bytes = toBytes txo byteArrayToHex (unwrap bytes) `shouldEqual` txOutputBinaryFixture1 test "Transaction serialization #1" $ serializeTX txFixture1 txBinaryFixture1 @@ -158,13 +157,13 @@ serializeTX :: Transaction -> String -> Aff Unit serializeTX tx fixture = liftEffect $ do cslTX <- TS.convertTransaction $ tx - let bytes = toBytes $ cast cslTX + let bytes = toBytes cslTX byteArrayToHex (unwrap bytes) `shouldEqual` fixture txSerializedRoundtrip :: Transaction -> Aff Unit txSerializedRoundtrip tx = do cslTX <- liftEffect $ TS.convertTransaction tx - let serialized = toBytes $ cast cslTX + let serialized = toBytes cslTX deserialized <- errMaybe "Cannot deserialize bytes" $ fromBytes serialized expected <- errMaybe "Cannot convert TX from CSL to CTL" $ hush $ TD.convertTransaction deserialized diff --git a/test/Serialization/Hash.purs b/test/Serialization/Hash.purs index 03c920f36e..05638f255b 100644 --- a/test/Serialization/Hash.purs +++ b/test/Serialization/Hash.purs @@ -22,7 +22,6 @@ import Data.Newtype (unwrap) import Data.Unit (Unit) import Effect.Aff (Aff) import Test.Ctl.Utils (assertTrue, errMaybe) -import Untagged.Castable (cast) pkhBech32 :: Bech32String pkhBech32 = "addr_vkh1zuctrdcq6ctd29242w8g84nlz0q38t2lnv3zzfcrfqktx0c9tzp" @@ -43,7 +42,7 @@ suite = do let pkhB32 = ed25519KeyHashToBech32Unsafe "addr_vkh" pkh mPkhB32 = ed25519KeyHashToBech32 "addr_vkh" pkh - pkhBts = toBytes $ cast pkh + pkhBts = toBytes pkh -- TODO: use fromBytes instead? pkh2 = ed25519KeyHashFromBytes $ unwrap pkhBts @@ -73,7 +72,7 @@ suite = do let scrhB32 = scriptHashToBech32Unsafe "stake_vkh" scrh mScrhB32 = scriptHashToBech32 "stake_vkh" scrh - scrhBts = toBytes $ cast scrh + scrhBts = toBytes scrh -- TODO: use fromBytes instead? scrhFromBytes = scriptHashFromBytes $ unwrap scrhBts scrhFromBech = scriptHashFromBech32 scrhB32 From 6588226bbff07e9041161b230412afa0ef2c3ecc Mon Sep 17 00:00:00 2001 From: Calum Sieppert Date: Mon, 5 Dec 2022 11:48:45 -0700 Subject: [PATCH 046/373] Fix type error after merge --- test/Wallet/Cip30/SignData.purs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/test/Wallet/Cip30/SignData.purs b/test/Wallet/Cip30/SignData.purs index a4c2933557..99e629d6d1 100644 --- a/test/Wallet/Cip30/SignData.purs +++ b/test/Wallet/Cip30/SignData.purs @@ -128,7 +128,7 @@ checkCip30SignDataResponse address { key, signature } = do checkVerification coseSign1 coseKey = do publicKey <- errMaybe "COSE_Key's x (-2) header must be set to public key bytes" - (getCoseKeyHeaderX coseKey >>= (fromBytes <<< unwrap)) + (getCoseKeyHeaderX coseKey >>= (fromBytes <<< wrap <<< unwrap)) sigStructBytes <- getSignedData coseSign1 assertTrue "Signature verification failed" =<< verifySignature coseSign1 publicKey sigStructBytes From a123fe7232a1e87165f7fe6bb4d3186e24c4f1d9 Mon Sep 17 00:00:00 2001 From: Calum Sieppert Date: Mon, 5 Dec 2022 11:54:55 -0700 Subject: [PATCH 047/373] Make consistent which types work with `from/toBytes` --- src/Internal/Deserialization/FromBytes.purs | 36 +++++++++++++++++---- src/Internal/Serialization/ToBytes.purs | 2 ++ 2 files changed, 31 insertions(+), 7 deletions(-) diff --git a/src/Internal/Deserialization/FromBytes.purs b/src/Internal/Deserialization/FromBytes.purs index 943b77d9d6..39d57623cc 100644 --- a/src/Internal/Deserialization/FromBytes.purs +++ b/src/Internal/Deserialization/FromBytes.purs @@ -10,7 +10,8 @@ import Prelude import Ctl.Internal.Deserialization.Error (FromBytesError, fromBytesErrorHelper) import Ctl.Internal.Error (E) import Ctl.Internal.FfiHelpers (ErrorFfiHelper) -import Ctl.Internal.Serialization.Hash (VRFKeyHash) +import Ctl.Internal.Serialization.Address (Address) +import Ctl.Internal.Serialization.Hash (Ed25519KeyHash, ScriptHash, VRFKeyHash) import Ctl.Internal.Serialization.Types ( AuxiliaryDataHash , DataHash @@ -22,9 +23,12 @@ import Ctl.Internal.Serialization.Types , PlutusData , PoolMetadataHash , PublicKey + , Redeemers , ScriptDataHash , Transaction + , TransactionBody , TransactionHash + , TransactionOutput , TransactionUnspentOutput , TransactionWitnessSet , Value @@ -42,12 +46,21 @@ import Type.Row (type (+)) class FromBytes a where fromBytes' :: forall (r :: Row Type). ByteArray -> E (FromBytesError + r) a +instance FromBytes Address where + fromBytes' = _fromBytes "Address" fromBytesErrorHelper + instance FromBytes AuxiliaryDataHash where fromBytes' = _fromBytes "AuxiliaryDataHash" fromBytesErrorHelper instance FromBytes DataHash where fromBytes' = _fromBytes "DataHash" fromBytesErrorHelper +instance FromBytes Ed25519KeyHash where + fromBytes' = _fromBytes "Ed25519KeyHash" fromBytesErrorHelper + +instance FromBytes Ed25519Signature where + fromBytes' = _fromBytes "Ed25519Signature" fromBytesErrorHelper + instance FromBytes GenesisDelegateHash where fromBytes' = _fromBytes "GenesisDelegateHash" fromBytesErrorHelper @@ -66,15 +79,30 @@ instance FromBytes PlutusData where instance FromBytes PoolMetadataHash where fromBytes' = _fromBytes "PoolMetadataHash" fromBytesErrorHelper +instance FromBytes PublicKey where + fromBytes' = _fromBytes "PublicKey" fromBytesErrorHelper + +instance FromBytes Redeemers where + fromBytes' = _fromBytes "Redeemers" fromBytesErrorHelper + instance FromBytes ScriptDataHash where fromBytes' = _fromBytes "ScriptDataHash" fromBytesErrorHelper +instance FromBytes ScriptHash where + fromBytes' = _fromBytes "ScriptHash" fromBytesErrorHelper + instance FromBytes Transaction where fromBytes' = _fromBytes "Transaction" fromBytesErrorHelper +instance FromBytes TransactionBody where + fromBytes' = _fromBytes "TransactionBody" fromBytesErrorHelper + instance FromBytes TransactionHash where fromBytes' = _fromBytes "TransactionHash" fromBytesErrorHelper +instance FromBytes TransactionOutput where + fromBytes' = _fromBytes "TransactionOutput" fromBytesErrorHelper + instance FromBytes TransactionUnspentOutput where fromBytes' = _fromBytes "TransactionUnspentOutput" fromBytesErrorHelper @@ -84,12 +112,6 @@ instance FromBytes TransactionWitnessSet where instance FromBytes Value where fromBytes' = _fromBytes "Value" fromBytesErrorHelper -instance FromBytes PublicKey where - fromBytes' = _fromBytes "PublicKey" fromBytesErrorHelper - -instance FromBytes Ed25519Signature where - fromBytes' = _fromBytes "Ed25519Signature" fromBytesErrorHelper - instance FromBytes VRFKeyHash where fromBytes' = _fromBytes "VRFKeyHash" fromBytesErrorHelper diff --git a/src/Internal/Serialization/ToBytes.purs b/src/Internal/Serialization/ToBytes.purs index f3721c06a7..e6244e1147 100644 --- a/src/Internal/Serialization/ToBytes.purs +++ b/src/Internal/Serialization/ToBytes.purs @@ -12,6 +12,7 @@ import Ctl.Internal.Serialization.Types , Ed25519Signature , GenesisDelegateHash , GenesisHash + , Mint , NativeScript , PlutusData , PoolMetadataHash @@ -37,6 +38,7 @@ type SerializationData = Address |+| Ed25519Signature |+| GenesisDelegateHash |+| GenesisHash + |+| Mint |+| NativeScript |+| PlutusData |+| PoolMetadataHash From 2c5995581664b155d6d4a43e8e60089e391ebe96 Mon Sep 17 00:00:00 2001 From: Calum Sieppert Date: Mon, 5 Dec 2022 12:23:12 -0700 Subject: [PATCH 048/373] Remove `FromBytes` instance for `PublicKey` --- src/Internal/Deserialization/FromBytes.purs | 3 --- 1 file changed, 3 deletions(-) diff --git a/src/Internal/Deserialization/FromBytes.purs b/src/Internal/Deserialization/FromBytes.purs index 39d57623cc..3c465eb0b4 100644 --- a/src/Internal/Deserialization/FromBytes.purs +++ b/src/Internal/Deserialization/FromBytes.purs @@ -79,9 +79,6 @@ instance FromBytes PlutusData where instance FromBytes PoolMetadataHash where fromBytes' = _fromBytes "PoolMetadataHash" fromBytesErrorHelper -instance FromBytes PublicKey where - fromBytes' = _fromBytes "PublicKey" fromBytesErrorHelper - instance FromBytes Redeemers where fromBytes' = _fromBytes "Redeemers" fromBytesErrorHelper From 73dd6732dcd273c35c8225cfd9d3c5e9c855601e Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Mon, 5 Dec 2022 21:42:33 +0000 Subject: [PATCH 049/373] Add docs about issue --- src/Contract/Transaction.purs | 6 ++++++ src/Internal/QueryM/Kupo.purs | 2 ++ 2 files changed, 8 insertions(+) diff --git a/src/Contract/Transaction.purs b/src/Contract/Transaction.purs index dc0c61d744..7d25bfb157 100644 --- a/src/Contract/Transaction.purs +++ b/src/Contract/Transaction.purs @@ -544,6 +544,8 @@ getTxByHash = wrapContract <<< QueryM.getTxByHash <<< unwrap -- | Wait until a transaction with given hash is confirmed. -- | Use `awaitTxConfirmedWithTimeout` if you want to limit the time of waiting. +-- | Will fail to confirm if the transaction includes no outputs +-- | https://github.com/Plutonomicon/cardano-transaction-lib/issues/1293 awaitTxConfirmed :: forall (r :: Row Type) . TransactionHash @@ -552,6 +554,8 @@ awaitTxConfirmed = wrapContract <<< AwaitTx.awaitTxConfirmed <<< unwrap -- | Same as `awaitTxConfirmed`, but allows to specify a timeout in seconds for waiting. -- | Throws an exception on timeout. +-- | Will fail to confirm if the transaction includes no outputs +-- | https://github.com/Plutonomicon/cardano-transaction-lib/issues/1293 awaitTxConfirmedWithTimeout :: forall (r :: Row Type) . Seconds @@ -563,6 +567,8 @@ awaitTxConfirmedWithTimeout timeout = wrapContract -- | Same as `awaitTxConfirmed`, but allows to specify a timeout in slots for waiting. -- | Throws an exception on timeout. +-- | Will fail to confirm if the transaction includes no outputs +-- | https://github.com/Plutonomicon/cardano-transaction-lib/issues/1293 awaitTxConfirmedWithTimeoutSlots :: forall (r :: Row Type) . Int diff --git a/src/Internal/QueryM/Kupo.purs b/src/Internal/QueryM/Kupo.purs index ce3fd48a29..8c17bc7a31 100644 --- a/src/Internal/QueryM/Kupo.purs +++ b/src/Internal/QueryM/Kupo.purs @@ -148,6 +148,8 @@ getScriptsByHashes = <<< map (Map.catMaybes <<< Map.fromFoldable) <<< parTraverse (\sh -> Tuple sh <$> ExceptT (getScriptByHash sh)) +-- FIXME: This can only confirm transactions with at least one output. +-- https://github.com/Plutonomicon/cardano-transaction-lib/issues/1293 isTxConfirmed :: TransactionHash -> QueryM (Either ClientError Boolean) isTxConfirmed (TransactionHash txHash) = do let endpoint = "/matches/*@" <> byteArrayToHex txHash From cabb583f876561a4b8736d526b927085615d0c5b Mon Sep 17 00:00:00 2001 From: Calum Sieppert Date: Mon, 5 Dec 2022 16:58:06 -0700 Subject: [PATCH 050/373] Revert "Remove `FromBytes` instance for `PublicKey`" This reverts commit 2c5995581664b155d6d4a43e8e60089e391ebe96. --- src/Internal/Deserialization/FromBytes.purs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/src/Internal/Deserialization/FromBytes.purs b/src/Internal/Deserialization/FromBytes.purs index 3c465eb0b4..39d57623cc 100644 --- a/src/Internal/Deserialization/FromBytes.purs +++ b/src/Internal/Deserialization/FromBytes.purs @@ -79,6 +79,9 @@ instance FromBytes PlutusData where instance FromBytes PoolMetadataHash where fromBytes' = _fromBytes "PoolMetadataHash" fromBytesErrorHelper +instance FromBytes PublicKey where + fromBytes' = _fromBytes "PublicKey" fromBytesErrorHelper + instance FromBytes Redeemers where fromBytes' = _fromBytes "Redeemers" fromBytesErrorHelper From 06b893d5e1c242d4d8e771a59fd392ed2512777f Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Tue, 6 Dec 2022 11:50:41 +0000 Subject: [PATCH 051/373] Update comment --- src/Contract/Transaction.purs | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/src/Contract/Transaction.purs b/src/Contract/Transaction.purs index 2405fe368a..5368047c0f 100644 --- a/src/Contract/Transaction.purs +++ b/src/Contract/Transaction.purs @@ -507,7 +507,8 @@ getTxByHash th = do -- | Wait until a transaction with given hash is confirmed. -- | Use `awaitTxConfirmedWithTimeout` if you want to limit the time of waiting. --- | Will fail to confirm if the transaction includes no outputs +-- | Will fail to confirm if the transaction includes no outputs on the +-- | CtlBackend -- | https://github.com/Plutonomicon/cardano-transaction-lib/issues/1293 awaitTxConfirmed :: TransactionHash @@ -516,7 +517,8 @@ awaitTxConfirmed = Contract.awaitTxConfirmed <<< unwrap -- | Same as `awaitTxConfirmed`, but allows to specify a timeout in seconds for waiting. -- | Throws an exception on timeout. --- | Will fail to confirm if the transaction includes no outputs +-- | Will fail to confirm if the transaction includes no outputs on the +-- | CtlBackend -- | https://github.com/Plutonomicon/cardano-transaction-lib/issues/1293 awaitTxConfirmedWithTimeout :: Seconds @@ -527,7 +529,8 @@ awaitTxConfirmedWithTimeout timeout = -- | Same as `awaitTxConfirmed`, but allows to specify a timeout in slots for waiting. -- | Throws an exception on timeout. --- | Will fail to confirm if the transaction includes no outputs +-- | Will fail to confirm if the transaction includes no outputs on the +-- | CtlBackend -- | https://github.com/Plutonomicon/cardano-transaction-lib/issues/1293 awaitTxConfirmedWithTimeoutSlots :: Int From d3ae0e0ffcf304712bff615da437f139a31790d9 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Tue, 6 Dec 2022 11:59:01 +0000 Subject: [PATCH 052/373] Fix SignData example --- examples/SignData.purs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/examples/SignData.purs b/examples/SignData.purs index 393c01c12c..cec35b1d60 100644 --- a/examples/SignData.purs +++ b/examples/SignData.purs @@ -2,7 +2,7 @@ module Ctl.Examples.SignData (main, example, contract) where import Contract.Prelude -import Contract.Config (ConfigParams, testnetNamiConfig) +import Contract.Config (ContractParams, testnetNamiConfig) import Contract.Log (logInfo') import Contract.Monad (Contract, launchAff_, liftedM, runContract) import Contract.Prim.ByteArray (RawBytes, rawBytesFromAscii) @@ -16,10 +16,10 @@ import Test.Ctl.Wallet.Cip30.SignData (checkCip30SignDataResponse) main :: Effect Unit main = example testnetNamiConfig -example :: ConfigParams () -> Effect Unit +example :: ContractParams -> Effect Unit example = launchAff_ <<< flip runContract contract -contract :: Contract () Unit +contract :: Contract Unit contract = do logInfo' "Running Examples.SignData" @@ -35,7 +35,7 @@ contract = do payload :: RawBytes payload = unsafePartial fromJust $ rawBytesFromAscii "Hello world!" - testSignDataWithAddress :: String -> Address -> Contract () Unit + testSignDataWithAddress :: String -> Address -> Contract Unit testSignDataWithAddress addressLabel address = do dataSignature <- signData address payload From cc00c9caaf94c90a6af5a41c93fd692412db344c Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Tue, 6 Dec 2022 15:34:29 +0000 Subject: [PATCH 053/373] Move Logger out of QueryM. Remove hooks from QueryM. Move mkWalletFromSpec into Ctl.Internal.Wallet.Spec --- src/Contract/Config.purs | 4 +- src/Internal/Contract/Hooks.purs | 23 ++++++ src/Internal/Contract/Monad.purs | 16 ++-- src/Internal/{QueryM => }/Logging.purs | 26 ++++++- src/Internal/Plutip/Server.purs | 6 +- src/Internal/Plutip/Types.purs | 2 +- src/Internal/QueryM.purs | 89 ++--------------------- src/Internal/QueryM/Config.purs | 3 +- src/Internal/Test/E2E/Feedback/Hooks.purs | 2 +- src/Internal/Test/E2E/Runner.purs | 3 +- src/Internal/Wallet/Spec.purs | 40 ++++++++++ 11 files changed, 105 insertions(+), 109 deletions(-) create mode 100644 src/Internal/Contract/Hooks.purs rename src/Internal/{QueryM => }/Logging.purs (73%) diff --git a/src/Contract/Config.purs b/src/Contract/Config.purs index 94fe255646..9643ec2b30 100644 --- a/src/Contract/Config.purs +++ b/src/Contract/Config.purs @@ -27,14 +27,14 @@ module Contract.Config import Prelude import Contract.Address (NetworkId(MainnetId, TestnetId)) +import Ctl.Internal.Contract.Hooks (Hooks, emptyHooks) as X +import Ctl.Internal.Contract.Hooks (emptyHooks) import Ctl.Internal.Contract.Monad (ContractParams) import Ctl.Internal.Contract.QueryBackend ( QueryBackendParams(CtlBackendParams, BlockfrostBackendParams) , mkSingletonBackendParams ) import Ctl.Internal.Deserialization.Keys (privateKeyFromBytes) -import Ctl.Internal.QueryM (emptyHooks) -import Ctl.Internal.QueryM (emptyHooks) as X import Ctl.Internal.QueryM.ServerConfig ( Host , ServerConfig diff --git a/src/Internal/Contract/Hooks.purs b/src/Internal/Contract/Hooks.purs new file mode 100644 index 0000000000..a6512af72d --- /dev/null +++ b/src/Internal/Contract/Hooks.purs @@ -0,0 +1,23 @@ +module Ctl.Internal.Contract.Hooks (Hooks, emptyHooks) where + +import Prelude + +import Data.Maybe (Maybe(Nothing)) +import Effect (Effect) +import Effect.Exception (Error) + +type Hooks = + { beforeSign :: Maybe (Effect Unit) + , beforeInit :: Maybe (Effect Unit) + , onSuccess :: Maybe (Effect Unit) + , onError :: Maybe (Error -> Effect Unit) + } + +emptyHooks :: Hooks +emptyHooks = + { beforeSign: Nothing + , beforeInit: Nothing + , onSuccess: Nothing + , onError: Nothing + } + diff --git a/src/Internal/Contract/Monad.purs b/src/Internal/Contract/Monad.purs index 3dff7b529b..1d89e14d91 100644 --- a/src/Internal/Contract/Monad.purs +++ b/src/Internal/Contract/Monad.purs @@ -35,6 +35,7 @@ import Control.Parallel , sequential ) import Control.Plus (class Plus) +import Ctl.Internal.Contract.Hooks (Hooks) import Ctl.Internal.Contract.QueryBackend ( CtlBackend , QueryBackend(BlockfrostBackend, CtlBackend) @@ -46,22 +47,19 @@ import Ctl.Internal.Contract.QueryBackend ) import Ctl.Internal.Helpers (liftM, liftedM, logWithLevel) import Ctl.Internal.JsWebSocket (_wsClose, _wsFinalize) +import Ctl.Internal.Logging (Logger, mkLogger, setupLogs) import Ctl.Internal.QueryM - ( Hooks - , Logger - , QueryEnv + ( QueryEnv , QueryM , WebSocket , getEraSummariesAff , getProtocolParametersAff , getSystemStartAff , mkDatumCacheWebSocketAff - , mkLogger , mkOgmiosWebSocketAff - , mkWalletBySpec , underlyingWebSocket ) -import Ctl.Internal.QueryM.Logging (setupLogs) +-- TOD Move/translate these types into Cardano import Ctl.Internal.QueryM.Ogmios ( ProtocolParameters , RelativeTime @@ -73,7 +71,7 @@ import Ctl.Internal.Serialization.Address (NetworkId, Slot) import Ctl.Internal.Types.UsedTxOuts (UsedTxOuts, newUsedTxOuts) import Ctl.Internal.Wallet (Wallet) import Ctl.Internal.Wallet (getNetworkId) as Wallet -import Ctl.Internal.Wallet.Spec (WalletSpec) +import Ctl.Internal.Wallet.Spec (WalletSpec, mkWalletBySpec) import Data.Either (Either(Left, Right)) import Data.Foldable (maximumBy) import Data.Function (on) @@ -238,7 +236,6 @@ mkContractEnv params = do , hooks: params.hooks } --- TODO Move CtlServer to a backend? Wouldn't make sense as a 'main' backend though buildBackend :: Logger -> QueryBackends QueryBackendParams @@ -366,7 +363,6 @@ withContractEnv params action = do -- | environment (see `withContractEnv`) type ContractParams = { backendParams :: QueryBackends QueryBackendParams - -- TODO: Move CtlServer to a backend? , ctlServerConfig :: Maybe ServerConfig , networkId :: NetworkId , logLevel :: LogLevel @@ -407,14 +403,12 @@ mkQueryEnv contractEnv ctlBackend = , walletSpec: contractEnv.walletSpec , customLogger: contractEnv.customLogger , suppressLogs: contractEnv.suppressLogs - , hooks: contractEnv.hooks } , runtime: { ogmiosWs: ctlBackend.ogmios.ws , datumCacheWs: ctlBackend.odc.ws , wallet: contractEnv.wallet , usedTxOuts: contractEnv.usedTxOuts - -- TODO: Make queryM use the new constants , pparams: contractEnv.ledgerConstants.pparams } , extraConfig: {} diff --git a/src/Internal/QueryM/Logging.purs b/src/Internal/Logging.purs similarity index 73% rename from src/Internal/QueryM/Logging.purs rename to src/Internal/Logging.purs index 726f1d917f..787d526f6c 100644 --- a/src/Internal/QueryM/Logging.purs +++ b/src/Internal/Logging.purs @@ -1,21 +1,39 @@ -module Ctl.Internal.QueryM.Logging +module Ctl.Internal.Logging ( setupLogs + , mkLogger + , Logger ) where import Prelude -import Ctl.Internal.QueryM (Logger, mkLogger) +import Ctl.Internal.Helpers (logString) +import Data.JSDate (now) import Data.List (List(Cons, Nil)) import Data.List as List import Data.Log.Level (LogLevel) import Data.Log.Message (Message) -import Data.Maybe (Maybe(Just)) +import Data.Map as Map +import Data.Maybe (Maybe(Just, Nothing)) import Data.Traversable (for_) import Effect (Effect) -import Effect.Aff (Aff) +import Effect.Aff (Aff, launchAff_) import Effect.Class (liftEffect) import Effect.Ref as Ref +type Logger = LogLevel -> String -> Effect Unit + +mkLogger + :: LogLevel + -> Maybe (LogLevel -> Message -> Aff Unit) + -> Logger +mkLogger logLevel mbCustomLogger level message = + case mbCustomLogger of + Nothing -> logString logLevel level message + Just logger -> liftEffect do + timestamp <- now + launchAff_ $ logger logLevel + { level, message, tags: Map.empty, timestamp } + -- | Setup internal machinery for log suppression. setupLogs :: LogLevel diff --git a/src/Internal/Plutip/Server.purs b/src/Internal/Plutip/Server.purs index f671a73f13..d3db78769e 100644 --- a/src/Internal/Plutip/Server.purs +++ b/src/Internal/Plutip/Server.purs @@ -31,6 +31,7 @@ import Control.Monad.Error.Class (liftEither) import Control.Monad.State (State, execState, modify_) import Control.Monad.Trans.Class (lift) import Control.Monad.Writer (censor, execWriterT, tell) +import Ctl.Internal.Contract.Hooks (emptyHooks) import Ctl.Internal.Contract.Monad ( buildBackend , getLedgerConstants @@ -41,6 +42,7 @@ import Ctl.Internal.Contract.QueryBackend , mkSingletonBackendParams ) import Ctl.Internal.Helpers ((<>)) +import Ctl.Internal.Logging (Logger, mkLogger, setupLogs) import Ctl.Internal.Plutip.PortCheck (isPortAvailable) import Ctl.Internal.Plutip.Spawn ( ManagedProcess @@ -76,11 +78,7 @@ import Ctl.Internal.Plutip.UtxoDistribution ) import Ctl.Internal.QueryM ( ClientError(ClientDecodeJsonError, ClientHttpError) - , Logger - , emptyHooks - , mkLogger ) -import Ctl.Internal.QueryM.Logging (setupLogs) import Ctl.Internal.QueryM.UniqueId (uniqueId) import Ctl.Internal.Test.TestPlanM (TestPlanM) import Ctl.Internal.Types.UsedTxOuts (newUsedTxOuts) diff --git a/src/Internal/Plutip/Types.purs b/src/Internal/Plutip/Types.purs index 23f07f567c..fd4313444d 100644 --- a/src/Internal/Plutip/Types.purs +++ b/src/Internal/Plutip/Types.purs @@ -34,8 +34,8 @@ import Aeson , toStringifiedNumbersJson , (.:) ) +import Ctl.Internal.Contract.Hooks (Hooks) import Ctl.Internal.Deserialization.Keys (privateKeyFromBytes) -import Ctl.Internal.QueryM (Hooks) import Ctl.Internal.QueryM.ServerConfig (ServerConfig) import Ctl.Internal.Serialization.Types (PrivateKey) import Ctl.Internal.Types.ByteArray (hexToByteArray) diff --git a/src/Internal/QueryM.purs b/src/Internal/QueryM.purs index 90fc8c3d67..0595164787 100644 --- a/src/Internal/QueryM.purs +++ b/src/Internal/QueryM.purs @@ -14,7 +14,6 @@ module Ctl.Internal.QueryM , DatumCacheWebSocket , DefaultQueryEnv , ListenerSet - , Logger , OgmiosListeners , OgmiosWebSocket , QueryConfig @@ -25,7 +24,6 @@ module Ctl.Internal.QueryM , QueryRuntime , SubmitTxListenerSet , WebSocket(WebSocket) - , Hooks , allowError , evaluateTxOgmios , getChainTip @@ -39,7 +37,6 @@ module Ctl.Internal.QueryM , mkDatumCacheWebSocketAff , mkDatumCacheRequest , mkListenerSet - , mkLogger , defaultMessageListener , mkOgmiosRequest , mkOgmiosRequestAff @@ -47,12 +44,9 @@ module Ctl.Internal.QueryM , mkQueryRuntime , mkRequest , mkRequestAff - -- TODO Move mkWalletBySpec into Contract once import cycles are resolved - , mkWalletBySpec , scriptToAeson , submitTxOgmios , underlyingWebSocket - , emptyHooks ) where import Prelude @@ -90,7 +84,7 @@ import Control.Monad.Rec.Class (class MonadRec) import Control.Parallel (class Parallel, parallel, sequential) import Control.Plus (class Plus) import Ctl.Internal.Cardano.Types.Transaction (PoolPubKeyHash) -import Ctl.Internal.Helpers (logString, logWithLevel) +import Ctl.Internal.Helpers (logWithLevel) import Ctl.Internal.JsWebSocket ( JsWebSocket , Url @@ -103,6 +97,7 @@ import Ctl.Internal.JsWebSocket , _wsFinalize , _wsSend ) +import Ctl.Internal.Logging (Logger, mkLogger) import Ctl.Internal.QueryM.DatumCacheWsp ( GetTxByHashR ) @@ -166,40 +161,16 @@ import Ctl.Internal.Types.CborBytes (CborBytes) import Ctl.Internal.Types.Chain as Chain import Ctl.Internal.Types.Scripts (PlutusScript) import Ctl.Internal.Types.UsedTxOuts (UsedTxOuts, newUsedTxOuts) -import Ctl.Internal.Wallet - ( Wallet - , WalletExtension - ( LodeWallet - , EternlWallet - , FlintWallet - , GeroWallet - , NamiWallet - ) - , mkKeyWallet - , mkWalletAff - ) +import Ctl.Internal.Wallet (Wallet) import Ctl.Internal.Wallet.Key (PrivatePaymentKey, PrivateStakeKey) -import Ctl.Internal.Wallet.KeyFile - ( privatePaymentKeyFromFile - , privateStakeKeyFromFile - ) import Ctl.Internal.Wallet.Spec - ( PrivatePaymentKeySource(PrivatePaymentKeyFile, PrivatePaymentKeyValue) - , PrivateStakeKeySource(PrivateStakeKeyFile, PrivateStakeKeyValue) - , WalletSpec - ( UseKeys - , ConnectToGero - , ConnectToNami - , ConnectToFlint - , ConnectToEternl - , ConnectToLode - ) + ( WalletSpec + , mkWalletBySpec ) import Data.Bifunctor (lmap) import Data.Either (Either(Left, Right), either, isRight) import Data.Foldable (foldl) import Data.HTTP.Method (Method(POST)) -import Data.JSDate (now) import Data.Log.Level (LogLevel(Error, Debug)) import Data.Log.Message (Message) import Data.Map as Map @@ -221,7 +192,7 @@ import Effect.Aff ) import Effect.Aff.Class (class MonadAff, liftAff) import Effect.Class (class MonadEffect, liftEffect) -import Effect.Exception (Error, error, throw, try) +import Effect.Exception (Error, error, throw) import Effect.Ref (Ref) import Effect.Ref as Ref @@ -244,21 +215,6 @@ type ClusterSetup = } } -type Hooks = - { beforeSign :: Maybe (Effect Unit) - , beforeInit :: Maybe (Effect Unit) - , onSuccess :: Maybe (Effect Unit) - , onError :: Maybe (Error -> Effect Unit) - } - -emptyHooks :: Hooks -emptyHooks = - { beforeSign: Nothing - , beforeInit: Nothing - , onSuccess: Nothing - , onError: Nothing - } - -- | `QueryConfig` contains a complete specification on how to initialize a -- | `QueryM` environment. -- | It includes: @@ -277,7 +233,6 @@ type QueryConfig = , walletSpec :: Maybe WalletSpec , customLogger :: Maybe (LogLevel -> Message -> Aff Unit) , suppressLogs :: Boolean - , hooks :: Hooks } -- | Reusable part of `QueryRuntime` that can be shared between many `QueryM` @@ -368,7 +323,6 @@ mkQueryRuntime :: QueryConfig -> Aff QueryRuntime mkQueryRuntime config = do - for_ config.hooks.beforeInit (void <<< liftEffect <<< try) usedTxOuts <- newUsedTxOuts datumCacheWsRef <- liftEffect $ Ref.new Nothing QueryRuntimeModel datumCacheWs (ogmiosWs /\ pparams) wallet <- sequential $ @@ -393,23 +347,6 @@ mkQueryRuntime config = do where logger = mkLogger config.logLevel config.customLogger -mkWalletBySpec :: NetworkId -> WalletSpec -> Aff Wallet -mkWalletBySpec networkId = case _ of - UseKeys paymentKeySpec mbStakeKeySpec -> do - privatePaymentKey <- case paymentKeySpec of - PrivatePaymentKeyFile filePath -> - privatePaymentKeyFromFile filePath - PrivatePaymentKeyValue key -> pure key - mbPrivateStakeKey <- for mbStakeKeySpec case _ of - PrivateStakeKeyFile filePath -> privateStakeKeyFromFile filePath - PrivateStakeKeyValue key -> pure key - pure $ mkKeyWallet networkId privatePaymentKey mbPrivateStakeKey - ConnectToNami -> mkWalletAff NamiWallet - ConnectToGero -> mkWalletAff GeroWallet - ConnectToFlint -> mkWalletAff FlintWallet - ConnectToEternl -> mkWalletAff EternlWallet - ConnectToLode -> mkWalletAff LodeWallet - getProtocolParametersAff :: OgmiosWebSocket -> (LogLevel -> String -> Effect Unit) @@ -1008,20 +945,6 @@ mkRequest listeners' ws jsonWspCall getLs inp = do logger <- getLogger liftAff $ mkRequestAff listeners' ws logger jsonWspCall getLs inp -type Logger = LogLevel -> String -> Effect Unit - -mkLogger - :: LogLevel - -> Maybe (LogLevel -> Message -> Aff Unit) - -> Logger -mkLogger logLevel mbCustomLogger level message = - case mbCustomLogger of - Nothing -> logString logLevel level message - Just logger -> liftEffect do - timestamp <- now - launchAff_ $ logger logLevel - { level, message, tags: Map.empty, timestamp } - getLogger :: QueryM Logger getLogger = do logLevel <- asks $ _.config >>> _.logLevel diff --git a/src/Internal/QueryM/Config.purs b/src/Internal/QueryM/Config.purs index 531441e216..b2332d5f42 100644 --- a/src/Internal/QueryM/Config.purs +++ b/src/Internal/QueryM/Config.purs @@ -3,7 +3,7 @@ module Ctl.Internal.QueryM.Config , testnetQueryConfig ) where -import Ctl.Internal.QueryM (QueryConfig, emptyHooks) +import Ctl.Internal.QueryM (QueryConfig) import Ctl.Internal.QueryM.ServerConfig ( defaultDatumCacheWsConfig , defaultKupoServerConfig @@ -25,7 +25,6 @@ testnetTraceQueryConfig = , walletSpec: Nothing , customLogger: Nothing , suppressLogs: false - , hooks: emptyHooks } testnetQueryConfig :: QueryConfig diff --git a/src/Internal/Test/E2E/Feedback/Hooks.purs b/src/Internal/Test/E2E/Feedback/Hooks.purs index ce78a0a114..3ba01fb576 100644 --- a/src/Internal/Test/E2E/Feedback/Hooks.purs +++ b/src/Internal/Test/E2E/Feedback/Hooks.purs @@ -5,7 +5,7 @@ module Ctl.Internal.Test.E2E.Feedback.Hooks import Prelude -import Ctl.Internal.QueryM (Hooks) +import Ctl.Internal.Contract.Hooks (Hooks) import Ctl.Internal.Test.E2E.Feedback ( BrowserEvent(Sign, ConfirmAccess, Success, Failure) ) diff --git a/src/Internal/Test/E2E/Runner.purs b/src/Internal/Test/E2E/Runner.purs index 990103b3f0..391bbacac1 100644 --- a/src/Internal/Test/E2E/Runner.purs +++ b/src/Internal/Test/E2E/Runner.purs @@ -12,6 +12,7 @@ import Affjax.ResponseFormat as Affjax.ResponseFormat import Control.Alt ((<|>)) import Control.Monad.Error.Class (liftMaybe) import Control.Promise (Promise, toAffE) +import Ctl.Internal.Contract.Hooks (emptyHooks) import Ctl.Internal.Contract.QueryBackend ( QueryBackend(CtlBackend) , defaultBackend @@ -21,7 +22,7 @@ import Ctl.Internal.Helpers (liftedM, (<>)) import Ctl.Internal.Plutip.Server (withPlutipContractEnv) import Ctl.Internal.Plutip.Types (PlutipConfig) import Ctl.Internal.Plutip.UtxoDistribution (withStakeKey) -import Ctl.Internal.QueryM (ClusterSetup, emptyHooks) +import Ctl.Internal.QueryM (ClusterSetup) import Ctl.Internal.Test.E2E.Browser (withBrowser) import Ctl.Internal.Test.E2E.Feedback ( BrowserEvent(ConfirmAccess, Sign, Success, Failure) diff --git a/src/Internal/Wallet/Spec.purs b/src/Internal/Wallet/Spec.purs index b064bf637b..8f4584f2b7 100644 --- a/src/Internal/Wallet/Spec.purs +++ b/src/Internal/Wallet/Spec.purs @@ -9,10 +9,32 @@ module Ctl.Internal.Wallet.Spec ) , PrivateStakeKeySource(PrivateStakeKeyFile, PrivateStakeKeyValue) , PrivatePaymentKeySource(PrivatePaymentKeyFile, PrivatePaymentKeyValue) + , mkWalletBySpec ) where +import Prelude + +import Ctl.Internal.Serialization.Address (NetworkId) +import Ctl.Internal.Wallet + ( Wallet + , WalletExtension + ( NamiWallet + , GeroWallet + , FlintWallet + , EternlWallet + , LodeWallet + ) + , mkKeyWallet + , mkWalletAff + ) import Ctl.Internal.Wallet.Key (PrivatePaymentKey, PrivateStakeKey) +import Ctl.Internal.Wallet.KeyFile + ( privatePaymentKeyFromFile + , privateStakeKeyFromFile + ) import Data.Maybe (Maybe) +import Data.Traversable (for) +import Effect.Aff (Aff) import Node.Path (FilePath) data PrivatePaymentKeySource @@ -31,3 +53,21 @@ data WalletSpec | ConnectToFlint | ConnectToEternl | ConnectToLode + +mkWalletBySpec :: NetworkId -> WalletSpec -> Aff Wallet +mkWalletBySpec networkId = case _ of + UseKeys paymentKeySpec mbStakeKeySpec -> do + privatePaymentKey <- case paymentKeySpec of + PrivatePaymentKeyFile filePath -> + privatePaymentKeyFromFile filePath + PrivatePaymentKeyValue key -> pure key + mbPrivateStakeKey <- for mbStakeKeySpec case _ of + PrivateStakeKeyFile filePath -> privateStakeKeyFromFile filePath + PrivateStakeKeyValue key -> pure key + pure $ mkKeyWallet networkId privatePaymentKey mbPrivateStakeKey + ConnectToNami -> mkWalletAff NamiWallet + ConnectToGero -> mkWalletAff GeroWallet + ConnectToFlint -> mkWalletAff FlintWallet + ConnectToEternl -> mkWalletAff EternlWallet + ConnectToLode -> mkWalletAff LodeWallet + From bb6478bc84a62aa05b7f3fd55255392da7862999 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Tue, 6 Dec 2022 17:41:35 +0000 Subject: [PATCH 054/373] Revert removal of era summaries for slot conversions, add a handle to contract to implement fetching erasummaries --- doc/faq.md | 2 - src/Contract/Time.purs | 15 +- src/Internal/Contract/Monad.purs | 38 +---- src/Internal/Contract/QueryHandle.purs | 9 +- src/Internal/Contract/WaitUntilSlot.purs | 43 ++--- src/Internal/QueryM.purs | 9 -- src/Internal/Types/Interval.purs | 197 +++++++++++------------ src/Internal/Types/ScriptLookups.purs | 5 +- test/BalanceTx/Time.purs | 15 +- test/Integration.purs | 9 +- test/Types/Interval.purs | 130 +++++---------- test/Unit.purs | 3 +- 12 files changed, 188 insertions(+), 287 deletions(-) diff --git a/doc/faq.md b/doc/faq.md index f764cea75e..141d38f47b 100644 --- a/doc/faq.md +++ b/doc/faq.md @@ -31,8 +31,6 @@ Local `cardano-node` lags behind the global network time, so when using time con To do anything time-related, it's best to rely on local node chain tip time, instead of using `Date.now()` as a source of truth. This is often a requirement when using `mustValidateIn`, because the node will reject the transaction if it appears too early. -TODO Rethink these Time related questions - ### Q: Time/slot conversion functions return `Nothing`. Why is that? Time/slot conversion functions depend on `eraSummaries` [Ogmios local state query](https://ogmios.dev/mini-protocols/local-state-query/), that returns era bounds and slotting parameters details, required for proper slot arithmetic. The most common source of the problem is that Ogmios does not return enough epochs into the future. diff --git a/src/Contract/Time.purs b/src/Contract/Time.purs index 8fb8b87a64..5073fd761f 100644 --- a/src/Contract/Time.purs +++ b/src/Contract/Time.purs @@ -3,8 +3,6 @@ module Contract.Time ( getCurrentEpoch , getEraSummaries , getSystemStart - , getSlotLength - , getSlotReference , module Chain , module ExportOgmios , module Interval @@ -40,12 +38,9 @@ import Ctl.Internal.QueryM.Ogmios import Ctl.Internal.QueryM.Ogmios ( CurrentEpoch(CurrentEpoch) , EraSummaries - , RelativeTime - , SlotLength , SystemStart ) import Ctl.Internal.Serialization.Address (BlockId(BlockId), Slot(Slot)) as SerializationAddress -import Ctl.Internal.Serialization.Address (Slot) import Ctl.Internal.Types.Interval ( AbsTime(AbsTime) , Closure @@ -115,7 +110,7 @@ getCurrentEpoch = do $ UInt.fromString $ BigInt.toString (bigInt :: BigInt.BigInt) --- | Get `EraSummaries` as used for Slot arithemetic. Ogmios only. +-- | Get `EraSummaries` as used for Slot arithemetic. -- | Details can be found https://ogmios.dev/api/ under "eraSummaries" query getEraSummaries :: Contract EraSummaries getEraSummaries = wrapQueryM EraSummaries.getEraSummaries @@ -124,11 +119,3 @@ getEraSummaries = wrapQueryM EraSummaries.getEraSummaries getSystemStart :: Contract SystemStart getSystemStart = do asks $ _.ledgerConstants >>> _.systemStart - -getSlotLength :: Contract SlotLength -getSlotLength = do - asks $ _.ledgerConstants >>> _.slotLength - -getSlotReference :: Contract { slot :: Slot, time :: RelativeTime } -getSlotReference = do - asks $ _.ledgerConstants >>> _.slotReference diff --git a/src/Internal/Contract/Monad.purs b/src/Internal/Contract/Monad.purs index 1d89e14d91..bc4309e133 100644 --- a/src/Internal/Contract/Monad.purs +++ b/src/Internal/Contract/Monad.purs @@ -45,14 +45,13 @@ import Ctl.Internal.Contract.QueryBackend , defaultBackend , lookupBackend ) -import Ctl.Internal.Helpers (liftM, liftedM, logWithLevel) +import Ctl.Internal.Helpers (liftM, logWithLevel) import Ctl.Internal.JsWebSocket (_wsClose, _wsFinalize) import Ctl.Internal.Logging (Logger, mkLogger, setupLogs) import Ctl.Internal.QueryM ( QueryEnv , QueryM , WebSocket - , getEraSummariesAff , getProtocolParametersAff , getSystemStartAff , mkDatumCacheWebSocketAff @@ -62,19 +61,15 @@ import Ctl.Internal.QueryM -- TOD Move/translate these types into Cardano import Ctl.Internal.QueryM.Ogmios ( ProtocolParameters - , RelativeTime - , SlotLength , SystemStart ) as Ogmios import Ctl.Internal.QueryM.ServerConfig (ServerConfig) -import Ctl.Internal.Serialization.Address (NetworkId, Slot) +import Ctl.Internal.Serialization.Address (NetworkId) import Ctl.Internal.Types.UsedTxOuts (UsedTxOuts, newUsedTxOuts) import Ctl.Internal.Wallet (Wallet) import Ctl.Internal.Wallet (getNetworkId) as Wallet import Ctl.Internal.Wallet.Spec (WalletSpec, mkWalletBySpec) import Data.Either (Either(Left, Right)) -import Data.Foldable (maximumBy) -import Data.Function (on) import Data.Log.Level (LogLevel) import Data.Log.Message (Message) import Data.Maybe (Maybe(Just, Nothing), fromMaybe) @@ -177,21 +172,11 @@ type ContractEnv = , hooks :: Hooks , wallet :: Maybe Wallet , usedTxOuts :: UsedTxOuts - -- TODO: Duplicate types to Contract - -- We don't support changing protocol parameters, so supporting a HFC is even less unlikely - -- slotLength can only change with a HFC. + -- ledgerConstants are values that technically may change, but we assume to be + -- constant during Contract evaluation , ledgerConstants :: { pparams :: Ogmios.ProtocolParameters , systemStart :: Ogmios.SystemStart - -- Why not use Duration? - , slotLength :: Ogmios.SlotLength - -- A reference point in which the slotLength is assumed to be constant from - -- then until now, not including HFC which occur during contract evaluation - -- TODO: Drop systemStart and just normalize time AOT - -- Maybe not drop it, we export it in Contract. I'm not sure why though - -- TODO: We need to indicate that calculations in the past may be inaccurate - -- Or enforce slot reference to be as 'relatively old' - , slotReference :: { slot :: Slot, time :: Ogmios.RelativeTime } } } @@ -270,25 +255,12 @@ getLedgerConstants -> Aff { pparams :: Ogmios.ProtocolParameters , systemStart :: Ogmios.SystemStart - , slotLength :: Ogmios.SlotLength - , slotReference :: { slot :: Slot, time :: Ogmios.RelativeTime } } getLedgerConstants logger = case _ of CtlBackend { ogmios: { ws } } -> do pparams <- getProtocolParametersAff ws logger systemStart <- getSystemStartAff ws logger - -- Do we ever recieve an eraSummary ahead of schedule? - -- Maybe search for the chainTip's era - latestEraSummary <- liftedM (error "Could not get EraSummary") do - map unwrap - <<< - (maximumBy (compare `on` (unwrap >>> _.start >>> unwrap >>> _.slot))) - <<< unwrap <$> getEraSummariesAff ws logger - let - slotLength = _.slotLength $ unwrap $ _.parameters $ latestEraSummary - slotReference = (\{ slot, time } -> { slot, time }) $ unwrap $ _.start $ - latestEraSummary - pure { pparams, slotLength, systemStart, slotReference } + pure { pparams, systemStart } BlockfrostBackend _ -> undefined -- | Ensure that `NetworkId` from wallet is the same as specified in the diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs index 16b125b927..51ae38763e 100644 --- a/src/Internal/Contract/QueryHandle.purs +++ b/src/Internal/Contract/QueryHandle.purs @@ -25,6 +25,7 @@ import Ctl.Internal.Hashing (transactionHash) as Hashing import Ctl.Internal.QueryM (ClientError, QueryM) import Ctl.Internal.QueryM (evaluateTxOgmios, getChainTip, submitTxOgmios) as QueryM import Ctl.Internal.QueryM.CurrentEpoch (getCurrentEpoch) as QueryM +import Ctl.Internal.QueryM.EraSummaries (getEraSummaries) as QueryM import Ctl.Internal.QueryM.GetTxByHash (getTxByHash) as QueryM import Ctl.Internal.QueryM.Kupo ( getDatumByHash @@ -35,7 +36,11 @@ import Ctl.Internal.QueryM.Kupo , isTxConfirmed , utxosAt ) as Kupo -import Ctl.Internal.QueryM.Ogmios (AdditionalUtxoSet, CurrentEpoch) as Ogmios +import Ctl.Internal.QueryM.Ogmios + ( AdditionalUtxoSet + , CurrentEpoch + , EraSummaries + ) as Ogmios import Ctl.Internal.QueryM.Ogmios (SubmitTxR(SubmitTxSuccess), TxEvaluationR) import Ctl.Internal.Serialization (convertTransaction, toBytes) as Serialization import Ctl.Internal.Serialization.Address (Address) @@ -69,6 +74,7 @@ type QueryHandle = , submitTx :: Transaction -> Aff (Maybe TransactionHash) , getTxByHash :: TransactionHash -> Aff (Maybe Transaction) , evaluateTx :: Transaction -> Ogmios.AdditionalUtxoSet -> Aff TxEvaluationR + , getEraSummaries :: Aff Ogmios.EraSummaries } getQueryHandle :: Contract QueryHandle @@ -115,6 +121,7 @@ queryHandleForCtlBackend contractEnv backend = Serialization.convertTransaction tx ) QueryM.evaluateTxOgmios txBytes additionalUtxos + , getEraSummaries: runQueryM' QueryM.getEraSummaries } where runQueryM' :: forall (a :: Type). QueryM a -> Aff a diff --git a/src/Internal/Contract/WaitUntilSlot.purs b/src/Internal/Contract/WaitUntilSlot.purs index d273e9e6cc..b0b755296e 100644 --- a/src/Internal/Contract/WaitUntilSlot.purs +++ b/src/Internal/Contract/WaitUntilSlot.purs @@ -8,20 +8,25 @@ module Ctl.Internal.Contract.WaitUntilSlot import Prelude import Contract.Log (logTrace') +import Control.Monad.Error.Class (liftEither) import Control.Monad.Reader.Class (asks) import Ctl.Internal.Contract (getChainTip) import Ctl.Internal.Contract.Monad (Contract) +import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.Helpers (liftM) -import Ctl.Internal.QueryM.Ogmios (RelativeTime, SlotLength, SystemStart) +import Ctl.Internal.QueryM.Ogmios (EraSummaries, SystemStart) import Ctl.Internal.Serialization.Address (Slot(Slot)) import Ctl.Internal.Types.BigNum as BigNum import Ctl.Internal.Types.Chain as Chain import Ctl.Internal.Types.Interval ( POSIXTime(POSIXTime) + , findSlotEraSummary + , getSlotLength , slotToPosixTime ) import Ctl.Internal.Types.Natural (Natural) import Ctl.Internal.Types.Natural as Natural +import Data.Bifunctor (lmap) import Data.BigInt as BigInt import Data.DateTime.Instant (unInstant) import Data.Either (hush) @@ -36,22 +41,25 @@ import Effect.Now (now) -- | The returned slot will be no less than the slot provided as argument. waitUntilSlot :: Slot -> Contract Chain.Tip -waitUntilSlot futureSlot = +waitUntilSlot futureSlot = do + queryHandle <- getQueryHandle getChainTip >>= case _ of tip@(Chain.Tip (Chain.ChainTip { slot })) | slot >= futureSlot -> pure tip | otherwise -> do - { systemStart, slotLength, slotReference } <- asks _.ledgerConstants - let slotLengthMs = unwrap slotLength * 1000.0 + { systemStart } <- asks _.ledgerConstants + eraSummaries <- liftAff $ queryHandle.getEraSummaries + slotLengthMs <- map getSlotLength $ liftEither + $ lmap (const $ error "Unable to get current Era summary") + $ findSlotEraSummary eraSummaries slot -- `timePadding` in slots -- If there are less than `slotPadding` slots remaining, start querying for chainTip -- repeatedly, because it's possible that at any given moment Ogmios suddenly -- synchronizes with node that is also synchronized with global time. - getLag slotReference slotLength systemStart slot >>= logLag - slotLengthMs + getLag eraSummaries systemStart slot >>= logLag slotLengthMs futureTime <- liftEffect - (slotToPosixTime slotReference slotLength systemStart futureSlot) + (slotToPosixTime eraSummaries systemStart futureSlot) >>= hush >>> liftM (error "Unable to convert Slot to POSIXTime") delayTime <- estimateDelayUntil futureTime liftAff $ delay delayTime @@ -64,9 +72,8 @@ waitUntilSlot futureSlot = | currentSlot_ >= futureSlot -> pure currentTip | otherwise -> do liftAff $ delay $ Milliseconds slotLengthMs - getLag slotReference slotLength systemStart currentSlot_ - >>= logLag - slotLengthMs + getLag eraSummaries systemStart currentSlot_ + >>= logLag slotLengthMs fetchRepeatedly Chain.TipAtGenesis -> do liftAff $ delay retryDelay @@ -90,15 +97,13 @@ waitUntilSlot futureSlot = -- | Calculate difference between estimated POSIX time of given slot -- | and current time. getLag - :: { slot :: Slot, time :: RelativeTime } - -> SlotLength + :: EraSummaries -> SystemStart -> Slot -> Contract Milliseconds -getLag slotReference slotLength sysStart nowSlot = do - nowPosixTime <- - liftEffect (slotToPosixTime slotReference slotLength sysStart nowSlot) >>= - hush >>> liftM (error "Unable to convert Slot to POSIXTime") +getLag eraSummaries sysStart nowSlot = do + nowPosixTime <- liftEffect (slotToPosixTime eraSummaries sysStart nowSlot) >>= + hush >>> liftM (error "Unable to convert Slot to POSIXTime") nowMs <- unwrap <<< unInstant <$> liftEffect now logTrace' $ "getLag: current slot: " <> BigNum.toString (unwrap nowSlot) @@ -170,9 +175,11 @@ slotToEndPOSIXTime :: Slot -> Contract POSIXTime slotToEndPOSIXTime slot = do futureSlot <- liftM (error "Unable to advance slot") $ wrap <$> BigNum.add (unwrap slot) (BigNum.fromInt 1) - { systemStart, slotLength, slotReference } <- asks _.ledgerConstants + { systemStart } <- asks _.ledgerConstants + queryHandle <- getQueryHandle + eraSummaries <- liftAff $ queryHandle.getEraSummaries futureTime <- liftEffect $ - slotToPosixTime slotReference slotLength systemStart futureSlot + slotToPosixTime eraSummaries systemStart futureSlot >>= hush >>> liftM (error "Unable to convert Slot to POSIXTime") -- We assume that a slot is 1000 milliseconds here. -- TODO Don't diff --git a/src/Internal/QueryM.purs b/src/Internal/QueryM.purs index 0595164787..f95daebc87 100644 --- a/src/Internal/QueryM.purs +++ b/src/Internal/QueryM.purs @@ -365,15 +365,6 @@ getSystemStartAff ogmiosWs logger = _.systemStart unit -getEraSummariesAff - :: OgmiosWebSocket - -> (LogLevel -> String -> Effect Unit) - -> Aff Ogmios.EraSummaries -getEraSummariesAff ogmiosWs logger = - mkOgmiosRequestAff ogmiosWs logger Ogmios.queryEraSummariesCall - _.eraSummaries - unit - -------------------------------------------------------------------------------- -- Ogmios Local State Query Protocol -------------------------------------------------------------------------------- diff --git a/src/Internal/Types/Interval.purs b/src/Internal/Types/Interval.purs index c71d532890..3034b151de 100644 --- a/src/Internal/Types/Interval.purs +++ b/src/Internal/Types/Interval.purs @@ -96,8 +96,6 @@ import Ctl.Internal.Plutus.Types.DataSchema import Ctl.Internal.QueryM.Ogmios ( EraSummaries(EraSummaries) , EraSummary(EraSummary) - , RelativeTime - , SlotLength , SystemStart , aesonObject , slotLengthFactor @@ -699,22 +697,21 @@ extractArg o = do -- | Start, then add any excess for a UNIX Epoch time. Recall that POSIXTime -- | is in milliseconds for Protocol Version >= 6. slotToPosixTime - :: { slot :: Slot, time :: RelativeTime } - -> SlotLength + :: EraSummaries -> SystemStart -> Slot -> Effect (Either SlotToPosixTimeError POSIXTime) -slotToPosixTime slotReference slotLength sysStart slot = runExceptT do +slotToPosixTime eraSummaries sysStart slot = runExceptT do -- Get JSDate: sysStartD <- liftEffect $ parse $ unwrap sysStart -- Find current era: - -- currentEra <- liftEither $ findSlotEraSummary eraSummaries slot + currentEra <- liftEither $ findSlotEraSummary eraSummaries slot -- Convert absolute slot (relative to System start) to relative slot of era - relSlot <- liftEither $ relSlotFromSlot slotReference.slot slot + relSlot <- liftEither $ relSlotFromSlot currentEra slot -- Convert relative slot to relative time for that era - relTime <- liftM CannotGetBigIntFromNumber $ relTimeFromRelSlot slotLength + relTime <- liftM CannotGetBigIntFromNumber $ relTimeFromRelSlot currentEra relSlot - absTime <- liftEither $ absTimeFromRelTime slotReference.time relTime + absTime <- liftEither $ absTimeFromRelTime currentEra relTime -- Get POSIX time for system start sysStartPosix <- liftM CannotGetBigIntFromNumber $ BigInt.fromNumber @@ -809,40 +806,42 @@ instance Show AbsTime where -- | in conjunction with `findSlotEraSummary`. However, we choose to make the -- | function more general, guarding against a larger `start`ing slot relSlotFromSlot - :: Slot -> Slot -> Either SlotToPosixTimeError RelSlot -relSlotFromSlot start s@(Slot slot) = do + :: EraSummary -> Slot -> Either SlotToPosixTimeError RelSlot +relSlotFromSlot (EraSummary { start }) s@(Slot slot) = do let - startSlot = BigNum.toBigIntUnsafe $ unwrap start + startSlot = BigNum.toBigIntUnsafe $ unwrap (unwrap start).slot biSlot = BigNum.toBigIntUnsafe slot unless (startSlot <= biSlot) (throwError $ StartingSlotGreaterThanSlot s) pure $ wrap $ biSlot - startSlot -relTimeFromRelSlot :: SlotLength -> RelSlot -> Maybe RelTime -relTimeFromRelSlot slotLength (RelSlot relSlot) = - (<$>) wrap <<< BigInt.fromNumber $ (BigInt.toNumber relSlot) * - (unwrap slotLength) +relTimeFromRelSlot :: EraSummary -> RelSlot -> Maybe RelTime +relTimeFromRelSlot eraSummary (RelSlot relSlot) = + let + slotLength = getSlotLength eraSummary + in + (<$>) wrap <<< BigInt.fromNumber $ (BigInt.toNumber relSlot) * slotLength -- As justified in https://github.com/input-output-hk/ouroboros-network/blob/bd9e5653647c3489567e02789b0ec5b75c726db2/ouroboros-consensus/src/Ouroboros/Consensus/HardFork/History/Qry.hs#L461-L481 -- Treat the upperbound as inclusive. -- | Returns the absolute time relative to some system start, not UNIX epoch. absTimeFromRelTime - :: RelativeTime -> RelTime -> Either SlotToPosixTimeError AbsTime -absTimeFromRelTime start (RelTime relTime) = do + :: EraSummary -> RelTime -> Either SlotToPosixTimeError AbsTime +absTimeFromRelTime (EraSummary { start, end }) (RelTime relTime) = do let - startTime = unwrap start * slotLengthFactor + startTime = unwrap (unwrap start).time * slotLengthFactor absTime = startTime + BigInt.toNumber relTime -- relative to System Start, not UNIX Epoch. - -- If `EraSummary` doesn't have an end, the condition is automatically - -- satisfied. We use `<=` as justified by the source code. - -- Note the hack that we don't have `end` for the current era, if we did not - -- here could be issues going far into the future. But certain contracts are - -- required to be in the distant future. Onchain, this uses POSIXTime which - -- is stable, unlike Slots. - -- endTime = maybe (absTime + one) - -- ((*) slotLengthFactor <<< unwrap <<< _.time <<< unwrap) - -- end - -- unless - -- (absTime <= endTime) - -- (throwError $ EndTimeLessThanTime absTime) + -- If `EraSummary` doesn't have an end, the condition is automatically + -- satisfied. We use `<=` as justified by the source code. + -- Note the hack that we don't have `end` for the current era, if we did not + -- here could be issues going far into the future. But certain contracts are + -- required to be in the distant future. Onchain, this uses POSIXTime which + -- is stable, unlike Slots. + endTime = maybe (absTime + one) + ((*) slotLengthFactor <<< unwrap <<< _.time <<< unwrap) + end + unless + (absTime <= endTime) + (throwError $ EndTimeLessThanTime absTime) wrap <$> (liftM CannotGetBigIntFromNumber $ BigInt.fromNumber absTime) @@ -939,36 +938,33 @@ instance DecodeAeson PosixTimeToSlotError where -- | Converts a `POSIXTime` to `Slot` given an `EraSummaries` and -- | `SystemStart` queried from Ogmios. posixTimeToSlot - :: { slot :: Slot, time :: RelativeTime } - -> SlotLength + :: EraSummaries -> SystemStart -> POSIXTime -> Effect (Either PosixTimeToSlotError Slot) -posixTimeToSlot slotReference slotLength sysStart pt'@(POSIXTime pt) = - runExceptT do - -- Get JSDate: - sysStartD <- liftEffect $ parse $ unwrap sysStart - -- Get POSIX time for system start - sysStartPosix <- liftM CannotGetBigIntFromNumber' - $ BigInt.fromNumber - $ getTime sysStartD - -- Ensure the time we are converting is after the system start, otherwise - -- we have negative slots. - unless (sysStartPosix <= pt) - $ throwError - $ PosixTimeBeforeSystemStart pt' - -- Keep as milliseconds: - let absTime = wrap $ pt - sysStartPosix - -- Find current era: - -- currentEra <- liftEither $ findTimeEraSummary eraSummaries absTime - -- Get relative time from absolute time w.r.t. current era - relTime <- liftEither $ relTimeFromAbsTime slotReference.time absTime - -- Convert to relative slot - relSlotMod <- liftM CannotGetBigIntFromNumber' $ relSlotFromRelTime - slotLength - relTime - -- Get absolute slot relative to system start - liftEither $ slotFromRelSlot slotReference.slot relSlotMod +posixTimeToSlot eraSummaries sysStart pt'@(POSIXTime pt) = runExceptT do + -- Get JSDate: + sysStartD <- liftEffect $ parse $ unwrap sysStart + -- Get POSIX time for system start + sysStartPosix <- liftM CannotGetBigIntFromNumber' + $ BigInt.fromNumber + $ getTime sysStartD + -- Ensure the time we are converting is after the system start, otherwise + -- we have negative slots. + unless (sysStartPosix <= pt) + $ throwError + $ PosixTimeBeforeSystemStart pt' + -- Keep as milliseconds: + let absTime = wrap $ pt - sysStartPosix + -- Find current era: + currentEra <- liftEither $ findTimeEraSummary eraSummaries absTime + -- Get relative time from absolute time w.r.t. current era + relTime <- liftEither $ relTimeFromAbsTime currentEra absTime + -- Convert to relative slot + relSlotMod <- liftM CannotGetBigIntFromNumber' $ relSlotFromRelTime currentEra + relTime + -- Get absolute slot relative to system start + liftEither $ slotFromRelSlot currentEra relSlotMod -- | Finds the `EraSummary` an `AbsTime` lies inside (if any). findTimeEraSummary @@ -991,9 +987,9 @@ findTimeEraSummary (EraSummaries eraSummaries) absTime@(AbsTime at) = end relTimeFromAbsTime - :: RelativeTime -> AbsTime -> Either PosixTimeToSlotError RelTime -relTimeFromAbsTime start at@(AbsTime absTime) = do - let startTime = unwrap start * slotLengthFactor + :: EraSummary -> AbsTime -> Either PosixTimeToSlotError RelTime +relTimeFromAbsTime (EraSummary { start }) at@(AbsTime absTime) = do + let startTime = unwrap (unwrap start).time * slotLengthFactor unless (startTime <= BigInt.toNumber absTime) (throwError $ StartTimeGreaterThanTime at) let @@ -1007,39 +1003,39 @@ relTimeFromAbsTime start at@(AbsTime absTime) = do -- | Converts relative time to relative slot (using Euclidean division) and -- | modulus for any leftover. relSlotFromRelTime - :: SlotLength -> RelTime -> Maybe (RelSlot /\ ModTime) -relSlotFromRelTime slotLength (RelTime relTime) = + :: EraSummary -> RelTime -> Maybe (RelSlot /\ ModTime) +relSlotFromRelTime eraSummary (RelTime relTime) = let + slotLength = getSlotLength eraSummary relSlot = wrap <$> - (BigInt.fromNumber <<< Math.trunc) - (BigInt.toNumber relTime / unwrap slotLength) + (BigInt.fromNumber <<< Math.trunc) (BigInt.toNumber relTime / slotLength) modTime = wrap <$> - BigInt.fromNumber (BigInt.toNumber relTime Math.% unwrap slotLength) + BigInt.fromNumber (BigInt.toNumber relTime Math.% slotLength) in (/\) <$> relSlot <*> modTime slotFromRelSlot - :: Slot -> RelSlot /\ ModTime -> Either PosixTimeToSlotError Slot + :: EraSummary -> RelSlot /\ ModTime -> Either PosixTimeToSlotError Slot slotFromRelSlot - start -- (EraSummary { start, end }) - (RelSlot relSlot /\ _) = do + (EraSummary { start, end }) + (RelSlot relSlot /\ mt@(ModTime modTime)) = do let - startSlot = BigNum.toBigIntUnsafe $ unwrap start + startSlot = BigNum.toBigIntUnsafe $ unwrap (unwrap start).slot -- Round down to the nearest Slot to accept Milliseconds as input. slot = startSlot + relSlot -- relative to system start - -- If `EraSummary` doesn't have an end, the condition is automatically - -- satisfied. We use `<=` as justified by the source code. - -- Note the hack that we don't have `end` for the current era, if we did not - -- here could be issues going far into the future. But certain contracts are - -- required to be in the distant future. Onchain, this uses POSIXTime which - -- is stable, unlike Slots. - -- endSlot = maybe (slot + one) - -- (BigNum.toBigIntUnsafe <<< unwrap <<< _.slot <<< unwrap) - -- end + -- If `EraSummary` doesn't have an end, the condition is automatically + -- satisfied. We use `<=` as justified by the source code. + -- Note the hack that we don't have `end` for the current era, if we did not + -- here could be issues going far into the future. But certain contracts are + -- required to be in the distant future. Onchain, this uses POSIXTime which + -- is stable, unlike Slots. + endSlot = maybe (slot + one) + (BigNum.toBigIntUnsafe <<< unwrap <<< _.slot <<< unwrap) + end bnSlot <- liftM CannotGetBigNumFromBigInt' $ BigNum.fromBigInt slot -- Check we are less than the end slot, or if equal, there is no excess: - -- unless (slot < endSlot || slot == endSlot && modTime == zero) - -- (throwError $ EndSlotLessThanSlotOrModNonZero (wrap bnSlot) mt) + unless (slot < endSlot || slot == endSlot && modTime == zero) + (throwError $ EndSlotLessThanSlotOrModNonZero (wrap bnSlot) mt) pure $ wrap bnSlot -- | Get SlotLength in Milliseconds @@ -1063,32 +1059,28 @@ sequenceInterval AlwaysInterval = pure AlwaysInterval -- | Converts a `POSIXTimeRange` to `SlotRange` given an `EraSummaries` and -- | `SystemStart` queried from Ogmios. posixTimeRangeToSlotRange - :: { slot :: Slot, time :: RelativeTime } - -> SlotLength + :: EraSummaries -> SystemStart -> POSIXTimeRange -> Effect (Either PosixTimeToSlotError SlotRange) posixTimeRangeToSlotRange - slotReference - slotLength + eraSummaries sysStart range = sequenceInterval <$> - sequenceInterval (posixTimeToSlot slotReference slotLength sysStart <$> range) + sequenceInterval (posixTimeToSlot eraSummaries sysStart <$> range) -- | Converts a `SlotRange` to `POSIXTimeRange` given an `EraSummaries` and -- | `SystemStart` queried from Ogmios. slotRangeToPosixTimeRange - :: { slot :: Slot, time :: RelativeTime } - -> SlotLength + :: EraSummaries -> SystemStart -> SlotRange -> Effect (Either SlotToPosixTimeError POSIXTimeRange) slotRangeToPosixTimeRange - slotReference - slotLength + eraSummaries sysStart range = sequenceInterval <$> - sequenceInterval (slotToPosixTime slotReference slotLength sysStart <$> range) + sequenceInterval (slotToPosixTime eraSummaries sysStart <$> range) type TransactionValiditySlot = { validityStartInterval :: Maybe Slot, timeToLive :: Maybe Slot } @@ -1120,14 +1112,12 @@ slotRangeToTransactionValidity EmptyInterval = -- | Converts a `POSIXTimeRange` to a transaction validity interval via a -- | `SlotRange` to be used when building a CSL transaction body posixTimeRangeToTransactionValidity - :: { slot :: Slot, time :: RelativeTime } - -> SlotLength + :: EraSummaries -> SystemStart -> POSIXTimeRange -> Effect (Either PosixTimeToSlotError TransactionValiditySlot) -posixTimeRangeToTransactionValidity sr sl ss = - map (map slotRangeToTransactionValidity) <<< posixTimeRangeToSlotRange sr sl - ss +posixTimeRangeToTransactionValidity es ss = + map (map slotRangeToTransactionValidity) <<< posixTimeRangeToSlotRange es ss data ToOnChainPosixTimeRangeError = PosixTimeToSlotError' PosixTimeToSlotError @@ -1300,22 +1290,21 @@ haskIntervalToInterval (HaskInterval { ivFrom, ivTo }) = case ivFrom, ivTo of -- | `OnchainPOSIXTimeRange` is intended to equal the validity range found in -- | the on-chain `ScriptContext` toOnchainPosixTimeRange - :: { slot :: Slot, time :: RelativeTime } - -> SlotLength + :: EraSummaries -> SystemStart -> POSIXTimeRange -> Effect (Either ToOnChainPosixTimeRangeError OnchainPOSIXTimeRange) -toOnchainPosixTimeRange sr sl ss ptr = runExceptT do +toOnchainPosixTimeRange es ss ptr = runExceptT do { validityStartInterval, timeToLive } <- - ExceptT $ posixTimeRangeToTransactionValidity sr sl ss ptr + ExceptT $ posixTimeRangeToTransactionValidity es ss ptr <#> lmap PosixTimeToSlotError' case validityStartInterval, timeToLive of Nothing, Nothing -> liftEither $ Right $ wrap always - Just s, Nothing -> ExceptT $ slotToPosixTime sr sl ss s + Just s, Nothing -> ExceptT $ slotToPosixTime es ss s <#> bimap SlotToPosixTimeError' (from >>> wrap) - Nothing, Just s -> ExceptT $ slotToPosixTime sr sl ss s + Nothing, Just s -> ExceptT $ slotToPosixTime es ss s <#> bimap SlotToPosixTimeError' (to >>> wrap) Just s1, Just s2 -> do - t1 <- ExceptT $ slotToPosixTime sr sl ss s1 <#> lmap SlotToPosixTimeError' - t2 <- ExceptT $ slotToPosixTime sr sl ss s2 <#> lmap SlotToPosixTimeError' + t1 <- ExceptT $ slotToPosixTime es ss s1 <#> lmap SlotToPosixTimeError' + t2 <- ExceptT $ slotToPosixTime es ss s2 <#> lmap SlotToPosixTimeError' liftEither $ Right $ wrap $ mkFiniteInterval t1 t2 diff --git a/src/Internal/Types/ScriptLookups.purs b/src/Internal/Types/ScriptLookups.purs index 527426ec86..6309045d47 100644 --- a/src/Internal/Types/ScriptLookups.purs +++ b/src/Internal/Types/ScriptLookups.purs @@ -1053,10 +1053,11 @@ processConstraint mpsMap osMap c = do case c of MustIncludeDatum dat -> addDatum dat MustValidateIn posixTimeRange -> do - { slotReference, slotLength, systemStart } <- asks _.ledgerConstants + { systemStart } <- asks _.ledgerConstants + eraSummaries <- liftAff $ queryHandle.getEraSummaries runExceptT do ({ timeToLive, validityStartInterval }) <- ExceptT $ liftEffect $ - posixTimeRangeToTransactionValidity slotReference slotLength + posixTimeRangeToTransactionValidity eraSummaries systemStart posixTimeRange <#> lmap (CannotConvertPOSIXTimeRange posixTimeRange) diff --git a/test/BalanceTx/Time.purs b/test/BalanceTx/Time.purs index 20d44ac2ef..7a1f9cce70 100644 --- a/test/BalanceTx/Time.purs +++ b/test/BalanceTx/Time.purs @@ -14,8 +14,7 @@ import Contract.Time , Slot , always , from - , getSlotLength - , getSlotReference + , getEraSummaries , getSystemStart , maxSlot , mkFiniteInterval @@ -157,23 +156,19 @@ getTimeFromUnbalanced utx = validityToPosixTime $ unwrap body toPosixTime :: Slot -> Contract POSIXTime toPosixTime time = do - slotReference <- getSlotReference - slotLength <- getSlotLength + eraSummaries <- getEraSummaries systemStart <- getSystemStart - eitherTime <- liftEffect $ slotToPosixTime slotReference slotLength - systemStart - time + eitherTime <- liftEffect $ slotToPosixTime eraSummaries systemStart time case eitherTime of Left e -> (throwError <<< error <<< show) e Right value -> pure value toPosixTimeRange :: Interval Slot -> Contract (Interval POSIXTime) toPosixTimeRange range = do - slotReference <- getSlotReference - slotLength <- getSlotLength + eraSummaries <- getEraSummaries systemStart <- getSystemStart eitherRange <- liftEffect $ - slotRangeToPosixTimeRange slotReference slotLength systemStart range + slotRangeToPosixTimeRange eraSummaries systemStart range case eitherRange of Left e -> (throwError <<< error <<< show) e Right value -> pure value diff --git a/test/Integration.purs b/test/Integration.purs index 8e0689a1b4..cd9978c28b 100644 --- a/test/Integration.purs +++ b/test/Integration.purs @@ -4,7 +4,7 @@ import Prelude import Contract.Config (testnetConfig) import Contract.Monad (runContract) -import Contract.Time (getSlotLength, getSlotReference, getSystemStart) +import Contract.Time (getEraSummaries, getSystemStart) import Ctl.Internal.Contract.Monad (wrapQueryM) import Ctl.Internal.Test.TestPlanM (TestPlanM, interpret) import Effect (Effect) @@ -34,10 +34,9 @@ testPlan = do skip $ flip mapTest Types.Interval.suite \f -> runContract testnetConfig { suppressLogs = true } do - slotReference <- getSlotReference - slotLength <- getSlotLength - systemStart <- getSystemStart - liftEffect $ f { slotReference, slotLength, systemStart } + eraSummaries <- getEraSummaries + sysStart <- getSystemStart + liftEffect $ f eraSummaries sysStart Collateral.suite PrivateKey.suite Logging.suite diff --git a/test/Types/Interval.purs b/test/Types/Interval.purs index b00da46ee4..61f901fc45 100644 --- a/test/Types/Interval.purs +++ b/test/Types/Interval.purs @@ -2,9 +2,6 @@ module Test.Ctl.Types.Interval ( suite , eraSummariesFixture , systemStartFixture - , slotLengthFixture - , slotReferenceFixture - , contextFixture ) where import Prelude @@ -12,13 +9,7 @@ import Prelude import Aeson (class DecodeAeson, decodeJsonString, printJsonDecodeError) import Control.Monad.Error.Class (liftEither) import Control.Monad.Except (throwError) -import Ctl.Internal.Helpers (liftedM) -import Ctl.Internal.QueryM.Ogmios - ( EraSummaries - , RelativeTime - , SlotLength - , SystemStart - ) +import Ctl.Internal.QueryM.Ogmios (EraSummaries, SystemStart) import Ctl.Internal.Serialization.Address (Slot(Slot)) import Ctl.Internal.Test.TestPlanM (TestPlanM) import Ctl.Internal.Types.BigNum (fromInt) as BigNum @@ -42,10 +33,7 @@ import Ctl.Internal.Types.Interval import Data.Bifunctor (lmap) import Data.BigInt (fromInt, fromString) as BigInt import Data.Either (Either(Left, Right), either) -import Data.Foldable (maximumBy) -import Data.Function (on) import Data.Maybe (fromJust) -import Data.Newtype (unwrap) import Data.Traversable (traverse_) import Effect (Effect) import Effect.Exception (error) @@ -58,13 +46,7 @@ import Test.QuickCheck (Result(Success, Failed), quickCheck, ()) import Test.QuickCheck.Combinators ((&=&)) import Test.Spec.Assertions (shouldEqual) -type Context = - { slotReference :: { slot :: Slot, time :: RelativeTime } - , slotLength :: SlotLength - , systemStart :: SystemStart - } - -suite :: TestPlanM (Context -> Effect Unit) Unit +suite :: TestPlanM (EraSummaries -> SystemStart -> Effect Unit) Unit suite = do group "Interval" do group "EraSumaries related" do @@ -102,36 +84,12 @@ eraSummariesFixture :: Effect EraSummaries eraSummariesFixture = loadOgmiosFixture "eraSummaries" "bbf8b1d7d2487e750104ec2b5a31fa86" -slotLengthFixture :: Effect SlotLength -slotLengthFixture = do - latestEraSummary <- liftedM (error "Could not get EraSummary") do - map unwrap - <<< (maximumBy (compare `on` (unwrap >>> _.start >>> unwrap >>> _.slot))) - <<< unwrap <$> eraSummariesFixture - pure $ _.slotLength $ unwrap $ _.parameters $ latestEraSummary - -slotReferenceFixture :: Effect { slot :: Slot, time :: RelativeTime } -slotReferenceFixture = do - latestEraSummary <- liftedM (error "Could not get EraSummary") do - map unwrap - <<< (maximumBy (compare `on` (unwrap >>> _.start >>> unwrap >>> _.slot))) - <<< unwrap <$> eraSummariesFixture - pure $ (\{ slot, time } -> { slot, time }) $ unwrap $ _.start $ - latestEraSummary - systemStartFixture :: Effect SystemStart systemStartFixture = loadOgmiosFixture "systemStart" "ed0caad81f6936e0c122ef6f3c7de5e8" -contextFixture :: Effect Context -contextFixture = do - slotReference <- slotReferenceFixture - slotLength <- slotLengthFixture - systemStart <- systemStartFixture - pure { slotReference, slotLength, systemStart } - -testPosixTimeToSlot :: Context -> Effect Unit -testPosixTimeToSlot ctx = do +testPosixTimeToSlot :: EraSummaries -> SystemStart -> Effect Unit +testPosixTimeToSlot eraSummaries sysStart = do let -- Tests currently pass "exactly" for seconds precision, which makes sense -- given converting to a Slot will round down to the near slot length @@ -181,37 +139,35 @@ testPosixTimeToSlot ctx = do [ "1603636353000" , "1613636755000" ] - traverse_ (idTest identity) posixTimes + traverse_ (idTest eraSummaries sysStart identity) posixTimes -- With Milliseconds, we generally round down, provided the aren't at the -- end with non-zero excess: - idTest + idTest eraSummaries sysStart (const $ mkPosixTime "1613636754000") (mkPosixTime "1613636754999") - idTest + idTest eraSummaries sysStart (const $ mkPosixTime "1613636754000") (mkPosixTime "1613636754500") - idTest + idTest eraSummaries sysStart (const $ mkPosixTime "1613636754000") (mkPosixTime "1613636754499") where idTest - :: (POSIXTime -> POSIXTime) + :: EraSummaries + -> SystemStart + -> (POSIXTime -> POSIXTime) -> POSIXTime -> Effect Unit - idTest transf posixTime = do - posixTimeToSlot ctx.slotReference ctx.slotLength ctx.systemStart posixTime - >>= case _ of - Left err -> throwError $ error $ show err - Right slot -> do - ePosixTime <- slotToPosixTime ctx.slotReference ctx.slotLength - ctx.systemStart - slot - either (throwError <<< error <<< show) - (shouldEqual $ transf posixTime) - ePosixTime + idTest es ss transf posixTime = do + posixTimeToSlot es ss posixTime >>= case _ of + Left err -> throwError $ error $ show err + Right slot -> do + ePosixTime <- slotToPosixTime es ss slot + either (throwError <<< error <<< show) (shouldEqual $ transf posixTime) + ePosixTime -testSlotToPosixTime :: Context -> Effect Unit -testSlotToPosixTime ctx = do +testSlotToPosixTime :: EraSummaries -> SystemStart -> Effect Unit +testSlotToPosixTime eraSummaries sysStart = do -- See *Testing far into the future note during hardforks:* for details on -- how far into the future we test with slots when a hardfork occurs. let @@ -225,42 +181,40 @@ testSlotToPosixTime ctx = do , 232 , 1 ] - traverse_ idTest slots + traverse_ (idTest eraSummaries sysStart) slots where - idTest :: Slot -> Effect Unit - idTest slot = do - slotToPosixTime ctx.slotReference ctx.slotLength ctx.systemStart slot >>= - case _ of - Left err -> throwError $ error $ show err - Right posixTime -> do - eSlot <- posixTimeToSlot ctx.slotReference ctx.slotLength - ctx.systemStart - posixTime - either (throwError <<< error <<< show) (shouldEqual slot) eSlot + idTest :: EraSummaries -> SystemStart -> Slot -> Effect Unit + idTest es ss slot = do + slotToPosixTime es ss slot >>= case _ of + Left err -> throwError $ error $ show err + Right posixTime -> do + eSlot <- posixTimeToSlot es ss posixTime + either (throwError <<< error <<< show) (shouldEqual slot) eSlot mkSlot :: Int -> Slot mkSlot = Slot <<< BigNum.fromInt -testPosixTimeToSlotError :: Context -> Effect Unit -testPosixTimeToSlotError ctx = do +testPosixTimeToSlotError :: EraSummaries -> SystemStart -> Effect Unit +testPosixTimeToSlotError eraSummaries sysStart = do let posixTime = mkPosixTime "1000" -- Some difficulty reproducing all the errors - errTest + errTest eraSummaries sysStart posixTime (PosixTimeBeforeSystemStart posixTime) where errTest - :: POSIXTime + :: EraSummaries + -> SystemStart + -> POSIXTime -> PosixTimeToSlotError -> Effect Unit - errTest posixTime expectedErr = do - posixTimeToSlot ctx.slotReference ctx.slotLength ctx.systemStart posixTime - >>= case _ of - Left err -> err `shouldEqual` expectedErr - Right _ -> - throwError $ error $ "Test should have failed giving: " <> show - expectedErr + errTest es ss posixTime expectedErr = do + posixTimeToSlot es ss posixTime >>= case _ of + Left err -> err `shouldEqual` expectedErr + Right _ -> + throwError $ error $ "Test should have failed giving: " <> show + expectedErr -- All this test can be generalized to use : -- forall (a::Type) . Arbitrary a => Ord a => Ring a @@ -433,8 +387,8 @@ testIntersection = quickCheck test -- Helpers -------------------------------------------------------------------------------- -liftToTest :: Effect Unit -> (Context -> Effect Unit) -liftToTest = pure +liftToTest :: Effect Unit -> (EraSummaries -> SystemStart -> Effect Unit) +liftToTest = pure <<< pure withMsg :: String -> Result -> Result withMsg _ Success = Success diff --git a/test/Unit.purs b/test/Unit.purs index 285a35cbd0..c714aa9e45 100644 --- a/test/Unit.purs +++ b/test/Unit.purs @@ -75,6 +75,7 @@ testPlan = do Types.Transaction.suite Ctl.Data.Interval.suite flip mapTest Types.Interval.suite \f -> liftEffect $ join $ - f <$> Types.Interval.contextFixture + f <$> Types.Interval.eraSummariesFixture + <*> Types.Interval.systemStartFixture E2E.Route.suite MustSpendTotal.suite From a3a422b245d064c49b45f6d50ff339ee2d5ab8bd Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Tue, 6 Dec 2022 18:54:55 +0000 Subject: [PATCH 055/373] Remove comment --- src/Internal/Contract/AwaitTxConfirmed.purs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/Internal/Contract/AwaitTxConfirmed.purs b/src/Internal/Contract/AwaitTxConfirmed.purs index 959e2dcf53..6bb64a9a9b 100644 --- a/src/Internal/Contract/AwaitTxConfirmed.purs +++ b/src/Internal/Contract/AwaitTxConfirmed.purs @@ -11,7 +11,6 @@ import Ctl.Internal.Contract (getChainTip) import Ctl.Internal.Contract.Monad (Contract) import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.Contract.WaitUntilSlot (waitUntilSlot) --- import Ctl.Internal.QueryM.Kupo (isTxConfirmed) as Kupo import Ctl.Internal.QueryM.Ogmios (TxHash) import Ctl.Internal.Serialization.Address (Slot) import Ctl.Internal.Types.BigNum as BigNum From a746e05a2ec0c87213d57c876b7e8f7acfa87a7e Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Tue, 6 Dec 2022 19:02:26 +0000 Subject: [PATCH 056/373] Remove missing export from QueryM. Drop uses of TxHash in Contract --- src/Contract/Transaction.purs | 8 +++----- src/Internal/Contract/AwaitTxConfirmed.purs | 12 ++++++------ src/Internal/QueryM.purs | 1 - 3 files changed, 9 insertions(+), 12 deletions(-) diff --git a/src/Contract/Transaction.purs b/src/Contract/Transaction.purs index 5368047c0f..30eb248c89 100644 --- a/src/Contract/Transaction.purs +++ b/src/Contract/Transaction.purs @@ -513,7 +513,7 @@ getTxByHash th = do awaitTxConfirmed :: TransactionHash -> Contract Unit -awaitTxConfirmed = Contract.awaitTxConfirmed <<< unwrap +awaitTxConfirmed = Contract.awaitTxConfirmed -- | Same as `awaitTxConfirmed`, but allows to specify a timeout in seconds for waiting. -- | Throws an exception on timeout. @@ -524,8 +524,7 @@ awaitTxConfirmedWithTimeout :: Seconds -> TransactionHash -> Contract Unit -awaitTxConfirmedWithTimeout timeout = - Contract.awaitTxConfirmedWithTimeout timeout <<< unwrap +awaitTxConfirmedWithTimeout = Contract.awaitTxConfirmedWithTimeout -- | Same as `awaitTxConfirmed`, but allows to specify a timeout in slots for waiting. -- | Throws an exception on timeout. @@ -536,8 +535,7 @@ awaitTxConfirmedWithTimeoutSlots :: Int -> TransactionHash -> Contract Unit -awaitTxConfirmedWithTimeoutSlots timeout = - Contract.awaitTxConfirmedWithTimeoutSlots timeout <<< unwrap +awaitTxConfirmedWithTimeoutSlots = Contract.awaitTxConfirmedWithTimeoutSlots -- | Builds an expected utxo set from transaction outputs. Predicts output -- | references (`TransactionInput`s) for each output by calculating the diff --git a/src/Internal/Contract/AwaitTxConfirmed.purs b/src/Internal/Contract/AwaitTxConfirmed.purs index 6bb64a9a9b..81cf81879f 100644 --- a/src/Internal/Contract/AwaitTxConfirmed.purs +++ b/src/Internal/Contract/AwaitTxConfirmed.purs @@ -11,10 +11,10 @@ import Ctl.Internal.Contract (getChainTip) import Ctl.Internal.Contract.Monad (Contract) import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.Contract.WaitUntilSlot (waitUntilSlot) -import Ctl.Internal.QueryM.Ogmios (TxHash) import Ctl.Internal.Serialization.Address (Slot) import Ctl.Internal.Types.BigNum as BigNum import Ctl.Internal.Types.Chain as Chain +import Ctl.Internal.Types.Transaction (TransactionHash) import Data.Either (either) import Data.Maybe (maybe) import Data.Newtype (unwrap, wrap) @@ -25,10 +25,10 @@ import Effect.Aff.Class (liftAff) import Effect.Class (liftEffect) import Effect.Exception (throw) -awaitTxConfirmed :: TxHash -> Contract Unit +awaitTxConfirmed :: TransactionHash -> Contract Unit awaitTxConfirmed = awaitTxConfirmedWithTimeout (Seconds infinity) -awaitTxConfirmedWithTimeout :: Seconds -> TxHash -> Contract Unit +awaitTxConfirmedWithTimeout :: Seconds -> TransactionHash -> Contract Unit awaitTxConfirmedWithTimeout timeoutSeconds txHash = -- If timeout is infinity, do not use a timeout at all if unwrap timeoutSeconds == infinity then void findTx @@ -58,7 +58,7 @@ awaitTxConfirmedWithTimeout timeoutSeconds txHash = delayTime :: Milliseconds delayTime = wrap 1000.0 -awaitTxConfirmedWithTimeoutSlots :: Int -> TxHash -> Contract Unit +awaitTxConfirmedWithTimeoutSlots :: Int -> TransactionHash -> Contract Unit awaitTxConfirmedWithTimeoutSlots timeoutSlots txHash = getCurrentSlot >>= addSlots timeoutSlots >>= go where @@ -86,9 +86,9 @@ awaitTxConfirmedWithTimeoutSlots timeoutSlots txHash = void $ addSlots 1 slot >>= waitUntilSlot go timeout -isTxConfirmed :: TxHash -> Contract Boolean +isTxConfirmed :: TransactionHash -> Contract Boolean isTxConfirmed txHash = do queryHandle <- getQueryHandle - liftAff $ queryHandle.isTxConfirmed (wrap txHash) + liftAff $ queryHandle.isTxConfirmed txHash >>= either (liftEffect <<< throw <<< show) pure diff --git a/src/Internal/QueryM.purs b/src/Internal/QueryM.purs index f95daebc87..e88010dd51 100644 --- a/src/Internal/QueryM.purs +++ b/src/Internal/QueryM.purs @@ -30,7 +30,6 @@ module Ctl.Internal.QueryM , getLogger , getProtocolParametersAff , getSystemStartAff - , getEraSummariesAff , handleAffjaxResponse , listeners , postAeson From f510319484229d8428d17590a4cad579c3e0edbc Mon Sep 17 00:00:00 2001 From: Gregory Gerasev Date: Wed, 7 Dec 2022 00:12:42 +0300 Subject: [PATCH 057/373] Apply suggestions from code review Co-authored-by: Joseph Young --- src/Internal/Deserialization/PlutusData.purs | 2 +- src/Internal/Deserialization/UnspentOutput.purs | 2 +- src/Internal/Deserialization/WitnessSet.purs | 3 +-- src/Internal/Serialization.purs | 2 +- src/Internal/TxOutput.purs | 3 +-- 5 files changed, 5 insertions(+), 7 deletions(-) diff --git a/src/Internal/Deserialization/PlutusData.purs b/src/Internal/Deserialization/PlutusData.purs index b5acb4671f..c2d867176c 100644 --- a/src/Internal/Deserialization/PlutusData.purs +++ b/src/Internal/Deserialization/PlutusData.purs @@ -51,7 +51,7 @@ convertPlutusConstr pd = do constr <- _PlutusData_constr maybeFfiHelper pd let data' = convertPlutusData <$> - (_unpackPlutusList containerHelper $ _ConstrPlutusData_data constr) + _unpackPlutusList containerHelper (_ConstrPlutusData_data constr) alt <- BigNum.toBigInt $ _ConstrPlutusData_alternative constr pure $ T.Constr alt data' diff --git a/src/Internal/Deserialization/UnspentOutput.purs b/src/Internal/Deserialization/UnspentOutput.purs index 25b05fb0ba..3082838b50 100644 --- a/src/Internal/Deserialization/UnspentOutput.purs +++ b/src/Internal/Deserialization/UnspentOutput.purs @@ -98,7 +98,7 @@ convertOutput output = do mbDatum = getPlutusData maybeFfiHelper output datum <- case mbDatum, mbDataHash of Just _, Just _ -> Nothing -- impossible, so it's better to fail - Just datumValue, Nothing -> pure <<< OutputDatum <<< wrap $ + Just datumValue, Nothing -> pure $ OutputDatum $ wrap $ convertPlutusData datumValue Nothing, Just datumHash -> pure $ OutputDatumHash datumHash Nothing, Nothing -> pure NoOutputDatum diff --git a/src/Internal/Deserialization/WitnessSet.purs b/src/Internal/Deserialization/WitnessSet.purs index b00d50dbfe..0543f40a1c 100644 --- a/src/Internal/Deserialization/WitnessSet.purs +++ b/src/Internal/Deserialization/WitnessSet.purs @@ -67,8 +67,7 @@ convertWitnessSet ws = do nativeScripts <- for (getNativeScripts maybeFfiHelper ws) convertNativeScripts redeemers <- for (getRedeemers maybeFfiHelper ws) convertRedeemers let - plutusData = map convertPlutusList - (getWitnessSetPlutusData maybeFfiHelper ws) + plutusData = convertPlutusList <$> getWitnessSetPlutusData maybeFfiHelper ws plutusScripts <- for (getPlutusScripts maybeFfiHelper ws) convertPlutusScripts pure $ T.TransactionWitnessSet { vkeys: getVkeywitnesses maybeFfiHelper ws <#> convertVkeyWitnesses diff --git a/src/Internal/Serialization.purs b/src/Internal/Serialization.purs index 13abf86762..a1b2376fb7 100644 --- a/src/Internal/Serialization.purs +++ b/src/Internal/Serialization.purs @@ -793,7 +793,7 @@ convertTxOutput transactionOutputSetDataHash txo OutputDatum datumValue -> do transactionOutputSetPlutusData txo - =<< pure (convertPlutusData $ unwrap datumValue) + $ convertPlutusData $ unwrap datumValue for_ scriptRef $ convertScriptRef >>> transactionOutputSetScriptRef txo pure txo diff --git a/src/Internal/TxOutput.purs b/src/Internal/TxOutput.purs index 34a5406ede..f7018f2886 100644 --- a/src/Internal/TxOutput.purs +++ b/src/Internal/TxOutput.purs @@ -106,8 +106,7 @@ ogmiosDatumToDatum :: String -> Maybe Datum ogmiosDatumToDatum = hexToByteArray >=> fromBytes - >=> (Deserialization.convertPlutusData >>> Just) - >>> map Datum + >=> (Deserialization.convertPlutusData >>> Datum >>> Just) -- | Converts an internal `DataHash` to an Ogmios datumhash `String` datumHashToOgmiosDatumHash :: DataHash -> String From 72d1a14ad2f49ba972cf557a1db80511a4012d0c Mon Sep 17 00:00:00 2001 From: uhbif19 Date: Wed, 7 Dec 2022 00:13:58 +0300 Subject: [PATCH 058/373] Fix review comments --- examples/ContractTestUtils.purs | 2 +- examples/SatisfiesAnyOf.purs | 5 ++- src/Contract/ScriptLookups.purs | 1 - src/Contract/Transaction.purs | 1 - src/Internal/Deserialization/PlutusData.purs | 15 +++---- src/Internal/Hashing.purs | 1 - src/Internal/QueryM.purs | 44 +++++++++----------- src/Internal/Serialization.purs | 3 +- src/Internal/Serialization/PlutusData.purs | 2 +- src/Internal/Serialization/WitnessSet.purs | 8 +--- src/Internal/Types/ScriptLookups.purs | 26 +++++------- src/Internal/Types/TypedTxOut.purs | 9 ++-- test/Data.purs | 2 +- test/Plutip/Contract.purs | 7 ++-- test/Serialization.purs | 9 ++-- 15 files changed, 55 insertions(+), 80 deletions(-) diff --git a/examples/ContractTestUtils.purs b/examples/ContractTestUtils.purs index 0ce8e0263f..a3a997eff5 100644 --- a/examples/ContractTestUtils.purs +++ b/examples/ContractTestUtils.purs @@ -87,7 +87,7 @@ mkAssertions params@(ContractParams p) = do liftedM "Failed to get sender address" $ head <$> getWalletAddresses receiverAddress <- liftedM "Failed to get receiver address" (getReceiverAddress params) - let dhash = datumHash $ p.datumToAttach + let dhash = datumHash p.datumToAttach pure $ [ TestUtils.assertGainAtAddress' (label receiverAddress "Receiver") diff --git a/examples/SatisfiesAnyOf.purs b/examples/SatisfiesAnyOf.purs index d6168d2345..6816fb3966 100644 --- a/examples/SatisfiesAnyOf.purs +++ b/examples/SatisfiesAnyOf.purs @@ -40,9 +40,10 @@ wrongDatum = Datum $ Integer $ BigInt.fromInt 42 testMustSatisfyAnyOf :: Contract () Unit testMustSatisfyAnyOf = do - let wrongDatumHash = Hashing.datumHash wrongDatum - let correctDatumHash = Hashing.datumHash unitDatum let + wrongDatumHash = Hashing.datumHash wrongDatum + correctDatumHash = Hashing.datumHash unitDatum + constraints :: TxConstraints Unit Unit constraints = Constraints.mustSatisfyAnyOf [ Constraints.mustHashDatum wrongDatumHash unitDatum diff --git a/src/Contract/ScriptLookups.purs b/src/Contract/ScriptLookups.purs index 3d34b333bf..7dd71b24c5 100644 --- a/src/Contract/ScriptLookups.purs +++ b/src/Contract/ScriptLookups.purs @@ -37,7 +37,6 @@ import Ctl.Internal.Types.ScriptLookups , CannotConvertPOSIXTimeRange , CannotGetMintingPolicyScriptIndex , CannotGetValidatorHashFromAddress - , MkTypedTxOutFailed , TypedTxOutHasNoDatumHash , CannotHashMintingPolicy , CannotHashValidator diff --git a/src/Contract/Transaction.purs b/src/Contract/Transaction.purs index dc0c61d744..1efe04e9bd 100644 --- a/src/Contract/Transaction.purs +++ b/src/Contract/Transaction.purs @@ -220,7 +220,6 @@ import Ctl.Internal.Types.ScriptLookups , CannotConvertPOSIXTimeRange , CannotGetMintingPolicyScriptIndex , CannotGetValidatorHashFromAddress - , MkTypedTxOutFailed , TypedTxOutHasNoDatumHash , CannotHashMintingPolicy , CannotHashValidator diff --git a/src/Internal/Deserialization/PlutusData.purs b/src/Internal/Deserialization/PlutusData.purs index c2d867176c..820f535a89 100644 --- a/src/Internal/Deserialization/PlutusData.purs +++ b/src/Internal/Deserialization/PlutusData.purs @@ -29,7 +29,7 @@ import Ctl.Internal.Types.CborBytes (CborBytes) import Ctl.Internal.Types.PlutusData ( PlutusData(Constr, Map, List, Integer, Bytes) ) as T -import Data.Maybe (Maybe(Just), fromJust) +import Data.Maybe (Maybe, fromJust) import Data.Newtype (unwrap) import Data.Traversable (traverse) import Data.Tuple (Tuple(Tuple)) @@ -57,12 +57,10 @@ convertPlutusConstr pd = do convertPlutusMap :: PlutusData -> Maybe T.PlutusData convertPlutusMap pd = do - entries <- _PlutusData_map maybeFfiHelper pd >>= - _unpackPlutusMap containerHelper Tuple >>> traverse - \(k /\ v) -> do - let k' = convertPlutusData k - let v' = convertPlutusData v - pure (k' /\ v') + entries <- _PlutusData_map maybeFfiHelper pd <#> + _unpackPlutusMap containerHelper Tuple >>> map + \(k /\ v) -> (convertPlutusData k /\ convertPlutusData v) + pure $ T.Map entries convertPlutusList :: PlutusData -> Maybe T.PlutusData @@ -80,8 +78,7 @@ convertPlutusBytes :: PlutusData -> Maybe T.PlutusData convertPlutusBytes pd = T.Bytes <$> _PlutusData_bytes maybeFfiHelper pd deserializeData :: forall (a :: Type). FromData a => CborBytes -> Maybe a -deserializeData = (fromData <=< (Just <<< convertPlutusData) <=< fromBytes) <<< - unwrap +deserializeData = fromData <=< map convertPlutusData <<< fromBytes <<< unwrap foreign import _PlutusData_constr :: MaybeFfiHelper -> PlutusData -> Maybe ConstrPlutusData diff --git a/src/Internal/Hashing.purs b/src/Internal/Hashing.purs index 86a7a1dbf2..238a122d3b 100644 --- a/src/Internal/Hashing.purs +++ b/src/Internal/Hashing.purs @@ -31,7 +31,6 @@ import Ctl.Internal.Types.ByteArray (ByteArray) import Ctl.Internal.Types.Datum (Datum) import Ctl.Internal.Types.Scripts (PlutusScript) import Ctl.Internal.Types.Transaction (DataHash, TransactionHash) -import Data.Maybe (Maybe) import Data.Newtype (unwrap, wrap) import Untagged.Union (asOneOf) diff --git a/src/Internal/QueryM.purs b/src/Internal/QueryM.purs index 5c22d06f68..cf40370222 100644 --- a/src/Internal/QueryM.purs +++ b/src/Internal/QueryM.purs @@ -185,7 +185,7 @@ import Ctl.Internal.QueryM.ServerConfig , mkWsUrl ) import Ctl.Internal.QueryM.UniqueId (ListenerId) -import Ctl.Internal.Serialization (toBytes) as Serialization +import Ctl.Internal.Serialization (serializeData, toBytes) as Serialization import Ctl.Internal.Serialization.Address ( Address , NetworkId(TestnetId, MainnetId) @@ -196,7 +196,7 @@ import Ctl.Internal.Serialization.Address ) import Ctl.Internal.Serialization.PlutusData (convertPlutusData) as Serialization import Ctl.Internal.Types.ByteArray (byteArrayToHex) -import Ctl.Internal.Types.CborBytes (CborBytes) +import Ctl.Internal.Types.CborBytes (CborBytes, cborBytesToHex) import Ctl.Internal.Types.Chain as Chain import Ctl.Internal.Types.Datum (DataHash, Datum) import Ctl.Internal.Types.PlutusData (PlutusData) @@ -821,33 +821,27 @@ applyArgs script args = Just config -> let ps = map plutusDataToAeson args + + language :: Language + language = snd $ unwrap script + + url :: String + url = mkHttpUrl config <> "apply-args" + + reqBody :: Aeson + reqBody = encodeAeson + $ Object.fromFoldable + [ "script" /\ scriptToAeson script + , "args" /\ encodeAeson ps + ] in - do - let - language :: Language - language = snd $ unwrap script - - url :: String - url = mkHttpUrl config <> "apply-args" - - reqBody :: Aeson - reqBody = encodeAeson - $ Object.fromFoldable - [ "script" /\ scriptToAeson script - , "args" /\ encodeAeson ps - ] - liftAff (postAeson url reqBody) - <#> map (PlutusScript <<< flip Tuple language) <<< - handleAffjaxResponse + liftAff (postAeson url reqBody) + <#> map (PlutusScript <<< flip Tuple language) <<< + handleAffjaxResponse where plutusDataToAeson :: PlutusData -> Aeson plutusDataToAeson = - ( encodeAeson - <<< byteArrayToHex - <<< Serialization.toBytes - <<< asOneOf - ) - <<< Serialization.convertPlutusData + encodeAeson <<< cborBytesToHex <<< Serialization.serializeData -- Checks response status code and returns `ClientError` in case of failure, -- otherwise attempts to decode the result. diff --git a/src/Internal/Serialization.purs b/src/Internal/Serialization.purs index a1b2376fb7..505f05108e 100644 --- a/src/Internal/Serialization.purs +++ b/src/Internal/Serialization.purs @@ -870,8 +870,7 @@ hashScriptData cms rs ps = do -- function, the resulting hash will be wrong case ps of [] -> _hashScriptDataNoDatums rs' cms' - _ -> _hashScriptData rs' cms' =<< - pure (map convertPlutusData ps) + _ -> _hashScriptData rs' cms' $ map convertPlutusData ps serializeData :: forall (a :: Type). ToData a => a -> CborBytes serializeData = wrap <<< toBytes <<< asOneOf <<< convertPlutusData <<< diff --git a/src/Internal/Serialization/PlutusData.purs b/src/Internal/Serialization/PlutusData.purs index b4fbf01cd6..87ca09b549 100644 --- a/src/Internal/Serialization/PlutusData.purs +++ b/src/Internal/Serialization/PlutusData.purs @@ -36,7 +36,7 @@ convertPlutusData x = unsafePartial $ fromJust $ case x of T.Map mp -> Just $ convertPlutusMap mp T.List lst -> Just $ convertPlutusList lst T.Integer n -> convertPlutusInteger n - T.Bytes b -> pure $ _mkPlutusData_bytes b + T.Bytes b -> Just $ _mkPlutusData_bytes b convertConstr :: BigInt.BigInt -> Array T.PlutusData -> Maybe PlutusData convertConstr alt list = diff --git a/src/Internal/Serialization/WitnessSet.purs b/src/Internal/Serialization/WitnessSet.purs index 260710c3f0..32dbeaadae 100644 --- a/src/Internal/Serialization/WitnessSet.purs +++ b/src/Internal/Serialization/WitnessSet.purs @@ -5,7 +5,6 @@ module Ctl.Internal.Serialization.WitnessSet , convertWitnessSet , convertRedeemers , convertRedeemer - , convertPlutusDataEffect , convertRedeemerTag , convertExUnits , convertBootstrap @@ -110,7 +109,7 @@ convertWitnessSet (T.TransactionWitnessSet tws) = do for_ ps (convertPlutusScript >>> addPlutusScript scripts) txWitnessSetSetPlutusScripts ws scripts for_ tws.plutusData - (traverse convertPlutusDataEffect >=> _wsSetPlutusData containerHelper ws) + (map convertPlutusData >>> _wsSetPlutusData containerHelper ws) for_ tws.redeemers (traverse convertRedeemer >=> _wsSetRedeemers containerHelper ws) pure ws @@ -124,13 +123,10 @@ convertRedeemer (T.Redeemer { tag, index, "data": data_, exUnits }) = do tag' <- convertRedeemerTag tag index' <- maybe (throw "Failed to convert redeemer index") pure $ BigNum.fromBigInt index - data' <- convertPlutusDataEffect data_ + let data' = convertPlutusData data_ exUnits' <- convertExUnits exUnits newRedeemer tag' index' data' exUnits' -convertPlutusDataEffect :: PD.PlutusData -> Effect PDS.PlutusData -convertPlutusDataEffect pd = pure $ convertPlutusData pd - convertRedeemerTag :: Tag.RedeemerTag -> Effect RedeemerTag convertRedeemerTag = _newRedeemerTag <<< case _ of Tag.Spend -> "spend" diff --git a/src/Internal/Types/ScriptLookups.purs b/src/Internal/Types/ScriptLookups.purs index 413519b925..1fee35fa26 100644 --- a/src/Internal/Types/ScriptLookups.purs +++ b/src/Internal/Types/ScriptLookups.purs @@ -19,7 +19,6 @@ module Ctl.Internal.Types.ScriptLookups , DatumWrongHash , MintingPolicyHashNotCurrencySymbol , MintingPolicyNotFound - , MkTypedTxOutFailed , ModifyTx , OwnPubKeyAndStakeKeyMissing , TxOutRefNotFound @@ -424,8 +423,7 @@ validatorM = pure <<< validator -- | A script lookups value with a datum. datum :: forall (a :: Type). Datum -> ScriptLookups a datum dt = - Hashing.datumHash dt - # \dh -> over ScriptLookups _ { datums = singleton dh dt } mempty + over ScriptLookups _ { datums = singleton (Hashing.datumHash dt) dt } mempty -- | Add your own `PaymentPubKeyHash` to the lookup. ownPaymentPubKeyHash :: forall (a :: Type). PaymentPubKeyHash -> ScriptLookups a @@ -846,10 +844,10 @@ addOwnOutput (OutputConstraint { datum: d, value }) = do runExceptT do ScriptLookups { typedValidator } <- use _lookups inst <- liftM TypedValidatorMissing typedValidator - let value' = fromPlutusValue value - typedTxOut <- except $ mkTypedTxOut networkId inst d value' - # note MkTypedTxOutFailed - let txOut = typedTxOutTxOut typedTxOut + let + value' = fromPlutusValue value + typedTxOut = mkTypedTxOut networkId inst d value' + txOut = typedTxOutTxOut typedTxOut -- We are erroring if we don't have a datumhash given the polymorphic datum -- in the `OutputConstraint`: dHash <- liftM TypedTxOutHasNoDatumHash (typedTxOutDatumHash typedTxOut) @@ -911,7 +909,6 @@ data MkUnbalancedTxError | DatumWrongHash DataHash Datum | MintingPolicyHashNotCurrencySymbol MintingPolicyHash | MintingPolicyNotFound MintingPolicyHash - | MkTypedTxOutFailed | ModifyTx ModifyTxError | OwnPubKeyAndStakeKeyMissing | TxOutRefNotFound TransactionInput @@ -1240,7 +1237,7 @@ processConstraint mpsMap osMap = do -- Array of datums. datum' <- for mDatum \(dat /\ datp) -> do when (datp == DatumWitness) $ ExceptT $ addDatum dat - outputDatum dat datp + pure $ outputDatum dat datp let address = case skh of Just skh' -> payPubKeyHashBaseAddress networkId pkh skh' @@ -1257,7 +1254,7 @@ processConstraint mpsMap osMap = do networkId <- getNetworkId let amount = fromPlutusValue plutusValue runExceptT do - datum' <- outputDatum dat datp + let datum' = outputDatum dat datp let txOut = TransactionOutput { address: @@ -1453,13 +1450,10 @@ processConstraint mpsMap osMap = do outputDatum :: Datum -> DatumPresence - -> ExceptT - MkUnbalancedTxError - (StateT (ConstraintProcessingState a) (QueryMExtended () Aff)) - OutputDatum + -> OutputDatum outputDatum dat = case _ of - DatumInline -> pure $ OutputDatum dat - DatumWitness -> pure $ OutputDatumHash $ Hashing.datumHash dat + DatumInline -> OutputDatum dat + DatumWitness -> OutputDatumHash $ Hashing.datumHash dat credentialToStakeCredential :: Credential -> StakeCredential credentialToStakeCredential cred = case cred of diff --git a/src/Internal/Types/TypedTxOut.purs b/src/Internal/Types/TypedTxOut.purs index a516374d4f..617a21e10b 100644 --- a/src/Internal/Types/TypedTxOut.purs +++ b/src/Internal/Types/TypedTxOut.purs @@ -172,7 +172,7 @@ mkTypedTxOut -> TypedValidator validator -> datum -> Value - -> Maybe (TypedTxOut validator datum) + -> TypedTxOut validator datum mkTypedTxOut networkId typedVal dt amount = let dHash = Hashing.datumHash $ Datum $ toData dt @@ -180,12 +180,10 @@ mkTypedTxOut networkId typedVal dt amount = -- "validatorAddress" also currently doesn't account for staking. address = typedValidatorEnterpriseAddress networkId typedVal in - Just <<< mkTypedTxOut' dt $ + mkTypedTxOut' dt $ wrap { address , amount - -- TODO: populate properly - -- https://github.com/Plutonomicon/cardano-transaction-lib/issues/691 , datum: OutputDatumHash dHash , scriptRef: Nothing } @@ -271,8 +269,7 @@ typeTxOut void $ checkValidatorAddress networkId typedVal address pd <- ExceptT $ getDatumByHash dHash <#> note (CannotQueryDatum dHash) dtOut <- ExceptT $ checkDatum typedVal pd - except $ - note CannotMakeTypedTxOut (mkTypedTxOut networkId typedVal dtOut amount) + pure $ mkTypedTxOut networkId typedVal dtOut amount -- | Create a `TypedTxOutRef` from an existing `TransactionInput` -- | by checking the types of its parts. To do this we need to cross-reference diff --git a/test/Data.purs b/test/Data.purs index bd64858e18..a98ce2996c 100644 --- a/test/Data.purs +++ b/test/Data.purs @@ -552,7 +552,7 @@ instance (FromData a) => FromData (Tree a) where fromData x = genericFromData x fromBytesFromData :: forall a. FromData a => String -> Maybe a -fromBytesFromData binary = fromData =<< (Just <<< PDD.convertPlutusData) =<< +fromBytesFromData binary = fromData <<< PDD.convertPlutusData =<< fromBytes (hexToByteArrayUnsafe binary) diff --git a/test/Plutip/Contract.purs b/test/Plutip/Contract.purs index cc35473c96..66eaedd837 100644 --- a/test/Plutip/Contract.purs +++ b/test/Plutip/Contract.purs @@ -753,9 +753,10 @@ suite = do awaitTxConfirmed txId logInfo' "Tx submitted successfully, trying to fetch datum from ODC" - let hash1 = datumHash datum1 - let hash2 = datumHash datum2 - let hashes = map datumHash datums + let + hash1 = datumHash datum1 + hash2 = datumHash datum2 + hashes = map datumHash datums actualDatums1 <- getDatumsByHashes hashes actualDatums1 `shouldEqual` Map.fromFoldable diff --git a/test/Serialization.purs b/test/Serialization.purs index b3eecaaa2b..dae71a99e7 100644 --- a/test/Serialization.purs +++ b/test/Serialization.purs @@ -13,13 +13,14 @@ import Ctl.Internal.Deserialization.FromBytes (fromBytes, fromBytesEffect) import Ctl.Internal.Deserialization.Transaction (convertTransaction) as TD import Ctl.Internal.Helpers (liftM) import Ctl.Internal.Serialization (convertTransaction) as TS -import Ctl.Internal.Serialization (convertTxOutput, toBytes) +import Ctl.Internal.Serialization (convertTxOutput, serializeData, toBytes) import Ctl.Internal.Serialization.Keys (bytesFromPublicKey) import Ctl.Internal.Serialization.PlutusData (convertPlutusData) import Ctl.Internal.Serialization.Types (TransactionHash) import Ctl.Internal.Test.TestPlanM (TestPlanM) import Ctl.Internal.Types.BigNum (fromString) as BN import Ctl.Internal.Types.ByteArray (byteArrayToHex, hexToByteArrayUnsafe) +import Ctl.Internal.Types.CborBytes (cborBytesToHex) import Ctl.Internal.Types.PlutusData as PD import Data.BigInt as BigInt import Data.Either (hush) @@ -113,10 +114,8 @@ suite = do test "PlutusData #6 - Integer 0 (regression to https://github.com/Plutonomicon/cardano-transaction-lib/issues/488 ?)" $ do - let - datum = convertPlutusData $ PD.Integer (BigInt.fromInt 0) - let bytes = toBytes (asOneOf datum) - byteArrayToHex bytes `shouldEqual` "00" + let bytes = serializeData $ PD.Integer (BigInt.fromInt 0) + cborBytesToHex bytes `shouldEqual` "00" test "TransactionOutput serialization" $ liftEffect do txo <- convertTxOutput txOutputFixture1 let bytes = toBytes (asOneOf txo) From f18bac23c9fc71a3f5ae1b0f9be2a57eeae9248a Mon Sep 17 00:00:00 2001 From: Calum Sieppert Date: Tue, 6 Dec 2022 17:44:45 -0700 Subject: [PATCH 059/373] Don't export `Address.purs`'s `toBytes` equivalents --- src/Internal/Serialization/Address.purs | 3 --- src/Internal/Serialization/ToBytes.purs | 8 +++++++- src/Internal/Wallet/Cip30/SignData.purs | 6 +++--- test/Serialization/Address.purs | 9 ++++----- test/Wallet/Cip30/SignData.purs | 4 ++-- 5 files changed, 16 insertions(+), 14 deletions(-) diff --git a/src/Internal/Serialization/Address.purs b/src/Internal/Serialization/Address.purs index 7de32661f3..af73748fa5 100644 --- a/src/Internal/Serialization/Address.purs +++ b/src/Internal/Serialization/Address.purs @@ -11,14 +11,12 @@ module Ctl.Internal.Serialization.Address , PointerAddress , RewardAddress , StakeCredential - , addressBytes , addressBech32 , addressNetworkId , intToNetworkId , keyHashCredential , scriptHashCredential , withStakeCredential - , stakeCredentialToBytes , baseAddress , baseAddressPaymentCred , baseAddressDelegationCred @@ -46,7 +44,6 @@ module Ctl.Internal.Serialization.Address , byronAddressToBase58 , byronAddressFromBase58 , byronAddressFromBytes - , byronAddressBytes , byronProtocolMagic , byronAddressAttributes , byronAddressNetworkId diff --git a/src/Internal/Serialization/ToBytes.purs b/src/Internal/Serialization/ToBytes.purs index e6244e1147..552f7f3e3d 100644 --- a/src/Internal/Serialization/ToBytes.purs +++ b/src/Internal/Serialization/ToBytes.purs @@ -4,7 +4,11 @@ module Ctl.Internal.Serialization.ToBytes import Prelude -import Ctl.Internal.Serialization.Address (Address) +import Ctl.Internal.Serialization.Address + ( Address + , ByronAddress + , StakeCredential + ) import Ctl.Internal.Serialization.Hash (Ed25519KeyHash, ScriptHash, VRFKeyHash) import Ctl.Internal.Serialization.Types ( AuxiliaryDataHash @@ -33,6 +37,7 @@ import Untagged.Union (type (|+|)) type SerializationData = Address |+| AuxiliaryDataHash + |+| ByronAddress |+| DataHash |+| Ed25519KeyHash |+| Ed25519Signature @@ -45,6 +50,7 @@ type SerializationData = Address |+| Redeemers |+| ScriptDataHash |+| ScriptHash + |+| StakeCredential |+| Transaction |+| TransactionBody |+| TransactionHash diff --git a/src/Internal/Wallet/Cip30/SignData.purs b/src/Internal/Wallet/Cip30/SignData.purs index b47c70a0c2..b7c8741c4b 100644 --- a/src/Internal/Wallet/Cip30/SignData.purs +++ b/src/Internal/Wallet/Cip30/SignData.purs @@ -2,11 +2,12 @@ module Ctl.Internal.Wallet.Cip30.SignData (signData) where import Prelude -import Ctl.Internal.Serialization.Address (Address, addressBytes) +import Ctl.Internal.Serialization.Address (Address) import Ctl.Internal.Serialization.Keys ( bytesFromPublicKey , publicKeyFromPrivateKey ) +import Ctl.Internal.Serialization.ToBytes (toBytes) import Ctl.Internal.Serialization.Types (PrivateKey) import Ctl.Internal.Types.ByteArray (ByteArray) import Ctl.Internal.Types.CborBytes (CborBytes(CborBytes)) @@ -72,6 +73,5 @@ signData privatePaymentKey address (RawBytes payload) = protectedHeaders = do headerMap <- newHeaderMap setAlgHeaderToEdDsa headerMap - setAddressHeader (addressBytes address) headerMap + setAddressHeader (toBytes address) headerMap pure $ newProtectedHeaderMap headerMap - diff --git a/test/Serialization/Address.purs b/test/Serialization/Address.purs index 7a08b17fb6..aec7f1207d 100644 --- a/test/Serialization/Address.purs +++ b/test/Serialization/Address.purs @@ -6,7 +6,6 @@ import Contract.Address (addressWithNetworkTagFromBech32) import Ctl.Internal.Serialization.Address ( NetworkId(MainnetId, TestnetId) , addressBech32 - , addressBytes , addressFromBech32 , addressFromBytes , addressNetworkId @@ -31,7 +30,6 @@ import Ctl.Internal.Serialization.Address , rewardAddressToAddress , scriptHashCredential , stakeCredentialFromBytes - , stakeCredentialToBytes , stakeCredentialToKeyHash , stakeCredentialToScriptHash ) @@ -41,6 +39,7 @@ import Ctl.Internal.Serialization.Hash , ed25519KeyHashFromBech32 , scriptHashFromBytes ) +import Ctl.Internal.Serialization.ToBytes (toBytes) import Ctl.Internal.Test.TestPlanM (TestPlanM) import Ctl.Internal.Types.Aliases (Bech32String) import Ctl.Internal.Types.BigNum (fromInt, fromStringUnsafe) as BigNum @@ -81,7 +80,7 @@ addressFunctionsTest = test "Address tests" $ do addressFromBech32 bechstr bechstr `shouldEqual` addressBech32 addr1 addressFromBech32 "randomstuff" `shouldEqual` Nothing - let addrBts = addressBytes addr1 + let addrBts = toBytes addr1 addr2 <- errMaybe "addressFromBech32 failed on valid bech32" $ addressFromBytes addrBts addr2 `shouldEqual` addr1 @@ -103,8 +102,8 @@ stakeCredentialTests = test "StakeCredential tests" $ do let pkhCred = keyHashCredential $ pkh schCred = scriptHashCredential $ scrh - pkhCredBytes = stakeCredentialToBytes pkhCred - schCredBytes = stakeCredentialToBytes schCred + pkhCredBytes = toBytes pkhCred + schCredBytes = toBytes schCred pkhCred2 <- errMaybe "stakeCredentialFromBytes failed on valid bytes" $ stakeCredentialFromBytes diff --git a/test/Wallet/Cip30/SignData.purs b/test/Wallet/Cip30/SignData.purs index 99e629d6d1..cc2fd0c03c 100644 --- a/test/Wallet/Cip30/SignData.purs +++ b/test/Wallet/Cip30/SignData.purs @@ -13,13 +13,13 @@ import Ctl.Internal.FfiHelpers (MaybeFfiHelper, maybeFfiHelper) import Ctl.Internal.Serialization.Address ( Address , NetworkId(MainnetId) - , addressBytes , intToNetworkId ) import Ctl.Internal.Serialization.Keys ( bytesFromPublicKey , publicKeyFromPrivateKey ) +import Ctl.Internal.Serialization.ToBytes (toBytes) import Ctl.Internal.Serialization.Types (PrivateKey, PublicKey) import Ctl.Internal.Test.TestPlanM (TestPlanM) import Ctl.Internal.Types.ByteArray (byteArrayFromIntArrayUnsafe) @@ -103,7 +103,7 @@ checkCip30SignDataResponse address { key, signature } = do assertTrue "COSE_Sign1's \"address\" header must be set to address bytes" ( getCoseSign1ProtectedHeaderAddress coseSign1 - == Just (addressBytes address) + == Just (toBytes address) ) checkCoseKeyHeaders :: COSEKey -> Aff Unit From e93d244ec78d30d0a1edfe37256b0fc408d5b91b Mon Sep 17 00:00:00 2001 From: Calum Sieppert Date: Tue, 6 Dec 2022 19:40:33 -0700 Subject: [PATCH 060/373] Don't export `Address.purs`'s `fromBytes` equivalents --- src/Internal/Deserialization/FromBytes.purs | 12 +++++++++++- src/Internal/QueryM/Kupo.purs | 3 +-- src/Internal/Serialization/Address.purs | 3 --- src/Internal/Wallet/Cip30.purs | 3 +-- test/Serialization/Address.purs | 15 ++++++--------- 5 files changed, 19 insertions(+), 17 deletions(-) diff --git a/src/Internal/Deserialization/FromBytes.purs b/src/Internal/Deserialization/FromBytes.purs index 39d57623cc..391a789a15 100644 --- a/src/Internal/Deserialization/FromBytes.purs +++ b/src/Internal/Deserialization/FromBytes.purs @@ -10,7 +10,11 @@ import Prelude import Ctl.Internal.Deserialization.Error (FromBytesError, fromBytesErrorHelper) import Ctl.Internal.Error (E) import Ctl.Internal.FfiHelpers (ErrorFfiHelper) -import Ctl.Internal.Serialization.Address (Address) +import Ctl.Internal.Serialization.Address + ( Address + , ByronAddress + , StakeCredential + ) import Ctl.Internal.Serialization.Hash (Ed25519KeyHash, ScriptHash, VRFKeyHash) import Ctl.Internal.Serialization.Types ( AuxiliaryDataHash @@ -52,6 +56,9 @@ instance FromBytes Address where instance FromBytes AuxiliaryDataHash where fromBytes' = _fromBytes "AuxiliaryDataHash" fromBytesErrorHelper +instance FromBytes ByronAddress where + fromBytes' = _fromBytes "ByronAddress" fromBytesErrorHelper + instance FromBytes DataHash where fromBytes' = _fromBytes "DataHash" fromBytesErrorHelper @@ -91,6 +98,9 @@ instance FromBytes ScriptDataHash where instance FromBytes ScriptHash where fromBytes' = _fromBytes "ScriptHash" fromBytesErrorHelper +instance FromBytes StakeCredential where + fromBytes' = _fromBytes "StakeCredential" fromBytesErrorHelper + instance FromBytes Transaction where fromBytes' = _fromBytes "Transaction" fromBytesErrorHelper diff --git a/src/Internal/QueryM/Kupo.purs b/src/Internal/QueryM/Kupo.purs index fb7a26bb8f..4f9dbb9c17 100644 --- a/src/Internal/QueryM/Kupo.purs +++ b/src/Internal/QueryM/Kupo.purs @@ -54,7 +54,6 @@ import Ctl.Internal.Serialization.Address ( Address , addressBech32 , addressFromBech32 - , addressFromBytes ) import Ctl.Internal.Serialization.Hash (ScriptHash) import Ctl.Internal.Types.ByteArray (ByteArray, byteArrayToHex, hexToByteArray) @@ -176,7 +175,7 @@ instance DecodeAeson KupoTransactionOutput where decodeAddress obj = getField obj "address" >>= \x -> note (TypeMismatch "Expected bech32 or base16 encoded Shelley address") - (addressFromBech32 x <|> (addressFromBytes =<< hexToCborBytes x)) + (addressFromBech32 x <|> (fromBytes =<< hexToCborBytes x)) decodeDatumHash :: Object Aeson diff --git a/src/Internal/Serialization/Address.purs b/src/Internal/Serialization/Address.purs index af73748fa5..d6ce9371b7 100644 --- a/src/Internal/Serialization/Address.purs +++ b/src/Internal/Serialization/Address.purs @@ -30,8 +30,6 @@ module Ctl.Internal.Serialization.Address , NetworkId(MainnetId, TestnetId) , stakeCredentialToKeyHash , stakeCredentialToScriptHash - , stakeCredentialFromBytes - , addressFromBytes , addressFromBech32 , addressPaymentCred , addressStakeCred @@ -43,7 +41,6 @@ module Ctl.Internal.Serialization.Address , baseAddressNetworkId , byronAddressToBase58 , byronAddressFromBase58 - , byronAddressFromBytes , byronProtocolMagic , byronAddressAttributes , byronAddressNetworkId diff --git a/src/Internal/Wallet/Cip30.purs b/src/Internal/Wallet/Cip30.purs index 8104ce1027..605532fd5e 100644 --- a/src/Internal/Wallet/Cip30.purs +++ b/src/Internal/Wallet/Cip30.purs @@ -27,7 +27,6 @@ import Ctl.Internal.FfiHelpers (MaybeFfiHelper, maybeFfiHelper) import Ctl.Internal.Serialization (convertTransaction, toBytes) as Serialization import Ctl.Internal.Serialization.Address ( Address - , addressFromBytes , baseAddressBytes , baseAddressFromAddress , enterpriseAddressBytes @@ -145,7 +144,7 @@ getWalletAddresses conn = Promise.toAffE (_getAddresses conn) <#> hexStringToAddress :: String -> Maybe Address hexStringToAddress = - ((addressFromBytes <<< rawBytesAsCborBytes) <=< hexToRawBytes) + ((fromBytes <<< rawBytesAsCborBytes) <=< hexToRawBytes) -- | Get collateral using CIP-30 `getCollateral` method. -- | Throws on `Promise` rejection by wallet, returns `Nothing` if no collateral diff --git a/test/Serialization/Address.purs b/test/Serialization/Address.purs index aec7f1207d..a67c88d9e1 100644 --- a/test/Serialization/Address.purs +++ b/test/Serialization/Address.purs @@ -3,11 +3,11 @@ module Test.Ctl.Serialization.Address (suite) where import Prelude import Contract.Address (addressWithNetworkTagFromBech32) +import Ctl.Internal.Deserialization.FromBytes (fromBytes) import Ctl.Internal.Serialization.Address ( NetworkId(MainnetId, TestnetId) , addressBech32 , addressFromBech32 - , addressFromBytes , addressNetworkId , baseAddressDelegationCred , baseAddressFromAddress @@ -29,7 +29,6 @@ import Ctl.Internal.Serialization.Address , rewardAddressPaymentCred , rewardAddressToAddress , scriptHashCredential - , stakeCredentialFromBytes , stakeCredentialToKeyHash , stakeCredentialToScriptHash ) @@ -82,7 +81,7 @@ addressFunctionsTest = test "Address tests" $ do addressFromBech32 "randomstuff" `shouldEqual` Nothing let addrBts = toBytes addr1 addr2 <- errMaybe "addressFromBech32 failed on valid bech32" $ - addressFromBytes addrBts + fromBytes addrBts addr2 `shouldEqual` addr1 addressNetworkId addr2 `shouldEqual` MainnetId testnetAddr <- @@ -105,17 +104,15 @@ stakeCredentialTests = test "StakeCredential tests" $ do pkhCredBytes = toBytes pkhCred schCredBytes = toBytes schCred - pkhCred2 <- errMaybe "stakeCredentialFromBytes failed on valid bytes" $ - stakeCredentialFromBytes - pkhCredBytes + pkhCred2 <- errMaybe "StakeCredential FromBytes failed on valid bytes" $ + fromBytes pkhCredBytes pkh2 <- errMaybe "stakeCredentialToKeyHash failed" $ stakeCredentialToKeyHash pkhCred2 pkh2 `shouldEqual` pkh stakeCredentialToScriptHash pkhCred2 `shouldEqual` Nothing - schCred2 <- errMaybe "takeCredentialFromBytes failed on valid bytes" $ - stakeCredentialFromBytes - schCredBytes + schCred2 <- errMaybe "StakeCredential FromBytes failed on valid bytes" $ + fromBytes schCredBytes sch2 <- errMaybe "stakeCredentialToScriptHash failed" $ stakeCredentialToScriptHash schCred2 sch2 `shouldEqual` scrh From 7094a4eb406eff9dd85b1bacdb2e45bafa685a38 Mon Sep 17 00:00:00 2001 From: Calum Sieppert Date: Tue, 6 Dec 2022 21:21:49 -0700 Subject: [PATCH 061/373] Remove todo comments and cleanup --- src/Internal/Hashing.purs | 3 +-- src/Internal/QueryM/Pools.purs | 6 ------ test/Serialization/Hash.purs | 5 ++--- 3 files changed, 3 insertions(+), 11 deletions(-) diff --git a/src/Internal/Hashing.purs b/src/Internal/Hashing.purs index 79add6ac1b..ce3cf696bf 100644 --- a/src/Internal/Hashing.purs +++ b/src/Internal/Hashing.purs @@ -56,8 +56,7 @@ datumHash :: Datum -> Maybe DataHash datumHash = map (wrap <<< unwrap <<< toBytes <<< hashPlutusData) <<< convertPlutusData - <<< - unwrap + <<< unwrap -- | Calculates the hash of the transaction by applying `blake2b256Hash` to -- | the cbor-encoded transaction body. diff --git a/src/Internal/QueryM/Pools.purs b/src/Internal/QueryM/Pools.purs index df5400fbe8..69519f261e 100644 --- a/src/Internal/QueryM/Pools.purs +++ b/src/Internal/QueryM/Pools.purs @@ -80,9 +80,6 @@ getValidatorHashDelegationsAndRewards skh = do stringRep :: String stringRep = scriptHashToBech32Unsafe "script" $ unwrap skh - -- byteHex :: String - -- byteHex = byteArrayToHex $ unwrap $ toBytes $ unwrap skh - sh :: ScriptHash sh = unwrap skh @@ -102,9 +99,6 @@ getPubKeyHashDelegationsAndRewards pkh = do stringRep = ed25519KeyHashToBech32Unsafe "stake_vkh" $ unwrap $ unwrap pkh - -- byteHex :: String - -- byteHex = byteArrayToHex $ unwrap $ toBytes $ unwrap $ unwrap pkh - ed :: Ed25519KeyHash ed = unwrap $ unwrap pkh diff --git a/test/Serialization/Hash.purs b/test/Serialization/Hash.purs index 05638f255b..bef8dc102d 100644 --- a/test/Serialization/Hash.purs +++ b/test/Serialization/Hash.purs @@ -21,6 +21,7 @@ import Data.Maybe (Maybe(Just, Nothing), isNothing) import Data.Newtype (unwrap) import Data.Unit (Unit) import Effect.Aff (Aff) +import Mote (test) import Test.Ctl.Utils (assertTrue, errMaybe) pkhBech32 :: Bech32String @@ -33,7 +34,7 @@ invalidBech32 :: Bech32String invalidBech32 = "addr_vkh1zuctrdcq6ctd29242w8g8444z0q38t2lnv3zzf44fqktx044444" suite :: TestPlanM (Aff Unit) Unit -suite = do +suite = test "Serialization.Hash" do assertTrue "ed25519KeyHashFromBech32 returns Nothing on random string" (isNothing $ ed25519KeyHashFromBech32 invalidBech32) @@ -43,7 +44,6 @@ suite = do pkhB32 = ed25519KeyHashToBech32Unsafe "addr_vkh" pkh mPkhB32 = ed25519KeyHashToBech32 "addr_vkh" pkh pkhBts = toBytes pkh - -- TODO: use fromBytes instead? pkh2 = ed25519KeyHashFromBytes $ unwrap pkhBts assertTrue @@ -73,7 +73,6 @@ suite = do scrhB32 = scriptHashToBech32Unsafe "stake_vkh" scrh mScrhB32 = scriptHashToBech32 "stake_vkh" scrh scrhBts = toBytes scrh - -- TODO: use fromBytes instead? scrhFromBytes = scriptHashFromBytes $ unwrap scrhBts scrhFromBech = scriptHashFromBech32 scrhB32 From f4220a40f86218cf189524201036ba9c06b342a0 Mon Sep 17 00:00:00 2001 From: Calum Sieppert Date: Tue, 6 Dec 2022 21:54:50 -0700 Subject: [PATCH 062/373] Reduce repetition in FromBytes --- src/Internal/Deserialization/FromBytes.purs | 57 ++++++++++++--------- 1 file changed, 32 insertions(+), 25 deletions(-) diff --git a/src/Internal/Deserialization/FromBytes.purs b/src/Internal/Deserialization/FromBytes.purs index 391a789a15..ebad87837b 100644 --- a/src/Internal/Deserialization/FromBytes.purs +++ b/src/Internal/Deserialization/FromBytes.purs @@ -51,79 +51,79 @@ class FromBytes a where fromBytes' :: forall (r :: Row Type). ByteArray -> E (FromBytesError + r) a instance FromBytes Address where - fromBytes' = _fromBytes "Address" fromBytesErrorHelper + fromBytes' = fromBytes'' "Address" instance FromBytes AuxiliaryDataHash where - fromBytes' = _fromBytes "AuxiliaryDataHash" fromBytesErrorHelper + fromBytes' = fromBytes'' "AuxiliaryDataHash" instance FromBytes ByronAddress where - fromBytes' = _fromBytes "ByronAddress" fromBytesErrorHelper + fromBytes' = fromBytes'' "ByronAddress" instance FromBytes DataHash where - fromBytes' = _fromBytes "DataHash" fromBytesErrorHelper + fromBytes' = fromBytes'' "DataHash" instance FromBytes Ed25519KeyHash where - fromBytes' = _fromBytes "Ed25519KeyHash" fromBytesErrorHelper + fromBytes' = fromBytes'' "Ed25519KeyHash" instance FromBytes Ed25519Signature where - fromBytes' = _fromBytes "Ed25519Signature" fromBytesErrorHelper + fromBytes' = fromBytes'' "Ed25519Signature" instance FromBytes GenesisDelegateHash where - fromBytes' = _fromBytes "GenesisDelegateHash" fromBytesErrorHelper + fromBytes' = fromBytes'' "GenesisDelegateHash" instance FromBytes GenesisHash where - fromBytes' = _fromBytes "GenesisHash" fromBytesErrorHelper + fromBytes' = fromBytes'' "GenesisHash" instance FromBytes Mint where - fromBytes' = _fromBytes "Mint" fromBytesErrorHelper + fromBytes' = fromBytes'' "Mint" instance FromBytes NativeScript where - fromBytes' = _fromBytes "NativeScript" fromBytesErrorHelper + fromBytes' = fromBytes'' "NativeScript" instance FromBytes PlutusData where - fromBytes' = _fromBytes "PlutusData" fromBytesErrorHelper + fromBytes' = fromBytes'' "PlutusData" instance FromBytes PoolMetadataHash where - fromBytes' = _fromBytes "PoolMetadataHash" fromBytesErrorHelper + fromBytes' = fromBytes'' "PoolMetadataHash" instance FromBytes PublicKey where - fromBytes' = _fromBytes "PublicKey" fromBytesErrorHelper + fromBytes' = fromBytes'' "PublicKey" instance FromBytes Redeemers where - fromBytes' = _fromBytes "Redeemers" fromBytesErrorHelper + fromBytes' = fromBytes'' "Redeemers" instance FromBytes ScriptDataHash where - fromBytes' = _fromBytes "ScriptDataHash" fromBytesErrorHelper + fromBytes' = fromBytes'' "ScriptDataHash" instance FromBytes ScriptHash where - fromBytes' = _fromBytes "ScriptHash" fromBytesErrorHelper + fromBytes' = fromBytes'' "ScriptHash" instance FromBytes StakeCredential where - fromBytes' = _fromBytes "StakeCredential" fromBytesErrorHelper + fromBytes' = fromBytes'' "StakeCredential" instance FromBytes Transaction where - fromBytes' = _fromBytes "Transaction" fromBytesErrorHelper + fromBytes' = fromBytes'' "Transaction" instance FromBytes TransactionBody where - fromBytes' = _fromBytes "TransactionBody" fromBytesErrorHelper + fromBytes' = fromBytes'' "TransactionBody" instance FromBytes TransactionHash where - fromBytes' = _fromBytes "TransactionHash" fromBytesErrorHelper + fromBytes' = fromBytes'' "TransactionHash" instance FromBytes TransactionOutput where - fromBytes' = _fromBytes "TransactionOutput" fromBytesErrorHelper + fromBytes' = fromBytes'' "TransactionOutput" instance FromBytes TransactionUnspentOutput where - fromBytes' = _fromBytes "TransactionUnspentOutput" fromBytesErrorHelper + fromBytes' = fromBytes'' "TransactionUnspentOutput" instance FromBytes TransactionWitnessSet where - fromBytes' = _fromBytes "TransactionWitnessSet" fromBytesErrorHelper + fromBytes' = fromBytes'' "TransactionWitnessSet" instance FromBytes Value where - fromBytes' = _fromBytes "Value" fromBytesErrorHelper + fromBytes' = fromBytes'' "Value" instance FromBytes VRFKeyHash where - fromBytes' = _fromBytes "VRFKeyHash" fromBytesErrorHelper + fromBytes' = fromBytes'' "VRFKeyHash" -- for backward compatibility until `Maybe` is abandoned. Then to be renamed. fromBytes :: forall (a :: Type). FromBytes a => CborBytes -> Maybe a @@ -135,6 +135,13 @@ fromBytesEffect bytes = Nothing -> throw "from_bytes() call failed" Just a -> pure a +fromBytes'' + :: forall (r :: Row Type) (a :: Type) + . String + -> ByteArray + -> E (FromBytesError + r) a +fromBytes'' = flip _fromBytes fromBytesErrorHelper + ---- Foreign imports foreign import _fromBytes From 6e6a5f19f4d663d4c1bb647222dc4a31fc54ab2d Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Wed, 7 Dec 2022 12:46:02 +0000 Subject: [PATCH 063/373] Remove submitE. remove/address some TODOs. Make exports explicit. --- src/Contract/Transaction.purs | 12 +-- src/Internal/BalanceTx/BalanceTx.purs | 7 +- src/Internal/Contract/Monad.purs | 24 +++-- src/Internal/Contract/QueryBackend.purs | 2 - src/Internal/Contract/QueryHandle.purs | 23 +++-- src/Internal/Contract/Sign.purs | 8 +- src/Internal/Contract/Wallet.purs | 112 ++++++++++-------------- src/Internal/QueryM.purs | 40 +-------- src/Internal/Wallet.purs | 39 +++++---- src/Internal/Wallet/Cip30Mock.purs | 11 ++- test/Integration.purs | 1 - test/QueryM/AffInterface.purs | 14 +-- 12 files changed, 113 insertions(+), 180 deletions(-) diff --git a/src/Contract/Transaction.purs b/src/Contract/Transaction.purs index 30eb248c89..13b2c896b0 100644 --- a/src/Contract/Transaction.purs +++ b/src/Contract/Transaction.purs @@ -31,7 +31,6 @@ module Contract.Transaction , reindexSpentScriptRedeemers , signTransaction , submit - , submitE , withBalancedTx , withBalancedTxWithConstraints , withBalancedTxs @@ -40,7 +39,7 @@ module Contract.Transaction import Prelude -import Aeson (class EncodeAeson, Aeson) +import Aeson (class EncodeAeson) import Contract.Monad ( Contract , liftContractM @@ -48,7 +47,6 @@ import Contract.Monad , liftedM , runContractInEnv ) -import Contract.Prelude (undefined) import Control.Monad.Error.Class (catchError, throwError) import Control.Monad.Reader (ReaderT, asks, runReaderT) import Control.Monad.Reader.Class (ask) @@ -295,14 +293,6 @@ submit tx = do queryHandle <- getQueryHandle liftedM "Failed to submit tx" $ liftAff $ queryHandle.submitTx $ unwrap tx --- | Like `submit` except when Ogmios sends a SubmitFail the error is returned --- | as an Array of Aesons. -submitE - :: BalancedSignedTransaction - -> Contract (Either (Array Aeson) TransactionHash) -submitE = -- TODO - undefined - -- | Calculate the minimum transaction fee. calculateMinFee :: Transaction diff --git a/src/Internal/BalanceTx/BalanceTx.purs b/src/Internal/BalanceTx/BalanceTx.purs index 2b7313ad93..701beaac5f 100644 --- a/src/Internal/BalanceTx/BalanceTx.purs +++ b/src/Internal/BalanceTx/BalanceTx.purs @@ -104,13 +104,10 @@ import Ctl.Internal.Cardano.Types.Value , posNonAdaAsset , valueToCoin' ) -import Ctl.Internal.Contract.Monad (Contract) +import Ctl.Internal.Contract.Monad (Contract, filterLockedUtxos) import Ctl.Internal.Contract.QueryHandle (getQueryHandle) -import Ctl.Internal.Contract.Wallet - ( filterLockedUtxos - , getWalletCollateral - ) import Ctl.Internal.Contract.Wallet (getChangeAddress, getWalletAddresses) as Contract +import Ctl.Internal.Contract.Wallet (getWalletCollateral) import Ctl.Internal.Serialization.Address ( Address , addressPaymentCred diff --git a/src/Internal/Contract/Monad.purs b/src/Internal/Contract/Monad.purs index bc4309e133..57096e351b 100644 --- a/src/Internal/Contract/Monad.purs +++ b/src/Internal/Contract/Monad.purs @@ -12,6 +12,7 @@ module Ctl.Internal.Contract.Monad , withContractEnv , buildBackend , getLedgerConstants + , filterLockedUtxos ) where import Prelude @@ -25,7 +26,7 @@ import Control.Monad.Error.Class ) import Control.Monad.Logger.Class (class MonadLogger) import Control.Monad.Reader.Class (class MonadAsk, class MonadReader, ask, asks) -import Control.Monad.Reader.Trans (ReaderT, runReaderT) +import Control.Monad.Reader.Trans (ReaderT, runReaderT, withReaderT) import Control.Monad.Rec.Class (class MonadRec) import Control.Parallel ( class Parallel @@ -35,6 +36,7 @@ import Control.Parallel , sequential ) import Control.Plus (class Plus) +import Ctl.Internal.Cardano.Types.Transaction (UtxoMap) import Ctl.Internal.Contract.Hooks (Hooks) import Ctl.Internal.Contract.QueryBackend ( CtlBackend @@ -45,7 +47,7 @@ import Ctl.Internal.Contract.QueryBackend , defaultBackend , lookupBackend ) -import Ctl.Internal.Helpers (liftM, logWithLevel) +import Ctl.Internal.Helpers (filterMapWithKeyM, liftM, logWithLevel) import Ctl.Internal.JsWebSocket (_wsClose, _wsFinalize) import Ctl.Internal.Logging (Logger, mkLogger, setupLogs) import Ctl.Internal.QueryM @@ -58,14 +60,14 @@ import Ctl.Internal.QueryM , mkOgmiosWebSocketAff , underlyingWebSocket ) --- TOD Move/translate these types into Cardano +-- TODO Move/translate these types into Cardano import Ctl.Internal.QueryM.Ogmios ( ProtocolParameters , SystemStart ) as Ogmios import Ctl.Internal.QueryM.ServerConfig (ServerConfig) import Ctl.Internal.Serialization.Address (NetworkId) -import Ctl.Internal.Types.UsedTxOuts (UsedTxOuts, newUsedTxOuts) +import Ctl.Internal.Types.UsedTxOuts (UsedTxOuts, isTxOutRefUsed, newUsedTxOuts) import Ctl.Internal.Wallet (Wallet) import Ctl.Internal.Wallet (getNetworkId) as Wallet import Ctl.Internal.Wallet.Spec (WalletSpec, mkWalletBySpec) @@ -228,8 +230,6 @@ buildBackend buildBackend logger = parTraverse case _ of CtlBackendParams { ogmiosConfig, kupoConfig, odcConfig } -> do datumCacheWsRef <- liftEffect $ Ref.new Nothing - -- TODO Check the network in env matches up with the network of odc, ogmios and kupo - -- Need to pass in the networkid sequential ado odcWs <- parallel $ mkDatumCacheWebSocketAff datumCacheWsRef logger odcConfig @@ -386,3 +386,15 @@ mkQueryEnv contractEnv ctlBackend = , extraConfig: {} } +-------------------------------------------------------------------------------- +-- Helpers +-------------------------------------------------------------------------------- + +filterLockedUtxos :: UtxoMap -> Contract UtxoMap +filterLockedUtxos utxos = + withTxRefsCache $ + flip filterMapWithKeyM utxos + (\k _ -> not <$> isTxOutRefUsed (unwrap k)) + +withTxRefsCache :: forall (a :: Type). ReaderT UsedTxOuts Aff a -> Contract a +withTxRefsCache = Contract <<< withReaderT _.usedTxOuts diff --git a/src/Internal/Contract/QueryBackend.purs b/src/Internal/Contract/QueryBackend.purs index 249014896f..226e991f8b 100644 --- a/src/Internal/Contract/QueryBackend.purs +++ b/src/Internal/Contract/QueryBackend.purs @@ -33,8 +33,6 @@ import Effect.Exception (throw) -- | A generic type to represent a choice of backend with a set of fallback -- | backends when an operation is not supported by the default. --- TODO Should this just be a list? --- How do operations decide on what backend to use? data QueryBackends (backend :: Type) = QueryBackends backend (Map QueryBackendLabel backend) diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs index 51ae38763e..0002e4ecce 100644 --- a/src/Internal/Contract/QueryHandle.purs +++ b/src/Internal/Contract/QueryHandle.purs @@ -1,4 +1,8 @@ -module Ctl.Internal.Contract.QueryHandle where +module Ctl.Internal.Contract.QueryHandle + ( getQueryHandle + , QueryHandle + , AffE + ) where import Prelude @@ -57,7 +61,8 @@ import Effect.Class (liftEffect) import Undefined (undefined) import Untagged.Union (asOneOf) --- Why ClientError? +-- TODO Either move ClientError out of QueryM or make a new error type +-- and convert from ClientError. type AffE (a :: Type) = Aff (Either ClientError a) type QueryHandle = @@ -78,17 +83,9 @@ type QueryHandle = } getQueryHandle :: Contract QueryHandle -getQueryHandle = - ask <#> \contractEnv -> - case defaultBackend contractEnv.backend of - CtlBackend backend -> - queryHandleForCtlBackend contractEnv backend - BlockfrostBackend backend -> - queryHandleForBlockfrostBackend contractEnv backend - -getQueryHandle' :: ContractEnv -> QueryHandle -getQueryHandle' contractEnv = - case defaultBackend contractEnv.backend of +getQueryHandle = do + contractEnv <- ask + pure case defaultBackend contractEnv.backend of CtlBackend backend -> queryHandleForCtlBackend contractEnv backend BlockfrostBackend backend -> diff --git a/src/Internal/Contract/Sign.purs b/src/Internal/Contract/Sign.purs index 84483556ec..008e7b5f99 100644 --- a/src/Internal/Contract/Sign.purs +++ b/src/Internal/Contract/Sign.purs @@ -10,14 +10,16 @@ import Ctl.Internal.Cardano.Types.Transaction as Transaction import Ctl.Internal.Contract.Monad (Contract) import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.Contract.Wallet - ( callCip30Wallet - , getWalletAddresses + ( getWalletAddresses , getWalletUtxos , withWallet ) import Ctl.Internal.Helpers (liftedM) import Ctl.Internal.Types.Transaction (TransactionInput) -import Ctl.Internal.Wallet (Wallet(KeyWallet, Lode, Eternl, Flint, Gero, Nami)) +import Ctl.Internal.Wallet + ( Wallet(KeyWallet, Lode, Eternl, Flint, Gero, Nami) + , callCip30Wallet + ) import Data.Array (elem, fromFoldable) import Data.Either (hush) import Data.Lens ((<>~)) diff --git a/src/Internal/Contract/Wallet.purs b/src/Internal/Contract/Wallet.purs index ff990cc41d..5ecb47972a 100644 --- a/src/Internal/Contract/Wallet.purs +++ b/src/Internal/Contract/Wallet.purs @@ -1,18 +1,32 @@ -module Ctl.Internal.Contract.Wallet where +module Ctl.Internal.Contract.Wallet + ( getUnusedAddresses + , getChangeAddress + , getRewardAddresses + , getWalletAddresses + , signData + , getWallet + , getNetworkId + , ownPubKeyHashes + , ownPaymentPubKeyHashes + , ownStakePubKeysHashes + , withWalletAff + , withWallet + , getWalletCollateral + , getWalletBalance + , getWalletUtxos + ) where import Prelude -import Control.Monad.Reader (withReaderT) -import Control.Monad.Reader.Trans (ReaderT, asks) +import Control.Monad.Reader.Trans (asks) import Ctl.Internal.Cardano.Types.Transaction (UtxoMap) import Ctl.Internal.Cardano.Types.TransactionUnspentOutput ( TransactionUnspentOutput ) import Ctl.Internal.Cardano.Types.Value (Value) -import Ctl.Internal.Contract.Monad (Contract) +import Ctl.Internal.Contract.Monad (Contract, filterLockedUtxos) import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.Helpers (liftM, liftedM) -import Ctl.Internal.Helpers as Helpers import Ctl.Internal.Serialization.Address ( Address , NetworkId @@ -27,11 +41,9 @@ import Ctl.Internal.Types.PubKeyHash , StakePubKeyHash ) import Ctl.Internal.Types.RawBytes (RawBytes) -import Ctl.Internal.Types.UsedTxOuts (UsedTxOuts, isTxOutRefUsed) import Ctl.Internal.Wallet - ( Cip30Connection - , Cip30Wallet - , Wallet(KeyWallet, Lode, Flint, Gero, Nami, Eternl) + ( Wallet + , actionBasedOnWallet ) import Ctl.Internal.Wallet ( getChangeAddress @@ -113,49 +125,23 @@ withWallet act = do wallet <- liftedM (error "No wallet set") $ asks _.wallet act wallet -callCip30Wallet - :: forall (a :: Type) - . Cip30Wallet - -> (Cip30Wallet -> (Cip30Connection -> Aff a)) - -> Aff a -callCip30Wallet wallet act = act wallet wallet.connection - --- TODO Move -filterLockedUtxos :: UtxoMap -> Contract UtxoMap -filterLockedUtxos utxos = - withTxRefsCache $ - flip Helpers.filterMapWithKeyM utxos - (\k _ -> not <$> isTxOutRefUsed (unwrap k)) - -withTxRefsCache - :: forall (m :: Type -> Type) (a :: Type) - . ReaderT UsedTxOuts Aff a - -> Contract a -withTxRefsCache = wrap <<< withReaderT _.usedTxOuts - getWalletCollateral :: Contract (Maybe (Array TransactionUnspentOutput)) getWalletCollateral = do - queryHandle <- getQueryHandle - mbCollateralUTxOs <- asks (_.wallet) >>= maybe (pure Nothing) - case _ of - Nami wallet -> liftAff $ callCip30Wallet wallet _.getCollateral - Gero wallet -> liftAff $ callCip30Wallet wallet _.getCollateral - Flint wallet -> liftAff $ callCip30Wallet wallet _.getCollateral - Lode wallet -> liftAff $ callCip30Wallet wallet _.getCollateral - Eternl wallet -> liftAff $ callCip30Wallet wallet _.getCollateral - KeyWallet kw -> do - let addr = (unwrap kw).address - utxos <- (liftAff $ queryHandle.utxosAt addr) - <#> hush >>> fromMaybe Map.empty - >>= filterLockedUtxos - pparams <- asks $ _.ledgerConstants >>> _.pparams <#> unwrap - let - coinsPerUtxoUnit = pparams.coinsPerUtxoUnit - maxCollateralInputs = UInt.toInt $ - pparams.maxCollateralInputs - liftEffect $ (unwrap kw).selectCollateral coinsPerUtxoUnit - maxCollateralInputs - utxos + mbCollateralUTxOs <- asks (_.wallet) >>= maybe (pure Nothing) do + actionBasedOnWallet _.getCollateral \kw -> do + queryHandle <- getQueryHandle + let addr = (unwrap kw).address + utxos <- (liftAff $ queryHandle.utxosAt addr) + <#> hush >>> fromMaybe Map.empty + >>= filterLockedUtxos + pparams <- asks $ _.ledgerConstants >>> _.pparams <#> unwrap + let + coinsPerUtxoUnit = pparams.coinsPerUtxoUnit + maxCollateralInputs = UInt.toInt $ + pparams.maxCollateralInputs + liftEffect $ (unwrap kw).selectCollateral coinsPerUtxoUnit + maxCollateralInputs + utxos for_ mbCollateralUTxOs \collateralUTxOs -> do pparams <- asks $ _.ledgerConstants >>> _.pparams let @@ -174,13 +160,8 @@ getWalletBalance :: Contract (Maybe Value) getWalletBalance = do queryHandle <- getQueryHandle - asks _.wallet >>= map join <<< traverse case _ of - Nami wallet -> liftAff $ wallet.getBalance wallet.connection - Gero wallet -> liftAff $ wallet.getBalance wallet.connection - Eternl wallet -> liftAff $ wallet.getBalance wallet.connection - Flint wallet -> liftAff $ wallet.getBalance wallet.connection - Lode wallet -> liftAff $ wallet.getBalance wallet.connection - KeyWallet _ -> do + asks _.wallet >>= map join <<< traverse do + actionBasedOnWallet _.getBalance \_ -> do -- Implement via `utxosAt` addresses <- getWalletAddresses fold <$> for addresses \address -> do @@ -191,17 +172,12 @@ getWalletBalance = do getWalletUtxos :: Contract (Maybe UtxoMap) getWalletUtxos = do queryHandle <- getQueryHandle - asks _.wallet >>= map join <<< traverse case _ of - Nami wallet -> liftAff $ wallet.getUtxos wallet.connection <#> map toUtxoMap - Gero wallet -> liftAff $ wallet.getUtxos wallet.connection <#> map toUtxoMap - Flint wallet -> liftAff $ wallet.getUtxos wallet.connection <#> map - toUtxoMap - Eternl wallet -> liftAff $ wallet.getUtxos wallet.connection <#> map - toUtxoMap - Lode wallet -> liftAff $ wallet.getUtxos wallet.connection <#> map toUtxoMap - KeyWallet _ -> do - mbAddress <- getWalletAddresses <#> head - map join $ for mbAddress $ map hush <<< liftAff <<< queryHandle.utxosAt + asks _.wallet >>= map join <<< traverse do + actionBasedOnWallet + (\w conn -> w.getUtxos conn <#> map toUtxoMap) + \_ -> do + mbAddress <- getWalletAddresses <#> head + map join $ for mbAddress $ map hush <<< liftAff <<< queryHandle.utxosAt where toUtxoMap :: Array TransactionUnspentOutput -> UtxoMap toUtxoMap = Map.fromFoldable <<< map diff --git a/src/Internal/QueryM.purs b/src/Internal/QueryM.purs index e88010dd51..e0901d612c 100644 --- a/src/Internal/QueryM.purs +++ b/src/Internal/QueryM.purs @@ -40,7 +40,6 @@ module Ctl.Internal.QueryM , mkOgmiosRequest , mkOgmiosRequestAff , mkOgmiosWebSocketAff - , mkQueryRuntime , mkRequest , mkRequestAff , scriptToAeson @@ -159,12 +158,11 @@ import Ctl.Internal.Types.ByteArray (byteArrayToHex) import Ctl.Internal.Types.CborBytes (CborBytes) import Ctl.Internal.Types.Chain as Chain import Ctl.Internal.Types.Scripts (PlutusScript) -import Ctl.Internal.Types.UsedTxOuts (UsedTxOuts, newUsedTxOuts) +import Ctl.Internal.Types.UsedTxOuts (UsedTxOuts) import Ctl.Internal.Wallet (Wallet) import Ctl.Internal.Wallet.Key (PrivatePaymentKey, PrivateStakeKey) import Ctl.Internal.Wallet.Spec ( WalletSpec - , mkWalletBySpec ) import Data.Bifunctor (lmap) import Data.Either (Either(Left, Right), either, isRight) @@ -176,7 +174,7 @@ import Data.Map as Map import Data.Maybe (Maybe(Just, Nothing), fromMaybe, isJust, maybe) import Data.MediaType.Common (applicationJSON) import Data.Newtype (class Newtype, unwrap, wrap) -import Data.Traversable (for, for_, traverse_) +import Data.Traversable (for_, traverse_) import Data.Tuple (fst) import Data.Tuple.Nested (type (/\), (/\)) import Effect (Effect) @@ -312,40 +310,6 @@ instance Parallel (QueryMExtended r ParAff) (QueryMExtended r Aff) where sequential :: QueryMExtended r ParAff ~> QueryMExtended r Aff sequential = wrap <<< sequential <<< unwrap --- | Used in `mkQueryRuntime` only -data QueryRuntimeModel = QueryRuntimeModel - DatumCacheWebSocket - (OgmiosWebSocket /\ Ogmios.ProtocolParameters) - (Maybe Wallet) - -mkQueryRuntime - :: QueryConfig - -> Aff QueryRuntime -mkQueryRuntime config = do - usedTxOuts <- newUsedTxOuts - datumCacheWsRef <- liftEffect $ Ref.new Nothing - QueryRuntimeModel datumCacheWs (ogmiosWs /\ pparams) wallet <- sequential $ - QueryRuntimeModel - <$> parallel - ( mkDatumCacheWebSocketAff datumCacheWsRef logger - config.datumCacheConfig - ) - <*> parallel do - ogmiosWs <- - mkOgmiosWebSocketAff datumCacheWsRef logger config.ogmiosConfig - pparams <- getProtocolParametersAff ogmiosWs logger - pure $ ogmiosWs /\ pparams - <*> parallel (for config.walletSpec $ mkWalletBySpec config.networkId) - pure - { ogmiosWs - , datumCacheWs - , wallet - , usedTxOuts - , pparams - } - where - logger = mkLogger config.logLevel config.customLogger - getProtocolParametersAff :: OgmiosWebSocket -> (LogLevel -> String -> Effect Unit) diff --git a/src/Internal/Wallet.purs b/src/Internal/Wallet.purs index d4b5582bec..66917dd80d 100644 --- a/src/Internal/Wallet.purs +++ b/src/Internal/Wallet.purs @@ -34,11 +34,12 @@ module Ctl.Internal.Wallet , getChangeAddress , getRewardAddresses , getWalletAddresses - , actionBasedOnWalletAff + , actionBasedOnWallet , signData , ownPubKeyHashes , ownPaymentPubKeyHashes , ownStakePubKeysHashes + , callCip30Wallet ) where import Prelude @@ -93,6 +94,7 @@ import Data.Traversable (traverse) import Data.Tuple.Nested ((/\)) import Effect (Effect) import Effect.Aff (Aff, delay, error) +import Effect.Aff.Class (class MonadAff, liftAff) import Effect.Class (liftEffect) import Effect.Exception (throw) import Partial.Unsafe (unsafePartial) @@ -308,7 +310,7 @@ dummySign tx@(Transaction { witnessSet: tws@(TransactionWitnessSet ws) }) = getNetworkId :: Wallet -> Aff NetworkId getNetworkId wallet = do - actionBasedOnWalletAff + actionBasedOnWallet (\w -> intToNetworkId <=< _.getNetworkId w) (\kw -> pure (unwrap kw).networkId) wallet @@ -321,48 +323,49 @@ getNetworkId wallet = do getUnusedAddresses :: Wallet -> Aff (Array Address) getUnusedAddresses wallet = fold <$> do - actionBasedOnWalletAff _.getUnusedAddresses + actionBasedOnWallet _.getUnusedAddresses (\_ -> pure $ pure []) wallet getChangeAddress :: Wallet -> Aff (Maybe Address) getChangeAddress wallet = do - actionBasedOnWalletAff _.getChangeAddress + actionBasedOnWallet _.getChangeAddress (\kw -> pure $ pure (unwrap kw).address) wallet getRewardAddresses :: Wallet -> Aff (Array Address) getRewardAddresses wallet = fold <$> do - actionBasedOnWalletAff _.getRewardAddresses + actionBasedOnWallet _.getRewardAddresses (\kw -> pure $ pure $ pure (unwrap kw).address) wallet getWalletAddresses :: Wallet -> Aff (Array Address) getWalletAddresses wallet = fold <$> do - actionBasedOnWalletAff _.getWalletAddresses + actionBasedOnWallet _.getWalletAddresses (\kw -> pure $ pure $ Array.singleton (unwrap kw).address) wallet signData :: Address -> RawBytes -> Wallet -> Aff (Maybe DataSignature) signData address payload wallet = do - actionBasedOnWalletAff + actionBasedOnWallet (\w conn -> w.signData conn address payload) (\kw -> pure <$> (unwrap kw).signData payload) wallet -actionBasedOnWalletAff - :: forall (a :: Type) - . (Cip30Wallet -> Cip30Connection -> Aff a) - -> (KeyWallet -> Aff a) +actionBasedOnWallet + :: forall (m :: Type -> Type) (a :: Type) + . MonadAff m + => (Cip30Wallet -> Cip30Connection -> Aff a) + -> (KeyWallet -> m a) -> Wallet - -> Aff a -actionBasedOnWalletAff walletAction keyWalletAction = + -> m a +actionBasedOnWallet walletAction keyWalletAction = case _ of - Eternl wallet -> callCip30Wallet wallet walletAction - Nami wallet -> callCip30Wallet wallet walletAction - Gero wallet -> callCip30Wallet wallet walletAction - Flint wallet -> callCip30Wallet wallet walletAction - Lode wallet -> callCip30Wallet wallet walletAction + Eternl wallet -> liftAff $ callCip30Wallet wallet walletAction + Nami wallet -> liftAff $ callCip30Wallet wallet walletAction + Gero wallet -> liftAff $ callCip30Wallet wallet walletAction + Flint wallet -> liftAff $ callCip30Wallet wallet walletAction + Lode wallet -> liftAff $ callCip30Wallet wallet walletAction KeyWallet kw -> keyWalletAction kw ownPubKeyHashes :: Wallet -> Aff (Array PubKeyHash) diff --git a/src/Internal/Wallet/Cip30Mock.purs b/src/Internal/Wallet/Cip30Mock.purs index e42d45a973..1bed819c4e 100644 --- a/src/Internal/Wallet/Cip30Mock.purs +++ b/src/Internal/Wallet/Cip30Mock.purs @@ -1,4 +1,7 @@ -module Ctl.Internal.Wallet.Cip30Mock where +module Ctl.Internal.Wallet.Cip30Mock + ( withCip30Mock + , WalletMock(MockFlint, MockGero, MockNami, MockLode) + ) where import Prelude @@ -10,7 +13,7 @@ import Control.Promise (Promise, fromAff) import Ctl.Internal.Cardano.Types.TransactionUnspentOutput ( TransactionUnspentOutput(TransactionUnspentOutput) ) -import Ctl.Internal.Contract.QueryHandle (getQueryHandle') +import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.Deserialization.Transaction (deserializeTransaction) import Ctl.Internal.Helpers (liftEither) import Ctl.Internal.Serialization @@ -116,10 +119,11 @@ mkCip30Mock :: PrivatePaymentKey -> Maybe PrivateStakeKey -> Contract Cip30Mock mkCip30Mock pKey mSKey = do env <- ask + queryHandle <- getQueryHandle let getCollateralUtxos utxos = do let - pparams = unwrap $ env.ledgerConstants.pparams + pparams = unwrap env.ledgerConstants.pparams coinsPerUtxoUnit = pparams.coinsPerUtxoUnit maxCollateralInputs = UInt.toInt $ pparams.maxCollateralInputs @@ -130,7 +134,6 @@ mkCip30Mock pKey mSKey = do <#> fold utxosAt address = liftMaybe (error "No UTxOs at address") <<< hush =<< do - let queryHandle = getQueryHandle' env queryHandle.utxosAt address keyWallet = privateKeysToKeyWallet env.networkId pKey mSKey diff --git a/test/Integration.purs b/test/Integration.purs index cd9978c28b..5f30c19047 100644 --- a/test/Integration.purs +++ b/test/Integration.purs @@ -42,6 +42,5 @@ testPlan = do Logging.suite BalanceTx.Time.suite where - -- TODO Don't use wrapQueryM runQueryM' = runContract (testnetConfig { suppressLogs = true }) <<< wrapQueryM diff --git a/test/QueryM/AffInterface.purs b/test/QueryM/AffInterface.purs index 3d9e6d4330..1024952fcc 100644 --- a/test/QueryM/AffInterface.purs +++ b/test/QueryM/AffInterface.purs @@ -27,6 +27,9 @@ import Test.Spec.Assertions (shouldSatisfy) -- help verify that the Aff interface for websockets itself works, -- not that the data represents expected values, as that would depend on chain -- state, and ogmios itself. +-- +-- note: the only way to run QueryM is via Contract, which implicitly requires +-- some Ogmios endpoints to be called, and are therefore not included here. suite :: TestPlanM (QueryM Unit) Unit suite = do group "QueryM" do @@ -56,17 +59,6 @@ testGetChainTip :: QueryM Unit testGetChainTip = do void getChainTip --- TODO Move this. Or put it in contract tests (maybe it already is) --- testWaitUntilSlot :: QueryM Unit --- testWaitUntilSlot = do --- void $ getChainTip >>= case _ of --- TipAtGenesis -> throwError $ error "Tip is at genesis" --- Tip (ChainTip { slot }) -> do --- waitUntilSlot $ over Slot --- (fromMaybe (BigNum.fromInt 0) <<< BigNum.add (BigNum.fromInt 10)) --- slot - --- Remove eraSummaries from queryM? testGetEraSummaries :: QueryM Unit testGetEraSummaries = do void getEraSummaries From b21a403cadd33d2d9ac35dc6d76cc19df79136f3 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Wed, 7 Dec 2022 13:07:13 +0000 Subject: [PATCH 064/373] Another explicit export --- src/Internal/Contract.purs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Internal/Contract.purs b/src/Internal/Contract.purs index a90d6d6244..1543ab0a45 100644 --- a/src/Internal/Contract.purs +++ b/src/Internal/Contract.purs @@ -1,4 +1,4 @@ -module Ctl.Internal.Contract where +module Ctl.Internal.Contract (getChainTip, getProtocolParameters) where import Prelude From ff79fb1c16f9e15e93bffe03adfdf146874603cd Mon Sep 17 00:00:00 2001 From: uhbif19 Date: Wed, 7 Dec 2022 22:20:01 +0300 Subject: [PATCH 065/373] Make PlutusData.Constr first argument BigNum to match how CSL works --- src/Contract/PlutusData.purs | 2 +- src/Internal/Deserialization/PlutusData.purs | 2 +- src/Internal/FromData.purs | 23 ++++++++++---------- src/Internal/Plutus/Types/Transaction.purs | 20 +++++++++-------- src/Internal/Serialization.purs | 3 ++- src/Internal/Serialization/PlutusData.purs | 11 +++++----- src/Internal/ToData.purs | 20 ++++++++--------- src/Internal/Types/BigNum.purs | 2 ++ src/Internal/Types/Interval.purs | 12 +++++----- src/Internal/Types/PlutusData.purs | 3 ++- src/Internal/Types/Rational.purs | 6 +++-- src/Internal/Types/Transaction.purs | 10 +++++---- test/Data.purs | 9 ++++---- test/Fixtures.purs | 6 ++--- test/Serialization.purs | 4 ++-- 15 files changed, 72 insertions(+), 61 deletions(-) diff --git a/src/Contract/PlutusData.purs b/src/Contract/PlutusData.purs index e380955398..76a8ee1c23 100644 --- a/src/Contract/PlutusData.purs +++ b/src/Contract/PlutusData.purs @@ -33,7 +33,7 @@ import Ctl.Internal.FromData , FromDataError ( ArgsWantedButGot , FromDataFailed - , BigIntToIntFailed + , BigNumToIntFailed , IndexWantedButGot , WantedConstrGot ) diff --git a/src/Internal/Deserialization/PlutusData.purs b/src/Internal/Deserialization/PlutusData.purs index 820f535a89..95a4e4e07e 100644 --- a/src/Internal/Deserialization/PlutusData.purs +++ b/src/Internal/Deserialization/PlutusData.purs @@ -52,7 +52,7 @@ convertPlutusConstr pd = do let data' = convertPlutusData <$> _unpackPlutusList containerHelper (_ConstrPlutusData_data constr) - alt <- BigNum.toBigInt $ _ConstrPlutusData_alternative constr + alt = _ConstrPlutusData_alternative constr pure $ T.Constr alt data' convertPlutusMap :: PlutusData -> Maybe T.PlutusData diff --git a/src/Internal/FromData.purs b/src/Internal/FromData.purs index c9f58473e0..2e683fa324 100644 --- a/src/Internal/FromData.purs +++ b/src/Internal/FromData.purs @@ -2,7 +2,7 @@ module Ctl.Internal.FromData ( FromDataError ( ArgsWantedButGot , FromDataFailed - , BigIntToIntFailed + , BigNumToIntFailed , IndexWantedButGot , WantedConstrGot ) @@ -32,6 +32,7 @@ import Ctl.Internal.TypeLevel.RowList.Unordered.Indexed ) import Ctl.Internal.Types.BigNum (BigNum) import Ctl.Internal.Types.BigNum (fromBigInt) as BigNum +import Ctl.Internal.Types.BigNum as BigNum import Ctl.Internal.Types.ByteArray (ByteArray) import Ctl.Internal.Types.CborBytes (CborBytes) import Ctl.Internal.Types.PlutusData (PlutusData(Bytes, Constr, List, Integer)) @@ -64,7 +65,7 @@ import Type.Proxy (Proxy(Proxy)) data FromDataError = ArgsWantedButGot String Int (Array PlutusData) | FromDataFailed String PlutusData - | BigIntToIntFailed String BigInt + | BigNumToIntFailed String BigNum | IndexWantedButGot String Int Int | WantedConstrGot String PlutusData @@ -143,7 +144,7 @@ else instance FromDataWithSchema t (G.Constructor constr args) where fromDataWithSchema _ _ (Constr i pdArgs) = do let constrName = reflectSymbol (Proxy :: Proxy constr) - gotIx <- note (BigIntToIntFailed constrName i) (BigInt.toInt i) + gotIx <- note (BigNumToIntFailed constrName i) (BigNum.toInt i) wantedIx <- pure $ natVal (Proxy :: Proxy ix) noteB (IndexWantedButGot constrName wantedIx gotIx) (wantedIx == gotIx) { head: repArgs, tail: pdArgs' } <- fromDataArgs (Proxy :: Proxy t) @@ -249,28 +250,28 @@ instance FromData Void where instance FromData Unit where fromData (Constr n []) - | n == zero = Just unit + | n == BigNum.zero = Just unit fromData _ = Nothing -- NOTE: For the sake of compatibility the following fromDatas have to match -- https://github.com/input-output-hk/plutus/blob/1f31e640e8a258185db01fa899da63f9018c0e85/plutus-tx/src/PlutusTx/IsData/Instances.hs instance FromData Boolean where fromData (Constr n []) - | n == zero = Just false - | n == one = Just true + | n == BigNum.zero = Just false + | n == BigNum.one = Just true fromData _ = Nothing instance FromData a => FromData (Maybe a) where fromData (Constr n [ pd ]) - | n == zero = maybe Nothing (Just <<< Just) (fromData pd) -- Just is zero-indexed by Plutus + | n == BigNum.zero = maybe Nothing (Just <<< Just) (fromData pd) -- Just is zero-indexed by Plutus fromData (Constr n []) - | n == one = Just Nothing + | n == BigNum.one = Just Nothing fromData _ = Nothing instance (FromData a, FromData b) => FromData (Either a b) where fromData (Constr n [ pd ]) - | n == zero = maybe Nothing (Just <<< Left) (fromData pd) - | n == one = maybe Nothing (Just <<< Right) (fromData pd) + | n == BigNum.zero = maybe Nothing (Just <<< Left) (fromData pd) + | n == BigNum.one = maybe Nothing (Just <<< Right) (fromData pd) fromData _ = Nothing instance Fail (Text "Int is not supported, use BigInt instead") => FromData Int where @@ -301,7 +302,7 @@ instance FromData a => FromData (List a) where instance (FromData a, FromData b) => FromData (Tuple a b) where fromData (Constr n [ a, b ]) - | n == zero = Tuple <$> fromData a <*> fromData b + | n == BigNum.zero = Tuple <$> fromData a <*> fromData b fromData _ = Nothing instance FromData ByteArray where diff --git a/src/Internal/Plutus/Types/Transaction.purs b/src/Internal/Plutus/Types/Transaction.purs index e1f2c24fa4..ec6030739b 100644 --- a/src/Internal/Plutus/Types/Transaction.purs +++ b/src/Internal/Plutus/Types/Transaction.purs @@ -20,6 +20,7 @@ import Ctl.Internal.Plutus.Types.Address (Address) import Ctl.Internal.Plutus.Types.Value (Value) import Ctl.Internal.Serialization.Hash (ScriptHash) import Ctl.Internal.ToData (class ToData, toData) +import Ctl.Internal.Types.BigNum as BigNum import Ctl.Internal.Types.OutputDatum (OutputDatum) import Ctl.Internal.Types.PlutusData (PlutusData(Constr)) import Ctl.Internal.Types.Transaction (TransactionInput) @@ -58,19 +59,20 @@ derive newtype instance DecodeAeson TransactionOutput derive newtype instance EncodeAeson TransactionOutput instance FromData TransactionOutput where - fromData (Constr n [ addr, amt, datum, referenceScript ]) | n == zero = - TransactionOutput <$> - ( { address: _, amount: _, datum: _, referenceScript: _ } - <$> fromData addr - <*> fromData amt - <*> fromData datum - <*> fromData referenceScript - ) + fromData (Constr n [ addr, amt, datum, referenceScript ]) + | n == BigNum.zero = + TransactionOutput <$> + ( { address: _, amount: _, datum: _, referenceScript: _ } + <$> fromData addr + <*> fromData amt + <*> fromData datum + <*> fromData referenceScript + ) fromData _ = Nothing instance ToData TransactionOutput where toData (TransactionOutput { address, amount, datum, referenceScript }) = - Constr zero + Constr BigNum.zero [ toData address, toData amount, toData datum, toData referenceScript ] newtype TransactionOutputWithRefScript = TransactionOutputWithRefScript diff --git a/src/Internal/Serialization.purs b/src/Internal/Serialization.purs index 505f05108e..a6eaa3e657 100644 --- a/src/Internal/Serialization.purs +++ b/src/Internal/Serialization.purs @@ -793,7 +793,8 @@ convertTxOutput transactionOutputSetDataHash txo OutputDatum datumValue -> do transactionOutputSetPlutusData txo - $ convertPlutusData $ unwrap datumValue + $ convertPlutusData + $ unwrap datumValue for_ scriptRef $ convertScriptRef >>> transactionOutputSetScriptRef txo pure txo diff --git a/src/Internal/Serialization/PlutusData.purs b/src/Internal/Serialization/PlutusData.purs index 87ca09b549..36e1246c9e 100644 --- a/src/Internal/Serialization/PlutusData.purs +++ b/src/Internal/Serialization/PlutusData.purs @@ -19,7 +19,6 @@ import Ctl.Internal.Serialization.Types , PlutusMap ) import Ctl.Internal.Types.BigNum (BigNum) -import Ctl.Internal.Types.BigNum (fromBigInt) as BigNum import Ctl.Internal.Types.ByteArray (ByteArray) import Ctl.Internal.Types.PlutusData as T import Data.BigInt as BigInt @@ -32,17 +31,17 @@ convertPlutusData :: T.PlutusData -> PlutusData -- Unsafe fromJust here is correct, because we cover every PlutusData -- constructor, and Just will be returned by one of functions convertPlutusData x = unsafePartial $ fromJust $ case x of - T.Constr alt list -> convertConstr alt list + T.Constr alt list -> Just $ convertConstr alt list T.Map mp -> Just $ convertPlutusMap mp T.List lst -> Just $ convertPlutusList lst T.Integer n -> convertPlutusInteger n T.Bytes b -> Just $ _mkPlutusData_bytes b -convertConstr :: BigInt.BigInt -> Array T.PlutusData -> Maybe PlutusData +convertConstr :: BigNum -> Array T.PlutusData -> PlutusData convertConstr alt list = - map _mkPlutusData_constr $ _mkConstrPlutusData - <$> (BigNum.fromBigInt alt) - <*> Just (_packPlutusList containerHelper $ map convertPlutusData list) + _mkPlutusData_constr $ _mkConstrPlutusData + alt + (_packPlutusList containerHelper $ map convertPlutusData list) convertPlutusList :: Array T.PlutusData -> PlutusData convertPlutusList x = diff --git a/src/Internal/ToData.purs b/src/Internal/ToData.purs index 5c10e5a458..d36b41bcf1 100644 --- a/src/Internal/ToData.purs +++ b/src/Internal/ToData.purs @@ -26,7 +26,7 @@ import Ctl.Internal.TypeLevel.RowList.Unordered.Indexed , class GetWithLabel ) import Ctl.Internal.Types.BigNum (BigNum) -import Ctl.Internal.Types.BigNum (toBigIntUnsafe) as BigNum +import Ctl.Internal.Types.BigNum (fromInt, one, toBigIntUnsafe, zero) as BigNum import Ctl.Internal.Types.ByteArray (ByteArray(ByteArray)) import Ctl.Internal.Types.CborBytes (CborBytes) import Ctl.Internal.Types.PlutusData (PlutusData(Constr, Integer, List, Bytes)) @@ -147,7 +147,7 @@ instance ) => ToDataWithSchema t (G.Constructor constr arg) where toDataWithSchema p (G.Constructor args) = Constr - (fromInt <<< natVal $ (Proxy :: Proxy index)) + (BigNum.fromInt <<< natVal $ (Proxy :: Proxy index)) (toDataArgs p (Proxy :: Proxy constr) args) -- | ToDataArgs instances for Data.Generic.Rep @@ -236,21 +236,21 @@ instance ToData Void where toData = absurd instance ToData Unit where - toData _ = Constr zero [] + toData _ = Constr BigNum.zero [] -- NOTE: For the sake of compatibility the following toDatas have to match -- https://github.com/input-output-hk/plutus/blob/1f31e640e8a258185db01fa899da63f9018c0e85/plutus-tx/src/PlutusTx/IsData/Instances.hs instance ToData Boolean where - toData false = Constr zero [] - toData true = Constr one [] + toData false = Constr BigNum.zero [] + toData true = Constr BigNum.one [] instance ToData a => ToData (Maybe a) where - toData (Just x) = Constr zero [ toData x ] -- Just is zero-indexed by Plutus - toData Nothing = Constr one [] + toData (Just x) = Constr BigNum.zero [ toData x ] -- Just is zero-indexed by Plutus + toData Nothing = Constr BigNum.one [] instance (ToData a, ToData b) => ToData (Either a b) where - toData (Left e) = Constr zero [ toData e ] - toData (Right x) = Constr one [ toData x ] + toData (Left e) = Constr BigNum.zero [ toData e ] + toData (Right x) = Constr BigNum.one [ toData x ] instance Fail (Text "Int is not supported, use BigInt instead") => ToData Int where toData = toData <<< BigInt.fromInt @@ -274,7 +274,7 @@ instance ToData a => ToData (List a) where toData = foldableToPlutusData instance (ToData a, ToData b) => ToData (Tuple a b) where - toData (Tuple a b) = Constr zero [ toData a, toData b ] + toData (Tuple a b) = Constr BigNum.zero [ toData a, toData b ] -- Note that nothing prevents the denominator from being zero, we could provide -- safety here: diff --git a/src/Internal/Types/BigNum.purs b/src/Internal/Types/BigNum.purs index 1d7fb61a84..27c1542842 100644 --- a/src/Internal/Types/BigNum.purs +++ b/src/Internal/Types/BigNum.purs @@ -59,6 +59,8 @@ instance DecodeAeson BigNum where instance EncodeAeson BigNum where encodeAeson' = encodeAeson' <<< toBigIntUnsafe +-- Semiring cannot be implemented, because add and mul returns Maybe BigNum + fromBigInt :: BigInt -> Maybe BigNum fromBigInt = fromString <<< BigInt.toString diff --git a/src/Internal/Types/Interval.purs b/src/Internal/Types/Interval.purs index 3034b151de..7aa6a40fa7 100644 --- a/src/Internal/Types/Interval.purs +++ b/src/Internal/Types/Interval.purs @@ -274,31 +274,31 @@ instance Ord a => MeetSemilattice (Interval a) where -- This instance is written to be compatible with plutus. instance (ToData a, Ord a, Semiring a) => ToData (Interval a) where toData (FiniteInterval start end) = - ( Constr (BigInt.fromInt 0) + ( Constr BigNum.zero [ toData $ lowerBound start , toData $ strictUpperBound (end + one) ] ) toData (StartAt end) = - ( Constr (BigInt.fromInt 0) + ( Constr BigNum.zero [ toData (LowerBound NegInf true :: LowerBound a) , toData $ strictUpperBound (end + one) ] ) toData (EndAt start) = - ( Constr (BigInt.fromInt 0) + ( Constr BigNum.zero [ toData $ lowerBound start , toData (UpperBound PosInf true :: UpperBound a) ] ) toData AlwaysInterval = - ( Constr (BigInt.fromInt 0) + ( Constr BigNum.zero [ toData (LowerBound NegInf true :: LowerBound a) , toData (UpperBound PosInf true :: UpperBound a) ] ) toData EmptyInterval = - ( Constr (BigInt.fromInt 0) + ( Constr BigNum.zero [ toData (LowerBound PosInf true :: LowerBound a) , toData (UpperBound NegInf true :: UpperBound a) ] @@ -315,7 +315,7 @@ instance Ord a => BoundedJoinSemilattice (Interval a) where -- This instance is written to be compatible with plutus. instance (FromData a, Ord a, Ring a) => FromData (Interval a) where - fromData (Constr index [ lower, upper ]) | index == zero = do + fromData (Constr index [ lower, upper ]) | index == BigNum.zero = do (LowerBound start startBool) <- fromData lower (UpperBound end endBool) <- fromData upper case diff --git a/src/Internal/Types/PlutusData.purs b/src/Internal/Types/PlutusData.purs index 7a13ab1e44..d1cac4da69 100644 --- a/src/Internal/Types/PlutusData.purs +++ b/src/Internal/Types/PlutusData.purs @@ -21,6 +21,7 @@ import Aeson , (.:) ) import Control.Alt ((<|>)) +import Ctl.Internal.Types.BigNum (BigNum) import Ctl.Internal.Types.ByteArray (ByteArray, hexToByteArray) import Data.BigInt (BigInt) import Data.Either (Either(Left)) @@ -33,7 +34,7 @@ import Data.Tuple.Nested ((/\)) -- Doesn't distinguish "BuiltinData" and "Data" like Plutus: data PlutusData - = Constr BigInt (Array PlutusData) + = Constr BigNum (Array PlutusData) | Map (Array (Tuple PlutusData PlutusData)) | List (Array PlutusData) | Integer BigInt diff --git a/src/Internal/Types/Rational.purs b/src/Internal/Types/Rational.purs index 898265efb0..80c8017d55 100644 --- a/src/Internal/Types/Rational.purs +++ b/src/Internal/Types/Rational.purs @@ -22,6 +22,7 @@ import Aeson ) import Ctl.Internal.FromData (class FromData) import Ctl.Internal.ToData (class ToData) +import Ctl.Internal.Types.BigNum as BigNum import Ctl.Internal.Types.Natural (Natural) import Ctl.Internal.Types.Natural (fromBigInt', toBigInt) as Nat import Ctl.Internal.Types.PlutusData (PlutusData(Constr, Integer)) @@ -101,11 +102,12 @@ denominatorAsNat = Nat.fromBigInt' <<< denominator -------------------------------------------------------------------------------- instance ToData Rational where - toData r = Constr zero [ Integer (numerator r), Integer (denominator r) ] + toData r = + Constr BigNum.zero [ Integer (numerator r), Integer (denominator r) ] instance FromData Rational where fromData (Constr c [ Integer n, Integer d ]) - | c == zero = reduce n d + | c == BigNum.zero = reduce n d fromData _ = Nothing -------------------------------------------------------------------------------- diff --git a/src/Internal/Types/Transaction.purs b/src/Internal/Types/Transaction.purs index 3fc654a3a0..c00b4ca1b6 100644 --- a/src/Internal/Types/Transaction.purs +++ b/src/Internal/Types/Transaction.purs @@ -11,6 +11,7 @@ import Prelude import Aeson (class DecodeAeson, class EncodeAeson) import Ctl.Internal.FromData (class FromData, fromData) import Ctl.Internal.ToData (class ToData, toData) +import Ctl.Internal.Types.BigNum as BigNum import Ctl.Internal.Types.ByteArray (ByteArray, byteArrayToHex) import Ctl.Internal.Types.PlutusData (PlutusData(Constr)) import Data.Generic.Rep (class Generic) @@ -46,7 +47,7 @@ instance Show TransactionInput where -- `Constr` is used for indexing, and `TransactionInput` is always zero-indexed instance FromData TransactionInput where - fromData (Constr n [ txId, idx ]) | n == zero = + fromData (Constr n [ txId, idx ]) | n == BigNum.zero = TransactionInput <$> ({ transactionId: _, index: _ } <$> fromData txId <*> fromData idx) fromData _ = Nothing @@ -54,7 +55,7 @@ instance FromData TransactionInput where -- `Constr` is used for indexing, and `TransactionInput` is always zero-indexed instance ToData TransactionInput where toData (TransactionInput { transactionId, index }) = - Constr zero [ toData transactionId, toData index ] + Constr BigNum.zero [ toData transactionId, toData index ] -- | 32-bytes blake2b256 hash of a tx body. -- | NOTE. Plutus docs might incorrectly state that it uses @@ -78,12 +79,13 @@ instance Show TransactionHash where -- Plutus actually has this as a zero indexed record instance FromData TransactionHash where - fromData (Constr n [ bytes ]) | n == zero = TransactionHash <$> fromData bytes + fromData (Constr n [ bytes ]) | n == BigNum.zero = TransactionHash <$> + fromData bytes fromData _ = Nothing -- Plutus actually has this as a zero indexed record instance ToData TransactionHash where - toData (TransactionHash bytes) = Constr zero [ toData bytes ] + toData (TransactionHash bytes) = Constr BigNum.zero [ toData bytes ] newtype DataHash = DataHash ByteArray diff --git a/test/Data.purs b/test/Data.purs index a98ce2996c..31fbc86fc3 100644 --- a/test/Data.purs +++ b/test/Data.purs @@ -30,6 +30,7 @@ import Ctl.Internal.TypeLevel.RowList.Unordered.Indexed , ConsI , NilI ) +import Ctl.Internal.Types.BigNum as BigNum import Ctl.Internal.Types.ByteArray (hexToByteArrayUnsafe) import Ctl.Internal.Types.PlutusData (PlutusData(Constr, Integer)) import Data.BigInt (BigInt) @@ -178,18 +179,18 @@ suite = do plutusDataRoundtripProperty (Proxy :: Proxy EType) test "CType: C1 constructor shouldn't accept empty arguments" $ let - pd = Constr (BigInt.fromInt 1) [] + pd = Constr BigNum.one [] in shouldEqualWith fromData (const (Nothing :: Maybe CType)) pd test "CType: C1 constructor shouldn't accept more than one argument" $ let - pd = Constr (BigInt.fromInt 1) - [ (Constr (BigInt.fromInt 1) []), (Integer $ BigInt.fromInt 0) ] + pd = Constr BigNum.one + [ (Constr BigNum.one []), (Integer $ BigInt.fromInt 0) ] in shouldEqualWith fromData (const (Nothing :: Maybe CType)) pd test "CType: C0 constructor shouldn't accept any arguments" $ let - pd = Constr (BigInt.fromInt 0) [ (Constr (BigInt.fromInt 1) []) ] + pd = Constr BigNum.zero [ (Constr BigNum.one []) ] in shouldEqualWith fromData (const (Nothing :: Maybe CType)) pd test "FType and FType' toData/fromData are the same" $ diff --git a/test/Fixtures.purs b/test/Fixtures.purs index 0015e5f31b..14efee722c 100644 --- a/test/Fixtures.purs +++ b/test/Fixtures.purs @@ -77,7 +77,7 @@ import Prelude import Aeson (Aeson, aesonNull, decodeAeson, fromString, parseJsonStringToAeson) import Contract.Numeric.BigNum (BigNum) -import Contract.Numeric.BigNum (fromBigInt, fromInt) as BigNum +import Contract.Numeric.BigNum (fromBigInt, fromInt, one, zero) as BigNum import Contract.Transaction ( PoolPubKeyHash(PoolPubKeyHash) , vrfKeyHashFromBytes @@ -1250,7 +1250,7 @@ plutusDataFixture3 = PD.Bytes ) plutusDataFixture4 :: PD.PlutusData -plutusDataFixture4 = PD.Constr (BigInt.fromInt 1) +plutusDataFixture4 = PD.Constr BigNum.one [ plutusDataFixture2, plutusDataFixture3 ] plutusDataFixture5 :: PD.PlutusData @@ -1273,7 +1273,7 @@ plutusDataFixture7 = PD.List ] plutusDataFixture8 :: PD.PlutusData -plutusDataFixture8 = PD.Constr (BigInt.fromInt 0) +plutusDataFixture8 = PD.Constr BigNum.zero [ PD.Bytes ( hexToByteArrayUnsafe "da13ed22b9294f1d86bbd530e99b1456884c7364bf16c90edc1ae41e" diff --git a/test/Serialization.purs b/test/Serialization.purs index dae71a99e7..46271ad20a 100644 --- a/test/Serialization.purs +++ b/test/Serialization.purs @@ -18,7 +18,7 @@ import Ctl.Internal.Serialization.Keys (bytesFromPublicKey) import Ctl.Internal.Serialization.PlutusData (convertPlutusData) import Ctl.Internal.Serialization.Types (TransactionHash) import Ctl.Internal.Test.TestPlanM (TestPlanM) -import Ctl.Internal.Types.BigNum (fromString) as BN +import Ctl.Internal.Types.BigNum (fromString, one) as BN import Ctl.Internal.Types.ByteArray (byteArrayToHex, hexToByteArrayUnsafe) import Ctl.Internal.Types.CborBytes (cborBytesToHex) import Ctl.Internal.Types.PlutusData as PD @@ -80,7 +80,7 @@ suite = do pure unit test "PlutusData #1 - Constr" $ do let - datum = PD.Constr (BigInt.fromInt 1) + datum = PD.Constr BN.one [ PD.Integer (BigInt.fromInt 1) , PD.Integer (BigInt.fromInt 2) ] From bcd7889d3b1b87deaf4f039e478be080b6d355e8 Mon Sep 17 00:00:00 2001 From: Gregory Gerasev Date: Wed, 7 Dec 2022 22:25:52 +0300 Subject: [PATCH 066/373] Apply suggestions from code review Co-authored-by: Bradley <80346526+Bradley-Heather@users.noreply.github.com> --- src/Internal/Types/ScriptLookups.purs | 3 +-- test/Deserialization.purs | 2 +- 2 files changed, 2 insertions(+), 3 deletions(-) diff --git a/src/Internal/Types/ScriptLookups.purs b/src/Internal/Types/ScriptLookups.purs index 1fee35fa26..a06cbc8431 100644 --- a/src/Internal/Types/ScriptLookups.purs +++ b/src/Internal/Types/ScriptLookups.purs @@ -1255,8 +1255,7 @@ processConstraint mpsMap osMap = do let amount = fromPlutusValue plutusValue runExceptT do let datum' = outputDatum dat datp - let - txOut = TransactionOutput + txOut = TransactionOutput { address: case mbCredential of Nothing -> validatorHashEnterpriseAddress networkId vlh diff --git a/test/Deserialization.purs b/test/Deserialization.purs index 3402ed5807..54be12ef35 100644 --- a/test/Deserialization.purs +++ b/test/Deserialization.purs @@ -108,7 +108,7 @@ suite = do let pdRoundTripTest ctlPd = do let cslPd = SPD.convertPlutusData ctlPd - let pdBytes = toBytes (asOneOf cslPd) + pdBytes = toBytes (asOneOf cslPd) cslPd' <- errMaybe "Failed to fromBytes PlutusData" $ fromBytes pdBytes let ctlPd' = DPD.convertPlutusData cslPd' From 4310021cc1d6a6105a0c66dd992fec5644ad88cd Mon Sep 17 00:00:00 2001 From: Calum Sieppert Date: Wed, 7 Dec 2022 13:42:46 -0700 Subject: [PATCH 067/373] Typo Co-authored-by: Bradley <80346526+Bradley-Heather@users.noreply.github.com> --- src/Internal/Serialization/ToBytes.purs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Internal/Serialization/ToBytes.purs b/src/Internal/Serialization/ToBytes.purs index 552f7f3e3d..1cc86ebc17 100644 --- a/src/Internal/Serialization/ToBytes.purs +++ b/src/Internal/Serialization/ToBytes.purs @@ -60,7 +60,7 @@ type SerializationData = Address |+| Value |+| VRFKeyHash --- and more as needed +-- Add more as needed -- NOTE returns cbor encoding for all but hash types, for which it returns raw bytes foreign import _toBytes From 5ba20167379ae0007155b7689c658b55c3d4ebe8 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Thu, 8 Dec 2022 11:03:27 +0000 Subject: [PATCH 068/373] Apply suppressed logger before contract env creation --- src/Internal/Contract/Monad.purs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Internal/Contract/Monad.purs b/src/Internal/Contract/Monad.purs index 57096e351b..79f91f4c08 100644 --- a/src/Internal/Contract/Monad.purs +++ b/src/Internal/Contract/Monad.purs @@ -309,7 +309,7 @@ withContractEnv params action = do | params.suppressLogs = Just $ map liftEffect <<< addLogEntry | otherwise = params.customLogger - contractEnv <- mkContractEnv params <#> _ { customLogger = customLogger } + contractEnv <- mkContractEnv params { customLogger = customLogger } for_ contractEnv.wallet $ walletNetworkCheck contractEnv.networkId eiRes <- attempt $ supervise (action contractEnv) From 42c58091569de482f8a5c34bff4db597722acaff Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Thu, 8 Dec 2022 11:05:39 +0000 Subject: [PATCH 069/373] Improve wording --- doc/side-by-side-ctl-plutus-comparison.md | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/doc/side-by-side-ctl-plutus-comparison.md b/doc/side-by-side-ctl-plutus-comparison.md index fe0beaedc0..1d88fe4150 100644 --- a/doc/side-by-side-ctl-plutus-comparison.md +++ b/doc/side-by-side-ctl-plutus-comparison.md @@ -41,14 +41,14 @@ newtype Contract w (s :: Row *) e a = Contract { unContract :: Eff (ContractEffs ``` The Plutus `Contract` environment is specialized to just two values and is fixed. -Also, Plutus `Contract` uses a phantom type `s` to contract schema +Also, Plutus `Contract` uses a phantom type `s` for the contract schema and parameters `w` for a writer and `e` for errors. In the case of CTL we don't have the contract schema parameter or the writer -parameter since CTL definition allows performing arbitrary effects, from the -use of `Aff`. `Aff` allows us to use asynchronous effects, which has a similar -effect as using `IO` in Haskell, although isn't the same. While most effectful -actions are defined directly in terms of those provided by `Aff`, logging is -provided by a configurable logger stored in `ContractEnv`. +parameter since the definition of CTL allows performing arbitrary effects, from +the use of `Aff`. `Aff` allows us to use asynchronous effects, which has a +similar effect as using `IO` in Haskell, although isn't the same. While most +effectful actions are defined directly in terms of those provided by `Aff`, +logging is provided by a configurable logger stored in `ContractEnv`. ## Contract comparison From bff0ed19a10bde070133d50938be43117b4641bb Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Thu, 8 Dec 2022 13:16:32 +0000 Subject: [PATCH 070/373] Qualified import suggestions --- src/Contract/Chain.purs | 30 +++----------------- src/Contract/Wallet.purs | 30 ++------------------ src/Contract/Wallet/KeyFile.purs | 11 ++++--- src/Internal/BalanceTx/BalanceTx.purs | 6 ++-- src/Internal/BalanceTx/ExUnitsAndMinFee.purs | 5 ++-- 5 files changed, 20 insertions(+), 62 deletions(-) diff --git a/src/Contract/Chain.purs b/src/Contract/Chain.purs index 580d3626dd..8de4dd2c17 100644 --- a/src/Contract/Chain.purs +++ b/src/Contract/Chain.purs @@ -1,41 +1,19 @@ -- | A module for Chain-related querying. module Contract.Chain - ( getTip - , waitUntilSlot - , waitNSlots - , currentTime - , currentSlot - , module Chain + ( module Chain + , module Contract + , module Contract.WaitUntilSlot ) where -import Contract.Monad (Contract) import Ctl.Internal.Contract (getChainTip) as Contract import Ctl.Internal.Contract.WaitUntilSlot ( currentSlot , currentTime , waitNSlots , waitUntilSlot - ) as Contract -import Ctl.Internal.Serialization.Address (Slot) + ) as Contract.WaitUntilSlot import Ctl.Internal.Types.Chain ( BlockHeaderHash(BlockHeaderHash) , ChainTip(ChainTip) , Tip(Tip, TipAtGenesis) ) as Chain -import Ctl.Internal.Types.Interval (POSIXTime) -import Ctl.Internal.Types.Natural (Natural) - -getTip :: Contract Chain.Tip -getTip = Contract.getChainTip - -waitUntilSlot :: Slot -> Contract Chain.Tip -waitUntilSlot = Contract.waitUntilSlot - -waitNSlots :: Natural -> Contract Chain.Tip -waitNSlots = Contract.waitNSlots - -currentTime :: Contract POSIXTime -currentTime = Contract.currentTime - -currentSlot :: Contract Slot -currentSlot = Contract.currentSlot diff --git a/src/Contract/Wallet.purs b/src/Contract/Wallet.purs index f39cc02684..f89c10cd39 100644 --- a/src/Contract/Wallet.purs +++ b/src/Contract/Wallet.purs @@ -3,13 +3,9 @@ module Contract.Wallet ( mkKeyWalletFromPrivateKeys , withKeyWallet , getNetworkId - , getUnusedAddresses - , getChangeAddress - , getRewardAddresses - , getWallet - , signData , module Contract.Address , module Contract.Utxos + , module Contract.Wallet , module Deserialization.Keys , module Wallet , module Ctl.Internal.Wallet.Key @@ -30,10 +26,9 @@ import Ctl.Internal.Contract.Wallet , getUnusedAddresses , getWallet , signData - ) as Contract + ) as Contract.Wallet import Ctl.Internal.Deserialization.Keys (privateKeyFromBytes) as Deserialization.Keys -import Ctl.Internal.Serialization.Address (Address, NetworkId) -import Ctl.Internal.Types.RawBytes (RawBytes) +import Ctl.Internal.Serialization.Address (NetworkId) import Ctl.Internal.Wallet ( Wallet(Gero, Nami, Flint, Lode, Eternl, KeyWallet) , WalletExtension @@ -50,7 +45,6 @@ import Ctl.Internal.Wallet , walletToWalletExtension ) as Wallet import Ctl.Internal.Wallet (Wallet(KeyWallet)) -import Ctl.Internal.Wallet.Cip30 (DataSignature) import Ctl.Internal.Wallet.Key (KeyWallet, privateKeysToKeyWallet) as Wallet import Ctl.Internal.Wallet.Key ( PrivatePaymentKey(PrivatePaymentKey) @@ -75,24 +69,6 @@ import Data.Maybe (Maybe(Just)) getNetworkId :: Contract NetworkId getNetworkId = asks _.networkId -getUnusedAddresses :: Contract (Array Address) -getUnusedAddresses = Contract.getUnusedAddresses - -getChangeAddress :: Contract (Maybe Address) -getChangeAddress = Contract.getChangeAddress - -getRewardAddresses :: Contract (Array Address) -getRewardAddresses = Contract.getRewardAddresses - -signData - :: Address - -> RawBytes - -> Contract (Maybe DataSignature) -signData address dat = Contract.signData address dat - -getWallet :: Contract (Maybe Wallet) -getWallet = Contract.getWallet - withKeyWallet :: forall (a :: Type) . Wallet.KeyWallet diff --git a/src/Contract/Wallet/KeyFile.purs b/src/Contract/Wallet/KeyFile.purs index 6eb4aafadc..1948f045cd 100644 --- a/src/Contract/Wallet/KeyFile.purs +++ b/src/Contract/Wallet/KeyFile.purs @@ -1,15 +1,14 @@ -- | Node-only module. Allows to work with Skeys stored in files. module Contract.Wallet.KeyFile ( mkKeyWalletFromFiles - , module Ctl.Internal.Wallet.KeyFile + , module Wallet.KeyFile ) where import Prelude import Control.Monad.Reader.Class (asks) import Ctl.Internal.Contract.Monad (Contract) -import Ctl.Internal.Wallet.Key (KeyWallet) as Wallet -import Ctl.Internal.Wallet.Key (privateKeysToKeyWallet) +import Ctl.Internal.Wallet.Key (KeyWallet, privateKeysToKeyWallet) import Ctl.Internal.Wallet.KeyFile ( privatePaymentKeyFromFile , privatePaymentKeyFromTextEnvelope @@ -17,6 +16,10 @@ import Ctl.Internal.Wallet.KeyFile , privateStakeKeyFromFile , privateStakeKeyFromTextEnvelope , privateStakeKeyToFile + ) as Wallet.KeyFile +import Ctl.Internal.Wallet.KeyFile + ( privatePaymentKeyFromFile + , privateStakeKeyFromFile ) import Data.Maybe (Maybe) import Data.Traversable (traverse) @@ -31,7 +34,7 @@ import Node.Path (FilePath) -- | -- | **NodeJS only** mkKeyWalletFromFiles - :: FilePath -> Maybe FilePath -> Contract Wallet.KeyWallet + :: FilePath -> Maybe FilePath -> Contract KeyWallet mkKeyWalletFromFiles paymentKeyFile mbStakeKeyFile = do networkId <- asks _.networkId liftAff $ privateKeysToKeyWallet networkId diff --git a/src/Internal/BalanceTx/BalanceTx.purs b/src/Internal/BalanceTx/BalanceTx.purs index 701beaac5f..d702728d0f 100644 --- a/src/Internal/BalanceTx/BalanceTx.purs +++ b/src/Internal/BalanceTx/BalanceTx.purs @@ -106,7 +106,7 @@ import Ctl.Internal.Cardano.Types.Value ) import Ctl.Internal.Contract.Monad (Contract, filterLockedUtxos) import Ctl.Internal.Contract.QueryHandle (getQueryHandle) -import Ctl.Internal.Contract.Wallet (getChangeAddress, getWalletAddresses) as Contract +import Ctl.Internal.Contract.Wallet (getChangeAddress, getWalletAddresses) as Contract.Wallet import Ctl.Internal.Contract.Wallet (getWalletCollateral) import Ctl.Internal.Serialization.Address ( Address @@ -154,7 +154,7 @@ balanceTxWithConstraints unbalancedTx constraintsBuilder = do srcAddrs <- asksConstraints Constraints._srcAddresses - >>= maybe (liftContract Contract.getWalletAddresses) pure + >>= maybe (liftContract Contract.Wallet.getWalletAddresses) pure changeAddr <- getChangeAddress @@ -188,7 +188,7 @@ balanceTxWithConstraints unbalancedTx constraintsBuilder = do getChangeAddress :: BalanceTxM Address getChangeAddress = liftMaybe CouldNotGetChangeAddress - =<< maybe (liftContract Contract.getChangeAddress) (pure <<< Just) + =<< maybe (liftContract Contract.Wallet.getChangeAddress) (pure <<< Just) =<< asksConstraints Constraints._changeAddress unbalancedTxWithNetworkId :: BalanceTxM Transaction diff --git a/src/Internal/BalanceTx/ExUnitsAndMinFee.purs b/src/Internal/BalanceTx/ExUnitsAndMinFee.purs index 18af77b886..53ac4aaf92 100644 --- a/src/Internal/BalanceTx/ExUnitsAndMinFee.purs +++ b/src/Internal/BalanceTx/ExUnitsAndMinFee.purs @@ -41,7 +41,7 @@ import Ctl.Internal.Cardano.Types.Transaction , _redeemers , _witnessSet ) -import Ctl.Internal.Contract.MinFee (calculateMinFee) as Contract +import Ctl.Internal.Contract.MinFee (calculateMinFee) as Contract.MinFee import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.Plutus.Conversion (fromPlutusUtxoMap) import Ctl.Internal.QueryM.Ogmios @@ -140,7 +140,8 @@ evalExUnitsAndMinFee (PrebalancedTransaction unattachedTx) allUtxos = do additionalUtxos <- fromPlutusUtxoMap networkId <$> asksConstraints Constraints._additionalUtxos - minFee <- liftContract $ Contract.calculateMinFee finalizedTx additionalUtxos + minFee <- liftContract $ Contract.MinFee.calculateMinFee finalizedTx + additionalUtxos pure $ reindexedUnattachedTxWithExUnits /\ unwrap minFee -- | Attaches datums and redeemers, sets the script integrity hash, From ec183c63625134efddab17d42c4fae5cf25b5c81 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Thu, 8 Dec 2022 15:56:03 +0100 Subject: [PATCH 071/373] Test invariants of UtxoIndex --- src/Internal/BalanceTx/CoinSelection.purs | 32 ++- src/Internal/Serialization/Address.purs | 7 +- src/Internal/Serialization/Hash.purs | 17 +- src/Internal/Types/Transaction.purs | 14 +- test/CoinSelection/UtxoIndex.purs | 251 ++++++++++++++++++++++ test/Unit.purs | 2 + 6 files changed, 308 insertions(+), 15 deletions(-) create mode 100644 test/CoinSelection/UtxoIndex.purs diff --git a/src/Internal/BalanceTx/CoinSelection.purs b/src/Internal/BalanceTx/CoinSelection.purs index 717c1dd22f..1e3c5b6f9d 100644 --- a/src/Internal/BalanceTx/CoinSelection.purs +++ b/src/Internal/BalanceTx/CoinSelection.purs @@ -5,16 +5,17 @@ -- | The algorithm supports two selection strategies (optimal and minimal) and -- | uses priority ordering and round-robin processing to handle the problem -- | of over-selection. -module Ctl.Internal.BalanceTx.CoinSelection - ( Asset +module Ctl.Internal.BalanceTx.CoinSelection {-( Asset , SelectionState(SelectionState) , SelectionStrategy(SelectionStrategyMinimal, SelectionStrategyOptimal) , UtxoIndex(UtxoIndex) , _leftoverUtxos + , _utxos , buildUtxoIndex + , emptyUtxoIndex , performMultiAssetSelection , selectedInputs - ) where + )-} where import Prelude @@ -51,6 +52,7 @@ import Data.BigInt (abs, fromInt, toString) as BigInt import Data.Foldable (foldMap) as Foldable import Data.Foldable (foldl) import Data.Function (applyFlipped) +import Data.Generic.Rep (class Generic) import Data.HashMap (HashMap) import Data.HashMap (alter, empty, lookup, update) as HashMap import Data.Hashable (class Hashable, hash) @@ -65,6 +67,7 @@ import Data.Maybe (Maybe(Just, Nothing), fromMaybe, maybe, maybe') import Data.Newtype (class Newtype, unwrap, wrap) import Data.Set (Set) import Data.Set (fromFoldable, toUnfoldable) as Set +import Data.Show.Generic (genericShow) import Data.Tuple (fst) as Tuple import Data.Tuple.Nested (type (/\), (/\)) import Effect.Class (class MonadEffect, liftEffect) @@ -427,8 +430,12 @@ selectRandomWithPriority utxoIndex filters = -- | https://github.com/input-output-hk/cardano-wallet/blob/791541da69b9b3f434bb9ead43de406cc18b0373/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L485 data Asset = AssetLovelace | Asset AssetClass +derive instance Generic Asset _ derive instance Eq Asset +instance Show Asset where + show = genericShow + instance Hashable Asset where hash AssetLovelace = hash (Nothing :: Maybe AssetClass) hash (Asset asset) = hash (Just asset) @@ -484,7 +491,12 @@ newtype UtxoIndex = UtxoIndex -- ^ The complete set of all utxos. } +derive instance Generic UtxoIndex _ derive instance Newtype UtxoIndex _ +derive instance Eq UtxoIndex + +instance Show UtxoIndex where + show = genericShow _indexAnyWith :: Lens' UtxoIndex (HashMap Asset UtxoMap) _indexAnyWith = _Newtype <<< prop (Proxy :: Proxy "indexAnyWith") @@ -505,13 +517,13 @@ buildUtxoIndex utxos = utxos' :: Array TxUnspentOutput utxos' = Map.toUnfoldable utxos - emptyUtxoIndex :: UtxoIndex - emptyUtxoIndex = UtxoIndex - { indexAnyWith: HashMap.empty - , indexSingletons: HashMap.empty - , indexPairs: HashMap.empty - , utxos: Map.empty - } +emptyUtxoIndex :: UtxoIndex +emptyUtxoIndex = UtxoIndex + { indexAnyWith: HashMap.empty + , indexSingletons: HashMap.empty + , indexPairs: HashMap.empty + , utxos: Map.empty + } -- | Taken from cardano-wallet: -- | https://github.com/input-output-hk/cardano-wallet/blob/791541da69b9b3f434bb9ead43de406cc18b0373/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L561 diff --git a/src/Internal/Serialization/Address.purs b/src/Internal/Serialization/Address.purs index 8b2e32f348..2daf538cd9 100644 --- a/src/Internal/Serialization/Address.purs +++ b/src/Internal/Serialization/Address.purs @@ -115,13 +115,15 @@ import Ctl.Internal.Types.PlutusData (PlutusData(Bytes)) import Data.Either (note) import Data.Function (on) import Data.Generic.Rep (class Generic) -import Data.Maybe (Maybe(Just, Nothing), fromJust) +import Data.Maybe (Maybe(Just, Nothing), fromJust, fromMaybe) import Data.Newtype (class Newtype, unwrap, wrap) import Data.Op (Op(Op)) import Data.Show.Generic (genericShow) import Data.UInt (UInt) import Data.UInt as UInt import Partial.Unsafe (unsafePartial) +import Test.QuickCheck.Arbitrary (class Arbitrary) +import Test.QuickCheck.Gen (chooseInt) newtype Slot = Slot BigNum @@ -398,6 +400,9 @@ derive instance Generic NetworkId _ instance Show NetworkId where show = genericShow +instance Arbitrary NetworkId where + arbitrary = fromMaybe MainnetId <<< intToNetworkId <$> chooseInt 0 1 + paymentKeyHashStakeKeyHashAddress :: NetworkId -> Ed25519KeyHash -> Ed25519KeyHash -> BaseAddress paymentKeyHashStakeKeyHashAddress networkId pkh skh = baseAddress diff --git a/src/Internal/Serialization/Hash.purs b/src/Internal/Serialization/Hash.purs index b4f20ae727..992b6080ca 100644 --- a/src/Internal/Serialization/Hash.purs +++ b/src/Internal/Serialization/Hash.purs @@ -31,12 +31,20 @@ import Ctl.Internal.Serialization.Types (NativeScript) import Ctl.Internal.ToData (class ToData, toData) import Ctl.Internal.Types.Aliases (Bech32String) import Ctl.Internal.Types.PlutusData (PlutusData(Bytes)) -import Ctl.Internal.Types.RawBytes (RawBytes, hexToRawBytes, rawBytesToHex) +import Ctl.Internal.Types.RawBytes + ( RawBytes + , hexToRawBytes + , rawBytesFromIntArrayUnsafe + , rawBytesToHex + ) import Ctl.Internal.Types.TransactionMetadata (TransactionMetadatum(Bytes)) as Metadata import Data.Either (Either(Left, Right), note) import Data.Function (on) -import Data.Maybe (Maybe(Nothing, Just), maybe) +import Data.Maybe (Maybe(Nothing, Just), fromJust, maybe) import Data.Newtype (unwrap, wrap) +import Partial.Unsafe (unsafePartial) +import Test.QuickCheck.Arbitrary (class Arbitrary) +import Test.QuickCheck.Gen (chooseInt, vectorOf) -- | PubKeyHash and StakeKeyHash refers to blake2b-224 hash digests of Ed25519 -- | verification keys @@ -79,6 +87,11 @@ instance DecodeAeson Ed25519KeyHash where instance EncodeAeson Ed25519KeyHash where encodeAeson' = encodeAeson' <<< rawBytesToHex <<< ed25519KeyHashToBytes +instance Arbitrary Ed25519KeyHash where + arbitrary = + unsafePartial fromJust <<< ed25519KeyHashFromBytes <<< + rawBytesFromIntArrayUnsafe <$> vectorOf 28 (chooseInt 0 255) + foreign import _ed25519KeyHashFromBytesImpl :: MaybeFfiHelper -> RawBytes diff --git a/src/Internal/Types/Transaction.purs b/src/Internal/Types/Transaction.purs index 3fc654a3a0..7cd59e7fb3 100644 --- a/src/Internal/Types/Transaction.purs +++ b/src/Internal/Types/Transaction.purs @@ -11,13 +11,19 @@ import Prelude import Aeson (class DecodeAeson, class EncodeAeson) import Ctl.Internal.FromData (class FromData, fromData) import Ctl.Internal.ToData (class ToData, toData) -import Ctl.Internal.Types.ByteArray (ByteArray, byteArrayToHex) +import Ctl.Internal.Types.ByteArray + ( ByteArray + , byteArrayFromIntArrayUnsafe + , byteArrayToHex + ) import Ctl.Internal.Types.PlutusData (PlutusData(Constr)) import Data.Generic.Rep (class Generic) import Data.Maybe (Maybe(Nothing)) -import Data.Newtype (class Newtype) +import Data.Newtype (class Newtype, wrap) import Data.Show.Generic (genericShow) import Data.UInt (UInt) +import Test.QuickCheck.Arbitrary (class Arbitrary) +import Test.QuickCheck.Gen (chooseInt, vectorOf) newtype TransactionInput = TransactionInput { transactionId :: TransactionHash @@ -85,6 +91,10 @@ instance FromData TransactionHash where instance ToData TransactionHash where toData (TransactionHash bytes) = Constr zero [ toData bytes ] +instance Arbitrary TransactionHash where + arbitrary = + wrap <<< byteArrayFromIntArrayUnsafe <$> vectorOf 32 (chooseInt 0 255) + newtype DataHash = DataHash ByteArray derive instance Generic DataHash _ diff --git a/test/CoinSelection/UtxoIndex.purs b/test/CoinSelection/UtxoIndex.purs new file mode 100644 index 0000000000..3ab9baec37 --- /dev/null +++ b/test/CoinSelection/UtxoIndex.purs @@ -0,0 +1,251 @@ +module Test.Ctl.CoinSelection.UtxoIndex where + +import Prelude + +import Control.Apply (lift2) +import Ctl.Internal.BalanceTx.CoinSelection + ( Asset(..) + , BundleCategory(..) + , UtxoIndex + ) +import Ctl.Internal.BalanceTx.CoinSelection as UtxoIndex +import Ctl.Internal.Cardano.Types.Transaction + ( TransactionOutput(TransactionOutput) + , UtxoMap + ) +import Ctl.Internal.Cardano.Types.Value (Value) +import Ctl.Internal.Cardano.Types.Value (getAssetQuantity, valueAssets) as Value +import Ctl.Internal.Serialization.Address + ( Address + , NetworkId(MainnetId) + , baseAddressToAddress + , paymentKeyHashStakeKeyHashAddress + ) +import Ctl.Internal.Test.TestPlanM (TestPlanM) +import Ctl.Internal.Types.OutputDatum (OutputDatum(NoOutputDatum)) +import Ctl.Internal.Types.Transaction + ( TransactionHash(..) + , TransactionInput(..) + ) +import Data.Array (all) as Array +import Data.BigInt (BigInt) +import Data.BigInt (fromInt) as BigInt +import Data.Foldable (all, and, length) as Foldable +import Data.Generic.Rep (class Generic) +import Data.HashMap (HashMap) +import Data.HashMap (lookup, toArrayBy) as HashMap +import Data.Lens (Lens') +import Data.Lens.Getter ((^.)) +import Data.Map (empty, lookup, toUnfoldable) as Map +import Data.Map.Gen (genMap) as Map +import Data.Maybe (Maybe(Nothing), fromMaybe, maybe) +import Data.Newtype (class Newtype, unwrap, wrap) +import Data.Show.Generic (genericShow) +import Data.Tuple (Tuple(Tuple)) +import Data.Tuple.Nested (type (/\), (/\)) +import Data.UInt (fromInt) as UInt +import Effect.Aff (Aff) +import Mote (group, test) +import Test.QuickCheck (Result(Failed, Success)) as QuickCheck +import Test.QuickCheck.Arbitrary (class Arbitrary, arbitrary) +import Test.QuickCheck.Gen (Gen) +import Test.Spec.Assertions (shouldEqual) +import Test.Spec.QuickCheck (quickCheck) +import Undefined (undefined) + +suite :: TestPlanM (Aff Unit) Unit +suite = + group "UtxoIndex" do + test "prop_buildUtxoIndex_empty" do + UtxoIndex.buildUtxoIndex Map.empty `shouldEqual` UtxoIndex.emptyUtxoIndex + + test "prop_buildUtxoIndex_invariant" do + quickCheck prop_buildUtxoIndex_invariant + +prop_buildUtxoIndex_invariant :: ArbitraryUtxoMap -> QuickCheck.Result +prop_buildUtxoIndex_invariant = + invariantHolds <<< UtxoIndex.buildUtxoIndex <<< unwrap + +-------------------------------------------------------------------------------- +-- Arbitrary +-------------------------------------------------------------------------------- + +newtype ArbitraryUtxoMap = ArbitraryUtxoMap UtxoMap + +derive instance Generic ArbitraryUtxoMap _ +derive instance Newtype ArbitraryUtxoMap _ + +instance Show ArbitraryUtxoMap where + show = genericShow + +instance Arbitrary ArbitraryUtxoMap where + arbitrary = wrap <$> Map.genMap (unwrap <$> oref) (unwrap <$> txOutput) + where + oref :: Gen ArbitraryTransactionInput + oref = arbitrary + + txOutput :: Gen ArbitraryTransactionOutput + txOutput = arbitrary + +newtype ArbitraryTransactionInput = + ArbitraryTransactionInput TransactionInput + +derive instance Newtype ArbitraryTransactionInput _ + +instance Arbitrary ArbitraryTransactionInput where + arbitrary = wrap <$> lift2 mkTxInput arbitrary arbitrary + where + mkTxInput :: TransactionHash -> Int -> TransactionInput + mkTxInput transactionId index = + TransactionInput + { transactionId + , index: UInt.fromInt index + } + +newtype ArbitraryTransactionOutput = + ArbitraryTransactionOutput TransactionOutput + +derive instance Newtype ArbitraryTransactionOutput _ + +instance Arbitrary ArbitraryTransactionOutput where + arbitrary = wrap <$> lift2 mkTxOutput arbitrary arbitrary + where + mkTxOutput :: ArbitraryAddress -> Value -> TransactionOutput + mkTxOutput address amount = + TransactionOutput + { address: unwrap address + , amount + , datum: NoOutputDatum + , scriptRef: Nothing + } + +newtype ArbitraryAddress = ArbitraryAddress Address + +derive instance Newtype ArbitraryAddress _ + +instance Arbitrary ArbitraryAddress where + arbitrary = + wrap <<< baseAddressToAddress <$> + lift2 (paymentKeyHashStakeKeyHashAddress MainnetId) arbitrary arbitrary + +-------------------------------------------------------------------------------- +-- Invariants +-------------------------------------------------------------------------------- + +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/791541da69b9b3f434bb9ead43de406cc18b0373/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L614 +data UtxoIndexInvariantStatus + = InvariantHolds + -- ^ Indicates a successful check of the invariants. + | InvariantUtxoIndexIncomplete + -- ^ Indicates that the `UtxoIndex` is missing one or more entries. + | InvariantUtxoIndexNonMinimal + +-- ^ Indicates that the `UtxoIndex` has one or more unnecessary entries. + +derive instance Generic UtxoIndexInvariantStatus _ + +instance Show UtxoIndexInvariantStatus where + show = genericShow + +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/9d73b57e23392e25148cfc8db560cb8f656cb56a/lib/primitive/test/spec/Cardano/Wallet/Primitive/Types/UTxOIndexSpec.hs#L183 +invariantHolds :: UtxoIndex -> QuickCheck.Result +invariantHolds utxoIndex = + case checkUtxoIndexInvariants utxoIndex of + InvariantHolds -> QuickCheck.Success + status -> QuickCheck.Failed (show status) + +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/791541da69b9b3f434bb9ead43de406cc18b0373/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L632 +checkUtxoIndexInvariants :: UtxoIndex -> UtxoIndexInvariantStatus +checkUtxoIndexInvariants utxoIndex + | not (checkUtxoIndexComplete utxoIndex) = + InvariantUtxoIndexIncomplete + | not (checkUtxoIndexMinimal utxoIndex) = + InvariantUtxoIndexNonMinimal + | otherwise = + InvariantHolds + +-- | Check that every entry from the map of all utxos is properly indexed. +-- | +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/791541da69b9b3f434bb9ead43de406cc18b0373/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L682 +checkUtxoIndexComplete :: UtxoIndex -> Boolean +checkUtxoIndexComplete utxoIndex = + Array.all hasEntries (Map.toUnfoldable $ utxoIndex ^. UtxoIndex._utxos) + where + hasEntries :: TransactionInput /\ TransactionOutput -> Boolean + hasEntries (oref /\ out) = + case UtxoIndex.categorizeUtxoEntry out of + BundleWithNoAssets -> + UtxoIndex._indexSingletons `hasEntryForAsset` AssetLovelace + BundleWithOneAsset asset -> + UtxoIndex._indexPairs `hasEntryForAsset` AssetLovelace + && UtxoIndex._indexSingletons `hasEntryForAsset` Asset asset + BundleWithTwoAssets asset0 asset1 -> + UtxoIndex._indexAnyWith `hasEntryForAsset` AssetLovelace + && UtxoIndex._indexPairs `hasEntryForAsset` Asset asset0 + && UtxoIndex._indexPairs `hasEntryForAsset` Asset asset1 + BundleWithMultipleAssets assets -> + UtxoIndex._indexAnyWith `hasEntryForAsset` AssetLovelace && + flip Foldable.all assets \asset -> + (UtxoIndex._indexAnyWith `hasEntryForAsset` Asset asset) + where + hasEntryForAsset + :: Lens' UtxoIndex (HashMap Asset UtxoMap) -> Asset -> Boolean + hasEntryForAsset getter asset = + maybe false (eq out) $ + (Map.lookup oref =<< HashMap.lookup asset (utxoIndex ^. getter)) + +-- | Check that every indexed entry is required by some entry in the map of all +-- | utxos. +-- | +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/791541da69b9b3f434bb9ead43de406cc18b0373/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L715 +checkUtxoIndexMinimal :: UtxoIndex -> Boolean +checkUtxoIndexMinimal utxoIndex = + UtxoIndex._indexSingletons `testEntriesWith` txOutputHasOneAsset + && UtxoIndex._indexPairs `testEntriesWith` txOutputHasTwoAssetsWith + && UtxoIndex._indexAnyWith `testEntriesWith` txOutputHasAsset + where + testEntriesWith + :: Lens' UtxoIndex (HashMap Asset UtxoMap) + -> (TransactionOutput -> Asset -> Boolean) + -> Boolean + testEntriesWith subset test' = + utxoIndex ^. subset + # HashMap.toArrayBy Tuple + # Array.all \(asset /\ utxos) -> + Array.all (entryMatches (flip test' asset)) (Map.toUnfoldable utxos) + where + entryMatches + :: (TransactionOutput -> Boolean) + -> TransactionInput /\ TransactionOutput + -> Boolean + entryMatches test'' (oref /\ txOutput) = + maybe false test'' $ + Map.lookup oref (utxoIndex ^. UtxoIndex._utxos) + + txOutputHasOneAsset :: TransactionOutput -> Asset -> Boolean + txOutputHasOneAsset txOutput AssetLovelace = + txOutputAssetCount txOutput == zero + txOutputHasOneAsset txOutput asset = + txOutputHasAsset txOutput asset && txOutputAssetCount txOutput == one + + txOutputHasTwoAssetsWith :: TransactionOutput -> Asset -> Boolean + txOutputHasTwoAssetsWith txOutput AssetLovelace = + txOutputAssetCount txOutput == one + txOutputHasTwoAssetsWith txOutput asset = + txOutputHasAsset txOutput asset + && txOutputAssetCount txOutput == BigInt.fromInt 2 + + txOutputHasAsset :: TransactionOutput -> Asset -> Boolean + txOutputHasAsset _ AssetLovelace = true + txOutputHasAsset (TransactionOutput { amount }) (Asset asset) = + Value.getAssetQuantity asset amount >= one + + txOutputAssetCount :: TransactionOutput -> BigInt + txOutputAssetCount = + Foldable.length <<< Value.valueAssets <<< _.amount <<< unwrap + diff --git a/test/Unit.purs b/test/Unit.purs index 8ac64084a3..4324c2a36c 100644 --- a/test/Unit.purs +++ b/test/Unit.purs @@ -9,6 +9,7 @@ import Effect.Class (liftEffect) import Mote.Monad (mapTest) import Test.Ctl.Base64 as Base64 import Test.Ctl.ByteArray as ByteArray +import Test.Ctl.CoinSelection.UtxoIndex as UtxoIndex import Test.Ctl.Data as Data import Test.Ctl.Data.Interval as Ctl.Data.Interval import Test.Ctl.Deserialization as Deserialization @@ -79,3 +80,4 @@ testPlan = do <*> Types.Interval.systemStartFixture E2E.Route.suite MustSpendTotal.suite + UtxoIndex.suite From 0455c588463456aeae180225bdc3011a722ebf47 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Thu, 8 Dec 2022 17:45:24 +0100 Subject: [PATCH 072/373] Add more tests for UtxoIndex, Minor UtxoIndex refactorings, Fix warnings --- src/Internal/BalanceTx/BalanceTx.purs | 7 +- src/Internal/BalanceTx/CoinSelection.purs | 229 ++----------- src/Internal/CoinSelection/UtxoIndex.purs | 388 ++++++++++++++++++++++ test/CoinSelection/UtxoIndex.purs | 213 ++++-------- 4 files changed, 475 insertions(+), 362 deletions(-) create mode 100644 src/Internal/CoinSelection/UtxoIndex.purs diff --git a/src/Internal/BalanceTx/BalanceTx.purs b/src/Internal/BalanceTx/BalanceTx.purs index 9fce0e0d01..9023fcb27b 100644 --- a/src/Internal/BalanceTx/BalanceTx.purs +++ b/src/Internal/BalanceTx/BalanceTx.purs @@ -13,9 +13,7 @@ import Control.Parallel (parTraverse) import Ctl.Internal.BalanceTx.CoinSelection ( SelectionState , SelectionStrategy - , UtxoIndex , _leftoverUtxos - , buildUtxoIndex , performMultiAssetSelection , selectedInputs ) @@ -113,6 +111,7 @@ import Ctl.Internal.Cardano.Types.Value , getAssetQuantity , valueAssets ) as Value +import Ctl.Internal.CoinSelection.UtxoIndex (UtxoIndex, buildUtxoIndex) import Ctl.Internal.Helpers ((??)) import Ctl.Internal.Partition (equipartition, partition) import Ctl.Internal.QueryM (QueryM, getProtocolParameters) @@ -306,7 +305,7 @@ runBalancer p = do -- | after generation of change, the first balancing step `PrebalanceTx` -- | is performed, otherwise we proceed to `BalanceChangeAndMinFee`. runNextBalancerStep :: BalancerState -> BalanceTxM FinalizedTransaction - runNextBalancerStep state@{ transaction, leftoverUtxos } = do + runNextBalancerStep state@{ transaction } = do let txBody = transaction ^. _body' inputValue <- except $ getInputValue p.allUtxos txBody changeOutputs <- makeChange p.changeAddress inputValue p.certsFee txBody @@ -354,7 +353,7 @@ runBalancer p = do -- | since this pre-condition is sometimes required for successfull script -- | execution during transaction evaluation. evaluateTx :: BalancerState -> BalanceTxM BalancerState - evaluateTx state@{ transaction, changeOutputs, leftoverUtxos } = do + evaluateTx state@{ transaction, changeOutputs } = do let prebalancedTx :: PrebalancedTransaction prebalancedTx = wrap $ setTxChangeOutputs changeOutputs transaction diff --git a/src/Internal/BalanceTx/CoinSelection.purs b/src/Internal/BalanceTx/CoinSelection.purs index 1e3c5b6f9d..50de43e42b 100644 --- a/src/Internal/BalanceTx/CoinSelection.purs +++ b/src/Internal/BalanceTx/CoinSelection.purs @@ -5,17 +5,13 @@ -- | The algorithm supports two selection strategies (optimal and minimal) and -- | uses priority ordering and round-robin processing to handle the problem -- | of over-selection. -module Ctl.Internal.BalanceTx.CoinSelection {-( Asset - , SelectionState(SelectionState) +module Ctl.Internal.BalanceTx.CoinSelection + ( SelectionState(SelectionState) , SelectionStrategy(SelectionStrategyMinimal, SelectionStrategyOptimal) - , UtxoIndex(UtxoIndex) , _leftoverUtxos - , _utxos - , buildUtxoIndex - , emptyUtxoIndex , performMultiAssetSelection , selectedInputs - )-} where + ) where import Prelude @@ -29,49 +25,48 @@ import Ctl.Internal.BalanceTx.Error , Expected(Expected) , ImpossibleError(Impossible) ) -import Ctl.Internal.Cardano.Types.Transaction (TransactionOutput, UtxoMap) +import Ctl.Internal.Cardano.Types.Transaction (UtxoMap) import Ctl.Internal.Cardano.Types.Value (AssetClass(AssetClass), Coin, Value) import Ctl.Internal.Cardano.Types.Value ( getAssetQuantity , getCurrencySymbol , leq - , valueAssetClasses , valueAssets , valueToCoin , valueToCoin' ) as Value +import Ctl.Internal.CoinSelection.UtxoIndex + ( Asset(Asset, AssetLovelace) + , SelectionFilter(SelectAnyWith, SelectPairWith, SelectSingleton) + , TxUnspentOutput + , UtxoIndex + , selectRandomWithFilter + , utxoIndexDeleteEntry + , utxoIndexUniverse + ) import Ctl.Internal.Types.ByteArray (byteArrayToHex) import Ctl.Internal.Types.TokenName (getTokenName) as TokenName import Ctl.Internal.Types.Transaction (TransactionInput) import Data.Array (snoc, uncons) as Array -import Data.Array ((!!)) import Data.Array.NonEmpty (NonEmptyArray) import Data.Array.NonEmpty (cons', fromArray, singleton, uncons) as NEArray import Data.BigInt (BigInt) import Data.BigInt (abs, fromInt, toString) as BigInt import Data.Foldable (foldMap) as Foldable -import Data.Foldable (foldl) import Data.Function (applyFlipped) -import Data.Generic.Rep (class Generic) -import Data.HashMap (HashMap) -import Data.HashMap (alter, empty, lookup, update) as HashMap -import Data.Hashable (class Hashable, hash) import Data.Lens (Lens') import Data.Lens.Getter (view, (^.)) import Data.Lens.Iso.Newtype (_Newtype) import Data.Lens.Record (prop) -import Data.Lens.Setter (over, (%~)) -import Data.Map (Map) +import Data.Lens.Setter (over) import Data.Map as Map -import Data.Maybe (Maybe(Just, Nothing), fromMaybe, maybe, maybe') +import Data.Maybe (Maybe(Just, Nothing), maybe, maybe') import Data.Newtype (class Newtype, unwrap, wrap) import Data.Set (Set) -import Data.Set (fromFoldable, toUnfoldable) as Set -import Data.Show.Generic (genericShow) +import Data.Set (fromFoldable) as Set import Data.Tuple (fst) as Tuple import Data.Tuple.Nested (type (/\), (/\)) -import Effect.Class (class MonadEffect, liftEffect) -import Effect.Random (randomInt) as Random +import Effect.Class (class MonadEffect) import Type.Proxy (Proxy(Proxy)) -------------------------------------------------------------------------------- @@ -88,7 +83,7 @@ import Type.Proxy (Proxy(Proxy)) -- | strategy will help to ensure that a wallet's utxo distribution can evolve -- | over time to resemble the typical distribution of payments made by the -- | wallet owner. --- | +-- , utxoIndexUniverse| -- | Specifying `SelectionStrategyMinimal` will cause the selection algorithm to -- | only select just enough of each asset from the available utxo set to meet -- | the required amount. It is advised to use this strategy only when @@ -128,7 +123,7 @@ performMultiAssetSelection strategy utxoIndex requiredValue = BalanceInsufficientError (Expected requiredValue) (Actual availableValue) availableValue :: Value - availableValue = balance (utxoIndex ^. _utxos) + availableValue = balance (utxoIndexUniverse utxoIndex) selectors :: Array (SelectionState -> m (Maybe SelectionState)) @@ -422,196 +417,10 @@ selectRandomWithPriority utxoIndex filters = maybe' (\_ -> selectRandomWithPriority utxoIndex xs) (pure <<< Just) =<< selectRandomWithFilter utxoIndex filter --------------------------------------------------------------------------------- --- Asset --------------------------------------------------------------------------------- - --- | Taken from cardano-wallet: --- | https://github.com/input-output-hk/cardano-wallet/blob/791541da69b9b3f434bb9ead43de406cc18b0373/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L485 -data Asset = AssetLovelace | Asset AssetClass - -derive instance Generic Asset _ -derive instance Eq Asset - -instance Show Asset where - show = genericShow - -instance Hashable Asset where - hash AssetLovelace = hash (Nothing :: Maybe AssetClass) - hash (Asset asset) = hash (Just asset) - --------------------------------------------------------------------------------- --- SelectionFilter --------------------------------------------------------------------------------- - --- | Taken from cardano-wallet: --- | https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L399 -data SelectionFilter - = SelectSingleton Asset - | SelectPairWith Asset - | SelectAnyWith Asset - -type TxUnspentOutput = TransactionInput /\ TransactionOutput - --------------------------------------------------------------------------------- --- UtxoIndex --------------------------------------------------------------------------------- - --- | Taken from cardano-wallet: --- | https://github.com/input-output-hk/cardano-wallet/blob/791541da69b9b3f434bb9ead43de406cc18b0373/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L537 -data BundleCategory - = BundleWithNoAssets - | BundleWithOneAsset AssetClass - | BundleWithTwoAssets AssetClass AssetClass - | BundleWithMultipleAssets (Set AssetClass) - --- | Taken from cardano-wallet: --- | https://github.com/input-output-hk/cardano-wallet/blob/791541da69b9b3f434bb9ead43de406cc18b0373/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L546 -categorizeUtxoEntry :: TransactionOutput -> BundleCategory -categorizeUtxoEntry txOutput = case Set.toUnfoldable bundleAssets of - [] -> BundleWithNoAssets - [ a ] -> BundleWithOneAsset a - [ a, b ] -> BundleWithTwoAssets a b - _ -> BundleWithMultipleAssets bundleAssets - where - bundleAssets :: Set AssetClass - bundleAssets = txOutputAssetClasses txOutput - --- | Taken from cardano-wallet: --- | https://github.com/input-output-hk/cardano-wallet/blob/791541da69b9b3f434bb9ead43de406cc18b0373/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L176 -newtype UtxoIndex = UtxoIndex - { indexAnyWith :: HashMap Asset UtxoMap - -- ^ An index of all utxos that contain the given asset. - , indexSingletons :: HashMap Asset UtxoMap - -- ^ An index of all utxos that contain the given asset and no other assets. - , indexPairs :: HashMap Asset UtxoMap - -- ^ An index of all utxos that contain the given asset and exactly one - -- other asset. - , utxos :: UtxoMap - -- ^ The complete set of all utxos. - } - -derive instance Generic UtxoIndex _ -derive instance Newtype UtxoIndex _ -derive instance Eq UtxoIndex - -instance Show UtxoIndex where - show = genericShow - -_indexAnyWith :: Lens' UtxoIndex (HashMap Asset UtxoMap) -_indexAnyWith = _Newtype <<< prop (Proxy :: Proxy "indexAnyWith") - -_indexSingletons :: Lens' UtxoIndex (HashMap Asset UtxoMap) -_indexSingletons = _Newtype <<< prop (Proxy :: Proxy "indexSingletons") - -_indexPairs :: Lens' UtxoIndex (HashMap Asset UtxoMap) -_indexPairs = _Newtype <<< prop (Proxy :: Proxy "indexPairs") - -_utxos :: Lens' UtxoIndex UtxoMap -_utxos = _Newtype <<< prop (Proxy :: Proxy "utxos") - -buildUtxoIndex :: UtxoMap -> UtxoIndex -buildUtxoIndex utxos = - foldl (flip utxoIndexInsertEntry) emptyUtxoIndex utxos' - where - utxos' :: Array TxUnspentOutput - utxos' = Map.toUnfoldable utxos - -emptyUtxoIndex :: UtxoIndex -emptyUtxoIndex = UtxoIndex - { indexAnyWith: HashMap.empty - , indexSingletons: HashMap.empty - , indexPairs: HashMap.empty - , utxos: Map.empty - } - --- | Taken from cardano-wallet: --- | https://github.com/input-output-hk/cardano-wallet/blob/791541da69b9b3f434bb9ead43de406cc18b0373/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L561 -utxoIndexInsertEntry :: TxUnspentOutput -> UtxoIndex -> UtxoIndex -utxoIndexInsertEntry (oref /\ out) = - (_utxos %~ Map.insert oref out) <<< updateUtxoIndex out insertEntry - where - insertEntry :: Asset -> HashMap Asset UtxoMap -> HashMap Asset UtxoMap - insertEntry = - HashMap.alter - (Just <<< maybe (Map.singleton oref out) (Map.insert oref out)) - --- | Taken from cardano-wallet: --- | https://github.com/input-output-hk/cardano-wallet/blob/791541da69b9b3f434bb9ead43de406cc18b0373/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L295 -utxoIndexDeleteEntry :: TxUnspentOutput -> UtxoIndex -> UtxoIndex -utxoIndexDeleteEntry (inp /\ out) = - (_utxos %~ Map.delete inp) <<< updateUtxoIndex out deleteEntry - where - deleteEntry :: Asset -> HashMap Asset UtxoMap -> HashMap Asset UtxoMap - deleteEntry = HashMap.update (Just <<< Map.delete inp) - -updateUtxoIndex - :: TransactionOutput - -> (Asset -> HashMap Asset UtxoMap -> HashMap Asset UtxoMap) - -> UtxoIndex - -> UtxoIndex -updateUtxoIndex out manageEntry = - case categorizeUtxoEntry out of - BundleWithNoAssets -> - _indexSingletons %~ manageEntry AssetLovelace - BundleWithOneAsset asset -> - (_indexPairs %~ manageEntry AssetLovelace) - <<< (_indexSingletons %~ manageEntry (Asset asset)) - BundleWithTwoAssets asset0 asset1 -> - (_indexAnyWith %~ manageEntry AssetLovelace) - <<< (_indexPairs %~ manageEntry (Asset asset0)) - <<< (_indexPairs %~ manageEntry (Asset asset1)) - BundleWithMultipleAssets assets -> - (_indexAnyWith %~ flip (foldl (flip (manageEntry <<< Asset))) assets) - <<< (_indexAnyWith %~ manageEntry AssetLovelace) - --- | Taken from cardano-wallet: --- | https://github.com/input-output-hk/cardano-wallet/blob/791541da69b9b3f434bb9ead43de406cc18b0373/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L418 -selectRandomWithFilter - :: forall (m :: Type -> Type) - . MonadEffect m - => UtxoIndex - -> SelectionFilter - -> m (Maybe (TxUnspentOutput /\ UtxoIndex)) -selectRandomWithFilter utxoIndex selectionFilter = - selectRandomMapMember selectionUtxoMap - <#> map (\utxo -> utxo /\ utxoIndexDeleteEntry utxo utxoIndex) - where - selectionUtxoMap :: UtxoMap - selectionUtxoMap = - case selectionFilter of - SelectSingleton asset -> - asset `lookupWith` _indexSingletons - SelectPairWith asset -> - asset `lookupWith` _indexPairs - SelectAnyWith asset -> - asset `lookupWith` _indexAnyWith - where - lookupWith :: Asset -> Lens' UtxoIndex (HashMap Asset UtxoMap) -> UtxoMap - lookupWith asset getter = - fromMaybe Map.empty $ HashMap.lookup asset (utxoIndex ^. getter) - -------------------------------------------------------------------------------- -- Helpers -------------------------------------------------------------------------------- --- | Taken from cardano-wallet: --- | https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L598 -selectRandomMapMember - :: forall (m :: Type -> Type) (k :: Type) (v :: Type) - . MonadEffect m - => Map k v - -> m (Maybe (k /\ v)) -selectRandomMapMember m - | Map.isEmpty m = pure Nothing - | otherwise = liftEffect do - idx <- Random.randomInt zero (Map.size m - one) - pure $ Map.toUnfoldable m !! idx - -txOutputAssetClasses :: TransactionOutput -> Set AssetClass -txOutputAssetClasses = - Set.fromFoldable <<< Value.valueAssetClasses <<< _.amount <<< unwrap - showAssetClassWithQuantity :: AssetClass -> BigInt -> String showAssetClassWithQuantity (AssetClass cs tn) quantity = "(Asset (" <> displayCurrencySymbol <> displayTokenName <> displayQuantity diff --git a/src/Internal/CoinSelection/UtxoIndex.purs b/src/Internal/CoinSelection/UtxoIndex.purs new file mode 100644 index 0000000000..bceec72867 --- /dev/null +++ b/src/Internal/CoinSelection/UtxoIndex.purs @@ -0,0 +1,388 @@ +module Ctl.Internal.CoinSelection.UtxoIndex + ( Asset(Asset, AssetLovelace) + , SelectionFilter(SelectAnyWith, SelectPairWith, SelectSingleton) + , TxUnspentOutput + , UtxoIndex + , UtxoIndexInvariantStatus + ( InvariantHolds + , InvariantUtxoIndexIncomplete + , InvariantUtxoIndexNonMinimal + ) + , buildUtxoIndex + , checkUtxoIndexInvariants + , emptyUtxoIndex + , selectRandomWithFilter + , utxoIndexDeleteEntry + , utxoIndexInsertEntry + , utxoIndexUniverse + ) where + +import Prelude + +import Ctl.Internal.Cardano.Types.Transaction + ( TransactionOutput(TransactionOutput) + , UtxoMap + ) +import Ctl.Internal.Cardano.Types.Value (AssetClass) +import Ctl.Internal.Cardano.Types.Value + ( getAssetQuantity + , valueAssetClasses + , valueAssets + ) as Value +import Ctl.Internal.Types.Transaction (TransactionInput) +import Data.Array (all, foldl) as Array +import Data.Array ((!!)) +import Data.BigInt (BigInt) +import Data.BigInt (fromInt) as BigInt +import Data.Foldable (all, length) as Foldable +import Data.Foldable (foldl) +import Data.Generic.Rep (class Generic) +import Data.HashMap (HashMap) +import Data.HashMap (alter, empty, lookup, toArrayBy, update) as HashMap +import Data.Hashable (class Hashable, hash) +import Data.Lens (Lens') +import Data.Lens.Getter (view, (^.)) +import Data.Lens.Iso (Iso', iso) +import Data.Lens.Record (prop) +import Data.Lens.Setter ((%~)) +import Data.Map (Map) +import Data.Map + ( delete + , empty + , insert + , isEmpty + , lookup + , singleton + , size + , toUnfoldable + ) as Map +import Data.Maybe (Maybe(Just, Nothing), fromMaybe, maybe) +import Data.Newtype (unwrap) +import Data.Set (Set) +import Data.Set (fromFoldable, toUnfoldable) as Set +import Data.Show.Generic (genericShow) +import Data.Tuple (Tuple(Tuple)) +import Data.Tuple.Nested (type (/\), (/\)) +import Effect.Class (class MonadEffect, liftEffect) +import Effect.Random (randomInt) as Random +import Type.Proxy (Proxy(Proxy)) + +-- | A utxo set that is indexed by asset identifier. +-- | The index provides a mapping from assets to subsets of the utxo set. +-- | +-- | The index makes it possible to efficiently compute the subset of a utxo set +-- | containing a particular asset, or to select just a single utxo containing a +-- | particular asset, without having to search linearly through the entire set +-- | +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/791541da69b9b3f434bb9ead43de406cc18b0373/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L176 +type UtxoIndexRec = + { indexAnyWith :: HashMap Asset UtxoMap + -- ^ An index of all utxos that contain the given asset. + , indexSingletons :: HashMap Asset UtxoMap + -- ^ An index of all utxos that contain the given asset and no other assets. + , indexPairs :: HashMap Asset UtxoMap + -- ^ An index of all utxos that contain the given asset and exactly one + -- other asset. + , utxos :: UtxoMap + -- ^ The complete set of all utxos. + } + +newtype UtxoIndex = UtxoIndex UtxoIndexRec + +derive instance Eq UtxoIndex + +instance Show UtxoIndex where + show (UtxoIndex utxoIndex) = "(UtxoIndex " <> show utxoIndex <> ")" + +utxoIndexUniverse :: UtxoIndex -> UtxoMap +utxoIndexUniverse = view _utxos + +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/791541da69b9b3f434bb9ead43de406cc18b0373/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L485 +data Asset = AssetLovelace | Asset AssetClass + +derive instance Generic Asset _ +derive instance Eq Asset + +instance Show Asset where + show = genericShow + +instance Hashable Asset where + hash AssetLovelace = hash (Nothing :: Maybe AssetClass) + hash (Asset asset) = hash (Just asset) + +-------------------------------------------------------------------------------- +-- Builders +-------------------------------------------------------------------------------- + +-- | An index with no entries. +emptyUtxoIndex :: UtxoIndex +emptyUtxoIndex = UtxoIndex + { indexAnyWith: HashMap.empty + , indexSingletons: HashMap.empty + , indexPairs: HashMap.empty + , utxos: Map.empty + } + +-- | Creates an index from a `UtxoMap`. +buildUtxoIndex :: UtxoMap -> UtxoIndex +buildUtxoIndex = + Array.foldl (flip utxoIndexInsertEntry) emptyUtxoIndex <<< Map.toUnfoldable + +-------------------------------------------------------------------------------- +-- Modifiers +-------------------------------------------------------------------------------- + +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/791541da69b9b3f434bb9ead43de406cc18b0373/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L561 +utxoIndexInsertEntry :: TxUnspentOutput -> UtxoIndex -> UtxoIndex +utxoIndexInsertEntry (oref /\ out) = + (_utxos %~ Map.insert oref out) <<< updateUtxoIndex out insertEntry + where + insertEntry :: Asset -> HashMap Asset UtxoMap -> HashMap Asset UtxoMap + insertEntry = + HashMap.alter + (Just <<< maybe (Map.singleton oref out) (Map.insert oref out)) + +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/791541da69b9b3f434bb9ead43de406cc18b0373/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L295 +utxoIndexDeleteEntry :: TxUnspentOutput -> UtxoIndex -> UtxoIndex +utxoIndexDeleteEntry (inp /\ out) = + (_utxos %~ Map.delete inp) <<< updateUtxoIndex out deleteEntry + where + deleteEntry :: Asset -> HashMap Asset UtxoMap -> HashMap Asset UtxoMap + deleteEntry = HashMap.update (Just <<< Map.delete inp) + +updateUtxoIndex + :: TransactionOutput + -> (Asset -> HashMap Asset UtxoMap -> HashMap Asset UtxoMap) + -> UtxoIndex + -> UtxoIndex +updateUtxoIndex out manageEntry = + case categorizeUtxoEntry out of + BundleWithNoAssets -> + _indexSingletons %~ manageEntry AssetLovelace + BundleWithOneAsset asset -> + (_indexPairs %~ manageEntry AssetLovelace) + <<< (_indexSingletons %~ manageEntry (Asset asset)) + BundleWithTwoAssets asset0 asset1 -> + (_indexAnyWith %~ manageEntry AssetLovelace) + <<< (_indexPairs %~ manageEntry (Asset asset0)) + <<< (_indexPairs %~ manageEntry (Asset asset1)) + BundleWithMultipleAssets assets -> + (_indexAnyWith %~ flip (foldl (flip (manageEntry <<< Asset))) assets) + <<< (_indexAnyWith %~ manageEntry AssetLovelace) + +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/791541da69b9b3f434bb9ead43de406cc18b0373/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L537 +data BundleCategory + = BundleWithNoAssets + | BundleWithOneAsset AssetClass + | BundleWithTwoAssets AssetClass AssetClass + | BundleWithMultipleAssets (Set AssetClass) + +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/791541da69b9b3f434bb9ead43de406cc18b0373/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L546 +categorizeUtxoEntry :: TransactionOutput -> BundleCategory +categorizeUtxoEntry txOutput = case Set.toUnfoldable bundleAssets of + [] -> BundleWithNoAssets + [ a ] -> BundleWithOneAsset a + [ a, b ] -> BundleWithTwoAssets a b + _ -> BundleWithMultipleAssets bundleAssets + where + bundleAssets :: Set AssetClass + bundleAssets = txOutputAssetClasses txOutput + +-------------------------------------------------------------------------------- +-- Selection +-------------------------------------------------------------------------------- + +type TxUnspentOutput = TransactionInput /\ TransactionOutput + +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L399 +data SelectionFilter + = SelectSingleton Asset + | SelectPairWith Asset + | SelectAnyWith Asset + +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/791541da69b9b3f434bb9ead43de406cc18b0373/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L418 +selectRandomWithFilter + :: forall (m :: Type -> Type) + . MonadEffect m + => UtxoIndex + -> SelectionFilter + -> m (Maybe (TxUnspentOutput /\ UtxoIndex)) +selectRandomWithFilter utxoIndex selectionFilter = + selectRandomMapMember selectionUtxoMap + <#> map (\utxo -> utxo /\ utxoIndexDeleteEntry utxo utxoIndex) + where + selectionUtxoMap :: UtxoMap + selectionUtxoMap = + case selectionFilter of + SelectSingleton asset -> + asset `lookupWith` _indexSingletons + SelectPairWith asset -> + asset `lookupWith` _indexPairs + SelectAnyWith asset -> + asset `lookupWith` _indexAnyWith + where + lookupWith :: Asset -> Lens' UtxoIndex (HashMap Asset UtxoMap) -> UtxoMap + lookupWith asset getter = + fromMaybe Map.empty $ HashMap.lookup asset (utxoIndex ^. getter) + +-------------------------------------------------------------------------------- +-- Lenses for accessing `UtxoIndex` fields +-------------------------------------------------------------------------------- + +_UtxoIndex :: Iso' UtxoIndex UtxoIndexRec +_UtxoIndex = iso (\(UtxoIndex rec) -> rec) UtxoIndex + +_indexAnyWith :: Lens' UtxoIndex (HashMap Asset UtxoMap) +_indexAnyWith = _UtxoIndex <<< prop (Proxy :: Proxy "indexAnyWith") + +_indexSingletons :: Lens' UtxoIndex (HashMap Asset UtxoMap) +_indexSingletons = _UtxoIndex <<< prop (Proxy :: Proxy "indexSingletons") + +_indexPairs :: Lens' UtxoIndex (HashMap Asset UtxoMap) +_indexPairs = _UtxoIndex <<< prop (Proxy :: Proxy "indexPairs") + +_utxos :: Lens' UtxoIndex UtxoMap +_utxos = _UtxoIndex <<< prop (Proxy :: Proxy "utxos") + +-------------------------------------------------------------------------------- +-- Helpers +-------------------------------------------------------------------------------- + +txOutputAssetClasses :: TransactionOutput -> Set AssetClass +txOutputAssetClasses = + Set.fromFoldable <<< Value.valueAssetClasses <<< _.amount <<< unwrap + +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/3d722b27f6dbd2cf05da497297e60e3b54b1ef6e/lib/wallet/src/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L598 +selectRandomMapMember + :: forall (m :: Type -> Type) (k :: Type) (v :: Type) + . MonadEffect m + => Map k v + -> m (Maybe (k /\ v)) +selectRandomMapMember m + | Map.isEmpty m = pure Nothing + | otherwise = liftEffect do + idx <- Random.randomInt zero (Map.size m - one) + pure $ Map.toUnfoldable m !! idx + +-------------------------------------------------------------------------------- +-- Invariant +-------------------------------------------------------------------------------- + +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/791541da69b9b3f434bb9ead43de406cc18b0373/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L614 +data UtxoIndexInvariantStatus + = InvariantHolds + -- ^ Indicates a successful check of the invariants. + | InvariantUtxoIndexIncomplete + -- ^ Indicates that the `UtxoIndex` is missing one or more entries. + | InvariantUtxoIndexNonMinimal + +-- ^ Indicates that the `UtxoIndex` has one or more unnecessary entries. + +derive instance Generic UtxoIndexInvariantStatus _ + +instance Show UtxoIndexInvariantStatus where + show = genericShow + +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/791541da69b9b3f434bb9ead43de406cc18b0373/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L632 +checkUtxoIndexInvariants :: UtxoIndex -> UtxoIndexInvariantStatus +checkUtxoIndexInvariants utxoIndex + | not (checkUtxoIndexComplete utxoIndex) = + InvariantUtxoIndexIncomplete + | not (checkUtxoIndexMinimal utxoIndex) = + InvariantUtxoIndexNonMinimal + | otherwise = + InvariantHolds + +-- | Check that every entry from the map of all utxos is properly indexed. +-- | +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/791541da69b9b3f434bb9ead43de406cc18b0373/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L682 +checkUtxoIndexComplete :: UtxoIndex -> Boolean +checkUtxoIndexComplete utxoIndex = + Array.all hasEntries (Map.toUnfoldable $ utxoIndex ^. _utxos) + where + hasEntries :: TransactionInput /\ TransactionOutput -> Boolean + hasEntries (oref /\ out) = + case categorizeUtxoEntry out of + BundleWithNoAssets -> + _indexSingletons `hasEntryForAsset` AssetLovelace + BundleWithOneAsset asset -> + _indexPairs `hasEntryForAsset` AssetLovelace + && _indexSingletons `hasEntryForAsset` Asset asset + BundleWithTwoAssets asset0 asset1 -> + _indexAnyWith `hasEntryForAsset` AssetLovelace + && _indexPairs `hasEntryForAsset` Asset asset0 + && _indexPairs `hasEntryForAsset` Asset asset1 + BundleWithMultipleAssets assets -> + _indexAnyWith `hasEntryForAsset` AssetLovelace && + flip Foldable.all assets \asset -> + (_indexAnyWith `hasEntryForAsset` Asset asset) + where + hasEntryForAsset + :: Lens' UtxoIndex (HashMap Asset UtxoMap) -> Asset -> Boolean + hasEntryForAsset getter asset = + maybe false (eq out) $ + (Map.lookup oref =<< HashMap.lookup asset (utxoIndex ^. getter)) + +-- | Check that every indexed entry is required by some entry in the map of all +-- | utxos. +-- | +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/791541da69b9b3f434bb9ead43de406cc18b0373/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L715 +checkUtxoIndexMinimal :: UtxoIndex -> Boolean +checkUtxoIndexMinimal utxoIndex = + _indexSingletons `testEntriesWith` txOutputHasOneAsset + && _indexPairs `testEntriesWith` txOutputHasTwoAssetsWith + && _indexAnyWith `testEntriesWith` txOutputHasAsset + where + testEntriesWith + :: Lens' UtxoIndex (HashMap Asset UtxoMap) + -> (TransactionOutput -> Asset -> Boolean) + -> Boolean + testEntriesWith subset test' = + utxoIndex ^. subset + # HashMap.toArrayBy Tuple + # Array.all \(asset /\ utxos) -> + Array.all (entryMatches (flip test' asset)) (Map.toUnfoldable utxos) + where + entryMatches + :: (TransactionOutput -> Boolean) + -> TransactionInput /\ TransactionOutput + -> Boolean + entryMatches test'' (oref /\ _) = + maybe false test'' $ + Map.lookup oref (utxoIndexUniverse utxoIndex) + + txOutputHasOneAsset :: TransactionOutput -> Asset -> Boolean + txOutputHasOneAsset txOutput AssetLovelace = + txOutputAssetCount txOutput == zero + txOutputHasOneAsset txOutput asset = + txOutputHasAsset txOutput asset && txOutputAssetCount txOutput == one + + txOutputHasTwoAssetsWith :: TransactionOutput -> Asset -> Boolean + txOutputHasTwoAssetsWith txOutput AssetLovelace = + txOutputAssetCount txOutput == one + txOutputHasTwoAssetsWith txOutput asset = + txOutputHasAsset txOutput asset + && txOutputAssetCount txOutput == BigInt.fromInt 2 + + txOutputHasAsset :: TransactionOutput -> Asset -> Boolean + txOutputHasAsset _ AssetLovelace = true + txOutputHasAsset (TransactionOutput { amount }) (Asset asset) = + Value.getAssetQuantity asset amount >= one + + txOutputAssetCount :: TransactionOutput -> BigInt + txOutputAssetCount = + Foldable.length <<< Value.valueAssets <<< _.amount <<< unwrap + diff --git a/test/CoinSelection/UtxoIndex.purs b/test/CoinSelection/UtxoIndex.purs index 3ab9baec37..2222dd14f3 100644 --- a/test/CoinSelection/UtxoIndex.purs +++ b/test/CoinSelection/UtxoIndex.purs @@ -3,18 +3,22 @@ module Test.Ctl.CoinSelection.UtxoIndex where import Prelude import Control.Apply (lift2) -import Ctl.Internal.BalanceTx.CoinSelection - ( Asset(..) - , BundleCategory(..) - , UtxoIndex - ) -import Ctl.Internal.BalanceTx.CoinSelection as UtxoIndex import Ctl.Internal.Cardano.Types.Transaction ( TransactionOutput(TransactionOutput) , UtxoMap ) import Ctl.Internal.Cardano.Types.Value (Value) -import Ctl.Internal.Cardano.Types.Value (getAssetQuantity, valueAssets) as Value +import Ctl.Internal.CoinSelection.UtxoIndex + ( UtxoIndex + , UtxoIndexInvariantStatus(InvariantHolds) + ) +import Ctl.Internal.CoinSelection.UtxoIndex + ( buildUtxoIndex + , checkUtxoIndexInvariants + , emptyUtxoIndex + , utxoIndexDeleteEntry + , utxoIndexInsertEntry + ) as UtxoIndex import Ctl.Internal.Serialization.Address ( Address , NetworkId(MainnetId) @@ -24,25 +28,17 @@ import Ctl.Internal.Serialization.Address import Ctl.Internal.Test.TestPlanM (TestPlanM) import Ctl.Internal.Types.OutputDatum (OutputDatum(NoOutputDatum)) import Ctl.Internal.Types.Transaction - ( TransactionHash(..) - , TransactionInput(..) + ( TransactionHash + , TransactionInput(TransactionInput) ) -import Data.Array (all) as Array -import Data.BigInt (BigInt) -import Data.BigInt (fromInt) as BigInt -import Data.Foldable (all, and, length) as Foldable import Data.Generic.Rep (class Generic) -import Data.HashMap (HashMap) -import Data.HashMap (lookup, toArrayBy) as HashMap -import Data.Lens (Lens') -import Data.Lens.Getter ((^.)) -import Data.Map (empty, lookup, toUnfoldable) as Map +import Data.Map (empty) as Map import Data.Map.Gen (genMap) as Map -import Data.Maybe (Maybe(Nothing), fromMaybe, maybe) +import Data.Maybe (Maybe(Nothing)) import Data.Newtype (class Newtype, unwrap, wrap) import Data.Show.Generic (genericShow) import Data.Tuple (Tuple(Tuple)) -import Data.Tuple.Nested (type (/\), (/\)) +import Data.Tuple.Nested (type (/\)) import Data.UInt (fromInt) as UInt import Effect.Aff (Aff) import Mote (group, test) @@ -51,7 +47,6 @@ import Test.QuickCheck.Arbitrary (class Arbitrary, arbitrary) import Test.QuickCheck.Gen (Gen) import Test.Spec.Assertions (shouldEqual) import Test.Spec.QuickCheck (quickCheck) -import Undefined (undefined) suite :: TestPlanM (Aff Unit) Unit suite = @@ -62,14 +57,49 @@ suite = test "prop_buildUtxoIndex_invariant" do quickCheck prop_buildUtxoIndex_invariant + test "prop_utxoIndexInsertEntry_invariant" do + quickCheck prop_utxoIndexInsertEntry_invariant + + test "prop_utxoIndexDeleteEntry_invariant" do + quickCheck prop_utxoIndexDeleteEntry_invariant + prop_buildUtxoIndex_invariant :: ArbitraryUtxoMap -> QuickCheck.Result prop_buildUtxoIndex_invariant = invariantHolds <<< UtxoIndex.buildUtxoIndex <<< unwrap +prop_utxoIndexInsertEntry_invariant + :: ArbitraryTxUnspentOut -> ArbitraryUtxoIndex -> QuickCheck.Result +prop_utxoIndexInsertEntry_invariant entry utxoIndex = + invariantHolds $ + UtxoIndex.utxoIndexInsertEntry (unwrap entry) (unwrap utxoIndex) + +prop_utxoIndexDeleteEntry_invariant + :: ArbitraryTxUnspentOut -> ArbitraryUtxoIndex -> QuickCheck.Result +prop_utxoIndexDeleteEntry_invariant entry utxoIndex = + invariantHolds $ + UtxoIndex.utxoIndexDeleteEntry (unwrap entry) (unwrap utxoIndex) + +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/9d73b57e23392e25148cfc8db560cb8f656cb56a/lib/primitive/test/spec/Cardano/Wallet/Primitive/Types/UTxOIndexSpec.hs#L183 +invariantHolds :: UtxoIndex -> QuickCheck.Result +invariantHolds utxoIndex = + case UtxoIndex.checkUtxoIndexInvariants utxoIndex of + InvariantHolds -> QuickCheck.Success + status -> QuickCheck.Failed (show status) + -------------------------------------------------------------------------------- -- Arbitrary -------------------------------------------------------------------------------- +newtype ArbitraryUtxoIndex = ArbitraryUtxoIndex UtxoIndex + +derive instance Newtype ArbitraryUtxoIndex _ + +instance Arbitrary ArbitraryUtxoIndex where + arbitrary = + (arbitrary :: Gen ArbitraryUtxoMap) + <#> wrap <<< UtxoIndex.buildUtxoIndex <<< unwrap + newtype ArbitraryUtxoMap = ArbitraryUtxoMap UtxoMap derive instance Generic ArbitraryUtxoMap _ @@ -79,13 +109,21 @@ instance Show ArbitraryUtxoMap where show = genericShow instance Arbitrary ArbitraryUtxoMap where - arbitrary = wrap <$> Map.genMap (unwrap <$> oref) (unwrap <$> txOutput) - where - oref :: Gen ArbitraryTransactionInput - oref = arbitrary + arbitrary = wrap <$> Map.genMap genTransactionInput genTransactionOutput + +newtype ArbitraryTxUnspentOut = + ArbitraryTxUnspentOut (TransactionInput /\ TransactionOutput) + +derive instance Newtype ArbitraryTxUnspentOut _ + +instance Arbitrary ArbitraryTxUnspentOut where + arbitrary = wrap <$> lift2 Tuple genTransactionInput genTransactionOutput + +genTransactionInput :: Gen TransactionInput +genTransactionInput = unwrap <$> (arbitrary :: Gen ArbitraryTransactionInput) - txOutput :: Gen ArbitraryTransactionOutput - txOutput = arbitrary +genTransactionOutput :: Gen TransactionOutput +genTransactionOutput = unwrap <$> (arbitrary :: Gen ArbitraryTransactionOutput) newtype ArbitraryTransactionInput = ArbitraryTransactionInput TransactionInput @@ -128,124 +166,3 @@ instance Arbitrary ArbitraryAddress where wrap <<< baseAddressToAddress <$> lift2 (paymentKeyHashStakeKeyHashAddress MainnetId) arbitrary arbitrary --------------------------------------------------------------------------------- --- Invariants --------------------------------------------------------------------------------- - --- | Taken from cardano-wallet: --- | https://github.com/input-output-hk/cardano-wallet/blob/791541da69b9b3f434bb9ead43de406cc18b0373/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L614 -data UtxoIndexInvariantStatus - = InvariantHolds - -- ^ Indicates a successful check of the invariants. - | InvariantUtxoIndexIncomplete - -- ^ Indicates that the `UtxoIndex` is missing one or more entries. - | InvariantUtxoIndexNonMinimal - --- ^ Indicates that the `UtxoIndex` has one or more unnecessary entries. - -derive instance Generic UtxoIndexInvariantStatus _ - -instance Show UtxoIndexInvariantStatus where - show = genericShow - --- | Taken from cardano-wallet: --- | https://github.com/input-output-hk/cardano-wallet/blob/9d73b57e23392e25148cfc8db560cb8f656cb56a/lib/primitive/test/spec/Cardano/Wallet/Primitive/Types/UTxOIndexSpec.hs#L183 -invariantHolds :: UtxoIndex -> QuickCheck.Result -invariantHolds utxoIndex = - case checkUtxoIndexInvariants utxoIndex of - InvariantHolds -> QuickCheck.Success - status -> QuickCheck.Failed (show status) - --- | Taken from cardano-wallet: --- | https://github.com/input-output-hk/cardano-wallet/blob/791541da69b9b3f434bb9ead43de406cc18b0373/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L632 -checkUtxoIndexInvariants :: UtxoIndex -> UtxoIndexInvariantStatus -checkUtxoIndexInvariants utxoIndex - | not (checkUtxoIndexComplete utxoIndex) = - InvariantUtxoIndexIncomplete - | not (checkUtxoIndexMinimal utxoIndex) = - InvariantUtxoIndexNonMinimal - | otherwise = - InvariantHolds - --- | Check that every entry from the map of all utxos is properly indexed. --- | --- | Taken from cardano-wallet: --- | https://github.com/input-output-hk/cardano-wallet/blob/791541da69b9b3f434bb9ead43de406cc18b0373/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L682 -checkUtxoIndexComplete :: UtxoIndex -> Boolean -checkUtxoIndexComplete utxoIndex = - Array.all hasEntries (Map.toUnfoldable $ utxoIndex ^. UtxoIndex._utxos) - where - hasEntries :: TransactionInput /\ TransactionOutput -> Boolean - hasEntries (oref /\ out) = - case UtxoIndex.categorizeUtxoEntry out of - BundleWithNoAssets -> - UtxoIndex._indexSingletons `hasEntryForAsset` AssetLovelace - BundleWithOneAsset asset -> - UtxoIndex._indexPairs `hasEntryForAsset` AssetLovelace - && UtxoIndex._indexSingletons `hasEntryForAsset` Asset asset - BundleWithTwoAssets asset0 asset1 -> - UtxoIndex._indexAnyWith `hasEntryForAsset` AssetLovelace - && UtxoIndex._indexPairs `hasEntryForAsset` Asset asset0 - && UtxoIndex._indexPairs `hasEntryForAsset` Asset asset1 - BundleWithMultipleAssets assets -> - UtxoIndex._indexAnyWith `hasEntryForAsset` AssetLovelace && - flip Foldable.all assets \asset -> - (UtxoIndex._indexAnyWith `hasEntryForAsset` Asset asset) - where - hasEntryForAsset - :: Lens' UtxoIndex (HashMap Asset UtxoMap) -> Asset -> Boolean - hasEntryForAsset getter asset = - maybe false (eq out) $ - (Map.lookup oref =<< HashMap.lookup asset (utxoIndex ^. getter)) - --- | Check that every indexed entry is required by some entry in the map of all --- | utxos. --- | --- | Taken from cardano-wallet: --- | https://github.com/input-output-hk/cardano-wallet/blob/791541da69b9b3f434bb9ead43de406cc18b0373/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L715 -checkUtxoIndexMinimal :: UtxoIndex -> Boolean -checkUtxoIndexMinimal utxoIndex = - UtxoIndex._indexSingletons `testEntriesWith` txOutputHasOneAsset - && UtxoIndex._indexPairs `testEntriesWith` txOutputHasTwoAssetsWith - && UtxoIndex._indexAnyWith `testEntriesWith` txOutputHasAsset - where - testEntriesWith - :: Lens' UtxoIndex (HashMap Asset UtxoMap) - -> (TransactionOutput -> Asset -> Boolean) - -> Boolean - testEntriesWith subset test' = - utxoIndex ^. subset - # HashMap.toArrayBy Tuple - # Array.all \(asset /\ utxos) -> - Array.all (entryMatches (flip test' asset)) (Map.toUnfoldable utxos) - where - entryMatches - :: (TransactionOutput -> Boolean) - -> TransactionInput /\ TransactionOutput - -> Boolean - entryMatches test'' (oref /\ txOutput) = - maybe false test'' $ - Map.lookup oref (utxoIndex ^. UtxoIndex._utxos) - - txOutputHasOneAsset :: TransactionOutput -> Asset -> Boolean - txOutputHasOneAsset txOutput AssetLovelace = - txOutputAssetCount txOutput == zero - txOutputHasOneAsset txOutput asset = - txOutputHasAsset txOutput asset && txOutputAssetCount txOutput == one - - txOutputHasTwoAssetsWith :: TransactionOutput -> Asset -> Boolean - txOutputHasTwoAssetsWith txOutput AssetLovelace = - txOutputAssetCount txOutput == one - txOutputHasTwoAssetsWith txOutput asset = - txOutputHasAsset txOutput asset - && txOutputAssetCount txOutput == BigInt.fromInt 2 - - txOutputHasAsset :: TransactionOutput -> Asset -> Boolean - txOutputHasAsset _ AssetLovelace = true - txOutputHasAsset (TransactionOutput { amount }) (Asset asset) = - Value.getAssetQuantity asset amount >= one - - txOutputAssetCount :: TransactionOutput -> BigInt - txOutputAssetCount = - Foldable.length <<< Value.valueAssets <<< _.amount <<< unwrap - From f1315d826cfb10780901b871a763a628a693dd33 Mon Sep 17 00:00:00 2001 From: uhbif19 Date: Fri, 9 Dec 2022 00:33:07 +0300 Subject: [PATCH 073/373] Fix indentation syntax error --- src/Internal/Types/ScriptLookups.purs | 20 ++++++++++---------- 1 file changed, 10 insertions(+), 10 deletions(-) diff --git a/src/Internal/Types/ScriptLookups.purs b/src/Internal/Types/ScriptLookups.purs index a06cbc8431..1c1da043e1 100644 --- a/src/Internal/Types/ScriptLookups.purs +++ b/src/Internal/Types/ScriptLookups.purs @@ -1254,16 +1254,16 @@ processConstraint mpsMap osMap = do networkId <- getNetworkId let amount = fromPlutusValue plutusValue runExceptT do - let datum' = outputDatum dat datp - txOut = TransactionOutput - { address: - case mbCredential of - Nothing -> validatorHashEnterpriseAddress networkId vlh - Just cred -> baseAddressToAddress $ baseAddress - { network: networkId - , paymentCred: scriptHashCredential (unwrap vlh) - , delegationCred: credentialToStakeCredential cred - } + let + datum' = outputDatum dat datp + txOut = TransactionOutput + { address: case mbCredential of + Nothing -> validatorHashEnterpriseAddress networkId vlh + Just cred -> baseAddressToAddress $ baseAddress + { network: networkId + , paymentCred: scriptHashCredential (unwrap vlh) + , delegationCred: credentialToStakeCredential cred + } , amount -- TODO: save correct and scriptRef, should be done in -- Constraints API upgrade that follows Vasil From c48fc41276543b5d4cc9b885b65bd359eaedd3f2 Mon Sep 17 00:00:00 2001 From: uhbif19 Date: Fri, 9 Dec 2022 00:34:03 +0300 Subject: [PATCH 074/373] Make convertBigInt return without Maybe --- src/Internal/Serialization/PlutusData.purs | 26 ++++++++++++---------- 1 file changed, 14 insertions(+), 12 deletions(-) diff --git a/src/Internal/Serialization/PlutusData.purs b/src/Internal/Serialization/PlutusData.purs index 36e1246c9e..b607fc2069 100644 --- a/src/Internal/Serialization/PlutusData.purs +++ b/src/Internal/Serialization/PlutusData.purs @@ -22,20 +22,18 @@ import Ctl.Internal.Types.BigNum (BigNum) import Ctl.Internal.Types.ByteArray (ByteArray) import Ctl.Internal.Types.PlutusData as T import Data.BigInt as BigInt -import Data.Maybe (Maybe(Just), fromJust) +import Data.Maybe (Maybe, fromJust) import Data.Tuple (Tuple, fst, snd) import Data.Tuple.Nested (type (/\), (/\)) import Partial.Unsafe (unsafePartial) convertPlutusData :: T.PlutusData -> PlutusData --- Unsafe fromJust here is correct, because we cover every PlutusData --- constructor, and Just will be returned by one of functions -convertPlutusData x = unsafePartial $ fromJust $ case x of - T.Constr alt list -> Just $ convertConstr alt list - T.Map mp -> Just $ convertPlutusMap mp - T.List lst -> Just $ convertPlutusList lst +convertPlutusData x = case x of + T.Constr alt list -> convertConstr alt list + T.Map mp -> convertPlutusMap mp + T.List lst -> convertPlutusList lst T.Integer n -> convertPlutusInteger n - T.Bytes b -> Just $ _mkPlutusData_bytes b + T.Bytes b -> _mkPlutusData_bytes b convertConstr :: BigNum -> Array T.PlutusData -> PlutusData convertConstr alt list = @@ -56,12 +54,16 @@ convertPlutusMap mp = in _mkPlutusData_map $ _packMap fst snd entries -convertPlutusInteger :: BigInt.BigInt -> Maybe PlutusData +convertPlutusInteger :: BigInt.BigInt -> PlutusData convertPlutusInteger n = - _mkPlutusData_integer <$> convertBigInt n + _mkPlutusData_integer $ convertBigInt n -convertBigInt :: BigInt.BigInt -> Maybe BigInt -convertBigInt n = _bigIntFromString maybeFfiHelper (BigInt.toString n) +convertBigInt :: BigInt.BigInt -> BigInt +-- Unsafe is safe here, cuz both BigInt's are dynamic sized, +-- so range errors are not a concern, and `BigInt.toString` always +-- returns parsable string +convertBigInt n = unsafePartial $ fromJust $ + _bigIntFromString maybeFfiHelper (BigInt.toString n) packPlutusList :: Array T.PlutusData -> PlutusList packPlutusList = (_packPlutusList containerHelper) From 6c88db151f25becd2c1f19f418cbb19ce329f175 Mon Sep 17 00:00:00 2001 From: uhbif19 Date: Fri, 9 Dec 2022 00:34:32 +0300 Subject: [PATCH 075/373] Fix formatting --- test/Deserialization.purs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/test/Deserialization.purs b/test/Deserialization.purs index 54be12ef35..268e753d57 100644 --- a/test/Deserialization.purs +++ b/test/Deserialization.purs @@ -107,8 +107,9 @@ suite = do group "CSL <-> CTL PlutusData roundtrip tests" do let pdRoundTripTest ctlPd = do - let cslPd = SPD.convertPlutusData ctlPd - pdBytes = toBytes (asOneOf cslPd) + let + cslPd = SPD.convertPlutusData ctlPd + pdBytes = toBytes (asOneOf cslPd) cslPd' <- errMaybe "Failed to fromBytes PlutusData" $ fromBytes pdBytes let ctlPd' = DPD.convertPlutusData cslPd' From 5857e5eb826b27ba484c6ef36ee5ff3b8484a072 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Fri, 9 Dec 2022 12:16:48 +0000 Subject: [PATCH 076/373] add helper for constructing ctl/bf backends. Fix exports --- doc/getting-started.md | 7 ++++--- src/Contract/Chain.purs | 8 ++++++-- src/Contract/Config.purs | 6 +++--- src/Contract/Wallet.purs | 4 ++-- src/Internal/Contract/QueryBackend.purs | 14 ++++++++++++++ src/Internal/Plutip/Server.purs | 5 ++--- src/Internal/Test/E2E/Route.purs | 7 ++----- 7 files changed, 33 insertions(+), 18 deletions(-) diff --git a/doc/getting-started.md b/doc/getting-started.md index eabfc3e100..819acc9c58 100644 --- a/doc/getting-started.md +++ b/doc/getting-started.md @@ -106,7 +106,7 @@ main = Contract.Monad.launchAff_ do The `ContractEnv` type contains configuration values and websocket connections that are required to execute contracts written in CTL. The users should not construct it directly - `Contract.Config.ContractParams` should be used instead. -For local development and testing, we provide `Contract.Config.testnetConfig` where all service hosts are set to `localhost` and the `logLevel` is set to `Trace`. +For local development and testing, we provide `Contract.Config.testnetConfig` where all `CtlBackend` service hosts are set to `localhost` and the `logLevel` is set to `Trace`. It is **not recommended to directly construct or manipulate a `ContractEnv` yourself** as the process of making a new config initializes websockets. Instead, use `Contract.Monad.ContractParams` with `runContract`. @@ -118,8 +118,9 @@ An example of building a `Contract` via `ContractParams` is as follows: main :: Effect Unit main = Contract.Monad.launchAff_ do -- we re-export this for you let - (config :: ContractParams) = - { backendParams: mkSingletonBackendParams $ CtlBackendParams + config :: ContractParams + config = + { backendParams: mkCtlBackendParams { ogmiosConfig: defaultOgmiosWsConfig , odcConfig: defaultDatumCacheWsConfig , kupoConfig: defaultKupoServerConfig diff --git a/src/Contract/Chain.purs b/src/Contract/Chain.purs index 8de4dd2c17..123117c430 100644 --- a/src/Contract/Chain.purs +++ b/src/Contract/Chain.purs @@ -1,10 +1,11 @@ -- | A module for Chain-related querying. module Contract.Chain - ( module Chain - , module Contract + ( getTip + , module Chain , module Contract.WaitUntilSlot ) where +import Contract.Monad (Contract) import Ctl.Internal.Contract (getChainTip) as Contract import Ctl.Internal.Contract.WaitUntilSlot ( currentSlot @@ -17,3 +18,6 @@ import Ctl.Internal.Types.Chain , ChainTip(ChainTip) , Tip(Tip, TipAtGenesis) ) as Chain + +getTip :: Contract Chain.Tip +getTip = Contract.getChainTip diff --git a/src/Contract/Config.purs b/src/Contract/Config.purs index 9643ec2b30..d86176ad5b 100644 --- a/src/Contract/Config.purs +++ b/src/Contract/Config.purs @@ -24,14 +24,14 @@ module Contract.Config , module X ) where -import Prelude - import Contract.Address (NetworkId(MainnetId, TestnetId)) import Ctl.Internal.Contract.Hooks (Hooks, emptyHooks) as X import Ctl.Internal.Contract.Hooks (emptyHooks) import Ctl.Internal.Contract.Monad (ContractParams) import Ctl.Internal.Contract.QueryBackend ( QueryBackendParams(CtlBackendParams, BlockfrostBackendParams) + , mkBlockfrostBackendParams + , mkCtlBackendParams , mkSingletonBackendParams ) import Ctl.Internal.Deserialization.Keys (privateKeyFromBytes) @@ -65,7 +65,7 @@ import Data.Maybe (Maybe(Just, Nothing)) testnetConfig :: ContractParams testnetConfig = - { backendParams: mkSingletonBackendParams $ CtlBackendParams + { backendParams: mkCtlBackendParams { ogmiosConfig: defaultOgmiosWsConfig , odcConfig: defaultDatumCacheWsConfig , kupoConfig: defaultKupoServerConfig diff --git a/src/Contract/Wallet.purs b/src/Contract/Wallet.purs index f89c10cd39..9bddca9bc9 100644 --- a/src/Contract/Wallet.purs +++ b/src/Contract/Wallet.purs @@ -5,7 +5,7 @@ module Contract.Wallet , getNetworkId , module Contract.Address , module Contract.Utxos - , module Contract.Wallet + , module X , module Deserialization.Keys , module Wallet , module Ctl.Internal.Wallet.Key @@ -26,7 +26,7 @@ import Ctl.Internal.Contract.Wallet , getUnusedAddresses , getWallet , signData - ) as Contract.Wallet + ) as X import Ctl.Internal.Deserialization.Keys (privateKeyFromBytes) as Deserialization.Keys import Ctl.Internal.Serialization.Address (NetworkId) import Ctl.Internal.Wallet diff --git a/src/Internal/Contract/QueryBackend.purs b/src/Internal/Contract/QueryBackend.purs index 226e991f8b..317d9b6a40 100644 --- a/src/Internal/Contract/QueryBackend.purs +++ b/src/Internal/Contract/QueryBackend.purs @@ -11,6 +11,8 @@ module Ctl.Internal.Contract.QueryBackend , lookupBackend , mkBackendParams , mkSingletonBackendParams + , mkCtlBackendParams + , mkBlockfrostBackendParams ) where import Prelude @@ -52,6 +54,18 @@ mkSingletonBackendParams :: QueryBackendParams -> QueryBackends QueryBackendParams mkSingletonBackendParams = flip QueryBackends Map.empty +mkCtlBackendParams + :: { ogmiosConfig :: ServerConfig + , kupoConfig :: ServerConfig + , odcConfig :: ServerConfig + } + -> QueryBackends QueryBackendParams +mkCtlBackendParams = mkSingletonBackendParams <<< CtlBackendParams + +mkBlockfrostBackendParams :: ServerConfig -> QueryBackends QueryBackendParams +mkBlockfrostBackendParams = mkSingletonBackendParams <<< BlockfrostBackendParams + <<< { blockfrostConfig: _ } + mkBackendParams :: QueryBackendParams -> Array QueryBackendParams diff --git a/src/Internal/Plutip/Server.purs b/src/Internal/Plutip/Server.purs index d3db78769e..b7397f2c5f 100644 --- a/src/Internal/Plutip/Server.purs +++ b/src/Internal/Plutip/Server.purs @@ -20,7 +20,6 @@ import Affjax.RequestBody as RequestBody import Affjax.RequestHeader as Header import Affjax.ResponseFormat as Affjax.ResponseFormat import Contract.Address (NetworkId(MainnetId)) -import Contract.Config (QueryBackendParams(CtlBackendParams)) import Contract.Monad ( Contract , ContractEnv @@ -39,7 +38,7 @@ import Ctl.Internal.Contract.Monad ) import Ctl.Internal.Contract.QueryBackend ( defaultBackend - , mkSingletonBackendParams + , mkCtlBackendParams ) import Ctl.Internal.Helpers ((<>)) import Ctl.Internal.Logging (Logger, mkLogger, setupLogs) @@ -759,7 +758,7 @@ mkClusterContractEnv -> Aff ContractEnv mkClusterContractEnv plutipCfg logger customLogger = do usedTxOuts <- newUsedTxOuts - backend <- buildBackend logger $ mkSingletonBackendParams $ CtlBackendParams + backend <- buildBackend logger $ mkCtlBackendParams { ogmiosConfig: plutipCfg.ogmiosConfig , odcConfig: plutipCfg.ogmiosDatumCacheConfig , kupoConfig: plutipCfg.kupoConfig diff --git a/src/Internal/Test/E2E/Route.purs b/src/Internal/Test/E2E/Route.purs index 723307e8a9..0d3b0f04e9 100644 --- a/src/Internal/Test/E2E/Route.purs +++ b/src/Internal/Test/E2E/Route.purs @@ -20,10 +20,7 @@ import Contract.Wallet import Contract.Wallet.Key (privateKeysToKeyWallet) import Control.Alt ((<|>)) import Control.Monad.Error.Class (liftMaybe) -import Ctl.Internal.Contract.QueryBackend - ( QueryBackendParams(CtlBackendParams) - , mkSingletonBackendParams - ) +import Ctl.Internal.Contract.QueryBackend (mkCtlBackendParams) import Ctl.Internal.Helpers (liftEither) import Ctl.Internal.QueryM (ClusterSetup) import Ctl.Internal.Serialization.Address (NetworkId(MainnetId)) @@ -216,7 +213,7 @@ route configs tests = do } config = config - { backendParams = mkSingletonBackendParams $ CtlBackendParams + { backendParams = mkCtlBackendParams { ogmiosConfig: ogmiosConfig , odcConfig: datumCacheConfig , kupoConfig: kupoConfig From 0a472d3d7f3bebce74ce2f25b04df1a10968d02c Mon Sep 17 00:00:00 2001 From: Amir Rad Date: Fri, 9 Dec 2022 13:46:50 +0000 Subject: [PATCH 077/373] Leftover comments after type sig change --- doc/plutus-comparison.md | 2 +- src/Contract/Scripts.purs | 2 +- src/Internal/QueryM.purs | 11 +++++------ 3 files changed, 7 insertions(+), 8 deletions(-) diff --git a/doc/plutus-comparison.md b/doc/plutus-comparison.md index 4608b6c75e..9dfd00e224 100644 --- a/doc/plutus-comparison.md +++ b/doc/plutus-comparison.md @@ -127,7 +127,7 @@ As noted above, all scripts and various script newtypes (`Validator`, `MintingPo #### Applying arguments to parameterized scripts -CTL is currently unable to build full UPLC ASTs on the frontend (although support for this may be added in the future). This means that Plutus' `applyCode`, which is the default method for applying arguments to parameterized scripts, has no direct equivalent in CTL. We do, however, support a workaround for applying arguments to parameterized scripts. `Contract.Scripts.applyArgs` allows you to apply a list of `PlutusData` arguments to any type isomorphic to a `PlutusScript`. Using this allows you to dynamically apply arguments during contract execution, but also implies the following: +CTL is currently unable to build full UPLC ASTs on the frontend (although support for this may be added in the future). This means that Plutus' `applyCode`, which is the default method for applying arguments to parameterized scripts, has no direct equivalent in CTL. We do, however, support a workaround for applying arguments to parameterized scripts. `Contract.Scripts.applyArgs` allows you to apply a list of `PlutusData` arguments to a `PlutusScript`. Using this allows you to dynamically apply arguments during contract execution, but also implies the following: - `applyArgs` must be effectful, as we use our Haskell server to do the actual script application - All of your domain types must have `Contract.PlutusData.ToData` instances (or some other way of converting them to `PlutusData`) diff --git a/src/Contract/Scripts.purs b/src/Contract/Scripts.purs index 50d4d976da..bec2a5eb7a 100644 --- a/src/Contract/Scripts.purs +++ b/src/Contract/Scripts.purs @@ -69,7 +69,7 @@ import Ctl.Internal.Types.TypedValidator import Data.Either (Either, hush) import Data.Maybe (Maybe) --- | Apply `PlutusData` arguments to any type isomorphic to `PlutusScript`, +-- | Apply `PlutusData` arguments to a`PlutusScript`, -- | returning an updated script with the provided arguments applied applyArgs :: forall (r :: Row Type) diff --git a/src/Internal/QueryM.purs b/src/Internal/QueryM.purs index 8da676b621..226a73df00 100644 --- a/src/Internal/QueryM.purs +++ b/src/Internal/QueryM.purs @@ -1,4 +1,7 @@ --- | CTL query layer monad +-- | CTL query layer monad. +-- | This module defines an Aff interface for Ogmios Websocket Queries. +-- | Since WebSockets do not define a mechanism for linking request/response. +-- | Or for verifying that the connection is live, those concerns are addressed here module Ctl.Internal.QueryM ( module ExportDispatcher , module ExportServerConfig @@ -280,10 +283,6 @@ import Effect.Ref as Ref import Foreign.Object as Object import Untagged.Union (asOneOf) --- This module defines an Aff interface for Ogmios Websocket Queries --- Since WebSockets do not define a mechanism for linking request/response --- Or for verifying that the connection is live, those concerns are addressed --- here -- | Cluster setup contains everything that is needed to run a `Contract` on -- | a local cluster: paramters to connect to the services and private keys @@ -800,7 +799,7 @@ instance Show ClientError where <> err <> ")" --- | Apply `PlutusData` arguments to any type isomorphic to `PlutusScript`, +-- | Apply `PlutusData` arguments to a `PlutusScript`, -- | returning an updated script with the provided arguments applied applyArgs :: PlutusScript From 5c231bde3421c2ad1239beff728692efefa42bf4 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Fri, 9 Dec 2022 16:54:48 +0100 Subject: [PATCH 078/373] BalanceTx: Always generate change if tx has no outputs --- src/Internal/BalanceTx/BalanceTx.purs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/src/Internal/BalanceTx/BalanceTx.purs b/src/Internal/BalanceTx/BalanceTx.purs index 9fce0e0d01..1877d46e7d 100644 --- a/src/Internal/BalanceTx/BalanceTx.purs +++ b/src/Internal/BalanceTx/BalanceTx.purs @@ -411,7 +411,10 @@ setTxChangeOutputs outputs = _body' <<< _outputs %~ flip append outputs makeChange :: Address -> Value -> Coin -> TxBody -> BalanceTxM (Array TransactionOutput) makeChange changeAddress inputValue certsFee txBody = - if excessValue == mempty then pure mempty + -- Always generate change when a transaction has no outputs to avoid issues + -- with transaction confirmation: + -- FIXME: https://github.com/Plutonomicon/cardano-transaction-lib/issues/1293 + if excessValue == mempty && (txBody ^. _outputs) /= mempty then pure mempty else map (mkChangeOutput changeAddress) <$> ( assignCoinsToChangeValues changeAddress excessCoin From d344442be443ceb9c2151695ae97b02c8e6f62a3 Mon Sep 17 00:00:00 2001 From: uhbif19 Date: Sat, 10 Dec 2022 02:09:47 +0300 Subject: [PATCH 079/373] Add to CHANGELOG --- CHANGELOG.md | 1 + 1 file changed, 1 insertion(+) diff --git a/CHANGELOG.md b/CHANGELOG.md index 85543733d3..ec5e259cc4 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -40,6 +40,7 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) - Running plutip servers attaches on SIGINT handlers and therefore node will not exit by default. ([#1231](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1231)). - `TestPlanM`, `interpret` and `interpretWithConfig` are now public in `Contract.Test.Mote` and our custom `consoleReporter` in `Contract.Test.Mote.ConsoleReporter`. ([#1261](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1261)). +- Internal datum conversions are now total, resulting in some datum-related Contract functions dropping the use of `Maybe`, for example `datumHash`, `convertPlutusData` (and related functions) ([#1284](https://github.com/Plutonomicon/cardano-transaction-lib/issues/1284)). ### Removed From 4c834e6c48cb42c616778b81970095150d1b110a Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Sun, 11 Dec 2022 13:54:47 +0100 Subject: [PATCH 080/373] Fix comment --- src/Internal/BalanceTx/CoinSelection.purs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Internal/BalanceTx/CoinSelection.purs b/src/Internal/BalanceTx/CoinSelection.purs index 50de43e42b..d377b1d28c 100644 --- a/src/Internal/BalanceTx/CoinSelection.purs +++ b/src/Internal/BalanceTx/CoinSelection.purs @@ -83,7 +83,7 @@ import Type.Proxy (Proxy(Proxy)) -- | strategy will help to ensure that a wallet's utxo distribution can evolve -- | over time to resemble the typical distribution of payments made by the -- | wallet owner. --- , utxoIndexUniverse| +-- | -- | Specifying `SelectionStrategyMinimal` will cause the selection algorithm to -- | only select just enough of each asset from the available utxo set to meet -- | the required amount. It is advised to use this strategy only when From 10bc14aa810edd4255131c090f2ec04a868296d0 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Sun, 11 Dec 2022 15:13:08 +0100 Subject: [PATCH 081/373] Refactor QueryBackend and QueryBackendParams --- src/Contract/Config.purs | 1 - src/Internal/Contract/Monad.purs | 106 ++++++++--------- src/Internal/Contract/QueryBackend.purs | 150 ++++++------------------ src/Internal/Contract/QueryHandle.purs | 10 +- src/Internal/Plutip/Server.purs | 7 +- src/Internal/Test/E2E/Runner.purs | 9 +- 6 files changed, 92 insertions(+), 191 deletions(-) diff --git a/src/Contract/Config.purs b/src/Contract/Config.purs index d86176ad5b..b9647b3784 100644 --- a/src/Contract/Config.purs +++ b/src/Contract/Config.purs @@ -32,7 +32,6 @@ import Ctl.Internal.Contract.QueryBackend ( QueryBackendParams(CtlBackendParams, BlockfrostBackendParams) , mkBlockfrostBackendParams , mkCtlBackendParams - , mkSingletonBackendParams ) import Ctl.Internal.Deserialization.Keys (privateKeyFromBytes) import Ctl.Internal.QueryM.ServerConfig diff --git a/src/Internal/Contract/Monad.purs b/src/Internal/Contract/Monad.purs index 79f91f4c08..34bb04559c 100644 --- a/src/Internal/Contract/Monad.purs +++ b/src/Internal/Contract/Monad.purs @@ -28,24 +28,18 @@ import Control.Monad.Logger.Class (class MonadLogger) import Control.Monad.Reader.Class (class MonadAsk, class MonadReader, ask, asks) import Control.Monad.Reader.Trans (ReaderT, runReaderT, withReaderT) import Control.Monad.Rec.Class (class MonadRec) -import Control.Parallel - ( class Parallel - , parTraverse - , parTraverse_ - , parallel - , sequential - ) +import Control.Parallel (class Parallel, parallel, sequential) import Control.Plus (class Plus) import Ctl.Internal.Cardano.Types.Transaction (UtxoMap) import Ctl.Internal.Contract.Hooks (Hooks) import Ctl.Internal.Contract.QueryBackend - ( CtlBackend + ( BlockfrostBackend + , CtlBackend + , CtlBackendParams , QueryBackend(BlockfrostBackend, CtlBackend) - , QueryBackendLabel(CtlBackendLabel) , QueryBackendParams(BlockfrostBackendParams, CtlBackendParams) - , QueryBackends - , defaultBackend - , lookupBackend + , getBlockfrostBackend + , getCtlBackend ) import Ctl.Internal.Helpers (filterMapWithKeyM, liftM, logWithLevel) import Ctl.Internal.JsWebSocket (_wsClose, _wsFinalize) @@ -60,11 +54,7 @@ import Ctl.Internal.QueryM , mkOgmiosWebSocketAff , underlyingWebSocket ) --- TODO Move/translate these types into Cardano -import Ctl.Internal.QueryM.Ogmios - ( ProtocolParameters - , SystemStart - ) as Ogmios +import Ctl.Internal.QueryM.Ogmios (ProtocolParameters, SystemStart) as Ogmios import Ctl.Internal.QueryM.ServerConfig (ServerConfig) import Ctl.Internal.Serialization.Address (NetworkId) import Ctl.Internal.Types.UsedTxOuts (UsedTxOuts, isTxOutRefUsed, newUsedTxOuts) @@ -76,7 +66,7 @@ import Data.Log.Level (LogLevel) import Data.Log.Message (Message) import Data.Maybe (Maybe(Just, Nothing), fromMaybe) import Data.Newtype (class Newtype, unwrap) -import Data.Traversable (for_, traverse) +import Data.Traversable (for_, traverse, traverse_) import Effect (Effect) import Effect.Aff (Aff, ParAff, attempt, error, finally, supervise) import Effect.Aff.Class (liftAff) @@ -163,7 +153,7 @@ runContractInEnv contractEnv = -------------------------------------------------------------------------------- type ContractEnv = - { backend :: QueryBackends QueryBackend + { backend :: QueryBackend -- ctlServer is currently used for applyArgs, which is needed for all backends. This will be removed later , ctlServerConfig :: Maybe ServerConfig , networkId :: NetworkId @@ -197,7 +187,7 @@ mkContractEnv params = do b1 <- parallel do backend <- buildBackend logger params.backendParams -- Use the default backend to fetch ledger constants - ledgerConstants <- getLedgerConstants logger $ defaultBackend backend + ledgerConstants <- getLedgerConstants logger backend pure $ merge { backend, ledgerConstants } b2 <- parallel do wallet <- buildWallet @@ -223,12 +213,15 @@ mkContractEnv params = do , hooks: params.hooks } -buildBackend - :: Logger - -> QueryBackends QueryBackendParams - -> Aff (QueryBackends QueryBackend) -buildBackend logger = parTraverse case _ of - CtlBackendParams { ogmiosConfig, kupoConfig, odcConfig } -> do +buildBackend :: Logger -> QueryBackendParams -> Aff QueryBackend +buildBackend logger = case _ of + CtlBackendParams ctlParams blockfrostParams -> + flip CtlBackend blockfrostParams <$> buildCtlBackend ctlParams + BlockfrostBackendParams blockfrostParams ctlParams -> + BlockfrostBackend blockfrostParams <$> traverse buildCtlBackend ctlParams + where + buildCtlBackend :: CtlBackendParams -> Aff CtlBackend + buildCtlBackend { ogmiosConfig, kupoConfig, odcConfig } = do datumCacheWsRef <- liftEffect $ Ref.new Nothing sequential ado odcWs <- parallel $ mkDatumCacheWebSocketAff datumCacheWsRef logger @@ -236,18 +229,16 @@ buildBackend logger = parTraverse case _ of ogmiosWs <- parallel $ mkOgmiosWebSocketAff datumCacheWsRef logger ogmiosConfig in - CtlBackend - { ogmios: - { config: ogmiosConfig - , ws: ogmiosWs - } - , odc: - { config: odcConfig - , ws: odcWs - } - , kupoConfig - } - BlockfrostBackendParams bf -> pure $ BlockfrostBackend bf + { ogmios: + { config: ogmiosConfig + , ws: ogmiosWs + } + , odc: + { config: odcConfig + , ws: odcWs + } + , kupoConfig + } getLedgerConstants :: Logger @@ -257,11 +248,11 @@ getLedgerConstants , systemStart :: Ogmios.SystemStart } getLedgerConstants logger = case _ of - CtlBackend { ogmios: { ws } } -> do + CtlBackend { ogmios: { ws } } _ -> do pparams <- getProtocolParametersAff ws logger systemStart <- getSystemStartAff ws logger pure { pparams, systemStart } - BlockfrostBackend _ -> undefined + BlockfrostBackend _ _ -> undefined -- | Ensure that `NetworkId` from wallet is the same as specified in the -- | `ContractEnv`. @@ -279,18 +270,20 @@ walletNetworkCheck envNetworkId wallet = do -- | Finalizes a `Contract` environment. -- | Closes the connections in `ContractEnv`, effectively making it unusable. -stopContractEnv - :: ContractEnv - -> Aff Unit -stopContractEnv contractEnv = do - flip parTraverse_ contractEnv.backend case _ of - CtlBackend { ogmios, odc } -> do - let - stopWs :: forall (a :: Type). WebSocket a -> Effect Unit - stopWs = ((*>) <$> _wsFinalize <*> _wsClose) <<< underlyingWebSocket - liftEffect $ stopWs odc.ws - liftEffect $ stopWs ogmios.ws - BlockfrostBackend _ -> undefined +stopContractEnv :: ContractEnv -> Aff Unit +stopContractEnv { backend } = liftEffect do + traverse_ stopCtlRuntime (getCtlBackend backend) + traverse_ stopBlockfrostRuntime (getBlockfrostBackend backend) + where + stopCtlRuntime :: CtlBackend -> Effect Unit + stopCtlRuntime { ogmios, odc } = + stopWebSocket odc.ws *> stopWebSocket ogmios.ws + + stopBlockfrostRuntime :: BlockfrostBackend -> Effect Unit + stopBlockfrostRuntime = undefined + + stopWebSocket :: forall (a :: Type). WebSocket a -> Effect Unit + stopWebSocket = ((*>) <$> _wsFinalize <*> _wsClose) <<< underlyingWebSocket -- | Constructs and finalizes a contract environment that is usable inside a -- | bracket callback. @@ -334,7 +327,7 @@ withContractEnv params action = do -- | contains multiple contracts that can be run in parallel, reusing the same -- | environment (see `withContractEnv`) type ContractParams = - { backendParams :: QueryBackends QueryBackendParams + { backendParams :: QueryBackendParams , ctlServerConfig :: Maybe ServerConfig , networkId :: NetworkId , logLevel :: LogLevel @@ -352,10 +345,9 @@ type ContractParams = wrapQueryM :: forall (a :: Type). QueryM a -> Contract a wrapQueryM qm = do backend <- asks _.backend - ctlBackend <- liftM (error "Operation only supported on CTL backend") $ - lookupBackend CtlBackendLabel backend >>= case _ of - CtlBackend b -> Just b - _ -> Nothing + ctlBackend <- + getCtlBackend backend + # liftM (error "Operation only supported on CTL backend") contractEnv <- ask liftAff $ runQueryM contractEnv ctlBackend qm diff --git a/src/Internal/Contract/QueryBackend.purs b/src/Internal/Contract/QueryBackend.purs index 317d9b6a40..ff2b41d3f9 100644 --- a/src/Internal/Contract/QueryBackend.purs +++ b/src/Internal/Contract/QueryBackend.purs @@ -1,125 +1,30 @@ module Ctl.Internal.Contract.QueryBackend ( BlockfrostBackend + , BlockfrostBackendParams , CtlBackend + , CtlBackendParams , QueryBackend(BlockfrostBackend, CtlBackend) - , QueryBackendLabel(BlockfrostBackendLabel, CtlBackendLabel) , QueryBackendParams(BlockfrostBackendParams, CtlBackendParams) - , QueryBackends - , class HasQueryBackendLabel - , backendLabel - , defaultBackend - , lookupBackend - , mkBackendParams - , mkSingletonBackendParams - , mkCtlBackendParams + , getBlockfrostBackend + , getCtlBackend , mkBlockfrostBackendParams + , mkCtlBackendParams ) where import Prelude import Ctl.Internal.QueryM (DatumCacheWebSocket, OgmiosWebSocket) import Ctl.Internal.QueryM.ServerConfig (ServerConfig) -import Data.Array (nub) as Array -import Data.Array ((:)) -import Data.Foldable (class Foldable, foldMap, foldl, foldr, length) -import Data.Map (Map) -import Data.Map (empty, insert, lookup) as Map -import Data.Maybe (Maybe(Just)) -import Data.Traversable (class Traversable, sequence, traverse) -import Effect (Effect) -import Effect.Exception (throw) - --------------------------------------------------------------------------------- --- QueryBackends --------------------------------------------------------------------------------- - --- | A generic type to represent a choice of backend with a set of fallback --- | backends when an operation is not supported by the default. -data QueryBackends (backend :: Type) = - QueryBackends backend (Map QueryBackendLabel backend) - --- Functor breaks this datatype... -derive instance Functor QueryBackends - -instance Foldable QueryBackends where - foldr f z (QueryBackends x xs) = f x (foldr f z xs) - foldl f z (QueryBackends x xs) = foldl f (f z x) xs - foldMap f (QueryBackends x xs) = f x <> foldMap f xs - -instance Traversable QueryBackends where - traverse f (QueryBackends x xs) = QueryBackends <$> f x <*> traverse f xs - sequence (QueryBackends x xs) = QueryBackends <$> x <*> sequence xs - -mkSingletonBackendParams - :: QueryBackendParams -> QueryBackends QueryBackendParams -mkSingletonBackendParams = flip QueryBackends Map.empty - -mkCtlBackendParams - :: { ogmiosConfig :: ServerConfig - , kupoConfig :: ServerConfig - , odcConfig :: ServerConfig - } - -> QueryBackends QueryBackendParams -mkCtlBackendParams = mkSingletonBackendParams <<< CtlBackendParams - -mkBlockfrostBackendParams :: ServerConfig -> QueryBackends QueryBackendParams -mkBlockfrostBackendParams = mkSingletonBackendParams <<< BlockfrostBackendParams - <<< { blockfrostConfig: _ } - -mkBackendParams - :: QueryBackendParams - -> Array QueryBackendParams - -> Effect (QueryBackends QueryBackendParams) -mkBackendParams defaultBackend' backends = - case length backends + 1 /= numUniqueBackends of - true -> - throw "mkBackendParams: multiple configs for the same service" - false -> - pure $ QueryBackends defaultBackend' $ - foldl (\mp b -> Map.insert (backendLabel b) b mp) Map.empty backends - where - numUniqueBackends :: Int - numUniqueBackends = - length $ Array.nub $ map backendLabel (defaultBackend' : backends) - -defaultBackend :: forall (backend :: Type). QueryBackends backend -> backend -defaultBackend (QueryBackends backend _) = backend - --- Still requires a match on the backend constructor... -lookupBackend - :: forall (backend :: Type) - . HasQueryBackendLabel backend - => QueryBackendLabel - -> QueryBackends backend - -> Maybe backend -lookupBackend key (QueryBackends defaultBackend' backends) - | key == backendLabel defaultBackend' = Just defaultBackend' - | otherwise = Map.lookup key backends - --------------------------------------------------------------------------------- --- QueryBackendLabel --------------------------------------------------------------------------------- - -data QueryBackendLabel = CtlBackendLabel | BlockfrostBackendLabel - -derive instance Eq QueryBackendLabel -derive instance Ord QueryBackendLabel - -class HasQueryBackendLabel (t :: Type) where - backendLabel :: t -> QueryBackendLabel - -instance HasQueryBackendLabel QueryBackend where - backendLabel (CtlBackend _) = CtlBackendLabel - backendLabel (BlockfrostBackend _) = BlockfrostBackendLabel - -instance HasQueryBackendLabel QueryBackendParams where - backendLabel (CtlBackendParams _) = CtlBackendLabel - backendLabel (BlockfrostBackendParams _) = BlockfrostBackendLabel +import Data.Maybe (Maybe(Just, Nothing)) -------------------------------------------------------------------------------- -- QueryBackend -------------------------------------------------------------------------------- +data QueryBackend + = CtlBackend CtlBackend (Maybe BlockfrostBackend) + | BlockfrostBackend BlockfrostBackend (Maybe CtlBackend) + type CtlBackend = { ogmios :: { config :: ServerConfig @@ -136,21 +41,34 @@ type BlockfrostBackend = { blockfrostConfig :: ServerConfig } -data QueryBackend - = CtlBackend CtlBackend - | BlockfrostBackend BlockfrostBackend +getCtlBackend :: QueryBackend -> Maybe CtlBackend +getCtlBackend (CtlBackend backend _) = Just backend +getCtlBackend (BlockfrostBackend _ backend) = backend + +getBlockfrostBackend :: QueryBackend -> Maybe BlockfrostBackend +getBlockfrostBackend (CtlBackend _ backend) = backend +getBlockfrostBackend (BlockfrostBackend backend _) = Just backend -------------------------------------------------------------------------------- -- QueryBackendParams -------------------------------------------------------------------------------- data QueryBackendParams - = CtlBackendParams - { ogmiosConfig :: ServerConfig - , kupoConfig :: ServerConfig - , odcConfig :: ServerConfig - } - | BlockfrostBackendParams - { blockfrostConfig :: ServerConfig - } + = CtlBackendParams CtlBackendParams (Maybe BlockfrostBackendParams) + | BlockfrostBackendParams BlockfrostBackendParams (Maybe CtlBackendParams) + +type CtlBackendParams = + { ogmiosConfig :: ServerConfig + , kupoConfig :: ServerConfig + , odcConfig :: ServerConfig + } + +type BlockfrostBackendParams = + { blockfrostConfig :: ServerConfig + } + +mkCtlBackendParams :: CtlBackendParams -> QueryBackendParams +mkCtlBackendParams = flip CtlBackendParams Nothing +mkBlockfrostBackendParams :: BlockfrostBackendParams -> QueryBackendParams +mkBlockfrostBackendParams = flip BlockfrostBackendParams Nothing diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs index 0002e4ecce..2b30c7df22 100644 --- a/src/Internal/Contract/QueryHandle.purs +++ b/src/Internal/Contract/QueryHandle.purs @@ -23,7 +23,6 @@ import Ctl.Internal.Contract.QueryBackend ( BlockfrostBackend , CtlBackend , QueryBackend(BlockfrostBackend, CtlBackend) - , defaultBackend ) import Ctl.Internal.Hashing (transactionHash) as Hashing import Ctl.Internal.QueryM (ClientError, QueryM) @@ -83,12 +82,11 @@ type QueryHandle = } getQueryHandle :: Contract QueryHandle -getQueryHandle = do - contractEnv <- ask - pure case defaultBackend contractEnv.backend of - CtlBackend backend -> +getQueryHandle = ask <#> \contractEnv -> + case contractEnv.backend of + CtlBackend backend _ -> queryHandleForCtlBackend contractEnv backend - BlockfrostBackend backend -> + BlockfrostBackend backend _ -> queryHandleForBlockfrostBackend contractEnv backend queryHandleForCtlBackend :: ContractEnv -> CtlBackend -> QueryHandle diff --git a/src/Internal/Plutip/Server.purs b/src/Internal/Plutip/Server.purs index b7397f2c5f..e243fdbd07 100644 --- a/src/Internal/Plutip/Server.purs +++ b/src/Internal/Plutip/Server.purs @@ -36,10 +36,7 @@ import Ctl.Internal.Contract.Monad , getLedgerConstants , stopContractEnv ) -import Ctl.Internal.Contract.QueryBackend - ( defaultBackend - , mkCtlBackendParams - ) +import Ctl.Internal.Contract.QueryBackend (mkCtlBackendParams) import Ctl.Internal.Helpers ((<>)) import Ctl.Internal.Logging (Logger, mkLogger, setupLogs) import Ctl.Internal.Plutip.PortCheck (isPortAvailable) @@ -763,7 +760,7 @@ mkClusterContractEnv plutipCfg logger customLogger = do , odcConfig: plutipCfg.ogmiosDatumCacheConfig , kupoConfig: plutipCfg.kupoConfig } - ledgerConstants <- getLedgerConstants logger $ defaultBackend backend + ledgerConstants <- getLedgerConstants logger backend pure { backend , ctlServerConfig: plutipCfg.ctlServerConfig diff --git a/src/Internal/Test/E2E/Runner.purs b/src/Internal/Test/E2E/Runner.purs index 7f6c52daf1..5dd88265d9 100644 --- a/src/Internal/Test/E2E/Runner.purs +++ b/src/Internal/Test/E2E/Runner.purs @@ -13,10 +13,7 @@ import Control.Alt ((<|>)) import Control.Monad.Error.Class (liftMaybe) import Control.Promise (Promise, toAffE) import Ctl.Internal.Contract.Hooks (emptyHooks) -import Ctl.Internal.Contract.QueryBackend - ( QueryBackend(CtlBackend) - , defaultBackend - ) +import Ctl.Internal.Contract.QueryBackend (QueryBackend(CtlBackend)) import Ctl.Internal.Deserialization.Keys (privateKeyFromBytes) import Ctl.Internal.Helpers (liftedM, (<>)) import Ctl.Internal.Plutip.Server (withPlutipContractEnv) @@ -268,8 +265,8 @@ testPlan opts@{ tests } rt@{ wallets } = -- https://github.com/Plutonomicon/cardano-transaction-lib/issues/1197 liftAff $ withPlutipContractEnv (buildPlutipConfig opts) distr \env wallet -> do - (clusterSetup :: ClusterSetup) <- case defaultBackend env.backend of - CtlBackend backend -> pure + (clusterSetup :: ClusterSetup) <- case env.backend of + CtlBackend backend _ -> pure { ctlServerConfig: env.ctlServerConfig , ogmiosConfig: backend.ogmios.config , datumCacheConfig: backend.odc.config From e44f95996a1d640b1bf363104b5d08e5e4dc1525 Mon Sep 17 00:00:00 2001 From: Gregory Gerasev Date: Mon, 12 Dec 2022 13:04:02 +0400 Subject: [PATCH 082/373] Remove Maybe from BigNum.toBigInt output --- CHANGELOG.md | 4 +- src/Internal/BalanceTx/Collateral.purs | 4 +- src/Internal/BalanceTx/UtxoMinAda.purs | 6 +-- src/Internal/Deserialization/Transaction.purs | 52 ++++++++----------- .../Deserialization/UnspentOutput.purs | 4 +- src/Internal/Deserialization/WitnessSet.purs | 19 ++++--- src/Internal/Serialization/MinFee.purs | 6 +-- src/Internal/ToData.purs | 4 +- src/Internal/Types/BigNum.purs | 19 ++----- src/Internal/Types/Interval.purs | 16 +++--- test/Deserialization.purs | 2 +- 11 files changed, 59 insertions(+), 77 deletions(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index ec5e259cc4..756ca0b8a5 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -40,10 +40,12 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) - Running plutip servers attaches on SIGINT handlers and therefore node will not exit by default. ([#1231](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1231)). - `TestPlanM`, `interpret` and `interpretWithConfig` are now public in `Contract.Test.Mote` and our custom `consoleReporter` in `Contract.Test.Mote.ConsoleReporter`. ([#1261](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1261)). -- Internal datum conversions are now total, resulting in some datum-related Contract functions dropping the use of `Maybe`, for example `datumHash`, `convertPlutusData` (and related functions) ([#1284](https://github.com/Plutonomicon/cardano-transaction-lib/issues/1284)). +- Internal datum conversions are now total, resulting in some datum-related Contract functions dropping the use of `Maybe`, for example `datumHash`, `convertPlutusData` (and related functions). The same with `BigNum.toBigInt`. ([#1284](https://github.com/Plutonomicon/cardano-transaction-lib/issues/1284)). ### Removed +- `BigNum.toBigIntUnsafe` is dropped. ([#1284](https://github.com/Plutonomicon/cardano-transaction-lib/issues/1284)). + ### Fixed - Added missing `stakePoolTargetNum` ("`nOpt`") protocol parameter (see [CIP-9](https://cips.cardano.org/cips/cip9/)) ([#571](https://github.com/Plutonomicon/cardano-transaction-lib/issues/571)) diff --git a/src/Internal/BalanceTx/Collateral.purs b/src/Internal/BalanceTx/Collateral.purs index 019bbd4949..29cb936c09 100644 --- a/src/Internal/BalanceTx/Collateral.purs +++ b/src/Internal/BalanceTx/Collateral.purs @@ -28,7 +28,7 @@ import Ctl.Internal.Cardano.Types.TransactionUnspentOutput import Ctl.Internal.Cardano.Types.Value (Coin, NonAdaAsset) import Ctl.Internal.Cardano.Types.Value (getNonAdaAsset, mkValue, valueToCoin') as Value import Ctl.Internal.Serialization.Address (Address) -import Ctl.Internal.Types.BigNum (maxValue, toBigIntUnsafe) as BigNum +import Ctl.Internal.Types.BigNum (maxValue, toBigInt) as BigNum import Ctl.Internal.Types.OutputDatum (OutputDatum(NoOutputDatum)) import Data.BigInt (BigInt) import Data.Either (Either(Left, Right), note) @@ -80,7 +80,7 @@ addTxCollateralReturn collateral transaction ownAddress = setTxCollateralReturn collAdaValue collNonAdaAsset = do let maxBigNumAdaValue :: Coin - maxBigNumAdaValue = wrap (BigNum.toBigIntUnsafe BigNum.maxValue) + maxBigNumAdaValue = wrap (BigNum.toBigInt BigNum.maxValue) collReturnOutputRec = { address: ownAddress diff --git a/src/Internal/BalanceTx/UtxoMinAda.purs b/src/Internal/BalanceTx/UtxoMinAda.purs index 52ce898a80..e6e9bc785d 100644 --- a/src/Internal/BalanceTx/UtxoMinAda.purs +++ b/src/Internal/BalanceTx/UtxoMinAda.purs @@ -21,7 +21,7 @@ import Ctl.Internal.Types.BigNum ( fromBigInt , maxValue , toBigInt - , toBigIntUnsafe + , toBigInt ) as BigNum import Data.BigInt (BigInt) import Data.Maybe (Maybe, fromJust) @@ -49,10 +49,10 @@ utxoMinAdaValue coinsPerUtxoUnit txOutput = do (BigNum.fromBigInt n) pure $ minAdaForOutput maybeFfiHelper cslTxOutput dataCost -- useful spy: BigNum.toBigInt >>= (pure <<< spy "utxoMinAdaValue") - >>= BigNum.toBigInt + <#> BigNum.toBigInt adaOnlyUtxoMinAdaValue :: CoinsPerUtxoUnit -> Effect BigInt adaOnlyUtxoMinAdaValue coinsPerUtxoUnit = map (unsafePartial fromJust) <<< utxoMinAdaValue coinsPerUtxoUnit <<< fakeOutputWithValue - $ lovelaceValueOf (BigNum.toBigIntUnsafe BigNum.maxValue) + $ lovelaceValueOf (BigNum.toBigInt BigNum.maxValue) diff --git a/src/Internal/Deserialization/Transaction.purs b/src/Internal/Deserialization/Transaction.purs index 578b3f96c9..135cb81191 100644 --- a/src/Internal/Deserialization/Transaction.purs +++ b/src/Internal/Deserialization/Transaction.purs @@ -183,7 +183,7 @@ import Ctl.Internal.Serialization.Types , Withdrawals ) as Csl import Ctl.Internal.Types.BigNum (BigNum) as Csl -import Ctl.Internal.Types.BigNum (toBigInt') as BigNum +import Ctl.Internal.Types.BigNum (toBigInt) as BigNum import Ctl.Internal.Types.ByteArray (ByteArray) import Ctl.Internal.Types.CborBytes (CborBytes) import Ctl.Internal.Types.Int (Int) as Csl @@ -246,9 +246,8 @@ convertTxBody txBody = do outputs <- _txBodyOutputs containerHelper txBody # traverse (convertOutput >>> cslErr "TransactionOutput") - fee <- - Coin <$> (_txBodyFee txBody # BigNum.toBigInt' "Tx fee") let + fee = Coin $ (_txBodyFee txBody # BigNum.toBigInt) networkId = _txBodyNetworkId Csl.TestnetId Csl.MainnetId maybeFfiHelper txBody @@ -262,7 +261,7 @@ convertTxBody txBody = do (map <<< map) (M.fromFoldable <<< map (lmap T.RewardAddress)) -- bignum -> coin <<< (traverse <<< traverse <<< traverse) - (BigNum.toBigInt' "txbody withdrawals" >>> map Coin) + (pure <<< BigNum.toBigInt >>> Coin) $ ws update <- traverse convertUpdate $ _txBodyUpdate maybeFfiHelper txBody @@ -287,9 +286,9 @@ convertTxBody txBody = do _txBodyCollateralReturn maybeFfiHelper txBody # traverse (convertOutput >>> cslErr "TransactionOutput") - totalCollateral <- - _txBodyTotalCollateral maybeFfiHelper txBody # traverse - (BigNum.toBigInt' "txbody withdrawals" >>> map Coin) + let + totalCollateral = _txBodyTotalCollateral maybeFfiHelper txBody <#> + (BigNum.toBigInt >>> Coin) pure $ T.TxBody { inputs @@ -473,20 +472,16 @@ convertProtocolParamUpdate cslPpu = do let ppu = _unpackProtocolParamUpdate maybeFfiHelper cslPpu lbl = (<>) "ProtocolParamUpdate." - - minfeeA <- traverse (map Coin <<< BigNum.toBigInt' (lbl "minfeeA")) - ppu.minfeeA - minfeeB <- traverse (map Coin <<< BigNum.toBigInt' (lbl "minfeeB")) - ppu.minfeeB + minfeeA = map (Coin <<< BigNum.toBigInt) ppu.minfeeA + minfeeB = map (Coin <<< BigNum.toBigInt) ppu.minfeeB maxBlockBodySize <- traverse (cslNumberToUInt (lbl "maxBlockBodySize")) ppu.maxBlockBodySize maxTxSize <- traverse (cslNumberToUInt (lbl "maxTxSize")) ppu.maxTxSize maxBlockHeaderSize <- traverse (cslNumberToUInt (lbl "maxBlockHeaderSize")) ppu.maxBlockHeaderSize - keyDeposit <- traverse (map Coin <<< BigNum.toBigInt' (lbl "keyDeposit")) - ppu.keyDeposit - poolDeposit <- traverse (map Coin <<< BigNum.toBigInt' (lbl "poolDeposit")) - ppu.poolDeposit + let + keyDeposit = map (Coin <<< BigNum.toBigInt) ppu.keyDeposit + poolDeposit = map (Coin <<< BigNum.toBigInt) ppu.poolDeposit maxEpoch <- traverse (map T.Epoch <<< cslNumberToUInt (lbl "maxEpoch")) ppu.maxEpoch nOpt <- traverse (cslNumberToUInt (lbl "nOpt")) ppu.nOpt @@ -494,10 +489,10 @@ convertProtocolParamUpdate cslPpu = do ppu.protocolVersion costModels <- addErrTrace (lbl "costModels") $ traverse convertCostModels ppu.costModels - maxTxExUnits <- traverse (convertExUnits (lbl "maxTxExUnits")) - ppu.maxTxExUnits - maxBlockExUnits <- traverse (convertExUnits (lbl "maxBlockExUnits")) - ppu.maxBlockExUnits + let + maxTxExUnits = map (convertExUnits (lbl "maxTxExUnits")) ppu.maxTxExUnits + maxBlockExUnits = map (convertExUnits (lbl "maxBlockExUnits")) + ppu.maxBlockExUnits maxValueSize <- traverse (cslNumberToUInt (lbl "maxValueSize")) ppu.maxValueSize pure @@ -574,9 +569,7 @@ convertGeneralTransactionMetadata = -- convert tuple type traverse ( bitraverse - ( map TransactionMetadatumLabel <<< BigNum.toBigInt' - "MetadatumLabel: " - ) + (pure <<< TransactionMetadatumLabel <<< BigNum.toBigInt) (convertMetadatum "GeneralTransactionMetadata: ") ) -- fold to map and and wrap @@ -640,23 +633,20 @@ cslRatioToRational :: forall (r :: Row Type) . String -> { denominator :: Csl.BigNum, numerator :: Csl.BigNum } - -> E (FromCslRepError + r) (Ratio BigInt) -cslRatioToRational err { numerator, denominator } = reduce - <$> BigNum.toBigInt' (err <> " cslRatioToRational") numerator - <*> BigNum.toBigInt' (err <> " cslRatioToRational") denominator + -> Ratio BigInt +cslRatioToRational err { numerator, denominator } = + reduce (BigNum.toBigInt numerator) (BigNum.toBigInt denominator) convertExUnits :: forall (r :: Row Type) . String -> Csl.ExUnits - -> E (FromCslRepError + r) T.ExUnits + -> T.ExUnits convertExUnits nm cslExunits = let { mem, steps } = _unpackExUnits cslExunits in - { mem: _, steps: _ } - <$> BigNum.toBigInt' (nm <> " mem") mem - <*> BigNum.toBigInt' (nm <> " steps") steps + { mem: _, steps: _ } (BigNum.toBigInt mem) (BigNum.toBigInt steps) convertScriptDataHash :: Csl.ScriptDataHash -> T.ScriptDataHash convertScriptDataHash = asOneOf >>> toBytes >>> T.ScriptDataHash diff --git a/src/Internal/Deserialization/UnspentOutput.purs b/src/Internal/Deserialization/UnspentOutput.purs index 3082838b50..60076eacf4 100644 --- a/src/Internal/Deserialization/UnspentOutput.purs +++ b/src/Internal/Deserialization/UnspentOutput.purs @@ -113,7 +113,7 @@ convertScriptRef = withScriptRef convertValue :: Value -> Maybe T.Value convertValue value = do - coin <- BigNum.toBigInt $ getCoin value + let coin = BigNum.toBigInt $ getCoin value -- multiasset is optional multiasset <- for (getMultiAsset maybeFfiHelper value) \multiasset -> do let @@ -141,7 +141,7 @@ convertValue value = do map Map.fromFoldable ) -- convert BigNum values, possibly failing - traverse (traverse BigNum.toBigInt) multiasset'' + pure $ map (map BigNum.toBigInt) multiasset'' pure $ T.mkValue (T.Coin coin) $ T.mkNonAdaAsset (fromMaybe Map.empty multiasset) diff --git a/src/Internal/Deserialization/WitnessSet.purs b/src/Internal/Deserialization/WitnessSet.purs index 0543f40a1c..2e0411a092 100644 --- a/src/Internal/Deserialization/WitnessSet.purs +++ b/src/Internal/Deserialization/WitnessSet.purs @@ -124,9 +124,10 @@ convertRedeemers = extractRedeemers >>> traverse convertRedeemer convertRedeemer :: Redeemer -> Maybe T.Redeemer convertRedeemer redeemer = do tag <- convertRedeemerTag $ getRedeemerTag redeemer - index <- BigNum.toBigInt $ getRedeemerIndex redeemer - exUnits <- convertExUnits $ getExUnits redeemer - let data_ = convertPlutusData $ getRedeemerPlutusData redeemer + let + index = BigNum.toBigInt $ getRedeemerIndex redeemer + exUnits = convertExUnits $ getExUnits redeemer + data_ = convertPlutusData $ getRedeemerPlutusData redeemer pure $ T.Redeemer { tag , index @@ -142,11 +143,13 @@ convertRedeemerTag tag = case getRedeemerTagKind tag of 3 -> Just Tag.Reward _ -> Nothing -convertExUnits :: ExUnits -> Maybe T.ExUnits -convertExUnits eu = do - mem <- BigNum.toBigInt $ getExUnitsMem eu - steps <- BigNum.toBigInt $ getExUnitsSteps eu - pure { mem, steps } +convertExUnits :: ExUnits -> T.ExUnits +convertExUnits eu = + let + mem = BigNum.toBigInt $ getExUnitsMem eu + steps = BigNum.toBigInt $ getExUnitsSteps eu + in + { mem, steps } foreign import getVkeywitnesses :: MaybeFfiHelper -> TransactionWitnessSet -> Maybe Vkeywitnesses diff --git a/src/Internal/Serialization/MinFee.purs b/src/Internal/Serialization/MinFee.purs index 87f983f9c4..6ba3b9175f 100644 --- a/src/Internal/Serialization/MinFee.purs +++ b/src/Internal/Serialization/MinFee.purs @@ -39,14 +39,12 @@ calculateMinFeeCsl (ProtocolParameters pparams) selfSigners txNoSigs = do let tx = addFakeSignatures selfSigners txNoSigs cslTx <- liftEffect $ Serialization.convertTransaction tx minFee <- liftMaybe (error "Unable to calculate min_fee") $ - BigNum.toBigInt =<< _minFee maybeFfiHelper cslTx + BigNum.toBigInt <$> _minFee maybeFfiHelper cslTx (BigNum.fromUInt pparams.txFeeFixed) (BigNum.fromUInt pparams.txFeePerByte) let exUnitPrices = pparams.prices exUnitPricesCsl <- liftEffect $ Serialization.convertExUnitPrices exUnitPrices - minScriptFee <- - liftMaybe (error "Unable to calculate min_script_fee") $ - BigNum.toBigInt (_minScriptFee exUnitPricesCsl cslTx) + let minScriptFee = BigNum.toBigInt (_minScriptFee exUnitPricesCsl cslTx) pure $ wrap $ minFee + minScriptFee -- | Adds fake signatures for each expected signature of a transaction. diff --git a/src/Internal/ToData.purs b/src/Internal/ToData.purs index d36b41bcf1..904ac7e437 100644 --- a/src/Internal/ToData.purs +++ b/src/Internal/ToData.purs @@ -26,7 +26,7 @@ import Ctl.Internal.TypeLevel.RowList.Unordered.Indexed , class GetWithLabel ) import Ctl.Internal.Types.BigNum (BigNum) -import Ctl.Internal.Types.BigNum (fromInt, one, toBigIntUnsafe, zero) as BigNum +import Ctl.Internal.Types.BigNum (fromInt, one, toBigInt, zero) as BigNum import Ctl.Internal.Types.ByteArray (ByteArray(ByteArray)) import Ctl.Internal.Types.CborBytes (CborBytes) import Ctl.Internal.Types.PlutusData (PlutusData(Constr, Integer, List, Bytes)) @@ -259,7 +259,7 @@ instance ToData BigInt where toData = Integer instance ToData BigNum where - toData = toData <<< BigNum.toBigIntUnsafe + toData = toData <<< BigNum.toBigInt instance ToData UInt where toData = toData <<< uIntToBigInt diff --git a/src/Internal/Types/BigNum.purs b/src/Internal/Types/BigNum.purs index 27c1542842..6ffdfb38af 100644 --- a/src/Internal/Types/BigNum.purs +++ b/src/Internal/Types/BigNum.purs @@ -9,8 +9,6 @@ module Ctl.Internal.Types.BigNum , mul , one , toBigInt - , toBigInt' - , toBigIntUnsafe , toInt , toInt' , toString @@ -57,26 +55,17 @@ instance DecodeAeson BigNum where <<< fromBigInt <=< decodeAeson instance EncodeAeson BigNum where - encodeAeson' = encodeAeson' <<< toBigIntUnsafe + encodeAeson' = encodeAeson' <<< toBigInt -- Semiring cannot be implemented, because add and mul returns Maybe BigNum fromBigInt :: BigInt -> Maybe BigNum fromBigInt = fromString <<< BigInt.toString -toBigInt :: BigNum -> Maybe BigInt -toBigInt = BigInt.fromString <<< toString - -toBigIntUnsafe :: BigNum -> BigInt -toBigIntUnsafe = +toBigInt :: BigNum -> BigInt +toBigInt = -- Converting uint64 to an arbitrary length integer should never fail. - unsafePartial fromJust <<< toBigInt - -toBigInt' - :: forall (r :: Row Type). String -> BigNum -> E (FromCslRepError + r) BigInt -toBigInt' nm bn = - noteE (fromCslRepError (nm <> ": CSL.BigNum (" <> show bn <> ") -> BigInt ")) - $ toBigInt bn + unsafePartial fromJust <<< BigInt.fromString <<< toString toInt :: BigNum -> Maybe Int toInt = Int.fromString <<< toString diff --git a/src/Internal/Types/Interval.purs b/src/Internal/Types/Interval.purs index 7aa6a40fa7..9ca976ac7e 100644 --- a/src/Internal/Types/Interval.purs +++ b/src/Internal/Types/Interval.purs @@ -108,7 +108,7 @@ import Ctl.Internal.Types.BigNum , fromBigInt , maxValue , one - , toBigIntUnsafe + , toBigInt , zero ) as BigNum import Ctl.Internal.Types.PlutusData (PlutusData(Constr)) @@ -735,13 +735,13 @@ findSlotEraSummary (EraSummaries eraSummaries) slot = note (CannotFindSlotInEraSummaries slot) $ find pred eraSummaries where biSlot :: BigInt - biSlot = BigNum.toBigIntUnsafe $ unwrap slot + biSlot = BigNum.toBigInt $ unwrap slot pred :: EraSummary -> Boolean pred (EraSummary { start, end }) = - BigNum.toBigIntUnsafe (unwrap (unwrap start).slot) <= biSlot + BigNum.toBigInt (unwrap (unwrap start).slot) <= biSlot && maybe true - ((<) biSlot <<< BigNum.toBigIntUnsafe <<< unwrap <<< _.slot <<< unwrap) + ((<) biSlot <<< BigNum.toBigInt <<< unwrap <<< _.slot <<< unwrap) end -- This doesn't need to be exported but we can do it for tests. @@ -809,8 +809,8 @@ relSlotFromSlot :: EraSummary -> Slot -> Either SlotToPosixTimeError RelSlot relSlotFromSlot (EraSummary { start }) s@(Slot slot) = do let - startSlot = BigNum.toBigIntUnsafe $ unwrap (unwrap start).slot - biSlot = BigNum.toBigIntUnsafe slot + startSlot = BigNum.toBigInt $ unwrap (unwrap start).slot + biSlot = BigNum.toBigInt slot unless (startSlot <= biSlot) (throwError $ StartingSlotGreaterThanSlot s) pure $ wrap $ biSlot - startSlot @@ -1020,7 +1020,7 @@ slotFromRelSlot (EraSummary { start, end }) (RelSlot relSlot /\ mt@(ModTime modTime)) = do let - startSlot = BigNum.toBigIntUnsafe $ unwrap (unwrap start).slot + startSlot = BigNum.toBigInt $ unwrap (unwrap start).slot -- Round down to the nearest Slot to accept Milliseconds as input. slot = startSlot + relSlot -- relative to system start -- If `EraSummary` doesn't have an end, the condition is automatically @@ -1030,7 +1030,7 @@ slotFromRelSlot -- required to be in the distant future. Onchain, this uses POSIXTime which -- is stable, unlike Slots. endSlot = maybe (slot + one) - (BigNum.toBigIntUnsafe <<< unwrap <<< _.slot <<< unwrap) + (BigNum.toBigInt <<< unwrap <<< _.slot <<< unwrap) end bnSlot <- liftM CannotGetBigNumFromBigInt' $ BigNum.fromBigInt slot -- Check we are less than the end slot, or if equal, there is no excess: diff --git a/test/Deserialization.purs b/test/Deserialization.purs index 268e753d57..53dc6e18d2 100644 --- a/test/Deserialization.purs +++ b/test/Deserialization.purs @@ -102,7 +102,7 @@ suite = do test "Deserialization is inverse to serialization" do let bigInt = BigInt.fromInt 123 res <- errMaybe "Failed to serialize BigInt" $ BigNum.fromBigInt bigInt - >>= BigNum.toBigInt + <#> BigNum.toBigInt res `shouldEqual` bigInt group "CSL <-> CTL PlutusData roundtrip tests" do let From 1ba468f51ed3ab075c54af5b7b34926ccc189301 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Mon, 12 Dec 2022 12:07:02 +0100 Subject: [PATCH 083/373] Address requested changes --- src/Internal/Contract/Monad.purs | 11 ++++------- 1 file changed, 4 insertions(+), 7 deletions(-) diff --git a/src/Internal/Contract/Monad.purs b/src/Internal/Contract/Monad.purs index 34bb04559c..04db522855 100644 --- a/src/Internal/Contract/Monad.purs +++ b/src/Internal/Contract/Monad.purs @@ -54,6 +54,7 @@ import Ctl.Internal.QueryM , mkOgmiosWebSocketAff , underlyingWebSocket ) +-- TODO: Move/translate these types into Cardano import Ctl.Internal.QueryM.Ogmios (ProtocolParameters, SystemStart) as Ogmios import Ctl.Internal.QueryM.ServerConfig (ServerConfig) import Ctl.Internal.Serialization.Address (NetworkId) @@ -192,7 +193,7 @@ mkContractEnv params = do b2 <- parallel do wallet <- buildWallet pure $ merge { wallet } - -- compose the sub-builders together + -- Compose the sub-builders together in b1 >>> b2 >>> merge { usedTxOuts } pure $ build envBuilder constants @@ -271,17 +272,13 @@ walletNetworkCheck envNetworkId wallet = do -- | Finalizes a `Contract` environment. -- | Closes the connections in `ContractEnv`, effectively making it unusable. stopContractEnv :: ContractEnv -> Aff Unit -stopContractEnv { backend } = liftEffect do - traverse_ stopCtlRuntime (getCtlBackend backend) - traverse_ stopBlockfrostRuntime (getBlockfrostBackend backend) +stopContractEnv { backend } = + liftEffect $ traverse_ stopCtlRuntime (getCtlBackend backend) where stopCtlRuntime :: CtlBackend -> Effect Unit stopCtlRuntime { ogmios, odc } = stopWebSocket odc.ws *> stopWebSocket ogmios.ws - stopBlockfrostRuntime :: BlockfrostBackend -> Effect Unit - stopBlockfrostRuntime = undefined - stopWebSocket :: forall (a :: Type). WebSocket a -> Effect Unit stopWebSocket = ((*>) <$> _wsFinalize <*> _wsClose) <<< underlyingWebSocket From 863ec1cc2fc2014eacaccb62a3d0cc1904635cfc Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Mon, 12 Dec 2022 17:12:56 +0000 Subject: [PATCH 084/373] Restore Alt and Plus instance to Contract --- src/Internal/Contract/Monad.purs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Internal/Contract/Monad.purs b/src/Internal/Contract/Monad.purs index 79f91f4c08..e2f6b05e9c 100644 --- a/src/Internal/Contract/Monad.purs +++ b/src/Internal/Contract/Monad.purs @@ -104,6 +104,8 @@ derive instance Newtype (Contract a) _ derive newtype instance Functor Contract derive newtype instance Apply Contract derive newtype instance Applicative Contract +derive newtype instance Alt Contract +derive newtype instance Plus Contract derive newtype instance Bind Contract derive newtype instance Monad Contract derive newtype instance MonadEffect Contract From e638d001d4b468371d2534ab9b22026d97cf5a63 Mon Sep 17 00:00:00 2001 From: Gregory Gerasev Date: Tue, 13 Dec 2022 02:19:45 +0400 Subject: [PATCH 085/373] Apply suggestions from code review Co-authored-by: Joseph Young --- src/Internal/Deserialization/Transaction.purs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Internal/Deserialization/Transaction.purs b/src/Internal/Deserialization/Transaction.purs index 135cb81191..b83f7d8b39 100644 --- a/src/Internal/Deserialization/Transaction.purs +++ b/src/Internal/Deserialization/Transaction.purs @@ -247,7 +247,7 @@ convertTxBody txBody = do _txBodyOutputs containerHelper txBody # traverse (convertOutput >>> cslErr "TransactionOutput") let - fee = Coin $ (_txBodyFee txBody # BigNum.toBigInt) + fee = Coin $ BigNum.toBigInt $ _txBodyFee txBody networkId = _txBodyNetworkId Csl.TestnetId Csl.MainnetId maybeFfiHelper txBody @@ -472,8 +472,8 @@ convertProtocolParamUpdate cslPpu = do let ppu = _unpackProtocolParamUpdate maybeFfiHelper cslPpu lbl = (<>) "ProtocolParamUpdate." - minfeeA = map (Coin <<< BigNum.toBigInt) ppu.minfeeA - minfeeB = map (Coin <<< BigNum.toBigInt) ppu.minfeeB + minfeeA = Coin <<< BigNum.toBigInt <$> ppu.minfeeA + minfeeB = Coin <<< BigNum.toBigInt <$> ppu.minfeeB maxBlockBodySize <- traverse (cslNumberToUInt (lbl "maxBlockBodySize")) ppu.maxBlockBodySize maxTxSize <- traverse (cslNumberToUInt (lbl "maxTxSize")) ppu.maxTxSize From e0d0d6d30c49637c5543758b4037fd0275ccb82c Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Mon, 12 Dec 2022 22:44:25 +0000 Subject: [PATCH 086/373] Remove ODC. Add getTxMetadata handle and Kupo implementation to replace one case of full tx fetching --- doc/ctl-as-dependency.md | 2 +- doc/development.md | 2 +- doc/e2e-testing.md | 1 - doc/getting-started.md | 9 -- doc/plutip-testing.md | 2 - doc/runtime.md | 3 - doc/test-plan.md | 2 - examples/Datums.purs | 5 +- examples/Helpers.purs | 9 +- nix/ctl-server-nixos-module.nix | 1 - nix/runtime.nix | 48 -------- src/Contract/Config.purs | 2 - src/Contract/PlutusData.purs | 7 -- src/Contract/Test/Utils.purs | 12 +- src/Contract/Transaction.purs | 14 +-- src/Internal/Contract/Monad.purs | 47 +++----- src/Internal/Contract/QueryBackend.purs | 7 +- src/Internal/Contract/QueryHandle.purs | 11 +- src/Internal/Deserialization/FromBytes.js | 3 + src/Internal/Deserialization/FromBytes.purs | 10 ++ src/Internal/Plutip/Server.purs | 46 -------- src/Internal/Plutip/Types.purs | 1 - src/Internal/QueryM.purs | 122 +++----------------- src/Internal/QueryM/Config.purs | 4 +- src/Internal/QueryM/DatumCacheWsp.purs | 116 ------------------- src/Internal/QueryM/GetTxByHash.purs | 29 ----- src/Internal/QueryM/JsonWsp.purs | 2 +- src/Internal/QueryM/Kupo.purs | 50 ++++++-- src/Internal/QueryM/ServerConfig.purs | 13 --- src/Internal/Test/E2E/Options.purs | 12 -- src/Internal/Test/E2E/Route.purs | 2 - src/Internal/Test/E2E/Runner.purs | 12 -- templates/ctl-scaffold/test/Main.purs | 6 - test/Ogmios/GenerateFixtures.purs | 3 - test/OgmiosDatumCache.purs | 63 ---------- test/Plutip/Common.purs | 6 - test/Plutip/Contract.purs | 5 +- test/Plutip/Utils.purs | 12 +- test/QueryM/AffInterface.purs | 9 -- test/Unit.purs | 2 - test/e2e.env | 1 - 41 files changed, 118 insertions(+), 595 deletions(-) delete mode 100644 src/Internal/QueryM/DatumCacheWsp.purs delete mode 100644 src/Internal/QueryM/GetTxByHash.purs delete mode 100644 test/OgmiosDatumCache.purs diff --git a/doc/ctl-as-dependency.md b/doc/ctl-as-dependency.md index 17617a14f6..4b2c1953f3 100644 --- a/doc/ctl-as-dependency.md +++ b/doc/ctl-as-dependency.md @@ -23,7 +23,7 @@ The following caveats alway applies when using CTL from your project: CTL exposes two `overlay`s from its flake. You can use these in the Nix setup of your own project to use the same setup as we do, e.g. the same packages and PS builders: - `overlays.purescript` contains Purescript builders to compile Purescript sources, build bundles with Webpack (`bundlePursProject`), run unit tests using NodeJS (`runPursTest`), run CTL contracts on a private testnet using Plutip (`runPlutipTest`), or build Pursuit documentation (`buildSearchablePursDocs` and `launchSearchablePursDocs`) -- `overlays.runtime` contains various packages and other tools used in CTL's runtime, including `ogmios`, `kupo`, `ogmios-datum-cache`, `plutip-server`, and our own `ctl-server`. It also defines `buildCtlRuntime` and `launchCtlRuntime` to help you quickly launch all runtime services (see the [runtime docs](./runtime.md)) +- `overlays.runtime` contains various packages and other tools used in CTL's runtime, including `ogmios`, `kupo`, `plutip-server`, and our own `ctl-server`. It also defines `buildCtlRuntime` and `launchCtlRuntime` to help you quickly launch all runtime services (see the [runtime docs](./runtime.md)) We've split the overlays into two components to allow users to more easily choose which parts of CTL's Nix infrastructure they would like to directly consume. For example, some users do not require a pre-packaged runtime and would prefer to build it themselves with more control over its components (e.g. by directly using `ogmios` from their own `inputs`). Such users might still like to use our `purescript` overlay -- splitting the `overlays` allows us to support this. `overlays.runtime` also contains several haskell.nix packages which may cause issues with `hackage.nix` versions in your own project. diff --git a/doc/development.md b/doc/development.md index c963a5fc40..3bc21aebb1 100644 --- a/doc/development.md +++ b/doc/development.md @@ -100,7 +100,7 @@ Don't forget to update the [template `package.json`](../templates/ctl-scaffold/p ## Switching development networks -Set new `network.name` and `network.magic` in `runtime.nix`. Point `datumCache.blockFetcher.firstBlock` to a correct block/slot. Also see [Changing network configurations](./runtime.md#changing-network-configurations) +Set new `network.name` and `network.magic` in `runtime.nix`. Also see [Changing network configurations](./runtime.md#changing-network-configurations) ## Maintaining the template diff --git a/doc/e2e-testing.md b/doc/e2e-testing.md index cd6bd78304..18959183b5 100644 --- a/doc/e2e-testing.md +++ b/doc/e2e-testing.md @@ -124,7 +124,6 @@ The tests can set up using CLI arguments, environment variables, or both. CLI ar |------------------------------------------------------------------------|-----------------------------|----------------------------| | E2E+Plutip: Plutip port number | `--plutip-port` | `PLUTIP_PORT` | | E2E+Plutip: Ogmios port number | `--ogmios-port` | `OGMIOS_PORT` | -| E2E+Plutip: ODC port number | `--ogmios-datum-cache-port` | `OGMIOS_DATUM_CACHE_PORT` | | E2E+Plutip: CTL server port | `--ctl-server-port` | `CTL_SERVER_PORT` | | E2E+Plutip: Postgres port | `--postgres-port` | `POSTGRES_PORT` | | E2E+Plutip: Kupo port | `--kupo-port` | `KUPO_PORT` | diff --git a/doc/getting-started.md b/doc/getting-started.md index 819acc9c58..600306f885 100644 --- a/doc/getting-started.md +++ b/doc/getting-started.md @@ -122,7 +122,6 @@ main = Contract.Monad.launchAff_ do -- we re-export this for you config = { backendParams: mkCtlBackendParams { ogmiosConfig: defaultOgmiosWsConfig - , odcConfig: defaultDatumCacheWsConfig , kupoConfig: defaultKupoServerConfig } , ctlServerConfig: defaultServerConfig @@ -148,14 +147,6 @@ customOgmiosWsConfig = , secure: false , path: Just "/api/ogmios" } - -customDatumCacheWsConfig :: ServerConfig -customDatumCacheWsConfig = - { port: UInt.fromInt 80 - , host: "localhost" - , secure: false - , path: Just "/api/ogmios-datum-cache" - } ``` ## Building and submitting transactions diff --git a/doc/plutip-testing.md b/doc/plutip-testing.md index f7e8908786..7391ad7d45 100644 --- a/doc/plutip-testing.md +++ b/doc/plutip-testing.md @@ -18,8 +18,6 @@ CTL depends on a number of binaries in the `$PATH` to execute Plutip tests: - `plutip-server` to launch a local `cardano-node` cluster - [`ogmios`](https://ogmios.dev/) - [`kupo`](https://cardanosolutions.github.io/kupo/) -- [`ogmios-datum-cache`](https://github.com/mlabs-haskell/ogmios-datum-cache) -- PostgreSQL: `initdb`, `createdb` and `psql` for `ogmios-datum-cache` storage If you plan on using CTL's `applyArgs` effect, you must also ensure the following is on your `$PATH`: diff --git a/doc/runtime.md b/doc/runtime.md index ddbab0a648..d08eed184e 100644 --- a/doc/runtime.md +++ b/doc/runtime.md @@ -23,9 +23,6 @@ The services that are currently **required** are: - Required to query UTxOs and resolve inline datums and reference scripts - You **must** use Kupo v2.2.0 or greater with CTL - Like Ogmios, Kupo requires a running Cardano node -- [`ogmios-datum-cache`](https://github.com/mlabs-haskell/ogmios-datum-cache) - - This is required to query for datums, which Ogmios itself does not support - - This in turn requires a PostgreSQL DB Optional services: diff --git a/doc/test-plan.md b/doc/test-plan.md index 71b1f4d2aa..589124d7ab 100644 --- a/doc/test-plan.md +++ b/doc/test-plan.md @@ -218,8 +218,6 @@ Currently, we require parsing tests for the following data structures, organized - [x] `ProtocolParameters` - [x] `TxEvaluationR` - [x] `SubmitTxR` -- `ogmios-datum-cache` - - [x] `GetTxByHashR` - `cardano-serialization-lib` - `Transaction` - [x] Serialization diff --git a/examples/Datums.purs b/examples/Datums.purs index b343cc5072..ca631287c5 100644 --- a/examples/Datums.purs +++ b/examples/Datums.purs @@ -1,6 +1,7 @@ --- | An example of fetching datums from `ogmios-datum-cache`. Helpful to test --- | out the datum-cache integration +-- | An example of fetching datums from `Kupo` or `Blockfrost`. Helpful to test +-- | out the backend integration -- | +-- TODO Rewrite this example or remove it -- | To run this example: -- | -- | * launch all required services with `nix run .#ctl-runtime` diff --git a/examples/Helpers.purs b/examples/Helpers.purs index a552623529..df9401c34d 100644 --- a/examples/Helpers.purs +++ b/examples/Helpers.purs @@ -21,7 +21,6 @@ import Contract.Transaction , TransactionHash , awaitTxConfirmed , balanceTx - , getTxByHash , getTxFinalFee , signTransaction , submit @@ -30,7 +29,6 @@ import Contract.TxConstraints as Constraints import Contract.Value (CurrencySymbol, TokenName, Value) import Contract.Value (mkTokenName, scriptCurrencySymbol) as Value import Data.BigInt (BigInt) -import Effect.Exception (throw) buildBalanceSignAndSubmitTx' :: forall (validator :: Type) (datum :: Type) @@ -91,10 +89,5 @@ submitAndLog bsTx = do txId <- submit bsTx logInfo' $ "Tx ID: " <> show txId awaitTxConfirmed txId - mbTransaction <- getTxByHash txId - logInfo' $ "Retrieved tx: " <> show mbTransaction - liftEffect $ when (isNothing mbTransaction) do - void $ throw "Unable to get Tx contents" - when (mbTransaction /= Just (unwrap bsTx)) do - throw "Tx contents do not match" + logInfo' $ "Confirmed Tx ID: " <> show txId diff --git a/nix/ctl-server-nixos-module.nix b/nix/ctl-server-nixos-module.nix index 7b1464ae3b..dd55f799db 100644 --- a/nix/ctl-server-nixos-module.nix +++ b/nix/ctl-server-nixos-module.nix @@ -42,7 +42,6 @@ with lib; { "network.target" "cardano-node.service" "ogmios.service" - "ogmios-datum-cache.service" ]; serviceConfig = { User = cfg.user; diff --git a/nix/runtime.nix b/nix/runtime.nix index 30921c03ab..28f9e73dfb 100644 --- a/nix/runtime.nix +++ b/nix/runtime.nix @@ -39,19 +39,6 @@ rec { password = "ctl"; db = "ctl-${network.name}"; }; - datumCache = { - port = 9999; - controlApiToken = ""; - blockFetcher = { - firstBlock = { - slot = 1345203; - id = "8f027f183cc72dc90d4cdb8b5815deaef4b57d5a10f078ebfce87cadf9cae688"; - }; - autoStart = true; - startFromLast = false; - filter = builtins.toJSON { const = true; }; - }; - }; kupo = { port = 1442; since = "origin"; @@ -200,41 +187,6 @@ rec { }; }; }; - ogmios-datum-cache = - let - filter = inputs.nixpkgs.lib.strings.replaceStrings - [ "\"" "\\" ] [ "\\\"" "\\\\" ] - datumCache.blockFetcher.filter; - in - { - service = { - useHostStore = true; - ports = [ (bindPort datumCache.port) ]; - restart = "on-failure"; - depends_on = [ "postgres-${network.name}" "ogmios" ]; - command = [ - "${pkgs.bash}/bin/sh" - "-c" - '' - ${pkgs.ogmios-datum-cache}/bin/ogmios-datum-cache \ - --log-level warn \ - --use-latest \ - --server-api "${toString datumCache.controlApiToken}" \ - --server-port ${toString datumCache.port} \ - --ogmios-address ogmios \ - --ogmios-port ${toString ogmios.port} \ - --db-port 5432 \ - --db-host postgres-${network.name} \ - --db-user "${postgres.user}" \ - --db-name "${postgres.db}" \ - --db-password "${postgres.password}" \ - --block-slot ${toString datumCache.blockFetcher.firstBlock.slot} \ - --block-hash "${datumCache.blockFetcher.firstBlock.id}" \ - --block-filter "${filter}" - '' - ]; - }; - }; } // pkgs.lib.optionalAttrs ctlServer.enable { ctl-server = { service = { diff --git a/src/Contract/Config.purs b/src/Contract/Config.purs index b9647b3784..adbac6b9ea 100644 --- a/src/Contract/Config.purs +++ b/src/Contract/Config.purs @@ -37,7 +37,6 @@ import Ctl.Internal.Deserialization.Keys (privateKeyFromBytes) import Ctl.Internal.QueryM.ServerConfig ( Host , ServerConfig - , defaultDatumCacheWsConfig , defaultKupoServerConfig , defaultOgmiosWsConfig , defaultServerConfig @@ -66,7 +65,6 @@ testnetConfig :: ContractParams testnetConfig = { backendParams: mkCtlBackendParams { ogmiosConfig: defaultOgmiosWsConfig - , odcConfig: defaultDatumCacheWsConfig , kupoConfig: defaultKupoServerConfig } , ctlServerConfig: Just defaultServerConfig diff --git a/src/Contract/PlutusData.purs b/src/Contract/PlutusData.purs index 246d145f62..21cc81cc9f 100644 --- a/src/Contract/PlutusData.purs +++ b/src/Contract/PlutusData.purs @@ -8,7 +8,6 @@ module Contract.PlutusData , getDatumsByHashesWithError , module DataSchema , module Datum - , module ExportQueryM , module Hashing , module IsData , module Nat @@ -68,12 +67,6 @@ import Ctl.Internal.Plutus.Types.DataSchema , PNil , PSchema ) as DataSchema -import Ctl.Internal.QueryM - ( DatumCacheListeners - , DatumCacheWebSocket - , defaultDatumCacheWsConfig - , mkDatumCacheWebSocketAff - ) as ExportQueryM import Ctl.Internal.Serialization (serializeData) as Serialization import Ctl.Internal.ToData ( class ToData diff --git a/src/Contract/Test/Utils.purs b/src/Contract/Test/Utils.purs index c636f6557f..1e2975ae0b 100644 --- a/src/Contract/Test/Utils.purs +++ b/src/Contract/Test/Utils.purs @@ -61,10 +61,9 @@ import Contract.PlutusData (OutputDatum) import Contract.Prelude (Effect) import Contract.Transaction ( ScriptRef - , Transaction(Transaction) , TransactionHash , TransactionOutputWithRefScript - , getTxByHash + , getTxMetadata ) import Contract.Utxos (utxosAt) import Contract.Value (CurrencySymbol, TokenName, Value, valueOf, valueToCoin') @@ -575,16 +574,13 @@ assertTxHasMetadataImpl -> a -> ContractAssertionM Unit Unit assertTxHasMetadataImpl mdLabel txHash expectedMetadata = do - Transaction { auxiliaryData } <- - assertContractM (CouldNotGetTxByHash txHash) (getTxByHash txHash) - generalMetadata <- - assertContractM' (TransactionHasNoMetadata txHash Nothing) - (map unwrap <<< _.metadata <<< unwrap =<< auxiliaryData) + assertContractM (TransactionHasNoMetadata txHash Nothing) + (getTxMetadata txHash) rawMetadata <- assertContractM' (TransactionHasNoMetadata txHash (Just mdLabel)) - (Map.lookup (metadataLabel (Proxy :: Proxy a)) generalMetadata) + (Map.lookup (metadataLabel (Proxy :: Proxy a)) (unwrap generalMetadata)) (metadata :: a) <- assertContractM' (CouldNotParseMetadata mdLabel) diff --git a/src/Contract/Transaction.purs b/src/Contract/Transaction.purs index 13b2c896b0..5bd049986e 100644 --- a/src/Contract/Transaction.purs +++ b/src/Contract/Transaction.purs @@ -11,8 +11,8 @@ module Contract.Transaction , balanceTxsWithConstraints , balanceTxM , calculateMinFee + , getTxMetadata , createAdditionalUtxos - , getTxByHash , getTxFinalFee , module BalanceTxError , module ExportQueryM @@ -40,6 +40,7 @@ module Contract.Transaction import Prelude import Aeson (class EncodeAeson) +import Contract.Metadata (GeneralTransactionMetadata) import Contract.Monad ( Contract , liftContractM @@ -487,13 +488,12 @@ getTxFinalFee :: BalancedSignedTransaction -> BigInt getTxFinalFee = unwrap <<< view (Transaction._body <<< Transaction._fee) <<< unwrap --- | Get `Transaction` contents by hash -getTxByHash - :: TransactionHash - -> Contract (Maybe Transaction) -getTxByHash th = do +-- TODO Throw the Either errors? +-- | Fetch transaction metadata. +getTxMetadata :: TransactionHash -> Contract (Maybe GeneralTransactionMetadata) +getTxMetadata th = do queryHandle <- getQueryHandle - liftAff $ queryHandle.getTxByHash th + liftAff $ join <<< hush <$> queryHandle.getTxMetadata th -- | Wait until a transaction with given hash is confirmed. -- | Use `awaitTxConfirmedWithTimeout` if you want to limit the time of waiting. diff --git a/src/Internal/Contract/Monad.purs b/src/Internal/Contract/Monad.purs index 903474bdd6..7a10f4682b 100644 --- a/src/Internal/Contract/Monad.purs +++ b/src/Internal/Contract/Monad.purs @@ -33,12 +33,10 @@ import Control.Plus (class Plus) import Ctl.Internal.Cardano.Types.Transaction (UtxoMap) import Ctl.Internal.Contract.Hooks (Hooks) import Ctl.Internal.Contract.QueryBackend - ( BlockfrostBackend - , CtlBackend + ( CtlBackend , CtlBackendParams , QueryBackend(BlockfrostBackend, CtlBackend) , QueryBackendParams(BlockfrostBackendParams, CtlBackendParams) - , getBlockfrostBackend , getCtlBackend ) import Ctl.Internal.Helpers (filterMapWithKeyM, liftM, logWithLevel) @@ -50,30 +48,29 @@ import Ctl.Internal.QueryM , WebSocket , getProtocolParametersAff , getSystemStartAff - , mkDatumCacheWebSocketAff , mkOgmiosWebSocketAff , underlyingWebSocket ) -- TODO: Move/translate these types into Cardano import Ctl.Internal.QueryM.Ogmios (ProtocolParameters, SystemStart) as Ogmios +import Ctl.Internal.QueryM.Kupo (isTxConfirmedAff) import Ctl.Internal.QueryM.ServerConfig (ServerConfig) import Ctl.Internal.Serialization.Address (NetworkId) import Ctl.Internal.Types.UsedTxOuts (UsedTxOuts, isTxOutRefUsed, newUsedTxOuts) import Ctl.Internal.Wallet (Wallet) import Ctl.Internal.Wallet (getNetworkId) as Wallet import Ctl.Internal.Wallet.Spec (WalletSpec, mkWalletBySpec) -import Data.Either (Either(Left, Right)) +import Data.Either (Either(Left, Right), isRight) import Data.Log.Level (LogLevel) import Data.Log.Message (Message) -import Data.Maybe (Maybe(Just, Nothing), fromMaybe) -import Data.Newtype (class Newtype, unwrap) +import Data.Maybe (Maybe(Just), fromMaybe) +import Data.Newtype (class Newtype, unwrap, wrap) import Data.Traversable (for_, traverse, traverse_) import Effect (Effect) import Effect.Aff (Aff, ParAff, attempt, error, finally, supervise) import Effect.Aff.Class (liftAff) import Effect.Class (class MonadEffect, liftEffect) import Effect.Exception (Error, throw, try) -import Effect.Ref (new) as Ref import MedeaPrelude (class MonadAff) import Record.Builder (build, merge) import Undefined (undefined) @@ -224,24 +221,16 @@ buildBackend logger = case _ of BlockfrostBackend blockfrostParams <$> traverse buildCtlBackend ctlParams where buildCtlBackend :: CtlBackendParams -> Aff CtlBackend - buildCtlBackend { ogmiosConfig, kupoConfig, odcConfig } = do - datumCacheWsRef <- liftEffect $ Ref.new Nothing - sequential ado - odcWs <- parallel $ mkDatumCacheWebSocketAff datumCacheWsRef logger - odcConfig - ogmiosWs <- parallel $ mkOgmiosWebSocketAff datumCacheWsRef logger - ogmiosConfig - in - { ogmios: - { config: ogmiosConfig - , ws: ogmiosWs - } - , odc: - { config: odcConfig - , ws: odcWs - } - , kupoConfig - } + buildCtlBackend { ogmiosConfig, kupoConfig } = do + let isTxConfirmed = map isRight <<< isTxConfirmedAff kupoConfig <<< wrap + ogmiosWs <- mkOgmiosWebSocketAff isTxConfirmed logger ogmiosConfig + pure + { ogmios: + { config: ogmiosConfig + , ws: ogmiosWs + } + , kupoConfig + } getLedgerConstants :: Logger @@ -278,8 +267,8 @@ stopContractEnv { backend } = liftEffect $ traverse_ stopCtlRuntime (getCtlBackend backend) where stopCtlRuntime :: CtlBackend -> Effect Unit - stopCtlRuntime { ogmios, odc } = - stopWebSocket odc.ws *> stopWebSocket ogmios.ws + stopCtlRuntime { ogmios } = + stopWebSocket ogmios.ws stopWebSocket :: forall (a :: Type). WebSocket a -> Effect Unit stopWebSocket = ((*>) <$> _wsFinalize <*> _wsClose) <<< underlyingWebSocket @@ -358,7 +347,6 @@ mkQueryEnv :: ContractEnv -> CtlBackend -> QueryEnv () mkQueryEnv contractEnv ctlBackend = { config: { ctlServerConfig: contractEnv.ctlServerConfig - , datumCacheConfig: ctlBackend.odc.config , ogmiosConfig: ctlBackend.ogmios.config , kupoConfig: ctlBackend.kupoConfig , networkId: contractEnv.networkId @@ -369,7 +357,6 @@ mkQueryEnv contractEnv ctlBackend = } , runtime: { ogmiosWs: ctlBackend.ogmios.ws - , datumCacheWs: ctlBackend.odc.ws , wallet: contractEnv.wallet , usedTxOuts: contractEnv.usedTxOuts , pparams: contractEnv.ledgerConstants.pparams diff --git a/src/Internal/Contract/QueryBackend.purs b/src/Internal/Contract/QueryBackend.purs index ff2b41d3f9..bba4f219a3 100644 --- a/src/Internal/Contract/QueryBackend.purs +++ b/src/Internal/Contract/QueryBackend.purs @@ -13,7 +13,7 @@ module Ctl.Internal.Contract.QueryBackend import Prelude -import Ctl.Internal.QueryM (DatumCacheWebSocket, OgmiosWebSocket) +import Ctl.Internal.QueryM (OgmiosWebSocket) import Ctl.Internal.QueryM.ServerConfig (ServerConfig) import Data.Maybe (Maybe(Just, Nothing)) @@ -30,10 +30,6 @@ type CtlBackend = { config :: ServerConfig , ws :: OgmiosWebSocket } - , odc :: - { config :: ServerConfig - , ws :: DatumCacheWebSocket - } , kupoConfig :: ServerConfig } @@ -60,7 +56,6 @@ data QueryBackendParams type CtlBackendParams = { ogmiosConfig :: ServerConfig , kupoConfig :: ServerConfig - , odcConfig :: ServerConfig } type BlockfrostBackendParams = diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs index 2b30c7df22..9ed701ba41 100644 --- a/src/Internal/Contract/QueryHandle.purs +++ b/src/Internal/Contract/QueryHandle.purs @@ -29,12 +29,12 @@ import Ctl.Internal.QueryM (ClientError, QueryM) import Ctl.Internal.QueryM (evaluateTxOgmios, getChainTip, submitTxOgmios) as QueryM import Ctl.Internal.QueryM.CurrentEpoch (getCurrentEpoch) as QueryM import Ctl.Internal.QueryM.EraSummaries (getEraSummaries) as QueryM -import Ctl.Internal.QueryM.GetTxByHash (getTxByHash) as QueryM import Ctl.Internal.QueryM.Kupo ( getDatumByHash , getDatumsByHashes , getScriptByHash , getScriptsByHashes + , getTxMetadata , getUtxoByOref , isTxConfirmed , utxosAt @@ -50,10 +50,11 @@ import Ctl.Internal.Serialization.Address (Address) import Ctl.Internal.Serialization.Hash (ScriptHash) import Ctl.Internal.Types.Chain as Chain import Ctl.Internal.Types.Datum (DataHash, Datum) +import Ctl.Internal.Types.TransactionMetadata (GeneralTransactionMetadata) import Ctl.Internal.Types.Transaction (TransactionHash, TransactionInput) import Data.Either (Either) import Data.Map (Map) -import Data.Maybe (Maybe(Just, Nothing)) +import Data.Maybe (Maybe(Just, Nothing), isJust) import Data.Newtype (unwrap, wrap) import Effect.Aff (Aff) import Effect.Class (liftEffect) @@ -71,12 +72,12 @@ type QueryHandle = , getScriptsByHashes :: Array ScriptHash -> AffE (Map ScriptHash ScriptRef) , getUtxoByOref :: TransactionInput -> AffE (Maybe TransactionOutput) , isTxConfirmed :: TransactionHash -> AffE Boolean + , getTxMetadata :: TransactionHash -> AffE (Maybe GeneralTransactionMetadata) , utxosAt :: Address -> AffE UtxoMap , getChainTip :: Aff Chain.Tip , getCurrentEpoch :: Aff Ogmios.CurrentEpoch -- TODO Capture errors from all backends , submitTx :: Transaction -> Aff (Maybe TransactionHash) - , getTxByHash :: TransactionHash -> Aff (Maybe Transaction) , evaluateTx :: Transaction -> Ogmios.AdditionalUtxoSet -> Aff TxEvaluationR , getEraSummaries :: Aff Ogmios.EraSummaries } @@ -96,7 +97,8 @@ queryHandleForCtlBackend contractEnv backend = , getScriptByHash: runQueryM' <<< Kupo.getScriptByHash , getScriptsByHashes: runQueryM' <<< Kupo.getScriptsByHashes , getUtxoByOref: runQueryM' <<< Kupo.getUtxoByOref - , isTxConfirmed: runQueryM' <<< Kupo.isTxConfirmed + , isTxConfirmed: runQueryM' <<< map (map isJust) <<< Kupo.isTxConfirmed + , getTxMetadata: runQueryM' <<< Kupo.getTxMetadata , utxosAt: runQueryM' <<< Kupo.utxosAt , getChainTip: runQueryM' QueryM.getChainTip , getCurrentEpoch: runQueryM' QueryM.getCurrentEpoch @@ -109,7 +111,6 @@ queryHandleForCtlBackend contractEnv backend = case result of SubmitTxSuccess a -> pure $ Just $ wrap a _ -> pure Nothing - , getTxByHash: runQueryM' <<< QueryM.getTxByHash <<< unwrap , evaluateTx: \tx additionalUtxos -> runQueryM' do txBytes <- liftEffect ( wrap <<< Serialization.toBytes <<< asOneOf <$> diff --git a/src/Internal/Deserialization/FromBytes.js b/src/Internal/Deserialization/FromBytes.js index 7a66a5e20b..84dca53c28 100644 --- a/src/Internal/Deserialization/FromBytes.js +++ b/src/Internal/Deserialization/FromBytes.js @@ -23,6 +23,9 @@ exports._fromBytesTransactionUnspentOutput = fromBytes( "TransactionUnspentOutput" ); exports._fromBytesTransactionWitnessSet = fromBytes("TransactionWitnessSet"); +exports._fromBytesGeneralTransactionMetadata = fromBytes( + "GeneralTransactionMetadata" +); exports._fromBytesNativeScript = fromBytes("NativeScript"); exports._fromBytesMint = fromBytes("Mint"); exports._fromBytesVRFKeyHash = fromBytes("VRFKeyHash"); diff --git a/src/Internal/Deserialization/FromBytes.purs b/src/Internal/Deserialization/FromBytes.purs index 0b63165778..ec32ee733f 100644 --- a/src/Internal/Deserialization/FromBytes.purs +++ b/src/Internal/Deserialization/FromBytes.purs @@ -15,6 +15,7 @@ import Ctl.Internal.FfiHelpers (ErrorFfiHelper, errorHelper) import Ctl.Internal.Serialization.Types ( DataHash , Ed25519Signature + , GeneralTransactionMetadata , Mint , NativeScript , PlutusData @@ -57,6 +58,9 @@ instance FromBytes TransactionUnspentOutput where instance FromBytes TransactionWitnessSet where fromBytes' = _fromBytesTransactionWitnessSet eh +instance FromBytes GeneralTransactionMetadata where + fromBytes' = _fromBytesGeneralTransactionMetadata eh + instance FromBytes NativeScript where fromBytes' = _fromBytesNativeScript eh @@ -133,6 +137,12 @@ foreign import _fromBytesTransactionWitnessSet -> ByteArray -> E r TransactionWitnessSet +foreign import _fromBytesGeneralTransactionMetadata + :: forall (r :: Row Type) + . ErrorFfiHelper r + -> ByteArray + -> E r GeneralTransactionMetadata + foreign import _fromBytesNativeScript :: forall (r :: Row Type). ErrorFfiHelper r -> ByteArray -> E r NativeScript diff --git a/src/Internal/Plutip/Server.purs b/src/Internal/Plutip/Server.purs index e243fdbd07..9eb577f55a 100644 --- a/src/Internal/Plutip/Server.purs +++ b/src/Internal/Plutip/Server.purs @@ -298,7 +298,6 @@ startPlutipContractEnv plutipCfg distr cleanupRef = do startPostgres' response startOgmios' response startKupo' response - startOgmiosDatumCache' response startMCtlServer' { env, printLogs, clearLogs } <- mkContractEnv' wallets <- mkWallets' env ourKey response @@ -367,12 +366,6 @@ startPlutipContractEnv plutipCfg distr cleanupRef = do liftEffect $ cleanupTmpDir process workdir pure unit - startOgmiosDatumCache' :: ClusterStartupParameters -> Aff Unit - startOgmiosDatumCache' response = - bracket (startOgmiosDatumCache plutipCfg response) - (stopChildProcessWithPort plutipCfg.ogmiosDatumCacheConfig.port) $ const - (pure unit) - startMCtlServer' :: Aff Unit startMCtlServer' = case plutipCfg.ctlServerConfig of Nothing -> pure unit @@ -443,7 +436,6 @@ configCheck cfg = do [ cfg.port /\ "plutip-server" , cfg.ogmiosConfig.port /\ "ogmios" , cfg.kupoConfig.port /\ "kupo" - , cfg.ogmiosDatumCacheConfig.port /\ "ogmios-datum-cache" , cfg.postgresConfig.port /\ "postgres" ] <> foldMap (pure <<< (_ /\ "ctl-server") <<< _.port) cfg.ctlServerConfig occupiedServices <- Array.catMaybes <$> for services \(port /\ service) -> do @@ -711,43 +703,6 @@ stopChildProcessWithPortAndRemoveOnSignal port (childProcess /\ _ /\ sig) = do unless isAvailable do liftEffect $ throw "retry" liftEffect $ removeOnSignal sig - -startOgmiosDatumCache - :: PlutipConfig - -> ClusterStartupParameters - -> Aff ManagedProcess -startOgmiosDatumCache cfg _params = do - apiKey <- liftEffect $ uniqueId "token" - let - arguments :: Array String - arguments = - [ "--server-api" - , apiKey - , "--server-port" - , UInt.toString cfg.ogmiosDatumCacheConfig.port - , "--ogmios-address" - , cfg.ogmiosDatumCacheConfig.host - , "--ogmios-port" - , UInt.toString cfg.ogmiosConfig.port - , "--db-port" - , UInt.toString cfg.postgresConfig.port - , "--db-host" - , cfg.postgresConfig.host - , "--db-user" - , cfg.postgresConfig.user - , "--db-name" - , cfg.postgresConfig.dbname - , "--db-password" - , cfg.postgresConfig.password - , "--use-latest" - , "--from-origin" - ] - spawn "ogmios-datum-cache" arguments defaultSpawnOptions - -- Wait for "Intersection found" string in the output - $ Just - $ String.indexOf (Pattern "Intersection found") - >>> maybe NoOp (const Success) - mkClusterContractEnv :: PlutipConfig -> Logger @@ -757,7 +712,6 @@ mkClusterContractEnv plutipCfg logger customLogger = do usedTxOuts <- newUsedTxOuts backend <- buildBackend logger $ mkCtlBackendParams { ogmiosConfig: plutipCfg.ogmiosConfig - , odcConfig: plutipCfg.ogmiosDatumCacheConfig , kupoConfig: plutipCfg.kupoConfig } ledgerConstants <- getLedgerConstants logger backend diff --git a/src/Internal/Plutip/Types.purs b/src/Internal/Plutip/Types.purs index fd4313444d..528f23ef39 100644 --- a/src/Internal/Plutip/Types.purs +++ b/src/Internal/Plutip/Types.purs @@ -59,7 +59,6 @@ type PlutipConfig = , logLevel :: LogLevel -- Server configs are used to deploy the corresponding services: , ogmiosConfig :: ServerConfig - , ogmiosDatumCacheConfig :: ServerConfig -- Set this to `Nothing` to avoid spawning `ctl-server` , ctlServerConfig :: Maybe ServerConfig , kupoConfig :: ServerConfig diff --git a/src/Internal/QueryM.purs b/src/Internal/QueryM.purs index e0901d612c..02dc0869a6 100644 --- a/src/Internal/QueryM.purs +++ b/src/Internal/QueryM.purs @@ -10,8 +10,6 @@ module Ctl.Internal.QueryM , ClientOtherError ) , ClusterSetup - , DatumCacheListeners - , DatumCacheWebSocket , DefaultQueryEnv , ListenerSet , OgmiosListeners @@ -24,7 +22,6 @@ module Ctl.Internal.QueryM , QueryRuntime , SubmitTxListenerSet , WebSocket(WebSocket) - , allowError , evaluateTxOgmios , getChainTip , getLogger @@ -33,8 +30,6 @@ module Ctl.Internal.QueryM , handleAffjaxResponse , listeners , postAeson - , mkDatumCacheWebSocketAff - , mkDatumCacheRequest , mkListenerSet , defaultMessageListener , mkOgmiosRequest @@ -49,6 +44,7 @@ module Ctl.Internal.QueryM import Prelude +-- import Ctl.Internal.QueryM.Kupo (isTxConfirmed) import Aeson ( class DecodeAeson , Aeson @@ -96,10 +92,6 @@ import Ctl.Internal.JsWebSocket , _wsSend ) import Ctl.Internal.Logging (Logger, mkLogger) -import Ctl.Internal.QueryM.DatumCacheWsp - ( GetTxByHashR - ) -import Ctl.Internal.QueryM.DatumCacheWsp as DcWsp import Ctl.Internal.QueryM.Dispatcher ( DispatchError(JsError, JsonError, FaultError, ListenerCancelled) , Dispatcher @@ -139,17 +131,14 @@ import Ctl.Internal.QueryM.Ogmios as Ogmios import Ctl.Internal.QueryM.ServerConfig ( Host , ServerConfig - , defaultDatumCacheWsConfig , defaultOgmiosWsConfig , defaultServerConfig , mkHttpUrl - , mkOgmiosDatumCacheWsUrl , mkServerUrl , mkWsUrl ) as ExportServerConfig import Ctl.Internal.QueryM.ServerConfig ( ServerConfig - , mkOgmiosDatumCacheWsUrl , mkWsUrl ) import Ctl.Internal.QueryM.UniqueId (ListenerId) @@ -171,7 +160,7 @@ import Data.HTTP.Method (Method(POST)) import Data.Log.Level (LogLevel(Error, Debug)) import Data.Log.Message (Message) import Data.Map as Map -import Data.Maybe (Maybe(Just, Nothing), fromMaybe, isJust, maybe) +import Data.Maybe (Maybe(Just, Nothing), fromMaybe, maybe) import Data.MediaType.Common (applicationJSON) import Data.Newtype (class Newtype, unwrap, wrap) import Data.Traversable (for_, traverse_) @@ -189,8 +178,7 @@ import Effect.Aff ) import Effect.Aff.Class (class MonadAff, liftAff) import Effect.Class (class MonadEffect, liftEffect) -import Effect.Exception (Error, error, throw) -import Effect.Ref (Ref) +import Effect.Exception (Error, error) import Effect.Ref as Ref -- This module defines an Aff interface for Ogmios Websocket Queries @@ -204,7 +192,6 @@ import Effect.Ref as Ref type ClusterSetup = { ctlServerConfig :: Maybe ServerConfig , ogmiosConfig :: ServerConfig - , datumCacheConfig :: ServerConfig , kupoConfig :: ServerConfig , keys :: { payment :: PrivatePaymentKey @@ -222,7 +209,6 @@ type ClusterSetup = -- | - optional custom logger type QueryConfig = { ctlServerConfig :: Maybe ServerConfig - , datumCacheConfig :: ServerConfig , ogmiosConfig :: ServerConfig , kupoConfig :: ServerConfig , networkId :: NetworkId @@ -242,7 +228,6 @@ type QueryConfig = -- | - Current protocol parameters type QueryRuntime = { ogmiosWs :: OgmiosWebSocket - , datumCacheWs :: DatumCacheWebSocket , wallet :: Maybe Wallet , usedTxOuts :: UsedTxOuts , pparams :: Ogmios.ProtocolParameters @@ -403,19 +388,6 @@ mempoolSnapshotHasTxAff ogmiosWs logger ms = mkOgmiosRequestAff ogmiosWs logger (Ogmios.mempoolSnapshotHasTxCall ms) _.mempoolHasTx --------------------------------------------------------------------------------- --- Datum Cache Queries --------------------------------------------------------------------------------- - -checkTxByHashAff :: DatumCacheWebSocket -> Logger -> TxHash -> Aff Boolean -checkTxByHashAff datumCacheWs logger = - mkDatumCacheRequestAff datumCacheWs logger DcWsp.getTxByHashCall _.getTxByHash - >>> map (unwrap >>> isJust) - -allowError - :: forall (a :: Type). (Either Error a -> Effect Unit) -> a -> Effect Unit -allowError func = func <<< Right - -------------------------------------------------------------------------------- -- Affjax -------------------------------------------------------------------------------- @@ -496,7 +468,6 @@ scriptToAeson = encodeAeson <<< byteArrayToHex <<< fst <<< unwrap -- failure handling data WebSocket listeners = WebSocket JsWebSocket listeners type OgmiosWebSocket = WebSocket OgmiosListeners -type DatumCacheWebSocket = WebSocket DatumCacheListeners -- getter underlyingWebSocket :: forall (a :: Type). WebSocket a -> JsWebSocket @@ -510,25 +481,15 @@ listeners (WebSocket _ ls) = ls -- OgmiosWebSocket Setup and PrimOps -------------------------------------------------------------------------------- -mkDatumCacheWebSocketAff - :: Ref (Maybe DatumCacheWebSocket) - -> Logger - -> ServerConfig - -> Aff DatumCacheWebSocket -mkDatumCacheWebSocketAff datumCacheWsRef logger serverConfig = do - lens <- liftEffect $ mkDatumCacheWebSocketLens logger - makeAff $ \continue -> - mkServiceWebSocket lens (mkOgmiosDatumCacheWsUrl serverConfig) \res -> - res # either (\_ -> continue res) - (\ws -> Ref.write (Just ws) datumCacheWsRef *> continue res) +type IsTxConfirmed = TxHash -> Aff Boolean mkOgmiosWebSocketAff - :: Ref (Maybe DatumCacheWebSocket) + :: IsTxConfirmed -> Logger -> ServerConfig -> Aff OgmiosWebSocket -mkOgmiosWebSocketAff datumCacheWsRef logger serverConfig = do - lens <- liftEffect $ mkOgmiosWebSocketLens logger datumCacheWsRef +mkOgmiosWebSocketAff isTxConfirmed logger serverConfig = do + lens <- liftEffect $ mkOgmiosWebSocketLens logger isTxConfirmed makeAff $ mkServiceWebSocket lens (mkWsUrl serverConfig) mkServiceWebSocket @@ -588,13 +549,13 @@ mkServiceWebSocket lens url continue = do -- | the request. resendPendingSubmitRequests :: OgmiosWebSocket - -> Ref (Maybe DatumCacheWebSocket) + -> IsTxConfirmed -> Logger -> (RequestBody -> Effect Unit) -> Dispatcher -> PendingSubmitTxRequests -> Effect Unit -resendPendingSubmitRequests ogmiosWs odcWs logger sendRequest dispatcher pr = do +resendPendingSubmitRequests ogmiosWs isTxConfirmed logger sendRequest dispatcher pr = do submitTxPendingRequests <- Ref.read pr unless (Map.isEmpty submitTxPendingRequests) do -- Acquiring a mempool snapshot should never fail and, @@ -628,11 +589,8 @@ resendPendingSubmitRequests ogmiosWs odcWs logger sendRequest dispatcher pr = do retrySubmitTx <- if txInMempool then pure false else do - datumCacheWebSocket <- liftEffect do - let err = "handlePendingSubmitRequest: failed to access ODC WebSocket" - maybe (throw err) pure =<< Ref.read odcWs -- Check if the transaction was included in the block: - txConfirmed <- checkTxByHashAff datumCacheWebSocket logger txHash + txConfirmed <- isTxConfirmed txHash log "Tx confirmed" txConfirmed txHash unless txConfirmed $ liftEffect do sendRequest requestBody @@ -651,7 +609,7 @@ resendPendingSubmitRequests ogmiosWs odcWs logger sendRequest dispatcher pr = do { "result": { "SubmitSuccess": { "txId": txHash } } } -------------------------------------------------------------------------------- --- `MkServiceWebSocketLens` for ogmios and ogmios-datum-cache +-- `MkServiceWebSocketLens` for ogmios -------------------------------------------------------------------------------- type MkServiceWebSocketLens (listeners :: Type) = @@ -662,34 +620,11 @@ type MkServiceWebSocketLens (listeners :: Type) = , resendPendingRequests :: JsWebSocket -> Effect Unit } -mkDatumCacheWebSocketLens - :: Logger -> Effect (MkServiceWebSocketLens DatumCacheListeners) -mkDatumCacheWebSocketLens logger = do - dispatcher <- newDispatcher - pendingRequests <- newPendingRequests - pure $ - let - datumCacheWebSocket :: JsWebSocket -> DatumCacheWebSocket - datumCacheWebSocket ws = WebSocket ws - { getTxByHash: mkListenerSet dispatcher pendingRequests - } - - resendPendingRequests :: JsWebSocket -> Effect Unit - resendPendingRequests ws = - Ref.read pendingRequests >>= traverse_ (_wsSend ws (logger Debug)) - in - { serviceName: "ogmios-datum-cache" - , dispatcher - , logger - , typedWebSocket: datumCacheWebSocket - , resendPendingRequests - } - mkOgmiosWebSocketLens :: Logger - -> Ref (Maybe DatumCacheWebSocket) + -> IsTxConfirmed -> Effect (MkServiceWebSocketLens OgmiosListeners) -mkOgmiosWebSocketLens logger datumCacheWebSocketRef = do +mkOgmiosWebSocketLens logger isTxConfirmed = do dispatcher <- newDispatcher pendingRequests <- newPendingRequests pendingSubmitTxRequests <- newPendingRequests @@ -727,7 +662,7 @@ mkOgmiosWebSocketLens logger datumCacheWebSocketRef = do resendPendingRequests ws = do let sendRequest = _wsSend ws (logger Debug) Ref.read pendingRequests >>= traverse_ sendRequest - resendPendingSubmitRequests (ogmiosWebSocket ws) datumCacheWebSocketRef + resendPendingSubmitRequests (ogmiosWebSocket ws) isTxConfirmed logger sendRequest dispatcher @@ -760,10 +695,6 @@ type OgmiosListeners = , delegationsAndRewards :: ListenerSet (Array String) DelegationsAndRewardsR } -type DatumCacheListeners = - { getTxByHash :: ListenerSet TxHash GetTxByHashR - } - -- convenience type for adding additional query types later type ListenerSet (request :: Type) (response :: Type) = { addMessageListener :: @@ -862,31 +793,6 @@ mkOgmiosRequestAff ogmiosWs = mkRequestAff (listeners ogmiosWs) (underlyingWebSocket ogmiosWs) --- | Builds a Datum Cache request action using `QueryM` -mkDatumCacheRequest - :: forall (request :: Type) (response :: Type) - . JsonWsp.JsonWspCall request response - -> (DatumCacheListeners -> ListenerSet request response) - -> request - -> QueryM response -mkDatumCacheRequest jsonWspCall getLs inp = do - listeners' <- asks $ listeners <<< _.datumCacheWs <<< _.runtime - websocket <- asks $ underlyingWebSocket <<< _.datumCacheWs <<< _.runtime - mkRequest listeners' websocket jsonWspCall getLs inp - --- | Builds a Datum Cache request action using `Aff` -mkDatumCacheRequestAff - :: forall (request :: Type) (response :: Type) - . DatumCacheWebSocket - -> Logger - -> JsonWsp.JsonWspCall request response - -> (DatumCacheListeners -> ListenerSet request response) - -> request - -> Aff response -mkDatumCacheRequestAff datumCacheWs = mkRequestAff - (listeners datumCacheWs) - (underlyingWebSocket datumCacheWs) - mkRequest :: forall (request :: Type) (response :: Type) (listeners :: Type) . listeners diff --git a/src/Internal/QueryM/Config.purs b/src/Internal/QueryM/Config.purs index b2332d5f42..009e3c2dab 100644 --- a/src/Internal/QueryM/Config.purs +++ b/src/Internal/QueryM/Config.purs @@ -5,8 +5,7 @@ module Ctl.Internal.QueryM.Config import Ctl.Internal.QueryM (QueryConfig) import Ctl.Internal.QueryM.ServerConfig - ( defaultDatumCacheWsConfig - , defaultKupoServerConfig + ( defaultKupoServerConfig , defaultOgmiosWsConfig , defaultServerConfig ) @@ -18,7 +17,6 @@ testnetTraceQueryConfig :: QueryConfig testnetTraceQueryConfig = { ctlServerConfig: Just defaultServerConfig , ogmiosConfig: defaultOgmiosWsConfig - , datumCacheConfig: defaultDatumCacheWsConfig , kupoConfig: defaultKupoServerConfig , networkId: TestnetId , logLevel: Trace diff --git a/src/Internal/QueryM/DatumCacheWsp.purs b/src/Internal/QueryM/DatumCacheWsp.purs deleted file mode 100644 index b6f9db8a45..0000000000 --- a/src/Internal/QueryM/DatumCacheWsp.purs +++ /dev/null @@ -1,116 +0,0 @@ -module Ctl.Internal.QueryM.DatumCacheWsp - ( DatumCacheMethod - ( GetTxByHash - ) - , GetTxByHashR(GetTxByHashR) - , WspFault(WspFault) - , faultToString - , getTxByHashCall - , JsonWspRequest - , JsonWspResponse - ) where - -import Prelude - -import Aeson - ( class DecodeAeson - , class EncodeAeson - , Aeson - , JsonDecodeError - , decodeAeson - , getNestedAeson - , stringifyAeson - ) -import Control.Alt ((<|>)) -import Ctl.Internal.Base64 (Base64String) -import Ctl.Internal.QueryM.JsonWsp (JsonWspCall, mkCallType) -import Ctl.Internal.QueryM.UniqueId (ListenerId) -import Ctl.Internal.Types.ByteArray (ByteArray, byteArrayToHex) -import Data.Either (Either) -import Data.Generic.Rep (class Generic) -import Data.Maybe (Maybe(Nothing)) -import Data.Newtype (class Newtype) -import Data.Show.Generic (genericShow) - -newtype WspFault = WspFault Aeson - -faultToString :: WspFault -> String -faultToString (WspFault j) = stringifyAeson j - -type JsonWspRequest (a :: Type) = - { type :: String - , version :: String - , servicename :: String - , methodname :: String - , args :: a - , mirror :: ListenerId - } - -type JsonWspResponse = - { type :: String - , version :: String - , servicename :: String - , methodname :: String - , result :: Maybe Aeson - , fault :: Maybe WspFault - , reflection :: ListenerId - } - --- TODO --- This should be changed to `GetTxByHashR Transaction` once we support `getTxById` --- --- See https://github.com/Plutonomicon/cardano-transaction-lib/issues/30 -newtype GetTxByHashR = GetTxByHashR (Maybe Base64String) - -derive instance Newtype GetTxByHashR _ -derive instance Generic GetTxByHashR _ - -instance Show GetTxByHashR where - show = genericShow - -instance DecodeAeson GetTxByHashR where - decodeAeson r = GetTxByHashR <$> - let - txFound :: Either JsonDecodeError (Maybe Base64String) - txFound = - getNestedAeson r [ "TxFound", "value" ] >>= decodeAeson - - txNotFound :: Either JsonDecodeError (Maybe Base64String) - txNotFound = - Nothing <$ getNestedAeson r [ "TxNotFound" ] - in - txFound <|> txNotFound - --- TODO: delete -data DatumCacheMethod = GetTxByHash - -derive instance Eq DatumCacheMethod - -instance Show DatumCacheMethod where - show = datumCacheMethodToString - -datumCacheMethodToString :: DatumCacheMethod -> String -datumCacheMethodToString = case _ of - GetTxByHash -> "GetTxByHash" - -type TxHash = ByteArray - -getTxByHashCall :: JsonWspCall TxHash GetTxByHashR -getTxByHashCall = mkDatumCacheCallType - GetTxByHash - ({ hash: _ } <<< byteArrayToHex) - --- convenience helper -mkDatumCacheCallType - :: forall (a :: Type) (i :: Type) (o :: Type) - . EncodeAeson (JsonWspRequest a) - => DatumCacheMethod - -> (i -> a) - -> JsonWspCall i o -mkDatumCacheCallType method args = mkCallType - { "type": "jsonwsp/request" - , version: "1.0" - , servicename: "ogmios" - } - { methodname: datumCacheMethodToString method, args } - diff --git a/src/Internal/QueryM/GetTxByHash.purs b/src/Internal/QueryM/GetTxByHash.purs deleted file mode 100644 index 2bd028fe5d..0000000000 --- a/src/Internal/QueryM/GetTxByHash.purs +++ /dev/null @@ -1,29 +0,0 @@ -module Ctl.Internal.QueryM.GetTxByHash where - -import Prelude - -import Ctl.Internal.Base64 (toByteArray) -import Ctl.Internal.Cardano.Types.Transaction (Transaction) -import Ctl.Internal.Deserialization.Transaction (deserializeTransaction) -import Ctl.Internal.QueryM (QueryM, mkDatumCacheRequest) -import Ctl.Internal.QueryM.DatumCacheWsp as QueryM -import Ctl.Internal.QueryM.Ogmios (TxHash) -import Ctl.Internal.Types.CborBytes (CborBytes(CborBytes)) -import Data.Either (hush) -import Data.Maybe (Maybe(Just, Nothing), maybe) -import Data.Newtype (unwrap) -import Effect.Class (liftEffect) -import Effect.Exception (throw) - -getTxByHash :: TxHash -> QueryM (Maybe Transaction) -getTxByHash txHash = do - unwrap <$> mkDatumCacheRequest QueryM.getTxByHashCall _.getTxByHash txHash >>= - maybe - (pure Nothing) - \txBase64 -> do - let - txBytes = CborBytes $ toByteArray txBase64 - maybe (liftEffect $ throw "Unable to decode transaction") - (pure <<< Just) - $ hush - $ deserializeTransaction txBytes diff --git a/src/Internal/QueryM/JsonWsp.purs b/src/Internal/QueryM/JsonWsp.purs index 3b40e70e2e..5426eb3bbf 100644 --- a/src/Internal/QueryM/JsonWsp.purs +++ b/src/Internal/QueryM/JsonWsp.purs @@ -1,5 +1,5 @@ -- | Provides basics types and operations for working with JSON RPC protocol --- | used by Ogmios and ogmios-datum-cache +-- | used by Ogmios module Ctl.Internal.QueryM.JsonWsp ( JsonWspRequest , JsonWspResponse diff --git a/src/Internal/QueryM/Kupo.purs b/src/Internal/QueryM/Kupo.purs index 8c17bc7a31..0bd71fd7e0 100644 --- a/src/Internal/QueryM/Kupo.purs +++ b/src/Internal/QueryM/Kupo.purs @@ -3,13 +3,17 @@ module Ctl.Internal.QueryM.Kupo , getDatumsByHashes , getScriptByHash , getScriptsByHashes + , getTxMetadata , getUtxoByOref , isTxConfirmed + , isTxConfirmedAff , utxosAt ) where import Prelude +import Ctl.Internal.Deserialization.Transaction (convertGeneralTransactionMetadata) +import Ctl.Internal.Types.BigNum (toString) as BigNum import Aeson ( class DecodeAeson , Aeson @@ -53,9 +57,10 @@ import Ctl.Internal.QueryM , QueryM , handleAffjaxResponse ) -import Ctl.Internal.QueryM.ServerConfig (mkHttpUrl) +import Ctl.Internal.QueryM.ServerConfig (ServerConfig, mkHttpUrl) import Ctl.Internal.Serialization.Address ( Address + , Slot , addressBech32 , addressFromBech32 , addressFromBytes @@ -74,9 +79,10 @@ import Ctl.Internal.Types.Transaction ( TransactionHash(TransactionHash) , TransactionInput(TransactionInput) ) -import Data.Array (null) as Array +import Ctl.Internal.Types.TransactionMetadata (GeneralTransactionMetadata) +import Data.Array (uncons) import Data.BigInt (BigInt) -import Data.Either (Either(Left, Right), note) +import Data.Either (Either(Left, Right), hush, note) import Data.Foldable (fold) import Data.Generic.Rep (class Generic) import Data.HTTP.Method (Method(GET)) @@ -90,6 +96,7 @@ import Data.Traversable (traverse) import Data.Tuple (Tuple(Tuple)) import Data.Tuple.Nested (type (/\), (/\)) import Data.UInt (toString) as UInt +import Effect.Aff (Aff) import Effect.Aff.Class (liftAff) import Foreign.Object (Object) import Foreign.Object (toUnfoldable) as Object @@ -150,11 +157,33 @@ getScriptsByHashes = -- FIXME: This can only confirm transactions with at least one output. -- https://github.com/Plutonomicon/cardano-transaction-lib/issues/1293 -isTxConfirmed :: TransactionHash -> QueryM (Either ClientError Boolean) -isTxConfirmed (TransactionHash txHash) = do +isTxConfirmed :: TransactionHash -> QueryM (Either ClientError (Maybe Slot)) +isTxConfirmed th = do + config <- asks (_.kupoConfig <<< _.config) + liftAff $ isTxConfirmedAff config th + +-- Exported due to Ogmios requiring confirmations at a websocket level +isTxConfirmedAff :: ServerConfig -> TransactionHash -> Aff (Either ClientError (Maybe Slot)) +isTxConfirmedAff config (TransactionHash txHash) = do let endpoint = "/matches/*@" <> byteArrayToHex txHash - kupoGetRequest endpoint - <#> map (not <<< Array.null :: Array Aeson -> _) <<< handleAffjaxResponse + kupoGetRequestAff config endpoint + <#> handleAffjaxResponse >>> map \utxos -> + case uncons ( utxos :: _ { created_at :: { slot_no :: Slot } } ) of + Just { head } -> Just head.created_at.slot_no + _ -> Nothing + +getTxMetadata :: TransactionHash -> QueryM (Either ClientError (Maybe GeneralTransactionMetadata)) +getTxMetadata txHash = runExceptT do + ExceptT (isTxConfirmed txHash) >>= case _ of + Nothing -> pure Nothing + Just slot -> do + let endpoint = "/metadata/" <> BigNum.toString (unwrap slot) <> "?transaction_id=" <> byteArrayToHex (unwrap txHash) + generalTxMetadatas + <- ExceptT $ handleAffjaxResponse <$> kupoGetRequest endpoint + case uncons ( generalTxMetadatas :: _ { raw :: String } ) of + Just { head, tail: [] } -> + pure $ hexToByteArray head.raw >>= (fromBytes >=> convertGeneralTransactionMetadata >>> hush) + _ -> pure Nothing -------------------------------------------------------------------------------- -- `utxosAt` response parsing @@ -391,7 +420,12 @@ kupoGetRequest :: String -> QueryM (Either Affjax.Error (Affjax.Response String)) kupoGetRequest endpoint = do config <- asks (_.kupoConfig <<< _.config) - liftAff $ Affjax.request $ Affjax.defaultRequest + liftAff $ kupoGetRequestAff config endpoint + +kupoGetRequestAff + :: ServerConfig -> String -> Aff (Either Affjax.Error (Affjax.Response String)) +kupoGetRequestAff config endpoint = do + Affjax.request $ Affjax.defaultRequest { method = Left GET , url = mkHttpUrl config <> endpoint , responseFormat = Affjax.ResponseFormat.string diff --git a/src/Internal/QueryM/ServerConfig.purs b/src/Internal/QueryM/ServerConfig.purs index a6b8187708..00932ae201 100644 --- a/src/Internal/QueryM/ServerConfig.purs +++ b/src/Internal/QueryM/ServerConfig.purs @@ -1,12 +1,10 @@ module Ctl.Internal.QueryM.ServerConfig ( Host , ServerConfig - , defaultDatumCacheWsConfig , defaultKupoServerConfig , defaultOgmiosWsConfig , defaultServerConfig , mkHttpUrl - , mkOgmiosDatumCacheWsUrl , mkServerUrl , mkWsUrl ) where @@ -44,14 +42,6 @@ defaultOgmiosWsConfig = , path: Nothing } -defaultDatumCacheWsConfig :: ServerConfig -defaultDatumCacheWsConfig = - { port: UInt.fromInt 9999 - , host: "localhost" - , secure: false - , path: Nothing - } - defaultKupoServerConfig :: ServerConfig defaultKupoServerConfig = { port: UInt.fromInt 4008 @@ -66,9 +56,6 @@ mkHttpUrl = mkServerUrl "http" mkWsUrl :: ServerConfig -> Url mkWsUrl = mkServerUrl "ws" -mkOgmiosDatumCacheWsUrl :: ServerConfig -> Url -mkOgmiosDatumCacheWsUrl cfg = mkWsUrl cfg <> "ws" - mkServerUrl :: String -> ServerConfig -> Url mkServerUrl protocol cfg = (if cfg.secure then (protocol <> "s") else protocol) diff --git a/src/Internal/Test/E2E/Options.purs b/src/Internal/Test/E2E/Options.purs index fa17acc51d..c695b40eca 100644 --- a/src/Internal/Test/E2E/Options.purs +++ b/src/Internal/Test/E2E/Options.purs @@ -95,7 +95,6 @@ type TestOptions = Record type ClusterPortsOptions_ (r :: Row Type) = ( plutipPort :: Maybe UInt , ogmiosPort :: Maybe UInt - , ogmiosDatumCachePort :: Maybe UInt , ctlServerPort :: Maybe UInt , postgresPort :: Maybe UInt , kupoPort :: Maybe UInt @@ -333,14 +332,12 @@ defaultPorts :: { ctlServer :: Int , kupo :: Int , ogmios :: Int - , ogmiosDatumCache :: Int , plutip :: Int , postgres :: Int } defaultPorts = { plutip: 8087 , ogmios: 1345 - , ogmiosDatumCache: 10005 , ctlServer: 8088 , postgres: 5438 , kupo: 1443 @@ -364,14 +361,6 @@ clusterPortsOptionsParser = ado showPort "OGMIOS" defaultPorts.ogmios , metavar "PORT" ] - ogmiosDatumCachePort <- option (Just <$> uintParser) $ fold - [ long "ogmios-datum-cache-port" - , help "Ogmios Datum Cache port for use with local Plutip cluster" - , value Nothing - , showDefaultWith $ const $ - showPort "OGMIOS_DATUM_CACHE" defaultPorts.ogmiosDatumCache - , metavar "PORT" - ] ctlServerPort <- option (Just <$> uintParser) $ fold [ long "ctl-server-port" , help "ctl-server port for use with local Plutip cluster" @@ -399,7 +388,6 @@ clusterPortsOptionsParser = ado in { plutipPort , ogmiosPort - , ogmiosDatumCachePort , ctlServerPort , postgresPort , kupoPort diff --git a/src/Internal/Test/E2E/Route.purs b/src/Internal/Test/E2E/Route.purs index 0d3b0f04e9..515003709e 100644 --- a/src/Internal/Test/E2E/Route.purs +++ b/src/Internal/Test/E2E/Route.purs @@ -208,14 +208,12 @@ route configs tests = do setClusterOptions { ctlServerConfig , ogmiosConfig - , datumCacheConfig , kupoConfig } config = config { backendParams = mkCtlBackendParams { ogmiosConfig: ogmiosConfig - , odcConfig: datumCacheConfig , kupoConfig: kupoConfig } , ctlServerConfig = ctlServerConfig diff --git a/src/Internal/Test/E2E/Runner.purs b/src/Internal/Test/E2E/Runner.purs index 5dd88265d9..f275d7386c 100644 --- a/src/Internal/Test/E2E/Runner.purs +++ b/src/Internal/Test/E2E/Runner.purs @@ -200,13 +200,6 @@ buildPlutipConfig options = , secure: false , path: Nothing } - , ogmiosDatumCacheConfig: - { port: fromMaybe (UInt.fromInt defaultPorts.ogmiosDatumCache) - options.ogmiosDatumCachePort - , host: "127.0.0.1" - , secure: false - , path: Nothing - } , ctlServerConfig: Just { port: fromMaybe (UInt.fromInt defaultPorts.ctlServer) options.ctlServerPort @@ -269,7 +262,6 @@ testPlan opts@{ tests } rt@{ wallets } = CtlBackend backend _ -> pure { ctlServerConfig: env.ctlServerConfig , ogmiosConfig: backend.ogmios.config - , datumCacheConfig: backend.odc.config , kupoConfig: backend.kupoConfig , keys: { payment: keyWalletPrivatePaymentKey wallet @@ -365,7 +357,6 @@ readTestRuntime testOptions = do <<< delete (Proxy :: Proxy "testTimeout") <<< delete (Proxy :: Proxy "plutipPort") <<< delete (Proxy :: Proxy "ogmiosPort") - <<< delete (Proxy :: Proxy "ogmiosDatumCachePort") <<< delete (Proxy :: Proxy "ctlServerPort") <<< delete (Proxy :: Proxy "postgresPort") <<< delete (Proxy :: Proxy "skipJQuery") @@ -379,8 +370,6 @@ readPorts testOptions = do readPortNumber "PLUTIP" testOptions.plutipPort ogmiosPort <- readPortNumber "OGMIOS" testOptions.ogmiosPort - ogmiosDatumCachePort <- - readPortNumber "OGMIOS_DATUM_CACHE" testOptions.ogmiosDatumCachePort ctlServerPort <- readPortNumber "CTL_SERVER" testOptions.ctlServerPort postgresPort <- @@ -390,7 +379,6 @@ readPorts testOptions = do pure { plutipPort , ogmiosPort - , ogmiosDatumCachePort , ctlServerPort , postgresPort , kupoPort diff --git a/templates/ctl-scaffold/test/Main.purs b/templates/ctl-scaffold/test/Main.purs index 518b87057f..f2dd876b52 100644 --- a/templates/ctl-scaffold/test/Main.purs +++ b/templates/ctl-scaffold/test/Main.purs @@ -58,12 +58,6 @@ config = , secure: false , path: Nothing } - , ogmiosDatumCacheConfig: - { port: UInt.fromInt 10000 - , host: "127.0.0.1" - , secure: false - , path: Nothing - } , ctlServerConfig: Just { port: UInt.fromInt 8083 , host: "127.0.0.1" diff --git a/test/Ogmios/GenerateFixtures.purs b/test/Ogmios/GenerateFixtures.purs index 5bcb89f49c..0b9fa4f4c7 100644 --- a/test/Ogmios/GenerateFixtures.purs +++ b/test/Ogmios/GenerateFixtures.purs @@ -43,9 +43,6 @@ import Node.FS.Aff (writeTextFile) import Node.Path (concat) -- A simple websocket for testing --- TODO Generalize websocket constructors using type classes traversing rows --- to factor mk{Ogmios{DatumCache,},}WebSocket into a single implementation --- https://github.com/Plutonomicon/cardano-transaction-lib/issues/664 mkWebSocket :: forall (a :: Type) (b :: Type) . DecodeAeson b diff --git a/test/OgmiosDatumCache.purs b/test/OgmiosDatumCache.purs deleted file mode 100644 index b763b26b74..0000000000 --- a/test/OgmiosDatumCache.purs +++ /dev/null @@ -1,63 +0,0 @@ -module Test.Ctl.OgmiosDatumCache - ( suite - ) where - -import Prelude - -import Aeson (caseAesonArray, decodeAeson, encodeAeson) -import Contract.Address (ByteArray) -import Control.Monad.Error.Class (class MonadThrow) -import Ctl.Internal.Hashing (datumHash) -import Ctl.Internal.Test.TestPlanM (TestPlanM) -import Ctl.Internal.Types.Datum (Datum(Datum)) -import Ctl.Internal.Types.PlutusData (PlutusData) -import Data.Either (Either(Left, Right)) -import Data.Newtype (unwrap) -import Data.Traversable (for_) -import Effect.Aff (Aff) -import Effect.Class (class MonadEffect) -import Effect.Exception (Error) -import Mote (group, skip, test) -import Test.Ctl.Utils (errEither, errMaybe, readAeson) -import Test.Spec.Assertions (shouldEqual) - -suite :: TestPlanM (Aff Unit) Unit -suite = group "Ogmios Datum Cache tests" $ do - -- TODO Move - skip $ test - "Plutus data samples should satisfy the Aeson roundtrip test (FIXME: \ - \https://github.com/mlabs-haskell/purescript-aeson/issues/7)" - plutusDataToFromAesonTest - test "Plutus data samples should have a compatible hash" plutusDataHashingTest - --- TODO Add GetTxByHash - -readPlutusDataSamples - :: forall (m :: Type -> Type) - . MonadEffect m - => m (Array { hash :: ByteArray, plutusData :: PlutusData }) -readPlutusDataSamples = do - errEither <<< decodeAeson =<< readAeson - "./fixtures/test/ogmios-datum-cache/plutus-data-samples.json" - -plutusDataToFromAesonTest - :: forall (m :: Type -> Type). MonadEffect m => MonadThrow Error m => m Unit -plutusDataToFromAesonTest = do - pdsAes <- readAeson - "./fixtures/test/ogmios-datum-cache/plutus-data-samples.json" - aess <- errEither <<< caseAesonArray (Left "Expected a Json array") Right $ - pdsAes - for_ aess \aes -> do - (sample :: { hash :: ByteArray, plutusData :: PlutusData }) <- errEither $ - decodeAeson aes - let aes' = encodeAeson sample - aes `shouldEqual` aes' - -plutusDataHashingTest - :: forall (m :: Type -> Type). MonadEffect m => MonadThrow Error m => m Unit -plutusDataHashingTest = do - plutusDataSamples <- readPlutusDataSamples - let elems = plutusDataSamples - for_ elems \{ hash, plutusData } -> do - hash' <- errMaybe "Couldn't hash the datum" <<< datumHash $ Datum plutusData - hash `shouldEqual` unwrap hash' diff --git a/test/Plutip/Common.purs b/test/Plutip/Common.purs index 7d3711f895..4f985c9e20 100644 --- a/test/Plutip/Common.purs +++ b/test/Plutip/Common.purs @@ -28,12 +28,6 @@ config = , secure: false , path: Nothing } - , ogmiosDatumCacheConfig: - { port: UInt.fromInt 10000 - , host: "127.0.0.1" - , secure: false - , path: Nothing - } , ctlServerConfig: Just { port: UInt.fromInt 8083 , host: "127.0.0.1" diff --git a/test/Plutip/Contract.purs b/test/Plutip/Contract.purs index 73e00bfb21..d96f5c855f 100644 --- a/test/Plutip/Contract.purs +++ b/test/Plutip/Contract.purs @@ -690,7 +690,8 @@ suite = do mkDatumHash :: String -> DataHash mkDatumHash = wrap <<< hexToByteArrayUnsafe -- Nothing is expected, because we are in an empty chain. - -- This test only checks for ability to connect to ODC + -- This test only checks for ability to connect to the datum-querying + -- backend. logInfo' <<< show =<< getDatumByHash ( mkDatumHash "42be572a6d9a8a2ec0df04f14b0d4fcbe4a7517d74975dfff914514f12316252" @@ -752,7 +753,7 @@ suite = do logInfo' "Running GetDatums submittx" txId <- payToTest vhash awaitTxConfirmed txId - logInfo' "Tx submitted successfully, trying to fetch datum from ODC" + logInfo' "Tx submitted successfully, trying to fetch datum" hash1 <- liftM (error "Couldn't get hash for datums 1") $ datumHash datum1 diff --git a/test/Plutip/Utils.purs b/test/Plutip/Utils.purs index a023f571d3..a02909571d 100644 --- a/test/Plutip/Utils.purs +++ b/test/Plutip/Utils.purs @@ -10,29 +10,23 @@ import Contract.Monad (Contract) import Contract.Transaction ( BalancedSignedTransaction , awaitTxConfirmed - , getTxByHash , submit ) import Control.Monad.Reader (asks) import Ctl.Internal.Types.UsedTxOuts (TxOutRefCache) -import Data.Maybe (Maybe(Just), isNothing) import Data.Newtype (unwrap) import Effect.Class (liftEffect) -import Effect.Exception (throw) import Effect.Ref as Ref +-- TODO: Get everything we can about a tx and confirm them +-- eg. outputs, metadata, datums, scripts submitAndLog :: BalancedSignedTransaction -> Contract Unit submitAndLog bsTx = do txId <- submit bsTx logInfo' $ "Tx ID: " <> show txId awaitTxConfirmed txId - mbTransaction <- getTxByHash txId - logInfo' $ "Tx: " <> show mbTransaction - liftEffect $ when (isNothing mbTransaction) do - void $ throw "Unable to get Tx contents" - when (mbTransaction /= Just (unwrap bsTx)) do - throw "Tx contents do not match" + logInfo' $ "Confirmed Tx ID: " <> show txId getLockedInputs :: Contract TxOutRefCache getLockedInputs = do diff --git a/test/QueryM/AffInterface.purs b/test/QueryM/AffInterface.purs index 1024952fcc..d575915aff 100644 --- a/test/QueryM/AffInterface.purs +++ b/test/QueryM/AffInterface.purs @@ -10,7 +10,6 @@ import Ctl.Internal.QueryM ) import Ctl.Internal.QueryM.CurrentEpoch (getCurrentEpoch) import Ctl.Internal.QueryM.EraSummaries (getEraSummaries) -import Ctl.Internal.QueryM.GetTxByHash (getTxByHash) import Ctl.Internal.Test.TestPlanM (TestPlanM) import Ctl.Internal.Types.ByteArray (hexToByteArrayUnsafe) import Data.Either (Either(Left, Right)) @@ -46,14 +45,6 @@ suite = do Left error -> do (Pattern "Server responded with `fault`" `indexOf` show error) `shouldSatisfy` isJust - group "Ogmios datum cache" do - test "Can process GetTxByHash" do - testOgmiosGetTxByHash - -testOgmiosGetTxByHash :: QueryM Unit -testOgmiosGetTxByHash = do - void $ getTxByHash $ hexToByteArrayUnsafe - "f7c47c65216f7057569111d962a74de807de57e79f7efa86b4e454d42c875e4e" testGetChainTip :: QueryM Unit testGetChainTip = do diff --git a/test/Unit.purs b/test/Unit.purs index c714aa9e45..8663fe6ad0 100644 --- a/test/Unit.purs +++ b/test/Unit.purs @@ -24,7 +24,6 @@ import Test.Ctl.NativeScript as NativeScript import Test.Ctl.Ogmios.Address as Ogmios.Address import Test.Ctl.Ogmios.Aeson as Ogmios.Aeson import Test.Ctl.Ogmios.EvaluateTx as Ogmios.EvaluateTx -import Test.Ctl.OgmiosDatumCache as OgmiosDatumCache import Test.Ctl.Parser as Parser import Test.Ctl.ProtocolParams as ProtocolParams import Test.Ctl.Serialization as Serialization @@ -66,7 +65,6 @@ testPlan = do Transaction.suite TxOutput.suite UsedTxOuts.suite - OgmiosDatumCache.suite Ogmios.Address.suite Ogmios.Aeson.suite Ogmios.EvaluateTx.suite diff --git a/test/e2e.env b/test/e2e.env index ec1f105adf..80661b0027 100755 --- a/test/e2e.env +++ b/test/e2e.env @@ -68,7 +68,6 @@ export E2E_EXTRA_BROWSER_ARGS="--disable-web-security" # Bypass CORS for Kupo # Port numbers used by services when testing with Plutip export PLUTIP_PORT=8087 export OGMIOS_PORT=1345 -export OGMIOS_DATUM_CACHE_PORT=10005 export CTL_SERVER_PORT=8088 export POSTGRES_PORT=5438 From 013f8bb5b20097de0d20aeec22d1910599afb919 Mon Sep 17 00:00:00 2001 From: peter Date: Tue, 13 Dec 2022 10:02:39 +0100 Subject: [PATCH 087/373] wip: some unit-tests failing --- src/Internal/Cardano/Types/Transaction.purs | 2 ++ src/Internal/Deserialization/Transaction.purs | 9 +++++++++ src/Internal/Serialization.js | 4 ++++ src/Internal/Serialization.purs | 15 +++++++++++++++ test/Fixtures.purs | 2 ++ 5 files changed, 32 insertions(+) diff --git a/src/Internal/Cardano/Types/Transaction.purs b/src/Internal/Cardano/Types/Transaction.purs index 9859afea20..90c23e796f 100644 --- a/src/Internal/Cardano/Types/Transaction.purs +++ b/src/Internal/Cardano/Types/Transaction.purs @@ -402,6 +402,8 @@ type ProtocolParamUpdate = , maxTxExUnits :: Maybe ExUnits , maxBlockExUnits :: Maybe ExUnits , maxValueSize :: Maybe UInt + , collateralPercentage :: Maybe UInt + , maxCollateralInputs :: Maybe UInt } type ExUnitPrices = diff --git a/src/Internal/Deserialization/Transaction.purs b/src/Internal/Deserialization/Transaction.purs index 578b3f96c9..3c8aeab503 100644 --- a/src/Internal/Deserialization/Transaction.purs +++ b/src/Internal/Deserialization/Transaction.purs @@ -500,6 +500,11 @@ convertProtocolParamUpdate cslPpu = do ppu.maxBlockExUnits maxValueSize <- traverse (cslNumberToUInt (lbl "maxValueSize")) ppu.maxValueSize + collateralPercentage <- traverse + (cslNumberToUInt (lbl "collateralPercentage")) + ppu.collateralPercentage + maxCollateralInputs <- traverse (cslNumberToUInt (lbl "maxCollateralInputs")) + ppu.maxCollateralInputs pure { minfeeA , minfeeB @@ -521,6 +526,8 @@ convertProtocolParamUpdate cslPpu = do , maxTxExUnits , maxBlockExUnits , maxValueSize + , collateralPercentage + , maxCollateralInputs } convertNonce :: Csl.Nonce -> T.Nonce @@ -706,6 +713,8 @@ foreign import _unpackProtocolParamUpdate , maxTxExUnits :: Maybe Csl.ExUnits , maxBlockExUnits :: Maybe Csl.ExUnits , maxValueSize :: Maybe Number + , collateralPercentage :: Maybe Number + , maxCollateralInputs :: Maybe Number } foreign import _unpackCostModels diff --git a/src/Internal/Serialization.js b/src/Internal/Serialization.js index 1764d25b00..2cc0811319 100644 --- a/src/Internal/Serialization.js +++ b/src/Internal/Serialization.js @@ -349,6 +349,10 @@ exports.ppuSetMaxBlockExUnits = setter("max_block_ex_units"); exports.ppuSetMaxValueSize = setter("max_value_size"); +exports.ppuSetCollateralPercentage = setter("collateral_percentage"); + +exports.ppuSetMaxCollateralInputs = setter("max_collateral_inputs"); + exports.newProtocolParamUpdate = () => lib.ProtocolParamUpdate.new(); exports.newProposedProtocolParameterUpdates = containerHelper => kvs => () => diff --git a/src/Internal/Serialization.purs b/src/Internal/Serialization.purs index 1d8eddb043..408cd313f6 100644 --- a/src/Internal/Serialization.purs +++ b/src/Internal/Serialization.purs @@ -19,6 +19,7 @@ module Ctl.Internal.Serialization import Prelude +import Contract.Metadata (TransactionMetadatum(..)) import Ctl.Internal.Cardano.Types.ScriptRef ( ScriptRef(NativeScriptRef, PlutusScriptRef) ) as T @@ -470,6 +471,16 @@ foreign import ppuSetMaxValueSize -> Int -> Effect Unit +foreign import ppuSetCollateralPercentage + :: ProtocolParamUpdate + -> Int + -> Effect Unit + +foreign import ppuSetMaxCollateralInputs + :: ProtocolParamUpdate + -> Int + -> Effect Unit + foreign import newProposedProtocolParameterUpdates :: ContainerHelper -> Array (GenesisHash /\ ProtocolParamUpdate) @@ -580,6 +591,8 @@ convertProtocolParamUpdate , maxTxExUnits , maxBlockExUnits , maxValueSize + , collateralPercentage + , maxCollateralInputs } = do ppu <- newProtocolParamUpdate for_ minfeeA $ ppuSetMinfeeA ppu @@ -627,6 +640,8 @@ convertProtocolParamUpdate for_ maxTxExUnits $ convertExUnits >=> ppuSetMaxTxExUnits ppu for_ maxBlockExUnits $ convertExUnits >=> ppuSetMaxBlockExUnits ppu for_ maxValueSize $ UInt.toInt >>> ppuSetMaxValueSize ppu + for_ collateralPercentage $ UInt.toInt >>> ppuSetCollateralPercentage ppu + for_ maxCollateralInputs $ UInt.toInt >>> ppuSetMaxCollateralInputs ppu pure ppu mkUnitInterval diff --git a/test/Fixtures.purs b/test/Fixtures.purs index 0015e5f31b..87cb8e50b3 100644 --- a/test/Fixtures.purs +++ b/test/Fixtures.purs @@ -321,6 +321,8 @@ proposedProtocolParameterUpdates1 = ProposedProtocolParameterUpdates $ , maxBlockExUnits: Just { mem: BigInt.fromInt 1, steps: BigInt.fromInt 1 } , maxValueSize: Just $ UInt.fromInt 1 + , collateralPercentage: Just $ UInt.fromInt 1 + , maxCollateralInputs: Just $ UInt.fromInt 1 } ] From 7463cca69a4b0391e3413f05c181f25529e16645 Mon Sep 17 00:00:00 2001 From: peter Date: Tue, 13 Dec 2022 12:18:13 +0100 Subject: [PATCH 088/373] with higher collateralPercentage --- src/Internal/Serialization.purs | 1 - test/Fixtures.purs | 4 ++-- 2 files changed, 2 insertions(+), 3 deletions(-) diff --git a/src/Internal/Serialization.purs b/src/Internal/Serialization.purs index 408cd313f6..b00f76820c 100644 --- a/src/Internal/Serialization.purs +++ b/src/Internal/Serialization.purs @@ -19,7 +19,6 @@ module Ctl.Internal.Serialization import Prelude -import Contract.Metadata (TransactionMetadatum(..)) import Ctl.Internal.Cardano.Types.ScriptRef ( ScriptRef(NativeScriptRef, PlutusScriptRef) ) as T diff --git a/test/Fixtures.purs b/test/Fixtures.purs index 87cb8e50b3..5b11316602 100644 --- a/test/Fixtures.purs +++ b/test/Fixtures.purs @@ -321,8 +321,8 @@ proposedProtocolParameterUpdates1 = ProposedProtocolParameterUpdates $ , maxBlockExUnits: Just { mem: BigInt.fromInt 1, steps: BigInt.fromInt 1 } , maxValueSize: Just $ UInt.fromInt 1 - , collateralPercentage: Just $ UInt.fromInt 1 - , maxCollateralInputs: Just $ UInt.fromInt 1 + , collateralPercentage: Just $ UInt.fromInt 140 + , maxCollateralInputs: Just $ UInt.fromInt 10 } ] From 0e6723961a96c103ebb356ff03941e6101003c59 Mon Sep 17 00:00:00 2001 From: peter Date: Tue, 13 Dec 2022 13:36:05 +0100 Subject: [PATCH 089/373] add fields to _unpackProtocolParamUpdate --- src/Internal/Deserialization/Transaction.js | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Internal/Deserialization/Transaction.js b/src/Internal/Deserialization/Transaction.js index d5c99090d9..3b082314d1 100644 --- a/src/Internal/Deserialization/Transaction.js +++ b/src/Internal/Deserialization/Transaction.js @@ -180,6 +180,8 @@ exports._unpackProtocolParamUpdate = maybe => ppu => { maxTxExUnits: optional(ppu.max_tx_ex_units()), maxBlockExUnits: optional(ppu.max_block_ex_units()), maxValueSize: optional(ppu.max_value_size()), + collateralPercentage: optional(ppu.collateral_percentage()), + maxCollateralInputs: optional(ppu.max_collateral_inputs()), }; }; From ec5f4868e7931f76682d3380f45267f02fd0e015 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Tue, 13 Dec 2022 14:11:52 +0000 Subject: [PATCH 090/373] Drop more references to ODC. Drop postgres --- Makefile | 6 +- README.md | 2 +- doc/e2e-testing.md | 1 - doc/faq.md | 15 - flake.lock | 3670 ++----------------------- flake.nix | 12 +- nix/default.nix | 11 +- nix/runtime.nix | 27 +- nix/test-nixos-configuration.nix | 11 - src/Contract/Test/Plutip.purs | 1 - src/Internal/Plutip/Server.purs | 86 - src/Internal/Plutip/Types.purs | 11 - src/Internal/QueryM.purs | 1 - src/Internal/Test/E2E/Options.purs | 12 - src/Internal/Test/E2E/Runner.purs | 11 - src/Internal/Types/PlutusData.purs | 2 +- templates/ctl-scaffold/test/Main.purs | 7 - test/Plutip/Common.purs | 7 - test/e2e.env | 1 - 19 files changed, 309 insertions(+), 3585 deletions(-) diff --git a/Makefile b/Makefile index 89f568324b..3c45271b85 100644 --- a/Makefile +++ b/Makefile @@ -1,7 +1,6 @@ SHELL := bash .ONESHELL: -.PHONY: run-dev run-build check-format format run-datum-cache-postgres-console - query-testnet-tip clean check-explicit-exports +.PHONY: run-dev run-build check-format format query-testnet-tip clean check-explicit-exports .SHELLFLAGS := -eu -o pipefail -c ps-sources := $(shell fd -epurs -Etmp) @@ -49,9 +48,6 @@ format: make check-examples-imports make check-whitespace -run-datum-cache-postgres-console: - @nix shell nixpkgs#postgresql -c psql postgresql://ctxlib:ctxlib@localhost:5432 - query-preview-testnet-tip: CARDANO_NODE_SOCKET_PATH=${preview-node-ipc}/node.socket cardano-cli query tip \ --testnet-magic 2 diff --git a/README.md b/README.md index 01c15602d9..0822aeb514 100644 --- a/README.md +++ b/README.md @@ -68,7 +68,7 @@ CTL is directly inspired by the Plutus Application Backend (PAB). Unlike PAB, ho - This has been solved using Ogmios & Kupo - We will support an alternative BlockFrost backend as well in the future 3. How do we query for datums (i.e. the datums themselves and not just their hashes)? - - `ogmios-datum-cache` solves this problem + - `Kupo` solves this problem 4. How do we submit the transaction? - This is done via browser-based light wallet integration in the browser based on CIP-30 5. How closely should we follow Plutus' `Contract` API? diff --git a/doc/e2e-testing.md b/doc/e2e-testing.md index 18959183b5..e4d3802ccd 100644 --- a/doc/e2e-testing.md +++ b/doc/e2e-testing.md @@ -125,7 +125,6 @@ The tests can set up using CLI arguments, environment variables, or both. CLI ar | E2E+Plutip: Plutip port number | `--plutip-port` | `PLUTIP_PORT` | | E2E+Plutip: Ogmios port number | `--ogmios-port` | `OGMIOS_PORT` | | E2E+Plutip: CTL server port | `--ctl-server-port` | `CTL_SERVER_PORT` | -| E2E+Plutip: Postgres port | `--postgres-port` | `POSTGRES_PORT` | | E2E+Plutip: Kupo port | `--kupo-port` | `KUPO_PORT` | The default configuration can be found in `test/e2e.env`. diff --git a/doc/faq.md b/doc/faq.md index 141d38f47b..43e6246f05 100644 --- a/doc/faq.md +++ b/doc/faq.md @@ -51,21 +51,6 @@ Haskell's `aeson` library encodes long integers as JSON numbers, which leads to This is because the node hasn't fully synced. The protocol parameter name changed from `coinsPerUtxoWord` to `coinsPerUtxoByte` in Babbage. CTL only supports the latest era, but Ogmios returns different protocol parameters format depending on current era of a local node. -### Q: Why do I get an error from `foreign.js` when running Plutip tests locally? - -The most likely reason for this is that spawning the external processes from `Contract.Test.Plutip` fails. Make sure that all of the required services are on your `$PATH` (see more [here](./runtime.md); you can also set `shell.withRuntime = true;` to ensure that these are always added to your shell environment when running `nix develop`). Also, check your logs closely. You might see something like: - -``` -/home/me/ctl-project/output/Effect.Aff/foreign.js:532 - throw util.fromLeft(step); - ^ - -Error: Command failed: initdb /tmp/nix-shell.2AQ4vD/nix-shell.6SMFfq/6s0mchkxl6w9m3m7/postgres/data -initdb: error: invalid locale settings; check LANG and LC_* environment variables -``` - -The last line is the the most important part. Postgres will fail if your locale is not configured correctly. We _could_ try to do this in the `shellHook` when creating the project `devShell`, but dealing with locales is non-trivial and could cause more issues than it solves. You can find more information online regarding this error and how to potentially solve it, for example [here](https://stackoverflow.com/questions/41956994/initdb-bin-invalid-locale-settings-check-lang-and-lc-environment-variables) and [here](https://askubuntu.com/questions/114759/warning-setlocale-lc-all-cannot-change-locale). - ### How can I write my own Nix derivations using the project returned by `purescriptProject`? If the different derivation builders that `purescriptProject` gives you out-of-the-box (e.g. `runPursTest`, `bundlePursProject`, etc...) are not sufficient, you can access the compiled project (all of the original `src` argument plus the `output` directory that `purs` produces) and the generated `node_modules` using the `compiled` and `nodeModules` attributes, respectively. These can be used to write your own derivations without needing to recompile the entire project (that is, the generated output can be shared between all of your Nix components). For example: diff --git a/flake.lock b/flake.lock index 9c1a90f2e4..4dfff4ab6d 100644 --- a/flake.lock +++ b/flake.lock @@ -34,23 +34,6 @@ "type": "github" } }, - "CHaP_3": { - "flake": false, - "locked": { - "lastModified": 1666726035, - "narHash": "sha256-EBodp9DJb8Z+aVbuezVwLJ9Q9XIJUXFd/n2skay3FeU=", - "owner": "input-output-hk", - "repo": "cardano-haskell-packages", - "rev": "b074321c4c8cbf2c3789436ab11eaa43e1c441a7", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-haskell-packages", - "rev": "b074321c4c8cbf2c3789436ab11eaa43e1c441a7", - "type": "github" - } - }, "HTTP": { "flake": false, "locked": { @@ -131,86 +114,6 @@ "type": "github" } }, - "HTTP_14": { - "flake": false, - "locked": { - "lastModified": 1451647621, - "narHash": "sha256-oHIyw3x0iKBexEo49YeUDV1k74ZtyYKGR2gNJXXRxts=", - "owner": "phadej", - "repo": "HTTP", - "rev": "9bc0996d412fef1787449d841277ef663ad9a915", - "type": "github" - }, - "original": { - "owner": "phadej", - "repo": "HTTP", - "type": "github" - } - }, - "HTTP_15": { - "flake": false, - "locked": { - "lastModified": 1451647621, - "narHash": "sha256-oHIyw3x0iKBexEo49YeUDV1k74ZtyYKGR2gNJXXRxts=", - "owner": "phadej", - "repo": "HTTP", - "rev": "9bc0996d412fef1787449d841277ef663ad9a915", - "type": "github" - }, - "original": { - "owner": "phadej", - "repo": "HTTP", - "type": "github" - } - }, - "HTTP_16": { - "flake": false, - "locked": { - "lastModified": 1451647621, - "narHash": "sha256-oHIyw3x0iKBexEo49YeUDV1k74ZtyYKGR2gNJXXRxts=", - "owner": "phadej", - "repo": "HTTP", - "rev": "9bc0996d412fef1787449d841277ef663ad9a915", - "type": "github" - }, - "original": { - "owner": "phadej", - "repo": "HTTP", - "type": "github" - } - }, - "HTTP_17": { - "flake": false, - "locked": { - "lastModified": 1451647621, - "narHash": "sha256-oHIyw3x0iKBexEo49YeUDV1k74ZtyYKGR2gNJXXRxts=", - "owner": "phadej", - "repo": "HTTP", - "rev": "9bc0996d412fef1787449d841277ef663ad9a915", - "type": "github" - }, - "original": { - "owner": "phadej", - "repo": "HTTP", - "type": "github" - } - }, - "HTTP_18": { - "flake": false, - "locked": { - "lastModified": 1451647621, - "narHash": "sha256-oHIyw3x0iKBexEo49YeUDV1k74ZtyYKGR2gNJXXRxts=", - "owner": "phadej", - "repo": "HTTP", - "rev": "9bc0996d412fef1787449d841277ef663ad9a915", - "type": "github" - }, - "original": { - "owner": "phadej", - "repo": "HTTP", - "type": "github" - } - }, "HTTP_2": { "flake": false, "locked": { @@ -416,36 +319,6 @@ "type": "github" } }, - "blank_5": { - "locked": { - "lastModified": 1625557891, - "narHash": "sha256-O8/MWsPBGhhyPoPLHZAuoZiiHo9q6FLlEeIDEXuj6T4=", - "owner": "divnix", - "repo": "blank", - "rev": "5a5d2684073d9f563072ed07c871d577a6c614a8", - "type": "github" - }, - "original": { - "owner": "divnix", - "repo": "blank", - "type": "github" - } - }, - "blank_6": { - "locked": { - "lastModified": 1625557891, - "narHash": "sha256-O8/MWsPBGhhyPoPLHZAuoZiiHo9q6FLlEeIDEXuj6T4=", - "owner": "divnix", - "repo": "blank", - "rev": "5a5d2684073d9f563072ed07c871d577a6c614a8", - "type": "github" - }, - "original": { - "owner": "divnix", - "repo": "blank", - "type": "github" - } - }, "bot-plutus-interface": { "inputs": { "Win32-network": "Win32-network", @@ -585,91 +458,6 @@ "type": "github" } }, - "cabal-32_14": { - "flake": false, - "locked": { - "lastModified": 1603716527, - "narHash": "sha256-X0TFfdD4KZpwl0Zr6x+PLxUt/VyKQfX7ylXHdmZIL+w=", - "owner": "haskell", - "repo": "cabal", - "rev": "48bf10787e27364730dd37a42b603cee8d6af7ee", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.2", - "repo": "cabal", - "type": "github" - } - }, - "cabal-32_15": { - "flake": false, - "locked": { - "lastModified": 1603716527, - "narHash": "sha256-sDbrmur9Zfp4mPKohCD8IDZfXJ0Tjxpmr2R+kg5PpSY=", - "owner": "haskell", - "repo": "cabal", - "rev": "94aaa8e4720081f9c75497e2735b90f6a819b08e", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.2", - "repo": "cabal", - "type": "github" - } - }, - "cabal-32_16": { - "flake": false, - "locked": { - "lastModified": 1603716527, - "narHash": "sha256-sDbrmur9Zfp4mPKohCD8IDZfXJ0Tjxpmr2R+kg5PpSY=", - "owner": "haskell", - "repo": "cabal", - "rev": "94aaa8e4720081f9c75497e2735b90f6a819b08e", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.2", - "repo": "cabal", - "type": "github" - } - }, - "cabal-32_17": { - "flake": false, - "locked": { - "lastModified": 1603716527, - "narHash": "sha256-sDbrmur9Zfp4mPKohCD8IDZfXJ0Tjxpmr2R+kg5PpSY=", - "owner": "haskell", - "repo": "cabal", - "rev": "94aaa8e4720081f9c75497e2735b90f6a819b08e", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.2", - "repo": "cabal", - "type": "github" - } - }, - "cabal-32_18": { - "flake": false, - "locked": { - "lastModified": 1603716527, - "narHash": "sha256-X0TFfdD4KZpwl0Zr6x+PLxUt/VyKQfX7ylXHdmZIL+w=", - "owner": "haskell", - "repo": "cabal", - "rev": "48bf10787e27364730dd37a42b603cee8d6af7ee", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.2", - "repo": "cabal", - "type": "github" - } - }, "cabal-32_2": { "flake": false, "locked": { @@ -891,7 +679,7 @@ "type": "github" } }, - "cabal-34_14": { + "cabal-34_2": { "flake": false, "locked": { "lastModified": 1640353650, @@ -908,14 +696,14 @@ "type": "github" } }, - "cabal-34_15": { + "cabal-34_3": { "flake": false, "locked": { - "lastModified": 1622475795, - "narHash": "sha256-chwTL304Cav+7p38d9mcb+egABWmxo2Aq+xgVBgEb/U=", + "lastModified": 1640353650, + "narHash": "sha256-N1t6M3/wqj90AEdRkeC8i923gQYUpzSr8b40qVOZ1Rk=", "owner": "haskell", "repo": "cabal", - "rev": "b086c1995cdd616fc8d91f46a21e905cc50a1049", + "rev": "942639c18c0cd8ec53e0a6f8d120091af35312cd", "type": "github" }, "original": { @@ -925,14 +713,14 @@ "type": "github" } }, - "cabal-34_16": { + "cabal-34_4": { "flake": false, "locked": { - "lastModified": 1622475795, - "narHash": "sha256-chwTL304Cav+7p38d9mcb+egABWmxo2Aq+xgVBgEb/U=", + "lastModified": 1640353650, + "narHash": "sha256-N1t6M3/wqj90AEdRkeC8i923gQYUpzSr8b40qVOZ1Rk=", "owner": "haskell", "repo": "cabal", - "rev": "b086c1995cdd616fc8d91f46a21e905cc50a1049", + "rev": "942639c18c0cd8ec53e0a6f8d120091af35312cd", "type": "github" }, "original": { @@ -942,7 +730,7 @@ "type": "github" } }, - "cabal-34_17": { + "cabal-34_5": { "flake": false, "locked": { "lastModified": 1622475795, @@ -959,14 +747,14 @@ "type": "github" } }, - "cabal-34_18": { + "cabal-34_6": { "flake": false, "locked": { - "lastModified": 1640353650, - "narHash": "sha256-N1t6M3/wqj90AEdRkeC8i923gQYUpzSr8b40qVOZ1Rk=", + "lastModified": 1622475795, + "narHash": "sha256-chwTL304Cav+7p38d9mcb+egABWmxo2Aq+xgVBgEb/U=", "owner": "haskell", "repo": "cabal", - "rev": "942639c18c0cd8ec53e0a6f8d120091af35312cd", + "rev": "b086c1995cdd616fc8d91f46a21e905cc50a1049", "type": "github" }, "original": { @@ -976,14 +764,14 @@ "type": "github" } }, - "cabal-34_2": { + "cabal-34_7": { "flake": false, "locked": { - "lastModified": 1640353650, - "narHash": "sha256-N1t6M3/wqj90AEdRkeC8i923gQYUpzSr8b40qVOZ1Rk=", + "lastModified": 1622475795, + "narHash": "sha256-chwTL304Cav+7p38d9mcb+egABWmxo2Aq+xgVBgEb/U=", "owner": "haskell", "repo": "cabal", - "rev": "942639c18c0cd8ec53e0a6f8d120091af35312cd", + "rev": "b086c1995cdd616fc8d91f46a21e905cc50a1049", "type": "github" }, "original": { @@ -993,7 +781,7 @@ "type": "github" } }, - "cabal-34_3": { + "cabal-34_8": { "flake": false, "locked": { "lastModified": 1640353650, @@ -1010,7 +798,7 @@ "type": "github" } }, - "cabal-34_4": { + "cabal-34_9": { "flake": false, "locked": { "lastModified": 1640353650, @@ -1027,194 +815,41 @@ "type": "github" } }, - "cabal-34_5": { + "cabal-36": { "flake": false, "locked": { - "lastModified": 1622475795, - "narHash": "sha256-chwTL304Cav+7p38d9mcb+egABWmxo2Aq+xgVBgEb/U=", + "lastModified": 1641652457, + "narHash": "sha256-BlFPKP4C4HRUJeAbdembX1Rms1LD380q9s0qVDeoAak=", "owner": "haskell", "repo": "cabal", - "rev": "b086c1995cdd616fc8d91f46a21e905cc50a1049", + "rev": "f27667f8ec360c475027dcaee0138c937477b070", "type": "github" }, "original": { "owner": "haskell", - "ref": "3.4", + "ref": "3.6", "repo": "cabal", "type": "github" } }, - "cabal-34_6": { + "cabal-36_10": { "flake": false, "locked": { - "lastModified": 1622475795, - "narHash": "sha256-chwTL304Cav+7p38d9mcb+egABWmxo2Aq+xgVBgEb/U=", + "lastModified": 1640163203, + "narHash": "sha256-TwDWP2CffT0j40W6zr0J1Qbu+oh3nsF1lUx9446qxZM=", "owner": "haskell", "repo": "cabal", - "rev": "b086c1995cdd616fc8d91f46a21e905cc50a1049", + "rev": "ecf418050c1821f25e2e218f1be94c31e0465df1", "type": "github" }, "original": { "owner": "haskell", - "ref": "3.4", + "ref": "3.6", "repo": "cabal", "type": "github" } }, - "cabal-34_7": { - "flake": false, - "locked": { - "lastModified": 1622475795, - "narHash": "sha256-chwTL304Cav+7p38d9mcb+egABWmxo2Aq+xgVBgEb/U=", - "owner": "haskell", - "repo": "cabal", - "rev": "b086c1995cdd616fc8d91f46a21e905cc50a1049", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.4", - "repo": "cabal", - "type": "github" - } - }, - "cabal-34_8": { - "flake": false, - "locked": { - "lastModified": 1640353650, - "narHash": "sha256-N1t6M3/wqj90AEdRkeC8i923gQYUpzSr8b40qVOZ1Rk=", - "owner": "haskell", - "repo": "cabal", - "rev": "942639c18c0cd8ec53e0a6f8d120091af35312cd", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.4", - "repo": "cabal", - "type": "github" - } - }, - "cabal-34_9": { - "flake": false, - "locked": { - "lastModified": 1640353650, - "narHash": "sha256-N1t6M3/wqj90AEdRkeC8i923gQYUpzSr8b40qVOZ1Rk=", - "owner": "haskell", - "repo": "cabal", - "rev": "942639c18c0cd8ec53e0a6f8d120091af35312cd", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.4", - "repo": "cabal", - "type": "github" - } - }, - "cabal-36": { - "flake": false, - "locked": { - "lastModified": 1641652457, - "narHash": "sha256-BlFPKP4C4HRUJeAbdembX1Rms1LD380q9s0qVDeoAak=", - "owner": "haskell", - "repo": "cabal", - "rev": "f27667f8ec360c475027dcaee0138c937477b070", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.6", - "repo": "cabal", - "type": "github" - } - }, - "cabal-36_10": { - "flake": false, - "locked": { - "lastModified": 1640163203, - "narHash": "sha256-TwDWP2CffT0j40W6zr0J1Qbu+oh3nsF1lUx9446qxZM=", - "owner": "haskell", - "repo": "cabal", - "rev": "ecf418050c1821f25e2e218f1be94c31e0465df1", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.6", - "repo": "cabal", - "type": "github" - } - }, - "cabal-36_11": { - "flake": false, - "locked": { - "lastModified": 1641652457, - "narHash": "sha256-BlFPKP4C4HRUJeAbdembX1Rms1LD380q9s0qVDeoAak=", - "owner": "haskell", - "repo": "cabal", - "rev": "f27667f8ec360c475027dcaee0138c937477b070", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.6", - "repo": "cabal", - "type": "github" - } - }, - "cabal-36_12": { - "flake": false, - "locked": { - "lastModified": 1641652457, - "narHash": "sha256-BlFPKP4C4HRUJeAbdembX1Rms1LD380q9s0qVDeoAak=", - "owner": "haskell", - "repo": "cabal", - "rev": "f27667f8ec360c475027dcaee0138c937477b070", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.6", - "repo": "cabal", - "type": "github" - } - }, - "cabal-36_13": { - "flake": false, - "locked": { - "lastModified": 1640163203, - "narHash": "sha256-TwDWP2CffT0j40W6zr0J1Qbu+oh3nsF1lUx9446qxZM=", - "owner": "haskell", - "repo": "cabal", - "rev": "ecf418050c1821f25e2e218f1be94c31e0465df1", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.6", - "repo": "cabal", - "type": "github" - } - }, - "cabal-36_14": { - "flake": false, - "locked": { - "lastModified": 1640163203, - "narHash": "sha256-TwDWP2CffT0j40W6zr0J1Qbu+oh3nsF1lUx9446qxZM=", - "owner": "haskell", - "repo": "cabal", - "rev": "ecf418050c1821f25e2e218f1be94c31e0465df1", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.6", - "repo": "cabal", - "type": "github" - } - }, - "cabal-36_15": { + "cabal-36_11": { "flake": false, "locked": { "lastModified": 1641652457, @@ -1451,22 +1086,6 @@ } }, "cardano-configurations_3": { - "flake": false, - "locked": { - "lastModified": 1662514199, - "narHash": "sha256-Z71TP5nHA9ch4DRwftz8my5RwYOjH/xA/WlcJqUTtYY=", - "owner": "input-output-hk", - "repo": "cardano-configurations", - "rev": "182b16cb743867b0b24b7af92efbf427b2b09b52", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-configurations", - "type": "github" - } - }, - "cardano-configurations_4": { "flake": false, "locked": { "lastModified": 1667387423, @@ -1575,7 +1194,7 @@ }, "cardano-mainnet-mirror_4": { "inputs": { - "nixpkgs": "nixpkgs_20" + "nixpkgs": "nixpkgs_18" }, "locked": { "lastModified": 1642701714, @@ -1594,7 +1213,7 @@ }, "cardano-mainnet-mirror_5": { "inputs": { - "nixpkgs": "nixpkgs_22" + "nixpkgs": "nixpkgs_20" }, "locked": { "lastModified": 1642701714, @@ -1613,64 +1232,7 @@ }, "cardano-mainnet-mirror_6": { "inputs": { - "nixpkgs": "nixpkgs_23" - }, - "locked": { - "lastModified": 1642701714, - "narHash": "sha256-SR3luE+ePX6U193EKE/KSEuVzWAW0YsyPYDC4hOvALs=", - "owner": "input-output-hk", - "repo": "cardano-mainnet-mirror", - "rev": "819488be9eabbba6aaa7c931559bc584d8071e3d", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "ref": "nix", - "repo": "cardano-mainnet-mirror", - "type": "github" - } - }, - "cardano-mainnet-mirror_7": { - "inputs": { - "nixpkgs": "nixpkgs_28" - }, - "locked": { - "lastModified": 1642701714, - "narHash": "sha256-SR3luE+ePX6U193EKE/KSEuVzWAW0YsyPYDC4hOvALs=", - "owner": "input-output-hk", - "repo": "cardano-mainnet-mirror", - "rev": "819488be9eabbba6aaa7c931559bc584d8071e3d", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "ref": "nix", - "repo": "cardano-mainnet-mirror", - "type": "github" - } - }, - "cardano-mainnet-mirror_8": { - "inputs": { - "nixpkgs": "nixpkgs_30" - }, - "locked": { - "lastModified": 1642701714, - "narHash": "sha256-SR3luE+ePX6U193EKE/KSEuVzWAW0YsyPYDC4hOvALs=", - "owner": "input-output-hk", - "repo": "cardano-mainnet-mirror", - "rev": "819488be9eabbba6aaa7c931559bc584d8071e3d", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "ref": "nix", - "repo": "cardano-mainnet-mirror", - "type": "github" - } - }, - "cardano-mainnet-mirror_9": { - "inputs": { - "nixpkgs": "nixpkgs_31" + "nixpkgs": "nixpkgs_21" }, "locked": { "lastModified": 1642701714, @@ -1742,39 +1304,6 @@ "haskellNix": "haskellNix_8", "iohkNix": "iohkNix_8", "membench": "membench_4", - "nixpkgs": [ - "ogmios-datum-cache-nixos", - "ogmios", - "cardano-node", - "node-snapshot", - "membench", - "cardano-node-snapshot", - "haskellNix", - "nixpkgs-2105" - ], - "utils": "utils_6" - }, - "locked": { - "lastModified": 1644954571, - "narHash": "sha256-c6MM1mQoS/AnTIrwaRmITK4L4i9lLNtkjOUHiseBtUs=", - "owner": "input-output-hk", - "repo": "cardano-node", - "rev": "30d62b86e7b98da28ef8ad9412e4e00a1ba1231d", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-node", - "rev": "30d62b86e7b98da28ef8ad9412e4e00a1ba1231d", - "type": "github" - } - }, - "cardano-node-snapshot_3": { - "inputs": { - "customConfig": "customConfig_12", - "haskellNix": "haskellNix_12", - "iohkNix": "iohkNix_12", - "membench": "membench_6", "nixpkgs": [ "ogmios-nixos", "cardano-node", @@ -1784,7 +1313,7 @@ "haskellNix", "nixpkgs-2105" ], - "utils": "utils_11" + "utils": "utils_6" }, "locked": { "lastModified": 1644954571, @@ -1853,32 +1382,28 @@ "inputs": { "cardano-mainnet-mirror": "cardano-mainnet-mirror_4", "cardano-node-workbench": [ - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "blank" ], "customConfig": "customConfig_6", - "flake-compat": "flake-compat_11", + "flake-compat": "flake-compat_9", "hackageNix": "hackageNix_2", "haskellNix": "haskellNix_6", "hostNixpkgs": [ - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "nixpkgs" ], "iohkNix": "iohkNix_6", "nixTools": "nixTools_2", "nixpkgs": [ - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "haskellNix", "nixpkgs-unstable" ], "node-measured": [ - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "blank" ], "node-process": "node-process_2", @@ -1901,54 +1426,6 @@ "type": "github" } }, - "cardano-node_4": { - "inputs": { - "cardano-mainnet-mirror": "cardano-mainnet-mirror_7", - "cardano-node-workbench": [ - "ogmios-nixos", - "blank" - ], - "customConfig": "customConfig_10", - "flake-compat": "flake-compat_15", - "hackageNix": "hackageNix_3", - "haskellNix": "haskellNix_10", - "hostNixpkgs": [ - "ogmios-nixos", - "cardano-node", - "nixpkgs" - ], - "iohkNix": "iohkNix_10", - "nixTools": "nixTools_3", - "nixpkgs": [ - "ogmios-nixos", - "cardano-node", - "haskellNix", - "nixpkgs-unstable" - ], - "node-measured": [ - "ogmios-nixos", - "blank" - ], - "node-process": "node-process_3", - "node-snapshot": "node-snapshot_3", - "plutus-apps": "plutus-apps_4", - "utils": "utils_14" - }, - "locked": { - "lastModified": 1659625017, - "narHash": "sha256-4IrheFeoWfvkZQndEk4fGUkOiOjcVhcyXZ6IqmvkDgg=", - "owner": "input-output-hk", - "repo": "cardano-node", - "rev": "950c4e222086fed5ca53564e642434ce9307b0b9", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "ref": "1.35.3", - "repo": "cardano-node", - "type": "github" - } - }, "cardano-prelude": { "flake": false, "locked": { @@ -2046,86 +1523,6 @@ "type": "github" } }, - "cardano-shell_14": { - "flake": false, - "locked": { - "lastModified": 1608537748, - "narHash": "sha256-PulY1GfiMgKVnBci3ex4ptk2UNYMXqGjJOxcPy2KYT4=", - "owner": "input-output-hk", - "repo": "cardano-shell", - "rev": "9392c75087cb9a3d453998f4230930dea3a95725", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-shell", - "type": "github" - } - }, - "cardano-shell_15": { - "flake": false, - "locked": { - "lastModified": 1608537748, - "narHash": "sha256-PulY1GfiMgKVnBci3ex4ptk2UNYMXqGjJOxcPy2KYT4=", - "owner": "input-output-hk", - "repo": "cardano-shell", - "rev": "9392c75087cb9a3d453998f4230930dea3a95725", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-shell", - "type": "github" - } - }, - "cardano-shell_16": { - "flake": false, - "locked": { - "lastModified": 1608537748, - "narHash": "sha256-PulY1GfiMgKVnBci3ex4ptk2UNYMXqGjJOxcPy2KYT4=", - "owner": "input-output-hk", - "repo": "cardano-shell", - "rev": "9392c75087cb9a3d453998f4230930dea3a95725", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-shell", - "type": "github" - } - }, - "cardano-shell_17": { - "flake": false, - "locked": { - "lastModified": 1608537748, - "narHash": "sha256-PulY1GfiMgKVnBci3ex4ptk2UNYMXqGjJOxcPy2KYT4=", - "owner": "input-output-hk", - "repo": "cardano-shell", - "rev": "9392c75087cb9a3d453998f4230930dea3a95725", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-shell", - "type": "github" - } - }, - "cardano-shell_18": { - "flake": false, - "locked": { - "lastModified": 1608537748, - "narHash": "sha256-PulY1GfiMgKVnBci3ex4ptk2UNYMXqGjJOxcPy2KYT4=", - "owner": "input-output-hk", - "repo": "cardano-shell", - "rev": "9392c75087cb9a3d453998f4230930dea3a95725", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-shell", - "type": "github" - } - }, "cardano-shell_2": { "flake": false, "locked": { @@ -2303,66 +1700,6 @@ "type": "github" } }, - "customConfig_10": { - "locked": { - "lastModified": 1630400035, - "narHash": "sha256-MWaVOCzuFwp09wZIW9iHq5wWen5C69I940N1swZLEQ0=", - "owner": "input-output-hk", - "repo": "empty-flake", - "rev": "2040a05b67bf9a669ce17eca56beb14b4206a99a", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "empty-flake", - "type": "github" - } - }, - "customConfig_11": { - "locked": { - "lastModified": 1630400035, - "narHash": "sha256-MWaVOCzuFwp09wZIW9iHq5wWen5C69I940N1swZLEQ0=", - "owner": "input-output-hk", - "repo": "empty-flake", - "rev": "2040a05b67bf9a669ce17eca56beb14b4206a99a", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "empty-flake", - "type": "github" - } - }, - "customConfig_12": { - "locked": { - "lastModified": 1630400035, - "narHash": "sha256-MWaVOCzuFwp09wZIW9iHq5wWen5C69I940N1swZLEQ0=", - "owner": "input-output-hk", - "repo": "empty-flake", - "rev": "2040a05b67bf9a669ce17eca56beb14b4206a99a", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "empty-flake", - "type": "github" - } - }, - "customConfig_13": { - "locked": { - "lastModified": 1630400035, - "narHash": "sha256-MWaVOCzuFwp09wZIW9iHq5wWen5C69I940N1swZLEQ0=", - "owner": "input-output-hk", - "repo": "empty-flake", - "rev": "2040a05b67bf9a669ce17eca56beb14b4206a99a", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "empty-flake", - "type": "github" - } - }, "customConfig_2": { "locked": { "lastModified": 1630400035, @@ -2515,39 +1852,6 @@ } }, "devshell_2": { - "inputs": { - "flake-utils": [ - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "std", - "flake-utils" - ], - "nixpkgs": [ - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "std", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1663445644, - "narHash": "sha256-+xVlcK60x7VY1vRJbNUEAHi17ZuoQxAIH4S4iUFUGBA=", - "owner": "numtide", - "repo": "devshell", - "rev": "e3dc3e21594fe07bdb24bdf1c8657acaa4cb8f66", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "devshell", - "type": "github" - } - }, - "devshell_3": { "inputs": { "flake-utils": [ "ogmios-nixos", @@ -2610,39 +1914,6 @@ } }, "dmerge_2": { - "inputs": { - "nixlib": [ - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "std", - "nixpkgs" - ], - "yants": [ - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "std", - "yants" - ] - }, - "locked": { - "lastModified": 1659548052, - "narHash": "sha256-fzI2gp1skGA8mQo/FBFrUAtY0GQkAIAaV/V127TJPyY=", - "owner": "divnix", - "repo": "data-merge", - "rev": "d160d18ce7b1a45b88344aa3f13ed1163954b497", - "type": "github" - }, - "original": { - "owner": "divnix", - "repo": "data-merge", - "type": "github" - } - }, - "dmerge_3": { "inputs": { "nixlib": [ "ogmios-nixos", @@ -2819,16 +2090,15 @@ "flake-compat_11": { "flake": false, "locked": { - "lastModified": 1647532380, - "narHash": "sha256-wswAxyO8AJTH7d5oU8VK82yBCpqwA+p6kLgpb1f1PAY=", + "lastModified": 1635892615, + "narHash": "sha256-harGbMZr4hzat2BWBU+Y5OYXlu+fVz7E4WeQzHi5o8A=", "owner": "input-output-hk", "repo": "flake-compat", - "rev": "7da118186435255a30b5ffeabba9629c344c0bec", + "rev": "eca47d3377946315596da653862d341ee5341318", "type": "github" }, "original": { "owner": "input-output-hk", - "ref": "fixes", "repo": "flake-compat", "type": "github" } @@ -2852,27 +2122,27 @@ "flake-compat_13": { "flake": false, "locked": { - "lastModified": 1635892615, - "narHash": "sha256-harGbMZr4hzat2BWBU+Y5OYXlu+fVz7E4WeQzHi5o8A=", - "owner": "input-output-hk", + "lastModified": 1650374568, + "narHash": "sha256-Z+s0J8/r907g149rllvwhb4pKi8Wam5ij0st8PwAh+E=", + "owner": "edolstra", "repo": "flake-compat", - "rev": "eca47d3377946315596da653862d341ee5341318", + "rev": "b4a34015c698c7793d592d66adbab377907a2be8", "type": "github" }, "original": { - "owner": "input-output-hk", + "owner": "edolstra", "repo": "flake-compat", "type": "github" } }, - "flake-compat_14": { + "flake-compat_2": { "flake": false, "locked": { - "lastModified": 1650374568, - "narHash": "sha256-Z+s0J8/r907g149rllvwhb4pKi8Wam5ij0st8PwAh+E=", + "lastModified": 1641205782, + "narHash": "sha256-4jY7RCWUoZ9cKD8co0/4tFARpWB+57+r1bLLvXNJliY=", "owner": "edolstra", "repo": "flake-compat", - "rev": "b4a34015c698c7793d592d66adbab377907a2be8", + "rev": "b7547d3eed6f32d06102ead8991ec52ab0a4f1a7", "type": "github" }, "original": { @@ -2881,120 +2151,23 @@ "type": "github" } }, - "flake-compat_15": { + "flake-compat_3": { "flake": false, "locked": { - "lastModified": 1647532380, - "narHash": "sha256-wswAxyO8AJTH7d5oU8VK82yBCpqwA+p6kLgpb1f1PAY=", + "lastModified": 1635892615, + "narHash": "sha256-harGbMZr4hzat2BWBU+Y5OYXlu+fVz7E4WeQzHi5o8A=", "owner": "input-output-hk", "repo": "flake-compat", - "rev": "7da118186435255a30b5ffeabba9629c344c0bec", + "rev": "eca47d3377946315596da653862d341ee5341318", "type": "github" }, "original": { "owner": "input-output-hk", - "ref": "fixes", "repo": "flake-compat", "type": "github" } }, - "flake-compat_16": { - "flake": false, - "locked": { - "lastModified": 1650374568, - "narHash": "sha256-Z+s0J8/r907g149rllvwhb4pKi8Wam5ij0st8PwAh+E=", - "owner": "edolstra", - "repo": "flake-compat", - "rev": "b4a34015c698c7793d592d66adbab377907a2be8", - "type": "github" - }, - "original": { - "owner": "edolstra", - "repo": "flake-compat", - "type": "github" - } - }, - "flake-compat_17": { - "flake": false, - "locked": { - "lastModified": 1635892615, - "narHash": "sha256-harGbMZr4hzat2BWBU+Y5OYXlu+fVz7E4WeQzHi5o8A=", - "owner": "input-output-hk", - "repo": "flake-compat", - "rev": "eca47d3377946315596da653862d341ee5341318", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "flake-compat", - "type": "github" - } - }, - "flake-compat_18": { - "flake": false, - "locked": { - "lastModified": 1650374568, - "narHash": "sha256-Z+s0J8/r907g149rllvwhb4pKi8Wam5ij0st8PwAh+E=", - "owner": "edolstra", - "repo": "flake-compat", - "rev": "b4a34015c698c7793d592d66adbab377907a2be8", - "type": "github" - }, - "original": { - "owner": "edolstra", - "repo": "flake-compat", - "type": "github" - } - }, - "flake-compat_19": { - "flake": false, - "locked": { - "lastModified": 1650374568, - "narHash": "sha256-Z+s0J8/r907g149rllvwhb4pKi8Wam5ij0st8PwAh+E=", - "owner": "edolstra", - "repo": "flake-compat", - "rev": "b4a34015c698c7793d592d66adbab377907a2be8", - "type": "github" - }, - "original": { - "owner": "edolstra", - "repo": "flake-compat", - "type": "github" - } - }, - "flake-compat_2": { - "flake": false, - "locked": { - "lastModified": 1641205782, - "narHash": "sha256-4jY7RCWUoZ9cKD8co0/4tFARpWB+57+r1bLLvXNJliY=", - "owner": "edolstra", - "repo": "flake-compat", - "rev": "b7547d3eed6f32d06102ead8991ec52ab0a4f1a7", - "type": "github" - }, - "original": { - "owner": "edolstra", - "repo": "flake-compat", - "type": "github" - } - }, - "flake-compat_3": { - "flake": false, - "locked": { - "lastModified": 1635892615, - "narHash": "sha256-harGbMZr4hzat2BWBU+Y5OYXlu+fVz7E4WeQzHi5o8A=", - "owner": "input-output-hk", - "repo": "flake-compat", - "rev": "eca47d3377946315596da653862d341ee5341318", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "flake-compat", - "type": "github" - } - }, - "flake-compat_4": { + "flake-compat_4": { "flake": false, "locked": { "lastModified": 1650374568, @@ -3078,15 +2251,16 @@ "flake-compat_9": { "flake": false, "locked": { - "lastModified": 1650374568, - "narHash": "sha256-Z+s0J8/r907g149rllvwhb4pKi8Wam5ij0st8PwAh+E=", - "owner": "edolstra", + "lastModified": 1647532380, + "narHash": "sha256-wswAxyO8AJTH7d5oU8VK82yBCpqwA+p6kLgpb1f1PAY=", + "owner": "input-output-hk", "repo": "flake-compat", - "rev": "b4a34015c698c7793d592d66adbab377907a2be8", + "rev": "7da118186435255a30b5ffeabba9629c344c0bec", "type": "github" }, "original": { - "owner": "edolstra", + "owner": "input-output-hk", + "ref": "fixes", "repo": "flake-compat", "type": "github" } @@ -3364,81 +2538,6 @@ "type": "github" } }, - "flake-utils_25": { - "locked": { - "lastModified": 1644229661, - "narHash": "sha256-1YdnJAsNy69bpcjuoKdOYQX0YxZBiCYZo4Twxerqv7k=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "3cecb5b042f7f209c56ffd8371b2711a290ec797", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "flake-utils_26": { - "locked": { - "lastModified": 1623875721, - "narHash": "sha256-A8BU7bjS5GirpAUv4QA+QnJ4CceLHkcXdRp4xITDB0s=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "f7e004a55b120c02ecb6219596820fcd32ca8772", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "flake-utils_27": { - "locked": { - "lastModified": 1623875721, - "narHash": "sha256-A8BU7bjS5GirpAUv4QA+QnJ4CceLHkcXdRp4xITDB0s=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "f7e004a55b120c02ecb6219596820fcd32ca8772", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "flake-utils_28": { - "locked": { - "lastModified": 1623875721, - "narHash": "sha256-A8BU7bjS5GirpAUv4QA+QnJ4CceLHkcXdRp4xITDB0s=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "f7e004a55b120c02ecb6219596820fcd32ca8772", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "flake-utils_29": { - "locked": { - "lastModified": 1644229661, - "narHash": "sha256-1YdnJAsNy69bpcjuoKdOYQX0YxZBiCYZo4Twxerqv7k=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "3cecb5b042f7f209c56ffd8371b2711a290ec797", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, "flake-utils_3": { "locked": { "lastModified": 1619345332, @@ -3454,51 +2553,6 @@ "type": "github" } }, - "flake-utils_30": { - "locked": { - "lastModified": 1653893745, - "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "1ed9fb1935d260de5fe1c2f7ee0ebaae17ed2fa1", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "flake-utils_31": { - "locked": { - "lastModified": 1659877975, - "narHash": "sha256-zllb8aq3YO3h8B/U0/J1WBgAL8EX5yWf5pMj3G0NAmc=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "c0e246b9b83f637f4681389ecabcb2681b4f3af0", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "flake-utils_32": { - "locked": { - "lastModified": 1653893745, - "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "1ed9fb1935d260de5fe1c2f7ee0ebaae17ed2fa1", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, "flake-utils_4": { "locked": { "lastModified": 1652776076, @@ -3692,7 +2746,7 @@ "type": "github" } }, - "ghc-8.6.5-iohk_14": { + "ghc-8.6.5-iohk_2": { "flake": false, "locked": { "lastModified": 1600920045, @@ -3709,7 +2763,7 @@ "type": "github" } }, - "ghc-8.6.5-iohk_15": { + "ghc-8.6.5-iohk_3": { "flake": false, "locked": { "lastModified": 1600920045, @@ -3726,7 +2780,7 @@ "type": "github" } }, - "ghc-8.6.5-iohk_16": { + "ghc-8.6.5-iohk_4": { "flake": false, "locked": { "lastModified": 1600920045, @@ -3743,7 +2797,7 @@ "type": "github" } }, - "ghc-8.6.5-iohk_17": { + "ghc-8.6.5-iohk_5": { "flake": false, "locked": { "lastModified": 1600920045, @@ -3760,7 +2814,7 @@ "type": "github" } }, - "ghc-8.6.5-iohk_18": { + "ghc-8.6.5-iohk_6": { "flake": false, "locked": { "lastModified": 1600920045, @@ -3777,7 +2831,7 @@ "type": "github" } }, - "ghc-8.6.5-iohk_2": { + "ghc-8.6.5-iohk_7": { "flake": false, "locked": { "lastModified": 1600920045, @@ -3794,7 +2848,7 @@ "type": "github" } }, - "ghc-8.6.5-iohk_3": { + "ghc-8.6.5-iohk_8": { "flake": false, "locked": { "lastModified": 1600920045, @@ -3811,7 +2865,7 @@ "type": "github" } }, - "ghc-8.6.5-iohk_4": { + "ghc-8.6.5-iohk_9": { "flake": false, "locked": { "lastModified": 1600920045, @@ -3828,112 +2882,27 @@ "type": "github" } }, - "ghc-8.6.5-iohk_5": { + "goblins": { "flake": false, "locked": { - "lastModified": 1600920045, - "narHash": "sha256-DO6kxJz248djebZLpSzTGD6s8WRpNI9BTwUeOf5RwY8=", + "lastModified": 1598362523, + "narHash": "sha256-z9ut0y6umDIjJIRjz9KSvKgotuw06/S8QDwOtVdGiJ0=", "owner": "input-output-hk", - "repo": "ghc", - "rev": "95713a6ecce4551240da7c96b6176f980af75cae", + "repo": "goblins", + "rev": "cde90a2b27f79187ca8310b6549331e59595e7ba", "type": "github" }, "original": { "owner": "input-output-hk", - "ref": "release/8.6.5-iohk", - "repo": "ghc", + "repo": "goblins", + "rev": "cde90a2b27f79187ca8310b6549331e59595e7ba", "type": "github" } }, - "ghc-8.6.5-iohk_6": { - "flake": false, - "locked": { - "lastModified": 1600920045, - "narHash": "sha256-DO6kxJz248djebZLpSzTGD6s8WRpNI9BTwUeOf5RwY8=", - "owner": "input-output-hk", - "repo": "ghc", - "rev": "95713a6ecce4551240da7c96b6176f980af75cae", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "ref": "release/8.6.5-iohk", - "repo": "ghc", - "type": "github" - } - }, - "ghc-8.6.5-iohk_7": { - "flake": false, - "locked": { - "lastModified": 1600920045, - "narHash": "sha256-DO6kxJz248djebZLpSzTGD6s8WRpNI9BTwUeOf5RwY8=", - "owner": "input-output-hk", - "repo": "ghc", - "rev": "95713a6ecce4551240da7c96b6176f980af75cae", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "ref": "release/8.6.5-iohk", - "repo": "ghc", - "type": "github" - } - }, - "ghc-8.6.5-iohk_8": { - "flake": false, - "locked": { - "lastModified": 1600920045, - "narHash": "sha256-DO6kxJz248djebZLpSzTGD6s8WRpNI9BTwUeOf5RwY8=", - "owner": "input-output-hk", - "repo": "ghc", - "rev": "95713a6ecce4551240da7c96b6176f980af75cae", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "ref": "release/8.6.5-iohk", - "repo": "ghc", - "type": "github" - } - }, - "ghc-8.6.5-iohk_9": { - "flake": false, - "locked": { - "lastModified": 1600920045, - "narHash": "sha256-DO6kxJz248djebZLpSzTGD6s8WRpNI9BTwUeOf5RwY8=", - "owner": "input-output-hk", - "repo": "ghc", - "rev": "95713a6ecce4551240da7c96b6176f980af75cae", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "ref": "release/8.6.5-iohk", - "repo": "ghc", - "type": "github" - } - }, - "goblins": { - "flake": false, - "locked": { - "lastModified": 1598362523, - "narHash": "sha256-z9ut0y6umDIjJIRjz9KSvKgotuw06/S8QDwOtVdGiJ0=", - "owner": "input-output-hk", - "repo": "goblins", - "rev": "cde90a2b27f79187ca8310b6549331e59595e7ba", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "goblins", - "rev": "cde90a2b27f79187ca8310b6549331e59595e7ba", - "type": "github" - } - }, - "gomod2nix": { - "inputs": { - "nixpkgs": "nixpkgs_15", - "utils": "utils_5" + "gomod2nix": { + "inputs": { + "nixpkgs": "nixpkgs_15", + "utils": "utils_5" }, "locked": { "lastModified": 1655245309, @@ -3951,7 +2920,7 @@ }, "gomod2nix_2": { "inputs": { - "nixpkgs": "nixpkgs_25", + "nixpkgs": "nixpkgs_23", "utils": "utils_10" }, "locked": { @@ -3968,25 +2937,6 @@ "type": "github" } }, - "gomod2nix_3": { - "inputs": { - "nixpkgs": "nixpkgs_33", - "utils": "utils_15" - }, - "locked": { - "lastModified": 1655245309, - "narHash": "sha256-d/YPoQ/vFn1+GTmSdvbSBSTOai61FONxB4+Lt6w/IVI=", - "owner": "tweag", - "repo": "gomod2nix", - "rev": "40d32f82fc60d66402eb0972e6e368aeab3faf58", - "type": "github" - }, - "original": { - "owner": "tweag", - "repo": "gomod2nix", - "type": "github" - } - }, "hackage": { "flake": false, "locked": { @@ -4035,22 +2985,6 @@ "type": "github" } }, - "hackageNix_3": { - "flake": false, - "locked": { - "lastModified": 1656898050, - "narHash": "sha256-jemAb/Wm/uT+QhV12GlyeA5euSWxYzr2HOYoK4MZps0=", - "owner": "input-output-hk", - "repo": "hackage.nix", - "rev": "4f1dd530219ca1165f523ffb2c62213ebede4046", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "hackage.nix", - "type": "github" - } - }, "hackage_10": { "flake": false, "locked": { @@ -4083,70 +3017,6 @@ "type": "github" } }, - "hackage_12": { - "flake": false, - "locked": { - "lastModified": 1643073363, - "narHash": "sha256-66oSXQKEDIOSQ2uKAS9facCX/Zuh/jFgyFDtxEqN9sk=", - "owner": "input-output-hk", - "repo": "hackage.nix", - "rev": "4ef9bd3a32316ce236164c7ebff00ebeb33236e2", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "hackage.nix", - "type": "github" - } - }, - "hackage_13": { - "flake": false, - "locked": { - "lastModified": 1643073363, - "narHash": "sha256-66oSXQKEDIOSQ2uKAS9facCX/Zuh/jFgyFDtxEqN9sk=", - "owner": "input-output-hk", - "repo": "hackage.nix", - "rev": "4ef9bd3a32316ce236164c7ebff00ebeb33236e2", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "hackage.nix", - "type": "github" - } - }, - "hackage_14": { - "flake": false, - "locked": { - "lastModified": 1639098768, - "narHash": "sha256-DZ4sG8FeDxWvBLixrj0jELXjtebZ0SCCPmQW43HNzIE=", - "owner": "input-output-hk", - "repo": "hackage.nix", - "rev": "c7b123af6b0b9b364cab03363504d42dca16a4b5", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "hackage.nix", - "type": "github" - } - }, - "hackage_15": { - "flake": false, - "locked": { - "lastModified": 1667783503, - "narHash": "sha256-25ZZPMQi9YQbXz3tZYPECVUI0FAQkJcDUIA/v8+mo9E=", - "owner": "input-output-hk", - "repo": "hackage.nix", - "rev": "1f77f69e6dd92b5130cbe681b74e8fc0d29d63ff", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "hackage.nix", - "type": "github" - } - }, "hackage_2": { "flake": false, "locked": { @@ -4416,15 +3286,14 @@ "cabal-34": "cabal-34_13", "cabal-36": "cabal-36_11", "cardano-shell": "cardano-shell_13", - "flake-compat": "flake-compat_13", + "flake-compat": "flake-compat_11", "flake-utils": "flake-utils_21", "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_13", "hackage": "hackage_11", "hpc-coveralls": "hpc-coveralls_13", "hydra": "hydra_7", "nixpkgs": [ - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "nixpkgs" ], "nixpkgs-2003": "nixpkgs-2003_13", @@ -4450,46 +3319,6 @@ "type": "github" } }, - "haskell-nix_5": { - "inputs": { - "HTTP": "HTTP_18", - "cabal-32": "cabal-32_18", - "cabal-34": "cabal-34_18", - "cabal-36": "cabal-36_15", - "cardano-shell": "cardano-shell_18", - "flake-compat": "flake-compat_17", - "flake-utils": "flake-utils_29", - "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_18", - "hackage": "hackage_15", - "hpc-coveralls": "hpc-coveralls_18", - "hydra": "hydra_9", - "nixpkgs": [ - "ogmios-nixos", - "nixpkgs" - ], - "nixpkgs-2003": "nixpkgs-2003_18", - "nixpkgs-2105": "nixpkgs-2105_18", - "nixpkgs-2111": "nixpkgs-2111_18", - "nixpkgs-2205": "nixpkgs-2205_3", - "nixpkgs-unstable": "nixpkgs-unstable_18", - "old-ghc-nix": "old-ghc-nix_18", - "stackage": "stackage_18", - "tullia": "tullia_3" - }, - "locked": { - "lastModified": 1667783630, - "narHash": "sha256-IzbvNxsOVxHJGY70qAzaEOPmz4Fw93+4qLFd2on/ZAc=", - "owner": "input-output-hk", - "repo": "haskell.nix", - "rev": "f1f330065199dc4eca017bc21de0c67bc46df393", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "haskell.nix", - "type": "github" - } - }, "haskellNix": { "inputs": { "HTTP": "HTTP_2", @@ -4528,34 +3357,34 @@ "type": "github" } }, - "haskellNix_10": { + "haskellNix_2": { "inputs": { - "HTTP": "HTTP_14", - "cabal-32": "cabal-32_14", - "cabal-34": "cabal-34_14", - "cabal-36": "cabal-36_12", - "cardano-shell": "cardano-shell_14", - "flake-utils": "flake-utils_25", - "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_14", + "HTTP": "HTTP_4", + "cabal-32": "cabal-32_4", + "cabal-34": "cabal-34_4", + "cabal-36": "cabal-36_4", + "cardano-shell": "cardano-shell_4", + "flake-utils": "flake-utils_9", + "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_4", "hackage": [ - "ogmios-nixos", + "ogmios", "cardano-node", "hackageNix" ], - "hpc-coveralls": "hpc-coveralls_14", - "hydra": "hydra_8", - "nix-tools": "nix-tools_12", + "hpc-coveralls": "hpc-coveralls_4", + "hydra": "hydra_4", + "nix-tools": "nix-tools_4", "nixpkgs": [ - "ogmios-nixos", + "ogmios", "cardano-node", "nixpkgs" ], - "nixpkgs-2003": "nixpkgs-2003_14", - "nixpkgs-2105": "nixpkgs-2105_14", - "nixpkgs-2111": "nixpkgs-2111_14", - "nixpkgs-unstable": "nixpkgs-unstable_14", - "old-ghc-nix": "old-ghc-nix_14", - "stackage": "stackage_14" + "nixpkgs-2003": "nixpkgs-2003_4", + "nixpkgs-2105": "nixpkgs-2105_4", + "nixpkgs-2111": "nixpkgs-2111_4", + "nixpkgs-unstable": "nixpkgs-unstable_4", + "old-ghc-nix": "old-ghc-nix_4", + "stackage": "stackage_4" }, "locked": { "lastModified": 1656898207, @@ -4571,30 +3400,30 @@ "type": "github" } }, - "haskellNix_11": { + "haskellNix_3": { "inputs": { - "HTTP": "HTTP_15", - "cabal-32": "cabal-32_15", - "cabal-34": "cabal-34_15", - "cabal-36": "cabal-36_13", - "cardano-shell": "cardano-shell_15", - "flake-utils": "flake-utils_26", - "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_15", - "hackage": "hackage_12", - "hpc-coveralls": "hpc-coveralls_15", - "nix-tools": "nix-tools_13", + "HTTP": "HTTP_5", + "cabal-32": "cabal-32_5", + "cabal-34": "cabal-34_5", + "cabal-36": "cabal-36_5", + "cardano-shell": "cardano-shell_5", + "flake-utils": "flake-utils_10", + "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_5", + "hackage": "hackage_4", + "hpc-coveralls": "hpc-coveralls_5", + "nix-tools": "nix-tools_5", "nixpkgs": [ - "ogmios-nixos", + "ogmios", "cardano-node", "node-snapshot", "nixpkgs" ], - "nixpkgs-2003": "nixpkgs-2003_15", - "nixpkgs-2105": "nixpkgs-2105_15", - "nixpkgs-2111": "nixpkgs-2111_15", - "nixpkgs-unstable": "nixpkgs-unstable_15", - "old-ghc-nix": "old-ghc-nix_15", - "stackage": "stackage_15" + "nixpkgs-2003": "nixpkgs-2003_5", + "nixpkgs-2105": "nixpkgs-2105_5", + "nixpkgs-2111": "nixpkgs-2111_5", + "nixpkgs-unstable": "nixpkgs-unstable_5", + "old-ghc-nix": "old-ghc-nix_5", + "stackage": "stackage_5" }, "locked": { "lastModified": 1643073543, @@ -4610,32 +3439,32 @@ "type": "github" } }, - "haskellNix_12": { + "haskellNix_4": { "inputs": { - "HTTP": "HTTP_16", - "cabal-32": "cabal-32_16", - "cabal-34": "cabal-34_16", - "cabal-36": "cabal-36_14", - "cardano-shell": "cardano-shell_16", - "flake-utils": "flake-utils_27", - "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_16", - "hackage": "hackage_13", - "hpc-coveralls": "hpc-coveralls_16", - "nix-tools": "nix-tools_14", + "HTTP": "HTTP_6", + "cabal-32": "cabal-32_6", + "cabal-34": "cabal-34_6", + "cabal-36": "cabal-36_6", + "cardano-shell": "cardano-shell_6", + "flake-utils": "flake-utils_11", + "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_6", + "hackage": "hackage_5", + "hpc-coveralls": "hpc-coveralls_6", + "nix-tools": "nix-tools_6", "nixpkgs": [ - "ogmios-nixos", + "ogmios", "cardano-node", "node-snapshot", "membench", "cardano-node-snapshot", "nixpkgs" ], - "nixpkgs-2003": "nixpkgs-2003_16", - "nixpkgs-2105": "nixpkgs-2105_16", - "nixpkgs-2111": "nixpkgs-2111_16", - "nixpkgs-unstable": "nixpkgs-unstable_16", - "old-ghc-nix": "old-ghc-nix_16", - "stackage": "stackage_16" + "nixpkgs-2003": "nixpkgs-2003_6", + "nixpkgs-2105": "nixpkgs-2105_6", + "nixpkgs-2111": "nixpkgs-2111_6", + "nixpkgs-unstable": "nixpkgs-unstable_6", + "old-ghc-nix": "old-ghc-nix_6", + "stackage": "stackage_6" }, "locked": { "lastModified": 1643073543, @@ -4651,169 +3480,7 @@ "type": "github" } }, - "haskellNix_13": { - "inputs": { - "HTTP": "HTTP_17", - "cabal-32": "cabal-32_17", - "cabal-34": "cabal-34_17", - "cardano-shell": "cardano-shell_17", - "flake-utils": "flake-utils_28", - "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_17", - "hackage": "hackage_14", - "hpc-coveralls": "hpc-coveralls_17", - "nix-tools": "nix-tools_15", - "nixpkgs": [ - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "plutus-example", - "nixpkgs" - ], - "nixpkgs-2003": "nixpkgs-2003_17", - "nixpkgs-2105": "nixpkgs-2105_17", - "nixpkgs-2111": "nixpkgs-2111_17", - "nixpkgs-unstable": "nixpkgs-unstable_17", - "old-ghc-nix": "old-ghc-nix_17", - "stackage": "stackage_17" - }, - "locked": { - "lastModified": 1639098904, - "narHash": "sha256-7VrCNEaKGLm4pTOS11dt1dRL2033oqrNCfal0uONsqA=", - "owner": "input-output-hk", - "repo": "haskell.nix", - "rev": "b18c6ce0867fee77f12ecf41dc6c67f7a59d9826", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "haskell.nix", - "type": "github" - } - }, - "haskellNix_2": { - "inputs": { - "HTTP": "HTTP_4", - "cabal-32": "cabal-32_4", - "cabal-34": "cabal-34_4", - "cabal-36": "cabal-36_4", - "cardano-shell": "cardano-shell_4", - "flake-utils": "flake-utils_9", - "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_4", - "hackage": [ - "ogmios", - "cardano-node", - "hackageNix" - ], - "hpc-coveralls": "hpc-coveralls_4", - "hydra": "hydra_4", - "nix-tools": "nix-tools_4", - "nixpkgs": [ - "ogmios", - "cardano-node", - "nixpkgs" - ], - "nixpkgs-2003": "nixpkgs-2003_4", - "nixpkgs-2105": "nixpkgs-2105_4", - "nixpkgs-2111": "nixpkgs-2111_4", - "nixpkgs-unstable": "nixpkgs-unstable_4", - "old-ghc-nix": "old-ghc-nix_4", - "stackage": "stackage_4" - }, - "locked": { - "lastModified": 1656898207, - "narHash": "sha256-hshNfCnrmhIvM4T+O0/JRZymsHmq9YiIJ4bpzNVTD98=", - "owner": "input-output-hk", - "repo": "haskell.nix", - "rev": "21230476adfef5fa77fb19fbda396f22006a02bc", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "haskell.nix", - "type": "github" - } - }, - "haskellNix_3": { - "inputs": { - "HTTP": "HTTP_5", - "cabal-32": "cabal-32_5", - "cabal-34": "cabal-34_5", - "cabal-36": "cabal-36_5", - "cardano-shell": "cardano-shell_5", - "flake-utils": "flake-utils_10", - "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_5", - "hackage": "hackage_4", - "hpc-coveralls": "hpc-coveralls_5", - "nix-tools": "nix-tools_5", - "nixpkgs": [ - "ogmios", - "cardano-node", - "node-snapshot", - "nixpkgs" - ], - "nixpkgs-2003": "nixpkgs-2003_5", - "nixpkgs-2105": "nixpkgs-2105_5", - "nixpkgs-2111": "nixpkgs-2111_5", - "nixpkgs-unstable": "nixpkgs-unstable_5", - "old-ghc-nix": "old-ghc-nix_5", - "stackage": "stackage_5" - }, - "locked": { - "lastModified": 1643073543, - "narHash": "sha256-g2l/KDWzMRTFRugNVcx3CPZeyA5BNcH9/zDiqFpprB4=", - "owner": "input-output-hk", - "repo": "haskell.nix", - "rev": "14f740c7c8f535581c30b1697018e389680e24cb", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "haskell.nix", - "type": "github" - } - }, - "haskellNix_4": { - "inputs": { - "HTTP": "HTTP_6", - "cabal-32": "cabal-32_6", - "cabal-34": "cabal-34_6", - "cabal-36": "cabal-36_6", - "cardano-shell": "cardano-shell_6", - "flake-utils": "flake-utils_11", - "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_6", - "hackage": "hackage_5", - "hpc-coveralls": "hpc-coveralls_6", - "nix-tools": "nix-tools_6", - "nixpkgs": [ - "ogmios", - "cardano-node", - "node-snapshot", - "membench", - "cardano-node-snapshot", - "nixpkgs" - ], - "nixpkgs-2003": "nixpkgs-2003_6", - "nixpkgs-2105": "nixpkgs-2105_6", - "nixpkgs-2111": "nixpkgs-2111_6", - "nixpkgs-unstable": "nixpkgs-unstable_6", - "old-ghc-nix": "old-ghc-nix_6", - "stackage": "stackage_6" - }, - "locked": { - "lastModified": 1643073543, - "narHash": "sha256-g2l/KDWzMRTFRugNVcx3CPZeyA5BNcH9/zDiqFpprB4=", - "owner": "input-output-hk", - "repo": "haskell.nix", - "rev": "14f740c7c8f535581c30b1697018e389680e24cb", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "haskell.nix", - "type": "github" - } - }, - "haskellNix_5": { + "haskellNix_5": { "inputs": { "HTTP": "HTTP_7", "cabal-32": "cabal-32_7", @@ -4862,8 +3529,7 @@ "flake-utils": "flake-utils_17", "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_9", "hackage": [ - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "hackageNix" ], @@ -4871,8 +3537,7 @@ "hydra": "hydra_6", "nix-tools": "nix-tools_8", "nixpkgs": [ - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "nixpkgs" ], @@ -4910,8 +3575,7 @@ "hpc-coveralls": "hpc-coveralls_10", "nix-tools": "nix-tools_9", "nixpkgs": [ - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "nixpkgs" @@ -4950,8 +3614,7 @@ "hpc-coveralls": "hpc-coveralls_11", "nix-tools": "nix-tools_10", "nixpkgs": [ - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "membench", @@ -4991,8 +3654,7 @@ "hpc-coveralls": "hpc-coveralls_12", "nix-tools": "nix-tools_11", "nixpkgs": [ - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "plutus-example", @@ -5116,86 +3778,6 @@ "type": "github" } }, - "hpc-coveralls_14": { - "flake": false, - "locked": { - "lastModified": 1607498076, - "narHash": "sha256-8uqsEtivphgZWYeUo5RDUhp6bO9j2vaaProQxHBltQk=", - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "rev": "14df0f7d229f4cd2e79f8eabb1a740097fdfa430", - "type": "github" - }, - "original": { - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "type": "github" - } - }, - "hpc-coveralls_15": { - "flake": false, - "locked": { - "lastModified": 1607498076, - "narHash": "sha256-8uqsEtivphgZWYeUo5RDUhp6bO9j2vaaProQxHBltQk=", - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "rev": "14df0f7d229f4cd2e79f8eabb1a740097fdfa430", - "type": "github" - }, - "original": { - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "type": "github" - } - }, - "hpc-coveralls_16": { - "flake": false, - "locked": { - "lastModified": 1607498076, - "narHash": "sha256-8uqsEtivphgZWYeUo5RDUhp6bO9j2vaaProQxHBltQk=", - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "rev": "14df0f7d229f4cd2e79f8eabb1a740097fdfa430", - "type": "github" - }, - "original": { - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "type": "github" - } - }, - "hpc-coveralls_17": { - "flake": false, - "locked": { - "lastModified": 1607498076, - "narHash": "sha256-8uqsEtivphgZWYeUo5RDUhp6bO9j2vaaProQxHBltQk=", - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "rev": "14df0f7d229f4cd2e79f8eabb1a740097fdfa430", - "type": "github" - }, - "original": { - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "type": "github" - } - }, - "hpc-coveralls_18": { - "flake": false, - "locked": { - "lastModified": 1607498076, - "narHash": "sha256-8uqsEtivphgZWYeUo5RDUhp6bO9j2vaaProQxHBltQk=", - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "rev": "14df0f7d229f4cd2e79f8eabb1a740097fdfa430", - "type": "github" - }, - "original": { - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "type": "github" - } - }, "hpc-coveralls_2": { "flake": false, "locked": { @@ -5466,8 +4048,7 @@ "inputs": { "nix": "nix_6", "nixpkgs": [ - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "haskellNix", "hydra", @@ -5492,8 +4073,7 @@ "inputs": { "nix": "nix_7", "nixpkgs": [ - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "haskell-nix", "hydra", "nix", @@ -5513,63 +4093,14 @@ "type": "indirect" } }, - "hydra_8": { - "inputs": { - "nix": "nix_8", - "nixpkgs": [ - "ogmios-nixos", - "cardano-node", - "haskellNix", - "hydra", - "nix", - "nixpkgs" - ] - }, + "hysterical-screams": { + "flake": false, "locked": { - "lastModified": 1646878427, - "narHash": "sha256-KtbrofMtN8GlM7D+n90kixr7QpSlVmdN+vK5CA/aRzc=", - "owner": "NixOS", - "repo": "hydra", - "rev": "28b682b85b7efc5cf7974065792a1f22203a5927", - "type": "github" - }, - "original": { - "id": "hydra", - "type": "indirect" - } - }, - "hydra_9": { - "inputs": { - "nix": "nix_9", - "nixpkgs": [ - "ogmios-nixos", - "haskell-nix", - "hydra", - "nix", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1646878427, - "narHash": "sha256-KtbrofMtN8GlM7D+n90kixr7QpSlVmdN+vK5CA/aRzc=", - "owner": "NixOS", - "repo": "hydra", - "rev": "28b682b85b7efc5cf7974065792a1f22203a5927", - "type": "github" - }, - "original": { - "id": "hydra", - "type": "indirect" - } - }, - "hysterical-screams": { - "flake": false, - "locked": { - "lastModified": 1654007733, - "narHash": "sha256-d4N3rUzg45BUs5Lx/kK7vXYsLMNoO15dlzo7t8lGIXA=", - "owner": "raduom", - "repo": "hysterical-screams", - "rev": "4c523469e9efd3f0d10d17da3304923b7b0e0674", + "lastModified": 1654007733, + "narHash": "sha256-d4N3rUzg45BUs5Lx/kK7vXYsLMNoO15dlzo7t8lGIXA=", + "owner": "raduom", + "repo": "hysterical-screams", + "rev": "4c523469e9efd3f0d10d17da3304923b7b0e0674", "type": "github" }, "original": { @@ -5693,29 +4224,6 @@ } }, "iohk-nix_4": { - "inputs": { - "nixpkgs": [ - "ogmios-datum-cache-nixos", - "ogmios", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1649070135, - "narHash": "sha256-UFKqcOSdPWk3TYUCPHF22p1zf7aXQpCmmgf7UMg7fWA=", - "owner": "input-output-hk", - "repo": "iohk-nix", - "rev": "cecab9c71d1064f05f1615eead56ac0b9196bc20", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "iohk-nix", - "rev": "cecab9c71d1064f05f1615eead56ac0b9196bc20", - "type": "github" - } - }, - "iohk-nix_5": { "inputs": { "nixpkgs": [ "ogmios-nixos", @@ -5758,100 +4266,6 @@ "type": "github" } }, - "iohkNix_10": { - "inputs": { - "nixpkgs": [ - "ogmios-nixos", - "cardano-node", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1653579289, - "narHash": "sha256-wveDdPsgB/3nAGAdFaxrcgLEpdi0aJ5kEVNtI+YqVfo=", - "owner": "input-output-hk", - "repo": "iohk-nix", - "rev": "edb2d2df2ebe42bbdf03a0711115cf6213c9d366", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "iohk-nix", - "type": "github" - } - }, - "iohkNix_11": { - "inputs": { - "nixpkgs": [ - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1631778944, - "narHash": "sha256-N5eCcUYtZ5kUOl/JJGjx6ZzhA3uIn1itDRTiRV+3jLw=", - "owner": "input-output-hk", - "repo": "iohk-nix", - "rev": "db2c75a09c696271194bb3ef25ec8e9839b594b7", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "iohk-nix", - "type": "github" - } - }, - "iohkNix_12": { - "inputs": { - "nixpkgs": [ - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "membench", - "cardano-node-snapshot", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1631778944, - "narHash": "sha256-N5eCcUYtZ5kUOl/JJGjx6ZzhA3uIn1itDRTiRV+3jLw=", - "owner": "input-output-hk", - "repo": "iohk-nix", - "rev": "db2c75a09c696271194bb3ef25ec8e9839b594b7", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "iohk-nix", - "type": "github" - } - }, - "iohkNix_13": { - "inputs": { - "nixpkgs": [ - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "plutus-example", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1633964277, - "narHash": "sha256-7G/BK514WiMRr90EswNBthe8SmH9tjPaTBba/RW/VA8=", - "owner": "input-output-hk", - "repo": "iohk-nix", - "rev": "1e51437aac8a0e49663cb21e781f34163c81ebfb", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "iohk-nix", - "type": "github" - } - }, "iohkNix_2": { "inputs": { "nixpkgs": [ @@ -5949,8 +4363,7 @@ "iohkNix_6": { "inputs": { "nixpkgs": [ - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "nixpkgs" ] @@ -5972,8 +4385,7 @@ "iohkNix_7": { "inputs": { "nixpkgs": [ - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "nixpkgs" @@ -5996,8 +4408,7 @@ "iohkNix_8": { "inputs": { "nixpkgs": [ - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "membench", @@ -6022,8 +4433,7 @@ "iohkNix_9": { "inputs": { "nixpkgs": [ - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "plutus-example", @@ -6202,38 +4612,6 @@ "type": "github" } }, - "lowdown-src_8": { - "flake": false, - "locked": { - "lastModified": 1633514407, - "narHash": "sha256-Dw32tiMjdK9t3ETl5fzGrutQTzh2rufgZV4A/BbxuD4=", - "owner": "kristapsdz", - "repo": "lowdown", - "rev": "d2c2b44ff6c27b936ec27358a2653caaef8f73b8", - "type": "github" - }, - "original": { - "owner": "kristapsdz", - "repo": "lowdown", - "type": "github" - } - }, - "lowdown-src_9": { - "flake": false, - "locked": { - "lastModified": 1633514407, - "narHash": "sha256-Dw32tiMjdK9t3ETl5fzGrutQTzh2rufgZV4A/BbxuD4=", - "owner": "kristapsdz", - "repo": "lowdown", - "rev": "d2c2b44ff6c27b936ec27358a2653caaef8f73b8", - "type": "github" - }, - "original": { - "owner": "kristapsdz", - "repo": "lowdown", - "type": "github" - } - }, "mdbook-kroki-preprocessor": { "flake": false, "locked": { @@ -6266,22 +4644,6 @@ "type": "github" } }, - "mdbook-kroki-preprocessor_3": { - "flake": false, - "locked": { - "lastModified": 1661755005, - "narHash": "sha256-1TJuUzfyMycWlOQH67LR63/ll2GDZz25I3JfScy/Jnw=", - "owner": "JoelCourtney", - "repo": "mdbook-kroki-preprocessor", - "rev": "93adb5716d035829efed27f65f2f0833a7d3e76f", - "type": "github" - }, - "original": { - "owner": "JoelCourtney", - "repo": "mdbook-kroki-preprocessor", - "type": "github" - } - }, "membench": { "inputs": { "cardano-mainnet-mirror": "cardano-mainnet-mirror_2", @@ -6370,21 +4732,18 @@ "inputs": { "cardano-mainnet-mirror": "cardano-mainnet-mirror_5", "cardano-node-measured": [ - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot" ], "cardano-node-process": [ - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot" ], "cardano-node-snapshot": "cardano-node-snapshot_2", "nixpkgs": [ - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "nixpkgs" @@ -6409,32 +4768,28 @@ "inputs": { "cardano-mainnet-mirror": "cardano-mainnet-mirror_6", "cardano-node-measured": [ - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "membench", "cardano-node-snapshot" ], "cardano-node-process": [ - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "membench", "cardano-node-snapshot" ], "cardano-node-snapshot": [ - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "membench", "cardano-node-snapshot" ], "nixpkgs": [ - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "membench", @@ -6457,145 +4812,35 @@ "type": "github" } }, - "membench_5": { + "n2c": { "inputs": { - "cardano-mainnet-mirror": "cardano-mainnet-mirror_8", - "cardano-node-measured": [ - "ogmios-nixos", - "cardano-node", - "node-snapshot" - ], - "cardano-node-process": [ - "ogmios-nixos", - "cardano-node", - "node-snapshot" - ], - "cardano-node-snapshot": "cardano-node-snapshot_3", + "flake-utils": "flake-utils_16", "nixpkgs": [ - "ogmios-nixos", - "cardano-node", - "node-snapshot", + "ogmios", + "haskell-nix", + "tullia", + "std", "nixpkgs" - ], - "ouroboros-network": "ouroboros-network_7" + ] }, "locked": { - "lastModified": 1645070579, - "narHash": "sha256-AxL6tCOnzYnE6OquoFzj+X1bLDr1PQx3d8/vXm+rbfA=", - "owner": "input-output-hk", - "repo": "cardano-memory-benchmark", - "rev": "65643e000186de1335e24ec89159db8ba85e1c1a", + "lastModified": 1665039323, + "narHash": "sha256-SAh3ZjFGsaCI8FRzXQyp56qcGdAqgKEfJWPCQ0Sr7tQ=", + "owner": "nlewo", + "repo": "nix2container", + "rev": "b008fe329ffb59b67bf9e7b08ede6ee792f2741a", "type": "github" }, "original": { - "owner": "input-output-hk", - "repo": "cardano-memory-benchmark", + "owner": "nlewo", + "repo": "nix2container", "type": "github" } }, - "membench_6": { + "n2c_2": { "inputs": { - "cardano-mainnet-mirror": "cardano-mainnet-mirror_9", - "cardano-node-measured": [ - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "membench", - "cardano-node-snapshot" - ], - "cardano-node-process": [ - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "membench", - "cardano-node-snapshot" - ], - "cardano-node-snapshot": [ - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "membench", - "cardano-node-snapshot" - ], - "nixpkgs": [ - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "membench", - "cardano-node-snapshot", - "nixpkgs" - ], - "ouroboros-network": "ouroboros-network_6" - }, - "locked": { - "lastModified": 1644547122, - "narHash": "sha256-8nWK+ScMACvRQLbA27gwXNoZver+Wx/cF7V37044koY=", - "owner": "input-output-hk", - "repo": "cardano-memory-benchmark", - "rev": "9d8ff4b9394de0421ee95caa511d01163de88b77", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-memory-benchmark", - "type": "github" - } - }, - "n2c": { - "inputs": { - "flake-utils": "flake-utils_16", - "nixpkgs": [ - "ogmios", - "haskell-nix", - "tullia", - "std", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1665039323, - "narHash": "sha256-SAh3ZjFGsaCI8FRzXQyp56qcGdAqgKEfJWPCQ0Sr7tQ=", - "owner": "nlewo", - "repo": "nix2container", - "rev": "b008fe329ffb59b67bf9e7b08ede6ee792f2741a", - "type": "github" - }, - "original": { - "owner": "nlewo", - "repo": "nix2container", - "type": "github" - } - }, - "n2c_2": { - "inputs": { - "flake-utils": "flake-utils_24", - "nixpkgs": [ - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "std", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1665039323, - "narHash": "sha256-SAh3ZjFGsaCI8FRzXQyp56qcGdAqgKEfJWPCQ0Sr7tQ=", - "owner": "nlewo", - "repo": "nix2container", - "rev": "b008fe329ffb59b67bf9e7b08ede6ee792f2741a", - "type": "github" - }, - "original": { - "owner": "nlewo", - "repo": "nix2container", - "type": "github" - } - }, - "n2c_3": { - "inputs": { - "flake-utils": "flake-utils_32", - "nixpkgs": [ + "flake-utils": "flake-utils_24", + "nixpkgs": [ "ogmios-nixos", "haskell-nix", "tullia", @@ -6678,48 +4923,7 @@ }, "nix-nomad_2": { "inputs": { - "flake-compat": "flake-compat_14", - "flake-utils": [ - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "nix2container", - "flake-utils" - ], - "gomod2nix": "gomod2nix_2", - "nixpkgs": [ - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "nixpkgs" - ], - "nixpkgs-lib": [ - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1658277770, - "narHash": "sha256-T/PgG3wUn8Z2rnzfxf2VqlR1CBjInPE0l1yVzXxPnt0=", - "owner": "tristanpemble", - "repo": "nix-nomad", - "rev": "054adcbdd0a836ae1c20951b67ed549131fd2d70", - "type": "github" - }, - "original": { - "owner": "tristanpemble", - "repo": "nix-nomad", - "type": "github" - } - }, - "nix-nomad_3": { - "inputs": { - "flake-compat": "flake-compat_18", + "flake-compat": "flake-compat_12", "flake-utils": [ "ogmios-nixos", "haskell-nix", @@ -6727,7 +4931,7 @@ "nix2container", "flake-utils" ], - "gomod2nix": "gomod2nix_3", + "gomod2nix": "gomod2nix_2", "nixpkgs": [ "ogmios-nixos", "haskell-nix", @@ -6803,70 +5007,6 @@ "type": "github" } }, - "nix-tools_12": { - "flake": false, - "locked": { - "lastModified": 1649424170, - "narHash": "sha256-XgKXWispvv5RCvZzPb+p7e6Hy3LMuRjafKMl7kXzxGw=", - "owner": "input-output-hk", - "repo": "nix-tools", - "rev": "e109c94016e3b6e0db7ed413c793e2d4bdb24aa7", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "nix-tools", - "type": "github" - } - }, - "nix-tools_13": { - "flake": false, - "locked": { - "lastModified": 1636018067, - "narHash": "sha256-ng306fkuwr6V/malWtt3979iAC4yMVDDH2ViwYB6sQE=", - "owner": "input-output-hk", - "repo": "nix-tools", - "rev": "ed5bd7215292deba55d6ab7a4e8c21f8b1564dda", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "nix-tools", - "type": "github" - } - }, - "nix-tools_14": { - "flake": false, - "locked": { - "lastModified": 1636018067, - "narHash": "sha256-ng306fkuwr6V/malWtt3979iAC4yMVDDH2ViwYB6sQE=", - "owner": "input-output-hk", - "repo": "nix-tools", - "rev": "ed5bd7215292deba55d6ab7a4e8c21f8b1564dda", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "nix-tools", - "type": "github" - } - }, - "nix-tools_15": { - "flake": false, - "locked": { - "lastModified": 1636018067, - "narHash": "sha256-ng306fkuwr6V/malWtt3979iAC4yMVDDH2ViwYB6sQE=", - "owner": "input-output-hk", - "repo": "nix-tools", - "rev": "ed5bd7215292deba55d6ab7a4e8c21f8b1564dda", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "nix-tools", - "type": "github" - } - }, "nix-tools_2": { "flake": false, "locked": { @@ -7017,26 +5157,7 @@ "nix2container_2": { "inputs": { "flake-utils": "flake-utils_22", - "nixpkgs": "nixpkgs_26" - }, - "locked": { - "lastModified": 1658567952, - "narHash": "sha256-XZ4ETYAMU7XcpEeAFP3NOl9yDXNuZAen/aIJ84G+VgA=", - "owner": "nlewo", - "repo": "nix2container", - "rev": "60bb43d405991c1378baf15a40b5811a53e32ffa", - "type": "github" - }, - "original": { - "owner": "nlewo", - "repo": "nix2container", - "type": "github" - } - }, - "nix2container_3": { - "inputs": { - "flake-utils": "flake-utils_30", - "nixpkgs": "nixpkgs_34" + "nixpkgs": "nixpkgs_24" }, "locked": { "lastModified": 1658567952, @@ -7084,22 +5205,6 @@ "type": "github" } }, - "nixTools_3": { - "flake": false, - "locked": { - "lastModified": 1649424170, - "narHash": "sha256-XgKXWispvv5RCvZzPb+p7e6Hy3LMuRjafKMl7kXzxGw=", - "owner": "input-output-hk", - "repo": "nix-tools", - "rev": "e109c94016e3b6e0db7ed413c793e2d4bdb24aa7", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "nix-tools", - "type": "github" - } - }, "nix_2": { "inputs": { "lowdown-src": "lowdown-src_2", @@ -7187,7 +5292,7 @@ "nix_6": { "inputs": { "lowdown-src": "lowdown-src_6", - "nixpkgs": "nixpkgs_21", + "nixpkgs": "nixpkgs_19", "nixpkgs-regression": "nixpkgs-regression_6" }, "locked": { @@ -7208,7 +5313,7 @@ "nix_7": { "inputs": { "lowdown-src": "lowdown-src_7", - "nixpkgs": "nixpkgs_24", + "nixpkgs": "nixpkgs_22", "nixpkgs-regression": "nixpkgs-regression_7" }, "locked": { @@ -7226,48 +5331,6 @@ "type": "github" } }, - "nix_8": { - "inputs": { - "lowdown-src": "lowdown-src_8", - "nixpkgs": "nixpkgs_29", - "nixpkgs-regression": "nixpkgs-regression_8" - }, - "locked": { - "lastModified": 1643066034, - "narHash": "sha256-xEPeMcNJVOeZtoN+d+aRwolpW8mFSEQx76HTRdlhPhg=", - "owner": "NixOS", - "repo": "nix", - "rev": "a1cd7e58606a41fcf62bf8637804cf8306f17f62", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "2.6.0", - "repo": "nix", - "type": "github" - } - }, - "nix_9": { - "inputs": { - "lowdown-src": "lowdown-src_9", - "nixpkgs": "nixpkgs_32", - "nixpkgs-regression": "nixpkgs-regression_9" - }, - "locked": { - "lastModified": 1643066034, - "narHash": "sha256-xEPeMcNJVOeZtoN+d+aRwolpW8mFSEQx76HTRdlhPhg=", - "owner": "NixOS", - "repo": "nix", - "rev": "a1cd7e58606a41fcf62bf8637804cf8306f17f62", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "2.6.0", - "repo": "nix", - "type": "github" - } - }, "nixago": { "inputs": { "flake-utils": [ @@ -7307,47 +5370,6 @@ } }, "nixago_2": { - "inputs": { - "flake-utils": [ - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "std", - "flake-utils" - ], - "nixago-exts": [ - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "std", - "blank" - ], - "nixpkgs": [ - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "std", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1661824785, - "narHash": "sha256-/PnwdWoO/JugJZHtDUioQp3uRiWeXHUdgvoyNbXesz8=", - "owner": "nix-community", - "repo": "nixago", - "rev": "8c1f9e5f1578d4b2ea989f618588d62a335083c3", - "type": "github" - }, - "original": { - "owner": "nix-community", - "repo": "nixago", - "type": "github" - } - }, - "nixago_3": { "inputs": { "flake-utils": [ "ogmios-nixos", @@ -7480,86 +5502,6 @@ "type": "github" } }, - "nixpkgs-2003_14": { - "locked": { - "lastModified": 1620055814, - "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-20.03-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2003_15": { - "locked": { - "lastModified": 1620055814, - "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-20.03-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2003_16": { - "locked": { - "lastModified": 1620055814, - "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-20.03-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2003_17": { - "locked": { - "lastModified": 1620055814, - "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-20.03-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2003_18": { - "locked": { - "lastModified": 1620055814, - "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-20.03-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, "nixpkgs-2003_2": { "locked": { "lastModified": 1620055814, @@ -7592,87 +5534,7 @@ "type": "github" } }, - "nixpkgs-2003_4": { - "locked": { - "lastModified": 1620055814, - "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-20.03-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2003_5": { - "locked": { - "lastModified": 1620055814, - "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-20.03-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2003_6": { - "locked": { - "lastModified": 1620055814, - "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-20.03-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2003_7": { - "locked": { - "lastModified": 1620055814, - "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-20.03-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2003_8": { - "locked": { - "lastModified": 1620055814, - "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-20.03-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2003_9": { + "nixpkgs-2003_4": { "locked": { "lastModified": 1620055814, "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", @@ -7688,87 +5550,87 @@ "type": "github" } }, - "nixpkgs-2105": { + "nixpkgs-2003_5": { "locked": { - "lastModified": 1645296114, - "narHash": "sha256-y53N7TyIkXsjMpOG7RhvqJFGDacLs9HlyHeSTBioqYU=", + "lastModified": 1620055814, + "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "530a53dcbc9437363471167a5e4762c5fcfa34a1", + "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", "type": "github" }, "original": { "owner": "NixOS", - "ref": "nixpkgs-21.05-darwin", + "ref": "nixpkgs-20.03-darwin", "repo": "nixpkgs", "type": "github" } }, - "nixpkgs-2105_10": { + "nixpkgs-2003_6": { "locked": { - "lastModified": 1640283157, - "narHash": "sha256-6Ddfop+rKE+Gl9Tjp9YIrkfoYPzb8F80ergdjcq3/MY=", + "lastModified": 1620055814, + "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "dde1557825c5644c869c5efc7448dc03722a8f09", + "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", "type": "github" }, "original": { "owner": "NixOS", - "ref": "nixpkgs-21.05-darwin", + "ref": "nixpkgs-20.03-darwin", "repo": "nixpkgs", "type": "github" } }, - "nixpkgs-2105_11": { + "nixpkgs-2003_7": { "locked": { - "lastModified": 1640283157, - "narHash": "sha256-6Ddfop+rKE+Gl9Tjp9YIrkfoYPzb8F80ergdjcq3/MY=", + "lastModified": 1620055814, + "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "dde1557825c5644c869c5efc7448dc03722a8f09", + "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", "type": "github" }, "original": { "owner": "NixOS", - "ref": "nixpkgs-21.05-darwin", + "ref": "nixpkgs-20.03-darwin", "repo": "nixpkgs", "type": "github" } }, - "nixpkgs-2105_12": { + "nixpkgs-2003_8": { "locked": { - "lastModified": 1630481079, - "narHash": "sha256-leWXLchbAbqOlLT6tju631G40SzQWPqaAXQG3zH1Imw=", + "lastModified": 1620055814, + "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "110a2c9ebbf5d4a94486854f18a37a938cfacbbb", + "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", "type": "github" }, "original": { "owner": "NixOS", - "ref": "nixpkgs-21.05-darwin", + "ref": "nixpkgs-20.03-darwin", "repo": "nixpkgs", "type": "github" } }, - "nixpkgs-2105_13": { + "nixpkgs-2003_9": { "locked": { - "lastModified": 1659914493, - "narHash": "sha256-lkA5X3VNMKirvA+SUzvEhfA7XquWLci+CGi505YFAIs=", + "lastModified": 1620055814, + "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "022caabb5f2265ad4006c1fa5b1ebe69fb0c3faf", + "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", "type": "github" }, "original": { "owner": "NixOS", - "ref": "nixpkgs-21.05-darwin", + "ref": "nixpkgs-20.03-darwin", "repo": "nixpkgs", "type": "github" } }, - "nixpkgs-2105_14": { + "nixpkgs-2105": { "locked": { "lastModified": 1645296114, "narHash": "sha256-y53N7TyIkXsjMpOG7RhvqJFGDacLs9HlyHeSTBioqYU=", @@ -7784,7 +5646,7 @@ "type": "github" } }, - "nixpkgs-2105_15": { + "nixpkgs-2105_10": { "locked": { "lastModified": 1640283157, "narHash": "sha256-6Ddfop+rKE+Gl9Tjp9YIrkfoYPzb8F80ergdjcq3/MY=", @@ -7800,7 +5662,7 @@ "type": "github" } }, - "nixpkgs-2105_16": { + "nixpkgs-2105_11": { "locked": { "lastModified": 1640283157, "narHash": "sha256-6Ddfop+rKE+Gl9Tjp9YIrkfoYPzb8F80ergdjcq3/MY=", @@ -7816,7 +5678,7 @@ "type": "github" } }, - "nixpkgs-2105_17": { + "nixpkgs-2105_12": { "locked": { "lastModified": 1630481079, "narHash": "sha256-leWXLchbAbqOlLT6tju631G40SzQWPqaAXQG3zH1Imw=", @@ -7832,7 +5694,7 @@ "type": "github" } }, - "nixpkgs-2105_18": { + "nixpkgs-2105_13": { "locked": { "lastModified": 1659914493, "narHash": "sha256-lkA5X3VNMKirvA+SUzvEhfA7XquWLci+CGi505YFAIs=", @@ -8056,86 +5918,6 @@ "type": "github" } }, - "nixpkgs-2111_14": { - "locked": { - "lastModified": 1648744337, - "narHash": "sha256-bYe1dFJAXovjqiaPKrmAbSBEK5KUkgwVaZcTbSoJ7hg=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "0a58eebd8ec65ffdef2ce9562784123a73922052", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-21.11-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2111_15": { - "locked": { - "lastModified": 1640283207, - "narHash": "sha256-SCwl7ZnCfMDsuSYvwIroiAlk7n33bW8HFfY8NvKhcPA=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "64c7e3388bbd9206e437713351e814366e0c3284", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-21.11-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2111_16": { - "locked": { - "lastModified": 1640283207, - "narHash": "sha256-SCwl7ZnCfMDsuSYvwIroiAlk7n33bW8HFfY8NvKhcPA=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "64c7e3388bbd9206e437713351e814366e0c3284", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-21.11-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2111_17": { - "locked": { - "lastModified": 1638410074, - "narHash": "sha256-MQYI4k4XkoTzpeRjq5wl+1NShsl1CKq8MISFuZ81sWs=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "5b80f23502f8e902612a8c631dfce383e1c56596", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-21.11-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2111_18": { - "locked": { - "lastModified": 1659446231, - "narHash": "sha256-hekabNdTdgR/iLsgce5TGWmfIDZ86qjPhxDg/8TlzhE=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "eabc38219184cc3e04a974fe31857d8e0eac098d", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-21.11-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, "nixpkgs-2111_2": { "locked": { "lastModified": 1648744337, @@ -8296,22 +6078,6 @@ "type": "github" } }, - "nixpkgs-2205_3": { - "locked": { - "lastModified": 1663981975, - "narHash": "sha256-TKaxWAVJR+a5JJauKZqibmaM5e/Pi5tBDx9s8fl/kSE=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "309faedb8338d3ae8ad8f1043b3ccf48c9cc2970", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-22.05-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, "nixpkgs-regression": { "locked": { "lastModified": 1643052045, @@ -8348,186 +6114,76 @@ "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "indirect" - } - }, - "nixpkgs-regression_4": { - "locked": { - "lastModified": 1643052045, - "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "indirect" - } - }, - "nixpkgs-regression_5": { - "locked": { - "lastModified": 1643052045, - "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "indirect" - } - }, - "nixpkgs-regression_6": { - "locked": { - "lastModified": 1643052045, - "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "indirect" - } - }, - "nixpkgs-regression_7": { - "locked": { - "lastModified": 1643052045, - "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "indirect" - } - }, - "nixpkgs-regression_8": { - "locked": { - "lastModified": 1643052045, - "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "indirect" - } - }, - "nixpkgs-regression_9": { - "locked": { - "lastModified": 1643052045, - "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "indirect" - } - }, - "nixpkgs-unstable": { - "locked": { - "lastModified": 1648219316, - "narHash": "sha256-Ctij+dOi0ZZIfX5eMhgwugfvB+WZSrvVNAyAuANOsnQ=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "30d3d79b7d3607d56546dd2a6b49e156ba0ec634", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-unstable", - "repo": "nixpkgs", + "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", "type": "github" + }, + "original": { + "id": "nixpkgs", + "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", + "type": "indirect" } }, - "nixpkgs-unstable_10": { + "nixpkgs-regression_4": { "locked": { - "lastModified": 1641285291, - "narHash": "sha256-KYaOBNGar3XWTxTsYPr9P6u74KAqNq0wobEC236U+0c=", + "lastModified": 1643052045, + "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "0432195a4b8d68faaa7d3d4b355260a3120aeeae", + "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", "type": "github" }, "original": { - "owner": "NixOS", - "ref": "nixpkgs-unstable", - "repo": "nixpkgs", - "type": "github" + "id": "nixpkgs", + "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", + "type": "indirect" } }, - "nixpkgs-unstable_11": { + "nixpkgs-regression_5": { "locked": { - "lastModified": 1641285291, - "narHash": "sha256-KYaOBNGar3XWTxTsYPr9P6u74KAqNq0wobEC236U+0c=", + "lastModified": 1643052045, + "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "0432195a4b8d68faaa7d3d4b355260a3120aeeae", + "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", "type": "github" }, "original": { - "owner": "NixOS", - "ref": "nixpkgs-unstable", - "repo": "nixpkgs", - "type": "github" + "id": "nixpkgs", + "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", + "type": "indirect" } }, - "nixpkgs-unstable_12": { + "nixpkgs-regression_6": { "locked": { - "lastModified": 1635295995, - "narHash": "sha256-sGYiXjFlxTTMNb4NSkgvX+knOOTipE6gqwPUQpxNF+c=", + "lastModified": 1643052045, + "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "22a500a3f87bbce73bd8d777ef920b43a636f018", + "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", "type": "github" }, "original": { - "owner": "NixOS", - "ref": "nixpkgs-unstable", - "repo": "nixpkgs", - "type": "github" + "id": "nixpkgs", + "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", + "type": "indirect" } }, - "nixpkgs-unstable_13": { + "nixpkgs-regression_7": { "locked": { - "lastModified": 1663905476, - "narHash": "sha256-0CSwRKaYravh9v6qSlBpM0gNg0UhKT2lL7Yn6Zbx7UM=", + "lastModified": 1643052045, + "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "e14f9fb57315f0d4abde222364f19f88c77d2b79", + "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", "type": "github" }, "original": { - "owner": "NixOS", - "ref": "nixpkgs-unstable", - "repo": "nixpkgs", - "type": "github" + "id": "nixpkgs", + "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", + "type": "indirect" } }, - "nixpkgs-unstable_14": { + "nixpkgs-unstable": { "locked": { "lastModified": 1648219316, "narHash": "sha256-Ctij+dOi0ZZIfX5eMhgwugfvB+WZSrvVNAyAuANOsnQ=", @@ -8543,7 +6199,7 @@ "type": "github" } }, - "nixpkgs-unstable_15": { + "nixpkgs-unstable_10": { "locked": { "lastModified": 1641285291, "narHash": "sha256-KYaOBNGar3XWTxTsYPr9P6u74KAqNq0wobEC236U+0c=", @@ -8559,7 +6215,7 @@ "type": "github" } }, - "nixpkgs-unstable_16": { + "nixpkgs-unstable_11": { "locked": { "lastModified": 1641285291, "narHash": "sha256-KYaOBNGar3XWTxTsYPr9P6u74KAqNq0wobEC236U+0c=", @@ -8575,7 +6231,7 @@ "type": "github" } }, - "nixpkgs-unstable_17": { + "nixpkgs-unstable_12": { "locked": { "lastModified": 1635295995, "narHash": "sha256-sGYiXjFlxTTMNb4NSkgvX+knOOTipE6gqwPUQpxNF+c=", @@ -8591,7 +6247,7 @@ "type": "github" } }, - "nixpkgs-unstable_18": { + "nixpkgs-unstable_13": { "locked": { "lastModified": 1663905476, "narHash": "sha256-0CSwRKaYravh9v6qSlBpM0gNg0UhKT2lL7Yn6Zbx7UM=", @@ -8856,34 +6512,31 @@ }, "nixpkgs_18": { "locked": { - "lastModified": 1634172192, - "narHash": "sha256-FBF4U/T+bMg4sEyT/zkgasvVquGzgdAf4y8uCosKMmo=", + "lastModified": 1642336556, + "narHash": "sha256-QSPPbFEwy0T0DrIuSzAACkaANPQaR1lZR/nHZGz9z04=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "2cf9db0e3d45b9d00f16f2836cb1297bcadc475e", + "rev": "f3d9d4bd898cca7d04af2ae4f6ef01f2219df3d6", "type": "github" }, "original": { - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "2cf9db0e3d45b9d00f16f2836cb1297bcadc475e", - "type": "github" + "id": "nixpkgs", + "type": "indirect" } }, "nixpkgs_19": { "locked": { - "lastModified": 1634172192, - "narHash": "sha256-FBF4U/T+bMg4sEyT/zkgasvVquGzgdAf4y8uCosKMmo=", + "lastModified": 1632864508, + "narHash": "sha256-d127FIvGR41XbVRDPVvozUPQ/uRHbHwvfyKHwEt5xFM=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "2cf9db0e3d45b9d00f16f2836cb1297bcadc475e", + "rev": "82891b5e2c2359d7e58d08849e4c89511ab94234", "type": "github" }, "original": { - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "2cf9db0e3d45b9d00f16f2836cb1297bcadc475e", - "type": "github" + "id": "nixpkgs", + "ref": "nixos-21.05-small", + "type": "indirect" } }, "nixpkgs_2": { @@ -8917,35 +6570,6 @@ } }, "nixpkgs_21": { - "locked": { - "lastModified": 1632864508, - "narHash": "sha256-d127FIvGR41XbVRDPVvozUPQ/uRHbHwvfyKHwEt5xFM=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "82891b5e2c2359d7e58d08849e4c89511ab94234", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "ref": "nixos-21.05-small", - "type": "indirect" - } - }, - "nixpkgs_22": { - "locked": { - "lastModified": 1642336556, - "narHash": "sha256-QSPPbFEwy0T0DrIuSzAACkaANPQaR1lZR/nHZGz9z04=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "f3d9d4bd898cca7d04af2ae4f6ef01f2219df3d6", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "type": "indirect" - } - }, - "nixpkgs_23": { "locked": { "lastModified": 1642336556, "narHash": "sha256-QSPPbFEwy0T0DrIuSzAACkaANPQaR1lZR/nHZGz9z04=", @@ -8959,7 +6583,7 @@ "type": "indirect" } }, - "nixpkgs_24": { + "nixpkgs_22": { "locked": { "lastModified": 1632864508, "narHash": "sha256-d127FIvGR41XbVRDPVvozUPQ/uRHbHwvfyKHwEt5xFM=", @@ -8974,7 +6598,7 @@ "type": "indirect" } }, - "nixpkgs_25": { + "nixpkgs_23": { "locked": { "lastModified": 1653581809, "narHash": "sha256-Uvka0V5MTGbeOfWte25+tfRL3moECDh1VwokWSZUdoY=", @@ -8990,7 +6614,7 @@ "type": "github" } }, - "nixpkgs_26": { + "nixpkgs_24": { "locked": { "lastModified": 1654807842, "narHash": "sha256-ADymZpr6LuTEBXcy6RtFHcUZdjKTBRTMYwu19WOx17E=", @@ -9005,7 +6629,7 @@ "type": "github" } }, - "nixpkgs_27": { + "nixpkgs_25": { "locked": { "lastModified": 1665087388, "narHash": "sha256-FZFPuW9NWHJteATOf79rZfwfRn5fE0wi9kRzvGfDHPA=", @@ -9021,35 +6645,6 @@ "type": "github" } }, - "nixpkgs_28": { - "locked": { - "lastModified": 1642336556, - "narHash": "sha256-QSPPbFEwy0T0DrIuSzAACkaANPQaR1lZR/nHZGz9z04=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "f3d9d4bd898cca7d04af2ae4f6ef01f2219df3d6", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "type": "indirect" - } - }, - "nixpkgs_29": { - "locked": { - "lastModified": 1632864508, - "narHash": "sha256-d127FIvGR41XbVRDPVvozUPQ/uRHbHwvfyKHwEt5xFM=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "82891b5e2c2359d7e58d08849e4c89511ab94234", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "ref": "nixos-21.05-small", - "type": "indirect" - } - }, "nixpkgs_3": { "locked": { "lastModified": 1619531122, @@ -9064,96 +6659,6 @@ "type": "indirect" } }, - "nixpkgs_30": { - "locked": { - "lastModified": 1642336556, - "narHash": "sha256-QSPPbFEwy0T0DrIuSzAACkaANPQaR1lZR/nHZGz9z04=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "f3d9d4bd898cca7d04af2ae4f6ef01f2219df3d6", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "type": "indirect" - } - }, - "nixpkgs_31": { - "locked": { - "lastModified": 1642336556, - "narHash": "sha256-QSPPbFEwy0T0DrIuSzAACkaANPQaR1lZR/nHZGz9z04=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "f3d9d4bd898cca7d04af2ae4f6ef01f2219df3d6", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "type": "indirect" - } - }, - "nixpkgs_32": { - "locked": { - "lastModified": 1632864508, - "narHash": "sha256-d127FIvGR41XbVRDPVvozUPQ/uRHbHwvfyKHwEt5xFM=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "82891b5e2c2359d7e58d08849e4c89511ab94234", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "ref": "nixos-21.05-small", - "type": "indirect" - } - }, - "nixpkgs_33": { - "locked": { - "lastModified": 1653581809, - "narHash": "sha256-Uvka0V5MTGbeOfWte25+tfRL3moECDh1VwokWSZUdoY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "83658b28fe638a170a19b8933aa008b30640fbd1", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixos-unstable", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs_34": { - "locked": { - "lastModified": 1654807842, - "narHash": "sha256-ADymZpr6LuTEBXcy6RtFHcUZdjKTBRTMYwu19WOx17E=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "fc909087cc3386955f21b4665731dbdaceefb1d8", - "type": "github" - }, - "original": { - "owner": "NixOS", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs_35": { - "locked": { - "lastModified": 1665087388, - "narHash": "sha256-FZFPuW9NWHJteATOf79rZfwfRn5fE0wi9kRzvGfDHPA=", - "owner": "nixos", - "repo": "nixpkgs", - "rev": "95fda953f6db2e9496d2682c4fc7b82f959878f7", - "type": "github" - }, - "original": { - "owner": "nixos", - "ref": "nixpkgs-unstable", - "repo": "nixpkgs", - "type": "github" - } - }, "nixpkgs_4": { "locked": { "lastModified": 1656461576, @@ -9229,36 +6734,20 @@ }, "nixpkgs_9": { "locked": { - "lastModified": 1632864508, - "narHash": "sha256-d127FIvGR41XbVRDPVvozUPQ/uRHbHwvfyKHwEt5xFM=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "82891b5e2c2359d7e58d08849e4c89511ab94234", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "ref": "nixos-21.05-small", - "type": "indirect" - } - }, - "node-process": { - "flake": false, - "locked": { - "lastModified": 1654323094, - "narHash": "sha256-zbmpZeBgUUly8QgR2mrVUN0A+0iLczufNvCCRxAo3GY=", - "owner": "input-output-hk", - "repo": "cardano-node", - "rev": "ec20745f17cb4fa8824fdf341d1412c774bc94b9", + "lastModified": 1632864508, + "narHash": "sha256-d127FIvGR41XbVRDPVvozUPQ/uRHbHwvfyKHwEt5xFM=", + "owner": "NixOS", + "repo": "nixpkgs", + "rev": "82891b5e2c2359d7e58d08849e4c89511ab94234", "type": "github" }, "original": { - "owner": "input-output-hk", - "repo": "cardano-node", - "type": "github" + "id": "nixpkgs", + "ref": "nixos-21.05-small", + "type": "indirect" } }, - "node-process_2": { + "node-process": { "flake": false, "locked": { "lastModified": 1654323094, @@ -9274,7 +6763,7 @@ "type": "github" } }, - "node-process_3": { + "node-process_2": { "flake": false, "locked": { "lastModified": 1654323094, @@ -9328,8 +6817,7 @@ "iohkNix": "iohkNix_7", "membench": "membench_3", "nixpkgs": [ - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "haskellNix", @@ -9353,37 +6841,6 @@ "type": "github" } }, - "node-snapshot_3": { - "inputs": { - "customConfig": "customConfig_11", - "haskellNix": "haskellNix_11", - "iohkNix": "iohkNix_11", - "membench": "membench_5", - "nixpkgs": [ - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "haskellNix", - "nixpkgs-2105" - ], - "plutus-example": "plutus-example_3", - "utils": "utils_13" - }, - "locked": { - "lastModified": 1645120669, - "narHash": "sha256-2MKfGsYS5n69+pfqNHb4IH/E95ok1MD7mhEYfUpRcz4=", - "owner": "input-output-hk", - "repo": "cardano-node", - "rev": "7f00e3ea5a61609e19eeeee4af35241571efdf5c", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-node", - "rev": "7f00e3ea5a61609e19eeeee4af35241571efdf5c", - "type": "github" - } - }, "ogmios": { "inputs": { "CHaP": "CHaP", @@ -9414,110 +6871,31 @@ "type": "github" } }, - "ogmios-datum-cache": { - "inputs": { - "flake-compat": "flake-compat_9", - "nixpkgs": "nixpkgs_18", - "unstable_nixpkgs": "unstable_nixpkgs" - }, - "locked": { - "lastModified": 1668515878, - "narHash": "sha256-r4aOSSz9jZZPreUkgOpS3ZpYFV4cxNVCUQFIpBZ8Y9k=", - "owner": "mlabs-haskell", - "repo": "ogmios-datum-cache", - "rev": "862c6bfcb6110b8fe816e26b3bba105dfb492b24", - "type": "github" - }, - "original": { - "owner": "mlabs-haskell", - "repo": "ogmios-datum-cache", - "rev": "862c6bfcb6110b8fe816e26b3bba105dfb492b24", - "type": "github" - } - }, - "ogmios-datum-cache-nixos": { - "inputs": { - "cardano-configurations": "cardano-configurations_3", - "cardano-node": [ - "ogmios-datum-cache-nixos", - "ogmios", - "cardano-node" - ], - "flake-compat": "flake-compat_10", - "nixpkgs": "nixpkgs_19", - "ogmios": "ogmios_2", - "unstable_nixpkgs": "unstable_nixpkgs_2" - }, - "locked": { - "lastModified": 1667912888, - "narHash": "sha256-6KS0c1PZ44ZTcE2ioXC0GiIuyTKnG5MeKX7nDZ6Knus=", - "owner": "mlabs-haskell", - "repo": "ogmios-datum-cache", - "rev": "a33a576fefe2248e9906e7b8044a30955cca0061", - "type": "github" - }, - "original": { - "owner": "mlabs-haskell", - "ref": "marton/nixos-module", - "repo": "ogmios-datum-cache", - "type": "github" - } - }, "ogmios-nixos": { - "inputs": { - "CHaP": "CHaP_3", - "blank": "blank_5", - "cardano-configurations": "cardano-configurations_4", - "cardano-node": "cardano-node_4", - "flake-compat": "flake-compat_16", - "haskell-nix": "haskell-nix_5", - "iohk-nix": "iohk-nix_5", - "nixpkgs": [ - "ogmios-nixos", - "haskell-nix", - "nixpkgs-unstable" - ] - }, - "locked": { - "lastModified": 1668087435, - "narHash": "sha256-pbx/+mP2pu4vQuTV3YtFXrOZOVOBS9JH9eDqgjnHyZ4=", - "owner": "mlabs-haskell", - "repo": "ogmios", - "rev": "3b229c1795efa30243485730b78ea053992fdc7a", - "type": "github" - }, - "original": { - "owner": "mlabs-haskell", - "repo": "ogmios", - "type": "github" - } - }, - "ogmios_2": { "inputs": { "CHaP": "CHaP_2", "blank": "blank_3", + "cardano-configurations": "cardano-configurations_3", "cardano-node": "cardano-node_3", - "flake-compat": "flake-compat_12", + "flake-compat": "flake-compat_10", "haskell-nix": "haskell-nix_4", "iohk-nix": "iohk-nix_4", "nixpkgs": [ - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "haskell-nix", "nixpkgs-unstable" ] }, "locked": { - "lastModified": 1667904967, - "narHash": "sha256-KAWv/plBLRqZiBYUl0plXQdMPzFs7G89VhTbg122kA4=", + "lastModified": 1668087435, + "narHash": "sha256-pbx/+mP2pu4vQuTV3YtFXrOZOVOBS9JH9eDqgjnHyZ4=", "owner": "mlabs-haskell", "repo": "ogmios", - "rev": "dbc1a03dca6a876a25d54a8716504837909c6e8c", + "rev": "3b229c1795efa30243485730b78ea053992fdc7a", "type": "github" }, "original": { "owner": "mlabs-haskell", - "ref": "staging", "repo": "ogmios", "type": "github" } @@ -9607,91 +6985,6 @@ "type": "github" } }, - "old-ghc-nix_14": { - "flake": false, - "locked": { - "lastModified": 1631092763, - "narHash": "sha256-sIKgO+z7tj4lw3u6oBZxqIhDrzSkvpHtv0Kki+lh9Fg=", - "owner": "angerman", - "repo": "old-ghc-nix", - "rev": "af48a7a7353e418119b6dfe3cd1463a657f342b8", - "type": "github" - }, - "original": { - "owner": "angerman", - "ref": "master", - "repo": "old-ghc-nix", - "type": "github" - } - }, - "old-ghc-nix_15": { - "flake": false, - "locked": { - "lastModified": 1631092763, - "narHash": "sha256-sIKgO+z7tj4lw3u6oBZxqIhDrzSkvpHtv0Kki+lh9Fg=", - "owner": "angerman", - "repo": "old-ghc-nix", - "rev": "af48a7a7353e418119b6dfe3cd1463a657f342b8", - "type": "github" - }, - "original": { - "owner": "angerman", - "ref": "master", - "repo": "old-ghc-nix", - "type": "github" - } - }, - "old-ghc-nix_16": { - "flake": false, - "locked": { - "lastModified": 1631092763, - "narHash": "sha256-sIKgO+z7tj4lw3u6oBZxqIhDrzSkvpHtv0Kki+lh9Fg=", - "owner": "angerman", - "repo": "old-ghc-nix", - "rev": "af48a7a7353e418119b6dfe3cd1463a657f342b8", - "type": "github" - }, - "original": { - "owner": "angerman", - "ref": "master", - "repo": "old-ghc-nix", - "type": "github" - } - }, - "old-ghc-nix_17": { - "flake": false, - "locked": { - "lastModified": 1631092763, - "narHash": "sha256-sIKgO+z7tj4lw3u6oBZxqIhDrzSkvpHtv0Kki+lh9Fg=", - "owner": "angerman", - "repo": "old-ghc-nix", - "rev": "af48a7a7353e418119b6dfe3cd1463a657f342b8", - "type": "github" - }, - "original": { - "owner": "angerman", - "ref": "master", - "repo": "old-ghc-nix", - "type": "github" - } - }, - "old-ghc-nix_18": { - "flake": false, - "locked": { - "lastModified": 1631092763, - "narHash": "sha256-sIKgO+z7tj4lw3u6oBZxqIhDrzSkvpHtv0Kki+lh9Fg=", - "owner": "angerman", - "repo": "old-ghc-nix", - "rev": "af48a7a7353e418119b6dfe3cd1463a657f342b8", - "type": "github" - }, - "original": { - "owner": "angerman", - "ref": "master", - "repo": "old-ghc-nix", - "type": "github" - } - }, "old-ghc-nix_2": { "flake": false, "locked": { @@ -9926,44 +7219,12 @@ "type": "github" } }, - "ouroboros-network_6": { - "flake": false, - "locked": { - "lastModified": 1643385024, - "narHash": "sha256-9R4Z1jBsTcEgBHxhzjCJnroEcdfMsTjf8kwg6uPue+Q=", - "owner": "input-output-hk", - "repo": "ouroboros-network", - "rev": "8e97076176d465f5f4f86d5b5596220272630649", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "ouroboros-network", - "type": "github" - } - }, - "ouroboros-network_7": { - "flake": false, - "locked": { - "lastModified": 1643385024, - "narHash": "sha256-9R4Z1jBsTcEgBHxhzjCJnroEcdfMsTjf8kwg6uPue+Q=", - "owner": "input-output-hk", - "repo": "ouroboros-network", - "rev": "8e97076176d465f5f4f86d5b5596220272630649", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "ouroboros-network", - "type": "github" - } - }, "plutip": { "inputs": { "bot-plutus-interface": [ "bot-plutus-interface" ], - "flake-compat": "flake-compat_19", + "flake-compat": "flake-compat_13", "haskell-nix": [ "bot-plutus-interface", "haskell-nix" @@ -10059,59 +7320,12 @@ "type": "github" } }, - "plutus-apps_4": { - "flake": false, - "locked": { - "lastModified": 1654271253, - "narHash": "sha256-GQDPzyVtcbbESmckMvzoTEKa/UWWJH7djh1TWQjzFow=", - "owner": "input-output-hk", - "repo": "plutus-apps", - "rev": "61de89d33340279b8452a0dbb52a87111db87e82", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "plutus-apps", - "type": "github" - } - }, "plutus-example": { "inputs": { "customConfig": "customConfig_5", "haskellNix": "haskellNix_5", - "iohkNix": "iohkNix_5", - "nixpkgs": [ - "ogmios", - "cardano-node", - "node-snapshot", - "plutus-example", - "haskellNix", - "nixpkgs-2105" - ], - "utils": "utils_2" - }, - "locked": { - "lastModified": 1640022647, - "narHash": "sha256-M+YnF7Zj/7QK2pu0T75xNVaX0eEeijtBH8yz+jEHIMM=", - "owner": "input-output-hk", - "repo": "cardano-node", - "rev": "814df2c146f5d56f8c35a681fe75e85b905aed5d", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-node", - "rev": "814df2c146f5d56f8c35a681fe75e85b905aed5d", - "type": "github" - } - }, - "plutus-example_2": { - "inputs": { - "customConfig": "customConfig_9", - "haskellNix": "haskellNix_9", - "iohkNix": "iohkNix_9", + "iohkNix": "iohkNix_5", "nixpkgs": [ - "ogmios-datum-cache-nixos", "ogmios", "cardano-node", "node-snapshot", @@ -10119,7 +7333,7 @@ "haskellNix", "nixpkgs-2105" ], - "utils": "utils_7" + "utils": "utils_2" }, "locked": { "lastModified": 1640022647, @@ -10136,11 +7350,11 @@ "type": "github" } }, - "plutus-example_3": { + "plutus-example_2": { "inputs": { - "customConfig": "customConfig_13", - "haskellNix": "haskellNix_13", - "iohkNix": "iohkNix_13", + "customConfig": "customConfig_9", + "haskellNix": "haskellNix_9", + "iohkNix": "iohkNix_9", "nixpkgs": [ "ogmios-nixos", "cardano-node", @@ -10149,7 +7363,7 @@ "haskellNix", "nixpkgs-2105" ], - "utils": "utils_12" + "utils": "utils_7" }, "locked": { "lastModified": 1640022647, @@ -10250,8 +7464,6 @@ "nixpkgs" ], "ogmios": "ogmios", - "ogmios-datum-cache": "ogmios-datum-cache", - "ogmios-datum-cache-nixos": "ogmios-datum-cache-nixos", "ogmios-nixos": "ogmios-nixos", "plutip": "plutip" } @@ -10353,86 +7565,6 @@ "type": "github" } }, - "stackage_14": { - "flake": false, - "locked": { - "lastModified": 1656898145, - "narHash": "sha256-EMgMzdANg6r5gEUkMtv5ujDo2/Kx7JJXoXiDKjDVoLw=", - "owner": "input-output-hk", - "repo": "stackage.nix", - "rev": "835a5f2d2a1acafb77add430fc8c2dd47282ef32", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "stackage.nix", - "type": "github" - } - }, - "stackage_15": { - "flake": false, - "locked": { - "lastModified": 1643073493, - "narHash": "sha256-5cPd1+i/skvJY9vJO1BhVRPcJObqkxDSywBEppDmb1U=", - "owner": "input-output-hk", - "repo": "stackage.nix", - "rev": "48e1188855ca38f3b7e2a8dba5352767a2f0a8f7", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "stackage.nix", - "type": "github" - } - }, - "stackage_16": { - "flake": false, - "locked": { - "lastModified": 1643073493, - "narHash": "sha256-5cPd1+i/skvJY9vJO1BhVRPcJObqkxDSywBEppDmb1U=", - "owner": "input-output-hk", - "repo": "stackage.nix", - "rev": "48e1188855ca38f3b7e2a8dba5352767a2f0a8f7", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "stackage.nix", - "type": "github" - } - }, - "stackage_17": { - "flake": false, - "locked": { - "lastModified": 1639012797, - "narHash": "sha256-hiLyBa5XFBvxD+BcYPKyYd/0dNMccxAuywFNqYtIIvs=", - "owner": "input-output-hk", - "repo": "stackage.nix", - "rev": "9ea6ea359da91c75a71e334b25aa7dc5ddc4b2c6", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "stackage.nix", - "type": "github" - } - }, - "stackage_18": { - "flake": false, - "locked": { - "lastModified": 1667610757, - "narHash": "sha256-H4dlMk5EW50xOtGo+5Srm3HGQV1+hY9ttgRQ+Sew5uA=", - "owner": "input-output-hk", - "repo": "stackage.nix", - "rev": "01d8ea53f65b08910003a1990547bab75ed6068a", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "stackage.nix", - "type": "github" - } - }, "stackage_2": { "flake": false, "locked": { @@ -10608,8 +7740,7 @@ "dmerge": "dmerge_2", "flake-utils": "flake-utils_23", "makes": [ - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "haskell-nix", "tullia", "std", @@ -10617,8 +7748,7 @@ ], "mdbook-kroki-preprocessor": "mdbook-kroki-preprocessor_2", "microvm": [ - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "haskell-nix", "tullia", "std", @@ -10626,7 +7756,7 @@ ], "n2c": "n2c_2", "nixago": "nixago_2", - "nixpkgs": "nixpkgs_27", + "nixpkgs": "nixpkgs_25", "yants": "yants_2" }, "locked": { @@ -10643,46 +7773,6 @@ "type": "github" } }, - "std_3": { - "inputs": { - "blank": "blank_6", - "devshell": "devshell_3", - "dmerge": "dmerge_3", - "flake-utils": "flake-utils_31", - "makes": [ - "ogmios-nixos", - "haskell-nix", - "tullia", - "std", - "blank" - ], - "mdbook-kroki-preprocessor": "mdbook-kroki-preprocessor_3", - "microvm": [ - "ogmios-nixos", - "haskell-nix", - "tullia", - "std", - "blank" - ], - "n2c": "n2c_3", - "nixago": "nixago_3", - "nixpkgs": "nixpkgs_35", - "yants": "yants_3" - }, - "locked": { - "lastModified": 1665513321, - "narHash": "sha256-D6Pacw9yf/HMs84KYuCxHXnNDL7v43gtcka5URagFqE=", - "owner": "divnix", - "repo": "std", - "rev": "94a90eedb9cfc115b12ae8f6622d9904788559e4", - "type": "github" - }, - "original": { - "owner": "divnix", - "repo": "std", - "type": "github" - } - }, "tailwind-haskell": { "inputs": { "flake-utils": "flake-utils_4", @@ -10732,38 +7822,12 @@ "inputs": { "nix-nomad": "nix-nomad_2", "nix2container": "nix2container_2", - "nixpkgs": [ - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "nixpkgs" - ], - "std": "std_2" - }, - "locked": { - "lastModified": 1666200256, - "narHash": "sha256-cJPS8zBu30SMhxMe7I8DWutwqMuhPsEez87y9gxMKc4=", - "owner": "input-output-hk", - "repo": "tullia", - "rev": "575362c2244498e8d2c97f72861510fa72e75d44", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "tullia", - "type": "github" - } - }, - "tullia_3": { - "inputs": { - "nix-nomad": "nix-nomad_3", - "nix2container": "nix2container_3", "nixpkgs": [ "ogmios-nixos", "haskell-nix", "nixpkgs" ], - "std": "std_3" + "std": "std_2" }, "locked": { "lastModified": 1666200256, @@ -10796,36 +7860,6 @@ "type": "github" } }, - "unstable_nixpkgs": { - "locked": { - "lastModified": 1653307806, - "narHash": "sha256-VPej3GE4IBMwYnXRfbiVqMWKa32+ysuvbHRkQXD0gTw=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "9d7aff488a8f9429d9e6cd82c10dffbf21907fb1", - "type": "github" - }, - "original": { - "owner": "NixOS", - "repo": "nixpkgs", - "type": "github" - } - }, - "unstable_nixpkgs_2": { - "locked": { - "lastModified": 1653307806, - "narHash": "sha256-VPej3GE4IBMwYnXRfbiVqMWKa32+ysuvbHRkQXD0gTw=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "9d7aff488a8f9429d9e6cd82c10dffbf21907fb1", - "type": "github" - }, - "original": { - "owner": "NixOS", - "repo": "nixpkgs", - "type": "github" - } - }, "utils": { "locked": { "lastModified": 1623875721, @@ -10856,81 +7890,6 @@ "type": "github" } }, - "utils_11": { - "locked": { - "lastModified": 1623875721, - "narHash": "sha256-A8BU7bjS5GirpAUv4QA+QnJ4CceLHkcXdRp4xITDB0s=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "f7e004a55b120c02ecb6219596820fcd32ca8772", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "utils_12": { - "locked": { - "lastModified": 1638122382, - "narHash": "sha256-sQzZzAbvKEqN9s0bzWuYmRaA03v40gaJ4+iL1LXjaeI=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "74f7e4319258e287b0f9cb95426c9853b282730b", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "utils_13": { - "locked": { - "lastModified": 1623875721, - "narHash": "sha256-A8BU7bjS5GirpAUv4QA+QnJ4CceLHkcXdRp4xITDB0s=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "f7e004a55b120c02ecb6219596820fcd32ca8772", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "utils_14": { - "locked": { - "lastModified": 1653893745, - "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "1ed9fb1935d260de5fe1c2f7ee0ebaae17ed2fa1", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "utils_15": { - "locked": { - "lastModified": 1653893745, - "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "1ed9fb1935d260de5fe1c2f7ee0ebaae17ed2fa1", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, "utils_2": { "locked": { "lastModified": 1638122382, @@ -11076,31 +8035,6 @@ } }, "yants_2": { - "inputs": { - "nixpkgs": [ - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "std", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1660507851, - "narHash": "sha256-BKjq7JnVuUR/xDtcv6Vm9GYGKAblisXrAgybor9hT/s=", - "owner": "divnix", - "repo": "yants", - "rev": "0b895ca02a8fa72bad50b454cb3e7d8a66407c96", - "type": "github" - }, - "original": { - "owner": "divnix", - "repo": "yants", - "type": "github" - } - }, - "yants_3": { "inputs": { "nixpkgs": [ "ogmios-nixos", diff --git a/flake.nix b/flake.nix index 0d9dcef907..a794026f93 100644 --- a/flake.nix +++ b/flake.nix @@ -35,11 +35,8 @@ cardano-wallet.url = "github:mlabs-haskell/cardano-wallet?rev=9d34b2633ace6aa32c1556d33c8c2df63dbc8f5b"; - ogmios-datum-cache.url = "github:mlabs-haskell/ogmios-datum-cache/862c6bfcb6110b8fe816e26b3bba105dfb492b24"; - - # ogmios and ogmios-datum-cache nixos modules (remove and replace with the above after merging and updating) + # ogmios nixos module (remove and replace with the above after merging and updating) ogmios-nixos.url = "github:mlabs-haskell/ogmios"; - ogmios-datum-cache-nixos.url = "github:mlabs-haskell/ogmios-datum-cache/marton/nixos-module"; cardano-node.follows = "ogmios-nixos/cardano-node"; # for new environments like preview and preprod. TODO: remove this when cardano-node is updated @@ -300,8 +297,6 @@ { plutip-server = inputs.plutip.packages.${system}."plutip:exe:plutip-server"; - ogmios-datum-cache = - inputs.ogmios-datum-cache.defaultPackage.${system}; ogmios = ogmios.packages.${system}."ogmios:exe:ogmios"; kupo = inputs.kupo-nixos.defaultPackage.${system}; buildCtlRuntime = buildCtlRuntime final; @@ -526,11 +521,6 @@ services.ogmios.package = inputs.ogmios.packages.x86_64-linux."ogmios:exe:ogmios"; } - inputs.ogmios-datum-cache-nixos.nixosModules.ogmios-datum-cache - { - services.ogmios-datum-cache.package = - inputs.ogmios-datum-cache.packages.x86_64-linux."ogmios-datum-cache"; - } self.nixosModules.ctl-server ./nix/test-nixos-configuration.nix ]; diff --git a/nix/default.nix b/nix/default.nix index 831c0127bc..03ef02daaf 100644 --- a/nix/default.nix +++ b/nix/default.nix @@ -128,9 +128,7 @@ let lists.optional withRuntime ( [ pkgs.ogmios - pkgs.ogmios-datum-cache pkgs.plutip-server - pkgs.postgresql pkgs.kupo ] # this package will be soon put into its own overlay, so we'll @@ -242,7 +240,7 @@ let # the following required `buildInputs` available in your own package set: # # - `ogmios` - # - `ogmios-datum-cache` + # - `kupo` # - `plutip-server` # # If you require `ctl-server` to be present in `PATH` (e.g. because your @@ -263,9 +261,7 @@ let runPursTest ( args // { buildInputs = with pkgs; [ - postgresql ogmios - ogmios-datum-cache plutip-server kupo ] @@ -345,9 +341,8 @@ let buildInputs = with pkgs; [ project nodeModules - postgresql ogmios - ogmios-datum-cache + kupo plutip-server chromium python38 # To serve bundled CTL @@ -370,9 +365,7 @@ let export E2E_NO_HEADLESS=false export PLUTIP_PORT=8087 export OGMIOS_PORT=1345 - export OGMIOS_DATUM_CACHE_PORT=10005 export CTL_SERVER_PORT=8088 - export POSTGRES_PORT=5438 export E2E_SKIP_JQUERY_DOWNLOAD=true export E2E_EXTRA_BROWSER_ARGS="--disable-web-security" diff --git a/nix/runtime.nix b/nix/runtime.nix index 28f9e73dfb..894c255c9a 100644 --- a/nix/runtime.nix +++ b/nix/runtime.nix @@ -12,8 +12,7 @@ rec { }; # *All* of these values are optional, and shown with their default # values. If you need even more customization, you can use `overideAttrs` - # to change the values after calling `buildCtlRuntime` (e.g. a secrets - # volume for the `postgres` service) + # to change the values after calling `buildCtlRuntime` node = { port = 3001; # the version of the node to use, corresponds to the image version tag, @@ -29,16 +28,6 @@ rec { enable = true; port = 8081; }; - postgres = { - # User-facing port on host machine. - # Can be set to null in order to not bind postgres port to host. - # Postgres will always be accessible via `postgres:5432` from - # containers. - port = 5432; - user = "ctl"; - password = "ctl"; - db = "ctl-${network.name}"; - }; kupo = { port = 1442; since = "origin"; @@ -173,20 +162,6 @@ rec { ]; }; }; - "postgres-${network.name}" = { - service = { - image = "postgres:13"; - ports = - if postgres.port == null - then [ ] - else [ "${toString postgres.port}:5432" ]; - environment = { - POSTGRES_USER = "${postgres.user}"; - POSTGRES_PASSWORD = "${postgres.password}"; - POSTGRES_DB = "${postgres.db}"; - }; - }; - }; } // pkgs.lib.optionalAttrs ctlServer.enable { ctl-server = { service = { diff --git a/nix/test-nixos-configuration.nix b/nix/test-nixos-configuration.nix index 8cd403c929..3ae986800b 100644 --- a/nix/test-nixos-configuration.nix +++ b/nix/test-nixos-configuration.nix @@ -23,8 +23,6 @@ # services - services.postgresql.enable = true; - services.cardano-node = { enable = true; systemdSocketActivation = true; @@ -38,14 +36,5 @@ nodeSocket = "/var/run/cardano-node/node.socket"; }; - services.ogmios-datum-cache = { - enable = true; - host = "0.0.0.0"; - useLatest = true; - blockSlot = 5854109; - blockHash = "85366c607a9777b887733de621aa2008aec9db4f3e6a114fb90ec2909bc06f14"; - blockFilter = builtins.toJSON { const = true; }; - }; - services.ctl-server.enable = true; } diff --git a/src/Contract/Test/Plutip.purs b/src/Contract/Test/Plutip.purs index c08fa933a8..beb0b21f9e 100644 --- a/src/Contract/Test/Plutip.purs +++ b/src/Contract/Test/Plutip.purs @@ -22,7 +22,6 @@ import Ctl.Internal.Plutip.Types , InitialUTxOs , InitialUTxOsWithStakeKey , PlutipConfig - , PostgresConfig , UtxoAmount ) as X import Ctl.Internal.Plutip.Types (PlutipConfig) diff --git a/src/Internal/Plutip/Server.purs b/src/Internal/Plutip/Server.purs index 9eb577f55a..c56a568ee7 100644 --- a/src/Internal/Plutip/Server.purs +++ b/src/Internal/Plutip/Server.purs @@ -58,7 +58,6 @@ import Ctl.Internal.Plutip.Types , InitialUTxODistribution , InitialUTxOs , PlutipConfig - , PostgresConfig , PrivateKeyResponse(PrivateKeyResponse) , StartClusterResponse(ClusterStartupSuccess, ClusterStartupFailure) , StopClusterRequest(StopClusterRequest) @@ -295,7 +294,6 @@ startPlutipContractEnv plutipCfg distr cleanupRef = do configCheck plutipCfg startPlutipServer' ourKey /\ response <- startPlutipCluster' - startPostgres' response startOgmios' response startKupo' response startMCtlServer' @@ -344,14 +342,6 @@ startPlutipContractEnv plutipCfg distr cleanupRef = do (const $ void $ stopPlutipCluster plutipCfg) pure - startPostgres' :: ClusterStartupParameters -> Aff Unit - startPostgres' response = - bracket (startPostgresServer plutipCfg.postgresConfig response) - (stopChildProcessWithPortAndRemoveOnSignal plutipCfg.postgresConfig.port) - \(process /\ workingDir /\ _) -> do - liftEffect $ cleanupTmpDir process workingDir - void $ configurePostgresServer plutipCfg.postgresConfig - startOgmios' :: ClusterStartupParameters -> Aff Unit startOgmios' response = bracket (startOgmios plutipCfg response) @@ -436,7 +426,6 @@ configCheck cfg = do [ cfg.port /\ "plutip-server" , cfg.ogmiosConfig.port /\ "ogmios" , cfg.kupoConfig.port /\ "kupo" - , cfg.postgresConfig.port /\ "postgres" ] <> foldMap (pure <<< (_ /\ "ctl-server") <<< _.port) cfg.ctlServerConfig occupiedServices <- Array.catMaybes <$> for services \(port /\ service) -> do isPortAvailable port <#> if _ then Nothing else Just (port /\ service) @@ -608,81 +597,6 @@ checkPlutipServer cfg = do $ const $ stopPlutipCluster cfg -startPostgresServer - :: PostgresConfig - -> ClusterStartupParameters - -> Aff (ManagedProcess /\ String /\ OnSignalRef) -startPostgresServer pgConfig params = do - tmpDir <- liftEffect tmpdir - randomStr <- liftEffect $ uniqueId "" - let - workingDir = tmpDir <> randomStr - databaseDir = workingDir <> "postgres/data" - postgresSocket = workingDir <> "postgres" - testClusterDir = (dirname <<< dirname) params.nodeConfigPath - sig <- liftEffect $ cleanupOnSigint workingDir testClusterDir - waitForStop =<< spawn "initdb" - [ "--locale=C", "--encoding=UTF-8", databaseDir ] - defaultSpawnOptions - Nothing - pgChildProcess <- spawn "postgres" - [ "-D" - , databaseDir - , "-p" - , UInt.toString pgConfig.port - , "-h" - , pgConfig.host - , "-k" - , postgresSocket - ] - defaultSpawnOptions - Nothing - pure (pgChildProcess /\ workingDir /\ sig) - -configurePostgresServer - :: PostgresConfig -> Aff Unit -configurePostgresServer pgConfig = do - defaultRecovering $ waitForStop =<< spawn "psql" - [ "-h" - , pgConfig.host - , "-p" - , UInt.toString pgConfig.port - , "-d" - , "postgres" - , "-c" - , "\\q" - ] - defaultSpawnOptions - Nothing - waitForStop =<< spawn "psql" - [ "-h" - , pgConfig.host - , "-p" - , UInt.toString pgConfig.port - , "-d" - , "postgres" - , "-c" - , "CREATE ROLE " <> pgConfig.user - <> " WITH LOGIN SUPERUSER CREATEDB PASSWORD '" - <> pgConfig.password - <> "';" - ] - defaultSpawnOptions - Nothing - waitForStop =<< spawn "createdb" - [ "-h" - , pgConfig.host - , "-p" - , UInt.toString pgConfig.port - , "-U" - , pgConfig.user - , "-O" - , pgConfig.user - , pgConfig.dbname - ] - defaultSpawnOptions - Nothing - -- | Kill a process and wait for it to stop listening on a specific port. stopChildProcessWithPort :: UInt -> ManagedProcess -> Aff Unit stopChildProcessWithPort port childProcess = do diff --git a/src/Internal/Plutip/Types.purs b/src/Internal/Plutip/Types.purs index 528f23ef39..d85b3d2393 100644 --- a/src/Internal/Plutip/Types.purs +++ b/src/Internal/Plutip/Types.purs @@ -6,7 +6,6 @@ module Ctl.Internal.Plutip.Types , InitialUTxODistribution , InitialUTxOsWithStakeKey(InitialUTxOsWithStakeKey) , PlutipConfig - , PostgresConfig , ClusterStartupRequest(ClusterStartupRequest) , PrivateKeyResponse(PrivateKeyResponse) , ClusterStartupFailureReason @@ -62,21 +61,11 @@ type PlutipConfig = -- Set this to `Nothing` to avoid spawning `ctl-server` , ctlServerConfig :: Maybe ServerConfig , kupoConfig :: ServerConfig - -- Should be synchronized with `defaultConfig.postgres` in `flake.nix` - , postgresConfig :: PostgresConfig , customLogger :: Maybe (LogLevel -> Message -> Aff Unit) , suppressLogs :: Boolean , hooks :: Hooks } -type PostgresConfig = - { host :: String - , port :: UInt - , user :: String - , password :: String - , dbname :: String - } - type FilePath = String type ErrorMessage = String diff --git a/src/Internal/QueryM.purs b/src/Internal/QueryM.purs index 02dc0869a6..71af45e1bd 100644 --- a/src/Internal/QueryM.purs +++ b/src/Internal/QueryM.purs @@ -44,7 +44,6 @@ module Ctl.Internal.QueryM import Prelude --- import Ctl.Internal.QueryM.Kupo (isTxConfirmed) import Aeson ( class DecodeAeson , Aeson diff --git a/src/Internal/Test/E2E/Options.purs b/src/Internal/Test/E2E/Options.purs index c695b40eca..8d5db60dc3 100644 --- a/src/Internal/Test/E2E/Options.purs +++ b/src/Internal/Test/E2E/Options.purs @@ -96,7 +96,6 @@ type ClusterPortsOptions_ (r :: Row Type) = ( plutipPort :: Maybe UInt , ogmiosPort :: Maybe UInt , ctlServerPort :: Maybe UInt - , postgresPort :: Maybe UInt , kupoPort :: Maybe UInt | r ) @@ -333,13 +332,11 @@ defaultPorts , kupo :: Int , ogmios :: Int , plutip :: Int - , postgres :: Int } defaultPorts = { plutip: 8087 , ogmios: 1345 , ctlServer: 8088 - , postgres: 5438 , kupo: 1443 } @@ -369,14 +366,6 @@ clusterPortsOptionsParser = ado showPort "CTL_SERVER" defaultPorts.ctlServer , metavar "PORT" ] - postgresPort <- option (Just <$> uintParser) $ fold - [ long "postgres-port" - , help "Postgres port for use with local Plutip cluster" - , value Nothing - , showDefaultWith $ const $ - showPort "POSTGRES" defaultPorts.postgres - , metavar "PORT" - ] kupoPort <- option (Just <$> uintParser) $ fold [ long "kupo-port" , help "Kupo port for use with local Plutip cluster" @@ -389,7 +378,6 @@ clusterPortsOptionsParser = ado { plutipPort , ogmiosPort , ctlServerPort - , postgresPort , kupoPort } where diff --git a/src/Internal/Test/E2E/Runner.purs b/src/Internal/Test/E2E/Runner.purs index f275d7386c..0753988018 100644 --- a/src/Internal/Test/E2E/Runner.purs +++ b/src/Internal/Test/E2E/Runner.purs @@ -207,13 +207,6 @@ buildPlutipConfig options = , secure: false , path: Nothing } - , postgresConfig: - { host: "127.0.0.1" - , port: fromMaybe (UInt.fromInt 5438) options.postgresPort - , user: "ctxlib" - , password: "ctxlib" - , dbname: "ctxlib" - } , kupoConfig: { host: "127.0.0.1" , port: fromMaybe (UInt.fromInt defaultPorts.kupo) options.kupoPort @@ -358,7 +351,6 @@ readTestRuntime testOptions = do <<< delete (Proxy :: Proxy "plutipPort") <<< delete (Proxy :: Proxy "ogmiosPort") <<< delete (Proxy :: Proxy "ctlServerPort") - <<< delete (Proxy :: Proxy "postgresPort") <<< delete (Proxy :: Proxy "skipJQuery") <<< delete (Proxy :: Proxy "kupoPort") ) @@ -372,15 +364,12 @@ readPorts testOptions = do readPortNumber "OGMIOS" testOptions.ogmiosPort ctlServerPort <- readPortNumber "CTL_SERVER" testOptions.ctlServerPort - postgresPort <- - readPortNumber "POSTGRES" testOptions.postgresPort kupoPort <- readPortNumber "KUPO" testOptions.kupoPort pure { plutipPort , ogmiosPort , ctlServerPort - , postgresPort , kupoPort } where diff --git a/src/Internal/Types/PlutusData.purs b/src/Internal/Types/PlutusData.purs index 7a13ab1e44..00c59cbe32 100644 --- a/src/Internal/Types/PlutusData.purs +++ b/src/Internal/Types/PlutusData.purs @@ -46,7 +46,7 @@ derive instance Generic PlutusData _ instance Show PlutusData where show x = genericShow x --- Ogmios Datum Cache Json format +-- Based off Ogmios Datum Cache Json format, although we no longer use ODC instance DecodeAeson PlutusData where decodeAeson aeson = decodeConstr <|> decodeMap diff --git a/templates/ctl-scaffold/test/Main.purs b/templates/ctl-scaffold/test/Main.purs index f2dd876b52..2b3f7cc74b 100644 --- a/templates/ctl-scaffold/test/Main.purs +++ b/templates/ctl-scaffold/test/Main.purs @@ -70,13 +70,6 @@ config = , secure: false , path: Nothing } - , postgresConfig: - { host: "127.0.0.1" - , port: UInt.fromInt 5433 - , user: "ctxlib" - , password: "ctxlib" - , dbname: "ctxlib" - } , customLogger: Nothing , suppressLogs: true , hooks: emptyHooks diff --git a/test/Plutip/Common.purs b/test/Plutip/Common.purs index 4f985c9e20..2ab6c32310 100644 --- a/test/Plutip/Common.purs +++ b/test/Plutip/Common.purs @@ -40,13 +40,6 @@ config = , secure: false , path: Nothing } - , postgresConfig: - { host: "127.0.0.1" - , port: UInt.fromInt 5433 - , user: "ctxlib" - , password: "ctxlib" - , dbname: "ctxlib" - } , suppressLogs: true , customLogger: Nothing , hooks: emptyHooks diff --git a/test/e2e.env b/test/e2e.env index 80661b0027..53289852a5 100755 --- a/test/e2e.env +++ b/test/e2e.env @@ -69,7 +69,6 @@ export E2E_EXTRA_BROWSER_ARGS="--disable-web-security" # Bypass CORS for Kupo export PLUTIP_PORT=8087 export OGMIOS_PORT=1345 export CTL_SERVER_PORT=8088 -export POSTGRES_PORT=5438 export ETERNL_CRX="test-data/preview/extensions/eternl.crx" export ETERNL_CRX_URL="https://github.com/mlabs-haskell/ctl-e2e-assets/releases/download/preview-1/preview-eternl-1.9.7_0.crx" From 4e4067cf22dd487c3b46bacf88d10152333e761f Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Tue, 13 Dec 2022 14:13:28 +0000 Subject: [PATCH 091/373] Update template rev --- templates/ctl-scaffold/flake.lock | 3692 +++-------------------------- templates/ctl-scaffold/flake.nix | 2 +- 2 files changed, 292 insertions(+), 3402 deletions(-) diff --git a/templates/ctl-scaffold/flake.lock b/templates/ctl-scaffold/flake.lock index 8af2b819b2..07081dc6f0 100644 --- a/templates/ctl-scaffold/flake.lock +++ b/templates/ctl-scaffold/flake.lock @@ -34,23 +34,6 @@ "type": "github" } }, - "CHaP_3": { - "flake": false, - "locked": { - "lastModified": 1666726035, - "narHash": "sha256-EBodp9DJb8Z+aVbuezVwLJ9Q9XIJUXFd/n2skay3FeU=", - "owner": "input-output-hk", - "repo": "cardano-haskell-packages", - "rev": "b074321c4c8cbf2c3789436ab11eaa43e1c441a7", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-haskell-packages", - "rev": "b074321c4c8cbf2c3789436ab11eaa43e1c441a7", - "type": "github" - } - }, "HTTP": { "flake": false, "locked": { @@ -131,86 +114,6 @@ "type": "github" } }, - "HTTP_14": { - "flake": false, - "locked": { - "lastModified": 1451647621, - "narHash": "sha256-oHIyw3x0iKBexEo49YeUDV1k74ZtyYKGR2gNJXXRxts=", - "owner": "phadej", - "repo": "HTTP", - "rev": "9bc0996d412fef1787449d841277ef663ad9a915", - "type": "github" - }, - "original": { - "owner": "phadej", - "repo": "HTTP", - "type": "github" - } - }, - "HTTP_15": { - "flake": false, - "locked": { - "lastModified": 1451647621, - "narHash": "sha256-oHIyw3x0iKBexEo49YeUDV1k74ZtyYKGR2gNJXXRxts=", - "owner": "phadej", - "repo": "HTTP", - "rev": "9bc0996d412fef1787449d841277ef663ad9a915", - "type": "github" - }, - "original": { - "owner": "phadej", - "repo": "HTTP", - "type": "github" - } - }, - "HTTP_16": { - "flake": false, - "locked": { - "lastModified": 1451647621, - "narHash": "sha256-oHIyw3x0iKBexEo49YeUDV1k74ZtyYKGR2gNJXXRxts=", - "owner": "phadej", - "repo": "HTTP", - "rev": "9bc0996d412fef1787449d841277ef663ad9a915", - "type": "github" - }, - "original": { - "owner": "phadej", - "repo": "HTTP", - "type": "github" - } - }, - "HTTP_17": { - "flake": false, - "locked": { - "lastModified": 1451647621, - "narHash": "sha256-oHIyw3x0iKBexEo49YeUDV1k74ZtyYKGR2gNJXXRxts=", - "owner": "phadej", - "repo": "HTTP", - "rev": "9bc0996d412fef1787449d841277ef663ad9a915", - "type": "github" - }, - "original": { - "owner": "phadej", - "repo": "HTTP", - "type": "github" - } - }, - "HTTP_18": { - "flake": false, - "locked": { - "lastModified": 1451647621, - "narHash": "sha256-oHIyw3x0iKBexEo49YeUDV1k74ZtyYKGR2gNJXXRxts=", - "owner": "phadej", - "repo": "HTTP", - "rev": "9bc0996d412fef1787449d841277ef663ad9a915", - "type": "github" - }, - "original": { - "owner": "phadej", - "repo": "HTTP", - "type": "github" - } - }, "HTTP_2": { "flake": false, "locked": { @@ -416,36 +319,6 @@ "type": "github" } }, - "blank_5": { - "locked": { - "lastModified": 1625557891, - "narHash": "sha256-O8/MWsPBGhhyPoPLHZAuoZiiHo9q6FLlEeIDEXuj6T4=", - "owner": "divnix", - "repo": "blank", - "rev": "5a5d2684073d9f563072ed07c871d577a6c614a8", - "type": "github" - }, - "original": { - "owner": "divnix", - "repo": "blank", - "type": "github" - } - }, - "blank_6": { - "locked": { - "lastModified": 1625557891, - "narHash": "sha256-O8/MWsPBGhhyPoPLHZAuoZiiHo9q6FLlEeIDEXuj6T4=", - "owner": "divnix", - "repo": "blank", - "rev": "5a5d2684073d9f563072ed07c871d577a6c614a8", - "type": "github" - }, - "original": { - "owner": "divnix", - "repo": "blank", - "type": "github" - } - }, "bot-plutus-interface": { "inputs": { "Win32-network": "Win32-network", @@ -587,91 +460,6 @@ "type": "github" } }, - "cabal-32_14": { - "flake": false, - "locked": { - "lastModified": 1603716527, - "narHash": "sha256-X0TFfdD4KZpwl0Zr6x+PLxUt/VyKQfX7ylXHdmZIL+w=", - "owner": "haskell", - "repo": "cabal", - "rev": "48bf10787e27364730dd37a42b603cee8d6af7ee", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.2", - "repo": "cabal", - "type": "github" - } - }, - "cabal-32_15": { - "flake": false, - "locked": { - "lastModified": 1603716527, - "narHash": "sha256-sDbrmur9Zfp4mPKohCD8IDZfXJ0Tjxpmr2R+kg5PpSY=", - "owner": "haskell", - "repo": "cabal", - "rev": "94aaa8e4720081f9c75497e2735b90f6a819b08e", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.2", - "repo": "cabal", - "type": "github" - } - }, - "cabal-32_16": { - "flake": false, - "locked": { - "lastModified": 1603716527, - "narHash": "sha256-sDbrmur9Zfp4mPKohCD8IDZfXJ0Tjxpmr2R+kg5PpSY=", - "owner": "haskell", - "repo": "cabal", - "rev": "94aaa8e4720081f9c75497e2735b90f6a819b08e", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.2", - "repo": "cabal", - "type": "github" - } - }, - "cabal-32_17": { - "flake": false, - "locked": { - "lastModified": 1603716527, - "narHash": "sha256-sDbrmur9Zfp4mPKohCD8IDZfXJ0Tjxpmr2R+kg5PpSY=", - "owner": "haskell", - "repo": "cabal", - "rev": "94aaa8e4720081f9c75497e2735b90f6a819b08e", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.2", - "repo": "cabal", - "type": "github" - } - }, - "cabal-32_18": { - "flake": false, - "locked": { - "lastModified": 1603716527, - "narHash": "sha256-X0TFfdD4KZpwl0Zr6x+PLxUt/VyKQfX7ylXHdmZIL+w=", - "owner": "haskell", - "repo": "cabal", - "rev": "48bf10787e27364730dd37a42b603cee8d6af7ee", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.2", - "repo": "cabal", - "type": "github" - } - }, "cabal-32_2": { "flake": false, "locked": { @@ -893,7 +681,7 @@ "type": "github" } }, - "cabal-34_14": { + "cabal-34_2": { "flake": false, "locked": { "lastModified": 1640353650, @@ -910,14 +698,14 @@ "type": "github" } }, - "cabal-34_15": { + "cabal-34_3": { "flake": false, "locked": { - "lastModified": 1622475795, - "narHash": "sha256-chwTL304Cav+7p38d9mcb+egABWmxo2Aq+xgVBgEb/U=", + "lastModified": 1640353650, + "narHash": "sha256-N1t6M3/wqj90AEdRkeC8i923gQYUpzSr8b40qVOZ1Rk=", "owner": "haskell", "repo": "cabal", - "rev": "b086c1995cdd616fc8d91f46a21e905cc50a1049", + "rev": "942639c18c0cd8ec53e0a6f8d120091af35312cd", "type": "github" }, "original": { @@ -927,14 +715,14 @@ "type": "github" } }, - "cabal-34_16": { + "cabal-34_4": { "flake": false, "locked": { - "lastModified": 1622475795, - "narHash": "sha256-chwTL304Cav+7p38d9mcb+egABWmxo2Aq+xgVBgEb/U=", + "lastModified": 1640353650, + "narHash": "sha256-N1t6M3/wqj90AEdRkeC8i923gQYUpzSr8b40qVOZ1Rk=", "owner": "haskell", "repo": "cabal", - "rev": "b086c1995cdd616fc8d91f46a21e905cc50a1049", + "rev": "942639c18c0cd8ec53e0a6f8d120091af35312cd", "type": "github" }, "original": { @@ -944,7 +732,7 @@ "type": "github" } }, - "cabal-34_17": { + "cabal-34_5": { "flake": false, "locked": { "lastModified": 1622475795, @@ -961,14 +749,14 @@ "type": "github" } }, - "cabal-34_18": { + "cabal-34_6": { "flake": false, "locked": { - "lastModified": 1640353650, - "narHash": "sha256-N1t6M3/wqj90AEdRkeC8i923gQYUpzSr8b40qVOZ1Rk=", + "lastModified": 1622475795, + "narHash": "sha256-chwTL304Cav+7p38d9mcb+egABWmxo2Aq+xgVBgEb/U=", "owner": "haskell", "repo": "cabal", - "rev": "942639c18c0cd8ec53e0a6f8d120091af35312cd", + "rev": "b086c1995cdd616fc8d91f46a21e905cc50a1049", "type": "github" }, "original": { @@ -978,14 +766,14 @@ "type": "github" } }, - "cabal-34_2": { + "cabal-34_7": { "flake": false, "locked": { - "lastModified": 1640353650, - "narHash": "sha256-N1t6M3/wqj90AEdRkeC8i923gQYUpzSr8b40qVOZ1Rk=", + "lastModified": 1622475795, + "narHash": "sha256-chwTL304Cav+7p38d9mcb+egABWmxo2Aq+xgVBgEb/U=", "owner": "haskell", "repo": "cabal", - "rev": "942639c18c0cd8ec53e0a6f8d120091af35312cd", + "rev": "b086c1995cdd616fc8d91f46a21e905cc50a1049", "type": "github" }, "original": { @@ -995,7 +783,7 @@ "type": "github" } }, - "cabal-34_3": { + "cabal-34_8": { "flake": false, "locked": { "lastModified": 1640353650, @@ -1012,7 +800,7 @@ "type": "github" } }, - "cabal-34_4": { + "cabal-34_9": { "flake": false, "locked": { "lastModified": 1640353650, @@ -1029,194 +817,41 @@ "type": "github" } }, - "cabal-34_5": { + "cabal-36": { "flake": false, "locked": { - "lastModified": 1622475795, - "narHash": "sha256-chwTL304Cav+7p38d9mcb+egABWmxo2Aq+xgVBgEb/U=", + "lastModified": 1641652457, + "narHash": "sha256-BlFPKP4C4HRUJeAbdembX1Rms1LD380q9s0qVDeoAak=", "owner": "haskell", "repo": "cabal", - "rev": "b086c1995cdd616fc8d91f46a21e905cc50a1049", + "rev": "f27667f8ec360c475027dcaee0138c937477b070", "type": "github" }, "original": { "owner": "haskell", - "ref": "3.4", + "ref": "3.6", "repo": "cabal", "type": "github" } }, - "cabal-34_6": { + "cabal-36_10": { "flake": false, "locked": { - "lastModified": 1622475795, - "narHash": "sha256-chwTL304Cav+7p38d9mcb+egABWmxo2Aq+xgVBgEb/U=", + "lastModified": 1640163203, + "narHash": "sha256-TwDWP2CffT0j40W6zr0J1Qbu+oh3nsF1lUx9446qxZM=", "owner": "haskell", "repo": "cabal", - "rev": "b086c1995cdd616fc8d91f46a21e905cc50a1049", + "rev": "ecf418050c1821f25e2e218f1be94c31e0465df1", "type": "github" }, "original": { "owner": "haskell", - "ref": "3.4", + "ref": "3.6", "repo": "cabal", "type": "github" } }, - "cabal-34_7": { - "flake": false, - "locked": { - "lastModified": 1622475795, - "narHash": "sha256-chwTL304Cav+7p38d9mcb+egABWmxo2Aq+xgVBgEb/U=", - "owner": "haskell", - "repo": "cabal", - "rev": "b086c1995cdd616fc8d91f46a21e905cc50a1049", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.4", - "repo": "cabal", - "type": "github" - } - }, - "cabal-34_8": { - "flake": false, - "locked": { - "lastModified": 1640353650, - "narHash": "sha256-N1t6M3/wqj90AEdRkeC8i923gQYUpzSr8b40qVOZ1Rk=", - "owner": "haskell", - "repo": "cabal", - "rev": "942639c18c0cd8ec53e0a6f8d120091af35312cd", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.4", - "repo": "cabal", - "type": "github" - } - }, - "cabal-34_9": { - "flake": false, - "locked": { - "lastModified": 1640353650, - "narHash": "sha256-N1t6M3/wqj90AEdRkeC8i923gQYUpzSr8b40qVOZ1Rk=", - "owner": "haskell", - "repo": "cabal", - "rev": "942639c18c0cd8ec53e0a6f8d120091af35312cd", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.4", - "repo": "cabal", - "type": "github" - } - }, - "cabal-36": { - "flake": false, - "locked": { - "lastModified": 1641652457, - "narHash": "sha256-BlFPKP4C4HRUJeAbdembX1Rms1LD380q9s0qVDeoAak=", - "owner": "haskell", - "repo": "cabal", - "rev": "f27667f8ec360c475027dcaee0138c937477b070", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.6", - "repo": "cabal", - "type": "github" - } - }, - "cabal-36_10": { - "flake": false, - "locked": { - "lastModified": 1640163203, - "narHash": "sha256-TwDWP2CffT0j40W6zr0J1Qbu+oh3nsF1lUx9446qxZM=", - "owner": "haskell", - "repo": "cabal", - "rev": "ecf418050c1821f25e2e218f1be94c31e0465df1", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.6", - "repo": "cabal", - "type": "github" - } - }, - "cabal-36_11": { - "flake": false, - "locked": { - "lastModified": 1641652457, - "narHash": "sha256-BlFPKP4C4HRUJeAbdembX1Rms1LD380q9s0qVDeoAak=", - "owner": "haskell", - "repo": "cabal", - "rev": "f27667f8ec360c475027dcaee0138c937477b070", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.6", - "repo": "cabal", - "type": "github" - } - }, - "cabal-36_12": { - "flake": false, - "locked": { - "lastModified": 1641652457, - "narHash": "sha256-BlFPKP4C4HRUJeAbdembX1Rms1LD380q9s0qVDeoAak=", - "owner": "haskell", - "repo": "cabal", - "rev": "f27667f8ec360c475027dcaee0138c937477b070", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.6", - "repo": "cabal", - "type": "github" - } - }, - "cabal-36_13": { - "flake": false, - "locked": { - "lastModified": 1640163203, - "narHash": "sha256-TwDWP2CffT0j40W6zr0J1Qbu+oh3nsF1lUx9446qxZM=", - "owner": "haskell", - "repo": "cabal", - "rev": "ecf418050c1821f25e2e218f1be94c31e0465df1", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.6", - "repo": "cabal", - "type": "github" - } - }, - "cabal-36_14": { - "flake": false, - "locked": { - "lastModified": 1640163203, - "narHash": "sha256-TwDWP2CffT0j40W6zr0J1Qbu+oh3nsF1lUx9446qxZM=", - "owner": "haskell", - "repo": "cabal", - "rev": "ecf418050c1821f25e2e218f1be94c31e0465df1", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.6", - "repo": "cabal", - "type": "github" - } - }, - "cabal-36_15": { + "cabal-36_11": { "flake": false, "locked": { "lastModified": 1641652457, @@ -1453,22 +1088,6 @@ } }, "cardano-configurations_3": { - "flake": false, - "locked": { - "lastModified": 1662514199, - "narHash": "sha256-Z71TP5nHA9ch4DRwftz8my5RwYOjH/xA/WlcJqUTtYY=", - "owner": "input-output-hk", - "repo": "cardano-configurations", - "rev": "182b16cb743867b0b24b7af92efbf427b2b09b52", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-configurations", - "type": "github" - } - }, - "cardano-configurations_4": { "flake": false, "locked": { "lastModified": 1667387423, @@ -1577,7 +1196,7 @@ }, "cardano-mainnet-mirror_4": { "inputs": { - "nixpkgs": "nixpkgs_20" + "nixpkgs": "nixpkgs_18" }, "locked": { "lastModified": 1642701714, @@ -1596,7 +1215,7 @@ }, "cardano-mainnet-mirror_5": { "inputs": { - "nixpkgs": "nixpkgs_22" + "nixpkgs": "nixpkgs_20" }, "locked": { "lastModified": 1642701714, @@ -1615,64 +1234,7 @@ }, "cardano-mainnet-mirror_6": { "inputs": { - "nixpkgs": "nixpkgs_23" - }, - "locked": { - "lastModified": 1642701714, - "narHash": "sha256-SR3luE+ePX6U193EKE/KSEuVzWAW0YsyPYDC4hOvALs=", - "owner": "input-output-hk", - "repo": "cardano-mainnet-mirror", - "rev": "819488be9eabbba6aaa7c931559bc584d8071e3d", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "ref": "nix", - "repo": "cardano-mainnet-mirror", - "type": "github" - } - }, - "cardano-mainnet-mirror_7": { - "inputs": { - "nixpkgs": "nixpkgs_28" - }, - "locked": { - "lastModified": 1642701714, - "narHash": "sha256-SR3luE+ePX6U193EKE/KSEuVzWAW0YsyPYDC4hOvALs=", - "owner": "input-output-hk", - "repo": "cardano-mainnet-mirror", - "rev": "819488be9eabbba6aaa7c931559bc584d8071e3d", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "ref": "nix", - "repo": "cardano-mainnet-mirror", - "type": "github" - } - }, - "cardano-mainnet-mirror_8": { - "inputs": { - "nixpkgs": "nixpkgs_30" - }, - "locked": { - "lastModified": 1642701714, - "narHash": "sha256-SR3luE+ePX6U193EKE/KSEuVzWAW0YsyPYDC4hOvALs=", - "owner": "input-output-hk", - "repo": "cardano-mainnet-mirror", - "rev": "819488be9eabbba6aaa7c931559bc584d8071e3d", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "ref": "nix", - "repo": "cardano-mainnet-mirror", - "type": "github" - } - }, - "cardano-mainnet-mirror_9": { - "inputs": { - "nixpkgs": "nixpkgs_31" + "nixpkgs": "nixpkgs_21" }, "locked": { "lastModified": 1642701714, @@ -1745,40 +1307,6 @@ "haskellNix": "haskellNix_8", "iohkNix": "iohkNix_8", "membench": "membench_4", - "nixpkgs": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "cardano-node", - "node-snapshot", - "membench", - "cardano-node-snapshot", - "haskellNix", - "nixpkgs-2105" - ], - "utils": "utils_6" - }, - "locked": { - "lastModified": 1644954571, - "narHash": "sha256-c6MM1mQoS/AnTIrwaRmITK4L4i9lLNtkjOUHiseBtUs=", - "owner": "input-output-hk", - "repo": "cardano-node", - "rev": "30d62b86e7b98da28ef8ad9412e4e00a1ba1231d", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-node", - "rev": "30d62b86e7b98da28ef8ad9412e4e00a1ba1231d", - "type": "github" - } - }, - "cardano-node-snapshot_3": { - "inputs": { - "customConfig": "customConfig_12", - "haskellNix": "haskellNix_12", - "iohkNix": "iohkNix_12", - "membench": "membench_6", "nixpkgs": [ "ctl", "ogmios-nixos", @@ -1789,7 +1317,7 @@ "haskellNix", "nixpkgs-2105" ], - "utils": "utils_11" + "utils": "utils_6" }, "locked": { "lastModified": 1644954571, @@ -1863,18 +1391,16 @@ "cardano-mainnet-mirror": "cardano-mainnet-mirror_4", "cardano-node-workbench": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "blank" ], "customConfig": "customConfig_6", - "flake-compat": "flake-compat_11", + "flake-compat": "flake-compat_9", "hackageNix": "hackageNix_2", "haskellNix": "haskellNix_6", "hostNixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "nixpkgs" ], @@ -1882,16 +1408,14 @@ "nixTools": "nixTools_2", "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "haskellNix", "nixpkgs-unstable" ], "node-measured": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "blank" ], "node-process": "node-process_2", @@ -1914,58 +1438,6 @@ "type": "github" } }, - "cardano-node_4": { - "inputs": { - "cardano-mainnet-mirror": "cardano-mainnet-mirror_7", - "cardano-node-workbench": [ - "ctl", - "ogmios-nixos", - "blank" - ], - "customConfig": "customConfig_10", - "flake-compat": "flake-compat_15", - "hackageNix": "hackageNix_3", - "haskellNix": "haskellNix_10", - "hostNixpkgs": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "nixpkgs" - ], - "iohkNix": "iohkNix_10", - "nixTools": "nixTools_3", - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "haskellNix", - "nixpkgs-unstable" - ], - "node-measured": [ - "ctl", - "ogmios-nixos", - "blank" - ], - "node-process": "node-process_3", - "node-snapshot": "node-snapshot_3", - "plutus-apps": "plutus-apps_4", - "utils": "utils_14" - }, - "locked": { - "lastModified": 1659625017, - "narHash": "sha256-4IrheFeoWfvkZQndEk4fGUkOiOjcVhcyXZ6IqmvkDgg=", - "owner": "input-output-hk", - "repo": "cardano-node", - "rev": "950c4e222086fed5ca53564e642434ce9307b0b9", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "ref": "1.35.3", - "repo": "cardano-node", - "type": "github" - } - }, "cardano-prelude": { "flake": false, "locked": { @@ -2063,86 +1535,6 @@ "type": "github" } }, - "cardano-shell_14": { - "flake": false, - "locked": { - "lastModified": 1608537748, - "narHash": "sha256-PulY1GfiMgKVnBci3ex4ptk2UNYMXqGjJOxcPy2KYT4=", - "owner": "input-output-hk", - "repo": "cardano-shell", - "rev": "9392c75087cb9a3d453998f4230930dea3a95725", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-shell", - "type": "github" - } - }, - "cardano-shell_15": { - "flake": false, - "locked": { - "lastModified": 1608537748, - "narHash": "sha256-PulY1GfiMgKVnBci3ex4ptk2UNYMXqGjJOxcPy2KYT4=", - "owner": "input-output-hk", - "repo": "cardano-shell", - "rev": "9392c75087cb9a3d453998f4230930dea3a95725", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-shell", - "type": "github" - } - }, - "cardano-shell_16": { - "flake": false, - "locked": { - "lastModified": 1608537748, - "narHash": "sha256-PulY1GfiMgKVnBci3ex4ptk2UNYMXqGjJOxcPy2KYT4=", - "owner": "input-output-hk", - "repo": "cardano-shell", - "rev": "9392c75087cb9a3d453998f4230930dea3a95725", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-shell", - "type": "github" - } - }, - "cardano-shell_17": { - "flake": false, - "locked": { - "lastModified": 1608537748, - "narHash": "sha256-PulY1GfiMgKVnBci3ex4ptk2UNYMXqGjJOxcPy2KYT4=", - "owner": "input-output-hk", - "repo": "cardano-shell", - "rev": "9392c75087cb9a3d453998f4230930dea3a95725", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-shell", - "type": "github" - } - }, - "cardano-shell_18": { - "flake": false, - "locked": { - "lastModified": 1608537748, - "narHash": "sha256-PulY1GfiMgKVnBci3ex4ptk2UNYMXqGjJOxcPy2KYT4=", - "owner": "input-output-hk", - "repo": "cardano-shell", - "rev": "9392c75087cb9a3d453998f4230930dea3a95725", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-shell", - "type": "github" - } - }, "cardano-shell_2": { "flake": false, "locked": { @@ -2343,23 +1735,21 @@ "nixpkgs" ], "ogmios": "ogmios", - "ogmios-datum-cache": "ogmios-datum-cache", - "ogmios-datum-cache-nixos": "ogmios-datum-cache-nixos", "ogmios-nixos": "ogmios-nixos", "plutip": "plutip" }, "locked": { - "lastModified": 1669915060, - "narHash": "sha256-UC0CBT67HUdI1bPEdZRABBn43Cj2j1ZE7X9Ejw6EaX0=", + "lastModified": 1670940712, + "narHash": "sha256-jcs8dNDDioeGf2FSfsBkO7/yn035PEDxErBBOf0CJz0=", "owner": "Plutonomicon", "repo": "cardano-transaction-lib", - "rev": "6d6cc0ee04bb7c4f4763c804b4078f5d9705f3f9", + "rev": "ec5f4868e7931f76682d3380f45267f02fd0e015", "type": "github" }, "original": { "owner": "Plutonomicon", "repo": "cardano-transaction-lib", - "rev": "6d6cc0ee04bb7c4f4763c804b4078f5d9705f3f9", + "rev": "ec5f4868e7931f76682d3380f45267f02fd0e015", "type": "github" } }, @@ -2378,66 +1768,6 @@ "type": "github" } }, - "customConfig_10": { - "locked": { - "lastModified": 1630400035, - "narHash": "sha256-MWaVOCzuFwp09wZIW9iHq5wWen5C69I940N1swZLEQ0=", - "owner": "input-output-hk", - "repo": "empty-flake", - "rev": "2040a05b67bf9a669ce17eca56beb14b4206a99a", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "empty-flake", - "type": "github" - } - }, - "customConfig_11": { - "locked": { - "lastModified": 1630400035, - "narHash": "sha256-MWaVOCzuFwp09wZIW9iHq5wWen5C69I940N1swZLEQ0=", - "owner": "input-output-hk", - "repo": "empty-flake", - "rev": "2040a05b67bf9a669ce17eca56beb14b4206a99a", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "empty-flake", - "type": "github" - } - }, - "customConfig_12": { - "locked": { - "lastModified": 1630400035, - "narHash": "sha256-MWaVOCzuFwp09wZIW9iHq5wWen5C69I940N1swZLEQ0=", - "owner": "input-output-hk", - "repo": "empty-flake", - "rev": "2040a05b67bf9a669ce17eca56beb14b4206a99a", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "empty-flake", - "type": "github" - } - }, - "customConfig_13": { - "locked": { - "lastModified": 1630400035, - "narHash": "sha256-MWaVOCzuFwp09wZIW9iHq5wWen5C69I940N1swZLEQ0=", - "owner": "input-output-hk", - "repo": "empty-flake", - "rev": "2040a05b67bf9a669ce17eca56beb14b4206a99a", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "empty-flake", - "type": "github" - } - }, "customConfig_2": { "locked": { "lastModified": 1630400035, @@ -2592,41 +1922,6 @@ } }, "devshell_2": { - "inputs": { - "flake-utils": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "std", - "flake-utils" - ], - "nixpkgs": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "std", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1663445644, - "narHash": "sha256-+xVlcK60x7VY1vRJbNUEAHi17ZuoQxAIH4S4iUFUGBA=", - "owner": "numtide", - "repo": "devshell", - "rev": "e3dc3e21594fe07bdb24bdf1c8657acaa4cb8f66", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "devshell", - "type": "github" - } - }, - "devshell_3": { "inputs": { "flake-utils": [ "ctl", @@ -2693,41 +1988,6 @@ } }, "dmerge_2": { - "inputs": { - "nixlib": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "std", - "nixpkgs" - ], - "yants": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "std", - "yants" - ] - }, - "locked": { - "lastModified": 1659548052, - "narHash": "sha256-fzI2gp1skGA8mQo/FBFrUAtY0GQkAIAaV/V127TJPyY=", - "owner": "divnix", - "repo": "data-merge", - "rev": "d160d18ce7b1a45b88344aa3f13ed1163954b497", - "type": "github" - }, - "original": { - "owner": "divnix", - "repo": "data-merge", - "type": "github" - } - }, - "dmerge_3": { "inputs": { "nixlib": [ "ctl", @@ -2906,16 +2166,15 @@ "flake-compat_11": { "flake": false, "locked": { - "lastModified": 1647532380, - "narHash": "sha256-wswAxyO8AJTH7d5oU8VK82yBCpqwA+p6kLgpb1f1PAY=", + "lastModified": 1635892615, + "narHash": "sha256-harGbMZr4hzat2BWBU+Y5OYXlu+fVz7E4WeQzHi5o8A=", "owner": "input-output-hk", "repo": "flake-compat", - "rev": "7da118186435255a30b5ffeabba9629c344c0bec", + "rev": "eca47d3377946315596da653862d341ee5341318", "type": "github" }, "original": { "owner": "input-output-hk", - "ref": "fixes", "repo": "flake-compat", "type": "github" } @@ -2939,15 +2198,15 @@ "flake-compat_13": { "flake": false, "locked": { - "lastModified": 1635892615, - "narHash": "sha256-harGbMZr4hzat2BWBU+Y5OYXlu+fVz7E4WeQzHi5o8A=", - "owner": "input-output-hk", + "lastModified": 1650374568, + "narHash": "sha256-Z+s0J8/r907g149rllvwhb4pKi8Wam5ij0st8PwAh+E=", + "owner": "edolstra", "repo": "flake-compat", - "rev": "eca47d3377946315596da653862d341ee5341318", + "rev": "b4a34015c698c7793d592d66adbab377907a2be8", "type": "github" }, "original": { - "owner": "input-output-hk", + "owner": "edolstra", "repo": "flake-compat", "type": "github" } @@ -2955,11 +2214,11 @@ "flake-compat_14": { "flake": false, "locked": { - "lastModified": 1650374568, - "narHash": "sha256-Z+s0J8/r907g149rllvwhb4pKi8Wam5ij0st8PwAh+E=", + "lastModified": 1668681692, + "narHash": "sha256-Ht91NGdewz8IQLtWZ9LCeNXMSXHUss+9COoqu6JLmXU=", "owner": "edolstra", "repo": "flake-compat", - "rev": "b4a34015c698c7793d592d66adbab377907a2be8", + "rev": "009399224d5e398d03b22badca40a37ac85412a1", "type": "github" }, "original": { @@ -2968,88 +2227,7 @@ "type": "github" } }, - "flake-compat_15": { - "flake": false, - "locked": { - "lastModified": 1647532380, - "narHash": "sha256-wswAxyO8AJTH7d5oU8VK82yBCpqwA+p6kLgpb1f1PAY=", - "owner": "input-output-hk", - "repo": "flake-compat", - "rev": "7da118186435255a30b5ffeabba9629c344c0bec", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "ref": "fixes", - "repo": "flake-compat", - "type": "github" - } - }, - "flake-compat_16": { - "flake": false, - "locked": { - "lastModified": 1650374568, - "narHash": "sha256-Z+s0J8/r907g149rllvwhb4pKi8Wam5ij0st8PwAh+E=", - "owner": "edolstra", - "repo": "flake-compat", - "rev": "b4a34015c698c7793d592d66adbab377907a2be8", - "type": "github" - }, - "original": { - "owner": "edolstra", - "repo": "flake-compat", - "type": "github" - } - }, - "flake-compat_17": { - "flake": false, - "locked": { - "lastModified": 1635892615, - "narHash": "sha256-harGbMZr4hzat2BWBU+Y5OYXlu+fVz7E4WeQzHi5o8A=", - "owner": "input-output-hk", - "repo": "flake-compat", - "rev": "eca47d3377946315596da653862d341ee5341318", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "flake-compat", - "type": "github" - } - }, - "flake-compat_18": { - "flake": false, - "locked": { - "lastModified": 1650374568, - "narHash": "sha256-Z+s0J8/r907g149rllvwhb4pKi8Wam5ij0st8PwAh+E=", - "owner": "edolstra", - "repo": "flake-compat", - "rev": "b4a34015c698c7793d592d66adbab377907a2be8", - "type": "github" - }, - "original": { - "owner": "edolstra", - "repo": "flake-compat", - "type": "github" - } - }, - "flake-compat_19": { - "flake": false, - "locked": { - "lastModified": 1650374568, - "narHash": "sha256-Z+s0J8/r907g149rllvwhb4pKi8Wam5ij0st8PwAh+E=", - "owner": "edolstra", - "repo": "flake-compat", - "rev": "b4a34015c698c7793d592d66adbab377907a2be8", - "type": "github" - }, - "original": { - "owner": "edolstra", - "repo": "flake-compat", - "type": "github" - } - }, - "flake-compat_2": { + "flake-compat_2": { "flake": false, "locked": { "lastModified": 1641205782, @@ -3065,22 +2243,6 @@ "type": "github" } }, - "flake-compat_20": { - "flake": false, - "locked": { - "lastModified": 1668681692, - "narHash": "sha256-Ht91NGdewz8IQLtWZ9LCeNXMSXHUss+9COoqu6JLmXU=", - "owner": "edolstra", - "repo": "flake-compat", - "rev": "009399224d5e398d03b22badca40a37ac85412a1", - "type": "github" - }, - "original": { - "owner": "edolstra", - "repo": "flake-compat", - "type": "github" - } - }, "flake-compat_3": { "flake": false, "locked": { @@ -3181,15 +2343,16 @@ "flake-compat_9": { "flake": false, "locked": { - "lastModified": 1650374568, - "narHash": "sha256-Z+s0J8/r907g149rllvwhb4pKi8Wam5ij0st8PwAh+E=", - "owner": "edolstra", + "lastModified": 1647532380, + "narHash": "sha256-wswAxyO8AJTH7d5oU8VK82yBCpqwA+p6kLgpb1f1PAY=", + "owner": "input-output-hk", "repo": "flake-compat", - "rev": "b4a34015c698c7793d592d66adbab377907a2be8", + "rev": "7da118186435255a30b5ffeabba9629c344c0bec", "type": "github" }, "original": { - "owner": "edolstra", + "owner": "input-output-hk", + "ref": "fixes", "repo": "flake-compat", "type": "github" } @@ -3467,81 +2630,6 @@ "type": "github" } }, - "flake-utils_25": { - "locked": { - "lastModified": 1644229661, - "narHash": "sha256-1YdnJAsNy69bpcjuoKdOYQX0YxZBiCYZo4Twxerqv7k=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "3cecb5b042f7f209c56ffd8371b2711a290ec797", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "flake-utils_26": { - "locked": { - "lastModified": 1623875721, - "narHash": "sha256-A8BU7bjS5GirpAUv4QA+QnJ4CceLHkcXdRp4xITDB0s=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "f7e004a55b120c02ecb6219596820fcd32ca8772", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "flake-utils_27": { - "locked": { - "lastModified": 1623875721, - "narHash": "sha256-A8BU7bjS5GirpAUv4QA+QnJ4CceLHkcXdRp4xITDB0s=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "f7e004a55b120c02ecb6219596820fcd32ca8772", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "flake-utils_28": { - "locked": { - "lastModified": 1623875721, - "narHash": "sha256-A8BU7bjS5GirpAUv4QA+QnJ4CceLHkcXdRp4xITDB0s=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "f7e004a55b120c02ecb6219596820fcd32ca8772", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "flake-utils_29": { - "locked": { - "lastModified": 1644229661, - "narHash": "sha256-1YdnJAsNy69bpcjuoKdOYQX0YxZBiCYZo4Twxerqv7k=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "3cecb5b042f7f209c56ffd8371b2711a290ec797", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, "flake-utils_3": { "locked": { "lastModified": 1619345332, @@ -3557,51 +2645,6 @@ "type": "github" } }, - "flake-utils_30": { - "locked": { - "lastModified": 1653893745, - "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "1ed9fb1935d260de5fe1c2f7ee0ebaae17ed2fa1", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "flake-utils_31": { - "locked": { - "lastModified": 1659877975, - "narHash": "sha256-zllb8aq3YO3h8B/U0/J1WBgAL8EX5yWf5pMj3G0NAmc=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "c0e246b9b83f637f4681389ecabcb2681b4f3af0", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "flake-utils_32": { - "locked": { - "lastModified": 1653893745, - "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "1ed9fb1935d260de5fe1c2f7ee0ebaae17ed2fa1", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, "flake-utils_4": { "locked": { "lastModified": 1652776076, @@ -3795,7 +2838,7 @@ "type": "github" } }, - "ghc-8.6.5-iohk_14": { + "ghc-8.6.5-iohk_2": { "flake": false, "locked": { "lastModified": 1600920045, @@ -3812,7 +2855,7 @@ "type": "github" } }, - "ghc-8.6.5-iohk_15": { + "ghc-8.6.5-iohk_3": { "flake": false, "locked": { "lastModified": 1600920045, @@ -3829,7 +2872,7 @@ "type": "github" } }, - "ghc-8.6.5-iohk_16": { + "ghc-8.6.5-iohk_4": { "flake": false, "locked": { "lastModified": 1600920045, @@ -3846,7 +2889,7 @@ "type": "github" } }, - "ghc-8.6.5-iohk_17": { + "ghc-8.6.5-iohk_5": { "flake": false, "locked": { "lastModified": 1600920045, @@ -3863,7 +2906,7 @@ "type": "github" } }, - "ghc-8.6.5-iohk_18": { + "ghc-8.6.5-iohk_6": { "flake": false, "locked": { "lastModified": 1600920045, @@ -3880,7 +2923,7 @@ "type": "github" } }, - "ghc-8.6.5-iohk_2": { + "ghc-8.6.5-iohk_7": { "flake": false, "locked": { "lastModified": 1600920045, @@ -3897,7 +2940,7 @@ "type": "github" } }, - "ghc-8.6.5-iohk_3": { + "ghc-8.6.5-iohk_8": { "flake": false, "locked": { "lastModified": 1600920045, @@ -3914,7 +2957,7 @@ "type": "github" } }, - "ghc-8.6.5-iohk_4": { + "ghc-8.6.5-iohk_9": { "flake": false, "locked": { "lastModified": 1600920045, @@ -3931,112 +2974,27 @@ "type": "github" } }, - "ghc-8.6.5-iohk_5": { + "goblins": { "flake": false, "locked": { - "lastModified": 1600920045, - "narHash": "sha256-DO6kxJz248djebZLpSzTGD6s8WRpNI9BTwUeOf5RwY8=", + "lastModified": 1598362523, + "narHash": "sha256-z9ut0y6umDIjJIRjz9KSvKgotuw06/S8QDwOtVdGiJ0=", "owner": "input-output-hk", - "repo": "ghc", - "rev": "95713a6ecce4551240da7c96b6176f980af75cae", + "repo": "goblins", + "rev": "cde90a2b27f79187ca8310b6549331e59595e7ba", "type": "github" }, "original": { "owner": "input-output-hk", - "ref": "release/8.6.5-iohk", - "repo": "ghc", + "repo": "goblins", + "rev": "cde90a2b27f79187ca8310b6549331e59595e7ba", "type": "github" } }, - "ghc-8.6.5-iohk_6": { - "flake": false, - "locked": { - "lastModified": 1600920045, - "narHash": "sha256-DO6kxJz248djebZLpSzTGD6s8WRpNI9BTwUeOf5RwY8=", - "owner": "input-output-hk", - "repo": "ghc", - "rev": "95713a6ecce4551240da7c96b6176f980af75cae", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "ref": "release/8.6.5-iohk", - "repo": "ghc", - "type": "github" - } - }, - "ghc-8.6.5-iohk_7": { - "flake": false, - "locked": { - "lastModified": 1600920045, - "narHash": "sha256-DO6kxJz248djebZLpSzTGD6s8WRpNI9BTwUeOf5RwY8=", - "owner": "input-output-hk", - "repo": "ghc", - "rev": "95713a6ecce4551240da7c96b6176f980af75cae", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "ref": "release/8.6.5-iohk", - "repo": "ghc", - "type": "github" - } - }, - "ghc-8.6.5-iohk_8": { - "flake": false, - "locked": { - "lastModified": 1600920045, - "narHash": "sha256-DO6kxJz248djebZLpSzTGD6s8WRpNI9BTwUeOf5RwY8=", - "owner": "input-output-hk", - "repo": "ghc", - "rev": "95713a6ecce4551240da7c96b6176f980af75cae", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "ref": "release/8.6.5-iohk", - "repo": "ghc", - "type": "github" - } - }, - "ghc-8.6.5-iohk_9": { - "flake": false, - "locked": { - "lastModified": 1600920045, - "narHash": "sha256-DO6kxJz248djebZLpSzTGD6s8WRpNI9BTwUeOf5RwY8=", - "owner": "input-output-hk", - "repo": "ghc", - "rev": "95713a6ecce4551240da7c96b6176f980af75cae", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "ref": "release/8.6.5-iohk", - "repo": "ghc", - "type": "github" - } - }, - "goblins": { - "flake": false, - "locked": { - "lastModified": 1598362523, - "narHash": "sha256-z9ut0y6umDIjJIRjz9KSvKgotuw06/S8QDwOtVdGiJ0=", - "owner": "input-output-hk", - "repo": "goblins", - "rev": "cde90a2b27f79187ca8310b6549331e59595e7ba", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "goblins", - "rev": "cde90a2b27f79187ca8310b6549331e59595e7ba", - "type": "github" - } - }, - "gomod2nix": { - "inputs": { - "nixpkgs": "nixpkgs_15", - "utils": "utils_5" + "gomod2nix": { + "inputs": { + "nixpkgs": "nixpkgs_15", + "utils": "utils_5" }, "locked": { "lastModified": 1655245309, @@ -4054,7 +3012,7 @@ }, "gomod2nix_2": { "inputs": { - "nixpkgs": "nixpkgs_25", + "nixpkgs": "nixpkgs_23", "utils": "utils_10" }, "locked": { @@ -4071,25 +3029,6 @@ "type": "github" } }, - "gomod2nix_3": { - "inputs": { - "nixpkgs": "nixpkgs_33", - "utils": "utils_15" - }, - "locked": { - "lastModified": 1655245309, - "narHash": "sha256-d/YPoQ/vFn1+GTmSdvbSBSTOai61FONxB4+Lt6w/IVI=", - "owner": "tweag", - "repo": "gomod2nix", - "rev": "40d32f82fc60d66402eb0972e6e368aeab3faf58", - "type": "github" - }, - "original": { - "owner": "tweag", - "repo": "gomod2nix", - "type": "github" - } - }, "hackage": { "flake": false, "locked": { @@ -4138,22 +3077,6 @@ "type": "github" } }, - "hackageNix_3": { - "flake": false, - "locked": { - "lastModified": 1656898050, - "narHash": "sha256-jemAb/Wm/uT+QhV12GlyeA5euSWxYzr2HOYoK4MZps0=", - "owner": "input-output-hk", - "repo": "hackage.nix", - "rev": "4f1dd530219ca1165f523ffb2c62213ebede4046", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "hackage.nix", - "type": "github" - } - }, "hackage_10": { "flake": false, "locked": { @@ -4186,70 +3109,6 @@ "type": "github" } }, - "hackage_12": { - "flake": false, - "locked": { - "lastModified": 1643073363, - "narHash": "sha256-66oSXQKEDIOSQ2uKAS9facCX/Zuh/jFgyFDtxEqN9sk=", - "owner": "input-output-hk", - "repo": "hackage.nix", - "rev": "4ef9bd3a32316ce236164c7ebff00ebeb33236e2", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "hackage.nix", - "type": "github" - } - }, - "hackage_13": { - "flake": false, - "locked": { - "lastModified": 1643073363, - "narHash": "sha256-66oSXQKEDIOSQ2uKAS9facCX/Zuh/jFgyFDtxEqN9sk=", - "owner": "input-output-hk", - "repo": "hackage.nix", - "rev": "4ef9bd3a32316ce236164c7ebff00ebeb33236e2", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "hackage.nix", - "type": "github" - } - }, - "hackage_14": { - "flake": false, - "locked": { - "lastModified": 1639098768, - "narHash": "sha256-DZ4sG8FeDxWvBLixrj0jELXjtebZ0SCCPmQW43HNzIE=", - "owner": "input-output-hk", - "repo": "hackage.nix", - "rev": "c7b123af6b0b9b364cab03363504d42dca16a4b5", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "hackage.nix", - "type": "github" - } - }, - "hackage_15": { - "flake": false, - "locked": { - "lastModified": 1667783503, - "narHash": "sha256-25ZZPMQi9YQbXz3tZYPECVUI0FAQkJcDUIA/v8+mo9E=", - "owner": "input-output-hk", - "repo": "hackage.nix", - "rev": "1f77f69e6dd92b5130cbe681b74e8fc0d29d63ff", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "hackage.nix", - "type": "github" - } - }, "hackage_2": { "flake": false, "locked": { @@ -4522,7 +3381,7 @@ "cabal-34": "cabal-34_13", "cabal-36": "cabal-36_11", "cardano-shell": "cardano-shell_13", - "flake-compat": "flake-compat_13", + "flake-compat": "flake-compat_11", "flake-utils": "flake-utils_21", "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_13", "hackage": "hackage_11", @@ -4530,8 +3389,7 @@ "hydra": "hydra_7", "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "nixpkgs" ], "nixpkgs-2003": "nixpkgs-2003_13", @@ -4557,47 +3415,6 @@ "type": "github" } }, - "haskell-nix_5": { - "inputs": { - "HTTP": "HTTP_18", - "cabal-32": "cabal-32_18", - "cabal-34": "cabal-34_18", - "cabal-36": "cabal-36_15", - "cardano-shell": "cardano-shell_18", - "flake-compat": "flake-compat_17", - "flake-utils": "flake-utils_29", - "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_18", - "hackage": "hackage_15", - "hpc-coveralls": "hpc-coveralls_18", - "hydra": "hydra_9", - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "nixpkgs" - ], - "nixpkgs-2003": "nixpkgs-2003_18", - "nixpkgs-2105": "nixpkgs-2105_18", - "nixpkgs-2111": "nixpkgs-2111_18", - "nixpkgs-2205": "nixpkgs-2205_3", - "nixpkgs-unstable": "nixpkgs-unstable_18", - "old-ghc-nix": "old-ghc-nix_18", - "stackage": "stackage_18", - "tullia": "tullia_3" - }, - "locked": { - "lastModified": 1667783630, - "narHash": "sha256-IzbvNxsOVxHJGY70qAzaEOPmz4Fw93+4qLFd2on/ZAc=", - "owner": "input-output-hk", - "repo": "haskell.nix", - "rev": "f1f330065199dc4eca017bc21de0c67bc46df393", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "haskell.nix", - "type": "github" - } - }, "haskellNix": { "inputs": { "HTTP": "HTTP_2", @@ -4637,36 +3454,36 @@ "type": "github" } }, - "haskellNix_10": { + "haskellNix_2": { "inputs": { - "HTTP": "HTTP_14", - "cabal-32": "cabal-32_14", - "cabal-34": "cabal-34_14", - "cabal-36": "cabal-36_12", - "cardano-shell": "cardano-shell_14", - "flake-utils": "flake-utils_25", - "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_14", + "HTTP": "HTTP_4", + "cabal-32": "cabal-32_4", + "cabal-34": "cabal-34_4", + "cabal-36": "cabal-36_4", + "cardano-shell": "cardano-shell_4", + "flake-utils": "flake-utils_9", + "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_4", "hackage": [ "ctl", - "ogmios-nixos", + "ogmios", "cardano-node", "hackageNix" ], - "hpc-coveralls": "hpc-coveralls_14", - "hydra": "hydra_8", - "nix-tools": "nix-tools_12", + "hpc-coveralls": "hpc-coveralls_4", + "hydra": "hydra_4", + "nix-tools": "nix-tools_4", "nixpkgs": [ "ctl", - "ogmios-nixos", + "ogmios", "cardano-node", "nixpkgs" ], - "nixpkgs-2003": "nixpkgs-2003_14", - "nixpkgs-2105": "nixpkgs-2105_14", - "nixpkgs-2111": "nixpkgs-2111_14", - "nixpkgs-unstable": "nixpkgs-unstable_14", - "old-ghc-nix": "old-ghc-nix_14", - "stackage": "stackage_14" + "nixpkgs-2003": "nixpkgs-2003_4", + "nixpkgs-2105": "nixpkgs-2105_4", + "nixpkgs-2111": "nixpkgs-2111_4", + "nixpkgs-unstable": "nixpkgs-unstable_4", + "old-ghc-nix": "old-ghc-nix_4", + "stackage": "stackage_4" }, "locked": { "lastModified": 1656898207, @@ -4682,31 +3499,31 @@ "type": "github" } }, - "haskellNix_11": { + "haskellNix_3": { "inputs": { - "HTTP": "HTTP_15", - "cabal-32": "cabal-32_15", - "cabal-34": "cabal-34_15", - "cabal-36": "cabal-36_13", - "cardano-shell": "cardano-shell_15", - "flake-utils": "flake-utils_26", - "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_15", - "hackage": "hackage_12", - "hpc-coveralls": "hpc-coveralls_15", - "nix-tools": "nix-tools_13", + "HTTP": "HTTP_5", + "cabal-32": "cabal-32_5", + "cabal-34": "cabal-34_5", + "cabal-36": "cabal-36_5", + "cardano-shell": "cardano-shell_5", + "flake-utils": "flake-utils_10", + "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_5", + "hackage": "hackage_4", + "hpc-coveralls": "hpc-coveralls_5", + "nix-tools": "nix-tools_5", "nixpkgs": [ "ctl", - "ogmios-nixos", + "ogmios", "cardano-node", "node-snapshot", "nixpkgs" ], - "nixpkgs-2003": "nixpkgs-2003_15", - "nixpkgs-2105": "nixpkgs-2105_15", - "nixpkgs-2111": "nixpkgs-2111_15", - "nixpkgs-unstable": "nixpkgs-unstable_15", - "old-ghc-nix": "old-ghc-nix_15", - "stackage": "stackage_15" + "nixpkgs-2003": "nixpkgs-2003_5", + "nixpkgs-2105": "nixpkgs-2105_5", + "nixpkgs-2111": "nixpkgs-2111_5", + "nixpkgs-unstable": "nixpkgs-unstable_5", + "old-ghc-nix": "old-ghc-nix_5", + "stackage": "stackage_5" }, "locked": { "lastModified": 1643073543, @@ -4722,33 +3539,33 @@ "type": "github" } }, - "haskellNix_12": { + "haskellNix_4": { "inputs": { - "HTTP": "HTTP_16", - "cabal-32": "cabal-32_16", - "cabal-34": "cabal-34_16", - "cabal-36": "cabal-36_14", - "cardano-shell": "cardano-shell_16", - "flake-utils": "flake-utils_27", - "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_16", - "hackage": "hackage_13", - "hpc-coveralls": "hpc-coveralls_16", - "nix-tools": "nix-tools_14", + "HTTP": "HTTP_6", + "cabal-32": "cabal-32_6", + "cabal-34": "cabal-34_6", + "cabal-36": "cabal-36_6", + "cardano-shell": "cardano-shell_6", + "flake-utils": "flake-utils_11", + "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_6", + "hackage": "hackage_5", + "hpc-coveralls": "hpc-coveralls_6", + "nix-tools": "nix-tools_6", "nixpkgs": [ "ctl", - "ogmios-nixos", + "ogmios", "cardano-node", "node-snapshot", "membench", "cardano-node-snapshot", "nixpkgs" ], - "nixpkgs-2003": "nixpkgs-2003_16", - "nixpkgs-2105": "nixpkgs-2105_16", - "nixpkgs-2111": "nixpkgs-2111_16", - "nixpkgs-unstable": "nixpkgs-unstable_16", - "old-ghc-nix": "old-ghc-nix_16", - "stackage": "stackage_16" + "nixpkgs-2003": "nixpkgs-2003_6", + "nixpkgs-2105": "nixpkgs-2105_6", + "nixpkgs-2111": "nixpkgs-2111_6", + "nixpkgs-unstable": "nixpkgs-unstable_6", + "old-ghc-nix": "old-ghc-nix_6", + "stackage": "stackage_6" }, "locked": { "lastModified": 1643073543, @@ -4764,174 +3581,7 @@ "type": "github" } }, - "haskellNix_13": { - "inputs": { - "HTTP": "HTTP_17", - "cabal-32": "cabal-32_17", - "cabal-34": "cabal-34_17", - "cardano-shell": "cardano-shell_17", - "flake-utils": "flake-utils_28", - "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_17", - "hackage": "hackage_14", - "hpc-coveralls": "hpc-coveralls_17", - "nix-tools": "nix-tools_15", - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "plutus-example", - "nixpkgs" - ], - "nixpkgs-2003": "nixpkgs-2003_17", - "nixpkgs-2105": "nixpkgs-2105_17", - "nixpkgs-2111": "nixpkgs-2111_17", - "nixpkgs-unstable": "nixpkgs-unstable_17", - "old-ghc-nix": "old-ghc-nix_17", - "stackage": "stackage_17" - }, - "locked": { - "lastModified": 1639098904, - "narHash": "sha256-7VrCNEaKGLm4pTOS11dt1dRL2033oqrNCfal0uONsqA=", - "owner": "input-output-hk", - "repo": "haskell.nix", - "rev": "b18c6ce0867fee77f12ecf41dc6c67f7a59d9826", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "haskell.nix", - "type": "github" - } - }, - "haskellNix_2": { - "inputs": { - "HTTP": "HTTP_4", - "cabal-32": "cabal-32_4", - "cabal-34": "cabal-34_4", - "cabal-36": "cabal-36_4", - "cardano-shell": "cardano-shell_4", - "flake-utils": "flake-utils_9", - "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_4", - "hackage": [ - "ctl", - "ogmios", - "cardano-node", - "hackageNix" - ], - "hpc-coveralls": "hpc-coveralls_4", - "hydra": "hydra_4", - "nix-tools": "nix-tools_4", - "nixpkgs": [ - "ctl", - "ogmios", - "cardano-node", - "nixpkgs" - ], - "nixpkgs-2003": "nixpkgs-2003_4", - "nixpkgs-2105": "nixpkgs-2105_4", - "nixpkgs-2111": "nixpkgs-2111_4", - "nixpkgs-unstable": "nixpkgs-unstable_4", - "old-ghc-nix": "old-ghc-nix_4", - "stackage": "stackage_4" - }, - "locked": { - "lastModified": 1656898207, - "narHash": "sha256-hshNfCnrmhIvM4T+O0/JRZymsHmq9YiIJ4bpzNVTD98=", - "owner": "input-output-hk", - "repo": "haskell.nix", - "rev": "21230476adfef5fa77fb19fbda396f22006a02bc", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "haskell.nix", - "type": "github" - } - }, - "haskellNix_3": { - "inputs": { - "HTTP": "HTTP_5", - "cabal-32": "cabal-32_5", - "cabal-34": "cabal-34_5", - "cabal-36": "cabal-36_5", - "cardano-shell": "cardano-shell_5", - "flake-utils": "flake-utils_10", - "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_5", - "hackage": "hackage_4", - "hpc-coveralls": "hpc-coveralls_5", - "nix-tools": "nix-tools_5", - "nixpkgs": [ - "ctl", - "ogmios", - "cardano-node", - "node-snapshot", - "nixpkgs" - ], - "nixpkgs-2003": "nixpkgs-2003_5", - "nixpkgs-2105": "nixpkgs-2105_5", - "nixpkgs-2111": "nixpkgs-2111_5", - "nixpkgs-unstable": "nixpkgs-unstable_5", - "old-ghc-nix": "old-ghc-nix_5", - "stackage": "stackage_5" - }, - "locked": { - "lastModified": 1643073543, - "narHash": "sha256-g2l/KDWzMRTFRugNVcx3CPZeyA5BNcH9/zDiqFpprB4=", - "owner": "input-output-hk", - "repo": "haskell.nix", - "rev": "14f740c7c8f535581c30b1697018e389680e24cb", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "haskell.nix", - "type": "github" - } - }, - "haskellNix_4": { - "inputs": { - "HTTP": "HTTP_6", - "cabal-32": "cabal-32_6", - "cabal-34": "cabal-34_6", - "cabal-36": "cabal-36_6", - "cardano-shell": "cardano-shell_6", - "flake-utils": "flake-utils_11", - "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_6", - "hackage": "hackage_5", - "hpc-coveralls": "hpc-coveralls_6", - "nix-tools": "nix-tools_6", - "nixpkgs": [ - "ctl", - "ogmios", - "cardano-node", - "node-snapshot", - "membench", - "cardano-node-snapshot", - "nixpkgs" - ], - "nixpkgs-2003": "nixpkgs-2003_6", - "nixpkgs-2105": "nixpkgs-2105_6", - "nixpkgs-2111": "nixpkgs-2111_6", - "nixpkgs-unstable": "nixpkgs-unstable_6", - "old-ghc-nix": "old-ghc-nix_6", - "stackage": "stackage_6" - }, - "locked": { - "lastModified": 1643073543, - "narHash": "sha256-g2l/KDWzMRTFRugNVcx3CPZeyA5BNcH9/zDiqFpprB4=", - "owner": "input-output-hk", - "repo": "haskell.nix", - "rev": "14f740c7c8f535581c30b1697018e389680e24cb", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "haskell.nix", - "type": "github" - } - }, - "haskellNix_5": { + "haskellNix_5": { "inputs": { "HTTP": "HTTP_7", "cabal-32": "cabal-32_7", @@ -4982,8 +3632,7 @@ "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_9", "hackage": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "hackageNix" ], @@ -4992,8 +3641,7 @@ "nix-tools": "nix-tools_8", "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "nixpkgs" ], @@ -5032,8 +3680,7 @@ "nix-tools": "nix-tools_9", "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "nixpkgs" @@ -5073,8 +3720,7 @@ "nix-tools": "nix-tools_10", "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "membench", @@ -5115,8 +3761,7 @@ "nix-tools": "nix-tools_11", "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "plutus-example", @@ -5240,86 +3885,6 @@ "type": "github" } }, - "hpc-coveralls_14": { - "flake": false, - "locked": { - "lastModified": 1607498076, - "narHash": "sha256-8uqsEtivphgZWYeUo5RDUhp6bO9j2vaaProQxHBltQk=", - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "rev": "14df0f7d229f4cd2e79f8eabb1a740097fdfa430", - "type": "github" - }, - "original": { - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "type": "github" - } - }, - "hpc-coveralls_15": { - "flake": false, - "locked": { - "lastModified": 1607498076, - "narHash": "sha256-8uqsEtivphgZWYeUo5RDUhp6bO9j2vaaProQxHBltQk=", - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "rev": "14df0f7d229f4cd2e79f8eabb1a740097fdfa430", - "type": "github" - }, - "original": { - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "type": "github" - } - }, - "hpc-coveralls_16": { - "flake": false, - "locked": { - "lastModified": 1607498076, - "narHash": "sha256-8uqsEtivphgZWYeUo5RDUhp6bO9j2vaaProQxHBltQk=", - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "rev": "14df0f7d229f4cd2e79f8eabb1a740097fdfa430", - "type": "github" - }, - "original": { - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "type": "github" - } - }, - "hpc-coveralls_17": { - "flake": false, - "locked": { - "lastModified": 1607498076, - "narHash": "sha256-8uqsEtivphgZWYeUo5RDUhp6bO9j2vaaProQxHBltQk=", - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "rev": "14df0f7d229f4cd2e79f8eabb1a740097fdfa430", - "type": "github" - }, - "original": { - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "type": "github" - } - }, - "hpc-coveralls_18": { - "flake": false, - "locked": { - "lastModified": 1607498076, - "narHash": "sha256-8uqsEtivphgZWYeUo5RDUhp6bO9j2vaaProQxHBltQk=", - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "rev": "14df0f7d229f4cd2e79f8eabb1a740097fdfa430", - "type": "github" - }, - "original": { - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "type": "github" - } - }, "hpc-coveralls_2": { "flake": false, "locked": { @@ -5596,8 +4161,7 @@ "nix": "nix_6", "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "haskellNix", "hydra", @@ -5623,8 +4187,7 @@ "nix": "nix_7", "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "haskell-nix", "hydra", "nix", @@ -5644,59 +4207,8 @@ "type": "indirect" } }, - "hydra_8": { - "inputs": { - "nix": "nix_8", - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "haskellNix", - "hydra", - "nix", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1646878427, - "narHash": "sha256-KtbrofMtN8GlM7D+n90kixr7QpSlVmdN+vK5CA/aRzc=", - "owner": "NixOS", - "repo": "hydra", - "rev": "28b682b85b7efc5cf7974065792a1f22203a5927", - "type": "github" - }, - "original": { - "id": "hydra", - "type": "indirect" - } - }, - "hydra_9": { - "inputs": { - "nix": "nix_9", - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "haskell-nix", - "hydra", - "nix", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1646878427, - "narHash": "sha256-KtbrofMtN8GlM7D+n90kixr7QpSlVmdN+vK5CA/aRzc=", - "owner": "NixOS", - "repo": "hydra", - "rev": "28b682b85b7efc5cf7974065792a1f22203a5927", - "type": "github" - }, - "original": { - "id": "hydra", - "type": "indirect" - } - }, - "hysterical-screams": { - "flake": false, + "hysterical-screams": { + "flake": false, "locked": { "lastModified": 1654007733, "narHash": "sha256-d4N3rUzg45BUs5Lx/kK7vXYsLMNoO15dlzo7t8lGIXA=", @@ -5828,30 +4340,6 @@ } }, "iohk-nix_4": { - "inputs": { - "nixpkgs": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1649070135, - "narHash": "sha256-UFKqcOSdPWk3TYUCPHF22p1zf7aXQpCmmgf7UMg7fWA=", - "owner": "input-output-hk", - "repo": "iohk-nix", - "rev": "cecab9c71d1064f05f1615eead56ac0b9196bc20", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "iohk-nix", - "rev": "cecab9c71d1064f05f1615eead56ac0b9196bc20", - "type": "github" - } - }, - "iohk-nix_5": { "inputs": { "nixpkgs": [ "ctl", @@ -5896,104 +4384,6 @@ "type": "github" } }, - "iohkNix_10": { - "inputs": { - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1653579289, - "narHash": "sha256-wveDdPsgB/3nAGAdFaxrcgLEpdi0aJ5kEVNtI+YqVfo=", - "owner": "input-output-hk", - "repo": "iohk-nix", - "rev": "edb2d2df2ebe42bbdf03a0711115cf6213c9d366", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "iohk-nix", - "type": "github" - } - }, - "iohkNix_11": { - "inputs": { - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1631778944, - "narHash": "sha256-N5eCcUYtZ5kUOl/JJGjx6ZzhA3uIn1itDRTiRV+3jLw=", - "owner": "input-output-hk", - "repo": "iohk-nix", - "rev": "db2c75a09c696271194bb3ef25ec8e9839b594b7", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "iohk-nix", - "type": "github" - } - }, - "iohkNix_12": { - "inputs": { - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "membench", - "cardano-node-snapshot", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1631778944, - "narHash": "sha256-N5eCcUYtZ5kUOl/JJGjx6ZzhA3uIn1itDRTiRV+3jLw=", - "owner": "input-output-hk", - "repo": "iohk-nix", - "rev": "db2c75a09c696271194bb3ef25ec8e9839b594b7", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "iohk-nix", - "type": "github" - } - }, - "iohkNix_13": { - "inputs": { - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "plutus-example", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1633964277, - "narHash": "sha256-7G/BK514WiMRr90EswNBthe8SmH9tjPaTBba/RW/VA8=", - "owner": "input-output-hk", - "repo": "iohk-nix", - "rev": "1e51437aac8a0e49663cb21e781f34163c81ebfb", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "iohk-nix", - "type": "github" - } - }, "iohkNix_2": { "inputs": { "nixpkgs": [ @@ -6096,8 +4486,7 @@ "inputs": { "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "nixpkgs" ] @@ -6120,8 +4509,7 @@ "inputs": { "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "nixpkgs" @@ -6145,8 +4533,7 @@ "inputs": { "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "membench", @@ -6172,8 +4559,7 @@ "inputs": { "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "plutus-example", @@ -6354,38 +4740,6 @@ "type": "github" } }, - "lowdown-src_8": { - "flake": false, - "locked": { - "lastModified": 1633514407, - "narHash": "sha256-Dw32tiMjdK9t3ETl5fzGrutQTzh2rufgZV4A/BbxuD4=", - "owner": "kristapsdz", - "repo": "lowdown", - "rev": "d2c2b44ff6c27b936ec27358a2653caaef8f73b8", - "type": "github" - }, - "original": { - "owner": "kristapsdz", - "repo": "lowdown", - "type": "github" - } - }, - "lowdown-src_9": { - "flake": false, - "locked": { - "lastModified": 1633514407, - "narHash": "sha256-Dw32tiMjdK9t3ETl5fzGrutQTzh2rufgZV4A/BbxuD4=", - "owner": "kristapsdz", - "repo": "lowdown", - "rev": "d2c2b44ff6c27b936ec27358a2653caaef8f73b8", - "type": "github" - }, - "original": { - "owner": "kristapsdz", - "repo": "lowdown", - "type": "github" - } - }, "mdbook-kroki-preprocessor": { "flake": false, "locked": { @@ -6418,22 +4772,6 @@ "type": "github" } }, - "mdbook-kroki-preprocessor_3": { - "flake": false, - "locked": { - "lastModified": 1661755005, - "narHash": "sha256-1TJuUzfyMycWlOQH67LR63/ll2GDZz25I3JfScy/Jnw=", - "owner": "JoelCourtney", - "repo": "mdbook-kroki-preprocessor", - "rev": "93adb5716d035829efed27f65f2f0833a7d3e76f", - "type": "github" - }, - "original": { - "owner": "JoelCourtney", - "repo": "mdbook-kroki-preprocessor", - "type": "github" - } - }, "membench": { "inputs": { "cardano-mainnet-mirror": "cardano-mainnet-mirror_2", @@ -6530,23 +4868,20 @@ "cardano-mainnet-mirror": "cardano-mainnet-mirror_5", "cardano-node-measured": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot" ], "cardano-node-process": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot" ], "cardano-node-snapshot": "cardano-node-snapshot_2", "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "nixpkgs" @@ -6572,8 +4907,7 @@ "cardano-mainnet-mirror": "cardano-mainnet-mirror_6", "cardano-node-measured": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "membench", @@ -6581,8 +4915,7 @@ ], "cardano-node-process": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "membench", @@ -6590,8 +4923,7 @@ ], "cardano-node-snapshot": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "membench", @@ -6599,8 +4931,7 @@ ], "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "membench", @@ -6623,153 +4954,35 @@ "type": "github" } }, - "membench_5": { + "n2c": { "inputs": { - "cardano-mainnet-mirror": "cardano-mainnet-mirror_8", - "cardano-node-measured": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot" - ], - "cardano-node-process": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot" - ], - "cardano-node-snapshot": "cardano-node-snapshot_3", + "flake-utils": "flake-utils_16", "nixpkgs": [ "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot", + "ogmios", + "haskell-nix", + "tullia", + "std", "nixpkgs" - ], - "ouroboros-network": "ouroboros-network_7" + ] }, "locked": { - "lastModified": 1645070579, - "narHash": "sha256-AxL6tCOnzYnE6OquoFzj+X1bLDr1PQx3d8/vXm+rbfA=", - "owner": "input-output-hk", - "repo": "cardano-memory-benchmark", - "rev": "65643e000186de1335e24ec89159db8ba85e1c1a", + "lastModified": 1665039323, + "narHash": "sha256-SAh3ZjFGsaCI8FRzXQyp56qcGdAqgKEfJWPCQ0Sr7tQ=", + "owner": "nlewo", + "repo": "nix2container", + "rev": "b008fe329ffb59b67bf9e7b08ede6ee792f2741a", "type": "github" }, "original": { - "owner": "input-output-hk", - "repo": "cardano-memory-benchmark", + "owner": "nlewo", + "repo": "nix2container", "type": "github" } }, - "membench_6": { - "inputs": { - "cardano-mainnet-mirror": "cardano-mainnet-mirror_9", - "cardano-node-measured": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "membench", - "cardano-node-snapshot" - ], - "cardano-node-process": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "membench", - "cardano-node-snapshot" - ], - "cardano-node-snapshot": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "membench", - "cardano-node-snapshot" - ], - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "membench", - "cardano-node-snapshot", - "nixpkgs" - ], - "ouroboros-network": "ouroboros-network_6" - }, - "locked": { - "lastModified": 1644547122, - "narHash": "sha256-8nWK+ScMACvRQLbA27gwXNoZver+Wx/cF7V37044koY=", - "owner": "input-output-hk", - "repo": "cardano-memory-benchmark", - "rev": "9d8ff4b9394de0421ee95caa511d01163de88b77", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-memory-benchmark", - "type": "github" - } - }, - "n2c": { - "inputs": { - "flake-utils": "flake-utils_16", - "nixpkgs": [ - "ctl", - "ogmios", - "haskell-nix", - "tullia", - "std", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1665039323, - "narHash": "sha256-SAh3ZjFGsaCI8FRzXQyp56qcGdAqgKEfJWPCQ0Sr7tQ=", - "owner": "nlewo", - "repo": "nix2container", - "rev": "b008fe329ffb59b67bf9e7b08ede6ee792f2741a", - "type": "github" - }, - "original": { - "owner": "nlewo", - "repo": "nix2container", - "type": "github" - } - }, - "n2c_2": { + "n2c_2": { "inputs": { "flake-utils": "flake-utils_24", - "nixpkgs": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "std", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1665039323, - "narHash": "sha256-SAh3ZjFGsaCI8FRzXQyp56qcGdAqgKEfJWPCQ0Sr7tQ=", - "owner": "nlewo", - "repo": "nix2container", - "rev": "b008fe329ffb59b67bf9e7b08ede6ee792f2741a", - "type": "github" - }, - "original": { - "owner": "nlewo", - "repo": "nix2container", - "type": "github" - } - }, - "n2c_3": { - "inputs": { - "flake-utils": "flake-utils_32", "nixpkgs": [ "ctl", "ogmios-nixos", @@ -6857,51 +5070,7 @@ }, "nix-nomad_2": { "inputs": { - "flake-compat": "flake-compat_14", - "flake-utils": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "nix2container", - "flake-utils" - ], - "gomod2nix": "gomod2nix_2", - "nixpkgs": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "nixpkgs" - ], - "nixpkgs-lib": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1658277770, - "narHash": "sha256-T/PgG3wUn8Z2rnzfxf2VqlR1CBjInPE0l1yVzXxPnt0=", - "owner": "tristanpemble", - "repo": "nix-nomad", - "rev": "054adcbdd0a836ae1c20951b67ed549131fd2d70", - "type": "github" - }, - "original": { - "owner": "tristanpemble", - "repo": "nix-nomad", - "type": "github" - } - }, - "nix-nomad_3": { - "inputs": { - "flake-compat": "flake-compat_18", + "flake-compat": "flake-compat_12", "flake-utils": [ "ctl", "ogmios-nixos", @@ -6910,7 +5079,7 @@ "nix2container", "flake-utils" ], - "gomod2nix": "gomod2nix_3", + "gomod2nix": "gomod2nix_2", "nixpkgs": [ "ctl", "ogmios-nixos", @@ -6988,70 +5157,6 @@ "type": "github" } }, - "nix-tools_12": { - "flake": false, - "locked": { - "lastModified": 1649424170, - "narHash": "sha256-XgKXWispvv5RCvZzPb+p7e6Hy3LMuRjafKMl7kXzxGw=", - "owner": "input-output-hk", - "repo": "nix-tools", - "rev": "e109c94016e3b6e0db7ed413c793e2d4bdb24aa7", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "nix-tools", - "type": "github" - } - }, - "nix-tools_13": { - "flake": false, - "locked": { - "lastModified": 1636018067, - "narHash": "sha256-ng306fkuwr6V/malWtt3979iAC4yMVDDH2ViwYB6sQE=", - "owner": "input-output-hk", - "repo": "nix-tools", - "rev": "ed5bd7215292deba55d6ab7a4e8c21f8b1564dda", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "nix-tools", - "type": "github" - } - }, - "nix-tools_14": { - "flake": false, - "locked": { - "lastModified": 1636018067, - "narHash": "sha256-ng306fkuwr6V/malWtt3979iAC4yMVDDH2ViwYB6sQE=", - "owner": "input-output-hk", - "repo": "nix-tools", - "rev": "ed5bd7215292deba55d6ab7a4e8c21f8b1564dda", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "nix-tools", - "type": "github" - } - }, - "nix-tools_15": { - "flake": false, - "locked": { - "lastModified": 1636018067, - "narHash": "sha256-ng306fkuwr6V/malWtt3979iAC4yMVDDH2ViwYB6sQE=", - "owner": "input-output-hk", - "repo": "nix-tools", - "rev": "ed5bd7215292deba55d6ab7a4e8c21f8b1564dda", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "nix-tools", - "type": "github" - } - }, "nix-tools_2": { "flake": false, "locked": { @@ -7202,26 +5307,7 @@ "nix2container_2": { "inputs": { "flake-utils": "flake-utils_22", - "nixpkgs": "nixpkgs_26" - }, - "locked": { - "lastModified": 1658567952, - "narHash": "sha256-XZ4ETYAMU7XcpEeAFP3NOl9yDXNuZAen/aIJ84G+VgA=", - "owner": "nlewo", - "repo": "nix2container", - "rev": "60bb43d405991c1378baf15a40b5811a53e32ffa", - "type": "github" - }, - "original": { - "owner": "nlewo", - "repo": "nix2container", - "type": "github" - } - }, - "nix2container_3": { - "inputs": { - "flake-utils": "flake-utils_30", - "nixpkgs": "nixpkgs_34" + "nixpkgs": "nixpkgs_24" }, "locked": { "lastModified": 1658567952, @@ -7269,22 +5355,6 @@ "type": "github" } }, - "nixTools_3": { - "flake": false, - "locked": { - "lastModified": 1649424170, - "narHash": "sha256-XgKXWispvv5RCvZzPb+p7e6Hy3LMuRjafKMl7kXzxGw=", - "owner": "input-output-hk", - "repo": "nix-tools", - "rev": "e109c94016e3b6e0db7ed413c793e2d4bdb24aa7", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "nix-tools", - "type": "github" - } - }, "nix_2": { "inputs": { "lowdown-src": "lowdown-src_2", @@ -7372,7 +5442,7 @@ "nix_6": { "inputs": { "lowdown-src": "lowdown-src_6", - "nixpkgs": "nixpkgs_21", + "nixpkgs": "nixpkgs_19", "nixpkgs-regression": "nixpkgs-regression_6" }, "locked": { @@ -7393,7 +5463,7 @@ "nix_7": { "inputs": { "lowdown-src": "lowdown-src_7", - "nixpkgs": "nixpkgs_24", + "nixpkgs": "nixpkgs_22", "nixpkgs-regression": "nixpkgs-regression_7" }, "locked": { @@ -7411,48 +5481,6 @@ "type": "github" } }, - "nix_8": { - "inputs": { - "lowdown-src": "lowdown-src_8", - "nixpkgs": "nixpkgs_29", - "nixpkgs-regression": "nixpkgs-regression_8" - }, - "locked": { - "lastModified": 1643066034, - "narHash": "sha256-xEPeMcNJVOeZtoN+d+aRwolpW8mFSEQx76HTRdlhPhg=", - "owner": "NixOS", - "repo": "nix", - "rev": "a1cd7e58606a41fcf62bf8637804cf8306f17f62", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "2.6.0", - "repo": "nix", - "type": "github" - } - }, - "nix_9": { - "inputs": { - "lowdown-src": "lowdown-src_9", - "nixpkgs": "nixpkgs_32", - "nixpkgs-regression": "nixpkgs-regression_9" - }, - "locked": { - "lastModified": 1643066034, - "narHash": "sha256-xEPeMcNJVOeZtoN+d+aRwolpW8mFSEQx76HTRdlhPhg=", - "owner": "NixOS", - "repo": "nix", - "rev": "a1cd7e58606a41fcf62bf8637804cf8306f17f62", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "2.6.0", - "repo": "nix", - "type": "github" - } - }, "nixago": { "inputs": { "flake-utils": [ @@ -7495,50 +5523,6 @@ } }, "nixago_2": { - "inputs": { - "flake-utils": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "std", - "flake-utils" - ], - "nixago-exts": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "std", - "blank" - ], - "nixpkgs": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "std", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1661824785, - "narHash": "sha256-/PnwdWoO/JugJZHtDUioQp3uRiWeXHUdgvoyNbXesz8=", - "owner": "nix-community", - "repo": "nixago", - "rev": "8c1f9e5f1578d4b2ea989f618588d62a335083c3", - "type": "github" - }, - "original": { - "owner": "nix-community", - "repo": "nixago", - "type": "github" - } - }, - "nixago_3": { "inputs": { "flake-utils": [ "ctl", @@ -7674,86 +5658,6 @@ "type": "github" } }, - "nixpkgs-2003_14": { - "locked": { - "lastModified": 1620055814, - "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-20.03-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2003_15": { - "locked": { - "lastModified": 1620055814, - "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-20.03-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2003_16": { - "locked": { - "lastModified": 1620055814, - "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-20.03-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2003_17": { - "locked": { - "lastModified": 1620055814, - "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-20.03-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2003_18": { - "locked": { - "lastModified": 1620055814, - "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-20.03-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, "nixpkgs-2003_2": { "locked": { "lastModified": 1620055814, @@ -7786,87 +5690,7 @@ "type": "github" } }, - "nixpkgs-2003_4": { - "locked": { - "lastModified": 1620055814, - "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-20.03-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2003_5": { - "locked": { - "lastModified": 1620055814, - "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-20.03-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2003_6": { - "locked": { - "lastModified": 1620055814, - "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-20.03-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2003_7": { - "locked": { - "lastModified": 1620055814, - "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-20.03-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2003_8": { - "locked": { - "lastModified": 1620055814, - "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-20.03-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2003_9": { + "nixpkgs-2003_4": { "locked": { "lastModified": 1620055814, "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", @@ -7882,87 +5706,87 @@ "type": "github" } }, - "nixpkgs-2105": { + "nixpkgs-2003_5": { "locked": { - "lastModified": 1645296114, - "narHash": "sha256-y53N7TyIkXsjMpOG7RhvqJFGDacLs9HlyHeSTBioqYU=", + "lastModified": 1620055814, + "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "530a53dcbc9437363471167a5e4762c5fcfa34a1", + "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", "type": "github" }, "original": { "owner": "NixOS", - "ref": "nixpkgs-21.05-darwin", + "ref": "nixpkgs-20.03-darwin", "repo": "nixpkgs", "type": "github" } }, - "nixpkgs-2105_10": { + "nixpkgs-2003_6": { "locked": { - "lastModified": 1640283157, - "narHash": "sha256-6Ddfop+rKE+Gl9Tjp9YIrkfoYPzb8F80ergdjcq3/MY=", + "lastModified": 1620055814, + "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "dde1557825c5644c869c5efc7448dc03722a8f09", + "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", "type": "github" }, "original": { "owner": "NixOS", - "ref": "nixpkgs-21.05-darwin", + "ref": "nixpkgs-20.03-darwin", "repo": "nixpkgs", "type": "github" } }, - "nixpkgs-2105_11": { + "nixpkgs-2003_7": { "locked": { - "lastModified": 1640283157, - "narHash": "sha256-6Ddfop+rKE+Gl9Tjp9YIrkfoYPzb8F80ergdjcq3/MY=", + "lastModified": 1620055814, + "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "dde1557825c5644c869c5efc7448dc03722a8f09", + "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", "type": "github" }, "original": { "owner": "NixOS", - "ref": "nixpkgs-21.05-darwin", + "ref": "nixpkgs-20.03-darwin", "repo": "nixpkgs", "type": "github" } }, - "nixpkgs-2105_12": { + "nixpkgs-2003_8": { "locked": { - "lastModified": 1630481079, - "narHash": "sha256-leWXLchbAbqOlLT6tju631G40SzQWPqaAXQG3zH1Imw=", + "lastModified": 1620055814, + "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "110a2c9ebbf5d4a94486854f18a37a938cfacbbb", + "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", "type": "github" }, "original": { "owner": "NixOS", - "ref": "nixpkgs-21.05-darwin", + "ref": "nixpkgs-20.03-darwin", "repo": "nixpkgs", "type": "github" } }, - "nixpkgs-2105_13": { + "nixpkgs-2003_9": { "locked": { - "lastModified": 1659914493, - "narHash": "sha256-lkA5X3VNMKirvA+SUzvEhfA7XquWLci+CGi505YFAIs=", + "lastModified": 1620055814, + "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "022caabb5f2265ad4006c1fa5b1ebe69fb0c3faf", + "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", "type": "github" }, "original": { "owner": "NixOS", - "ref": "nixpkgs-21.05-darwin", + "ref": "nixpkgs-20.03-darwin", "repo": "nixpkgs", "type": "github" } }, - "nixpkgs-2105_14": { + "nixpkgs-2105": { "locked": { "lastModified": 1645296114, "narHash": "sha256-y53N7TyIkXsjMpOG7RhvqJFGDacLs9HlyHeSTBioqYU=", @@ -7978,7 +5802,7 @@ "type": "github" } }, - "nixpkgs-2105_15": { + "nixpkgs-2105_10": { "locked": { "lastModified": 1640283157, "narHash": "sha256-6Ddfop+rKE+Gl9Tjp9YIrkfoYPzb8F80ergdjcq3/MY=", @@ -7994,7 +5818,7 @@ "type": "github" } }, - "nixpkgs-2105_16": { + "nixpkgs-2105_11": { "locked": { "lastModified": 1640283157, "narHash": "sha256-6Ddfop+rKE+Gl9Tjp9YIrkfoYPzb8F80ergdjcq3/MY=", @@ -8010,7 +5834,7 @@ "type": "github" } }, - "nixpkgs-2105_17": { + "nixpkgs-2105_12": { "locked": { "lastModified": 1630481079, "narHash": "sha256-leWXLchbAbqOlLT6tju631G40SzQWPqaAXQG3zH1Imw=", @@ -8026,7 +5850,7 @@ "type": "github" } }, - "nixpkgs-2105_18": { + "nixpkgs-2105_13": { "locked": { "lastModified": 1659914493, "narHash": "sha256-lkA5X3VNMKirvA+SUzvEhfA7XquWLci+CGi505YFAIs=", @@ -8250,86 +6074,6 @@ "type": "github" } }, - "nixpkgs-2111_14": { - "locked": { - "lastModified": 1648744337, - "narHash": "sha256-bYe1dFJAXovjqiaPKrmAbSBEK5KUkgwVaZcTbSoJ7hg=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "0a58eebd8ec65ffdef2ce9562784123a73922052", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-21.11-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2111_15": { - "locked": { - "lastModified": 1640283207, - "narHash": "sha256-SCwl7ZnCfMDsuSYvwIroiAlk7n33bW8HFfY8NvKhcPA=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "64c7e3388bbd9206e437713351e814366e0c3284", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-21.11-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2111_16": { - "locked": { - "lastModified": 1640283207, - "narHash": "sha256-SCwl7ZnCfMDsuSYvwIroiAlk7n33bW8HFfY8NvKhcPA=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "64c7e3388bbd9206e437713351e814366e0c3284", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-21.11-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2111_17": { - "locked": { - "lastModified": 1638410074, - "narHash": "sha256-MQYI4k4XkoTzpeRjq5wl+1NShsl1CKq8MISFuZ81sWs=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "5b80f23502f8e902612a8c631dfce383e1c56596", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-21.11-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2111_18": { - "locked": { - "lastModified": 1659446231, - "narHash": "sha256-hekabNdTdgR/iLsgce5TGWmfIDZ86qjPhxDg/8TlzhE=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "eabc38219184cc3e04a974fe31857d8e0eac098d", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-21.11-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, "nixpkgs-2111_2": { "locked": { "lastModified": 1648744337, @@ -8490,22 +6234,6 @@ "type": "github" } }, - "nixpkgs-2205_3": { - "locked": { - "lastModified": 1663981975, - "narHash": "sha256-TKaxWAVJR+a5JJauKZqibmaM5e/Pi5tBDx9s8fl/kSE=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "309faedb8338d3ae8ad8f1043b3ccf48c9cc2970", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-22.05-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, "nixpkgs-regression": { "locked": { "lastModified": 1643052045, @@ -8539,189 +6267,79 @@ "nixpkgs-regression_3": { "locked": { "lastModified": 1643052045, - "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "indirect" - } - }, - "nixpkgs-regression_4": { - "locked": { - "lastModified": 1643052045, - "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "indirect" - } - }, - "nixpkgs-regression_5": { - "locked": { - "lastModified": 1643052045, - "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "indirect" - } - }, - "nixpkgs-regression_6": { - "locked": { - "lastModified": 1643052045, - "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "indirect" - } - }, - "nixpkgs-regression_7": { - "locked": { - "lastModified": 1643052045, - "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "indirect" - } - }, - "nixpkgs-regression_8": { - "locked": { - "lastModified": 1643052045, - "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "indirect" - } - }, - "nixpkgs-regression_9": { - "locked": { - "lastModified": 1643052045, - "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "indirect" - } - }, - "nixpkgs-unstable": { - "locked": { - "lastModified": 1648219316, - "narHash": "sha256-Ctij+dOi0ZZIfX5eMhgwugfvB+WZSrvVNAyAuANOsnQ=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "30d3d79b7d3607d56546dd2a6b49e156ba0ec634", - "type": "github" - }, - "original": { + "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", "owner": "NixOS", - "ref": "nixpkgs-unstable", "repo": "nixpkgs", + "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", "type": "github" + }, + "original": { + "id": "nixpkgs", + "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", + "type": "indirect" } }, - "nixpkgs-unstable_10": { + "nixpkgs-regression_4": { "locked": { - "lastModified": 1641285291, - "narHash": "sha256-KYaOBNGar3XWTxTsYPr9P6u74KAqNq0wobEC236U+0c=", + "lastModified": 1643052045, + "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "0432195a4b8d68faaa7d3d4b355260a3120aeeae", + "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", "type": "github" }, "original": { - "owner": "NixOS", - "ref": "nixpkgs-unstable", - "repo": "nixpkgs", - "type": "github" + "id": "nixpkgs", + "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", + "type": "indirect" } }, - "nixpkgs-unstable_11": { + "nixpkgs-regression_5": { "locked": { - "lastModified": 1641285291, - "narHash": "sha256-KYaOBNGar3XWTxTsYPr9P6u74KAqNq0wobEC236U+0c=", + "lastModified": 1643052045, + "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "0432195a4b8d68faaa7d3d4b355260a3120aeeae", + "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", "type": "github" }, "original": { - "owner": "NixOS", - "ref": "nixpkgs-unstable", - "repo": "nixpkgs", - "type": "github" + "id": "nixpkgs", + "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", + "type": "indirect" } }, - "nixpkgs-unstable_12": { + "nixpkgs-regression_6": { "locked": { - "lastModified": 1635295995, - "narHash": "sha256-sGYiXjFlxTTMNb4NSkgvX+knOOTipE6gqwPUQpxNF+c=", + "lastModified": 1643052045, + "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "22a500a3f87bbce73bd8d777ef920b43a636f018", + "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", "type": "github" }, "original": { - "owner": "NixOS", - "ref": "nixpkgs-unstable", - "repo": "nixpkgs", - "type": "github" + "id": "nixpkgs", + "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", + "type": "indirect" } }, - "nixpkgs-unstable_13": { + "nixpkgs-regression_7": { "locked": { - "lastModified": 1663905476, - "narHash": "sha256-0CSwRKaYravh9v6qSlBpM0gNg0UhKT2lL7Yn6Zbx7UM=", + "lastModified": 1643052045, + "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "e14f9fb57315f0d4abde222364f19f88c77d2b79", + "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", "type": "github" }, "original": { - "owner": "NixOS", - "ref": "nixpkgs-unstable", - "repo": "nixpkgs", - "type": "github" + "id": "nixpkgs", + "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", + "type": "indirect" } }, - "nixpkgs-unstable_14": { + "nixpkgs-unstable": { "locked": { "lastModified": 1648219316, "narHash": "sha256-Ctij+dOi0ZZIfX5eMhgwugfvB+WZSrvVNAyAuANOsnQ=", @@ -8737,7 +6355,7 @@ "type": "github" } }, - "nixpkgs-unstable_15": { + "nixpkgs-unstable_10": { "locked": { "lastModified": 1641285291, "narHash": "sha256-KYaOBNGar3XWTxTsYPr9P6u74KAqNq0wobEC236U+0c=", @@ -8753,7 +6371,7 @@ "type": "github" } }, - "nixpkgs-unstable_16": { + "nixpkgs-unstable_11": { "locked": { "lastModified": 1641285291, "narHash": "sha256-KYaOBNGar3XWTxTsYPr9P6u74KAqNq0wobEC236U+0c=", @@ -8769,7 +6387,7 @@ "type": "github" } }, - "nixpkgs-unstable_17": { + "nixpkgs-unstable_12": { "locked": { "lastModified": 1635295995, "narHash": "sha256-sGYiXjFlxTTMNb4NSkgvX+knOOTipE6gqwPUQpxNF+c=", @@ -8785,7 +6403,7 @@ "type": "github" } }, - "nixpkgs-unstable_18": { + "nixpkgs-unstable_13": { "locked": { "lastModified": 1663905476, "narHash": "sha256-0CSwRKaYravh9v6qSlBpM0gNg0UhKT2lL7Yn6Zbx7UM=", @@ -9050,34 +6668,31 @@ }, "nixpkgs_18": { "locked": { - "lastModified": 1634172192, - "narHash": "sha256-FBF4U/T+bMg4sEyT/zkgasvVquGzgdAf4y8uCosKMmo=", + "lastModified": 1642336556, + "narHash": "sha256-QSPPbFEwy0T0DrIuSzAACkaANPQaR1lZR/nHZGz9z04=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "2cf9db0e3d45b9d00f16f2836cb1297bcadc475e", + "rev": "f3d9d4bd898cca7d04af2ae4f6ef01f2219df3d6", "type": "github" }, "original": { - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "2cf9db0e3d45b9d00f16f2836cb1297bcadc475e", - "type": "github" + "id": "nixpkgs", + "type": "indirect" } }, "nixpkgs_19": { "locked": { - "lastModified": 1634172192, - "narHash": "sha256-FBF4U/T+bMg4sEyT/zkgasvVquGzgdAf4y8uCosKMmo=", + "lastModified": 1632864508, + "narHash": "sha256-d127FIvGR41XbVRDPVvozUPQ/uRHbHwvfyKHwEt5xFM=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "2cf9db0e3d45b9d00f16f2836cb1297bcadc475e", + "rev": "82891b5e2c2359d7e58d08849e4c89511ab94234", "type": "github" }, "original": { - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "2cf9db0e3d45b9d00f16f2836cb1297bcadc475e", - "type": "github" + "id": "nixpkgs", + "ref": "nixos-21.05-small", + "type": "indirect" } }, "nixpkgs_2": { @@ -9111,35 +6726,6 @@ } }, "nixpkgs_21": { - "locked": { - "lastModified": 1632864508, - "narHash": "sha256-d127FIvGR41XbVRDPVvozUPQ/uRHbHwvfyKHwEt5xFM=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "82891b5e2c2359d7e58d08849e4c89511ab94234", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "ref": "nixos-21.05-small", - "type": "indirect" - } - }, - "nixpkgs_22": { - "locked": { - "lastModified": 1642336556, - "narHash": "sha256-QSPPbFEwy0T0DrIuSzAACkaANPQaR1lZR/nHZGz9z04=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "f3d9d4bd898cca7d04af2ae4f6ef01f2219df3d6", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "type": "indirect" - } - }, - "nixpkgs_23": { "locked": { "lastModified": 1642336556, "narHash": "sha256-QSPPbFEwy0T0DrIuSzAACkaANPQaR1lZR/nHZGz9z04=", @@ -9153,7 +6739,7 @@ "type": "indirect" } }, - "nixpkgs_24": { + "nixpkgs_22": { "locked": { "lastModified": 1632864508, "narHash": "sha256-d127FIvGR41XbVRDPVvozUPQ/uRHbHwvfyKHwEt5xFM=", @@ -9168,7 +6754,7 @@ "type": "indirect" } }, - "nixpkgs_25": { + "nixpkgs_23": { "locked": { "lastModified": 1653581809, "narHash": "sha256-Uvka0V5MTGbeOfWte25+tfRL3moECDh1VwokWSZUdoY=", @@ -9184,7 +6770,7 @@ "type": "github" } }, - "nixpkgs_26": { + "nixpkgs_24": { "locked": { "lastModified": 1654807842, "narHash": "sha256-ADymZpr6LuTEBXcy6RtFHcUZdjKTBRTMYwu19WOx17E=", @@ -9199,7 +6785,7 @@ "type": "github" } }, - "nixpkgs_27": { + "nixpkgs_25": { "locked": { "lastModified": 1665087388, "narHash": "sha256-FZFPuW9NWHJteATOf79rZfwfRn5fE0wi9kRzvGfDHPA=", @@ -9215,35 +6801,6 @@ "type": "github" } }, - "nixpkgs_28": { - "locked": { - "lastModified": 1642336556, - "narHash": "sha256-QSPPbFEwy0T0DrIuSzAACkaANPQaR1lZR/nHZGz9z04=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "f3d9d4bd898cca7d04af2ae4f6ef01f2219df3d6", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "type": "indirect" - } - }, - "nixpkgs_29": { - "locked": { - "lastModified": 1632864508, - "narHash": "sha256-d127FIvGR41XbVRDPVvozUPQ/uRHbHwvfyKHwEt5xFM=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "82891b5e2c2359d7e58d08849e4c89511ab94234", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "ref": "nixos-21.05-small", - "type": "indirect" - } - }, "nixpkgs_3": { "locked": { "lastModified": 1619531122, @@ -9258,96 +6815,6 @@ "type": "indirect" } }, - "nixpkgs_30": { - "locked": { - "lastModified": 1642336556, - "narHash": "sha256-QSPPbFEwy0T0DrIuSzAACkaANPQaR1lZR/nHZGz9z04=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "f3d9d4bd898cca7d04af2ae4f6ef01f2219df3d6", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "type": "indirect" - } - }, - "nixpkgs_31": { - "locked": { - "lastModified": 1642336556, - "narHash": "sha256-QSPPbFEwy0T0DrIuSzAACkaANPQaR1lZR/nHZGz9z04=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "f3d9d4bd898cca7d04af2ae4f6ef01f2219df3d6", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "type": "indirect" - } - }, - "nixpkgs_32": { - "locked": { - "lastModified": 1632864508, - "narHash": "sha256-d127FIvGR41XbVRDPVvozUPQ/uRHbHwvfyKHwEt5xFM=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "82891b5e2c2359d7e58d08849e4c89511ab94234", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "ref": "nixos-21.05-small", - "type": "indirect" - } - }, - "nixpkgs_33": { - "locked": { - "lastModified": 1653581809, - "narHash": "sha256-Uvka0V5MTGbeOfWte25+tfRL3moECDh1VwokWSZUdoY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "83658b28fe638a170a19b8933aa008b30640fbd1", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixos-unstable", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs_34": { - "locked": { - "lastModified": 1654807842, - "narHash": "sha256-ADymZpr6LuTEBXcy6RtFHcUZdjKTBRTMYwu19WOx17E=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "fc909087cc3386955f21b4665731dbdaceefb1d8", - "type": "github" - }, - "original": { - "owner": "NixOS", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs_35": { - "locked": { - "lastModified": 1665087388, - "narHash": "sha256-FZFPuW9NWHJteATOf79rZfwfRn5fE0wi9kRzvGfDHPA=", - "owner": "nixos", - "repo": "nixpkgs", - "rev": "95fda953f6db2e9496d2682c4fc7b82f959878f7", - "type": "github" - }, - "original": { - "owner": "nixos", - "ref": "nixpkgs-unstable", - "repo": "nixpkgs", - "type": "github" - } - }, "nixpkgs_4": { "locked": { "lastModified": 1656461576, @@ -9424,35 +6891,19 @@ "nixpkgs_9": { "locked": { "lastModified": 1632864508, - "narHash": "sha256-d127FIvGR41XbVRDPVvozUPQ/uRHbHwvfyKHwEt5xFM=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "82891b5e2c2359d7e58d08849e4c89511ab94234", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "ref": "nixos-21.05-small", - "type": "indirect" - } - }, - "node-process": { - "flake": false, - "locked": { - "lastModified": 1654323094, - "narHash": "sha256-zbmpZeBgUUly8QgR2mrVUN0A+0iLczufNvCCRxAo3GY=", - "owner": "input-output-hk", - "repo": "cardano-node", - "rev": "ec20745f17cb4fa8824fdf341d1412c774bc94b9", + "narHash": "sha256-d127FIvGR41XbVRDPVvozUPQ/uRHbHwvfyKHwEt5xFM=", + "owner": "NixOS", + "repo": "nixpkgs", + "rev": "82891b5e2c2359d7e58d08849e4c89511ab94234", "type": "github" }, "original": { - "owner": "input-output-hk", - "repo": "cardano-node", - "type": "github" + "id": "nixpkgs", + "ref": "nixos-21.05-small", + "type": "indirect" } }, - "node-process_2": { + "node-process": { "flake": false, "locked": { "lastModified": 1654323094, @@ -9468,7 +6919,7 @@ "type": "github" } }, - "node-process_3": { + "node-process_2": { "flake": false, "locked": { "lastModified": 1654323094, @@ -9524,8 +6975,7 @@ "membench": "membench_3", "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "haskellNix", @@ -9549,38 +6999,6 @@ "type": "github" } }, - "node-snapshot_3": { - "inputs": { - "customConfig": "customConfig_11", - "haskellNix": "haskellNix_11", - "iohkNix": "iohkNix_11", - "membench": "membench_5", - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "haskellNix", - "nixpkgs-2105" - ], - "plutus-example": "plutus-example_3", - "utils": "utils_13" - }, - "locked": { - "lastModified": 1645120669, - "narHash": "sha256-2MKfGsYS5n69+pfqNHb4IH/E95ok1MD7mhEYfUpRcz4=", - "owner": "input-output-hk", - "repo": "cardano-node", - "rev": "7f00e3ea5a61609e19eeeee4af35241571efdf5c", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-node", - "rev": "7f00e3ea5a61609e19eeeee4af35241571efdf5c", - "type": "github" - } - }, "ogmios": { "inputs": { "CHaP": "CHaP", @@ -9612,113 +7030,32 @@ "type": "github" } }, - "ogmios-datum-cache": { - "inputs": { - "flake-compat": "flake-compat_9", - "nixpkgs": "nixpkgs_18", - "unstable_nixpkgs": "unstable_nixpkgs" - }, - "locked": { - "lastModified": 1668515878, - "narHash": "sha256-r4aOSSz9jZZPreUkgOpS3ZpYFV4cxNVCUQFIpBZ8Y9k=", - "owner": "mlabs-haskell", - "repo": "ogmios-datum-cache", - "rev": "862c6bfcb6110b8fe816e26b3bba105dfb492b24", - "type": "github" - }, - "original": { - "owner": "mlabs-haskell", - "repo": "ogmios-datum-cache", - "rev": "862c6bfcb6110b8fe816e26b3bba105dfb492b24", - "type": "github" - } - }, - "ogmios-datum-cache-nixos": { - "inputs": { - "cardano-configurations": "cardano-configurations_3", - "cardano-node": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "cardano-node" - ], - "flake-compat": "flake-compat_10", - "nixpkgs": "nixpkgs_19", - "ogmios": "ogmios_2", - "unstable_nixpkgs": "unstable_nixpkgs_2" - }, - "locked": { - "lastModified": 1667912888, - "narHash": "sha256-6KS0c1PZ44ZTcE2ioXC0GiIuyTKnG5MeKX7nDZ6Knus=", - "owner": "mlabs-haskell", - "repo": "ogmios-datum-cache", - "rev": "a33a576fefe2248e9906e7b8044a30955cca0061", - "type": "github" - }, - "original": { - "owner": "mlabs-haskell", - "ref": "marton/nixos-module", - "repo": "ogmios-datum-cache", - "type": "github" - } - }, "ogmios-nixos": { - "inputs": { - "CHaP": "CHaP_3", - "blank": "blank_5", - "cardano-configurations": "cardano-configurations_4", - "cardano-node": "cardano-node_4", - "flake-compat": "flake-compat_16", - "haskell-nix": "haskell-nix_5", - "iohk-nix": "iohk-nix_5", - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "haskell-nix", - "nixpkgs-unstable" - ] - }, - "locked": { - "lastModified": 1668087435, - "narHash": "sha256-pbx/+mP2pu4vQuTV3YtFXrOZOVOBS9JH9eDqgjnHyZ4=", - "owner": "mlabs-haskell", - "repo": "ogmios", - "rev": "3b229c1795efa30243485730b78ea053992fdc7a", - "type": "github" - }, - "original": { - "owner": "mlabs-haskell", - "repo": "ogmios", - "type": "github" - } - }, - "ogmios_2": { "inputs": { "CHaP": "CHaP_2", "blank": "blank_3", + "cardano-configurations": "cardano-configurations_3", "cardano-node": "cardano-node_3", - "flake-compat": "flake-compat_12", + "flake-compat": "flake-compat_10", "haskell-nix": "haskell-nix_4", "iohk-nix": "iohk-nix_4", "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "haskell-nix", "nixpkgs-unstable" ] }, "locked": { - "lastModified": 1667904967, - "narHash": "sha256-KAWv/plBLRqZiBYUl0plXQdMPzFs7G89VhTbg122kA4=", + "lastModified": 1668087435, + "narHash": "sha256-pbx/+mP2pu4vQuTV3YtFXrOZOVOBS9JH9eDqgjnHyZ4=", "owner": "mlabs-haskell", "repo": "ogmios", - "rev": "dbc1a03dca6a876a25d54a8716504837909c6e8c", + "rev": "3b229c1795efa30243485730b78ea053992fdc7a", "type": "github" }, "original": { "owner": "mlabs-haskell", - "ref": "staging", "repo": "ogmios", "type": "github" } @@ -9808,91 +7145,6 @@ "type": "github" } }, - "old-ghc-nix_14": { - "flake": false, - "locked": { - "lastModified": 1631092763, - "narHash": "sha256-sIKgO+z7tj4lw3u6oBZxqIhDrzSkvpHtv0Kki+lh9Fg=", - "owner": "angerman", - "repo": "old-ghc-nix", - "rev": "af48a7a7353e418119b6dfe3cd1463a657f342b8", - "type": "github" - }, - "original": { - "owner": "angerman", - "ref": "master", - "repo": "old-ghc-nix", - "type": "github" - } - }, - "old-ghc-nix_15": { - "flake": false, - "locked": { - "lastModified": 1631092763, - "narHash": "sha256-sIKgO+z7tj4lw3u6oBZxqIhDrzSkvpHtv0Kki+lh9Fg=", - "owner": "angerman", - "repo": "old-ghc-nix", - "rev": "af48a7a7353e418119b6dfe3cd1463a657f342b8", - "type": "github" - }, - "original": { - "owner": "angerman", - "ref": "master", - "repo": "old-ghc-nix", - "type": "github" - } - }, - "old-ghc-nix_16": { - "flake": false, - "locked": { - "lastModified": 1631092763, - "narHash": "sha256-sIKgO+z7tj4lw3u6oBZxqIhDrzSkvpHtv0Kki+lh9Fg=", - "owner": "angerman", - "repo": "old-ghc-nix", - "rev": "af48a7a7353e418119b6dfe3cd1463a657f342b8", - "type": "github" - }, - "original": { - "owner": "angerman", - "ref": "master", - "repo": "old-ghc-nix", - "type": "github" - } - }, - "old-ghc-nix_17": { - "flake": false, - "locked": { - "lastModified": 1631092763, - "narHash": "sha256-sIKgO+z7tj4lw3u6oBZxqIhDrzSkvpHtv0Kki+lh9Fg=", - "owner": "angerman", - "repo": "old-ghc-nix", - "rev": "af48a7a7353e418119b6dfe3cd1463a657f342b8", - "type": "github" - }, - "original": { - "owner": "angerman", - "ref": "master", - "repo": "old-ghc-nix", - "type": "github" - } - }, - "old-ghc-nix_18": { - "flake": false, - "locked": { - "lastModified": 1631092763, - "narHash": "sha256-sIKgO+z7tj4lw3u6oBZxqIhDrzSkvpHtv0Kki+lh9Fg=", - "owner": "angerman", - "repo": "old-ghc-nix", - "rev": "af48a7a7353e418119b6dfe3cd1463a657f342b8", - "type": "github" - }, - "original": { - "owner": "angerman", - "ref": "master", - "repo": "old-ghc-nix", - "type": "github" - } - }, "old-ghc-nix_2": { "flake": false, "locked": { @@ -10127,45 +7379,13 @@ "type": "github" } }, - "ouroboros-network_6": { - "flake": false, - "locked": { - "lastModified": 1643385024, - "narHash": "sha256-9R4Z1jBsTcEgBHxhzjCJnroEcdfMsTjf8kwg6uPue+Q=", - "owner": "input-output-hk", - "repo": "ouroboros-network", - "rev": "8e97076176d465f5f4f86d5b5596220272630649", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "ouroboros-network", - "type": "github" - } - }, - "ouroboros-network_7": { - "flake": false, - "locked": { - "lastModified": 1643385024, - "narHash": "sha256-9R4Z1jBsTcEgBHxhzjCJnroEcdfMsTjf8kwg6uPue+Q=", - "owner": "input-output-hk", - "repo": "ouroboros-network", - "rev": "8e97076176d465f5f4f86d5b5596220272630649", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "ouroboros-network", - "type": "github" - } - }, "plutip": { "inputs": { "bot-plutus-interface": [ "ctl", "bot-plutus-interface" ], - "flake-compat": "flake-compat_19", + "flake-compat": "flake-compat_13", "haskell-nix": [ "ctl", "bot-plutus-interface", @@ -10264,22 +7484,6 @@ "type": "github" } }, - "plutus-apps_4": { - "flake": false, - "locked": { - "lastModified": 1654271253, - "narHash": "sha256-GQDPzyVtcbbESmckMvzoTEKa/UWWJH7djh1TWQjzFow=", - "owner": "input-output-hk", - "repo": "plutus-apps", - "rev": "61de89d33340279b8452a0dbb52a87111db87e82", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "plutus-apps", - "type": "github" - } - }, "plutus-example": { "inputs": { "customConfig": "customConfig_5", @@ -10314,40 +7518,8 @@ "plutus-example_2": { "inputs": { "customConfig": "customConfig_9", - "haskellNix": "haskellNix_9", - "iohkNix": "iohkNix_9", - "nixpkgs": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "cardano-node", - "node-snapshot", - "plutus-example", - "haskellNix", - "nixpkgs-2105" - ], - "utils": "utils_7" - }, - "locked": { - "lastModified": 1640022647, - "narHash": "sha256-M+YnF7Zj/7QK2pu0T75xNVaX0eEeijtBH8yz+jEHIMM=", - "owner": "input-output-hk", - "repo": "cardano-node", - "rev": "814df2c146f5d56f8c35a681fe75e85b905aed5d", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-node", - "rev": "814df2c146f5d56f8c35a681fe75e85b905aed5d", - "type": "github" - } - }, - "plutus-example_3": { - "inputs": { - "customConfig": "customConfig_13", - "haskellNix": "haskellNix_13", - "iohkNix": "iohkNix_13", + "haskellNix": "haskellNix_9", + "iohkNix": "iohkNix_9", "nixpkgs": [ "ctl", "ogmios-nixos", @@ -10357,7 +7529,7 @@ "haskellNix", "nixpkgs-2105" ], - "utils": "utils_12" + "utils": "utils_7" }, "locked": { "lastModified": 1640022647, @@ -10430,7 +7602,7 @@ "root": { "inputs": { "ctl": "ctl", - "flake-compat": "flake-compat_20", + "flake-compat": "flake-compat_14", "nixpkgs": [ "ctl", "nixpkgs" @@ -10534,86 +7706,6 @@ "type": "github" } }, - "stackage_14": { - "flake": false, - "locked": { - "lastModified": 1656898145, - "narHash": "sha256-EMgMzdANg6r5gEUkMtv5ujDo2/Kx7JJXoXiDKjDVoLw=", - "owner": "input-output-hk", - "repo": "stackage.nix", - "rev": "835a5f2d2a1acafb77add430fc8c2dd47282ef32", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "stackage.nix", - "type": "github" - } - }, - "stackage_15": { - "flake": false, - "locked": { - "lastModified": 1643073493, - "narHash": "sha256-5cPd1+i/skvJY9vJO1BhVRPcJObqkxDSywBEppDmb1U=", - "owner": "input-output-hk", - "repo": "stackage.nix", - "rev": "48e1188855ca38f3b7e2a8dba5352767a2f0a8f7", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "stackage.nix", - "type": "github" - } - }, - "stackage_16": { - "flake": false, - "locked": { - "lastModified": 1643073493, - "narHash": "sha256-5cPd1+i/skvJY9vJO1BhVRPcJObqkxDSywBEppDmb1U=", - "owner": "input-output-hk", - "repo": "stackage.nix", - "rev": "48e1188855ca38f3b7e2a8dba5352767a2f0a8f7", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "stackage.nix", - "type": "github" - } - }, - "stackage_17": { - "flake": false, - "locked": { - "lastModified": 1639012797, - "narHash": "sha256-hiLyBa5XFBvxD+BcYPKyYd/0dNMccxAuywFNqYtIIvs=", - "owner": "input-output-hk", - "repo": "stackage.nix", - "rev": "9ea6ea359da91c75a71e334b25aa7dc5ddc4b2c6", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "stackage.nix", - "type": "github" - } - }, - "stackage_18": { - "flake": false, - "locked": { - "lastModified": 1667610757, - "narHash": "sha256-H4dlMk5EW50xOtGo+5Srm3HGQV1+hY9ttgRQ+Sew5uA=", - "owner": "input-output-hk", - "repo": "stackage.nix", - "rev": "01d8ea53f65b08910003a1990547bab75ed6068a", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "stackage.nix", - "type": "github" - } - }, "stackage_2": { "flake": false, "locked": { @@ -10792,8 +7884,7 @@ "flake-utils": "flake-utils_23", "makes": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "haskell-nix", "tullia", "std", @@ -10802,8 +7893,7 @@ "mdbook-kroki-preprocessor": "mdbook-kroki-preprocessor_2", "microvm": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "haskell-nix", "tullia", "std", @@ -10811,7 +7901,7 @@ ], "n2c": "n2c_2", "nixago": "nixago_2", - "nixpkgs": "nixpkgs_27", + "nixpkgs": "nixpkgs_25", "yants": "yants_2" }, "locked": { @@ -10828,48 +7918,6 @@ "type": "github" } }, - "std_3": { - "inputs": { - "blank": "blank_6", - "devshell": "devshell_3", - "dmerge": "dmerge_3", - "flake-utils": "flake-utils_31", - "makes": [ - "ctl", - "ogmios-nixos", - "haskell-nix", - "tullia", - "std", - "blank" - ], - "mdbook-kroki-preprocessor": "mdbook-kroki-preprocessor_3", - "microvm": [ - "ctl", - "ogmios-nixos", - "haskell-nix", - "tullia", - "std", - "blank" - ], - "n2c": "n2c_3", - "nixago": "nixago_3", - "nixpkgs": "nixpkgs_35", - "yants": "yants_3" - }, - "locked": { - "lastModified": 1665513321, - "narHash": "sha256-D6Pacw9yf/HMs84KYuCxHXnNDL7v43gtcka5URagFqE=", - "owner": "divnix", - "repo": "std", - "rev": "94a90eedb9cfc115b12ae8f6622d9904788559e4", - "type": "github" - }, - "original": { - "owner": "divnix", - "repo": "std", - "type": "github" - } - }, "tailwind-haskell": { "inputs": { "flake-utils": "flake-utils_4", @@ -10920,40 +7968,13 @@ "inputs": { "nix-nomad": "nix-nomad_2", "nix2container": "nix2container_2", - "nixpkgs": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "nixpkgs" - ], - "std": "std_2" - }, - "locked": { - "lastModified": 1666200256, - "narHash": "sha256-cJPS8zBu30SMhxMe7I8DWutwqMuhPsEez87y9gxMKc4=", - "owner": "input-output-hk", - "repo": "tullia", - "rev": "575362c2244498e8d2c97f72861510fa72e75d44", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "tullia", - "type": "github" - } - }, - "tullia_3": { - "inputs": { - "nix-nomad": "nix-nomad_3", - "nix2container": "nix2container_3", "nixpkgs": [ "ctl", "ogmios-nixos", "haskell-nix", "nixpkgs" ], - "std": "std_3" + "std": "std_2" }, "locked": { "lastModified": 1666200256, @@ -10986,36 +8007,6 @@ "type": "github" } }, - "unstable_nixpkgs": { - "locked": { - "lastModified": 1653307806, - "narHash": "sha256-VPej3GE4IBMwYnXRfbiVqMWKa32+ysuvbHRkQXD0gTw=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "9d7aff488a8f9429d9e6cd82c10dffbf21907fb1", - "type": "github" - }, - "original": { - "owner": "NixOS", - "repo": "nixpkgs", - "type": "github" - } - }, - "unstable_nixpkgs_2": { - "locked": { - "lastModified": 1653307806, - "narHash": "sha256-VPej3GE4IBMwYnXRfbiVqMWKa32+ysuvbHRkQXD0gTw=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "9d7aff488a8f9429d9e6cd82c10dffbf21907fb1", - "type": "github" - }, - "original": { - "owner": "NixOS", - "repo": "nixpkgs", - "type": "github" - } - }, "utils": { "locked": { "lastModified": 1623875721, @@ -11046,81 +8037,6 @@ "type": "github" } }, - "utils_11": { - "locked": { - "lastModified": 1623875721, - "narHash": "sha256-A8BU7bjS5GirpAUv4QA+QnJ4CceLHkcXdRp4xITDB0s=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "f7e004a55b120c02ecb6219596820fcd32ca8772", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "utils_12": { - "locked": { - "lastModified": 1638122382, - "narHash": "sha256-sQzZzAbvKEqN9s0bzWuYmRaA03v40gaJ4+iL1LXjaeI=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "74f7e4319258e287b0f9cb95426c9853b282730b", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "utils_13": { - "locked": { - "lastModified": 1623875721, - "narHash": "sha256-A8BU7bjS5GirpAUv4QA+QnJ4CceLHkcXdRp4xITDB0s=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "f7e004a55b120c02ecb6219596820fcd32ca8772", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "utils_14": { - "locked": { - "lastModified": 1653893745, - "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "1ed9fb1935d260de5fe1c2f7ee0ebaae17ed2fa1", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "utils_15": { - "locked": { - "lastModified": 1653893745, - "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "1ed9fb1935d260de5fe1c2f7ee0ebaae17ed2fa1", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, "utils_2": { "locked": { "lastModified": 1638122382, @@ -11267,32 +8183,6 @@ } }, "yants_2": { - "inputs": { - "nixpkgs": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "std", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1660507851, - "narHash": "sha256-BKjq7JnVuUR/xDtcv6Vm9GYGKAblisXrAgybor9hT/s=", - "owner": "divnix", - "repo": "yants", - "rev": "0b895ca02a8fa72bad50b454cb3e7d8a66407c96", - "type": "github" - }, - "original": { - "owner": "divnix", - "repo": "yants", - "type": "github" - } - }, - "yants_3": { "inputs": { "nixpkgs": [ "ctl", diff --git a/templates/ctl-scaffold/flake.nix b/templates/ctl-scaffold/flake.nix index cb33434d06..c17022850d 100644 --- a/templates/ctl-scaffold/flake.nix +++ b/templates/ctl-scaffold/flake.nix @@ -10,7 +10,7 @@ type = "github"; owner = "Plutonomicon"; repo = "cardano-transaction-lib"; - rev = "6d6cc0ee04bb7c4f4763c804b4078f5d9705f3f9"; + rev = "ec5f4868e7931f76682d3380f45267f02fd0e015"; }; # To use the same version of `nixpkgs` as we do nixpkgs.follows = "ctl/nixpkgs"; From 56471711ed2421dfc9b416f4ce297b005cdfd936 Mon Sep 17 00:00:00 2001 From: peter Date: Tue, 13 Dec 2022 15:26:07 +0100 Subject: [PATCH 092/373] wip: tests pass only without updates --- CHANGELOG.md | 2 +- test/Fixtures.purs | 61 +++------------------------------------------- 2 files changed, 4 insertions(+), 59 deletions(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index ee50458956..26920c5482 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -137,7 +137,7 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) ### Runtime Dependencies -- [Ogmios](https://github.com/mlabs-haskell/ogmios) - v5.5.7 +- [Ogmios](https://github.com/mlabs-haskell/ogmios) - v5.5.7 - [Kupo](https://github.com/CardanoSolutions/kupo) - v2.2.0 - [Cardano-Node](https://github.com/input-output-hk/cardano-node/) - v1.35.3 - [Ogmios-Datum-Cache](https://github.com/mlabs-haskell/ogmios-datum-cache) - commit 862c6bfcb6110b8fe816e26b3bba105dfb492b24 diff --git a/test/Fixtures.purs b/test/Fixtures.purs index 5b11316602..354495bd0e 100644 --- a/test/Fixtures.purs +++ b/test/Fixtures.purs @@ -321,8 +321,8 @@ proposedProtocolParameterUpdates1 = ProposedProtocolParameterUpdates $ , maxBlockExUnits: Just { mem: BigInt.fromInt 1, steps: BigInt.fromInt 1 } , maxValueSize: Just $ UInt.fromInt 1 - , collateralPercentage: Just $ UInt.fromInt 140 - , maxCollateralInputs: Just $ UInt.fromInt 10 + , collateralPercentage: Nothing -- Just $ UInt.fromInt 140 + , maxCollateralInputs: Nothing -- Just $ UInt.fromInt 10 } ] @@ -791,62 +791,7 @@ txBinaryFixture3 = txBinaryFixture4 :: String txBinaryFixture4 = - "84ae00818258205d677265fa5bb21ce6d8c7502aca70b9316d10e958611f3c6b758f65ad9599\ - \96000182a40058390030fb3b8539951e26f034910a5a37f22cb99d94d1d409f69ddbaea9710f\ - \45aaf1b2959db6e5ff94dbb1f823bf257680c3c723ac2d49f97546011a0023e8fa028201d818\ - \418003d8185182014e4d01000033222220051200120011a30058390030fb3b8539951e26f034\ - \910a5a37f22cb99d94d1d409f69ddbaea9710f45aaf1b2959db6e5ff94dbb1f823bf257680c3\ - \c723ac2d49f97546011a000f424003d81858468200830301828200581c1c12f03c1ef2e935ac\ - \c35ec2e6f96c650fd3bfba3e96550504d533618200581c30fb3b8539951e26f034910a5a37f2\ - \2cb99d94d1d409f69ddbaea971021a0002b56903187b048882008200581c1730b1b700d616d5\ - \1555538e83d67f13c113ad5f9b22212703482cb382018200581c1730b1b700d616d51555538e\ - \83d67f13c113ad5f9b22212703482cb383028200581c1730b1b700d616d51555538e83d67f13\ - \c113ad5f9b22212703482cb3581c1730b1b700d616d51555538e83d67f13c113ad5f9b222127\ - \03482cb38a03581c1730b1b700d616d51555538e83d67f13c113ad5f9b22212703482cb35820\ - \fbf6d41985670b9041c5bf362b5262cf34add5d265975de176d613ca05f370960101d81e8201\ - \01581de11730b1b700d616d51555538e83d67f13c113ad5f9b22212703482cb381581c1730b1\ - \b700d616d51555538e83d67f13c113ad5f9b22212703482cb3838400191f90447f000001507b\ - \7b7b7b7b7b7b7b7b7b7b7b7b7b7b7b8301191f906b6578616d706c652e636f6d82026b657861\ - \6d706c652e636f6d827468747470733a2f2f6578616d706c652e636f6d2f582094b8cac47761\ - \c1140c57a48d56ab15d27a842abff041b3798b8618fa84641f5a8304581c1730b1b700d616d5\ - \1555538e83d67f13c113ad5f9b22212703482cb3018405581c5d677265fa5bb21ce6d8c7502a\ - \ca70b9316d10e958611f3c6b758f65581c5d677265fa5bb21ce6d8c7502aca70b9316d10e958\ - \611f3c6b758f655820fbf6d41985670b9041c5bf362b5262cf34add5d265975de176d613ca05\ - \f37096820682010182068201a18200581c1730b1b700d616d51555538e83d67f13c113ad5f9b\ - \22212703482cb30105a1581de01730b1b700d616d51555538e83d67f13c113ad5f9b22212703\ - \482cb3010682a1581c5d677265fa5bb21ce6d8c7502aca70b9316d10e958611f3c6b758f65b4\ - \000101010219271003192710041903e8050106010701080109d81e8201010ad81e8201010bd8\ - \1e8201010e8201011001110112a20098a61a0003236119032c01011903e819023b00011903e8\ - \195e7104011903e818201a0001ca761928eb041959d818641959d818641959d818641959d818\ - \641959d818641959d81864186418641959d81864194c5118201a0002acfa182019b551041a00\ - \0363151901ff00011a00015c3518201a000797751936f404021a0002ff941a0006ea7818dc00\ - \01011903e8196ff604021a0003bd081a00034ec5183e011a00102e0f19312a011a00032e8019\ - \01a5011a0002da781903e819cf06011a00013a34182019a8f118201903e818201a00013aac01\ - \19e143041903e80a1a00030219189c011a00030219189c011a0003207c1901d9011a00033000\ - \1901ff0119ccf3182019fd40182019ffd5182019581e18201940b318201a00012adf18201a00\ - \02ff941a0006ea7818dc0001011a00010f92192da7000119eabb18201a0002ff941a0006ea78\ - \18dc0001011a0002ff941a0006ea7818dc0001011a000c504e197712041a001d6af61a000142\ - \5b041a00040c660004001a00014fab18201a0003236119032c010119a0de18201a00033d7618\ - \201979f41820197fb8182019a95d1820197df718201995aa18201a009063b91903fd0a0198af\ - \1a0003236119032c01011903e819023b00011903e8195e7104011903e818201a0001ca761928\ - \eb041959d818641959d818641959d818641959d818641959d818641959d81864186418641959\ - \d81864194c5118201a0002acfa182019b551041a000363151901ff00011a00015c3518201a00\ - \0797751936f404021a0002ff941a0006ea7818dc0001011903e8196ff604021a0003bd081a00\ - \034ec5183e011a00102e0f19312a011a00032e801901a5011a0002da781903e819cf06011a00\ - \013a34182019a8f118201903e818201a00013aac0119e143041903e80a1a00030219189c011a\ - \00030219189c011a0003207c1901d9011a000330001901ff0119ccf3182019fd40182019ffd5\ - \182019581e18201940b318201a00012adf18201a0002ff941a0006ea7818dc0001011a00010f\ - \92192da7000119eabb18201a0002ff941a0006ea7818dc0001011a0002ff941a0006ea7818dc\ - \0001011a0011b22c1a0005fdde00021a000c504e197712041a001d6af61a0001425b041a0004\ - \0c660004001a00014fab18201a0003236119032c010119a0de18201a00033d7618201979f418\ - \20197fb8182019a95d1820197df718201995aa18201b00000004a817c8001b00000004a817c8\ - \001a009063b91903fd0a1b00000004a817c800001b00000004a817c8001382d81e820101d81e\ - \8201011482010115820101160101075820000000000000000000000000000000000000000000\ - \000000000000000000000008187c09a1581c1d6445ddeda578117f393848e685128f1e78ad0c\ - \4e48129c5964dc2ea14a4974657374546f6b656e010e81581c1c12f03c1ef2e935acc35ec2e6\ - \f96c650fd3bfba3e96550504d533610f01108258390030fb3b8539951e26f034910a5a37f22c\ - \b99d94d1d409f69ddbaea9711c12f03c1ef2e935acc35ec2e6f96c650fd3bfba3e96550504d5\ - \336100111a004c4b40a0f5f6" + "84ae00818258205d677265fa5bb21ce6d8c7502aca70b9316d10e958611f3c6b758f65ad959996000182a40058390030fb3b8539951e26f034910a5a37f22cb99d94d1d409f69ddbaea9710f45aaf1b2959db6e5ff94dbb1f823bf257680c3c723ac2d49f97546011a0023e8fa028201d818418003d8185182014e4d01000033222220051200120011a30058390030fb3b8539951e26f034910a5a37f22cb99d94d1d409f69ddbaea9710f45aaf1b2959db6e5ff94dbb1f823bf257680c3c723ac2d49f97546011a000f424003d81858468200830301828200581c1c12f03c1ef2e935acc35ec2e6f96c650fd3bfba3e96550504d533618200581c30fb3b8539951e26f034910a5a37f22cb99d94d1d409f69ddbaea971021a0002b56903187b048882008200581c1730b1b700d616d51555538e83d67f13c113ad5f9b22212703482cb382018200581c1730b1b700d616d51555538e83d67f13c113ad5f9b22212703482cb383028200581c1730b1b700d616d51555538e83d67f13c113ad5f9b22212703482cb3581c1730b1b700d616d51555538e83d67f13c113ad5f9b22212703482cb38a03581c1730b1b700d616d51555538e83d67f13c113ad5f9b22212703482cb35820fbf6d41985670b9041c5bf362b5262cf34add5d265975de176d613ca05f370960101d81e820101581de11730b1b700d616d51555538e83d67f13c113ad5f9b22212703482cb381581c1730b1b700d616d51555538e83d67f13c113ad5f9b22212703482cb3838400191f90447f000001507b7b7b7b7b7b7b7b7b7b7b7b7b7b7b7b8301191f906b6578616d706c652e636f6d82026b6578616d706c652e636f6d827468747470733a2f2f6578616d706c652e636f6d2f582094b8cac47761c1140c57a48d56ab15d27a842abff041b3798b8618fa84641f5a8304581c1730b1b700d616d51555538e83d67f13c113ad5f9b22212703482cb3018405581c5d677265fa5bb21ce6d8c7502aca70b9316d10e958611f3c6b758f65581c5d677265fa5bb21ce6d8c7502aca70b9316d10e958611f3c6b758f655820fbf6d41985670b9041c5bf362b5262cf34add5d265975de176d613ca05f37096820682010182068201a18200581c1730b1b700d616d51555538e83d67f13c113ad5f9b22212703482cb30105a1581de01730b1b700d616d51555538e83d67f13c113ad5f9b22212703482cb3010682a1581c5d677265fa5bb21ce6d8c7502aca70b9316d10e958611f3c6b758f65b4000101010219271003192710041903e8050106010701080109d81e8201010ad81e8201010bd81e8201010e8201011001110112a20098a61a0003236119032c01011903e819023b00011903e8195e7104011903e818201a0001ca761928eb041959d818641959d818641959d818641959d818641959d818641959d81864186418641959d81864194c5118201a0002acfa182019b551041a000363151901ff00011a00015c3518201a000797751936f404021a0002ff941a0006ea7818dc0001011903e8196ff604021a0003bd081a00034ec5183e011a00102e0f19312a011a00032e801901a5011a0002da781903e819cf06011a00013a34182019a8f118201903e818201a00013aac0119e143041903e80a1a00030219189c011a00030219189c011a0003207c1901d9011a000330001901ff0119ccf3182019fd40182019ffd5182019581e18201940b318201a00012adf18201a0002ff941a0006ea7818dc0001011a00010f92192da7000119eabb18201a0002ff941a0006ea7818dc0001011a0002ff941a0006ea7818dc0001011a000c504e197712041a001d6af61a0001425b041a00040c660004001a00014fab18201a0003236119032c010119a0de18201a00033d7618201979f41820197fb8182019a95d1820197df718201995aa18201a009063b91903fd0a0198af1a0003236119032c01011903e819023b00011903e8195e7104011903e818201a0001ca761928eb041959d818641959d818641959d818641959d818641959d818641959d81864186418641959d81864194c5118201a0002acfa182019b551041a000363151901ff00011a00015c3518201a000797751936f404021a0002ff941a0006ea7818dc0001011903e8196ff604021a0003bd081a00034ec5183e011a00102e0f19312a011a00032e801901a5011a0002da781903e819cf06011a00013a34182019a8f118201903e818201a00013aac0119e143041903e80a1a00030219189c011a00030219189c011a0003207c1901d9011a000330001901ff0119ccf3182019fd40182019ffd5182019581e18201940b318201a00012adf18201a0002ff941a0006ea7818dc0001011a00010f92192da7000119eabb18201a0002ff941a0006ea7818dc0001011a0002ff941a0006ea7818dc0001011a0011b22c1a0005fdde00021a000c504e197712041a001d6af61a0001425b041a00040c660004001a00014fab18201a0003236119032c010119a0de18201a00033d7618201979f41820197fb8182019a95d1820197df718201995aa18201b00000004a817c8001b00000004a817c8001a009063b91903fd0a1b00000004a817c800001b00000004a817c8001382d81e820101d81e8201011482010115820101160101075820000000000000000000000000000000000000000000000000000000000000000008187c09a1581c1d6445ddeda578117f393848e685128f1e78ad0c4e48129c5964dc2ea14a4974657374546f6b656e010e81581c1c12f03c1ef2e935acc35ec2e6f96c650fd3bfba3e96550504d533610f01108258390030fb3b8539951e26f034910a5a37f22cb99d94d1d409f69ddbaea9711c12f03c1ef2e935acc35ec2e6f96c650fd3bfba3e96550504d5336100111a004c4b40a0f5f6" txBinaryFixture5 :: String txBinaryFixture5 = From 4b127da69bf32684ea398ba991b84c6a3ab3516e Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Tue, 13 Dec 2022 14:53:25 +0000 Subject: [PATCH 093/373] Update template --- templates/ctl-scaffold/flake.lock | 3692 +++-------------------------- templates/ctl-scaffold/flake.nix | 2 +- 2 files changed, 292 insertions(+), 3402 deletions(-) diff --git a/templates/ctl-scaffold/flake.lock b/templates/ctl-scaffold/flake.lock index 20482cf5d7..91afddc9d0 100644 --- a/templates/ctl-scaffold/flake.lock +++ b/templates/ctl-scaffold/flake.lock @@ -34,23 +34,6 @@ "type": "github" } }, - "CHaP_3": { - "flake": false, - "locked": { - "lastModified": 1666726035, - "narHash": "sha256-EBodp9DJb8Z+aVbuezVwLJ9Q9XIJUXFd/n2skay3FeU=", - "owner": "input-output-hk", - "repo": "cardano-haskell-packages", - "rev": "b074321c4c8cbf2c3789436ab11eaa43e1c441a7", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-haskell-packages", - "rev": "b074321c4c8cbf2c3789436ab11eaa43e1c441a7", - "type": "github" - } - }, "HTTP": { "flake": false, "locked": { @@ -131,86 +114,6 @@ "type": "github" } }, - "HTTP_14": { - "flake": false, - "locked": { - "lastModified": 1451647621, - "narHash": "sha256-oHIyw3x0iKBexEo49YeUDV1k74ZtyYKGR2gNJXXRxts=", - "owner": "phadej", - "repo": "HTTP", - "rev": "9bc0996d412fef1787449d841277ef663ad9a915", - "type": "github" - }, - "original": { - "owner": "phadej", - "repo": "HTTP", - "type": "github" - } - }, - "HTTP_15": { - "flake": false, - "locked": { - "lastModified": 1451647621, - "narHash": "sha256-oHIyw3x0iKBexEo49YeUDV1k74ZtyYKGR2gNJXXRxts=", - "owner": "phadej", - "repo": "HTTP", - "rev": "9bc0996d412fef1787449d841277ef663ad9a915", - "type": "github" - }, - "original": { - "owner": "phadej", - "repo": "HTTP", - "type": "github" - } - }, - "HTTP_16": { - "flake": false, - "locked": { - "lastModified": 1451647621, - "narHash": "sha256-oHIyw3x0iKBexEo49YeUDV1k74ZtyYKGR2gNJXXRxts=", - "owner": "phadej", - "repo": "HTTP", - "rev": "9bc0996d412fef1787449d841277ef663ad9a915", - "type": "github" - }, - "original": { - "owner": "phadej", - "repo": "HTTP", - "type": "github" - } - }, - "HTTP_17": { - "flake": false, - "locked": { - "lastModified": 1451647621, - "narHash": "sha256-oHIyw3x0iKBexEo49YeUDV1k74ZtyYKGR2gNJXXRxts=", - "owner": "phadej", - "repo": "HTTP", - "rev": "9bc0996d412fef1787449d841277ef663ad9a915", - "type": "github" - }, - "original": { - "owner": "phadej", - "repo": "HTTP", - "type": "github" - } - }, - "HTTP_18": { - "flake": false, - "locked": { - "lastModified": 1451647621, - "narHash": "sha256-oHIyw3x0iKBexEo49YeUDV1k74ZtyYKGR2gNJXXRxts=", - "owner": "phadej", - "repo": "HTTP", - "rev": "9bc0996d412fef1787449d841277ef663ad9a915", - "type": "github" - }, - "original": { - "owner": "phadej", - "repo": "HTTP", - "type": "github" - } - }, "HTTP_2": { "flake": false, "locked": { @@ -416,36 +319,6 @@ "type": "github" } }, - "blank_5": { - "locked": { - "lastModified": 1625557891, - "narHash": "sha256-O8/MWsPBGhhyPoPLHZAuoZiiHo9q6FLlEeIDEXuj6T4=", - "owner": "divnix", - "repo": "blank", - "rev": "5a5d2684073d9f563072ed07c871d577a6c614a8", - "type": "github" - }, - "original": { - "owner": "divnix", - "repo": "blank", - "type": "github" - } - }, - "blank_6": { - "locked": { - "lastModified": 1625557891, - "narHash": "sha256-O8/MWsPBGhhyPoPLHZAuoZiiHo9q6FLlEeIDEXuj6T4=", - "owner": "divnix", - "repo": "blank", - "rev": "5a5d2684073d9f563072ed07c871d577a6c614a8", - "type": "github" - }, - "original": { - "owner": "divnix", - "repo": "blank", - "type": "github" - } - }, "bot-plutus-interface": { "inputs": { "Win32-network": "Win32-network", @@ -587,91 +460,6 @@ "type": "github" } }, - "cabal-32_14": { - "flake": false, - "locked": { - "lastModified": 1603716527, - "narHash": "sha256-X0TFfdD4KZpwl0Zr6x+PLxUt/VyKQfX7ylXHdmZIL+w=", - "owner": "haskell", - "repo": "cabal", - "rev": "48bf10787e27364730dd37a42b603cee8d6af7ee", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.2", - "repo": "cabal", - "type": "github" - } - }, - "cabal-32_15": { - "flake": false, - "locked": { - "lastModified": 1603716527, - "narHash": "sha256-sDbrmur9Zfp4mPKohCD8IDZfXJ0Tjxpmr2R+kg5PpSY=", - "owner": "haskell", - "repo": "cabal", - "rev": "94aaa8e4720081f9c75497e2735b90f6a819b08e", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.2", - "repo": "cabal", - "type": "github" - } - }, - "cabal-32_16": { - "flake": false, - "locked": { - "lastModified": 1603716527, - "narHash": "sha256-sDbrmur9Zfp4mPKohCD8IDZfXJ0Tjxpmr2R+kg5PpSY=", - "owner": "haskell", - "repo": "cabal", - "rev": "94aaa8e4720081f9c75497e2735b90f6a819b08e", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.2", - "repo": "cabal", - "type": "github" - } - }, - "cabal-32_17": { - "flake": false, - "locked": { - "lastModified": 1603716527, - "narHash": "sha256-sDbrmur9Zfp4mPKohCD8IDZfXJ0Tjxpmr2R+kg5PpSY=", - "owner": "haskell", - "repo": "cabal", - "rev": "94aaa8e4720081f9c75497e2735b90f6a819b08e", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.2", - "repo": "cabal", - "type": "github" - } - }, - "cabal-32_18": { - "flake": false, - "locked": { - "lastModified": 1603716527, - "narHash": "sha256-X0TFfdD4KZpwl0Zr6x+PLxUt/VyKQfX7ylXHdmZIL+w=", - "owner": "haskell", - "repo": "cabal", - "rev": "48bf10787e27364730dd37a42b603cee8d6af7ee", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.2", - "repo": "cabal", - "type": "github" - } - }, "cabal-32_2": { "flake": false, "locked": { @@ -893,7 +681,7 @@ "type": "github" } }, - "cabal-34_14": { + "cabal-34_2": { "flake": false, "locked": { "lastModified": 1640353650, @@ -910,14 +698,14 @@ "type": "github" } }, - "cabal-34_15": { + "cabal-34_3": { "flake": false, "locked": { - "lastModified": 1622475795, - "narHash": "sha256-chwTL304Cav+7p38d9mcb+egABWmxo2Aq+xgVBgEb/U=", + "lastModified": 1640353650, + "narHash": "sha256-N1t6M3/wqj90AEdRkeC8i923gQYUpzSr8b40qVOZ1Rk=", "owner": "haskell", "repo": "cabal", - "rev": "b086c1995cdd616fc8d91f46a21e905cc50a1049", + "rev": "942639c18c0cd8ec53e0a6f8d120091af35312cd", "type": "github" }, "original": { @@ -927,14 +715,14 @@ "type": "github" } }, - "cabal-34_16": { + "cabal-34_4": { "flake": false, "locked": { - "lastModified": 1622475795, - "narHash": "sha256-chwTL304Cav+7p38d9mcb+egABWmxo2Aq+xgVBgEb/U=", + "lastModified": 1640353650, + "narHash": "sha256-N1t6M3/wqj90AEdRkeC8i923gQYUpzSr8b40qVOZ1Rk=", "owner": "haskell", "repo": "cabal", - "rev": "b086c1995cdd616fc8d91f46a21e905cc50a1049", + "rev": "942639c18c0cd8ec53e0a6f8d120091af35312cd", "type": "github" }, "original": { @@ -944,7 +732,7 @@ "type": "github" } }, - "cabal-34_17": { + "cabal-34_5": { "flake": false, "locked": { "lastModified": 1622475795, @@ -961,14 +749,14 @@ "type": "github" } }, - "cabal-34_18": { + "cabal-34_6": { "flake": false, "locked": { - "lastModified": 1640353650, - "narHash": "sha256-N1t6M3/wqj90AEdRkeC8i923gQYUpzSr8b40qVOZ1Rk=", + "lastModified": 1622475795, + "narHash": "sha256-chwTL304Cav+7p38d9mcb+egABWmxo2Aq+xgVBgEb/U=", "owner": "haskell", "repo": "cabal", - "rev": "942639c18c0cd8ec53e0a6f8d120091af35312cd", + "rev": "b086c1995cdd616fc8d91f46a21e905cc50a1049", "type": "github" }, "original": { @@ -978,14 +766,14 @@ "type": "github" } }, - "cabal-34_2": { + "cabal-34_7": { "flake": false, "locked": { - "lastModified": 1640353650, - "narHash": "sha256-N1t6M3/wqj90AEdRkeC8i923gQYUpzSr8b40qVOZ1Rk=", + "lastModified": 1622475795, + "narHash": "sha256-chwTL304Cav+7p38d9mcb+egABWmxo2Aq+xgVBgEb/U=", "owner": "haskell", "repo": "cabal", - "rev": "942639c18c0cd8ec53e0a6f8d120091af35312cd", + "rev": "b086c1995cdd616fc8d91f46a21e905cc50a1049", "type": "github" }, "original": { @@ -995,7 +783,7 @@ "type": "github" } }, - "cabal-34_3": { + "cabal-34_8": { "flake": false, "locked": { "lastModified": 1640353650, @@ -1012,7 +800,7 @@ "type": "github" } }, - "cabal-34_4": { + "cabal-34_9": { "flake": false, "locked": { "lastModified": 1640353650, @@ -1029,194 +817,41 @@ "type": "github" } }, - "cabal-34_5": { + "cabal-36": { "flake": false, "locked": { - "lastModified": 1622475795, - "narHash": "sha256-chwTL304Cav+7p38d9mcb+egABWmxo2Aq+xgVBgEb/U=", + "lastModified": 1641652457, + "narHash": "sha256-BlFPKP4C4HRUJeAbdembX1Rms1LD380q9s0qVDeoAak=", "owner": "haskell", "repo": "cabal", - "rev": "b086c1995cdd616fc8d91f46a21e905cc50a1049", + "rev": "f27667f8ec360c475027dcaee0138c937477b070", "type": "github" }, "original": { "owner": "haskell", - "ref": "3.4", + "ref": "3.6", "repo": "cabal", "type": "github" } }, - "cabal-34_6": { + "cabal-36_10": { "flake": false, "locked": { - "lastModified": 1622475795, - "narHash": "sha256-chwTL304Cav+7p38d9mcb+egABWmxo2Aq+xgVBgEb/U=", + "lastModified": 1640163203, + "narHash": "sha256-TwDWP2CffT0j40W6zr0J1Qbu+oh3nsF1lUx9446qxZM=", "owner": "haskell", "repo": "cabal", - "rev": "b086c1995cdd616fc8d91f46a21e905cc50a1049", + "rev": "ecf418050c1821f25e2e218f1be94c31e0465df1", "type": "github" }, "original": { "owner": "haskell", - "ref": "3.4", + "ref": "3.6", "repo": "cabal", "type": "github" } }, - "cabal-34_7": { - "flake": false, - "locked": { - "lastModified": 1622475795, - "narHash": "sha256-chwTL304Cav+7p38d9mcb+egABWmxo2Aq+xgVBgEb/U=", - "owner": "haskell", - "repo": "cabal", - "rev": "b086c1995cdd616fc8d91f46a21e905cc50a1049", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.4", - "repo": "cabal", - "type": "github" - } - }, - "cabal-34_8": { - "flake": false, - "locked": { - "lastModified": 1640353650, - "narHash": "sha256-N1t6M3/wqj90AEdRkeC8i923gQYUpzSr8b40qVOZ1Rk=", - "owner": "haskell", - "repo": "cabal", - "rev": "942639c18c0cd8ec53e0a6f8d120091af35312cd", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.4", - "repo": "cabal", - "type": "github" - } - }, - "cabal-34_9": { - "flake": false, - "locked": { - "lastModified": 1640353650, - "narHash": "sha256-N1t6M3/wqj90AEdRkeC8i923gQYUpzSr8b40qVOZ1Rk=", - "owner": "haskell", - "repo": "cabal", - "rev": "942639c18c0cd8ec53e0a6f8d120091af35312cd", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.4", - "repo": "cabal", - "type": "github" - } - }, - "cabal-36": { - "flake": false, - "locked": { - "lastModified": 1641652457, - "narHash": "sha256-BlFPKP4C4HRUJeAbdembX1Rms1LD380q9s0qVDeoAak=", - "owner": "haskell", - "repo": "cabal", - "rev": "f27667f8ec360c475027dcaee0138c937477b070", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.6", - "repo": "cabal", - "type": "github" - } - }, - "cabal-36_10": { - "flake": false, - "locked": { - "lastModified": 1640163203, - "narHash": "sha256-TwDWP2CffT0j40W6zr0J1Qbu+oh3nsF1lUx9446qxZM=", - "owner": "haskell", - "repo": "cabal", - "rev": "ecf418050c1821f25e2e218f1be94c31e0465df1", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.6", - "repo": "cabal", - "type": "github" - } - }, - "cabal-36_11": { - "flake": false, - "locked": { - "lastModified": 1641652457, - "narHash": "sha256-BlFPKP4C4HRUJeAbdembX1Rms1LD380q9s0qVDeoAak=", - "owner": "haskell", - "repo": "cabal", - "rev": "f27667f8ec360c475027dcaee0138c937477b070", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.6", - "repo": "cabal", - "type": "github" - } - }, - "cabal-36_12": { - "flake": false, - "locked": { - "lastModified": 1641652457, - "narHash": "sha256-BlFPKP4C4HRUJeAbdembX1Rms1LD380q9s0qVDeoAak=", - "owner": "haskell", - "repo": "cabal", - "rev": "f27667f8ec360c475027dcaee0138c937477b070", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.6", - "repo": "cabal", - "type": "github" - } - }, - "cabal-36_13": { - "flake": false, - "locked": { - "lastModified": 1640163203, - "narHash": "sha256-TwDWP2CffT0j40W6zr0J1Qbu+oh3nsF1lUx9446qxZM=", - "owner": "haskell", - "repo": "cabal", - "rev": "ecf418050c1821f25e2e218f1be94c31e0465df1", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.6", - "repo": "cabal", - "type": "github" - } - }, - "cabal-36_14": { - "flake": false, - "locked": { - "lastModified": 1640163203, - "narHash": "sha256-TwDWP2CffT0j40W6zr0J1Qbu+oh3nsF1lUx9446qxZM=", - "owner": "haskell", - "repo": "cabal", - "rev": "ecf418050c1821f25e2e218f1be94c31e0465df1", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.6", - "repo": "cabal", - "type": "github" - } - }, - "cabal-36_15": { + "cabal-36_11": { "flake": false, "locked": { "lastModified": 1641652457, @@ -1453,22 +1088,6 @@ } }, "cardano-configurations_3": { - "flake": false, - "locked": { - "lastModified": 1662514199, - "narHash": "sha256-Z71TP5nHA9ch4DRwftz8my5RwYOjH/xA/WlcJqUTtYY=", - "owner": "input-output-hk", - "repo": "cardano-configurations", - "rev": "182b16cb743867b0b24b7af92efbf427b2b09b52", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-configurations", - "type": "github" - } - }, - "cardano-configurations_4": { "flake": false, "locked": { "lastModified": 1667387423, @@ -1577,7 +1196,7 @@ }, "cardano-mainnet-mirror_4": { "inputs": { - "nixpkgs": "nixpkgs_20" + "nixpkgs": "nixpkgs_18" }, "locked": { "lastModified": 1642701714, @@ -1596,7 +1215,7 @@ }, "cardano-mainnet-mirror_5": { "inputs": { - "nixpkgs": "nixpkgs_22" + "nixpkgs": "nixpkgs_20" }, "locked": { "lastModified": 1642701714, @@ -1615,64 +1234,7 @@ }, "cardano-mainnet-mirror_6": { "inputs": { - "nixpkgs": "nixpkgs_23" - }, - "locked": { - "lastModified": 1642701714, - "narHash": "sha256-SR3luE+ePX6U193EKE/KSEuVzWAW0YsyPYDC4hOvALs=", - "owner": "input-output-hk", - "repo": "cardano-mainnet-mirror", - "rev": "819488be9eabbba6aaa7c931559bc584d8071e3d", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "ref": "nix", - "repo": "cardano-mainnet-mirror", - "type": "github" - } - }, - "cardano-mainnet-mirror_7": { - "inputs": { - "nixpkgs": "nixpkgs_28" - }, - "locked": { - "lastModified": 1642701714, - "narHash": "sha256-SR3luE+ePX6U193EKE/KSEuVzWAW0YsyPYDC4hOvALs=", - "owner": "input-output-hk", - "repo": "cardano-mainnet-mirror", - "rev": "819488be9eabbba6aaa7c931559bc584d8071e3d", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "ref": "nix", - "repo": "cardano-mainnet-mirror", - "type": "github" - } - }, - "cardano-mainnet-mirror_8": { - "inputs": { - "nixpkgs": "nixpkgs_30" - }, - "locked": { - "lastModified": 1642701714, - "narHash": "sha256-SR3luE+ePX6U193EKE/KSEuVzWAW0YsyPYDC4hOvALs=", - "owner": "input-output-hk", - "repo": "cardano-mainnet-mirror", - "rev": "819488be9eabbba6aaa7c931559bc584d8071e3d", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "ref": "nix", - "repo": "cardano-mainnet-mirror", - "type": "github" - } - }, - "cardano-mainnet-mirror_9": { - "inputs": { - "nixpkgs": "nixpkgs_31" + "nixpkgs": "nixpkgs_21" }, "locked": { "lastModified": 1642701714, @@ -1745,40 +1307,6 @@ "haskellNix": "haskellNix_8", "iohkNix": "iohkNix_8", "membench": "membench_4", - "nixpkgs": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "cardano-node", - "node-snapshot", - "membench", - "cardano-node-snapshot", - "haskellNix", - "nixpkgs-2105" - ], - "utils": "utils_6" - }, - "locked": { - "lastModified": 1644954571, - "narHash": "sha256-c6MM1mQoS/AnTIrwaRmITK4L4i9lLNtkjOUHiseBtUs=", - "owner": "input-output-hk", - "repo": "cardano-node", - "rev": "30d62b86e7b98da28ef8ad9412e4e00a1ba1231d", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-node", - "rev": "30d62b86e7b98da28ef8ad9412e4e00a1ba1231d", - "type": "github" - } - }, - "cardano-node-snapshot_3": { - "inputs": { - "customConfig": "customConfig_12", - "haskellNix": "haskellNix_12", - "iohkNix": "iohkNix_12", - "membench": "membench_6", "nixpkgs": [ "ctl", "ogmios-nixos", @@ -1789,7 +1317,7 @@ "haskellNix", "nixpkgs-2105" ], - "utils": "utils_11" + "utils": "utils_6" }, "locked": { "lastModified": 1644954571, @@ -1863,18 +1391,16 @@ "cardano-mainnet-mirror": "cardano-mainnet-mirror_4", "cardano-node-workbench": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "blank" ], "customConfig": "customConfig_6", - "flake-compat": "flake-compat_11", + "flake-compat": "flake-compat_9", "hackageNix": "hackageNix_2", "haskellNix": "haskellNix_6", "hostNixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "nixpkgs" ], @@ -1882,16 +1408,14 @@ "nixTools": "nixTools_2", "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "haskellNix", "nixpkgs-unstable" ], "node-measured": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "blank" ], "node-process": "node-process_2", @@ -1914,58 +1438,6 @@ "type": "github" } }, - "cardano-node_4": { - "inputs": { - "cardano-mainnet-mirror": "cardano-mainnet-mirror_7", - "cardano-node-workbench": [ - "ctl", - "ogmios-nixos", - "blank" - ], - "customConfig": "customConfig_10", - "flake-compat": "flake-compat_15", - "hackageNix": "hackageNix_3", - "haskellNix": "haskellNix_10", - "hostNixpkgs": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "nixpkgs" - ], - "iohkNix": "iohkNix_10", - "nixTools": "nixTools_3", - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "haskellNix", - "nixpkgs-unstable" - ], - "node-measured": [ - "ctl", - "ogmios-nixos", - "blank" - ], - "node-process": "node-process_3", - "node-snapshot": "node-snapshot_3", - "plutus-apps": "plutus-apps_4", - "utils": "utils_14" - }, - "locked": { - "lastModified": 1659625017, - "narHash": "sha256-4IrheFeoWfvkZQndEk4fGUkOiOjcVhcyXZ6IqmvkDgg=", - "owner": "input-output-hk", - "repo": "cardano-node", - "rev": "950c4e222086fed5ca53564e642434ce9307b0b9", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "ref": "1.35.3", - "repo": "cardano-node", - "type": "github" - } - }, "cardano-prelude": { "flake": false, "locked": { @@ -2063,86 +1535,6 @@ "type": "github" } }, - "cardano-shell_14": { - "flake": false, - "locked": { - "lastModified": 1608537748, - "narHash": "sha256-PulY1GfiMgKVnBci3ex4ptk2UNYMXqGjJOxcPy2KYT4=", - "owner": "input-output-hk", - "repo": "cardano-shell", - "rev": "9392c75087cb9a3d453998f4230930dea3a95725", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-shell", - "type": "github" - } - }, - "cardano-shell_15": { - "flake": false, - "locked": { - "lastModified": 1608537748, - "narHash": "sha256-PulY1GfiMgKVnBci3ex4ptk2UNYMXqGjJOxcPy2KYT4=", - "owner": "input-output-hk", - "repo": "cardano-shell", - "rev": "9392c75087cb9a3d453998f4230930dea3a95725", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-shell", - "type": "github" - } - }, - "cardano-shell_16": { - "flake": false, - "locked": { - "lastModified": 1608537748, - "narHash": "sha256-PulY1GfiMgKVnBci3ex4ptk2UNYMXqGjJOxcPy2KYT4=", - "owner": "input-output-hk", - "repo": "cardano-shell", - "rev": "9392c75087cb9a3d453998f4230930dea3a95725", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-shell", - "type": "github" - } - }, - "cardano-shell_17": { - "flake": false, - "locked": { - "lastModified": 1608537748, - "narHash": "sha256-PulY1GfiMgKVnBci3ex4ptk2UNYMXqGjJOxcPy2KYT4=", - "owner": "input-output-hk", - "repo": "cardano-shell", - "rev": "9392c75087cb9a3d453998f4230930dea3a95725", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-shell", - "type": "github" - } - }, - "cardano-shell_18": { - "flake": false, - "locked": { - "lastModified": 1608537748, - "narHash": "sha256-PulY1GfiMgKVnBci3ex4ptk2UNYMXqGjJOxcPy2KYT4=", - "owner": "input-output-hk", - "repo": "cardano-shell", - "rev": "9392c75087cb9a3d453998f4230930dea3a95725", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-shell", - "type": "github" - } - }, "cardano-shell_2": { "flake": false, "locked": { @@ -2343,23 +1735,21 @@ "nixpkgs" ], "ogmios": "ogmios", - "ogmios-datum-cache": "ogmios-datum-cache", - "ogmios-datum-cache-nixos": "ogmios-datum-cache-nixos", "ogmios-nixos": "ogmios-nixos", "plutip": "plutip" }, "locked": { - "lastModified": 1670867033, - "narHash": "sha256-1izeIiiNYHnfTL+qs8buB+2UQ7aUkkQtBQwX09HT9ac=", + "lastModified": 1670943157, + "narHash": "sha256-d36d6WhQ/2j40gWFeQtWDcHh6x74X6lykAAjURfURVU=", "owner": "Plutonomicon", "repo": "cardano-transaction-lib", - "rev": "fc35733e483c21e55e5acabacb1d9e192f91a032", + "rev": "30f35db524a3d855852fcfb8d7069defbedbbe76", "type": "github" }, "original": { "owner": "Plutonomicon", "repo": "cardano-transaction-lib", - "rev": "fc35733e483c21e55e5acabacb1d9e192f91a032", + "rev": "30f35db524a3d855852fcfb8d7069defbedbbe76", "type": "github" } }, @@ -2378,66 +1768,6 @@ "type": "github" } }, - "customConfig_10": { - "locked": { - "lastModified": 1630400035, - "narHash": "sha256-MWaVOCzuFwp09wZIW9iHq5wWen5C69I940N1swZLEQ0=", - "owner": "input-output-hk", - "repo": "empty-flake", - "rev": "2040a05b67bf9a669ce17eca56beb14b4206a99a", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "empty-flake", - "type": "github" - } - }, - "customConfig_11": { - "locked": { - "lastModified": 1630400035, - "narHash": "sha256-MWaVOCzuFwp09wZIW9iHq5wWen5C69I940N1swZLEQ0=", - "owner": "input-output-hk", - "repo": "empty-flake", - "rev": "2040a05b67bf9a669ce17eca56beb14b4206a99a", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "empty-flake", - "type": "github" - } - }, - "customConfig_12": { - "locked": { - "lastModified": 1630400035, - "narHash": "sha256-MWaVOCzuFwp09wZIW9iHq5wWen5C69I940N1swZLEQ0=", - "owner": "input-output-hk", - "repo": "empty-flake", - "rev": "2040a05b67bf9a669ce17eca56beb14b4206a99a", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "empty-flake", - "type": "github" - } - }, - "customConfig_13": { - "locked": { - "lastModified": 1630400035, - "narHash": "sha256-MWaVOCzuFwp09wZIW9iHq5wWen5C69I940N1swZLEQ0=", - "owner": "input-output-hk", - "repo": "empty-flake", - "rev": "2040a05b67bf9a669ce17eca56beb14b4206a99a", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "empty-flake", - "type": "github" - } - }, "customConfig_2": { "locked": { "lastModified": 1630400035, @@ -2592,41 +1922,6 @@ } }, "devshell_2": { - "inputs": { - "flake-utils": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "std", - "flake-utils" - ], - "nixpkgs": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "std", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1663445644, - "narHash": "sha256-+xVlcK60x7VY1vRJbNUEAHi17ZuoQxAIH4S4iUFUGBA=", - "owner": "numtide", - "repo": "devshell", - "rev": "e3dc3e21594fe07bdb24bdf1c8657acaa4cb8f66", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "devshell", - "type": "github" - } - }, - "devshell_3": { "inputs": { "flake-utils": [ "ctl", @@ -2693,41 +1988,6 @@ } }, "dmerge_2": { - "inputs": { - "nixlib": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "std", - "nixpkgs" - ], - "yants": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "std", - "yants" - ] - }, - "locked": { - "lastModified": 1659548052, - "narHash": "sha256-fzI2gp1skGA8mQo/FBFrUAtY0GQkAIAaV/V127TJPyY=", - "owner": "divnix", - "repo": "data-merge", - "rev": "d160d18ce7b1a45b88344aa3f13ed1163954b497", - "type": "github" - }, - "original": { - "owner": "divnix", - "repo": "data-merge", - "type": "github" - } - }, - "dmerge_3": { "inputs": { "nixlib": [ "ctl", @@ -2906,16 +2166,15 @@ "flake-compat_11": { "flake": false, "locked": { - "lastModified": 1647532380, - "narHash": "sha256-wswAxyO8AJTH7d5oU8VK82yBCpqwA+p6kLgpb1f1PAY=", + "lastModified": 1635892615, + "narHash": "sha256-harGbMZr4hzat2BWBU+Y5OYXlu+fVz7E4WeQzHi5o8A=", "owner": "input-output-hk", "repo": "flake-compat", - "rev": "7da118186435255a30b5ffeabba9629c344c0bec", + "rev": "eca47d3377946315596da653862d341ee5341318", "type": "github" }, "original": { "owner": "input-output-hk", - "ref": "fixes", "repo": "flake-compat", "type": "github" } @@ -2939,15 +2198,15 @@ "flake-compat_13": { "flake": false, "locked": { - "lastModified": 1635892615, - "narHash": "sha256-harGbMZr4hzat2BWBU+Y5OYXlu+fVz7E4WeQzHi5o8A=", - "owner": "input-output-hk", + "lastModified": 1650374568, + "narHash": "sha256-Z+s0J8/r907g149rllvwhb4pKi8Wam5ij0st8PwAh+E=", + "owner": "edolstra", "repo": "flake-compat", - "rev": "eca47d3377946315596da653862d341ee5341318", + "rev": "b4a34015c698c7793d592d66adbab377907a2be8", "type": "github" }, "original": { - "owner": "input-output-hk", + "owner": "edolstra", "repo": "flake-compat", "type": "github" } @@ -2955,11 +2214,11 @@ "flake-compat_14": { "flake": false, "locked": { - "lastModified": 1650374568, - "narHash": "sha256-Z+s0J8/r907g149rllvwhb4pKi8Wam5ij0st8PwAh+E=", + "lastModified": 1668681692, + "narHash": "sha256-Ht91NGdewz8IQLtWZ9LCeNXMSXHUss+9COoqu6JLmXU=", "owner": "edolstra", "repo": "flake-compat", - "rev": "b4a34015c698c7793d592d66adbab377907a2be8", + "rev": "009399224d5e398d03b22badca40a37ac85412a1", "type": "github" }, "original": { @@ -2968,88 +2227,7 @@ "type": "github" } }, - "flake-compat_15": { - "flake": false, - "locked": { - "lastModified": 1647532380, - "narHash": "sha256-wswAxyO8AJTH7d5oU8VK82yBCpqwA+p6kLgpb1f1PAY=", - "owner": "input-output-hk", - "repo": "flake-compat", - "rev": "7da118186435255a30b5ffeabba9629c344c0bec", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "ref": "fixes", - "repo": "flake-compat", - "type": "github" - } - }, - "flake-compat_16": { - "flake": false, - "locked": { - "lastModified": 1650374568, - "narHash": "sha256-Z+s0J8/r907g149rllvwhb4pKi8Wam5ij0st8PwAh+E=", - "owner": "edolstra", - "repo": "flake-compat", - "rev": "b4a34015c698c7793d592d66adbab377907a2be8", - "type": "github" - }, - "original": { - "owner": "edolstra", - "repo": "flake-compat", - "type": "github" - } - }, - "flake-compat_17": { - "flake": false, - "locked": { - "lastModified": 1635892615, - "narHash": "sha256-harGbMZr4hzat2BWBU+Y5OYXlu+fVz7E4WeQzHi5o8A=", - "owner": "input-output-hk", - "repo": "flake-compat", - "rev": "eca47d3377946315596da653862d341ee5341318", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "flake-compat", - "type": "github" - } - }, - "flake-compat_18": { - "flake": false, - "locked": { - "lastModified": 1650374568, - "narHash": "sha256-Z+s0J8/r907g149rllvwhb4pKi8Wam5ij0st8PwAh+E=", - "owner": "edolstra", - "repo": "flake-compat", - "rev": "b4a34015c698c7793d592d66adbab377907a2be8", - "type": "github" - }, - "original": { - "owner": "edolstra", - "repo": "flake-compat", - "type": "github" - } - }, - "flake-compat_19": { - "flake": false, - "locked": { - "lastModified": 1650374568, - "narHash": "sha256-Z+s0J8/r907g149rllvwhb4pKi8Wam5ij0st8PwAh+E=", - "owner": "edolstra", - "repo": "flake-compat", - "rev": "b4a34015c698c7793d592d66adbab377907a2be8", - "type": "github" - }, - "original": { - "owner": "edolstra", - "repo": "flake-compat", - "type": "github" - } - }, - "flake-compat_2": { + "flake-compat_2": { "flake": false, "locked": { "lastModified": 1641205782, @@ -3065,22 +2243,6 @@ "type": "github" } }, - "flake-compat_20": { - "flake": false, - "locked": { - "lastModified": 1668681692, - "narHash": "sha256-Ht91NGdewz8IQLtWZ9LCeNXMSXHUss+9COoqu6JLmXU=", - "owner": "edolstra", - "repo": "flake-compat", - "rev": "009399224d5e398d03b22badca40a37ac85412a1", - "type": "github" - }, - "original": { - "owner": "edolstra", - "repo": "flake-compat", - "type": "github" - } - }, "flake-compat_3": { "flake": false, "locked": { @@ -3181,15 +2343,16 @@ "flake-compat_9": { "flake": false, "locked": { - "lastModified": 1650374568, - "narHash": "sha256-Z+s0J8/r907g149rllvwhb4pKi8Wam5ij0st8PwAh+E=", - "owner": "edolstra", + "lastModified": 1647532380, + "narHash": "sha256-wswAxyO8AJTH7d5oU8VK82yBCpqwA+p6kLgpb1f1PAY=", + "owner": "input-output-hk", "repo": "flake-compat", - "rev": "b4a34015c698c7793d592d66adbab377907a2be8", + "rev": "7da118186435255a30b5ffeabba9629c344c0bec", "type": "github" }, "original": { - "owner": "edolstra", + "owner": "input-output-hk", + "ref": "fixes", "repo": "flake-compat", "type": "github" } @@ -3467,81 +2630,6 @@ "type": "github" } }, - "flake-utils_25": { - "locked": { - "lastModified": 1644229661, - "narHash": "sha256-1YdnJAsNy69bpcjuoKdOYQX0YxZBiCYZo4Twxerqv7k=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "3cecb5b042f7f209c56ffd8371b2711a290ec797", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "flake-utils_26": { - "locked": { - "lastModified": 1623875721, - "narHash": "sha256-A8BU7bjS5GirpAUv4QA+QnJ4CceLHkcXdRp4xITDB0s=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "f7e004a55b120c02ecb6219596820fcd32ca8772", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "flake-utils_27": { - "locked": { - "lastModified": 1623875721, - "narHash": "sha256-A8BU7bjS5GirpAUv4QA+QnJ4CceLHkcXdRp4xITDB0s=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "f7e004a55b120c02ecb6219596820fcd32ca8772", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "flake-utils_28": { - "locked": { - "lastModified": 1623875721, - "narHash": "sha256-A8BU7bjS5GirpAUv4QA+QnJ4CceLHkcXdRp4xITDB0s=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "f7e004a55b120c02ecb6219596820fcd32ca8772", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "flake-utils_29": { - "locked": { - "lastModified": 1644229661, - "narHash": "sha256-1YdnJAsNy69bpcjuoKdOYQX0YxZBiCYZo4Twxerqv7k=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "3cecb5b042f7f209c56ffd8371b2711a290ec797", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, "flake-utils_3": { "locked": { "lastModified": 1619345332, @@ -3557,51 +2645,6 @@ "type": "github" } }, - "flake-utils_30": { - "locked": { - "lastModified": 1653893745, - "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "1ed9fb1935d260de5fe1c2f7ee0ebaae17ed2fa1", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "flake-utils_31": { - "locked": { - "lastModified": 1659877975, - "narHash": "sha256-zllb8aq3YO3h8B/U0/J1WBgAL8EX5yWf5pMj3G0NAmc=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "c0e246b9b83f637f4681389ecabcb2681b4f3af0", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "flake-utils_32": { - "locked": { - "lastModified": 1653893745, - "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "1ed9fb1935d260de5fe1c2f7ee0ebaae17ed2fa1", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, "flake-utils_4": { "locked": { "lastModified": 1652776076, @@ -3795,7 +2838,7 @@ "type": "github" } }, - "ghc-8.6.5-iohk_14": { + "ghc-8.6.5-iohk_2": { "flake": false, "locked": { "lastModified": 1600920045, @@ -3812,7 +2855,7 @@ "type": "github" } }, - "ghc-8.6.5-iohk_15": { + "ghc-8.6.5-iohk_3": { "flake": false, "locked": { "lastModified": 1600920045, @@ -3829,7 +2872,7 @@ "type": "github" } }, - "ghc-8.6.5-iohk_16": { + "ghc-8.6.5-iohk_4": { "flake": false, "locked": { "lastModified": 1600920045, @@ -3846,7 +2889,7 @@ "type": "github" } }, - "ghc-8.6.5-iohk_17": { + "ghc-8.6.5-iohk_5": { "flake": false, "locked": { "lastModified": 1600920045, @@ -3863,7 +2906,7 @@ "type": "github" } }, - "ghc-8.6.5-iohk_18": { + "ghc-8.6.5-iohk_6": { "flake": false, "locked": { "lastModified": 1600920045, @@ -3880,7 +2923,7 @@ "type": "github" } }, - "ghc-8.6.5-iohk_2": { + "ghc-8.6.5-iohk_7": { "flake": false, "locked": { "lastModified": 1600920045, @@ -3897,7 +2940,7 @@ "type": "github" } }, - "ghc-8.6.5-iohk_3": { + "ghc-8.6.5-iohk_8": { "flake": false, "locked": { "lastModified": 1600920045, @@ -3914,7 +2957,7 @@ "type": "github" } }, - "ghc-8.6.5-iohk_4": { + "ghc-8.6.5-iohk_9": { "flake": false, "locked": { "lastModified": 1600920045, @@ -3931,112 +2974,27 @@ "type": "github" } }, - "ghc-8.6.5-iohk_5": { + "goblins": { "flake": false, "locked": { - "lastModified": 1600920045, - "narHash": "sha256-DO6kxJz248djebZLpSzTGD6s8WRpNI9BTwUeOf5RwY8=", + "lastModified": 1598362523, + "narHash": "sha256-z9ut0y6umDIjJIRjz9KSvKgotuw06/S8QDwOtVdGiJ0=", "owner": "input-output-hk", - "repo": "ghc", - "rev": "95713a6ecce4551240da7c96b6176f980af75cae", + "repo": "goblins", + "rev": "cde90a2b27f79187ca8310b6549331e59595e7ba", "type": "github" }, "original": { "owner": "input-output-hk", - "ref": "release/8.6.5-iohk", - "repo": "ghc", + "repo": "goblins", + "rev": "cde90a2b27f79187ca8310b6549331e59595e7ba", "type": "github" } }, - "ghc-8.6.5-iohk_6": { - "flake": false, - "locked": { - "lastModified": 1600920045, - "narHash": "sha256-DO6kxJz248djebZLpSzTGD6s8WRpNI9BTwUeOf5RwY8=", - "owner": "input-output-hk", - "repo": "ghc", - "rev": "95713a6ecce4551240da7c96b6176f980af75cae", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "ref": "release/8.6.5-iohk", - "repo": "ghc", - "type": "github" - } - }, - "ghc-8.6.5-iohk_7": { - "flake": false, - "locked": { - "lastModified": 1600920045, - "narHash": "sha256-DO6kxJz248djebZLpSzTGD6s8WRpNI9BTwUeOf5RwY8=", - "owner": "input-output-hk", - "repo": "ghc", - "rev": "95713a6ecce4551240da7c96b6176f980af75cae", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "ref": "release/8.6.5-iohk", - "repo": "ghc", - "type": "github" - } - }, - "ghc-8.6.5-iohk_8": { - "flake": false, - "locked": { - "lastModified": 1600920045, - "narHash": "sha256-DO6kxJz248djebZLpSzTGD6s8WRpNI9BTwUeOf5RwY8=", - "owner": "input-output-hk", - "repo": "ghc", - "rev": "95713a6ecce4551240da7c96b6176f980af75cae", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "ref": "release/8.6.5-iohk", - "repo": "ghc", - "type": "github" - } - }, - "ghc-8.6.5-iohk_9": { - "flake": false, - "locked": { - "lastModified": 1600920045, - "narHash": "sha256-DO6kxJz248djebZLpSzTGD6s8WRpNI9BTwUeOf5RwY8=", - "owner": "input-output-hk", - "repo": "ghc", - "rev": "95713a6ecce4551240da7c96b6176f980af75cae", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "ref": "release/8.6.5-iohk", - "repo": "ghc", - "type": "github" - } - }, - "goblins": { - "flake": false, - "locked": { - "lastModified": 1598362523, - "narHash": "sha256-z9ut0y6umDIjJIRjz9KSvKgotuw06/S8QDwOtVdGiJ0=", - "owner": "input-output-hk", - "repo": "goblins", - "rev": "cde90a2b27f79187ca8310b6549331e59595e7ba", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "goblins", - "rev": "cde90a2b27f79187ca8310b6549331e59595e7ba", - "type": "github" - } - }, - "gomod2nix": { - "inputs": { - "nixpkgs": "nixpkgs_15", - "utils": "utils_5" + "gomod2nix": { + "inputs": { + "nixpkgs": "nixpkgs_15", + "utils": "utils_5" }, "locked": { "lastModified": 1655245309, @@ -4054,7 +3012,7 @@ }, "gomod2nix_2": { "inputs": { - "nixpkgs": "nixpkgs_25", + "nixpkgs": "nixpkgs_23", "utils": "utils_10" }, "locked": { @@ -4071,25 +3029,6 @@ "type": "github" } }, - "gomod2nix_3": { - "inputs": { - "nixpkgs": "nixpkgs_33", - "utils": "utils_15" - }, - "locked": { - "lastModified": 1655245309, - "narHash": "sha256-d/YPoQ/vFn1+GTmSdvbSBSTOai61FONxB4+Lt6w/IVI=", - "owner": "tweag", - "repo": "gomod2nix", - "rev": "40d32f82fc60d66402eb0972e6e368aeab3faf58", - "type": "github" - }, - "original": { - "owner": "tweag", - "repo": "gomod2nix", - "type": "github" - } - }, "hackage": { "flake": false, "locked": { @@ -4138,22 +3077,6 @@ "type": "github" } }, - "hackageNix_3": { - "flake": false, - "locked": { - "lastModified": 1656898050, - "narHash": "sha256-jemAb/Wm/uT+QhV12GlyeA5euSWxYzr2HOYoK4MZps0=", - "owner": "input-output-hk", - "repo": "hackage.nix", - "rev": "4f1dd530219ca1165f523ffb2c62213ebede4046", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "hackage.nix", - "type": "github" - } - }, "hackage_10": { "flake": false, "locked": { @@ -4186,70 +3109,6 @@ "type": "github" } }, - "hackage_12": { - "flake": false, - "locked": { - "lastModified": 1643073363, - "narHash": "sha256-66oSXQKEDIOSQ2uKAS9facCX/Zuh/jFgyFDtxEqN9sk=", - "owner": "input-output-hk", - "repo": "hackage.nix", - "rev": "4ef9bd3a32316ce236164c7ebff00ebeb33236e2", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "hackage.nix", - "type": "github" - } - }, - "hackage_13": { - "flake": false, - "locked": { - "lastModified": 1643073363, - "narHash": "sha256-66oSXQKEDIOSQ2uKAS9facCX/Zuh/jFgyFDtxEqN9sk=", - "owner": "input-output-hk", - "repo": "hackage.nix", - "rev": "4ef9bd3a32316ce236164c7ebff00ebeb33236e2", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "hackage.nix", - "type": "github" - } - }, - "hackage_14": { - "flake": false, - "locked": { - "lastModified": 1639098768, - "narHash": "sha256-DZ4sG8FeDxWvBLixrj0jELXjtebZ0SCCPmQW43HNzIE=", - "owner": "input-output-hk", - "repo": "hackage.nix", - "rev": "c7b123af6b0b9b364cab03363504d42dca16a4b5", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "hackage.nix", - "type": "github" - } - }, - "hackage_15": { - "flake": false, - "locked": { - "lastModified": 1667783503, - "narHash": "sha256-25ZZPMQi9YQbXz3tZYPECVUI0FAQkJcDUIA/v8+mo9E=", - "owner": "input-output-hk", - "repo": "hackage.nix", - "rev": "1f77f69e6dd92b5130cbe681b74e8fc0d29d63ff", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "hackage.nix", - "type": "github" - } - }, "hackage_2": { "flake": false, "locked": { @@ -4522,7 +3381,7 @@ "cabal-34": "cabal-34_13", "cabal-36": "cabal-36_11", "cardano-shell": "cardano-shell_13", - "flake-compat": "flake-compat_13", + "flake-compat": "flake-compat_11", "flake-utils": "flake-utils_21", "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_13", "hackage": "hackage_11", @@ -4530,8 +3389,7 @@ "hydra": "hydra_7", "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "nixpkgs" ], "nixpkgs-2003": "nixpkgs-2003_13", @@ -4557,47 +3415,6 @@ "type": "github" } }, - "haskell-nix_5": { - "inputs": { - "HTTP": "HTTP_18", - "cabal-32": "cabal-32_18", - "cabal-34": "cabal-34_18", - "cabal-36": "cabal-36_15", - "cardano-shell": "cardano-shell_18", - "flake-compat": "flake-compat_17", - "flake-utils": "flake-utils_29", - "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_18", - "hackage": "hackage_15", - "hpc-coveralls": "hpc-coveralls_18", - "hydra": "hydra_9", - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "nixpkgs" - ], - "nixpkgs-2003": "nixpkgs-2003_18", - "nixpkgs-2105": "nixpkgs-2105_18", - "nixpkgs-2111": "nixpkgs-2111_18", - "nixpkgs-2205": "nixpkgs-2205_3", - "nixpkgs-unstable": "nixpkgs-unstable_18", - "old-ghc-nix": "old-ghc-nix_18", - "stackage": "stackage_18", - "tullia": "tullia_3" - }, - "locked": { - "lastModified": 1667783630, - "narHash": "sha256-IzbvNxsOVxHJGY70qAzaEOPmz4Fw93+4qLFd2on/ZAc=", - "owner": "input-output-hk", - "repo": "haskell.nix", - "rev": "f1f330065199dc4eca017bc21de0c67bc46df393", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "haskell.nix", - "type": "github" - } - }, "haskellNix": { "inputs": { "HTTP": "HTTP_2", @@ -4637,36 +3454,36 @@ "type": "github" } }, - "haskellNix_10": { + "haskellNix_2": { "inputs": { - "HTTP": "HTTP_14", - "cabal-32": "cabal-32_14", - "cabal-34": "cabal-34_14", - "cabal-36": "cabal-36_12", - "cardano-shell": "cardano-shell_14", - "flake-utils": "flake-utils_25", - "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_14", + "HTTP": "HTTP_4", + "cabal-32": "cabal-32_4", + "cabal-34": "cabal-34_4", + "cabal-36": "cabal-36_4", + "cardano-shell": "cardano-shell_4", + "flake-utils": "flake-utils_9", + "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_4", "hackage": [ "ctl", - "ogmios-nixos", + "ogmios", "cardano-node", "hackageNix" ], - "hpc-coveralls": "hpc-coveralls_14", - "hydra": "hydra_8", - "nix-tools": "nix-tools_12", + "hpc-coveralls": "hpc-coveralls_4", + "hydra": "hydra_4", + "nix-tools": "nix-tools_4", "nixpkgs": [ "ctl", - "ogmios-nixos", + "ogmios", "cardano-node", "nixpkgs" ], - "nixpkgs-2003": "nixpkgs-2003_14", - "nixpkgs-2105": "nixpkgs-2105_14", - "nixpkgs-2111": "nixpkgs-2111_14", - "nixpkgs-unstable": "nixpkgs-unstable_14", - "old-ghc-nix": "old-ghc-nix_14", - "stackage": "stackage_14" + "nixpkgs-2003": "nixpkgs-2003_4", + "nixpkgs-2105": "nixpkgs-2105_4", + "nixpkgs-2111": "nixpkgs-2111_4", + "nixpkgs-unstable": "nixpkgs-unstable_4", + "old-ghc-nix": "old-ghc-nix_4", + "stackage": "stackage_4" }, "locked": { "lastModified": 1656898207, @@ -4682,31 +3499,31 @@ "type": "github" } }, - "haskellNix_11": { + "haskellNix_3": { "inputs": { - "HTTP": "HTTP_15", - "cabal-32": "cabal-32_15", - "cabal-34": "cabal-34_15", - "cabal-36": "cabal-36_13", - "cardano-shell": "cardano-shell_15", - "flake-utils": "flake-utils_26", - "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_15", - "hackage": "hackage_12", - "hpc-coveralls": "hpc-coveralls_15", - "nix-tools": "nix-tools_13", + "HTTP": "HTTP_5", + "cabal-32": "cabal-32_5", + "cabal-34": "cabal-34_5", + "cabal-36": "cabal-36_5", + "cardano-shell": "cardano-shell_5", + "flake-utils": "flake-utils_10", + "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_5", + "hackage": "hackage_4", + "hpc-coveralls": "hpc-coveralls_5", + "nix-tools": "nix-tools_5", "nixpkgs": [ "ctl", - "ogmios-nixos", + "ogmios", "cardano-node", "node-snapshot", "nixpkgs" ], - "nixpkgs-2003": "nixpkgs-2003_15", - "nixpkgs-2105": "nixpkgs-2105_15", - "nixpkgs-2111": "nixpkgs-2111_15", - "nixpkgs-unstable": "nixpkgs-unstable_15", - "old-ghc-nix": "old-ghc-nix_15", - "stackage": "stackage_15" + "nixpkgs-2003": "nixpkgs-2003_5", + "nixpkgs-2105": "nixpkgs-2105_5", + "nixpkgs-2111": "nixpkgs-2111_5", + "nixpkgs-unstable": "nixpkgs-unstable_5", + "old-ghc-nix": "old-ghc-nix_5", + "stackage": "stackage_5" }, "locked": { "lastModified": 1643073543, @@ -4722,33 +3539,33 @@ "type": "github" } }, - "haskellNix_12": { + "haskellNix_4": { "inputs": { - "HTTP": "HTTP_16", - "cabal-32": "cabal-32_16", - "cabal-34": "cabal-34_16", - "cabal-36": "cabal-36_14", - "cardano-shell": "cardano-shell_16", - "flake-utils": "flake-utils_27", - "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_16", - "hackage": "hackage_13", - "hpc-coveralls": "hpc-coveralls_16", - "nix-tools": "nix-tools_14", + "HTTP": "HTTP_6", + "cabal-32": "cabal-32_6", + "cabal-34": "cabal-34_6", + "cabal-36": "cabal-36_6", + "cardano-shell": "cardano-shell_6", + "flake-utils": "flake-utils_11", + "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_6", + "hackage": "hackage_5", + "hpc-coveralls": "hpc-coveralls_6", + "nix-tools": "nix-tools_6", "nixpkgs": [ "ctl", - "ogmios-nixos", + "ogmios", "cardano-node", "node-snapshot", "membench", "cardano-node-snapshot", "nixpkgs" ], - "nixpkgs-2003": "nixpkgs-2003_16", - "nixpkgs-2105": "nixpkgs-2105_16", - "nixpkgs-2111": "nixpkgs-2111_16", - "nixpkgs-unstable": "nixpkgs-unstable_16", - "old-ghc-nix": "old-ghc-nix_16", - "stackage": "stackage_16" + "nixpkgs-2003": "nixpkgs-2003_6", + "nixpkgs-2105": "nixpkgs-2105_6", + "nixpkgs-2111": "nixpkgs-2111_6", + "nixpkgs-unstable": "nixpkgs-unstable_6", + "old-ghc-nix": "old-ghc-nix_6", + "stackage": "stackage_6" }, "locked": { "lastModified": 1643073543, @@ -4764,174 +3581,7 @@ "type": "github" } }, - "haskellNix_13": { - "inputs": { - "HTTP": "HTTP_17", - "cabal-32": "cabal-32_17", - "cabal-34": "cabal-34_17", - "cardano-shell": "cardano-shell_17", - "flake-utils": "flake-utils_28", - "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_17", - "hackage": "hackage_14", - "hpc-coveralls": "hpc-coveralls_17", - "nix-tools": "nix-tools_15", - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "plutus-example", - "nixpkgs" - ], - "nixpkgs-2003": "nixpkgs-2003_17", - "nixpkgs-2105": "nixpkgs-2105_17", - "nixpkgs-2111": "nixpkgs-2111_17", - "nixpkgs-unstable": "nixpkgs-unstable_17", - "old-ghc-nix": "old-ghc-nix_17", - "stackage": "stackage_17" - }, - "locked": { - "lastModified": 1639098904, - "narHash": "sha256-7VrCNEaKGLm4pTOS11dt1dRL2033oqrNCfal0uONsqA=", - "owner": "input-output-hk", - "repo": "haskell.nix", - "rev": "b18c6ce0867fee77f12ecf41dc6c67f7a59d9826", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "haskell.nix", - "type": "github" - } - }, - "haskellNix_2": { - "inputs": { - "HTTP": "HTTP_4", - "cabal-32": "cabal-32_4", - "cabal-34": "cabal-34_4", - "cabal-36": "cabal-36_4", - "cardano-shell": "cardano-shell_4", - "flake-utils": "flake-utils_9", - "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_4", - "hackage": [ - "ctl", - "ogmios", - "cardano-node", - "hackageNix" - ], - "hpc-coveralls": "hpc-coveralls_4", - "hydra": "hydra_4", - "nix-tools": "nix-tools_4", - "nixpkgs": [ - "ctl", - "ogmios", - "cardano-node", - "nixpkgs" - ], - "nixpkgs-2003": "nixpkgs-2003_4", - "nixpkgs-2105": "nixpkgs-2105_4", - "nixpkgs-2111": "nixpkgs-2111_4", - "nixpkgs-unstable": "nixpkgs-unstable_4", - "old-ghc-nix": "old-ghc-nix_4", - "stackage": "stackage_4" - }, - "locked": { - "lastModified": 1656898207, - "narHash": "sha256-hshNfCnrmhIvM4T+O0/JRZymsHmq9YiIJ4bpzNVTD98=", - "owner": "input-output-hk", - "repo": "haskell.nix", - "rev": "21230476adfef5fa77fb19fbda396f22006a02bc", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "haskell.nix", - "type": "github" - } - }, - "haskellNix_3": { - "inputs": { - "HTTP": "HTTP_5", - "cabal-32": "cabal-32_5", - "cabal-34": "cabal-34_5", - "cabal-36": "cabal-36_5", - "cardano-shell": "cardano-shell_5", - "flake-utils": "flake-utils_10", - "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_5", - "hackage": "hackage_4", - "hpc-coveralls": "hpc-coveralls_5", - "nix-tools": "nix-tools_5", - "nixpkgs": [ - "ctl", - "ogmios", - "cardano-node", - "node-snapshot", - "nixpkgs" - ], - "nixpkgs-2003": "nixpkgs-2003_5", - "nixpkgs-2105": "nixpkgs-2105_5", - "nixpkgs-2111": "nixpkgs-2111_5", - "nixpkgs-unstable": "nixpkgs-unstable_5", - "old-ghc-nix": "old-ghc-nix_5", - "stackage": "stackage_5" - }, - "locked": { - "lastModified": 1643073543, - "narHash": "sha256-g2l/KDWzMRTFRugNVcx3CPZeyA5BNcH9/zDiqFpprB4=", - "owner": "input-output-hk", - "repo": "haskell.nix", - "rev": "14f740c7c8f535581c30b1697018e389680e24cb", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "haskell.nix", - "type": "github" - } - }, - "haskellNix_4": { - "inputs": { - "HTTP": "HTTP_6", - "cabal-32": "cabal-32_6", - "cabal-34": "cabal-34_6", - "cabal-36": "cabal-36_6", - "cardano-shell": "cardano-shell_6", - "flake-utils": "flake-utils_11", - "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_6", - "hackage": "hackage_5", - "hpc-coveralls": "hpc-coveralls_6", - "nix-tools": "nix-tools_6", - "nixpkgs": [ - "ctl", - "ogmios", - "cardano-node", - "node-snapshot", - "membench", - "cardano-node-snapshot", - "nixpkgs" - ], - "nixpkgs-2003": "nixpkgs-2003_6", - "nixpkgs-2105": "nixpkgs-2105_6", - "nixpkgs-2111": "nixpkgs-2111_6", - "nixpkgs-unstable": "nixpkgs-unstable_6", - "old-ghc-nix": "old-ghc-nix_6", - "stackage": "stackage_6" - }, - "locked": { - "lastModified": 1643073543, - "narHash": "sha256-g2l/KDWzMRTFRugNVcx3CPZeyA5BNcH9/zDiqFpprB4=", - "owner": "input-output-hk", - "repo": "haskell.nix", - "rev": "14f740c7c8f535581c30b1697018e389680e24cb", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "haskell.nix", - "type": "github" - } - }, - "haskellNix_5": { + "haskellNix_5": { "inputs": { "HTTP": "HTTP_7", "cabal-32": "cabal-32_7", @@ -4982,8 +3632,7 @@ "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_9", "hackage": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "hackageNix" ], @@ -4992,8 +3641,7 @@ "nix-tools": "nix-tools_8", "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "nixpkgs" ], @@ -5032,8 +3680,7 @@ "nix-tools": "nix-tools_9", "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "nixpkgs" @@ -5073,8 +3720,7 @@ "nix-tools": "nix-tools_10", "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "membench", @@ -5115,8 +3761,7 @@ "nix-tools": "nix-tools_11", "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "plutus-example", @@ -5240,86 +3885,6 @@ "type": "github" } }, - "hpc-coveralls_14": { - "flake": false, - "locked": { - "lastModified": 1607498076, - "narHash": "sha256-8uqsEtivphgZWYeUo5RDUhp6bO9j2vaaProQxHBltQk=", - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "rev": "14df0f7d229f4cd2e79f8eabb1a740097fdfa430", - "type": "github" - }, - "original": { - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "type": "github" - } - }, - "hpc-coveralls_15": { - "flake": false, - "locked": { - "lastModified": 1607498076, - "narHash": "sha256-8uqsEtivphgZWYeUo5RDUhp6bO9j2vaaProQxHBltQk=", - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "rev": "14df0f7d229f4cd2e79f8eabb1a740097fdfa430", - "type": "github" - }, - "original": { - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "type": "github" - } - }, - "hpc-coveralls_16": { - "flake": false, - "locked": { - "lastModified": 1607498076, - "narHash": "sha256-8uqsEtivphgZWYeUo5RDUhp6bO9j2vaaProQxHBltQk=", - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "rev": "14df0f7d229f4cd2e79f8eabb1a740097fdfa430", - "type": "github" - }, - "original": { - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "type": "github" - } - }, - "hpc-coveralls_17": { - "flake": false, - "locked": { - "lastModified": 1607498076, - "narHash": "sha256-8uqsEtivphgZWYeUo5RDUhp6bO9j2vaaProQxHBltQk=", - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "rev": "14df0f7d229f4cd2e79f8eabb1a740097fdfa430", - "type": "github" - }, - "original": { - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "type": "github" - } - }, - "hpc-coveralls_18": { - "flake": false, - "locked": { - "lastModified": 1607498076, - "narHash": "sha256-8uqsEtivphgZWYeUo5RDUhp6bO9j2vaaProQxHBltQk=", - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "rev": "14df0f7d229f4cd2e79f8eabb1a740097fdfa430", - "type": "github" - }, - "original": { - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "type": "github" - } - }, "hpc-coveralls_2": { "flake": false, "locked": { @@ -5596,8 +4161,7 @@ "nix": "nix_6", "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "haskellNix", "hydra", @@ -5623,8 +4187,7 @@ "nix": "nix_7", "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "haskell-nix", "hydra", "nix", @@ -5644,59 +4207,8 @@ "type": "indirect" } }, - "hydra_8": { - "inputs": { - "nix": "nix_8", - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "haskellNix", - "hydra", - "nix", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1646878427, - "narHash": "sha256-KtbrofMtN8GlM7D+n90kixr7QpSlVmdN+vK5CA/aRzc=", - "owner": "NixOS", - "repo": "hydra", - "rev": "28b682b85b7efc5cf7974065792a1f22203a5927", - "type": "github" - }, - "original": { - "id": "hydra", - "type": "indirect" - } - }, - "hydra_9": { - "inputs": { - "nix": "nix_9", - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "haskell-nix", - "hydra", - "nix", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1646878427, - "narHash": "sha256-KtbrofMtN8GlM7D+n90kixr7QpSlVmdN+vK5CA/aRzc=", - "owner": "NixOS", - "repo": "hydra", - "rev": "28b682b85b7efc5cf7974065792a1f22203a5927", - "type": "github" - }, - "original": { - "id": "hydra", - "type": "indirect" - } - }, - "hysterical-screams": { - "flake": false, + "hysterical-screams": { + "flake": false, "locked": { "lastModified": 1654007733, "narHash": "sha256-d4N3rUzg45BUs5Lx/kK7vXYsLMNoO15dlzo7t8lGIXA=", @@ -5828,30 +4340,6 @@ } }, "iohk-nix_4": { - "inputs": { - "nixpkgs": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1649070135, - "narHash": "sha256-UFKqcOSdPWk3TYUCPHF22p1zf7aXQpCmmgf7UMg7fWA=", - "owner": "input-output-hk", - "repo": "iohk-nix", - "rev": "cecab9c71d1064f05f1615eead56ac0b9196bc20", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "iohk-nix", - "rev": "cecab9c71d1064f05f1615eead56ac0b9196bc20", - "type": "github" - } - }, - "iohk-nix_5": { "inputs": { "nixpkgs": [ "ctl", @@ -5896,104 +4384,6 @@ "type": "github" } }, - "iohkNix_10": { - "inputs": { - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1653579289, - "narHash": "sha256-wveDdPsgB/3nAGAdFaxrcgLEpdi0aJ5kEVNtI+YqVfo=", - "owner": "input-output-hk", - "repo": "iohk-nix", - "rev": "edb2d2df2ebe42bbdf03a0711115cf6213c9d366", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "iohk-nix", - "type": "github" - } - }, - "iohkNix_11": { - "inputs": { - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1631778944, - "narHash": "sha256-N5eCcUYtZ5kUOl/JJGjx6ZzhA3uIn1itDRTiRV+3jLw=", - "owner": "input-output-hk", - "repo": "iohk-nix", - "rev": "db2c75a09c696271194bb3ef25ec8e9839b594b7", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "iohk-nix", - "type": "github" - } - }, - "iohkNix_12": { - "inputs": { - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "membench", - "cardano-node-snapshot", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1631778944, - "narHash": "sha256-N5eCcUYtZ5kUOl/JJGjx6ZzhA3uIn1itDRTiRV+3jLw=", - "owner": "input-output-hk", - "repo": "iohk-nix", - "rev": "db2c75a09c696271194bb3ef25ec8e9839b594b7", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "iohk-nix", - "type": "github" - } - }, - "iohkNix_13": { - "inputs": { - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "plutus-example", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1633964277, - "narHash": "sha256-7G/BK514WiMRr90EswNBthe8SmH9tjPaTBba/RW/VA8=", - "owner": "input-output-hk", - "repo": "iohk-nix", - "rev": "1e51437aac8a0e49663cb21e781f34163c81ebfb", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "iohk-nix", - "type": "github" - } - }, "iohkNix_2": { "inputs": { "nixpkgs": [ @@ -6096,8 +4486,7 @@ "inputs": { "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "nixpkgs" ] @@ -6120,8 +4509,7 @@ "inputs": { "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "nixpkgs" @@ -6145,8 +4533,7 @@ "inputs": { "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "membench", @@ -6172,8 +4559,7 @@ "inputs": { "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "plutus-example", @@ -6354,38 +4740,6 @@ "type": "github" } }, - "lowdown-src_8": { - "flake": false, - "locked": { - "lastModified": 1633514407, - "narHash": "sha256-Dw32tiMjdK9t3ETl5fzGrutQTzh2rufgZV4A/BbxuD4=", - "owner": "kristapsdz", - "repo": "lowdown", - "rev": "d2c2b44ff6c27b936ec27358a2653caaef8f73b8", - "type": "github" - }, - "original": { - "owner": "kristapsdz", - "repo": "lowdown", - "type": "github" - } - }, - "lowdown-src_9": { - "flake": false, - "locked": { - "lastModified": 1633514407, - "narHash": "sha256-Dw32tiMjdK9t3ETl5fzGrutQTzh2rufgZV4A/BbxuD4=", - "owner": "kristapsdz", - "repo": "lowdown", - "rev": "d2c2b44ff6c27b936ec27358a2653caaef8f73b8", - "type": "github" - }, - "original": { - "owner": "kristapsdz", - "repo": "lowdown", - "type": "github" - } - }, "mdbook-kroki-preprocessor": { "flake": false, "locked": { @@ -6418,22 +4772,6 @@ "type": "github" } }, - "mdbook-kroki-preprocessor_3": { - "flake": false, - "locked": { - "lastModified": 1661755005, - "narHash": "sha256-1TJuUzfyMycWlOQH67LR63/ll2GDZz25I3JfScy/Jnw=", - "owner": "JoelCourtney", - "repo": "mdbook-kroki-preprocessor", - "rev": "93adb5716d035829efed27f65f2f0833a7d3e76f", - "type": "github" - }, - "original": { - "owner": "JoelCourtney", - "repo": "mdbook-kroki-preprocessor", - "type": "github" - } - }, "membench": { "inputs": { "cardano-mainnet-mirror": "cardano-mainnet-mirror_2", @@ -6530,23 +4868,20 @@ "cardano-mainnet-mirror": "cardano-mainnet-mirror_5", "cardano-node-measured": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot" ], "cardano-node-process": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot" ], "cardano-node-snapshot": "cardano-node-snapshot_2", "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "nixpkgs" @@ -6572,8 +4907,7 @@ "cardano-mainnet-mirror": "cardano-mainnet-mirror_6", "cardano-node-measured": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "membench", @@ -6581,8 +4915,7 @@ ], "cardano-node-process": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "membench", @@ -6590,8 +4923,7 @@ ], "cardano-node-snapshot": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "membench", @@ -6599,8 +4931,7 @@ ], "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "membench", @@ -6623,153 +4954,35 @@ "type": "github" } }, - "membench_5": { + "n2c": { "inputs": { - "cardano-mainnet-mirror": "cardano-mainnet-mirror_8", - "cardano-node-measured": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot" - ], - "cardano-node-process": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot" - ], - "cardano-node-snapshot": "cardano-node-snapshot_3", + "flake-utils": "flake-utils_16", "nixpkgs": [ "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot", + "ogmios", + "haskell-nix", + "tullia", + "std", "nixpkgs" - ], - "ouroboros-network": "ouroboros-network_7" + ] }, "locked": { - "lastModified": 1645070579, - "narHash": "sha256-AxL6tCOnzYnE6OquoFzj+X1bLDr1PQx3d8/vXm+rbfA=", - "owner": "input-output-hk", - "repo": "cardano-memory-benchmark", - "rev": "65643e000186de1335e24ec89159db8ba85e1c1a", + "lastModified": 1665039323, + "narHash": "sha256-SAh3ZjFGsaCI8FRzXQyp56qcGdAqgKEfJWPCQ0Sr7tQ=", + "owner": "nlewo", + "repo": "nix2container", + "rev": "b008fe329ffb59b67bf9e7b08ede6ee792f2741a", "type": "github" }, "original": { - "owner": "input-output-hk", - "repo": "cardano-memory-benchmark", + "owner": "nlewo", + "repo": "nix2container", "type": "github" } }, - "membench_6": { - "inputs": { - "cardano-mainnet-mirror": "cardano-mainnet-mirror_9", - "cardano-node-measured": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "membench", - "cardano-node-snapshot" - ], - "cardano-node-process": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "membench", - "cardano-node-snapshot" - ], - "cardano-node-snapshot": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "membench", - "cardano-node-snapshot" - ], - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "membench", - "cardano-node-snapshot", - "nixpkgs" - ], - "ouroboros-network": "ouroboros-network_6" - }, - "locked": { - "lastModified": 1644547122, - "narHash": "sha256-8nWK+ScMACvRQLbA27gwXNoZver+Wx/cF7V37044koY=", - "owner": "input-output-hk", - "repo": "cardano-memory-benchmark", - "rev": "9d8ff4b9394de0421ee95caa511d01163de88b77", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-memory-benchmark", - "type": "github" - } - }, - "n2c": { - "inputs": { - "flake-utils": "flake-utils_16", - "nixpkgs": [ - "ctl", - "ogmios", - "haskell-nix", - "tullia", - "std", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1665039323, - "narHash": "sha256-SAh3ZjFGsaCI8FRzXQyp56qcGdAqgKEfJWPCQ0Sr7tQ=", - "owner": "nlewo", - "repo": "nix2container", - "rev": "b008fe329ffb59b67bf9e7b08ede6ee792f2741a", - "type": "github" - }, - "original": { - "owner": "nlewo", - "repo": "nix2container", - "type": "github" - } - }, - "n2c_2": { + "n2c_2": { "inputs": { "flake-utils": "flake-utils_24", - "nixpkgs": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "std", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1665039323, - "narHash": "sha256-SAh3ZjFGsaCI8FRzXQyp56qcGdAqgKEfJWPCQ0Sr7tQ=", - "owner": "nlewo", - "repo": "nix2container", - "rev": "b008fe329ffb59b67bf9e7b08ede6ee792f2741a", - "type": "github" - }, - "original": { - "owner": "nlewo", - "repo": "nix2container", - "type": "github" - } - }, - "n2c_3": { - "inputs": { - "flake-utils": "flake-utils_32", "nixpkgs": [ "ctl", "ogmios-nixos", @@ -6857,51 +5070,7 @@ }, "nix-nomad_2": { "inputs": { - "flake-compat": "flake-compat_14", - "flake-utils": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "nix2container", - "flake-utils" - ], - "gomod2nix": "gomod2nix_2", - "nixpkgs": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "nixpkgs" - ], - "nixpkgs-lib": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1658277770, - "narHash": "sha256-T/PgG3wUn8Z2rnzfxf2VqlR1CBjInPE0l1yVzXxPnt0=", - "owner": "tristanpemble", - "repo": "nix-nomad", - "rev": "054adcbdd0a836ae1c20951b67ed549131fd2d70", - "type": "github" - }, - "original": { - "owner": "tristanpemble", - "repo": "nix-nomad", - "type": "github" - } - }, - "nix-nomad_3": { - "inputs": { - "flake-compat": "flake-compat_18", + "flake-compat": "flake-compat_12", "flake-utils": [ "ctl", "ogmios-nixos", @@ -6910,7 +5079,7 @@ "nix2container", "flake-utils" ], - "gomod2nix": "gomod2nix_3", + "gomod2nix": "gomod2nix_2", "nixpkgs": [ "ctl", "ogmios-nixos", @@ -6988,70 +5157,6 @@ "type": "github" } }, - "nix-tools_12": { - "flake": false, - "locked": { - "lastModified": 1649424170, - "narHash": "sha256-XgKXWispvv5RCvZzPb+p7e6Hy3LMuRjafKMl7kXzxGw=", - "owner": "input-output-hk", - "repo": "nix-tools", - "rev": "e109c94016e3b6e0db7ed413c793e2d4bdb24aa7", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "nix-tools", - "type": "github" - } - }, - "nix-tools_13": { - "flake": false, - "locked": { - "lastModified": 1636018067, - "narHash": "sha256-ng306fkuwr6V/malWtt3979iAC4yMVDDH2ViwYB6sQE=", - "owner": "input-output-hk", - "repo": "nix-tools", - "rev": "ed5bd7215292deba55d6ab7a4e8c21f8b1564dda", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "nix-tools", - "type": "github" - } - }, - "nix-tools_14": { - "flake": false, - "locked": { - "lastModified": 1636018067, - "narHash": "sha256-ng306fkuwr6V/malWtt3979iAC4yMVDDH2ViwYB6sQE=", - "owner": "input-output-hk", - "repo": "nix-tools", - "rev": "ed5bd7215292deba55d6ab7a4e8c21f8b1564dda", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "nix-tools", - "type": "github" - } - }, - "nix-tools_15": { - "flake": false, - "locked": { - "lastModified": 1636018067, - "narHash": "sha256-ng306fkuwr6V/malWtt3979iAC4yMVDDH2ViwYB6sQE=", - "owner": "input-output-hk", - "repo": "nix-tools", - "rev": "ed5bd7215292deba55d6ab7a4e8c21f8b1564dda", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "nix-tools", - "type": "github" - } - }, "nix-tools_2": { "flake": false, "locked": { @@ -7202,26 +5307,7 @@ "nix2container_2": { "inputs": { "flake-utils": "flake-utils_22", - "nixpkgs": "nixpkgs_26" - }, - "locked": { - "lastModified": 1658567952, - "narHash": "sha256-XZ4ETYAMU7XcpEeAFP3NOl9yDXNuZAen/aIJ84G+VgA=", - "owner": "nlewo", - "repo": "nix2container", - "rev": "60bb43d405991c1378baf15a40b5811a53e32ffa", - "type": "github" - }, - "original": { - "owner": "nlewo", - "repo": "nix2container", - "type": "github" - } - }, - "nix2container_3": { - "inputs": { - "flake-utils": "flake-utils_30", - "nixpkgs": "nixpkgs_34" + "nixpkgs": "nixpkgs_24" }, "locked": { "lastModified": 1658567952, @@ -7269,22 +5355,6 @@ "type": "github" } }, - "nixTools_3": { - "flake": false, - "locked": { - "lastModified": 1649424170, - "narHash": "sha256-XgKXWispvv5RCvZzPb+p7e6Hy3LMuRjafKMl7kXzxGw=", - "owner": "input-output-hk", - "repo": "nix-tools", - "rev": "e109c94016e3b6e0db7ed413c793e2d4bdb24aa7", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "nix-tools", - "type": "github" - } - }, "nix_2": { "inputs": { "lowdown-src": "lowdown-src_2", @@ -7372,7 +5442,7 @@ "nix_6": { "inputs": { "lowdown-src": "lowdown-src_6", - "nixpkgs": "nixpkgs_21", + "nixpkgs": "nixpkgs_19", "nixpkgs-regression": "nixpkgs-regression_6" }, "locked": { @@ -7393,7 +5463,7 @@ "nix_7": { "inputs": { "lowdown-src": "lowdown-src_7", - "nixpkgs": "nixpkgs_24", + "nixpkgs": "nixpkgs_22", "nixpkgs-regression": "nixpkgs-regression_7" }, "locked": { @@ -7411,48 +5481,6 @@ "type": "github" } }, - "nix_8": { - "inputs": { - "lowdown-src": "lowdown-src_8", - "nixpkgs": "nixpkgs_29", - "nixpkgs-regression": "nixpkgs-regression_8" - }, - "locked": { - "lastModified": 1643066034, - "narHash": "sha256-xEPeMcNJVOeZtoN+d+aRwolpW8mFSEQx76HTRdlhPhg=", - "owner": "NixOS", - "repo": "nix", - "rev": "a1cd7e58606a41fcf62bf8637804cf8306f17f62", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "2.6.0", - "repo": "nix", - "type": "github" - } - }, - "nix_9": { - "inputs": { - "lowdown-src": "lowdown-src_9", - "nixpkgs": "nixpkgs_32", - "nixpkgs-regression": "nixpkgs-regression_9" - }, - "locked": { - "lastModified": 1643066034, - "narHash": "sha256-xEPeMcNJVOeZtoN+d+aRwolpW8mFSEQx76HTRdlhPhg=", - "owner": "NixOS", - "repo": "nix", - "rev": "a1cd7e58606a41fcf62bf8637804cf8306f17f62", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "2.6.0", - "repo": "nix", - "type": "github" - } - }, "nixago": { "inputs": { "flake-utils": [ @@ -7495,50 +5523,6 @@ } }, "nixago_2": { - "inputs": { - "flake-utils": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "std", - "flake-utils" - ], - "nixago-exts": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "std", - "blank" - ], - "nixpkgs": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "std", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1661824785, - "narHash": "sha256-/PnwdWoO/JugJZHtDUioQp3uRiWeXHUdgvoyNbXesz8=", - "owner": "nix-community", - "repo": "nixago", - "rev": "8c1f9e5f1578d4b2ea989f618588d62a335083c3", - "type": "github" - }, - "original": { - "owner": "nix-community", - "repo": "nixago", - "type": "github" - } - }, - "nixago_3": { "inputs": { "flake-utils": [ "ctl", @@ -7674,86 +5658,6 @@ "type": "github" } }, - "nixpkgs-2003_14": { - "locked": { - "lastModified": 1620055814, - "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-20.03-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2003_15": { - "locked": { - "lastModified": 1620055814, - "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-20.03-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2003_16": { - "locked": { - "lastModified": 1620055814, - "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-20.03-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2003_17": { - "locked": { - "lastModified": 1620055814, - "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-20.03-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2003_18": { - "locked": { - "lastModified": 1620055814, - "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-20.03-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, "nixpkgs-2003_2": { "locked": { "lastModified": 1620055814, @@ -7786,87 +5690,7 @@ "type": "github" } }, - "nixpkgs-2003_4": { - "locked": { - "lastModified": 1620055814, - "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-20.03-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2003_5": { - "locked": { - "lastModified": 1620055814, - "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-20.03-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2003_6": { - "locked": { - "lastModified": 1620055814, - "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-20.03-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2003_7": { - "locked": { - "lastModified": 1620055814, - "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-20.03-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2003_8": { - "locked": { - "lastModified": 1620055814, - "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-20.03-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2003_9": { + "nixpkgs-2003_4": { "locked": { "lastModified": 1620055814, "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", @@ -7882,87 +5706,87 @@ "type": "github" } }, - "nixpkgs-2105": { + "nixpkgs-2003_5": { "locked": { - "lastModified": 1645296114, - "narHash": "sha256-y53N7TyIkXsjMpOG7RhvqJFGDacLs9HlyHeSTBioqYU=", + "lastModified": 1620055814, + "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "530a53dcbc9437363471167a5e4762c5fcfa34a1", + "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", "type": "github" }, "original": { "owner": "NixOS", - "ref": "nixpkgs-21.05-darwin", + "ref": "nixpkgs-20.03-darwin", "repo": "nixpkgs", "type": "github" } }, - "nixpkgs-2105_10": { + "nixpkgs-2003_6": { "locked": { - "lastModified": 1640283157, - "narHash": "sha256-6Ddfop+rKE+Gl9Tjp9YIrkfoYPzb8F80ergdjcq3/MY=", + "lastModified": 1620055814, + "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "dde1557825c5644c869c5efc7448dc03722a8f09", + "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", "type": "github" }, "original": { "owner": "NixOS", - "ref": "nixpkgs-21.05-darwin", + "ref": "nixpkgs-20.03-darwin", "repo": "nixpkgs", "type": "github" } }, - "nixpkgs-2105_11": { + "nixpkgs-2003_7": { "locked": { - "lastModified": 1640283157, - "narHash": "sha256-6Ddfop+rKE+Gl9Tjp9YIrkfoYPzb8F80ergdjcq3/MY=", + "lastModified": 1620055814, + "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "dde1557825c5644c869c5efc7448dc03722a8f09", + "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", "type": "github" }, "original": { "owner": "NixOS", - "ref": "nixpkgs-21.05-darwin", + "ref": "nixpkgs-20.03-darwin", "repo": "nixpkgs", "type": "github" } }, - "nixpkgs-2105_12": { + "nixpkgs-2003_8": { "locked": { - "lastModified": 1630481079, - "narHash": "sha256-leWXLchbAbqOlLT6tju631G40SzQWPqaAXQG3zH1Imw=", + "lastModified": 1620055814, + "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "110a2c9ebbf5d4a94486854f18a37a938cfacbbb", + "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", "type": "github" }, "original": { "owner": "NixOS", - "ref": "nixpkgs-21.05-darwin", + "ref": "nixpkgs-20.03-darwin", "repo": "nixpkgs", "type": "github" } }, - "nixpkgs-2105_13": { + "nixpkgs-2003_9": { "locked": { - "lastModified": 1659914493, - "narHash": "sha256-lkA5X3VNMKirvA+SUzvEhfA7XquWLci+CGi505YFAIs=", + "lastModified": 1620055814, + "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "022caabb5f2265ad4006c1fa5b1ebe69fb0c3faf", + "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", "type": "github" }, "original": { "owner": "NixOS", - "ref": "nixpkgs-21.05-darwin", + "ref": "nixpkgs-20.03-darwin", "repo": "nixpkgs", "type": "github" } }, - "nixpkgs-2105_14": { + "nixpkgs-2105": { "locked": { "lastModified": 1645296114, "narHash": "sha256-y53N7TyIkXsjMpOG7RhvqJFGDacLs9HlyHeSTBioqYU=", @@ -7978,7 +5802,7 @@ "type": "github" } }, - "nixpkgs-2105_15": { + "nixpkgs-2105_10": { "locked": { "lastModified": 1640283157, "narHash": "sha256-6Ddfop+rKE+Gl9Tjp9YIrkfoYPzb8F80ergdjcq3/MY=", @@ -7994,7 +5818,7 @@ "type": "github" } }, - "nixpkgs-2105_16": { + "nixpkgs-2105_11": { "locked": { "lastModified": 1640283157, "narHash": "sha256-6Ddfop+rKE+Gl9Tjp9YIrkfoYPzb8F80ergdjcq3/MY=", @@ -8010,7 +5834,7 @@ "type": "github" } }, - "nixpkgs-2105_17": { + "nixpkgs-2105_12": { "locked": { "lastModified": 1630481079, "narHash": "sha256-leWXLchbAbqOlLT6tju631G40SzQWPqaAXQG3zH1Imw=", @@ -8026,7 +5850,7 @@ "type": "github" } }, - "nixpkgs-2105_18": { + "nixpkgs-2105_13": { "locked": { "lastModified": 1659914493, "narHash": "sha256-lkA5X3VNMKirvA+SUzvEhfA7XquWLci+CGi505YFAIs=", @@ -8250,86 +6074,6 @@ "type": "github" } }, - "nixpkgs-2111_14": { - "locked": { - "lastModified": 1648744337, - "narHash": "sha256-bYe1dFJAXovjqiaPKrmAbSBEK5KUkgwVaZcTbSoJ7hg=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "0a58eebd8ec65ffdef2ce9562784123a73922052", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-21.11-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2111_15": { - "locked": { - "lastModified": 1640283207, - "narHash": "sha256-SCwl7ZnCfMDsuSYvwIroiAlk7n33bW8HFfY8NvKhcPA=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "64c7e3388bbd9206e437713351e814366e0c3284", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-21.11-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2111_16": { - "locked": { - "lastModified": 1640283207, - "narHash": "sha256-SCwl7ZnCfMDsuSYvwIroiAlk7n33bW8HFfY8NvKhcPA=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "64c7e3388bbd9206e437713351e814366e0c3284", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-21.11-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2111_17": { - "locked": { - "lastModified": 1638410074, - "narHash": "sha256-MQYI4k4XkoTzpeRjq5wl+1NShsl1CKq8MISFuZ81sWs=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "5b80f23502f8e902612a8c631dfce383e1c56596", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-21.11-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2111_18": { - "locked": { - "lastModified": 1659446231, - "narHash": "sha256-hekabNdTdgR/iLsgce5TGWmfIDZ86qjPhxDg/8TlzhE=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "eabc38219184cc3e04a974fe31857d8e0eac098d", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-21.11-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, "nixpkgs-2111_2": { "locked": { "lastModified": 1648744337, @@ -8490,22 +6234,6 @@ "type": "github" } }, - "nixpkgs-2205_3": { - "locked": { - "lastModified": 1663981975, - "narHash": "sha256-TKaxWAVJR+a5JJauKZqibmaM5e/Pi5tBDx9s8fl/kSE=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "309faedb8338d3ae8ad8f1043b3ccf48c9cc2970", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-22.05-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, "nixpkgs-regression": { "locked": { "lastModified": 1643052045, @@ -8539,189 +6267,79 @@ "nixpkgs-regression_3": { "locked": { "lastModified": 1643052045, - "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "indirect" - } - }, - "nixpkgs-regression_4": { - "locked": { - "lastModified": 1643052045, - "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "indirect" - } - }, - "nixpkgs-regression_5": { - "locked": { - "lastModified": 1643052045, - "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "indirect" - } - }, - "nixpkgs-regression_6": { - "locked": { - "lastModified": 1643052045, - "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "indirect" - } - }, - "nixpkgs-regression_7": { - "locked": { - "lastModified": 1643052045, - "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "indirect" - } - }, - "nixpkgs-regression_8": { - "locked": { - "lastModified": 1643052045, - "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "indirect" - } - }, - "nixpkgs-regression_9": { - "locked": { - "lastModified": 1643052045, - "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "indirect" - } - }, - "nixpkgs-unstable": { - "locked": { - "lastModified": 1648219316, - "narHash": "sha256-Ctij+dOi0ZZIfX5eMhgwugfvB+WZSrvVNAyAuANOsnQ=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "30d3d79b7d3607d56546dd2a6b49e156ba0ec634", - "type": "github" - }, - "original": { + "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", "owner": "NixOS", - "ref": "nixpkgs-unstable", "repo": "nixpkgs", + "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", "type": "github" + }, + "original": { + "id": "nixpkgs", + "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", + "type": "indirect" } }, - "nixpkgs-unstable_10": { + "nixpkgs-regression_4": { "locked": { - "lastModified": 1641285291, - "narHash": "sha256-KYaOBNGar3XWTxTsYPr9P6u74KAqNq0wobEC236U+0c=", + "lastModified": 1643052045, + "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "0432195a4b8d68faaa7d3d4b355260a3120aeeae", + "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", "type": "github" }, "original": { - "owner": "NixOS", - "ref": "nixpkgs-unstable", - "repo": "nixpkgs", - "type": "github" + "id": "nixpkgs", + "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", + "type": "indirect" } }, - "nixpkgs-unstable_11": { + "nixpkgs-regression_5": { "locked": { - "lastModified": 1641285291, - "narHash": "sha256-KYaOBNGar3XWTxTsYPr9P6u74KAqNq0wobEC236U+0c=", + "lastModified": 1643052045, + "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "0432195a4b8d68faaa7d3d4b355260a3120aeeae", + "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", "type": "github" }, "original": { - "owner": "NixOS", - "ref": "nixpkgs-unstable", - "repo": "nixpkgs", - "type": "github" + "id": "nixpkgs", + "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", + "type": "indirect" } }, - "nixpkgs-unstable_12": { + "nixpkgs-regression_6": { "locked": { - "lastModified": 1635295995, - "narHash": "sha256-sGYiXjFlxTTMNb4NSkgvX+knOOTipE6gqwPUQpxNF+c=", + "lastModified": 1643052045, + "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "22a500a3f87bbce73bd8d777ef920b43a636f018", + "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", "type": "github" }, "original": { - "owner": "NixOS", - "ref": "nixpkgs-unstable", - "repo": "nixpkgs", - "type": "github" + "id": "nixpkgs", + "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", + "type": "indirect" } }, - "nixpkgs-unstable_13": { + "nixpkgs-regression_7": { "locked": { - "lastModified": 1663905476, - "narHash": "sha256-0CSwRKaYravh9v6qSlBpM0gNg0UhKT2lL7Yn6Zbx7UM=", + "lastModified": 1643052045, + "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "e14f9fb57315f0d4abde222364f19f88c77d2b79", + "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", "type": "github" }, "original": { - "owner": "NixOS", - "ref": "nixpkgs-unstable", - "repo": "nixpkgs", - "type": "github" + "id": "nixpkgs", + "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", + "type": "indirect" } }, - "nixpkgs-unstable_14": { + "nixpkgs-unstable": { "locked": { "lastModified": 1648219316, "narHash": "sha256-Ctij+dOi0ZZIfX5eMhgwugfvB+WZSrvVNAyAuANOsnQ=", @@ -8737,7 +6355,7 @@ "type": "github" } }, - "nixpkgs-unstable_15": { + "nixpkgs-unstable_10": { "locked": { "lastModified": 1641285291, "narHash": "sha256-KYaOBNGar3XWTxTsYPr9P6u74KAqNq0wobEC236U+0c=", @@ -8753,7 +6371,7 @@ "type": "github" } }, - "nixpkgs-unstable_16": { + "nixpkgs-unstable_11": { "locked": { "lastModified": 1641285291, "narHash": "sha256-KYaOBNGar3XWTxTsYPr9P6u74KAqNq0wobEC236U+0c=", @@ -8769,7 +6387,7 @@ "type": "github" } }, - "nixpkgs-unstable_17": { + "nixpkgs-unstable_12": { "locked": { "lastModified": 1635295995, "narHash": "sha256-sGYiXjFlxTTMNb4NSkgvX+knOOTipE6gqwPUQpxNF+c=", @@ -8785,7 +6403,7 @@ "type": "github" } }, - "nixpkgs-unstable_18": { + "nixpkgs-unstable_13": { "locked": { "lastModified": 1663905476, "narHash": "sha256-0CSwRKaYravh9v6qSlBpM0gNg0UhKT2lL7Yn6Zbx7UM=", @@ -9050,34 +6668,31 @@ }, "nixpkgs_18": { "locked": { - "lastModified": 1634172192, - "narHash": "sha256-FBF4U/T+bMg4sEyT/zkgasvVquGzgdAf4y8uCosKMmo=", + "lastModified": 1642336556, + "narHash": "sha256-QSPPbFEwy0T0DrIuSzAACkaANPQaR1lZR/nHZGz9z04=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "2cf9db0e3d45b9d00f16f2836cb1297bcadc475e", + "rev": "f3d9d4bd898cca7d04af2ae4f6ef01f2219df3d6", "type": "github" }, "original": { - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "2cf9db0e3d45b9d00f16f2836cb1297bcadc475e", - "type": "github" + "id": "nixpkgs", + "type": "indirect" } }, "nixpkgs_19": { "locked": { - "lastModified": 1634172192, - "narHash": "sha256-FBF4U/T+bMg4sEyT/zkgasvVquGzgdAf4y8uCosKMmo=", + "lastModified": 1632864508, + "narHash": "sha256-d127FIvGR41XbVRDPVvozUPQ/uRHbHwvfyKHwEt5xFM=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "2cf9db0e3d45b9d00f16f2836cb1297bcadc475e", + "rev": "82891b5e2c2359d7e58d08849e4c89511ab94234", "type": "github" }, "original": { - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "2cf9db0e3d45b9d00f16f2836cb1297bcadc475e", - "type": "github" + "id": "nixpkgs", + "ref": "nixos-21.05-small", + "type": "indirect" } }, "nixpkgs_2": { @@ -9111,35 +6726,6 @@ } }, "nixpkgs_21": { - "locked": { - "lastModified": 1632864508, - "narHash": "sha256-d127FIvGR41XbVRDPVvozUPQ/uRHbHwvfyKHwEt5xFM=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "82891b5e2c2359d7e58d08849e4c89511ab94234", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "ref": "nixos-21.05-small", - "type": "indirect" - } - }, - "nixpkgs_22": { - "locked": { - "lastModified": 1642336556, - "narHash": "sha256-QSPPbFEwy0T0DrIuSzAACkaANPQaR1lZR/nHZGz9z04=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "f3d9d4bd898cca7d04af2ae4f6ef01f2219df3d6", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "type": "indirect" - } - }, - "nixpkgs_23": { "locked": { "lastModified": 1642336556, "narHash": "sha256-QSPPbFEwy0T0DrIuSzAACkaANPQaR1lZR/nHZGz9z04=", @@ -9153,7 +6739,7 @@ "type": "indirect" } }, - "nixpkgs_24": { + "nixpkgs_22": { "locked": { "lastModified": 1632864508, "narHash": "sha256-d127FIvGR41XbVRDPVvozUPQ/uRHbHwvfyKHwEt5xFM=", @@ -9168,7 +6754,7 @@ "type": "indirect" } }, - "nixpkgs_25": { + "nixpkgs_23": { "locked": { "lastModified": 1653581809, "narHash": "sha256-Uvka0V5MTGbeOfWte25+tfRL3moECDh1VwokWSZUdoY=", @@ -9184,7 +6770,7 @@ "type": "github" } }, - "nixpkgs_26": { + "nixpkgs_24": { "locked": { "lastModified": 1654807842, "narHash": "sha256-ADymZpr6LuTEBXcy6RtFHcUZdjKTBRTMYwu19WOx17E=", @@ -9199,7 +6785,7 @@ "type": "github" } }, - "nixpkgs_27": { + "nixpkgs_25": { "locked": { "lastModified": 1665087388, "narHash": "sha256-FZFPuW9NWHJteATOf79rZfwfRn5fE0wi9kRzvGfDHPA=", @@ -9215,35 +6801,6 @@ "type": "github" } }, - "nixpkgs_28": { - "locked": { - "lastModified": 1642336556, - "narHash": "sha256-QSPPbFEwy0T0DrIuSzAACkaANPQaR1lZR/nHZGz9z04=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "f3d9d4bd898cca7d04af2ae4f6ef01f2219df3d6", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "type": "indirect" - } - }, - "nixpkgs_29": { - "locked": { - "lastModified": 1632864508, - "narHash": "sha256-d127FIvGR41XbVRDPVvozUPQ/uRHbHwvfyKHwEt5xFM=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "82891b5e2c2359d7e58d08849e4c89511ab94234", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "ref": "nixos-21.05-small", - "type": "indirect" - } - }, "nixpkgs_3": { "locked": { "lastModified": 1619531122, @@ -9258,96 +6815,6 @@ "type": "indirect" } }, - "nixpkgs_30": { - "locked": { - "lastModified": 1642336556, - "narHash": "sha256-QSPPbFEwy0T0DrIuSzAACkaANPQaR1lZR/nHZGz9z04=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "f3d9d4bd898cca7d04af2ae4f6ef01f2219df3d6", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "type": "indirect" - } - }, - "nixpkgs_31": { - "locked": { - "lastModified": 1642336556, - "narHash": "sha256-QSPPbFEwy0T0DrIuSzAACkaANPQaR1lZR/nHZGz9z04=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "f3d9d4bd898cca7d04af2ae4f6ef01f2219df3d6", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "type": "indirect" - } - }, - "nixpkgs_32": { - "locked": { - "lastModified": 1632864508, - "narHash": "sha256-d127FIvGR41XbVRDPVvozUPQ/uRHbHwvfyKHwEt5xFM=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "82891b5e2c2359d7e58d08849e4c89511ab94234", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "ref": "nixos-21.05-small", - "type": "indirect" - } - }, - "nixpkgs_33": { - "locked": { - "lastModified": 1653581809, - "narHash": "sha256-Uvka0V5MTGbeOfWte25+tfRL3moECDh1VwokWSZUdoY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "83658b28fe638a170a19b8933aa008b30640fbd1", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixos-unstable", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs_34": { - "locked": { - "lastModified": 1654807842, - "narHash": "sha256-ADymZpr6LuTEBXcy6RtFHcUZdjKTBRTMYwu19WOx17E=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "fc909087cc3386955f21b4665731dbdaceefb1d8", - "type": "github" - }, - "original": { - "owner": "NixOS", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs_35": { - "locked": { - "lastModified": 1665087388, - "narHash": "sha256-FZFPuW9NWHJteATOf79rZfwfRn5fE0wi9kRzvGfDHPA=", - "owner": "nixos", - "repo": "nixpkgs", - "rev": "95fda953f6db2e9496d2682c4fc7b82f959878f7", - "type": "github" - }, - "original": { - "owner": "nixos", - "ref": "nixpkgs-unstable", - "repo": "nixpkgs", - "type": "github" - } - }, "nixpkgs_4": { "locked": { "lastModified": 1656461576, @@ -9424,35 +6891,19 @@ "nixpkgs_9": { "locked": { "lastModified": 1632864508, - "narHash": "sha256-d127FIvGR41XbVRDPVvozUPQ/uRHbHwvfyKHwEt5xFM=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "82891b5e2c2359d7e58d08849e4c89511ab94234", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "ref": "nixos-21.05-small", - "type": "indirect" - } - }, - "node-process": { - "flake": false, - "locked": { - "lastModified": 1654323094, - "narHash": "sha256-zbmpZeBgUUly8QgR2mrVUN0A+0iLczufNvCCRxAo3GY=", - "owner": "input-output-hk", - "repo": "cardano-node", - "rev": "ec20745f17cb4fa8824fdf341d1412c774bc94b9", + "narHash": "sha256-d127FIvGR41XbVRDPVvozUPQ/uRHbHwvfyKHwEt5xFM=", + "owner": "NixOS", + "repo": "nixpkgs", + "rev": "82891b5e2c2359d7e58d08849e4c89511ab94234", "type": "github" }, "original": { - "owner": "input-output-hk", - "repo": "cardano-node", - "type": "github" + "id": "nixpkgs", + "ref": "nixos-21.05-small", + "type": "indirect" } }, - "node-process_2": { + "node-process": { "flake": false, "locked": { "lastModified": 1654323094, @@ -9468,7 +6919,7 @@ "type": "github" } }, - "node-process_3": { + "node-process_2": { "flake": false, "locked": { "lastModified": 1654323094, @@ -9524,8 +6975,7 @@ "membench": "membench_3", "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "haskellNix", @@ -9549,38 +6999,6 @@ "type": "github" } }, - "node-snapshot_3": { - "inputs": { - "customConfig": "customConfig_11", - "haskellNix": "haskellNix_11", - "iohkNix": "iohkNix_11", - "membench": "membench_5", - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "haskellNix", - "nixpkgs-2105" - ], - "plutus-example": "plutus-example_3", - "utils": "utils_13" - }, - "locked": { - "lastModified": 1645120669, - "narHash": "sha256-2MKfGsYS5n69+pfqNHb4IH/E95ok1MD7mhEYfUpRcz4=", - "owner": "input-output-hk", - "repo": "cardano-node", - "rev": "7f00e3ea5a61609e19eeeee4af35241571efdf5c", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-node", - "rev": "7f00e3ea5a61609e19eeeee4af35241571efdf5c", - "type": "github" - } - }, "ogmios": { "inputs": { "CHaP": "CHaP", @@ -9612,113 +7030,32 @@ "type": "github" } }, - "ogmios-datum-cache": { - "inputs": { - "flake-compat": "flake-compat_9", - "nixpkgs": "nixpkgs_18", - "unstable_nixpkgs": "unstable_nixpkgs" - }, - "locked": { - "lastModified": 1668515878, - "narHash": "sha256-r4aOSSz9jZZPreUkgOpS3ZpYFV4cxNVCUQFIpBZ8Y9k=", - "owner": "mlabs-haskell", - "repo": "ogmios-datum-cache", - "rev": "862c6bfcb6110b8fe816e26b3bba105dfb492b24", - "type": "github" - }, - "original": { - "owner": "mlabs-haskell", - "repo": "ogmios-datum-cache", - "rev": "862c6bfcb6110b8fe816e26b3bba105dfb492b24", - "type": "github" - } - }, - "ogmios-datum-cache-nixos": { - "inputs": { - "cardano-configurations": "cardano-configurations_3", - "cardano-node": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "cardano-node" - ], - "flake-compat": "flake-compat_10", - "nixpkgs": "nixpkgs_19", - "ogmios": "ogmios_2", - "unstable_nixpkgs": "unstable_nixpkgs_2" - }, - "locked": { - "lastModified": 1667912888, - "narHash": "sha256-6KS0c1PZ44ZTcE2ioXC0GiIuyTKnG5MeKX7nDZ6Knus=", - "owner": "mlabs-haskell", - "repo": "ogmios-datum-cache", - "rev": "a33a576fefe2248e9906e7b8044a30955cca0061", - "type": "github" - }, - "original": { - "owner": "mlabs-haskell", - "ref": "marton/nixos-module", - "repo": "ogmios-datum-cache", - "type": "github" - } - }, "ogmios-nixos": { - "inputs": { - "CHaP": "CHaP_3", - "blank": "blank_5", - "cardano-configurations": "cardano-configurations_4", - "cardano-node": "cardano-node_4", - "flake-compat": "flake-compat_16", - "haskell-nix": "haskell-nix_5", - "iohk-nix": "iohk-nix_5", - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "haskell-nix", - "nixpkgs-unstable" - ] - }, - "locked": { - "lastModified": 1668087435, - "narHash": "sha256-pbx/+mP2pu4vQuTV3YtFXrOZOVOBS9JH9eDqgjnHyZ4=", - "owner": "mlabs-haskell", - "repo": "ogmios", - "rev": "3b229c1795efa30243485730b78ea053992fdc7a", - "type": "github" - }, - "original": { - "owner": "mlabs-haskell", - "repo": "ogmios", - "type": "github" - } - }, - "ogmios_2": { "inputs": { "CHaP": "CHaP_2", "blank": "blank_3", + "cardano-configurations": "cardano-configurations_3", "cardano-node": "cardano-node_3", - "flake-compat": "flake-compat_12", + "flake-compat": "flake-compat_10", "haskell-nix": "haskell-nix_4", "iohk-nix": "iohk-nix_4", "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "haskell-nix", "nixpkgs-unstable" ] }, "locked": { - "lastModified": 1667904967, - "narHash": "sha256-KAWv/plBLRqZiBYUl0plXQdMPzFs7G89VhTbg122kA4=", + "lastModified": 1668087435, + "narHash": "sha256-pbx/+mP2pu4vQuTV3YtFXrOZOVOBS9JH9eDqgjnHyZ4=", "owner": "mlabs-haskell", "repo": "ogmios", - "rev": "dbc1a03dca6a876a25d54a8716504837909c6e8c", + "rev": "3b229c1795efa30243485730b78ea053992fdc7a", "type": "github" }, "original": { "owner": "mlabs-haskell", - "ref": "staging", "repo": "ogmios", "type": "github" } @@ -9808,91 +7145,6 @@ "type": "github" } }, - "old-ghc-nix_14": { - "flake": false, - "locked": { - "lastModified": 1631092763, - "narHash": "sha256-sIKgO+z7tj4lw3u6oBZxqIhDrzSkvpHtv0Kki+lh9Fg=", - "owner": "angerman", - "repo": "old-ghc-nix", - "rev": "af48a7a7353e418119b6dfe3cd1463a657f342b8", - "type": "github" - }, - "original": { - "owner": "angerman", - "ref": "master", - "repo": "old-ghc-nix", - "type": "github" - } - }, - "old-ghc-nix_15": { - "flake": false, - "locked": { - "lastModified": 1631092763, - "narHash": "sha256-sIKgO+z7tj4lw3u6oBZxqIhDrzSkvpHtv0Kki+lh9Fg=", - "owner": "angerman", - "repo": "old-ghc-nix", - "rev": "af48a7a7353e418119b6dfe3cd1463a657f342b8", - "type": "github" - }, - "original": { - "owner": "angerman", - "ref": "master", - "repo": "old-ghc-nix", - "type": "github" - } - }, - "old-ghc-nix_16": { - "flake": false, - "locked": { - "lastModified": 1631092763, - "narHash": "sha256-sIKgO+z7tj4lw3u6oBZxqIhDrzSkvpHtv0Kki+lh9Fg=", - "owner": "angerman", - "repo": "old-ghc-nix", - "rev": "af48a7a7353e418119b6dfe3cd1463a657f342b8", - "type": "github" - }, - "original": { - "owner": "angerman", - "ref": "master", - "repo": "old-ghc-nix", - "type": "github" - } - }, - "old-ghc-nix_17": { - "flake": false, - "locked": { - "lastModified": 1631092763, - "narHash": "sha256-sIKgO+z7tj4lw3u6oBZxqIhDrzSkvpHtv0Kki+lh9Fg=", - "owner": "angerman", - "repo": "old-ghc-nix", - "rev": "af48a7a7353e418119b6dfe3cd1463a657f342b8", - "type": "github" - }, - "original": { - "owner": "angerman", - "ref": "master", - "repo": "old-ghc-nix", - "type": "github" - } - }, - "old-ghc-nix_18": { - "flake": false, - "locked": { - "lastModified": 1631092763, - "narHash": "sha256-sIKgO+z7tj4lw3u6oBZxqIhDrzSkvpHtv0Kki+lh9Fg=", - "owner": "angerman", - "repo": "old-ghc-nix", - "rev": "af48a7a7353e418119b6dfe3cd1463a657f342b8", - "type": "github" - }, - "original": { - "owner": "angerman", - "ref": "master", - "repo": "old-ghc-nix", - "type": "github" - } - }, "old-ghc-nix_2": { "flake": false, "locked": { @@ -10127,45 +7379,13 @@ "type": "github" } }, - "ouroboros-network_6": { - "flake": false, - "locked": { - "lastModified": 1643385024, - "narHash": "sha256-9R4Z1jBsTcEgBHxhzjCJnroEcdfMsTjf8kwg6uPue+Q=", - "owner": "input-output-hk", - "repo": "ouroboros-network", - "rev": "8e97076176d465f5f4f86d5b5596220272630649", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "ouroboros-network", - "type": "github" - } - }, - "ouroboros-network_7": { - "flake": false, - "locked": { - "lastModified": 1643385024, - "narHash": "sha256-9R4Z1jBsTcEgBHxhzjCJnroEcdfMsTjf8kwg6uPue+Q=", - "owner": "input-output-hk", - "repo": "ouroboros-network", - "rev": "8e97076176d465f5f4f86d5b5596220272630649", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "ouroboros-network", - "type": "github" - } - }, "plutip": { "inputs": { "bot-plutus-interface": [ "ctl", "bot-plutus-interface" ], - "flake-compat": "flake-compat_19", + "flake-compat": "flake-compat_13", "haskell-nix": [ "ctl", "bot-plutus-interface", @@ -10264,22 +7484,6 @@ "type": "github" } }, - "plutus-apps_4": { - "flake": false, - "locked": { - "lastModified": 1654271253, - "narHash": "sha256-GQDPzyVtcbbESmckMvzoTEKa/UWWJH7djh1TWQjzFow=", - "owner": "input-output-hk", - "repo": "plutus-apps", - "rev": "61de89d33340279b8452a0dbb52a87111db87e82", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "plutus-apps", - "type": "github" - } - }, "plutus-example": { "inputs": { "customConfig": "customConfig_5", @@ -10314,40 +7518,8 @@ "plutus-example_2": { "inputs": { "customConfig": "customConfig_9", - "haskellNix": "haskellNix_9", - "iohkNix": "iohkNix_9", - "nixpkgs": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "cardano-node", - "node-snapshot", - "plutus-example", - "haskellNix", - "nixpkgs-2105" - ], - "utils": "utils_7" - }, - "locked": { - "lastModified": 1640022647, - "narHash": "sha256-M+YnF7Zj/7QK2pu0T75xNVaX0eEeijtBH8yz+jEHIMM=", - "owner": "input-output-hk", - "repo": "cardano-node", - "rev": "814df2c146f5d56f8c35a681fe75e85b905aed5d", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-node", - "rev": "814df2c146f5d56f8c35a681fe75e85b905aed5d", - "type": "github" - } - }, - "plutus-example_3": { - "inputs": { - "customConfig": "customConfig_13", - "haskellNix": "haskellNix_13", - "iohkNix": "iohkNix_13", + "haskellNix": "haskellNix_9", + "iohkNix": "iohkNix_9", "nixpkgs": [ "ctl", "ogmios-nixos", @@ -10357,7 +7529,7 @@ "haskellNix", "nixpkgs-2105" ], - "utils": "utils_12" + "utils": "utils_7" }, "locked": { "lastModified": 1640022647, @@ -10430,7 +7602,7 @@ "root": { "inputs": { "ctl": "ctl", - "flake-compat": "flake-compat_20", + "flake-compat": "flake-compat_14", "nixpkgs": [ "ctl", "nixpkgs" @@ -10534,86 +7706,6 @@ "type": "github" } }, - "stackage_14": { - "flake": false, - "locked": { - "lastModified": 1656898145, - "narHash": "sha256-EMgMzdANg6r5gEUkMtv5ujDo2/Kx7JJXoXiDKjDVoLw=", - "owner": "input-output-hk", - "repo": "stackage.nix", - "rev": "835a5f2d2a1acafb77add430fc8c2dd47282ef32", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "stackage.nix", - "type": "github" - } - }, - "stackage_15": { - "flake": false, - "locked": { - "lastModified": 1643073493, - "narHash": "sha256-5cPd1+i/skvJY9vJO1BhVRPcJObqkxDSywBEppDmb1U=", - "owner": "input-output-hk", - "repo": "stackage.nix", - "rev": "48e1188855ca38f3b7e2a8dba5352767a2f0a8f7", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "stackage.nix", - "type": "github" - } - }, - "stackage_16": { - "flake": false, - "locked": { - "lastModified": 1643073493, - "narHash": "sha256-5cPd1+i/skvJY9vJO1BhVRPcJObqkxDSywBEppDmb1U=", - "owner": "input-output-hk", - "repo": "stackage.nix", - "rev": "48e1188855ca38f3b7e2a8dba5352767a2f0a8f7", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "stackage.nix", - "type": "github" - } - }, - "stackage_17": { - "flake": false, - "locked": { - "lastModified": 1639012797, - "narHash": "sha256-hiLyBa5XFBvxD+BcYPKyYd/0dNMccxAuywFNqYtIIvs=", - "owner": "input-output-hk", - "repo": "stackage.nix", - "rev": "9ea6ea359da91c75a71e334b25aa7dc5ddc4b2c6", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "stackage.nix", - "type": "github" - } - }, - "stackage_18": { - "flake": false, - "locked": { - "lastModified": 1667610757, - "narHash": "sha256-H4dlMk5EW50xOtGo+5Srm3HGQV1+hY9ttgRQ+Sew5uA=", - "owner": "input-output-hk", - "repo": "stackage.nix", - "rev": "01d8ea53f65b08910003a1990547bab75ed6068a", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "stackage.nix", - "type": "github" - } - }, "stackage_2": { "flake": false, "locked": { @@ -10792,8 +7884,7 @@ "flake-utils": "flake-utils_23", "makes": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "haskell-nix", "tullia", "std", @@ -10802,8 +7893,7 @@ "mdbook-kroki-preprocessor": "mdbook-kroki-preprocessor_2", "microvm": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "haskell-nix", "tullia", "std", @@ -10811,7 +7901,7 @@ ], "n2c": "n2c_2", "nixago": "nixago_2", - "nixpkgs": "nixpkgs_27", + "nixpkgs": "nixpkgs_25", "yants": "yants_2" }, "locked": { @@ -10828,48 +7918,6 @@ "type": "github" } }, - "std_3": { - "inputs": { - "blank": "blank_6", - "devshell": "devshell_3", - "dmerge": "dmerge_3", - "flake-utils": "flake-utils_31", - "makes": [ - "ctl", - "ogmios-nixos", - "haskell-nix", - "tullia", - "std", - "blank" - ], - "mdbook-kroki-preprocessor": "mdbook-kroki-preprocessor_3", - "microvm": [ - "ctl", - "ogmios-nixos", - "haskell-nix", - "tullia", - "std", - "blank" - ], - "n2c": "n2c_3", - "nixago": "nixago_3", - "nixpkgs": "nixpkgs_35", - "yants": "yants_3" - }, - "locked": { - "lastModified": 1665513321, - "narHash": "sha256-D6Pacw9yf/HMs84KYuCxHXnNDL7v43gtcka5URagFqE=", - "owner": "divnix", - "repo": "std", - "rev": "94a90eedb9cfc115b12ae8f6622d9904788559e4", - "type": "github" - }, - "original": { - "owner": "divnix", - "repo": "std", - "type": "github" - } - }, "tailwind-haskell": { "inputs": { "flake-utils": "flake-utils_4", @@ -10920,40 +7968,13 @@ "inputs": { "nix-nomad": "nix-nomad_2", "nix2container": "nix2container_2", - "nixpkgs": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "nixpkgs" - ], - "std": "std_2" - }, - "locked": { - "lastModified": 1666200256, - "narHash": "sha256-cJPS8zBu30SMhxMe7I8DWutwqMuhPsEez87y9gxMKc4=", - "owner": "input-output-hk", - "repo": "tullia", - "rev": "575362c2244498e8d2c97f72861510fa72e75d44", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "tullia", - "type": "github" - } - }, - "tullia_3": { - "inputs": { - "nix-nomad": "nix-nomad_3", - "nix2container": "nix2container_3", "nixpkgs": [ "ctl", "ogmios-nixos", "haskell-nix", "nixpkgs" ], - "std": "std_3" + "std": "std_2" }, "locked": { "lastModified": 1666200256, @@ -10986,36 +8007,6 @@ "type": "github" } }, - "unstable_nixpkgs": { - "locked": { - "lastModified": 1653307806, - "narHash": "sha256-VPej3GE4IBMwYnXRfbiVqMWKa32+ysuvbHRkQXD0gTw=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "9d7aff488a8f9429d9e6cd82c10dffbf21907fb1", - "type": "github" - }, - "original": { - "owner": "NixOS", - "repo": "nixpkgs", - "type": "github" - } - }, - "unstable_nixpkgs_2": { - "locked": { - "lastModified": 1653307806, - "narHash": "sha256-VPej3GE4IBMwYnXRfbiVqMWKa32+ysuvbHRkQXD0gTw=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "9d7aff488a8f9429d9e6cd82c10dffbf21907fb1", - "type": "github" - }, - "original": { - "owner": "NixOS", - "repo": "nixpkgs", - "type": "github" - } - }, "utils": { "locked": { "lastModified": 1623875721, @@ -11046,81 +8037,6 @@ "type": "github" } }, - "utils_11": { - "locked": { - "lastModified": 1623875721, - "narHash": "sha256-A8BU7bjS5GirpAUv4QA+QnJ4CceLHkcXdRp4xITDB0s=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "f7e004a55b120c02ecb6219596820fcd32ca8772", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "utils_12": { - "locked": { - "lastModified": 1638122382, - "narHash": "sha256-sQzZzAbvKEqN9s0bzWuYmRaA03v40gaJ4+iL1LXjaeI=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "74f7e4319258e287b0f9cb95426c9853b282730b", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "utils_13": { - "locked": { - "lastModified": 1623875721, - "narHash": "sha256-A8BU7bjS5GirpAUv4QA+QnJ4CceLHkcXdRp4xITDB0s=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "f7e004a55b120c02ecb6219596820fcd32ca8772", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "utils_14": { - "locked": { - "lastModified": 1653893745, - "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "1ed9fb1935d260de5fe1c2f7ee0ebaae17ed2fa1", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "utils_15": { - "locked": { - "lastModified": 1653893745, - "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "1ed9fb1935d260de5fe1c2f7ee0ebaae17ed2fa1", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, "utils_2": { "locked": { "lastModified": 1638122382, @@ -11267,32 +8183,6 @@ } }, "yants_2": { - "inputs": { - "nixpkgs": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "std", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1660507851, - "narHash": "sha256-BKjq7JnVuUR/xDtcv6Vm9GYGKAblisXrAgybor9hT/s=", - "owner": "divnix", - "repo": "yants", - "rev": "0b895ca02a8fa72bad50b454cb3e7d8a66407c96", - "type": "github" - }, - "original": { - "owner": "divnix", - "repo": "yants", - "type": "github" - } - }, - "yants_3": { "inputs": { "nixpkgs": [ "ctl", diff --git a/templates/ctl-scaffold/flake.nix b/templates/ctl-scaffold/flake.nix index 9e43f517bb..5981be7180 100644 --- a/templates/ctl-scaffold/flake.nix +++ b/templates/ctl-scaffold/flake.nix @@ -10,7 +10,7 @@ type = "github"; owner = "Plutonomicon"; repo = "cardano-transaction-lib"; - rev = "fc35733e483c21e55e5acabacb1d9e192f91a032"; + rev = "30f35db524a3d855852fcfb8d7069defbedbbe76"; }; # To use the same version of `nixpkgs` as we do nixpkgs.follows = "ctl/nixpkgs"; From ba30a38a1e60fdfafb04de6d190694f477ec4b9e Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Tue, 13 Dec 2022 15:23:22 +0000 Subject: [PATCH 094/373] Formatting --- doc/faq.md | 2 +- doc/plutus-comparison.md | 1 + doc/runtime.md | 1 + doc/side-by-side-ctl-plutus-comparison.md | 1 - src/Internal/Contract/Monad.purs | 2 +- src/Internal/Contract/QueryHandle.purs | 2 +- src/Internal/Plutip/Server.purs | 1 + src/Internal/QueryM.purs | 8 +++++- src/Internal/QueryM/Kupo.purs | 33 +++++++++++++++-------- 9 files changed, 35 insertions(+), 16 deletions(-) diff --git a/doc/faq.md b/doc/faq.md index b088dbf97f..35aa58c00a 100644 --- a/doc/faq.md +++ b/doc/faq.md @@ -8,6 +8,7 @@ This document lists common problems encountered by CTL users and developers. - [Bundling-related](#bundling-related) - [Q: `lib.something` is not a function, why?](#q-libsomething-is-not-a-function-why) + - [Q: I see `spago: Error: Remote host not found`, why?](#q-i-see-spago-error-remote-host-not-found-why) - [Common Contract execution problems](#common-contract-execution-problems) - [Q: What are the common reasons behind InsufficientTxInputs error?](#q-what-are-the-common-reasons-behind-insufficienttxinputs-error) - [Time-related](#time-related) @@ -18,7 +19,6 @@ This document lists common problems encountered by CTL users and developers. - [Q: Why `aeson` and not `argonaut`?](#q-why-aeson-and-not-argonaut) - [Miscellaneous](#miscellaneous) - [Q: Why am I getting `Error: (AtKey "coinsPerUtxoByte" MissingValue)`?](#q-why-am-i-getting-error-atkey-coinsperutxobyte-missingvalue) - - [Q: Why do I get an error from `foreign.js` when running Plutip tests locally?](#q-why-do-i-get-an-error-from-foreignjs-when-running-plutip-tests-locally) - [How can I write my own Nix derivations using the project returned by `purescriptProject`?](#how-can-i-write-my-own-nix-derivations-using-the-project-returned-by-purescriptproject) diff --git a/doc/plutus-comparison.md b/doc/plutus-comparison.md index d199810860..44a90f2226 100644 --- a/doc/plutus-comparison.md +++ b/doc/plutus-comparison.md @@ -12,6 +12,7 @@ Note that differences between Haskell and Purescript, while also relevant to suc - [Library vs. process](#library-vs-process) - [The `Contract` type](#the-contract-type) - [API differences](#api-differences) + - [Transaction manipulation API](#transaction-manipulation-api) - [Constraints and lookups](#constraints-and-lookups) - [Babbage-era constraints](#babbage-era-constraints) - [Typed scripts](#typed-scripts) diff --git a/doc/runtime.md b/doc/runtime.md index 9d5bdc51be..947fb609ab 100644 --- a/doc/runtime.md +++ b/doc/runtime.md @@ -10,6 +10,7 @@ In order to run CTL's `Contract` effects, several services are required. These c - [Using NixOS module](#using-nixos-module) - [Using CTL's `runtime` overlay](#using-ctls-runtime-overlay) - [Changing network configurations](#changing-network-configurations) +- [Blockfrost Backend](#blockfrost-backend) - [Wallet requirements](#wallet-requirements) diff --git a/doc/side-by-side-ctl-plutus-comparison.md b/doc/side-by-side-ctl-plutus-comparison.md index 424a86c5c8..2fdec78db8 100644 --- a/doc/side-by-side-ctl-plutus-comparison.md +++ b/doc/side-by-side-ctl-plutus-comparison.md @@ -12,7 +12,6 @@ both of them. - [About `Contract` in CTL and Plutus](#about-contract-in-ctl-and-plutus) - [Contract comparison](#contract-comparison) - - [Signature and submit](#signature-and-submit) - [MustPayTo functions](#mustpayto-functions) - [The `give` contract](#the-give-contract) - [The `grab` contract](#the-grab-contract) diff --git a/src/Internal/Contract/Monad.purs b/src/Internal/Contract/Monad.purs index 7a10f4682b..b8ba776e7e 100644 --- a/src/Internal/Contract/Monad.purs +++ b/src/Internal/Contract/Monad.purs @@ -51,9 +51,9 @@ import Ctl.Internal.QueryM , mkOgmiosWebSocketAff , underlyingWebSocket ) +import Ctl.Internal.QueryM.Kupo (isTxConfirmedAff) -- TODO: Move/translate these types into Cardano import Ctl.Internal.QueryM.Ogmios (ProtocolParameters, SystemStart) as Ogmios -import Ctl.Internal.QueryM.Kupo (isTxConfirmedAff) import Ctl.Internal.QueryM.ServerConfig (ServerConfig) import Ctl.Internal.Serialization.Address (NetworkId) import Ctl.Internal.Types.UsedTxOuts (UsedTxOuts, isTxOutRefUsed, newUsedTxOuts) diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs index 9ed701ba41..beada1d6f8 100644 --- a/src/Internal/Contract/QueryHandle.purs +++ b/src/Internal/Contract/QueryHandle.purs @@ -50,8 +50,8 @@ import Ctl.Internal.Serialization.Address (Address) import Ctl.Internal.Serialization.Hash (ScriptHash) import Ctl.Internal.Types.Chain as Chain import Ctl.Internal.Types.Datum (DataHash, Datum) -import Ctl.Internal.Types.TransactionMetadata (GeneralTransactionMetadata) import Ctl.Internal.Types.Transaction (TransactionHash, TransactionInput) +import Ctl.Internal.Types.TransactionMetadata (GeneralTransactionMetadata) import Data.Either (Either) import Data.Map (Map) import Data.Maybe (Maybe(Just, Nothing), isJust) diff --git a/src/Internal/Plutip/Server.purs b/src/Internal/Plutip/Server.purs index c56a568ee7..84a92c35fb 100644 --- a/src/Internal/Plutip/Server.purs +++ b/src/Internal/Plutip/Server.purs @@ -617,6 +617,7 @@ stopChildProcessWithPortAndRemoveOnSignal port (childProcess /\ _ /\ sig) = do unless isAvailable do liftEffect $ throw "retry" liftEffect $ removeOnSignal sig + mkClusterContractEnv :: PlutipConfig -> Logger diff --git a/src/Internal/QueryM.purs b/src/Internal/QueryM.purs index 71af45e1bd..271dbfbd4e 100644 --- a/src/Internal/QueryM.purs +++ b/src/Internal/QueryM.purs @@ -554,7 +554,13 @@ resendPendingSubmitRequests -> Dispatcher -> PendingSubmitTxRequests -> Effect Unit -resendPendingSubmitRequests ogmiosWs isTxConfirmed logger sendRequest dispatcher pr = do +resendPendingSubmitRequests + ogmiosWs + isTxConfirmed + logger + sendRequest + dispatcher + pr = do submitTxPendingRequests <- Ref.read pr unless (Map.isEmpty submitTxPendingRequests) do -- Acquiring a mempool snapshot should never fail and, diff --git a/src/Internal/QueryM/Kupo.purs b/src/Internal/QueryM/Kupo.purs index 0bd71fd7e0..8a6976ad75 100644 --- a/src/Internal/QueryM/Kupo.purs +++ b/src/Internal/QueryM/Kupo.purs @@ -12,8 +12,6 @@ module Ctl.Internal.QueryM.Kupo import Prelude -import Ctl.Internal.Deserialization.Transaction (convertGeneralTransactionMetadata) -import Ctl.Internal.Types.BigNum (toString) as BigNum import Aeson ( class DecodeAeson , Aeson @@ -52,6 +50,9 @@ import Ctl.Internal.Cardano.Types.Value import Ctl.Internal.Deserialization.FromBytes (fromBytes) import Ctl.Internal.Deserialization.NativeScript (convertNativeScript) import Ctl.Internal.Deserialization.PlutusData (deserializeData) +import Ctl.Internal.Deserialization.Transaction + ( convertGeneralTransactionMetadata + ) import Ctl.Internal.QueryM ( ClientError(ClientOtherError) , QueryM @@ -66,6 +67,7 @@ import Ctl.Internal.Serialization.Address , addressFromBytes ) import Ctl.Internal.Serialization.Hash (ScriptHash, scriptHashToBytes) +import Ctl.Internal.Types.BigNum (toString) as BigNum import Ctl.Internal.Types.ByteArray (ByteArray, byteArrayToHex, hexToByteArray) import Ctl.Internal.Types.CborBytes (hexToCborBytes) import Ctl.Internal.Types.Datum (DataHash(DataHash), Datum) @@ -163,26 +165,33 @@ isTxConfirmed th = do liftAff $ isTxConfirmedAff config th -- Exported due to Ogmios requiring confirmations at a websocket level -isTxConfirmedAff :: ServerConfig -> TransactionHash -> Aff (Either ClientError (Maybe Slot)) +isTxConfirmedAff + :: ServerConfig -> TransactionHash -> Aff (Either ClientError (Maybe Slot)) isTxConfirmedAff config (TransactionHash txHash) = do let endpoint = "/matches/*@" <> byteArrayToHex txHash kupoGetRequestAff config endpoint <#> handleAffjaxResponse >>> map \utxos -> - case uncons ( utxos :: _ { created_at :: { slot_no :: Slot } } ) of + case uncons (utxos :: _ { created_at :: { slot_no :: Slot } }) of Just { head } -> Just head.created_at.slot_no _ -> Nothing -getTxMetadata :: TransactionHash -> QueryM (Either ClientError (Maybe GeneralTransactionMetadata)) +getTxMetadata + :: TransactionHash + -> QueryM (Either ClientError (Maybe GeneralTransactionMetadata)) getTxMetadata txHash = runExceptT do ExceptT (isTxConfirmed txHash) >>= case _ of Nothing -> pure Nothing Just slot -> do - let endpoint = "/metadata/" <> BigNum.toString (unwrap slot) <> "?transaction_id=" <> byteArrayToHex (unwrap txHash) - generalTxMetadatas - <- ExceptT $ handleAffjaxResponse <$> kupoGetRequest endpoint - case uncons ( generalTxMetadatas :: _ { raw :: String } ) of + let + endpoint = "/metadata/" <> BigNum.toString (unwrap slot) + <> "?transaction_id=" + <> byteArrayToHex (unwrap txHash) + generalTxMetadatas <- ExceptT $ handleAffjaxResponse <$> kupoGetRequest + endpoint + case uncons (generalTxMetadatas :: _ { raw :: String }) of Just { head, tail: [] } -> - pure $ hexToByteArray head.raw >>= (fromBytes >=> convertGeneralTransactionMetadata >>> hush) + pure $ hexToByteArray head.raw >>= + (fromBytes >=> convertGeneralTransactionMetadata >>> hush) _ -> pure Nothing -------------------------------------------------------------------------------- @@ -423,7 +432,9 @@ kupoGetRequest endpoint = do liftAff $ kupoGetRequestAff config endpoint kupoGetRequestAff - :: ServerConfig -> String -> Aff (Either Affjax.Error (Affjax.Response String)) + :: ServerConfig + -> String + -> Aff (Either Affjax.Error (Affjax.Response String)) kupoGetRequestAff config endpoint = do Affjax.request $ Affjax.defaultRequest { method = Left GET From c2dde03df26b16501961851b959dba00faae06cf Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Tue, 13 Dec 2022 15:27:00 +0000 Subject: [PATCH 095/373] Wording --- doc/side-by-side-ctl-plutus-comparison.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/doc/side-by-side-ctl-plutus-comparison.md b/doc/side-by-side-ctl-plutus-comparison.md index 2fdec78db8..61fea0b9ad 100644 --- a/doc/side-by-side-ctl-plutus-comparison.md +++ b/doc/side-by-side-ctl-plutus-comparison.md @@ -24,7 +24,7 @@ The current definition of `Contract` in CTL is : ```PureScript type ContractEnv = - { -- Internal type holding holding connections to backend services, ledger + { -- Internal type holding connections to backend services, ledger -- constants which are fixed during contract evaluation, and user defined -- values like the choice of wallet and logger. } From f5ce131941d2fb52a359552331d2bb98cd19ff85 Mon Sep 17 00:00:00 2001 From: Gregory Gerasev Date: Tue, 13 Dec 2022 02:24:49 +0400 Subject: [PATCH 096/373] Fix review suggestions --- src/Internal/Deserialization/Transaction.purs | 12 +++++------- 1 file changed, 5 insertions(+), 7 deletions(-) diff --git a/src/Internal/Deserialization/Transaction.purs b/src/Internal/Deserialization/Transaction.purs index b83f7d8b39..25d0cc2a96 100644 --- a/src/Internal/Deserialization/Transaction.purs +++ b/src/Internal/Deserialization/Transaction.purs @@ -480,8 +480,8 @@ convertProtocolParamUpdate cslPpu = do maxBlockHeaderSize <- traverse (cslNumberToUInt (lbl "maxBlockHeaderSize")) ppu.maxBlockHeaderSize let - keyDeposit = map (Coin <<< BigNum.toBigInt) ppu.keyDeposit - poolDeposit = map (Coin <<< BigNum.toBigInt) ppu.poolDeposit + keyDeposit = Coin <<< BigNum.toBigInt <$> ppu.keyDeposit + poolDeposit = Coin <<< BigNum.toBigInt <$> ppu.poolDeposit maxEpoch <- traverse (map T.Epoch <<< cslNumberToUInt (lbl "maxEpoch")) ppu.maxEpoch nOpt <- traverse (cslNumberToUInt (lbl "nOpt")) ppu.nOpt @@ -490,11 +490,9 @@ convertProtocolParamUpdate cslPpu = do costModels <- addErrTrace (lbl "costModels") $ traverse convertCostModels ppu.costModels let - maxTxExUnits = map (convertExUnits (lbl "maxTxExUnits")) ppu.maxTxExUnits - maxBlockExUnits = map (convertExUnits (lbl "maxBlockExUnits")) - ppu.maxBlockExUnits - maxValueSize <- traverse (cslNumberToUInt (lbl "maxValueSize")) - ppu.maxValueSize + maxTxExUnits = convertExUnits (lbl "maxTxExUnits") <$> ppu.maxTxExUnits + maxBlockExUnits = convertExUnits (lbl "maxBlockExUnits") <$> ppu.maxBlockExUnits + maxValueSize <- traverse (cslNumberToUInt (lbl "maxValueSize")) ppu.maxValueSize pure { minfeeA , minfeeB From 06bccd6cc68debb84473bf10406cbb34547ee184 Mon Sep 17 00:00:00 2001 From: Gregory Gerasev Date: Tue, 13 Dec 2022 22:28:02 +0400 Subject: [PATCH 097/373] Remove unneccesary from CHANGELOG --- CHANGELOG.md | 2 -- 1 file changed, 2 deletions(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index 756ca0b8a5..92eba5073f 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -44,8 +44,6 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) ### Removed -- `BigNum.toBigIntUnsafe` is dropped. ([#1284](https://github.com/Plutonomicon/cardano-transaction-lib/issues/1284)). - ### Fixed - Added missing `stakePoolTargetNum` ("`nOpt`") protocol parameter (see [CIP-9](https://cips.cardano.org/cips/cip9/)) ([#571](https://github.com/Plutonomicon/cardano-transaction-lib/issues/571)) From b7e0cd2d822ee65470bb0fa9e57c6efb0d1d2a22 Mon Sep 17 00:00:00 2001 From: Gregory Gerasev Date: Tue, 13 Dec 2022 22:35:44 +0400 Subject: [PATCH 098/373] Fix PR review comments --- src/Internal/Deserialization/Transaction.purs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Internal/Deserialization/Transaction.purs b/src/Internal/Deserialization/Transaction.purs index 25d0cc2a96..4f8118a509 100644 --- a/src/Internal/Deserialization/Transaction.purs +++ b/src/Internal/Deserialization/Transaction.purs @@ -261,7 +261,7 @@ convertTxBody txBody = do (map <<< map) (M.fromFoldable <<< map (lmap T.RewardAddress)) -- bignum -> coin <<< (traverse <<< traverse <<< traverse) - (pure <<< BigNum.toBigInt >>> Coin) + (BigNum.toBigInt >>> Coin >>> pure) $ ws update <- traverse convertUpdate $ _txBodyUpdate maybeFfiHelper txBody From 1d062a1591121f25cbcf2c53791529baefdfd205 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Tue, 13 Dec 2022 19:52:49 +0100 Subject: [PATCH 099/373] WIP: Add unit tests for performMultiAssetSelection --- CHANGELOG.md | 2 +- doc/faq.md | 1 + doc/plutus-comparison.md | 1 + doc/side-by-side-ctl-plutus-comparison.md | 1 - examples/Helpers.purs | 8 +- src/Internal/BalanceTx/CoinSelection.purs | 14 ++ src/Internal/Cardano/Types/Value.purs | 3 + test/CoinSelection/Arbitrary.purs | 133 +++++++++++++ test/CoinSelection/CoinSelection.purs | 231 ++++++++++++++++++++++ test/CoinSelection/UtxoIndex.purs | 115 +---------- test/Unit.purs | 4 +- 11 files changed, 394 insertions(+), 119 deletions(-) create mode 100644 test/CoinSelection/Arbitrary.purs create mode 100644 test/CoinSelection/CoinSelection.purs diff --git a/CHANGELOG.md b/CHANGELOG.md index d263d27998..6f82db2c16 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -139,7 +139,7 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) ### Runtime Dependencies -- [Ogmios](https://github.com/mlabs-haskell/ogmios) - v5.5.7 +- [Ogmios](https://github.com/mlabs-haskell/ogmios) - v5.5.7 - [Kupo](https://github.com/CardanoSolutions/kupo) - v2.2.0 - [Cardano-Node](https://github.com/input-output-hk/cardano-node/) - v1.35.3 - [Ogmios-Datum-Cache](https://github.com/mlabs-haskell/ogmios-datum-cache) - commit 862c6bfcb6110b8fe816e26b3bba105dfb492b24 diff --git a/doc/faq.md b/doc/faq.md index 1353b50ee2..7e0c35cd6f 100644 --- a/doc/faq.md +++ b/doc/faq.md @@ -8,6 +8,7 @@ This document lists common problems encountered by CTL users and developers. - [Bundling-related](#bundling-related) - [Q: `lib.something` is not a function, why?](#q-libsomething-is-not-a-function-why) + - [Q: I see `spago: Error: Remote host not found`, why?](#q-i-see-spago-error-remote-host-not-found-why) - [Common Contract execution problems](#common-contract-execution-problems) - [Q: What are the common reasons behind InsufficientTxInputs error?](#q-what-are-the-common-reasons-behind-insufficienttxinputs-error) - [Time-related](#time-related) diff --git a/doc/plutus-comparison.md b/doc/plutus-comparison.md index 5bca6e64ee..eb24c96630 100644 --- a/doc/plutus-comparison.md +++ b/doc/plutus-comparison.md @@ -12,6 +12,7 @@ Note that differences between Haskell and Purescript, while also relevant to suc - [Library vs. process](#library-vs-process) - [The `Contract` type](#the-contract-type) - [API differences](#api-differences) + - [Transaction manipulation API](#transaction-manipulation-api) - [Constraints and lookups](#constraints-and-lookups) - [Babbage-era constraints](#babbage-era-constraints) - [Typed scripts](#typed-scripts) diff --git a/doc/side-by-side-ctl-plutus-comparison.md b/doc/side-by-side-ctl-plutus-comparison.md index 2352d87c05..e6bf890cc6 100644 --- a/doc/side-by-side-ctl-plutus-comparison.md +++ b/doc/side-by-side-ctl-plutus-comparison.md @@ -12,7 +12,6 @@ both of them. - [About `Contract` in CTL and Plutus](#about-contract-in-ctl-and-plutus) - [Contract comparison](#contract-comparison) - - [Signature and submit](#signature-and-submit) - [MustPayTo functions](#mustpayto-functions) - [The `give` contract](#the-give-contract) - [The `grab` contract](#the-grab-contract) diff --git a/examples/Helpers.purs b/examples/Helpers.purs index 892852571b..9569340f8f 100644 --- a/examples/Helpers.purs +++ b/examples/Helpers.purs @@ -9,24 +9,18 @@ import Contract.Prelude import Contract.Address (PaymentPubKeyHash, StakePubKeyHash) import Contract.Log (logInfo') -import Contract.Monad (Contract, liftContractM, liftedE) +import Contract.Monad (Contract, liftContractM) import Contract.Prim.ByteArray (byteArrayFromAscii) -import Contract.ScriptLookups (ScriptLookups, mkUnbalancedTx) as Lookups import Contract.Scripts (MintingPolicy) import Contract.Transaction ( BalancedSignedTransaction - , TransactionHash , awaitTxConfirmed - , balanceTx , getTxByHash - , getTxFinalFee - , signTransaction , submit ) import Contract.TxConstraints as Constraints import Contract.Value (CurrencySymbol, TokenName, Value) import Contract.Value (mkTokenName, scriptCurrencySymbol) as Value -import Data.BigInt (BigInt) import Effect.Exception (throw) mkCurrencySymbol diff --git a/src/Internal/BalanceTx/CoinSelection.purs b/src/Internal/BalanceTx/CoinSelection.purs index d377b1d28c..0701d61c2e 100644 --- a/src/Internal/BalanceTx/CoinSelection.purs +++ b/src/Internal/BalanceTx/CoinSelection.purs @@ -54,6 +54,7 @@ import Data.BigInt (BigInt) import Data.BigInt (abs, fromInt, toString) as BigInt import Data.Foldable (foldMap) as Foldable import Data.Function (applyFlipped) +import Data.Generic.Rep (class Generic) import Data.Lens (Lens') import Data.Lens.Getter (view, (^.)) import Data.Lens.Iso.Newtype (_Newtype) @@ -64,9 +65,12 @@ import Data.Maybe (Maybe(Just, Nothing), maybe, maybe') import Data.Newtype (class Newtype, unwrap, wrap) import Data.Set (Set) import Data.Set (fromFoldable) as Set +import Data.Show.Generic (genericShow) import Data.Tuple (fst) as Tuple import Data.Tuple.Nested (type (/\), (/\)) import Effect.Class (class MonadEffect) +import Test.QuickCheck.Arbitrary (class Arbitrary) +import Test.QuickCheck.Gen (elements) as Arbitrary import Type.Proxy (Proxy(Proxy)) -------------------------------------------------------------------------------- @@ -96,6 +100,11 @@ import Type.Proxy (Proxy(Proxy)) -- | https://github.com/input-output-hk/cardano-wallet/blob/a61d37f2557b8cb5c47b57da79375afad698eed4/lib/wallet/src/Cardano/Wallet/CoinSelection/Internal/Balance.hs#L325 data SelectionStrategy = SelectionStrategyOptimal | SelectionStrategyMinimal +instance Arbitrary SelectionStrategy where + arbitrary = + Arbitrary.elements $ + NEArray.cons' SelectionStrategyOptimal [ SelectionStrategyMinimal ] + -- | Performs a coin selection using the specified selection strategy. -- | -- | Throws a `BalanceInsufficientError` if the balance of the provided utxo @@ -150,7 +159,12 @@ newtype SelectionState = SelectionState , selectedUtxos :: UtxoMap } +derive instance Generic SelectionState _ derive instance Newtype SelectionState _ +derive instance Eq SelectionState + +instance Show SelectionState where + show = genericShow _leftoverUtxos :: Lens' SelectionState UtxoIndex _leftoverUtxos = _Newtype <<< prop (Proxy :: Proxy "leftoverUtxos") diff --git a/src/Internal/Cardano/Types/Value.purs b/src/Internal/Cardano/Types/Value.purs index dbb7b5e247..e34f24f095 100644 --- a/src/Internal/Cardano/Types/Value.purs +++ b/src/Internal/Cardano/Types/Value.purs @@ -535,6 +535,9 @@ derive instance Generic AssetClass _ derive instance Eq AssetClass derive instance Ord AssetClass +instance Arbitrary AssetClass where + arbitrary = AssetClass <$> arbitrary <*> arbitrary + instance Show AssetClass where show = genericShow diff --git a/test/CoinSelection/Arbitrary.purs b/test/CoinSelection/Arbitrary.purs new file mode 100644 index 0000000000..5192df0dd8 --- /dev/null +++ b/test/CoinSelection/Arbitrary.purs @@ -0,0 +1,133 @@ +module Test.Ctl.CoinSelection.Arbitrary where + +import Prelude + +import Control.Apply (lift2) +import Ctl.Internal.Cardano.Types.Transaction + ( TransactionOutput(TransactionOutput) + , UtxoMap + ) +import Ctl.Internal.Cardano.Types.Value (Value) +import Ctl.Internal.CoinSelection.UtxoIndex (UtxoIndex) +import Ctl.Internal.CoinSelection.UtxoIndex (buildUtxoIndex) as UtxoIndex +import Ctl.Internal.Serialization.Address + ( Address + , NetworkId(MainnetId) + , baseAddressToAddress + , paymentKeyHashStakeKeyHashAddress + ) +import Ctl.Internal.Types.OutputDatum (OutputDatum(NoOutputDatum)) +import Ctl.Internal.Types.Transaction + ( TransactionHash + , TransactionInput(TransactionInput) + ) +import Data.Generic.Rep (class Generic) +import Data.Map.Gen (genMap) as Map +import Data.Maybe (Maybe(Nothing)) +import Data.Newtype (class Newtype, unwrap, wrap) +import Data.Show.Generic (genericShow) +import Data.Tuple (Tuple(Tuple)) +import Data.Tuple.Nested (type (/\)) +import Data.UInt (fromInt) as UInt +import Test.QuickCheck.Arbitrary (class Arbitrary, arbitrary) +import Test.QuickCheck.Gen (Gen) + +-------------------------------------------------------------------------------- +-- ArbitraryUtxoIndex +-------------------------------------------------------------------------------- + +newtype ArbitraryUtxoIndex = ArbitraryUtxoIndex UtxoIndex + +derive instance Newtype ArbitraryUtxoIndex _ + +instance Arbitrary ArbitraryUtxoIndex where + arbitrary = + (arbitrary :: Gen ArbitraryUtxoMap) + <#> wrap <<< UtxoIndex.buildUtxoIndex <<< unwrap + +-------------------------------------------------------------------------------- +-- ArbitraryUtxoMap +-------------------------------------------------------------------------------- + +newtype ArbitraryUtxoMap = ArbitraryUtxoMap UtxoMap + +derive instance Generic ArbitraryUtxoMap _ +derive instance Newtype ArbitraryUtxoMap _ + +instance Show ArbitraryUtxoMap where + show = genericShow + +instance Arbitrary ArbitraryUtxoMap where + arbitrary = wrap <$> Map.genMap genTransactionInput genTransactionOutput + +-------------------------------------------------------------------------------- +-- ArbitraryTxUnspentOut +-------------------------------------------------------------------------------- + +newtype ArbitraryTxUnspentOut = + ArbitraryTxUnspentOut (TransactionInput /\ TransactionOutput) + +derive instance Newtype ArbitraryTxUnspentOut _ + +instance Arbitrary ArbitraryTxUnspentOut where + arbitrary = wrap <$> lift2 Tuple genTransactionInput genTransactionOutput + +genTransactionInput :: Gen TransactionInput +genTransactionInput = unwrap <$> (arbitrary :: Gen ArbitraryTransactionInput) + +genTransactionOutput :: Gen TransactionOutput +genTransactionOutput = unwrap <$> (arbitrary :: Gen ArbitraryTransactionOutput) + +-------------------------------------------------------------------------------- +-- ArbitraryTransactionInput +-------------------------------------------------------------------------------- + +newtype ArbitraryTransactionInput = + ArbitraryTransactionInput TransactionInput + +derive instance Newtype ArbitraryTransactionInput _ + +instance Arbitrary ArbitraryTransactionInput where + arbitrary = wrap <$> lift2 mkTxInput arbitrary arbitrary + where + mkTxInput :: TransactionHash -> Int -> TransactionInput + mkTxInput transactionId index = + TransactionInput + { transactionId + , index: UInt.fromInt index + } + +-------------------------------------------------------------------------------- +-- ArbitraryTransactionOutput +-------------------------------------------------------------------------------- + +newtype ArbitraryTransactionOutput = + ArbitraryTransactionOutput TransactionOutput + +derive instance Newtype ArbitraryTransactionOutput _ + +instance Arbitrary ArbitraryTransactionOutput where + arbitrary = wrap <$> lift2 mkTxOutput arbitrary arbitrary + where + mkTxOutput :: ArbitraryAddress -> Value -> TransactionOutput + mkTxOutput address amount = + TransactionOutput + { address: unwrap address + , amount + , datum: NoOutputDatum + , scriptRef: Nothing + } + +-------------------------------------------------------------------------------- +-- ArbitraryAddress +-------------------------------------------------------------------------------- + +newtype ArbitraryAddress = ArbitraryAddress Address + +derive instance Newtype ArbitraryAddress _ + +instance Arbitrary ArbitraryAddress where + arbitrary = + wrap <<< baseAddressToAddress <$> + lift2 (paymentKeyHashStakeKeyHashAddress MainnetId) arbitrary arbitrary + diff --git a/test/CoinSelection/CoinSelection.purs b/test/CoinSelection/CoinSelection.purs new file mode 100644 index 0000000000..203cf99ca6 --- /dev/null +++ b/test/CoinSelection/CoinSelection.purs @@ -0,0 +1,231 @@ +module Test.Ctl.CoinSelection (suite) where + +import Prelude + +import Control.Monad.Error.Class (class MonadThrow) +import Ctl.Internal.BalanceTx.CoinSelection + ( SelectionState + , SelectionStrategy(SelectionStrategyMinimal, SelectionStrategyOptimal) + , performMultiAssetSelection + ) +import Ctl.Internal.BalanceTx.Error (BalanceTxError) +import Ctl.Internal.Cardano.Types.Transaction + ( TransactionOutput(TransactionOutput) + ) +import Ctl.Internal.Cardano.Types.Value + ( CurrencySymbol + , NonAdaAsset + , Value + , mkCoin + , mkSingletonNonAdaAsset + , mkValue + ) +import Ctl.Internal.CoinSelection.UtxoIndex (UtxoIndex) +import Ctl.Internal.CoinSelection.UtxoIndex (buildUtxoIndex) as UtxoIndex +import Ctl.Internal.Test.TestPlanM (TestPlanM) +import Ctl.Internal.Types.ByteArray (byteArrayFromAscii) +import Ctl.Internal.Types.OutputDatum (OutputDatum(NoOutputDatum)) +import Ctl.Internal.Types.TokenName (TokenName, mkTokenName) +import Ctl.Internal.Types.Transaction (TransactionInput) +import Data.BigInt (fromInt) as BigInt +import Data.Foldable (fold, foldMap) +import Data.Generic.Rep (class Generic) +import Data.Map (empty, fromFoldable, values) as Map +import Data.Maybe (Maybe(Nothing), fromJust) +import Data.Newtype (class Newtype, unwrap, wrap) +import Data.Show.Generic (genericShow) +import Data.Traversable (for, for_) +import Data.Tuple (Tuple(Tuple)) +import Data.Tuple.Nested (type (/\), (/\)) +import Effect (Effect) +import Effect.Aff (Aff) +import Effect.Class (class MonadEffect, liftEffect) +import Effect.Exception (throw) +import Effect.Unsafe (unsafePerformEffect) +import Mote (group, test) +import Partial.Unsafe (unsafePartial) +import Test.Ctl.CoinSelection.Arbitrary + ( ArbitraryAddress + , ArbitraryTransactionInput + , ArbitraryUtxoIndex + ) +import Test.Ctl.CoinSelection.UtxoIndex (suite) as UtxoIndex +import Test.Ctl.Fixtures (currencySymbol1) as Fixtures +import Test.QuickCheck (class Testable, Result, assertEquals) +import Test.QuickCheck (test) as QuickCheck +import Test.QuickCheck.Arbitrary (arbitrary) +import Test.QuickCheck.Gen (Gen, randomSampleOne) +import Test.Spec.Assertions (shouldEqual) +import Test.Spec.QuickCheck (quickCheck) + +suite :: TestPlanM (Aff Unit) Unit +suite = + group "CoinSelection" do + UtxoIndex.suite + group "performMultiAssetSelection" do + performMultiAssetSelection_unitTests + test "prop_performMultiAssetSelection_empty" do + quickCheck prop_performMultiAssetSelection_empty + +-------------------------------------------------------------------------------- +-- Tests +-------------------------------------------------------------------------------- + +prop_performMultiAssetSelection_empty + :: SelectionStrategy -> ArbitraryUtxoIndex -> CoinSelectionTestM Result +prop_performMultiAssetSelection_empty strategy utxoIndex = + assertEquals targetSelState <$> + performMultiAssetSelection strategy (unwrap utxoIndex) mempty + where + targetSelState :: SelectionState + targetSelState = + wrap { leftoverUtxos: unwrap utxoIndex, selectedUtxos: Map.empty } + +performMultiAssetSelection_unitTests :: TestPlanM (Aff Unit) Unit +performMultiAssetSelection_unitTests = + for_ selFixtures \{ testLabel, strategy, inpFixture, outFixture } -> + test testLabel $ liftEffect $ (unwrap :: CoinSelectionTestM _ -> _) do + td <- liftEffect $ + selTestDataFromFixtures (inpFixture strategy) (outFixture strategy) + selectedUtxos <- + _.selectedUtxos <<< unwrap <$> + performMultiAssetSelection td.strategy td.utxoIndex td.requiredValue + liftEffect $ + td.selectedValue `shouldEqual` + foldMap (_.amount <<< unwrap) (Map.values selectedUtxos) + +-------------------------------------------------------------------------------- +-- Fixtures +-------------------------------------------------------------------------------- + +data AssetFixture = AssetA | AssetB | AssetC + +derive instance Generic AssetFixture _ + +instance Show AssetFixture where + show = genericShow + +assetClassFromFixture :: AssetFixture -> CurrencySymbol /\ TokenName +assetClassFromFixture = + Tuple Fixtures.currencySymbol1 <<< tokenNameFromAscii <<< show + where + tokenNameFromAscii :: String -> TokenName + tokenNameFromAscii = + unsafePartial fromJust <<< (mkTokenName <=< byteArrayFromAscii) + +type TokenBundleFixture = Int /\ Array (AssetFixture /\ Int) + +assetFromFixture :: AssetFixture /\ Int -> NonAdaAsset +assetFromFixture (assetFixture /\ quantity) = + mkSingletonNonAdaAsset currencySymbol tokenName (BigInt.fromInt quantity) + where + currencySymbol /\ tokenName = assetClassFromFixture assetFixture + +valueFromFixture :: TokenBundleFixture -> Value +valueFromFixture (coin /\ assets) = + mkValue (mkCoin coin) (foldMap assetFromFixture assets) + +type SelInputFixture = + { strategy :: SelectionStrategy + , requiredValue :: TokenBundleFixture + , utxos :: Array TokenBundleFixture + } + +type SelOutputFixture = Array TokenBundleFixture + +type SelTestData = + { strategy :: SelectionStrategy + , requiredValue :: Value + , utxoIndex :: UtxoIndex + , selectedValue :: Value + } + +selTestDataFromFixtures + :: SelInputFixture -> SelOutputFixture -> Effect SelTestData +selTestDataFromFixtures inpFixture outFixture = do + utxoIndex <- + UtxoIndex.buildUtxoIndex <<< Map.fromFoldable <$> + for inpFixture.utxos \bundle -> + Tuple <$> txInputSample <*> mkTxOutput (valueFromFixture bundle) + pure + { strategy: inpFixture.strategy + , requiredValue: valueFromFixture inpFixture.requiredValue + , utxoIndex + , selectedValue: fold (valueFromFixture <$> outFixture) + } + where + txInputSample :: Effect TransactionInput + txInputSample = + unwrap <$> randomSampleOne (arbitrary :: Gen ArbitraryTransactionInput) + + mkTxOutput :: Value -> Effect TransactionOutput + mkTxOutput amount = do + address <- unwrap <$> randomSampleOne (arbitrary :: Gen ArbitraryAddress) + pure $ TransactionOutput + { address, amount, datum: NoOutputDatum, scriptRef: Nothing } + +-------------------------------------------------------------------------------- + +selInputFixture0 :: SelectionStrategy -> SelInputFixture +selInputFixture0 strategy = + { strategy + , requiredValue: 100 /\ [ AssetA /\ 5 ] + , utxos: + [ 40 /\ [ AssetA /\ 5 ] -- singleton for AssetA + , 40 /\ [ AssetA /\ 5 ] -- singleton for AssetA + , 60 /\ mempty -- singleton for AssetLovelace + , 10 /\ [ AssetA /\ 4, AssetB /\ 1 ] -- pair for AssetA and AssetB + , 100 /\ [ AssetA /\ 5, AssetB /\ 1, AssetC /\ 1 ] -- multiple assets + ] + } + +selOutputFixture0 :: SelectionStrategy -> SelOutputFixture +selOutputFixture0 strategy = + case strategy of + SelectionStrategyOptimal -> + [ 40 /\ [ AssetA /\ 5 ], 40 /\ [ AssetA /\ 5 ], 60 /\ mempty ] + SelectionStrategyMinimal -> + [ 40 /\ [ AssetA /\ 5 ], 60 /\ mempty ] + +-------------------------------------------------------------------------------- + +type SelectionTest = + { testLabel :: String + , strategy :: SelectionStrategy + , inpFixture :: SelectionStrategy -> SelInputFixture + , outFixture :: SelectionStrategy -> SelOutputFixture + } + +selFixtures :: Array SelectionTest +selFixtures = + [ { testLabel: "Selects only singletons (optimal strategy)" + , strategy: SelectionStrategyOptimal + , inpFixture: selInputFixture0 + , outFixture: selOutputFixture0 + } + , { testLabel: "Selects only singletons (minimal strategy)" + , strategy: SelectionStrategyMinimal + , inpFixture: selInputFixture0 + , outFixture: selOutputFixture0 + } + ] + +-------------------------------------------------------------------------------- +-- CoinSelectionTestM +-------------------------------------------------------------------------------- + +newtype CoinSelectionTestM (a :: Type) = CoinSelectionTestM (Effect a) + +derive instance Newtype (CoinSelectionTestM a) _ +derive newtype instance Functor CoinSelectionTestM +derive newtype instance Apply CoinSelectionTestM +derive newtype instance Applicative CoinSelectionTestM +derive newtype instance Bind CoinSelectionTestM +derive newtype instance Monad CoinSelectionTestM +derive newtype instance MonadEffect CoinSelectionTestM + +instance MonadThrow BalanceTxError CoinSelectionTestM where + throwError = liftEffect <<< throw <<< show + +instance Testable prop => Testable (CoinSelectionTestM prop) where + test = QuickCheck.test <<< unsafePerformEffect <<< unwrap diff --git a/test/CoinSelection/UtxoIndex.purs b/test/CoinSelection/UtxoIndex.purs index 2222dd14f3..0325e91ba0 100644 --- a/test/CoinSelection/UtxoIndex.purs +++ b/test/CoinSelection/UtxoIndex.purs @@ -1,13 +1,7 @@ -module Test.Ctl.CoinSelection.UtxoIndex where +module Test.Ctl.CoinSelection.UtxoIndex (suite) where import Prelude -import Control.Apply (lift2) -import Ctl.Internal.Cardano.Types.Transaction - ( TransactionOutput(TransactionOutput) - , UtxoMap - ) -import Ctl.Internal.Cardano.Types.Value (Value) import Ctl.Internal.CoinSelection.UtxoIndex ( UtxoIndex , UtxoIndexInvariantStatus(InvariantHolds) @@ -19,32 +13,17 @@ import Ctl.Internal.CoinSelection.UtxoIndex , utxoIndexDeleteEntry , utxoIndexInsertEntry ) as UtxoIndex -import Ctl.Internal.Serialization.Address - ( Address - , NetworkId(MainnetId) - , baseAddressToAddress - , paymentKeyHashStakeKeyHashAddress - ) import Ctl.Internal.Test.TestPlanM (TestPlanM) -import Ctl.Internal.Types.OutputDatum (OutputDatum(NoOutputDatum)) -import Ctl.Internal.Types.Transaction - ( TransactionHash - , TransactionInput(TransactionInput) - ) -import Data.Generic.Rep (class Generic) import Data.Map (empty) as Map -import Data.Map.Gen (genMap) as Map -import Data.Maybe (Maybe(Nothing)) -import Data.Newtype (class Newtype, unwrap, wrap) -import Data.Show.Generic (genericShow) -import Data.Tuple (Tuple(Tuple)) -import Data.Tuple.Nested (type (/\)) -import Data.UInt (fromInt) as UInt +import Data.Newtype (unwrap) import Effect.Aff (Aff) import Mote (group, test) +import Test.Ctl.CoinSelection.Arbitrary + ( ArbitraryTxUnspentOut + , ArbitraryUtxoIndex + , ArbitraryUtxoMap + ) import Test.QuickCheck (Result(Failed, Success)) as QuickCheck -import Test.QuickCheck.Arbitrary (class Arbitrary, arbitrary) -import Test.QuickCheck.Gen (Gen) import Test.Spec.Assertions (shouldEqual) import Test.Spec.QuickCheck (quickCheck) @@ -86,83 +65,3 @@ invariantHolds utxoIndex = case UtxoIndex.checkUtxoIndexInvariants utxoIndex of InvariantHolds -> QuickCheck.Success status -> QuickCheck.Failed (show status) - --------------------------------------------------------------------------------- --- Arbitrary --------------------------------------------------------------------------------- - -newtype ArbitraryUtxoIndex = ArbitraryUtxoIndex UtxoIndex - -derive instance Newtype ArbitraryUtxoIndex _ - -instance Arbitrary ArbitraryUtxoIndex where - arbitrary = - (arbitrary :: Gen ArbitraryUtxoMap) - <#> wrap <<< UtxoIndex.buildUtxoIndex <<< unwrap - -newtype ArbitraryUtxoMap = ArbitraryUtxoMap UtxoMap - -derive instance Generic ArbitraryUtxoMap _ -derive instance Newtype ArbitraryUtxoMap _ - -instance Show ArbitraryUtxoMap where - show = genericShow - -instance Arbitrary ArbitraryUtxoMap where - arbitrary = wrap <$> Map.genMap genTransactionInput genTransactionOutput - -newtype ArbitraryTxUnspentOut = - ArbitraryTxUnspentOut (TransactionInput /\ TransactionOutput) - -derive instance Newtype ArbitraryTxUnspentOut _ - -instance Arbitrary ArbitraryTxUnspentOut where - arbitrary = wrap <$> lift2 Tuple genTransactionInput genTransactionOutput - -genTransactionInput :: Gen TransactionInput -genTransactionInput = unwrap <$> (arbitrary :: Gen ArbitraryTransactionInput) - -genTransactionOutput :: Gen TransactionOutput -genTransactionOutput = unwrap <$> (arbitrary :: Gen ArbitraryTransactionOutput) - -newtype ArbitraryTransactionInput = - ArbitraryTransactionInput TransactionInput - -derive instance Newtype ArbitraryTransactionInput _ - -instance Arbitrary ArbitraryTransactionInput where - arbitrary = wrap <$> lift2 mkTxInput arbitrary arbitrary - where - mkTxInput :: TransactionHash -> Int -> TransactionInput - mkTxInput transactionId index = - TransactionInput - { transactionId - , index: UInt.fromInt index - } - -newtype ArbitraryTransactionOutput = - ArbitraryTransactionOutput TransactionOutput - -derive instance Newtype ArbitraryTransactionOutput _ - -instance Arbitrary ArbitraryTransactionOutput where - arbitrary = wrap <$> lift2 mkTxOutput arbitrary arbitrary - where - mkTxOutput :: ArbitraryAddress -> Value -> TransactionOutput - mkTxOutput address amount = - TransactionOutput - { address: unwrap address - , amount - , datum: NoOutputDatum - , scriptRef: Nothing - } - -newtype ArbitraryAddress = ArbitraryAddress Address - -derive instance Newtype ArbitraryAddress _ - -instance Arbitrary ArbitraryAddress where - arbitrary = - wrap <<< baseAddressToAddress <$> - lift2 (paymentKeyHashStakeKeyHashAddress MainnetId) arbitrary arbitrary - diff --git a/test/Unit.purs b/test/Unit.purs index 4324c2a36c..4d984d5752 100644 --- a/test/Unit.purs +++ b/test/Unit.purs @@ -9,7 +9,7 @@ import Effect.Class (liftEffect) import Mote.Monad (mapTest) import Test.Ctl.Base64 as Base64 import Test.Ctl.ByteArray as ByteArray -import Test.Ctl.CoinSelection.UtxoIndex as UtxoIndex +import Test.Ctl.CoinSelection as CoinSelection import Test.Ctl.Data as Data import Test.Ctl.Data.Interval as Ctl.Data.Interval import Test.Ctl.Deserialization as Deserialization @@ -80,4 +80,4 @@ testPlan = do <*> Types.Interval.systemStartFixture E2E.Route.suite MustSpendTotal.suite - UtxoIndex.suite + CoinSelection.suite From c3e26ca23af9065b807abbce2150a174b32f13be Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Tue, 13 Dec 2022 21:47:45 +0000 Subject: [PATCH 100/373] Restore behaviour of getDatumsByHashesWithErrors. remove the query handle and implement it in contract --- src/Contract/PlutusData.purs | 36 ++++++++++++++------------ src/Internal/Contract/Monad.purs | 2 +- src/Internal/Contract/QueryHandle.purs | 3 --- src/Internal/QueryM/Kupo.purs | 8 ------ test/Plutip/Contract.purs | 14 +++++----- 5 files changed, 27 insertions(+), 36 deletions(-) diff --git a/src/Contract/PlutusData.purs b/src/Contract/PlutusData.purs index 21cc81cc9f..6ed943c17f 100644 --- a/src/Contract/PlutusData.purs +++ b/src/Contract/PlutusData.purs @@ -5,7 +5,7 @@ module Contract.PlutusData ( getDatumByHash , getDatumsByHashes - , getDatumsByHashesWithError + , getDatumsByHashesWithErrors , module DataSchema , module Datum , module Hashing @@ -23,6 +23,7 @@ module Contract.PlutusData import Prelude import Contract.Monad (Contract) +import Control.Parallel (parTraverse) import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.Deserialization.PlutusData (deserializeData) as Deserialization import Ctl.Internal.FromData @@ -96,10 +97,11 @@ import Ctl.Internal.Types.Redeemer , redeemerHash , unitRedeemer ) as Redeemer -import Data.Bifunctor (lmap) -import Data.Either (Either, hush) +import Data.Either (Either(Left, Right), hush) import Data.Map (Map) -import Data.Maybe (Maybe) +import Data.Map as Map +import Data.Maybe (Maybe(Just, Nothing)) +import Data.Tuple (Tuple(Tuple)) import Effect.Aff.Class (liftAff) -- | Retrieve the full resolved datum associated to a given datum hash. @@ -110,19 +112,19 @@ getDatumByHash dataHash = do -- | Retrieve full resolved datums associated with given datum hashes. -- | The resulting `Map` will only contain datums that have been successfully --- | resolved. This function returns `Nothing` in case of an error during --- | response processing (bad HTTP code or response parsing error). -getDatumsByHashes :: Array DataHash -> Contract (Maybe (Map DataHash Datum)) -getDatumsByHashes hashes = do - queryHandle <- getQueryHandle - liftAff $ hush <$> queryHandle.getDatumsByHashes hashes +-- | resolved. +getDatumsByHashes :: Array DataHash -> Contract (Map DataHash Datum) +getDatumsByHashes hashes = + Map.mapMaybe hush <$> getDatumsByHashesWithErrors hashes -- | Retrieve full resolved datums associated with given datum hashes. --- | The resulting `Map` will only contain datums that have been successfully --- | resolved. -getDatumsByHashesWithError - :: Array DataHash -> Contract (Either String (Map DataHash Datum)) -getDatumsByHashesWithError hashes = do +-- | Errors are returned per datum. +getDatumsByHashesWithErrors + :: Array DataHash -> Contract (Map DataHash (Either String Datum)) +getDatumsByHashesWithErrors hashes = do queryHandle <- getQueryHandle - liftAff $ lmap show <$> queryHandle.getDatumsByHashes hashes - + liftAff $ Map.fromFoldable <$> flip parTraverse hashes + \dh -> queryHandle.getDatumByHash dh <#> Tuple dh <<< case _ of + Right (Just datum) -> Right datum + Right Nothing -> Left "Datum not found" + Left err -> Left $ show err diff --git a/src/Internal/Contract/Monad.purs b/src/Internal/Contract/Monad.purs index b8ba776e7e..151f45d698 100644 --- a/src/Internal/Contract/Monad.purs +++ b/src/Internal/Contract/Monad.purs @@ -186,7 +186,6 @@ mkContractEnv params = do envBuilder <- sequential ado b1 <- parallel do backend <- buildBackend logger params.backendParams - -- Use the default backend to fetch ledger constants ledgerConstants <- getLedgerConstants logger backend pure $ merge { backend, ledgerConstants } b2 <- parallel do @@ -232,6 +231,7 @@ buildBackend logger = case _ of , kupoConfig } +-- | Query for the ledger constants, ideally using the main backend getLedgerConstants :: Logger -> QueryBackend diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs index beada1d6f8..155f5cd92f 100644 --- a/src/Internal/Contract/QueryHandle.purs +++ b/src/Internal/Contract/QueryHandle.purs @@ -31,7 +31,6 @@ import Ctl.Internal.QueryM.CurrentEpoch (getCurrentEpoch) as QueryM import Ctl.Internal.QueryM.EraSummaries (getEraSummaries) as QueryM import Ctl.Internal.QueryM.Kupo ( getDatumByHash - , getDatumsByHashes , getScriptByHash , getScriptsByHashes , getTxMetadata @@ -67,7 +66,6 @@ type AffE (a :: Type) = Aff (Either ClientError a) type QueryHandle = { getDatumByHash :: DataHash -> AffE (Maybe Datum) - , getDatumsByHashes :: Array DataHash -> AffE (Map DataHash Datum) , getScriptByHash :: ScriptHash -> AffE (Maybe ScriptRef) , getScriptsByHashes :: Array ScriptHash -> AffE (Map ScriptHash ScriptRef) , getUtxoByOref :: TransactionInput -> AffE (Maybe TransactionOutput) @@ -93,7 +91,6 @@ getQueryHandle = ask <#> \contractEnv -> queryHandleForCtlBackend :: ContractEnv -> CtlBackend -> QueryHandle queryHandleForCtlBackend contractEnv backend = { getDatumByHash: runQueryM' <<< Kupo.getDatumByHash - , getDatumsByHashes: runQueryM' <<< Kupo.getDatumsByHashes , getScriptByHash: runQueryM' <<< Kupo.getScriptByHash , getScriptsByHashes: runQueryM' <<< Kupo.getScriptsByHashes , getUtxoByOref: runQueryM' <<< Kupo.getUtxoByOref diff --git a/src/Internal/QueryM/Kupo.purs b/src/Internal/QueryM/Kupo.purs index 8a6976ad75..b60344195c 100644 --- a/src/Internal/QueryM/Kupo.purs +++ b/src/Internal/QueryM/Kupo.purs @@ -1,6 +1,5 @@ module Ctl.Internal.QueryM.Kupo ( getDatumByHash - , getDatumsByHashes , getScriptByHash , getScriptsByHashes , getTxMetadata @@ -137,13 +136,6 @@ getDatumByHash (DataHash dataHashBytes) = do kupoGetRequest endpoint <#> map unwrapKupoDatum <<< handleAffjaxResponse -getDatumsByHashes - :: Array DataHash -> QueryM (Either ClientError (Map DataHash Datum)) -getDatumsByHashes = - runExceptT - <<< map (Map.catMaybes <<< Map.fromFoldable) - <<< parTraverse (\dh -> Tuple dh <$> ExceptT (getDatumByHash dh)) - getScriptByHash :: ScriptHash -> QueryM (Either ClientError (Maybe ScriptRef)) getScriptByHash scriptHash = do let endpoint = "/scripts/" <> rawBytesToHex (scriptHashToBytes scriptHash) diff --git a/test/Plutip/Contract.purs b/test/Plutip/Contract.purs index d3004462da..92b989584e 100644 --- a/test/Plutip/Contract.purs +++ b/test/Plutip/Contract.purs @@ -28,7 +28,7 @@ import Contract.PlutusData , Redeemer(Redeemer) , getDatumByHash , getDatumsByHashes - , getDatumsByHashesWithError + , getDatumsByHashesWithErrors ) import Contract.Prelude (liftM, mconcat) import Contract.Prim.ByteArray (byteArrayFromAscii, hexToByteArrayUnsafe) @@ -702,7 +702,7 @@ suite = do , mkDatumHash "e8cb7d18e81b0be160c114c563c020dcc7bf148a1994b73912db3ea1318d488b" ] - logInfo' <<< show =<< getDatumsByHashesWithError + logInfo' <<< show =<< getDatumsByHashesWithErrors [ mkDatumHash "777093fe6dfffdb3bd2033ad71745f5e2319589e36be4bc9c8cca65ac2bfeb8f" , mkDatumHash @@ -763,17 +763,17 @@ suite = do traverse datumHash datums actualDatums1 <- getDatumsByHashes hashes - actualDatums1 `shouldEqual` Just + actualDatums1 `shouldEqual` ( Map.fromFoldable [ hash1 /\ datum1 , hash2 /\ datum2 ] ) - actualDatums2 <- getDatumsByHashesWithError hashes - actualDatums2 `shouldEqual` Right + actualDatums2 <- getDatumsByHashesWithErrors hashes + actualDatums2 `shouldEqual` ( Map.fromFoldable - [ hash1 /\ datum1 - , hash2 /\ datum2 + [ hash1 /\ Right datum1 + , hash2 /\ Right datum2 ] ) From 1cec8aba3c6af28b4fb8fd68ba4582f616ac8566 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Wed, 14 Dec 2022 12:02:38 +0000 Subject: [PATCH 101/373] Use helper functions where possible. Remove unused imports and dead code. --- CHANGELOG.md | 2 +- src/Contract/Config.purs | 4 +++- src/Contract/Monad.purs | 1 + src/Contract/Staking.purs | 4 +++- src/Contract/Time.purs | 2 +- src/Contract/Wallet.purs | 4 ++-- src/Contract/Wallet/KeyFile.purs | 19 +++++++++++++++++-- src/Internal/BalanceTx/BalanceTx.purs | 4 ++-- src/Internal/Contract/MinFee.purs | 4 ++-- src/Internal/Contract/Wallet.purs | 22 +++++++++------------- src/Internal/Plutip/Server.purs | 15 ++------------- src/Internal/QueryM/Kupo.purs | 6 +++--- src/Internal/Types/ScriptLookups.purs | 14 +++++++------- src/Internal/Wallet.purs | 20 +++++++------------- test/BalanceTx/Collateral.purs | 6 +++--- 15 files changed, 63 insertions(+), 64 deletions(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index d263d27998..6f82db2c16 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -139,7 +139,7 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) ### Runtime Dependencies -- [Ogmios](https://github.com/mlabs-haskell/ogmios) - v5.5.7 +- [Ogmios](https://github.com/mlabs-haskell/ogmios) - v5.5.7 - [Kupo](https://github.com/CardanoSolutions/kupo) - v2.2.0 - [Cardano-Node](https://github.com/input-output-hk/cardano-node/) - v1.35.3 - [Ogmios-Datum-Cache](https://github.com/mlabs-haskell/ogmios-datum-cache) - commit 862c6bfcb6110b8fe816e26b3bba105dfb492b24 diff --git a/src/Contract/Config.purs b/src/Contract/Config.purs index 2976733087..2787232109 100644 --- a/src/Contract/Config.purs +++ b/src/Contract/Config.purs @@ -32,7 +32,9 @@ import Ctl.Internal.Contract.Hooks (emptyHooks) import Ctl.Internal.Contract.Monad (ContractParams) import Ctl.Internal.Contract.QueryBackend ( QueryBackendParams(CtlBackendParams, BlockfrostBackendParams) - , mkBlockfrostBackendParams + -- TODO Export once the following is stable + -- https://github.com/Plutonomicon/cardano-transaction-lib/issues/1118 + -- , mkBlockfrostBackendParams , mkCtlBackendParams ) import Ctl.Internal.Deserialization.Keys (privateKeyFromBytes) diff --git a/src/Contract/Monad.purs b/src/Contract/Monad.purs index daf702b4d0..9bdddc400b 100644 --- a/src/Contract/Monad.purs +++ b/src/Contract/Monad.purs @@ -22,6 +22,7 @@ import Ctl.Internal.Contract.Monad ( Contract(Contract) , ContractEnv , ContractParams + , ParContract(ParContract) , runContract , runContractInEnv , withContractEnv diff --git a/src/Contract/Staking.purs b/src/Contract/Staking.purs index b253213c86..5efce834c7 100644 --- a/src/Contract/Staking.purs +++ b/src/Contract/Staking.purs @@ -3,6 +3,7 @@ module Contract.Staking , getPoolParameters , getPubKeyHashDelegationsAndRewards , getValidatorHashDelegationsAndRewards + , module X ) where import Prelude @@ -14,6 +15,7 @@ import Ctl.Internal.Cardano.Types.Transaction ) import Ctl.Internal.Contract.Monad (wrapQueryM) import Ctl.Internal.QueryM.Pools (DelegationsAndRewards) +import Ctl.Internal.QueryM.Pools (DelegationsAndRewards) as X import Ctl.Internal.QueryM.Pools as QueryM import Ctl.Internal.Types.PubKeyHash (StakePubKeyHash) import Ctl.Internal.Types.Scripts (StakeValidatorHash) @@ -25,7 +27,7 @@ getPoolIds = wrapQueryM QueryM.getPoolIds getPoolParameters :: PoolPubKeyHash -> Contract PoolRegistrationParams -getPoolParameters poolId = wrapQueryM $ QueryM.getPoolParameters poolId +getPoolParameters = wrapQueryM <<< QueryM.getPoolParameters getPubKeyHashDelegationsAndRewards :: StakePubKeyHash diff --git a/src/Contract/Time.purs b/src/Contract/Time.purs index 5073fd761f..8d54a62152 100644 --- a/src/Contract/Time.purs +++ b/src/Contract/Time.purs @@ -117,5 +117,5 @@ getEraSummaries = wrapQueryM EraSummaries.getEraSummaries -- | Get the current system start time. getSystemStart :: Contract SystemStart -getSystemStart = do +getSystemStart = asks $ _.ledgerConstants >>> _.systemStart diff --git a/src/Contract/Wallet.purs b/src/Contract/Wallet.purs index 9bddca9bc9..d48182aba9 100644 --- a/src/Contract/Wallet.purs +++ b/src/Contract/Wallet.purs @@ -74,8 +74,8 @@ withKeyWallet . Wallet.KeyWallet -> Contract a -> Contract a -withKeyWallet wallet action = do - local _ { wallet = Just $ KeyWallet wallet } action +withKeyWallet wallet = + local _ { wallet = Just $ KeyWallet wallet } mkKeyWalletFromPrivateKeys :: PrivatePaymentKey -> Maybe PrivateStakeKey -> Contract Wallet.KeyWallet diff --git a/src/Contract/Wallet/KeyFile.purs b/src/Contract/Wallet/KeyFile.purs index 1948f045cd..c5a86b7436 100644 --- a/src/Contract/Wallet/KeyFile.purs +++ b/src/Contract/Wallet/KeyFile.purs @@ -1,11 +1,13 @@ --- | Node-only module. Allows to work with Skeys stored in files. +-- | Node-only module. Allows working with Skeys stored in files. module Contract.Wallet.KeyFile ( mkKeyWalletFromFiles + , mkKeyWalletFromFilesAff , module Wallet.KeyFile ) where import Prelude +import Contract.Config (NetworkId) import Control.Monad.Reader.Class (asks) import Ctl.Internal.Contract.Monad (Contract) import Ctl.Internal.Wallet.Key (KeyWallet, privateKeysToKeyWallet) @@ -23,6 +25,7 @@ import Ctl.Internal.Wallet.KeyFile ) import Data.Maybe (Maybe) import Data.Traversable (traverse) +import Effect.Aff (Aff) import Effect.Aff.Class (liftAff) import Node.Path (FilePath) @@ -37,6 +40,18 @@ mkKeyWalletFromFiles :: FilePath -> Maybe FilePath -> Contract KeyWallet mkKeyWalletFromFiles paymentKeyFile mbStakeKeyFile = do networkId <- asks _.networkId - liftAff $ privateKeysToKeyWallet networkId + liftAff $ mkKeyWalletFromFilesAff networkId paymentKeyFile mbStakeKeyFile + +-- | Load `PrivateKey`s from `skey` files (the files should be in JSON format as +-- | accepted by cardano-cli) given a network id. +-- | The keys should have `PaymentSigningKeyShelley_ed25519` and +-- | `StakeSigningKeyShelley_ed25519` types, respectively. +-- | The stake key is optional. +-- | +-- | **NodeJS only** +mkKeyWalletFromFilesAff + :: NetworkId -> FilePath -> Maybe FilePath -> Aff KeyWallet +mkKeyWalletFromFilesAff networkId paymentKeyFile mbStakeKeyFile = + privateKeysToKeyWallet networkId <$> privatePaymentKeyFromFile paymentKeyFile <*> traverse privateStakeKeyFromFile mbStakeKeyFile diff --git a/src/Internal/BalanceTx/BalanceTx.purs b/src/Internal/BalanceTx/BalanceTx.purs index d702728d0f..e86c477151 100644 --- a/src/Internal/BalanceTx/BalanceTx.purs +++ b/src/Internal/BalanceTx/BalanceTx.purs @@ -10,7 +10,6 @@ import Control.Monad.Error.Class (liftMaybe) import Control.Monad.Except.Trans (ExceptT(ExceptT), except, runExceptT) import Control.Monad.Logger.Class (class MonadLogger) import Control.Monad.Logger.Class as Logger -import Control.Monad.Reader.Class (asks) import Control.Parallel (parTraverse) import Ctl.Internal.BalanceTx.Collateral ( addTxCollateral @@ -104,6 +103,7 @@ import Ctl.Internal.Cardano.Types.Value , posNonAdaAsset , valueToCoin' ) +import Ctl.Internal.Contract (getProtocolParameters) import Ctl.Internal.Contract.Monad (Contract, filterLockedUtxos) import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.Contract.Wallet (getChangeAddress, getWalletAddresses) as Contract.Wallet @@ -143,7 +143,7 @@ balanceTxWithConstraints -> BalanceTxConstraintsBuilder -> Contract (Either BalanceTxError FinalizedTransaction) balanceTxWithConstraints unbalancedTx constraintsBuilder = do - pparams <- asks $ _.ledgerConstants >>> _.pparams + pparams <- getProtocolParameters queryHandle <- getQueryHandle withBalanceTxConstraints constraintsBuilder $ runExceptT do diff --git a/src/Internal/Contract/MinFee.purs b/src/Internal/Contract/MinFee.purs index 39a5d06eed..a2a04a0f14 100644 --- a/src/Internal/Contract/MinFee.purs +++ b/src/Internal/Contract/MinFee.purs @@ -2,7 +2,6 @@ module Ctl.Internal.Contract.MinFee (calculateMinFee) where import Prelude -import Control.Monad.Reader.Class (asks) import Ctl.Internal.Cardano.Types.Transaction ( Transaction , UtxoMap @@ -14,6 +13,7 @@ import Ctl.Internal.Cardano.Types.TransactionUnspentOutput ( TransactionUnspentOutput ) import Ctl.Internal.Cardano.Types.Value (Coin) +import Ctl.Internal.Contract (getProtocolParameters) import Ctl.Internal.Contract.Monad (Contract) import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.Contract.Wallet (getWalletAddresses, getWalletCollateral) @@ -45,7 +45,7 @@ import Effect.Aff.Class (liftAff) calculateMinFee :: Transaction -> UtxoMap -> Contract Coin calculateMinFee tx additionalUtxos = do selfSigners <- getSelfSigners tx additionalUtxos - pparams <- asks $ _.ledgerConstants >>> _.pparams + pparams <- getProtocolParameters calculateMinFeeCsl pparams selfSigners tx getSelfSigners :: Transaction -> UtxoMap -> Contract (Set Ed25519KeyHash) diff --git a/src/Internal/Contract/Wallet.purs b/src/Internal/Contract/Wallet.purs index 01298ae1f8..2efab5afbf 100644 --- a/src/Internal/Contract/Wallet.purs +++ b/src/Internal/Contract/Wallet.purs @@ -25,6 +25,7 @@ import Ctl.Internal.Cardano.Types.TransactionUnspentOutput ) import Ctl.Internal.Cardano.Types.Value (Value) import Ctl.Internal.Cardano.Types.Value (geq, lovelaceValueOf) as Value +import Ctl.Internal.Contract (getProtocolParameters) import Ctl.Internal.Contract.Monad (Contract, filterLockedUtxos) import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.Helpers (liftM, liftedM) @@ -86,7 +87,7 @@ signData :: Address -> RawBytes -> Contract (Maybe DataSignature) signData address payload = withWalletAff (Aff.signData address payload) getWallet :: Contract (Maybe Wallet) -getWallet = asks (_.wallet) +getWallet = asks _.wallet getNetworkId :: Contract NetworkId getNetworkId = asks _.networkId @@ -124,25 +125,21 @@ withWalletAff act = withWallet (liftAff <<< act) withWallet :: forall (a :: Type). (Wallet -> Contract a) -> Contract a withWallet act = do - wallet <- liftedM (error "No wallet set") $ asks _.wallet + wallet <- liftedM (error "No wallet set") getWallet act wallet getWalletCollateral :: Contract (Maybe (Array TransactionUnspentOutput)) getWalletCollateral = do - mbCollateralUTxOs <- asks (_.wallet) >>= maybe (pure Nothing) do + { maxCollateralInputs, coinsPerUtxoUnit } <- unwrap <$> getProtocolParameters + mbCollateralUTxOs <- getWallet >>= maybe (pure Nothing) do actionBasedOnWallet _.getCollateral \kw -> do queryHandle <- getQueryHandle let addr = (unwrap kw).address utxos <- (liftAff $ queryHandle.utxosAt addr) <#> hush >>> fromMaybe Map.empty >>= filterLockedUtxos - pparams <- asks $ _.ledgerConstants >>> _.pparams <#> unwrap - let - coinsPerUtxoUnit = pparams.coinsPerUtxoUnit - maxCollateralInputs = UInt.toInt $ - pparams.maxCollateralInputs liftEffect $ (unwrap kw).selectCollateral coinsPerUtxoUnit - maxCollateralInputs + (UInt.toInt maxCollateralInputs) utxos let @@ -168,11 +165,10 @@ getWalletCollateral = do colUtxos for_ sufficientUtxos \collateralUTxOs -> do - pparams <- asks $ _.ledgerConstants >>> _.pparams let tooManyCollateralUTxOs = UInt.fromInt (Array.length collateralUTxOs) > - (unwrap pparams).maxCollateralInputs + maxCollateralInputs when tooManyCollateralUTxOs do liftEffect $ throw tooManyCollateralUTxOsError pure sufficientUtxos @@ -185,7 +181,7 @@ getWalletBalance :: Contract (Maybe Value) getWalletBalance = do queryHandle <- getQueryHandle - asks _.wallet >>= map join <<< traverse do + getWallet >>= map join <<< traverse do actionBasedOnWallet _.getBalance \_ -> do -- Implement via `utxosAt` addresses <- getWalletAddresses @@ -197,7 +193,7 @@ getWalletBalance = do getWalletUtxos :: Contract (Maybe UtxoMap) getWalletUtxos = do queryHandle <- getQueryHandle - asks _.wallet >>= map join <<< traverse do + getWallet >>= map join <<< traverse do actionBasedOnWallet (\w conn -> w.getUtxos conn <#> map toUtxoMap) \_ -> do diff --git a/src/Internal/Plutip/Server.purs b/src/Internal/Plutip/Server.purs index 84a92c35fb..b80a387473 100644 --- a/src/Internal/Plutip/Server.purs +++ b/src/Internal/Plutip/Server.purs @@ -44,13 +44,11 @@ import Ctl.Internal.Plutip.Spawn ( ManagedProcess , NewOutputAction(Success, NoOp) , OnSignalRef - , cleanupOnSigint , cleanupOnSigint' , cleanupTmpDir , removeOnSignal , spawn , stop - , waitForStop ) import Ctl.Internal.Plutip.Types ( ClusterStartupParameters @@ -74,7 +72,6 @@ import Ctl.Internal.Plutip.UtxoDistribution import Ctl.Internal.QueryM ( ClientError(ClientDecodeJsonError, ClientHttpError) ) -import Ctl.Internal.QueryM.UniqueId (uniqueId) import Ctl.Internal.Test.TestPlanM (TestPlanM) import Ctl.Internal.Types.UsedTxOuts (newUsedTxOuts) import Ctl.Internal.Wallet.Key (PrivatePaymentKey(PrivatePaymentKey)) @@ -113,7 +110,7 @@ import Mote.Description (Description(Group, Test)) import Mote.Monad (MoteT(MoteT), mapTest) import Node.ChildProcess (defaultSpawnOptions) import Node.FS.Sync (exists, mkdir) as FSSync -import Node.Path (FilePath, dirname) +import Node.Path (FilePath) import Type.Prelude (Proxy(Proxy)) -- | Run a single `Contract` in Plutip environment. @@ -372,7 +369,7 @@ startPlutipContractEnv plutipCfg distr cleanupRef = do -> Aff wallets mkWallets' env ourKey response = do runContractInEnv - ((_ { customLogger = Just (\_ _ -> pure unit) }) env) + env { customLogger = Just (\_ _ -> pure unit) } do wallets <- liftContractM @@ -657,14 +654,6 @@ defaultRetryPolicy :: RetryPolicy defaultRetryPolicy = limitRetriesByCumulativeDelay (Milliseconds 3000.00) $ constantDelay (Milliseconds 100.0) -defaultRecovering :: forall (a :: Type). Aff a -> Aff a -defaultRecovering f = - recovering retryPolicy ([ \_ _ -> pure true ]) $ const f - where - retryPolicy :: RetryPolicy - retryPolicy = limitRetriesByCumulativeDelay (Milliseconds 3000.00) $ - constantDelay (Milliseconds 100.0) - mkServerEndpointUrl :: PlutipConfig -> String -> String mkServerEndpointUrl cfg path = do "http://" <> cfg.host <> ":" <> UInt.toString cfg.port <> path diff --git a/src/Internal/QueryM/Kupo.purs b/src/Internal/QueryM/Kupo.purs index b60344195c..6ccc3b3d2d 100644 --- a/src/Internal/QueryM/Kupo.purs +++ b/src/Internal/QueryM/Kupo.purs @@ -180,11 +180,11 @@ getTxMetadata txHash = runExceptT do <> byteArrayToHex (unwrap txHash) generalTxMetadatas <- ExceptT $ handleAffjaxResponse <$> kupoGetRequest endpoint - case uncons (generalTxMetadatas :: _ { raw :: String }) of + pure case uncons (generalTxMetadatas :: _ { raw :: String }) of Just { head, tail: [] } -> - pure $ hexToByteArray head.raw >>= + hexToByteArray head.raw >>= (fromBytes >=> convertGeneralTransactionMetadata >>> hush) - _ -> pure Nothing + _ -> Nothing -------------------------------------------------------------------------------- -- `utxosAt` response parsing diff --git a/src/Internal/Types/ScriptLookups.purs b/src/Internal/Types/ScriptLookups.purs index 6309045d47..6cca881c27 100644 --- a/src/Internal/Types/ScriptLookups.purs +++ b/src/Internal/Types/ScriptLookups.purs @@ -101,6 +101,7 @@ import Ctl.Internal.Cardano.Types.Value , negation , split ) +import Ctl.Internal.Contract (getProtocolParameters) import Ctl.Internal.Contract.Monad (Contract, wrapQueryM) import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.Hashing (datumHash) as Hashing @@ -640,8 +641,7 @@ runConstraintsM -> TxConstraints redeemer datum -> Contract (Either MkUnbalancedTxError (ConstraintProcessingState validator)) runConstraintsM lookups txConstraints = do - costModels <- asks $ _.ledgerConstants >>> _.pparams >>> unwrap >>> - _.costModels + { costModels } <- unwrap <$> getProtocolParameters let initCps :: ConstraintProcessingState validator initCps = @@ -813,7 +813,7 @@ addOwnInput -> InputConstraint redeemer -> ConstraintsM validator (Either MkUnbalancedTxError Unit) addOwnInput _pd (InputConstraint { txOutRef }) = do - networkId <- asks _.networkId + networkId <- getNetworkId runExceptT do ScriptLookups { txOutputs, typedValidator } <- use _lookups -- Convert to Cardano type @@ -839,7 +839,7 @@ addOwnOutput -> ConstraintsM validator (Either MkUnbalancedTxError Unit) addOwnOutput (OutputConstraint { datum: d, value }) = do queryHandle <- lift $ getQueryHandle - networkId <- asks _.networkId + networkId <- getNetworkId runExceptT do ScriptLookups { typedValidator } <- use _lookups inst <- liftM TypedValidatorMissing typedValidator @@ -1377,7 +1377,7 @@ processConstraint mpsMap osMap c = do poolKeyHash attachToCps attachNativeScript (unwrap stakeValidator) MustWithdrawStakePubKey spkh -> runExceptT do - networkId <- asks _.networkId + networkId <- lift getNetworkId mbRewards <- lift $ lift $ wrapQueryM $ getPubKeyHashDelegationsAndRewards spkh ({ rewards }) <- ExceptT $ pure $ note (CannotWithdrawRewardsPubKey spkh) @@ -1389,7 +1389,7 @@ processConstraint mpsMap osMap c = do Map.union (Map.singleton rewardAddress (fromMaybe (Coin zero) rewards)) MustWithdrawStakePlutusScript stakeValidator redeemerData -> runExceptT do let hash = plutusScriptStakeValidatorHash stakeValidator - networkId <- asks _.networkId + networkId <- lift getNetworkId mbRewards <- lift $ lift $ wrapQueryM $ getValidatorHashDelegationsAndRewards hash let @@ -1412,7 +1412,7 @@ processConstraint mpsMap osMap c = do _redeemersTxIns <>= Array.singleton (redeemer /\ Nothing) MustWithdrawStakeNativeScript stakeValidator -> runExceptT do let hash = nativeScriptStakeValidatorHash stakeValidator - networkId <- asks _.networkId + networkId <- lift getNetworkId mbRewards <- lift $ lift $ wrapQueryM $ getValidatorHashDelegationsAndRewards hash let diff --git a/src/Internal/Wallet.purs b/src/Internal/Wallet.purs index 0e2d16fa9c..d63c335909 100644 --- a/src/Internal/Wallet.purs +++ b/src/Internal/Wallet.purs @@ -316,11 +316,10 @@ dummySign tx@(Transaction { witnessSet: tws@(TransactionWitnessSet ws) }) = ) getNetworkId :: Wallet -> Aff NetworkId -getNetworkId wallet = do +getNetworkId = actionBasedOnWallet (\w -> intToNetworkId <=< _.getNetworkId w) - (\kw -> pure (unwrap kw).networkId) - wallet + \kw -> pure (unwrap kw).networkId where intToNetworkId :: Int -> Aff NetworkId intToNetworkId = case _ of @@ -330,15 +329,12 @@ getNetworkId wallet = do getUnusedAddresses :: Wallet -> Aff (Array Address) getUnusedAddresses wallet = fold <$> do - actionBasedOnWallet _.getUnusedAddresses - (\_ -> pure $ pure []) - wallet + actionBasedOnWallet _.getUnusedAddresses mempty wallet getChangeAddress :: Wallet -> Aff (Maybe Address) -getChangeAddress wallet = do +getChangeAddress = actionBasedOnWallet _.getChangeAddress - (\kw -> pure $ pure (unwrap kw).address) - wallet + \kw -> pure $ pure (unwrap kw).address getRewardAddresses :: Wallet -> Aff (Array Address) getRewardAddresses wallet = fold <$> do @@ -353,11 +349,10 @@ getWalletAddresses wallet = fold <$> do wallet signData :: Address -> RawBytes -> Wallet -> Aff (Maybe DataSignature) -signData address payload wallet = do +signData address payload = actionBasedOnWallet (\w conn -> w.signData conn address payload) - (\kw -> pure <$> (unwrap kw).signData payload) - wallet + \kw -> pure <$> (unwrap kw).signData payload actionBasedOnWallet :: forall (m :: Type -> Type) (a :: Type) @@ -395,7 +390,6 @@ ownStakePubKeysHashes wallet = do addresses <- getWalletAddresses wallet pure $ addressToMStakePubKeyHash <$> addresses where - addressToMStakePubKeyHash :: Address -> Maybe StakePubKeyHash addressToMStakePubKeyHash address = do baseAddress <- baseAddressFromAddress address diff --git a/test/BalanceTx/Collateral.purs b/test/BalanceTx/Collateral.purs index 44c3adb2a4..2aa90ab025 100644 --- a/test/BalanceTx/Collateral.purs +++ b/test/BalanceTx/Collateral.purs @@ -4,7 +4,7 @@ import Prelude import Contract.Config (testnetConfig) import Contract.Monad (Contract, runContract) -import Control.Monad.Reader.Trans (asks) +import Contract.ProtocolParameters (getProtocolParameters) import Ctl.Internal.BalanceTx.Collateral.Select ( maxCandidateUtxos , minRequiredCollateral @@ -85,12 +85,12 @@ withParams test = where getMaxCollateralInputs :: Contract Int getMaxCollateralInputs = - asks $ _.ledgerConstants >>> _.pparams <#> + getProtocolParameters <#> UInt.toInt <<< _.maxCollateralInputs <<< unwrap getCoinsPerUtxoUnit :: Contract CoinsPerUtxoUnit getCoinsPerUtxoUnit = - asks (_.ledgerConstants >>> _.pparams) <#> unwrap >>> + getProtocolParameters <#> unwrap >>> _.coinsPerUtxoUnit -- | Ada-only tx output sufficient to cover `minRequiredCollateral`. From a3d146f56e4cc789511241fe83f8d1cc68f3796c Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Wed, 14 Dec 2022 13:37:46 +0100 Subject: [PATCH 102/373] Unit tests for performSelection: Test selection improvement logic --- src/Contract/Hashing.purs | 4 +- src/Internal/Hashing.js | 8 +++ src/Internal/Hashing.purs | 8 ++- test/CoinSelection/CoinSelection.purs | 72 ++++++++++++++++++++------- 4 files changed, 73 insertions(+), 19 deletions(-) diff --git a/src/Contract/Hashing.purs b/src/Contract/Hashing.purs index 2f645b428a..ab41931812 100644 --- a/src/Contract/Hashing.purs +++ b/src/Contract/Hashing.purs @@ -4,7 +4,9 @@ module Contract.Hashing import Contract.Scripts (plutusScriptStakeValidatorHash) as X import Ctl.Internal.Hashing - ( blake2b256Hash + ( blake2b224Hash + , blake2b224HashHex + , blake2b256Hash , blake2b256HashHex , datumHash , plutusScriptHash diff --git a/src/Internal/Hashing.js b/src/Internal/Hashing.js index 29c2080bd7..e61e1651c8 100644 --- a/src/Internal/Hashing.js +++ b/src/Internal/Hashing.js @@ -11,6 +11,14 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } +exports.blake2b224Hash = bytesToHash => { + return Blake2.blake2b(bytesToHash, null, 28); +}; + +exports.blake2b224HashHex = bytesToHash => { + return Blake2.blake2bHex(bytesToHash, null, 28); +}; + exports.blake2b256Hash = bytesToHash => { return Blake2.blake2b(bytesToHash, null, 32); }; diff --git a/src/Internal/Hashing.purs b/src/Internal/Hashing.purs index f1b4cd6fbe..5a69d5494c 100644 --- a/src/Internal/Hashing.purs +++ b/src/Internal/Hashing.purs @@ -1,5 +1,7 @@ module Ctl.Internal.Hashing - ( blake2b256Hash + ( blake2b224Hash + , blake2b224HashHex + , blake2b256Hash , blake2b256HashHex , datumHash , plutusScriptHash @@ -35,6 +37,10 @@ import Data.Maybe (Maybe) import Data.Newtype (unwrap, wrap) import Untagged.Union (asOneOf) +foreign import blake2b224Hash :: ByteArray -> ByteArray + +foreign import blake2b224HashHex :: ByteArray -> String + foreign import blake2b256Hash :: ByteArray -> ByteArray foreign import blake2b256HashHex :: ByteArray -> String diff --git a/test/CoinSelection/CoinSelection.purs b/test/CoinSelection/CoinSelection.purs index 203cf99ca6..747c88cbb2 100644 --- a/test/CoinSelection/CoinSelection.purs +++ b/test/CoinSelection/CoinSelection.purs @@ -17,11 +17,13 @@ import Ctl.Internal.Cardano.Types.Value , NonAdaAsset , Value , mkCoin + , mkCurrencySymbol , mkSingletonNonAdaAsset , mkValue ) import Ctl.Internal.CoinSelection.UtxoIndex (UtxoIndex) import Ctl.Internal.CoinSelection.UtxoIndex (buildUtxoIndex) as UtxoIndex +import Ctl.Internal.Hashing (blake2b224Hash) import Ctl.Internal.Test.TestPlanM (TestPlanM) import Ctl.Internal.Types.ByteArray (byteArrayFromAscii) import Ctl.Internal.Types.OutputDatum (OutputDatum(NoOutputDatum)) @@ -50,7 +52,6 @@ import Test.Ctl.CoinSelection.Arbitrary , ArbitraryUtxoIndex ) import Test.Ctl.CoinSelection.UtxoIndex (suite) as UtxoIndex -import Test.Ctl.Fixtures (currencySymbol1) as Fixtures import Test.QuickCheck (class Testable, Result, assertEquals) import Test.QuickCheck (test) as QuickCheck import Test.QuickCheck.Arbitrary (arbitrary) @@ -64,7 +65,7 @@ suite = UtxoIndex.suite group "performMultiAssetSelection" do performMultiAssetSelection_unitTests - test "prop_performMultiAssetSelection_empty" do + test "Performs a selection with zero outputs" do quickCheck prop_performMultiAssetSelection_empty -------------------------------------------------------------------------------- @@ -83,8 +84,9 @@ prop_performMultiAssetSelection_empty strategy utxoIndex = performMultiAssetSelection_unitTests :: TestPlanM (Aff Unit) Unit performMultiAssetSelection_unitTests = - for_ selFixtures \{ testLabel, strategy, inpFixture, outFixture } -> - test testLabel $ liftEffect $ (unwrap :: CoinSelectionTestM _ -> _) do + for_ selFixtures \{ testLabel, strategy, inpFixture, outFixture } -> do + let testLabel' = testLabel <> showSelStrategy strategy + test testLabel' $ liftEffect $ (unwrap :: CoinSelectionTestM _ -> _) do td <- liftEffect $ selTestDataFromFixtures (inpFixture strategy) (outFixture strategy) selectedUtxos <- @@ -94,6 +96,12 @@ performMultiAssetSelection_unitTests = td.selectedValue `shouldEqual` foldMap (_.amount <<< unwrap) (Map.values selectedUtxos) +showSelStrategy :: SelectionStrategy -> String +showSelStrategy strategy = + case strategy of + SelectionStrategyOptimal -> " (optimal strategy)" + SelectionStrategyMinimal -> " (minimal strategy)" + -------------------------------------------------------------------------------- -- Fixtures -------------------------------------------------------------------------------- @@ -106,9 +114,14 @@ instance Show AssetFixture where show = genericShow assetClassFromFixture :: AssetFixture -> CurrencySymbol /\ TokenName -assetClassFromFixture = - Tuple Fixtures.currencySymbol1 <<< tokenNameFromAscii <<< show +assetClassFromFixture asset = + currencySymbolFromAscii (show asset) /\ tokenNameFromAscii (show asset) where + currencySymbolFromAscii :: String -> CurrencySymbol + currencySymbolFromAscii str = + unsafePartial fromJust $ + mkCurrencySymbol =<< map blake2b224Hash (byteArrayFromAscii str) + tokenNameFromAscii :: String -> TokenName tokenNameFromAscii = unsafePartial fromJust <<< (mkTokenName <=< byteArrayFromAscii) @@ -187,6 +200,26 @@ selOutputFixture0 strategy = SelectionStrategyMinimal -> [ 40 /\ [ AssetA /\ 5 ], 60 /\ mempty ] +selInputFixture1 :: SelectionStrategy -> SelInputFixture +selInputFixture1 strategy = + { strategy + , requiredValue: 100 /\ [ AssetA /\ 5 ] + , utxos: + [ 100 /\ [ AssetA /\ 5 ] + -- ^ singleton for AssetA - covers the output asset quantity, + -- but the selection can still be improved + , 50 /\ [ AssetA /\ 5, AssetB /\ 1 ] + -- ^ pair for AssetA and AssetB - should not be considered to + -- improve the selection for AssetA + , 50 /\ [ AssetA /\ 4, AssetB /\ 1, AssetC /\ 1 ] + -- ^ bundle containing multiple assets including AssetA - should not be + -- considered to improve the selection for AssetA + ] + } + +selOutputFixture1 :: SelectionStrategy -> SelOutputFixture +selOutputFixture1 _ = [ 100 /\ [ AssetA /\ 5 ] ] + -------------------------------------------------------------------------------- type SelectionTest = @@ -196,19 +229,24 @@ type SelectionTest = , outFixture :: SelectionStrategy -> SelOutputFixture } +selTestsForBothStrategies + :: (SelectionStrategy -> SelInputFixture) + -> (SelectionStrategy -> SelOutputFixture) + -> String + -> Array SelectionTest +selTestsForBothStrategies inpFixture outFixture testLabel = + [ mkTest SelectionStrategyOptimal, mkTest SelectionStrategyMinimal ] + where + mkTest :: SelectionStrategy -> SelectionTest + mkTest strategy = { testLabel, strategy, inpFixture, outFixture } + selFixtures :: Array SelectionTest selFixtures = - [ { testLabel: "Selects only singletons (optimal strategy)" - , strategy: SelectionStrategyOptimal - , inpFixture: selInputFixture0 - , outFixture: selOutputFixture0 - } - , { testLabel: "Selects only singletons (minimal strategy)" - , strategy: SelectionStrategyMinimal - , inpFixture: selInputFixture0 - , outFixture: selOutputFixture0 - } - ] + selTestsForBothStrategies selInputFixture0 selOutputFixture0 + "Selects only from the 'singletons' subset if possible" + <> + selTestsForBothStrategies selInputFixture1 selOutputFixture1 + "Selects only from the 'singletons' subset to improve selection" -------------------------------------------------------------------------------- -- CoinSelectionTestM From 696e320367eb60f6a32abc21f4e4833e858f3115 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Wed, 14 Dec 2022 16:43:05 +0100 Subject: [PATCH 103/373] Add more tests for performSelection, Refactor code --- test/CoinSelection/CoinSelection.purs | 140 +++++++++++++------------- 1 file changed, 69 insertions(+), 71 deletions(-) diff --git a/test/CoinSelection/CoinSelection.purs b/test/CoinSelection/CoinSelection.purs index 747c88cbb2..2c98d84837 100644 --- a/test/CoinSelection/CoinSelection.purs +++ b/test/CoinSelection/CoinSelection.purs @@ -64,9 +64,14 @@ suite = group "CoinSelection" do UtxoIndex.suite group "performMultiAssetSelection" do - performMultiAssetSelection_unitTests test "Performs a selection with zero outputs" do quickCheck prop_performMultiAssetSelection_empty + runSelectionTestWithFixture selFixture0 + "Selects only from the 'singletons' subset if possible" + runSelectionTestWithFixture selFixture1 + "Selects only from the 'singletons' subset to improve selection" + runSelectionTestWithFixture selFixture2 + "Selects from the 'pairs' subset if the 'singletons' subset is empty" -------------------------------------------------------------------------------- -- Tests @@ -82,13 +87,13 @@ prop_performMultiAssetSelection_empty strategy utxoIndex = targetSelState = wrap { leftoverUtxos: unwrap utxoIndex, selectedUtxos: Map.empty } -performMultiAssetSelection_unitTests :: TestPlanM (Aff Unit) Unit -performMultiAssetSelection_unitTests = - for_ selFixtures \{ testLabel, strategy, inpFixture, outFixture } -> do +runSelectionTestWithFixture + :: (SelectionStrategy -> SelFixture) -> String -> TestPlanM (Aff Unit) Unit +runSelectionTestWithFixture mkFixture testLabel = + for_ [ SelectionStrategyOptimal, SelectionStrategyMinimal ] \strategy -> do let testLabel' = testLabel <> showSelStrategy strategy test testLabel' $ liftEffect $ (unwrap :: CoinSelectionTestM _ -> _) do - td <- liftEffect $ - selTestDataFromFixtures (inpFixture strategy) (outFixture strategy) + td <- liftEffect $ selTestDataFromFixture (mkFixture strategy) selectedUtxos <- _.selectedUtxos <<< unwrap <$> performMultiAssetSelection td.strategy td.utxoIndex td.requiredValue @@ -113,6 +118,22 @@ derive instance Generic AssetFixture _ instance Show AssetFixture where show = genericShow +type TokenBundleFixture = Int /\ Array (AssetFixture /\ Int) + +type SelFixture = + { strategy :: SelectionStrategy + , requiredValue :: TokenBundleFixture + , utxos :: Array TokenBundleFixture + , selectedUtxos :: Array TokenBundleFixture + } + +type SelTestData = + { strategy :: SelectionStrategy + , requiredValue :: Value + , utxoIndex :: UtxoIndex + , selectedValue :: Value + } + assetClassFromFixture :: AssetFixture -> CurrencySymbol /\ TokenName assetClassFromFixture asset = currencySymbolFromAscii (show asset) /\ tokenNameFromAscii (show asset) @@ -126,8 +147,6 @@ assetClassFromFixture asset = tokenNameFromAscii = unsafePartial fromJust <<< (mkTokenName <=< byteArrayFromAscii) -type TokenBundleFixture = Int /\ Array (AssetFixture /\ Int) - assetFromFixture :: AssetFixture /\ Int -> NonAdaAsset assetFromFixture (assetFixture /\ quantity) = mkSingletonNonAdaAsset currencySymbol tokenName (BigInt.fromInt quantity) @@ -138,33 +157,17 @@ valueFromFixture :: TokenBundleFixture -> Value valueFromFixture (coin /\ assets) = mkValue (mkCoin coin) (foldMap assetFromFixture assets) -type SelInputFixture = - { strategy :: SelectionStrategy - , requiredValue :: TokenBundleFixture - , utxos :: Array TokenBundleFixture - } - -type SelOutputFixture = Array TokenBundleFixture - -type SelTestData = - { strategy :: SelectionStrategy - , requiredValue :: Value - , utxoIndex :: UtxoIndex - , selectedValue :: Value - } - -selTestDataFromFixtures - :: SelInputFixture -> SelOutputFixture -> Effect SelTestData -selTestDataFromFixtures inpFixture outFixture = do +selTestDataFromFixture :: SelFixture -> Effect SelTestData +selTestDataFromFixture selFixture = do utxoIndex <- UtxoIndex.buildUtxoIndex <<< Map.fromFoldable <$> - for inpFixture.utxos \bundle -> + for selFixture.utxos \bundle -> Tuple <$> txInputSample <*> mkTxOutput (valueFromFixture bundle) pure - { strategy: inpFixture.strategy - , requiredValue: valueFromFixture inpFixture.requiredValue + { strategy: selFixture.strategy + , requiredValue: valueFromFixture selFixture.requiredValue , utxoIndex - , selectedValue: fold (valueFromFixture <$> outFixture) + , selectedValue: fold (valueFromFixture <$> selFixture.selectedUtxos) } where txInputSample :: Effect TransactionInput @@ -179,8 +182,8 @@ selTestDataFromFixtures inpFixture outFixture = do -------------------------------------------------------------------------------- -selInputFixture0 :: SelectionStrategy -> SelInputFixture -selInputFixture0 strategy = +selFixture0 :: SelectionStrategy -> SelFixture +selFixture0 strategy = { strategy , requiredValue: 100 /\ [ AssetA /\ 5 ] , utxos: @@ -190,18 +193,16 @@ selInputFixture0 strategy = , 10 /\ [ AssetA /\ 4, AssetB /\ 1 ] -- pair for AssetA and AssetB , 100 /\ [ AssetA /\ 5, AssetB /\ 1, AssetC /\ 1 ] -- multiple assets ] + , selectedUtxos: + case strategy of + SelectionStrategyOptimal -> + [ 40 /\ [ AssetA /\ 5 ], 40 /\ [ AssetA /\ 5 ], 60 /\ mempty ] + SelectionStrategyMinimal -> + [ 40 /\ [ AssetA /\ 5 ], 60 /\ mempty ] } -selOutputFixture0 :: SelectionStrategy -> SelOutputFixture -selOutputFixture0 strategy = - case strategy of - SelectionStrategyOptimal -> - [ 40 /\ [ AssetA /\ 5 ], 40 /\ [ AssetA /\ 5 ], 60 /\ mempty ] - SelectionStrategyMinimal -> - [ 40 /\ [ AssetA /\ 5 ], 60 /\ mempty ] - -selInputFixture1 :: SelectionStrategy -> SelInputFixture -selInputFixture1 strategy = +selFixture1 :: SelectionStrategy -> SelFixture +selFixture1 strategy = { strategy , requiredValue: 100 /\ [ AssetA /\ 5 ] , utxos: @@ -215,39 +216,36 @@ selInputFixture1 strategy = -- ^ bundle containing multiple assets including AssetA - should not be -- considered to improve the selection for AssetA ] + , selectedUtxos: [ 100 /\ [ AssetA /\ 5 ] ] } -selOutputFixture1 :: SelectionStrategy -> SelOutputFixture -selOutputFixture1 _ = [ 100 /\ [ AssetA /\ 5 ] ] - --------------------------------------------------------------------------------- - -type SelectionTest = - { testLabel :: String - , strategy :: SelectionStrategy - , inpFixture :: SelectionStrategy -> SelInputFixture - , outFixture :: SelectionStrategy -> SelOutputFixture +selFixture2 :: SelectionStrategy -> SelFixture +selFixture2 strategy = + { strategy + , requiredValue: 100 /\ [ AssetA /\ 10 ] + , utxos: + [ 50 /\ [ AssetA /\ 4, AssetB /\ 1 ] + -- ^ pair for AssetA and AssetB + -- should be selected to cover the required quantity of AssetA + , 50 /\ [ AssetA /\ 6, AssetB /\ 3 ] + -- ^ pair for AssetA and AssetB + -- should be selected to cover the required quantity of AssetA + , 70 /\ mempty + -- ^ singleton for AssetLovelace + -- should be selected to cover the required quantity of AssetLovelace + , 100 /\ [ AssetA /\ 10, AssetB /\ 1, AssetC /\ 1 ] + -- ^ bundle containing multiple assets including AssetA + -- should not be selected + , 50 /\ [ AssetB /\ 1 ] + -- ^ singleton for AssetB - should not be selected + ] + , selectedUtxos: + [ 50 /\ [ AssetA /\ 4, AssetB /\ 1 ] + , 50 /\ [ AssetA /\ 6, AssetB /\ 3 ] + , 70 /\ mempty + ] } -selTestsForBothStrategies - :: (SelectionStrategy -> SelInputFixture) - -> (SelectionStrategy -> SelOutputFixture) - -> String - -> Array SelectionTest -selTestsForBothStrategies inpFixture outFixture testLabel = - [ mkTest SelectionStrategyOptimal, mkTest SelectionStrategyMinimal ] - where - mkTest :: SelectionStrategy -> SelectionTest - mkTest strategy = { testLabel, strategy, inpFixture, outFixture } - -selFixtures :: Array SelectionTest -selFixtures = - selTestsForBothStrategies selInputFixture0 selOutputFixture0 - "Selects only from the 'singletons' subset if possible" - <> - selTestsForBothStrategies selInputFixture1 selOutputFixture1 - "Selects only from the 'singletons' subset to improve selection" - -------------------------------------------------------------------------------- -- CoinSelectionTestM -------------------------------------------------------------------------------- From 881c21652e896b627d786ee6e57cafe828e17f6d Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Wed, 14 Dec 2022 18:31:27 +0000 Subject: [PATCH 104/373] Export getScriptByHash, remove the internal plural handle from Contract --- src/Contract/Scripts.purs | 28 +++++++++++++++++++++++++- src/Internal/Contract/QueryHandle.purs | 6 +----- src/Internal/QueryM/Kupo.purs | 8 -------- 3 files changed, 28 insertions(+), 14 deletions(-) diff --git a/src/Contract/Scripts.purs b/src/Contract/Scripts.purs index fb1f6cae39..b490c768c6 100644 --- a/src/Contract/Scripts.purs +++ b/src/Contract/Scripts.purs @@ -4,6 +4,8 @@ module Contract.Scripts ( applyArgs , applyArgsM + , getScriptByHash + , getScriptsByHashes , module ExportQueryM , module ExportScripts , module Hash @@ -16,6 +18,7 @@ module Contract.Scripts import Prelude import Contract.Monad (Contract) +import Control.Parallel (parTraverse) import Ctl.Internal.Cardano.Types.NativeScript ( NativeScript ( ScriptPubkey @@ -26,8 +29,11 @@ import Ctl.Internal.Cardano.Types.NativeScript , TimelockExpiry ) ) as NativeScript +import Ctl.Internal.Cardano.Types.ScriptRef (ScriptRef) import Ctl.Internal.Contract.ApplyArgs (applyArgs) as Contract +import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.NativeScripts (NativeScriptHash(NativeScriptHash)) as X +import Ctl.Internal.QueryM (ClientError) import Ctl.Internal.QueryM ( ClientError ( ClientHttpError @@ -41,6 +47,7 @@ import Ctl.Internal.Scripts , plutusScriptStakeValidatorHash , validatorHash ) as ExportScripts +import Ctl.Internal.Serialization.Hash (ScriptHash) import Ctl.Internal.Serialization.Hash (ScriptHash) as Hash import Ctl.Internal.Types.PlutusData (PlutusData) import Ctl.Internal.Types.Scripts @@ -67,14 +74,33 @@ import Ctl.Internal.Types.TypedValidator , typedValidatorScript ) as TypedValidator import Data.Either (Either, hush) +import Data.Map (Map) +import Data.Map as Map import Data.Maybe (Maybe) +import Data.Tuple (Tuple(Tuple)) +import Effect.Aff.Class (liftAff) + +-- | Retrieve a `ScriptRef` given the hash +getScriptByHash :: ScriptHash -> Contract (Either ClientError (Maybe ScriptRef)) +getScriptByHash hash = do + queryHandle <- getQueryHandle + liftAff $ queryHandle.getScriptByHash hash + +-- | Retrieve `ScriptRef`s given their hashes +getScriptsByHashes + :: Array ScriptHash + -> Contract (Map ScriptHash (Either ClientError (Maybe ScriptRef))) +getScriptsByHashes hashes = do + queryHandle <- getQueryHandle + liftAff $ Map.fromFoldable <$> flip parTraverse hashes + \sh -> queryHandle.getScriptByHash sh <#> Tuple sh -- | Apply `PlutusData` arguments to any type isomorphic to `PlutusScript`, -- | returning an updated script with the provided arguments applied applyArgs :: PlutusScript -> Array PlutusData - -> Contract (Either ExportQueryM.ClientError PlutusScript) + -> Contract (Either ClientError PlutusScript) applyArgs = Contract.applyArgs -- | Same as `applyArgs` with arguments hushed. diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs index 155f5cd92f..ee239260ca 100644 --- a/src/Internal/Contract/QueryHandle.purs +++ b/src/Internal/Contract/QueryHandle.purs @@ -32,7 +32,6 @@ import Ctl.Internal.QueryM.EraSummaries (getEraSummaries) as QueryM import Ctl.Internal.QueryM.Kupo ( getDatumByHash , getScriptByHash - , getScriptsByHashes , getTxMetadata , getUtxoByOref , isTxConfirmed @@ -52,7 +51,6 @@ import Ctl.Internal.Types.Datum (DataHash, Datum) import Ctl.Internal.Types.Transaction (TransactionHash, TransactionInput) import Ctl.Internal.Types.TransactionMetadata (GeneralTransactionMetadata) import Data.Either (Either) -import Data.Map (Map) import Data.Maybe (Maybe(Just, Nothing), isJust) import Data.Newtype (unwrap, wrap) import Effect.Aff (Aff) @@ -67,10 +65,9 @@ type AffE (a :: Type) = Aff (Either ClientError a) type QueryHandle = { getDatumByHash :: DataHash -> AffE (Maybe Datum) , getScriptByHash :: ScriptHash -> AffE (Maybe ScriptRef) - , getScriptsByHashes :: Array ScriptHash -> AffE (Map ScriptHash ScriptRef) + , getTxMetadata :: TransactionHash -> AffE (Maybe GeneralTransactionMetadata) , getUtxoByOref :: TransactionInput -> AffE (Maybe TransactionOutput) , isTxConfirmed :: TransactionHash -> AffE Boolean - , getTxMetadata :: TransactionHash -> AffE (Maybe GeneralTransactionMetadata) , utxosAt :: Address -> AffE UtxoMap , getChainTip :: Aff Chain.Tip , getCurrentEpoch :: Aff Ogmios.CurrentEpoch @@ -92,7 +89,6 @@ queryHandleForCtlBackend :: ContractEnv -> CtlBackend -> QueryHandle queryHandleForCtlBackend contractEnv backend = { getDatumByHash: runQueryM' <<< Kupo.getDatumByHash , getScriptByHash: runQueryM' <<< Kupo.getScriptByHash - , getScriptsByHashes: runQueryM' <<< Kupo.getScriptsByHashes , getUtxoByOref: runQueryM' <<< Kupo.getUtxoByOref , isTxConfirmed: runQueryM' <<< map (map isJust) <<< Kupo.isTxConfirmed , getTxMetadata: runQueryM' <<< Kupo.getTxMetadata diff --git a/src/Internal/QueryM/Kupo.purs b/src/Internal/QueryM/Kupo.purs index 6ccc3b3d2d..3b1acc93fa 100644 --- a/src/Internal/QueryM/Kupo.purs +++ b/src/Internal/QueryM/Kupo.purs @@ -1,7 +1,6 @@ module Ctl.Internal.QueryM.Kupo ( getDatumByHash , getScriptByHash - , getScriptsByHashes , getTxMetadata , getUtxoByOref , isTxConfirmed @@ -142,13 +141,6 @@ getScriptByHash scriptHash = do kupoGetRequest endpoint <#> map unwrapKupoScriptRef <<< handleAffjaxResponse -getScriptsByHashes - :: Array ScriptHash -> QueryM (Either ClientError (Map ScriptHash ScriptRef)) -getScriptsByHashes = - runExceptT - <<< map (Map.catMaybes <<< Map.fromFoldable) - <<< parTraverse (\sh -> Tuple sh <$> ExceptT (getScriptByHash sh)) - -- FIXME: This can only confirm transactions with at least one output. -- https://github.com/Plutonomicon/cardano-transaction-lib/issues/1293 isTxConfirmed :: TransactionHash -> QueryM (Either ClientError (Maybe Slot)) From 845ee5b70a61f0608789db154f13d8bc6c7df86a Mon Sep 17 00:00:00 2001 From: Calum Sieppert Date: Wed, 14 Dec 2022 13:44:38 -0700 Subject: [PATCH 105/373] Use $ consistently and remove unnecessary variables --- src/Contract/Transaction.purs | 2 +- src/Internal/Deserialization/Error.purs | 2 +- src/Internal/Deserialization/Transaction.purs | 4 ++-- src/Internal/Deserialization/UnspentOutput.purs | 4 ++-- src/Internal/QueryM/Pools.purs | 11 +++-------- src/Internal/Serialization.purs | 12 ++++++------ src/Internal/Wallet/Cip30.purs | 3 +-- src/Internal/Wallet/Cip30Mock.purs | 10 +++++----- test/Data.purs | 2 +- test/Deserialization.purs | 12 ++++++------ test/Fixtures.purs | 4 ++-- test/Serialization.purs | 2 +- test/Wallet/Cip30/SignData.purs | 2 +- 13 files changed, 32 insertions(+), 38 deletions(-) diff --git a/src/Contract/Transaction.purs b/src/Contract/Transaction.purs index 2f9d730b38..b6fda2d033 100644 --- a/src/Contract/Transaction.purs +++ b/src/Contract/Transaction.purs @@ -311,7 +311,7 @@ submitE . BalancedSignedTransaction -> Contract r (Either (Array Aeson) TransactionHash) submitE tx = do - cslTx <- liftEffect $ Serialization.convertTransaction (unwrap tx) + cslTx <- liftEffect $ Serialization.convertTransaction $ unwrap tx let txHash = Hashing.transactionHash cslTx logDebug' $ "Pre-calculated tx hash: " <> show txHash let txCborBytes = Serialization.toBytes cslTx diff --git a/src/Internal/Deserialization/Error.purs b/src/Internal/Deserialization/Error.purs index 21f2709437..dd425ff4b5 100644 --- a/src/Internal/Deserialization/Error.purs +++ b/src/Internal/Deserialization/Error.purs @@ -87,4 +87,4 @@ fromBytesError = Left <<< inj _fromBytesError fromBytesErrorHelper :: forall (r :: Row Type) . ErrorFfiHelper (FromBytesError + r) -fromBytesErrorHelper = errorHelper (inj _fromBytesError) +fromBytesErrorHelper = errorHelper $ inj _fromBytesError diff --git a/src/Internal/Deserialization/Transaction.purs b/src/Internal/Deserialization/Transaction.purs index c62389be79..41aa48968e 100644 --- a/src/Internal/Deserialization/Transaction.purs +++ b/src/Internal/Deserialization/Transaction.purs @@ -348,8 +348,8 @@ convertCertificate = _convertCert certConvHelper , genesisKeyDelegation: \genesisHash genesisDelegateHash vrfKeyhash -> do pure $ T.GenesisKeyDelegation { genesisHash: T.GenesisHash $ unwrap $ toBytes genesisHash - , genesisDelegateHash: T.GenesisDelegateHash - (unwrap $ toBytes genesisDelegateHash) + , genesisDelegateHash: T.GenesisDelegateHash $ unwrap + $ toBytes genesisDelegateHash , vrfKeyhash: VRFKeyHash vrfKeyhash } , moveInstantaneousRewardsToOtherPotCert: \pot amount -> do diff --git a/src/Internal/Deserialization/UnspentOutput.purs b/src/Internal/Deserialization/UnspentOutput.purs index b2e820fc5e..c9dd3c204c 100644 --- a/src/Internal/Deserialization/UnspentOutput.purs +++ b/src/Internal/Deserialization/UnspentOutput.purs @@ -79,8 +79,8 @@ convertInput :: TransactionInput -> Maybe T.TransactionInput convertInput input = do index <- UInt.fromInt' $ getTransactionIndex input pure $ T.TransactionInput - { transactionId: T.TransactionHash $ unwrap $ toBytes - (getTransactionHash input) + { transactionId: T.TransactionHash $ unwrap $ toBytes $ + getTransactionHash input , index } diff --git a/src/Internal/QueryM/Pools.purs b/src/Internal/QueryM/Pools.purs index 69519f261e..5fbad728f9 100644 --- a/src/Internal/QueryM/Pools.purs +++ b/src/Internal/QueryM/Pools.purs @@ -80,11 +80,8 @@ getValidatorHashDelegationsAndRewards skh = do stringRep :: String stringRep = scriptHashToBech32Unsafe "script" $ unwrap skh - sh :: ScriptHash - sh = unwrap skh - byteHex :: String - byteHex = byteArrayToHex $ unwrap $ toBytes sh + byteHex = byteArrayToHex $ unwrap $ toBytes (unwrap skh :: ScriptHash) -- TODO: batched variant getPubKeyHashDelegationsAndRewards @@ -99,8 +96,6 @@ getPubKeyHashDelegationsAndRewards pkh = do stringRep = ed25519KeyHashToBech32Unsafe "stake_vkh" $ unwrap $ unwrap pkh - ed :: Ed25519KeyHash - ed = unwrap $ unwrap pkh - byteHex :: String - byteHex = byteArrayToHex $ unwrap $ toBytes ed + byteHex = byteArrayToHex $ unwrap $ toBytes + (unwrap $ unwrap pkh :: Ed25519KeyHash) diff --git a/src/Internal/Serialization.purs b/src/Internal/Serialization.purs index e536817090..cf8daac723 100644 --- a/src/Internal/Serialization.purs +++ b/src/Internal/Serialization.purs @@ -537,7 +537,7 @@ convertUpdate :: T.Update -> Effect Update convertUpdate { proposedProtocolParameterUpdates, epoch } = do ppUpdates <- convertProposedProtocolParameterUpdates proposedProtocolParameterUpdates - newUpdate ppUpdates (UInt.toInt $ unwrap epoch) + newUpdate ppUpdates $ UInt.toInt $ unwrap epoch convertProposedProtocolParameterUpdates :: T.ProposedProtocolParameterUpdates @@ -547,8 +547,8 @@ convertProposedProtocolParameterUpdates ppus = for (Map.toUnfoldable $ unwrap ppus) \(genesisHash /\ ppu) -> do Tuple <$> - ( fromJustEff "Failed to convert genesis hash" $ fromBytes - (wrap $ unwrap genesisHash) + ( fromJustEff "Failed to convert genesis hash" $ fromBytes $ wrap + $ unwrap genesisHash ) <*> convertProtocolParamUpdate ppu @@ -723,8 +723,8 @@ convertMoveInstantaneousReward (T.ToStakeCreds { pot, amounts }) = convertPoolMetadata :: T.PoolMetadata -> Effect PoolMetadata convertPoolMetadata (T.PoolMetadata { url: T.URL url, hash: T.PoolMetadataHash hash }) = - ( (fromJustEff "Failed to convert script data hash" <<< fromBytes <<< wrap) - >=> (newPoolMetadata url) + ( fromJustEff "Failed to convert script data hash" <<< fromBytes <<< wrap + >=> newPoolMetadata url ) hash convertRelays :: Array T.Relay -> Effect Relays @@ -779,7 +779,7 @@ convertTxInputs fInputs = do convertTxInput :: T.TransactionInput -> Effect TransactionInput convertTxInput (T.TransactionInput { transactionId, index }) = do - tx_hash <- fromBytesEffect (wrap $ unwrap transactionId) + tx_hash <- fromBytesEffect $ wrap $ unwrap transactionId newTransactionInput tx_hash index convertTxOutputs :: Array T.TransactionOutput -> Effect TransactionOutputs diff --git a/src/Internal/Wallet/Cip30.purs b/src/Internal/Wallet/Cip30.purs index 605532fd5e..a36bff1eed 100644 --- a/src/Internal/Wallet/Cip30.purs +++ b/src/Internal/Wallet/Cip30.purs @@ -143,8 +143,7 @@ getWalletAddresses conn = Promise.toAffE (_getAddresses conn) <#> traverse hexStringToAddress hexStringToAddress :: String -> Maybe Address -hexStringToAddress = - ((fromBytes <<< rawBytesAsCborBytes) <=< hexToRawBytes) +hexStringToAddress = fromBytes <<< rawBytesAsCborBytes <=< hexToRawBytes -- | Get collateral using CIP-30 `getCollateral` method. -- | Throws on `Promise` rejection by wallet, returns `Nothing` if no collateral diff --git a/src/Internal/Wallet/Cip30Mock.purs b/src/Internal/Wallet/Cip30Mock.purs index 7717ee252d..ff982f9276 100644 --- a/src/Internal/Wallet/Cip30Mock.purs +++ b/src/Internal/Wallet/Cip30Mock.purs @@ -178,14 +178,14 @@ mkCip30Mock pKey mSKey = do pure $ byteArrayToHex $ unwrap $ toBytes value , getUsedAddresses: fromAff do (unwrap keyWallet).address config.networkId <#> \address -> - [ (byteArrayToHex <<< unwrap <<< toBytes) address ] + [ byteArrayToHex $ unwrap $ toBytes address ] , getUnusedAddresses: fromAff $ pure [] , getChangeAddress: fromAff do (unwrap keyWallet).address config.networkId <#> - (byteArrayToHex <<< unwrap <<< toBytes) + byteArrayToHex <<< unwrap <<< toBytes , getRewardAddresses: fromAff do (unwrap keyWallet).address config.networkId <#> \address -> - [ (byteArrayToHex <<< unwrap <<< toBytes) address ] + [ byteArrayToHex $ unwrap $ toBytes address ] , signTx: \str -> unsafePerformEffect $ fromAff do txBytes <- liftMaybe (error "Unable to convert CBOR") $ hexToByteArray str @@ -197,8 +197,8 @@ mkCip30Mock pKey mSKey = do cslWitnessSet <- liftEffect $ convertWitnessSet witness pure $ byteArrayToHex $ unwrap $ toBytes cslWitnessSet , signData: mkFn2 \_addr msg -> unsafePerformEffect $ fromAff do - msgBytes <- liftMaybe (error "Unable to convert CBOR") - (hexToByteArray msg) + msgBytes <- liftMaybe (error "Unable to convert CBOR") $ + hexToByteArray msg { key, signature } <- (unwrap keyWallet).signData config.networkId (wrap msgBytes) pure { key: cborBytesToHex key, signature: cborBytesToHex signature } diff --git a/test/Data.purs b/test/Data.purs index 7586fb5fc0..08c45a1327 100644 --- a/test/Data.purs +++ b/test/Data.purs @@ -567,7 +567,7 @@ testBinaryFixture value binaryFixture = do test ("Deserialization: " <> show value) do fromBytesFromData binaryFixture `shouldEqual` Just value test ("Serialization: " <> show value) do - map toBytes (PDS.convertPlutusData (toData value)) + map toBytes (PDS.convertPlutusData $ toData value) `shouldEqual` Just (wrap $ hexToByteArrayUnsafe binaryFixture) diff --git a/test/Deserialization.purs b/test/Deserialization.purs index 29f4a46d90..8cd1326359 100644 --- a/test/Deserialization.purs +++ b/test/Deserialization.purs @@ -148,7 +148,7 @@ suite = do output `shouldEqual` txOutputFixture1 test "fixture #1" do res <- errMaybe "Failed deserialization 4" do - (fromBytes $ wrap utxoFixture1) >>= + fromBytes (wrap utxoFixture1) >>= convertUnspentOutput res `shouldEqual` utxoFixture1' group "Transaction Roundtrips" do @@ -161,7 +161,7 @@ suite = do group "WitnessSet - deserialization" do group "fixture #1" do res <- errMaybe "Failed deserialization 5" do - (fromBytes $ wrap witnessSetFixture1) >>= convertWitnessSet + fromBytes (wrap witnessSetFixture1) >>= convertWitnessSet test "has vkeys" do (unwrap res).vkeys `shouldSatisfy` isJust test "has plutusData" do @@ -176,15 +176,15 @@ suite = do (unwrap res).nativeScripts `shouldSatisfy` isNothing test "fixture #2" do res <- errMaybe "Failed deserialization 6" do - (fromBytes $ wrap witnessSetFixture2) >>= convertWitnessSet + fromBytes (wrap witnessSetFixture2) >>= convertWitnessSet res `shouldEqual` witnessSetFixture2Value test "fixture #3" do res <- errMaybe "Failed deserialization 7" do - (fromBytes $ wrap witnessSetFixture3) >>= convertWitnessSet + fromBytes (wrap witnessSetFixture3) >>= convertWitnessSet res `shouldEqual` witnessSetFixture3Value group "fixture #4" do res <- errMaybe "Failed deserialization 8" $ - (fromBytes $ wrap witnessSetFixture4) >>= convertWitnessSet + fromBytes (wrap witnessSetFixture4) >>= convertWitnessSet test "has nativeScripts" do (unwrap res).nativeScripts `shouldSatisfy` isJust group "NativeScript - deserializaton is inverse to serialization" do @@ -222,7 +222,7 @@ suite = do -> m Unit witnessSetRoundTrip fixture = do ws0 <- errMaybe "Failed deserialization" $ - (fromBytes $ wrap fixture) >>= convertWitnessSet + fromBytes (wrap fixture) >>= convertWitnessSet ws1 <- liftEffect $ SW.convertWitnessSet ws0 ws2 <- errMaybe "Failed deserialization" $ convertWitnessSet ws1 ws0 `shouldEqual` ws2 -- value representation diff --git a/test/Fixtures.purs b/test/Fixtures.purs index b558620a77..270bc93d5d 100644 --- a/test/Fixtures.purs +++ b/test/Fixtures.purs @@ -569,7 +569,7 @@ txFixture4 = , PoolRegistration { operator: wrap ed25519KeyHash1 , vrfKeyhash: unsafePartial $ VRFKeyHash $ fromJust $ - (fromBytes <<< wrap) =<< + fromBytes <<< wrap =<< hexToByteArray "fbf6d41985670b9041c5bf362b5262cf34add5d265975de176d613ca05f37096" , pledge: bigNumOne @@ -611,7 +611,7 @@ txFixture4 = $ hexToByteArrayUnsafe "5d677265fa5bb21ce6d8c7502aca70b9316d10e958611f3c6b758f65" , vrfKeyhash: unsafePartial $ VRFKeyHash $ fromJust $ - (fromBytes <<< wrap) =<< + fromBytes <<< wrap =<< hexToByteArray "fbf6d41985670b9041c5bf362b5262cf34add5d265975de176d613ca05f37096" } diff --git a/test/Serialization.purs b/test/Serialization.purs index 91dd1cc6d7..d45df25d1a 100644 --- a/test/Serialization.purs +++ b/test/Serialization.purs @@ -108,7 +108,7 @@ suite = do "PlutusData #6 - Integer 0 (regression to https://github.com/Plutonomicon/cardano-transaction-lib/issues/488 ?)" $ do let - datum = PD.Integer (BigInt.fromInt 0) + datum = PD.Integer $ BigInt.fromInt 0 datum' <- errMaybe "Cannot convertPlutusData" $ convertPlutusData datum let bytes = toBytes datum' diff --git a/test/Wallet/Cip30/SignData.purs b/test/Wallet/Cip30/SignData.purs index cc2fd0c03c..4d05976808 100644 --- a/test/Wallet/Cip30/SignData.purs +++ b/test/Wallet/Cip30/SignData.purs @@ -128,7 +128,7 @@ checkCip30SignDataResponse address { key, signature } = do checkVerification coseSign1 coseKey = do publicKey <- errMaybe "COSE_Key's x (-2) header must be set to public key bytes" - (getCoseKeyHeaderX coseKey >>= (fromBytes <<< wrap <<< unwrap)) + $ getCoseKeyHeaderX coseKey >>= fromBytes <<< wrap <<< unwrap sigStructBytes <- getSignedData coseSign1 assertTrue "Signature verification failed" =<< verifySignature coseSign1 publicKey sigStructBytes From 6f1d9a1cd68033d1a61c1b5408c8d3394b83e10a Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Wed, 14 Dec 2022 21:20:38 +0000 Subject: [PATCH 106/373] Don't export BFP constr --- src/Contract/Config.purs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Contract/Config.purs b/src/Contract/Config.purs index 2787232109..70c2060fc8 100644 --- a/src/Contract/Config.purs +++ b/src/Contract/Config.purs @@ -31,10 +31,10 @@ import Ctl.Internal.Contract.Hooks (Hooks, emptyHooks) as X import Ctl.Internal.Contract.Hooks (emptyHooks) import Ctl.Internal.Contract.Monad (ContractParams) import Ctl.Internal.Contract.QueryBackend - ( QueryBackendParams(CtlBackendParams, BlockfrostBackendParams) - -- TODO Export once the following is stable - -- https://github.com/Plutonomicon/cardano-transaction-lib/issues/1118 - -- , mkBlockfrostBackendParams + ( -- TODO Export Blockfrost once the following is stable + -- https://github.com/Plutonomicon/cardano-transaction-lib/issues/1118 + -- , mkBlockfrostBackendParams + QueryBackendParams(CtlBackendParams {-, BlockfrostBackendParams-} ) , mkCtlBackendParams ) import Ctl.Internal.Deserialization.Keys (privateKeyFromBytes) From 40b7cbec3efc1ac0128d31b66594d68f8a58f062 Mon Sep 17 00:00:00 2001 From: Calum Sieppert Date: Wed, 14 Dec 2022 14:34:38 -0700 Subject: [PATCH 107/373] Restore `scriptHashToBytes` and `ed25519KeyHashToBytes` In correspondance with https://github.com/Plutonomicon/cardano-transaction-lib/pull/1285#discussion_r1041753386 --- src/Internal/Cardano/Types/Value.purs | 12 ++++--- .../Deserialization/UnspentOutput.purs | 4 +-- src/Internal/Plutus/Types/CurrencySymbol.purs | 12 ++++--- src/Internal/QueryM/Kupo.purs | 6 ++-- src/Internal/QueryM/Pools.purs | 14 ++++---- src/Internal/Serialization/Hash.purs | 34 ++++++++++++------- test/Serialization/Hash.purs | 15 ++------ 7 files changed, 52 insertions(+), 45 deletions(-) diff --git a/src/Internal/Cardano/Types/Value.purs b/src/Internal/Cardano/Types/Value.purs index 59abe88837..08faf15c22 100644 --- a/src/Internal/Cardano/Types/Value.purs +++ b/src/Internal/Cardano/Types/Value.purs @@ -68,8 +68,11 @@ import Ctl.Internal.FromData (class FromData) import Ctl.Internal.Helpers (encodeMap, showWithParens) import Ctl.Internal.Metadata.FromMetadata (class FromMetadata) import Ctl.Internal.Metadata.ToMetadata (class ToMetadata) -import Ctl.Internal.Serialization.Hash (ScriptHash, scriptHashFromBytes) -import Ctl.Internal.Serialization.ToBytes (toBytes) +import Ctl.Internal.Serialization.Hash + ( ScriptHash + , scriptHashFromBytes + , scriptHashToBytes + ) import Ctl.Internal.ToData (class ToData) import Ctl.Internal.Types.ByteArray ( ByteArray @@ -778,7 +781,7 @@ currencyScriptHash (CurrencySymbol byteArray) = unsafePartial fromJust $ scriptHashFromBytes byteArray scriptHashAsCurrencySymbol :: ScriptHash -> CurrencySymbol -scriptHashAsCurrencySymbol = CurrencySymbol <<< unwrap <<< toBytes +scriptHashAsCurrencySymbol = CurrencySymbol <<< unwrap <<< scriptHashToBytes -- | The minting policy hash of a currency symbol currencyMPSHash :: CurrencySymbol -> MintingPolicyHash @@ -789,7 +792,8 @@ currencyMPSHash = MintingPolicyHash <<< currencyScriptHash -- Plutus doesn't use Maybe here. -- | The currency symbol of a monetary policy hash mpsSymbol :: MintingPolicyHash -> Maybe CurrencySymbol -mpsSymbol (MintingPolicyHash h) = mkCurrencySymbol $ unwrap $ toBytes h +mpsSymbol (MintingPolicyHash h) = mkCurrencySymbol $ unwrap $ scriptHashToBytes + h -- Like `mapEither` that works with 'These'. mapThese diff --git a/src/Internal/Deserialization/UnspentOutput.purs b/src/Internal/Deserialization/UnspentOutput.purs index c9dd3c204c..fb1d2c7335 100644 --- a/src/Internal/Deserialization/UnspentOutput.purs +++ b/src/Internal/Deserialization/UnspentOutput.purs @@ -31,7 +31,7 @@ import Ctl.Internal.Deserialization.WitnessSet (convertPlutusScript) import Ctl.Internal.FfiHelpers (MaybeFfiHelper, maybeFfiHelper) import Ctl.Internal.Serialization (toBytes) import Ctl.Internal.Serialization.Address (Address) -import Ctl.Internal.Serialization.Hash (ScriptHash) +import Ctl.Internal.Serialization.Hash (ScriptHash, scriptHashToBytes) import Ctl.Internal.Serialization.Types ( AssetName , Assets @@ -126,7 +126,7 @@ convertValue value = do ( traverse ( bitraverse -- scripthash to currency symbol - (toBytes >>> unwrap >>> T.mkCurrencySymbol) + (scriptHashToBytes >>> unwrap >>> T.mkCurrencySymbol) -- nested assetname to tokenname (traverse (ltraverse (T.assetNameName >>> T.mkTokenName))) ) diff --git a/src/Internal/Plutus/Types/CurrencySymbol.purs b/src/Internal/Plutus/Types/CurrencySymbol.purs index ba17b0a2a5..d3b2334f7e 100644 --- a/src/Internal/Plutus/Types/CurrencySymbol.purs +++ b/src/Internal/Plutus/Types/CurrencySymbol.purs @@ -23,8 +23,11 @@ import Control.Monad.Gen as Gen import Ctl.Internal.FromData (class FromData) import Ctl.Internal.Metadata.FromMetadata (class FromMetadata) import Ctl.Internal.Metadata.ToMetadata (class ToMetadata) -import Ctl.Internal.Serialization.Hash (ScriptHash, scriptHashFromBytes) -import Ctl.Internal.Serialization.ToBytes (toBytes) +import Ctl.Internal.Serialization.Hash + ( ScriptHash + , scriptHashFromBytes + , scriptHashToBytes + ) import Ctl.Internal.ToData (class ToData) import Ctl.Internal.Types.ByteArray (ByteArray, hexToByteArrayUnsafe) import Ctl.Internal.Types.Scripts (MintingPolicyHash(MintingPolicyHash)) @@ -74,7 +77,7 @@ adaSymbol :: CurrencySymbol adaSymbol = CurrencySymbol mempty scriptHashAsCurrencySymbol :: ScriptHash -> CurrencySymbol -scriptHashAsCurrencySymbol = CurrencySymbol <<< unwrap <<< toBytes +scriptHashAsCurrencySymbol = CurrencySymbol <<< unwrap <<< scriptHashToBytes -- | The minting policy hash of a currency symbol. currencyMPSHash :: CurrencySymbol -> MintingPolicyHash @@ -82,7 +85,8 @@ currencyMPSHash = MintingPolicyHash <<< currencyScriptHash -- | The currency symbol of a monetary policy hash. mpsSymbol :: MintingPolicyHash -> Maybe CurrencySymbol -mpsSymbol (MintingPolicyHash h) = mkCurrencySymbol $ unwrap $ toBytes h +mpsSymbol (MintingPolicyHash h) = mkCurrencySymbol $ unwrap $ scriptHashToBytes + h getCurrencySymbol :: CurrencySymbol -> ByteArray getCurrencySymbol (CurrencySymbol curSymbol) = curSymbol diff --git a/src/Internal/QueryM/Kupo.purs b/src/Internal/QueryM/Kupo.purs index 4f9dbb9c17..d6916cef6e 100644 --- a/src/Internal/QueryM/Kupo.purs +++ b/src/Internal/QueryM/Kupo.purs @@ -49,13 +49,12 @@ import Ctl.Internal.QueryM , handleAffjaxResponse ) import Ctl.Internal.QueryM.ServerConfig (mkHttpUrl) -import Ctl.Internal.Serialization (toBytes) import Ctl.Internal.Serialization.Address ( Address , addressBech32 , addressFromBech32 ) -import Ctl.Internal.Serialization.Hash (ScriptHash) +import Ctl.Internal.Serialization.Hash (ScriptHash, scriptHashToBytes) import Ctl.Internal.Types.ByteArray (ByteArray, byteArrayToHex, hexToByteArray) import Ctl.Internal.Types.CborBytes (hexToCborBytes) import Ctl.Internal.Types.Datum (DataHash(DataHash), Datum) @@ -125,8 +124,7 @@ getDatumByHash (DataHash dataHashBytes) = do getScriptByHash :: ScriptHash -> QueryM (Either ClientError (Maybe ScriptRef)) getScriptByHash scriptHash = do let - endpoint = "/scripts/" <> rawBytesToHex - (wrap $ unwrap $ toBytes scriptHash) + endpoint = "/scripts/" <> rawBytesToHex (scriptHashToBytes scriptHash) kupoGetRequest endpoint <#> map unwrapKupoScriptRef <<< handleAffjaxResponse diff --git a/src/Internal/QueryM/Pools.purs b/src/Internal/QueryM/Pools.purs index 5fbad728f9..a6c66822f2 100644 --- a/src/Internal/QueryM/Pools.purs +++ b/src/Internal/QueryM/Pools.purs @@ -8,7 +8,6 @@ module Ctl.Internal.QueryM.Pools import Prelude -import Contract.Scripts (ScriptHash) import Ctl.Internal.Cardano.Types.Transaction ( PoolPubKeyHash , PoolRegistrationParams @@ -22,12 +21,12 @@ import Ctl.Internal.QueryM.Ogmios ) import Ctl.Internal.QueryM.Ogmios as Ogmios import Ctl.Internal.Serialization.Hash - ( Ed25519KeyHash - , ed25519KeyHashToBech32 + ( ed25519KeyHashToBech32 , ed25519KeyHashToBech32Unsafe + , ed25519KeyHashToBytes , scriptHashToBech32Unsafe + , scriptHashToBytes ) -import Ctl.Internal.Serialization.ToBytes (toBytes) import Ctl.Internal.Types.ByteArray (byteArrayToHex) import Ctl.Internal.Types.PubKeyHash (StakePubKeyHash) import Ctl.Internal.Types.Scripts (StakeValidatorHash) @@ -81,7 +80,7 @@ getValidatorHashDelegationsAndRewards skh = do stringRep = scriptHashToBech32Unsafe "script" $ unwrap skh byteHex :: String - byteHex = byteArrayToHex $ unwrap $ toBytes (unwrap skh :: ScriptHash) + byteHex = byteArrayToHex $ unwrap $ scriptHashToBytes $ unwrap skh -- TODO: batched variant getPubKeyHashDelegationsAndRewards @@ -97,5 +96,6 @@ getPubKeyHashDelegationsAndRewards pkh = do ed25519KeyHashToBech32Unsafe "stake_vkh" $ unwrap $ unwrap pkh byteHex :: String - byteHex = byteArrayToHex $ unwrap $ toBytes - (unwrap $ unwrap pkh :: Ed25519KeyHash) + byteHex = byteArrayToHex $ unwrap $ ed25519KeyHashToBytes + $ unwrap + $ unwrap pkh diff --git a/src/Internal/Serialization/Hash.purs b/src/Internal/Serialization/Hash.purs index 6938a80c4c..b9d5e83d01 100644 --- a/src/Internal/Serialization/Hash.purs +++ b/src/Internal/Serialization/Hash.purs @@ -6,11 +6,13 @@ module Ctl.Internal.Serialization.Hash , ed25519KeyHashFromBytes , ed25519KeyHashToBech32 , ed25519KeyHashToBech32Unsafe + , ed25519KeyHashToBytes , nativeScriptHash , scriptHashFromBech32 , scriptHashFromBytes , scriptHashToBech32 , scriptHashToBech32Unsafe + , scriptHashToBytes ) where import Prelude @@ -31,10 +33,12 @@ import Ctl.Internal.ToData (class ToData, toData) import Ctl.Internal.Types.Aliases (Bech32String) import Ctl.Internal.Types.ByteArray (ByteArray, byteArrayToHex, hexToByteArray) import Ctl.Internal.Types.PlutusData (PlutusData(Bytes)) +import Ctl.Internal.Types.RawBytes (RawBytes, rawBytesToHex) import Ctl.Internal.Types.TransactionMetadata (TransactionMetadatum(Bytes)) as Metadata import Data.Either (Either(Left, Right), note) import Data.Function (on) import Data.Maybe (Maybe(Nothing, Just), maybe) +import Data.Newtype (unwrap, wrap) -- We can't use ToBytes class here, because of cyclic dependencies -- | Encodes the hash to `CborBytes` @@ -79,24 +83,24 @@ foreign import _scriptHashFromBech32Impl foreign import data Ed25519KeyHash :: Type instance Eq Ed25519KeyHash where - eq = eq `on` hashToBytes + eq = eq `on` ed25519KeyHashToBytes instance Ord Ed25519KeyHash where - compare = compare `on` hashToBytes + compare = compare `on` ed25519KeyHashToBytes instance Show Ed25519KeyHash where - show edkh = "(Ed25519KeyHash " <> byteArrayToHex (hashToBytes edkh) + show edkh = "(Ed25519KeyHash " <> rawBytesToHex (ed25519KeyHashToBytes edkh) <> ")" instance ToData Ed25519KeyHash where - toData = toData <<< hashToBytes + toData = toData <<< unwrap <<< ed25519KeyHashToBytes instance FromData Ed25519KeyHash where fromData (Bytes kh) = ed25519KeyHashFromBytes kh fromData _ = Nothing instance ToMetadata Ed25519KeyHash where - toMetadata = toMetadata <<< hashToBytes + toMetadata = toMetadata <<< ed25519KeyHashToBytes instance FromMetadata Ed25519KeyHash where fromMetadata (Metadata.Bytes kh) = ed25519KeyHashFromBytes kh @@ -113,7 +117,7 @@ instance DecodeAeson Ed25519KeyHash where ) instance EncodeAeson Ed25519KeyHash where - encodeAeson' = encodeAeson' <<< byteArrayToHex <<< hashToBytes + encodeAeson' = encodeAeson' <<< rawBytesToHex <<< ed25519KeyHashToBytes -- | Convert ed25519KeyHash to Bech32 representation with given prefix. -- | Will crash if prefix is invalid (length, mixed-case, etc) @@ -121,6 +125,9 @@ instance EncodeAeson Ed25519KeyHash where ed25519KeyHashToBech32Unsafe ∷ String → Ed25519KeyHash → Bech32String ed25519KeyHashToBech32Unsafe = hashToBech32Unsafe +ed25519KeyHashToBytes :: Ed25519KeyHash -> RawBytes +ed25519KeyHashToBytes = wrap <<< hashToBytes + scriptHashToBech32Unsafe ∷ String → ScriptHash → Bech32String scriptHashToBech32Unsafe = hashToBech32Unsafe @@ -140,23 +147,23 @@ ed25519KeyHashToBech32 = _ed25519KeyHashToBech32Impl maybeFfiHelper foreign import data ScriptHash :: Type instance Eq ScriptHash where - eq = eq `on` hashToBytes + eq = eq `on` scriptHashToBytes instance Ord ScriptHash where - compare = compare `on` hashToBytes + compare = compare `on` scriptHashToBytes instance Show ScriptHash where - show edkh = "(ScriptHash " <> byteArrayToHex (hashToBytes edkh) <> ")" + show edkh = "(ScriptHash " <> rawBytesToHex (scriptHashToBytes edkh) <> ")" instance ToData ScriptHash where - toData = toData <<< hashToBytes + toData = toData <<< unwrap <<< scriptHashToBytes instance FromData ScriptHash where fromData (Bytes bytes) = scriptHashFromBytes bytes fromData _ = Nothing instance ToMetadata ScriptHash where - toMetadata = toMetadata <<< hashToBytes + toMetadata = toMetadata <<< scriptHashToBytes instance FromMetadata ScriptHash where fromMetadata (Metadata.Bytes bytes) = scriptHashFromBytes bytes @@ -169,12 +176,15 @@ instance DecodeAeson ScriptHash where caseAesonString Nothing (Just <=< scriptHashFromBytes <=< hexToByteArray) instance EncodeAeson ScriptHash where - encodeAeson' sh = encodeAeson' $ hashToBytes sh + encodeAeson' sh = encodeAeson' $ scriptHashToBytes sh _ed25519KeyHashToBech32Impl ∷ MaybeFfiHelper → String → Ed25519KeyHash → Maybe Bech32String _ed25519KeyHashToBech32Impl = hashToBech32Impl +scriptHashToBytes :: ScriptHash -> RawBytes +scriptHashToBytes = wrap <<< hashToBytes + _scriptHashToBech32Impl ∷ MaybeFfiHelper → String → ScriptHash → Maybe Bech32String _scriptHashToBech32Impl = hashToBech32Impl diff --git a/test/Serialization/Hash.purs b/test/Serialization/Hash.purs index bef8dc102d..256a47b441 100644 --- a/test/Serialization/Hash.purs +++ b/test/Serialization/Hash.purs @@ -1,16 +1,7 @@ module Test.Ctl.Serialization.Hash (suite) where import Control.Bind (bind, discard) -import Ctl.Internal.Serialization.Hash - ( ed25519KeyHashFromBech32 - , ed25519KeyHashFromBytes - , ed25519KeyHashToBech32 - , ed25519KeyHashToBech32Unsafe - , scriptHashFromBech32 - , scriptHashFromBytes - , scriptHashToBech32 - , scriptHashToBech32Unsafe - ) +import Ctl.Internal.Serialization.Hash (ed25519KeyHashFromBech32, ed25519KeyHashFromBytes, ed25519KeyHashToBech32, ed25519KeyHashToBech32Unsafe, ed25519KeyHashToBytes, scriptHashFromBech32, scriptHashFromBytes, scriptHashToBech32, scriptHashToBech32Unsafe, scriptHashToBytes) import Ctl.Internal.Serialization.ToBytes (toBytes) import Ctl.Internal.Test.TestPlanM (TestPlanM) import Ctl.Internal.Types.Aliases (Bech32String) @@ -43,7 +34,7 @@ suite = test "Serialization.Hash" do let pkhB32 = ed25519KeyHashToBech32Unsafe "addr_vkh" pkh mPkhB32 = ed25519KeyHashToBech32 "addr_vkh" pkh - pkhBts = toBytes pkh + pkhBts = ed25519KeyHashToBytes pkh pkh2 = ed25519KeyHashFromBytes $ unwrap pkhBts assertTrue @@ -72,7 +63,7 @@ suite = test "Serialization.Hash" do let scrhB32 = scriptHashToBech32Unsafe "stake_vkh" scrh mScrhB32 = scriptHashToBech32 "stake_vkh" scrh - scrhBts = toBytes scrh + scrhBts = scriptHashToBytes scrh scrhFromBytes = scriptHashFromBytes $ unwrap scrhBts scrhFromBech = scriptHashFromBech32 scrhB32 From 9629a49ca6b56d474819a763591557517f7f7601 Mon Sep 17 00:00:00 2001 From: Gregory Gerasev Date: Mon, 12 Dec 2022 09:27:52 +0400 Subject: [PATCH 108/373] Tests for runRoundRobinM --- src/Internal/BalanceTx/CoinSelection.purs | 1 + test/CoinSelection/RoundRobin.purs | 216 ++++++++++++++++++++++ 2 files changed, 217 insertions(+) create mode 100644 test/CoinSelection/RoundRobin.purs diff --git a/src/Internal/BalanceTx/CoinSelection.purs b/src/Internal/BalanceTx/CoinSelection.purs index d377b1d28c..8cdc9e1fd6 100644 --- a/src/Internal/BalanceTx/CoinSelection.purs +++ b/src/Internal/BalanceTx/CoinSelection.purs @@ -10,6 +10,7 @@ module Ctl.Internal.BalanceTx.CoinSelection , SelectionStrategy(SelectionStrategyMinimal, SelectionStrategyOptimal) , _leftoverUtxos , performMultiAssetSelection + , runRoundRobinM -- Exported for tests , selectedInputs ) where diff --git a/test/CoinSelection/RoundRobin.purs b/test/CoinSelection/RoundRobin.purs new file mode 100644 index 0000000000..1cf597bad5 --- /dev/null +++ b/test/CoinSelection/RoundRobin.purs @@ -0,0 +1,216 @@ +module Test.Ctl.CoinSelection.RoundRobin where + +import Prelude + +import Ctl.Internal.BalanceTx.CoinSelection (runRoundRobinM) +import Ctl.Internal.Test.TestPlanM (TestPlanM) +import Ctl.Internal.Types.TokenName (TokenName) +import Data.Foldable (all, foldl, sum) +import Data.Function (on) +import Data.Generic.Rep (class Generic) +import Data.Identity (Identity(Identity)) +import Data.List + ( List + , fromFoldable + , length + , singleton + , sort + , sortBy + , tail + , zip + , (:) + ) +import Data.Map (Map) +import Data.Map as Map +import Data.Map.Gen (genMap) +import Data.Maybe (Maybe(Just, Nothing), fromMaybe, maybe) +import Data.Newtype (class Newtype, unwrap) +import Data.NonEmpty (NonEmpty) +import Data.Ordering (invert) +import Data.Set as Set +import Data.Show.Generic (genericShow) +import Data.Tuple (snd, swap, uncurry) +import Data.Tuple.Nested (type (/\), (/\)) +import Data.Unfoldable (replicateA) +import Effect.Aff (Aff) +import Mote (group, test) +import Test.QuickCheck (Result, (), (===)) +import Test.QuickCheck.Arbitrary (class Arbitrary, arbitrary) +import Test.QuickCheck.Gen (Gen, chooseInt) +import Test.Spec.QuickCheck (quickCheck) + +suite :: TestPlanM (Aff Unit) Unit +suite = do + group "Grouping and ungrouping" do + test "groupByKey_ungroupByKey" $ + quickCheck + \(x :: List (Int /\ Int)) -> on (===) sort + x + (ungroupByKey $ groupByKey x) + test "ungroupByKey_groupByKey" $ + quickCheck + -- There is no Arbitrary for Map + \(wm :: ArbitraryMap Int (NonEmpty List Int)) -> + let + m = map fromFoldable $ unwrap wm + in + on (===) (map sort) + m + (groupByKey $ ungroupByKey m) + group "RoundRobin" do + test "identity" $ quickCheck prop_runRoundRobin_identity + test "iterationCount" $ quickCheck prop_runRoundRobin_iterationCount + test "iterationOrder" $ + quickCheck prop_runRoundRobin_iterationOrder + test "generationCount" $ + quickCheck prop_runRoundRobin_iterationOrder + test "generationOrder" $ + quickCheck prop_runRoundRobin_generationOrder + +-- Tests + +prop_runRoundRobin_identity :: SimpleMockRoundRobinState -> Array Unit -> Result +prop_runRoundRobin_identity state processors = + runRoundRobin state ((const Nothing) <$ processors) === state + +prop_runRoundRobin_iterationCount :: SimpleMockRoundRobinState -> Result +prop_runRoundRobin_iterationCount initialState = (===) + ( length $ + (unwrap $ runMockRoundRobin initialState).accumulatedEntries + ) + (sum (unwrap initialState).processorLifetimes) + +prop_runRoundRobin_iterationOrder :: SimpleMockRoundRobinState -> Result +prop_runRoundRobin_iterationOrder initialState = + sortDescending entries === entries + where + entries = swap <$> + (unwrap $ runMockRoundRobin initialState).accumulatedEntries + sortDescending = sortBy \x y -> invert $ compare x y + +prop_runRoundRobin_generationCount :: SimpleMockRoundRobinState -> Result +prop_runRoundRobin_generationCount initialState = + Map.filter (_ > 0) (unwrap initialState).processorLifetimes + === generationCounts + where + finalState = runMockRoundRobin initialState + + generationCounts :: Map TokenName Int + generationCounts = (unwrap finalState).accumulatedEntries + # groupByKey + # map length + +prop_runRoundRobin_generationOrder :: SimpleMockRoundRobinState -> Result +prop_runRoundRobin_generationOrder initialState = + result "initialState: " <> show initialState + where + finalState = runMockRoundRobin initialState + + generations :: Map Int (Set.Set TokenName) + generations = (unwrap finalState).accumulatedEntries + # map swap + # groupByKey + # map Set.fromFoldable + result = all (uncurry (flip Set.subset)) + $ consecutivePairs + $ snd <$> Map.toUnfoldable generations + +-- Utilites for tests + +runRoundRobin :: forall (s :: Type). s -> Array (s -> Maybe s) -> s +runRoundRobin state processors = + unwrap $ runRoundRobinM state $ (map Identity) <$> processors + +consecutivePairs :: forall a. List a -> List (a /\ a) +consecutivePairs xs = case tail xs of + Nothing -> fromFoldable [] + Just ys -> xs `zip` ys + +groupByKey :: forall k v. Ord k => List (k /\ v) -> Map k (List v) +groupByKey = foldl acc Map.empty + where + acc :: Map k (List v) -> (k /\ v) -> Map k (List v) + acc m (k /\ v) = Map.alter (Just <<< (maybe (singleton v) ((:) v))) k m + +ungroupByKey :: forall k v. Map k (List v) -> List (k /\ v) +ungroupByKey m = do + (k /\ vs) <- Map.toUnfoldable m + v <- vs + pure (k /\ v) + +-- Mock state used for testing + +-- From https://github.com/input-output-hk/cardano-wallet/blob/9d73b57e23392e25148cfc8db560cb8f656cb56a/lib/coin-selection/test/spec/Cardano/CoinSelection/BalanceSpec.hs#L4036 +newtype MockRoundRobinState k n = MockRoundRobinState + { processorLifetimes :: Map k n + , accumulatedEntries :: List (k /\ n) + } + +derive instance Newtype (MockRoundRobinState k n) _ +derive instance Generic (MockRoundRobinState k n) _ + +instance (Show k, Show n) => Show (MockRoundRobinState k n) where + show = genericShow + +type SimpleMockRoundRobinState = MockRoundRobinState TokenName Int + +derive instance Eq (MockRoundRobinState TokenName Int) + +instance Arbitrary SimpleMockRoundRobinState where + arbitrary = do + processorCount <- chooseInt 0 16 + lifetimes <- genProcessorLifetimes processorCount + pure $ MockRoundRobinState + { processorLifetimes: lifetimes, accumulatedEntries: fromFoldable [] } + where + genProcessorLifetimes :: Int -> Gen (Map.Map TokenName Int) + genProcessorLifetimes processorCount = + Map.fromFoldable <$> + (replicateA processorCount genProcessorLifetime :: Gen (Array _)) + + genProcessorLifetime :: Gen (TokenName /\ Int) + genProcessorLifetime = (/\) + <$> arbitrary + <*> chooseInt 0 127 -- Using `Arbitrary` leads to stack overflows in tests + +runMockRoundRobin + :: forall k n + . Ord k + => Ord n + => EuclideanRing n + => MockRoundRobinState k n + -> MockRoundRobinState k n +runMockRoundRobin initialState = runRoundRobin initialState processors + where + processors + :: Array (MockRoundRobinState k n -> Maybe (MockRoundRobinState k n)) + processors = mkProcessor <$> Map.toUnfoldable + (unwrap initialState).processorLifetimes + + mkProcessor + :: (k /\ n) -> MockRoundRobinState k n -> Maybe (MockRoundRobinState k n) + mkProcessor (k /\ n) s + | remainingLifetime k s <= zero = + Nothing + | otherwise = + Just $ MockRoundRobinState + { processorLifetimes: Map.update (Just <<< (_ - one)) k + (unwrap s).processorLifetimes + , accumulatedEntries: entry : (unwrap s).accumulatedEntries + } + where + entry :: (k /\ n) + entry = (k /\ (n - remainingLifetime k s)) + + remainingLifetime :: k -> MockRoundRobinState k n -> n + remainingLifetime k = + fromMaybe zero <<< Map.lookup k <<< _.processorLifetimes <<< unwrap + +-- Arbitrary instances + +newtype ArbitraryMap k v = ArbitraryMap (Map k v) + +derive instance Newtype (ArbitraryMap k v) _ + +instance (Ord k, Arbitrary k, Arbitrary v) => Arbitrary (ArbitraryMap k v) where + arbitrary = ArbitraryMap <$> genMap arbitrary arbitrary From 1fc5c0034c839e8971e9908b6c2942d8d30e6f6f Mon Sep 17 00:00:00 2001 From: Gregory Gerasev Date: Thu, 15 Dec 2022 13:20:43 +0400 Subject: [PATCH 109/373] Add CoinSelection tests, separate ArbitraryHelpers add support instances --- src/Internal/BalanceTx/CoinSelection.purs | 22 ++- src/Internal/Cardano/Types/Value.purs | 3 + src/Internal/CoinSelection/UtxoIndex.purs | 64 ++++++++- src/Internal/Types/ByteArray.purs | 11 +- src/Internal/Types/Transaction.purs | 15 +- test/CoinSelection/ArbitraryHelpers.purs | 134 ++++++++++++++++++ test/CoinSelection/SelectionState.purs | 88 ++++++++++++ test/CoinSelection/UtxoIndex.purs | 163 +++++++--------------- 8 files changed, 382 insertions(+), 118 deletions(-) create mode 100644 test/CoinSelection/ArbitraryHelpers.purs create mode 100644 test/CoinSelection/SelectionState.purs diff --git a/src/Internal/BalanceTx/CoinSelection.purs b/src/Internal/BalanceTx/CoinSelection.purs index 8cdc9e1fd6..cf3afbe651 100644 --- a/src/Internal/BalanceTx/CoinSelection.purs +++ b/src/Internal/BalanceTx/CoinSelection.purs @@ -12,6 +12,11 @@ module Ctl.Internal.BalanceTx.CoinSelection , performMultiAssetSelection , runRoundRobinM -- Exported for tests , selectedInputs + , selectUtxo + , selectRandomWithPriority + , empty + , mkSelectionState + , fromIndexFiltered ) where import Prelude @@ -41,8 +46,10 @@ import Ctl.Internal.CoinSelection.UtxoIndex , SelectionFilter(SelectAnyWith, SelectPairWith, SelectSingleton) , TxUnspentOutput , UtxoIndex + , emptyUtxoIndex , selectRandomWithFilter , utxoIndexDeleteEntry + , utxoIndexPartition , utxoIndexUniverse ) import Ctl.Internal.Types.ByteArray (byteArrayToHex) @@ -166,6 +173,20 @@ _selectedUtxos = _Newtype <<< prop (Proxy :: Proxy "selectedUtxos") mkSelectionState :: UtxoIndex -> SelectionState mkSelectionState = wrap <<< { leftoverUtxos: _, selectedUtxos: Map.empty } +-- | A completely empty selection with no selected or leftover UTxOs. +-- | +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/9d73b57e23392e25148cfc8db560cb8f656cb56a/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOSelection.hs#L183 +empty :: SelectionState +empty = mkSelectionState emptyUtxoIndex + +fromIndexFiltered + :: (TransactionInput -> Boolean) -> UtxoIndex -> SelectionState +fromIndexFiltered predicate index = SelectionState + { leftoverUtxos: no, selectedUtxos: utxoIndexUniverse yes } + where + yes /\ no = utxoIndexPartition predicate index + -- | Moves a single utxo entry from the leftover set to the selected set. -- | -- | Taken from cardano-wallet: @@ -437,4 +458,3 @@ showAssetClassWithQuantity (AssetClass cs tn) quantity = displayQuantity :: String displayQuantity = "quantity: " <> BigInt.toString quantity <> "))" - diff --git a/src/Internal/Cardano/Types/Value.purs b/src/Internal/Cardano/Types/Value.purs index dbb7b5e247..a250363bc5 100644 --- a/src/Internal/Cardano/Types/Value.purs +++ b/src/Internal/Cardano/Types/Value.purs @@ -541,6 +541,9 @@ instance Show AssetClass where instance Hashable AssetClass where hash (AssetClass cs tn) = hash (cs /\ tn) +instance Arbitrary AssetClass where + arbitrary = AssetClass <$> arbitrary <*> arbitrary + assetToValue :: AssetClass -> BigInt -> Value assetToValue (AssetClass cs tn) quantity = mkValue mempty (mkSingletonNonAdaAsset cs tn quantity) diff --git a/src/Internal/CoinSelection/UtxoIndex.purs b/src/Internal/CoinSelection/UtxoIndex.purs index bceec72867..6fdb9ae1f9 100644 --- a/src/Internal/CoinSelection/UtxoIndex.purs +++ b/src/Internal/CoinSelection/UtxoIndex.purs @@ -12,9 +12,12 @@ module Ctl.Internal.CoinSelection.UtxoIndex , checkUtxoIndexInvariants , emptyUtxoIndex , selectRandomWithFilter + , utxoIndexPartition , utxoIndexDeleteEntry , utxoIndexInsertEntry , utxoIndexUniverse + , utxoIndexDisjoint + , valueHasAsset ) where import Prelude @@ -23,19 +26,23 @@ import Ctl.Internal.Cardano.Types.Transaction ( TransactionOutput(TransactionOutput) , UtxoMap ) -import Ctl.Internal.Cardano.Types.Value (AssetClass) +import Ctl.Internal.Cardano.Types.Value (AssetClass, Value) import Ctl.Internal.Cardano.Types.Value ( getAssetQuantity , valueAssetClasses , valueAssets + , valueToCoin' ) as Value import Ctl.Internal.Types.Transaction (TransactionInput) import Data.Array (all, foldl) as Array import Data.Array ((!!)) +import Data.Array.NonEmpty (cons') +import Data.Bifunctor (bimap) import Data.BigInt (BigInt) import Data.BigInt (fromInt) as BigInt import Data.Foldable (all, length) as Foldable import Data.Foldable (foldl) +import Data.Function (on) import Data.Generic.Rep (class Generic) import Data.HashMap (HashMap) import Data.HashMap (alter, empty, lookup, toArrayBy, update) as HashMap @@ -45,11 +52,13 @@ import Data.Lens.Getter (view, (^.)) import Data.Lens.Iso (Iso', iso) import Data.Lens.Record (prop) import Data.Lens.Setter ((%~)) +import Data.List (List) import Data.Map (Map) import Data.Map ( delete , empty , insert + , intersection , isEmpty , lookup , singleton @@ -65,6 +74,8 @@ import Data.Tuple (Tuple(Tuple)) import Data.Tuple.Nested (type (/\), (/\)) import Effect.Class (class MonadEffect, liftEffect) import Effect.Random (randomInt) as Random +import Test.QuickCheck.Arbitrary (class Arbitrary, arbitrary) +import Test.QuickCheck.Gen (oneOf) import Type.Proxy (Proxy(Proxy)) -- | A utxo set that is indexed by asset identifier. @@ -112,6 +123,21 @@ instance Hashable Asset where hash AssetLovelace = hash (Nothing :: Maybe AssetClass) hash (Asset asset) = hash (Just asset) +instance Arbitrary Asset where + arbitrary = oneOf $ cons' (pure AssetLovelace) [ Asset <$> arbitrary ] + +-- | Indicates whether or not a given bundle includes a given asset. +-- | +-- | Both ada and non-ada assets can be queried. +-- | +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/9d73b57e23392e25148cfc8db560cb8f656cb56a/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L526 +valueHasAsset :: Value -> Asset -> Boolean +valueHasAsset amount AssetLovelace = + (Value.valueToCoin' amount) > (BigInt.fromInt 0) +valueHasAsset amount (Asset asset) = + Value.getAssetQuantity asset amount >= one + -------------------------------------------------------------------------------- -- Builders -------------------------------------------------------------------------------- @@ -130,6 +156,26 @@ buildUtxoIndex :: UtxoMap -> UtxoIndex buildUtxoIndex = Array.foldl (flip utxoIndexInsertEntry) emptyUtxoIndex <<< Map.toUnfoldable +-- | Partition `UtxoIndex` +-- | +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/9d73b57e23392e25148cfc8db560cb8f656cb56a/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L344 +utxoIndexPartition + :: (TransactionInput -> Boolean) -> UtxoIndex -> (UtxoIndex /\ UtxoIndex) +utxoIndexPartition predicate = + bimap buildUtxoIndex buildUtxoIndex <<< partitionMapOnKeys predicate + <<< utxoIndexUniverse + +partitionMapOnKeys + :: forall k v. Ord k => (k -> Boolean) -> Map k v -> Map k v /\ Map k v +partitionMapOnKeys p m = + foldl select (Map.empty /\ Map.empty) (Map.toUnfoldable m :: List (k /\ v)) + where + select :: (Map k v /\ Map k v) -> (k /\ v) -> (Map k v /\ Map k v) + select (yes /\ no) (k /\ v) = + if p k then (Map.insert k v yes) /\ no + else yes /\ (Map.insert k v no) + -------------------------------------------------------------------------------- -- Modifiers -------------------------------------------------------------------------------- @@ -194,6 +240,17 @@ categorizeUtxoEntry txOutput = case Set.toUnfoldable bundleAssets of bundleAssets :: Set AssetClass bundleAssets = txOutputAssetClasses txOutput +-------------------------------------------------------------------------------- +-- Set operations +-------------------------------------------------------------------------------- + +-- | Indicates whether a pair of UTxO indices are disjoint. +-- | +-- | Taken from cardano-wallet: +-- | https://github.com/input-output-hk/cardano-wallet/blob/9d73b57e23392e25148cfc8db560cb8f656cb56a/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L390 +utxoIndexDisjoint :: UtxoIndex -> UtxoIndex -> Boolean +utxoIndexDisjoint x y = Map.isEmpty $ on Map.intersection utxoIndexUniverse x y + -------------------------------------------------------------------------------- -- Selection -------------------------------------------------------------------------------- @@ -207,6 +264,11 @@ data SelectionFilter | SelectPairWith Asset | SelectAnyWith Asset +instance Arbitrary SelectionFilter where + arbitrary = oneOf $ + cons' (SelectSingleton <$> arbitrary) + [ (SelectPairWith <$> arbitrary), (SelectAnyWith <$> arbitrary) ] + -- | Taken from cardano-wallet: -- | https://github.com/input-output-hk/cardano-wallet/blob/791541da69b9b3f434bb9ead43de406cc18b0373/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L418 selectRandomWithFilter diff --git a/src/Internal/Types/ByteArray.purs b/src/Internal/Types/ByteArray.purs index 9996aa2519..df14ce364d 100644 --- a/src/Internal/Types/ByteArray.purs +++ b/src/Internal/Types/ByteArray.purs @@ -32,7 +32,12 @@ import Data.Maybe (Maybe(Just, Nothing)) import Data.Newtype (class Newtype) import Data.String.CodeUnits (toCharArray) import Data.Traversable (for) -import Test.QuickCheck.Arbitrary (class Arbitrary, arbitrary) +import Test.QuickCheck.Arbitrary + ( class Arbitrary + , class Coarbitrary + , arbitrary + , coarbitrary + ) newtype ByteArray = ByteArray Uint8Array @@ -118,6 +123,10 @@ foreign import subarray :: Int -> Int -> ByteArray -> ByteArray instance Arbitrary ByteArray where arbitrary = byteArrayFromIntArrayUnsafe <$> arbitrary +instance Coarbitrary ByteArray where + coarbitrary bytes generator = coarbitrary (byteArrayToIntArray bytes) + generator + -- | Convert characters in range `0-255` into a `ByteArray`. -- | Fails with `Nothing` if there are characters out of this range in a string. byteArrayFromAscii :: String -> Maybe ByteArray diff --git a/src/Internal/Types/Transaction.purs b/src/Internal/Types/Transaction.purs index 7cd59e7fb3..dce1f574f5 100644 --- a/src/Internal/Types/Transaction.purs +++ b/src/Internal/Types/Transaction.purs @@ -21,8 +21,12 @@ import Data.Generic.Rep (class Generic) import Data.Maybe (Maybe(Nothing)) import Data.Newtype (class Newtype, wrap) import Data.Show.Generic (genericShow) -import Data.UInt (UInt) -import Test.QuickCheck.Arbitrary (class Arbitrary) +import Data.UInt (UInt, toInt) +import Test.QuickCheck.Arbitrary + ( class Arbitrary + , class Coarbitrary + , coarbitrary + ) import Test.QuickCheck.Gen (chooseInt, vectorOf) newtype TransactionInput = TransactionInput @@ -62,6 +66,10 @@ instance ToData TransactionInput where toData (TransactionInput { transactionId, index }) = Constr zero [ toData transactionId, toData index ] +instance Coarbitrary TransactionInput where + coarbitrary (TransactionInput input) generator = + coarbitrary (toInt input.index) $ coarbitrary input.transactionId generator + -- | 32-bytes blake2b256 hash of a tx body. -- | NOTE. Plutus docs might incorrectly state that it uses -- | SHA256 for this purposes. @@ -95,6 +103,9 @@ instance Arbitrary TransactionHash where arbitrary = wrap <<< byteArrayFromIntArrayUnsafe <$> vectorOf 32 (chooseInt 0 255) +instance Coarbitrary TransactionHash where + coarbitrary (TransactionHash bytes) generator = coarbitrary bytes generator + newtype DataHash = DataHash ByteArray derive instance Generic DataHash _ diff --git a/test/CoinSelection/ArbitraryHelpers.purs b/test/CoinSelection/ArbitraryHelpers.purs new file mode 100644 index 0000000000..ebd68edc72 --- /dev/null +++ b/test/CoinSelection/ArbitraryHelpers.purs @@ -0,0 +1,134 @@ +module Test.Ctl.CoinSelection.ArbitraryHelpers where + +import Prelude + +import Control.Apply (lift2) +import Ctl.Internal.BalanceTx.CoinSelection as CoinSelection +import Ctl.Internal.Cardano.Types.Transaction + ( TransactionOutput(TransactionOutput) + , UtxoMap + ) +import Ctl.Internal.Cardano.Types.Value (Value) +import Ctl.Internal.CoinSelection.UtxoIndex + ( TxUnspentOutput + , UtxoIndex + ) +import Ctl.Internal.CoinSelection.UtxoIndex as UtxoIndex +import Ctl.Internal.Serialization.Address + ( Address + , NetworkId(MainnetId) + , baseAddressToAddress + , paymentKeyHashStakeKeyHashAddress + ) +import Ctl.Internal.Types.OutputDatum (OutputDatum(NoOutputDatum)) +import Ctl.Internal.Types.Transaction + ( TransactionHash + , TransactionInput(TransactionInput) + ) +import Data.Generic.Rep (class Generic) +import Data.Map.Gen (genMap) as Map +import Data.Maybe (Maybe(Nothing)) +import Data.Newtype (class Newtype, unwrap, wrap) +import Data.Show.Generic (genericShow) +import Data.Tuple (Tuple(Tuple)) +import Data.Tuple.Nested (type (/\), (/\)) +import Data.UInt (fromInt) as UInt +import Test.QuickCheck.Arbitrary (class Arbitrary, arbitrary) +import Test.QuickCheck.Gen (Gen) + +newtype ArbitraryUtxoIndex = ArbitraryUtxoIndex UtxoIndex + +derive instance Newtype ArbitraryUtxoIndex _ + +instance Arbitrary ArbitraryUtxoIndex where + arbitrary = + (arbitrary :: Gen ArbitraryUtxoMap) + <#> wrap <<< UtxoIndex.buildUtxoIndex <<< unwrap + +newtype ArbitrarySelectionState = ArbitrarySelectionState + CoinSelection.SelectionState + +derive instance Newtype ArbitrarySelectionState _ + +instance Arbitrary ArbitrarySelectionState where + arbitrary = ArbitrarySelectionState <$> + lift2 CoinSelection.fromIndexFiltered + (arbitrary :: Gen (TransactionInput -> Boolean)) + (unwrap <$> (arbitrary :: Gen ArbitraryUtxoIndex)) + +newtype ArbitraryUtxoMap = ArbitraryUtxoMap UtxoMap + +derive instance Generic ArbitraryUtxoMap _ +derive instance Newtype ArbitraryUtxoMap _ + +instance Show ArbitraryUtxoMap where + show = genericShow + +instance Arbitrary ArbitraryUtxoMap where + arbitrary = wrap <$> Map.genMap genTransactionInput genTransactionOutput + +newtype ArbitraryTxUnspentOut = + ArbitraryTxUnspentOut (TransactionInput /\ TransactionOutput) + +derive instance Newtype ArbitraryTxUnspentOut _ + +instance Arbitrary ArbitraryTxUnspentOut where + arbitrary = wrap <$> lift2 Tuple genTransactionInput genTransactionOutput + +genTransactionInput :: Gen TransactionInput +genTransactionInput = unwrap <$> (arbitrary :: Gen ArbitraryTransactionInput) + +genTransactionOutput :: Gen TransactionOutput +genTransactionOutput = unwrap <$> (arbitrary :: Gen ArbitraryTransactionOutput) + +newtype ArbitraryTransactionInput = + ArbitraryTransactionInput TransactionInput + +derive instance Newtype ArbitraryTransactionInput _ + +instance Arbitrary ArbitraryTransactionInput where + arbitrary = wrap <$> lift2 mkTxInput arbitrary arbitrary + where + mkTxInput :: TransactionHash -> Int -> TransactionInput + mkTxInput transactionId index = + TransactionInput + { transactionId + , index: UInt.fromInt index + } + +newtype ArbitraryTransactionOutput = + ArbitraryTransactionOutput TransactionOutput + +derive instance Newtype ArbitraryTransactionOutput _ + +instance Arbitrary ArbitraryTransactionOutput where + arbitrary = wrap <$> lift2 mkTxOutput arbitrary arbitrary + where + mkTxOutput :: ArbitraryAddress -> Value -> TransactionOutput + mkTxOutput address amount = + TransactionOutput + { address: unwrap address + , amount + , datum: NoOutputDatum + , scriptRef: Nothing + } + +newtype ArbitraryTxUnspentOutput = ArbitraryTxUnspentOutput TxUnspentOutput + +derive instance Newtype ArbitraryTxUnspentOutput _ + +instance Arbitrary ArbitraryTxUnspentOutput where + arbitrary = ArbitraryTxUnspentOutput <$> lift2 (/\) in_ out + where + in_ = unwrap <$> (arbitrary :: Gen ArbitraryTransactionInput) + out = unwrap <$> (arbitrary :: Gen ArbitraryTransactionOutput) + +newtype ArbitraryAddress = ArbitraryAddress Address + +derive instance Newtype ArbitraryAddress _ + +instance Arbitrary ArbitraryAddress where + arbitrary = + wrap <<< baseAddressToAddress <$> + lift2 (paymentKeyHashStakeKeyHashAddress MainnetId) arbitrary arbitrary + diff --git a/test/CoinSelection/SelectionState.purs b/test/CoinSelection/SelectionState.purs new file mode 100644 index 0000000000..c000ff18ae --- /dev/null +++ b/test/CoinSelection/SelectionState.purs @@ -0,0 +1,88 @@ +-- Taken from cardano-wallet: +-- https://github.com/input-output-hk/cardano-wallet/blob/9d73b57e23392e25148cfc8db560cb8f656cb56a/lib/primitive/test/spec/Cardano/Wallet/Primitive/Types/UTxOSelectionSpec.hs + +module Test.Ctl.CoinSelection.SelectionState + ( suite + ) where + +import Prelude + +import Ctl.Internal.BalanceTx.CoinSelection (SelectionState) +import Ctl.Internal.BalanceTx.CoinSelection as CoinSelection +import Ctl.Internal.CoinSelection.UtxoIndex as UtxoIndex +import Ctl.Internal.Test.TestPlanM (TestPlanM) +import Data.Array.NonEmpty (cons') +import Data.Maybe (Maybe(Just), isJust) +import Data.Newtype (unwrap) +import Data.Tuple.Nested ((/\)) +import Effect.Aff (Aff) +import Effect.Unsafe (unsafePerformEffect) +import Mote (group, test) +import Test.Ctl.CoinSelection.ArbitraryHelpers + ( ArbitrarySelectionState + , ArbitraryTxUnspentOutput + , ArbitraryUtxoIndex + ) +import Test.Spec.QuickCheck (quickCheck) + +suite :: TestPlanM (Aff Unit) Unit +suite = do + group "Generation" do + test "Arbitrary is valid" $ quickCheck prop_arbitrary_isValid + group "Construction" do + test "prop_mkSelectionState_isValid" $ quickCheck + prop_mkSelectionState_isValid + group "Modification" do + test "prop_select_isValid" $ quickCheck prop_select_isValid + test "prop_selectRandomWithPriority" $ quickCheck + prop_selectRandomWithPriority + +-- Tests + +prop_arbitrary_isValid :: ArbitrarySelectionState -> Boolean +prop_arbitrary_isValid = isValidSelection <<< unwrap + +prop_mkSelectionState_isValid :: ArbitraryUtxoIndex -> Boolean +prop_mkSelectionState_isValid = isValidSelection + <<< CoinSelection.mkSelectionState + <<< unwrap + +prop_select_isValid + :: ArbitraryTxUnspentOutput -> ArbitrarySelectionState -> Boolean +prop_select_isValid u s = isValidSelection $ + CoinSelection.selectUtxo (unwrap u) (unwrap s) + +prop_selectRandomWithPriority + :: ArbitraryUtxoIndex -> UtxoIndex.Asset -> UtxoIndex.Asset -> Boolean +prop_selectRandomWithPriority index a1 a2 = + if a1 == a2 then true + else + let + s1 = UtxoIndex.SelectPairWith a1 + s2 = UtxoIndex.SelectPairWith a2 + index' = unwrap index + haveMatchForAsset1 = unsafePerformEffect $ isJust <$> + (UtxoIndex.selectRandomWithFilter index' s1) + haveMatchForAsset2 = unsafePerformEffect $ isJust <$> + (UtxoIndex.selectRandomWithFilter index' s2) + result = unsafePerformEffect $ + CoinSelection.selectRandomWithPriority index' (cons' s1 [ s2 ]) + in + case result of + Just ((_ /\ b) /\ _) | (unwrap b).amount `UtxoIndex.valueHasAsset` a1 -> + do + haveMatchForAsset1 + Just ((_ /\ b) /\ _) | (unwrap b).amount `UtxoIndex.valueHasAsset` a2 -> + do + (not haveMatchForAsset1) && haveMatchForAsset2 + _ -> do + (not haveMatchForAsset1) && (not haveMatchForAsset2) + +-- Invariants + +isValidSelection :: SelectionState -> Boolean +isValidSelection s = UtxoIndex.utxoIndexDisjoint + (indexRecord.leftoverUtxos) + (UtxoIndex.buildUtxoIndex $ indexRecord.selectedUtxos) + where + indexRecord = unwrap s diff --git a/test/CoinSelection/UtxoIndex.purs b/test/CoinSelection/UtxoIndex.purs index 2222dd14f3..c9a0e1545e 100644 --- a/test/CoinSelection/UtxoIndex.purs +++ b/test/CoinSelection/UtxoIndex.purs @@ -1,50 +1,32 @@ -module Test.Ctl.CoinSelection.UtxoIndex where +module Test.Ctl.CoinSelection.UtxoIndex + ( suite + ) where import Prelude -import Control.Apply (lift2) -import Ctl.Internal.Cardano.Types.Transaction - ( TransactionOutput(TransactionOutput) - , UtxoMap - ) -import Ctl.Internal.Cardano.Types.Value (Value) import Ctl.Internal.CoinSelection.UtxoIndex ( UtxoIndex , UtxoIndexInvariantStatus(InvariantHolds) ) -import Ctl.Internal.CoinSelection.UtxoIndex - ( buildUtxoIndex - , checkUtxoIndexInvariants - , emptyUtxoIndex - , utxoIndexDeleteEntry - , utxoIndexInsertEntry - ) as UtxoIndex -import Ctl.Internal.Serialization.Address - ( Address - , NetworkId(MainnetId) - , baseAddressToAddress - , paymentKeyHashStakeKeyHashAddress - ) +import Ctl.Internal.CoinSelection.UtxoIndex as UtxoIndex import Ctl.Internal.Test.TestPlanM (TestPlanM) -import Ctl.Internal.Types.OutputDatum (OutputDatum(NoOutputDatum)) import Ctl.Internal.Types.Transaction - ( TransactionHash - , TransactionInput(TransactionInput) + ( TransactionInput(TransactionInput) ) -import Data.Generic.Rep (class Generic) import Data.Map (empty) as Map -import Data.Map.Gen (genMap) as Map -import Data.Maybe (Maybe(Nothing)) -import Data.Newtype (class Newtype, unwrap, wrap) -import Data.Show.Generic (genericShow) -import Data.Tuple (Tuple(Tuple)) -import Data.Tuple.Nested (type (/\)) -import Data.UInt (fromInt) as UInt +import Data.Maybe (Maybe(Nothing, Just)) +import Data.Newtype (unwrap) +import Data.Tuple.Nested ((/\)) import Effect.Aff (Aff) +import Effect.Unsafe (unsafePerformEffect) import Mote (group, test) +import Test.Ctl.CoinSelection.ArbitraryHelpers + ( ArbitraryTxUnspentOut + , ArbitraryUtxoIndex + , ArbitraryUtxoMap + ) import Test.QuickCheck (Result(Failed, Success)) as QuickCheck -import Test.QuickCheck.Arbitrary (class Arbitrary, arbitrary) -import Test.QuickCheck.Gen (Gen) +import Test.QuickCheck ((===)) import Test.Spec.Assertions (shouldEqual) import Test.Spec.QuickCheck (quickCheck) @@ -57,12 +39,20 @@ suite = test "prop_buildUtxoIndex_invariant" do quickCheck prop_buildUtxoIndex_invariant + test "prop_partition_disjoint" do + quickCheck prop_partition_disjoint + test "prop_utxoIndexInsertEntry_invariant" do quickCheck prop_utxoIndexInsertEntry_invariant test "prop_utxoIndexDeleteEntry_invariant" do quickCheck prop_utxoIndexDeleteEntry_invariant + group "SelectRandom" do + test "prop_selectRandom_invariant" $ quickCheck + prop_selectRandom_invariant + test "prop_selectRandom_empty" $ quickCheck prop_selectRandom_empty + prop_buildUtxoIndex_invariant :: ArbitraryUtxoMap -> QuickCheck.Result prop_buildUtxoIndex_invariant = invariantHolds <<< UtxoIndex.buildUtxoIndex <<< unwrap @@ -73,12 +63,39 @@ prop_utxoIndexInsertEntry_invariant entry utxoIndex = invariantHolds $ UtxoIndex.utxoIndexInsertEntry (unwrap entry) (unwrap utxoIndex) +prop_partition_disjoint + :: (TransactionInput -> Boolean) -> ArbitraryUtxoIndex -> Boolean +prop_partition_disjoint predicate index = UtxoIndex.utxoIndexDisjoint yes no + where + (yes /\ no) = UtxoIndex.utxoIndexPartition predicate (unwrap index) + prop_utxoIndexDeleteEntry_invariant :: ArbitraryTxUnspentOut -> ArbitraryUtxoIndex -> QuickCheck.Result prop_utxoIndexDeleteEntry_invariant entry utxoIndex = invariantHolds $ UtxoIndex.utxoIndexDeleteEntry (unwrap entry) (unwrap utxoIndex) +prop_selectRandom_invariant + :: ArbitraryUtxoIndex -> UtxoIndex.SelectionFilter -> QuickCheck.Result +prop_selectRandom_invariant index f = + let + result = unsafePerformEffect $ UtxoIndex.selectRandomWithFilter + (unwrap index) + f + check Nothing = QuickCheck.Success + check (Just (_ /\ index')) = invariantHolds index' + in + check result + +prop_selectRandom_empty :: UtxoIndex.SelectionFilter -> QuickCheck.Result +prop_selectRandom_empty f = + let + result = unsafePerformEffect $ UtxoIndex.selectRandomWithFilter + UtxoIndex.emptyUtxoIndex + f + in + result === Nothing + -- | Taken from cardano-wallet: -- | https://github.com/input-output-hk/cardano-wallet/blob/9d73b57e23392e25148cfc8db560cb8f656cb56a/lib/primitive/test/spec/Cardano/Wallet/Primitive/Types/UTxOIndexSpec.hs#L183 invariantHolds :: UtxoIndex -> QuickCheck.Result @@ -86,83 +103,3 @@ invariantHolds utxoIndex = case UtxoIndex.checkUtxoIndexInvariants utxoIndex of InvariantHolds -> QuickCheck.Success status -> QuickCheck.Failed (show status) - --------------------------------------------------------------------------------- --- Arbitrary --------------------------------------------------------------------------------- - -newtype ArbitraryUtxoIndex = ArbitraryUtxoIndex UtxoIndex - -derive instance Newtype ArbitraryUtxoIndex _ - -instance Arbitrary ArbitraryUtxoIndex where - arbitrary = - (arbitrary :: Gen ArbitraryUtxoMap) - <#> wrap <<< UtxoIndex.buildUtxoIndex <<< unwrap - -newtype ArbitraryUtxoMap = ArbitraryUtxoMap UtxoMap - -derive instance Generic ArbitraryUtxoMap _ -derive instance Newtype ArbitraryUtxoMap _ - -instance Show ArbitraryUtxoMap where - show = genericShow - -instance Arbitrary ArbitraryUtxoMap where - arbitrary = wrap <$> Map.genMap genTransactionInput genTransactionOutput - -newtype ArbitraryTxUnspentOut = - ArbitraryTxUnspentOut (TransactionInput /\ TransactionOutput) - -derive instance Newtype ArbitraryTxUnspentOut _ - -instance Arbitrary ArbitraryTxUnspentOut where - arbitrary = wrap <$> lift2 Tuple genTransactionInput genTransactionOutput - -genTransactionInput :: Gen TransactionInput -genTransactionInput = unwrap <$> (arbitrary :: Gen ArbitraryTransactionInput) - -genTransactionOutput :: Gen TransactionOutput -genTransactionOutput = unwrap <$> (arbitrary :: Gen ArbitraryTransactionOutput) - -newtype ArbitraryTransactionInput = - ArbitraryTransactionInput TransactionInput - -derive instance Newtype ArbitraryTransactionInput _ - -instance Arbitrary ArbitraryTransactionInput where - arbitrary = wrap <$> lift2 mkTxInput arbitrary arbitrary - where - mkTxInput :: TransactionHash -> Int -> TransactionInput - mkTxInput transactionId index = - TransactionInput - { transactionId - , index: UInt.fromInt index - } - -newtype ArbitraryTransactionOutput = - ArbitraryTransactionOutput TransactionOutput - -derive instance Newtype ArbitraryTransactionOutput _ - -instance Arbitrary ArbitraryTransactionOutput where - arbitrary = wrap <$> lift2 mkTxOutput arbitrary arbitrary - where - mkTxOutput :: ArbitraryAddress -> Value -> TransactionOutput - mkTxOutput address amount = - TransactionOutput - { address: unwrap address - , amount - , datum: NoOutputDatum - , scriptRef: Nothing - } - -newtype ArbitraryAddress = ArbitraryAddress Address - -derive instance Newtype ArbitraryAddress _ - -instance Arbitrary ArbitraryAddress where - arbitrary = - wrap <<< baseAddressToAddress <$> - lift2 (paymentKeyHashStakeKeyHashAddress MainnetId) arbitrary arbitrary - From fe8b3495e4546f17b849dd8a123982c217c32213 Mon Sep 17 00:00:00 2001 From: Gregory Gerasev Date: Thu, 15 Dec 2022 13:22:01 +0400 Subject: [PATCH 110/373] Add new suites to unit tests --- test/Unit.purs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/test/Unit.purs b/test/Unit.purs index 4324c2a36c..224a427f05 100644 --- a/test/Unit.purs +++ b/test/Unit.purs @@ -9,6 +9,8 @@ import Effect.Class (liftEffect) import Mote.Monad (mapTest) import Test.Ctl.Base64 as Base64 import Test.Ctl.ByteArray as ByteArray +import Test.Ctl.CoinSelection.RoundRobin as RoundRobin +import Test.Ctl.CoinSelection.SelectionState as SelectionState import Test.Ctl.CoinSelection.UtxoIndex as UtxoIndex import Test.Ctl.Data as Data import Test.Ctl.Data.Interval as Ctl.Data.Interval @@ -81,3 +83,5 @@ testPlan = do E2E.Route.suite MustSpendTotal.suite UtxoIndex.suite + SelectionState.suite + RoundRobin.suite From 5097a5572d947f72540f962e522736f0511ee839 Mon Sep 17 00:00:00 2001 From: Gregory Gerasev Date: Thu, 15 Dec 2022 13:26:49 +0400 Subject: [PATCH 111/373] Move Arbitrary from RoundRobin --- test/CoinSelection/ArbitraryHelpers.purs | 9 +++++++++ test/CoinSelection/RoundRobin.purs | 11 +---------- 2 files changed, 10 insertions(+), 10 deletions(-) diff --git a/test/CoinSelection/ArbitraryHelpers.purs b/test/CoinSelection/ArbitraryHelpers.purs index ebd68edc72..d8e78d66f2 100644 --- a/test/CoinSelection/ArbitraryHelpers.purs +++ b/test/CoinSelection/ArbitraryHelpers.purs @@ -8,6 +8,8 @@ import Ctl.Internal.Cardano.Types.Transaction ( TransactionOutput(TransactionOutput) , UtxoMap ) +import Data.Map.Gen (genMap) +import Data.Map (Map) import Ctl.Internal.Cardano.Types.Value (Value) import Ctl.Internal.CoinSelection.UtxoIndex ( TxUnspentOutput @@ -132,3 +134,10 @@ instance Arbitrary ArbitraryAddress where wrap <<< baseAddressToAddress <$> lift2 (paymentKeyHashStakeKeyHashAddress MainnetId) arbitrary arbitrary + +newtype ArbitraryMap k v = ArbitraryMap (Map k v) + +derive instance Newtype (ArbitraryMap k v) _ + +instance (Ord k, Arbitrary k, Arbitrary v) => Arbitrary (ArbitraryMap k v) where + arbitrary = ArbitraryMap <$> genMap arbitrary arbitrary diff --git a/test/CoinSelection/RoundRobin.purs b/test/CoinSelection/RoundRobin.purs index 1cf597bad5..7973de80ee 100644 --- a/test/CoinSelection/RoundRobin.purs +++ b/test/CoinSelection/RoundRobin.purs @@ -22,7 +22,6 @@ import Data.List ) import Data.Map (Map) import Data.Map as Map -import Data.Map.Gen (genMap) import Data.Maybe (Maybe(Just, Nothing), fromMaybe, maybe) import Data.Newtype (class Newtype, unwrap) import Data.NonEmpty (NonEmpty) @@ -38,6 +37,7 @@ import Test.QuickCheck (Result, (), (===)) import Test.QuickCheck.Arbitrary (class Arbitrary, arbitrary) import Test.QuickCheck.Gen (Gen, chooseInt) import Test.Spec.QuickCheck (quickCheck) +import Test.Ctl.CoinSelection.ArbitraryHelpers (ArbitraryMap) suite :: TestPlanM (Aff Unit) Unit suite = do @@ -205,12 +205,3 @@ runMockRoundRobin initialState = runRoundRobin initialState processors remainingLifetime :: k -> MockRoundRobinState k n -> n remainingLifetime k = fromMaybe zero <<< Map.lookup k <<< _.processorLifetimes <<< unwrap - --- Arbitrary instances - -newtype ArbitraryMap k v = ArbitraryMap (Map k v) - -derive instance Newtype (ArbitraryMap k v) _ - -instance (Ord k, Arbitrary k, Arbitrary v) => Arbitrary (ArbitraryMap k v) where - arbitrary = ArbitraryMap <$> genMap arbitrary arbitrary From 4d390cf014d8e5b01754e6f42d61e9c19fcc6bf6 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Thu, 15 Dec 2022 13:05:21 +0000 Subject: [PATCH 112/373] Warnings --- src/Internal/QueryM/Kupo.purs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Internal/QueryM/Kupo.purs b/src/Internal/QueryM/Kupo.purs index 3b1acc93fa..e38835011d 100644 --- a/src/Internal/QueryM/Kupo.purs +++ b/src/Internal/QueryM/Kupo.purs @@ -87,7 +87,7 @@ import Data.Foldable (fold) import Data.Generic.Rep (class Generic) import Data.HTTP.Method (Method(GET)) import Data.Map (Map) -import Data.Map (catMaybes, fromFoldable, lookup) as Map +import Data.Map (fromFoldable, lookup) as Map import Data.Maybe (Maybe(Just, Nothing), fromMaybe) import Data.Newtype (class Newtype, unwrap, wrap) import Data.Show.Generic (genericShow) From a1bb0240d39d609185c2c7da0f25bc40e9248bc7 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Thu, 15 Dec 2022 13:13:26 +0000 Subject: [PATCH 113/373] Update template rev properly --- templates/ctl-scaffold/flake.lock | 8 ++++---- templates/ctl-scaffold/flake.nix | 2 +- templates/ctl-scaffold/packages.dhall | 2 +- templates/ctl-scaffold/spago-packages.nix | 6 +++--- 4 files changed, 9 insertions(+), 9 deletions(-) diff --git a/templates/ctl-scaffold/flake.lock b/templates/ctl-scaffold/flake.lock index 91afddc9d0..c9ba1877fb 100644 --- a/templates/ctl-scaffold/flake.lock +++ b/templates/ctl-scaffold/flake.lock @@ -1739,17 +1739,17 @@ "plutip": "plutip" }, "locked": { - "lastModified": 1670943157, - "narHash": "sha256-d36d6WhQ/2j40gWFeQtWDcHh6x74X6lykAAjURfURVU=", + "lastModified": 1671109521, + "narHash": "sha256-RU/jWsYG6U066jbyiRJF9MGrToxbMIv+kX7c9Nu+Ves=", "owner": "Plutonomicon", "repo": "cardano-transaction-lib", - "rev": "30f35db524a3d855852fcfb8d7069defbedbbe76", + "rev": "4d390cf014d8e5b01754e6f42d61e9c19fcc6bf6", "type": "github" }, "original": { "owner": "Plutonomicon", "repo": "cardano-transaction-lib", - "rev": "30f35db524a3d855852fcfb8d7069defbedbbe76", + "rev": "4d390cf014d8e5b01754e6f42d61e9c19fcc6bf6", "type": "github" } }, diff --git a/templates/ctl-scaffold/flake.nix b/templates/ctl-scaffold/flake.nix index 5981be7180..5fbe7fd8b2 100644 --- a/templates/ctl-scaffold/flake.nix +++ b/templates/ctl-scaffold/flake.nix @@ -10,7 +10,7 @@ type = "github"; owner = "Plutonomicon"; repo = "cardano-transaction-lib"; - rev = "30f35db524a3d855852fcfb8d7069defbedbbe76"; + rev = "4d390cf014d8e5b01754e6f42d61e9c19fcc6bf6"; }; # To use the same version of `nixpkgs` as we do nixpkgs.follows = "ctl/nixpkgs"; diff --git a/templates/ctl-scaffold/packages.dhall b/templates/ctl-scaffold/packages.dhall index a196f1746f..0856cc7cfc 100644 --- a/templates/ctl-scaffold/packages.dhall +++ b/templates/ctl-scaffold/packages.dhall @@ -366,7 +366,7 @@ let additions = , "variant" ] , repo = "https://github.com/Plutonomicon/cardano-transaction-lib.git" - , version = "fc35733e483c21e55e5acabacb1d9e192f91a032" + , version = "4d390cf014d8e5b01754e6f42d61e9c19fcc6bf6" } } diff --git a/templates/ctl-scaffold/spago-packages.nix b/templates/ctl-scaffold/spago-packages.nix index 774722b39a..c9d68723bb 100644 --- a/templates/ctl-scaffold/spago-packages.nix +++ b/templates/ctl-scaffold/spago-packages.nix @@ -211,11 +211,11 @@ let "cardano-transaction-lib" = pkgs.stdenv.mkDerivation { name = "cardano-transaction-lib"; - version = "fc35733e483c21e55e5acabacb1d9e192f91a032"; + version = "4d390cf014d8e5b01754e6f42d61e9c19fcc6bf6"; src = pkgs.fetchgit { url = "https://github.com/Plutonomicon/cardano-transaction-lib.git"; - rev = "fc35733e483c21e55e5acabacb1d9e192f91a032"; - sha256 = "19zmsg8x65qc0lnl94llnr1r9v87xv3b7amz9kgpjq4d50idwb6n"; + rev = "4d390cf014d8e5b01754e6f42d61e9c19fcc6bf6"; + sha256 = "1ssmpvdz9p3yj7z8nc2vii7aphgl8l98kwinx8x4vs86qrdf6ks5"; }; phases = "installPhase"; installPhase = "ln -s $src $out"; From 77831d081bcd4838f0363f394db7c07772b81244 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Thu, 15 Dec 2022 13:14:48 +0000 Subject: [PATCH 114/373] Partially restore FAQ question --- doc/faq.md | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/doc/faq.md b/doc/faq.md index 973e53418d..aee5877595 100644 --- a/doc/faq.md +++ b/doc/faq.md @@ -117,7 +117,11 @@ If you are under wayland you need to add `--ozone-platform=wayland` to the argum This is because the node hasn't fully synced. The protocol parameter name changed from `coinsPerUtxoWord` to `coinsPerUtxoByte` in Babbage. CTL only supports the latest era, but Ogmios returns different protocol parameters format depending on current era of a local node. -### How can I write my own Nix derivations using the project returned by `purescriptProject`? +### Q: Why do I get an error from `foreign.js` when running Plutip tests locally? + +The most likely reason for this is that spawning the external processes from `Contract.Test.Plutip` fails. Make sure that all of the required services are on your `$PATH` (see more [here](./runtime.md); you can also set `shell.withRuntime = true;` to ensure that these are always added to your shell environment when running `nix develop`). + +### Q: How can I write my own Nix derivations using the project returned by `purescriptProject`? If the different derivation builders that `purescriptProject` gives you out-of-the-box (e.g. `runPursTest`, `bundlePursProject`, etc...) are not sufficient, you can access the compiled project (all of the original `src` argument plus the `output` directory that `purs` produces) and the generated `node_modules` using the `compiled` and `nodeModules` attributes, respectively. These can be used to write your own derivations without needing to recompile the entire project (that is, the generated output can be shared between all of your Nix components). For example: From 19293ef3a341b2e4f6f93aed3820bbb6eca5730c Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Thu, 15 Dec 2022 17:22:55 +0100 Subject: [PATCH 115/373] Apply suggestions, Update CHANGELOG.md --- CHANGELOG.md | 1 + src/Internal/BalanceTx/CoinSelection.purs | 1 + test/CoinSelection/CoinSelection.purs | 7 ++----- 3 files changed, 4 insertions(+), 5 deletions(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index 6f82db2c16..c996d79423 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -38,6 +38,7 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) ### Added - NuFi wallet support ([#1265](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1265)) +- `blake2b224Hash` and `blake2b224HashHex` functions for computing blake2b-224 hashes of arbitrary byte arrays ([#1323](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1323)) * Add `submitTxFromConstraints` and `submitTxFromConstraintsReturningFee` in `Contract.Transaction`. `submitTxFromConstraints` builds a transaction that satisfies the constraints, then submits it to the network. It is analog for `submitTxConstraintsWith` function in Plutus and replaces `Helpers.buildBalanceSignAndSubmitTx`. diff --git a/src/Internal/BalanceTx/CoinSelection.purs b/src/Internal/BalanceTx/CoinSelection.purs index 0701d61c2e..8f296e316e 100644 --- a/src/Internal/BalanceTx/CoinSelection.purs +++ b/src/Internal/BalanceTx/CoinSelection.purs @@ -9,6 +9,7 @@ module Ctl.Internal.BalanceTx.CoinSelection ( SelectionState(SelectionState) , SelectionStrategy(SelectionStrategyMinimal, SelectionStrategyOptimal) , _leftoverUtxos + , mkSelectionState , performMultiAssetSelection , selectedInputs ) where diff --git a/test/CoinSelection/CoinSelection.purs b/test/CoinSelection/CoinSelection.purs index 2c98d84837..5e3356c776 100644 --- a/test/CoinSelection/CoinSelection.purs +++ b/test/CoinSelection/CoinSelection.purs @@ -6,6 +6,7 @@ import Control.Monad.Error.Class (class MonadThrow) import Ctl.Internal.BalanceTx.CoinSelection ( SelectionState , SelectionStrategy(SelectionStrategyMinimal, SelectionStrategyOptimal) + , mkSelectionState , performMultiAssetSelection ) import Ctl.Internal.BalanceTx.Error (BalanceTxError) @@ -80,12 +81,8 @@ suite = prop_performMultiAssetSelection_empty :: SelectionStrategy -> ArbitraryUtxoIndex -> CoinSelectionTestM Result prop_performMultiAssetSelection_empty strategy utxoIndex = - assertEquals targetSelState <$> + assertEquals (mkSelectionState $ unwrap utxoIndex) <$> performMultiAssetSelection strategy (unwrap utxoIndex) mempty - where - targetSelState :: SelectionState - targetSelState = - wrap { leftoverUtxos: unwrap utxoIndex, selectedUtxos: Map.empty } runSelectionTestWithFixture :: (SelectionStrategy -> SelFixture) -> String -> TestPlanM (Aff Unit) Unit From 6df2757928d057921d62b9c74908b9d6a830824e Mon Sep 17 00:00:00 2001 From: Calum Sieppert Date: Thu, 15 Dec 2022 15:01:09 -0700 Subject: [PATCH 116/373] Fix `fd` usage to ignore inherited local system configuration Also remove the `tmp` exclusion, because this is automatically excluded as `tmp` is ignored in `.gitignore` --- Makefile | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/Makefile b/Makefile index 8cf135fe61..bd132a4c73 100644 --- a/Makefile +++ b/Makefile @@ -4,9 +4,9 @@ SHELL := bash query-testnet-tip clean check-explicit-exports .SHELLFLAGS := -eu -o pipefail -c -ps-sources := $(shell fd -epurs -Etmp) -nix-sources := $(shell fd -enix --exclude='spago*' -Etmp) -js-sources := $(shell fd -ejs -Etmp) +ps-sources := $(shell fd --no-ignore-parent -epurs) +nix-sources := $(shell fd --no-ignore-parent -enix --exclude='spago*') +js-sources := $(shell fd --no-ignore-parent -ejs) ps-entrypoint := Ctl.Examples.ByUrl # points to one of the example PureScript modules in examples/ ps-bundle = spago bundle-module -m ${ps-entrypoint} --to output.js preview-node-ipc = $(shell docker volume inspect store_node-preview-ipc | jq -r '.[0].Mountpoint') From d3c33d02d4fa672b64db37a2efa50532cdb8e844 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Fri, 16 Dec 2022 13:03:31 +0000 Subject: [PATCH 117/373] Remove ctl-server port from test-nixos-configuration.nix --- nix/test-nixos-configuration.nix | 1 - 1 file changed, 1 deletion(-) diff --git a/nix/test-nixos-configuration.nix b/nix/test-nixos-configuration.nix index 740eb69497..974f8214b0 100644 --- a/nix/test-nixos-configuration.nix +++ b/nix/test-nixos-configuration.nix @@ -8,7 +8,6 @@ forwardPorts = [ { from = "host"; host.port = 2222; guest.port = 22; } { from = "host"; host.port = 1337; guest.port = 1337; } - { from = "host"; host.port = 8081; guest.port = 8081; } { from = "host"; host.port = 9999; guest.port = 9999; } ]; }; From 44570053cedc5cbe16f937e2fa938bd21021636f Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Fri, 16 Dec 2022 14:32:05 +0100 Subject: [PATCH 118/373] BalanceTx: Fix bug in assignCoinsToChangeValues --- src/Internal/BalanceTx/BalanceTx.purs | 65 +++++++++++++++------------ 1 file changed, 36 insertions(+), 29 deletions(-) diff --git a/src/Internal/BalanceTx/BalanceTx.purs b/src/Internal/BalanceTx/BalanceTx.purs index 34a762edb9..dd6fbd55c1 100644 --- a/src/Internal/BalanceTx/BalanceTx.purs +++ b/src/Internal/BalanceTx/BalanceTx.purs @@ -141,7 +141,7 @@ import Data.Array.NonEmpty ) as NEArray import Data.BigInt (BigInt) import Data.Either (Either, note) -import Data.Foldable (fold, foldMap, foldr, length, sum) +import Data.Foldable (fold, foldMap, foldr, length, null, sum) import Data.Function (on) import Data.Lens.Getter ((^.)) import Data.Lens.Setter ((%~), (.~), (?~)) @@ -153,7 +153,7 @@ import Data.Newtype (class Newtype, unwrap, wrap) import Data.Set (Set) import Data.Set as Set import Data.Traversable (for, traverse) -import Data.Tuple (fst, snd) +import Data.Tuple (fst) import Data.Tuple.Nested (type (/\), (/\)) import Effect.Class (liftEffect) import Partial.Unsafe (unsafePartial) @@ -538,7 +538,9 @@ makeChangeForCoin weights excess = -- | the amount of ada is insufficient to cover them all. -- | -- | - continues dropping empty change maps from the start of the list until --- | it is possible to assign a minimum ada value to all remaining entries. +-- | it is possible to assign a minimum ada value to all remaining entries, +-- | or until only one entry remains (in which case it assigns a minimum +-- | ada value, even if the amount of ada is insufficient to cover it). -- | -- | - assigns the minimum ada quantity to all non-empty change `Value`s, even -- | if `adaAvailable` is insufficient, does not fail. @@ -551,48 +553,51 @@ assignCoinsToChangeValues -> NonEmptyArray (Value /\ BigInt) -> BalanceTxM (Array Value) assignCoinsToChangeValues changeAddress adaAvailable pairsAtStart = - flip worker pairsAtStart =<< adaRequiredAtStart + changeValuesAtStart <#> \changeValues -> + worker (adaRequiredAtStart changeValues) changeValues where - worker - :: BigInt - -> NonEmptyArray (Value /\ BigInt) - -> BalanceTxM (Array Value) + worker :: BigInt -> NonEmptyArray ChangeValue -> Array Value worker adaRequired = NEArray.uncons >>> case _ of - { head: pair, tail: [] } | noTokens pair && adaAvailable < adaRequired -> - pure mempty + { head: x, tail: xs } + | not (null xs) && adaAvailable < adaRequired && noTokens x -> + worker (adaRequired - x.minCoin) (fromArrayUnsafe xs) - { head: pair, tail: pairs } | noTokens pair && adaAvailable < adaRequired -> - minCoinFor (fst pair) >>= \minCoin -> - worker (adaRequired - minCoin) (fromArrayUnsafe pairs) - - { head, tail } -> do + { head: x, tail: xs } -> let - pairs :: NonEmptyArray (Value /\ BigInt) - pairs = NEArray.cons' head tail + changeValues :: NonEmptyArray ChangeValue + changeValues = NEArray.cons' x xs adaRemaining :: BigInt adaRemaining = max zero (adaAvailable - adaRequired) changeValuesForOutputCoins :: NonEmptyArray Value changeValuesForOutputCoins = - makeChangeForCoin (snd <$> pairs) adaRemaining - - changeValuesWithMinCoins <- traverse (assignMinimumCoin <<< fst) pairs - pure $ NEArray.toArray $ - NEArray.zipWith (<>) changeValuesWithMinCoins changeValuesForOutputCoins + makeChangeForCoin (_.outputAda <$> changeValues) adaRemaining + + changeValuesWithMinCoins :: NonEmptyArray Value + changeValuesWithMinCoins = assignMinCoin <$> changeValues + in + NEArray.toArray $ + NEArray.zipWith append changeValuesWithMinCoins + changeValuesForOutputCoins where - assignMinimumCoin :: Value -> BalanceTxM Value - assignMinimumCoin value@(Value _ assets) = - flip mkValue assets <<< wrap <$> minCoinFor value + noTokens :: ChangeValue -> Boolean + noTokens = null <<< Value.valueAssets <<< _.value + + assignMinCoin :: ChangeValue -> Value + assignMinCoin { value: (Value _ assets), minCoin } = + mkValue (wrap minCoin) assets fromArrayUnsafe :: forall (a :: Type). Array a -> NonEmptyArray a fromArrayUnsafe = unsafePartial fromJust <<< NEArray.fromArray - noTokens :: Value /\ BigInt -> Boolean - noTokens = Array.null <<< Value.valueAssets <<< fst + adaRequiredAtStart :: NonEmptyArray ChangeValue -> BigInt + adaRequiredAtStart = sum <<< map _.minCoin - adaRequiredAtStart :: BalanceTxM BigInt - adaRequiredAtStart = sum <$> traverse (minCoinFor <<< fst) pairsAtStart + changeValuesAtStart :: BalanceTxM (NonEmptyArray ChangeValue) + changeValuesAtStart = + for pairsAtStart \(value /\ outputAda) -> + { value, outputAda, minCoin: _ } <$> minCoinFor value minCoinFor :: Value -> BalanceTxM BigInt minCoinFor value = do @@ -601,6 +606,8 @@ assignCoinsToChangeValues changeAddress adaAvailable pairsAtStart = ExceptT $ liftEffect $ utxoMinAdaValue coinsPerUtxoUnit txOutput <#> note UtxoMinAdaValueCalculationFailed +type ChangeValue = { value :: Value, outputAda :: BigInt, minCoin :: BigInt } + newtype AssetCount = AssetCount Value derive instance Newtype AssetCount _ From 1ceb1ca012d16ac7cf33357e6e08270dbd65eae1 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Fri, 16 Dec 2022 13:54:51 +0000 Subject: [PATCH 119/373] Update template --- templates/ctl-scaffold/flake.lock | 3704 ++----------------------- templates/ctl-scaffold/flake.nix | 2 +- templates/ctl-scaffold/packages.dhall | 2 +- 3 files changed, 299 insertions(+), 3409 deletions(-) diff --git a/templates/ctl-scaffold/flake.lock b/templates/ctl-scaffold/flake.lock index 53ba37f525..cd3bb84e2a 100644 --- a/templates/ctl-scaffold/flake.lock +++ b/templates/ctl-scaffold/flake.lock @@ -52,23 +52,6 @@ } }, "CHaP_4": { - "flake": false, - "locked": { - "lastModified": 1666726035, - "narHash": "sha256-EBodp9DJb8Z+aVbuezVwLJ9Q9XIJUXFd/n2skay3FeU=", - "owner": "input-output-hk", - "repo": "cardano-haskell-packages", - "rev": "b074321c4c8cbf2c3789436ab11eaa43e1c441a7", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-haskell-packages", - "rev": "b074321c4c8cbf2c3789436ab11eaa43e1c441a7", - "type": "github" - } - }, - "CHaP_5": { "flake": false, "locked": { "lastModified": 1669289866, @@ -149,86 +132,6 @@ "type": "github" } }, - "HTTP_13": { - "flake": false, - "locked": { - "lastModified": 1451647621, - "narHash": "sha256-oHIyw3x0iKBexEo49YeUDV1k74ZtyYKGR2gNJXXRxts=", - "owner": "phadej", - "repo": "HTTP", - "rev": "9bc0996d412fef1787449d841277ef663ad9a915", - "type": "github" - }, - "original": { - "owner": "phadej", - "repo": "HTTP", - "type": "github" - } - }, - "HTTP_14": { - "flake": false, - "locked": { - "lastModified": 1451647621, - "narHash": "sha256-oHIyw3x0iKBexEo49YeUDV1k74ZtyYKGR2gNJXXRxts=", - "owner": "phadej", - "repo": "HTTP", - "rev": "9bc0996d412fef1787449d841277ef663ad9a915", - "type": "github" - }, - "original": { - "owner": "phadej", - "repo": "HTTP", - "type": "github" - } - }, - "HTTP_15": { - "flake": false, - "locked": { - "lastModified": 1451647621, - "narHash": "sha256-oHIyw3x0iKBexEo49YeUDV1k74ZtyYKGR2gNJXXRxts=", - "owner": "phadej", - "repo": "HTTP", - "rev": "9bc0996d412fef1787449d841277ef663ad9a915", - "type": "github" - }, - "original": { - "owner": "phadej", - "repo": "HTTP", - "type": "github" - } - }, - "HTTP_16": { - "flake": false, - "locked": { - "lastModified": 1451647621, - "narHash": "sha256-oHIyw3x0iKBexEo49YeUDV1k74ZtyYKGR2gNJXXRxts=", - "owner": "phadej", - "repo": "HTTP", - "rev": "9bc0996d412fef1787449d841277ef663ad9a915", - "type": "github" - }, - "original": { - "owner": "phadej", - "repo": "HTTP", - "type": "github" - } - }, - "HTTP_17": { - "flake": false, - "locked": { - "lastModified": 1451647621, - "narHash": "sha256-oHIyw3x0iKBexEo49YeUDV1k74ZtyYKGR2gNJXXRxts=", - "owner": "phadej", - "repo": "HTTP", - "rev": "9bc0996d412fef1787449d841277ef663ad9a915", - "type": "github" - }, - "original": { - "owner": "phadej", - "repo": "HTTP", - "type": "github" - } - }, "HTTP_2": { "flake": false, "locked": { @@ -432,42 +335,12 @@ "type": "github" } }, - "blank_6": { - "locked": { - "lastModified": 1625557891, - "narHash": "sha256-O8/MWsPBGhhyPoPLHZAuoZiiHo9q6FLlEeIDEXuj6T4=", - "owner": "divnix", - "repo": "blank", - "rev": "5a5d2684073d9f563072ed07c871d577a6c614a8", - "type": "github" - }, - "original": { - "owner": "divnix", - "repo": "blank", - "type": "github" - } - }, - "blank_7": { - "locked": { - "lastModified": 1625557891, - "narHash": "sha256-O8/MWsPBGhhyPoPLHZAuoZiiHo9q6FLlEeIDEXuj6T4=", - "owner": "divnix", - "repo": "blank", - "rev": "5a5d2684073d9f563072ed07c871d577a6c614a8", - "type": "github" - }, - "original": { - "owner": "divnix", - "repo": "blank", - "type": "github" - } - }, "bot-plutus-interface": { "inputs": { - "CHaP": "CHaP_5", - "flake-compat": "flake-compat_17", - "haskell-nix": "haskell-nix_5", - "iohk-nix": "iohk-nix_5", + "CHaP": "CHaP_4", + "flake-compat": "flake-compat_11", + "haskell-nix": "haskell-nix_4", + "iohk-nix": "iohk-nix_4", "nixpkgs": [ "ctl", "plutip", @@ -559,91 +432,6 @@ "type": "github" } }, - "cabal-32_13": { - "flake": false, - "locked": { - "lastModified": 1603716527, - "narHash": "sha256-sDbrmur9Zfp4mPKohCD8IDZfXJ0Tjxpmr2R+kg5PpSY=", - "owner": "haskell", - "repo": "cabal", - "rev": "94aaa8e4720081f9c75497e2735b90f6a819b08e", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.2", - "repo": "cabal", - "type": "github" - } - }, - "cabal-32_14": { - "flake": false, - "locked": { - "lastModified": 1603716527, - "narHash": "sha256-sDbrmur9Zfp4mPKohCD8IDZfXJ0Tjxpmr2R+kg5PpSY=", - "owner": "haskell", - "repo": "cabal", - "rev": "94aaa8e4720081f9c75497e2735b90f6a819b08e", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.2", - "repo": "cabal", - "type": "github" - } - }, - "cabal-32_15": { - "flake": false, - "locked": { - "lastModified": 1603716527, - "narHash": "sha256-sDbrmur9Zfp4mPKohCD8IDZfXJ0Tjxpmr2R+kg5PpSY=", - "owner": "haskell", - "repo": "cabal", - "rev": "94aaa8e4720081f9c75497e2735b90f6a819b08e", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.2", - "repo": "cabal", - "type": "github" - } - }, - "cabal-32_16": { - "flake": false, - "locked": { - "lastModified": 1603716527, - "narHash": "sha256-X0TFfdD4KZpwl0Zr6x+PLxUt/VyKQfX7ylXHdmZIL+w=", - "owner": "haskell", - "repo": "cabal", - "rev": "48bf10787e27364730dd37a42b603cee8d6af7ee", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.2", - "repo": "cabal", - "type": "github" - } - }, - "cabal-32_17": { - "flake": false, - "locked": { - "lastModified": 1603716527, - "narHash": "sha256-X0TFfdD4KZpwl0Zr6x+PLxUt/VyKQfX7ylXHdmZIL+w=", - "owner": "haskell", - "repo": "cabal", - "rev": "48bf10787e27364730dd37a42b603cee8d6af7ee", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.2", - "repo": "cabal", - "type": "github" - } - }, "cabal-32_2": { "flake": false, "locked": { @@ -848,14 +636,14 @@ "type": "github" } }, - "cabal-34_13": { + "cabal-34_2": { "flake": false, "locked": { - "lastModified": 1622475795, - "narHash": "sha256-chwTL304Cav+7p38d9mcb+egABWmxo2Aq+xgVBgEb/U=", + "lastModified": 1640353650, + "narHash": "sha256-N1t6M3/wqj90AEdRkeC8i923gQYUpzSr8b40qVOZ1Rk=", "owner": "haskell", "repo": "cabal", - "rev": "b086c1995cdd616fc8d91f46a21e905cc50a1049", + "rev": "942639c18c0cd8ec53e0a6f8d120091af35312cd", "type": "github" }, "original": { @@ -865,7 +653,7 @@ "type": "github" } }, - "cabal-34_14": { + "cabal-34_3": { "flake": false, "locked": { "lastModified": 1622475795, @@ -882,7 +670,7 @@ "type": "github" } }, - "cabal-34_15": { + "cabal-34_4": { "flake": false, "locked": { "lastModified": 1622475795, @@ -899,14 +687,14 @@ "type": "github" } }, - "cabal-34_16": { + "cabal-34_5": { "flake": false, "locked": { - "lastModified": 1640353650, - "narHash": "sha256-N1t6M3/wqj90AEdRkeC8i923gQYUpzSr8b40qVOZ1Rk=", + "lastModified": 1622475795, + "narHash": "sha256-chwTL304Cav+7p38d9mcb+egABWmxo2Aq+xgVBgEb/U=", "owner": "haskell", "repo": "cabal", - "rev": "942639c18c0cd8ec53e0a6f8d120091af35312cd", + "rev": "b086c1995cdd616fc8d91f46a21e905cc50a1049", "type": "github" }, "original": { @@ -916,7 +704,7 @@ "type": "github" } }, - "cabal-34_17": { + "cabal-34_6": { "flake": false, "locked": { "lastModified": 1640353650, @@ -933,7 +721,7 @@ "type": "github" } }, - "cabal-34_2": { + "cabal-34_7": { "flake": false, "locked": { "lastModified": 1640353650, @@ -950,7 +738,7 @@ "type": "github" } }, - "cabal-34_3": { + "cabal-34_8": { "flake": false, "locked": { "lastModified": 1622475795, @@ -967,7 +755,7 @@ "type": "github" } }, - "cabal-34_4": { + "cabal-34_9": { "flake": false, "locked": { "lastModified": 1622475795, @@ -984,206 +772,53 @@ "type": "github" } }, - "cabal-34_5": { + "cabal-36": { "flake": false, "locked": { - "lastModified": 1622475795, - "narHash": "sha256-chwTL304Cav+7p38d9mcb+egABWmxo2Aq+xgVBgEb/U=", + "lastModified": 1641652457, + "narHash": "sha256-BlFPKP4C4HRUJeAbdembX1Rms1LD380q9s0qVDeoAak=", "owner": "haskell", "repo": "cabal", - "rev": "b086c1995cdd616fc8d91f46a21e905cc50a1049", + "rev": "f27667f8ec360c475027dcaee0138c937477b070", "type": "github" }, "original": { "owner": "haskell", - "ref": "3.4", + "ref": "3.6", "repo": "cabal", "type": "github" } }, - "cabal-34_6": { + "cabal-36_10": { "flake": false, "locked": { - "lastModified": 1640353650, - "narHash": "sha256-N1t6M3/wqj90AEdRkeC8i923gQYUpzSr8b40qVOZ1Rk=", + "lastModified": 1641652457, + "narHash": "sha256-BlFPKP4C4HRUJeAbdembX1Rms1LD380q9s0qVDeoAak=", "owner": "haskell", "repo": "cabal", - "rev": "942639c18c0cd8ec53e0a6f8d120091af35312cd", + "rev": "f27667f8ec360c475027dcaee0138c937477b070", "type": "github" }, "original": { "owner": "haskell", - "ref": "3.4", + "ref": "3.6", "repo": "cabal", "type": "github" } }, - "cabal-34_7": { + "cabal-36_2": { "flake": false, "locked": { - "lastModified": 1640353650, - "narHash": "sha256-N1t6M3/wqj90AEdRkeC8i923gQYUpzSr8b40qVOZ1Rk=", + "lastModified": 1641652457, + "narHash": "sha256-BlFPKP4C4HRUJeAbdembX1Rms1LD380q9s0qVDeoAak=", "owner": "haskell", "repo": "cabal", - "rev": "942639c18c0cd8ec53e0a6f8d120091af35312cd", + "rev": "f27667f8ec360c475027dcaee0138c937477b070", "type": "github" }, "original": { "owner": "haskell", - "ref": "3.4", - "repo": "cabal", - "type": "github" - } - }, - "cabal-34_8": { - "flake": false, - "locked": { - "lastModified": 1622475795, - "narHash": "sha256-chwTL304Cav+7p38d9mcb+egABWmxo2Aq+xgVBgEb/U=", - "owner": "haskell", - "repo": "cabal", - "rev": "b086c1995cdd616fc8d91f46a21e905cc50a1049", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.4", - "repo": "cabal", - "type": "github" - } - }, - "cabal-34_9": { - "flake": false, - "locked": { - "lastModified": 1622475795, - "narHash": "sha256-chwTL304Cav+7p38d9mcb+egABWmxo2Aq+xgVBgEb/U=", - "owner": "haskell", - "repo": "cabal", - "rev": "b086c1995cdd616fc8d91f46a21e905cc50a1049", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.4", - "repo": "cabal", - "type": "github" - } - }, - "cabal-36": { - "flake": false, - "locked": { - "lastModified": 1641652457, - "narHash": "sha256-BlFPKP4C4HRUJeAbdembX1Rms1LD380q9s0qVDeoAak=", - "owner": "haskell", - "repo": "cabal", - "rev": "f27667f8ec360c475027dcaee0138c937477b070", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.6", - "repo": "cabal", - "type": "github" - } - }, - "cabal-36_10": { - "flake": false, - "locked": { - "lastModified": 1641652457, - "narHash": "sha256-BlFPKP4C4HRUJeAbdembX1Rms1LD380q9s0qVDeoAak=", - "owner": "haskell", - "repo": "cabal", - "rev": "f27667f8ec360c475027dcaee0138c937477b070", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.6", - "repo": "cabal", - "type": "github" - } - }, - "cabal-36_11": { - "flake": false, - "locked": { - "lastModified": 1640163203, - "narHash": "sha256-TwDWP2CffT0j40W6zr0J1Qbu+oh3nsF1lUx9446qxZM=", - "owner": "haskell", - "repo": "cabal", - "rev": "ecf418050c1821f25e2e218f1be94c31e0465df1", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.6", - "repo": "cabal", - "type": "github" - } - }, - "cabal-36_12": { - "flake": false, - "locked": { - "lastModified": 1640163203, - "narHash": "sha256-TwDWP2CffT0j40W6zr0J1Qbu+oh3nsF1lUx9446qxZM=", - "owner": "haskell", - "repo": "cabal", - "rev": "ecf418050c1821f25e2e218f1be94c31e0465df1", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.6", - "repo": "cabal", - "type": "github" - } - }, - "cabal-36_13": { - "flake": false, - "locked": { - "lastModified": 1641652457, - "narHash": "sha256-BlFPKP4C4HRUJeAbdembX1Rms1LD380q9s0qVDeoAak=", - "owner": "haskell", - "repo": "cabal", - "rev": "f27667f8ec360c475027dcaee0138c937477b070", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.6", - "repo": "cabal", - "type": "github" - } - }, - "cabal-36_14": { - "flake": false, - "locked": { - "lastModified": 1641652457, - "narHash": "sha256-BlFPKP4C4HRUJeAbdembX1Rms1LD380q9s0qVDeoAak=", - "owner": "haskell", - "repo": "cabal", - "rev": "f27667f8ec360c475027dcaee0138c937477b070", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.6", - "repo": "cabal", - "type": "github" - } - }, - "cabal-36_2": { - "flake": false, - "locked": { - "lastModified": 1641652457, - "narHash": "sha256-BlFPKP4C4HRUJeAbdembX1Rms1LD380q9s0qVDeoAak=", - "owner": "haskell", - "repo": "cabal", - "rev": "f27667f8ec360c475027dcaee0138c937477b070", - "type": "github" - }, - "original": { - "owner": "haskell", - "ref": "3.6", + "ref": "3.6", "repo": "cabal", "type": "github" } @@ -1340,22 +975,6 @@ } }, "cardano-configurations_3": { - "flake": false, - "locked": { - "lastModified": 1662514199, - "narHash": "sha256-Z71TP5nHA9ch4DRwftz8my5RwYOjH/xA/WlcJqUTtYY=", - "owner": "input-output-hk", - "repo": "cardano-configurations", - "rev": "182b16cb743867b0b24b7af92efbf427b2b09b52", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-configurations", - "type": "github" - } - }, - "cardano-configurations_4": { "flake": false, "locked": { "lastModified": 1667387423, @@ -1430,7 +1049,7 @@ }, "cardano-mainnet-mirror_4": { "inputs": { - "nixpkgs": "nixpkgs_13" + "nixpkgs": "nixpkgs_11" }, "locked": { "lastModified": 1642701714, @@ -1449,7 +1068,7 @@ }, "cardano-mainnet-mirror_5": { "inputs": { - "nixpkgs": "nixpkgs_15" + "nixpkgs": "nixpkgs_13" }, "locked": { "lastModified": 1642701714, @@ -1468,64 +1087,7 @@ }, "cardano-mainnet-mirror_6": { "inputs": { - "nixpkgs": "nixpkgs_16" - }, - "locked": { - "lastModified": 1642701714, - "narHash": "sha256-SR3luE+ePX6U193EKE/KSEuVzWAW0YsyPYDC4hOvALs=", - "owner": "input-output-hk", - "repo": "cardano-mainnet-mirror", - "rev": "819488be9eabbba6aaa7c931559bc584d8071e3d", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "ref": "nix", - "repo": "cardano-mainnet-mirror", - "type": "github" - } - }, - "cardano-mainnet-mirror_7": { - "inputs": { - "nixpkgs": "nixpkgs_21" - }, - "locked": { - "lastModified": 1642701714, - "narHash": "sha256-SR3luE+ePX6U193EKE/KSEuVzWAW0YsyPYDC4hOvALs=", - "owner": "input-output-hk", - "repo": "cardano-mainnet-mirror", - "rev": "819488be9eabbba6aaa7c931559bc584d8071e3d", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "ref": "nix", - "repo": "cardano-mainnet-mirror", - "type": "github" - } - }, - "cardano-mainnet-mirror_8": { - "inputs": { - "nixpkgs": "nixpkgs_23" - }, - "locked": { - "lastModified": 1642701714, - "narHash": "sha256-SR3luE+ePX6U193EKE/KSEuVzWAW0YsyPYDC4hOvALs=", - "owner": "input-output-hk", - "repo": "cardano-mainnet-mirror", - "rev": "819488be9eabbba6aaa7c931559bc584d8071e3d", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "ref": "nix", - "repo": "cardano-mainnet-mirror", - "type": "github" - } - }, - "cardano-mainnet-mirror_9": { - "inputs": { - "nixpkgs": "nixpkgs_24" + "nixpkgs": "nixpkgs_14" }, "locked": { "lastModified": 1642701714, @@ -1634,40 +1196,6 @@ "haskellNix": "haskellNix_7", "iohkNix": "iohkNix_7", "membench": "membench_4", - "nixpkgs": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "cardano-node", - "node-snapshot", - "membench", - "cardano-node-snapshot", - "haskellNix", - "nixpkgs-2105" - ], - "utils": "utils_6" - }, - "locked": { - "lastModified": 1644954571, - "narHash": "sha256-c6MM1mQoS/AnTIrwaRmITK4L4i9lLNtkjOUHiseBtUs=", - "owner": "input-output-hk", - "repo": "cardano-node", - "rev": "30d62b86e7b98da28ef8ad9412e4e00a1ba1231d", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-node", - "rev": "30d62b86e7b98da28ef8ad9412e4e00a1ba1231d", - "type": "github" - } - }, - "cardano-node-snapshot_3": { - "inputs": { - "customConfig": "customConfig_11", - "haskellNix": "haskellNix_11", - "iohkNix": "iohkNix_11", - "membench": "membench_6", "nixpkgs": [ "ctl", "ogmios-nixos", @@ -1678,7 +1206,7 @@ "haskellNix", "nixpkgs-2105" ], - "utils": "utils_11" + "utils": "utils_6" }, "locked": { "lastModified": 1644954571, @@ -1700,18 +1228,16 @@ "cardano-mainnet-mirror": "cardano-mainnet-mirror_4", "cardano-node-workbench": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "blank" ], "customConfig": "customConfig_5", - "flake-compat": "flake-compat_9", + "flake-compat": "flake-compat_7", "hackageNix": "hackageNix_2", "haskellNix": "haskellNix_5", "hostNixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "nixpkgs" ], @@ -1719,16 +1245,14 @@ "nixTools": "nixTools_2", "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "haskellNix", "nixpkgs-unstable" ], "node-measured": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "blank" ], "node-process": "node-process_2", @@ -1751,58 +1275,6 @@ "type": "github" } }, - "cardano-node_3": { - "inputs": { - "cardano-mainnet-mirror": "cardano-mainnet-mirror_7", - "cardano-node-workbench": [ - "ctl", - "ogmios-nixos", - "blank" - ], - "customConfig": "customConfig_9", - "flake-compat": "flake-compat_13", - "hackageNix": "hackageNix_3", - "haskellNix": "haskellNix_9", - "hostNixpkgs": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "nixpkgs" - ], - "iohkNix": "iohkNix_9", - "nixTools": "nixTools_3", - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "haskellNix", - "nixpkgs-unstable" - ], - "node-measured": [ - "ctl", - "ogmios-nixos", - "blank" - ], - "node-process": "node-process_3", - "node-snapshot": "node-snapshot_3", - "plutus-apps": "plutus-apps_3", - "utils": "utils_14" - }, - "locked": { - "lastModified": 1659625017, - "narHash": "sha256-4IrheFeoWfvkZQndEk4fGUkOiOjcVhcyXZ6IqmvkDgg=", - "owner": "input-output-hk", - "repo": "cardano-node", - "rev": "950c4e222086fed5ca53564e642434ce9307b0b9", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "ref": "1.35.3", - "repo": "cardano-node", - "type": "github" - } - }, "cardano-shell": { "flake": false, "locked": { @@ -1867,86 +1339,6 @@ "type": "github" } }, - "cardano-shell_13": { - "flake": false, - "locked": { - "lastModified": 1608537748, - "narHash": "sha256-PulY1GfiMgKVnBci3ex4ptk2UNYMXqGjJOxcPy2KYT4=", - "owner": "input-output-hk", - "repo": "cardano-shell", - "rev": "9392c75087cb9a3d453998f4230930dea3a95725", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-shell", - "type": "github" - } - }, - "cardano-shell_14": { - "flake": false, - "locked": { - "lastModified": 1608537748, - "narHash": "sha256-PulY1GfiMgKVnBci3ex4ptk2UNYMXqGjJOxcPy2KYT4=", - "owner": "input-output-hk", - "repo": "cardano-shell", - "rev": "9392c75087cb9a3d453998f4230930dea3a95725", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-shell", - "type": "github" - } - }, - "cardano-shell_15": { - "flake": false, - "locked": { - "lastModified": 1608537748, - "narHash": "sha256-PulY1GfiMgKVnBci3ex4ptk2UNYMXqGjJOxcPy2KYT4=", - "owner": "input-output-hk", - "repo": "cardano-shell", - "rev": "9392c75087cb9a3d453998f4230930dea3a95725", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-shell", - "type": "github" - } - }, - "cardano-shell_16": { - "flake": false, - "locked": { - "lastModified": 1608537748, - "narHash": "sha256-PulY1GfiMgKVnBci3ex4ptk2UNYMXqGjJOxcPy2KYT4=", - "owner": "input-output-hk", - "repo": "cardano-shell", - "rev": "9392c75087cb9a3d453998f4230930dea3a95725", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-shell", - "type": "github" - } - }, - "cardano-shell_17": { - "flake": false, - "locked": { - "lastModified": 1608537748, - "narHash": "sha256-PulY1GfiMgKVnBci3ex4ptk2UNYMXqGjJOxcPy2KYT4=", - "owner": "input-output-hk", - "repo": "cardano-shell", - "rev": "9392c75087cb9a3d453998f4230930dea3a95725", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-shell", - "type": "github" - } - }, "cardano-shell_2": { "flake": false, "locked": { @@ -2109,23 +1501,21 @@ "nixpkgs" ], "ogmios": "ogmios", - "ogmios-datum-cache": "ogmios-datum-cache", - "ogmios-datum-cache-nixos": "ogmios-datum-cache-nixos", "ogmios-nixos": "ogmios-nixos", "plutip": "plutip" }, "locked": { - "lastModified": 1671132140, - "narHash": "sha256-E9TBfAZGU18vM5L3jc44g102X4Z0q/FHS1A15ARc2n0=", + "lastModified": 1671198807, + "narHash": "sha256-/7MEP4t14HvJ0Hy198wRRz1cyfcFXzggyko2O6PAd+U=", "owner": "Plutonomicon", "repo": "cardano-transaction-lib", - "rev": "27f997461fda4a6f7eb52f1165a91d7d453fb990", + "rev": "001b639606f341489968d599fb0cef2900aeb474", "type": "github" }, "original": { "owner": "Plutonomicon", "repo": "cardano-transaction-lib", - "rev": "27f997461fda4a6f7eb52f1165a91d7d453fb990", + "rev": "001b639606f341489968d599fb0cef2900aeb474", "type": "github" } }, @@ -2144,51 +1534,6 @@ "type": "github" } }, - "customConfig_10": { - "locked": { - "lastModified": 1630400035, - "narHash": "sha256-MWaVOCzuFwp09wZIW9iHq5wWen5C69I940N1swZLEQ0=", - "owner": "input-output-hk", - "repo": "empty-flake", - "rev": "2040a05b67bf9a669ce17eca56beb14b4206a99a", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "empty-flake", - "type": "github" - } - }, - "customConfig_11": { - "locked": { - "lastModified": 1630400035, - "narHash": "sha256-MWaVOCzuFwp09wZIW9iHq5wWen5C69I940N1swZLEQ0=", - "owner": "input-output-hk", - "repo": "empty-flake", - "rev": "2040a05b67bf9a669ce17eca56beb14b4206a99a", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "empty-flake", - "type": "github" - } - }, - "customConfig_12": { - "locked": { - "lastModified": 1630400035, - "narHash": "sha256-MWaVOCzuFwp09wZIW9iHq5wWen5C69I940N1swZLEQ0=", - "owner": "input-output-hk", - "repo": "empty-flake", - "rev": "2040a05b67bf9a669ce17eca56beb14b4206a99a", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "empty-flake", - "type": "github" - } - }, "customConfig_2": { "locked": { "lastModified": 1630400035, @@ -2294,21 +1639,6 @@ "type": "github" } }, - "customConfig_9": { - "locked": { - "lastModified": 1630400035, - "narHash": "sha256-MWaVOCzuFwp09wZIW9iHq5wWen5C69I940N1swZLEQ0=", - "owner": "input-output-hk", - "repo": "empty-flake", - "rev": "2040a05b67bf9a669ce17eca56beb14b4206a99a", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "empty-flake", - "type": "github" - } - }, "devshell": { "inputs": { "flake-utils": [ @@ -2343,41 +1673,6 @@ } }, "devshell_2": { - "inputs": { - "flake-utils": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "std", - "flake-utils" - ], - "nixpkgs": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "std", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1663445644, - "narHash": "sha256-+xVlcK60x7VY1vRJbNUEAHi17ZuoQxAIH4S4iUFUGBA=", - "owner": "numtide", - "repo": "devshell", - "rev": "e3dc3e21594fe07bdb24bdf1c8657acaa4cb8f66", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "devshell", - "type": "github" - } - }, - "devshell_3": { "inputs": { "flake-utils": [ "ctl", @@ -2410,7 +1705,7 @@ "type": "github" } }, - "devshell_4": { + "devshell_3": { "inputs": { "flake-utils": [ "ctl", @@ -2479,41 +1774,6 @@ } }, "dmerge_2": { - "inputs": { - "nixlib": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "std", - "nixpkgs" - ], - "yants": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "std", - "yants" - ] - }, - "locked": { - "lastModified": 1659548052, - "narHash": "sha256-fzI2gp1skGA8mQo/FBFrUAtY0GQkAIAaV/V127TJPyY=", - "owner": "divnix", - "repo": "data-merge", - "rev": "d160d18ce7b1a45b88344aa3f13ed1163954b497", - "type": "github" - }, - "original": { - "owner": "divnix", - "repo": "data-merge", - "type": "github" - } - }, - "dmerge_3": { "inputs": { "nixlib": [ "ctl", @@ -2546,7 +1806,7 @@ "type": "github" } }, - "dmerge_4": { + "dmerge_3": { "inputs": { "nixlib": [ "ctl", @@ -2631,6 +1891,22 @@ } }, "flake-compat_11": { + "flake": false, + "locked": { + "lastModified": 1668681692, + "narHash": "sha256-Ht91NGdewz8IQLtWZ9LCeNXMSXHUss+9COoqu6JLmXU=", + "owner": "edolstra", + "repo": "flake-compat", + "rev": "009399224d5e398d03b22badca40a37ac85412a1", + "type": "github" + }, + "original": { + "owner": "edolstra", + "repo": "flake-compat", + "type": "github" + } + }, + "flake-compat_12": { "flake": false, "locked": { "lastModified": 1635892615, @@ -2646,7 +1922,7 @@ "type": "github" } }, - "flake-compat_12": { + "flake-compat_13": { "flake": false, "locked": { "lastModified": 1650374568, @@ -2662,31 +1938,14 @@ "type": "github" } }, - "flake-compat_13": { - "flake": false, - "locked": { - "lastModified": 1647532380, - "narHash": "sha256-wswAxyO8AJTH7d5oU8VK82yBCpqwA+p6kLgpb1f1PAY=", - "owner": "input-output-hk", - "repo": "flake-compat", - "rev": "7da118186435255a30b5ffeabba9629c344c0bec", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "ref": "fixes", - "repo": "flake-compat", - "type": "github" - } - }, "flake-compat_14": { "flake": false, "locked": { - "lastModified": 1650374568, - "narHash": "sha256-Z+s0J8/r907g149rllvwhb4pKi8Wam5ij0st8PwAh+E=", + "lastModified": 1668681692, + "narHash": "sha256-Ht91NGdewz8IQLtWZ9LCeNXMSXHUss+9COoqu6JLmXU=", "owner": "edolstra", "repo": "flake-compat", - "rev": "b4a34015c698c7793d592d66adbab377907a2be8", + "rev": "009399224d5e398d03b22badca40a37ac85412a1", "type": "github" }, "original": { @@ -2696,38 +1955,6 @@ } }, "flake-compat_15": { - "flake": false, - "locked": { - "lastModified": 1635892615, - "narHash": "sha256-harGbMZr4hzat2BWBU+Y5OYXlu+fVz7E4WeQzHi5o8A=", - "owner": "input-output-hk", - "repo": "flake-compat", - "rev": "eca47d3377946315596da653862d341ee5341318", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "flake-compat", - "type": "github" - } - }, - "flake-compat_16": { - "flake": false, - "locked": { - "lastModified": 1650374568, - "narHash": "sha256-Z+s0J8/r907g149rllvwhb4pKi8Wam5ij0st8PwAh+E=", - "owner": "edolstra", - "repo": "flake-compat", - "rev": "b4a34015c698c7793d592d66adbab377907a2be8", - "type": "github" - }, - "original": { - "owner": "edolstra", - "repo": "flake-compat", - "type": "github" - } - }, - "flake-compat_17": { "flake": false, "locked": { "lastModified": 1668681692, @@ -2743,38 +1970,6 @@ "type": "github" } }, - "flake-compat_18": { - "flake": false, - "locked": { - "lastModified": 1635892615, - "narHash": "sha256-harGbMZr4hzat2BWBU+Y5OYXlu+fVz7E4WeQzHi5o8A=", - "owner": "input-output-hk", - "repo": "flake-compat", - "rev": "eca47d3377946315596da653862d341ee5341318", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "flake-compat", - "type": "github" - } - }, - "flake-compat_19": { - "flake": false, - "locked": { - "lastModified": 1650374568, - "narHash": "sha256-Z+s0J8/r907g149rllvwhb4pKi8Wam5ij0st8PwAh+E=", - "owner": "edolstra", - "repo": "flake-compat", - "rev": "b4a34015c698c7793d592d66adbab377907a2be8", - "type": "github" - }, - "original": { - "owner": "edolstra", - "repo": "flake-compat", - "type": "github" - } - }, "flake-compat_2": { "flake": false, "locked": { @@ -2792,38 +1987,6 @@ "type": "github" } }, - "flake-compat_20": { - "flake": false, - "locked": { - "lastModified": 1668681692, - "narHash": "sha256-Ht91NGdewz8IQLtWZ9LCeNXMSXHUss+9COoqu6JLmXU=", - "owner": "edolstra", - "repo": "flake-compat", - "rev": "009399224d5e398d03b22badca40a37ac85412a1", - "type": "github" - }, - "original": { - "owner": "edolstra", - "repo": "flake-compat", - "type": "github" - } - }, - "flake-compat_21": { - "flake": false, - "locked": { - "lastModified": 1668681692, - "narHash": "sha256-Ht91NGdewz8IQLtWZ9LCeNXMSXHUss+9COoqu6JLmXU=", - "owner": "edolstra", - "repo": "flake-compat", - "rev": "009399224d5e398d03b22badca40a37ac85412a1", - "type": "github" - }, - "original": { - "owner": "edolstra", - "repo": "flake-compat", - "type": "github" - } - }, "flake-compat_3": { "flake": false, "locked": { @@ -2891,15 +2054,16 @@ "flake-compat_7": { "flake": false, "locked": { - "lastModified": 1650374568, - "narHash": "sha256-Z+s0J8/r907g149rllvwhb4pKi8Wam5ij0st8PwAh+E=", - "owner": "edolstra", + "lastModified": 1647532380, + "narHash": "sha256-wswAxyO8AJTH7d5oU8VK82yBCpqwA+p6kLgpb1f1PAY=", + "owner": "input-output-hk", "repo": "flake-compat", - "rev": "b4a34015c698c7793d592d66adbab377907a2be8", + "rev": "7da118186435255a30b5ffeabba9629c344c0bec", "type": "github" }, "original": { - "owner": "edolstra", + "owner": "input-output-hk", + "ref": "fixes", "repo": "flake-compat", "type": "github" } @@ -2923,16 +2087,15 @@ "flake-compat_9": { "flake": false, "locked": { - "lastModified": 1647532380, - "narHash": "sha256-wswAxyO8AJTH7d5oU8VK82yBCpqwA+p6kLgpb1f1PAY=", + "lastModified": 1635892615, + "narHash": "sha256-harGbMZr4hzat2BWBU+Y5OYXlu+fVz7E4WeQzHi5o8A=", "owner": "input-output-hk", "repo": "flake-compat", - "rev": "7da118186435255a30b5ffeabba9629c344c0bec", + "rev": "eca47d3377946315596da653862d341ee5341318", "type": "github" }, "original": { "owner": "input-output-hk", - "ref": "fixes", "repo": "flake-compat", "type": "github" } @@ -3118,66 +2281,6 @@ } }, "flake-utils_20": { - "locked": { - "lastModified": 1623875721, - "narHash": "sha256-A8BU7bjS5GirpAUv4QA+QnJ4CceLHkcXdRp4xITDB0s=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "f7e004a55b120c02ecb6219596820fcd32ca8772", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "flake-utils_21": { - "locked": { - "lastModified": 1623875721, - "narHash": "sha256-A8BU7bjS5GirpAUv4QA+QnJ4CceLHkcXdRp4xITDB0s=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "f7e004a55b120c02ecb6219596820fcd32ca8772", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "flake-utils_22": { - "locked": { - "lastModified": 1623875721, - "narHash": "sha256-A8BU7bjS5GirpAUv4QA+QnJ4CceLHkcXdRp4xITDB0s=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "f7e004a55b120c02ecb6219596820fcd32ca8772", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "flake-utils_23": { - "locked": { - "lastModified": 1644229661, - "narHash": "sha256-1YdnJAsNy69bpcjuoKdOYQX0YxZBiCYZo4Twxerqv7k=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "3cecb5b042f7f209c56ffd8371b2711a290ec797", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "flake-utils_24": { "locked": { "lastModified": 1653893745, "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", @@ -3192,7 +2295,7 @@ "type": "github" } }, - "flake-utils_25": { + "flake-utils_21": { "locked": { "lastModified": 1659877975, "narHash": "sha256-zllb8aq3YO3h8B/U0/J1WBgAL8EX5yWf5pMj3G0NAmc=", @@ -3207,37 +2310,7 @@ "type": "github" } }, - "flake-utils_26": { - "locked": { - "lastModified": 1653893745, - "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "1ed9fb1935d260de5fe1c2f7ee0ebaae17ed2fa1", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "flake-utils_27": { - "locked": { - "lastModified": 1644229661, - "narHash": "sha256-1YdnJAsNy69bpcjuoKdOYQX0YxZBiCYZo4Twxerqv7k=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "3cecb5b042f7f209c56ffd8371b2711a290ec797", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "flake-utils_28": { + "flake-utils_22": { "locked": { "lastModified": 1653893745, "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", @@ -3252,21 +2325,6 @@ "type": "github" } }, - "flake-utils_29": { - "locked": { - "lastModified": 1659877975, - "narHash": "sha256-zllb8aq3YO3h8B/U0/J1WBgAL8EX5yWf5pMj3G0NAmc=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "c0e246b9b83f637f4681389ecabcb2681b4f3af0", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, "flake-utils_3": { "locked": { "lastModified": 1644229661, @@ -3282,21 +2340,6 @@ "type": "github" } }, - "flake-utils_30": { - "locked": { - "lastModified": 1653893745, - "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "1ed9fb1935d260de5fe1c2f7ee0ebaae17ed2fa1", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, "flake-utils_4": { "locked": { "lastModified": 1623875721, @@ -3455,7 +2498,7 @@ "type": "github" } }, - "ghc-8.6.5-iohk_13": { + "ghc-8.6.5-iohk_2": { "flake": false, "locked": { "lastModified": 1600920045, @@ -3472,7 +2515,7 @@ "type": "github" } }, - "ghc-8.6.5-iohk_14": { + "ghc-8.6.5-iohk_3": { "flake": false, "locked": { "lastModified": 1600920045, @@ -3489,7 +2532,7 @@ "type": "github" } }, - "ghc-8.6.5-iohk_15": { + "ghc-8.6.5-iohk_4": { "flake": false, "locked": { "lastModified": 1600920045, @@ -3506,7 +2549,7 @@ "type": "github" } }, - "ghc-8.6.5-iohk_16": { + "ghc-8.6.5-iohk_5": { "flake": false, "locked": { "lastModified": 1600920045, @@ -3523,7 +2566,7 @@ "type": "github" } }, - "ghc-8.6.5-iohk_17": { + "ghc-8.6.5-iohk_6": { "flake": false, "locked": { "lastModified": 1600920045, @@ -3540,92 +2583,7 @@ "type": "github" } }, - "ghc-8.6.5-iohk_2": { - "flake": false, - "locked": { - "lastModified": 1600920045, - "narHash": "sha256-DO6kxJz248djebZLpSzTGD6s8WRpNI9BTwUeOf5RwY8=", - "owner": "input-output-hk", - "repo": "ghc", - "rev": "95713a6ecce4551240da7c96b6176f980af75cae", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "ref": "release/8.6.5-iohk", - "repo": "ghc", - "type": "github" - } - }, - "ghc-8.6.5-iohk_3": { - "flake": false, - "locked": { - "lastModified": 1600920045, - "narHash": "sha256-DO6kxJz248djebZLpSzTGD6s8WRpNI9BTwUeOf5RwY8=", - "owner": "input-output-hk", - "repo": "ghc", - "rev": "95713a6ecce4551240da7c96b6176f980af75cae", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "ref": "release/8.6.5-iohk", - "repo": "ghc", - "type": "github" - } - }, - "ghc-8.6.5-iohk_4": { - "flake": false, - "locked": { - "lastModified": 1600920045, - "narHash": "sha256-DO6kxJz248djebZLpSzTGD6s8WRpNI9BTwUeOf5RwY8=", - "owner": "input-output-hk", - "repo": "ghc", - "rev": "95713a6ecce4551240da7c96b6176f980af75cae", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "ref": "release/8.6.5-iohk", - "repo": "ghc", - "type": "github" - } - }, - "ghc-8.6.5-iohk_5": { - "flake": false, - "locked": { - "lastModified": 1600920045, - "narHash": "sha256-DO6kxJz248djebZLpSzTGD6s8WRpNI9BTwUeOf5RwY8=", - "owner": "input-output-hk", - "repo": "ghc", - "rev": "95713a6ecce4551240da7c96b6176f980af75cae", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "ref": "release/8.6.5-iohk", - "repo": "ghc", - "type": "github" - } - }, - "ghc-8.6.5-iohk_6": { - "flake": false, - "locked": { - "lastModified": 1600920045, - "narHash": "sha256-DO6kxJz248djebZLpSzTGD6s8WRpNI9BTwUeOf5RwY8=", - "owner": "input-output-hk", - "repo": "ghc", - "rev": "95713a6ecce4551240da7c96b6176f980af75cae", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "ref": "release/8.6.5-iohk", - "repo": "ghc", - "type": "github" - } - }, - "ghc-8.6.5-iohk_7": { + "ghc-8.6.5-iohk_7": { "flake": false, "locked": { "lastModified": 1600920045, @@ -3697,7 +2655,7 @@ }, "gomod2nix_2": { "inputs": { - "nixpkgs": "nixpkgs_18", + "nixpkgs": "nixpkgs_16", "utils": "utils_10" }, "locked": { @@ -3716,27 +2674,8 @@ }, "gomod2nix_3": { "inputs": { - "nixpkgs": "nixpkgs_26", - "utils": "utils_15" - }, - "locked": { - "lastModified": 1655245309, - "narHash": "sha256-d/YPoQ/vFn1+GTmSdvbSBSTOai61FONxB4+Lt6w/IVI=", - "owner": "tweag", - "repo": "gomod2nix", - "rev": "40d32f82fc60d66402eb0972e6e368aeab3faf58", - "type": "github" - }, - "original": { - "owner": "tweag", - "repo": "gomod2nix", - "type": "github" - } - }, - "gomod2nix_4": { - "inputs": { - "nixpkgs": "nixpkgs_30", - "utils": "utils_16" + "nixpkgs": "nixpkgs_20", + "utils": "utils_11" }, "locked": { "lastModified": 1655245309, @@ -3800,87 +2739,7 @@ "type": "github" } }, - "hackageNix_3": { - "flake": false, - "locked": { - "lastModified": 1656898050, - "narHash": "sha256-jemAb/Wm/uT+QhV12GlyeA5euSWxYzr2HOYoK4MZps0=", - "owner": "input-output-hk", - "repo": "hackage.nix", - "rev": "4f1dd530219ca1165f523ffb2c62213ebede4046", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "hackage.nix", - "type": "github" - } - }, "hackage_10": { - "flake": false, - "locked": { - "lastModified": 1643073363, - "narHash": "sha256-66oSXQKEDIOSQ2uKAS9facCX/Zuh/jFgyFDtxEqN9sk=", - "owner": "input-output-hk", - "repo": "hackage.nix", - "rev": "4ef9bd3a32316ce236164c7ebff00ebeb33236e2", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "hackage.nix", - "type": "github" - } - }, - "hackage_11": { - "flake": false, - "locked": { - "lastModified": 1643073363, - "narHash": "sha256-66oSXQKEDIOSQ2uKAS9facCX/Zuh/jFgyFDtxEqN9sk=", - "owner": "input-output-hk", - "repo": "hackage.nix", - "rev": "4ef9bd3a32316ce236164c7ebff00ebeb33236e2", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "hackage.nix", - "type": "github" - } - }, - "hackage_12": { - "flake": false, - "locked": { - "lastModified": 1639098768, - "narHash": "sha256-DZ4sG8FeDxWvBLixrj0jELXjtebZ0SCCPmQW43HNzIE=", - "owner": "input-output-hk", - "repo": "hackage.nix", - "rev": "c7b123af6b0b9b364cab03363504d42dca16a4b5", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "hackage.nix", - "type": "github" - } - }, - "hackage_13": { - "flake": false, - "locked": { - "lastModified": 1667783503, - "narHash": "sha256-25ZZPMQi9YQbXz3tZYPECVUI0FAQkJcDUIA/v8+mo9E=", - "owner": "input-output-hk", - "repo": "hackage.nix", - "rev": "1f77f69e6dd92b5130cbe681b74e8fc0d29d63ff", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "hackage.nix", - "type": "github" - } - }, - "hackage_14": { "flake": false, "locked": { "lastModified": 1669338728, @@ -4115,7 +2974,7 @@ "cabal-34": "cabal-34_11", "cabal-36": "cabal-36_9", "cardano-shell": "cardano-shell_11", - "flake-compat": "flake-compat_11", + "flake-compat": "flake-compat_9", "flake-utils": "flake-utils_15", "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_11", "hackage": "hackage_9", @@ -4123,8 +2982,7 @@ "hydra": "hydra_5", "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "nixpkgs" ], "nixpkgs-2003": "nixpkgs-2003_11", @@ -4152,72 +3010,31 @@ }, "haskell-nix_4": { "inputs": { - "HTTP": "HTTP_16", - "cabal-32": "cabal-32_16", - "cabal-34": "cabal-34_16", - "cabal-36": "cabal-36_13", - "cardano-shell": "cardano-shell_16", - "flake-compat": "flake-compat_15", - "flake-utils": "flake-utils_23", - "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_16", - "hackage": "hackage_13", - "hpc-coveralls": "hpc-coveralls_16", - "hydra": "hydra_7", - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "nixpkgs" - ], - "nixpkgs-2003": "nixpkgs-2003_16", - "nixpkgs-2105": "nixpkgs-2105_16", - "nixpkgs-2111": "nixpkgs-2111_16", - "nixpkgs-2205": "nixpkgs-2205_4", - "nixpkgs-unstable": "nixpkgs-unstable_16", - "old-ghc-nix": "old-ghc-nix_16", - "stackage": "stackage_16", - "tullia": "tullia_3" - }, - "locked": { - "lastModified": 1667783630, - "narHash": "sha256-IzbvNxsOVxHJGY70qAzaEOPmz4Fw93+4qLFd2on/ZAc=", - "owner": "input-output-hk", - "repo": "haskell.nix", - "rev": "f1f330065199dc4eca017bc21de0c67bc46df393", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "haskell.nix", - "type": "github" - } - }, - "haskell-nix_5": { - "inputs": { - "HTTP": "HTTP_17", - "cabal-32": "cabal-32_17", - "cabal-34": "cabal-34_17", - "cabal-36": "cabal-36_14", - "cardano-shell": "cardano-shell_17", - "flake-compat": "flake-compat_18", - "flake-utils": "flake-utils_27", - "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_17", - "hackage": "hackage_14", - "hpc-coveralls": "hpc-coveralls_17", - "hydra": "hydra_8", + "HTTP": "HTTP_12", + "cabal-32": "cabal-32_12", + "cabal-34": "cabal-34_12", + "cabal-36": "cabal-36_10", + "cardano-shell": "cardano-shell_12", + "flake-compat": "flake-compat_12", + "flake-utils": "flake-utils_19", + "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_12", + "hackage": "hackage_10", + "hpc-coveralls": "hpc-coveralls_12", + "hydra": "hydra_6", "nixpkgs": [ "ctl", "plutip", "bot-plutus-interface", "nixpkgs" ], - "nixpkgs-2003": "nixpkgs-2003_17", - "nixpkgs-2105": "nixpkgs-2105_17", - "nixpkgs-2111": "nixpkgs-2111_17", - "nixpkgs-2205": "nixpkgs-2205_5", - "nixpkgs-unstable": "nixpkgs-unstable_17", - "old-ghc-nix": "old-ghc-nix_17", - "stackage": "stackage_17", - "tullia": "tullia_4" + "nixpkgs-2003": "nixpkgs-2003_12", + "nixpkgs-2105": "nixpkgs-2105_12", + "nixpkgs-2111": "nixpkgs-2111_12", + "nixpkgs-2205": "nixpkgs-2205_4", + "nixpkgs-unstable": "nixpkgs-unstable_12", + "old-ghc-nix": "old-ghc-nix_12", + "stackage": "stackage_12", + "tullia": "tullia_3" }, "locked": { "lastModified": 1669338917, @@ -4279,31 +3096,31 @@ "type": "github" } }, - "haskellNix_10": { + "haskellNix_2": { "inputs": { - "HTTP": "HTTP_13", - "cabal-32": "cabal-32_13", - "cabal-34": "cabal-34_13", - "cabal-36": "cabal-36_11", - "cardano-shell": "cardano-shell_13", - "flake-utils": "flake-utils_20", - "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_13", - "hackage": "hackage_10", - "hpc-coveralls": "hpc-coveralls_13", - "nix-tools": "nix-tools_10", + "HTTP": "HTTP_3", + "cabal-32": "cabal-32_3", + "cabal-34": "cabal-34_3", + "cabal-36": "cabal-36_3", + "cardano-shell": "cardano-shell_3", + "flake-utils": "flake-utils_4", + "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_3", + "hackage": "hackage_2", + "hpc-coveralls": "hpc-coveralls_3", + "nix-tools": "nix-tools_2", "nixpkgs": [ "ctl", - "ogmios-nixos", + "ogmios", "cardano-node", "node-snapshot", "nixpkgs" ], - "nixpkgs-2003": "nixpkgs-2003_13", - "nixpkgs-2105": "nixpkgs-2105_13", - "nixpkgs-2111": "nixpkgs-2111_13", - "nixpkgs-unstable": "nixpkgs-unstable_13", - "old-ghc-nix": "old-ghc-nix_13", - "stackage": "stackage_13" + "nixpkgs-2003": "nixpkgs-2003_3", + "nixpkgs-2105": "nixpkgs-2105_3", + "nixpkgs-2111": "nixpkgs-2111_3", + "nixpkgs-unstable": "nixpkgs-unstable_3", + "old-ghc-nix": "old-ghc-nix_3", + "stackage": "stackage_3" }, "locked": { "lastModified": 1643073543, @@ -4319,129 +3136,7 @@ "type": "github" } }, - "haskellNix_11": { - "inputs": { - "HTTP": "HTTP_14", - "cabal-32": "cabal-32_14", - "cabal-34": "cabal-34_14", - "cabal-36": "cabal-36_12", - "cardano-shell": "cardano-shell_14", - "flake-utils": "flake-utils_21", - "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_14", - "hackage": "hackage_11", - "hpc-coveralls": "hpc-coveralls_14", - "nix-tools": "nix-tools_11", - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "membench", - "cardano-node-snapshot", - "nixpkgs" - ], - "nixpkgs-2003": "nixpkgs-2003_14", - "nixpkgs-2105": "nixpkgs-2105_14", - "nixpkgs-2111": "nixpkgs-2111_14", - "nixpkgs-unstable": "nixpkgs-unstable_14", - "old-ghc-nix": "old-ghc-nix_14", - "stackage": "stackage_14" - }, - "locked": { - "lastModified": 1643073543, - "narHash": "sha256-g2l/KDWzMRTFRugNVcx3CPZeyA5BNcH9/zDiqFpprB4=", - "owner": "input-output-hk", - "repo": "haskell.nix", - "rev": "14f740c7c8f535581c30b1697018e389680e24cb", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "haskell.nix", - "type": "github" - } - }, - "haskellNix_12": { - "inputs": { - "HTTP": "HTTP_15", - "cabal-32": "cabal-32_15", - "cabal-34": "cabal-34_15", - "cardano-shell": "cardano-shell_15", - "flake-utils": "flake-utils_22", - "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_15", - "hackage": "hackage_12", - "hpc-coveralls": "hpc-coveralls_15", - "nix-tools": "nix-tools_12", - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "plutus-example", - "nixpkgs" - ], - "nixpkgs-2003": "nixpkgs-2003_15", - "nixpkgs-2105": "nixpkgs-2105_15", - "nixpkgs-2111": "nixpkgs-2111_15", - "nixpkgs-unstable": "nixpkgs-unstable_15", - "old-ghc-nix": "old-ghc-nix_15", - "stackage": "stackage_15" - }, - "locked": { - "lastModified": 1639098904, - "narHash": "sha256-7VrCNEaKGLm4pTOS11dt1dRL2033oqrNCfal0uONsqA=", - "owner": "input-output-hk", - "repo": "haskell.nix", - "rev": "b18c6ce0867fee77f12ecf41dc6c67f7a59d9826", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "haskell.nix", - "type": "github" - } - }, - "haskellNix_2": { - "inputs": { - "HTTP": "HTTP_3", - "cabal-32": "cabal-32_3", - "cabal-34": "cabal-34_3", - "cabal-36": "cabal-36_3", - "cardano-shell": "cardano-shell_3", - "flake-utils": "flake-utils_4", - "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_3", - "hackage": "hackage_2", - "hpc-coveralls": "hpc-coveralls_3", - "nix-tools": "nix-tools_2", - "nixpkgs": [ - "ctl", - "ogmios", - "cardano-node", - "node-snapshot", - "nixpkgs" - ], - "nixpkgs-2003": "nixpkgs-2003_3", - "nixpkgs-2105": "nixpkgs-2105_3", - "nixpkgs-2111": "nixpkgs-2111_3", - "nixpkgs-unstable": "nixpkgs-unstable_3", - "old-ghc-nix": "old-ghc-nix_3", - "stackage": "stackage_3" - }, - "locked": { - "lastModified": 1643073543, - "narHash": "sha256-g2l/KDWzMRTFRugNVcx3CPZeyA5BNcH9/zDiqFpprB4=", - "owner": "input-output-hk", - "repo": "haskell.nix", - "rev": "14f740c7c8f535581c30b1697018e389680e24cb", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "haskell.nix", - "type": "github" - } - }, - "haskellNix_3": { + "haskellNix_3": { "inputs": { "HTTP": "HTTP_4", "cabal-32": "cabal-32_4", @@ -4534,8 +3229,7 @@ "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_7", "hackage": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "hackageNix" ], @@ -4544,8 +3238,7 @@ "nix-tools": "nix-tools_5", "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "nixpkgs" ], @@ -4584,8 +3277,7 @@ "nix-tools": "nix-tools_6", "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "nixpkgs" @@ -4625,8 +3317,7 @@ "nix-tools": "nix-tools_7", "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "membench", @@ -4667,8 +3358,7 @@ "nix-tools": "nix-tools_8", "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "plutus-example", @@ -4695,51 +3385,6 @@ "type": "github" } }, - "haskellNix_9": { - "inputs": { - "HTTP": "HTTP_12", - "cabal-32": "cabal-32_12", - "cabal-34": "cabal-34_12", - "cabal-36": "cabal-36_10", - "cardano-shell": "cardano-shell_12", - "flake-utils": "flake-utils_19", - "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_12", - "hackage": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "hackageNix" - ], - "hpc-coveralls": "hpc-coveralls_12", - "hydra": "hydra_6", - "nix-tools": "nix-tools_9", - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "nixpkgs" - ], - "nixpkgs-2003": "nixpkgs-2003_12", - "nixpkgs-2105": "nixpkgs-2105_12", - "nixpkgs-2111": "nixpkgs-2111_12", - "nixpkgs-unstable": "nixpkgs-unstable_12", - "old-ghc-nix": "old-ghc-nix_12", - "stackage": "stackage_12" - }, - "locked": { - "lastModified": 1656898207, - "narHash": "sha256-hshNfCnrmhIvM4T+O0/JRZymsHmq9YiIJ4bpzNVTD98=", - "owner": "input-output-hk", - "repo": "haskell.nix", - "rev": "21230476adfef5fa77fb19fbda396f22006a02bc", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "haskell.nix", - "type": "github" - } - }, "hpc-coveralls": { "flake": false, "locked": { @@ -4804,86 +3449,6 @@ "type": "github" } }, - "hpc-coveralls_13": { - "flake": false, - "locked": { - "lastModified": 1607498076, - "narHash": "sha256-8uqsEtivphgZWYeUo5RDUhp6bO9j2vaaProQxHBltQk=", - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "rev": "14df0f7d229f4cd2e79f8eabb1a740097fdfa430", - "type": "github" - }, - "original": { - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "type": "github" - } - }, - "hpc-coveralls_14": { - "flake": false, - "locked": { - "lastModified": 1607498076, - "narHash": "sha256-8uqsEtivphgZWYeUo5RDUhp6bO9j2vaaProQxHBltQk=", - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "rev": "14df0f7d229f4cd2e79f8eabb1a740097fdfa430", - "type": "github" - }, - "original": { - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "type": "github" - } - }, - "hpc-coveralls_15": { - "flake": false, - "locked": { - "lastModified": 1607498076, - "narHash": "sha256-8uqsEtivphgZWYeUo5RDUhp6bO9j2vaaProQxHBltQk=", - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "rev": "14df0f7d229f4cd2e79f8eabb1a740097fdfa430", - "type": "github" - }, - "original": { - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "type": "github" - } - }, - "hpc-coveralls_16": { - "flake": false, - "locked": { - "lastModified": 1607498076, - "narHash": "sha256-8uqsEtivphgZWYeUo5RDUhp6bO9j2vaaProQxHBltQk=", - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "rev": "14df0f7d229f4cd2e79f8eabb1a740097fdfa430", - "type": "github" - }, - "original": { - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "type": "github" - } - }, - "hpc-coveralls_17": { - "flake": false, - "locked": { - "lastModified": 1607498076, - "narHash": "sha256-8uqsEtivphgZWYeUo5RDUhp6bO9j2vaaProQxHBltQk=", - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "rev": "14df0f7d229f4cd2e79f8eabb1a740097fdfa430", - "type": "github" - }, - "original": { - "owner": "sevanspowell", - "repo": "hpc-coveralls", - "type": "github" - } - }, "hpc-coveralls_2": { "flake": false, "locked": { @@ -5093,8 +3658,7 @@ "nix": "nix_4", "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "haskellNix", "hydra", @@ -5120,8 +3684,7 @@ "nix": "nix_5", "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "haskell-nix", "hydra", "nix", @@ -5146,9 +3709,9 @@ "nix": "nix_6", "nixpkgs": [ "ctl", - "ogmios-nixos", - "cardano-node", - "haskellNix", + "plutip", + "bot-plutus-interface", + "haskell-nix", "hydra", "nix", "nixpkgs" @@ -5167,84 +3730,33 @@ "type": "indirect" } }, - "hydra_7": { + "iohk-nix": { "inputs": { - "nix": "nix_7", "nixpkgs": [ "ctl", - "ogmios-nixos", + "kupo-nixos", "haskell-nix", - "hydra", - "nix", "nixpkgs" ] }, "locked": { - "lastModified": 1646878427, - "narHash": "sha256-KtbrofMtN8GlM7D+n90kixr7QpSlVmdN+vK5CA/aRzc=", - "owner": "NixOS", - "repo": "hydra", - "rev": "28b682b85b7efc5cf7974065792a1f22203a5927", + "lastModified": 1653579289, + "narHash": "sha256-wveDdPsgB/3nAGAdFaxrcgLEpdi0aJ5kEVNtI+YqVfo=", + "owner": "input-output-hk", + "repo": "iohk-nix", + "rev": "edb2d2df2ebe42bbdf03a0711115cf6213c9d366", "type": "github" }, "original": { - "id": "hydra", - "type": "indirect" + "owner": "input-output-hk", + "repo": "iohk-nix", + "rev": "edb2d2df2ebe42bbdf03a0711115cf6213c9d366", + "type": "github" } }, - "hydra_8": { + "iohk-nix-environments": { "inputs": { - "nix": "nix_8", - "nixpkgs": [ - "ctl", - "plutip", - "bot-plutus-interface", - "haskell-nix", - "hydra", - "nix", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1646878427, - "narHash": "sha256-KtbrofMtN8GlM7D+n90kixr7QpSlVmdN+vK5CA/aRzc=", - "owner": "NixOS", - "repo": "hydra", - "rev": "28b682b85b7efc5cf7974065792a1f22203a5927", - "type": "github" - }, - "original": { - "id": "hydra", - "type": "indirect" - } - }, - "iohk-nix": { - "inputs": { - "nixpkgs": [ - "ctl", - "kupo-nixos", - "haskell-nix", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1653579289, - "narHash": "sha256-wveDdPsgB/3nAGAdFaxrcgLEpdi0aJ5kEVNtI+YqVfo=", - "owner": "input-output-hk", - "repo": "iohk-nix", - "rev": "edb2d2df2ebe42bbdf03a0711115cf6213c9d366", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "iohk-nix", - "rev": "edb2d2df2ebe42bbdf03a0711115cf6213c9d366", - "type": "github" - } - }, - "iohk-nix-environments": { - "inputs": { - "nixpkgs": "nixpkgs" + "nixpkgs": "nixpkgs" }, "locked": { "lastModified": 1670489000, @@ -5283,30 +3795,6 @@ } }, "iohk-nix_3": { - "inputs": { - "nixpkgs": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1649070135, - "narHash": "sha256-UFKqcOSdPWk3TYUCPHF22p1zf7aXQpCmmgf7UMg7fWA=", - "owner": "input-output-hk", - "repo": "iohk-nix", - "rev": "cecab9c71d1064f05f1615eead56ac0b9196bc20", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "iohk-nix", - "rev": "cecab9c71d1064f05f1615eead56ac0b9196bc20", - "type": "github" - } - }, - "iohk-nix_4": { "inputs": { "nixpkgs": [ "ctl", @@ -5329,7 +3817,7 @@ "type": "github" } }, - "iohk-nix_5": { + "iohk-nix_4": { "inputs": { "nixpkgs": [ "ctl", @@ -5375,81 +3863,6 @@ "type": "github" } }, - "iohkNix_10": { - "inputs": { - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1631778944, - "narHash": "sha256-N5eCcUYtZ5kUOl/JJGjx6ZzhA3uIn1itDRTiRV+3jLw=", - "owner": "input-output-hk", - "repo": "iohk-nix", - "rev": "db2c75a09c696271194bb3ef25ec8e9839b594b7", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "iohk-nix", - "type": "github" - } - }, - "iohkNix_11": { - "inputs": { - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "membench", - "cardano-node-snapshot", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1631778944, - "narHash": "sha256-N5eCcUYtZ5kUOl/JJGjx6ZzhA3uIn1itDRTiRV+3jLw=", - "owner": "input-output-hk", - "repo": "iohk-nix", - "rev": "db2c75a09c696271194bb3ef25ec8e9839b594b7", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "iohk-nix", - "type": "github" - } - }, - "iohkNix_12": { - "inputs": { - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "plutus-example", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1633964277, - "narHash": "sha256-7G/BK514WiMRr90EswNBthe8SmH9tjPaTBba/RW/VA8=", - "owner": "input-output-hk", - "repo": "iohk-nix", - "rev": "1e51437aac8a0e49663cb21e781f34163c81ebfb", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "iohk-nix", - "type": "github" - } - }, "iohkNix_2": { "inputs": { "nixpkgs": [ @@ -5529,8 +3942,7 @@ "inputs": { "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "nixpkgs" ] @@ -5553,8 +3965,7 @@ "inputs": { "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "nixpkgs" @@ -5578,8 +3989,7 @@ "inputs": { "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "membench", @@ -5605,8 +4015,7 @@ "inputs": { "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "plutus-example", @@ -5627,29 +4036,6 @@ "type": "github" } }, - "iohkNix_9": { - "inputs": { - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1653579289, - "narHash": "sha256-wveDdPsgB/3nAGAdFaxrcgLEpdi0aJ5kEVNtI+YqVfo=", - "owner": "input-output-hk", - "repo": "iohk-nix", - "rev": "edb2d2df2ebe42bbdf03a0711115cf6213c9d366", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "iohk-nix", - "type": "github" - } - }, "iserv-proxy": { "flake": false, "locked": { @@ -5810,38 +4196,6 @@ "type": "github" } }, - "lowdown-src_7": { - "flake": false, - "locked": { - "lastModified": 1633514407, - "narHash": "sha256-Dw32tiMjdK9t3ETl5fzGrutQTzh2rufgZV4A/BbxuD4=", - "owner": "kristapsdz", - "repo": "lowdown", - "rev": "d2c2b44ff6c27b936ec27358a2653caaef8f73b8", - "type": "github" - }, - "original": { - "owner": "kristapsdz", - "repo": "lowdown", - "type": "github" - } - }, - "lowdown-src_8": { - "flake": false, - "locked": { - "lastModified": 1633514407, - "narHash": "sha256-Dw32tiMjdK9t3ETl5fzGrutQTzh2rufgZV4A/BbxuD4=", - "owner": "kristapsdz", - "repo": "lowdown", - "rev": "d2c2b44ff6c27b936ec27358a2653caaef8f73b8", - "type": "github" - }, - "original": { - "owner": "kristapsdz", - "repo": "lowdown", - "type": "github" - } - }, "mdbook-kroki-preprocessor": { "flake": false, "locked": { @@ -5890,22 +4244,6 @@ "type": "github" } }, - "mdbook-kroki-preprocessor_4": { - "flake": false, - "locked": { - "lastModified": 1661755005, - "narHash": "sha256-1TJuUzfyMycWlOQH67LR63/ll2GDZz25I3JfScy/Jnw=", - "owner": "JoelCourtney", - "repo": "mdbook-kroki-preprocessor", - "rev": "93adb5716d035829efed27f65f2f0833a7d3e76f", - "type": "github" - }, - "original": { - "owner": "JoelCourtney", - "repo": "mdbook-kroki-preprocessor", - "type": "github" - } - }, "membench": { "inputs": { "cardano-mainnet-mirror": "cardano-mainnet-mirror_2", @@ -6002,23 +4340,20 @@ "cardano-mainnet-mirror": "cardano-mainnet-mirror_5", "cardano-node-measured": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot" ], "cardano-node-process": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot" ], "cardano-node-snapshot": "cardano-node-snapshot_2", "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "nixpkgs" @@ -6044,8 +4379,7 @@ "cardano-mainnet-mirror": "cardano-mainnet-mirror_6", "cardano-node-measured": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "membench", @@ -6053,8 +4387,7 @@ ], "cardano-node-process": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "membench", @@ -6062,8 +4395,7 @@ ], "cardano-node-snapshot": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "membench", @@ -6071,8 +4403,7 @@ ], "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "membench", @@ -6095,115 +4426,24 @@ "type": "github" } }, - "membench_5": { + "n2c": { "inputs": { - "cardano-mainnet-mirror": "cardano-mainnet-mirror_8", - "cardano-node-measured": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot" - ], - "cardano-node-process": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot" - ], - "cardano-node-snapshot": "cardano-node-snapshot_3", + "flake-utils": "flake-utils_10", "nixpkgs": [ "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot", + "ogmios", + "haskell-nix", + "tullia", + "std", "nixpkgs" - ], - "ouroboros-network": "ouroboros-network_6" + ] }, "locked": { - "lastModified": 1645070579, - "narHash": "sha256-AxL6tCOnzYnE6OquoFzj+X1bLDr1PQx3d8/vXm+rbfA=", - "owner": "input-output-hk", - "repo": "cardano-memory-benchmark", - "rev": "65643e000186de1335e24ec89159db8ba85e1c1a", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-memory-benchmark", - "type": "github" - } - }, - "membench_6": { - "inputs": { - "cardano-mainnet-mirror": "cardano-mainnet-mirror_9", - "cardano-node-measured": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "membench", - "cardano-node-snapshot" - ], - "cardano-node-process": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "membench", - "cardano-node-snapshot" - ], - "cardano-node-snapshot": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "membench", - "cardano-node-snapshot" - ], - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "membench", - "cardano-node-snapshot", - "nixpkgs" - ], - "ouroboros-network": "ouroboros-network_5" - }, - "locked": { - "lastModified": 1644547122, - "narHash": "sha256-8nWK+ScMACvRQLbA27gwXNoZver+Wx/cF7V37044koY=", - "owner": "input-output-hk", - "repo": "cardano-memory-benchmark", - "rev": "9d8ff4b9394de0421ee95caa511d01163de88b77", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-memory-benchmark", - "type": "github" - } - }, - "n2c": { - "inputs": { - "flake-utils": "flake-utils_10", - "nixpkgs": [ - "ctl", - "ogmios", - "haskell-nix", - "tullia", - "std", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1665039323, - "narHash": "sha256-SAh3ZjFGsaCI8FRzXQyp56qcGdAqgKEfJWPCQ0Sr7tQ=", - "owner": "nlewo", - "repo": "nix2container", - "rev": "b008fe329ffb59b67bf9e7b08ede6ee792f2741a", + "lastModified": 1665039323, + "narHash": "sha256-SAh3ZjFGsaCI8FRzXQyp56qcGdAqgKEfJWPCQ0Sr7tQ=", + "owner": "nlewo", + "repo": "nix2container", + "rev": "b008fe329ffb59b67bf9e7b08ede6ee792f2741a", "type": "github" }, "original": { @@ -6215,33 +4455,6 @@ "n2c_2": { "inputs": { "flake-utils": "flake-utils_18", - "nixpkgs": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "std", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1665039323, - "narHash": "sha256-SAh3ZjFGsaCI8FRzXQyp56qcGdAqgKEfJWPCQ0Sr7tQ=", - "owner": "nlewo", - "repo": "nix2container", - "rev": "b008fe329ffb59b67bf9e7b08ede6ee792f2741a", - "type": "github" - }, - "original": { - "owner": "nlewo", - "repo": "nix2container", - "type": "github" - } - }, - "n2c_3": { - "inputs": { - "flake-utils": "flake-utils_26", "nixpkgs": [ "ctl", "ogmios-nixos", @@ -6265,9 +4478,9 @@ "type": "github" } }, - "n2c_4": { + "n2c_3": { "inputs": { - "flake-utils": "flake-utils_30", + "flake-utils": "flake-utils_22", "nixpkgs": [ "ctl", "plutip", @@ -6356,51 +4569,7 @@ }, "nix-nomad_2": { "inputs": { - "flake-compat": "flake-compat_12", - "flake-utils": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "nix2container", - "flake-utils" - ], - "gomod2nix": "gomod2nix_2", - "nixpkgs": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "nixpkgs" - ], - "nixpkgs-lib": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1658277770, - "narHash": "sha256-T/PgG3wUn8Z2rnzfxf2VqlR1CBjInPE0l1yVzXxPnt0=", - "owner": "tristanpemble", - "repo": "nix-nomad", - "rev": "054adcbdd0a836ae1c20951b67ed549131fd2d70", - "type": "github" - }, - "original": { - "owner": "tristanpemble", - "repo": "nix-nomad", - "type": "github" - } - }, - "nix-nomad_3": { - "inputs": { - "flake-compat": "flake-compat_16", + "flake-compat": "flake-compat_10", "flake-utils": [ "ctl", "ogmios-nixos", @@ -6409,7 +4578,7 @@ "nix2container", "flake-utils" ], - "gomod2nix": "gomod2nix_3", + "gomod2nix": "gomod2nix_2", "nixpkgs": [ "ctl", "ogmios-nixos", @@ -6439,9 +4608,9 @@ "type": "github" } }, - "nix-nomad_4": { + "nix-nomad_3": { "inputs": { - "flake-compat": "flake-compat_19", + "flake-compat": "flake-compat_13", "flake-utils": [ "ctl", "plutip", @@ -6451,7 +4620,7 @@ "nix2container", "flake-utils" ], - "gomod2nix": "gomod2nix_4", + "gomod2nix": "gomod2nix_3", "nixpkgs": [ "ctl", "plutip", @@ -6499,54 +4668,6 @@ "type": "github" } }, - "nix-tools_10": { - "flake": false, - "locked": { - "lastModified": 1636018067, - "narHash": "sha256-ng306fkuwr6V/malWtt3979iAC4yMVDDH2ViwYB6sQE=", - "owner": "input-output-hk", - "repo": "nix-tools", - "rev": "ed5bd7215292deba55d6ab7a4e8c21f8b1564dda", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "nix-tools", - "type": "github" - } - }, - "nix-tools_11": { - "flake": false, - "locked": { - "lastModified": 1636018067, - "narHash": "sha256-ng306fkuwr6V/malWtt3979iAC4yMVDDH2ViwYB6sQE=", - "owner": "input-output-hk", - "repo": "nix-tools", - "rev": "ed5bd7215292deba55d6ab7a4e8c21f8b1564dda", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "nix-tools", - "type": "github" - } - }, - "nix-tools_12": { - "flake": false, - "locked": { - "lastModified": 1636018067, - "narHash": "sha256-ng306fkuwr6V/malWtt3979iAC4yMVDDH2ViwYB6sQE=", - "owner": "input-output-hk", - "repo": "nix-tools", - "rev": "ed5bd7215292deba55d6ab7a4e8c21f8b1564dda", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "nix-tools", - "type": "github" - } - }, "nix-tools_2": { "flake": false, "locked": { @@ -6659,22 +4780,6 @@ "type": "github" } }, - "nix-tools_9": { - "flake": false, - "locked": { - "lastModified": 1649424170, - "narHash": "sha256-XgKXWispvv5RCvZzPb+p7e6Hy3LMuRjafKMl7kXzxGw=", - "owner": "input-output-hk", - "repo": "nix-tools", - "rev": "e109c94016e3b6e0db7ed413c793e2d4bdb24aa7", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "nix-tools", - "type": "github" - } - }, "nix2container": { "inputs": { "flake-utils": "flake-utils_8", @@ -6697,7 +4802,7 @@ "nix2container_2": { "inputs": { "flake-utils": "flake-utils_16", - "nixpkgs": "nixpkgs_19" + "nixpkgs": "nixpkgs_17" }, "locked": { "lastModified": 1658567952, @@ -6715,27 +4820,8 @@ }, "nix2container_3": { "inputs": { - "flake-utils": "flake-utils_24", - "nixpkgs": "nixpkgs_27" - }, - "locked": { - "lastModified": 1658567952, - "narHash": "sha256-XZ4ETYAMU7XcpEeAFP3NOl9yDXNuZAen/aIJ84G+VgA=", - "owner": "nlewo", - "repo": "nix2container", - "rev": "60bb43d405991c1378baf15a40b5811a53e32ffa", - "type": "github" - }, - "original": { - "owner": "nlewo", - "repo": "nix2container", - "type": "github" - } - }, - "nix2container_4": { - "inputs": { - "flake-utils": "flake-utils_28", - "nixpkgs": "nixpkgs_31" + "flake-utils": "flake-utils_20", + "nixpkgs": "nixpkgs_21" }, "locked": { "lastModified": 1658567952, @@ -6783,22 +4869,6 @@ "type": "github" } }, - "nixTools_3": { - "flake": false, - "locked": { - "lastModified": 1649424170, - "narHash": "sha256-XgKXWispvv5RCvZzPb+p7e6Hy3LMuRjafKMl7kXzxGw=", - "owner": "input-output-hk", - "repo": "nix-tools", - "rev": "e109c94016e3b6e0db7ed413c793e2d4bdb24aa7", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "nix-tools", - "type": "github" - } - }, "nix_2": { "inputs": { "lowdown-src": "lowdown-src_2", @@ -6844,7 +4914,7 @@ "nix_4": { "inputs": { "lowdown-src": "lowdown-src_4", - "nixpkgs": "nixpkgs_14", + "nixpkgs": "nixpkgs_12", "nixpkgs-regression": "nixpkgs-regression_4" }, "locked": { @@ -6865,7 +4935,7 @@ "nix_5": { "inputs": { "lowdown-src": "lowdown-src_5", - "nixpkgs": "nixpkgs_17", + "nixpkgs": "nixpkgs_15", "nixpkgs-regression": "nixpkgs-regression_5" }, "locked": { @@ -6886,7 +4956,7 @@ "nix_6": { "inputs": { "lowdown-src": "lowdown-src_6", - "nixpkgs": "nixpkgs_22", + "nixpkgs": "nixpkgs_19", "nixpkgs-regression": "nixpkgs-regression_6" }, "locked": { @@ -6904,49 +4974,7 @@ "type": "github" } }, - "nix_7": { - "inputs": { - "lowdown-src": "lowdown-src_7", - "nixpkgs": "nixpkgs_25", - "nixpkgs-regression": "nixpkgs-regression_7" - }, - "locked": { - "lastModified": 1643066034, - "narHash": "sha256-xEPeMcNJVOeZtoN+d+aRwolpW8mFSEQx76HTRdlhPhg=", - "owner": "NixOS", - "repo": "nix", - "rev": "a1cd7e58606a41fcf62bf8637804cf8306f17f62", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "2.6.0", - "repo": "nix", - "type": "github" - } - }, - "nix_8": { - "inputs": { - "lowdown-src": "lowdown-src_8", - "nixpkgs": "nixpkgs_29", - "nixpkgs-regression": "nixpkgs-regression_8" - }, - "locked": { - "lastModified": 1643066034, - "narHash": "sha256-xEPeMcNJVOeZtoN+d+aRwolpW8mFSEQx76HTRdlhPhg=", - "owner": "NixOS", - "repo": "nix", - "rev": "a1cd7e58606a41fcf62bf8637804cf8306f17f62", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "2.6.0", - "repo": "nix", - "type": "github" - } - }, - "nixago": { + "nixago": { "inputs": { "flake-utils": [ "ctl", @@ -6988,50 +5016,6 @@ } }, "nixago_2": { - "inputs": { - "flake-utils": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "std", - "flake-utils" - ], - "nixago-exts": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "std", - "blank" - ], - "nixpkgs": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "std", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1661824785, - "narHash": "sha256-/PnwdWoO/JugJZHtDUioQp3uRiWeXHUdgvoyNbXesz8=", - "owner": "nix-community", - "repo": "nixago", - "rev": "8c1f9e5f1578d4b2ea989f618588d62a335083c3", - "type": "github" - }, - "original": { - "owner": "nix-community", - "repo": "nixago", - "type": "github" - } - }, - "nixago_3": { "inputs": { "flake-utils": [ "ctl", @@ -7072,7 +5056,7 @@ "type": "github" } }, - "nixago_4": { + "nixago_3": { "inputs": { "flake-utils": [ "ctl", @@ -7194,86 +5178,6 @@ "type": "github" } }, - "nixpkgs-2003_13": { - "locked": { - "lastModified": 1620055814, - "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-20.03-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2003_14": { - "locked": { - "lastModified": 1620055814, - "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-20.03-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2003_15": { - "locked": { - "lastModified": 1620055814, - "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-20.03-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2003_16": { - "locked": { - "lastModified": 1620055814, - "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-20.03-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2003_17": { - "locked": { - "lastModified": 1620055814, - "narHash": "sha256-8LEHoYSJiL901bTMVatq+rf8y7QtWuZhwwpKE2fyaRY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "1db42b7fe3878f3f5f7a4f2dc210772fd080e205", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-20.03-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, "nixpkgs-2003_2": { "locked": { "lastModified": 1620055814, @@ -7451,86 +5355,6 @@ } }, "nixpkgs-2105_12": { - "locked": { - "lastModified": 1645296114, - "narHash": "sha256-y53N7TyIkXsjMpOG7RhvqJFGDacLs9HlyHeSTBioqYU=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "530a53dcbc9437363471167a5e4762c5fcfa34a1", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-21.05-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2105_13": { - "locked": { - "lastModified": 1640283157, - "narHash": "sha256-6Ddfop+rKE+Gl9Tjp9YIrkfoYPzb8F80ergdjcq3/MY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "dde1557825c5644c869c5efc7448dc03722a8f09", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-21.05-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2105_14": { - "locked": { - "lastModified": 1640283157, - "narHash": "sha256-6Ddfop+rKE+Gl9Tjp9YIrkfoYPzb8F80ergdjcq3/MY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "dde1557825c5644c869c5efc7448dc03722a8f09", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-21.05-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2105_15": { - "locked": { - "lastModified": 1630481079, - "narHash": "sha256-leWXLchbAbqOlLT6tju631G40SzQWPqaAXQG3zH1Imw=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "110a2c9ebbf5d4a94486854f18a37a938cfacbbb", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-21.05-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2105_16": { - "locked": { - "lastModified": 1659914493, - "narHash": "sha256-lkA5X3VNMKirvA+SUzvEhfA7XquWLci+CGi505YFAIs=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "022caabb5f2265ad4006c1fa5b1ebe69fb0c3faf", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-21.05-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2105_17": { "locked": { "lastModified": 1659914493, "narHash": "sha256-lkA5X3VNMKirvA+SUzvEhfA7XquWLci+CGi505YFAIs=", @@ -7724,11 +5548,11 @@ }, "nixpkgs-2111_12": { "locked": { - "lastModified": 1648744337, - "narHash": "sha256-bYe1dFJAXovjqiaPKrmAbSBEK5KUkgwVaZcTbSoJ7hg=", + "lastModified": 1659446231, + "narHash": "sha256-hekabNdTdgR/iLsgce5TGWmfIDZ86qjPhxDg/8TlzhE=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "0a58eebd8ec65ffdef2ce9562784123a73922052", + "rev": "eabc38219184cc3e04a974fe31857d8e0eac098d", "type": "github" }, "original": { @@ -7738,13 +5562,13 @@ "type": "github" } }, - "nixpkgs-2111_13": { + "nixpkgs-2111_2": { "locked": { - "lastModified": 1640283207, - "narHash": "sha256-SCwl7ZnCfMDsuSYvwIroiAlk7n33bW8HFfY8NvKhcPA=", + "lastModified": 1659446231, + "narHash": "sha256-hekabNdTdgR/iLsgce5TGWmfIDZ86qjPhxDg/8TlzhE=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "64c7e3388bbd9206e437713351e814366e0c3284", + "rev": "eabc38219184cc3e04a974fe31857d8e0eac098d", "type": "github" }, "original": { @@ -7754,7 +5578,7 @@ "type": "github" } }, - "nixpkgs-2111_14": { + "nixpkgs-2111_3": { "locked": { "lastModified": 1640283207, "narHash": "sha256-SCwl7ZnCfMDsuSYvwIroiAlk7n33bW8HFfY8NvKhcPA=", @@ -7770,13 +5594,13 @@ "type": "github" } }, - "nixpkgs-2111_15": { + "nixpkgs-2111_4": { "locked": { - "lastModified": 1638410074, - "narHash": "sha256-MQYI4k4XkoTzpeRjq5wl+1NShsl1CKq8MISFuZ81sWs=", + "lastModified": 1640283207, + "narHash": "sha256-SCwl7ZnCfMDsuSYvwIroiAlk7n33bW8HFfY8NvKhcPA=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "5b80f23502f8e902612a8c631dfce383e1c56596", + "rev": "64c7e3388bbd9206e437713351e814366e0c3284", "type": "github" }, "original": { @@ -7786,13 +5610,13 @@ "type": "github" } }, - "nixpkgs-2111_16": { + "nixpkgs-2111_5": { "locked": { - "lastModified": 1659446231, - "narHash": "sha256-hekabNdTdgR/iLsgce5TGWmfIDZ86qjPhxDg/8TlzhE=", + "lastModified": 1638410074, + "narHash": "sha256-MQYI4k4XkoTzpeRjq5wl+1NShsl1CKq8MISFuZ81sWs=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "eabc38219184cc3e04a974fe31857d8e0eac098d", + "rev": "5b80f23502f8e902612a8c631dfce383e1c56596", "type": "github" }, "original": { @@ -7802,7 +5626,7 @@ "type": "github" } }, - "nixpkgs-2111_17": { + "nixpkgs-2111_6": { "locked": { "lastModified": 1659446231, "narHash": "sha256-hekabNdTdgR/iLsgce5TGWmfIDZ86qjPhxDg/8TlzhE=", @@ -7818,13 +5642,13 @@ "type": "github" } }, - "nixpkgs-2111_2": { + "nixpkgs-2111_7": { "locked": { - "lastModified": 1659446231, - "narHash": "sha256-hekabNdTdgR/iLsgce5TGWmfIDZ86qjPhxDg/8TlzhE=", + "lastModified": 1648744337, + "narHash": "sha256-bYe1dFJAXovjqiaPKrmAbSBEK5KUkgwVaZcTbSoJ7hg=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "eabc38219184cc3e04a974fe31857d8e0eac098d", + "rev": "0a58eebd8ec65ffdef2ce9562784123a73922052", "type": "github" }, "original": { @@ -7834,7 +5658,7 @@ "type": "github" } }, - "nixpkgs-2111_3": { + "nixpkgs-2111_8": { "locked": { "lastModified": 1640283207, "narHash": "sha256-SCwl7ZnCfMDsuSYvwIroiAlk7n33bW8HFfY8NvKhcPA=", @@ -7850,87 +5674,7 @@ "type": "github" } }, - "nixpkgs-2111_4": { - "locked": { - "lastModified": 1640283207, - "narHash": "sha256-SCwl7ZnCfMDsuSYvwIroiAlk7n33bW8HFfY8NvKhcPA=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "64c7e3388bbd9206e437713351e814366e0c3284", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-21.11-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2111_5": { - "locked": { - "lastModified": 1638410074, - "narHash": "sha256-MQYI4k4XkoTzpeRjq5wl+1NShsl1CKq8MISFuZ81sWs=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "5b80f23502f8e902612a8c631dfce383e1c56596", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-21.11-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2111_6": { - "locked": { - "lastModified": 1659446231, - "narHash": "sha256-hekabNdTdgR/iLsgce5TGWmfIDZ86qjPhxDg/8TlzhE=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "eabc38219184cc3e04a974fe31857d8e0eac098d", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-21.11-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2111_7": { - "locked": { - "lastModified": 1648744337, - "narHash": "sha256-bYe1dFJAXovjqiaPKrmAbSBEK5KUkgwVaZcTbSoJ7hg=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "0a58eebd8ec65ffdef2ce9562784123a73922052", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-21.11-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2111_8": { - "locked": { - "lastModified": 1640283207, - "narHash": "sha256-SCwl7ZnCfMDsuSYvwIroiAlk7n33bW8HFfY8NvKhcPA=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "64c7e3388bbd9206e437713351e814366e0c3284", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-21.11-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-2111_9": { + "nixpkgs-2111_9": { "locked": { "lastModified": 1640283207, "narHash": "sha256-SCwl7ZnCfMDsuSYvwIroiAlk7n33bW8HFfY8NvKhcPA=", @@ -8010,22 +5754,6 @@ "type": "github" } }, - "nixpkgs-2205_5": { - "locked": { - "lastModified": 1663981975, - "narHash": "sha256-TKaxWAVJR+a5JJauKZqibmaM5e/Pi5tBDx9s8fl/kSE=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "309faedb8338d3ae8ad8f1043b3ccf48c9cc2970", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-22.05-darwin", - "repo": "nixpkgs", - "type": "github" - } - }, "nixpkgs-2211": { "locked": { "lastModified": 1669997163, @@ -8132,36 +5860,6 @@ "type": "indirect" } }, - "nixpkgs-regression_7": { - "locked": { - "lastModified": 1643052045, - "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "indirect" - } - }, - "nixpkgs-regression_8": { - "locked": { - "lastModified": 1643052045, - "narHash": "sha256-uGJ0VXIhWKGXxkeNnq4TvV3CIOkUJ3PAoLZ3HMzNVMw=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "rev": "215d4d0fd80ca5163643b03a33fde804a29cc1e2", - "type": "indirect" - } - }, "nixpkgs-unstable": { "locked": { "lastModified": 1648219316, @@ -8211,86 +5909,6 @@ } }, "nixpkgs-unstable_12": { - "locked": { - "lastModified": 1648219316, - "narHash": "sha256-Ctij+dOi0ZZIfX5eMhgwugfvB+WZSrvVNAyAuANOsnQ=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "30d3d79b7d3607d56546dd2a6b49e156ba0ec634", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-unstable", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-unstable_13": { - "locked": { - "lastModified": 1641285291, - "narHash": "sha256-KYaOBNGar3XWTxTsYPr9P6u74KAqNq0wobEC236U+0c=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "0432195a4b8d68faaa7d3d4b355260a3120aeeae", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-unstable", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-unstable_14": { - "locked": { - "lastModified": 1641285291, - "narHash": "sha256-KYaOBNGar3XWTxTsYPr9P6u74KAqNq0wobEC236U+0c=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "0432195a4b8d68faaa7d3d4b355260a3120aeeae", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-unstable", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-unstable_15": { - "locked": { - "lastModified": 1635295995, - "narHash": "sha256-sGYiXjFlxTTMNb4NSkgvX+knOOTipE6gqwPUQpxNF+c=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "22a500a3f87bbce73bd8d777ef920b43a636f018", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-unstable", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-unstable_16": { - "locked": { - "lastModified": 1663905476, - "narHash": "sha256-0CSwRKaYravh9v6qSlBpM0gNg0UhKT2lL7Yn6Zbx7UM=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "e14f9fb57315f0d4abde222364f19f88c77d2b79", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixpkgs-unstable", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs-unstable_17": { "locked": { "lastModified": 1663905476, "narHash": "sha256-0CSwRKaYravh9v6qSlBpM0gNg0UhKT2lL7Yn6Zbx7UM=", @@ -8451,38 +6069,6 @@ } }, "nixpkgs_11": { - "locked": { - "lastModified": 1634172192, - "narHash": "sha256-FBF4U/T+bMg4sEyT/zkgasvVquGzgdAf4y8uCosKMmo=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "2cf9db0e3d45b9d00f16f2836cb1297bcadc475e", - "type": "github" - }, - "original": { - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "2cf9db0e3d45b9d00f16f2836cb1297bcadc475e", - "type": "github" - } - }, - "nixpkgs_12": { - "locked": { - "lastModified": 1634172192, - "narHash": "sha256-FBF4U/T+bMg4sEyT/zkgasvVquGzgdAf4y8uCosKMmo=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "2cf9db0e3d45b9d00f16f2836cb1297bcadc475e", - "type": "github" - }, - "original": { - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "2cf9db0e3d45b9d00f16f2836cb1297bcadc475e", - "type": "github" - } - }, - "nixpkgs_13": { "locked": { "lastModified": 1642336556, "narHash": "sha256-QSPPbFEwy0T0DrIuSzAACkaANPQaR1lZR/nHZGz9z04=", @@ -8496,7 +6082,7 @@ "type": "indirect" } }, - "nixpkgs_14": { + "nixpkgs_12": { "locked": { "lastModified": 1632864508, "narHash": "sha256-d127FIvGR41XbVRDPVvozUPQ/uRHbHwvfyKHwEt5xFM=", @@ -8511,7 +6097,7 @@ "type": "indirect" } }, - "nixpkgs_15": { + "nixpkgs_13": { "locked": { "lastModified": 1642336556, "narHash": "sha256-QSPPbFEwy0T0DrIuSzAACkaANPQaR1lZR/nHZGz9z04=", @@ -8525,7 +6111,7 @@ "type": "indirect" } }, - "nixpkgs_16": { + "nixpkgs_14": { "locked": { "lastModified": 1642336556, "narHash": "sha256-QSPPbFEwy0T0DrIuSzAACkaANPQaR1lZR/nHZGz9z04=", @@ -8539,7 +6125,7 @@ "type": "indirect" } }, - "nixpkgs_17": { + "nixpkgs_15": { "locked": { "lastModified": 1632864508, "narHash": "sha256-d127FIvGR41XbVRDPVvozUPQ/uRHbHwvfyKHwEt5xFM=", @@ -8554,7 +6140,7 @@ "type": "indirect" } }, - "nixpkgs_18": { + "nixpkgs_16": { "locked": { "lastModified": 1653581809, "narHash": "sha256-Uvka0V5MTGbeOfWte25+tfRL3moECDh1VwokWSZUdoY=", @@ -8570,7 +6156,7 @@ "type": "github" } }, - "nixpkgs_19": { + "nixpkgs_17": { "locked": { "lastModified": 1654807842, "narHash": "sha256-ADymZpr6LuTEBXcy6RtFHcUZdjKTBRTMYwu19WOx17E=", @@ -8585,22 +6171,7 @@ "type": "github" } }, - "nixpkgs_2": { - "locked": { - "lastModified": 1632864508, - "narHash": "sha256-d127FIvGR41XbVRDPVvozUPQ/uRHbHwvfyKHwEt5xFM=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "82891b5e2c2359d7e58d08849e4c89511ab94234", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "ref": "nixos-21.05-small", - "type": "indirect" - } - }, - "nixpkgs_20": { + "nixpkgs_18": { "locked": { "lastModified": 1665087388, "narHash": "sha256-FZFPuW9NWHJteATOf79rZfwfRn5fE0wi9kRzvGfDHPA=", @@ -8616,24 +6187,10 @@ "type": "github" } }, - "nixpkgs_21": { + "nixpkgs_19": { "locked": { - "lastModified": 1642336556, - "narHash": "sha256-QSPPbFEwy0T0DrIuSzAACkaANPQaR1lZR/nHZGz9z04=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "f3d9d4bd898cca7d04af2ae4f6ef01f2219df3d6", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "type": "indirect" - } - }, - "nixpkgs_22": { - "locked": { - "lastModified": 1632864508, - "narHash": "sha256-d127FIvGR41XbVRDPVvozUPQ/uRHbHwvfyKHwEt5xFM=", + "lastModified": 1632864508, + "narHash": "sha256-d127FIvGR41XbVRDPVvozUPQ/uRHbHwvfyKHwEt5xFM=", "owner": "NixOS", "repo": "nixpkgs", "rev": "82891b5e2c2359d7e58d08849e4c89511ab94234", @@ -8645,35 +6202,7 @@ "type": "indirect" } }, - "nixpkgs_23": { - "locked": { - "lastModified": 1642336556, - "narHash": "sha256-QSPPbFEwy0T0DrIuSzAACkaANPQaR1lZR/nHZGz9z04=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "f3d9d4bd898cca7d04af2ae4f6ef01f2219df3d6", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "type": "indirect" - } - }, - "nixpkgs_24": { - "locked": { - "lastModified": 1642336556, - "narHash": "sha256-QSPPbFEwy0T0DrIuSzAACkaANPQaR1lZR/nHZGz9z04=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "f3d9d4bd898cca7d04af2ae4f6ef01f2219df3d6", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "type": "indirect" - } - }, - "nixpkgs_25": { + "nixpkgs_2": { "locked": { "lastModified": 1632864508, "narHash": "sha256-d127FIvGR41XbVRDPVvozUPQ/uRHbHwvfyKHwEt5xFM=", @@ -8688,7 +6217,7 @@ "type": "indirect" } }, - "nixpkgs_26": { + "nixpkgs_20": { "locked": { "lastModified": 1653581809, "narHash": "sha256-Uvka0V5MTGbeOfWte25+tfRL3moECDh1VwokWSZUdoY=", @@ -8704,7 +6233,7 @@ "type": "github" } }, - "nixpkgs_27": { + "nixpkgs_21": { "locked": { "lastModified": 1654807842, "narHash": "sha256-ADymZpr6LuTEBXcy6RtFHcUZdjKTBRTMYwu19WOx17E=", @@ -8719,7 +6248,7 @@ "type": "github" } }, - "nixpkgs_28": { + "nixpkgs_22": { "locked": { "lastModified": 1665087388, "narHash": "sha256-FZFPuW9NWHJteATOf79rZfwfRn5fE0wi9kRzvGfDHPA=", @@ -8735,21 +6264,6 @@ "type": "github" } }, - "nixpkgs_29": { - "locked": { - "lastModified": 1632864508, - "narHash": "sha256-d127FIvGR41XbVRDPVvozUPQ/uRHbHwvfyKHwEt5xFM=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "82891b5e2c2359d7e58d08849e4c89511ab94234", - "type": "github" - }, - "original": { - "id": "nixpkgs", - "ref": "nixos-21.05-small", - "type": "indirect" - } - }, "nixpkgs_3": { "locked": { "lastModified": 1642336556, @@ -8764,53 +6278,6 @@ "type": "indirect" } }, - "nixpkgs_30": { - "locked": { - "lastModified": 1653581809, - "narHash": "sha256-Uvka0V5MTGbeOfWte25+tfRL3moECDh1VwokWSZUdoY=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "83658b28fe638a170a19b8933aa008b30640fbd1", - "type": "github" - }, - "original": { - "owner": "NixOS", - "ref": "nixos-unstable", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs_31": { - "locked": { - "lastModified": 1654807842, - "narHash": "sha256-ADymZpr6LuTEBXcy6RtFHcUZdjKTBRTMYwu19WOx17E=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "fc909087cc3386955f21b4665731dbdaceefb1d8", - "type": "github" - }, - "original": { - "owner": "NixOS", - "repo": "nixpkgs", - "type": "github" - } - }, - "nixpkgs_32": { - "locked": { - "lastModified": 1665087388, - "narHash": "sha256-FZFPuW9NWHJteATOf79rZfwfRn5fE0wi9kRzvGfDHPA=", - "owner": "nixos", - "repo": "nixpkgs", - "rev": "95fda953f6db2e9496d2682c4fc7b82f959878f7", - "type": "github" - }, - "original": { - "owner": "nixos", - "ref": "nixpkgs-unstable", - "repo": "nixpkgs", - "type": "github" - } - }, "nixpkgs_4": { "locked": { "lastModified": 1632864508, @@ -8932,22 +6399,6 @@ "type": "github" } }, - "node-process_3": { - "flake": false, - "locked": { - "lastModified": 1654323094, - "narHash": "sha256-zbmpZeBgUUly8QgR2mrVUN0A+0iLczufNvCCRxAo3GY=", - "owner": "input-output-hk", - "repo": "cardano-node", - "rev": "ec20745f17cb4fa8824fdf341d1412c774bc94b9", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-node", - "type": "github" - } - }, "node-snapshot": { "inputs": { "customConfig": "customConfig_2", @@ -8988,8 +6439,7 @@ "membench": "membench_3", "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "cardano-node", "node-snapshot", "haskellNix", @@ -9013,38 +6463,6 @@ "type": "github" } }, - "node-snapshot_3": { - "inputs": { - "customConfig": "customConfig_10", - "haskellNix": "haskellNix_10", - "iohkNix": "iohkNix_10", - "membench": "membench_5", - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "haskellNix", - "nixpkgs-2105" - ], - "plutus-example": "plutus-example_3", - "utils": "utils_13" - }, - "locked": { - "lastModified": 1645120669, - "narHash": "sha256-2MKfGsYS5n69+pfqNHb4IH/E95ok1MD7mhEYfUpRcz4=", - "owner": "input-output-hk", - "repo": "cardano-node", - "rev": "7f00e3ea5a61609e19eeeee4af35241571efdf5c", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-node", - "rev": "7f00e3ea5a61609e19eeeee4af35241571efdf5c", - "type": "github" - } - }, "ogmios": { "inputs": { "CHaP": "CHaP", @@ -9076,113 +6494,32 @@ "type": "github" } }, - "ogmios-datum-cache": { - "inputs": { - "flake-compat": "flake-compat_7", - "nixpkgs": "nixpkgs_11", - "unstable_nixpkgs": "unstable_nixpkgs" - }, - "locked": { - "lastModified": 1668515878, - "narHash": "sha256-r4aOSSz9jZZPreUkgOpS3ZpYFV4cxNVCUQFIpBZ8Y9k=", - "owner": "mlabs-haskell", - "repo": "ogmios-datum-cache", - "rev": "862c6bfcb6110b8fe816e26b3bba105dfb492b24", - "type": "github" - }, - "original": { - "owner": "mlabs-haskell", - "repo": "ogmios-datum-cache", - "rev": "862c6bfcb6110b8fe816e26b3bba105dfb492b24", - "type": "github" - } - }, - "ogmios-datum-cache-nixos": { - "inputs": { - "cardano-configurations": "cardano-configurations_3", - "cardano-node": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "cardano-node" - ], - "flake-compat": "flake-compat_8", - "nixpkgs": "nixpkgs_12", - "ogmios": "ogmios_2", - "unstable_nixpkgs": "unstable_nixpkgs_2" - }, - "locked": { - "lastModified": 1667912888, - "narHash": "sha256-6KS0c1PZ44ZTcE2ioXC0GiIuyTKnG5MeKX7nDZ6Knus=", - "owner": "mlabs-haskell", - "repo": "ogmios-datum-cache", - "rev": "a33a576fefe2248e9906e7b8044a30955cca0061", - "type": "github" - }, - "original": { - "owner": "mlabs-haskell", - "ref": "marton/nixos-module", - "repo": "ogmios-datum-cache", - "type": "github" - } - }, "ogmios-nixos": { - "inputs": { - "CHaP": "CHaP_4", - "blank": "blank_5", - "cardano-configurations": "cardano-configurations_4", - "cardano-node": "cardano-node_3", - "flake-compat": "flake-compat_14", - "haskell-nix": "haskell-nix_4", - "iohk-nix": "iohk-nix_4", - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "haskell-nix", - "nixpkgs-unstable" - ] - }, - "locked": { - "lastModified": 1668087435, - "narHash": "sha256-pbx/+mP2pu4vQuTV3YtFXrOZOVOBS9JH9eDqgjnHyZ4=", - "owner": "mlabs-haskell", - "repo": "ogmios", - "rev": "3b229c1795efa30243485730b78ea053992fdc7a", - "type": "github" - }, - "original": { - "owner": "mlabs-haskell", - "repo": "ogmios", - "type": "github" - } - }, - "ogmios_2": { "inputs": { "CHaP": "CHaP_3", "blank": "blank_3", + "cardano-configurations": "cardano-configurations_3", "cardano-node": "cardano-node_2", - "flake-compat": "flake-compat_10", + "flake-compat": "flake-compat_8", "haskell-nix": "haskell-nix_3", "iohk-nix": "iohk-nix_3", "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "haskell-nix", "nixpkgs-unstable" ] }, "locked": { - "lastModified": 1667904967, - "narHash": "sha256-KAWv/plBLRqZiBYUl0plXQdMPzFs7G89VhTbg122kA4=", + "lastModified": 1668087435, + "narHash": "sha256-pbx/+mP2pu4vQuTV3YtFXrOZOVOBS9JH9eDqgjnHyZ4=", "owner": "mlabs-haskell", "repo": "ogmios", - "rev": "dbc1a03dca6a876a25d54a8716504837909c6e8c", + "rev": "3b229c1795efa30243485730b78ea053992fdc7a", "type": "github" }, "original": { "owner": "mlabs-haskell", - "ref": "staging", "repo": "ogmios", "type": "github" } @@ -9255,91 +6592,6 @@ "type": "github" } }, - "old-ghc-nix_13": { - "flake": false, - "locked": { - "lastModified": 1631092763, - "narHash": "sha256-sIKgO+z7tj4lw3u6oBZxqIhDrzSkvpHtv0Kki+lh9Fg=", - "owner": "angerman", - "repo": "old-ghc-nix", - "rev": "af48a7a7353e418119b6dfe3cd1463a657f342b8", - "type": "github" - }, - "original": { - "owner": "angerman", - "ref": "master", - "repo": "old-ghc-nix", - "type": "github" - } - }, - "old-ghc-nix_14": { - "flake": false, - "locked": { - "lastModified": 1631092763, - "narHash": "sha256-sIKgO+z7tj4lw3u6oBZxqIhDrzSkvpHtv0Kki+lh9Fg=", - "owner": "angerman", - "repo": "old-ghc-nix", - "rev": "af48a7a7353e418119b6dfe3cd1463a657f342b8", - "type": "github" - }, - "original": { - "owner": "angerman", - "ref": "master", - "repo": "old-ghc-nix", - "type": "github" - } - }, - "old-ghc-nix_15": { - "flake": false, - "locked": { - "lastModified": 1631092763, - "narHash": "sha256-sIKgO+z7tj4lw3u6oBZxqIhDrzSkvpHtv0Kki+lh9Fg=", - "owner": "angerman", - "repo": "old-ghc-nix", - "rev": "af48a7a7353e418119b6dfe3cd1463a657f342b8", - "type": "github" - }, - "original": { - "owner": "angerman", - "ref": "master", - "repo": "old-ghc-nix", - "type": "github" - } - }, - "old-ghc-nix_16": { - "flake": false, - "locked": { - "lastModified": 1631092763, - "narHash": "sha256-sIKgO+z7tj4lw3u6oBZxqIhDrzSkvpHtv0Kki+lh9Fg=", - "owner": "angerman", - "repo": "old-ghc-nix", - "rev": "af48a7a7353e418119b6dfe3cd1463a657f342b8", - "type": "github" - }, - "original": { - "owner": "angerman", - "ref": "master", - "repo": "old-ghc-nix", - "type": "github" - } - }, - "old-ghc-nix_17": { - "flake": false, - "locked": { - "lastModified": 1631092763, - "narHash": "sha256-sIKgO+z7tj4lw3u6oBZxqIhDrzSkvpHtv0Kki+lh9Fg=", - "owner": "angerman", - "repo": "old-ghc-nix", - "rev": "af48a7a7353e418119b6dfe3cd1463a657f342b8", - "type": "github" - }, - "original": { - "owner": "angerman", - "ref": "master", - "repo": "old-ghc-nix", - "type": "github" - } - }, "old-ghc-nix_2": { "flake": false, "locked": { @@ -9540,38 +6792,6 @@ "type": "github" } }, - "ouroboros-network_5": { - "flake": false, - "locked": { - "lastModified": 1643385024, - "narHash": "sha256-9R4Z1jBsTcEgBHxhzjCJnroEcdfMsTjf8kwg6uPue+Q=", - "owner": "input-output-hk", - "repo": "ouroboros-network", - "rev": "8e97076176d465f5f4f86d5b5596220272630649", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "ouroboros-network", - "type": "github" - } - }, - "ouroboros-network_6": { - "flake": false, - "locked": { - "lastModified": 1643385024, - "narHash": "sha256-9R4Z1jBsTcEgBHxhzjCJnroEcdfMsTjf8kwg6uPue+Q=", - "owner": "input-output-hk", - "repo": "ouroboros-network", - "rev": "8e97076176d465f5f4f86d5b5596220272630649", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "ouroboros-network", - "type": "github" - } - }, "plutip": { "inputs": { "CHaP": [ @@ -9581,7 +6801,7 @@ "CHaP" ], "bot-plutus-interface": "bot-plutus-interface", - "flake-compat": "flake-compat_20", + "flake-compat": "flake-compat_14", "haskell-nix": [ "ctl", "plutip", @@ -9649,22 +6869,6 @@ "type": "github" } }, - "plutus-apps_3": { - "flake": false, - "locked": { - "lastModified": 1654271253, - "narHash": "sha256-GQDPzyVtcbbESmckMvzoTEKa/UWWJH7djh1TWQjzFow=", - "owner": "input-output-hk", - "repo": "plutus-apps", - "rev": "61de89d33340279b8452a0dbb52a87111db87e82", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "plutus-apps", - "type": "github" - } - }, "plutus-example": { "inputs": { "customConfig": "customConfig_4", @@ -9677,186 +6881,74 @@ "node-snapshot", "plutus-example", "haskellNix", - "nixpkgs-2105" - ], - "utils": "utils_2" - }, - "locked": { - "lastModified": 1640022647, - "narHash": "sha256-M+YnF7Zj/7QK2pu0T75xNVaX0eEeijtBH8yz+jEHIMM=", - "owner": "input-output-hk", - "repo": "cardano-node", - "rev": "814df2c146f5d56f8c35a681fe75e85b905aed5d", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-node", - "rev": "814df2c146f5d56f8c35a681fe75e85b905aed5d", - "type": "github" - } - }, - "plutus-example_2": { - "inputs": { - "customConfig": "customConfig_8", - "haskellNix": "haskellNix_8", - "iohkNix": "iohkNix_8", - "nixpkgs": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "cardano-node", - "node-snapshot", - "plutus-example", - "haskellNix", - "nixpkgs-2105" - ], - "utils": "utils_7" - }, - "locked": { - "lastModified": 1640022647, - "narHash": "sha256-M+YnF7Zj/7QK2pu0T75xNVaX0eEeijtBH8yz+jEHIMM=", - "owner": "input-output-hk", - "repo": "cardano-node", - "rev": "814df2c146f5d56f8c35a681fe75e85b905aed5d", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-node", - "rev": "814df2c146f5d56f8c35a681fe75e85b905aed5d", - "type": "github" - } - }, - "plutus-example_3": { - "inputs": { - "customConfig": "customConfig_12", - "haskellNix": "haskellNix_12", - "iohkNix": "iohkNix_12", - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "cardano-node", - "node-snapshot", - "plutus-example", - "haskellNix", - "nixpkgs-2105" - ], - "utils": "utils_12" - }, - "locked": { - "lastModified": 1640022647, - "narHash": "sha256-M+YnF7Zj/7QK2pu0T75xNVaX0eEeijtBH8yz+jEHIMM=", - "owner": "input-output-hk", - "repo": "cardano-node", - "rev": "814df2c146f5d56f8c35a681fe75e85b905aed5d", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "cardano-node", - "rev": "814df2c146f5d56f8c35a681fe75e85b905aed5d", - "type": "github" - } - }, - "root": { - "inputs": { - "ctl": "ctl", - "flake-compat": "flake-compat_21", - "nixpkgs": [ - "ctl", - "nixpkgs" - ] - } - }, - "stackage": { - "flake": false, - "locked": { - "lastModified": 1654219171, - "narHash": "sha256-5kp4VTlum+AMmoIbhtrcVSEfYhR4oTKSrwe1iysD8uU=", - "owner": "input-output-hk", - "repo": "stackage.nix", - "rev": "6d1fc076976ce6c45da5d077bf882487076efe5c", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "stackage.nix", - "type": "github" - } - }, - "stackage_10": { - "flake": false, - "locked": { - "lastModified": 1639012797, - "narHash": "sha256-hiLyBa5XFBvxD+BcYPKyYd/0dNMccxAuywFNqYtIIvs=", - "owner": "input-output-hk", - "repo": "stackage.nix", - "rev": "9ea6ea359da91c75a71e334b25aa7dc5ddc4b2c6", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "stackage.nix", - "type": "github" - } - }, - "stackage_11": { - "flake": false, - "locked": { - "lastModified": 1667610757, - "narHash": "sha256-H4dlMk5EW50xOtGo+5Srm3HGQV1+hY9ttgRQ+Sew5uA=", - "owner": "input-output-hk", - "repo": "stackage.nix", - "rev": "01d8ea53f65b08910003a1990547bab75ed6068a", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "stackage.nix", - "type": "github" - } - }, - "stackage_12": { - "flake": false, + "nixpkgs-2105" + ], + "utils": "utils_2" + }, "locked": { - "lastModified": 1656898145, - "narHash": "sha256-EMgMzdANg6r5gEUkMtv5ujDo2/Kx7JJXoXiDKjDVoLw=", + "lastModified": 1640022647, + "narHash": "sha256-M+YnF7Zj/7QK2pu0T75xNVaX0eEeijtBH8yz+jEHIMM=", "owner": "input-output-hk", - "repo": "stackage.nix", - "rev": "835a5f2d2a1acafb77add430fc8c2dd47282ef32", + "repo": "cardano-node", + "rev": "814df2c146f5d56f8c35a681fe75e85b905aed5d", "type": "github" }, "original": { "owner": "input-output-hk", - "repo": "stackage.nix", + "repo": "cardano-node", + "rev": "814df2c146f5d56f8c35a681fe75e85b905aed5d", "type": "github" } }, - "stackage_13": { - "flake": false, + "plutus-example_2": { + "inputs": { + "customConfig": "customConfig_8", + "haskellNix": "haskellNix_8", + "iohkNix": "iohkNix_8", + "nixpkgs": [ + "ctl", + "ogmios-nixos", + "cardano-node", + "node-snapshot", + "plutus-example", + "haskellNix", + "nixpkgs-2105" + ], + "utils": "utils_7" + }, "locked": { - "lastModified": 1643073493, - "narHash": "sha256-5cPd1+i/skvJY9vJO1BhVRPcJObqkxDSywBEppDmb1U=", + "lastModified": 1640022647, + "narHash": "sha256-M+YnF7Zj/7QK2pu0T75xNVaX0eEeijtBH8yz+jEHIMM=", "owner": "input-output-hk", - "repo": "stackage.nix", - "rev": "48e1188855ca38f3b7e2a8dba5352767a2f0a8f7", + "repo": "cardano-node", + "rev": "814df2c146f5d56f8c35a681fe75e85b905aed5d", "type": "github" }, "original": { "owner": "input-output-hk", - "repo": "stackage.nix", + "repo": "cardano-node", + "rev": "814df2c146f5d56f8c35a681fe75e85b905aed5d", "type": "github" } }, - "stackage_14": { + "root": { + "inputs": { + "ctl": "ctl", + "flake-compat": "flake-compat_15", + "nixpkgs": [ + "ctl", + "nixpkgs" + ] + } + }, + "stackage": { "flake": false, "locked": { - "lastModified": 1643073493, - "narHash": "sha256-5cPd1+i/skvJY9vJO1BhVRPcJObqkxDSywBEppDmb1U=", + "lastModified": 1654219171, + "narHash": "sha256-5kp4VTlum+AMmoIbhtrcVSEfYhR4oTKSrwe1iysD8uU=", "owner": "input-output-hk", "repo": "stackage.nix", - "rev": "48e1188855ca38f3b7e2a8dba5352767a2f0a8f7", + "rev": "6d1fc076976ce6c45da5d077bf882487076efe5c", "type": "github" }, "original": { @@ -9865,7 +6957,7 @@ "type": "github" } }, - "stackage_15": { + "stackage_10": { "flake": false, "locked": { "lastModified": 1639012797, @@ -9881,7 +6973,7 @@ "type": "github" } }, - "stackage_16": { + "stackage_11": { "flake": false, "locked": { "lastModified": 1667610757, @@ -9897,7 +6989,7 @@ "type": "github" } }, - "stackage_17": { + "stackage_12": { "flake": false, "locked": { "lastModified": 1669338854, @@ -10091,8 +7183,7 @@ "flake-utils": "flake-utils_17", "makes": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "haskell-nix", "tullia", "std", @@ -10101,8 +7192,7 @@ "mdbook-kroki-preprocessor": "mdbook-kroki-preprocessor_2", "microvm": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "haskell-nix", "tullia", "std", @@ -10110,7 +7200,7 @@ ], "n2c": "n2c_2", "nixago": "nixago_2", - "nixpkgs": "nixpkgs_20", + "nixpkgs": "nixpkgs_18", "yants": "yants_2" }, "locked": { @@ -10129,52 +7219,10 @@ }, "std_3": { "inputs": { - "blank": "blank_6", + "blank": "blank_5", "devshell": "devshell_3", "dmerge": "dmerge_3", - "flake-utils": "flake-utils_25", - "makes": [ - "ctl", - "ogmios-nixos", - "haskell-nix", - "tullia", - "std", - "blank" - ], - "mdbook-kroki-preprocessor": "mdbook-kroki-preprocessor_3", - "microvm": [ - "ctl", - "ogmios-nixos", - "haskell-nix", - "tullia", - "std", - "blank" - ], - "n2c": "n2c_3", - "nixago": "nixago_3", - "nixpkgs": "nixpkgs_28", - "yants": "yants_3" - }, - "locked": { - "lastModified": 1665513321, - "narHash": "sha256-D6Pacw9yf/HMs84KYuCxHXnNDL7v43gtcka5URagFqE=", - "owner": "divnix", - "repo": "std", - "rev": "94a90eedb9cfc115b12ae8f6622d9904788559e4", - "type": "github" - }, - "original": { - "owner": "divnix", - "repo": "std", - "type": "github" - } - }, - "std_4": { - "inputs": { - "blank": "blank_7", - "devshell": "devshell_4", - "dmerge": "dmerge_4", - "flake-utils": "flake-utils_29", + "flake-utils": "flake-utils_21", "makes": [ "ctl", "plutip", @@ -10184,7 +7232,7 @@ "std", "blank" ], - "mdbook-kroki-preprocessor": "mdbook-kroki-preprocessor_4", + "mdbook-kroki-preprocessor": "mdbook-kroki-preprocessor_3", "microvm": [ "ctl", "plutip", @@ -10194,10 +7242,10 @@ "std", "blank" ], - "n2c": "n2c_4", - "nixago": "nixago_4", - "nixpkgs": "nixpkgs_32", - "yants": "yants_4" + "n2c": "n2c_3", + "nixago": "nixago_3", + "nixpkgs": "nixpkgs_22", + "yants": "yants_3" }, "locked": { "lastModified": 1665513321, @@ -10245,8 +7293,7 @@ "nix2container": "nix2container_2", "nixpkgs": [ "ctl", - "ogmios-datum-cache-nixos", - "ogmios", + "ogmios-nixos", "haskell-nix", "nixpkgs" ], @@ -10270,32 +7317,6 @@ "inputs": { "nix-nomad": "nix-nomad_3", "nix2container": "nix2container_3", - "nixpkgs": [ - "ctl", - "ogmios-nixos", - "haskell-nix", - "nixpkgs" - ], - "std": "std_3" - }, - "locked": { - "lastModified": 1666200256, - "narHash": "sha256-cJPS8zBu30SMhxMe7I8DWutwqMuhPsEez87y9gxMKc4=", - "owner": "input-output-hk", - "repo": "tullia", - "rev": "575362c2244498e8d2c97f72861510fa72e75d44", - "type": "github" - }, - "original": { - "owner": "input-output-hk", - "repo": "tullia", - "type": "github" - } - }, - "tullia_4": { - "inputs": { - "nix-nomad": "nix-nomad_4", - "nix2container": "nix2container_4", "nixpkgs": [ "ctl", "plutip", @@ -10303,7 +7324,7 @@ "haskell-nix", "nixpkgs" ], - "std": "std_4" + "std": "std_3" }, "locked": { "lastModified": 1666200256, @@ -10319,36 +7340,6 @@ "type": "github" } }, - "unstable_nixpkgs": { - "locked": { - "lastModified": 1653307806, - "narHash": "sha256-VPej3GE4IBMwYnXRfbiVqMWKa32+ysuvbHRkQXD0gTw=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "9d7aff488a8f9429d9e6cd82c10dffbf21907fb1", - "type": "github" - }, - "original": { - "owner": "NixOS", - "repo": "nixpkgs", - "type": "github" - } - }, - "unstable_nixpkgs_2": { - "locked": { - "lastModified": 1653307806, - "narHash": "sha256-VPej3GE4IBMwYnXRfbiVqMWKa32+ysuvbHRkQXD0gTw=", - "owner": "NixOS", - "repo": "nixpkgs", - "rev": "9d7aff488a8f9429d9e6cd82c10dffbf21907fb1", - "type": "github" - }, - "original": { - "owner": "NixOS", - "repo": "nixpkgs", - "type": "github" - } - }, "utils": { "locked": { "lastModified": 1623875721, @@ -10380,81 +7371,6 @@ } }, "utils_11": { - "locked": { - "lastModified": 1623875721, - "narHash": "sha256-A8BU7bjS5GirpAUv4QA+QnJ4CceLHkcXdRp4xITDB0s=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "f7e004a55b120c02ecb6219596820fcd32ca8772", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "utils_12": { - "locked": { - "lastModified": 1638122382, - "narHash": "sha256-sQzZzAbvKEqN9s0bzWuYmRaA03v40gaJ4+iL1LXjaeI=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "74f7e4319258e287b0f9cb95426c9853b282730b", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "utils_13": { - "locked": { - "lastModified": 1623875721, - "narHash": "sha256-A8BU7bjS5GirpAUv4QA+QnJ4CceLHkcXdRp4xITDB0s=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "f7e004a55b120c02ecb6219596820fcd32ca8772", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "utils_14": { - "locked": { - "lastModified": 1653893745, - "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "1ed9fb1935d260de5fe1c2f7ee0ebaae17ed2fa1", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "utils_15": { - "locked": { - "lastModified": 1653893745, - "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "1ed9fb1935d260de5fe1c2f7ee0ebaae17ed2fa1", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "utils_16": { "locked": { "lastModified": 1653893745, "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", @@ -10615,32 +7531,6 @@ } }, "yants_2": { - "inputs": { - "nixpkgs": [ - "ctl", - "ogmios-datum-cache-nixos", - "ogmios", - "haskell-nix", - "tullia", - "std", - "nixpkgs" - ] - }, - "locked": { - "lastModified": 1660507851, - "narHash": "sha256-BKjq7JnVuUR/xDtcv6Vm9GYGKAblisXrAgybor9hT/s=", - "owner": "divnix", - "repo": "yants", - "rev": "0b895ca02a8fa72bad50b454cb3e7d8a66407c96", - "type": "github" - }, - "original": { - "owner": "divnix", - "repo": "yants", - "type": "github" - } - }, - "yants_3": { "inputs": { "nixpkgs": [ "ctl", @@ -10665,7 +7555,7 @@ "type": "github" } }, - "yants_4": { + "yants_3": { "inputs": { "nixpkgs": [ "ctl", diff --git a/templates/ctl-scaffold/flake.nix b/templates/ctl-scaffold/flake.nix index 11f59fbae8..69e179de7a 100644 --- a/templates/ctl-scaffold/flake.nix +++ b/templates/ctl-scaffold/flake.nix @@ -10,7 +10,7 @@ type = "github"; owner = "Plutonomicon"; repo = "cardano-transaction-lib"; - rev = "27f997461fda4a6f7eb52f1165a91d7d453fb990"; + rev = "001b639606f341489968d599fb0cef2900aeb474"; }; # To use the same version of `nixpkgs` as we do nixpkgs.follows = "ctl/nixpkgs"; diff --git a/templates/ctl-scaffold/packages.dhall b/templates/ctl-scaffold/packages.dhall index 7518057751..dcd15c5670 100644 --- a/templates/ctl-scaffold/packages.dhall +++ b/templates/ctl-scaffold/packages.dhall @@ -348,7 +348,7 @@ let additions = , "variant" ] , repo = "https://github.com/Plutonomicon/cardano-transaction-lib.git" - , version = "27f997461fda4a6f7eb52f1165a91d7d453fb990" + , version = "001b639606f341489968d599fb0cef2900aeb474" } , noble-secp256k1 = { dependencies = From 621a718af2d3301074ba32c9e92afe625020fe8d Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Fri, 16 Dec 2022 14:00:44 +0000 Subject: [PATCH 120/373] Fix malformed nix/runtime.nix --- nix/runtime.nix | 319 ++++++++++++++++++++++++------------------------ 1 file changed, 159 insertions(+), 160 deletions(-) diff --git a/nix/runtime.nix b/nix/runtime.nix index 8eb3972357..4297c34563 100644 --- a/nix/runtime.nix +++ b/nix/runtime.nix @@ -20,176 +20,175 @@ rec { tag = "1.35.4"; }; ogmios = { port = 1337; }; + kupo = { + port = 1442; + since = "origin"; + match = "*/*"; # matches Shelley addresses only + tag = "v2.2.0"; + # TODO: Do we want to support connection through ogmios? + }; + # Additional config that will be included in Arion's `docker-compose.raw`. This + # corresponds directly to YAML that would be written in a `docker-compose` file, + # e.g. volumes + extraDockerCompose = { }; + # Additional services to include in the `docker-compose` config that Arion + # produces. + # + # For a docker image: + # + # ``` + # foo = { + # service = { + # image = "bar:foo"; + # command = [ + # "baz" + # "--quux" + # ]; + # }; + # }; + # ``` + # + # For a Nix package: + # + # ``` + # foo = { + # service = { + # useHostStore = true; + # command = [ + # "${pkgs.baz}/bin/baz" + # "--quux" + # ]; + # }; + # }; + # + # ``` + extraServices = { }; }; - kupo = { - port = 1442; - since = "origin"; - match = "*/*"; # matches Shelley addresses only - tag = "v2.2.0"; - # TODO: Do we want to support connection through ogmios? - }; - # Additional config that will be included in Arion's `docker-compose.raw`. This - # corresponds directly to YAML that would be written in a `docker-compose` file, - # e.g. volumes - extraDockerCompose = { }; - # Additional services to include in the `docker-compose` config that Arion - # produces. - # - # For a docker image: - # - # ``` - # foo = { - # service = { - # image = "bar:foo"; - # command = [ - # "baz" - # "--quux" - # ]; - # }; - # }; - # ``` - # - # For a Nix package: - # - # ``` - # foo = { - # service = { - # useHostStore = true; - # command = [ - # "${pkgs.baz}/bin/baz" - # "--quux" - # ]; - # }; - # }; - # - # ``` - extraServices = { }; -}; -buildCtlRuntime = pkgs: extraConfig: { ... }: -let -inherit (builtins) toString; -config = with pkgs.lib; -fix (final: -recursiveUpdate -(defaultConfig final) -( -if isFunction extraConfig -then extraConfig final -else extraConfig -) -); -nodeDbVol = "node-${config.network.name}-db"; -nodeIpcVol = "node-${config.network.name}-ipc"; -kupoDbVol = "kupo-${config.network.name}-db"; -nodeSocketPath = "/ipc/node.socket"; -bindPort = port: "${toString port}:${toString port}"; -defaultServices = with config; { -cardano-node = { -service = { -image = "inputoutput/cardano-node:${node.tag}"; -ports = [ (bindPort node.port) ]; -volumes = [ -"${config.cardano-configurations}/network/${config.network.name}/cardano-node:/config" -"${config.cardano-configurations}/network/${config.network.name}/genesis:/genesis" -"${nodeDbVol}:/data" -"${nodeIpcVol}:/ipc" -]; -command = [ -"run" -"--config" -"/config/config.json" -"--database-path" -"/data/db" -"--socket-path" -"${nodeSocketPath}" -"--topology" -"/config/topology.json" -]; -}; -}; -kupo = { -service = { -image = "cardanosolutions/kupo:${kupo.tag}"; -ports = [ (bindPort kupo.port) ]; -volumes = [ -"${config.cardano-configurations}/network/${config.network.name}:/config" -"${nodeIpcVol}:/ipc" -"${kupoDbVol}:/kupo-db" -]; -command = [ -"--node-config" -"/config/cardano-node/config.json" -"--node-socket" -"${nodeSocketPath}" -"--since" -"${kupo.since}" -"--defer-db-indexes" -"--match" -"${"${kupo.match}"}" -"--host" -"0.0.0.0" -"--workdir" -"kupo-db" -]; -}; -}; -ogmios = { -service = { -useHostStore = true; -ports = [ (bindPort ogmios.port) ]; -volumes = [ -"${config.cardano-configurations}/network/${config.network.name}:/config" -"${nodeIpcVol}:/ipc" -]; -command = [ -"${pkgs.bash}/bin/sh" -"-c" -'' + buildCtlRuntime = pkgs: extraConfig: { ... }: + let + inherit (builtins) toString; + config = with pkgs.lib; + fix (final: + recursiveUpdate + (defaultConfig final) + ( + if isFunction extraConfig + then extraConfig final + else extraConfig + ) + ); + nodeDbVol = "node-${config.network.name}-db"; + nodeIpcVol = "node-${config.network.name}-ipc"; + kupoDbVol = "kupo-${config.network.name}-db"; + nodeSocketPath = "/ipc/node.socket"; + bindPort = port: "${toString port}:${toString port}"; + defaultServices = with config; { + cardano-node = { + service = { + image = "inputoutput/cardano-node:${node.tag}"; + ports = [ (bindPort node.port) ]; + volumes = [ + "${config.cardano-configurations}/network/${config.network.name}/cardano-node:/config" + "${config.cardano-configurations}/network/${config.network.name}/genesis:/genesis" + "${nodeDbVol}:/data" + "${nodeIpcVol}:/ipc" + ]; + command = [ + "run" + "--config" + "/config/config.json" + "--database-path" + "/data/db" + "--socket-path" + "${nodeSocketPath}" + "--topology" + "/config/topology.json" + ]; + }; + }; + kupo = { + service = { + image = "cardanosolutions/kupo:${kupo.tag}"; + ports = [ (bindPort kupo.port) ]; + volumes = [ + "${config.cardano-configurations}/network/${config.network.name}:/config" + "${nodeIpcVol}:/ipc" + "${kupoDbVol}:/kupo-db" + ]; + command = [ + "--node-config" + "/config/cardano-node/config.json" + "--node-socket" + "${nodeSocketPath}" + "--since" + "${kupo.since}" + "--defer-db-indexes" + "--match" + "${"${kupo.match}"}" + "--host" + "0.0.0.0" + "--workdir" + "kupo-db" + ]; + }; + }; + ogmios = { + service = { + useHostStore = true; + ports = [ (bindPort ogmios.port) ]; + volumes = [ + "${config.cardano-configurations}/network/${config.network.name}:/config" + "${nodeIpcVol}:/ipc" + ]; + command = [ + "${pkgs.bash}/bin/sh" + "-c" + '' ${pkgs.ogmios}/bin/ogmios \ --host ogmios \ --port ${toString ogmios.port} \ --node-socket /ipc/node.socket \ --node-config /config/cardano-node/config.json '' -]; -}; -}; -}; -in -{ -docker-compose.raw = pkgs.lib.recursiveUpdate -{ -volumes = { -"${nodeDbVol}" = { }; -"${nodeIpcVol}" = { }; -"${kupoDbVol}" = { }; -}; -} -config.extraDockerCompose; -services = pkgs.lib.recursiveUpdate defaultServices config.extraServices; -}; + ]; + }; + }; + }; + in + { + docker-compose.raw = pkgs.lib.recursiveUpdate + { + volumes = { + "${nodeDbVol}" = { }; + "${nodeIpcVol}" = { }; + "${kupoDbVol}" = { }; + }; + } + config.extraDockerCompose; + services = pkgs.lib.recursiveUpdate defaultServices config.extraServices; + }; -# Makes a set compatible with flake `apps` to launch all runtime services -launchCtlRuntime = pkgs: config: -let -binPath = "ctl-runtime"; -prebuilt = (pkgs.arion.build { -inherit pkgs; -modules = [ (buildCtlRuntime pkgs config) ]; -}).outPath; -script = pkgs.writeShellApplication { -name = binPath; -runtimeInputs = [ pkgs.arion pkgs.docker ]; -text = -'' + # Makes a set compatible with flake `apps` to launch all runtime services + launchCtlRuntime = pkgs: config: + let + binPath = "ctl-runtime"; + prebuilt = (pkgs.arion.build { + inherit pkgs; + modules = [ (buildCtlRuntime pkgs config) ]; + }).outPath; + script = pkgs.writeShellApplication { + name = binPath; + runtimeInputs = [ pkgs.arion pkgs.docker ]; + text = + '' ${pkgs.arion}/bin/arion --prebuilt-file ${prebuilt} up ''; -}; -in -{ -type = "app"; -program = "${script}/bin/${binPath}"; -}; + }; + in + { + type = "app"; + program = "${script}/bin/${binPath}"; + }; } From 403759818a886eb745687ef3a32b0944eecff2be Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Fri, 16 Dec 2022 14:16:59 +0000 Subject: [PATCH 121/373] Update spago-packages in template. --- templates/ctl-scaffold/spago-packages.nix | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/templates/ctl-scaffold/spago-packages.nix b/templates/ctl-scaffold/spago-packages.nix index c7cba0da4a..0dd10cce14 100644 --- a/templates/ctl-scaffold/spago-packages.nix +++ b/templates/ctl-scaffold/spago-packages.nix @@ -211,11 +211,11 @@ let "cardano-transaction-lib" = pkgs.stdenv.mkDerivation { name = "cardano-transaction-lib"; - version = "27f997461fda4a6f7eb52f1165a91d7d453fb990"; + version = "001b639606f341489968d599fb0cef2900aeb474"; src = pkgs.fetchgit { url = "https://github.com/Plutonomicon/cardano-transaction-lib.git"; - rev = "27f997461fda4a6f7eb52f1165a91d7d453fb990"; - sha256 = "0zfsbh2f8dah9d3z3avlhrgkcpc37378vxwj6cpmyls60ryc3m0k"; + rev = "001b639606f341489968d599fb0cef2900aeb474"; + sha256 = "1rbpq2ikndjar8h3hpq5yz4mqga7276ggdbws34ppq3miczh9czz"; }; phases = "installPhase"; installPhase = "ln -s $src $out"; From 6712888d9e90756ca06e86ec043cfd3862aaa985 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Fri, 16 Dec 2022 17:44:35 +0000 Subject: [PATCH 122/373] Update testplan, make kupo queries more testable --- doc/test-plan.md | 14 ++++++-- src/Internal/QueryM/Kupo.purs | 67 ++++++++++++++++++++++++++++------- 2 files changed, 66 insertions(+), 15 deletions(-) diff --git a/doc/test-plan.md b/doc/test-plan.md index ab86986bf9..57829640d3 100644 --- a/doc/test-plan.md +++ b/doc/test-plan.md @@ -120,12 +120,14 @@ In addition to the constraints/lookups listed above, there are several other cri - [x] `balanceTx` - [x] `signTransaction` - [x] `submit` - - [x] `getTxByHash` - [x] `awaitTxConfirmed` (implies `awaitTxConfirmedWithTimeout`) + - [ ] `getTxMetadata` - `Contract.Scripts.*` - [x] `validatorHash` - [x] `mintingPolicy` - [x] `applyArgs` + - [ ] `getScriptByHash` + - [ ] `getScriptsByHashes` - `Contract.Hashing.*` - [x] `datumHash` - [x] `plutusScriptHash` @@ -233,5 +235,11 @@ Currently, we require parsing tests for the following data structures, organized - `TransactionWitnessSet` - [x] Serialization - [x] Deserialization - -TODO: Kupo and Blockfrost +- Kupo + - [ ] `KupoUtxoMap` + - [ ] `KupoDatum` + - [ ] `KupoScriptRef` + - [ ] `KupoUtxoSlot` + - [ ] `KupoMetadata` +- Blockfrost + - TODO diff --git a/src/Internal/QueryM/Kupo.purs b/src/Internal/QueryM/Kupo.purs index e38835011d..f5d71a8127 100644 --- a/src/Internal/QueryM/Kupo.purs +++ b/src/Internal/QueryM/Kupo.purs @@ -151,13 +151,11 @@ isTxConfirmed th = do -- Exported due to Ogmios requiring confirmations at a websocket level isTxConfirmedAff :: ServerConfig -> TransactionHash -> Aff (Either ClientError (Maybe Slot)) -isTxConfirmedAff config (TransactionHash txHash) = do +isTxConfirmedAff config (TransactionHash txHash) = runExceptT do let endpoint = "/matches/*@" <> byteArrayToHex txHash - kupoGetRequestAff config endpoint - <#> handleAffjaxResponse >>> map \utxos -> - case uncons (utxos :: _ { created_at :: { slot_no :: Slot } }) of - Just { head } -> Just head.created_at.slot_no - _ -> Nothing + utxos <- ExceptT $ handleAffjaxResponse <$> kupoGetRequestAff config endpoint + -- Take the first utxo's slot to give the transactions slot + pure $ uncons utxos <#> _.head >>> unwrapKupoUtxoSlot getTxMetadata :: TransactionHash @@ -170,13 +168,10 @@ getTxMetadata txHash = runExceptT do endpoint = "/metadata/" <> BigNum.toString (unwrap slot) <> "?transaction_id=" <> byteArrayToHex (unwrap txHash) - generalTxMetadatas <- ExceptT $ handleAffjaxResponse <$> kupoGetRequest + metadata <- ExceptT $ handleAffjaxResponse <$> kupoGetRequest endpoint - pure case uncons (generalTxMetadatas :: _ { raw :: String }) of - Just { head, tail: [] } -> - hexToByteArray head.raw >>= - (fromBytes >=> convertGeneralTransactionMetadata >>> hush) - _ -> Nothing + -- `KupoMetadata` will fail parsing if there is more than one response + pure $ unwrapKupoMetadata metadata -------------------------------------------------------------------------------- -- `utxosAt` response parsing @@ -405,6 +400,54 @@ instance DecodeAeson KupoScriptRef where flip note (convertNativeScript nativeScript) $ TypeMismatch "decodeNativeScript: failed to convert native script" +------------------------------------------------------------------------------- +-- `isTxConfirmed` response parsing +------------------------------------------------------------------------------- + +newtype KupoUtxoSlot = KupoUtxoSlot Slot + +derive instance Generic KupoUtxoSlot _ +derive instance Eq KupoUtxoSlot + +instance Show KupoUtxoSlot where + show = genericShow + +instance DecodeAeson KupoUtxoSlot where + decodeAeson = decodeAeson >>> map (slot >>> KupoUtxoSlot) + where + slot :: { created_at :: { slot_no :: Slot } } -> Slot + slot = _.created_at.slot_no + +unwrapKupoUtxoSlot :: KupoUtxoSlot -> Slot +unwrapKupoUtxoSlot (KupoUtxoSlot slot) = slot + +-------------------------------------------------------------------------------- +-- `getTxMetadata` reponse parsing +-------------------------------------------------------------------------------- + +newtype KupoMetadata = KupoMetadata (Maybe GeneralTransactionMetadata) + +derive instance Generic KupoMetadata _ +derive instance Eq KupoMetadata + +instance Show KupoMetadata where + show = genericShow + +instance DecodeAeson KupoMetadata where + decodeAeson = decodeAeson >=> case _ of + [ { raw } :: { raw :: String } ] -> do + ba <- flip note (hexToByteArray raw) $ + TypeMismatch "Hexadecimal String" + metadata <- flip note (fromBytes ba) $ + TypeMismatch "Hexadecimal encoded Metadata" + -- Conversion should always succeed, so use it as the `Just` + pure $ KupoMetadata $ hush $ convertGeneralTransactionMetadata metadata + [] -> Right $ KupoMetadata Nothing + _ -> Left $ TypeMismatch "Singleton or Empty Array" + +unwrapKupoMetadata :: KupoMetadata -> Maybe GeneralTransactionMetadata +unwrapKupoMetadata (KupoMetadata mbMetadata) = mbMetadata + -------------------------------------------------------------------------------- -- Helpers -------------------------------------------------------------------------------- From 0bcd4395b9e884819ba6fbbd94b7e5453e00f06f Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Fri, 16 Dec 2022 19:03:18 +0100 Subject: [PATCH 123/373] BalanceTx: Always add at least one input --- src/Internal/BalanceTx/BalanceTx.purs | 59 +++++++++++++++------------ 1 file changed, 33 insertions(+), 26 deletions(-) diff --git a/src/Internal/BalanceTx/BalanceTx.purs b/src/Internal/BalanceTx/BalanceTx.purs index dd6fbd55c1..426eb30652 100644 --- a/src/Internal/BalanceTx/BalanceTx.purs +++ b/src/Internal/BalanceTx/BalanceTx.purs @@ -155,6 +155,7 @@ import Data.Set as Set import Data.Traversable (for, traverse) import Data.Tuple (fst) import Data.Tuple.Nested (type (/\), (/\)) +import Debug (spy, traceM) import Effect.Class (liftEffect) import Partial.Unsafe (unsafePartial) @@ -286,18 +287,31 @@ runBalancer p = do worker (PrebalanceTx state) = do logBalancerState "Pre-balancing (Stage 1)" p.allUtxos state prebalanceTx state >>= runNextBalancerStep - worker (BalanceChangeAndMinFee state@{ transaction, minFee }) = do - logBalancerState "Balancing change and fees (Stage 2)" p.allUtxos state - { transaction: balancedTx, minFee: newMinFee } <- evaluateTx state - case newMinFee <= minFee of - true -> - logTransaction "Balanced transaction (Done)" p.allUtxos balancedTx - *> finalizeTransaction balancedTx p.allUtxos - false -> - runNextBalancerStep $ state - { transaction = transaction # _body' <<< _fee .~ Coin newMinFee - , minFee = newMinFee - } + worker (BalanceChangeAndMinFee s@{ transaction, minFee, leftoverUtxos }) = + do + logBalancerState "Balancing change and fees (Stage 2)" p.allUtxos s + { transaction: balancedTx, minFee: newMinFee } <- evaluateTx s + case newMinFee <= minFee of + true -> + if (Set.isEmpty $ balancedTx ^. _body' <<< _inputs) then do + selectionState <- + performMultiAssetSelection p.strategy leftoverUtxos + (lovelaceValueOf one) + runNextBalancerStep $ s + { transaction = + balancedTx # _body' <<< _inputs %~ + Set.union (selectedInputs selectionState) + , leftoverUtxos = + selectionState ^. _leftoverUtxos + } + else + logTransaction "Balanced transaction (Done)" p.allUtxos balancedTx + *> finalizeTransaction balancedTx p.allUtxos + false -> + runNextBalancerStep $ s + { transaction = transaction # _body' <<< _fee .~ Coin newMinFee + , minFee = newMinFee + } -- | Determines which balancing step will be performed next. -- | @@ -321,20 +335,13 @@ runBalancer p = do -- | utxo set so that the total input value is sufficient to cover all -- | transaction outputs, including generated change and min fee. prebalanceTx :: BalancerState -> BalanceTxM BalancerState - prebalanceTx state@{ transaction, changeOutputs, leftoverUtxos } = do - - selectionState <- performCoinSelection - let - selectedInputs' :: Set TransactionInput - selectedInputs' = selectedInputs selectionState - - unbalancedTxWithInputs :: UnattachedUnbalancedTx - unbalancedTxWithInputs = - transaction # _body' <<< _inputs %~ Set.union selectedInputs' - - pure $ state - { transaction = unbalancedTxWithInputs - , leftoverUtxos = selectionState ^. _leftoverUtxos + prebalanceTx state@{ transaction, changeOutputs, leftoverUtxos } = + performCoinSelection <#> \selectionState -> state + { transaction = + transaction # _body' <<< _inputs %~ + Set.union (selectedInputs selectionState) + , leftoverUtxos = + selectionState ^. _leftoverUtxos } where performCoinSelection :: BalanceTxM SelectionState From 95262bd0b0df7532c54fbc68bd3f60d24a1f11ff Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Fri, 16 Dec 2022 19:09:06 +0100 Subject: [PATCH 124/373] Fix warnings --- src/Internal/BalanceTx/BalanceTx.purs | 3 --- 1 file changed, 3 deletions(-) diff --git a/src/Internal/BalanceTx/BalanceTx.purs b/src/Internal/BalanceTx/BalanceTx.purs index 426eb30652..5a16cf7851 100644 --- a/src/Internal/BalanceTx/BalanceTx.purs +++ b/src/Internal/BalanceTx/BalanceTx.purs @@ -124,7 +124,6 @@ import Ctl.Internal.QueryM.Utxos import Ctl.Internal.Serialization.Address (Address) import Ctl.Internal.Types.OutputDatum (OutputDatum(NoOutputDatum)) import Ctl.Internal.Types.ScriptLookups (UnattachedUnbalancedTx) -import Ctl.Internal.Types.Transaction (TransactionInput) import Ctl.Internal.Types.UnbalancedTransaction (_utxoIndex) import Data.Array as Array import Data.Array.NonEmpty (NonEmptyArray) @@ -150,12 +149,10 @@ import Data.Log.Tag (fromArray, tag) as TagSet import Data.Map (empty, filterKeys, lookup, union) as Map import Data.Maybe (Maybe(Nothing, Just), fromJust, fromMaybe, isJust, maybe) import Data.Newtype (class Newtype, unwrap, wrap) -import Data.Set (Set) import Data.Set as Set import Data.Traversable (for, traverse) import Data.Tuple (fst) import Data.Tuple.Nested (type (/\), (/\)) -import Debug (spy, traceM) import Effect.Class (liftEffect) import Partial.Unsafe (unsafePartial) From 36928211c489dcee2565b3175c38515c954b3f44 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Fri, 16 Dec 2022 19:25:34 +0100 Subject: [PATCH 125/373] Fix CHANGELOG.md --- CHANGELOG.md | 35 +++++++++++++++++++++++++---------- 1 file changed, 25 insertions(+), 10 deletions(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index 820c210fd6..91907ad2a0 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -7,36 +7,52 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) -- [[v4.0.0] - 2022-12-15](#v400---2022-12-15) +- [[Unreleased]](#unreleased) - [Added](#added) - [Changed](#changed) - [Removed](#removed) - [Fixed](#fixed) - - [Runtime Dependencies](#runtime-dependencies) -- [[3.0.0] - 2022-11-21](#300---2022-11-21) +- [[v4.0.0] - 2022-12-15](#v400---2022-12-15) - [Added](#added-1) - [Changed](#changed-1) - [Removed](#removed-1) - [Fixed](#fixed-1) - - [Runtime Dependencies](#runtime-dependencies-1) -- [[2.0.0] - 2022-09-12](#200---2022-09-12) + - [Runtime Dependencies](#runtime-dependencies) +- [[3.0.0] - 2022-11-21](#300---2022-11-21) - [Added](#added-2) - [Changed](#changed-2) - [Removed](#removed-2) - [Fixed](#fixed-2) -- [[2.0.0-alpha] - 2022-07-05](#200-alpha---2022-07-05) + - [Runtime Dependencies](#runtime-dependencies-1) +- [[2.0.0] - 2022-09-12](#200---2022-09-12) - [Added](#added-3) - - [Removed](#removed-3) - [Changed](#changed-3) + - [Removed](#removed-3) - [Fixed](#fixed-3) -- [[1.1.0] - 2022-06-30](#110---2022-06-30) +- [[2.0.0-alpha] - 2022-07-05](#200-alpha---2022-07-05) + - [Added](#added-4) + - [Removed](#removed-4) + - [Changed](#changed-4) - [Fixed](#fixed-4) -- [[1.0.1] - 2022-06-17](#101---2022-06-17) +- [[1.1.0] - 2022-06-30](#110---2022-06-30) - [Fixed](#fixed-5) +- [[1.0.1] - 2022-06-17](#101---2022-06-17) + - [Fixed](#fixed-6) - [[1.0.0] - 2022-06-10](#100---2022-06-10) +## [Unreleased] + +### Added +- `blake2b224Hash` and `blake2b224HashHex` functions for computing blake2b-224 hashes of arbitrary byte arrays ([#1323](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1323)) + +### Changed + +### Removed + +### Fixed + ## [v4.0.0] - 2022-12-15 ### Added @@ -44,7 +60,6 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) - NuFi wallet support ([#1265](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1265)) - Add `submitTxFromConstraints` and `submitTxFromConstraintsReturningFee` in `Contract.Transaction`. `submitTxFromConstraints` builds a transaction that satisfies the constraints, then submits it to the network. It is analogous to `submitTxConstraintsWith` function in Plutus and replaces `Helpers.buildBalanceSignAndSubmitTx`. - Support for CIP-49 crypto primitives: SECP256k1 [ECDSA](./src/Contract/Crypto/Secp256k1/ECDSA.purs) and [Schnorr](./src/Contract/Crypto/Secp256k1/Schnorr.purs) (verification functions, signing and key generation) ([1273](https://github.com/Plutonomicon/cardano-transaction-lib/issues/1273)) -- `blake2b224Hash` and `blake2b224HashHex` functions for computing blake2b-224 hashes of arbitrary byte arrays ([#1323](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1323)) ### Changed From 7a51dc63f877c9a8d771c366d9ac5f5667d87407 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Fri, 16 Dec 2022 22:12:41 +0000 Subject: [PATCH 126/373] Use safe matching of tagged CSL types via CSL's exported kinds. Use UInts for foreign types where CSL internally uses a u32 --- src/Internal/ApplyArgs.purs | 3 +- src/Internal/Deserialization/Language.js | 22 +- src/Internal/Deserialization/Language.purs | 23 +- src/Internal/Deserialization/NativeScript.js | 33 ++- .../Deserialization/NativeScript.purs | 86 ++----- src/Internal/Deserialization/PlutusData.purs | 1 + src/Internal/Deserialization/Transaction.js | 77 ++---- src/Internal/Deserialization/Transaction.purs | 227 +++++++----------- .../Deserialization/UnspentOutput.purs | 23 +- src/Internal/Deserialization/WitnessSet.purs | 24 +- src/Internal/QueryM/Kupo.purs | 3 +- test/Deserialization.purs | 3 +- 12 files changed, 204 insertions(+), 321 deletions(-) diff --git a/src/Internal/ApplyArgs.purs b/src/Internal/ApplyArgs.purs index 77b5d620a8..32c00e24a2 100644 --- a/src/Internal/ApplyArgs.purs +++ b/src/Internal/ApplyArgs.purs @@ -45,5 +45,4 @@ applyArgs script paramsList = left ApplyArgsError do S.convertPlutusData (List paramsList) appliedScript <- apply_params_to_script_either params (S.convertPlutusScript script) - note "Error converting back applied script" $ D.convertPlutusScript $ - appliedScript + Right $ D.convertPlutusScript appliedScript diff --git a/src/Internal/Deserialization/Language.js b/src/Internal/Deserialization/Language.js index 0e482dae32..6bb4bb73f0 100644 --- a/src/Internal/Deserialization/Language.js +++ b/src/Internal/Deserialization/Language.js @@ -7,20 +7,12 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } -// foreign import _convertLanguage -// :: forall r.ErrorFfiHelper r -> { plutusV1 :: Language, plutusV2 :: Language } -> CSL.Language -> E r Language -exports._convertLanguage = errorHelper => langCtors => cslLang => { - try { - if (cslLang.kind() == lib.LanguageKind.PlutusV1) { - return errorHelper.valid(langCtors.plutusV1); - } else if (cslLang.kind() == lib.LanguageKind.PlutusV2) { - return errorHelper.valid(langCtors.plutusV2); - } else { - return errorHelper.error( - "_convertLanguage: Unsupported language kind: " + cslLang.kind() - ); - } - } catch (e) { - return errorHelper.error("_convertLanguage raised: " + e); +exports._convertLanguage = langCtors => cslLang => { + if (cslLang.kind() == lib.LanguageKind.PlutusV1) { + return langCtors.plutusV1; + } else if (cslLang.kind() == lib.LanguageKind.PlutusV2) { + return langCtors.plutusV2; + } else { + throw "_convertLanguage: Unsupported language kind: " + cslLang.kind(); } }; diff --git a/src/Internal/Deserialization/Language.purs b/src/Internal/Deserialization/Language.purs index f13cc17fb1..8d7c34e436 100644 --- a/src/Internal/Deserialization/Language.purs +++ b/src/Internal/Deserialization/Language.purs @@ -3,34 +3,17 @@ module Ctl.Internal.Deserialization.Language , convertLanguage ) where -import Ctl.Internal.Deserialization.Error - ( FromCslRepError - , _fromCslRepError - ) -import Ctl.Internal.Error (E) -import Ctl.Internal.FfiHelpers - ( ErrorFfiHelper - , errorHelper - ) import Ctl.Internal.Serialization.Types (Language) as Csl import Ctl.Internal.Types.Scripts (Language(PlutusV1, PlutusV2)) as T -import Data.Variant (inj) -import Type.Row (type (+)) -convertLanguage - :: forall (r :: Row Type) - . Csl.Language - -> E (FromCslRepError + r) T.Language +convertLanguage :: Csl.Language -> T.Language convertLanguage = _convertLanguage - (errorHelper (inj _fromCslRepError)) { plutusV1: T.PlutusV1 , plutusV2: T.PlutusV2 } foreign import _convertLanguage - :: forall (r :: Row Type) - . ErrorFfiHelper r - -> { plutusV1 :: T.Language, plutusV2 :: T.Language } + :: { plutusV1 :: T.Language, plutusV2 :: T.Language } -> Csl.Language - -> E r T.Language + -> T.Language diff --git a/src/Internal/Deserialization/NativeScript.js b/src/Internal/Deserialization/NativeScript.js index db9dcdbee1..bf3efb8215 100644 --- a/src/Internal/Deserialization/NativeScript.js +++ b/src/Internal/Deserialization/NativeScript.js @@ -1,18 +1,33 @@ /* global BROWSER_RUNTIME */ -const getNativeScriptAs = prop => maybe => ns => { - const res = ns[prop](); - return res == null ? maybe.nothing : maybe.just(res); +let lib; +if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { + lib = require("@emurgo/cardano-serialization-lib-browser"); +} else { + lib = require("@emurgo/cardano-serialization-lib-nodejs"); +} + +exports._convertNativeScript = handler => ns => { + switch (ns.kind()) { + case lib.NativeScriptKind.ScriptPubkey: + return handler.scriptPubkey(ns.as_script_pubkey()); + case lib.NativeScriptKind.ScriptAll: + return handler.scriptAll(ns.as_script_all()); + case lib.NativeScriptKind.ScriptAny: + return handler.scriptAny(ns.as_script_any()); + case lib.NativeScriptKind.ScriptNOfK: + return handler.scriptNOfK(ns.as_script_n_of_k()); + case lib.NativeScriptKind.TimelockStart: + return handler.timelockStart(ns.as_timelock_start()); + case lib.NativeScriptKind.TimelockExpiry: + return handler.timelockExpiry(ns.as_timelock_expiry()); + default: + throw ("Impossible native script kind: " + ns.kind()); + } }; const call = property => object => object[property](); -exports.getScriptPubkey = getNativeScriptAs("as_script_pubkey"); -exports.getScriptAll = getNativeScriptAs("as_script_all"); -exports.getScriptAny = getNativeScriptAs("as_script_any"); -exports.getScriptNOfK = getNativeScriptAs("as_script_n_of_k"); -exports.getTimelockStart = getNativeScriptAs("as_timelock_start"); -exports.getTimelockExpiry = getNativeScriptAs("as_timelock_expiry"); exports.scriptPubkey_addr_keyhash = call("addr_keyhash"); exports.scriptAllScripts = helper => helper.unpackFromProperty("native_scripts"); diff --git a/src/Internal/Deserialization/NativeScript.purs b/src/Internal/Deserialization/NativeScript.purs index 45951c1730..ff5c2dd591 100644 --- a/src/Internal/Deserialization/NativeScript.purs +++ b/src/Internal/Deserialization/NativeScript.purs @@ -4,13 +4,10 @@ module Ctl.Internal.Deserialization.NativeScript import Prelude -import Control.Alt ((<|>)) import Ctl.Internal.Cardano.Types.NativeScript as T import Ctl.Internal.FfiHelpers ( ContainerHelper - , MaybeFfiHelper , containerHelper - , maybeFfiHelper ) import Ctl.Internal.Serialization.Address (Slot(Slot)) import Ctl.Internal.Serialization.Hash (Ed25519KeyHash) @@ -24,65 +21,32 @@ import Ctl.Internal.Serialization.Types , TimelockStart ) import Ctl.Internal.Types.BigNum (BigNum) -import Data.Maybe (Maybe) -import Data.Traversable (traverse) -convertNativeScript :: NativeScript -> Maybe T.NativeScript -convertNativeScript ns = - convertScriptPubKey ns - <|> convertScriptAll ns - <|> convertScriptAny ns - <|> convertScriptNOfK ns - <|> convertTimelockStart ns - <|> convertTimelockExpiry ns - -convertScriptPubKey :: NativeScript -> Maybe T.NativeScript -convertScriptPubKey ns = do - T.ScriptPubkey <<< scriptPubkey_addr_keyhash <$> - getScriptPubkey maybeFfiHelper ns - -convertScriptAll :: NativeScript -> Maybe T.NativeScript -convertScriptAll ns = do - scriptAll <- getScriptAll maybeFfiHelper ns - T.ScriptAll <$> traverse convertNativeScript - (scriptAllScripts containerHelper scriptAll) - -convertScriptAny :: NativeScript -> Maybe T.NativeScript -convertScriptAny ns = do - scriptAny <- getScriptAny maybeFfiHelper ns - T.ScriptAny <$> traverse convertNativeScript - (scriptAnyScripts containerHelper scriptAny) - -convertScriptNOfK :: NativeScript -> Maybe T.NativeScript -convertScriptNOfK ns = do - scriptNOfK <- getScriptNOfK maybeFfiHelper ns - res <- traverse convertNativeScript - (scriptNOfKScripts containerHelper scriptNOfK) - pure $ T.ScriptNOfK (scriptNOfK_n scriptNOfK) res - -convertTimelockStart :: NativeScript -> Maybe T.NativeScript -convertTimelockStart = - map (T.TimelockStart <<< Slot <<< timelockStart_slot) - <<< getTimelockStart maybeFfiHelper - -convertTimelockExpiry :: NativeScript -> Maybe T.NativeScript -convertTimelockExpiry = do - map (T.TimelockExpiry <<< Slot <<< timelockExpiry_slot) - <<< getTimelockExpiry maybeFfiHelper - -foreign import getScriptPubkey - :: MaybeFfiHelper -> NativeScript -> Maybe ScriptPubkey - -foreign import getScriptAll :: MaybeFfiHelper -> NativeScript -> Maybe ScriptAll -foreign import getScriptAny :: MaybeFfiHelper -> NativeScript -> Maybe ScriptAny -foreign import getScriptNOfK - :: MaybeFfiHelper -> NativeScript -> Maybe ScriptNOfK - -foreign import getTimelockStart - :: MaybeFfiHelper -> NativeScript -> Maybe TimelockStart - -foreign import getTimelockExpiry - :: MaybeFfiHelper -> NativeScript -> Maybe TimelockExpiry +type ConvertNativeScript (r :: Type) = + { scriptPubkey :: ScriptPubkey -> r + , scriptAll :: ScriptAll -> r + , scriptAny :: ScriptAny -> r + , scriptNOfK :: ScriptNOfK -> r + , timelockStart :: TimelockStart -> r + , timelockExpiry :: TimelockExpiry -> r + } + +convertNativeScript :: NativeScript -> T.NativeScript +convertNativeScript ns = _convertNativeScript + { scriptPubkey: T.ScriptPubkey <<< scriptPubkey_addr_keyhash + , scriptAll: T.ScriptAll <<< map convertNativeScript <<< scriptAllScripts + containerHelper + , scriptAny: T.ScriptAny <<< map convertNativeScript <<< scriptAnyScripts + containerHelper + , scriptNOfK: T.ScriptNOfK <$> scriptNOfK_n <*> + (map convertNativeScript <<< scriptNOfKScripts containerHelper) + , timelockStart: T.TimelockStart <<< Slot <<< timelockStart_slot + , timelockExpiry: T.TimelockExpiry <<< Slot <<< timelockExpiry_slot + } + ns + +foreign import _convertNativeScript + :: ConvertNativeScript T.NativeScript -> NativeScript -> T.NativeScript foreign import scriptPubkey_addr_keyhash :: ScriptPubkey -> Ed25519KeyHash foreign import scriptAllScripts diff --git a/src/Internal/Deserialization/PlutusData.purs b/src/Internal/Deserialization/PlutusData.purs index f30cd52c5d..63d7fe88b1 100644 --- a/src/Internal/Deserialization/PlutusData.purs +++ b/src/Internal/Deserialization/PlutusData.purs @@ -35,6 +35,7 @@ import Data.Traversable (traverse) import Data.Tuple (Tuple(Tuple)) import Data.Tuple.Nested (type (/\), (/\)) +-- TODO In the other PR convertPlutusData :: PlutusData -> Maybe T.PlutusData convertPlutusData pd = convertPlutusConstr pd diff --git a/src/Internal/Deserialization/Transaction.js b/src/Internal/Deserialization/Transaction.js index d5c99090d9..ed4386c5db 100644 --- a/src/Internal/Deserialization/Transaction.js +++ b/src/Internal/Deserialization/Transaction.js @@ -208,47 +208,20 @@ exports._unpackMetadataMap = containerHelper => exports._unpackMetadataList = containerHelper => containerHelper.unpack; exports._convertMetadatum = metadataCtors => cslMetadatum => { - // map - let r = null; - try { - r = cslMetadatum.as_map(); - } catch (_) { - r = null; - } - if (r) return metadataCtors.from_map(r); - // list - try { - r = cslMetadatum.as_list(); - } catch (_) { - r = null; - } - if (r) return metadataCtors.from_list(r); - - // int - try { - r = cslMetadatum.as_int(); - } catch (_) { - r = null; - } - if (r) return metadataCtors.from_int(r); - - // bytes - try { - r = cslMetadatum.as_bytes(); - } catch (_) { - r = null; - } - if (r) return metadataCtors.from_bytes(r); - - // text - try { - r = cslMetadatum.as_text(); - } catch (_) { - r = null; + switch (cslMetadatum.kind()) { + case lib.TransactionMetadatumKind.MetadataMap: + return metadataCtors.from_map(cslMetadatum.as_map()); + case lib.TransactionMetadatumKind.MetadataList: + return metadataCtors.from_list(cslMetadatum.as_list()); + case lib.TransactionMetadatumKind.Int: + return metadataCtors.from_int(cslMetadatum.as_int()); + case lib.TransactionMetadatumKind.Bytes: + return metadataCtors.from_bytes(cslMetadatum.as_bytes()); + case lib.TransactionMetadatumKind.Text: + return metadataCtors.from_text(cslMetadatum.as_text()); + default: + throw "Could not convert to known types."; } - if (r) return metadataCtors.from_text(r); - - return metadataCtors.error("Could not convert to known types."); }; exports._unpackExUnits = exunits => { @@ -290,22 +263,16 @@ exports.poolParamsRelays = containerHelper => poolParams => exports.poolParamsPoolMetadata = callMaybe("pool_metadata"); exports.convertRelay_ = helper => relay => { - let res = relay.as_single_host_addr(); - if (res) { - return helper.asSingleHostAddr(res); - } - - res = relay.as_single_host_name(); - if (res) { - return helper.asSingleHostName(res); - } - - res = relay.as_multi_host_name(); - if (res) { - return helper.asMultiHostName(res); + switch (relay.kind()) { + case lib.RelayKind.SingleHostAddr: + return helper.asSingleHostAddr(relay.as_single_host_addr()); + case lib.RelayKind.SingleHostName: + return helper.asSingleHostName(relay.as_single_host_name()); + case lib.RelayKind.MultiHostName: + return helper.asMultiHostName(relay.as_multi_host_name()); + default: + throw "convertRelay_: impossible happened: invalid Relay"; } - - throw "convertRelay_: impossible happened: invalid Relay"; }; exports.convertIpv6_ = ipv6 => ipv6.ip(); diff --git a/src/Internal/Deserialization/Transaction.purs b/src/Internal/Deserialization/Transaction.purs index 578b3f96c9..94b2e1caa3 100644 --- a/src/Internal/Deserialization/Transaction.purs +++ b/src/Internal/Deserialization/Transaction.purs @@ -57,14 +57,12 @@ module Ctl.Internal.Deserialization.Transaction , convertTxBody , convertUpdate , cslNumberToUInt - , cslIntToUInt , cslRatioToRational , deserializeTransaction ) where import Prelude -import Control.Lazy (fix) import Ctl.Internal.Cardano.Types.Transaction ( AuxiliaryData(AuxiliaryData) , AuxiliaryDataHash(AuxiliaryDataHash) @@ -114,7 +112,6 @@ import Ctl.Internal.Deserialization.Error , FromCslRepError , addErrTrace , cslErr - , fromCslRepError ) import Ctl.Internal.Deserialization.FromBytes (fromBytes') import Ctl.Internal.Deserialization.Language (convertLanguage) @@ -183,7 +180,7 @@ import Ctl.Internal.Serialization.Types , Withdrawals ) as Csl import Ctl.Internal.Types.BigNum (BigNum) as Csl -import Ctl.Internal.Types.BigNum (toBigInt') as BigNum +import Ctl.Internal.Types.BigNum (toBigInt', toBigIntUnsafe) as BigNum import Ctl.Internal.Types.ByteArray (ByteArray) import Ctl.Internal.Types.CborBytes (CborBytes) import Ctl.Internal.Types.Int (Int) as Csl @@ -206,7 +203,7 @@ import Data.Maybe (Maybe, fromMaybe) import Data.Newtype (unwrap, wrap) import Data.Ratio (Ratio, reduce) import Data.Set (fromFoldable) as Set -import Data.Traversable (for, traverse) +import Data.Traversable (traverse) import Data.Tuple.Nested (type (/\)) import Data.UInt (UInt) import Data.UInt as UInt @@ -227,8 +224,9 @@ convertTransaction tx = addErrTrace "convertTransaction" do witnessSet <- cslErr "convertWitnessSet" $ convertWitnessSet (_txWitnessSet tx) body <- convertTxBody $ _txBody tx - auxiliaryData <- traverse convertAuxiliaryData - (_txAuxiliaryData maybeFfiHelper tx) + let + auxiliaryData = convertAuxiliaryData <$> + _txAuxiliaryData maybeFfiHelper tx pure $ T.Transaction { body , witnessSet @@ -239,10 +237,9 @@ convertTransaction tx = addErrTrace "convertTransaction" do -- | Converts transaction body from foreign CSL representation to CTL's one. convertTxBody :: forall (r :: Row Type). Csl.TransactionBody -> Err r T.TxBody convertTxBody txBody = do - inputs <- - _txBodyInputs containerHelper txBody - # traverse (convertInput >>> cslErr "TransactionInput") - <#> Set.fromFoldable + let + inputs = Set.fromFoldable $ convertInput <$> _txBodyInputs containerHelper txBody + outputs <- _txBodyOutputs containerHelper txBody # traverse (convertOutput >>> cslErr "TransactionOutput") @@ -273,13 +270,10 @@ convertTxBody txBody = do _txBodyReferenceInputs maybeFfiHelper containerHelper txBody # fromMaybe mempty - referenceInputs <- - traverse (convertInput >>> cslErr "TransactionInput") cslReferenceInputs - <#> Set.fromFoldable + referenceInputs = Set.fromFoldable $ convertInput <$> cslReferenceInputs - certs <- addErrTrace "Tx body certificates" - $ traverse (traverse convertCertificate) - $ _txBodyCerts containerHelper + certs = map convertCertificate <$> + _txBodyCerts containerHelper maybeFfiHelper txBody @@ -309,8 +303,7 @@ convertTxBody txBody = do , scriptDataHash: convertScriptDataHash <$> _txBodyScriptDataHash maybeFfiHelper txBody - , collateral: _txBodyCollateral containerHelper maybeFfiHelper txBody >>= - traverse convertInput + , collateral: _txBodyCollateral containerHelper maybeFfiHelper txBody >>= map convertInput >>> pure , requiredSigners: _txBodyRequiredSigners containerHelper maybeFfiHelper txBody # (map <<< map) T.RequiredSigner @@ -336,28 +329,28 @@ convertUpdate u = do } convertCertificate - :: forall (r :: Row Type). Csl.Certificate -> Err r T.Certificate + :: Csl.Certificate -> T.Certificate convertCertificate = _convertCert certConvHelper where - certConvHelper :: CertConvHelper (Err r T.Certificate) + certConvHelper :: CertConvHelper T.Certificate certConvHelper = - { stakeDeregistration: pure <<< T.StakeDeregistration - , stakeRegistration: pure <<< T.StakeRegistration - , stakeDelegation: \sc -> pure <<< T.StakeDelegation sc <<< wrap + { stakeDeregistration: T.StakeDeregistration + , stakeRegistration: T.StakeRegistration + , stakeDelegation: \sc -> T.StakeDelegation sc <<< wrap , poolRegistration: convertPoolRegistration , poolRetirement: convertPoolRetirement , genesisKeyDelegation: \genesisHash genesisDelegateHash vrfKeyhash -> do - pure $ T.GenesisKeyDelegation + T.GenesisKeyDelegation { genesisHash: T.GenesisHash $ toBytes $ asOneOf genesisHash , genesisDelegateHash: T.GenesisDelegateHash (toBytes $ asOneOf genesisDelegateHash) , vrfKeyhash: VRFKeyHash vrfKeyhash } , moveInstantaneousRewardsToOtherPotCert: \pot amount -> do - pure $ T.MoveInstantaneousRewardsCert $ + T.MoveInstantaneousRewardsCert $ T.ToOtherPot { pot, amount: amount } , moveInstantaneousRewardsToStakeCreds: \pot amounts -> do - pure $ T.MoveInstantaneousRewardsCert $ + T.MoveInstantaneousRewardsCert $ T.ToStakeCreds { pot, amounts: convertMIRToStakeCredentials amounts } } @@ -367,13 +360,11 @@ convertMIRToStakeCredentials = T.MIRToStakeCredentials <<< M.fromFoldable <<< unpackMIRToStakeCredentials_ containerHelper -convertPoolRegistration - :: forall (r :: Row Type) - . Csl.PoolParams - -> Err r T.Certificate +convertPoolRegistration :: Csl.PoolParams -> T.Certificate convertPoolRegistration params = do - relays <- traverse convertRelay $ poolParamsRelays containerHelper params - pure $ T.PoolRegistration + let + relays = convertRelay <$> poolParamsRelays containerHelper params + T.PoolRegistration { operator: PoolPubKeyHash $ poolParamsOperator params , vrfKeyhash: VRFKeyHash $ poolParamsVrfKeyhash params , pledge: poolParamsPledge params @@ -394,29 +385,29 @@ type ConvertRelayHelper a = , asMultiHostName :: Csl.MultiHostName -> a } -convertRelay - :: forall (r :: Row Type). Csl.Relay -> Err r T.Relay -convertRelay relay = addErrTrace "Relay" do +convertRelay :: Csl.Relay -> T.Relay +convertRelay relay = do convertRelay_ { asSingleHostAddr: convertSingleHostAddr_ maybeFfiHelper \mbPort mbIpv4 mbIpv6 -> do - ipv4 <- for mbIpv4 convertIpv4 - ipv6 <- for mbIpv6 convertIpv6 - pure $ T.SingleHostAddr { port: mbPort, ipv4, ipv6 } + let + ipv4 = mbIpv4 <#> convertIpv4 + ipv6 = mbIpv6 <#> convertIpv6 + T.SingleHostAddr { port: mbPort, ipv4, ipv6 } , asSingleHostName: convertSingleHostName_ maybeFfiHelper - \port mbHost -> pure $ T.SingleHostName { port, dnsName: mbHost } - , asMultiHostName: pure <<< T.MultiHostName <<< { dnsName: _ } <<< + \port mbHost -> T.SingleHostName { port, dnsName: mbHost } + , asMultiHostName: T.MultiHostName <<< { dnsName: _ } <<< convertMultiHostName_ } relay -convertIpv6 :: forall (r :: Row Type). Csl.Ipv6 -> Err r T.Ipv6 -convertIpv6 = pure <<< T.Ipv6 <<< convertIpv6_ +convertIpv6 :: Csl.Ipv6 -> T.Ipv6 +convertIpv6 = T.Ipv6 <<< convertIpv6_ foreign import convertIpv6_ :: Csl.Ipv6 -> ByteArray -convertIpv4 :: forall (r :: Row Type). Csl.Ipv4 -> Err r T.Ipv4 -convertIpv4 = pure <<< T.Ipv4 <<< convertIpv4_ +convertIpv4 :: Csl.Ipv4 -> T.Ipv4 +convertIpv4 = T.Ipv4 <<< convertIpv4_ foreign import convertIpv4_ :: Csl.Ipv4 -> ByteArray @@ -441,13 +432,11 @@ foreign import convertMultiHostName_ -> String convertPoolRetirement - :: forall (r :: Row Type) - . Ed25519KeyHash - -> Int - -> Err r T.Certificate -convertPoolRetirement poolKeyHash epochInt = do - epoch <- wrap <$> cslIntToUInt "PoolRetirement.epoch" epochInt - pure $ T.PoolRetirement { poolKeyHash: wrap poolKeyHash, epoch } + :: Ed25519KeyHash + -> UInt + -> T.Certificate +convertPoolRetirement poolKeyHash epoch = do + T.PoolRetirement { poolKeyHash: wrap poolKeyHash, epoch: wrap epoch } convertMint :: Csl.Mint -> T.Mint convertMint mint = T.Mint $ mkNonAdaAsset @@ -537,7 +526,7 @@ convertCostModels cslCostMdls = mdls = _unpackCostModels containerHelper cslCostMdls in (T.Costmdls <<< M.fromFoldable) <$> traverse - (bitraverse convertLanguage convertCostModel) + (bitraverse (pure <<< convertLanguage) convertCostModel) mdls convertCostModel @@ -553,76 +542,54 @@ convertCostModel = map T.CostModel <<< traverse stringToInt <<< Int.fromBigInt =<< BigInt.fromString s convertAuxiliaryData - :: forall (r :: Row Type). Csl.AuxiliaryData -> Err r T.AuxiliaryData -convertAuxiliaryData ad = addErrTrace "convertAuxiliaryData" do - metadata <- traverse convertGeneralTransactionMetadata - (_adGeneralMetadata maybeFfiHelper ad) - pure $ T.AuxiliaryData + :: Csl.AuxiliaryData -> T.AuxiliaryData +convertAuxiliaryData ad = do + let + metadata = convertGeneralTransactionMetadata <$> + _adGeneralMetadata maybeFfiHelper ad + T.AuxiliaryData { metadata - , nativeScripts: convertNativeScripts =<< _adNativeScripts maybeFfiHelper ad - , plutusScripts: convertPlutusScripts =<< _adPlutusScripts maybeFfiHelper ad + , nativeScripts: pure <<< convertNativeScripts =<< _adNativeScripts + maybeFfiHelper + ad + , plutusScripts: pure <<< convertPlutusScripts =<< _adPlutusScripts + maybeFfiHelper + ad } convertGeneralTransactionMetadata - :: forall (r :: Row Type) - . Csl.GeneralTransactionMetadata - -> Err r GeneralTransactionMetadata -convertGeneralTransactionMetadata = - -- unpack to array of tuples - _unpackMetadatums containerHelper - >>> - -- convert tuple type - traverse - ( bitraverse - ( map TransactionMetadatumLabel <<< BigNum.toBigInt' - "MetadatumLabel: " - ) - (convertMetadatum "GeneralTransactionMetadata: ") - ) - -- fold to map and and wrap - >>> map (M.fromFoldable >>> wrap) - -convertMetadatum - :: forall (r :: Row Type) - . String - -> Csl.TransactionMetadatum - -> Err r TransactionMetadatum -convertMetadatum err = fix \_ -> addErrTrace err <<< _convertMetadatum - ( { error: fromCslRepError - , from_bytes: pure <<< Bytes - , from_int: pure <<< Int - , from_text: pure <<< Text - , from_map: convertMetadataMap convertMetadatum - , from_list: convertMetadataList convertMetadatum - } - ) + :: Csl.GeneralTransactionMetadata + -> GeneralTransactionMetadata +convertGeneralTransactionMetadata gtm = wrap + $ M.fromFoldable + $ bimap (TransactionMetadatumLabel <<< BigNum.toBigIntUnsafe) convertMetadatum + <$> _unpackMetadatums containerHelper gtm + +convertMetadatum :: Csl.TransactionMetadatum -> TransactionMetadatum +convertMetadatum tm = _convertMetadatum + { from_bytes: Bytes + , from_int: Int + , from_text: Text + , from_map: convertMetadataMap + , from_list: convertMetadataList + } + tm convertMetadataList - :: forall (r :: Row Type) - . (String -> Csl.TransactionMetadatum -> Err r TransactionMetadatum) - -> Csl.MetadataList - -> Err r TransactionMetadatum -convertMetadataList convert = map MetadataList - <<< traverse (convert "convertMetadataList") - <<< _unpackMetadataList containerHelper + :: Csl.MetadataList + -> TransactionMetadatum +convertMetadataList ml = MetadataList + $ convertMetadatum <$> _unpackMetadataList containerHelper ml convertMetadataMap - :: forall (r :: Row Type) - . (String -> Csl.TransactionMetadatum -> Err r TransactionMetadatum) - -> Csl.MetadataMap - -> Err r TransactionMetadatum -convertMetadataMap convert = - -- unpack to array of tuples - _unpackMetadataMap containerHelper - >>> - -- convert tuple type - traverse - ( bitraverse - (convert "convertMetadataMap key") - (convert "convertMetadataMap value") - ) - -- fold to map and and wrap - >>> map (M.fromFoldable >>> MetadataMap) + :: Csl.MetadataMap + -> TransactionMetadatum +convertMetadataMap mm = MetadataMap + $ M.fromFoldable + $ bimap convertMetadatum convertMetadatum + <$> _unpackMetadataMap containerHelper mm + +-- unpack to array of tuples ---- conversion helpers @@ -631,11 +598,6 @@ cslNumberToUInt cslNumberToUInt nm nb = cslErr (nm <> ": Number (" <> show nb <> ") -> UInt") $ UInt.fromNumber' nb -cslIntToUInt - :: forall (r :: Row Type). String -> Int -> E (FromCslRepError + r) UInt -cslIntToUInt nm nb = cslErr (nm <> ": Int (" <> show nb <> ") -> UInt") $ - UInt.fromInt' nb - cslRatioToRational :: forall (r :: Row Type) . String @@ -721,13 +683,12 @@ foreign import _unpackMetadataMap foreign import _unpackMetadataList :: ContainerHelper -> Csl.MetadataList -> Array Csl.TransactionMetadatum -type MetadatumHelper (r :: Row Type) = - { from_map :: Csl.MetadataMap -> Err r TransactionMetadatum - , from_list :: Csl.MetadataList -> Err r TransactionMetadatum - , from_int :: Csl.Int -> Err r TransactionMetadatum - , from_text :: String -> Err r TransactionMetadatum - , from_bytes :: ByteArray -> Err r TransactionMetadatum - , error :: String -> Err r TransactionMetadatum +type MetadatumHelper = + { from_map :: Csl.MetadataMap -> TransactionMetadatum + , from_list :: Csl.MetadataList -> TransactionMetadatum + , from_int :: Csl.Int -> TransactionMetadatum + , from_text :: String -> TransactionMetadatum + , from_bytes :: ByteArray -> TransactionMetadatum } foreign import _unpackProtocolVersion @@ -754,10 +715,9 @@ foreign import _unpackExUnitsPrices -> { memPrice :: Csl.UnitInterval, stepPrice :: Csl.UnitInterval } foreign import _convertMetadatum - :: forall (r :: Row Type) - . MetadatumHelper r + :: MetadatumHelper -> Csl.TransactionMetadatum - -> E (FromCslRepError + r) TransactionMetadatum + -> TransactionMetadatum foreign import _unpackMetadatums :: ContainerHelper @@ -889,7 +849,7 @@ type CertConvHelper (r :: Type) = , stakeDelegation :: Csl.StakeCredential -> Ed25519KeyHash -> r , poolRegistration :: Csl.PoolParams -> r - , poolRetirement :: Ed25519KeyHash -> Int -> r + , poolRetirement :: Ed25519KeyHash -> UInt -> r , genesisKeyDelegation :: Csl.GenesisHash -> Csl.GenesisDelegateHash @@ -902,10 +862,9 @@ type CertConvHelper (r :: Type) = } foreign import _convertCert - :: forall (r :: Row Type) - . CertConvHelper (Err r T.Certificate) + :: CertConvHelper T.Certificate -> Csl.Certificate - -> Err r T.Certificate + -> T.Certificate foreign import poolParamsOperator :: Csl.PoolParams -> Ed25519KeyHash foreign import poolParamsVrfKeyhash :: Csl.PoolParams -> Csl.VRFKeyHash diff --git a/src/Internal/Deserialization/UnspentOutput.purs b/src/Internal/Deserialization/UnspentOutput.purs index 5cc4f8fd84..a18a89346d 100644 --- a/src/Internal/Deserialization/UnspentOutput.purs +++ b/src/Internal/Deserialization/UnspentOutput.purs @@ -68,20 +68,22 @@ import Data.Newtype (unwrap, wrap) import Data.Traversable (for, traverse) import Data.Tuple (Tuple(Tuple)) import Data.Tuple.Nested (type (/\)) -import Data.UInt as UInt +import Data.UInt (UInt) import Untagged.Union (asOneOf) convertUnspentOutput :: TransactionUnspentOutput -> Maybe T.TransactionUnspentOutput convertUnspentOutput tuo = do - input <- convertInput $ getInput tuo + let + input = convertInput $ getInput tuo output <- convertOutput $ getOutput tuo pure $ T.TransactionUnspentOutput { input, output } -convertInput :: TransactionInput -> Maybe T.TransactionInput +convertInput :: TransactionInput -> T.TransactionInput convertInput input = do - index <- UInt.fromInt' $ getTransactionIndex input - pure $ T.TransactionInput + let + index = getTransactionIndex input + T.TransactionInput { transactionId: T.TransactionHash $ toBytes (asOneOf $ getTransactionHash input) , index @@ -102,14 +104,15 @@ convertOutput output = do datumValue Nothing, Just datumHash -> pure $ OutputDatumHash datumHash Nothing, Nothing -> pure NoOutputDatum - scriptRef <- getScriptRef maybeFfiHelper output # traverse convertScriptRef + let + scriptRef = getScriptRef maybeFfiHelper output <#> convertScriptRef pure $ T.TransactionOutput { address, amount, datum, scriptRef } -convertScriptRef :: ScriptRef -> Maybe T.ScriptRef +convertScriptRef :: ScriptRef -> T.ScriptRef convertScriptRef = withScriptRef - (convertNativeScript >>> map T.NativeScriptRef) - (convertPlutusScript >>> map T.PlutusScriptRef) + (convertNativeScript >>> T.NativeScriptRef) + (convertPlutusScript >>> T.PlutusScriptRef) convertValue :: Value -> Maybe T.Value convertValue value = do @@ -149,7 +152,7 @@ convertValue value = do foreign import getInput :: TransactionUnspentOutput -> TransactionInput foreign import getOutput :: TransactionUnspentOutput -> TransactionOutput foreign import getTransactionHash :: TransactionInput -> TransactionHash -foreign import getTransactionIndex :: TransactionInput -> Int +foreign import getTransactionIndex :: TransactionInput -> UInt foreign import getAddress :: TransactionOutput -> Address foreign import getPlutusData :: MaybeFfiHelper -> TransactionOutput -> Maybe PlutusData diff --git a/src/Internal/Deserialization/WitnessSet.purs b/src/Internal/Deserialization/WitnessSet.purs index 3597fa467b..9b65f28dd5 100644 --- a/src/Internal/Deserialization/WitnessSet.purs +++ b/src/Internal/Deserialization/WitnessSet.purs @@ -53,7 +53,6 @@ import Ctl.Internal.Types.ByteArray (ByteArray) import Ctl.Internal.Types.PlutusData (PlutusData) as T import Ctl.Internal.Types.RedeemerTag as Tag import Ctl.Internal.Types.Scripts (PlutusScript(PlutusScript)) as S -import Data.Either (hush) import Data.Maybe (Maybe(Just, Nothing)) import Data.Traversable (for, traverse) import Data.Tuple (curry) @@ -64,11 +63,12 @@ deserializeWitnessSet = _deserializeWitnessSet maybeFfiHelper convertWitnessSet :: TransactionWitnessSet -> Maybe T.TransactionWitnessSet convertWitnessSet ws = do - nativeScripts <- for (getNativeScripts maybeFfiHelper ws) convertNativeScripts + let + nativeScripts = getNativeScripts maybeFfiHelper ws <#> convertNativeScripts + plutusScripts = getPlutusScripts maybeFfiHelper ws <#> convertPlutusScripts redeemers <- for (getRedeemers maybeFfiHelper ws) convertRedeemers plutusData <- for (getWitnessSetPlutusData maybeFfiHelper ws) convertPlutusList - plutusScripts <- for (getPlutusScripts maybeFfiHelper ws) convertPlutusScripts pure $ T.TransactionWitnessSet { vkeys: getVkeywitnesses maybeFfiHelper ws <#> convertVkeyWitnesses , nativeScripts @@ -93,9 +93,9 @@ convertVkeyWitness witness = convertVkey :: Vkey -> T.Vkey convertVkey = T.Vkey <<< T.mkFromCslPubKey <<< vkeyPublicKey -convertNativeScripts :: NativeScripts -> Maybe (Array T.NativeScript) +convertNativeScripts :: NativeScripts -> Array T.NativeScript convertNativeScripts nativeScripts = - for (extractNativeScripts nativeScripts) convertNativeScript + extractNativeScripts nativeScripts <#> convertNativeScript convertBootstraps :: BootstrapWitnesses -> Array T.BootstrapWitness convertBootstraps = extractBootstraps >>> map \bootstrap -> @@ -105,15 +105,15 @@ convertBootstraps = extractBootstraps >>> map \bootstrap -> , attributes: getBootstrapAttributes bootstrap } -convertPlutusScripts :: PlutusScripts -> Maybe (Array S.PlutusScript) +convertPlutusScripts :: PlutusScripts -> Array S.PlutusScript convertPlutusScripts plutusScripts = - for (extractPlutusScripts plutusScripts) convertPlutusScript + extractPlutusScripts plutusScripts <#> convertPlutusScript -convertPlutusScript :: PlutusScript -> Maybe S.PlutusScript -convertPlutusScript plutusScript = - hush do - language <- convertLanguage $ plutusScriptVersion plutusScript - pure $ curry S.PlutusScript (plutusScriptBytes plutusScript) language +convertPlutusScript :: PlutusScript -> S.PlutusScript +convertPlutusScript plutusScript = do + let + language = convertLanguage $ plutusScriptVersion plutusScript + curry S.PlutusScript (plutusScriptBytes plutusScript) language convertPlutusList :: PlutusList -> Maybe (Array T.PlutusData) convertPlutusList = extractPlutusData >>> traverse convertPlutusData diff --git a/src/Internal/QueryM/Kupo.purs b/src/Internal/QueryM/Kupo.purs index 915dfd2406..01ccade6c6 100644 --- a/src/Internal/QueryM/Kupo.purs +++ b/src/Internal/QueryM/Kupo.purs @@ -352,8 +352,7 @@ instance DecodeAeson KupoScriptRef where nativeScript <- flip note (fromBytes scriptBytes) $ TypeMismatch "decodeNativeScript: from_bytes() call failed" - flip note (convertNativeScript nativeScript) $ - TypeMismatch "decodeNativeScript: failed to convert native script" + pure $ convertNativeScript nativeScript -------------------------------------------------------------------------------- -- Helpers diff --git a/test/Deserialization.purs b/test/Deserialization.purs index 6fa8133a60..063390ce61 100644 --- a/test/Deserialization.purs +++ b/test/Deserialization.purs @@ -264,7 +264,8 @@ testNativeScript input = do let bytes = Serialization.toBytes (asOneOf serialized) res <- errMaybe "Failed deserialization" $ fromBytes bytes - res' <- errMaybe "Failed deserialization" $ NSD.convertNativeScript res + let + res' = NSD.convertNativeScript res res' `shouldEqual` input txRoundtrip :: T.Transaction -> Aff Unit From c0f3ab4043d94d6cafc74c5335a9200158f25c7a Mon Sep 17 00:00:00 2001 From: nalane Date: Fri, 16 Dec 2022 20:40:08 -0700 Subject: [PATCH 127/373] toMetadata for String splits long strings fixed formatting Updated changelog implemented more direct fix for cip25 string issue Removed unneeded imports --- CHANGELOG.md | 3 ++- src/Internal/Metadata/Cip25/Cip25String.purs | 9 +++++++-- src/Internal/Metadata/Cip25/V2.purs | 16 +++++++++------- 3 files changed, 18 insertions(+), 10 deletions(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index 6909fe75a8..332fed42d7 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -7,7 +7,7 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) -- [[v4.0.0]](#v400) +- [[v4.0.0] - 2022-12-15](#v400---2022-12-15) - [Added](#added) - [Changed](#changed) - [Removed](#removed) @@ -63,6 +63,7 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) - Added missing `stakePoolTargetNum` ("`nOpt`") protocol parameter (see [CIP-9](https://cips.cardano.org/cips/cip9/)) ([#571](https://github.com/Plutonomicon/cardano-transaction-lib/issues/571)) - CIP-30 `signData` response handling ([#1289](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1289)) +- CIP-25 strings are now being split into chunks whose sizes are less than or equal to 64 to adhere to the CIP-25 standard ([#1343](https://github.com/Plutonomicon/cardano-transaction-lib/issues/1343)) ### Runtime Dependencies diff --git a/src/Internal/Metadata/Cip25/Cip25String.purs b/src/Internal/Metadata/Cip25/Cip25String.purs index f62351587d..0fa48c9bc9 100644 --- a/src/Internal/Metadata/Cip25/Cip25String.purs +++ b/src/Internal/Metadata/Cip25/Cip25String.purs @@ -32,7 +32,7 @@ import Data.Array as Array import Data.Either (hush, note) import Data.Foldable (fold, foldMap) import Data.Maybe (Maybe(Nothing, Just), isJust) -import Data.Newtype (unwrap, wrap) +import Data.Newtype (class Newtype, unwrap, wrap) import Data.String.CodePoints as String import Data.TextDecoder (decodeUtf8) import Data.TextEncoder (encodeUtf8) @@ -51,6 +51,8 @@ derive newtype instance ToData Cip25String derive newtype instance FromData Cip25String derive newtype instance EncodeAeson Cip25String +derive instance newtypeCip25String :: Newtype Cip25String _ + instance Show Cip25String where show (Cip25String str) = "(unsafePartial (fromJust (mkCip25String " <> show str @@ -142,5 +144,8 @@ toMetadataString str = case toCip25Strings str of fromMetadataString :: TransactionMetadatum -> Maybe String fromMetadataString datum = do fromCip25Strings <$> (Array.singleton <$> fromMetadata datum) <|> do - bytes :: Array ByteArray <- fromMetadata datum + strings :: Array Cip25String <- fromMetadata datum + let + bytes :: Array ByteArray + bytes = map (wrap <<< encodeUtf8 <<< unwrap) strings hush $ decodeUtf8 $ unwrap $ fold bytes diff --git a/src/Internal/Metadata/Cip25/V2.purs b/src/Internal/Metadata/Cip25/V2.purs index ba77262cee..ffdec2cc20 100644 --- a/src/Internal/Metadata/Cip25/V2.purs +++ b/src/Internal/Metadata/Cip25/V2.purs @@ -33,6 +33,8 @@ import Ctl.Internal.Metadata.Cip25.Cip25String ( Cip25String , fromDataString , fromMetadataString + , toDataString + , toMetadataString ) import Ctl.Internal.Metadata.Cip25.Common ( Cip25MetadataFile(Cip25MetadataFile) @@ -149,8 +151,8 @@ instance DecodeAeson Cip25V2 where -- the standard only specifies the encoding for Cip25Metadata). metadataEntryToMetadata :: Cip25MetadataEntry -> TransactionMetadatum metadataEntryToMetadata (Cip25MetadataEntry entry) = toMetadata $ - [ "name" /\ anyToMetadata entry.name - , "image" /\ anyToMetadata entry.image + [ "name" /\ toMetadata entry.name + , "image" /\ toMetadataString entry.image ] <> mbMediaType <> mbDescription @@ -158,11 +160,11 @@ metadataEntryToMetadata (Cip25MetadataEntry entry) = toMetadata $ where mbFiles = case entry.files of [] -> [] - files -> [ "files" /\ anyToMetadata files ] + files -> [ "files" /\ toMetadata files ] mbMediaType = fold $ entry.mediaType <#> \mediaType -> - [ "mediaType" /\ anyToMetadata mediaType ] + [ "mediaType" /\ toMetadata mediaType ] mbDescription = fold $ entry.description <#> \description -> - [ "description" /\ anyToMetadata description ] + [ "description" /\ toMetadataString description ] metadataEntryFromMetadata :: MintingPolicyHash @@ -181,7 +183,7 @@ metadataEntryFromMetadata policyId assetName contents = do metadataEntryToData :: Cip25MetadataEntry -> PlutusData metadataEntryToData (Cip25MetadataEntry entry) = toData $ AssocMap.Map $ [ "name" /\ toData entry.name - , "image" /\ toData entry.image + , "image" /\ toDataString entry.image ] <> mbMediaType <> mbDescription @@ -193,7 +195,7 @@ metadataEntryToData (Cip25MetadataEntry entry) = toData $ AssocMap.Map $ mbMediaType = fold $ entry.mediaType <#> \mediaType -> [ "mediaType" /\ toData mediaType ] mbDescription = fold $ entry.description <#> \description -> - [ "description" /\ toData description ] + [ "description" /\ toDataString description ] metadataEntryFromData :: MintingPolicyHash From 03ab5595e8fb3e272e09b4acfb28ce2d18da3c6d Mon Sep 17 00:00:00 2001 From: Gregory Gerasev Date: Sun, 18 Dec 2022 21:39:17 +0400 Subject: [PATCH 128/373] Update CHANGELOG.md Co-authored-by: Joseph Young --- CHANGELOG.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index d2880944f4..dc25bde9d7 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -49,7 +49,7 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) - Running plutip servers attaches on SIGINT handlers and therefore node will not exit by default. ([#1231](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1231)). - `TestPlanM`, `interpret` and `interpretWithConfig` are now public in `Contract.Test.Mote` and our custom `consoleReporter` in `Contract.Test.Mote.ConsoleReporter`. ([#1261](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1261)). -- Internal datum conversions are now total, resulting in some datum-related Contract functions dropping the use of `Maybe`, for example `datumHash`, `convertPlutusData` (and related functions). The same with `BigNum.toBigInt`. ([#1284](https://github.com/Plutonomicon/cardano-transaction-lib/issues/1284)). +- Internal datum conversions are now total, resulting in some datum-related Contract functions dropping the use of `Maybe`, for example `datumHash`, `convertPlutusData` and their related functions. ([#1284](https://github.com/Plutonomicon/cardano-transaction-lib/issues/1284)). - CIP-25 `policy_id` and `asset_name` metadata keys no longer include a `0x` prefix for compatibility with Blockfrost ([#1309](https://github.com/Plutonomicon/cardano-transaction-lib/issues/1309 "CTL's CIP25 metadata encoding is considered invalid by Blockfrost #1309")). - `purescript-aeson` package has been updated: - the performance has generally been improved From 61e78db87698b3ba24b1c48bee10209af5253ada Mon Sep 17 00:00:00 2001 From: Gregory Gerasev Date: Sun, 18 Dec 2022 23:01:58 +0400 Subject: [PATCH 129/373] Fix broken with merge --- examples/ECDSA.purs | 3 ++- examples/PaysWithDatum.purs | 8 ++++---- examples/Schnorr.purs | 3 ++- src/Internal/ApplyArgs.purs | 3 +-- src/Internal/Deserialization/Transaction.purs | 6 ++++-- test/ApplyArgs.purs | 7 ++++--- 6 files changed, 17 insertions(+), 13 deletions(-) diff --git a/examples/ECDSA.purs b/examples/ECDSA.purs index f0c10d6795..5d0bb46f2a 100644 --- a/examples/ECDSA.purs +++ b/examples/ECDSA.purs @@ -16,6 +16,7 @@ import Contract.Crypto.Secp256k1.Utils ) import Contract.Log (logInfo') import Contract.Monad (Contract, liftContractM) +import Contract.Numeric.BigNum as BigNum import Contract.PlutusData ( class ToData , PlutusData(Constr) @@ -48,7 +49,7 @@ derive instance Generic ECDSARedemeer _ derive instance Newtype ECDSARedemeer _ instance ToData ECDSARedemeer where - toData (ECDSARedemeer { msg, sig, pk }) = Constr zero + toData (ECDSARedemeer { msg, sig, pk }) = Constr BigNum.zero [ toData msg, toData sig, toData pk ] contract :: Contract () Unit diff --git a/examples/PaysWithDatum.purs b/examples/PaysWithDatum.purs index 4011eba7a4..37ef8f7f9b 100644 --- a/examples/PaysWithDatum.purs +++ b/examples/PaysWithDatum.purs @@ -77,10 +77,10 @@ contract = do skh <- join <<< head <$> ownStakePubKeysHashes address <- liftedM "Could not get own address" (head <$> getWalletAddresses) - let datum = Datum $ Integer $ BigInt.fromInt 42 - datumHash <- liftContractM "Could not compute datum hash" (datumHash datum) - let + datum = Datum $ Integer $ BigInt.fromInt 42 + datumHash' = datumHash datum + value :: Value value = Value.lovelaceValueOf (BigInt.fromInt 2_000_000) @@ -96,7 +96,7 @@ contract = do txHash <- submitTxFromConstraints lookups constraints awaitTxConfirmed txHash logInfo' "Tx submitted successfully!" - pure { address, txHash, datum, datumHash } + pure { address, txHash, datum, datumHash: datumHash' } assertions :: Array (ContractBasicAssertion () ContractResult Unit) assertions = diff --git a/examples/Schnorr.purs b/examples/Schnorr.purs index c836435ada..72e50826ab 100644 --- a/examples/Schnorr.purs +++ b/examples/Schnorr.purs @@ -12,6 +12,7 @@ import Contract.Crypto.Secp256k1.Schnorr import Contract.Crypto.Secp256k1.Utils (randomSecp256k1PrivateKey) import Contract.Log (logInfo') import Contract.Monad (Contract, liftContractM) +import Contract.Numeric.BigNum as BigNum import Contract.PlutusData ( class ToData , PlutusData(Constr) @@ -44,7 +45,7 @@ derive instance Generic SchnorrRedeemer _ derive instance Newtype SchnorrRedeemer _ instance ToData SchnorrRedeemer where - toData (SchnorrRedeemer { msg, sig, pk }) = Constr zero + toData (SchnorrRedeemer { msg, sig, pk }) = Constr BigNum.zero [ toData msg, toData sig, toData pk ] contract :: Contract () Unit diff --git a/src/Internal/ApplyArgs.purs b/src/Internal/ApplyArgs.purs index 77b5d620a8..268345b0a3 100644 --- a/src/Internal/ApplyArgs.purs +++ b/src/Internal/ApplyArgs.purs @@ -41,8 +41,7 @@ instance Show ApplyArgsError where applyArgs :: PlutusScript -> Array PlutusData -> Either ApplyArgsError PlutusScript applyArgs script paramsList = left ApplyArgsError do - params <- note "Error converting to serialized PlutusData" $ - S.convertPlutusData (List paramsList) + let params = S.convertPlutusData (List paramsList) appliedScript <- apply_params_to_script_either params (S.convertPlutusScript script) note "Error converting back applied script" $ D.convertPlutusScript $ diff --git a/src/Internal/Deserialization/Transaction.purs b/src/Internal/Deserialization/Transaction.purs index 4f8118a509..3ede1b1f49 100644 --- a/src/Internal/Deserialization/Transaction.purs +++ b/src/Internal/Deserialization/Transaction.purs @@ -491,8 +491,10 @@ convertProtocolParamUpdate cslPpu = do ppu.costModels let maxTxExUnits = convertExUnits (lbl "maxTxExUnits") <$> ppu.maxTxExUnits - maxBlockExUnits = convertExUnits (lbl "maxBlockExUnits") <$> ppu.maxBlockExUnits - maxValueSize <- traverse (cslNumberToUInt (lbl "maxValueSize")) ppu.maxValueSize + maxBlockExUnits = convertExUnits (lbl "maxBlockExUnits") <$> + ppu.maxBlockExUnits + maxValueSize <- traverse (cslNumberToUInt (lbl "maxValueSize")) + ppu.maxValueSize pure { minfeeA , minfeeB diff --git a/test/ApplyArgs.purs b/test/ApplyArgs.purs index 7ea7bcd091..880cd38465 100644 --- a/test/ApplyArgs.purs +++ b/test/ApplyArgs.purs @@ -3,6 +3,7 @@ module Test.Ctl.ApplyArgs (main, suite, contract) where import Contract.Prelude import Contract.Monad (Contract, launchAff_) +import Contract.Numeric.BigNum as BigNum import Contract.PlutusData (PlutusData(List, Map, Bytes, Constr), toData) import Contract.Prim.ByteArray (hexToByteArrayUnsafe) import Contract.Scripts (PlutusScript) @@ -84,12 +85,12 @@ params = , List [ un, bytes ] , longBytes , Map [ (i 5 /\ i 7), (bytes /\ i 8) ] - , Constr (fromInt 102) [ i 7, List [ un, bytes, longBytes ] ] - , Constr (fromInt 5) + , Constr (BigNum.fromInt 102) [ i 7, List [ un, bytes, longBytes ] ] + , Constr (BigNum.fromInt 5) [ List [] , List [ i 1 ] , Map [] - , Map [ (i 1 /\ un), (i 2 /\ Constr (fromInt 2) [ i 2 ]) ] + , Map [ (i 1 /\ un), (i 2 /\ Constr (BigNum.fromInt 2) [ i 2 ]) ] ] ] /\ "big-arg" ) From e18c1fc43f9173c8a04eeaeb1a9e72e58b68706a Mon Sep 17 00:00:00 2001 From: Gregory Gerasev Date: Sun, 18 Dec 2022 23:15:03 +0400 Subject: [PATCH 130/373] Fix warnings --- src/Internal/BalanceTx/UtxoMinAda.purs | 1 - src/Internal/Deserialization/PlutusData.purs | 2 -- src/Internal/Deserialization/Transaction.purs | 14 ++++++-------- src/Internal/FromData.purs | 2 -- src/Internal/QueryM.purs | 2 +- src/Internal/Serialization/WitnessSet.purs | 1 - src/Internal/ToData.purs | 2 +- src/Internal/Types/TypedTxOut.purs | 4 ++-- test/OgmiosDatumCache.purs | 2 +- 9 files changed, 11 insertions(+), 19 deletions(-) diff --git a/src/Internal/BalanceTx/UtxoMinAda.purs b/src/Internal/BalanceTx/UtxoMinAda.purs index e6e9bc785d..45f5cc4b8b 100644 --- a/src/Internal/BalanceTx/UtxoMinAda.purs +++ b/src/Internal/BalanceTx/UtxoMinAda.purs @@ -21,7 +21,6 @@ import Ctl.Internal.Types.BigNum ( fromBigInt , maxValue , toBigInt - , toBigInt ) as BigNum import Data.BigInt (BigInt) import Data.Maybe (Maybe, fromJust) diff --git a/src/Internal/Deserialization/PlutusData.purs b/src/Internal/Deserialization/PlutusData.purs index 95a4e4e07e..e5862c98a7 100644 --- a/src/Internal/Deserialization/PlutusData.purs +++ b/src/Internal/Deserialization/PlutusData.purs @@ -23,7 +23,6 @@ import Ctl.Internal.Serialization.Types , PlutusMap ) import Ctl.Internal.Types.BigNum (BigNum) -import Ctl.Internal.Types.BigNum (toBigInt) as BigNum import Ctl.Internal.Types.ByteArray (ByteArray) import Ctl.Internal.Types.CborBytes (CborBytes) import Ctl.Internal.Types.PlutusData @@ -31,7 +30,6 @@ import Ctl.Internal.Types.PlutusData ) as T import Data.Maybe (Maybe, fromJust) import Data.Newtype (unwrap) -import Data.Traversable (traverse) import Data.Tuple (Tuple(Tuple)) import Data.Tuple.Nested (type (/\), (/\)) import Partial.Unsafe (unsafePartial) diff --git a/src/Internal/Deserialization/Transaction.purs b/src/Internal/Deserialization/Transaction.purs index 3ede1b1f49..246ab711b9 100644 --- a/src/Internal/Deserialization/Transaction.purs +++ b/src/Internal/Deserialization/Transaction.purs @@ -490,8 +490,8 @@ convertProtocolParamUpdate cslPpu = do costModels <- addErrTrace (lbl "costModels") $ traverse convertCostModels ppu.costModels let - maxTxExUnits = convertExUnits (lbl "maxTxExUnits") <$> ppu.maxTxExUnits - maxBlockExUnits = convertExUnits (lbl "maxBlockExUnits") <$> + maxTxExUnits = convertExUnits <$> ppu.maxTxExUnits + maxBlockExUnits = convertExUnits <$> ppu.maxBlockExUnits maxValueSize <- traverse (cslNumberToUInt (lbl "maxValueSize")) ppu.maxValueSize @@ -631,18 +631,16 @@ cslIntToUInt nm nb = cslErr (nm <> ": Int (" <> show nb <> ") -> UInt") $ cslRatioToRational :: forall (r :: Row Type) - . String - -> { denominator :: Csl.BigNum, numerator :: Csl.BigNum } + . { denominator :: Csl.BigNum, numerator :: Csl.BigNum } -> Ratio BigInt -cslRatioToRational err { numerator, denominator } = +cslRatioToRational { numerator, denominator } = reduce (BigNum.toBigInt numerator) (BigNum.toBigInt denominator) convertExUnits :: forall (r :: Row Type) - . String - -> Csl.ExUnits + . Csl.ExUnits -> T.ExUnits -convertExUnits nm cslExunits = +convertExUnits cslExunits = let { mem, steps } = _unpackExUnits cslExunits in diff --git a/src/Internal/FromData.purs b/src/Internal/FromData.purs index d853abd699..6098b6356e 100644 --- a/src/Internal/FromData.purs +++ b/src/Internal/FromData.purs @@ -33,7 +33,6 @@ import Ctl.Internal.TypeLevel.RowList.Unordered.Indexed , class GetWithLabel ) import Ctl.Internal.Types.BigNum (BigNum) -import Ctl.Internal.Types.BigNum (fromBigInt) as BigNum import Ctl.Internal.Types.BigNum as BigNum import Ctl.Internal.Types.ByteArray (ByteArray) import Ctl.Internal.Types.CborBytes (CborBytes) @@ -43,7 +42,6 @@ import Data.Array (uncons) import Data.Array as Array import Data.ArrayBuffer.Types (Uint8Array) import Data.BigInt (BigInt) -import Data.BigInt as BigInt import Data.Either (Either(Left, Right), hush, note) import Data.Generic.Rep as G import Data.List (List) diff --git a/src/Internal/QueryM.purs b/src/Internal/QueryM.purs index eed84feec5..f7fe161c04 100644 --- a/src/Internal/QueryM.purs +++ b/src/Internal/QueryM.purs @@ -191,7 +191,7 @@ import Ctl.Internal.Serialization.Address , stakeCredentialToKeyHash ) import Ctl.Internal.Types.ByteArray (byteArrayToHex) -import Ctl.Internal.Types.CborBytes (CborBytes, cborBytesToHex) +import Ctl.Internal.Types.CborBytes (CborBytes) import Ctl.Internal.Types.Chain as Chain import Ctl.Internal.Types.Datum (DataHash, Datum) import Ctl.Internal.Types.PubKeyHash diff --git a/src/Internal/Serialization/WitnessSet.purs b/src/Internal/Serialization/WitnessSet.purs index 32dbeaadae..5c09c17da7 100644 --- a/src/Internal/Serialization/WitnessSet.purs +++ b/src/Internal/Serialization/WitnessSet.purs @@ -70,7 +70,6 @@ import Ctl.Internal.Types.Aliases (Bech32String) import Ctl.Internal.Types.BigNum (BigNum) import Ctl.Internal.Types.BigNum (fromBigInt) as BigNum import Ctl.Internal.Types.ByteArray (ByteArray) -import Ctl.Internal.Types.PlutusData (PlutusData) as PD import Ctl.Internal.Types.RedeemerTag as Tag import Data.Maybe (maybe) import Data.Traversable (for_, traverse, traverse_) diff --git a/src/Internal/ToData.purs b/src/Internal/ToData.purs index e98fd72501..722f1d6fe0 100644 --- a/src/Internal/ToData.purs +++ b/src/Internal/ToData.purs @@ -35,7 +35,7 @@ import Ctl.Internal.Types.RawBytes (RawBytes) import Data.Array (cons, sortWith) import Data.Array as Array import Data.ArrayBuffer.Types (Uint8Array) -import Data.BigInt (BigInt, fromInt) +import Data.BigInt (BigInt) import Data.BigInt as BigInt import Data.Either (Either(Left, Right)) import Data.Foldable (class Foldable) diff --git a/src/Internal/Types/TypedTxOut.purs b/src/Internal/Types/TypedTxOut.purs index 617a21e10b..cf731ec614 100644 --- a/src/Internal/Types/TypedTxOut.purs +++ b/src/Internal/Types/TypedTxOut.purs @@ -33,7 +33,7 @@ module Ctl.Internal.Types.TypedTxOut import Prelude import Control.Monad.Error.Class (throwError) -import Control.Monad.Except.Trans (ExceptT(ExceptT), except, runExceptT) +import Control.Monad.Except.Trans (ExceptT(ExceptT), runExceptT) import Ctl.Internal.Cardano.Types.Transaction ( TransactionOutput(TransactionOutput) ) @@ -56,7 +56,7 @@ import Ctl.Internal.Types.Transaction (TransactionInput) import Ctl.Internal.Types.TypedValidator (class DatumType, TypedValidator) import Data.Either (Either, note) import Data.Generic.Rep (class Generic) -import Data.Maybe (Maybe(Just, Nothing)) +import Data.Maybe (Maybe(Nothing)) import Data.Newtype (unwrap, wrap) import Data.Show.Generic (genericShow) diff --git a/test/OgmiosDatumCache.purs b/test/OgmiosDatumCache.purs index 8e4ef11601..65c778e9ad 100644 --- a/test/OgmiosDatumCache.purs +++ b/test/OgmiosDatumCache.purs @@ -21,7 +21,7 @@ import Effect.Aff (Aff) import Effect.Class (class MonadEffect) import Effect.Exception (Error) import Mote (group, skip, test) -import Test.Ctl.Utils (errEither, errMaybe, readAeson) +import Test.Ctl.Utils (errEither, readAeson) import Test.Spec.Assertions (shouldEqual) suite :: TestPlanM (Aff Unit) Unit From aab6c97c5d5fd81ba37d33aecf021cc917787792 Mon Sep 17 00:00:00 2001 From: Gregory Gerasev Date: Mon, 19 Dec 2022 00:11:17 +0400 Subject: [PATCH 131/373] Fix warnings --- examples/PaysWithDatum.purs | 1 - examples/SatisfiesAnyOf.purs | 1 - src/Internal/Types/ScriptLookups.purs | 2 +- test/Plutip/Contract.purs | 4 ++-- 4 files changed, 3 insertions(+), 5 deletions(-) diff --git a/examples/PaysWithDatum.purs b/examples/PaysWithDatum.purs index 37ef8f7f9b..921726023f 100644 --- a/examples/PaysWithDatum.purs +++ b/examples/PaysWithDatum.purs @@ -20,7 +20,6 @@ import Contract.Log (logInfo') import Contract.Monad ( Contract , launchAff_ - , liftContractM , liftedM , runContract ) diff --git a/examples/SatisfiesAnyOf.purs b/examples/SatisfiesAnyOf.purs index 6816fb3966..18234eb084 100644 --- a/examples/SatisfiesAnyOf.purs +++ b/examples/SatisfiesAnyOf.purs @@ -22,7 +22,6 @@ import Contract.PlutusData import Contract.ScriptLookups as Lookups import Contract.TxConstraints (TxConstraints) import Contract.TxConstraints as Constraints -import Control.Monad.Error.Class (liftMaybe) import Data.BigInt as BigInt import Effect.Exception (error) diff --git a/src/Internal/Types/ScriptLookups.purs b/src/Internal/Types/ScriptLookups.purs index 1c1da043e1..418ea23114 100644 --- a/src/Internal/Types/ScriptLookups.purs +++ b/src/Internal/Types/ScriptLookups.purs @@ -55,7 +55,7 @@ import Prelude hiding (join) import Aeson (class EncodeAeson) import Contract.Hashing (plutusScriptStakeValidatorHash) -import Control.Monad.Error.Class (catchError, liftMaybe, throwError) +import Control.Monad.Error.Class (catchError, throwError) import Control.Monad.Except.Trans (ExceptT(ExceptT), except, runExceptT) import Control.Monad.State.Trans (StateT, get, gets, put, runStateT) import Control.Monad.Trans.Class (lift) diff --git a/test/Plutip/Contract.purs b/test/Plutip/Contract.purs index e1a2f958e5..e9336d704b 100644 --- a/test/Plutip/Contract.purs +++ b/test/Plutip/Contract.purs @@ -36,7 +36,7 @@ import Contract.PlutusData , getDatumsByHashes , getDatumsByHashesWithErrors ) -import Contract.Prelude (liftM, mconcat) +import Contract.Prelude (mconcat) import Contract.Prim.ByteArray (byteArrayFromAscii, hexToByteArrayUnsafe) import Contract.ScriptLookups as Lookups import Contract.Scripts @@ -141,7 +141,7 @@ import Data.Newtype (unwrap, wrap) import Data.Traversable (traverse, traverse_) import Data.Tuple.Nested (type (/\), (/\)) import Effect.Class (liftEffect) -import Effect.Exception (error, throw) +import Effect.Exception (throw) import Mote (group, skip, test) import Mote.Monad (mapTest) import Safe.Coerce (coerce) From d9e0afdb4bb5841743e1b84c31d192ca8f39ada1 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Mon, 19 Dec 2022 11:33:21 +0000 Subject: [PATCH 132/373] Update CHANGELOG.md --- CHANGELOG.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index dc25bde9d7..8ee0f4e9e8 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -50,7 +50,7 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) - Running plutip servers attaches on SIGINT handlers and therefore node will not exit by default. ([#1231](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1231)). - `TestPlanM`, `interpret` and `interpretWithConfig` are now public in `Contract.Test.Mote` and our custom `consoleReporter` in `Contract.Test.Mote.ConsoleReporter`. ([#1261](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1261)). - Internal datum conversions are now total, resulting in some datum-related Contract functions dropping the use of `Maybe`, for example `datumHash`, `convertPlutusData` and their related functions. ([#1284](https://github.com/Plutonomicon/cardano-transaction-lib/issues/1284)). -- CIP-25 `policy_id` and `asset_name` metadata keys no longer include a `0x` prefix for compatibility with Blockfrost ([#1309](https://github.com/Plutonomicon/cardano-transaction-lib/issues/1309 "CTL's CIP25 metadata encoding is considered invalid by Blockfrost #1309")). +- CIP-25 `policy_id` and `asset_name` metadata keys no longer include a `0x` prefix for compatibility with Blockfrost ([#1309](https://github.com/Plutonomicon/cardano-transaction-lib/issues/1309)). - `purescript-aeson` package has been updated: - the performance has generally been improved - `encodeAeson'` is now `encodeAeson` (and it returns just `Aeson` instead of an `AesonEncoder`) From bbb0203984a57ff53255bbcdd9086bd8304e9349 Mon Sep 17 00:00:00 2001 From: peter Date: Mon, 19 Dec 2022 13:29:56 +0100 Subject: [PATCH 133/373] delete haskell related inputs for the flake --- flake.lock | 12 ------------ flake.nix | 7 ------- 2 files changed, 19 deletions(-) diff --git a/flake.lock b/flake.lock index 77c1366d14..2a4c479a5e 100644 --- a/flake.lock +++ b/flake.lock @@ -9549,10 +9549,6 @@ }, "root": { "inputs": { - "CHaP": [ - "ogmios", - "CHaP" - ], "cardano-configurations": "cardano-configurations", "cardano-node": [ "ogmios-nixos", @@ -9560,14 +9556,6 @@ ], "easy-purescript-nix": "easy-purescript-nix", "flake-compat": "flake-compat", - "haskell-nix": [ - "ogmios", - "haskell-nix" - ], - "iohk-nix": [ - "ogmios", - "iohk-nix" - ], "iohk-nix-environments": "iohk-nix-environments", "kupo": "kupo", "kupo-nixos": "kupo-nixos", diff --git a/flake.nix b/flake.nix index bbedaa937f..c8c7cf7ef4 100644 --- a/flake.nix +++ b/flake.nix @@ -4,10 +4,7 @@ nixConfig.bash-prompt = "\\[\\e[0m\\][\\[\\e[0;2m\\]nix-develop \\[\\e[0;1m\\]CTL \\[\\e[0;32m\\]\\w\\[\\e[0m\\]]\\[\\e[0m\\]$ \\[\\e[0m\\]"; inputs = { - iohk-nix.follows = "ogmios/iohk-nix"; - haskell-nix.follows = "ogmios/haskell-nix"; nixpkgs.follows = "ogmios/nixpkgs"; - CHaP.follows = "ogmios/CHaP"; flake-compat = { url = "github:edolstra/flake-compat"; @@ -50,10 +47,7 @@ outputs = { self , nixpkgs - , haskell-nix - , iohk-nix , cardano-configurations - , CHaP , ... }@inputs: let @@ -72,7 +66,6 @@ ogmios-fixtures = inputs.ogmios; }) ]; - inherit (haskell-nix) config; inherit system; }; From 4fb83c8d16e0a5f01d727f2816b292c5cd246ea3 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Mon, 19 Dec 2022 12:58:55 +0000 Subject: [PATCH 134/373] Unused import --- examples/SatisfiesAnyOf.purs | 1 - 1 file changed, 1 deletion(-) diff --git a/examples/SatisfiesAnyOf.purs b/examples/SatisfiesAnyOf.purs index 18234eb084..2c35ac4a96 100644 --- a/examples/SatisfiesAnyOf.purs +++ b/examples/SatisfiesAnyOf.purs @@ -23,7 +23,6 @@ import Contract.ScriptLookups as Lookups import Contract.TxConstraints (TxConstraints) import Contract.TxConstraints as Constraints import Data.BigInt as BigInt -import Effect.Exception (error) main :: Effect Unit main = example testnetNamiConfig From 5b5861cfd4f5e5605882bb31ab4fecdb94ccd5a7 Mon Sep 17 00:00:00 2001 From: Bradley Date: Mon, 19 Dec 2022 10:52:59 -0500 Subject: [PATCH 135/373] Add in Secp Explainer doc --- doc/Secp256k1-support.md | 40 ++++++++++++++++++++++++++++++++++++++++ 1 file changed, 40 insertions(+) create mode 100644 doc/Secp256k1-support.md diff --git a/doc/Secp256k1-support.md b/doc/Secp256k1-support.md new file mode 100644 index 0000000000..346e8f189d --- /dev/null +++ b/doc/Secp256k1-support.md @@ -0,0 +1,40 @@ +# CTL Secp256k1 Support + +This document is a reference/explainer for the new CTL features introduced with the Chang Hardfork. + +**Table of contents** + + + +- [Overview](#overview) +- [Usage](#usage) + + +## Overview + +See the [What is SECP](https://iohk.io/en/blog/posts/2022/11/03/what-is-secp-and-how-it-drives-cross-chain-development-on-cardano/) for a general overview of what SECP is and how it effects the Cardano blockchain. + +For a more in depth oversight please see [Cip-49](https://github.com/mlabs-haskell/CIPs/tree/c5bdd66fe49c19c341499f86cebaa2eef9e90b74/CIP-0049). + +## Usage + +[Cip-49](https://github.com/mlabs-haskell/CIPs/tree/c5bdd66fe49c19c341499f86cebaa2eef9e90b74/CIP-0049) provides two new builtin functions: + +Both functions take the following as Parameters: +- A verification key; +- An input to verify (either the message itself, or a hash); +- A signature. + +The two functions are: + +**1. A verification function for [ECDSA](https://en.bitcoin.it/wiki/Elliptic_Curve_Digital_Signature_Algorithm) signatures.** + +[ECDSA usage example](../examples/PlutusV2/ECDSA.purs)\ + +[ECDSA source code](../src/Contract/Crypto/Secp256k1/ECDSA.purs) + +**2. A verification function for [Schnorr](https://github.com/bitcoin/bips/blob/master/bip-0340.mediawiki) signatures.** + +[Schnorr usage example](../examples/PlutusV2/Schnorr.purs) + +[Schnorr source code](../src/Contract/Crypto/Secp256k1/Schnorr.purs) From a14b8387329fd7485e6d395c9a1a91bddc7a9190 Mon Sep 17 00:00:00 2001 From: Bradley Date: Mon, 19 Dec 2022 10:56:09 -0500 Subject: [PATCH 136/373] fix links --- doc/Secp256k1-support.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/doc/Secp256k1-support.md b/doc/Secp256k1-support.md index 346e8f189d..4c9bcd4d12 100644 --- a/doc/Secp256k1-support.md +++ b/doc/Secp256k1-support.md @@ -29,12 +29,12 @@ The two functions are: **1. A verification function for [ECDSA](https://en.bitcoin.it/wiki/Elliptic_Curve_Digital_Signature_Algorithm) signatures.** -[ECDSA usage example](../examples/PlutusV2/ECDSA.purs)\ +[ECDSA usage example](../examples/ECDSA.purs)\ [ECDSA source code](../src/Contract/Crypto/Secp256k1/ECDSA.purs) **2. A verification function for [Schnorr](https://github.com/bitcoin/bips/blob/master/bip-0340.mediawiki) signatures.** -[Schnorr usage example](../examples/PlutusV2/Schnorr.purs) +[Schnorr usage example](../examples/Schnorr.purs) [Schnorr source code](../src/Contract/Crypto/Secp256k1/Schnorr.purs) From 904eb52494220215b6db90d22994ae5462692b8e Mon Sep 17 00:00:00 2001 From: peter Date: Mon, 19 Dec 2022 17:07:57 +0100 Subject: [PATCH 137/373] with fixed csl version --- package-lock.json | 6653 +++++++++++++++++++++++++++++++++++++++++++- package.json | 4 +- test/Fixtures.purs | 61 +- 3 files changed, 6583 insertions(+), 135 deletions(-) diff --git a/package-lock.json b/package-lock.json index 8acd24e087..01b48bf461 100644 --- a/package-lock.json +++ b/package-lock.json @@ -1,8 +1,6466 @@ { "name": "cardano-transaction-lib", "version": "3.0.0", - "lockfileVersion": 1, + "lockfileVersion": 2, "requires": true, + "packages": { + "": { + "name": "cardano-transaction-lib", + "version": "3.0.0", + "license": "MIT", + "dependencies": { + "@emurgo/cardano-message-signing-browser": "1.0.1", + "@emurgo/cardano-message-signing-nodejs": "1.0.1", + "@emurgo/cardano-serialization-lib-browser": "11.2.1", + "@emurgo/cardano-serialization-lib-nodejs": "11.2.1", + "base64-js": "^1.5.1", + "big-integer": "1.6.51", + "blakejs": "1.2.1", + "bufferutil": "4.0.5", + "doctoc": "^2.2.1", + "jssha": "3.2.0", + "node-polyfill-webpack-plugin": "1.1.4", + "puppeteer-core": "^15.3.2", + "reconnecting-websocket": "4.4.0", + "uniqid": "5.4.0", + "ws": "8.4.0", + "xhr2": "0.2.1" + }, + "devDependencies": { + "buffer": "6.0.3", + "html-webpack-plugin": "5.5.0", + "webpack": "5.67.0", + "webpack-cli": "4.10", + "webpack-dev-server": "4.7.4" + } + }, + "node_modules/@discoveryjs/json-ext": { + "version": "0.5.7", + "resolved": "https://registry.npmjs.org/@discoveryjs/json-ext/-/json-ext-0.5.7.tgz", + "integrity": "sha512-dBVuXR082gk3jsFp7Rd/JI4kytwGHecnCoTtXFb7DB6CNHp4rg5k1bhg0nWdLGLnOV71lmDzGQaLMy8iPLY0pw==", + "dev": true, + "engines": { + "node": ">=10.0.0" + } + }, + "node_modules/@emurgo/cardano-message-signing-browser": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/@emurgo/cardano-message-signing-browser/-/cardano-message-signing-browser-1.0.1.tgz", + "integrity": "sha512-yC4Ymq44WR0bXO1wzxCoyc2W/RD1KSAla0oYhin7IYoVkp2raGp8wt7QNF4pDdNnTcejn5fyPyYY9dL4666H1w==" + }, + "node_modules/@emurgo/cardano-message-signing-nodejs": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/@emurgo/cardano-message-signing-nodejs/-/cardano-message-signing-nodejs-1.0.1.tgz", + "integrity": "sha512-PoKh1tQnJX18f8iEr8Jk1KXxKCn9eqaSslMI1pyOJvYRJhQVDLCh0+9YReufjp0oFJIY1ShcrR+4/WnECVZUKQ==" + }, + "node_modules/@emurgo/cardano-serialization-lib-browser": { + "version": "11.2.1", + "resolved": "https://registry.npmjs.org/@emurgo/cardano-serialization-lib-browser/-/cardano-serialization-lib-browser-11.2.1.tgz", + "integrity": "sha512-J9Pmeta7y1GYnMCxtb3GnGCRw6zk1wiQ8EdCYQRn/Yqa/ss1zoBjd41euVi02Eb58aLuOJS81nNU+BcMLGXvUg==" + }, + "node_modules/@emurgo/cardano-serialization-lib-nodejs": { + "version": "11.2.1", + "resolved": "https://registry.npmjs.org/@emurgo/cardano-serialization-lib-nodejs/-/cardano-serialization-lib-nodejs-11.2.1.tgz", + "integrity": "sha512-+Rw35NW4Qv/9uFaPxhKtxiIPmoBEIFMAgdqQxZTw6hNT/wvBp2TvwTBPnOW8ODs7GUAA8nrO1rJJAaxF+mAG2w==" + }, + "node_modules/@jridgewell/gen-mapping": { + "version": "0.3.2", + "resolved": "https://registry.npmjs.org/@jridgewell/gen-mapping/-/gen-mapping-0.3.2.tgz", + "integrity": "sha512-mh65xKQAzI6iBcFzwv28KVWSmCkdRBWoOh+bYQGW3+6OZvbbN3TqMGo5hqYxQniRcH9F2VZIoJCm4pa3BPDK/A==", + "dependencies": { + "@jridgewell/set-array": "^1.0.1", + "@jridgewell/sourcemap-codec": "^1.4.10", + "@jridgewell/trace-mapping": "^0.3.9" + }, + "engines": { + "node": ">=6.0.0" + } + }, + "node_modules/@jridgewell/resolve-uri": { + "version": "3.0.7", + "resolved": "https://registry.npmjs.org/@jridgewell/resolve-uri/-/resolve-uri-3.0.7.tgz", + "integrity": "sha512-8cXDaBBHOr2pQ7j77Y6Vp5VDT2sIqWyWQ56TjEq4ih/a4iST3dItRe8Q9fp0rrIl9DoKhWQtUQz/YpOxLkXbNA==", + "engines": { + "node": ">=6.0.0" + } + }, + "node_modules/@jridgewell/set-array": { + "version": "1.1.2", + "resolved": "https://registry.npmjs.org/@jridgewell/set-array/-/set-array-1.1.2.tgz", + "integrity": "sha512-xnkseuNADM0gt2bs+BvhO0p78Mk762YnZdsuzFV018NoG1Sj1SCQvpSqa7XUaTam5vAGasABV9qXASMKnFMwMw==", + "engines": { + "node": ">=6.0.0" + } + }, + "node_modules/@jridgewell/source-map": { + "version": "0.3.2", + "resolved": "https://registry.npmjs.org/@jridgewell/source-map/-/source-map-0.3.2.tgz", + "integrity": "sha512-m7O9o2uR8k2ObDysZYzdfhb08VuEml5oWGiosa1VdaPZ/A6QyPkAJuwN0Q1lhULOf6B7MtQmHENS743hWtCrgw==", + "dependencies": { + "@jridgewell/gen-mapping": "^0.3.0", + "@jridgewell/trace-mapping": "^0.3.9" + } + }, + "node_modules/@jridgewell/sourcemap-codec": { + "version": "1.4.13", + "resolved": "https://registry.npmjs.org/@jridgewell/sourcemap-codec/-/sourcemap-codec-1.4.13.tgz", + "integrity": "sha512-GryiOJmNcWbovBxTfZSF71V/mXbgcV3MewDe3kIMCLyIh5e7SKAeUZs+rMnJ8jkMolZ/4/VsdBmMrw3l+VdZ3w==" + }, + "node_modules/@jridgewell/trace-mapping": { + "version": "0.3.13", + "resolved": "https://registry.npmjs.org/@jridgewell/trace-mapping/-/trace-mapping-0.3.13.tgz", + "integrity": "sha512-o1xbKhp9qnIAoHJSWd6KlCZfqslL4valSF81H8ImioOAxluWYWOpWkpyktY2vnt4tbrX9XYaxovq6cgowaJp2w==", + "dependencies": { + "@jridgewell/resolve-uri": "^3.0.3", + "@jridgewell/sourcemap-codec": "^1.4.10" + } + }, + "node_modules/@nodelib/fs.scandir": { + "version": "2.1.5", + "resolved": "https://registry.npmjs.org/@nodelib/fs.scandir/-/fs.scandir-2.1.5.tgz", + "integrity": "sha512-vq24Bq3ym5HEQm2NKCr3yXDwjc7vTsEThRDnkp2DK9p1uqLR+DHurm/NOTo0KG7HYHU7eppKZj3MyqYuMBf62g==", + "dev": true, + "dependencies": { + "@nodelib/fs.stat": "2.0.5", + "run-parallel": "^1.1.9" + }, + "engines": { + "node": ">= 8" + } + }, + "node_modules/@nodelib/fs.stat": { + "version": "2.0.5", + "resolved": "https://registry.npmjs.org/@nodelib/fs.stat/-/fs.stat-2.0.5.tgz", + "integrity": "sha512-RkhPPp2zrqDAQA/2jNhnztcPAlv64XdhIp7a7454A5ovI7Bukxgt7MX7udwAu3zg1DcpPU0rz3VV1SeaqvY4+A==", + "dev": true, + "engines": { + "node": ">= 8" + } + }, + "node_modules/@nodelib/fs.walk": { + "version": "1.2.8", + "resolved": "https://registry.npmjs.org/@nodelib/fs.walk/-/fs.walk-1.2.8.tgz", + "integrity": "sha512-oGB+UxlgWcgQkgwo8GcEGwemoTFt3FIO9ababBmaGwXIoBKZ+GTy0pP185beGg7Llih/NSHSV2XAs1lnznocSg==", + "dev": true, + "dependencies": { + "@nodelib/fs.scandir": "2.1.5", + "fastq": "^1.6.0" + }, + "engines": { + "node": ">= 8" + } + }, + "node_modules/@textlint/ast-node-types": { + "version": "12.2.2", + "resolved": "https://registry.npmjs.org/@textlint/ast-node-types/-/ast-node-types-12.2.2.tgz", + "integrity": "sha512-VQAXUSGdmEajHXrMxeM9ZTS8UBJSVB0ghJFHpFfqYKlcDsjIqClSmTprY6521HoCoSLoUIGBxTC3jQyUMJFIWw==" + }, + "node_modules/@textlint/markdown-to-ast": { + "version": "12.2.3", + "resolved": "https://registry.npmjs.org/@textlint/markdown-to-ast/-/markdown-to-ast-12.2.3.tgz", + "integrity": "sha512-omZqcZV1Q8t9K0IKvlHNIdTV3SKNaS2P5qkbTjzDj7PuTuvG20JFqL9Naiwwi9ty3NzTzq+W8lLG3H2HgX0WvA==", + "dependencies": { + "@textlint/ast-node-types": "^12.2.2", + "debug": "^4.3.4", + "mdast-util-gfm-autolink-literal": "^0.1.3", + "remark-footnotes": "^3.0.0", + "remark-frontmatter": "^3.0.0", + "remark-gfm": "^1.0.0", + "remark-parse": "^9.0.0", + "traverse": "^0.6.7", + "unified": "^9.2.2" + } + }, + "node_modules/@textlint/markdown-to-ast/node_modules/debug": { + "version": "4.3.4", + "resolved": "https://registry.npmjs.org/debug/-/debug-4.3.4.tgz", + "integrity": "sha512-PRWFHuSU3eDtQJPvnNY7Jcket1j0t5OuOsFzPPzsekD52Zl8qUfFIPEiswXqIvHWGVHOgX+7G/vCNNhehwxfkQ==", + "dependencies": { + "ms": "2.1.2" + }, + "engines": { + "node": ">=6.0" + }, + "peerDependenciesMeta": { + "supports-color": { + "optional": true + } + } + }, + "node_modules/@textlint/markdown-to-ast/node_modules/ms": { + "version": "2.1.2", + "resolved": "https://registry.npmjs.org/ms/-/ms-2.1.2.tgz", + "integrity": "sha512-sGkPx+VjMtmA6MX27oA4FBFELFCZZ4S4XqeGOXCv68tT+jb3vk/RyaKWP0PTKyWtmLSM0b+adUTEvbs1PEaH2w==" + }, + "node_modules/@types/body-parser": { + "version": "1.19.2", + "resolved": "https://registry.npmjs.org/@types/body-parser/-/body-parser-1.19.2.tgz", + "integrity": "sha512-ALYone6pm6QmwZoAgeyNksccT9Q4AWZQ6PvfwR37GT6r6FWUPguq6sUmNGSMV2Wr761oQoBxwGGa6DR5o1DC9g==", + "dev": true, + "dependencies": { + "@types/connect": "*", + "@types/node": "*" + } + }, + "node_modules/@types/bonjour": { + "version": "3.5.10", + "resolved": "https://registry.npmjs.org/@types/bonjour/-/bonjour-3.5.10.tgz", + "integrity": "sha512-p7ienRMiS41Nu2/igbJxxLDWrSZ0WxM8UQgCeO9KhoVF7cOVFkrKsiDr1EsJIla8vV3oEEjGcz11jc5yimhzZw==", + "dev": true, + "dependencies": { + "@types/node": "*" + } + }, + "node_modules/@types/connect": { + "version": "3.4.35", + "resolved": "https://registry.npmjs.org/@types/connect/-/connect-3.4.35.tgz", + "integrity": "sha512-cdeYyv4KWoEgpBISTxWvqYsVy444DOqehiF3fM3ne10AmJ62RSyNkUnxMJXHQWRQQX2eR94m5y1IZyDwBjV9FQ==", + "dev": true, + "dependencies": { + "@types/node": "*" + } + }, + "node_modules/@types/connect-history-api-fallback": { + "version": "1.3.5", + "resolved": "https://registry.npmjs.org/@types/connect-history-api-fallback/-/connect-history-api-fallback-1.3.5.tgz", + "integrity": "sha512-h8QJa8xSb1WD4fpKBDcATDNGXghFj6/3GRWG6dhmRcu0RX1Ubasur2Uvx5aeEwlf0MwblEC2bMzzMQntxnw/Cw==", + "dev": true, + "dependencies": { + "@types/express-serve-static-core": "*", + "@types/node": "*" + } + }, + "node_modules/@types/eslint": { + "version": "8.4.3", + "resolved": "https://registry.npmjs.org/@types/eslint/-/eslint-8.4.3.tgz", + "integrity": "sha512-YP1S7YJRMPs+7KZKDb9G63n8YejIwW9BALq7a5j2+H4yl6iOv9CB29edho+cuFRrvmJbbaH2yiVChKLJVysDGw==", + "dependencies": { + "@types/estree": "*", + "@types/json-schema": "*" + } + }, + "node_modules/@types/eslint-scope": { + "version": "3.7.3", + "resolved": "https://registry.npmjs.org/@types/eslint-scope/-/eslint-scope-3.7.3.tgz", + "integrity": "sha512-PB3ldyrcnAicT35TWPs5IcwKD8S333HMaa2VVv4+wdvebJkjWuW/xESoB8IwRcog8HYVYamb1g/R31Qv5Bx03g==", + "dependencies": { + "@types/eslint": "*", + "@types/estree": "*" + } + }, + "node_modules/@types/estree": { + "version": "0.0.50", + "resolved": "https://registry.npmjs.org/@types/estree/-/estree-0.0.50.tgz", + "integrity": "sha512-C6N5s2ZFtuZRj54k2/zyRhNDjJwwcViAM3Nbm8zjBpbqAdZ00mr0CFxvSKeO8Y/e03WVFLpQMdHYVfUd6SB+Hw==" + }, + "node_modules/@types/express": { + "version": "4.17.13", + "resolved": "https://registry.npmjs.org/@types/express/-/express-4.17.13.tgz", + "integrity": "sha512-6bSZTPaTIACxn48l50SR+axgrqm6qXFIxrdAKaG6PaJk3+zuUr35hBlgT7vOmJcum+OEaIBLtHV/qloEAFITeA==", + "dev": true, + "dependencies": { + "@types/body-parser": "*", + "@types/express-serve-static-core": "^4.17.18", + "@types/qs": "*", + "@types/serve-static": "*" + } + }, + "node_modules/@types/express-serve-static-core": { + "version": "4.17.29", + "resolved": "https://registry.npmjs.org/@types/express-serve-static-core/-/express-serve-static-core-4.17.29.tgz", + "integrity": "sha512-uMd++6dMKS32EOuw1Uli3e3BPgdLIXmezcfHv7N4c1s3gkhikBplORPpMq3fuWkxncZN1reb16d5n8yhQ80x7Q==", + "dev": true, + "dependencies": { + "@types/node": "*", + "@types/qs": "*", + "@types/range-parser": "*" + } + }, + "node_modules/@types/html-minifier-terser": { + "version": "6.1.0", + "resolved": "https://registry.npmjs.org/@types/html-minifier-terser/-/html-minifier-terser-6.1.0.tgz", + "integrity": "sha512-oh/6byDPnL1zeNXFrDXFLyZjkr1MsBG667IM792caf1L2UPOOMf65NFzjUH/ltyfwjAGfs1rsX1eftK0jC/KIg==", + "dev": true + }, + "node_modules/@types/http-proxy": { + "version": "1.17.9", + "resolved": "https://registry.npmjs.org/@types/http-proxy/-/http-proxy-1.17.9.tgz", + "integrity": "sha512-QsbSjA/fSk7xB+UXlCT3wHBy5ai9wOcNDWwZAtud+jXhwOM3l+EYZh8Lng4+/6n8uar0J7xILzqftJdJ/Wdfkw==", + "dev": true, + "dependencies": { + "@types/node": "*" + } + }, + "node_modules/@types/json-schema": { + "version": "7.0.11", + "resolved": "https://registry.npmjs.org/@types/json-schema/-/json-schema-7.0.11.tgz", + "integrity": "sha512-wOuvG1SN4Us4rez+tylwwwCV1psiNVOkJeM3AUWUNWg/jDQY2+HE/444y5gc+jBmRqASOm2Oeh5c1axHobwRKQ==" + }, + "node_modules/@types/mdast": { + "version": "3.0.10", + "resolved": "https://registry.npmjs.org/@types/mdast/-/mdast-3.0.10.tgz", + "integrity": "sha512-W864tg/Osz1+9f4lrGTZpCSO5/z4608eUp19tbozkq2HJK6i3z1kT0H9tlADXuYIb1YYOBByU4Jsqkk75q48qA==", + "dependencies": { + "@types/unist": "*" + } + }, + "node_modules/@types/mime": { + "version": "1.3.2", + "resolved": "https://registry.npmjs.org/@types/mime/-/mime-1.3.2.tgz", + "integrity": "sha512-YATxVxgRqNH6nHEIsvg6k2Boc1JHI9ZbH5iWFFv/MTkchz3b1ieGDa5T0a9RznNdI0KhVbdbWSN+KWWrQZRxTw==", + "dev": true + }, + "node_modules/@types/node": { + "version": "17.0.35", + "resolved": "https://registry.npmjs.org/@types/node/-/node-17.0.35.tgz", + "integrity": "sha512-vu1SrqBjbbZ3J6vwY17jBs8Sr/BKA+/a/WtjRG+whKg1iuLFOosq872EXS0eXWILdO36DHQQeku/ZcL6hz2fpg==" + }, + "node_modules/@types/qs": { + "version": "6.9.7", + "resolved": "https://registry.npmjs.org/@types/qs/-/qs-6.9.7.tgz", + "integrity": "sha512-FGa1F62FT09qcrueBA6qYTrJPVDzah9a+493+o2PCXsesWHIn27G98TsSMs3WPNbZIEj4+VJf6saSFpvD+3Zsw==", + "dev": true + }, + "node_modules/@types/range-parser": { + "version": "1.2.4", + "resolved": "https://registry.npmjs.org/@types/range-parser/-/range-parser-1.2.4.tgz", + "integrity": "sha512-EEhsLsD6UsDM1yFhAvy0Cjr6VwmpMWqFBCb9w07wVugF7w9nfajxLuVmngTIpgS6svCnm6Vaw+MZhoDCKnOfsw==", + "dev": true + }, + "node_modules/@types/retry": { + "version": "0.12.0", + "resolved": "https://registry.npmjs.org/@types/retry/-/retry-0.12.0.tgz", + "integrity": "sha512-wWKOClTTiizcZhXnPY4wikVAwmdYHp8q6DmC+EJUzAMsycb7HB32Kh9RN4+0gExjmPmZSAQjgURXIGATPegAvA==", + "dev": true + }, + "node_modules/@types/serve-index": { + "version": "1.9.1", + "resolved": "https://registry.npmjs.org/@types/serve-index/-/serve-index-1.9.1.tgz", + "integrity": "sha512-d/Hs3nWDxNL2xAczmOVZNj92YZCS6RGxfBPjKzuu/XirCgXdpKEb88dYNbrYGint6IVWLNP+yonwVAuRC0T2Dg==", + "dev": true, + "dependencies": { + "@types/express": "*" + } + }, + "node_modules/@types/serve-static": { + "version": "1.13.10", + "resolved": "https://registry.npmjs.org/@types/serve-static/-/serve-static-1.13.10.tgz", + "integrity": "sha512-nCkHGI4w7ZgAdNkrEu0bv+4xNV/XDqW+DydknebMOQwkpDGx8G+HTlj7R7ABI8i8nKxVw0wtKPi1D+lPOkh4YQ==", + "dev": true, + "dependencies": { + "@types/mime": "^1", + "@types/node": "*" + } + }, + "node_modules/@types/sockjs": { + "version": "0.3.33", + "resolved": "https://registry.npmjs.org/@types/sockjs/-/sockjs-0.3.33.tgz", + "integrity": "sha512-f0KEEe05NvUnat+boPTZ0dgaLZ4SfSouXUgv5noUiefG2ajgKjmETo9ZJyuqsl7dfl2aHlLJUiki6B4ZYldiiw==", + "dev": true, + "dependencies": { + "@types/node": "*" + } + }, + "node_modules/@types/unist": { + "version": "2.0.6", + "resolved": "https://registry.npmjs.org/@types/unist/-/unist-2.0.6.tgz", + "integrity": "sha512-PBjIUxZHOuj0R15/xuwJYjFi+KZdNFrehocChv4g5hu6aFroHue8m0lBP0POdK2nKzbw0cgV1mws8+V/JAcEkQ==" + }, + "node_modules/@types/ws": { + "version": "8.5.3", + "resolved": "https://registry.npmjs.org/@types/ws/-/ws-8.5.3.tgz", + "integrity": "sha512-6YOoWjruKj1uLf3INHH7D3qTXwFfEsg1kf3c0uDdSBJwfa/llkwIjrAGV7j7mVgGNbzTQ3HiHKKDXl6bJPD97w==", + "dev": true, + "dependencies": { + "@types/node": "*" + } + }, + "node_modules/@types/yauzl": { + "version": "2.10.0", + "resolved": "https://registry.npmjs.org/@types/yauzl/-/yauzl-2.10.0.tgz", + "integrity": "sha512-Cn6WYCm0tXv8p6k+A8PvbDG763EDpBoTzHdA+Q/MF6H3sapGjCm9NzoaJncJS9tUKSuCoDs9XHxYYsQDgxR6kw==", + "optional": true, + "dependencies": { + "@types/node": "*" + } + }, + "node_modules/@webassemblyjs/ast": { + "version": "1.11.1", + "resolved": "https://registry.npmjs.org/@webassemblyjs/ast/-/ast-1.11.1.tgz", + "integrity": "sha512-ukBh14qFLjxTQNTXocdyksN5QdM28S1CxHt2rdskFyL+xFV7VremuBLVbmCePj+URalXBENx/9Lm7lnhihtCSw==", + "dependencies": { + "@webassemblyjs/helper-numbers": "1.11.1", + "@webassemblyjs/helper-wasm-bytecode": "1.11.1" + } + }, + "node_modules/@webassemblyjs/floating-point-hex-parser": { + "version": "1.11.1", + "resolved": "https://registry.npmjs.org/@webassemblyjs/floating-point-hex-parser/-/floating-point-hex-parser-1.11.1.tgz", + "integrity": "sha512-iGRfyc5Bq+NnNuX8b5hwBrRjzf0ocrJPI6GWFodBFzmFnyvrQ83SHKhmilCU/8Jv67i4GJZBMhEzltxzcNagtQ==" + }, + "node_modules/@webassemblyjs/helper-api-error": { + "version": "1.11.1", + "resolved": "https://registry.npmjs.org/@webassemblyjs/helper-api-error/-/helper-api-error-1.11.1.tgz", + "integrity": "sha512-RlhS8CBCXfRUR/cwo2ho9bkheSXG0+NwooXcc3PAILALf2QLdFyj7KGsKRbVc95hZnhnERon4kW/D3SZpp6Tcg==" + }, + "node_modules/@webassemblyjs/helper-buffer": { + "version": "1.11.1", + "resolved": "https://registry.npmjs.org/@webassemblyjs/helper-buffer/-/helper-buffer-1.11.1.tgz", + "integrity": "sha512-gwikF65aDNeeXa8JxXa2BAk+REjSyhrNC9ZwdT0f8jc4dQQeDQ7G4m0f2QCLPJiMTTO6wfDmRmj/pW0PsUvIcA==" + }, + "node_modules/@webassemblyjs/helper-numbers": { + "version": "1.11.1", + "resolved": "https://registry.npmjs.org/@webassemblyjs/helper-numbers/-/helper-numbers-1.11.1.tgz", + "integrity": "sha512-vDkbxiB8zfnPdNK9Rajcey5C0w+QJugEglN0of+kmO8l7lDb77AnlKYQF7aarZuCrv+l0UvqL+68gSDr3k9LPQ==", + "dependencies": { + "@webassemblyjs/floating-point-hex-parser": "1.11.1", + "@webassemblyjs/helper-api-error": "1.11.1", + "@xtuc/long": "4.2.2" + } + }, + "node_modules/@webassemblyjs/helper-wasm-bytecode": { + "version": "1.11.1", + "resolved": "https://registry.npmjs.org/@webassemblyjs/helper-wasm-bytecode/-/helper-wasm-bytecode-1.11.1.tgz", + "integrity": "sha512-PvpoOGiJwXeTrSf/qfudJhwlvDQxFgelbMqtq52WWiXC6Xgg1IREdngmPN3bs4RoO83PnL/nFrxucXj1+BX62Q==" + }, + "node_modules/@webassemblyjs/helper-wasm-section": { + "version": "1.11.1", + "resolved": "https://registry.npmjs.org/@webassemblyjs/helper-wasm-section/-/helper-wasm-section-1.11.1.tgz", + "integrity": "sha512-10P9No29rYX1j7F3EVPX3JvGPQPae+AomuSTPiF9eBQeChHI6iqjMIwR9JmOJXwpnn/oVGDk7I5IlskuMwU/pg==", + "dependencies": { + "@webassemblyjs/ast": "1.11.1", + "@webassemblyjs/helper-buffer": "1.11.1", + "@webassemblyjs/helper-wasm-bytecode": "1.11.1", + "@webassemblyjs/wasm-gen": "1.11.1" + } + }, + "node_modules/@webassemblyjs/ieee754": { + "version": "1.11.1", + "resolved": "https://registry.npmjs.org/@webassemblyjs/ieee754/-/ieee754-1.11.1.tgz", + "integrity": "sha512-hJ87QIPtAMKbFq6CGTkZYJivEwZDbQUgYd3qKSadTNOhVY7p+gfP6Sr0lLRVTaG1JjFj+r3YchoqRYxNH3M0GQ==", + "dependencies": { + "@xtuc/ieee754": "^1.2.0" + } + }, + "node_modules/@webassemblyjs/leb128": { + "version": "1.11.1", + "resolved": "https://registry.npmjs.org/@webassemblyjs/leb128/-/leb128-1.11.1.tgz", + "integrity": "sha512-BJ2P0hNZ0u+Th1YZXJpzW6miwqQUGcIHT1G/sf72gLVD9DZ5AdYTqPNbHZh6K1M5VmKvFXwGSWZADz+qBWxeRw==", + "dependencies": { + "@xtuc/long": "4.2.2" + } + }, + "node_modules/@webassemblyjs/utf8": { + "version": "1.11.1", + "resolved": "https://registry.npmjs.org/@webassemblyjs/utf8/-/utf8-1.11.1.tgz", + "integrity": "sha512-9kqcxAEdMhiwQkHpkNiorZzqpGrodQQ2IGrHHxCy+Ozng0ofyMA0lTqiLkVs1uzTRejX+/O0EOT7KxqVPuXosQ==" + }, + "node_modules/@webassemblyjs/wasm-edit": { + "version": "1.11.1", + "resolved": "https://registry.npmjs.org/@webassemblyjs/wasm-edit/-/wasm-edit-1.11.1.tgz", + "integrity": "sha512-g+RsupUC1aTHfR8CDgnsVRVZFJqdkFHpsHMfJuWQzWU3tvnLC07UqHICfP+4XyL2tnr1amvl1Sdp06TnYCmVkA==", + "dependencies": { + "@webassemblyjs/ast": "1.11.1", + "@webassemblyjs/helper-buffer": "1.11.1", + "@webassemblyjs/helper-wasm-bytecode": "1.11.1", + "@webassemblyjs/helper-wasm-section": "1.11.1", + "@webassemblyjs/wasm-gen": "1.11.1", + "@webassemblyjs/wasm-opt": "1.11.1", + "@webassemblyjs/wasm-parser": "1.11.1", + "@webassemblyjs/wast-printer": "1.11.1" + } + }, + "node_modules/@webassemblyjs/wasm-gen": { + "version": "1.11.1", + "resolved": "https://registry.npmjs.org/@webassemblyjs/wasm-gen/-/wasm-gen-1.11.1.tgz", + "integrity": "sha512-F7QqKXwwNlMmsulj6+O7r4mmtAlCWfO/0HdgOxSklZfQcDu0TpLiD1mRt/zF25Bk59FIjEuGAIyn5ei4yMfLhA==", + "dependencies": { + "@webassemblyjs/ast": "1.11.1", + "@webassemblyjs/helper-wasm-bytecode": "1.11.1", + "@webassemblyjs/ieee754": "1.11.1", + "@webassemblyjs/leb128": "1.11.1", + "@webassemblyjs/utf8": "1.11.1" + } + }, + "node_modules/@webassemblyjs/wasm-opt": { + "version": "1.11.1", + "resolved": "https://registry.npmjs.org/@webassemblyjs/wasm-opt/-/wasm-opt-1.11.1.tgz", + "integrity": "sha512-VqnkNqnZlU5EB64pp1l7hdm3hmQw7Vgqa0KF/KCNO9sIpI6Fk6brDEiX+iCOYrvMuBWDws0NkTOxYEb85XQHHw==", + "dependencies": { + "@webassemblyjs/ast": "1.11.1", + "@webassemblyjs/helper-buffer": "1.11.1", + "@webassemblyjs/wasm-gen": "1.11.1", + "@webassemblyjs/wasm-parser": "1.11.1" + } + }, + "node_modules/@webassemblyjs/wasm-parser": { + "version": "1.11.1", + "resolved": "https://registry.npmjs.org/@webassemblyjs/wasm-parser/-/wasm-parser-1.11.1.tgz", + "integrity": "sha512-rrBujw+dJu32gYB7/Lup6UhdkPx9S9SnobZzRVL7VcBH9Bt9bCBLEuX/YXOOtBsOZ4NQrRykKhffRWHvigQvOA==", + "dependencies": { + "@webassemblyjs/ast": "1.11.1", + "@webassemblyjs/helper-api-error": "1.11.1", + "@webassemblyjs/helper-wasm-bytecode": "1.11.1", + "@webassemblyjs/ieee754": "1.11.1", + "@webassemblyjs/leb128": "1.11.1", + "@webassemblyjs/utf8": "1.11.1" + } + }, + "node_modules/@webassemblyjs/wast-printer": { + "version": "1.11.1", + "resolved": "https://registry.npmjs.org/@webassemblyjs/wast-printer/-/wast-printer-1.11.1.tgz", + "integrity": "sha512-IQboUWM4eKzWW+N/jij2sRatKMh99QEelo3Eb2q0qXkvPRISAj8Qxtmw5itwqK+TTkBuUIE45AxYPToqPtL5gg==", + "dependencies": { + "@webassemblyjs/ast": "1.11.1", + "@xtuc/long": "4.2.2" + } + }, + "node_modules/@webpack-cli/configtest": { + "version": "1.2.0", + "resolved": "https://registry.npmjs.org/@webpack-cli/configtest/-/configtest-1.2.0.tgz", + "integrity": "sha512-4FB8Tj6xyVkyqjj1OaTqCjXYULB9FMkqQ8yGrZjRDrYh0nOE+7Lhs45WioWQQMV+ceFlE368Ukhe6xdvJM9Egg==", + "dev": true, + "peerDependencies": { + "webpack": "4.x.x || 5.x.x", + "webpack-cli": "4.x.x" + } + }, + "node_modules/@webpack-cli/info": { + "version": "1.5.0", + "resolved": "https://registry.npmjs.org/@webpack-cli/info/-/info-1.5.0.tgz", + "integrity": "sha512-e8tSXZpw2hPl2uMJY6fsMswaok5FdlGNRTktvFk2sD8RjH0hE2+XistawJx1vmKteh4NmGmNUrp+Tb2w+udPcQ==", + "dev": true, + "dependencies": { + "envinfo": "^7.7.3" + }, + "peerDependencies": { + "webpack-cli": "4.x.x" + } + }, + "node_modules/@webpack-cli/serve": { + "version": "1.7.0", + "resolved": "https://registry.npmjs.org/@webpack-cli/serve/-/serve-1.7.0.tgz", + "integrity": "sha512-oxnCNGj88fL+xzV+dacXs44HcDwf1ovs3AuEzvP7mqXw7fQntqIhQ1BRmynh4qEKQSSSRSWVyXRjmTbZIX9V2Q==", + "dev": true, + "peerDependencies": { + "webpack-cli": "4.x.x" + }, + "peerDependenciesMeta": { + "webpack-dev-server": { + "optional": true + } + } + }, + "node_modules/@xtuc/ieee754": { + "version": "1.2.0", + "resolved": "https://registry.npmjs.org/@xtuc/ieee754/-/ieee754-1.2.0.tgz", + "integrity": "sha512-DX8nKgqcGwsc0eJSqYt5lwP4DH5FlHnmuWWBRy7X0NcaGR0ZtuyeESgMwTYVEtxmsNGY+qit4QYT/MIYTOTPeA==" + }, + "node_modules/@xtuc/long": { + "version": "4.2.2", + "resolved": "https://registry.npmjs.org/@xtuc/long/-/long-4.2.2.tgz", + "integrity": "sha512-NuHqBY1PB/D8xU6s/thBgOAiAP7HOYDQ32+BFZILJ8ivkUkAHQnWfn6WhL79Owj1qmUnoN/YPhktdIoucipkAQ==" + }, + "node_modules/accepts": { + "version": "1.3.8", + "resolved": "https://registry.npmjs.org/accepts/-/accepts-1.3.8.tgz", + "integrity": "sha512-PYAthTa2m2VKxuvSD3DPC/Gy+U+sOA1LAuT8mkmRuvw+NACSaeXEQ+NHcVF7rONl6qcaxV3Uuemwawk+7+SJLw==", + "dev": true, + "dependencies": { + "mime-types": "~2.1.34", + "negotiator": "0.6.3" + }, + "engines": { + "node": ">= 0.6" + } + }, + "node_modules/acorn": { + "version": "8.7.1", + "resolved": "https://registry.npmjs.org/acorn/-/acorn-8.7.1.tgz", + "integrity": "sha512-Xx54uLJQZ19lKygFXOWsscKUbsBZW0CPykPhVQdhIeIwrbPmJzqeASDInc8nKBnp/JT6igTs82qPXz069H8I/A==", + "bin": { + "acorn": "bin/acorn" + }, + "engines": { + "node": ">=0.4.0" + } + }, + "node_modules/acorn-import-assertions": { + "version": "1.8.0", + "resolved": "https://registry.npmjs.org/acorn-import-assertions/-/acorn-import-assertions-1.8.0.tgz", + "integrity": "sha512-m7VZ3jwz4eK6A4Vtt8Ew1/mNbP24u0FhdyfA7fSvnJR6LMdfOYnmuIrrJAgrYfYJ10F/otaHTtrtrtmHdMNzEw==", + "peerDependencies": { + "acorn": "^8" + } + }, + "node_modules/agent-base": { + "version": "6.0.2", + "resolved": "https://registry.npmjs.org/agent-base/-/agent-base-6.0.2.tgz", + "integrity": "sha512-RZNwNclF7+MS/8bDg70amg32dyeZGZxiDuQmZxKLAlQjr3jGyLx+4Kkk58UO7D2QdgFIQCovuSuZESne6RG6XQ==", + "dependencies": { + "debug": "4" + }, + "engines": { + "node": ">= 6.0.0" + } + }, + "node_modules/agent-base/node_modules/debug": { + "version": "4.3.4", + "resolved": "https://registry.npmjs.org/debug/-/debug-4.3.4.tgz", + "integrity": "sha512-PRWFHuSU3eDtQJPvnNY7Jcket1j0t5OuOsFzPPzsekD52Zl8qUfFIPEiswXqIvHWGVHOgX+7G/vCNNhehwxfkQ==", + "dependencies": { + "ms": "2.1.2" + }, + "engines": { + "node": ">=6.0" + }, + "peerDependenciesMeta": { + "supports-color": { + "optional": true + } + } + }, + "node_modules/agent-base/node_modules/ms": { + "version": "2.1.2", + "resolved": "https://registry.npmjs.org/ms/-/ms-2.1.2.tgz", + "integrity": "sha512-sGkPx+VjMtmA6MX27oA4FBFELFCZZ4S4XqeGOXCv68tT+jb3vk/RyaKWP0PTKyWtmLSM0b+adUTEvbs1PEaH2w==" + }, + "node_modules/aggregate-error": { + "version": "3.1.0", + "resolved": "https://registry.npmjs.org/aggregate-error/-/aggregate-error-3.1.0.tgz", + "integrity": "sha512-4I7Td01quW/RpocfNayFdFVk1qSuoh0E7JrbRJ16nH01HhKFQ88INq9Sd+nd72zqRySlr9BmDA8xlEJ6vJMrYA==", + "dev": true, + "dependencies": { + "clean-stack": "^2.0.0", + "indent-string": "^4.0.0" + }, + "engines": { + "node": ">=8" + } + }, + "node_modules/ajv": { + "version": "6.12.6", + "resolved": "https://registry.npmjs.org/ajv/-/ajv-6.12.6.tgz", + "integrity": "sha512-j3fVLgvTo527anyYyJOGTYJbG+vnnQYvE0m5mmkc1TK+nxAppkCLMIL0aZ4dblVCNoGShhm+kzE4ZUykBoMg4g==", + "dependencies": { + "fast-deep-equal": "^3.1.1", + "fast-json-stable-stringify": "^2.0.0", + "json-schema-traverse": "^0.4.1", + "uri-js": "^4.2.2" + }, + "funding": { + "type": "github", + "url": "https://github.com/sponsors/epoberezkin" + } + }, + "node_modules/ajv-formats": { + "version": "2.1.1", + "resolved": "https://registry.npmjs.org/ajv-formats/-/ajv-formats-2.1.1.tgz", + "integrity": "sha512-Wx0Kx52hxE7C18hkMEggYlEifqWZtYaRgouJor+WMdPnQyEK13vgEWyVNup7SoeeoLMsr4kf5h6dOW11I15MUA==", + "dev": true, + "dependencies": { + "ajv": "^8.0.0" + }, + "peerDependencies": { + "ajv": "^8.0.0" + }, + "peerDependenciesMeta": { + "ajv": { + "optional": true + } + } + }, + "node_modules/ajv-formats/node_modules/ajv": { + "version": "8.11.0", + "resolved": "https://registry.npmjs.org/ajv/-/ajv-8.11.0.tgz", + "integrity": "sha512-wGgprdCvMalC0BztXvitD2hC04YffAvtsUn93JbGXYLAtCUO4xd17mCCZQxUOItiBwZvJScWo8NIvQMQ71rdpg==", + "dev": true, + "dependencies": { + "fast-deep-equal": "^3.1.1", + "json-schema-traverse": "^1.0.0", + "require-from-string": "^2.0.2", + "uri-js": "^4.2.2" + }, + "funding": { + "type": "github", + "url": "https://github.com/sponsors/epoberezkin" + } + }, + "node_modules/ajv-formats/node_modules/json-schema-traverse": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/json-schema-traverse/-/json-schema-traverse-1.0.0.tgz", + "integrity": "sha512-NM8/P9n3XjXhIZn1lLhkFaACTOURQXjWhV4BA/RnOv8xvgqtqpAX9IO4mRQxSx1Rlo4tqzeqb0sOlruaOy3dug==", + "dev": true + }, + "node_modules/ajv-keywords": { + "version": "3.5.2", + "resolved": "https://registry.npmjs.org/ajv-keywords/-/ajv-keywords-3.5.2.tgz", + "integrity": "sha512-5p6WTN0DdTGVQk6VjcEju19IgaHudalcfabD7yhDGeA6bcQnmL+CpveLJq/3hvfwd1aof6L386Ougkx6RfyMIQ==", + "peerDependencies": { + "ajv": "^6.9.1" + } + }, + "node_modules/anchor-markdown-header": { + "version": "0.6.0", + "resolved": "https://registry.npmjs.org/anchor-markdown-header/-/anchor-markdown-header-0.6.0.tgz", + "integrity": "sha512-v7HJMtE1X7wTpNFseRhxsY/pivP4uAJbidVhPT+yhz4i/vV1+qx371IXuV9V7bN6KjFtheLJxqaSm0Y/8neJTA==", + "dependencies": { + "emoji-regex": "~10.1.0" + } + }, + "node_modules/ansi-html-community": { + "version": "0.0.8", + "resolved": "https://registry.npmjs.org/ansi-html-community/-/ansi-html-community-0.0.8.tgz", + "integrity": "sha512-1APHAyr3+PCamwNw3bXCPp4HFLONZt/yIH0sZp0/469KWNTEy+qN5jQ3GVX6DMZ1UXAi34yVwtTeaG/HpBuuzw==", + "dev": true, + "engines": [ + "node >= 0.8.0" + ], + "bin": { + "ansi-html": "bin/ansi-html" + } + }, + "node_modules/ansi-regex": { + "version": "5.0.1", + "resolved": "https://registry.npmjs.org/ansi-regex/-/ansi-regex-5.0.1.tgz", + "integrity": "sha512-quJQXlTSUGL2LH9SUXo8VwsY4soanhgo6LNSm84E1LBcE8s3O0wpdiRzyR9z/ZZJMlMWv37qOOb9pdJlMUEKFQ==", + "dev": true, + "engines": { + "node": ">=8" + } + }, + "node_modules/anymatch": { + "version": "3.1.2", + "resolved": "https://registry.npmjs.org/anymatch/-/anymatch-3.1.2.tgz", + "integrity": "sha512-P43ePfOAIupkguHUycrc4qJ9kz8ZiuOUijaETwX7THt0Y/GNK7v0aa8rY816xWjZ7rJdA5XdMcpVFTKMq+RvWg==", + "dev": true, + "dependencies": { + "normalize-path": "^3.0.0", + "picomatch": "^2.0.4" + }, + "engines": { + "node": ">= 8" + } + }, + "node_modules/array-flatten": { + "version": "2.1.2", + "resolved": "https://registry.npmjs.org/array-flatten/-/array-flatten-2.1.2.tgz", + "integrity": "sha512-hNfzcOV8W4NdualtqBFPyVO+54DSJuZGY9qT4pRroB6S9e3iiido2ISIC5h9R2sPJ8H3FHCIiEnsv1lPXO3KtQ==", + "dev": true + }, + "node_modules/array-union": { + "version": "2.1.0", + "resolved": "https://registry.npmjs.org/array-union/-/array-union-2.1.0.tgz", + "integrity": "sha512-HGyxoOTYUyCM6stUe6EJgnd4EoewAI7zMdfqO+kGjnlZmBDz/cR5pf8r/cR4Wq60sL/p0IkcjUEEPwS3GFrIyw==", + "dev": true, + "engines": { + "node": ">=8" + } + }, + "node_modules/asn1.js": { + "version": "5.4.1", + "resolved": "https://registry.npmjs.org/asn1.js/-/asn1.js-5.4.1.tgz", + "integrity": "sha512-+I//4cYPccV8LdmBLiX8CYvf9Sp3vQsrqu2QNXRcrbiWvcx/UdlFiqUJJzxRQxgsZmvhXhn4cSKeSmoFjVdupA==", + "dependencies": { + "bn.js": "^4.0.0", + "inherits": "^2.0.1", + "minimalistic-assert": "^1.0.0", + "safer-buffer": "^2.1.0" + } + }, + "node_modules/asn1.js/node_modules/bn.js": { + "version": "4.12.0", + "resolved": "https://registry.npmjs.org/bn.js/-/bn.js-4.12.0.tgz", + "integrity": "sha512-c98Bf3tPniI+scsdk237ku1Dc3ujXQTSgyiPUDEOe7tRkhrqridvh8klBv0HCEso1OLOYcHuCv/cS6DNxKH+ZA==" + }, + "node_modules/assert": { + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/assert/-/assert-2.0.0.tgz", + "integrity": "sha512-se5Cd+js9dXJnu6Ag2JFc00t+HmHOen+8Q+L7O9zI0PqQXr20uk2J0XQqMxZEeo5U50o8Nvmmx7dZrl+Ufr35A==", + "dependencies": { + "es6-object-assign": "^1.1.0", + "is-nan": "^1.2.1", + "object-is": "^1.0.1", + "util": "^0.12.0" + } + }, + "node_modules/async": { + "version": "2.6.4", + "resolved": "https://registry.npmjs.org/async/-/async-2.6.4.tgz", + "integrity": "sha512-mzo5dfJYwAn29PeiJ0zvwTo04zj8HDJj0Mn8TD7sno7q12prdbnasKJHhkm2c1LgrhlJ0teaea8860oxi51mGA==", + "dev": true, + "dependencies": { + "lodash": "^4.17.14" + } + }, + "node_modules/available-typed-arrays": { + "version": "1.0.5", + "resolved": "https://registry.npmjs.org/available-typed-arrays/-/available-typed-arrays-1.0.5.tgz", + "integrity": "sha512-DMD0KiN46eipeziST1LPP/STfDU0sufISXmjSgvVsoU2tqxctQeASejWcfNtxYKqETM1UxQ8sp2OrSBWpHY6sw==", + "engines": { + "node": ">= 0.4" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/bail": { + "version": "1.0.5", + "resolved": "https://registry.npmjs.org/bail/-/bail-1.0.5.tgz", + "integrity": "sha512-xFbRxM1tahm08yHBP16MMjVUAvDaBMD38zsM9EMAUN61omwLmKlOpB/Zku5QkjZ8TZ4vn53pj+t518cH0S03RQ==", + "funding": { + "type": "github", + "url": "https://github.com/sponsors/wooorm" + } + }, + "node_modules/balanced-match": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/balanced-match/-/balanced-match-1.0.2.tgz", + "integrity": "sha512-3oSeUO0TMV67hN1AmbXsK4yaqU7tjiHlbxRDZOpH0KW9+CeX4bRAaX0Anxt0tx2MrpRpWwQaPwIlISEJhYU5Pw==" + }, + "node_modules/base64-js": { + "version": "1.5.1", + "resolved": "https://registry.npmjs.org/base64-js/-/base64-js-1.5.1.tgz", + "integrity": "sha512-AKpaYlHn8t4SVbOHCy+b5+KKgvR4vrsD8vbvrbiQJps7fKDTkjkDry6ji0rUJjC0kzbNePLwzxq8iypo41qeWA==", + "funding": [ + { + "type": "github", + "url": "https://github.com/sponsors/feross" + }, + { + "type": "patreon", + "url": "https://www.patreon.com/feross" + }, + { + "type": "consulting", + "url": "https://feross.org/support" + } + ] + }, + "node_modules/batch": { + "version": "0.6.1", + "resolved": "https://registry.npmjs.org/batch/-/batch-0.6.1.tgz", + "integrity": "sha1-3DQxT05nkxgJP8dgJyUl+UvyXBY=", + "dev": true + }, + "node_modules/big-integer": { + "version": "1.6.51", + "resolved": "https://registry.npmjs.org/big-integer/-/big-integer-1.6.51.tgz", + "integrity": "sha512-GPEid2Y9QU1Exl1rpO9B2IPJGHPSupF5GnVIP0blYvNOMer2bTvSWs1jGOUg04hTmu67nmLsQ9TBo1puaotBHg==", + "engines": { + "node": ">=0.6" + } + }, + "node_modules/binary-extensions": { + "version": "2.2.0", + "resolved": "https://registry.npmjs.org/binary-extensions/-/binary-extensions-2.2.0.tgz", + "integrity": "sha512-jDctJ/IVQbZoJykoeHbhXpOlNBqGNcwXJKJog42E5HDPUwQTSdjCHdihjj0DlnheQ7blbT6dHOafNAiS8ooQKA==", + "dev": true, + "engines": { + "node": ">=8" + } + }, + "node_modules/bl": { + "version": "4.1.0", + "resolved": "https://registry.npmjs.org/bl/-/bl-4.1.0.tgz", + "integrity": "sha512-1W07cM9gS6DcLperZfFSj+bWLtaPGSOHWhPiGzXmvVJbRLdG82sH/Kn8EtW1VqWVA54AKf2h5k5BbnIbwF3h6w==", + "dependencies": { + "buffer": "^5.5.0", + "inherits": "^2.0.4", + "readable-stream": "^3.4.0" + } + }, + "node_modules/bl/node_modules/buffer": { + "version": "5.7.1", + "resolved": "https://registry.npmjs.org/buffer/-/buffer-5.7.1.tgz", + "integrity": "sha512-EHcyIPBQ4BSGlvjB16k5KgAJ27CIsHY/2JBmCRReo48y9rQ3MaUzWX3KVlBa4U7MyX02HdVj0K7C3WaB3ju7FQ==", + "funding": [ + { + "type": "github", + "url": "https://github.com/sponsors/feross" + }, + { + "type": "patreon", + "url": "https://www.patreon.com/feross" + }, + { + "type": "consulting", + "url": "https://feross.org/support" + } + ], + "dependencies": { + "base64-js": "^1.3.1", + "ieee754": "^1.1.13" + } + }, + "node_modules/blakejs": { + "version": "1.2.1", + "resolved": "https://registry.npmjs.org/blakejs/-/blakejs-1.2.1.tgz", + "integrity": "sha512-QXUSXI3QVc/gJME0dBpXrag1kbzOqCjCX8/b54ntNyW6sjtoqxqRk3LTmXzaJoh71zMsDCjM+47jS7XiwN/+fQ==" + }, + "node_modules/bn.js": { + "version": "5.2.1", + "resolved": "https://registry.npmjs.org/bn.js/-/bn.js-5.2.1.tgz", + "integrity": "sha512-eXRvHzWyYPBuB4NBy0cmYQjGitUrtqwbvlzP3G6VFnNRbsZQIxQ10PbKKHt8gZ/HW/D/747aDl+QkDqg3KQLMQ==" + }, + "node_modules/body-parser": { + "version": "1.20.0", + "resolved": "https://registry.npmjs.org/body-parser/-/body-parser-1.20.0.tgz", + "integrity": "sha512-DfJ+q6EPcGKZD1QWUjSpqp+Q7bDQTsQIF4zfUAtZ6qk+H/3/QRhg9CEp39ss+/T2vw0+HaidC0ecJj/DRLIaKg==", + "dev": true, + "dependencies": { + "bytes": "3.1.2", + "content-type": "~1.0.4", + "debug": "2.6.9", + "depd": "2.0.0", + "destroy": "1.2.0", + "http-errors": "2.0.0", + "iconv-lite": "0.4.24", + "on-finished": "2.4.1", + "qs": "6.10.3", + "raw-body": "2.5.1", + "type-is": "~1.6.18", + "unpipe": "1.0.0" + }, + "engines": { + "node": ">= 0.8", + "npm": "1.2.8000 || >= 1.4.16" + } + }, + "node_modules/body-parser/node_modules/bytes": { + "version": "3.1.2", + "resolved": "https://registry.npmjs.org/bytes/-/bytes-3.1.2.tgz", + "integrity": "sha512-/Nf7TyzTx6S3yRJObOAV7956r8cr2+Oj8AC5dt8wSP3BQAoeX58NoHyCU8P8zGkNXStjTSi6fzO6F0pBdcYbEg==", + "dev": true, + "engines": { + "node": ">= 0.8" + } + }, + "node_modules/bonjour": { + "version": "3.5.0", + "resolved": "https://registry.npmjs.org/bonjour/-/bonjour-3.5.0.tgz", + "integrity": "sha1-jokKGD2O6aI5OzhExpGkK897yfU=", + "dev": true, + "dependencies": { + "array-flatten": "^2.1.0", + "deep-equal": "^1.0.1", + "dns-equal": "^1.0.0", + "dns-txt": "^2.0.2", + "multicast-dns": "^6.0.1", + "multicast-dns-service-types": "^1.1.0" + } + }, + "node_modules/boolbase": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/boolbase/-/boolbase-1.0.0.tgz", + "integrity": "sha1-aN/1++YMUes3cl6p4+0xDcwed24=", + "dev": true + }, + "node_modules/brace-expansion": { + "version": "1.1.11", + "resolved": "https://registry.npmjs.org/brace-expansion/-/brace-expansion-1.1.11.tgz", + "integrity": "sha512-iCuPHDFgrHX7H2vEI/5xpz07zSHB00TpugqhmYtVmMO6518mCuRMoOYFldEBl0g187ufozdaHgWKcYFb61qGiA==", + "dependencies": { + "balanced-match": "^1.0.0", + "concat-map": "0.0.1" + } + }, + "node_modules/braces": { + "version": "3.0.2", + "resolved": "https://registry.npmjs.org/braces/-/braces-3.0.2.tgz", + "integrity": "sha512-b8um+L1RzM3WDSzvhm6gIz1yfTbBt6YTlcEKAvsmqCZZFw46z626lVj9j1yEPW33H5H+lBQpZMP1k8l+78Ha0A==", + "dev": true, + "dependencies": { + "fill-range": "^7.0.1" + }, + "engines": { + "node": ">=8" + } + }, + "node_modules/brorand": { + "version": "1.1.0", + "resolved": "https://registry.npmjs.org/brorand/-/brorand-1.1.0.tgz", + "integrity": "sha1-EsJe/kCkXjwyPrhnWgoM5XsiNx8=" + }, + "node_modules/browserify-aes": { + "version": "1.2.0", + "resolved": "https://registry.npmjs.org/browserify-aes/-/browserify-aes-1.2.0.tgz", + "integrity": "sha512-+7CHXqGuspUn/Sl5aO7Ea0xWGAtETPXNSAjHo48JfLdPWcMng33Xe4znFvQweqc/uzk5zSOI3H52CYnjCfb5hA==", + "dependencies": { + "buffer-xor": "^1.0.3", + "cipher-base": "^1.0.0", + "create-hash": "^1.1.0", + "evp_bytestokey": "^1.0.3", + "inherits": "^2.0.1", + "safe-buffer": "^5.0.1" + } + }, + "node_modules/browserify-cipher": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/browserify-cipher/-/browserify-cipher-1.0.1.tgz", + "integrity": "sha512-sPhkz0ARKbf4rRQt2hTpAHqn47X3llLkUGn+xEJzLjwY8LRs2p0v7ljvI5EyoRO/mexrNunNECisZs+gw2zz1w==", + "dependencies": { + "browserify-aes": "^1.0.4", + "browserify-des": "^1.0.0", + "evp_bytestokey": "^1.0.0" + } + }, + "node_modules/browserify-des": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/browserify-des/-/browserify-des-1.0.2.tgz", + "integrity": "sha512-BioO1xf3hFwz4kc6iBhI3ieDFompMhrMlnDFC4/0/vd5MokpuAc3R+LYbwTA9A5Yc9pq9UYPqffKpW2ObuwX5A==", + "dependencies": { + "cipher-base": "^1.0.1", + "des.js": "^1.0.0", + "inherits": "^2.0.1", + "safe-buffer": "^5.1.2" + } + }, + "node_modules/browserify-rsa": { + "version": "4.1.0", + "resolved": "https://registry.npmjs.org/browserify-rsa/-/browserify-rsa-4.1.0.tgz", + "integrity": "sha512-AdEER0Hkspgno2aR97SAf6vi0y0k8NuOpGnVH3O99rcA5Q6sh8QxcngtHuJ6uXwnfAXNM4Gn1Gb7/MV1+Ymbog==", + "dependencies": { + "bn.js": "^5.0.0", + "randombytes": "^2.0.1" + } + }, + "node_modules/browserify-sign": { + "version": "4.2.1", + "resolved": "https://registry.npmjs.org/browserify-sign/-/browserify-sign-4.2.1.tgz", + "integrity": "sha512-/vrA5fguVAKKAVTNJjgSm1tRQDHUU6DbwO9IROu/0WAzC8PKhucDSh18J0RMvVeHAn5puMd+QHC2erPRNf8lmg==", + "dependencies": { + "bn.js": "^5.1.1", + "browserify-rsa": "^4.0.1", + "create-hash": "^1.2.0", + "create-hmac": "^1.1.7", + "elliptic": "^6.5.3", + "inherits": "^2.0.4", + "parse-asn1": "^5.1.5", + "readable-stream": "^3.6.0", + "safe-buffer": "^5.2.0" + } + }, + "node_modules/browserify-zlib": { + "version": "0.2.0", + "resolved": "https://registry.npmjs.org/browserify-zlib/-/browserify-zlib-0.2.0.tgz", + "integrity": "sha512-Z942RysHXmJrhqk88FmKBVq/v5tqmSkDz7p54G/MGyjMnCFFnC79XWNbg+Vta8W6Wb2qtSZTSxIGkJrRpCFEiA==", + "dependencies": { + "pako": "~1.0.5" + } + }, + "node_modules/browserslist": { + "version": "4.21.0", + "resolved": "https://registry.npmjs.org/browserslist/-/browserslist-4.21.0.tgz", + "integrity": "sha512-UQxE0DIhRB5z/zDz9iA03BOfxaN2+GQdBYH/2WrSIWEUrnpzTPJbhqt+umq6r3acaPRTW1FNTkrcp0PXgtFkvA==", + "funding": [ + { + "type": "opencollective", + "url": "https://opencollective.com/browserslist" + }, + { + "type": "tidelift", + "url": "https://tidelift.com/funding/github/npm/browserslist" + } + ], + "dependencies": { + "caniuse-lite": "^1.0.30001358", + "electron-to-chromium": "^1.4.164", + "node-releases": "^2.0.5", + "update-browserslist-db": "^1.0.0" + }, + "bin": { + "browserslist": "cli.js" + }, + "engines": { + "node": "^6 || ^7 || ^8 || ^9 || ^10 || ^11 || ^12 || >=13.7" + } + }, + "node_modules/buffer": { + "version": "6.0.3", + "resolved": "https://registry.npmjs.org/buffer/-/buffer-6.0.3.tgz", + "integrity": "sha512-FTiCpNxtwiZZHEZbcbTIcZjERVICn9yq/pDFkTl95/AxzD1naBctN7YO68riM/gLSDY7sdrMby8hofADYuuqOA==", + "funding": [ + { + "type": "github", + "url": "https://github.com/sponsors/feross" + }, + { + "type": "patreon", + "url": "https://www.patreon.com/feross" + }, + { + "type": "consulting", + "url": "https://feross.org/support" + } + ], + "dependencies": { + "base64-js": "^1.3.1", + "ieee754": "^1.2.1" + } + }, + "node_modules/buffer-crc32": { + "version": "0.2.13", + "resolved": "https://registry.npmjs.org/buffer-crc32/-/buffer-crc32-0.2.13.tgz", + "integrity": "sha512-VO9Ht/+p3SN7SKWqcrgEzjGbRSJYTx+Q1pTQC0wrWqHx0vpJraQ6GtHx8tvcg1rlK1byhU5gccxgOgj7B0TDkQ==", + "engines": { + "node": "*" + } + }, + "node_modules/buffer-from": { + "version": "1.1.2", + "resolved": "https://registry.npmjs.org/buffer-from/-/buffer-from-1.1.2.tgz", + "integrity": "sha512-E+XQCRwSbaaiChtv6k6Dwgc+bx+Bs6vuKJHHl5kox/BaKbhiXzqQOwK4cO22yElGp2OCmjwVhT3HmxgyPGnJfQ==" + }, + "node_modules/buffer-indexof": { + "version": "1.1.1", + "resolved": "https://registry.npmjs.org/buffer-indexof/-/buffer-indexof-1.1.1.tgz", + "integrity": "sha512-4/rOEg86jivtPTeOUUT61jJO1Ya1TrR/OkqCSZDyq84WJh3LuuiphBYJN+fm5xufIk4XAFcEwte/8WzC8If/1g==", + "dev": true + }, + "node_modules/buffer-xor": { + "version": "1.0.3", + "resolved": "https://registry.npmjs.org/buffer-xor/-/buffer-xor-1.0.3.tgz", + "integrity": "sha1-JuYe0UIvtw3ULm42cp7VHYVf6Nk=" + }, + "node_modules/bufferutil": { + "version": "4.0.5", + "resolved": "https://registry.npmjs.org/bufferutil/-/bufferutil-4.0.5.tgz", + "integrity": "sha512-HTm14iMQKK2FjFLRTM5lAVcyaUzOnqbPtesFIvREgXpJHdQm8bWS+GkQgIkfaBYRHuCnea7w8UVNfwiAQhlr9A==", + "hasInstallScript": true, + "dependencies": { + "node-gyp-build": "^4.3.0" + }, + "engines": { + "node": ">=6.14.2" + } + }, + "node_modules/builtin-status-codes": { + "version": "3.0.0", + "resolved": "https://registry.npmjs.org/builtin-status-codes/-/builtin-status-codes-3.0.0.tgz", + "integrity": "sha1-hZgoeOIbmOHGZCXgPQF0eI9Wnug=" + }, + "node_modules/bytes": { + "version": "3.0.0", + "resolved": "https://registry.npmjs.org/bytes/-/bytes-3.0.0.tgz", + "integrity": "sha1-0ygVQE1olpn4Wk6k+odV3ROpYEg=", + "dev": true, + "engines": { + "node": ">= 0.8" + } + }, + "node_modules/call-bind": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/call-bind/-/call-bind-1.0.2.tgz", + "integrity": "sha512-7O+FbCihrB5WGbFYesctwmTKae6rOiIzmz1icreWJ+0aA7LJfuqhEso2T9ncpcFtzMQtzXf2QGGueWJGTYsqrA==", + "dependencies": { + "function-bind": "^1.1.1", + "get-intrinsic": "^1.0.2" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/camel-case": { + "version": "4.1.2", + "resolved": "https://registry.npmjs.org/camel-case/-/camel-case-4.1.2.tgz", + "integrity": "sha512-gxGWBrTT1JuMx6R+o5PTXMmUnhnVzLQ9SNutD4YqKtI6ap897t3tKECYla6gCWEkplXnlNybEkZg9GEGxKFCgw==", + "dev": true, + "dependencies": { + "pascal-case": "^3.1.2", + "tslib": "^2.0.3" + } + }, + "node_modules/caniuse-lite": { + "version": "1.0.30001358", + "resolved": "https://registry.npmjs.org/caniuse-lite/-/caniuse-lite-1.0.30001358.tgz", + "integrity": "sha512-hvp8PSRymk85R20bsDra7ZTCpSVGN/PAz9pSAjPSjKC+rNmnUk5vCRgJwiTT/O4feQ/yu/drvZYpKxxhbFuChw==", + "funding": [ + { + "type": "opencollective", + "url": "https://opencollective.com/browserslist" + }, + { + "type": "tidelift", + "url": "https://tidelift.com/funding/github/npm/caniuse-lite" + } + ] + }, + "node_modules/ccount": { + "version": "1.1.0", + "resolved": "https://registry.npmjs.org/ccount/-/ccount-1.1.0.tgz", + "integrity": "sha512-vlNK021QdI7PNeiUh/lKkC/mNHHfV0m/Ad5JoI0TYtlBnJAslM/JIkm/tGC88bkLIwO6OQ5uV6ztS6kVAtCDlg==", + "funding": { + "type": "github", + "url": "https://github.com/sponsors/wooorm" + } + }, + "node_modules/character-entities": { + "version": "1.2.4", + "resolved": "https://registry.npmjs.org/character-entities/-/character-entities-1.2.4.tgz", + "integrity": "sha512-iBMyeEHxfVnIakwOuDXpVkc54HijNgCyQB2w0VfGQThle6NXn50zU6V/u+LDhxHcDUPojn6Kpga3PTAD8W1bQw==", + "funding": { + "type": "github", + "url": "https://github.com/sponsors/wooorm" + } + }, + "node_modules/character-entities-legacy": { + "version": "1.1.4", + "resolved": "https://registry.npmjs.org/character-entities-legacy/-/character-entities-legacy-1.1.4.tgz", + "integrity": "sha512-3Xnr+7ZFS1uxeiUDvV02wQ+QDbc55o97tIV5zHScSPJpcLm/r0DFPcoY3tYRp+VZukxuMeKgXYmsXQHO05zQeA==", + "funding": { + "type": "github", + "url": "https://github.com/sponsors/wooorm" + } + }, + "node_modules/character-reference-invalid": { + "version": "1.1.4", + "resolved": "https://registry.npmjs.org/character-reference-invalid/-/character-reference-invalid-1.1.4.tgz", + "integrity": "sha512-mKKUkUbhPpQlCOfIuZkvSEgktjPFIsZKRRbC6KWVEMvlzblj3i3asQv5ODsrwt0N3pHAEvjP8KTQPHkp0+6jOg==", + "funding": { + "type": "github", + "url": "https://github.com/sponsors/wooorm" + } + }, + "node_modules/chokidar": { + "version": "3.5.3", + "resolved": "https://registry.npmjs.org/chokidar/-/chokidar-3.5.3.tgz", + "integrity": "sha512-Dr3sfKRP6oTcjf2JmUmFJfeVMvXBdegxB0iVQ5eb2V10uFJUCAS8OByZdVAyVb8xXNz3GjjTgj9kLWsZTqE6kw==", + "dev": true, + "funding": [ + { + "type": "individual", + "url": "https://paulmillr.com/funding/" + } + ], + "dependencies": { + "anymatch": "~3.1.2", + "braces": "~3.0.2", + "glob-parent": "~5.1.2", + "is-binary-path": "~2.1.0", + "is-glob": "~4.0.1", + "normalize-path": "~3.0.0", + "readdirp": "~3.6.0" + }, + "engines": { + "node": ">= 8.10.0" + }, + "optionalDependencies": { + "fsevents": "~2.3.2" + } + }, + "node_modules/chownr": { + "version": "1.1.4", + "resolved": "https://registry.npmjs.org/chownr/-/chownr-1.1.4.tgz", + "integrity": "sha512-jJ0bqzaylmJtVnNgzTeSOs8DPavpbYgEr/b0YL8/2GO3xJEhInFmhKMUnEJQjZumK7KXGFhUy89PrsJWlakBVg==" + }, + "node_modules/chrome-trace-event": { + "version": "1.0.3", + "resolved": "https://registry.npmjs.org/chrome-trace-event/-/chrome-trace-event-1.0.3.tgz", + "integrity": "sha512-p3KULyQg4S7NIHixdwbGX+nFHkoBiA4YQmyWtjb8XngSKV124nJmRysgAeujbUVb15vh+RvFUfCPqU7rXk+hZg==", + "engines": { + "node": ">=6.0" + } + }, + "node_modules/cipher-base": { + "version": "1.0.4", + "resolved": "https://registry.npmjs.org/cipher-base/-/cipher-base-1.0.4.tgz", + "integrity": "sha512-Kkht5ye6ZGmwv40uUDZztayT2ThLQGfnj/T71N/XzeZeo3nf8foyW7zGTsPYkEya3m5f3cAypH+qe7YOrM1U2Q==", + "dependencies": { + "inherits": "^2.0.1", + "safe-buffer": "^5.0.1" + } + }, + "node_modules/clean-css": { + "version": "5.3.0", + "resolved": "https://registry.npmjs.org/clean-css/-/clean-css-5.3.0.tgz", + "integrity": "sha512-YYuuxv4H/iNb1Z/5IbMRoxgrzjWGhOEFfd+groZ5dMCVkpENiMZmwspdrzBo9286JjM1gZJPAyL7ZIdzuvu2AQ==", + "dev": true, + "dependencies": { + "source-map": "~0.6.0" + }, + "engines": { + "node": ">= 10.0" + } + }, + "node_modules/clean-stack": { + "version": "2.2.0", + "resolved": "https://registry.npmjs.org/clean-stack/-/clean-stack-2.2.0.tgz", + "integrity": "sha512-4diC9HaTE+KRAMWhDhrGOECgWZxoevMc5TlkObMqNSsVU62PYzXZ/SMTjzyGAFF1YusgxGcSWTEXBhp0CPwQ1A==", + "dev": true, + "engines": { + "node": ">=6" + } + }, + "node_modules/clone-deep": { + "version": "4.0.1", + "resolved": "https://registry.npmjs.org/clone-deep/-/clone-deep-4.0.1.tgz", + "integrity": "sha512-neHB9xuzh/wk0dIHweyAXv2aPGZIVk3pLMe+/RNzINf17fe0OG96QroktYAUm7SM1PBnzTabaLboqqxDyMU+SQ==", + "dev": true, + "dependencies": { + "is-plain-object": "^2.0.4", + "kind-of": "^6.0.2", + "shallow-clone": "^3.0.0" + }, + "engines": { + "node": ">=6" + } + }, + "node_modules/colorette": { + "version": "2.0.19", + "resolved": "https://registry.npmjs.org/colorette/-/colorette-2.0.19.tgz", + "integrity": "sha512-3tlv/dIP7FWvj3BsbHrGLJ6l/oKh1O3TcgBqMn+yyCagOxc23fyzDS6HypQbgxWbkpDnf52p1LuR4eWDQ/K9WQ==", + "dev": true + }, + "node_modules/commander": { + "version": "8.3.0", + "resolved": "https://registry.npmjs.org/commander/-/commander-8.3.0.tgz", + "integrity": "sha512-OkTL9umf+He2DZkUq8f8J9of7yL6RJKI24dVITBmNfZBmri9zYZQrKkuXiKhyfPSu8tUhnVBB1iKXevvnlR4Ww==", + "dev": true, + "engines": { + "node": ">= 12" + } + }, + "node_modules/compressible": { + "version": "2.0.18", + "resolved": "https://registry.npmjs.org/compressible/-/compressible-2.0.18.tgz", + "integrity": "sha512-AF3r7P5dWxL8MxyITRMlORQNaOA2IkAFaTr4k7BUumjPtRpGDTZpl0Pb1XCO6JeDCBdp126Cgs9sMxqSjgYyRg==", + "dev": true, + "dependencies": { + "mime-db": ">= 1.43.0 < 2" + }, + "engines": { + "node": ">= 0.6" + } + }, + "node_modules/compression": { + "version": "1.7.4", + "resolved": "https://registry.npmjs.org/compression/-/compression-1.7.4.tgz", + "integrity": "sha512-jaSIDzP9pZVS4ZfQ+TzvtiWhdpFhE2RDHz8QJkpX9SIpLq88VueF5jJw6t+6CUQcAoA6t+x89MLrWAqpfDE8iQ==", + "dev": true, + "dependencies": { + "accepts": "~1.3.5", + "bytes": "3.0.0", + "compressible": "~2.0.16", + "debug": "2.6.9", + "on-headers": "~1.0.2", + "safe-buffer": "5.1.2", + "vary": "~1.1.2" + }, + "engines": { + "node": ">= 0.8.0" + } + }, + "node_modules/compression/node_modules/safe-buffer": { + "version": "5.1.2", + "resolved": "https://registry.npmjs.org/safe-buffer/-/safe-buffer-5.1.2.tgz", + "integrity": "sha512-Gd2UZBJDkXlY7GbJxfsE8/nvKkUEU1G38c1siN6QP6a9PT9MmHB8GnpscSmMJSoF8LOIrt8ud/wPtojys4G6+g==", + "dev": true + }, + "node_modules/concat-map": { + "version": "0.0.1", + "resolved": "https://registry.npmjs.org/concat-map/-/concat-map-0.0.1.tgz", + "integrity": "sha512-/Srv4dswyQNBfohGpz9o6Yb3Gz3SrUDqBH5rTuhGR7ahtlbYKnVxw2bCFMRljaA7EXHaXZ8wsHdodFvbkhKmqg==" + }, + "node_modules/connect-history-api-fallback": { + "version": "1.6.0", + "resolved": "https://registry.npmjs.org/connect-history-api-fallback/-/connect-history-api-fallback-1.6.0.tgz", + "integrity": "sha512-e54B99q/OUoH64zYYRf3HBP5z24G38h5D3qXu23JGRoigpX5Ss4r9ZnDk3g0Z8uQC2x2lPaJ+UlWBc1ZWBWdLg==", + "dev": true, + "engines": { + "node": ">=0.8" + } + }, + "node_modules/console-browserify": { + "version": "1.2.0", + "resolved": "https://registry.npmjs.org/console-browserify/-/console-browserify-1.2.0.tgz", + "integrity": "sha512-ZMkYO/LkF17QvCPqM0gxw8yUzigAOZOSWSHg91FH6orS7vcEj5dVZTidN2fQ14yBSdg97RqhSNwLUXInd52OTA==" + }, + "node_modules/constants-browserify": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/constants-browserify/-/constants-browserify-1.0.0.tgz", + "integrity": "sha1-wguW2MYXdIqvHBYCF2DNJ/y4y3U=" + }, + "node_modules/content-disposition": { + "version": "0.5.4", + "resolved": "https://registry.npmjs.org/content-disposition/-/content-disposition-0.5.4.tgz", + "integrity": "sha512-FveZTNuGw04cxlAiWbzi6zTAL/lhehaWbTtgluJh4/E95DqMwTmha3KZN1aAWA8cFIhHzMZUvLevkw5Rqk+tSQ==", + "dev": true, + "dependencies": { + "safe-buffer": "5.2.1" + }, + "engines": { + "node": ">= 0.6" + } + }, + "node_modules/content-type": { + "version": "1.0.4", + "resolved": "https://registry.npmjs.org/content-type/-/content-type-1.0.4.tgz", + "integrity": "sha512-hIP3EEPs8tB9AT1L+NUqtwOAps4mk2Zob89MWXMHjHWg9milF/j4osnnQLXBCBFBk/tvIG/tUc9mOUJiPBhPXA==", + "dev": true, + "engines": { + "node": ">= 0.6" + } + }, + "node_modules/cookie": { + "version": "0.5.0", + "resolved": "https://registry.npmjs.org/cookie/-/cookie-0.5.0.tgz", + "integrity": "sha512-YZ3GUyn/o8gfKJlnlX7g7xq4gyO6OSuhGPKaaGssGB2qgDUS0gPgtTvoyZLTt9Ab6dC4hfc9dV5arkvc/OCmrw==", + "dev": true, + "engines": { + "node": ">= 0.6" + } + }, + "node_modules/cookie-signature": { + "version": "1.0.6", + "resolved": "https://registry.npmjs.org/cookie-signature/-/cookie-signature-1.0.6.tgz", + "integrity": "sha1-4wOogrNCzD7oylE6eZmXNNqzriw=", + "dev": true + }, + "node_modules/core-util-is": { + "version": "1.0.3", + "resolved": "https://registry.npmjs.org/core-util-is/-/core-util-is-1.0.3.tgz", + "integrity": "sha512-ZQBvi1DcpJ4GDqanjucZ2Hj3wEO5pZDS89BWbkcrvdxksJorwUDDZamX9ldFkp9aw2lmBDLgkObEA4DWNJ9FYQ==", + "dev": true + }, + "node_modules/create-ecdh": { + "version": "4.0.4", + "resolved": "https://registry.npmjs.org/create-ecdh/-/create-ecdh-4.0.4.tgz", + "integrity": "sha512-mf+TCx8wWc9VpuxfP2ht0iSISLZnt0JgWlrOKZiNqyUZWnjIaCIVNQArMHnCZKfEYRg6IM7A+NeJoN8gf/Ws0A==", + "dependencies": { + "bn.js": "^4.1.0", + "elliptic": "^6.5.3" + } + }, + "node_modules/create-ecdh/node_modules/bn.js": { + "version": "4.12.0", + "resolved": "https://registry.npmjs.org/bn.js/-/bn.js-4.12.0.tgz", + "integrity": "sha512-c98Bf3tPniI+scsdk237ku1Dc3ujXQTSgyiPUDEOe7tRkhrqridvh8klBv0HCEso1OLOYcHuCv/cS6DNxKH+ZA==" + }, + "node_modules/create-hash": { + "version": "1.2.0", + "resolved": "https://registry.npmjs.org/create-hash/-/create-hash-1.2.0.tgz", + "integrity": "sha512-z00bCGNHDG8mHAkP7CtT1qVu+bFQUPjYq/4Iv3C3kWjTFV10zIjfSoeqXo9Asws8gwSHDGj/hl2u4OGIjapeCg==", + "dependencies": { + "cipher-base": "^1.0.1", + "inherits": "^2.0.1", + "md5.js": "^1.3.4", + "ripemd160": "^2.0.1", + "sha.js": "^2.4.0" + } + }, + "node_modules/create-hmac": { + "version": "1.1.7", + "resolved": "https://registry.npmjs.org/create-hmac/-/create-hmac-1.1.7.tgz", + "integrity": "sha512-MJG9liiZ+ogc4TzUwuvbER1JRdgvUFSB5+VR/g5h82fGaIRWMWddtKBHi7/sVhfjQZ6SehlyhvQYrcYkaUIpLg==", + "dependencies": { + "cipher-base": "^1.0.3", + "create-hash": "^1.1.0", + "inherits": "^2.0.1", + "ripemd160": "^2.0.0", + "safe-buffer": "^5.0.1", + "sha.js": "^2.4.8" + } + }, + "node_modules/cross-fetch": { + "version": "3.1.5", + "resolved": "https://registry.npmjs.org/cross-fetch/-/cross-fetch-3.1.5.tgz", + "integrity": "sha512-lvb1SBsI0Z7GDwmuid+mU3kWVBwTVUbe7S0H52yaaAdQOXq2YktTCZdlAcNKFzE6QtRz0snpw9bNiPeOIkkQvw==", + "dependencies": { + "node-fetch": "2.6.7" + } + }, + "node_modules/cross-spawn": { + "version": "7.0.3", + "resolved": "https://registry.npmjs.org/cross-spawn/-/cross-spawn-7.0.3.tgz", + "integrity": "sha512-iRDPJKUPVEND7dHPO8rkbOnPpyDygcDFtWjpeWNCgy8WP2rXcxXL8TskReQl6OrB2G7+UJrags1q15Fudc7G6w==", + "dev": true, + "dependencies": { + "path-key": "^3.1.0", + "shebang-command": "^2.0.0", + "which": "^2.0.1" + }, + "engines": { + "node": ">= 8" + } + }, + "node_modules/crypto-browserify": { + "version": "3.12.0", + "resolved": "https://registry.npmjs.org/crypto-browserify/-/crypto-browserify-3.12.0.tgz", + "integrity": "sha512-fz4spIh+znjO2VjL+IdhEpRJ3YN6sMzITSBijk6FK2UvTqruSQW+/cCZTSNsMiZNvUeq0CqurF+dAbyiGOY6Wg==", + "dependencies": { + "browserify-cipher": "^1.0.0", + "browserify-sign": "^4.0.0", + "create-ecdh": "^4.0.0", + "create-hash": "^1.1.0", + "create-hmac": "^1.1.0", + "diffie-hellman": "^5.0.0", + "inherits": "^2.0.1", + "pbkdf2": "^3.0.3", + "public-encrypt": "^4.0.0", + "randombytes": "^2.0.0", + "randomfill": "^1.0.3" + }, + "engines": { + "node": "*" + } + }, + "node_modules/css-select": { + "version": "4.3.0", + "resolved": "https://registry.npmjs.org/css-select/-/css-select-4.3.0.tgz", + "integrity": "sha512-wPpOYtnsVontu2mODhA19JrqWxNsfdatRKd64kmpRbQgh1KtItko5sTnEpPdpSaJszTOhEMlF/RPz28qj4HqhQ==", + "dev": true, + "dependencies": { + "boolbase": "^1.0.0", + "css-what": "^6.0.1", + "domhandler": "^4.3.1", + "domutils": "^2.8.0", + "nth-check": "^2.0.1" + }, + "funding": { + "url": "https://github.com/sponsors/fb55" + } + }, + "node_modules/css-what": { + "version": "6.1.0", + "resolved": "https://registry.npmjs.org/css-what/-/css-what-6.1.0.tgz", + "integrity": "sha512-HTUrgRJ7r4dsZKU6GjmpfRK1O76h97Z8MfS1G0FozR+oF2kG6Vfe8JE6zwrkbxigziPHinCJ+gCPjA9EaBDtRw==", + "dev": true, + "engines": { + "node": ">= 6" + }, + "funding": { + "url": "https://github.com/sponsors/fb55" + } + }, + "node_modules/debug": { + "version": "2.6.9", + "resolved": "https://registry.npmjs.org/debug/-/debug-2.6.9.tgz", + "integrity": "sha512-bC7ElrdJaJnPbAP+1EotYvqZsb3ecl5wi6Bfi6BJTUcNowp6cvspg0jXznRTKDjm/E7AdgFBVeAPVMNcKGsHMA==", + "dev": true, + "dependencies": { + "ms": "2.0.0" + } + }, + "node_modules/deep-equal": { + "version": "1.1.1", + "resolved": "https://registry.npmjs.org/deep-equal/-/deep-equal-1.1.1.tgz", + "integrity": "sha512-yd9c5AdiqVcR+JjcwUQb9DkhJc8ngNr0MahEBGvDiJw8puWab2yZlh+nkasOnZP+EGTAP6rRp2JzJhJZzvNF8g==", + "dev": true, + "dependencies": { + "is-arguments": "^1.0.4", + "is-date-object": "^1.0.1", + "is-regex": "^1.0.4", + "object-is": "^1.0.1", + "object-keys": "^1.1.1", + "regexp.prototype.flags": "^1.2.0" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/default-gateway": { + "version": "6.0.3", + "resolved": "https://registry.npmjs.org/default-gateway/-/default-gateway-6.0.3.tgz", + "integrity": "sha512-fwSOJsbbNzZ/CUFpqFBqYfYNLj1NbMPm8MMCIzHjC83iSJRBEGmDUxU+WP661BaBQImeC2yHwXtz+P/O9o+XEg==", + "dev": true, + "dependencies": { + "execa": "^5.0.0" + }, + "engines": { + "node": ">= 10" + } + }, + "node_modules/define-lazy-prop": { + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/define-lazy-prop/-/define-lazy-prop-2.0.0.tgz", + "integrity": "sha512-Ds09qNh8yw3khSjiJjiUInaGX9xlqZDY7JVryGxdxV7NPeuqQfplOpQ66yJFZut3jLa5zOwkXw1g9EI2uKh4Og==", + "dev": true, + "engines": { + "node": ">=8" + } + }, + "node_modules/define-properties": { + "version": "1.1.4", + "resolved": "https://registry.npmjs.org/define-properties/-/define-properties-1.1.4.tgz", + "integrity": "sha512-uckOqKcfaVvtBdsVkdPv3XjveQJsNQqmhXgRi8uhvWWuPYZCNlzT8qAyblUgNoXdHdjMTzAqeGjAoli8f+bzPA==", + "dependencies": { + "has-property-descriptors": "^1.0.0", + "object-keys": "^1.1.1" + }, + "engines": { + "node": ">= 0.4" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/del": { + "version": "6.1.1", + "resolved": "https://registry.npmjs.org/del/-/del-6.1.1.tgz", + "integrity": "sha512-ua8BhapfP0JUJKC/zV9yHHDW/rDoDxP4Zhn3AkA6/xT6gY7jYXJiaeyBZznYVujhZZET+UgcbZiQ7sN3WqcImg==", + "dev": true, + "dependencies": { + "globby": "^11.0.1", + "graceful-fs": "^4.2.4", + "is-glob": "^4.0.1", + "is-path-cwd": "^2.2.0", + "is-path-inside": "^3.0.2", + "p-map": "^4.0.0", + "rimraf": "^3.0.2", + "slash": "^3.0.0" + }, + "engines": { + "node": ">=10" + }, + "funding": { + "url": "https://github.com/sponsors/sindresorhus" + } + }, + "node_modules/depd": { + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/depd/-/depd-2.0.0.tgz", + "integrity": "sha512-g7nH6P6dyDioJogAAGprGpCtVImJhpPk/roCzdb3fIh61/s/nPsfR6onyMwkCAR/OlC3yBC0lESvUoQEAssIrw==", + "dev": true, + "engines": { + "node": ">= 0.8" + } + }, + "node_modules/des.js": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/des.js/-/des.js-1.0.1.tgz", + "integrity": "sha512-Q0I4pfFrv2VPd34/vfLrFOoRmlYj3OV50i7fskps1jZWK1kApMWWT9G6RRUeYedLcBDIhnSDaUvJMb3AhUlaEA==", + "dependencies": { + "inherits": "^2.0.1", + "minimalistic-assert": "^1.0.0" + } + }, + "node_modules/destroy": { + "version": "1.2.0", + "resolved": "https://registry.npmjs.org/destroy/-/destroy-1.2.0.tgz", + "integrity": "sha512-2sJGJTaXIIaR1w4iJSNoN0hnMY7Gpc/n8D4qSCJw8QqFWXf7cuAgnEHxBpweaVcPevC2l3KpjYCx3NypQQgaJg==", + "dev": true, + "engines": { + "node": ">= 0.8", + "npm": "1.2.8000 || >= 1.4.16" + } + }, + "node_modules/detect-node": { + "version": "2.1.0", + "resolved": "https://registry.npmjs.org/detect-node/-/detect-node-2.1.0.tgz", + "integrity": "sha512-T0NIuQpnTvFDATNuHN5roPwSBG83rFsuO+MXXH9/3N1eFbn4wcPjttvjMLEPWJ0RGUYgQE7cGgS3tNxbqCGM7g==", + "dev": true + }, + "node_modules/devtools-protocol": { + "version": "0.0.1011705", + "resolved": "https://registry.npmjs.org/devtools-protocol/-/devtools-protocol-0.0.1011705.tgz", + "integrity": "sha512-OKvTvu9n3swmgYshvsyVHYX0+aPzCoYUnyXUacfQMmFtBtBKewV/gT4I9jkAbpTqtTi2E4S9MXLlvzBDUlqg0Q==" + }, + "node_modules/diffie-hellman": { + "version": "5.0.3", + "resolved": "https://registry.npmjs.org/diffie-hellman/-/diffie-hellman-5.0.3.tgz", + "integrity": "sha512-kqag/Nl+f3GwyK25fhUMYj81BUOrZ9IuJsjIcDE5icNM9FJHAVm3VcUDxdLPoQtTuUylWm6ZIknYJwwaPxsUzg==", + "dependencies": { + "bn.js": "^4.1.0", + "miller-rabin": "^4.0.0", + "randombytes": "^2.0.0" + } + }, + "node_modules/diffie-hellman/node_modules/bn.js": { + "version": "4.12.0", + "resolved": "https://registry.npmjs.org/bn.js/-/bn.js-4.12.0.tgz", + "integrity": "sha512-c98Bf3tPniI+scsdk237ku1Dc3ujXQTSgyiPUDEOe7tRkhrqridvh8klBv0HCEso1OLOYcHuCv/cS6DNxKH+ZA==" + }, + "node_modules/dir-glob": { + "version": "3.0.1", + "resolved": "https://registry.npmjs.org/dir-glob/-/dir-glob-3.0.1.tgz", + "integrity": "sha512-WkrWp9GR4KXfKGYzOLmTuGVi1UWFfws377n9cc55/tb6DuqyF6pcQ5AbiHEshaDpY9v6oaSr2XCDidGmMwdzIA==", + "dev": true, + "dependencies": { + "path-type": "^4.0.0" + }, + "engines": { + "node": ">=8" + } + }, + "node_modules/dns-equal": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/dns-equal/-/dns-equal-1.0.0.tgz", + "integrity": "sha512-z+paD6YUQsk+AbGCEM4PrOXSss5gd66QfcVBFTKR/HpFL9jCqikS94HYwKww6fQyO7IxrIIyUu+g0Ka9tUS2Cg==", + "dev": true + }, + "node_modules/dns-packet": { + "version": "1.3.4", + "resolved": "https://registry.npmjs.org/dns-packet/-/dns-packet-1.3.4.tgz", + "integrity": "sha512-BQ6F4vycLXBvdrJZ6S3gZewt6rcrks9KBgM9vrhW+knGRqc8uEdT7fuCwloc7nny5xNoMJ17HGH0R/6fpo8ECA==", + "dev": true, + "dependencies": { + "ip": "^1.1.0", + "safe-buffer": "^5.0.1" + } + }, + "node_modules/dns-txt": { + "version": "2.0.2", + "resolved": "https://registry.npmjs.org/dns-txt/-/dns-txt-2.0.2.tgz", + "integrity": "sha512-Ix5PrWjphuSoUXV/Zv5gaFHjnaJtb02F2+Si3Ht9dyJ87+Z/lMmy+dpNHtTGraNK958ndXq2i+GLkWsWHcKaBQ==", + "dev": true, + "dependencies": { + "buffer-indexof": "^1.0.0" + } + }, + "node_modules/doctoc": { + "version": "2.2.1", + "resolved": "https://registry.npmjs.org/doctoc/-/doctoc-2.2.1.tgz", + "integrity": "sha512-qNJ1gsuo7hH40vlXTVVrADm6pdg30bns/Mo7Nv1SxuXSM1bwF9b4xQ40a6EFT/L1cI+Yylbyi8MPI4G4y7XJzQ==", + "dependencies": { + "@textlint/markdown-to-ast": "^12.1.1", + "anchor-markdown-header": "^0.6.0", + "htmlparser2": "^7.2.0", + "minimist": "^1.2.6", + "underscore": "^1.13.2", + "update-section": "^0.3.3" + }, + "bin": { + "doctoc": "doctoc.js" + } + }, + "node_modules/doctoc/node_modules/entities": { + "version": "3.0.1", + "resolved": "https://registry.npmjs.org/entities/-/entities-3.0.1.tgz", + "integrity": "sha512-WiyBqoomrwMdFG1e0kqvASYfnlb0lp8M5o5Fw2OFq1hNZxxcNk8Ik0Xm7LxzBhuidnZB/UtBqVCgUz3kBOP51Q==", + "engines": { + "node": ">=0.12" + }, + "funding": { + "url": "https://github.com/fb55/entities?sponsor=1" + } + }, + "node_modules/doctoc/node_modules/htmlparser2": { + "version": "7.2.0", + "resolved": "https://registry.npmjs.org/htmlparser2/-/htmlparser2-7.2.0.tgz", + "integrity": "sha512-H7MImA4MS6cw7nbyURtLPO1Tms7C5H602LRETv95z1MxO/7CP7rDVROehUYeYBUYEON94NXXDEPmZuq+hX4sog==", + "funding": [ + "https://github.com/fb55/htmlparser2?sponsor=1", + { + "type": "github", + "url": "https://github.com/sponsors/fb55" + } + ], + "dependencies": { + "domelementtype": "^2.0.1", + "domhandler": "^4.2.2", + "domutils": "^2.8.0", + "entities": "^3.0.1" + } + }, + "node_modules/dom-converter": { + "version": "0.2.0", + "resolved": "https://registry.npmjs.org/dom-converter/-/dom-converter-0.2.0.tgz", + "integrity": "sha512-gd3ypIPfOMr9h5jIKq8E3sHOTCjeirnl0WK5ZdS1AW0Odt0b1PaWaHdJ4Qk4klv+YB9aJBS7mESXjFoDQPu6DA==", + "dev": true, + "dependencies": { + "utila": "~0.4" + } + }, + "node_modules/dom-serializer": { + "version": "1.4.1", + "resolved": "https://registry.npmjs.org/dom-serializer/-/dom-serializer-1.4.1.tgz", + "integrity": "sha512-VHwB3KfrcOOkelEG2ZOfxqLZdfkil8PtJi4P8N2MMXucZq2yLp75ClViUlOVwyoHEDjYU433Aq+5zWP61+RGag==", + "dependencies": { + "domelementtype": "^2.0.1", + "domhandler": "^4.2.0", + "entities": "^2.0.0" + }, + "funding": { + "url": "https://github.com/cheeriojs/dom-serializer?sponsor=1" + } + }, + "node_modules/domain-browser": { + "version": "4.22.0", + "resolved": "https://registry.npmjs.org/domain-browser/-/domain-browser-4.22.0.tgz", + "integrity": "sha512-IGBwjF7tNk3cwypFNH/7bfzBcgSCbaMOD3GsaY1AU/JRrnHnYgEM0+9kQt52iZxjNsjBtJYtao146V+f8jFZNw==", + "engines": { + "node": ">=10" + }, + "funding": { + "url": "https://bevry.me/fund" + } + }, + "node_modules/domelementtype": { + "version": "2.3.0", + "resolved": "https://registry.npmjs.org/domelementtype/-/domelementtype-2.3.0.tgz", + "integrity": "sha512-OLETBj6w0OsagBwdXnPdN0cnMfF9opN69co+7ZrbfPGrdpPVNBUj02spi6B1N7wChLQiPn4CSH/zJvXw56gmHw==", + "funding": [ + { + "type": "github", + "url": "https://github.com/sponsors/fb55" + } + ] + }, + "node_modules/domhandler": { + "version": "4.3.1", + "resolved": "https://registry.npmjs.org/domhandler/-/domhandler-4.3.1.tgz", + "integrity": "sha512-GrwoxYN+uWlzO8uhUXRl0P+kHE4GtVPfYzVLcUxPL7KNdHKj66vvlhiweIHqYYXWlw+T8iLMp42Lm67ghw4WMQ==", + "dependencies": { + "domelementtype": "^2.2.0" + }, + "engines": { + "node": ">= 4" + }, + "funding": { + "url": "https://github.com/fb55/domhandler?sponsor=1" + } + }, + "node_modules/domutils": { + "version": "2.8.0", + "resolved": "https://registry.npmjs.org/domutils/-/domutils-2.8.0.tgz", + "integrity": "sha512-w96Cjofp72M5IIhpjgobBimYEfoPjx1Vx0BSX9P30WBdZW2WIKU0T1Bd0kz2eNZ9ikjKgHbEyKx8BB6H1L3h3A==", + "dependencies": { + "dom-serializer": "^1.0.1", + "domelementtype": "^2.2.0", + "domhandler": "^4.2.0" + }, + "funding": { + "url": "https://github.com/fb55/domutils?sponsor=1" + } + }, + "node_modules/dot-case": { + "version": "3.0.4", + "resolved": "https://registry.npmjs.org/dot-case/-/dot-case-3.0.4.tgz", + "integrity": "sha512-Kv5nKlh6yRrdrGvxeJ2e5y2eRUpkUosIW4A2AS38zwSz27zu7ufDwQPi5Jhs3XAlGNetl3bmnGhQsMtkKJnj3w==", + "dev": true, + "dependencies": { + "no-case": "^3.0.4", + "tslib": "^2.0.3" + } + }, + "node_modules/ee-first": { + "version": "1.1.1", + "resolved": "https://registry.npmjs.org/ee-first/-/ee-first-1.1.1.tgz", + "integrity": "sha512-WMwm9LhRUo+WUaRN+vRuETqG89IgZphVSNkdFgeb6sS/E4OrDIN7t48CAewSHXc6C8lefD8KKfr5vY61brQlow==", + "dev": true + }, + "node_modules/electron-to-chromium": { + "version": "1.4.167", + "resolved": "https://registry.npmjs.org/electron-to-chromium/-/electron-to-chromium-1.4.167.tgz", + "integrity": "sha512-lPHuHXBwpkr4RcfaZBKm6TKOWG/1N9mVggUpP4fY3l1JIUU2x4fkM8928smYdZ5lF+6KCTAxo1aK9JmqT+X71Q==" + }, + "node_modules/elliptic": { + "version": "6.5.4", + "resolved": "https://registry.npmjs.org/elliptic/-/elliptic-6.5.4.tgz", + "integrity": "sha512-iLhC6ULemrljPZb+QutR5TQGB+pdW6KGD5RSegS+8sorOZT+rdQFbsQFJgvN3eRqNALqJer4oQ16YvJHlU8hzQ==", + "dependencies": { + "bn.js": "^4.11.9", + "brorand": "^1.1.0", + "hash.js": "^1.0.0", + "hmac-drbg": "^1.0.1", + "inherits": "^2.0.4", + "minimalistic-assert": "^1.0.1", + "minimalistic-crypto-utils": "^1.0.1" + } + }, + "node_modules/elliptic/node_modules/bn.js": { + "version": "4.12.0", + "resolved": "https://registry.npmjs.org/bn.js/-/bn.js-4.12.0.tgz", + "integrity": "sha512-c98Bf3tPniI+scsdk237ku1Dc3ujXQTSgyiPUDEOe7tRkhrqridvh8klBv0HCEso1OLOYcHuCv/cS6DNxKH+ZA==" + }, + "node_modules/emoji-regex": { + "version": "10.1.0", + "resolved": "https://registry.npmjs.org/emoji-regex/-/emoji-regex-10.1.0.tgz", + "integrity": "sha512-xAEnNCT3w2Tg6MA7ly6QqYJvEoY1tm9iIjJ3yMKK9JPlWuRHAMoe5iETwQnx3M9TVbFMfsrBgWKR+IsmswwNjg==" + }, + "node_modules/encodeurl": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/encodeurl/-/encodeurl-1.0.2.tgz", + "integrity": "sha512-TPJXq8JqFaVYm2CWmPvnP2Iyo4ZSM7/QKcSmuMLDObfpH5fi7RUGmd/rTDf+rut/saiDiQEeVTNgAmJEdAOx0w==", + "dev": true, + "engines": { + "node": ">= 0.8" + } + }, + "node_modules/end-of-stream": { + "version": "1.4.4", + "resolved": "https://registry.npmjs.org/end-of-stream/-/end-of-stream-1.4.4.tgz", + "integrity": "sha512-+uw1inIHVPQoaVuHzRyXd21icM+cnt4CzD5rW+NC1wjOUSTOs+Te7FOv7AhN7vS9x/oIyhLP5PR1H+phQAHu5Q==", + "dependencies": { + "once": "^1.4.0" + } + }, + "node_modules/enhanced-resolve": { + "version": "5.9.3", + "resolved": "https://registry.npmjs.org/enhanced-resolve/-/enhanced-resolve-5.9.3.tgz", + "integrity": "sha512-Bq9VSor+kjvW3f9/MiiR4eE3XYgOl7/rS8lnSxbRbF3kS0B2r+Y9w5krBWxZgDxASVZbdYrn5wT4j/Wb0J9qow==", + "dependencies": { + "graceful-fs": "^4.2.4", + "tapable": "^2.2.0" + }, + "engines": { + "node": ">=10.13.0" + } + }, + "node_modules/entities": { + "version": "2.2.0", + "resolved": "https://registry.npmjs.org/entities/-/entities-2.2.0.tgz", + "integrity": "sha512-p92if5Nz619I0w+akJrLZH0MX0Pb5DX39XOwQTtXSdQQOaYH03S1uIQp4mhOZtAXrxq4ViO67YTiLBo2638o9A==", + "funding": { + "url": "https://github.com/fb55/entities?sponsor=1" + } + }, + "node_modules/envinfo": { + "version": "7.8.1", + "resolved": "https://registry.npmjs.org/envinfo/-/envinfo-7.8.1.tgz", + "integrity": "sha512-/o+BXHmB7ocbHEAs6F2EnG0ogybVVUdkRunTT2glZU9XAaGmhqskrvKwqXuDfNjEO0LZKWdejEEpnq8aM0tOaw==", + "dev": true, + "bin": { + "envinfo": "dist/cli.js" + }, + "engines": { + "node": ">=4" + } + }, + "node_modules/es-abstract": { + "version": "1.20.1", + "resolved": "https://registry.npmjs.org/es-abstract/-/es-abstract-1.20.1.tgz", + "integrity": "sha512-WEm2oBhfoI2sImeM4OF2zE2V3BYdSF+KnSi9Sidz51fQHd7+JuF8Xgcj9/0o+OWeIeIS/MiuNnlruQrJf16GQA==", + "dependencies": { + "call-bind": "^1.0.2", + "es-to-primitive": "^1.2.1", + "function-bind": "^1.1.1", + "function.prototype.name": "^1.1.5", + "get-intrinsic": "^1.1.1", + "get-symbol-description": "^1.0.0", + "has": "^1.0.3", + "has-property-descriptors": "^1.0.0", + "has-symbols": "^1.0.3", + "internal-slot": "^1.0.3", + "is-callable": "^1.2.4", + "is-negative-zero": "^2.0.2", + "is-regex": "^1.1.4", + "is-shared-array-buffer": "^1.0.2", + "is-string": "^1.0.7", + "is-weakref": "^1.0.2", + "object-inspect": "^1.12.0", + "object-keys": "^1.1.1", + "object.assign": "^4.1.2", + "regexp.prototype.flags": "^1.4.3", + "string.prototype.trimend": "^1.0.5", + "string.prototype.trimstart": "^1.0.5", + "unbox-primitive": "^1.0.2" + }, + "engines": { + "node": ">= 0.4" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/es-module-lexer": { + "version": "0.9.3", + "resolved": "https://registry.npmjs.org/es-module-lexer/-/es-module-lexer-0.9.3.tgz", + "integrity": "sha512-1HQ2M2sPtxwnvOvT1ZClHyQDiggdNjURWpY2we6aMKCQiUVxTmVs2UYPLIrD84sS+kMdUwfBSylbJPwNnBrnHQ==" + }, + "node_modules/es-to-primitive": { + "version": "1.2.1", + "resolved": "https://registry.npmjs.org/es-to-primitive/-/es-to-primitive-1.2.1.tgz", + "integrity": "sha512-QCOllgZJtaUo9miYBcLChTUaHNjJF3PYs1VidD7AwiEj1kYxKeQTctLAezAOH5ZKRH0g2IgPn6KwB4IT8iRpvA==", + "dependencies": { + "is-callable": "^1.1.4", + "is-date-object": "^1.0.1", + "is-symbol": "^1.0.2" + }, + "engines": { + "node": ">= 0.4" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/es6-object-assign": { + "version": "1.1.0", + "resolved": "https://registry.npmjs.org/es6-object-assign/-/es6-object-assign-1.1.0.tgz", + "integrity": "sha512-MEl9uirslVwqQU369iHNWZXsI8yaZYGg/D65aOgZkeyFJwHYSxilf7rQzXKI7DdDuBPrBXbfk3sl9hJhmd5AUw==" + }, + "node_modules/escalade": { + "version": "3.1.1", + "resolved": "https://registry.npmjs.org/escalade/-/escalade-3.1.1.tgz", + "integrity": "sha512-k0er2gUkLf8O0zKJiAhmkTnJlTvINGv7ygDNPbeIsX/TJjGJZHuh9B2UxbsaEkmlEo9MfhrSzmhIlhRlI2GXnw==", + "engines": { + "node": ">=6" + } + }, + "node_modules/escape-html": { + "version": "1.0.3", + "resolved": "https://registry.npmjs.org/escape-html/-/escape-html-1.0.3.tgz", + "integrity": "sha512-NiSupZ4OeuGwr68lGIeym/ksIZMJodUGOSCZ/FSnTxcrekbvqrgdUxlJOMpijaKZVjAJrWrGs/6Jy8OMuyj9ow==", + "dev": true + }, + "node_modules/escape-string-regexp": { + "version": "4.0.0", + "resolved": "https://registry.npmjs.org/escape-string-regexp/-/escape-string-regexp-4.0.0.tgz", + "integrity": "sha512-TtpcNJ3XAzx3Gq8sWRzJaVajRs0uVxA2YAkdb1jm2YkPz4G6egUFAyA3n5vtEIZefPk5Wa4UXbKuS5fKkJWdgA==", + "engines": { + "node": ">=10" + }, + "funding": { + "url": "https://github.com/sponsors/sindresorhus" + } + }, + "node_modules/eslint-scope": { + "version": "5.1.1", + "resolved": "https://registry.npmjs.org/eslint-scope/-/eslint-scope-5.1.1.tgz", + "integrity": "sha512-2NxwbF/hZ0KpepYN0cNbo+FN6XoK7GaHlQhgx/hIZl6Va0bF45RQOOwhLIy8lQDbuCiadSLCBnH2CFYquit5bw==", + "dependencies": { + "esrecurse": "^4.3.0", + "estraverse": "^4.1.1" + }, + "engines": { + "node": ">=8.0.0" + } + }, + "node_modules/esrecurse": { + "version": "4.3.0", + "resolved": "https://registry.npmjs.org/esrecurse/-/esrecurse-4.3.0.tgz", + "integrity": "sha512-KmfKL3b6G+RXvP8N1vr3Tq1kL/oCFgn2NYXEtqP8/L3pKapUA4G8cFVaoF3SU323CD4XypR/ffioHmkti6/Tag==", + "dependencies": { + "estraverse": "^5.2.0" + }, + "engines": { + "node": ">=4.0" + } + }, + "node_modules/esrecurse/node_modules/estraverse": { + "version": "5.3.0", + "resolved": "https://registry.npmjs.org/estraverse/-/estraverse-5.3.0.tgz", + "integrity": "sha512-MMdARuVEQziNTeJD8DgMqmhwR11BRQ/cBP+pLtYdSTnf3MIO8fFeiINEbX36ZdNlfU/7A9f3gUw49B3oQsvwBA==", + "engines": { + "node": ">=4.0" + } + }, + "node_modules/estraverse": { + "version": "4.3.0", + "resolved": "https://registry.npmjs.org/estraverse/-/estraverse-4.3.0.tgz", + "integrity": "sha512-39nnKffWz8xN1BU/2c79n9nB9HDzo0niYUqx6xyqUnyoAnQyyWpOTdZEeiCch8BBu515t4wp9ZmgVfVhn9EBpw==", + "engines": { + "node": ">=4.0" + } + }, + "node_modules/etag": { + "version": "1.8.1", + "resolved": "https://registry.npmjs.org/etag/-/etag-1.8.1.tgz", + "integrity": "sha512-aIL5Fx7mawVa300al2BnEE4iNvo1qETxLrPI/o05L7z6go7fCw1J6EQmbK4FmJ2AS7kgVF/KEZWufBfdClMcPg==", + "dev": true, + "engines": { + "node": ">= 0.6" + } + }, + "node_modules/eventemitter3": { + "version": "4.0.7", + "resolved": "https://registry.npmjs.org/eventemitter3/-/eventemitter3-4.0.7.tgz", + "integrity": "sha512-8guHBZCwKnFhYdHr2ysuRWErTwhoN2X8XELRlrRwpmfeY2jjuUN4taQMsULKUVo1K4DvZl+0pgfyoysHxvmvEw==", + "dev": true + }, + "node_modules/events": { + "version": "3.3.0", + "resolved": "https://registry.npmjs.org/events/-/events-3.3.0.tgz", + "integrity": "sha512-mQw+2fkQbALzQ7V0MY0IqdnXNOeTtP4r0lN9z7AAawCXgqea7bDii20AYrIBrFd/Hx0M2Ocz6S111CaFkUcb0Q==", + "engines": { + "node": ">=0.8.x" + } + }, + "node_modules/evp_bytestokey": { + "version": "1.0.3", + "resolved": "https://registry.npmjs.org/evp_bytestokey/-/evp_bytestokey-1.0.3.tgz", + "integrity": "sha512-/f2Go4TognH/KvCISP7OUsHn85hT9nUkxxA9BEWxFn+Oj9o8ZNLm/40hdlgSLyuOimsrTKLUMEorQexp/aPQeA==", + "dependencies": { + "md5.js": "^1.3.4", + "safe-buffer": "^5.1.1" + } + }, + "node_modules/execa": { + "version": "5.1.1", + "resolved": "https://registry.npmjs.org/execa/-/execa-5.1.1.tgz", + "integrity": "sha512-8uSpZZocAZRBAPIEINJj3Lo9HyGitllczc27Eh5YYojjMFMn8yHMDMaUHE2Jqfq05D/wucwI4JGURyXt1vchyg==", + "dev": true, + "dependencies": { + "cross-spawn": "^7.0.3", + "get-stream": "^6.0.0", + "human-signals": "^2.1.0", + "is-stream": "^2.0.0", + "merge-stream": "^2.0.0", + "npm-run-path": "^4.0.1", + "onetime": "^5.1.2", + "signal-exit": "^3.0.3", + "strip-final-newline": "^2.0.0" + }, + "engines": { + "node": ">=10" + }, + "funding": { + "url": "https://github.com/sindresorhus/execa?sponsor=1" + } + }, + "node_modules/express": { + "version": "4.18.1", + "resolved": "https://registry.npmjs.org/express/-/express-4.18.1.tgz", + "integrity": "sha512-zZBcOX9TfehHQhtupq57OF8lFZ3UZi08Y97dwFCkD8p9d/d2Y3M+ykKcwaMDEL+4qyUolgBDX6AblpR3fL212Q==", + "dev": true, + "dependencies": { + "accepts": "~1.3.8", + "array-flatten": "1.1.1", + "body-parser": "1.20.0", + "content-disposition": "0.5.4", + "content-type": "~1.0.4", + "cookie": "0.5.0", + "cookie-signature": "1.0.6", + "debug": "2.6.9", + "depd": "2.0.0", + "encodeurl": "~1.0.2", + "escape-html": "~1.0.3", + "etag": "~1.8.1", + "finalhandler": "1.2.0", + "fresh": "0.5.2", + "http-errors": "2.0.0", + "merge-descriptors": "1.0.1", + "methods": "~1.1.2", + "on-finished": "2.4.1", + "parseurl": "~1.3.3", + "path-to-regexp": "0.1.7", + "proxy-addr": "~2.0.7", + "qs": "6.10.3", + "range-parser": "~1.2.1", + "safe-buffer": "5.2.1", + "send": "0.18.0", + "serve-static": "1.15.0", + "setprototypeof": "1.2.0", + "statuses": "2.0.1", + "type-is": "~1.6.18", + "utils-merge": "1.0.1", + "vary": "~1.1.2" + }, + "engines": { + "node": ">= 0.10.0" + } + }, + "node_modules/express/node_modules/array-flatten": { + "version": "1.1.1", + "resolved": "https://registry.npmjs.org/array-flatten/-/array-flatten-1.1.1.tgz", + "integrity": "sha512-PCVAQswWemu6UdxsDFFX/+gVeYqKAod3D3UVm91jHwynguOwAvYPhx8nNlM++NqRcK6CxxpUafjmhIdKiHibqg==", + "dev": true + }, + "node_modules/extend": { + "version": "3.0.2", + "resolved": "https://registry.npmjs.org/extend/-/extend-3.0.2.tgz", + "integrity": "sha512-fjquC59cD7CyW6urNXK0FBufkZcoiGG80wTuPujX590cB5Ttln20E2UB4S/WARVqhXffZl2LNgS+gQdPIIim/g==" + }, + "node_modules/extract-zip": { + "version": "2.0.1", + "resolved": "https://registry.npmjs.org/extract-zip/-/extract-zip-2.0.1.tgz", + "integrity": "sha512-GDhU9ntwuKyGXdZBUgTIe+vXnWj0fppUEtMDL0+idd5Sta8TGpHssn/eusA9mrPr9qNDym6SxAYZjNvCn/9RBg==", + "dependencies": { + "debug": "^4.1.1", + "get-stream": "^5.1.0", + "yauzl": "^2.10.0" + }, + "bin": { + "extract-zip": "cli.js" + }, + "engines": { + "node": ">= 10.17.0" + }, + "optionalDependencies": { + "@types/yauzl": "^2.9.1" + } + }, + "node_modules/extract-zip/node_modules/debug": { + "version": "4.3.4", + "resolved": "https://registry.npmjs.org/debug/-/debug-4.3.4.tgz", + "integrity": "sha512-PRWFHuSU3eDtQJPvnNY7Jcket1j0t5OuOsFzPPzsekD52Zl8qUfFIPEiswXqIvHWGVHOgX+7G/vCNNhehwxfkQ==", + "dependencies": { + "ms": "2.1.2" + }, + "engines": { + "node": ">=6.0" + }, + "peerDependenciesMeta": { + "supports-color": { + "optional": true + } + } + }, + "node_modules/extract-zip/node_modules/get-stream": { + "version": "5.2.0", + "resolved": "https://registry.npmjs.org/get-stream/-/get-stream-5.2.0.tgz", + "integrity": "sha512-nBF+F1rAZVCu/p7rjzgA+Yb4lfYXrpl7a6VmJrU8wF9I1CKvP/QwPNZHnOlwbTkY6dvtFIzFMSyQXbLoTQPRpA==", + "dependencies": { + "pump": "^3.0.0" + }, + "engines": { + "node": ">=8" + }, + "funding": { + "url": "https://github.com/sponsors/sindresorhus" + } + }, + "node_modules/extract-zip/node_modules/ms": { + "version": "2.1.2", + "resolved": "https://registry.npmjs.org/ms/-/ms-2.1.2.tgz", + "integrity": "sha512-sGkPx+VjMtmA6MX27oA4FBFELFCZZ4S4XqeGOXCv68tT+jb3vk/RyaKWP0PTKyWtmLSM0b+adUTEvbs1PEaH2w==" + }, + "node_modules/fast-deep-equal": { + "version": "3.1.3", + "resolved": "https://registry.npmjs.org/fast-deep-equal/-/fast-deep-equal-3.1.3.tgz", + "integrity": "sha512-f3qQ9oQy9j2AhBe/H9VC91wLmKBCCU/gDOnKNAYG5hswO7BLKj09Hc5HYNz9cGI++xlpDCIgDaitVs03ATR84Q==" + }, + "node_modules/fast-glob": { + "version": "3.2.11", + "resolved": "https://registry.npmjs.org/fast-glob/-/fast-glob-3.2.11.tgz", + "integrity": "sha512-xrO3+1bxSo3ZVHAnqzyuewYT6aMFHRAd4Kcs92MAonjwQZLsK9d0SF1IyQ3k5PoirxTW0Oe/RqFgMQ6TcNE5Ew==", + "dev": true, + "dependencies": { + "@nodelib/fs.stat": "^2.0.2", + "@nodelib/fs.walk": "^1.2.3", + "glob-parent": "^5.1.2", + "merge2": "^1.3.0", + "micromatch": "^4.0.4" + }, + "engines": { + "node": ">=8.6.0" + } + }, + "node_modules/fast-json-stable-stringify": { + "version": "2.1.0", + "resolved": "https://registry.npmjs.org/fast-json-stable-stringify/-/fast-json-stable-stringify-2.1.0.tgz", + "integrity": "sha512-lhd/wF+Lk98HZoTCtlVraHtfh5XYijIjalXck7saUtuanSDyLMxnHhSXEDJqHxD7msR8D0uCmqlkwjCV8xvwHw==" + }, + "node_modules/fastest-levenshtein": { + "version": "1.0.14", + "resolved": "https://registry.npmjs.org/fastest-levenshtein/-/fastest-levenshtein-1.0.14.tgz", + "integrity": "sha512-tFfWHjnuUfKE186Tfgr+jtaFc0mZTApEgKDOeyN+FwOqRkO/zK/3h1AiRd8u8CY53owL3CUmGr/oI9p/RdyLTA==", + "dev": true, + "engines": { + "node": ">= 4.9.1" + } + }, + "node_modules/fastq": { + "version": "1.13.0", + "resolved": "https://registry.npmjs.org/fastq/-/fastq-1.13.0.tgz", + "integrity": "sha512-YpkpUnK8od0o1hmeSc7UUs/eB/vIPWJYjKck2QKIzAf71Vm1AAQ3EbuZB3g2JIy+pg+ERD0vqI79KyZiB2e2Nw==", + "dev": true, + "dependencies": { + "reusify": "^1.0.4" + } + }, + "node_modules/fault": { + "version": "1.0.4", + "resolved": "https://registry.npmjs.org/fault/-/fault-1.0.4.tgz", + "integrity": "sha512-CJ0HCB5tL5fYTEA7ToAq5+kTwd++Borf1/bifxd9iT70QcXr4MRrO3Llf8Ifs70q+SJcGHFtnIE/Nw6giCtECA==", + "dependencies": { + "format": "^0.2.0" + }, + "funding": { + "type": "github", + "url": "https://github.com/sponsors/wooorm" + } + }, + "node_modules/faye-websocket": { + "version": "0.11.4", + "resolved": "https://registry.npmjs.org/faye-websocket/-/faye-websocket-0.11.4.tgz", + "integrity": "sha512-CzbClwlXAuiRQAlUyfqPgvPoNKTckTPGfwZV4ZdAhVcP2lh9KUxJg2b5GkE7XbjKQ3YJnQ9z6D9ntLAlB+tP8g==", + "dev": true, + "dependencies": { + "websocket-driver": ">=0.5.1" + }, + "engines": { + "node": ">=0.8.0" + } + }, + "node_modules/fd-slicer": { + "version": "1.1.0", + "resolved": "https://registry.npmjs.org/fd-slicer/-/fd-slicer-1.1.0.tgz", + "integrity": "sha512-cE1qsB/VwyQozZ+q1dGxR8LBYNZeofhEdUNGSMbQD3Gw2lAzX9Zb3uIU6Ebc/Fmyjo9AWWfnn0AUCHqtevs/8g==", + "dependencies": { + "pend": "~1.2.0" + } + }, + "node_modules/fill-range": { + "version": "7.0.1", + "resolved": "https://registry.npmjs.org/fill-range/-/fill-range-7.0.1.tgz", + "integrity": "sha512-qOo9F+dMUmC2Lcb4BbVvnKJxTPjCm+RRpe4gDuGrzkL7mEVl/djYSu2OdQ2Pa302N4oqkSg9ir6jaLWJ2USVpQ==", + "dev": true, + "dependencies": { + "to-regex-range": "^5.0.1" + }, + "engines": { + "node": ">=8" + } + }, + "node_modules/filter-obj": { + "version": "2.0.2", + "resolved": "https://registry.npmjs.org/filter-obj/-/filter-obj-2.0.2.tgz", + "integrity": "sha512-lO3ttPjHZRfjMcxWKb1j1eDhTFsu4meeR3lnMcnBFhk6RuLhvEiuALu2TlfL310ph4lCYYwgF/ElIjdP739tdg==", + "engines": { + "node": ">=8" + } + }, + "node_modules/finalhandler": { + "version": "1.2.0", + "resolved": "https://registry.npmjs.org/finalhandler/-/finalhandler-1.2.0.tgz", + "integrity": "sha512-5uXcUVftlQMFnWC9qu/svkWv3GTd2PfUhK/3PLkYNAe7FbqJMt3515HaxE6eRL74GdsriiwujiawdaB1BpEISg==", + "dev": true, + "dependencies": { + "debug": "2.6.9", + "encodeurl": "~1.0.2", + "escape-html": "~1.0.3", + "on-finished": "2.4.1", + "parseurl": "~1.3.3", + "statuses": "2.0.1", + "unpipe": "~1.0.0" + }, + "engines": { + "node": ">= 0.8" + } + }, + "node_modules/find-up": { + "version": "4.1.0", + "resolved": "https://registry.npmjs.org/find-up/-/find-up-4.1.0.tgz", + "integrity": "sha512-PpOwAdQ/YlXQ2vj8a3h8IipDuYRi3wceVQQGYWxNINccq40Anw7BlsEXCMbt1Zt+OLA6Fq9suIpIWD0OsnISlw==", + "dependencies": { + "locate-path": "^5.0.0", + "path-exists": "^4.0.0" + }, + "engines": { + "node": ">=8" + } + }, + "node_modules/follow-redirects": { + "version": "1.15.1", + "resolved": "https://registry.npmjs.org/follow-redirects/-/follow-redirects-1.15.1.tgz", + "integrity": "sha512-yLAMQs+k0b2m7cVxpS1VKJVvoz7SS9Td1zss3XRwXj+ZDH00RJgnuLx7E44wx02kQLrdM3aOOy+FpzS7+8OizA==", + "dev": true, + "funding": [ + { + "type": "individual", + "url": "https://github.com/sponsors/RubenVerborgh" + } + ], + "engines": { + "node": ">=4.0" + }, + "peerDependenciesMeta": { + "debug": { + "optional": true + } + } + }, + "node_modules/for-each": { + "version": "0.3.3", + "resolved": "https://registry.npmjs.org/for-each/-/for-each-0.3.3.tgz", + "integrity": "sha512-jqYfLp7mo9vIyQf8ykW2v7A+2N4QjeCeI5+Dz9XraiO1ign81wjiH7Fb9vSOWvQfNtmSa4H2RoQTrrXivdUZmw==", + "dependencies": { + "is-callable": "^1.1.3" + } + }, + "node_modules/format": { + "version": "0.2.2", + "resolved": "https://registry.npmjs.org/format/-/format-0.2.2.tgz", + "integrity": "sha512-wzsgA6WOq+09wrU1tsJ09udeR/YZRaeArL9e1wPbFg3GG2yDnC2ldKpxs4xunpFF9DgqCqOIra3bc1HWrJ37Ww==", + "engines": { + "node": ">=0.4.x" + } + }, + "node_modules/forwarded": { + "version": "0.2.0", + "resolved": "https://registry.npmjs.org/forwarded/-/forwarded-0.2.0.tgz", + "integrity": "sha512-buRG0fpBtRHSTCOASe6hD258tEubFoRLb4ZNA6NxMVHNw2gOcwHo9wyablzMzOA5z9xA9L1KNjk/Nt6MT9aYow==", + "dev": true, + "engines": { + "node": ">= 0.6" + } + }, + "node_modules/fresh": { + "version": "0.5.2", + "resolved": "https://registry.npmjs.org/fresh/-/fresh-0.5.2.tgz", + "integrity": "sha512-zJ2mQYM18rEFOudeV4GShTGIQ7RbzA7ozbU9I/XBpm7kqgMywgmylMwXHxZJmkVoYkna9d2pVXVXPdYTP9ej8Q==", + "dev": true, + "engines": { + "node": ">= 0.6" + } + }, + "node_modules/fs-constants": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/fs-constants/-/fs-constants-1.0.0.tgz", + "integrity": "sha512-y6OAwoSIf7FyjMIv94u+b5rdheZEjzR63GTyZJm5qh4Bi+2YgwLCcI/fPFZkL5PSixOt6ZNKm+w+Hfp/Bciwow==" + }, + "node_modules/fs-monkey": { + "version": "1.0.3", + "resolved": "https://registry.npmjs.org/fs-monkey/-/fs-monkey-1.0.3.tgz", + "integrity": "sha512-cybjIfiiE+pTWicSCLFHSrXZ6EilF30oh91FDP9S2B051prEa7QWfrVTQm10/dDpswBDXZugPa1Ogu8Yh+HV0Q==", + "dev": true + }, + "node_modules/fs.realpath": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/fs.realpath/-/fs.realpath-1.0.0.tgz", + "integrity": "sha512-OO0pH2lK6a0hZnAdau5ItzHPI6pUlvI7jMVnxUQRtw4owF2wk8lOSabtGDCTP4Ggrg2MbGnWO9X8K1t4+fGMDw==" + }, + "node_modules/fsevents": { + "version": "2.3.2", + "resolved": "https://registry.npmjs.org/fsevents/-/fsevents-2.3.2.tgz", + "integrity": "sha512-xiqMQR4xAeHTuB9uWm+fFRcIOgKBMiOBP+eXiyT7jsgVCq1bkVygt00oASowB7EdtpOHaaPgKt812P9ab+DDKA==", + "dev": true, + "hasInstallScript": true, + "optional": true, + "os": [ + "darwin" + ], + "engines": { + "node": "^8.16.0 || ^10.6.0 || >=11.0.0" + } + }, + "node_modules/function-bind": { + "version": "1.1.1", + "resolved": "https://registry.npmjs.org/function-bind/-/function-bind-1.1.1.tgz", + "integrity": "sha512-yIovAzMX49sF8Yl58fSCWJ5svSLuaibPxXQJFLmBObTuCr0Mf1KiPopGM9NiFjiYBCbfaa2Fh6breQ6ANVTI0A==" + }, + "node_modules/function.prototype.name": { + "version": "1.1.5", + "resolved": "https://registry.npmjs.org/function.prototype.name/-/function.prototype.name-1.1.5.tgz", + "integrity": "sha512-uN7m/BzVKQnCUF/iW8jYea67v++2u7m5UgENbHRtdDVclOUP+FMPlCNdmk0h/ysGyo2tavMJEDqJAkJdRa1vMA==", + "dependencies": { + "call-bind": "^1.0.2", + "define-properties": "^1.1.3", + "es-abstract": "^1.19.0", + "functions-have-names": "^1.2.2" + }, + "engines": { + "node": ">= 0.4" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/functions-have-names": { + "version": "1.2.3", + "resolved": "https://registry.npmjs.org/functions-have-names/-/functions-have-names-1.2.3.tgz", + "integrity": "sha512-xckBUXyTIqT97tq2x2AMb+g163b5JFysYk0x4qxNFwbfQkmNZoiRHb6sPzI9/QV33WeuvVYBUIiD4NzNIyqaRQ==", + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/get-intrinsic": { + "version": "1.1.1", + "resolved": "https://registry.npmjs.org/get-intrinsic/-/get-intrinsic-1.1.1.tgz", + "integrity": "sha512-kWZrnVM42QCiEA2Ig1bG8zjoIMOgxWwYCEeNdwY6Tv/cOSeGpcoX4pXHfKUxNKVoArnrEr2e9srnAxxGIraS9Q==", + "dependencies": { + "function-bind": "^1.1.1", + "has": "^1.0.3", + "has-symbols": "^1.0.1" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/get-stream": { + "version": "6.0.1", + "resolved": "https://registry.npmjs.org/get-stream/-/get-stream-6.0.1.tgz", + "integrity": "sha512-ts6Wi+2j3jQjqi70w5AlN8DFnkSwC+MqmxEzdEALB2qXZYV3X/b1CTfgPLGJNMeAWxdPfU8FO1ms3NUfaHCPYg==", + "dev": true, + "engines": { + "node": ">=10" + }, + "funding": { + "url": "https://github.com/sponsors/sindresorhus" + } + }, + "node_modules/get-symbol-description": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/get-symbol-description/-/get-symbol-description-1.0.0.tgz", + "integrity": "sha512-2EmdH1YvIQiZpltCNgkuiUnyukzxM/R6NDJX31Ke3BG1Nq5b0S2PhX59UKi9vZpPDQVdqn+1IcaAwnzTT5vCjw==", + "dependencies": { + "call-bind": "^1.0.2", + "get-intrinsic": "^1.1.1" + }, + "engines": { + "node": ">= 0.4" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/glob": { + "version": "7.2.3", + "resolved": "https://registry.npmjs.org/glob/-/glob-7.2.3.tgz", + "integrity": "sha512-nFR0zLpU2YCaRxwoCJvL6UvCH2JFyFVIvwTLsIf21AuHlMskA1hhTdk+LlYJtOlYt9v6dvszD2BGRqBL+iQK9Q==", + "dependencies": { + "fs.realpath": "^1.0.0", + "inflight": "^1.0.4", + "inherits": "2", + "minimatch": "^3.1.1", + "once": "^1.3.0", + "path-is-absolute": "^1.0.0" + }, + "engines": { + "node": "*" + }, + "funding": { + "url": "https://github.com/sponsors/isaacs" + } + }, + "node_modules/glob-parent": { + "version": "5.1.2", + "resolved": "https://registry.npmjs.org/glob-parent/-/glob-parent-5.1.2.tgz", + "integrity": "sha512-AOIgSQCepiJYwP3ARnGx+5VnTu2HBYdzbGP45eLw1vr3zB3vZLeyed1sC9hnbcOc9/SrMyM5RPQrkGz4aS9Zow==", + "dev": true, + "dependencies": { + "is-glob": "^4.0.1" + }, + "engines": { + "node": ">= 6" + } + }, + "node_modules/glob-to-regexp": { + "version": "0.4.1", + "resolved": "https://registry.npmjs.org/glob-to-regexp/-/glob-to-regexp-0.4.1.tgz", + "integrity": "sha512-lkX1HJXwyMcprw/5YUZc2s7DrpAiHB21/V+E1rHUrVNokkvB6bqMzT0VfV6/86ZNabt1k14YOIaT7nDvOX3Iiw==" + }, + "node_modules/globby": { + "version": "11.1.0", + "resolved": "https://registry.npmjs.org/globby/-/globby-11.1.0.tgz", + "integrity": "sha512-jhIXaOzy1sb8IyocaruWSn1TjmnBVs8Ayhcy83rmxNJ8q2uWKCAj3CnJY+KpGSXCueAPc0i05kVvVKtP1t9S3g==", + "dev": true, + "dependencies": { + "array-union": "^2.1.0", + "dir-glob": "^3.0.1", + "fast-glob": "^3.2.9", + "ignore": "^5.2.0", + "merge2": "^1.4.1", + "slash": "^3.0.0" + }, + "engines": { + "node": ">=10" + }, + "funding": { + "url": "https://github.com/sponsors/sindresorhus" + } + }, + "node_modules/graceful-fs": { + "version": "4.2.10", + "resolved": "https://registry.npmjs.org/graceful-fs/-/graceful-fs-4.2.10.tgz", + "integrity": "sha512-9ByhssR2fPVsNZj478qUUbKfmL0+t5BDVyjShtyZZLiK7ZDAArFFfopyOTj0M05wE2tJPisA4iTnnXl2YoPvOA==" + }, + "node_modules/handle-thing": { + "version": "2.0.1", + "resolved": "https://registry.npmjs.org/handle-thing/-/handle-thing-2.0.1.tgz", + "integrity": "sha512-9Qn4yBxelxoh2Ow62nP+Ka/kMnOXRi8BXnRaUwezLNhqelnN49xKz4F/dPP8OYLxLxq6JDtZb2i9XznUQbNPTg==", + "dev": true + }, + "node_modules/has": { + "version": "1.0.3", + "resolved": "https://registry.npmjs.org/has/-/has-1.0.3.tgz", + "integrity": "sha512-f2dvO0VU6Oej7RkWJGrehjbzMAjFp5/VKPp5tTpWIV4JHHZK1/BxbFRtf/siA2SWTe09caDmVtYYzWEIbBS4zw==", + "dependencies": { + "function-bind": "^1.1.1" + }, + "engines": { + "node": ">= 0.4.0" + } + }, + "node_modules/has-bigints": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/has-bigints/-/has-bigints-1.0.2.tgz", + "integrity": "sha512-tSvCKtBr9lkF0Ex0aQiP9N+OpV4zi2r/Nee5VkRDbaqv35RLYMzbwQfFSZZH0kR+Rd6302UJZ2p/bJCEoR3VoQ==", + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/has-flag": { + "version": "4.0.0", + "resolved": "https://registry.npmjs.org/has-flag/-/has-flag-4.0.0.tgz", + "integrity": "sha512-EykJT/Q1KjTWctppgIAgfSO0tKVuZUjhgMr17kqTumMl6Afv3EISleU7qZUzoXDFTAHTDC4NOoG/ZxU3EvlMPQ==", + "engines": { + "node": ">=8" + } + }, + "node_modules/has-property-descriptors": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/has-property-descriptors/-/has-property-descriptors-1.0.0.tgz", + "integrity": "sha512-62DVLZGoiEBDHQyqG4w9xCuZ7eJEwNmJRWw2VY84Oedb7WFcA27fiEVe8oUQx9hAUJ4ekurquucTGwsyO1XGdQ==", + "dependencies": { + "get-intrinsic": "^1.1.1" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/has-symbols": { + "version": "1.0.3", + "resolved": "https://registry.npmjs.org/has-symbols/-/has-symbols-1.0.3.tgz", + "integrity": "sha512-l3LCuF6MgDNwTDKkdYGEihYjt5pRPbEg46rtlmnSPlUbgmB8LOIrKJbYYFBSbnPaJexMKtiPO8hmeRjRz2Td+A==", + "engines": { + "node": ">= 0.4" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/has-tostringtag": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/has-tostringtag/-/has-tostringtag-1.0.0.tgz", + "integrity": "sha512-kFjcSNhnlGV1kyoGk7OXKSawH5JOb/LzUc5w9B02hOTO0dfFRjbHQKvg1d6cf3HbeUmtU9VbbV3qzZ2Teh97WQ==", + "dependencies": { + "has-symbols": "^1.0.2" + }, + "engines": { + "node": ">= 0.4" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/hash-base": { + "version": "3.1.0", + "resolved": "https://registry.npmjs.org/hash-base/-/hash-base-3.1.0.tgz", + "integrity": "sha512-1nmYp/rhMDiE7AYkDw+lLwlAzz0AntGIe51F3RfFfEqyQ3feY2eI/NcwC6umIQVOASPMsWJLJScWKSSvzL9IVA==", + "dependencies": { + "inherits": "^2.0.4", + "readable-stream": "^3.6.0", + "safe-buffer": "^5.2.0" + }, + "engines": { + "node": ">=4" + } + }, + "node_modules/hash.js": { + "version": "1.1.7", + "resolved": "https://registry.npmjs.org/hash.js/-/hash.js-1.1.7.tgz", + "integrity": "sha512-taOaskGt4z4SOANNseOviYDvjEJinIkRgmp7LbKP2YTTmVxWBl87s/uzK9r+44BclBSp2X7K1hqeNfz9JbBeXA==", + "dependencies": { + "inherits": "^2.0.3", + "minimalistic-assert": "^1.0.1" + } + }, + "node_modules/he": { + "version": "1.2.0", + "resolved": "https://registry.npmjs.org/he/-/he-1.2.0.tgz", + "integrity": "sha512-F/1DnUGPopORZi0ni+CvrCgHQ5FyEAHRLSApuYWMmrbSwoN2Mn/7k+Gl38gJnR7yyDZk6WLXwiGod1JOWNDKGw==", + "dev": true, + "bin": { + "he": "bin/he" + } + }, + "node_modules/hmac-drbg": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/hmac-drbg/-/hmac-drbg-1.0.1.tgz", + "integrity": "sha512-Tti3gMqLdZfhOQY1Mzf/AanLiqh1WTiJgEj26ZuYQ9fbkLomzGchCws4FyrSd4VkpBfiNhaE1On+lOz894jvXg==", + "dependencies": { + "hash.js": "^1.0.3", + "minimalistic-assert": "^1.0.0", + "minimalistic-crypto-utils": "^1.0.1" + } + }, + "node_modules/hpack.js": { + "version": "2.1.6", + "resolved": "https://registry.npmjs.org/hpack.js/-/hpack.js-2.1.6.tgz", + "integrity": "sha512-zJxVehUdMGIKsRaNt7apO2Gqp0BdqW5yaiGHXXmbpvxgBYVZnAql+BJb4RO5ad2MgpbZKn5G6nMnegrH1FcNYQ==", + "dev": true, + "dependencies": { + "inherits": "^2.0.1", + "obuf": "^1.0.0", + "readable-stream": "^2.0.1", + "wbuf": "^1.1.0" + } + }, + "node_modules/hpack.js/node_modules/readable-stream": { + "version": "2.3.7", + "resolved": "https://registry.npmjs.org/readable-stream/-/readable-stream-2.3.7.tgz", + "integrity": "sha512-Ebho8K4jIbHAxnuxi7o42OrZgF/ZTNcsZj6nRKyUmkhLFq8CHItp/fy6hQZuZmP/n3yZ9VBUbp4zz/mX8hmYPw==", + "dev": true, + "dependencies": { + "core-util-is": "~1.0.0", + "inherits": "~2.0.3", + "isarray": "~1.0.0", + "process-nextick-args": "~2.0.0", + "safe-buffer": "~5.1.1", + "string_decoder": "~1.1.1", + "util-deprecate": "~1.0.1" + } + }, + "node_modules/hpack.js/node_modules/safe-buffer": { + "version": "5.1.2", + "resolved": "https://registry.npmjs.org/safe-buffer/-/safe-buffer-5.1.2.tgz", + "integrity": "sha512-Gd2UZBJDkXlY7GbJxfsE8/nvKkUEU1G38c1siN6QP6a9PT9MmHB8GnpscSmMJSoF8LOIrt8ud/wPtojys4G6+g==", + "dev": true + }, + "node_modules/hpack.js/node_modules/string_decoder": { + "version": "1.1.1", + "resolved": "https://registry.npmjs.org/string_decoder/-/string_decoder-1.1.1.tgz", + "integrity": "sha512-n/ShnvDi6FHbbVfviro+WojiFzv+s8MPMHBczVePfUpDJLwoLT0ht1l4YwBCbi8pJAveEEdnkHyPyTP/mzRfwg==", + "dev": true, + "dependencies": { + "safe-buffer": "~5.1.0" + } + }, + "node_modules/html-entities": { + "version": "2.3.3", + "resolved": "https://registry.npmjs.org/html-entities/-/html-entities-2.3.3.tgz", + "integrity": "sha512-DV5Ln36z34NNTDgnz0EWGBLZENelNAtkiFA4kyNOG2tDI6Mz1uSWiq1wAKdyjnJwyDiDO7Fa2SO1CTxPXL8VxA==", + "dev": true + }, + "node_modules/html-minifier-terser": { + "version": "6.1.0", + "resolved": "https://registry.npmjs.org/html-minifier-terser/-/html-minifier-terser-6.1.0.tgz", + "integrity": "sha512-YXxSlJBZTP7RS3tWnQw74ooKa6L9b9i9QYXY21eUEvhZ3u9XLfv6OnFsQq6RxkhHygsaUMvYsZRV5rU/OVNZxw==", + "dev": true, + "dependencies": { + "camel-case": "^4.1.2", + "clean-css": "^5.2.2", + "commander": "^8.3.0", + "he": "^1.2.0", + "param-case": "^3.0.4", + "relateurl": "^0.2.7", + "terser": "^5.10.0" + }, + "bin": { + "html-minifier-terser": "cli.js" + }, + "engines": { + "node": ">=12" + } + }, + "node_modules/html-webpack-plugin": { + "version": "5.5.0", + "resolved": "https://registry.npmjs.org/html-webpack-plugin/-/html-webpack-plugin-5.5.0.tgz", + "integrity": "sha512-sy88PC2cRTVxvETRgUHFrL4No3UxvcH8G1NepGhqaTT+GXN2kTamqasot0inS5hXeg1cMbFDt27zzo9p35lZVw==", + "dev": true, + "dependencies": { + "@types/html-minifier-terser": "^6.0.0", + "html-minifier-terser": "^6.0.2", + "lodash": "^4.17.21", + "pretty-error": "^4.0.0", + "tapable": "^2.0.0" + }, + "engines": { + "node": ">=10.13.0" + }, + "funding": { + "type": "opencollective", + "url": "https://opencollective.com/html-webpack-plugin" + }, + "peerDependencies": { + "webpack": "^5.20.0" + } + }, + "node_modules/htmlparser2": { + "version": "6.1.0", + "resolved": "https://registry.npmjs.org/htmlparser2/-/htmlparser2-6.1.0.tgz", + "integrity": "sha512-gyyPk6rgonLFEDGoeRgQNaEUvdJ4ktTmmUh/h2t7s+M8oPpIPxgNACWa+6ESR57kXstwqPiCut0V8NRpcwgU7A==", + "dev": true, + "funding": [ + "https://github.com/fb55/htmlparser2?sponsor=1", + { + "type": "github", + "url": "https://github.com/sponsors/fb55" + } + ], + "dependencies": { + "domelementtype": "^2.0.1", + "domhandler": "^4.0.0", + "domutils": "^2.5.2", + "entities": "^2.0.0" + } + }, + "node_modules/http-deceiver": { + "version": "1.2.7", + "resolved": "https://registry.npmjs.org/http-deceiver/-/http-deceiver-1.2.7.tgz", + "integrity": "sha512-LmpOGxTfbpgtGVxJrj5k7asXHCgNZp5nLfp+hWc8QQRqtb7fUy6kRY3BO1h9ddF6yIPYUARgxGOwB42DnxIaNw==", + "dev": true + }, + "node_modules/http-errors": { + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/http-errors/-/http-errors-2.0.0.tgz", + "integrity": "sha512-FtwrG/euBzaEjYeRqOgly7G0qviiXoJWnvEH2Z1plBdXgbyjv34pHTSb9zoeHMyDy33+DWy5Wt9Wo+TURtOYSQ==", + "dev": true, + "dependencies": { + "depd": "2.0.0", + "inherits": "2.0.4", + "setprototypeof": "1.2.0", + "statuses": "2.0.1", + "toidentifier": "1.0.1" + }, + "engines": { + "node": ">= 0.8" + } + }, + "node_modules/http-parser-js": { + "version": "0.5.6", + "resolved": "https://registry.npmjs.org/http-parser-js/-/http-parser-js-0.5.6.tgz", + "integrity": "sha512-vDlkRPDJn93swjcjqMSaGSPABbIarsr1TLAui/gLDXzV5VsJNdXNzMYDyNBLQkjWQCJ1uizu8T2oDMhmGt0PRA==", + "dev": true + }, + "node_modules/http-proxy": { + "version": "1.18.1", + "resolved": "https://registry.npmjs.org/http-proxy/-/http-proxy-1.18.1.tgz", + "integrity": "sha512-7mz/721AbnJwIVbnaSv1Cz3Am0ZLT/UBwkC92VlxhXv/k/BBQfM2fXElQNC27BVGr0uwUpplYPQM9LnaBMR5NQ==", + "dev": true, + "dependencies": { + "eventemitter3": "^4.0.0", + "follow-redirects": "^1.0.0", + "requires-port": "^1.0.0" + }, + "engines": { + "node": ">=8.0.0" + } + }, + "node_modules/http-proxy-middleware": { + "version": "2.0.6", + "resolved": "https://registry.npmjs.org/http-proxy-middleware/-/http-proxy-middleware-2.0.6.tgz", + "integrity": "sha512-ya/UeJ6HVBYxrgYotAZo1KvPWlgB48kUJLDePFeneHsVujFaW5WNj2NgWCAE//B1Dl02BIfYlpNgBy8Kf8Rjmw==", + "dev": true, + "dependencies": { + "@types/http-proxy": "^1.17.8", + "http-proxy": "^1.18.1", + "is-glob": "^4.0.1", + "is-plain-obj": "^3.0.0", + "micromatch": "^4.0.2" + }, + "engines": { + "node": ">=12.0.0" + }, + "peerDependencies": { + "@types/express": "^4.17.13" + }, + "peerDependenciesMeta": { + "@types/express": { + "optional": true + } + } + }, + "node_modules/https-browserify": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/https-browserify/-/https-browserify-1.0.0.tgz", + "integrity": "sha512-J+FkSdyD+0mA0N+81tMotaRMfSL9SGi+xpD3T6YApKsc3bGSXJlfXri3VyFOeYkfLRQisDk1W+jIFFKBeUBbBg==" + }, + "node_modules/https-proxy-agent": { + "version": "5.0.1", + "resolved": "https://registry.npmjs.org/https-proxy-agent/-/https-proxy-agent-5.0.1.tgz", + "integrity": "sha512-dFcAjpTQFgoLMzC2VwU+C/CbS7uRL0lWmxDITmqm7C+7F0Odmj6s9l6alZc6AELXhrnggM2CeWSXHGOdX2YtwA==", + "dependencies": { + "agent-base": "6", + "debug": "4" + }, + "engines": { + "node": ">= 6" + } + }, + "node_modules/https-proxy-agent/node_modules/debug": { + "version": "4.3.4", + "resolved": "https://registry.npmjs.org/debug/-/debug-4.3.4.tgz", + "integrity": "sha512-PRWFHuSU3eDtQJPvnNY7Jcket1j0t5OuOsFzPPzsekD52Zl8qUfFIPEiswXqIvHWGVHOgX+7G/vCNNhehwxfkQ==", + "dependencies": { + "ms": "2.1.2" + }, + "engines": { + "node": ">=6.0" + }, + "peerDependenciesMeta": { + "supports-color": { + "optional": true + } + } + }, + "node_modules/https-proxy-agent/node_modules/ms": { + "version": "2.1.2", + "resolved": "https://registry.npmjs.org/ms/-/ms-2.1.2.tgz", + "integrity": "sha512-sGkPx+VjMtmA6MX27oA4FBFELFCZZ4S4XqeGOXCv68tT+jb3vk/RyaKWP0PTKyWtmLSM0b+adUTEvbs1PEaH2w==" + }, + "node_modules/human-signals": { + "version": "2.1.0", + "resolved": "https://registry.npmjs.org/human-signals/-/human-signals-2.1.0.tgz", + "integrity": "sha512-B4FFZ6q/T2jhhksgkbEW3HBvWIfDW85snkQgawt07S7J5QXTk6BkNV+0yAeZrM5QpMAdYlocGoljn0sJ/WQkFw==", + "dev": true, + "engines": { + "node": ">=10.17.0" + } + }, + "node_modules/iconv-lite": { + "version": "0.4.24", + "resolved": "https://registry.npmjs.org/iconv-lite/-/iconv-lite-0.4.24.tgz", + "integrity": "sha512-v3MXnZAcvnywkTUEZomIActle7RXXeedOR31wwl7VlyoXO4Qi9arvSenNQWne1TcRwhCL1HwLI21bEqdpj8/rA==", + "dev": true, + "dependencies": { + "safer-buffer": ">= 2.1.2 < 3" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/ieee754": { + "version": "1.2.1", + "resolved": "https://registry.npmjs.org/ieee754/-/ieee754-1.2.1.tgz", + "integrity": "sha512-dcyqhDvX1C46lXZcVqCpK+FtMRQVdIMN6/Df5js2zouUsqG7I6sFxitIC+7KYK29KdXOLHdu9zL4sFnoVQnqaA==", + "funding": [ + { + "type": "github", + "url": "https://github.com/sponsors/feross" + }, + { + "type": "patreon", + "url": "https://www.patreon.com/feross" + }, + { + "type": "consulting", + "url": "https://feross.org/support" + } + ] + }, + "node_modules/ignore": { + "version": "5.2.0", + "resolved": "https://registry.npmjs.org/ignore/-/ignore-5.2.0.tgz", + "integrity": "sha512-CmxgYGiEPCLhfLnpPp1MoRmifwEIOgjcHXxOBjv7mY96c+eWScsOP9c112ZyLdWHi0FxHjI+4uVhKYp/gcdRmQ==", + "dev": true, + "engines": { + "node": ">= 4" + } + }, + "node_modules/import-local": { + "version": "3.1.0", + "resolved": "https://registry.npmjs.org/import-local/-/import-local-3.1.0.tgz", + "integrity": "sha512-ASB07uLtnDs1o6EHjKpX34BKYDSqnFerfTOJL2HvMqF70LnxpjkzDB8J44oT9pu4AMPkQwf8jl6szgvNd2tRIg==", + "dev": true, + "dependencies": { + "pkg-dir": "^4.2.0", + "resolve-cwd": "^3.0.0" + }, + "bin": { + "import-local-fixture": "fixtures/cli.js" + }, + "engines": { + "node": ">=8" + }, + "funding": { + "url": "https://github.com/sponsors/sindresorhus" + } + }, + "node_modules/indent-string": { + "version": "4.0.0", + "resolved": "https://registry.npmjs.org/indent-string/-/indent-string-4.0.0.tgz", + "integrity": "sha512-EdDDZu4A2OyIK7Lr/2zG+w5jmbuk1DVBnEwREQvBzspBJkCEbRa8GxU1lghYcaGJCnRWibjDXlq779X1/y5xwg==", + "dev": true, + "engines": { + "node": ">=8" + } + }, + "node_modules/inflight": { + "version": "1.0.6", + "resolved": "https://registry.npmjs.org/inflight/-/inflight-1.0.6.tgz", + "integrity": "sha512-k92I/b08q4wvFscXCLvqfsHCrjrF7yiXsQuIVvVE7N82W3+aqpzuUdBbfhWcy/FZR3/4IgflMgKLOsvPDrGCJA==", + "dependencies": { + "once": "^1.3.0", + "wrappy": "1" + } + }, + "node_modules/inherits": { + "version": "2.0.4", + "resolved": "https://registry.npmjs.org/inherits/-/inherits-2.0.4.tgz", + "integrity": "sha512-k/vGaX4/Yla3WzyMCvTQOXYeIHvqOKtnqBduzTHpzpQZzAskKMhZ2K+EnBiSM9zGSoIFeMpXKxa4dYeZIQqewQ==" + }, + "node_modules/internal-slot": { + "version": "1.0.3", + "resolved": "https://registry.npmjs.org/internal-slot/-/internal-slot-1.0.3.tgz", + "integrity": "sha512-O0DB1JC/sPyZl7cIo78n5dR7eUSwwpYPiXRhTzNxZVAMUuB8vlnRFyLxdrVToks6XPLVnFfbzaVd5WLjhgg+vA==", + "dependencies": { + "get-intrinsic": "^1.1.0", + "has": "^1.0.3", + "side-channel": "^1.0.4" + }, + "engines": { + "node": ">= 0.4" + } + }, + "node_modules/interpret": { + "version": "2.2.0", + "resolved": "https://registry.npmjs.org/interpret/-/interpret-2.2.0.tgz", + "integrity": "sha512-Ju0Bz/cEia55xDwUWEa8+olFpCiQoypjnQySseKtmjNrnps3P+xfpUmGr90T7yjlVJmOtybRvPXhKMbHr+fWnw==", + "dev": true, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/ip": { + "version": "1.1.8", + "resolved": "https://registry.npmjs.org/ip/-/ip-1.1.8.tgz", + "integrity": "sha512-PuExPYUiu6qMBQb4l06ecm6T6ujzhmh+MeJcW9wa89PoAz5pvd4zPgN5WJV104mb6S2T1AwNIAaB70JNrLQWhg==", + "dev": true + }, + "node_modules/ipaddr.js": { + "version": "2.0.1", + "resolved": "https://registry.npmjs.org/ipaddr.js/-/ipaddr.js-2.0.1.tgz", + "integrity": "sha512-1qTgH9NG+IIJ4yfKs2e6Pp1bZg8wbDbKHT21HrLIeYBTRLgMYKnMTPAuI3Lcs61nfx5h1xlXnbJtH1kX5/d/ng==", + "dev": true, + "engines": { + "node": ">= 10" + } + }, + "node_modules/is-alphabetical": { + "version": "1.0.4", + "resolved": "https://registry.npmjs.org/is-alphabetical/-/is-alphabetical-1.0.4.tgz", + "integrity": "sha512-DwzsA04LQ10FHTZuL0/grVDk4rFoVH1pjAToYwBrHSxcrBIGQuXrQMtD5U1b0U2XVgKZCTLLP8u2Qxqhy3l2Vg==", + "funding": { + "type": "github", + "url": "https://github.com/sponsors/wooorm" + } + }, + "node_modules/is-alphanumerical": { + "version": "1.0.4", + "resolved": "https://registry.npmjs.org/is-alphanumerical/-/is-alphanumerical-1.0.4.tgz", + "integrity": "sha512-UzoZUr+XfVz3t3v4KyGEniVL9BDRoQtY7tOyrRybkVNjDFWyo1yhXNGrrBTQxp3ib9BLAWs7k2YKBQsFRkZG9A==", + "dependencies": { + "is-alphabetical": "^1.0.0", + "is-decimal": "^1.0.0" + }, + "funding": { + "type": "github", + "url": "https://github.com/sponsors/wooorm" + } + }, + "node_modules/is-arguments": { + "version": "1.1.1", + "resolved": "https://registry.npmjs.org/is-arguments/-/is-arguments-1.1.1.tgz", + "integrity": "sha512-8Q7EARjzEnKpt/PCD7e1cgUS0a6X8u5tdSiMqXhojOdoV9TsMsiO+9VLC5vAmO8N7/GmXn7yjR8qnA6bVAEzfA==", + "dependencies": { + "call-bind": "^1.0.2", + "has-tostringtag": "^1.0.0" + }, + "engines": { + "node": ">= 0.4" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/is-bigint": { + "version": "1.0.4", + "resolved": "https://registry.npmjs.org/is-bigint/-/is-bigint-1.0.4.tgz", + "integrity": "sha512-zB9CruMamjym81i2JZ3UMn54PKGsQzsJeo6xvN3HJJ4CAsQNB6iRutp2To77OfCNuoxspsIhzaPoO1zyCEhFOg==", + "dependencies": { + "has-bigints": "^1.0.1" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/is-binary-path": { + "version": "2.1.0", + "resolved": "https://registry.npmjs.org/is-binary-path/-/is-binary-path-2.1.0.tgz", + "integrity": "sha512-ZMERYes6pDydyuGidse7OsHxtbI7WVeUEozgR/g7rd0xUimYNlvZRE/K2MgZTjWy725IfelLeVcEM97mmtRGXw==", + "dev": true, + "dependencies": { + "binary-extensions": "^2.0.0" + }, + "engines": { + "node": ">=8" + } + }, + "node_modules/is-boolean-object": { + "version": "1.1.2", + "resolved": "https://registry.npmjs.org/is-boolean-object/-/is-boolean-object-1.1.2.tgz", + "integrity": "sha512-gDYaKHJmnj4aWxyj6YHyXVpdQawtVLHU5cb+eztPGczf6cjuTdwve5ZIEfgXqH4e57An1D1AKf8CZ3kYrQRqYA==", + "dependencies": { + "call-bind": "^1.0.2", + "has-tostringtag": "^1.0.0" + }, + "engines": { + "node": ">= 0.4" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/is-buffer": { + "version": "2.0.5", + "resolved": "https://registry.npmjs.org/is-buffer/-/is-buffer-2.0.5.tgz", + "integrity": "sha512-i2R6zNFDwgEHJyQUtJEk0XFi1i0dPFn/oqjK3/vPCcDeJvW5NQ83V8QbicfF1SupOaB0h8ntgBC2YiE7dfyctQ==", + "funding": [ + { + "type": "github", + "url": "https://github.com/sponsors/feross" + }, + { + "type": "patreon", + "url": "https://www.patreon.com/feross" + }, + { + "type": "consulting", + "url": "https://feross.org/support" + } + ], + "engines": { + "node": ">=4" + } + }, + "node_modules/is-callable": { + "version": "1.2.4", + "resolved": "https://registry.npmjs.org/is-callable/-/is-callable-1.2.4.tgz", + "integrity": "sha512-nsuwtxZfMX67Oryl9LCQ+upnC0Z0BgpwntpS89m1H/TLF0zNfzfLMV/9Wa/6MZsj0acpEjAO0KF1xT6ZdLl95w==", + "engines": { + "node": ">= 0.4" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/is-core-module": { + "version": "2.9.0", + "resolved": "https://registry.npmjs.org/is-core-module/-/is-core-module-2.9.0.tgz", + "integrity": "sha512-+5FPy5PnwmO3lvfMb0AsoPaBG+5KHUI0wYFXOtYPnVVVspTFUuMZNfNaNVRt3FZadstu2c8x23vykRW/NBoU6A==", + "dev": true, + "dependencies": { + "has": "^1.0.3" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/is-date-object": { + "version": "1.0.5", + "resolved": "https://registry.npmjs.org/is-date-object/-/is-date-object-1.0.5.tgz", + "integrity": "sha512-9YQaSxsAiSwcvS33MBk3wTCVnWK+HhF8VZR2jRxehM16QcVOdHqPn4VPHmRK4lSr38n9JriurInLcP90xsYNfQ==", + "dependencies": { + "has-tostringtag": "^1.0.0" + }, + "engines": { + "node": ">= 0.4" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/is-decimal": { + "version": "1.0.4", + "resolved": "https://registry.npmjs.org/is-decimal/-/is-decimal-1.0.4.tgz", + "integrity": "sha512-RGdriMmQQvZ2aqaQq3awNA6dCGtKpiDFcOzrTWrDAT2MiWrKQVPmxLGHl7Y2nNu6led0kEyoX0enY0qXYsv9zw==", + "funding": { + "type": "github", + "url": "https://github.com/sponsors/wooorm" + } + }, + "node_modules/is-docker": { + "version": "2.2.1", + "resolved": "https://registry.npmjs.org/is-docker/-/is-docker-2.2.1.tgz", + "integrity": "sha512-F+i2BKsFrH66iaUFc0woD8sLy8getkwTwtOBjvs56Cx4CgJDeKQeqfz8wAYiSb8JOprWhHH5p77PbmYCvvUuXQ==", + "dev": true, + "bin": { + "is-docker": "cli.js" + }, + "engines": { + "node": ">=8" + }, + "funding": { + "url": "https://github.com/sponsors/sindresorhus" + } + }, + "node_modules/is-extglob": { + "version": "2.1.1", + "resolved": "https://registry.npmjs.org/is-extglob/-/is-extglob-2.1.1.tgz", + "integrity": "sha512-SbKbANkN603Vi4jEZv49LeVJMn4yGwsbzZworEoyEiutsN3nJYdbO36zfhGJ6QEDpOZIFkDtnq5JRxmvl3jsoQ==", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/is-generator-function": { + "version": "1.0.10", + "resolved": "https://registry.npmjs.org/is-generator-function/-/is-generator-function-1.0.10.tgz", + "integrity": "sha512-jsEjy9l3yiXEQ+PsXdmBwEPcOxaXWLspKdplFUVI9vq1iZgIekeC0L167qeu86czQaxed3q/Uzuw0swL0irL8A==", + "dependencies": { + "has-tostringtag": "^1.0.0" + }, + "engines": { + "node": ">= 0.4" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/is-glob": { + "version": "4.0.3", + "resolved": "https://registry.npmjs.org/is-glob/-/is-glob-4.0.3.tgz", + "integrity": "sha512-xelSayHH36ZgE7ZWhli7pW34hNbNl8Ojv5KVmkJD4hBdD3th8Tfk9vYasLM+mXWOZhFkgZfxhLSnrwRr4elSSg==", + "dev": true, + "dependencies": { + "is-extglob": "^2.1.1" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/is-hexadecimal": { + "version": "1.0.4", + "resolved": "https://registry.npmjs.org/is-hexadecimal/-/is-hexadecimal-1.0.4.tgz", + "integrity": "sha512-gyPJuv83bHMpocVYoqof5VDiZveEoGoFL8m3BXNb2VW8Xs+rz9kqO8LOQ5DH6EsuvilT1ApazU0pyl+ytbPtlw==", + "funding": { + "type": "github", + "url": "https://github.com/sponsors/wooorm" + } + }, + "node_modules/is-nan": { + "version": "1.3.2", + "resolved": "https://registry.npmjs.org/is-nan/-/is-nan-1.3.2.tgz", + "integrity": "sha512-E+zBKpQ2t6MEo1VsonYmluk9NxGrbzpeeLC2xIViuO2EjU2xsXsBPwTr3Ykv9l08UYEVEdWeRZNouaZqF6RN0w==", + "dependencies": { + "call-bind": "^1.0.0", + "define-properties": "^1.1.3" + }, + "engines": { + "node": ">= 0.4" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/is-negative-zero": { + "version": "2.0.2", + "resolved": "https://registry.npmjs.org/is-negative-zero/-/is-negative-zero-2.0.2.tgz", + "integrity": "sha512-dqJvarLawXsFbNDeJW7zAz8ItJ9cd28YufuuFzh0G8pNHjJMnY08Dv7sYX2uF5UpQOwieAeOExEYAWWfu7ZZUA==", + "engines": { + "node": ">= 0.4" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/is-number": { + "version": "7.0.0", + "resolved": "https://registry.npmjs.org/is-number/-/is-number-7.0.0.tgz", + "integrity": "sha512-41Cifkg6e8TylSpdtTpeLVMqvSBEVzTttHvERD741+pnZ8ANv0004MRL43QKPDlK9cGvNp6NZWZUBlbGXYxxng==", + "dev": true, + "engines": { + "node": ">=0.12.0" + } + }, + "node_modules/is-number-object": { + "version": "1.0.7", + "resolved": "https://registry.npmjs.org/is-number-object/-/is-number-object-1.0.7.tgz", + "integrity": "sha512-k1U0IRzLMo7ZlYIfzRu23Oh6MiIFasgpb9X76eqfFZAqwH44UI4KTBvBYIZ1dSL9ZzChTB9ShHfLkR4pdW5krQ==", + "dependencies": { + "has-tostringtag": "^1.0.0" + }, + "engines": { + "node": ">= 0.4" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/is-path-cwd": { + "version": "2.2.0", + "resolved": "https://registry.npmjs.org/is-path-cwd/-/is-path-cwd-2.2.0.tgz", + "integrity": "sha512-w942bTcih8fdJPJmQHFzkS76NEP8Kzzvmw92cXsazb8intwLqPibPPdXf4ANdKV3rYMuuQYGIWtvz9JilB3NFQ==", + "dev": true, + "engines": { + "node": ">=6" + } + }, + "node_modules/is-path-inside": { + "version": "3.0.3", + "resolved": "https://registry.npmjs.org/is-path-inside/-/is-path-inside-3.0.3.tgz", + "integrity": "sha512-Fd4gABb+ycGAmKou8eMftCupSir5lRxqf4aD/vd0cD2qc4HL07OjCeuHMr8Ro4CoMaeCKDB0/ECBOVWjTwUvPQ==", + "dev": true, + "engines": { + "node": ">=8" + } + }, + "node_modules/is-plain-obj": { + "version": "3.0.0", + "resolved": "https://registry.npmjs.org/is-plain-obj/-/is-plain-obj-3.0.0.tgz", + "integrity": "sha512-gwsOE28k+23GP1B6vFl1oVh/WOzmawBrKwo5Ev6wMKzPkaXaCDIQKzLnvsA42DRlbVTWorkgTKIviAKCWkfUwA==", + "dev": true, + "engines": { + "node": ">=10" + }, + "funding": { + "url": "https://github.com/sponsors/sindresorhus" + } + }, + "node_modules/is-plain-object": { + "version": "2.0.4", + "resolved": "https://registry.npmjs.org/is-plain-object/-/is-plain-object-2.0.4.tgz", + "integrity": "sha512-h5PpgXkWitc38BBMYawTYMWJHFZJVnBquFE57xFpjB8pJFiF6gZ+bU+WyI/yqXiFR5mdLsgYNaPe8uao6Uv9Og==", + "dev": true, + "dependencies": { + "isobject": "^3.0.1" + }, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/is-regex": { + "version": "1.1.4", + "resolved": "https://registry.npmjs.org/is-regex/-/is-regex-1.1.4.tgz", + "integrity": "sha512-kvRdxDsxZjhzUX07ZnLydzS1TU/TJlTUHHY4YLL87e37oUA49DfkLqgy+VjFocowy29cKvcSiu+kIv728jTTVg==", + "dependencies": { + "call-bind": "^1.0.2", + "has-tostringtag": "^1.0.0" + }, + "engines": { + "node": ">= 0.4" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/is-shared-array-buffer": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/is-shared-array-buffer/-/is-shared-array-buffer-1.0.2.tgz", + "integrity": "sha512-sqN2UDu1/0y6uvXyStCOzyhAjCSlHceFoMKJW8W9EU9cvic/QdsZ0kEU93HEy3IUEFZIiH/3w+AH/UQbPHNdhA==", + "dependencies": { + "call-bind": "^1.0.2" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/is-stream": { + "version": "2.0.1", + "resolved": "https://registry.npmjs.org/is-stream/-/is-stream-2.0.1.tgz", + "integrity": "sha512-hFoiJiTl63nn+kstHGBtewWSKnQLpyb155KHheA1l39uvtO9nWIop1p3udqPcUd/xbF1VLMO4n7OI6p7RbngDg==", + "dev": true, + "engines": { + "node": ">=8" + }, + "funding": { + "url": "https://github.com/sponsors/sindresorhus" + } + }, + "node_modules/is-string": { + "version": "1.0.7", + "resolved": "https://registry.npmjs.org/is-string/-/is-string-1.0.7.tgz", + "integrity": "sha512-tE2UXzivje6ofPW7l23cjDOMa09gb7xlAqG6jG5ej6uPV32TlWP3NKPigtaGeHNu9fohccRYvIiZMfOOnOYUtg==", + "dependencies": { + "has-tostringtag": "^1.0.0" + }, + "engines": { + "node": ">= 0.4" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/is-symbol": { + "version": "1.0.4", + "resolved": "https://registry.npmjs.org/is-symbol/-/is-symbol-1.0.4.tgz", + "integrity": "sha512-C/CPBqKWnvdcxqIARxyOh4v1UUEOCHpgDa0WYgpKDFMszcrPcffg5uhwSgPCLD2WWxmq6isisz87tzT01tuGhg==", + "dependencies": { + "has-symbols": "^1.0.2" + }, + "engines": { + "node": ">= 0.4" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/is-typed-array": { + "version": "1.1.9", + "resolved": "https://registry.npmjs.org/is-typed-array/-/is-typed-array-1.1.9.tgz", + "integrity": "sha512-kfrlnTTn8pZkfpJMUgYD7YZ3qzeJgWUn8XfVYBARc4wnmNOmLbmuuaAs3q5fvB0UJOn6yHAKaGTPM7d6ezoD/A==", + "dependencies": { + "available-typed-arrays": "^1.0.5", + "call-bind": "^1.0.2", + "es-abstract": "^1.20.0", + "for-each": "^0.3.3", + "has-tostringtag": "^1.0.0" + }, + "engines": { + "node": ">= 0.4" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/is-weakref": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/is-weakref/-/is-weakref-1.0.2.tgz", + "integrity": "sha512-qctsuLZmIQ0+vSSMfoVvyFe2+GSEvnmZ2ezTup1SBse9+twCCeial6EEi3Nc2KFcf6+qz2FBPnjXsk8xhKSaPQ==", + "dependencies": { + "call-bind": "^1.0.2" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/is-wsl": { + "version": "2.2.0", + "resolved": "https://registry.npmjs.org/is-wsl/-/is-wsl-2.2.0.tgz", + "integrity": "sha512-fKzAra0rGJUUBwGBgNkHZuToZcn+TtXHpeCgmkMJMMYx1sQDYaCSyjJBSCa2nH1DGm7s3n1oBnohoVTBaN7Lww==", + "dev": true, + "dependencies": { + "is-docker": "^2.0.0" + }, + "engines": { + "node": ">=8" + } + }, + "node_modules/isarray": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/isarray/-/isarray-1.0.0.tgz", + "integrity": "sha512-VLghIWNM6ELQzo7zwmcg0NmTVyWKYjvIeM83yjp0wRDTmUnrM678fQbcKBo6n2CJEF0szoG//ytg+TKla89ALQ==", + "dev": true + }, + "node_modules/isexe": { + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/isexe/-/isexe-2.0.0.tgz", + "integrity": "sha512-RHxMLp9lnKHGHRng9QFhRCMbYAcVpn69smSGcq3f36xjgVVWThj4qqLbTLlq7Ssj8B+fIQ1EuCEGI2lKsyQeIw==", + "dev": true + }, + "node_modules/isobject": { + "version": "3.0.1", + "resolved": "https://registry.npmjs.org/isobject/-/isobject-3.0.1.tgz", + "integrity": "sha512-WhB9zCku7EGTj/HQQRz5aUQEUeoQZH2bWcltRErOpymJ4boYE6wL9Tbr23krRPSZ+C5zqNSrSw+Cc7sZZ4b7vg==", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/jest-worker": { + "version": "27.5.1", + "resolved": "https://registry.npmjs.org/jest-worker/-/jest-worker-27.5.1.tgz", + "integrity": "sha512-7vuh85V5cdDofPyxn58nrPjBktZo0u9x1g8WtjQol+jZDaE+fhN+cIvTj11GndBnMnyfrUOG1sZQxCdjKh+DKg==", + "dependencies": { + "@types/node": "*", + "merge-stream": "^2.0.0", + "supports-color": "^8.0.0" + }, + "engines": { + "node": ">= 10.13.0" + } + }, + "node_modules/json-parse-better-errors": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/json-parse-better-errors/-/json-parse-better-errors-1.0.2.tgz", + "integrity": "sha512-mrqyZKfX5EhL7hvqcV6WG1yYjnjeuYDzDhhcAAUrq8Po85NBQBJP+ZDUT75qZQ98IkUoBqdkExkukOU7Ts2wrw==" + }, + "node_modules/json-schema-traverse": { + "version": "0.4.1", + "resolved": "https://registry.npmjs.org/json-schema-traverse/-/json-schema-traverse-0.4.1.tgz", + "integrity": "sha512-xbbCH5dCYU5T8LcEhhuh7HJ88HXuW3qsI3Y0zOZFKfZEHcpWiHU/Jxzk629Brsab/mMiHQti9wMP+845RPe3Vg==" + }, + "node_modules/jssha": { + "version": "3.2.0", + "resolved": "https://registry.npmjs.org/jssha/-/jssha-3.2.0.tgz", + "integrity": "sha512-QuruyBENDWdN4tZwJbQq7/eAK85FqrI4oDbXjy5IBhYD+2pTJyBUWZe8ctWaCkrV0gy6AaelgOZZBMeswEa/6Q==", + "engines": { + "node": "*" + } + }, + "node_modules/kind-of": { + "version": "6.0.3", + "resolved": "https://registry.npmjs.org/kind-of/-/kind-of-6.0.3.tgz", + "integrity": "sha512-dcS1ul+9tmeD95T+x28/ehLgd9mENa3LsvDTtzm3vyBEO7RPptvAD+t44WVXaUjTBRcrpFeFlC8WCruUR456hw==", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/loader-runner": { + "version": "4.3.0", + "resolved": "https://registry.npmjs.org/loader-runner/-/loader-runner-4.3.0.tgz", + "integrity": "sha512-3R/1M+yS3j5ou80Me59j7F9IMs4PXs3VqRrm0TU3AbKPxlmpoY1TNscJV/oGJXo8qCatFGTfDbY6W6ipGOYXfg==", + "engines": { + "node": ">=6.11.5" + } + }, + "node_modules/locate-path": { + "version": "5.0.0", + "resolved": "https://registry.npmjs.org/locate-path/-/locate-path-5.0.0.tgz", + "integrity": "sha512-t7hw9pI+WvuwNJXwk5zVHpyhIqzg2qTlklJOf0mVxGSbe3Fp2VieZcduNYjaLDoy6p9uGpQEGWG87WpMKlNq8g==", + "dependencies": { + "p-locate": "^4.1.0" + }, + "engines": { + "node": ">=8" + } + }, + "node_modules/lodash": { + "version": "4.17.21", + "resolved": "https://registry.npmjs.org/lodash/-/lodash-4.17.21.tgz", + "integrity": "sha512-v2kDEe57lecTulaDIuNTPy3Ry4gLGJ6Z1O3vE1krgXZNrsQ+LFTGHVxVjcXPs17LhbZVGedAJv8XZ1tvj5FvSg==", + "dev": true + }, + "node_modules/longest-streak": { + "version": "2.0.4", + "resolved": "https://registry.npmjs.org/longest-streak/-/longest-streak-2.0.4.tgz", + "integrity": "sha512-vM6rUVCVUJJt33bnmHiZEvr7wPT78ztX7rojL+LW51bHtLh6HTjx84LA5W4+oa6aKEJA7jJu5LR6vQRBpA5DVg==", + "funding": { + "type": "github", + "url": "https://github.com/sponsors/wooorm" + } + }, + "node_modules/lower-case": { + "version": "2.0.2", + "resolved": "https://registry.npmjs.org/lower-case/-/lower-case-2.0.2.tgz", + "integrity": "sha512-7fm3l3NAF9WfN6W3JOmf5drwpVqX78JtoGJ3A6W0a6ZnldM41w2fV5D490psKFTpMds8TJse/eHLFFsNHHjHgg==", + "dev": true, + "dependencies": { + "tslib": "^2.0.3" + } + }, + "node_modules/markdown-table": { + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/markdown-table/-/markdown-table-2.0.0.tgz", + "integrity": "sha512-Ezda85ToJUBhM6WGaG6veasyym+Tbs3cMAw/ZhOPqXiYsr0jgocBV3j3nx+4lk47plLlIqjwuTm/ywVI+zjJ/A==", + "dependencies": { + "repeat-string": "^1.0.0" + }, + "funding": { + "type": "github", + "url": "https://github.com/sponsors/wooorm" + } + }, + "node_modules/md5.js": { + "version": "1.3.5", + "resolved": "https://registry.npmjs.org/md5.js/-/md5.js-1.3.5.tgz", + "integrity": "sha512-xitP+WxNPcTTOgnTJcrhM0xvdPepipPSf3I8EIpGKeFLjt3PlJLIDG3u8EX53ZIubkb+5U2+3rELYpEhHhzdkg==", + "dependencies": { + "hash-base": "^3.0.0", + "inherits": "^2.0.1", + "safe-buffer": "^5.1.2" + } + }, + "node_modules/mdast-util-find-and-replace": { + "version": "1.1.1", + "resolved": "https://registry.npmjs.org/mdast-util-find-and-replace/-/mdast-util-find-and-replace-1.1.1.tgz", + "integrity": "sha512-9cKl33Y21lyckGzpSmEQnIDjEfeeWelN5s1kUW1LwdB0Fkuq2u+4GdqcGEygYxJE8GVqCl0741bYXHgamfWAZA==", + "dependencies": { + "escape-string-regexp": "^4.0.0", + "unist-util-is": "^4.0.0", + "unist-util-visit-parents": "^3.0.0" + }, + "funding": { + "type": "opencollective", + "url": "https://opencollective.com/unified" + } + }, + "node_modules/mdast-util-footnote": { + "version": "0.1.7", + "resolved": "https://registry.npmjs.org/mdast-util-footnote/-/mdast-util-footnote-0.1.7.tgz", + "integrity": "sha512-QxNdO8qSxqbO2e3m09KwDKfWiLgqyCurdWTQ198NpbZ2hxntdc+VKS4fDJCmNWbAroUdYnSthu+XbZ8ovh8C3w==", + "dependencies": { + "mdast-util-to-markdown": "^0.6.0", + "micromark": "~2.11.0" + }, + "funding": { + "type": "opencollective", + "url": "https://opencollective.com/unified" + } + }, + "node_modules/mdast-util-from-markdown": { + "version": "0.8.5", + "resolved": "https://registry.npmjs.org/mdast-util-from-markdown/-/mdast-util-from-markdown-0.8.5.tgz", + "integrity": "sha512-2hkTXtYYnr+NubD/g6KGBS/0mFmBcifAsI0yIWRiRo0PjVs6SSOSOdtzbp6kSGnShDN6G5aWZpKQ2lWRy27mWQ==", + "dependencies": { + "@types/mdast": "^3.0.0", + "mdast-util-to-string": "^2.0.0", + "micromark": "~2.11.0", + "parse-entities": "^2.0.0", + "unist-util-stringify-position": "^2.0.0" + }, + "funding": { + "type": "opencollective", + "url": "https://opencollective.com/unified" + } + }, + "node_modules/mdast-util-frontmatter": { + "version": "0.2.0", + "resolved": "https://registry.npmjs.org/mdast-util-frontmatter/-/mdast-util-frontmatter-0.2.0.tgz", + "integrity": "sha512-FHKL4w4S5fdt1KjJCwB0178WJ0evnyyQr5kXTM3wrOVpytD0hrkvd+AOOjU9Td8onOejCkmZ+HQRT3CZ3coHHQ==", + "dependencies": { + "micromark-extension-frontmatter": "^0.2.0" + }, + "funding": { + "type": "opencollective", + "url": "https://opencollective.com/unified" + } + }, + "node_modules/mdast-util-gfm": { + "version": "0.1.2", + "resolved": "https://registry.npmjs.org/mdast-util-gfm/-/mdast-util-gfm-0.1.2.tgz", + "integrity": "sha512-NNkhDx/qYcuOWB7xHUGWZYVXvjPFFd6afg6/e2g+SV4r9q5XUcCbV4Wfa3DLYIiD+xAEZc6K4MGaE/m0KDcPwQ==", + "dependencies": { + "mdast-util-gfm-autolink-literal": "^0.1.0", + "mdast-util-gfm-strikethrough": "^0.2.0", + "mdast-util-gfm-table": "^0.1.0", + "mdast-util-gfm-task-list-item": "^0.1.0", + "mdast-util-to-markdown": "^0.6.1" + }, + "funding": { + "type": "opencollective", + "url": "https://opencollective.com/unified" + } + }, + "node_modules/mdast-util-gfm-autolink-literal": { + "version": "0.1.3", + "resolved": "https://registry.npmjs.org/mdast-util-gfm-autolink-literal/-/mdast-util-gfm-autolink-literal-0.1.3.tgz", + "integrity": "sha512-GjmLjWrXg1wqMIO9+ZsRik/s7PLwTaeCHVB7vRxUwLntZc8mzmTsLVr6HW1yLokcnhfURsn5zmSVdi3/xWWu1A==", + "dependencies": { + "ccount": "^1.0.0", + "mdast-util-find-and-replace": "^1.1.0", + "micromark": "^2.11.3" + }, + "funding": { + "type": "opencollective", + "url": "https://opencollective.com/unified" + } + }, + "node_modules/mdast-util-gfm-strikethrough": { + "version": "0.2.3", + "resolved": "https://registry.npmjs.org/mdast-util-gfm-strikethrough/-/mdast-util-gfm-strikethrough-0.2.3.tgz", + "integrity": "sha512-5OQLXpt6qdbttcDG/UxYY7Yjj3e8P7X16LzvpX8pIQPYJ/C2Z1qFGMmcw+1PZMUM3Z8wt8NRfYTvCni93mgsgA==", + "dependencies": { + "mdast-util-to-markdown": "^0.6.0" + }, + "funding": { + "type": "opencollective", + "url": "https://opencollective.com/unified" + } + }, + "node_modules/mdast-util-gfm-table": { + "version": "0.1.6", + "resolved": "https://registry.npmjs.org/mdast-util-gfm-table/-/mdast-util-gfm-table-0.1.6.tgz", + "integrity": "sha512-j4yDxQ66AJSBwGkbpFEp9uG/LS1tZV3P33fN1gkyRB2LoRL+RR3f76m0HPHaby6F4Z5xr9Fv1URmATlRRUIpRQ==", + "dependencies": { + "markdown-table": "^2.0.0", + "mdast-util-to-markdown": "~0.6.0" + }, + "funding": { + "type": "opencollective", + "url": "https://opencollective.com/unified" + } + }, + "node_modules/mdast-util-gfm-task-list-item": { + "version": "0.1.6", + "resolved": "https://registry.npmjs.org/mdast-util-gfm-task-list-item/-/mdast-util-gfm-task-list-item-0.1.6.tgz", + "integrity": "sha512-/d51FFIfPsSmCIRNp7E6pozM9z1GYPIkSy1urQ8s/o4TC22BZ7DqfHFWiqBD23bc7J3vV1Fc9O4QIHBlfuit8A==", + "dependencies": { + "mdast-util-to-markdown": "~0.6.0" + }, + "funding": { + "type": "opencollective", + "url": "https://opencollective.com/unified" + } + }, + "node_modules/mdast-util-to-markdown": { + "version": "0.6.5", + "resolved": "https://registry.npmjs.org/mdast-util-to-markdown/-/mdast-util-to-markdown-0.6.5.tgz", + "integrity": "sha512-XeV9sDE7ZlOQvs45C9UKMtfTcctcaj/pGwH8YLbMHoMOXNNCn2LsqVQOqrF1+/NU8lKDAqozme9SCXWyo9oAcQ==", + "dependencies": { + "@types/unist": "^2.0.0", + "longest-streak": "^2.0.0", + "mdast-util-to-string": "^2.0.0", + "parse-entities": "^2.0.0", + "repeat-string": "^1.0.0", + "zwitch": "^1.0.0" + }, + "funding": { + "type": "opencollective", + "url": "https://opencollective.com/unified" + } + }, + "node_modules/mdast-util-to-string": { + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/mdast-util-to-string/-/mdast-util-to-string-2.0.0.tgz", + "integrity": "sha512-AW4DRS3QbBayY/jJmD8437V1Gombjf8RSOUCMFBuo5iHi58AGEgVCKQ+ezHkZZDpAQS75hcBMpLqjpJTjtUL7w==", + "funding": { + "type": "opencollective", + "url": "https://opencollective.com/unified" + } + }, + "node_modules/media-typer": { + "version": "0.3.0", + "resolved": "https://registry.npmjs.org/media-typer/-/media-typer-0.3.0.tgz", + "integrity": "sha512-dq+qelQ9akHpcOl/gUVRTxVIOkAJ1wR3QAvb4RsVjS8oVoFjDGTc679wJYmUmknUF5HwMLOgb5O+a3KxfWapPQ==", + "dev": true, + "engines": { + "node": ">= 0.6" + } + }, + "node_modules/memfs": { + "version": "3.4.6", + "resolved": "https://registry.npmjs.org/memfs/-/memfs-3.4.6.tgz", + "integrity": "sha512-rH9mjopto6Wkr7RFuH9l9dk3qb2XGOcYKr7xMhaYqfzuJqOqhRrcFvfD7JMuPj6SLmPreh5+6eAuv36NFAU+Mw==", + "dev": true, + "dependencies": { + "fs-monkey": "^1.0.3" + }, + "engines": { + "node": ">= 4.0.0" + } + }, + "node_modules/merge-descriptors": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/merge-descriptors/-/merge-descriptors-1.0.1.tgz", + "integrity": "sha512-cCi6g3/Zr1iqQi6ySbseM1Xvooa98N0w31jzUYrXPX2xqObmFGHJ0tQ5u74H3mVh7wLouTseZyYIq39g8cNp1w==", + "dev": true + }, + "node_modules/merge-stream": { + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/merge-stream/-/merge-stream-2.0.0.tgz", + "integrity": "sha512-abv/qOcuPfk3URPfDzmZU1LKmuw8kT+0nIHvKrKgFrwifol/doWcdA4ZqsWQ8ENrFKkd67Mfpo/LovbIUsbt3w==" + }, + "node_modules/merge2": { + "version": "1.4.1", + "resolved": "https://registry.npmjs.org/merge2/-/merge2-1.4.1.tgz", + "integrity": "sha512-8q7VEgMJW4J8tcfVPy8g09NcQwZdbwFEqhe/WZkoIzjn/3TGDwtOCYtXGxA3O8tPzpczCCDgv+P2P5y00ZJOOg==", + "dev": true, + "engines": { + "node": ">= 8" + } + }, + "node_modules/methods": { + "version": "1.1.2", + "resolved": "https://registry.npmjs.org/methods/-/methods-1.1.2.tgz", + "integrity": "sha512-iclAHeNqNm68zFtnZ0e+1L2yUIdvzNoauKU4WBA3VvH/vPFieF7qfRlwUZU+DA9P9bPXIS90ulxoUoCH23sV2w==", + "dev": true, + "engines": { + "node": ">= 0.6" + } + }, + "node_modules/micromark": { + "version": "2.11.4", + "resolved": "https://registry.npmjs.org/micromark/-/micromark-2.11.4.tgz", + "integrity": "sha512-+WoovN/ppKolQOFIAajxi7Lu9kInbPxFuTBVEavFcL8eAfVstoc5MocPmqBeAdBOJV00uaVjegzH4+MA0DN/uA==", + "funding": [ + { + "type": "GitHub Sponsors", + "url": "https://github.com/sponsors/unifiedjs" + }, + { + "type": "OpenCollective", + "url": "https://opencollective.com/unified" + } + ], + "dependencies": { + "debug": "^4.0.0", + "parse-entities": "^2.0.0" + } + }, + "node_modules/micromark-extension-footnote": { + "version": "0.3.2", + "resolved": "https://registry.npmjs.org/micromark-extension-footnote/-/micromark-extension-footnote-0.3.2.tgz", + "integrity": "sha512-gr/BeIxbIWQoUm02cIfK7mdMZ/fbroRpLsck4kvFtjbzP4yi+OPVbnukTc/zy0i7spC2xYE/dbX1Sur8BEDJsQ==", + "dependencies": { + "micromark": "~2.11.0" + }, + "funding": { + "type": "opencollective", + "url": "https://opencollective.com/unified" + } + }, + "node_modules/micromark-extension-frontmatter": { + "version": "0.2.2", + "resolved": "https://registry.npmjs.org/micromark-extension-frontmatter/-/micromark-extension-frontmatter-0.2.2.tgz", + "integrity": "sha512-q6nPLFCMTLtfsctAuS0Xh4vaolxSFUWUWR6PZSrXXiRy+SANGllpcqdXFv2z07l0Xz/6Hl40hK0ffNCJPH2n1A==", + "dependencies": { + "fault": "^1.0.0" + }, + "funding": { + "type": "opencollective", + "url": "https://opencollective.com/unified" + } + }, + "node_modules/micromark-extension-gfm": { + "version": "0.3.3", + "resolved": "https://registry.npmjs.org/micromark-extension-gfm/-/micromark-extension-gfm-0.3.3.tgz", + "integrity": "sha512-oVN4zv5/tAIA+l3GbMi7lWeYpJ14oQyJ3uEim20ktYFAcfX1x3LNlFGGlmrZHt7u9YlKExmyJdDGaTt6cMSR/A==", + "dependencies": { + "micromark": "~2.11.0", + "micromark-extension-gfm-autolink-literal": "~0.5.0", + "micromark-extension-gfm-strikethrough": "~0.6.5", + "micromark-extension-gfm-table": "~0.4.0", + "micromark-extension-gfm-tagfilter": "~0.3.0", + "micromark-extension-gfm-task-list-item": "~0.3.0" + }, + "funding": { + "type": "opencollective", + "url": "https://opencollective.com/unified" + } + }, + "node_modules/micromark-extension-gfm-autolink-literal": { + "version": "0.5.7", + "resolved": "https://registry.npmjs.org/micromark-extension-gfm-autolink-literal/-/micromark-extension-gfm-autolink-literal-0.5.7.tgz", + "integrity": "sha512-ePiDGH0/lhcngCe8FtH4ARFoxKTUelMp4L7Gg2pujYD5CSMb9PbblnyL+AAMud/SNMyusbS2XDSiPIRcQoNFAw==", + "dependencies": { + "micromark": "~2.11.3" + }, + "funding": { + "type": "opencollective", + "url": "https://opencollective.com/unified" + } + }, + "node_modules/micromark-extension-gfm-strikethrough": { + "version": "0.6.5", + "resolved": "https://registry.npmjs.org/micromark-extension-gfm-strikethrough/-/micromark-extension-gfm-strikethrough-0.6.5.tgz", + "integrity": "sha512-PpOKlgokpQRwUesRwWEp+fHjGGkZEejj83k9gU5iXCbDG+XBA92BqnRKYJdfqfkrRcZRgGuPuXb7DaK/DmxOhw==", + "dependencies": { + "micromark": "~2.11.0" + }, + "funding": { + "type": "opencollective", + "url": "https://opencollective.com/unified" + } + }, + "node_modules/micromark-extension-gfm-table": { + "version": "0.4.3", + "resolved": "https://registry.npmjs.org/micromark-extension-gfm-table/-/micromark-extension-gfm-table-0.4.3.tgz", + "integrity": "sha512-hVGvESPq0fk6ALWtomcwmgLvH8ZSVpcPjzi0AjPclB9FsVRgMtGZkUcpE0zgjOCFAznKepF4z3hX8z6e3HODdA==", + "dependencies": { + "micromark": "~2.11.0" + }, + "funding": { + "type": "opencollective", + "url": "https://opencollective.com/unified" + } + }, + "node_modules/micromark-extension-gfm-tagfilter": { + "version": "0.3.0", + "resolved": "https://registry.npmjs.org/micromark-extension-gfm-tagfilter/-/micromark-extension-gfm-tagfilter-0.3.0.tgz", + "integrity": "sha512-9GU0xBatryXifL//FJH+tAZ6i240xQuFrSL7mYi8f4oZSbc+NvXjkrHemeYP0+L4ZUT+Ptz3b95zhUZnMtoi/Q==", + "funding": { + "type": "opencollective", + "url": "https://opencollective.com/unified" + } + }, + "node_modules/micromark-extension-gfm-task-list-item": { + "version": "0.3.3", + "resolved": "https://registry.npmjs.org/micromark-extension-gfm-task-list-item/-/micromark-extension-gfm-task-list-item-0.3.3.tgz", + "integrity": "sha512-0zvM5iSLKrc/NQl84pZSjGo66aTGd57C1idmlWmE87lkMcXrTxg1uXa/nXomxJytoje9trP0NDLvw4bZ/Z/XCQ==", + "dependencies": { + "micromark": "~2.11.0" + }, + "funding": { + "type": "opencollective", + "url": "https://opencollective.com/unified" + } + }, + "node_modules/micromark/node_modules/debug": { + "version": "4.3.4", + "resolved": "https://registry.npmjs.org/debug/-/debug-4.3.4.tgz", + "integrity": "sha512-PRWFHuSU3eDtQJPvnNY7Jcket1j0t5OuOsFzPPzsekD52Zl8qUfFIPEiswXqIvHWGVHOgX+7G/vCNNhehwxfkQ==", + "dependencies": { + "ms": "2.1.2" + }, + "engines": { + "node": ">=6.0" + }, + "peerDependenciesMeta": { + "supports-color": { + "optional": true + } + } + }, + "node_modules/micromark/node_modules/ms": { + "version": "2.1.2", + "resolved": "https://registry.npmjs.org/ms/-/ms-2.1.2.tgz", + "integrity": "sha512-sGkPx+VjMtmA6MX27oA4FBFELFCZZ4S4XqeGOXCv68tT+jb3vk/RyaKWP0PTKyWtmLSM0b+adUTEvbs1PEaH2w==" + }, + "node_modules/micromatch": { + "version": "4.0.5", + "resolved": "https://registry.npmjs.org/micromatch/-/micromatch-4.0.5.tgz", + "integrity": "sha512-DMy+ERcEW2q8Z2Po+WNXuw3c5YaUSFjAO5GsJqfEl7UjvtIuFKO6ZrKvcItdy98dwFI2N1tg3zNIdKaQT+aNdA==", + "dev": true, + "dependencies": { + "braces": "^3.0.2", + "picomatch": "^2.3.1" + }, + "engines": { + "node": ">=8.6" + } + }, + "node_modules/miller-rabin": { + "version": "4.0.1", + "resolved": "https://registry.npmjs.org/miller-rabin/-/miller-rabin-4.0.1.tgz", + "integrity": "sha512-115fLhvZVqWwHPbClyntxEVfVDfl9DLLTuJvq3g2O/Oxi8AiNouAHvDSzHS0viUJc+V5vm3eq91Xwqn9dp4jRA==", + "dependencies": { + "bn.js": "^4.0.0", + "brorand": "^1.0.1" + }, + "bin": { + "miller-rabin": "bin/miller-rabin" + } + }, + "node_modules/miller-rabin/node_modules/bn.js": { + "version": "4.12.0", + "resolved": "https://registry.npmjs.org/bn.js/-/bn.js-4.12.0.tgz", + "integrity": "sha512-c98Bf3tPniI+scsdk237ku1Dc3ujXQTSgyiPUDEOe7tRkhrqridvh8klBv0HCEso1OLOYcHuCv/cS6DNxKH+ZA==" + }, + "node_modules/mime": { + "version": "1.6.0", + "resolved": "https://registry.npmjs.org/mime/-/mime-1.6.0.tgz", + "integrity": "sha512-x0Vn8spI+wuJ1O6S7gnbaQg8Pxh4NNHb7KSINmEWKiPE4RKOplvijn+NkmYmmRgP68mc70j2EbeTFRsrswaQeg==", + "dev": true, + "bin": { + "mime": "cli.js" + }, + "engines": { + "node": ">=4" + } + }, + "node_modules/mime-db": { + "version": "1.52.0", + "resolved": "https://registry.npmjs.org/mime-db/-/mime-db-1.52.0.tgz", + "integrity": "sha512-sPU4uV7dYlvtWJxwwxHD0PuihVNiE7TyAbQ5SWxDCB9mUYvOgroQOwYQQOKPJ8CIbE+1ETVlOoK1UC2nU3gYvg==", + "engines": { + "node": ">= 0.6" + } + }, + "node_modules/mime-types": { + "version": "2.1.35", + "resolved": "https://registry.npmjs.org/mime-types/-/mime-types-2.1.35.tgz", + "integrity": "sha512-ZDY+bPm5zTTF+YpCrAU9nK0UgICYPT0QtT1NZWFv4s++TNkcgVaT0g6+4R2uI4MjQjzysHB1zxuWL50hzaeXiw==", + "dependencies": { + "mime-db": "1.52.0" + }, + "engines": { + "node": ">= 0.6" + } + }, + "node_modules/mimic-fn": { + "version": "2.1.0", + "resolved": "https://registry.npmjs.org/mimic-fn/-/mimic-fn-2.1.0.tgz", + "integrity": "sha512-OqbOk5oEQeAZ8WXWydlu9HJjz9WVdEIvamMCcXmuqUYjTknH/sqsWvhQ3vgwKFRR1HpjvNBKQ37nbJgYzGqGcg==", + "dev": true, + "engines": { + "node": ">=6" + } + }, + "node_modules/minimalistic-assert": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/minimalistic-assert/-/minimalistic-assert-1.0.1.tgz", + "integrity": "sha512-UtJcAD4yEaGtjPezWuO9wC4nwUnVH/8/Im3yEHQP4b67cXlD/Qr9hdITCU1xDbSEXg2XKNaP8jsReV7vQd00/A==" + }, + "node_modules/minimalistic-crypto-utils": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/minimalistic-crypto-utils/-/minimalistic-crypto-utils-1.0.1.tgz", + "integrity": "sha512-JIYlbt6g8i5jKfJ3xz7rF0LXmv2TkDxBLUkiBeZ7bAx4GnnNMr8xFpGnOxn6GhTEHx3SjRrZEoU+j04prX1ktg==" + }, + "node_modules/minimatch": { + "version": "3.1.2", + "resolved": "https://registry.npmjs.org/minimatch/-/minimatch-3.1.2.tgz", + "integrity": "sha512-J7p63hRiAjw1NDEww1W7i37+ByIrOWO5XQQAzZ3VOcL0PNybwpfmV/N05zFAzwQ9USyEcX6t3UO+K5aqBQOIHw==", + "dependencies": { + "brace-expansion": "^1.1.7" + }, + "engines": { + "node": "*" + } + }, + "node_modules/minimist": { + "version": "1.2.6", + "resolved": "https://registry.npmjs.org/minimist/-/minimist-1.2.6.tgz", + "integrity": "sha512-Jsjnk4bw3YJqYzbdyBiNsPWHPfO++UGG749Cxs6peCu5Xg4nrena6OVxOYxrQTqww0Jmwt+Ref8rggumkTLz9Q==" + }, + "node_modules/mkdirp": { + "version": "0.5.6", + "resolved": "https://registry.npmjs.org/mkdirp/-/mkdirp-0.5.6.tgz", + "integrity": "sha512-FP+p8RB8OWpF3YZBCrP5gtADmtXApB5AMLn+vdyA+PyxCjrCs00mjyUozssO33cwDeT3wNGdLxJ5M//YqtHAJw==", + "dev": true, + "dependencies": { + "minimist": "^1.2.6" + }, + "bin": { + "mkdirp": "bin/cmd.js" + } + }, + "node_modules/mkdirp-classic": { + "version": "0.5.3", + "resolved": "https://registry.npmjs.org/mkdirp-classic/-/mkdirp-classic-0.5.3.tgz", + "integrity": "sha512-gKLcREMhtuZRwRAfqP3RFW+TK4JqApVBtOIftVgjuABpAtpxhPGaDcfvbhNvD0B8iD1oUr/txX35NjcaY6Ns/A==" + }, + "node_modules/ms": { + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/ms/-/ms-2.0.0.tgz", + "integrity": "sha512-Tpp60P6IUJDTuOq/5Z8cdskzJujfwqfOTkrwIwj7IRISpnkJnT6SyJ4PCPnGMoFjC9ddhal5KVIYtAt97ix05A==", + "dev": true + }, + "node_modules/multicast-dns": { + "version": "6.2.3", + "resolved": "https://registry.npmjs.org/multicast-dns/-/multicast-dns-6.2.3.tgz", + "integrity": "sha512-ji6J5enbMyGRHIAkAOu3WdV8nggqviKCEKtXcOqfphZZtQrmHKycfynJ2V7eVPUA4NhJ6V7Wf4TmGbTwKE9B6g==", + "dev": true, + "dependencies": { + "dns-packet": "^1.3.1", + "thunky": "^1.0.2" + }, + "bin": { + "multicast-dns": "cli.js" + } + }, + "node_modules/multicast-dns-service-types": { + "version": "1.1.0", + "resolved": "https://registry.npmjs.org/multicast-dns-service-types/-/multicast-dns-service-types-1.1.0.tgz", + "integrity": "sha512-cnAsSVxIDsYt0v7HmC0hWZFwwXSh+E6PgCrREDuN/EsjgLwA5XRmlMHhSiDPrt6HxY1gTivEa/Zh7GtODoLevQ==", + "dev": true + }, + "node_modules/negotiator": { + "version": "0.6.3", + "resolved": "https://registry.npmjs.org/negotiator/-/negotiator-0.6.3.tgz", + "integrity": "sha512-+EUsqGPLsM+j/zdChZjsnX51g4XrHFOIXwfnCVPGlQk/k5giakcKsuxCObBRu6DSm9opw/O6slWbJdghQM4bBg==", + "dev": true, + "engines": { + "node": ">= 0.6" + } + }, + "node_modules/neo-async": { + "version": "2.6.2", + "resolved": "https://registry.npmjs.org/neo-async/-/neo-async-2.6.2.tgz", + "integrity": "sha512-Yd3UES5mWCSqR+qNT93S3UoYUkqAZ9lLg8a7g9rimsWmYGK8cVToA4/sF3RrshdyV3sAGMXVUmpMYOw+dLpOuw==" + }, + "node_modules/no-case": { + "version": "3.0.4", + "resolved": "https://registry.npmjs.org/no-case/-/no-case-3.0.4.tgz", + "integrity": "sha512-fgAN3jGAh+RoxUGZHTSOLJIqUc2wmoBwGR4tbpNAKmmovFoWq0OdRkb0VkldReO2a2iBT/OEulG9XSUc10r3zg==", + "dev": true, + "dependencies": { + "lower-case": "^2.0.2", + "tslib": "^2.0.3" + } + }, + "node_modules/node-fetch": { + "version": "2.6.7", + "resolved": "https://registry.npmjs.org/node-fetch/-/node-fetch-2.6.7.tgz", + "integrity": "sha512-ZjMPFEfVx5j+y2yF35Kzx5sF7kDzxuDj6ziH4FFbOp87zKDZNx8yExJIb05OGF4Nlt9IHFIMBkRl41VdvcNdbQ==", + "dependencies": { + "whatwg-url": "^5.0.0" + }, + "engines": { + "node": "4.x || >=6.0.0" + }, + "peerDependencies": { + "encoding": "^0.1.0" + }, + "peerDependenciesMeta": { + "encoding": { + "optional": true + } + } + }, + "node_modules/node-fetch/node_modules/tr46": { + "version": "0.0.3", + "resolved": "https://registry.npmjs.org/tr46/-/tr46-0.0.3.tgz", + "integrity": "sha512-N3WMsuqV66lT30CrXNbEjx4GEwlow3v6rr4mCcv6prnfwhS01rkgyFdjPNBYd9br7LpXV1+Emh01fHnq2Gdgrw==" + }, + "node_modules/node-fetch/node_modules/webidl-conversions": { + "version": "3.0.1", + "resolved": "https://registry.npmjs.org/webidl-conversions/-/webidl-conversions-3.0.1.tgz", + "integrity": "sha512-2JAn3z8AR6rjK8Sm8orRC0h/bcl/DqL7tRPdGZ4I1CjdF+EaMLmYxBHyXuKL849eucPFhvBoxMsflfOb8kxaeQ==" + }, + "node_modules/node-fetch/node_modules/whatwg-url": { + "version": "5.0.0", + "resolved": "https://registry.npmjs.org/whatwg-url/-/whatwg-url-5.0.0.tgz", + "integrity": "sha512-saE57nupxk6v3HY35+jzBwYa0rKSy0XR8JSxZPwgLr7ys0IBzhGviA1/TUGJLmSVqs8pb9AnvICXEuOHLprYTw==", + "dependencies": { + "tr46": "~0.0.3", + "webidl-conversions": "^3.0.0" + } + }, + "node_modules/node-forge": { + "version": "1.3.1", + "resolved": "https://registry.npmjs.org/node-forge/-/node-forge-1.3.1.tgz", + "integrity": "sha512-dPEtOeMvF9VMcYV/1Wb8CPoVAXtp6MKMlcbAt4ddqmGqUJ6fQZFXkNZNkNlfevtNkGtaSoXf/vNNNSvgrdXwtA==", + "dev": true, + "engines": { + "node": ">= 6.13.0" + } + }, + "node_modules/node-gyp-build": { + "version": "4.4.0", + "resolved": "https://registry.npmjs.org/node-gyp-build/-/node-gyp-build-4.4.0.tgz", + "integrity": "sha512-amJnQCcgtRVw9SvoebO3BKGESClrfXGCUTX9hSn1OuGQTQBOZmVd0Z0OlecpuRksKvbsUqALE8jls/ErClAPuQ==", + "bin": { + "node-gyp-build": "bin.js", + "node-gyp-build-optional": "optional.js", + "node-gyp-build-test": "build-test.js" + } + }, + "node_modules/node-polyfill-webpack-plugin": { + "version": "1.1.4", + "resolved": "https://registry.npmjs.org/node-polyfill-webpack-plugin/-/node-polyfill-webpack-plugin-1.1.4.tgz", + "integrity": "sha512-Z0XTKj1wRWO8o/Vjobsw5iOJCN+Sua3EZEUc2Ziy9CyVvmHKu6o+t4gUH9GOE0czyPR94LI6ZCV/PpcM8b5yow==", + "dependencies": { + "assert": "^2.0.0", + "browserify-zlib": "^0.2.0", + "buffer": "^6.0.3", + "console-browserify": "^1.2.0", + "constants-browserify": "^1.0.0", + "crypto-browserify": "^3.12.0", + "domain-browser": "^4.19.0", + "events": "^3.3.0", + "filter-obj": "^2.0.2", + "https-browserify": "^1.0.0", + "os-browserify": "^0.3.0", + "path-browserify": "^1.0.1", + "process": "^0.11.10", + "punycode": "^2.1.1", + "querystring-es3": "^0.2.1", + "readable-stream": "^3.6.0", + "stream-browserify": "^3.0.0", + "stream-http": "^3.2.0", + "string_decoder": "^1.3.0", + "timers-browserify": "^2.0.12", + "tty-browserify": "^0.0.1", + "url": "^0.11.0", + "util": "^0.12.4", + "vm-browserify": "^1.1.2" + }, + "engines": { + "node": ">=10" + }, + "peerDependencies": { + "webpack": ">=5" + } + }, + "node_modules/node-releases": { + "version": "2.0.5", + "resolved": "https://registry.npmjs.org/node-releases/-/node-releases-2.0.5.tgz", + "integrity": "sha512-U9h1NLROZTq9uE1SNffn6WuPDg8icmi3ns4rEl/oTfIle4iLjTliCzgTsbaIFMq/Xn078/lfY/BL0GWZ+psK4Q==" + }, + "node_modules/normalize-path": { + "version": "3.0.0", + "resolved": "https://registry.npmjs.org/normalize-path/-/normalize-path-3.0.0.tgz", + "integrity": "sha512-6eZs5Ls3WtCisHWp9S2GUy8dqkpGi4BVSz3GaqiE6ezub0512ESztXUwUB6C6IKbQkY2Pnb/mD4WYojCRwcwLA==", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/npm-run-path": { + "version": "4.0.1", + "resolved": "https://registry.npmjs.org/npm-run-path/-/npm-run-path-4.0.1.tgz", + "integrity": "sha512-S48WzZW777zhNIrn7gxOlISNAqi9ZC/uQFnRdbeIHhZhCA6UqpkOT8T1G7BvfdgP4Er8gF4sUbaS0i7QvIfCWw==", + "dev": true, + "dependencies": { + "path-key": "^3.0.0" + }, + "engines": { + "node": ">=8" + } + }, + "node_modules/nth-check": { + "version": "2.1.1", + "resolved": "https://registry.npmjs.org/nth-check/-/nth-check-2.1.1.tgz", + "integrity": "sha512-lqjrjmaOoAnWfMmBPL+XNnynZh2+swxiX3WUE0s4yEHI6m+AwrK2UZOimIRl3X/4QctVqS8AiZjFqyOGrMXb/w==", + "dev": true, + "dependencies": { + "boolbase": "^1.0.0" + }, + "funding": { + "url": "https://github.com/fb55/nth-check?sponsor=1" + } + }, + "node_modules/object-inspect": { + "version": "1.12.1", + "resolved": "https://registry.npmjs.org/object-inspect/-/object-inspect-1.12.1.tgz", + "integrity": "sha512-Y/jF6vnvEtOPGiKD1+q+X0CiUYRQtEHp89MLLUJ7TUivtH8Ugn2+3A7Rynqk7BRsAoqeOQWnFnjpDrKSxDgIGA==", + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/object-is": { + "version": "1.1.5", + "resolved": "https://registry.npmjs.org/object-is/-/object-is-1.1.5.tgz", + "integrity": "sha512-3cyDsyHgtmi7I7DfSSI2LDp6SK2lwvtbg0p0R1e0RvTqF5ceGx+K2dfSjm1bKDMVCFEDAQvy+o8c6a7VujOddw==", + "dependencies": { + "call-bind": "^1.0.2", + "define-properties": "^1.1.3" + }, + "engines": { + "node": ">= 0.4" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/object-keys": { + "version": "1.1.1", + "resolved": "https://registry.npmjs.org/object-keys/-/object-keys-1.1.1.tgz", + "integrity": "sha512-NuAESUOUMrlIXOfHKzD6bpPu3tYt3xvjNdRIQ+FeT0lNb4K8WR70CaDxhuNguS2XG+GjkyMwOzsN5ZktImfhLA==", + "engines": { + "node": ">= 0.4" + } + }, + "node_modules/object.assign": { + "version": "4.1.2", + "resolved": "https://registry.npmjs.org/object.assign/-/object.assign-4.1.2.tgz", + "integrity": "sha512-ixT2L5THXsApyiUPYKmW+2EHpXXe5Ii3M+f4e+aJFAHao5amFRW6J0OO6c/LU8Be47utCx2GL89hxGB6XSmKuQ==", + "dependencies": { + "call-bind": "^1.0.0", + "define-properties": "^1.1.3", + "has-symbols": "^1.0.1", + "object-keys": "^1.1.1" + }, + "engines": { + "node": ">= 0.4" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/obuf": { + "version": "1.1.2", + "resolved": "https://registry.npmjs.org/obuf/-/obuf-1.1.2.tgz", + "integrity": "sha512-PX1wu0AmAdPqOL1mWhqmlOd8kOIZQwGZw6rh7uby9fTc5lhaOWFLX3I6R1hrF9k3zUY40e6igsLGkDXK92LJNg==", + "dev": true + }, + "node_modules/on-finished": { + "version": "2.4.1", + "resolved": "https://registry.npmjs.org/on-finished/-/on-finished-2.4.1.tgz", + "integrity": "sha512-oVlzkg3ENAhCk2zdv7IJwd/QUD4z2RxRwpkcGY8psCVcCYZNq4wYnVWALHM+brtuJjePWiYF/ClmuDr8Ch5+kg==", + "dev": true, + "dependencies": { + "ee-first": "1.1.1" + }, + "engines": { + "node": ">= 0.8" + } + }, + "node_modules/on-headers": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/on-headers/-/on-headers-1.0.2.tgz", + "integrity": "sha512-pZAE+FJLoyITytdqK0U5s+FIpjN0JP3OzFi/u8Rx+EV5/W+JTWGXG8xFzevE7AjBfDqHv/8vL8qQsIhHnqRkrA==", + "dev": true, + "engines": { + "node": ">= 0.8" + } + }, + "node_modules/once": { + "version": "1.4.0", + "resolved": "https://registry.npmjs.org/once/-/once-1.4.0.tgz", + "integrity": "sha512-lNaJgI+2Q5URQBkccEKHTQOPaXdUxnZZElQTZY0MFUAuaEqe1E+Nyvgdz/aIyNi6Z9MzO5dv1H8n58/GELp3+w==", + "dependencies": { + "wrappy": "1" + } + }, + "node_modules/onetime": { + "version": "5.1.2", + "resolved": "https://registry.npmjs.org/onetime/-/onetime-5.1.2.tgz", + "integrity": "sha512-kbpaSSGJTWdAY5KPVeMOKXSrPtr8C8C7wodJbcsd51jRnmD+GZu8Y0VoU6Dm5Z4vWr0Ig/1NKuWRKf7j5aaYSg==", + "dev": true, + "dependencies": { + "mimic-fn": "^2.1.0" + }, + "engines": { + "node": ">=6" + }, + "funding": { + "url": "https://github.com/sponsors/sindresorhus" + } + }, + "node_modules/open": { + "version": "8.4.0", + "resolved": "https://registry.npmjs.org/open/-/open-8.4.0.tgz", + "integrity": "sha512-XgFPPM+B28FtCCgSb9I+s9szOC1vZRSwgWsRUA5ylIxRTgKozqjOCrVOqGsYABPYK5qnfqClxZTFBa8PKt2v6Q==", + "dev": true, + "dependencies": { + "define-lazy-prop": "^2.0.0", + "is-docker": "^2.1.1", + "is-wsl": "^2.2.0" + }, + "engines": { + "node": ">=12" + }, + "funding": { + "url": "https://github.com/sponsors/sindresorhus" + } + }, + "node_modules/os-browserify": { + "version": "0.3.0", + "resolved": "https://registry.npmjs.org/os-browserify/-/os-browserify-0.3.0.tgz", + "integrity": "sha512-gjcpUc3clBf9+210TRaDWbf+rZZZEshZ+DlXMRCeAjp0xhTrnQsKHypIy1J3d5hKdUzj69t708EHtU8P6bUn0A==" + }, + "node_modules/p-limit": { + "version": "2.3.0", + "resolved": "https://registry.npmjs.org/p-limit/-/p-limit-2.3.0.tgz", + "integrity": "sha512-//88mFWSJx8lxCzwdAABTJL2MyWB12+eIY7MDL2SqLmAkeKU9qxRvWuSyTjm3FUmpBEMuFfckAIqEaVGUDxb6w==", + "dependencies": { + "p-try": "^2.0.0" + }, + "engines": { + "node": ">=6" + }, + "funding": { + "url": "https://github.com/sponsors/sindresorhus" + } + }, + "node_modules/p-locate": { + "version": "4.1.0", + "resolved": "https://registry.npmjs.org/p-locate/-/p-locate-4.1.0.tgz", + "integrity": "sha512-R79ZZ/0wAxKGu3oYMlz8jy/kbhsNrS7SKZ7PxEHBgJ5+F2mtFW2fK2cOtBh1cHYkQsbzFV7I+EoRKe6Yt0oK7A==", + "dependencies": { + "p-limit": "^2.2.0" + }, + "engines": { + "node": ">=8" + } + }, + "node_modules/p-map": { + "version": "4.0.0", + "resolved": "https://registry.npmjs.org/p-map/-/p-map-4.0.0.tgz", + "integrity": "sha512-/bjOqmgETBYB5BoEeGVea8dmvHb2m9GLy1E9W43yeyfP6QQCZGFNa+XRceJEuDB6zqr+gKpIAmlLebMpykw/MQ==", + "dev": true, + "dependencies": { + "aggregate-error": "^3.0.0" + }, + "engines": { + "node": ">=10" + }, + "funding": { + "url": "https://github.com/sponsors/sindresorhus" + } + }, + "node_modules/p-retry": { + "version": "4.6.2", + "resolved": "https://registry.npmjs.org/p-retry/-/p-retry-4.6.2.tgz", + "integrity": "sha512-312Id396EbJdvRONlngUx0NydfrIQ5lsYu0znKVUzVvArzEIt08V1qhtyESbGVd1FGX7UKtiFp5uwKZdM8wIuQ==", + "dev": true, + "dependencies": { + "@types/retry": "0.12.0", + "retry": "^0.13.1" + }, + "engines": { + "node": ">=8" + } + }, + "node_modules/p-try": { + "version": "2.2.0", + "resolved": "https://registry.npmjs.org/p-try/-/p-try-2.2.0.tgz", + "integrity": "sha512-R4nPAVTAU0B9D35/Gk3uJf/7XYbQcyohSKdvAxIRSNghFl4e71hVoGnBNQz9cWaXxO2I10KTC+3jMdvvoKw6dQ==", + "engines": { + "node": ">=6" + } + }, + "node_modules/pako": { + "version": "1.0.11", + "resolved": "https://registry.npmjs.org/pako/-/pako-1.0.11.tgz", + "integrity": "sha512-4hLB8Py4zZce5s4yd9XzopqwVv/yGNhV1Bl8NTmCq1763HeK2+EwVTv+leGeL13Dnh2wfbqowVPXCIO0z4taYw==" + }, + "node_modules/param-case": { + "version": "3.0.4", + "resolved": "https://registry.npmjs.org/param-case/-/param-case-3.0.4.tgz", + "integrity": "sha512-RXlj7zCYokReqWpOPH9oYivUzLYZ5vAPIfEmCTNViosC78F8F0H9y7T7gG2M39ymgutxF5gcFEsyZQSph9Bp3A==", + "dev": true, + "dependencies": { + "dot-case": "^3.0.4", + "tslib": "^2.0.3" + } + }, + "node_modules/parse-asn1": { + "version": "5.1.6", + "resolved": "https://registry.npmjs.org/parse-asn1/-/parse-asn1-5.1.6.tgz", + "integrity": "sha512-RnZRo1EPU6JBnra2vGHj0yhp6ebyjBZpmUCLHWiFhxlzvBCCpAuZ7elsBp1PVAbQN0/04VD/19rfzlBSwLstMw==", + "dependencies": { + "asn1.js": "^5.2.0", + "browserify-aes": "^1.0.0", + "evp_bytestokey": "^1.0.0", + "pbkdf2": "^3.0.3", + "safe-buffer": "^5.1.1" + } + }, + "node_modules/parse-entities": { + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/parse-entities/-/parse-entities-2.0.0.tgz", + "integrity": "sha512-kkywGpCcRYhqQIchaWqZ875wzpS/bMKhz5HnN3p7wveJTkTtyAB/AlnS0f8DFSqYW1T82t6yEAkEcB+A1I3MbQ==", + "dependencies": { + "character-entities": "^1.0.0", + "character-entities-legacy": "^1.0.0", + "character-reference-invalid": "^1.0.0", + "is-alphanumerical": "^1.0.0", + "is-decimal": "^1.0.0", + "is-hexadecimal": "^1.0.0" + }, + "funding": { + "type": "github", + "url": "https://github.com/sponsors/wooorm" + } + }, + "node_modules/parseurl": { + "version": "1.3.3", + "resolved": "https://registry.npmjs.org/parseurl/-/parseurl-1.3.3.tgz", + "integrity": "sha512-CiyeOxFT/JZyN5m0z9PfXw4SCBJ6Sygz1Dpl0wqjlhDEGGBP1GnsUVEL0p63hoG1fcj3fHynXi9NYO4nWOL+qQ==", + "dev": true, + "engines": { + "node": ">= 0.8" + } + }, + "node_modules/pascal-case": { + "version": "3.1.2", + "resolved": "https://registry.npmjs.org/pascal-case/-/pascal-case-3.1.2.tgz", + "integrity": "sha512-uWlGT3YSnK9x3BQJaOdcZwrnV6hPpd8jFH1/ucpiLRPh/2zCVJKS19E4GvYHvaCcACn3foXZ0cLB9Wrx1KGe5g==", + "dev": true, + "dependencies": { + "no-case": "^3.0.4", + "tslib": "^2.0.3" + } + }, + "node_modules/path-browserify": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/path-browserify/-/path-browserify-1.0.1.tgz", + "integrity": "sha512-b7uo2UCUOYZcnF/3ID0lulOJi/bafxa1xPe7ZPsammBSpjSWQkjNxlt635YGS2MiR9GjvuXCtz2emr3jbsz98g==" + }, + "node_modules/path-exists": { + "version": "4.0.0", + "resolved": "https://registry.npmjs.org/path-exists/-/path-exists-4.0.0.tgz", + "integrity": "sha512-ak9Qy5Q7jYb2Wwcey5Fpvg2KoAc/ZIhLSLOSBmRmygPsGwkVVt0fZa0qrtMz+m6tJTAHfZQ8FnmB4MG4LWy7/w==", + "engines": { + "node": ">=8" + } + }, + "node_modules/path-is-absolute": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/path-is-absolute/-/path-is-absolute-1.0.1.tgz", + "integrity": "sha512-AVbw3UJ2e9bq64vSaS9Am0fje1Pa8pbGqTTsmXfaIiMpnr5DlDhfJOuLj9Sf95ZPVDAUerDfEk88MPmPe7UCQg==", + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/path-key": { + "version": "3.1.1", + "resolved": "https://registry.npmjs.org/path-key/-/path-key-3.1.1.tgz", + "integrity": "sha512-ojmeN0qd+y0jszEtoY48r0Peq5dwMEkIlCOu6Q5f41lfkswXuKtYrhgoTpLnyIcHm24Uhqx+5Tqm2InSwLhE6Q==", + "dev": true, + "engines": { + "node": ">=8" + } + }, + "node_modules/path-parse": { + "version": "1.0.7", + "resolved": "https://registry.npmjs.org/path-parse/-/path-parse-1.0.7.tgz", + "integrity": "sha512-LDJzPVEEEPR+y48z93A0Ed0yXb8pAByGWo/k5YYdYgpY2/2EsOsksJrq7lOHxryrVOn1ejG6oAp8ahvOIQD8sw==", + "dev": true + }, + "node_modules/path-to-regexp": { + "version": "0.1.7", + "resolved": "https://registry.npmjs.org/path-to-regexp/-/path-to-regexp-0.1.7.tgz", + "integrity": "sha512-5DFkuoqlv1uYQKxy8omFBeJPQcdoE07Kv2sferDCrAq1ohOU+MSDswDIbnx3YAM60qIOnYa53wBhXW0EbMonrQ==", + "dev": true + }, + "node_modules/path-type": { + "version": "4.0.0", + "resolved": "https://registry.npmjs.org/path-type/-/path-type-4.0.0.tgz", + "integrity": "sha512-gDKb8aZMDeD/tZWs9P6+q0J9Mwkdl6xMV8TjnGP3qJVJ06bdMgkbBlLU8IdfOsIsFz2BW1rNVT3XuNEl8zPAvw==", + "dev": true, + "engines": { + "node": ">=8" + } + }, + "node_modules/pbkdf2": { + "version": "3.1.2", + "resolved": "https://registry.npmjs.org/pbkdf2/-/pbkdf2-3.1.2.tgz", + "integrity": "sha512-iuh7L6jA7JEGu2WxDwtQP1ddOpaJNC4KlDEFfdQajSGgGPNi4OyDc2R7QnbY2bR9QjBVGwgvTdNJZoE7RaxUMA==", + "dependencies": { + "create-hash": "^1.1.2", + "create-hmac": "^1.1.4", + "ripemd160": "^2.0.1", + "safe-buffer": "^5.0.1", + "sha.js": "^2.4.8" + }, + "engines": { + "node": ">=0.12" + } + }, + "node_modules/pend": { + "version": "1.2.0", + "resolved": "https://registry.npmjs.org/pend/-/pend-1.2.0.tgz", + "integrity": "sha512-F3asv42UuXchdzt+xXqfW1OGlVBe+mxa2mqI0pg5yAHZPvFmY3Y6drSf/GQ1A86WgWEN9Kzh/WrgKa6iGcHXLg==" + }, + "node_modules/picocolors": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/picocolors/-/picocolors-1.0.0.tgz", + "integrity": "sha512-1fygroTLlHu66zi26VoTDv8yRgm0Fccecssto+MhsZ0D/DGW2sm8E8AjW7NU5VVTRt5GxbeZ5qBuJr+HyLYkjQ==" + }, + "node_modules/picomatch": { + "version": "2.3.1", + "resolved": "https://registry.npmjs.org/picomatch/-/picomatch-2.3.1.tgz", + "integrity": "sha512-JU3teHTNjmE2VCGFzuY8EXzCDVwEqB2a8fsIvwaStHhAWJEeVd1o1QD80CU6+ZdEXXSLbSsuLwJjkCBWqRQUVA==", + "dev": true, + "engines": { + "node": ">=8.6" + }, + "funding": { + "url": "https://github.com/sponsors/jonschlinkert" + } + }, + "node_modules/pkg-dir": { + "version": "4.2.0", + "resolved": "https://registry.npmjs.org/pkg-dir/-/pkg-dir-4.2.0.tgz", + "integrity": "sha512-HRDzbaKjC+AOWVXxAU/x54COGeIv9eb+6CkDSQoNTt4XyWoIJvuPsXizxu/Fr23EiekbtZwmh1IcIG/l/a10GQ==", + "dependencies": { + "find-up": "^4.0.0" + }, + "engines": { + "node": ">=8" + } + }, + "node_modules/portfinder": { + "version": "1.0.28", + "resolved": "https://registry.npmjs.org/portfinder/-/portfinder-1.0.28.tgz", + "integrity": "sha512-Se+2isanIcEqf2XMHjyUKskczxbPH7dQnlMjXX6+dybayyHvAf/TCgyMRlzf/B6QDhAEFOGes0pzRo3by4AbMA==", + "dev": true, + "dependencies": { + "async": "^2.6.2", + "debug": "^3.1.1", + "mkdirp": "^0.5.5" + }, + "engines": { + "node": ">= 0.12.0" + } + }, + "node_modules/portfinder/node_modules/debug": { + "version": "3.2.7", + "resolved": "https://registry.npmjs.org/debug/-/debug-3.2.7.tgz", + "integrity": "sha512-CFjzYYAi4ThfiQvizrFQevTTXHtnCqWfe7x1AhgEscTz6ZbLbfoLRLPugTQyBth6f8ZERVUSyWHFD/7Wu4t1XQ==", + "dev": true, + "dependencies": { + "ms": "^2.1.1" + } + }, + "node_modules/portfinder/node_modules/ms": { + "version": "2.1.3", + "resolved": "https://registry.npmjs.org/ms/-/ms-2.1.3.tgz", + "integrity": "sha512-6FlzubTLZG3J2a/NVCAleEhjzq5oxgHyaCU9yYXvcLsvoVaHJq/s5xXI6/XXP6tz7R9xAOtHnSO/tXtF3WRTlA==", + "dev": true + }, + "node_modules/pretty-error": { + "version": "4.0.0", + "resolved": "https://registry.npmjs.org/pretty-error/-/pretty-error-4.0.0.tgz", + "integrity": "sha512-AoJ5YMAcXKYxKhuJGdcvse+Voc6v1RgnsR3nWcYU7q4t6z0Q6T86sv5Zq8VIRbOWWFpvdGE83LtdSMNd+6Y0xw==", + "dev": true, + "dependencies": { + "lodash": "^4.17.20", + "renderkid": "^3.0.0" + } + }, + "node_modules/process": { + "version": "0.11.10", + "resolved": "https://registry.npmjs.org/process/-/process-0.11.10.tgz", + "integrity": "sha512-cdGef/drWFoydD1JsMzuFf8100nZl+GT+yacc2bEced5f9Rjk4z+WtFUTBu9PhOi9j/jfmBPu0mMEY4wIdAF8A==", + "engines": { + "node": ">= 0.6.0" + } + }, + "node_modules/process-nextick-args": { + "version": "2.0.1", + "resolved": "https://registry.npmjs.org/process-nextick-args/-/process-nextick-args-2.0.1.tgz", + "integrity": "sha512-3ouUOpQhtgrbOa17J7+uxOTpITYWaGP7/AhoR3+A+/1e9skrzelGi/dXzEYyvbxubEF6Wn2ypscTKiKJFFn1ag==", + "dev": true + }, + "node_modules/progress": { + "version": "2.0.3", + "resolved": "https://registry.npmjs.org/progress/-/progress-2.0.3.tgz", + "integrity": "sha512-7PiHtLll5LdnKIMw100I+8xJXR5gW2QwWYkT6iJva0bXitZKa/XMrSbdmg3r2Xnaidz9Qumd0VPaMrZlF9V9sA==", + "engines": { + "node": ">=0.4.0" + } + }, + "node_modules/proxy-addr": { + "version": "2.0.7", + "resolved": "https://registry.npmjs.org/proxy-addr/-/proxy-addr-2.0.7.tgz", + "integrity": "sha512-llQsMLSUDUPT44jdrU/O37qlnifitDP+ZwrmmZcoSKyLKvtZxpyV0n2/bD/N4tBAAZ/gJEdZU7KMraoK1+XYAg==", + "dev": true, + "dependencies": { + "forwarded": "0.2.0", + "ipaddr.js": "1.9.1" + }, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/proxy-addr/node_modules/ipaddr.js": { + "version": "1.9.1", + "resolved": "https://registry.npmjs.org/ipaddr.js/-/ipaddr.js-1.9.1.tgz", + "integrity": "sha512-0KI/607xoxSToH7GjN1FfSbLoU0+btTicjsQSWQlh/hZykN8KpmMf7uYwPW3R+akZ6R/w18ZlXSHBYXiYUPO3g==", + "dev": true, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/proxy-from-env": { + "version": "1.1.0", + "resolved": "https://registry.npmjs.org/proxy-from-env/-/proxy-from-env-1.1.0.tgz", + "integrity": "sha512-D+zkORCbA9f1tdWRK0RaCR3GPv50cMxcrz4X8k5LTSUD1Dkw47mKJEZQNunItRTkWwgtaUSo1RVFRIG9ZXiFYg==" + }, + "node_modules/public-encrypt": { + "version": "4.0.3", + "resolved": "https://registry.npmjs.org/public-encrypt/-/public-encrypt-4.0.3.tgz", + "integrity": "sha512-zVpa8oKZSz5bTMTFClc1fQOnyyEzpl5ozpi1B5YcvBrdohMjH2rfsBtyXcuNuwjsDIXmBYlF2N5FlJYhR29t8Q==", + "dependencies": { + "bn.js": "^4.1.0", + "browserify-rsa": "^4.0.0", + "create-hash": "^1.1.0", + "parse-asn1": "^5.0.0", + "randombytes": "^2.0.1", + "safe-buffer": "^5.1.2" + } + }, + "node_modules/public-encrypt/node_modules/bn.js": { + "version": "4.12.0", + "resolved": "https://registry.npmjs.org/bn.js/-/bn.js-4.12.0.tgz", + "integrity": "sha512-c98Bf3tPniI+scsdk237ku1Dc3ujXQTSgyiPUDEOe7tRkhrqridvh8klBv0HCEso1OLOYcHuCv/cS6DNxKH+ZA==" + }, + "node_modules/pump": { + "version": "3.0.0", + "resolved": "https://registry.npmjs.org/pump/-/pump-3.0.0.tgz", + "integrity": "sha512-LwZy+p3SFs1Pytd/jYct4wpv49HiYCqd9Rlc5ZVdk0V+8Yzv6jR5Blk3TRmPL1ft69TxP0IMZGJ+WPFU2BFhww==", + "dependencies": { + "end-of-stream": "^1.1.0", + "once": "^1.3.1" + } + }, + "node_modules/punycode": { + "version": "2.1.1", + "resolved": "https://registry.npmjs.org/punycode/-/punycode-2.1.1.tgz", + "integrity": "sha512-XRsRjdf+j5ml+y/6GKHPZbrF/8p2Yga0JPtdqTIY2Xe5ohJPD9saDJJLPvp9+NSBprVvevdXZybnj2cv8OEd0A==", + "engines": { + "node": ">=6" + } + }, + "node_modules/puppeteer-core": { + "version": "15.3.2", + "resolved": "https://registry.npmjs.org/puppeteer-core/-/puppeteer-core-15.3.2.tgz", + "integrity": "sha512-Fmca9UzXmJkRrvGBgUmrffGD2BlulUTfsVefV1+vqfNm4PnlZ/U1bfD6X8XQ0nftyyg520tmSKd81yH3Z2tszg==", + "dependencies": { + "cross-fetch": "3.1.5", + "debug": "4.3.4", + "devtools-protocol": "0.0.1011705", + "extract-zip": "2.0.1", + "https-proxy-agent": "5.0.1", + "pkg-dir": "4.2.0", + "progress": "2.0.3", + "proxy-from-env": "1.1.0", + "rimraf": "3.0.2", + "tar-fs": "2.1.1", + "unbzip2-stream": "1.4.3", + "ws": "8.8.0" + }, + "engines": { + "node": ">=14.1.0" + } + }, + "node_modules/puppeteer-core/node_modules/debug": { + "version": "4.3.4", + "resolved": "https://registry.npmjs.org/debug/-/debug-4.3.4.tgz", + "integrity": "sha512-PRWFHuSU3eDtQJPvnNY7Jcket1j0t5OuOsFzPPzsekD52Zl8qUfFIPEiswXqIvHWGVHOgX+7G/vCNNhehwxfkQ==", + "dependencies": { + "ms": "2.1.2" + }, + "engines": { + "node": ">=6.0" + }, + "peerDependenciesMeta": { + "supports-color": { + "optional": true + } + } + }, + "node_modules/puppeteer-core/node_modules/ms": { + "version": "2.1.2", + "resolved": "https://registry.npmjs.org/ms/-/ms-2.1.2.tgz", + "integrity": "sha512-sGkPx+VjMtmA6MX27oA4FBFELFCZZ4S4XqeGOXCv68tT+jb3vk/RyaKWP0PTKyWtmLSM0b+adUTEvbs1PEaH2w==" + }, + "node_modules/puppeteer-core/node_modules/ws": { + "version": "8.8.0", + "resolved": "https://registry.npmjs.org/ws/-/ws-8.8.0.tgz", + "integrity": "sha512-JDAgSYQ1ksuwqfChJusw1LSJ8BizJ2e/vVu5Lxjq3YvNJNlROv1ui4i+c/kUUrPheBvQl4c5UbERhTwKa6QBJQ==", + "engines": { + "node": ">=10.0.0" + }, + "peerDependencies": { + "bufferutil": "^4.0.1", + "utf-8-validate": "^5.0.2" + }, + "peerDependenciesMeta": { + "bufferutil": { + "optional": true + }, + "utf-8-validate": { + "optional": true + } + } + }, + "node_modules/qs": { + "version": "6.10.3", + "resolved": "https://registry.npmjs.org/qs/-/qs-6.10.3.tgz", + "integrity": "sha512-wr7M2E0OFRfIfJZjKGieI8lBKb7fRCH4Fv5KNPEs7gJ8jadvotdsS08PzOKR7opXhZ/Xkjtt3WF9g38drmyRqQ==", + "dev": true, + "dependencies": { + "side-channel": "^1.0.4" + }, + "engines": { + "node": ">=0.6" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/querystring": { + "version": "0.2.0", + "resolved": "https://registry.npmjs.org/querystring/-/querystring-0.2.0.tgz", + "integrity": "sha512-X/xY82scca2tau62i9mDyU9K+I+djTMUsvwf7xnUX5GLvVzgJybOJf4Y6o9Zx3oJK/LSXg5tTZBjwzqVPaPO2g==", + "deprecated": "The querystring API is considered Legacy. new code should use the URLSearchParams API instead.", + "engines": { + "node": ">=0.4.x" + } + }, + "node_modules/querystring-es3": { + "version": "0.2.1", + "resolved": "https://registry.npmjs.org/querystring-es3/-/querystring-es3-0.2.1.tgz", + "integrity": "sha512-773xhDQnZBMFobEiztv8LIl70ch5MSF/jUQVlhwFyBILqq96anmoctVIYz+ZRp0qbCKATTn6ev02M3r7Ga5vqA==", + "engines": { + "node": ">=0.4.x" + } + }, + "node_modules/queue-microtask": { + "version": "1.2.3", + "resolved": "https://registry.npmjs.org/queue-microtask/-/queue-microtask-1.2.3.tgz", + "integrity": "sha512-NuaNSa6flKT5JaSYQzJok04JzTL1CA6aGhv5rfLW3PgqA+M2ChpZQnAC8h8i4ZFkBS8X5RqkDBHA7r4hej3K9A==", + "dev": true, + "funding": [ + { + "type": "github", + "url": "https://github.com/sponsors/feross" + }, + { + "type": "patreon", + "url": "https://www.patreon.com/feross" + }, + { + "type": "consulting", + "url": "https://feross.org/support" + } + ] + }, + "node_modules/randombytes": { + "version": "2.1.0", + "resolved": "https://registry.npmjs.org/randombytes/-/randombytes-2.1.0.tgz", + "integrity": "sha512-vYl3iOX+4CKUWuxGi9Ukhie6fsqXqS9FE2Zaic4tNFD2N2QQaXOMFbuKK4QmDHC0JO6B1Zp41J0LpT0oR68amQ==", + "dependencies": { + "safe-buffer": "^5.1.0" + } + }, + "node_modules/randomfill": { + "version": "1.0.4", + "resolved": "https://registry.npmjs.org/randomfill/-/randomfill-1.0.4.tgz", + "integrity": "sha512-87lcbR8+MhcWcUiQ+9e+Rwx8MyR2P7qnt15ynUlbm3TU/fjbgz4GsvfSUDTemtCCtVCqb4ZcEFlyPNTh9bBTLw==", + "dependencies": { + "randombytes": "^2.0.5", + "safe-buffer": "^5.1.0" + } + }, + "node_modules/range-parser": { + "version": "1.2.1", + "resolved": "https://registry.npmjs.org/range-parser/-/range-parser-1.2.1.tgz", + "integrity": "sha512-Hrgsx+orqoygnmhFbKaHE6c296J+HTAQXoxEF6gNupROmmGJRoyzfG3ccAveqCBrwr/2yxQ5BVd/GTl5agOwSg==", + "dev": true, + "engines": { + "node": ">= 0.6" + } + }, + "node_modules/raw-body": { + "version": "2.5.1", + "resolved": "https://registry.npmjs.org/raw-body/-/raw-body-2.5.1.tgz", + "integrity": "sha512-qqJBtEyVgS0ZmPGdCFPWJ3FreoqvG4MVQln/kCgF7Olq95IbOp0/BWyMwbdtn4VTvkM8Y7khCQ2Xgk/tcrCXig==", + "dev": true, + "dependencies": { + "bytes": "3.1.2", + "http-errors": "2.0.0", + "iconv-lite": "0.4.24", + "unpipe": "1.0.0" + }, + "engines": { + "node": ">= 0.8" + } + }, + "node_modules/raw-body/node_modules/bytes": { + "version": "3.1.2", + "resolved": "https://registry.npmjs.org/bytes/-/bytes-3.1.2.tgz", + "integrity": "sha512-/Nf7TyzTx6S3yRJObOAV7956r8cr2+Oj8AC5dt8wSP3BQAoeX58NoHyCU8P8zGkNXStjTSi6fzO6F0pBdcYbEg==", + "dev": true, + "engines": { + "node": ">= 0.8" + } + }, + "node_modules/readable-stream": { + "version": "3.6.0", + "resolved": "https://registry.npmjs.org/readable-stream/-/readable-stream-3.6.0.tgz", + "integrity": "sha512-BViHy7LKeTz4oNnkcLJ+lVSL6vpiFeX6/d3oSH8zCW7UxP2onchk+vTGB143xuFjHS3deTgkKoXXymXqymiIdA==", + "dependencies": { + "inherits": "^2.0.3", + "string_decoder": "^1.1.1", + "util-deprecate": "^1.0.1" + }, + "engines": { + "node": ">= 6" + } + }, + "node_modules/readdirp": { + "version": "3.6.0", + "resolved": "https://registry.npmjs.org/readdirp/-/readdirp-3.6.0.tgz", + "integrity": "sha512-hOS089on8RduqdbhvQ5Z37A0ESjsqz6qnRcffsMU3495FuTdqSm+7bhJ29JvIOsBDEEnan5DPu9t3To9VRlMzA==", + "dev": true, + "dependencies": { + "picomatch": "^2.2.1" + }, + "engines": { + "node": ">=8.10.0" + } + }, + "node_modules/rechoir": { + "version": "0.7.1", + "resolved": "https://registry.npmjs.org/rechoir/-/rechoir-0.7.1.tgz", + "integrity": "sha512-/njmZ8s1wVeR6pjTZ+0nCnv8SpZNRMT2D1RLOJQESlYFDBvwpTA4KWJpZ+sBJ4+vhjILRcK7JIFdGCdxEAAitg==", + "dev": true, + "dependencies": { + "resolve": "^1.9.0" + }, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/reconnecting-websocket": { + "version": "4.4.0", + "resolved": "https://registry.npmjs.org/reconnecting-websocket/-/reconnecting-websocket-4.4.0.tgz", + "integrity": "sha512-D2E33ceRPga0NvTDhJmphEgJ7FUYF0v4lr1ki0csq06OdlxKfugGzN0dSkxM/NfqCxYELK4KcaTOUOjTV6Dcng==" + }, + "node_modules/regexp.prototype.flags": { + "version": "1.4.3", + "resolved": "https://registry.npmjs.org/regexp.prototype.flags/-/regexp.prototype.flags-1.4.3.tgz", + "integrity": "sha512-fjggEOO3slI6Wvgjwflkc4NFRCTZAu5CnNfBd5qOMYhWdn67nJBBu34/TkD++eeFmd8C9r9jfXJ27+nSiRkSUA==", + "dependencies": { + "call-bind": "^1.0.2", + "define-properties": "^1.1.3", + "functions-have-names": "^1.2.2" + }, + "engines": { + "node": ">= 0.4" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/relateurl": { + "version": "0.2.7", + "resolved": "https://registry.npmjs.org/relateurl/-/relateurl-0.2.7.tgz", + "integrity": "sha512-G08Dxvm4iDN3MLM0EsP62EDV9IuhXPR6blNz6Utcp7zyV3tr4HVNINt6MpaRWbxoOHT3Q7YN2P+jaHX8vUbgog==", + "dev": true, + "engines": { + "node": ">= 0.10" + } + }, + "node_modules/remark-footnotes": { + "version": "3.0.0", + "resolved": "https://registry.npmjs.org/remark-footnotes/-/remark-footnotes-3.0.0.tgz", + "integrity": "sha512-ZssAvH9FjGYlJ/PBVKdSmfyPc3Cz4rTWgZLI4iE/SX8Nt5l3o3oEjv3wwG5VD7xOjktzdwp5coac+kJV9l4jgg==", + "dependencies": { + "mdast-util-footnote": "^0.1.0", + "micromark-extension-footnote": "^0.3.0" + }, + "funding": { + "type": "opencollective", + "url": "https://opencollective.com/unified" + } + }, + "node_modules/remark-frontmatter": { + "version": "3.0.0", + "resolved": "https://registry.npmjs.org/remark-frontmatter/-/remark-frontmatter-3.0.0.tgz", + "integrity": "sha512-mSuDd3svCHs+2PyO29h7iijIZx4plX0fheacJcAoYAASfgzgVIcXGYSq9GFyYocFLftQs8IOmmkgtOovs6d4oA==", + "dependencies": { + "mdast-util-frontmatter": "^0.2.0", + "micromark-extension-frontmatter": "^0.2.0" + }, + "funding": { + "type": "opencollective", + "url": "https://opencollective.com/unified" + } + }, + "node_modules/remark-gfm": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/remark-gfm/-/remark-gfm-1.0.0.tgz", + "integrity": "sha512-KfexHJCiqvrdBZVbQ6RopMZGwaXz6wFJEfByIuEwGf0arvITHjiKKZ1dpXujjH9KZdm1//XJQwgfnJ3lmXaDPA==", + "dependencies": { + "mdast-util-gfm": "^0.1.0", + "micromark-extension-gfm": "^0.3.0" + }, + "funding": { + "type": "opencollective", + "url": "https://opencollective.com/unified" + } + }, + "node_modules/remark-parse": { + "version": "9.0.0", + "resolved": "https://registry.npmjs.org/remark-parse/-/remark-parse-9.0.0.tgz", + "integrity": "sha512-geKatMwSzEXKHuzBNU1z676sGcDcFoChMK38TgdHJNAYfFtsfHDQG7MoJAjs6sgYMqyLduCYWDIWZIxiPeafEw==", + "dependencies": { + "mdast-util-from-markdown": "^0.8.0" + }, + "funding": { + "type": "opencollective", + "url": "https://opencollective.com/unified" + } + }, + "node_modules/renderkid": { + "version": "3.0.0", + "resolved": "https://registry.npmjs.org/renderkid/-/renderkid-3.0.0.tgz", + "integrity": "sha512-q/7VIQA8lmM1hF+jn+sFSPWGlMkSAeNYcPLmDQx2zzuiDfaLrOmumR8iaUKlenFgh0XRPIUeSPlH3A+AW3Z5pg==", + "dev": true, + "dependencies": { + "css-select": "^4.1.3", + "dom-converter": "^0.2.0", + "htmlparser2": "^6.1.0", + "lodash": "^4.17.21", + "strip-ansi": "^6.0.1" + } + }, + "node_modules/repeat-string": { + "version": "1.6.1", + "resolved": "https://registry.npmjs.org/repeat-string/-/repeat-string-1.6.1.tgz", + "integrity": "sha512-PV0dzCYDNfRi1jCDbJzpW7jNNDRuCOG/jI5ctQcGKt/clZD+YcPS3yIlWuTJMmESC8aevCFmWJy5wjAFgNqN6w==", + "engines": { + "node": ">=0.10" + } + }, + "node_modules/require-from-string": { + "version": "2.0.2", + "resolved": "https://registry.npmjs.org/require-from-string/-/require-from-string-2.0.2.tgz", + "integrity": "sha512-Xf0nWe6RseziFMu+Ap9biiUbmplq6S9/p+7w7YXP/JBHhrUDDUhwa+vANyubuqfZWTveU//DYVGsDG7RKL/vEw==", + "dev": true, + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/requires-port": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/requires-port/-/requires-port-1.0.0.tgz", + "integrity": "sha512-KigOCHcocU3XODJxsu8i/j8T9tzT4adHiecwORRQ0ZZFcp7ahwXuRU1m+yuO90C5ZUyGeGfocHDI14M3L3yDAQ==", + "dev": true + }, + "node_modules/resolve": { + "version": "1.22.1", + "resolved": "https://registry.npmjs.org/resolve/-/resolve-1.22.1.tgz", + "integrity": "sha512-nBpuuYuY5jFsli/JIs1oldw6fOQCBioohqWZg/2hiaOybXOft4lonv85uDOKXdf8rhyK159cxU5cDcK/NKk8zw==", + "dev": true, + "dependencies": { + "is-core-module": "^2.9.0", + "path-parse": "^1.0.7", + "supports-preserve-symlinks-flag": "^1.0.0" + }, + "bin": { + "resolve": "bin/resolve" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/resolve-cwd": { + "version": "3.0.0", + "resolved": "https://registry.npmjs.org/resolve-cwd/-/resolve-cwd-3.0.0.tgz", + "integrity": "sha512-OrZaX2Mb+rJCpH/6CpSqt9xFVpN++x01XnN2ie9g6P5/3xelLAkXWVADpdz1IHD/KFfEXyE6V0U01OQ3UO2rEg==", + "dev": true, + "dependencies": { + "resolve-from": "^5.0.0" + }, + "engines": { + "node": ">=8" + } + }, + "node_modules/resolve-from": { + "version": "5.0.0", + "resolved": "https://registry.npmjs.org/resolve-from/-/resolve-from-5.0.0.tgz", + "integrity": "sha512-qYg9KP24dD5qka9J47d0aVky0N+b4fTU89LN9iDnjB5waksiC49rvMB0PrUJQGoTmH50XPiqOvAjDfaijGxYZw==", + "dev": true, + "engines": { + "node": ">=8" + } + }, + "node_modules/retry": { + "version": "0.13.1", + "resolved": "https://registry.npmjs.org/retry/-/retry-0.13.1.tgz", + "integrity": "sha512-XQBQ3I8W1Cge0Seh+6gjj03LbmRFWuoszgK9ooCpwYIrhhoO80pfq4cUkU5DkknwfOfFteRwlZ56PYOGYyFWdg==", + "dev": true, + "engines": { + "node": ">= 4" + } + }, + "node_modules/reusify": { + "version": "1.0.4", + "resolved": "https://registry.npmjs.org/reusify/-/reusify-1.0.4.tgz", + "integrity": "sha512-U9nH88a3fc/ekCF1l0/UP1IosiuIjyTh7hBvXVMHYgVcfGvt897Xguj2UOLDeI5BG2m7/uwyaLVT6fbtCwTyzw==", + "dev": true, + "engines": { + "iojs": ">=1.0.0", + "node": ">=0.10.0" + } + }, + "node_modules/rimraf": { + "version": "3.0.2", + "resolved": "https://registry.npmjs.org/rimraf/-/rimraf-3.0.2.tgz", + "integrity": "sha512-JZkJMZkAGFFPP2YqXZXPbMlMBgsxzE8ILs4lMIX/2o0L9UBw9O/Y3o6wFw/i9YLapcUJWwqbi3kdxIPdC62TIA==", + "dependencies": { + "glob": "^7.1.3" + }, + "bin": { + "rimraf": "bin.js" + }, + "funding": { + "url": "https://github.com/sponsors/isaacs" + } + }, + "node_modules/ripemd160": { + "version": "2.0.2", + "resolved": "https://registry.npmjs.org/ripemd160/-/ripemd160-2.0.2.tgz", + "integrity": "sha512-ii4iagi25WusVoiC4B4lq7pbXfAp3D9v5CwfkY33vffw2+pkDjY1D8GaN7spsxvCSx8dkPqOZCEZyfxcmJG2IA==", + "dependencies": { + "hash-base": "^3.0.0", + "inherits": "^2.0.1" + } + }, + "node_modules/run-parallel": { + "version": "1.2.0", + "resolved": "https://registry.npmjs.org/run-parallel/-/run-parallel-1.2.0.tgz", + "integrity": "sha512-5l4VyZR86LZ/lDxZTR6jqL8AFE2S0IFLMP26AbjsLVADxHdhB/c0GUsH+y39UfCi3dzz8OlQuPmnaJOMoDHQBA==", + "dev": true, + "funding": [ + { + "type": "github", + "url": "https://github.com/sponsors/feross" + }, + { + "type": "patreon", + "url": "https://www.patreon.com/feross" + }, + { + "type": "consulting", + "url": "https://feross.org/support" + } + ], + "dependencies": { + "queue-microtask": "^1.2.2" + } + }, + "node_modules/safe-buffer": { + "version": "5.2.1", + "resolved": "https://registry.npmjs.org/safe-buffer/-/safe-buffer-5.2.1.tgz", + "integrity": "sha512-rp3So07KcdmmKbGvgaNxQSJr7bGVSVk5S9Eq1F+ppbRo70+YeaDxkw5Dd8NPN+GD6bjnYm2VuPuCXmpuYvmCXQ==", + "funding": [ + { + "type": "github", + "url": "https://github.com/sponsors/feross" + }, + { + "type": "patreon", + "url": "https://www.patreon.com/feross" + }, + { + "type": "consulting", + "url": "https://feross.org/support" + } + ] + }, + "node_modules/safer-buffer": { + "version": "2.1.2", + "resolved": "https://registry.npmjs.org/safer-buffer/-/safer-buffer-2.1.2.tgz", + "integrity": "sha512-YZo3K82SD7Riyi0E1EQPojLz7kpepnSQI9IyPbHHg1XXXevb5dJI7tpyN2ADxGcQbHG7vcyRHk0cbwqcQriUtg==" + }, + "node_modules/schema-utils": { + "version": "3.1.1", + "resolved": "https://registry.npmjs.org/schema-utils/-/schema-utils-3.1.1.tgz", + "integrity": "sha512-Y5PQxS4ITlC+EahLuXaY86TXfR7Dc5lw294alXOq86JAHCihAIZfqv8nNCWvaEJvaC51uN9hbLGeV0cFBdH+Fw==", + "dependencies": { + "@types/json-schema": "^7.0.8", + "ajv": "^6.12.5", + "ajv-keywords": "^3.5.2" + }, + "engines": { + "node": ">= 10.13.0" + }, + "funding": { + "type": "opencollective", + "url": "https://opencollective.com/webpack" + } + }, + "node_modules/select-hose": { + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/select-hose/-/select-hose-2.0.0.tgz", + "integrity": "sha512-mEugaLK+YfkijB4fx0e6kImuJdCIt2LxCRcbEYPqRGCs4F2ogyfZU5IAZRdjCP8JPq2AtdNoC/Dux63d9Kiryg==", + "dev": true + }, + "node_modules/selfsigned": { + "version": "2.0.1", + "resolved": "https://registry.npmjs.org/selfsigned/-/selfsigned-2.0.1.tgz", + "integrity": "sha512-LmME957M1zOsUhG+67rAjKfiWFox3SBxE/yymatMZsAx+oMrJ0YQ8AToOnyCm7xbeg2ep37IHLxdu0o2MavQOQ==", + "dev": true, + "dependencies": { + "node-forge": "^1" + }, + "engines": { + "node": ">=10" + } + }, + "node_modules/send": { + "version": "0.18.0", + "resolved": "https://registry.npmjs.org/send/-/send-0.18.0.tgz", + "integrity": "sha512-qqWzuOjSFOuqPjFe4NOsMLafToQQwBSOEpS+FwEt3A2V3vKubTquT3vmLTQpFgMXp8AlFWFuP1qKaJZOtPpVXg==", + "dev": true, + "dependencies": { + "debug": "2.6.9", + "depd": "2.0.0", + "destroy": "1.2.0", + "encodeurl": "~1.0.2", + "escape-html": "~1.0.3", + "etag": "~1.8.1", + "fresh": "0.5.2", + "http-errors": "2.0.0", + "mime": "1.6.0", + "ms": "2.1.3", + "on-finished": "2.4.1", + "range-parser": "~1.2.1", + "statuses": "2.0.1" + }, + "engines": { + "node": ">= 0.8.0" + } + }, + "node_modules/send/node_modules/ms": { + "version": "2.1.3", + "resolved": "https://registry.npmjs.org/ms/-/ms-2.1.3.tgz", + "integrity": "sha512-6FlzubTLZG3J2a/NVCAleEhjzq5oxgHyaCU9yYXvcLsvoVaHJq/s5xXI6/XXP6tz7R9xAOtHnSO/tXtF3WRTlA==", + "dev": true + }, + "node_modules/serialize-javascript": { + "version": "6.0.0", + "resolved": "https://registry.npmjs.org/serialize-javascript/-/serialize-javascript-6.0.0.tgz", + "integrity": "sha512-Qr3TosvguFt8ePWqsvRfrKyQXIiW+nGbYpy8XK24NQHE83caxWt+mIymTT19DGFbNWNLfEwsrkSmN64lVWB9ag==", + "dependencies": { + "randombytes": "^2.1.0" + } + }, + "node_modules/serve-index": { + "version": "1.9.1", + "resolved": "https://registry.npmjs.org/serve-index/-/serve-index-1.9.1.tgz", + "integrity": "sha512-pXHfKNP4qujrtteMrSBb0rc8HJ9Ms/GrXwcUtUtD5s4ewDJI8bT3Cz2zTVRMKtri49pLx2e0Ya8ziP5Ya2pZZw==", + "dev": true, + "dependencies": { + "accepts": "~1.3.4", + "batch": "0.6.1", + "debug": "2.6.9", + "escape-html": "~1.0.3", + "http-errors": "~1.6.2", + "mime-types": "~2.1.17", + "parseurl": "~1.3.2" + }, + "engines": { + "node": ">= 0.8.0" + } + }, + "node_modules/serve-index/node_modules/depd": { + "version": "1.1.2", + "resolved": "https://registry.npmjs.org/depd/-/depd-1.1.2.tgz", + "integrity": "sha512-7emPTl6Dpo6JRXOXjLRxck+FlLRX5847cLKEn00PLAgc3g2hTZZgr+e4c2v6QpSmLeFP3n5yUo7ft6avBK/5jQ==", + "dev": true, + "engines": { + "node": ">= 0.6" + } + }, + "node_modules/serve-index/node_modules/http-errors": { + "version": "1.6.3", + "resolved": "https://registry.npmjs.org/http-errors/-/http-errors-1.6.3.tgz", + "integrity": "sha512-lks+lVC8dgGyh97jxvxeYTWQFvh4uw4yC12gVl63Cg30sjPX4wuGcdkICVXDAESr6OJGjqGA8Iz5mkeN6zlD7A==", + "dev": true, + "dependencies": { + "depd": "~1.1.2", + "inherits": "2.0.3", + "setprototypeof": "1.1.0", + "statuses": ">= 1.4.0 < 2" + }, + "engines": { + "node": ">= 0.6" + } + }, + "node_modules/serve-index/node_modules/inherits": { + "version": "2.0.3", + "resolved": "https://registry.npmjs.org/inherits/-/inherits-2.0.3.tgz", + "integrity": "sha512-x00IRNXNy63jwGkJmzPigoySHbaqpNuzKbBOmzK+g2OdZpQ9w+sxCN+VSB3ja7IAge2OP2qpfxTjeNcyjmW1uw==", + "dev": true + }, + "node_modules/serve-index/node_modules/setprototypeof": { + "version": "1.1.0", + "resolved": "https://registry.npmjs.org/setprototypeof/-/setprototypeof-1.1.0.tgz", + "integrity": "sha512-BvE/TwpZX4FXExxOxZyRGQQv651MSwmWKZGqvmPcRIjDqWub67kTKuIMx43cZZrS/cBBzwBcNDWoFxt2XEFIpQ==", + "dev": true + }, + "node_modules/serve-index/node_modules/statuses": { + "version": "1.5.0", + "resolved": "https://registry.npmjs.org/statuses/-/statuses-1.5.0.tgz", + "integrity": "sha512-OpZ3zP+jT1PI7I8nemJX4AKmAX070ZkYPVWV/AaKTJl+tXCTGyVdC1a4SL8RUQYEwk/f34ZX8UTykN68FwrqAA==", + "dev": true, + "engines": { + "node": ">= 0.6" + } + }, + "node_modules/serve-static": { + "version": "1.15.0", + "resolved": "https://registry.npmjs.org/serve-static/-/serve-static-1.15.0.tgz", + "integrity": "sha512-XGuRDNjXUijsUL0vl6nSD7cwURuzEgglbOaFuZM9g3kwDXOWVTck0jLzjPzGD+TazWbboZYu52/9/XPdUgne9g==", + "dev": true, + "dependencies": { + "encodeurl": "~1.0.2", + "escape-html": "~1.0.3", + "parseurl": "~1.3.3", + "send": "0.18.0" + }, + "engines": { + "node": ">= 0.8.0" + } + }, + "node_modules/setimmediate": { + "version": "1.0.5", + "resolved": "https://registry.npmjs.org/setimmediate/-/setimmediate-1.0.5.tgz", + "integrity": "sha512-MATJdZp8sLqDl/68LfQmbP8zKPLQNV6BIZoIgrscFDQ+RsvK/BxeDQOgyxKKoh0y/8h3BqVFnCqQ/gd+reiIXA==" + }, + "node_modules/setprototypeof": { + "version": "1.2.0", + "resolved": "https://registry.npmjs.org/setprototypeof/-/setprototypeof-1.2.0.tgz", + "integrity": "sha512-E5LDX7Wrp85Kil5bhZv46j8jOeboKq5JMmYM3gVGdGH8xFpPWXUMsNrlODCrkoxMEeNi/XZIwuRvY4XNwYMJpw==", + "dev": true + }, + "node_modules/sha.js": { + "version": "2.4.11", + "resolved": "https://registry.npmjs.org/sha.js/-/sha.js-2.4.11.tgz", + "integrity": "sha512-QMEp5B7cftE7APOjk5Y6xgrbWu+WkLVQwk8JNjZ8nKRciZaByEW6MubieAiToS7+dwvrjGhH8jRXz3MVd0AYqQ==", + "dependencies": { + "inherits": "^2.0.1", + "safe-buffer": "^5.0.1" + }, + "bin": { + "sha.js": "bin.js" + } + }, + "node_modules/shallow-clone": { + "version": "3.0.1", + "resolved": "https://registry.npmjs.org/shallow-clone/-/shallow-clone-3.0.1.tgz", + "integrity": "sha512-/6KqX+GVUdqPuPPd2LxDDxzX6CAbjJehAAOKlNpqqUpAqPM6HeL8f+o3a+JsyGjn2lv0WY8UsTgUJjU9Ok55NA==", + "dev": true, + "dependencies": { + "kind-of": "^6.0.2" + }, + "engines": { + "node": ">=8" + } + }, + "node_modules/shebang-command": { + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/shebang-command/-/shebang-command-2.0.0.tgz", + "integrity": "sha512-kHxr2zZpYtdmrN1qDjrrX/Z1rR1kG8Dx+gkpK1G4eXmvXswmcE1hTWBWYUzlraYw1/yZp6YuDY77YtvbN0dmDA==", + "dev": true, + "dependencies": { + "shebang-regex": "^3.0.0" + }, + "engines": { + "node": ">=8" + } + }, + "node_modules/shebang-regex": { + "version": "3.0.0", + "resolved": "https://registry.npmjs.org/shebang-regex/-/shebang-regex-3.0.0.tgz", + "integrity": "sha512-7++dFhtcx3353uBaq8DDR4NuxBetBzC7ZQOhmTQInHEd6bSrXdiEyzCvG07Z44UYdLShWUyXt5M/yhz8ekcb1A==", + "dev": true, + "engines": { + "node": ">=8" + } + }, + "node_modules/side-channel": { + "version": "1.0.4", + "resolved": "https://registry.npmjs.org/side-channel/-/side-channel-1.0.4.tgz", + "integrity": "sha512-q5XPytqFEIKHkGdiMIrY10mvLRvnQh42/+GoBlFW3b2LXLE2xxJpZFdm94we0BaoV3RwJyGqg5wS7epxTv0Zvw==", + "dependencies": { + "call-bind": "^1.0.0", + "get-intrinsic": "^1.0.2", + "object-inspect": "^1.9.0" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/signal-exit": { + "version": "3.0.7", + "resolved": "https://registry.npmjs.org/signal-exit/-/signal-exit-3.0.7.tgz", + "integrity": "sha512-wnD2ZE+l+SPC/uoS0vXeE9L1+0wuaMqKlfz9AMUo38JsyLSBWSFcHR1Rri62LZc12vLr1gb3jl7iwQhgwpAbGQ==", + "dev": true + }, + "node_modules/slash": { + "version": "3.0.0", + "resolved": "https://registry.npmjs.org/slash/-/slash-3.0.0.tgz", + "integrity": "sha512-g9Q1haeby36OSStwb4ntCGGGaKsaVSjQ68fBxoQcutl5fS1vuY18H3wSt3jFyFtrkx+Kz0V1G85A4MyAdDMi2Q==", + "dev": true, + "engines": { + "node": ">=8" + } + }, + "node_modules/sockjs": { + "version": "0.3.24", + "resolved": "https://registry.npmjs.org/sockjs/-/sockjs-0.3.24.tgz", + "integrity": "sha512-GJgLTZ7vYb/JtPSSZ10hsOYIvEYsjbNU+zPdIHcUaWVNUEPivzxku31865sSSud0Da0W4lEeOPlmw93zLQchuQ==", + "dev": true, + "dependencies": { + "faye-websocket": "^0.11.3", + "uuid": "^8.3.2", + "websocket-driver": "^0.7.4" + } + }, + "node_modules/source-map": { + "version": "0.6.1", + "resolved": "https://registry.npmjs.org/source-map/-/source-map-0.6.1.tgz", + "integrity": "sha512-UjgapumWlbMhkBgzT7Ykc5YXUT46F0iKu8SGXq0bcwP5dz/h0Plj6enJqjz1Zbq2l5WaqYnrVbwWOWMyF3F47g==", + "engines": { + "node": ">=0.10.0" + } + }, + "node_modules/source-map-support": { + "version": "0.5.21", + "resolved": "https://registry.npmjs.org/source-map-support/-/source-map-support-0.5.21.tgz", + "integrity": "sha512-uBHU3L3czsIyYXKX88fdrGovxdSCoTGDRZ6SYXtSRxLZUzHg5P/66Ht6uoUlHu9EZod+inXhKo3qQgwXUT/y1w==", + "dependencies": { + "buffer-from": "^1.0.0", + "source-map": "^0.6.0" + } + }, + "node_modules/spdy": { + "version": "4.0.2", + "resolved": "https://registry.npmjs.org/spdy/-/spdy-4.0.2.tgz", + "integrity": "sha512-r46gZQZQV+Kl9oItvl1JZZqJKGr+oEkB08A6BzkiR7593/7IbtuncXHd2YoYeTsG4157ZssMu9KYvUHLcjcDoA==", + "dev": true, + "dependencies": { + "debug": "^4.1.0", + "handle-thing": "^2.0.0", + "http-deceiver": "^1.2.7", + "select-hose": "^2.0.0", + "spdy-transport": "^3.0.0" + }, + "engines": { + "node": ">=6.0.0" + } + }, + "node_modules/spdy-transport": { + "version": "3.0.0", + "resolved": "https://registry.npmjs.org/spdy-transport/-/spdy-transport-3.0.0.tgz", + "integrity": "sha512-hsLVFE5SjA6TCisWeJXFKniGGOpBgMLmerfO2aCyCU5s7nJ/rpAepqmFifv/GCbSbueEeAJJnmSQ2rKC/g8Fcw==", + "dev": true, + "dependencies": { + "debug": "^4.1.0", + "detect-node": "^2.0.4", + "hpack.js": "^2.1.6", + "obuf": "^1.1.2", + "readable-stream": "^3.0.6", + "wbuf": "^1.7.3" + } + }, + "node_modules/spdy-transport/node_modules/debug": { + "version": "4.3.4", + "resolved": "https://registry.npmjs.org/debug/-/debug-4.3.4.tgz", + "integrity": "sha512-PRWFHuSU3eDtQJPvnNY7Jcket1j0t5OuOsFzPPzsekD52Zl8qUfFIPEiswXqIvHWGVHOgX+7G/vCNNhehwxfkQ==", + "dev": true, + "dependencies": { + "ms": "2.1.2" + }, + "engines": { + "node": ">=6.0" + }, + "peerDependenciesMeta": { + "supports-color": { + "optional": true + } + } + }, + "node_modules/spdy-transport/node_modules/ms": { + "version": "2.1.2", + "resolved": "https://registry.npmjs.org/ms/-/ms-2.1.2.tgz", + "integrity": "sha512-sGkPx+VjMtmA6MX27oA4FBFELFCZZ4S4XqeGOXCv68tT+jb3vk/RyaKWP0PTKyWtmLSM0b+adUTEvbs1PEaH2w==", + "dev": true + }, + "node_modules/spdy/node_modules/debug": { + "version": "4.3.4", + "resolved": "https://registry.npmjs.org/debug/-/debug-4.3.4.tgz", + "integrity": "sha512-PRWFHuSU3eDtQJPvnNY7Jcket1j0t5OuOsFzPPzsekD52Zl8qUfFIPEiswXqIvHWGVHOgX+7G/vCNNhehwxfkQ==", + "dev": true, + "dependencies": { + "ms": "2.1.2" + }, + "engines": { + "node": ">=6.0" + }, + "peerDependenciesMeta": { + "supports-color": { + "optional": true + } + } + }, + "node_modules/spdy/node_modules/ms": { + "version": "2.1.2", + "resolved": "https://registry.npmjs.org/ms/-/ms-2.1.2.tgz", + "integrity": "sha512-sGkPx+VjMtmA6MX27oA4FBFELFCZZ4S4XqeGOXCv68tT+jb3vk/RyaKWP0PTKyWtmLSM0b+adUTEvbs1PEaH2w==", + "dev": true + }, + "node_modules/statuses": { + "version": "2.0.1", + "resolved": "https://registry.npmjs.org/statuses/-/statuses-2.0.1.tgz", + "integrity": "sha512-RwNA9Z/7PrK06rYLIzFMlaF+l73iwpzsqRIFgbMLbTcLD6cOao82TaWefPXQvB2fOC4AjuYSEndS7N/mTCbkdQ==", + "dev": true, + "engines": { + "node": ">= 0.8" + } + }, + "node_modules/stream-browserify": { + "version": "3.0.0", + "resolved": "https://registry.npmjs.org/stream-browserify/-/stream-browserify-3.0.0.tgz", + "integrity": "sha512-H73RAHsVBapbim0tU2JwwOiXUj+fikfiaoYAKHF3VJfA0pe2BCzkhAHBlLG6REzE+2WNZcxOXjK7lkso+9euLA==", + "dependencies": { + "inherits": "~2.0.4", + "readable-stream": "^3.5.0" + } + }, + "node_modules/stream-http": { + "version": "3.2.0", + "resolved": "https://registry.npmjs.org/stream-http/-/stream-http-3.2.0.tgz", + "integrity": "sha512-Oq1bLqisTyK3TSCXpPbT4sdeYNdmyZJv1LxpEm2vu1ZhK89kSE5YXwZc3cWk0MagGaKriBh9mCFbVGtO+vY29A==", + "dependencies": { + "builtin-status-codes": "^3.0.0", + "inherits": "^2.0.4", + "readable-stream": "^3.6.0", + "xtend": "^4.0.2" + } + }, + "node_modules/string_decoder": { + "version": "1.3.0", + "resolved": "https://registry.npmjs.org/string_decoder/-/string_decoder-1.3.0.tgz", + "integrity": "sha512-hkRX8U1WjJFd8LsDJ2yQ/wWWxaopEsABU1XfkM8A+j0+85JAGppt16cr1Whg6KIbb4okU6Mql6BOj+uup/wKeA==", + "dependencies": { + "safe-buffer": "~5.2.0" + } + }, + "node_modules/string.prototype.trimend": { + "version": "1.0.5", + "resolved": "https://registry.npmjs.org/string.prototype.trimend/-/string.prototype.trimend-1.0.5.tgz", + "integrity": "sha512-I7RGvmjV4pJ7O3kdf+LXFpVfdNOxtCW/2C8f6jNiW4+PQchwxkCDzlk1/7p+Wl4bqFIZeF47qAHXLuHHWKAxog==", + "dependencies": { + "call-bind": "^1.0.2", + "define-properties": "^1.1.4", + "es-abstract": "^1.19.5" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/string.prototype.trimstart": { + "version": "1.0.5", + "resolved": "https://registry.npmjs.org/string.prototype.trimstart/-/string.prototype.trimstart-1.0.5.tgz", + "integrity": "sha512-THx16TJCGlsN0o6dl2o6ncWUsdgnLRSA23rRE5pyGBw/mLr3Ej/R2LaqCtgP8VNMGZsvMWnf9ooZPyY2bHvUFg==", + "dependencies": { + "call-bind": "^1.0.2", + "define-properties": "^1.1.4", + "es-abstract": "^1.19.5" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/strip-ansi": { + "version": "6.0.1", + "resolved": "https://registry.npmjs.org/strip-ansi/-/strip-ansi-6.0.1.tgz", + "integrity": "sha512-Y38VPSHcqkFrCpFnQ9vuSXmquuv5oXOKpGeT6aGrr3o3Gc9AlVa6JBfUSOCnbxGGZF+/0ooI7KrPuUSztUdU5A==", + "dev": true, + "dependencies": { + "ansi-regex": "^5.0.1" + }, + "engines": { + "node": ">=8" + } + }, + "node_modules/strip-final-newline": { + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/strip-final-newline/-/strip-final-newline-2.0.0.tgz", + "integrity": "sha512-BrpvfNAE3dcvq7ll3xVumzjKjZQ5tI1sEUIKr3Uoks0XUl45St3FlatVqef9prk4jRDzhW6WZg+3bk93y6pLjA==", + "dev": true, + "engines": { + "node": ">=6" + } + }, + "node_modules/supports-color": { + "version": "8.1.1", + "resolved": "https://registry.npmjs.org/supports-color/-/supports-color-8.1.1.tgz", + "integrity": "sha512-MpUEN2OodtUzxvKQl72cUF7RQ5EiHsGvSsVG0ia9c5RbWGL2CI4C7EpPS8UTBIplnlzZiNuV56w+FuNxy3ty2Q==", + "dependencies": { + "has-flag": "^4.0.0" + }, + "engines": { + "node": ">=10" + }, + "funding": { + "url": "https://github.com/chalk/supports-color?sponsor=1" + } + }, + "node_modules/supports-preserve-symlinks-flag": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/supports-preserve-symlinks-flag/-/supports-preserve-symlinks-flag-1.0.0.tgz", + "integrity": "sha512-ot0WnXS9fgdkgIcePe6RHNk1WA8+muPa6cSjeR3V8K27q9BB1rTE3R1p7Hv0z1ZyAc8s6Vvv8DIyWf681MAt0w==", + "dev": true, + "engines": { + "node": ">= 0.4" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/tapable": { + "version": "2.2.1", + "resolved": "https://registry.npmjs.org/tapable/-/tapable-2.2.1.tgz", + "integrity": "sha512-GNzQvQTOIP6RyTfE2Qxb8ZVlNmw0n88vp1szwWRimP02mnTsx3Wtn5qRdqY9w2XduFNUgvOwhNnQsjwCp+kqaQ==", + "engines": { + "node": ">=6" + } + }, + "node_modules/tar-fs": { + "version": "2.1.1", + "resolved": "https://registry.npmjs.org/tar-fs/-/tar-fs-2.1.1.tgz", + "integrity": "sha512-V0r2Y9scmbDRLCNex/+hYzvp/zyYjvFbHPNgVTKfQvVrb6guiE/fxP+XblDNR011utopbkex2nM4dHNV6GDsng==", + "dependencies": { + "chownr": "^1.1.1", + "mkdirp-classic": "^0.5.2", + "pump": "^3.0.0", + "tar-stream": "^2.1.4" + } + }, + "node_modules/tar-stream": { + "version": "2.2.0", + "resolved": "https://registry.npmjs.org/tar-stream/-/tar-stream-2.2.0.tgz", + "integrity": "sha512-ujeqbceABgwMZxEJnk2HDY2DlnUZ+9oEcb1KzTVfYHio0UE6dG71n60d8D2I4qNvleWrrXpmjpt7vZeF1LnMZQ==", + "dependencies": { + "bl": "^4.0.3", + "end-of-stream": "^1.4.1", + "fs-constants": "^1.0.0", + "inherits": "^2.0.3", + "readable-stream": "^3.1.1" + }, + "engines": { + "node": ">=6" + } + }, + "node_modules/terser": { + "version": "5.15.1", + "resolved": "https://registry.npmjs.org/terser/-/terser-5.15.1.tgz", + "integrity": "sha512-K1faMUvpm/FBxjBXud0LWVAGxmvoPbZbfTCYbSgaaYQaIXI3/TdI7a7ZGA73Zrou6Q8Zmz3oeUTsp/dj+ag2Xw==", + "dependencies": { + "@jridgewell/source-map": "^0.3.2", + "acorn": "^8.5.0", + "commander": "^2.20.0", + "source-map-support": "~0.5.20" + }, + "bin": { + "terser": "bin/terser" + }, + "engines": { + "node": ">=10" + } + }, + "node_modules/terser-webpack-plugin": { + "version": "5.3.3", + "resolved": "https://registry.npmjs.org/terser-webpack-plugin/-/terser-webpack-plugin-5.3.3.tgz", + "integrity": "sha512-Fx60G5HNYknNTNQnzQ1VePRuu89ZVYWfjRAeT5rITuCY/1b08s49e5kSQwHDirKZWuoKOBRFS98EUUoZ9kLEwQ==", + "dependencies": { + "@jridgewell/trace-mapping": "^0.3.7", + "jest-worker": "^27.4.5", + "schema-utils": "^3.1.1", + "serialize-javascript": "^6.0.0", + "terser": "^5.7.2" + }, + "engines": { + "node": ">= 10.13.0" + }, + "funding": { + "type": "opencollective", + "url": "https://opencollective.com/webpack" + }, + "peerDependencies": { + "webpack": "^5.1.0" + }, + "peerDependenciesMeta": { + "@swc/core": { + "optional": true + }, + "esbuild": { + "optional": true + }, + "uglify-js": { + "optional": true + } + } + }, + "node_modules/terser/node_modules/commander": { + "version": "2.20.3", + "resolved": "https://registry.npmjs.org/commander/-/commander-2.20.3.tgz", + "integrity": "sha512-GpVkmM8vF2vQUkj2LvZmD35JxeJOLCwJ9cUkugyk2nuhbv3+mJvpLYYt+0+USMxE+oj+ey/lJEnhZw75x/OMcQ==" + }, + "node_modules/through": { + "version": "2.3.8", + "resolved": "https://registry.npmjs.org/through/-/through-2.3.8.tgz", + "integrity": "sha512-w89qg7PI8wAdvX60bMDP+bFoD5Dvhm9oLheFp5O4a2QF0cSBGsBX4qZmadPMvVqlLJBBci+WqGGOAPvcDeNSVg==" + }, + "node_modules/thunky": { + "version": "1.1.0", + "resolved": "https://registry.npmjs.org/thunky/-/thunky-1.1.0.tgz", + "integrity": "sha512-eHY7nBftgThBqOyHGVN+l8gF0BucP09fMo0oO/Lb0w1OF80dJv+lDVpXG60WMQvkcxAkNybKsrEIE3ZtKGmPrA==", + "dev": true + }, + "node_modules/timers-browserify": { + "version": "2.0.12", + "resolved": "https://registry.npmjs.org/timers-browserify/-/timers-browserify-2.0.12.tgz", + "integrity": "sha512-9phl76Cqm6FhSX9Xe1ZUAMLtm1BLkKj2Qd5ApyWkXzsMRaA7dgr81kf4wJmQf/hAvg8EEyJxDo3du/0KlhPiKQ==", + "dependencies": { + "setimmediate": "^1.0.4" + }, + "engines": { + "node": ">=0.6.0" + } + }, + "node_modules/to-regex-range": { + "version": "5.0.1", + "resolved": "https://registry.npmjs.org/to-regex-range/-/to-regex-range-5.0.1.tgz", + "integrity": "sha512-65P7iz6X5yEr1cwcgvQxbbIw7Uk3gOy5dIdtZ4rDveLqhrdJP+Li/Hx6tyK0NEb+2GCyneCMJiGqrADCSNk8sQ==", + "dev": true, + "dependencies": { + "is-number": "^7.0.0" + }, + "engines": { + "node": ">=8.0" + } + }, + "node_modules/toidentifier": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/toidentifier/-/toidentifier-1.0.1.tgz", + "integrity": "sha512-o5sSPKEkg/DIQNmH43V0/uerLrpzVedkUh8tGNvaeXpfpuwjKenlSox/2O/BTlZUtEe+JG7s5YhEz608PlAHRA==", + "dev": true, + "engines": { + "node": ">=0.6" + } + }, + "node_modules/traverse": { + "version": "0.6.7", + "resolved": "https://registry.npmjs.org/traverse/-/traverse-0.6.7.tgz", + "integrity": "sha512-/y956gpUo9ZNCb99YjxG7OaslxZWHfCHAUUfshwqOXmxUIvqLjVO581BT+gM59+QV9tFe6/CGG53tsA1Y7RSdg==", + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/trough": { + "version": "1.0.5", + "resolved": "https://registry.npmjs.org/trough/-/trough-1.0.5.tgz", + "integrity": "sha512-rvuRbTarPXmMb79SmzEp8aqXNKcK+y0XaB298IXueQ8I2PsrATcPBCSPyK/dDNa2iWOhKlfNnOjdAOTBU/nkFA==", + "funding": { + "type": "github", + "url": "https://github.com/sponsors/wooorm" + } + }, + "node_modules/tslib": { + "version": "2.4.0", + "resolved": "https://registry.npmjs.org/tslib/-/tslib-2.4.0.tgz", + "integrity": "sha512-d6xOpEDfsi2CZVlPQzGeux8XMwLT9hssAsaPYExaQMuYskwb+x1x7J371tWlbBdWHroy99KnVB6qIkUbs5X3UQ==", + "dev": true + }, + "node_modules/tty-browserify": { + "version": "0.0.1", + "resolved": "https://registry.npmjs.org/tty-browserify/-/tty-browserify-0.0.1.tgz", + "integrity": "sha512-C3TaO7K81YvjCgQH9Q1S3R3P3BtN3RIM8n+OvX4il1K1zgE8ZhI0op7kClgkxtutIE8hQrcrHBXvIheqKUUCxw==" + }, + "node_modules/type-is": { + "version": "1.6.18", + "resolved": "https://registry.npmjs.org/type-is/-/type-is-1.6.18.tgz", + "integrity": "sha512-TkRKr9sUTxEH8MdfuCSP7VizJyzRNMjj2J2do2Jr3Kym598JVdEksuzPQCnlFPW4ky9Q+iA+ma9BGm06XQBy8g==", + "dev": true, + "dependencies": { + "media-typer": "0.3.0", + "mime-types": "~2.1.24" + }, + "engines": { + "node": ">= 0.6" + } + }, + "node_modules/unbox-primitive": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/unbox-primitive/-/unbox-primitive-1.0.2.tgz", + "integrity": "sha512-61pPlCD9h51VoreyJ0BReideM3MDKMKnh6+V9L08331ipq6Q8OFXZYiqP6n/tbHx4s5I9uRhcye6BrbkizkBDw==", + "dependencies": { + "call-bind": "^1.0.2", + "has-bigints": "^1.0.2", + "has-symbols": "^1.0.3", + "which-boxed-primitive": "^1.0.2" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/unbzip2-stream": { + "version": "1.4.3", + "resolved": "https://registry.npmjs.org/unbzip2-stream/-/unbzip2-stream-1.4.3.tgz", + "integrity": "sha512-mlExGW4w71ebDJviH16lQLtZS32VKqsSfk80GCfUlwT/4/hNRFsoscrF/c++9xinkMzECL1uL9DDwXqFWkruPg==", + "dependencies": { + "buffer": "^5.2.1", + "through": "^2.3.8" + } + }, + "node_modules/unbzip2-stream/node_modules/buffer": { + "version": "5.7.1", + "resolved": "https://registry.npmjs.org/buffer/-/buffer-5.7.1.tgz", + "integrity": "sha512-EHcyIPBQ4BSGlvjB16k5KgAJ27CIsHY/2JBmCRReo48y9rQ3MaUzWX3KVlBa4U7MyX02HdVj0K7C3WaB3ju7FQ==", + "funding": [ + { + "type": "github", + "url": "https://github.com/sponsors/feross" + }, + { + "type": "patreon", + "url": "https://www.patreon.com/feross" + }, + { + "type": "consulting", + "url": "https://feross.org/support" + } + ], + "dependencies": { + "base64-js": "^1.3.1", + "ieee754": "^1.1.13" + } + }, + "node_modules/underscore": { + "version": "1.13.6", + "resolved": "https://registry.npmjs.org/underscore/-/underscore-1.13.6.tgz", + "integrity": "sha512-+A5Sja4HP1M08MaXya7p5LvjuM7K6q/2EaC0+iovj/wOcMsTzMvDFbasi/oSapiwOlt252IqsKqPjCl7huKS0A==" + }, + "node_modules/unified": { + "version": "9.2.2", + "resolved": "https://registry.npmjs.org/unified/-/unified-9.2.2.tgz", + "integrity": "sha512-Sg7j110mtefBD+qunSLO1lqOEKdrwBFBrR6Qd8f4uwkhWNlbkaqwHse6e7QvD3AP/MNoJdEDLaf8OxYyoWgorQ==", + "dependencies": { + "bail": "^1.0.0", + "extend": "^3.0.0", + "is-buffer": "^2.0.0", + "is-plain-obj": "^2.0.0", + "trough": "^1.0.0", + "vfile": "^4.0.0" + }, + "funding": { + "type": "opencollective", + "url": "https://opencollective.com/unified" + } + }, + "node_modules/unified/node_modules/is-plain-obj": { + "version": "2.1.0", + "resolved": "https://registry.npmjs.org/is-plain-obj/-/is-plain-obj-2.1.0.tgz", + "integrity": "sha512-YWnfyRwxL/+SsrWYfOpUtz5b3YD+nyfkHvjbcanzk8zgyO4ASD67uVMRt8k5bM4lLMDnXfriRhOpemw+NfT1eA==", + "engines": { + "node": ">=8" + } + }, + "node_modules/uniqid": { + "version": "5.4.0", + "resolved": "https://registry.npmjs.org/uniqid/-/uniqid-5.4.0.tgz", + "integrity": "sha512-38JRbJ4Fj94VmnC7G/J/5n5SC7Ab46OM5iNtSstB/ko3l1b5g7ALt4qzHFgGciFkyiRNtDXtLNb+VsxtMSE77A==" + }, + "node_modules/unist-util-is": { + "version": "4.1.0", + "resolved": "https://registry.npmjs.org/unist-util-is/-/unist-util-is-4.1.0.tgz", + "integrity": "sha512-ZOQSsnce92GrxSqlnEEseX0gi7GH9zTJZ0p9dtu87WRb/37mMPO2Ilx1s/t9vBHrFhbgweUwb+t7cIn5dxPhZg==", + "funding": { + "type": "opencollective", + "url": "https://opencollective.com/unified" + } + }, + "node_modules/unist-util-stringify-position": { + "version": "2.0.3", + "resolved": "https://registry.npmjs.org/unist-util-stringify-position/-/unist-util-stringify-position-2.0.3.tgz", + "integrity": "sha512-3faScn5I+hy9VleOq/qNbAd6pAx7iH5jYBMS9I1HgQVijz/4mv5Bvw5iw1sC/90CODiKo81G/ps8AJrISn687g==", + "dependencies": { + "@types/unist": "^2.0.2" + }, + "funding": { + "type": "opencollective", + "url": "https://opencollective.com/unified" + } + }, + "node_modules/unist-util-visit-parents": { + "version": "3.1.1", + "resolved": "https://registry.npmjs.org/unist-util-visit-parents/-/unist-util-visit-parents-3.1.1.tgz", + "integrity": "sha512-1KROIZWo6bcMrZEwiH2UrXDyalAa0uqzWCxCJj6lPOvTve2WkfgCytoDTPaMnodXh1WrXOq0haVYHj99ynJlsg==", + "dependencies": { + "@types/unist": "^2.0.0", + "unist-util-is": "^4.0.0" + }, + "funding": { + "type": "opencollective", + "url": "https://opencollective.com/unified" + } + }, + "node_modules/unpipe": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/unpipe/-/unpipe-1.0.0.tgz", + "integrity": "sha512-pjy2bYhSsufwWlKwPc+l3cN7+wuJlK6uz0YdJEOlQDbl6jo/YlPi4mb8agUkVC8BF7V8NuzeyPNqRksA3hztKQ==", + "dev": true, + "engines": { + "node": ">= 0.8" + } + }, + "node_modules/update-browserslist-db": { + "version": "1.0.3", + "resolved": "https://registry.npmjs.org/update-browserslist-db/-/update-browserslist-db-1.0.3.tgz", + "integrity": "sha512-ufSazemeh9Gty0qiWtoRpJ9F5Q5W3xdIPm1UZQqYQv/q0Nyb9EMHUB2lu+O9x1re9WsorpMAUu4Y6Lxcs5n+XQ==", + "funding": [ + { + "type": "opencollective", + "url": "https://opencollective.com/browserslist" + }, + { + "type": "tidelift", + "url": "https://tidelift.com/funding/github/npm/browserslist" + } + ], + "dependencies": { + "escalade": "^3.1.1", + "picocolors": "^1.0.0" + }, + "bin": { + "browserslist-lint": "cli.js" + }, + "peerDependencies": { + "browserslist": ">= 4.21.0" + } + }, + "node_modules/update-section": { + "version": "0.3.3", + "resolved": "https://registry.npmjs.org/update-section/-/update-section-0.3.3.tgz", + "integrity": "sha512-BpRZMZpgXLuTiKeiu7kK0nIPwGdyrqrs6EDSaXtjD/aQ2T+qVo9a5hRC3HN3iJjCMxNT/VxoLGQ7E/OzE5ucnw==" + }, + "node_modules/uri-js": { + "version": "4.4.1", + "resolved": "https://registry.npmjs.org/uri-js/-/uri-js-4.4.1.tgz", + "integrity": "sha512-7rKUyy33Q1yc98pQ1DAmLtwX109F7TIfWlW1Ydo8Wl1ii1SeHieeh0HHfPeL2fMXK6z0s8ecKs9frCuLJvndBg==", + "dependencies": { + "punycode": "^2.1.0" + } + }, + "node_modules/url": { + "version": "0.11.0", + "resolved": "https://registry.npmjs.org/url/-/url-0.11.0.tgz", + "integrity": "sha512-kbailJa29QrtXnxgq+DdCEGlbTeYM2eJUxsz6vjZavrCYPMIFHMKQmSKYAIuUK2i7hgPm28a8piX5NTUtM/LKQ==", + "dependencies": { + "punycode": "1.3.2", + "querystring": "0.2.0" + } + }, + "node_modules/url/node_modules/punycode": { + "version": "1.3.2", + "resolved": "https://registry.npmjs.org/punycode/-/punycode-1.3.2.tgz", + "integrity": "sha512-RofWgt/7fL5wP1Y7fxE7/EmTLzQVnB0ycyibJ0OOHIlJqTNzglYFxVwETOcIoJqJmpDXJ9xImDv+Fq34F/d4Dw==" + }, + "node_modules/util": { + "version": "0.12.4", + "resolved": "https://registry.npmjs.org/util/-/util-0.12.4.tgz", + "integrity": "sha512-bxZ9qtSlGUWSOy9Qa9Xgk11kSslpuZwaxCg4sNIDj6FLucDab2JxnHwyNTCpHMtK1MjoQiWQ6DiUMZYbSrO+Sw==", + "dependencies": { + "inherits": "^2.0.3", + "is-arguments": "^1.0.4", + "is-generator-function": "^1.0.7", + "is-typed-array": "^1.1.3", + "safe-buffer": "^5.1.2", + "which-typed-array": "^1.1.2" + } + }, + "node_modules/util-deprecate": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/util-deprecate/-/util-deprecate-1.0.2.tgz", + "integrity": "sha512-EPD5q1uXyFxJpCrLnCc1nHnq3gOa6DZBocAIiI2TaSCA7VCJ1UJDMagCzIkXNsUYfD1daK//LTEQ8xiIbrHtcw==" + }, + "node_modules/utila": { + "version": "0.4.0", + "resolved": "https://registry.npmjs.org/utila/-/utila-0.4.0.tgz", + "integrity": "sha512-Z0DbgELS9/L/75wZbro8xAnT50pBVFQZ+hUEueGDU5FN51YSCYM+jdxsfCiHjwNP/4LCDD0i/graKpeBnOXKRA==", + "dev": true + }, + "node_modules/utils-merge": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/utils-merge/-/utils-merge-1.0.1.tgz", + "integrity": "sha512-pMZTvIkT1d+TFGvDOqodOclx0QWkkgi6Tdoa8gC8ffGAAqz9pzPTZWAybbsHHoED/ztMtkv/VoYTYyShUn81hA==", + "dev": true, + "engines": { + "node": ">= 0.4.0" + } + }, + "node_modules/uuid": { + "version": "8.3.2", + "resolved": "https://registry.npmjs.org/uuid/-/uuid-8.3.2.tgz", + "integrity": "sha512-+NYs2QeMWy+GWFOEm9xnn6HCDp0l7QBD7ml8zLUmJ+93Q5NF0NocErnwkTkXVFNiX3/fpC6afS8Dhb/gz7R7eg==", + "dev": true, + "bin": { + "uuid": "dist/bin/uuid" + } + }, + "node_modules/vary": { + "version": "1.1.2", + "resolved": "https://registry.npmjs.org/vary/-/vary-1.1.2.tgz", + "integrity": "sha512-BNGbWLfd0eUPabhkXUVm0j8uuvREyTh5ovRa/dyow/BqAbZJyC+5fU+IzQOzmAKzYqYRAISoRhdQr3eIZ/PXqg==", + "dev": true, + "engines": { + "node": ">= 0.8" + } + }, + "node_modules/vfile": { + "version": "4.2.1", + "resolved": "https://registry.npmjs.org/vfile/-/vfile-4.2.1.tgz", + "integrity": "sha512-O6AE4OskCG5S1emQ/4gl8zK586RqA3srz3nfK/Viy0UPToBc5Trp9BVFb1u0CjsKrAWwnpr4ifM/KBXPWwJbCA==", + "dependencies": { + "@types/unist": "^2.0.0", + "is-buffer": "^2.0.0", + "unist-util-stringify-position": "^2.0.0", + "vfile-message": "^2.0.0" + }, + "funding": { + "type": "opencollective", + "url": "https://opencollective.com/unified" + } + }, + "node_modules/vfile-message": { + "version": "2.0.4", + "resolved": "https://registry.npmjs.org/vfile-message/-/vfile-message-2.0.4.tgz", + "integrity": "sha512-DjssxRGkMvifUOJre00juHoP9DPWuzjxKuMDrhNbk2TdaYYBNMStsNhEOt3idrtI12VQYM/1+iM0KOzXi4pxwQ==", + "dependencies": { + "@types/unist": "^2.0.0", + "unist-util-stringify-position": "^2.0.0" + }, + "funding": { + "type": "opencollective", + "url": "https://opencollective.com/unified" + } + }, + "node_modules/vm-browserify": { + "version": "1.1.2", + "resolved": "https://registry.npmjs.org/vm-browserify/-/vm-browserify-1.1.2.tgz", + "integrity": "sha512-2ham8XPWTONajOR0ohOKOHXkm3+gaBmGut3SRuu75xLd/RRaY6vqgh8NBYYk7+RW3u5AtzPQZG8F10LHkl0lAQ==" + }, + "node_modules/watchpack": { + "version": "2.3.1", + "resolved": "https://registry.npmjs.org/watchpack/-/watchpack-2.3.1.tgz", + "integrity": "sha512-x0t0JuydIo8qCNctdDrn1OzH/qDzk2+rdCOC3YzumZ42fiMqmQ7T3xQurykYMhYfHaPHTp4ZxAx2NfUo1K6QaA==", + "dependencies": { + "glob-to-regexp": "^0.4.1", + "graceful-fs": "^4.1.2" + }, + "engines": { + "node": ">=10.13.0" + } + }, + "node_modules/wbuf": { + "version": "1.7.3", + "resolved": "https://registry.npmjs.org/wbuf/-/wbuf-1.7.3.tgz", + "integrity": "sha512-O84QOnr0icsbFGLS0O3bI5FswxzRr8/gHwWkDlQFskhSPryQXvrTMxjxGP4+iWYoauLoBvfDpkrOauZ+0iZpDA==", + "dev": true, + "dependencies": { + "minimalistic-assert": "^1.0.0" + } + }, + "node_modules/webpack": { + "version": "5.67.0", + "resolved": "https://registry.npmjs.org/webpack/-/webpack-5.67.0.tgz", + "integrity": "sha512-LjFbfMh89xBDpUMgA1W9Ur6Rn/gnr2Cq1jjHFPo4v6a79/ypznSYbAyPgGhwsxBtMIaEmDD1oJoA7BEYw/Fbrw==", + "dependencies": { + "@types/eslint-scope": "^3.7.0", + "@types/estree": "^0.0.50", + "@webassemblyjs/ast": "1.11.1", + "@webassemblyjs/wasm-edit": "1.11.1", + "@webassemblyjs/wasm-parser": "1.11.1", + "acorn": "^8.4.1", + "acorn-import-assertions": "^1.7.6", + "browserslist": "^4.14.5", + "chrome-trace-event": "^1.0.2", + "enhanced-resolve": "^5.8.3", + "es-module-lexer": "^0.9.0", + "eslint-scope": "5.1.1", + "events": "^3.2.0", + "glob-to-regexp": "^0.4.1", + "graceful-fs": "^4.2.9", + "json-parse-better-errors": "^1.0.2", + "loader-runner": "^4.2.0", + "mime-types": "^2.1.27", + "neo-async": "^2.6.2", + "schema-utils": "^3.1.0", + "tapable": "^2.1.1", + "terser-webpack-plugin": "^5.1.3", + "watchpack": "^2.3.1", + "webpack-sources": "^3.2.3" + }, + "bin": { + "webpack": "bin/webpack.js" + }, + "engines": { + "node": ">=10.13.0" + }, + "funding": { + "type": "opencollective", + "url": "https://opencollective.com/webpack" + }, + "peerDependenciesMeta": { + "webpack-cli": { + "optional": true + } + } + }, + "node_modules/webpack-cli": { + "version": "4.10.0", + "resolved": "https://registry.npmjs.org/webpack-cli/-/webpack-cli-4.10.0.tgz", + "integrity": "sha512-NLhDfH/h4O6UOy+0LSso42xvYypClINuMNBVVzX4vX98TmTaTUxwRbXdhucbFMd2qLaCTcLq/PdYrvi8onw90w==", + "dev": true, + "dependencies": { + "@discoveryjs/json-ext": "^0.5.0", + "@webpack-cli/configtest": "^1.2.0", + "@webpack-cli/info": "^1.5.0", + "@webpack-cli/serve": "^1.7.0", + "colorette": "^2.0.14", + "commander": "^7.0.0", + "cross-spawn": "^7.0.3", + "fastest-levenshtein": "^1.0.12", + "import-local": "^3.0.2", + "interpret": "^2.2.0", + "rechoir": "^0.7.0", + "webpack-merge": "^5.7.3" + }, + "bin": { + "webpack-cli": "bin/cli.js" + }, + "engines": { + "node": ">=10.13.0" + }, + "funding": { + "type": "opencollective", + "url": "https://opencollective.com/webpack" + }, + "peerDependencies": { + "webpack": "4.x.x || 5.x.x" + }, + "peerDependenciesMeta": { + "@webpack-cli/generators": { + "optional": true + }, + "@webpack-cli/migrate": { + "optional": true + }, + "webpack-bundle-analyzer": { + "optional": true + }, + "webpack-dev-server": { + "optional": true + } + } + }, + "node_modules/webpack-cli/node_modules/commander": { + "version": "7.2.0", + "resolved": "https://registry.npmjs.org/commander/-/commander-7.2.0.tgz", + "integrity": "sha512-QrWXB+ZQSVPmIWIhtEO9H+gwHaMGYiF5ChvoJ+K9ZGHG/sVsa6yiesAD1GC/x46sET00Xlwo1u49RVVVzvcSkw==", + "dev": true, + "engines": { + "node": ">= 10" + } + }, + "node_modules/webpack-dev-middleware": { + "version": "5.3.3", + "resolved": "https://registry.npmjs.org/webpack-dev-middleware/-/webpack-dev-middleware-5.3.3.tgz", + "integrity": "sha512-hj5CYrY0bZLB+eTO+x/j67Pkrquiy7kWepMHmUMoPsmcUaeEnQJqFzHJOyxgWlq746/wUuA64p9ta34Kyb01pA==", + "dev": true, + "dependencies": { + "colorette": "^2.0.10", + "memfs": "^3.4.3", + "mime-types": "^2.1.31", + "range-parser": "^1.2.1", + "schema-utils": "^4.0.0" + }, + "engines": { + "node": ">= 12.13.0" + }, + "funding": { + "type": "opencollective", + "url": "https://opencollective.com/webpack" + }, + "peerDependencies": { + "webpack": "^4.0.0 || ^5.0.0" + } + }, + "node_modules/webpack-dev-middleware/node_modules/ajv": { + "version": "8.11.0", + "resolved": "https://registry.npmjs.org/ajv/-/ajv-8.11.0.tgz", + "integrity": "sha512-wGgprdCvMalC0BztXvitD2hC04YffAvtsUn93JbGXYLAtCUO4xd17mCCZQxUOItiBwZvJScWo8NIvQMQ71rdpg==", + "dev": true, + "dependencies": { + "fast-deep-equal": "^3.1.1", + "json-schema-traverse": "^1.0.0", + "require-from-string": "^2.0.2", + "uri-js": "^4.2.2" + }, + "funding": { + "type": "github", + "url": "https://github.com/sponsors/epoberezkin" + } + }, + "node_modules/webpack-dev-middleware/node_modules/ajv-keywords": { + "version": "5.1.0", + "resolved": "https://registry.npmjs.org/ajv-keywords/-/ajv-keywords-5.1.0.tgz", + "integrity": "sha512-YCS/JNFAUyr5vAuhk1DWm1CBxRHW9LbJ2ozWeemrIqpbsqKjHVxYPyi5GC0rjZIT5JxJ3virVTS8wk4i/Z+krw==", + "dev": true, + "dependencies": { + "fast-deep-equal": "^3.1.3" + }, + "peerDependencies": { + "ajv": "^8.8.2" + } + }, + "node_modules/webpack-dev-middleware/node_modules/json-schema-traverse": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/json-schema-traverse/-/json-schema-traverse-1.0.0.tgz", + "integrity": "sha512-NM8/P9n3XjXhIZn1lLhkFaACTOURQXjWhV4BA/RnOv8xvgqtqpAX9IO4mRQxSx1Rlo4tqzeqb0sOlruaOy3dug==", + "dev": true + }, + "node_modules/webpack-dev-middleware/node_modules/schema-utils": { + "version": "4.0.0", + "resolved": "https://registry.npmjs.org/schema-utils/-/schema-utils-4.0.0.tgz", + "integrity": "sha512-1edyXKgh6XnJsJSQ8mKWXnN/BVaIbFMLpouRUrXgVq7WYne5kw3MW7UPhO44uRXQSIpTSXoJbmrR2X0w9kUTyg==", + "dev": true, + "dependencies": { + "@types/json-schema": "^7.0.9", + "ajv": "^8.8.0", + "ajv-formats": "^2.1.1", + "ajv-keywords": "^5.0.0" + }, + "engines": { + "node": ">= 12.13.0" + }, + "funding": { + "type": "opencollective", + "url": "https://opencollective.com/webpack" + } + }, + "node_modules/webpack-dev-server": { + "version": "4.7.4", + "resolved": "https://registry.npmjs.org/webpack-dev-server/-/webpack-dev-server-4.7.4.tgz", + "integrity": "sha512-nfdsb02Zi2qzkNmgtZjkrMOcXnYZ6FLKcQwpxT7MvmHKc+oTtDsBju8j+NMyAygZ9GW1jMEUpy3itHtqgEhe1A==", + "dev": true, + "dependencies": { + "@types/bonjour": "^3.5.9", + "@types/connect-history-api-fallback": "^1.3.5", + "@types/express": "^4.17.13", + "@types/serve-index": "^1.9.1", + "@types/sockjs": "^0.3.33", + "@types/ws": "^8.2.2", + "ansi-html-community": "^0.0.8", + "bonjour": "^3.5.0", + "chokidar": "^3.5.3", + "colorette": "^2.0.10", + "compression": "^1.7.4", + "connect-history-api-fallback": "^1.6.0", + "default-gateway": "^6.0.3", + "del": "^6.0.0", + "express": "^4.17.1", + "graceful-fs": "^4.2.6", + "html-entities": "^2.3.2", + "http-proxy-middleware": "^2.0.0", + "ipaddr.js": "^2.0.1", + "open": "^8.0.9", + "p-retry": "^4.5.0", + "portfinder": "^1.0.28", + "schema-utils": "^4.0.0", + "selfsigned": "^2.0.0", + "serve-index": "^1.9.1", + "sockjs": "^0.3.21", + "spdy": "^4.0.2", + "strip-ansi": "^7.0.0", + "webpack-dev-middleware": "^5.3.1", + "ws": "^8.4.2" + }, + "bin": { + "webpack-dev-server": "bin/webpack-dev-server.js" + }, + "engines": { + "node": ">= 12.13.0" + }, + "peerDependencies": { + "webpack": "^4.37.0 || ^5.0.0" + }, + "peerDependenciesMeta": { + "webpack-cli": { + "optional": true + } + } + }, + "node_modules/webpack-dev-server/node_modules/ajv": { + "version": "8.11.0", + "resolved": "https://registry.npmjs.org/ajv/-/ajv-8.11.0.tgz", + "integrity": "sha512-wGgprdCvMalC0BztXvitD2hC04YffAvtsUn93JbGXYLAtCUO4xd17mCCZQxUOItiBwZvJScWo8NIvQMQ71rdpg==", + "dev": true, + "dependencies": { + "fast-deep-equal": "^3.1.1", + "json-schema-traverse": "^1.0.0", + "require-from-string": "^2.0.2", + "uri-js": "^4.2.2" + }, + "funding": { + "type": "github", + "url": "https://github.com/sponsors/epoberezkin" + } + }, + "node_modules/webpack-dev-server/node_modules/ajv-keywords": { + "version": "5.1.0", + "resolved": "https://registry.npmjs.org/ajv-keywords/-/ajv-keywords-5.1.0.tgz", + "integrity": "sha512-YCS/JNFAUyr5vAuhk1DWm1CBxRHW9LbJ2ozWeemrIqpbsqKjHVxYPyi5GC0rjZIT5JxJ3virVTS8wk4i/Z+krw==", + "dev": true, + "dependencies": { + "fast-deep-equal": "^3.1.3" + }, + "peerDependencies": { + "ajv": "^8.8.2" + } + }, + "node_modules/webpack-dev-server/node_modules/ansi-regex": { + "version": "6.0.1", + "resolved": "https://registry.npmjs.org/ansi-regex/-/ansi-regex-6.0.1.tgz", + "integrity": "sha512-n5M855fKb2SsfMIiFFoVrABHJC8QtHwVx+mHWP3QcEqBHYienj5dHSgjbxtC0WEZXYt4wcD6zrQElDPhFuZgfA==", + "dev": true, + "engines": { + "node": ">=12" + }, + "funding": { + "url": "https://github.com/chalk/ansi-regex?sponsor=1" + } + }, + "node_modules/webpack-dev-server/node_modules/json-schema-traverse": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/json-schema-traverse/-/json-schema-traverse-1.0.0.tgz", + "integrity": "sha512-NM8/P9n3XjXhIZn1lLhkFaACTOURQXjWhV4BA/RnOv8xvgqtqpAX9IO4mRQxSx1Rlo4tqzeqb0sOlruaOy3dug==", + "dev": true + }, + "node_modules/webpack-dev-server/node_modules/schema-utils": { + "version": "4.0.0", + "resolved": "https://registry.npmjs.org/schema-utils/-/schema-utils-4.0.0.tgz", + "integrity": "sha512-1edyXKgh6XnJsJSQ8mKWXnN/BVaIbFMLpouRUrXgVq7WYne5kw3MW7UPhO44uRXQSIpTSXoJbmrR2X0w9kUTyg==", + "dev": true, + "dependencies": { + "@types/json-schema": "^7.0.9", + "ajv": "^8.8.0", + "ajv-formats": "^2.1.1", + "ajv-keywords": "^5.0.0" + }, + "engines": { + "node": ">= 12.13.0" + }, + "funding": { + "type": "opencollective", + "url": "https://opencollective.com/webpack" + } + }, + "node_modules/webpack-dev-server/node_modules/strip-ansi": { + "version": "7.0.1", + "resolved": "https://registry.npmjs.org/strip-ansi/-/strip-ansi-7.0.1.tgz", + "integrity": "sha512-cXNxvT8dFNRVfhVME3JAe98mkXDYN2O1l7jmcwMnOslDeESg1rF/OZMtK0nRAhiari1unG5cD4jG3rapUAkLbw==", + "dev": true, + "dependencies": { + "ansi-regex": "^6.0.1" + }, + "engines": { + "node": ">=12" + }, + "funding": { + "url": "https://github.com/chalk/strip-ansi?sponsor=1" + } + }, + "node_modules/webpack-dev-server/node_modules/ws": { + "version": "8.6.0", + "resolved": "https://registry.npmjs.org/ws/-/ws-8.6.0.tgz", + "integrity": "sha512-AzmM3aH3gk0aX7/rZLYvjdvZooofDu3fFOzGqcSnQ1tOcTWwhM/o+q++E8mAyVVIyUdajrkzWUGftaVSDLn1bw==", + "dev": true, + "engines": { + "node": ">=10.0.0" + }, + "peerDependencies": { + "bufferutil": "^4.0.1", + "utf-8-validate": "^5.0.2" + }, + "peerDependenciesMeta": { + "bufferutil": { + "optional": true + }, + "utf-8-validate": { + "optional": true + } + } + }, + "node_modules/webpack-merge": { + "version": "5.8.0", + "resolved": "https://registry.npmjs.org/webpack-merge/-/webpack-merge-5.8.0.tgz", + "integrity": "sha512-/SaI7xY0831XwP6kzuwhKWVKDP9t1QY1h65lAFLbZqMPIuYcD9QAW4u9STIbU9kaJbPBB/geU/gLr1wDjOhQ+Q==", + "dev": true, + "dependencies": { + "clone-deep": "^4.0.1", + "wildcard": "^2.0.0" + }, + "engines": { + "node": ">=10.0.0" + } + }, + "node_modules/webpack-sources": { + "version": "3.2.3", + "resolved": "https://registry.npmjs.org/webpack-sources/-/webpack-sources-3.2.3.tgz", + "integrity": "sha512-/DyMEOrDgLKKIG0fmvtz+4dUX/3Ghozwgm6iPp8KRhvn+eQf9+Q7GWxVNMk3+uCPWfdXYC4ExGBckIXdFEfH1w==", + "engines": { + "node": ">=10.13.0" + } + }, + "node_modules/websocket-driver": { + "version": "0.7.4", + "resolved": "https://registry.npmjs.org/websocket-driver/-/websocket-driver-0.7.4.tgz", + "integrity": "sha512-b17KeDIQVjvb0ssuSDF2cYXSg2iztliJ4B9WdsuB6J952qCPKmnVq4DyW5motImXHDC1cBT/1UezrJVsKw5zjg==", + "dev": true, + "dependencies": { + "http-parser-js": ">=0.5.1", + "safe-buffer": ">=5.1.0", + "websocket-extensions": ">=0.1.1" + }, + "engines": { + "node": ">=0.8.0" + } + }, + "node_modules/websocket-extensions": { + "version": "0.1.4", + "resolved": "https://registry.npmjs.org/websocket-extensions/-/websocket-extensions-0.1.4.tgz", + "integrity": "sha512-OqedPIGOfsDlo31UNwYbCFMSaO9m9G/0faIHj5/dZFDMFqPTcx6UwqyOy3COEaEOg/9VsGIpdqn62W5KhoKSpg==", + "dev": true, + "engines": { + "node": ">=0.8.0" + } + }, + "node_modules/which": { + "version": "2.0.2", + "resolved": "https://registry.npmjs.org/which/-/which-2.0.2.tgz", + "integrity": "sha512-BLI3Tl1TW3Pvl70l3yq3Y64i+awpwXqsGBYWkkqMtnbXgrMD+yj7rhW0kuEDxzJaYXGjEW5ogapKNMEKNMjibA==", + "dev": true, + "dependencies": { + "isexe": "^2.0.0" + }, + "bin": { + "node-which": "bin/node-which" + }, + "engines": { + "node": ">= 8" + } + }, + "node_modules/which-boxed-primitive": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/which-boxed-primitive/-/which-boxed-primitive-1.0.2.tgz", + "integrity": "sha512-bwZdv0AKLpplFY2KZRX6TvyuN7ojjr7lwkg6ml0roIy9YeuSr7JS372qlNW18UQYzgYK9ziGcerWqZOmEn9VNg==", + "dependencies": { + "is-bigint": "^1.0.1", + "is-boolean-object": "^1.1.0", + "is-number-object": "^1.0.4", + "is-string": "^1.0.5", + "is-symbol": "^1.0.3" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/which-typed-array": { + "version": "1.1.8", + "resolved": "https://registry.npmjs.org/which-typed-array/-/which-typed-array-1.1.8.tgz", + "integrity": "sha512-Jn4e5PItbcAHyLoRDwvPj1ypu27DJbtdYXUa5zsinrUx77Uvfb0cXwwnGMTn7cjUfhhqgVQnVJCwF+7cgU7tpw==", + "dependencies": { + "available-typed-arrays": "^1.0.5", + "call-bind": "^1.0.2", + "es-abstract": "^1.20.0", + "for-each": "^0.3.3", + "has-tostringtag": "^1.0.0", + "is-typed-array": "^1.1.9" + }, + "engines": { + "node": ">= 0.4" + }, + "funding": { + "url": "https://github.com/sponsors/ljharb" + } + }, + "node_modules/wildcard": { + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/wildcard/-/wildcard-2.0.0.tgz", + "integrity": "sha512-JcKqAHLPxcdb9KM49dufGXn2x3ssnfjbcaQdLlfZsL9rH9wgDQjUtDxbo8NE0F6SFvydeu1VhZe7hZuHsB2/pw==", + "dev": true + }, + "node_modules/wrappy": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/wrappy/-/wrappy-1.0.2.tgz", + "integrity": "sha1-tSQ9jz7BqjXxNkYFvA0QNuMKtp8=" + }, + "node_modules/ws": { + "version": "8.4.0", + "resolved": "https://registry.npmjs.org/ws/-/ws-8.4.0.tgz", + "integrity": "sha512-IHVsKe2pjajSUIl4KYMQOdlyliovpEPquKkqbwswulszzI7r0SfQrxnXdWAEqOlDCLrVSJzo+O1hAwdog2sKSQ==", + "engines": { + "node": ">=10.0.0" + }, + "peerDependencies": { + "bufferutil": "^4.0.1", + "utf-8-validate": "^5.0.2" + }, + "peerDependenciesMeta": { + "bufferutil": { + "optional": true + }, + "utf-8-validate": { + "optional": true + } + } + }, + "node_modules/xhr2": { + "version": "0.2.1", + "resolved": "https://registry.npmjs.org/xhr2/-/xhr2-0.2.1.tgz", + "integrity": "sha512-sID0rrVCqkVNUn8t6xuv9+6FViXjUVXq8H5rWOH2rz9fDNQEd4g0EA2XlcEdJXRz5BMEn4O1pJFdT+z4YHhoWw==", + "engines": { + "node": ">= 6" + } + }, + "node_modules/xtend": { + "version": "4.0.2", + "resolved": "https://registry.npmjs.org/xtend/-/xtend-4.0.2.tgz", + "integrity": "sha512-LKYU1iAXJXUgAXn9URjiu+MWhyUXHsvfp7mcuYm9dSUKK0/CjtrUwFAxD82/mCWbtLsGjFIad0wIsod4zrTAEQ==", + "engines": { + "node": ">=0.4" + } + }, + "node_modules/yauzl": { + "version": "2.10.0", + "resolved": "https://registry.npmjs.org/yauzl/-/yauzl-2.10.0.tgz", + "integrity": "sha512-p4a9I6X6nu6IhoGmBqAcbJy1mlC4j27vEPZX9F4L4/vZT3Lyq1VkFHw/V/PUcB9Buo+DG3iHkT0x3Qya58zc3g==", + "dependencies": { + "buffer-crc32": "~0.2.3", + "fd-slicer": "~1.1.0" + } + }, + "node_modules/zwitch": { + "version": "1.0.5", + "resolved": "https://registry.npmjs.org/zwitch/-/zwitch-1.0.5.tgz", + "integrity": "sha512-V50KMwwzqJV0NpZIZFwfOD5/lyny3WlSzRiXgA0G7VUnRlqttta1L6UQIHzd6EuBY/cHGfwTIck7w1yH6Q5zUw==", + "funding": { + "type": "github", + "url": "https://github.com/sponsors/wooorm" + } + } + }, "dependencies": { "@discoveryjs/json-ext": { "version": "0.5.7", @@ -21,20 +6479,19 @@ "integrity": "sha512-PoKh1tQnJX18f8iEr8Jk1KXxKCn9eqaSslMI1pyOJvYRJhQVDLCh0+9YReufjp0oFJIY1ShcrR+4/WnECVZUKQ==" }, "@emurgo/cardano-serialization-lib-browser": { - "version": "11.1.1-alpha.1", - "resolved": "https://registry.npmjs.org/@emurgo/cardano-serialization-lib-browser/-/cardano-serialization-lib-browser-11.1.1-alpha.1.tgz", - "integrity": "sha512-R/pVuu9fvnL11eUJ/5O9UDKhwSsAZKlEqKl2hfDoq69giBcsrlFohVrhZFiDt6Nuyic9k5XfsNMCXjYxKJJ3qQ==" + "version": "11.2.1", + "resolved": "https://registry.npmjs.org/@emurgo/cardano-serialization-lib-browser/-/cardano-serialization-lib-browser-11.2.1.tgz", + "integrity": "sha512-J9Pmeta7y1GYnMCxtb3GnGCRw6zk1wiQ8EdCYQRn/Yqa/ss1zoBjd41euVi02Eb58aLuOJS81nNU+BcMLGXvUg==" }, "@emurgo/cardano-serialization-lib-nodejs": { - "version": "11.1.1-alpha.1", - "resolved": "https://registry.npmjs.org/@emurgo/cardano-serialization-lib-nodejs/-/cardano-serialization-lib-nodejs-11.1.1-alpha.1.tgz", - "integrity": "sha512-aUwPZbRoxcFBi3aEJVowYW6AHDuzZ7Mxk4KSqa2N53JSw8CWzNWI7lx+9OCNrGGLGV+9yVqHC2skdg5P3j2bSg==" + "version": "11.2.1", + "resolved": "https://registry.npmjs.org/@emurgo/cardano-serialization-lib-nodejs/-/cardano-serialization-lib-nodejs-11.2.1.tgz", + "integrity": "sha512-+Rw35NW4Qv/9uFaPxhKtxiIPmoBEIFMAgdqQxZTw6hNT/wvBp2TvwTBPnOW8ODs7GUAA8nrO1rJJAaxF+mAG2w==" }, "@jridgewell/gen-mapping": { "version": "0.3.2", "resolved": "https://registry.npmjs.org/@jridgewell/gen-mapping/-/gen-mapping-0.3.2.tgz", "integrity": "sha512-mh65xKQAzI6iBcFzwv28KVWSmCkdRBWoOh+bYQGW3+6OZvbbN3TqMGo5hqYxQniRcH9F2VZIoJCm4pa3BPDK/A==", - "dev": true, "requires": { "@jridgewell/set-array": "^1.0.1", "@jridgewell/sourcemap-codec": "^1.4.10", @@ -44,20 +6501,17 @@ "@jridgewell/resolve-uri": { "version": "3.0.7", "resolved": "https://registry.npmjs.org/@jridgewell/resolve-uri/-/resolve-uri-3.0.7.tgz", - "integrity": "sha512-8cXDaBBHOr2pQ7j77Y6Vp5VDT2sIqWyWQ56TjEq4ih/a4iST3dItRe8Q9fp0rrIl9DoKhWQtUQz/YpOxLkXbNA==", - "dev": true + "integrity": "sha512-8cXDaBBHOr2pQ7j77Y6Vp5VDT2sIqWyWQ56TjEq4ih/a4iST3dItRe8Q9fp0rrIl9DoKhWQtUQz/YpOxLkXbNA==" }, "@jridgewell/set-array": { "version": "1.1.2", "resolved": "https://registry.npmjs.org/@jridgewell/set-array/-/set-array-1.1.2.tgz", - "integrity": "sha512-xnkseuNADM0gt2bs+BvhO0p78Mk762YnZdsuzFV018NoG1Sj1SCQvpSqa7XUaTam5vAGasABV9qXASMKnFMwMw==", - "dev": true + "integrity": "sha512-xnkseuNADM0gt2bs+BvhO0p78Mk762YnZdsuzFV018NoG1Sj1SCQvpSqa7XUaTam5vAGasABV9qXASMKnFMwMw==" }, "@jridgewell/source-map": { "version": "0.3.2", "resolved": "https://registry.npmjs.org/@jridgewell/source-map/-/source-map-0.3.2.tgz", "integrity": "sha512-m7O9o2uR8k2ObDysZYzdfhb08VuEml5oWGiosa1VdaPZ/A6QyPkAJuwN0Q1lhULOf6B7MtQmHENS743hWtCrgw==", - "dev": true, "requires": { "@jridgewell/gen-mapping": "^0.3.0", "@jridgewell/trace-mapping": "^0.3.9" @@ -66,14 +6520,12 @@ "@jridgewell/sourcemap-codec": { "version": "1.4.13", "resolved": "https://registry.npmjs.org/@jridgewell/sourcemap-codec/-/sourcemap-codec-1.4.13.tgz", - "integrity": "sha512-GryiOJmNcWbovBxTfZSF71V/mXbgcV3MewDe3kIMCLyIh5e7SKAeUZs+rMnJ8jkMolZ/4/VsdBmMrw3l+VdZ3w==", - "dev": true + "integrity": "sha512-GryiOJmNcWbovBxTfZSF71V/mXbgcV3MewDe3kIMCLyIh5e7SKAeUZs+rMnJ8jkMolZ/4/VsdBmMrw3l+VdZ3w==" }, "@jridgewell/trace-mapping": { "version": "0.3.13", "resolved": "https://registry.npmjs.org/@jridgewell/trace-mapping/-/trace-mapping-0.3.13.tgz", "integrity": "sha512-o1xbKhp9qnIAoHJSWd6KlCZfqslL4valSF81H8ImioOAxluWYWOpWkpyktY2vnt4tbrX9XYaxovq6cgowaJp2w==", - "dev": true, "requires": { "@jridgewell/resolve-uri": "^3.0.3", "@jridgewell/sourcemap-codec": "^1.4.10" @@ -183,7 +6635,6 @@ "version": "8.4.3", "resolved": "https://registry.npmjs.org/@types/eslint/-/eslint-8.4.3.tgz", "integrity": "sha512-YP1S7YJRMPs+7KZKDb9G63n8YejIwW9BALq7a5j2+H4yl6iOv9CB29edho+cuFRrvmJbbaH2yiVChKLJVysDGw==", - "dev": true, "requires": { "@types/estree": "*", "@types/json-schema": "*" @@ -193,7 +6644,6 @@ "version": "3.7.3", "resolved": "https://registry.npmjs.org/@types/eslint-scope/-/eslint-scope-3.7.3.tgz", "integrity": "sha512-PB3ldyrcnAicT35TWPs5IcwKD8S333HMaa2VVv4+wdvebJkjWuW/xESoB8IwRcog8HYVYamb1g/R31Qv5Bx03g==", - "dev": true, "requires": { "@types/eslint": "*", "@types/estree": "*" @@ -202,8 +6652,7 @@ "@types/estree": { "version": "0.0.50", "resolved": "https://registry.npmjs.org/@types/estree/-/estree-0.0.50.tgz", - "integrity": "sha512-C6N5s2ZFtuZRj54k2/zyRhNDjJwwcViAM3Nbm8zjBpbqAdZ00mr0CFxvSKeO8Y/e03WVFLpQMdHYVfUd6SB+Hw==", - "dev": true + "integrity": "sha512-C6N5s2ZFtuZRj54k2/zyRhNDjJwwcViAM3Nbm8zjBpbqAdZ00mr0CFxvSKeO8Y/e03WVFLpQMdHYVfUd6SB+Hw==" }, "@types/express": { "version": "4.17.13", @@ -246,8 +6695,7 @@ "@types/json-schema": { "version": "7.0.11", "resolved": "https://registry.npmjs.org/@types/json-schema/-/json-schema-7.0.11.tgz", - "integrity": "sha512-wOuvG1SN4Us4rez+tylwwwCV1psiNVOkJeM3AUWUNWg/jDQY2+HE/444y5gc+jBmRqASOm2Oeh5c1axHobwRKQ==", - "dev": true + "integrity": "sha512-wOuvG1SN4Us4rez+tylwwwCV1psiNVOkJeM3AUWUNWg/jDQY2+HE/444y5gc+jBmRqASOm2Oeh5c1axHobwRKQ==" }, "@types/mdast": { "version": "3.0.10", @@ -341,7 +6789,6 @@ "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/ast/-/ast-1.11.1.tgz", "integrity": "sha512-ukBh14qFLjxTQNTXocdyksN5QdM28S1CxHt2rdskFyL+xFV7VremuBLVbmCePj+URalXBENx/9Lm7lnhihtCSw==", - "dev": true, "requires": { "@webassemblyjs/helper-numbers": "1.11.1", "@webassemblyjs/helper-wasm-bytecode": "1.11.1" @@ -350,26 +6797,22 @@ "@webassemblyjs/floating-point-hex-parser": { "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/floating-point-hex-parser/-/floating-point-hex-parser-1.11.1.tgz", - "integrity": "sha512-iGRfyc5Bq+NnNuX8b5hwBrRjzf0ocrJPI6GWFodBFzmFnyvrQ83SHKhmilCU/8Jv67i4GJZBMhEzltxzcNagtQ==", - "dev": true + "integrity": "sha512-iGRfyc5Bq+NnNuX8b5hwBrRjzf0ocrJPI6GWFodBFzmFnyvrQ83SHKhmilCU/8Jv67i4GJZBMhEzltxzcNagtQ==" }, "@webassemblyjs/helper-api-error": { "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/helper-api-error/-/helper-api-error-1.11.1.tgz", - "integrity": "sha512-RlhS8CBCXfRUR/cwo2ho9bkheSXG0+NwooXcc3PAILALf2QLdFyj7KGsKRbVc95hZnhnERon4kW/D3SZpp6Tcg==", - "dev": true + "integrity": "sha512-RlhS8CBCXfRUR/cwo2ho9bkheSXG0+NwooXcc3PAILALf2QLdFyj7KGsKRbVc95hZnhnERon4kW/D3SZpp6Tcg==" }, "@webassemblyjs/helper-buffer": { "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/helper-buffer/-/helper-buffer-1.11.1.tgz", - "integrity": "sha512-gwikF65aDNeeXa8JxXa2BAk+REjSyhrNC9ZwdT0f8jc4dQQeDQ7G4m0f2QCLPJiMTTO6wfDmRmj/pW0PsUvIcA==", - "dev": true + "integrity": "sha512-gwikF65aDNeeXa8JxXa2BAk+REjSyhrNC9ZwdT0f8jc4dQQeDQ7G4m0f2QCLPJiMTTO6wfDmRmj/pW0PsUvIcA==" }, "@webassemblyjs/helper-numbers": { "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/helper-numbers/-/helper-numbers-1.11.1.tgz", "integrity": "sha512-vDkbxiB8zfnPdNK9Rajcey5C0w+QJugEglN0of+kmO8l7lDb77AnlKYQF7aarZuCrv+l0UvqL+68gSDr3k9LPQ==", - "dev": true, "requires": { "@webassemblyjs/floating-point-hex-parser": "1.11.1", "@webassemblyjs/helper-api-error": "1.11.1", @@ -379,14 +6822,12 @@ "@webassemblyjs/helper-wasm-bytecode": { "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/helper-wasm-bytecode/-/helper-wasm-bytecode-1.11.1.tgz", - "integrity": "sha512-PvpoOGiJwXeTrSf/qfudJhwlvDQxFgelbMqtq52WWiXC6Xgg1IREdngmPN3bs4RoO83PnL/nFrxucXj1+BX62Q==", - "dev": true + "integrity": "sha512-PvpoOGiJwXeTrSf/qfudJhwlvDQxFgelbMqtq52WWiXC6Xgg1IREdngmPN3bs4RoO83PnL/nFrxucXj1+BX62Q==" }, "@webassemblyjs/helper-wasm-section": { "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/helper-wasm-section/-/helper-wasm-section-1.11.1.tgz", "integrity": "sha512-10P9No29rYX1j7F3EVPX3JvGPQPae+AomuSTPiF9eBQeChHI6iqjMIwR9JmOJXwpnn/oVGDk7I5IlskuMwU/pg==", - "dev": true, "requires": { "@webassemblyjs/ast": "1.11.1", "@webassemblyjs/helper-buffer": "1.11.1", @@ -398,7 +6839,6 @@ "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/ieee754/-/ieee754-1.11.1.tgz", "integrity": "sha512-hJ87QIPtAMKbFq6CGTkZYJivEwZDbQUgYd3qKSadTNOhVY7p+gfP6Sr0lLRVTaG1JjFj+r3YchoqRYxNH3M0GQ==", - "dev": true, "requires": { "@xtuc/ieee754": "^1.2.0" } @@ -407,7 +6847,6 @@ "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/leb128/-/leb128-1.11.1.tgz", "integrity": "sha512-BJ2P0hNZ0u+Th1YZXJpzW6miwqQUGcIHT1G/sf72gLVD9DZ5AdYTqPNbHZh6K1M5VmKvFXwGSWZADz+qBWxeRw==", - "dev": true, "requires": { "@xtuc/long": "4.2.2" } @@ -415,14 +6854,12 @@ "@webassemblyjs/utf8": { "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/utf8/-/utf8-1.11.1.tgz", - "integrity": "sha512-9kqcxAEdMhiwQkHpkNiorZzqpGrodQQ2IGrHHxCy+Ozng0ofyMA0lTqiLkVs1uzTRejX+/O0EOT7KxqVPuXosQ==", - "dev": true + "integrity": "sha512-9kqcxAEdMhiwQkHpkNiorZzqpGrodQQ2IGrHHxCy+Ozng0ofyMA0lTqiLkVs1uzTRejX+/O0EOT7KxqVPuXosQ==" }, "@webassemblyjs/wasm-edit": { "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/wasm-edit/-/wasm-edit-1.11.1.tgz", "integrity": "sha512-g+RsupUC1aTHfR8CDgnsVRVZFJqdkFHpsHMfJuWQzWU3tvnLC07UqHICfP+4XyL2tnr1amvl1Sdp06TnYCmVkA==", - "dev": true, "requires": { "@webassemblyjs/ast": "1.11.1", "@webassemblyjs/helper-buffer": "1.11.1", @@ -438,7 +6875,6 @@ "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/wasm-gen/-/wasm-gen-1.11.1.tgz", "integrity": "sha512-F7QqKXwwNlMmsulj6+O7r4mmtAlCWfO/0HdgOxSklZfQcDu0TpLiD1mRt/zF25Bk59FIjEuGAIyn5ei4yMfLhA==", - "dev": true, "requires": { "@webassemblyjs/ast": "1.11.1", "@webassemblyjs/helper-wasm-bytecode": "1.11.1", @@ -451,7 +6887,6 @@ "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/wasm-opt/-/wasm-opt-1.11.1.tgz", "integrity": "sha512-VqnkNqnZlU5EB64pp1l7hdm3hmQw7Vgqa0KF/KCNO9sIpI6Fk6brDEiX+iCOYrvMuBWDws0NkTOxYEb85XQHHw==", - "dev": true, "requires": { "@webassemblyjs/ast": "1.11.1", "@webassemblyjs/helper-buffer": "1.11.1", @@ -463,7 +6898,6 @@ "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/wasm-parser/-/wasm-parser-1.11.1.tgz", "integrity": "sha512-rrBujw+dJu32gYB7/Lup6UhdkPx9S9SnobZzRVL7VcBH9Bt9bCBLEuX/YXOOtBsOZ4NQrRykKhffRWHvigQvOA==", - "dev": true, "requires": { "@webassemblyjs/ast": "1.11.1", "@webassemblyjs/helper-api-error": "1.11.1", @@ -477,7 +6911,6 @@ "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/wast-printer/-/wast-printer-1.11.1.tgz", "integrity": "sha512-IQboUWM4eKzWW+N/jij2sRatKMh99QEelo3Eb2q0qXkvPRISAj8Qxtmw5itwqK+TTkBuUIE45AxYPToqPtL5gg==", - "dev": true, "requires": { "@webassemblyjs/ast": "1.11.1", "@xtuc/long": "4.2.2" @@ -487,7 +6920,8 @@ "version": "1.2.0", "resolved": "https://registry.npmjs.org/@webpack-cli/configtest/-/configtest-1.2.0.tgz", "integrity": "sha512-4FB8Tj6xyVkyqjj1OaTqCjXYULB9FMkqQ8yGrZjRDrYh0nOE+7Lhs45WioWQQMV+ceFlE368Ukhe6xdvJM9Egg==", - "dev": true + "dev": true, + "requires": {} }, "@webpack-cli/info": { "version": "1.5.0", @@ -502,19 +6936,18 @@ "version": "1.7.0", "resolved": "https://registry.npmjs.org/@webpack-cli/serve/-/serve-1.7.0.tgz", "integrity": "sha512-oxnCNGj88fL+xzV+dacXs44HcDwf1ovs3AuEzvP7mqXw7fQntqIhQ1BRmynh4qEKQSSSRSWVyXRjmTbZIX9V2Q==", - "dev": true + "dev": true, + "requires": {} }, "@xtuc/ieee754": { "version": "1.2.0", "resolved": "https://registry.npmjs.org/@xtuc/ieee754/-/ieee754-1.2.0.tgz", - "integrity": "sha512-DX8nKgqcGwsc0eJSqYt5lwP4DH5FlHnmuWWBRy7X0NcaGR0ZtuyeESgMwTYVEtxmsNGY+qit4QYT/MIYTOTPeA==", - "dev": true + "integrity": "sha512-DX8nKgqcGwsc0eJSqYt5lwP4DH5FlHnmuWWBRy7X0NcaGR0ZtuyeESgMwTYVEtxmsNGY+qit4QYT/MIYTOTPeA==" }, "@xtuc/long": { "version": "4.2.2", "resolved": "https://registry.npmjs.org/@xtuc/long/-/long-4.2.2.tgz", - "integrity": "sha512-NuHqBY1PB/D8xU6s/thBgOAiAP7HOYDQ32+BFZILJ8ivkUkAHQnWfn6WhL79Owj1qmUnoN/YPhktdIoucipkAQ==", - "dev": true + "integrity": "sha512-NuHqBY1PB/D8xU6s/thBgOAiAP7HOYDQ32+BFZILJ8ivkUkAHQnWfn6WhL79Owj1qmUnoN/YPhktdIoucipkAQ==" }, "accepts": { "version": "1.3.8", @@ -529,14 +6962,13 @@ "acorn": { "version": "8.7.1", "resolved": "https://registry.npmjs.org/acorn/-/acorn-8.7.1.tgz", - "integrity": "sha512-Xx54uLJQZ19lKygFXOWsscKUbsBZW0CPykPhVQdhIeIwrbPmJzqeASDInc8nKBnp/JT6igTs82qPXz069H8I/A==", - "dev": true + "integrity": "sha512-Xx54uLJQZ19lKygFXOWsscKUbsBZW0CPykPhVQdhIeIwrbPmJzqeASDInc8nKBnp/JT6igTs82qPXz069H8I/A==" }, "acorn-import-assertions": { "version": "1.8.0", "resolved": "https://registry.npmjs.org/acorn-import-assertions/-/acorn-import-assertions-1.8.0.tgz", "integrity": "sha512-m7VZ3jwz4eK6A4Vtt8Ew1/mNbP24u0FhdyfA7fSvnJR6LMdfOYnmuIrrJAgrYfYJ10F/otaHTtrtrtmHdMNzEw==", - "dev": true + "requires": {} }, "agent-base": { "version": "6.0.2", @@ -575,7 +7007,6 @@ "version": "6.12.6", "resolved": "https://registry.npmjs.org/ajv/-/ajv-6.12.6.tgz", "integrity": "sha512-j3fVLgvTo527anyYyJOGTYJbG+vnnQYvE0m5mmkc1TK+nxAppkCLMIL0aZ4dblVCNoGShhm+kzE4ZUykBoMg4g==", - "dev": true, "requires": { "fast-deep-equal": "^3.1.1", "fast-json-stable-stringify": "^2.0.0", @@ -616,7 +7047,7 @@ "version": "3.5.2", "resolved": "https://registry.npmjs.org/ajv-keywords/-/ajv-keywords-3.5.2.tgz", "integrity": "sha512-5p6WTN0DdTGVQk6VjcEju19IgaHudalcfabD7yhDGeA6bcQnmL+CpveLJq/3hvfwd1aof6L386Ougkx6RfyMIQ==", - "dev": true + "requires": {} }, "anchor-markdown-header": { "version": "0.6.0", @@ -908,7 +7339,6 @@ "version": "4.21.0", "resolved": "https://registry.npmjs.org/browserslist/-/browserslist-4.21.0.tgz", "integrity": "sha512-UQxE0DIhRB5z/zDz9iA03BOfxaN2+GQdBYH/2WrSIWEUrnpzTPJbhqt+umq6r3acaPRTW1FNTkrcp0PXgtFkvA==", - "dev": true, "requires": { "caniuse-lite": "^1.0.30001358", "electron-to-chromium": "^1.4.164", @@ -933,8 +7363,7 @@ "buffer-from": { "version": "1.1.2", "resolved": "https://registry.npmjs.org/buffer-from/-/buffer-from-1.1.2.tgz", - "integrity": "sha512-E+XQCRwSbaaiChtv6k6Dwgc+bx+Bs6vuKJHHl5kox/BaKbhiXzqQOwK4cO22yElGp2OCmjwVhT3HmxgyPGnJfQ==", - "dev": true + "integrity": "sha512-E+XQCRwSbaaiChtv6k6Dwgc+bx+Bs6vuKJHHl5kox/BaKbhiXzqQOwK4cO22yElGp2OCmjwVhT3HmxgyPGnJfQ==" }, "buffer-indexof": { "version": "1.1.1", @@ -988,8 +7417,7 @@ "caniuse-lite": { "version": "1.0.30001358", "resolved": "https://registry.npmjs.org/caniuse-lite/-/caniuse-lite-1.0.30001358.tgz", - "integrity": "sha512-hvp8PSRymk85R20bsDra7ZTCpSVGN/PAz9pSAjPSjKC+rNmnUk5vCRgJwiTT/O4feQ/yu/drvZYpKxxhbFuChw==", - "dev": true + "integrity": "sha512-hvp8PSRymk85R20bsDra7ZTCpSVGN/PAz9pSAjPSjKC+rNmnUk5vCRgJwiTT/O4feQ/yu/drvZYpKxxhbFuChw==" }, "ccount": { "version": "1.1.0", @@ -1035,8 +7463,7 @@ "chrome-trace-event": { "version": "1.0.3", "resolved": "https://registry.npmjs.org/chrome-trace-event/-/chrome-trace-event-1.0.3.tgz", - "integrity": "sha512-p3KULyQg4S7NIHixdwbGX+nFHkoBiA4YQmyWtjb8XngSKV124nJmRysgAeujbUVb15vh+RvFUfCPqU7rXk+hZg==", - "dev": true + "integrity": "sha512-p3KULyQg4S7NIHixdwbGX+nFHkoBiA4YQmyWtjb8XngSKV124nJmRysgAeujbUVb15vh+RvFUfCPqU7rXk+hZg==" }, "cipher-base": { "version": "1.0.4", @@ -1511,8 +7938,7 @@ "electron-to-chromium": { "version": "1.4.167", "resolved": "https://registry.npmjs.org/electron-to-chromium/-/electron-to-chromium-1.4.167.tgz", - "integrity": "sha512-lPHuHXBwpkr4RcfaZBKm6TKOWG/1N9mVggUpP4fY3l1JIUU2x4fkM8928smYdZ5lF+6KCTAxo1aK9JmqT+X71Q==", - "dev": true + "integrity": "sha512-lPHuHXBwpkr4RcfaZBKm6TKOWG/1N9mVggUpP4fY3l1JIUU2x4fkM8928smYdZ5lF+6KCTAxo1aK9JmqT+X71Q==" }, "elliptic": { "version": "6.5.4", @@ -1558,7 +7984,6 @@ "version": "5.9.3", "resolved": "https://registry.npmjs.org/enhanced-resolve/-/enhanced-resolve-5.9.3.tgz", "integrity": "sha512-Bq9VSor+kjvW3f9/MiiR4eE3XYgOl7/rS8lnSxbRbF3kS0B2r+Y9w5krBWxZgDxASVZbdYrn5wT4j/Wb0J9qow==", - "dev": true, "requires": { "graceful-fs": "^4.2.4", "tapable": "^2.2.0" @@ -1608,8 +8033,7 @@ "es-module-lexer": { "version": "0.9.3", "resolved": "https://registry.npmjs.org/es-module-lexer/-/es-module-lexer-0.9.3.tgz", - "integrity": "sha512-1HQ2M2sPtxwnvOvT1ZClHyQDiggdNjURWpY2we6aMKCQiUVxTmVs2UYPLIrD84sS+kMdUwfBSylbJPwNnBrnHQ==", - "dev": true + "integrity": "sha512-1HQ2M2sPtxwnvOvT1ZClHyQDiggdNjURWpY2we6aMKCQiUVxTmVs2UYPLIrD84sS+kMdUwfBSylbJPwNnBrnHQ==" }, "es-to-primitive": { "version": "1.2.1", @@ -1629,8 +8053,7 @@ "escalade": { "version": "3.1.1", "resolved": "https://registry.npmjs.org/escalade/-/escalade-3.1.1.tgz", - "integrity": "sha512-k0er2gUkLf8O0zKJiAhmkTnJlTvINGv7ygDNPbeIsX/TJjGJZHuh9B2UxbsaEkmlEo9MfhrSzmhIlhRlI2GXnw==", - "dev": true + "integrity": "sha512-k0er2gUkLf8O0zKJiAhmkTnJlTvINGv7ygDNPbeIsX/TJjGJZHuh9B2UxbsaEkmlEo9MfhrSzmhIlhRlI2GXnw==" }, "escape-html": { "version": "1.0.3", @@ -1647,7 +8070,6 @@ "version": "5.1.1", "resolved": "https://registry.npmjs.org/eslint-scope/-/eslint-scope-5.1.1.tgz", "integrity": "sha512-2NxwbF/hZ0KpepYN0cNbo+FN6XoK7GaHlQhgx/hIZl6Va0bF45RQOOwhLIy8lQDbuCiadSLCBnH2CFYquit5bw==", - "dev": true, "requires": { "esrecurse": "^4.3.0", "estraverse": "^4.1.1" @@ -1657,7 +8079,6 @@ "version": "4.3.0", "resolved": "https://registry.npmjs.org/esrecurse/-/esrecurse-4.3.0.tgz", "integrity": "sha512-KmfKL3b6G+RXvP8N1vr3Tq1kL/oCFgn2NYXEtqP8/L3pKapUA4G8cFVaoF3SU323CD4XypR/ffioHmkti6/Tag==", - "dev": true, "requires": { "estraverse": "^5.2.0" }, @@ -1665,16 +8086,14 @@ "estraverse": { "version": "5.3.0", "resolved": "https://registry.npmjs.org/estraverse/-/estraverse-5.3.0.tgz", - "integrity": "sha512-MMdARuVEQziNTeJD8DgMqmhwR11BRQ/cBP+pLtYdSTnf3MIO8fFeiINEbX36ZdNlfU/7A9f3gUw49B3oQsvwBA==", - "dev": true + "integrity": "sha512-MMdARuVEQziNTeJD8DgMqmhwR11BRQ/cBP+pLtYdSTnf3MIO8fFeiINEbX36ZdNlfU/7A9f3gUw49B3oQsvwBA==" } } }, "estraverse": { "version": "4.3.0", "resolved": "https://registry.npmjs.org/estraverse/-/estraverse-4.3.0.tgz", - "integrity": "sha512-39nnKffWz8xN1BU/2c79n9nB9HDzo0niYUqx6xyqUnyoAnQyyWpOTdZEeiCch8BBu515t4wp9ZmgVfVhn9EBpw==", - "dev": true + "integrity": "sha512-39nnKffWz8xN1BU/2c79n9nB9HDzo0niYUqx6xyqUnyoAnQyyWpOTdZEeiCch8BBu515t4wp9ZmgVfVhn9EBpw==" }, "etag": { "version": "1.8.1", @@ -1808,8 +8227,7 @@ "fast-deep-equal": { "version": "3.1.3", "resolved": "https://registry.npmjs.org/fast-deep-equal/-/fast-deep-equal-3.1.3.tgz", - "integrity": "sha512-f3qQ9oQy9j2AhBe/H9VC91wLmKBCCU/gDOnKNAYG5hswO7BLKj09Hc5HYNz9cGI++xlpDCIgDaitVs03ATR84Q==", - "dev": true + "integrity": "sha512-f3qQ9oQy9j2AhBe/H9VC91wLmKBCCU/gDOnKNAYG5hswO7BLKj09Hc5HYNz9cGI++xlpDCIgDaitVs03ATR84Q==" }, "fast-glob": { "version": "3.2.11", @@ -1827,8 +8245,7 @@ "fast-json-stable-stringify": { "version": "2.1.0", "resolved": "https://registry.npmjs.org/fast-json-stable-stringify/-/fast-json-stable-stringify-2.1.0.tgz", - "integrity": "sha512-lhd/wF+Lk98HZoTCtlVraHtfh5XYijIjalXck7saUtuanSDyLMxnHhSXEDJqHxD7msR8D0uCmqlkwjCV8xvwHw==", - "dev": true + "integrity": "sha512-lhd/wF+Lk98HZoTCtlVraHtfh5XYijIjalXck7saUtuanSDyLMxnHhSXEDJqHxD7msR8D0uCmqlkwjCV8xvwHw==" }, "fastest-levenshtein": { "version": "1.0.14", @@ -2033,8 +8450,7 @@ "glob-to-regexp": { "version": "0.4.1", "resolved": "https://registry.npmjs.org/glob-to-regexp/-/glob-to-regexp-0.4.1.tgz", - "integrity": "sha512-lkX1HJXwyMcprw/5YUZc2s7DrpAiHB21/V+E1rHUrVNokkvB6bqMzT0VfV6/86ZNabt1k14YOIaT7nDvOX3Iiw==", - "dev": true + "integrity": "sha512-lkX1HJXwyMcprw/5YUZc2s7DrpAiHB21/V+E1rHUrVNokkvB6bqMzT0VfV6/86ZNabt1k14YOIaT7nDvOX3Iiw==" }, "globby": { "version": "11.1.0", @@ -2053,8 +8469,7 @@ "graceful-fs": { "version": "4.2.10", "resolved": "https://registry.npmjs.org/graceful-fs/-/graceful-fs-4.2.10.tgz", - "integrity": "sha512-9ByhssR2fPVsNZj478qUUbKfmL0+t5BDVyjShtyZZLiK7ZDAArFFfopyOTj0M05wE2tJPisA4iTnnXl2YoPvOA==", - "dev": true + "integrity": "sha512-9ByhssR2fPVsNZj478qUUbKfmL0+t5BDVyjShtyZZLiK7ZDAArFFfopyOTj0M05wE2tJPisA4iTnnXl2YoPvOA==" }, "handle-thing": { "version": "2.0.1", @@ -2078,8 +8493,7 @@ "has-flag": { "version": "4.0.0", "resolved": "https://registry.npmjs.org/has-flag/-/has-flag-4.0.0.tgz", - "integrity": "sha512-EykJT/Q1KjTWctppgIAgfSO0tKVuZUjhgMr17kqTumMl6Afv3EISleU7qZUzoXDFTAHTDC4NOoG/ZxU3EvlMPQ==", - "dev": true + "integrity": "sha512-EykJT/Q1KjTWctppgIAgfSO0tKVuZUjhgMr17kqTumMl6Afv3EISleU7qZUzoXDFTAHTDC4NOoG/ZxU3EvlMPQ==" }, "has-property-descriptors": { "version": "1.0.0", @@ -2649,7 +9063,6 @@ "version": "27.5.1", "resolved": "https://registry.npmjs.org/jest-worker/-/jest-worker-27.5.1.tgz", "integrity": "sha512-7vuh85V5cdDofPyxn58nrPjBktZo0u9x1g8WtjQol+jZDaE+fhN+cIvTj11GndBnMnyfrUOG1sZQxCdjKh+DKg==", - "dev": true, "requires": { "@types/node": "*", "merge-stream": "^2.0.0", @@ -2659,14 +9072,12 @@ "json-parse-better-errors": { "version": "1.0.2", "resolved": "https://registry.npmjs.org/json-parse-better-errors/-/json-parse-better-errors-1.0.2.tgz", - "integrity": "sha512-mrqyZKfX5EhL7hvqcV6WG1yYjnjeuYDzDhhcAAUrq8Po85NBQBJP+ZDUT75qZQ98IkUoBqdkExkukOU7Ts2wrw==", - "dev": true + "integrity": "sha512-mrqyZKfX5EhL7hvqcV6WG1yYjnjeuYDzDhhcAAUrq8Po85NBQBJP+ZDUT75qZQ98IkUoBqdkExkukOU7Ts2wrw==" }, "json-schema-traverse": { "version": "0.4.1", "resolved": "https://registry.npmjs.org/json-schema-traverse/-/json-schema-traverse-0.4.1.tgz", - "integrity": "sha512-xbbCH5dCYU5T8LcEhhuh7HJ88HXuW3qsI3Y0zOZFKfZEHcpWiHU/Jxzk629Brsab/mMiHQti9wMP+845RPe3Vg==", - "dev": true + "integrity": "sha512-xbbCH5dCYU5T8LcEhhuh7HJ88HXuW3qsI3Y0zOZFKfZEHcpWiHU/Jxzk629Brsab/mMiHQti9wMP+845RPe3Vg==" }, "jssha": { "version": "3.2.0", @@ -2682,8 +9093,7 @@ "loader-runner": { "version": "4.3.0", "resolved": "https://registry.npmjs.org/loader-runner/-/loader-runner-4.3.0.tgz", - "integrity": "sha512-3R/1M+yS3j5ou80Me59j7F9IMs4PXs3VqRrm0TU3AbKPxlmpoY1TNscJV/oGJXo8qCatFGTfDbY6W6ipGOYXfg==", - "dev": true + "integrity": "sha512-3R/1M+yS3j5ou80Me59j7F9IMs4PXs3VqRrm0TU3AbKPxlmpoY1TNscJV/oGJXo8qCatFGTfDbY6W6ipGOYXfg==" }, "locate-path": { "version": "5.0.0", @@ -2859,8 +9269,7 @@ "merge-stream": { "version": "2.0.0", "resolved": "https://registry.npmjs.org/merge-stream/-/merge-stream-2.0.0.tgz", - "integrity": "sha512-abv/qOcuPfk3URPfDzmZU1LKmuw8kT+0nIHvKrKgFrwifol/doWcdA4ZqsWQ8ENrFKkd67Mfpo/LovbIUsbt3w==", - "dev": true + "integrity": "sha512-abv/qOcuPfk3URPfDzmZU1LKmuw8kT+0nIHvKrKgFrwifol/doWcdA4ZqsWQ8ENrFKkd67Mfpo/LovbIUsbt3w==" }, "merge2": { "version": "1.4.1", @@ -2999,14 +9408,12 @@ "mime-db": { "version": "1.52.0", "resolved": "https://registry.npmjs.org/mime-db/-/mime-db-1.52.0.tgz", - "integrity": "sha512-sPU4uV7dYlvtWJxwwxHD0PuihVNiE7TyAbQ5SWxDCB9mUYvOgroQOwYQQOKPJ8CIbE+1ETVlOoK1UC2nU3gYvg==", - "dev": true + "integrity": "sha512-sPU4uV7dYlvtWJxwwxHD0PuihVNiE7TyAbQ5SWxDCB9mUYvOgroQOwYQQOKPJ8CIbE+1ETVlOoK1UC2nU3gYvg==" }, "mime-types": { "version": "2.1.35", "resolved": "https://registry.npmjs.org/mime-types/-/mime-types-2.1.35.tgz", "integrity": "sha512-ZDY+bPm5zTTF+YpCrAU9nK0UgICYPT0QtT1NZWFv4s++TNkcgVaT0g6+4R2uI4MjQjzysHB1zxuWL50hzaeXiw==", - "dev": true, "requires": { "mime-db": "1.52.0" } @@ -3085,8 +9492,7 @@ "neo-async": { "version": "2.6.2", "resolved": "https://registry.npmjs.org/neo-async/-/neo-async-2.6.2.tgz", - "integrity": "sha512-Yd3UES5mWCSqR+qNT93S3UoYUkqAZ9lLg8a7g9rimsWmYGK8cVToA4/sF3RrshdyV3sAGMXVUmpMYOw+dLpOuw==", - "dev": true + "integrity": "sha512-Yd3UES5mWCSqR+qNT93S3UoYUkqAZ9lLg8a7g9rimsWmYGK8cVToA4/sF3RrshdyV3sAGMXVUmpMYOw+dLpOuw==" }, "no-case": { "version": "3.0.4", @@ -3172,8 +9578,7 @@ "node-releases": { "version": "2.0.5", "resolved": "https://registry.npmjs.org/node-releases/-/node-releases-2.0.5.tgz", - "integrity": "sha512-U9h1NLROZTq9uE1SNffn6WuPDg8icmi3ns4rEl/oTfIle4iLjTliCzgTsbaIFMq/Xn078/lfY/BL0GWZ+psK4Q==", - "dev": true + "integrity": "sha512-U9h1NLROZTq9uE1SNffn6WuPDg8icmi3ns4rEl/oTfIle4iLjTliCzgTsbaIFMq/Xn078/lfY/BL0GWZ+psK4Q==" }, "normalize-path": { "version": "3.0.0", @@ -3438,8 +9843,7 @@ "picocolors": { "version": "1.0.0", "resolved": "https://registry.npmjs.org/picocolors/-/picocolors-1.0.0.tgz", - "integrity": "sha512-1fygroTLlHu66zi26VoTDv8yRgm0Fccecssto+MhsZ0D/DGW2sm8E8AjW7NU5VVTRt5GxbeZ5qBuJr+HyLYkjQ==", - "dev": true + "integrity": "sha512-1fygroTLlHu66zi26VoTDv8yRgm0Fccecssto+MhsZ0D/DGW2sm8E8AjW7NU5VVTRt5GxbeZ5qBuJr+HyLYkjQ==" }, "picomatch": { "version": "2.3.1", @@ -3601,7 +10005,8 @@ "ws": { "version": "8.8.0", "resolved": "https://registry.npmjs.org/ws/-/ws-8.8.0.tgz", - "integrity": "sha512-JDAgSYQ1ksuwqfChJusw1LSJ8BizJ2e/vVu5Lxjq3YvNJNlROv1ui4i+c/kUUrPheBvQl4c5UbERhTwKa6QBJQ==" + "integrity": "sha512-JDAgSYQ1ksuwqfChJusw1LSJ8BizJ2e/vVu5Lxjq3YvNJNlROv1ui4i+c/kUUrPheBvQl4c5UbERhTwKa6QBJQ==", + "requires": {} } } }, @@ -3865,7 +10270,6 @@ "version": "3.1.1", "resolved": "https://registry.npmjs.org/schema-utils/-/schema-utils-3.1.1.tgz", "integrity": "sha512-Y5PQxS4ITlC+EahLuXaY86TXfR7Dc5lw294alXOq86JAHCihAIZfqv8nNCWvaEJvaC51uN9hbLGeV0cFBdH+Fw==", - "dev": true, "requires": { "@types/json-schema": "^7.0.8", "ajv": "^6.12.5", @@ -3920,7 +10324,6 @@ "version": "6.0.0", "resolved": "https://registry.npmjs.org/serialize-javascript/-/serialize-javascript-6.0.0.tgz", "integrity": "sha512-Qr3TosvguFt8ePWqsvRfrKyQXIiW+nGbYpy8XK24NQHE83caxWt+mIymTT19DGFbNWNLfEwsrkSmN64lVWB9ag==", - "dev": true, "requires": { "randombytes": "^2.1.0" } @@ -4070,14 +10473,12 @@ "source-map": { "version": "0.6.1", "resolved": "https://registry.npmjs.org/source-map/-/source-map-0.6.1.tgz", - "integrity": "sha512-UjgapumWlbMhkBgzT7Ykc5YXUT46F0iKu8SGXq0bcwP5dz/h0Plj6enJqjz1Zbq2l5WaqYnrVbwWOWMyF3F47g==", - "dev": true + "integrity": "sha512-UjgapumWlbMhkBgzT7Ykc5YXUT46F0iKu8SGXq0bcwP5dz/h0Plj6enJqjz1Zbq2l5WaqYnrVbwWOWMyF3F47g==" }, "source-map-support": { "version": "0.5.21", "resolved": "https://registry.npmjs.org/source-map-support/-/source-map-support-0.5.21.tgz", "integrity": "sha512-uBHU3L3czsIyYXKX88fdrGovxdSCoTGDRZ6SYXtSRxLZUzHg5P/66Ht6uoUlHu9EZod+inXhKo3qQgwXUT/y1w==", - "dev": true, "requires": { "buffer-from": "^1.0.0", "source-map": "^0.6.0" @@ -4170,6 +10571,14 @@ "xtend": "^4.0.2" } }, + "string_decoder": { + "version": "1.3.0", + "resolved": "https://registry.npmjs.org/string_decoder/-/string_decoder-1.3.0.tgz", + "integrity": "sha512-hkRX8U1WjJFd8LsDJ2yQ/wWWxaopEsABU1XfkM8A+j0+85JAGppt16cr1Whg6KIbb4okU6Mql6BOj+uup/wKeA==", + "requires": { + "safe-buffer": "~5.2.0" + } + }, "string.prototype.trimend": { "version": "1.0.5", "resolved": "https://registry.npmjs.org/string.prototype.trimend/-/string.prototype.trimend-1.0.5.tgz", @@ -4190,14 +10599,6 @@ "es-abstract": "^1.19.5" } }, - "string_decoder": { - "version": "1.3.0", - "resolved": "https://registry.npmjs.org/string_decoder/-/string_decoder-1.3.0.tgz", - "integrity": "sha512-hkRX8U1WjJFd8LsDJ2yQ/wWWxaopEsABU1XfkM8A+j0+85JAGppt16cr1Whg6KIbb4okU6Mql6BOj+uup/wKeA==", - "requires": { - "safe-buffer": "~5.2.0" - } - }, "strip-ansi": { "version": "6.0.1", "resolved": "https://registry.npmjs.org/strip-ansi/-/strip-ansi-6.0.1.tgz", @@ -4217,7 +10618,6 @@ "version": "8.1.1", "resolved": "https://registry.npmjs.org/supports-color/-/supports-color-8.1.1.tgz", "integrity": "sha512-MpUEN2OodtUzxvKQl72cUF7RQ5EiHsGvSsVG0ia9c5RbWGL2CI4C7EpPS8UTBIplnlzZiNuV56w+FuNxy3ty2Q==", - "dev": true, "requires": { "has-flag": "^4.0.0" } @@ -4231,8 +10631,7 @@ "tapable": { "version": "2.2.1", "resolved": "https://registry.npmjs.org/tapable/-/tapable-2.2.1.tgz", - "integrity": "sha512-GNzQvQTOIP6RyTfE2Qxb8ZVlNmw0n88vp1szwWRimP02mnTsx3Wtn5qRdqY9w2XduFNUgvOwhNnQsjwCp+kqaQ==", - "dev": true + "integrity": "sha512-GNzQvQTOIP6RyTfE2Qxb8ZVlNmw0n88vp1szwWRimP02mnTsx3Wtn5qRdqY9w2XduFNUgvOwhNnQsjwCp+kqaQ==" }, "tar-fs": { "version": "2.1.1", @@ -4261,7 +10660,6 @@ "version": "5.15.1", "resolved": "https://registry.npmjs.org/terser/-/terser-5.15.1.tgz", "integrity": "sha512-K1faMUvpm/FBxjBXud0LWVAGxmvoPbZbfTCYbSgaaYQaIXI3/TdI7a7ZGA73Zrou6Q8Zmz3oeUTsp/dj+ag2Xw==", - "dev": true, "requires": { "@jridgewell/source-map": "^0.3.2", "acorn": "^8.5.0", @@ -4272,8 +10670,7 @@ "commander": { "version": "2.20.3", "resolved": "https://registry.npmjs.org/commander/-/commander-2.20.3.tgz", - "integrity": "sha512-GpVkmM8vF2vQUkj2LvZmD35JxeJOLCwJ9cUkugyk2nuhbv3+mJvpLYYt+0+USMxE+oj+ey/lJEnhZw75x/OMcQ==", - "dev": true + "integrity": "sha512-GpVkmM8vF2vQUkj2LvZmD35JxeJOLCwJ9cUkugyk2nuhbv3+mJvpLYYt+0+USMxE+oj+ey/lJEnhZw75x/OMcQ==" } } }, @@ -4281,7 +10678,6 @@ "version": "5.3.3", "resolved": "https://registry.npmjs.org/terser-webpack-plugin/-/terser-webpack-plugin-5.3.3.tgz", "integrity": "sha512-Fx60G5HNYknNTNQnzQ1VePRuu89ZVYWfjRAeT5rITuCY/1b08s49e5kSQwHDirKZWuoKOBRFS98EUUoZ9kLEwQ==", - "dev": true, "requires": { "@jridgewell/trace-mapping": "^0.3.7", "jest-worker": "^27.4.5", @@ -4448,7 +10844,6 @@ "version": "1.0.3", "resolved": "https://registry.npmjs.org/update-browserslist-db/-/update-browserslist-db-1.0.3.tgz", "integrity": "sha512-ufSazemeh9Gty0qiWtoRpJ9F5Q5W3xdIPm1UZQqYQv/q0Nyb9EMHUB2lu+O9x1re9WsorpMAUu4Y6Lxcs5n+XQ==", - "dev": true, "requires": { "escalade": "^3.1.1", "picocolors": "^1.0.0" @@ -4463,7 +10858,6 @@ "version": "4.4.1", "resolved": "https://registry.npmjs.org/uri-js/-/uri-js-4.4.1.tgz", "integrity": "sha512-7rKUyy33Q1yc98pQ1DAmLtwX109F7TIfWlW1Ydo8Wl1ii1SeHieeh0HHfPeL2fMXK6z0s8ecKs9frCuLJvndBg==", - "dev": true, "requires": { "punycode": "^2.1.0" } @@ -4555,7 +10949,6 @@ "version": "2.3.1", "resolved": "https://registry.npmjs.org/watchpack/-/watchpack-2.3.1.tgz", "integrity": "sha512-x0t0JuydIo8qCNctdDrn1OzH/qDzk2+rdCOC3YzumZ42fiMqmQ7T3xQurykYMhYfHaPHTp4ZxAx2NfUo1K6QaA==", - "dev": true, "requires": { "glob-to-regexp": "^0.4.1", "graceful-fs": "^4.1.2" @@ -4574,7 +10967,6 @@ "version": "5.67.0", "resolved": "https://registry.npmjs.org/webpack/-/webpack-5.67.0.tgz", "integrity": "sha512-LjFbfMh89xBDpUMgA1W9Ur6Rn/gnr2Cq1jjHFPo4v6a79/ypznSYbAyPgGhwsxBtMIaEmDD1oJoA7BEYw/Fbrw==", - "dev": true, "requires": { "@types/eslint-scope": "^3.7.0", "@types/estree": "^0.0.50", @@ -4780,7 +11172,8 @@ "version": "8.6.0", "resolved": "https://registry.npmjs.org/ws/-/ws-8.6.0.tgz", "integrity": "sha512-AzmM3aH3gk0aX7/rZLYvjdvZooofDu3fFOzGqcSnQ1tOcTWwhM/o+q++E8mAyVVIyUdajrkzWUGftaVSDLn1bw==", - "dev": true + "dev": true, + "requires": {} } } }, @@ -4797,8 +11190,7 @@ "webpack-sources": { "version": "3.2.3", "resolved": "https://registry.npmjs.org/webpack-sources/-/webpack-sources-3.2.3.tgz", - "integrity": "sha512-/DyMEOrDgLKKIG0fmvtz+4dUX/3Ghozwgm6iPp8KRhvn+eQf9+Q7GWxVNMk3+uCPWfdXYC4ExGBckIXdFEfH1w==", - "dev": true + "integrity": "sha512-/DyMEOrDgLKKIG0fmvtz+4dUX/3Ghozwgm6iPp8KRhvn+eQf9+Q7GWxVNMk3+uCPWfdXYC4ExGBckIXdFEfH1w==" }, "websocket-driver": { "version": "0.7.4", @@ -4865,7 +11257,8 @@ "ws": { "version": "8.4.0", "resolved": "https://registry.npmjs.org/ws/-/ws-8.4.0.tgz", - "integrity": "sha512-IHVsKe2pjajSUIl4KYMQOdlyliovpEPquKkqbwswulszzI7r0SfQrxnXdWAEqOlDCLrVSJzo+O1hAwdog2sKSQ==" + "integrity": "sha512-IHVsKe2pjajSUIl4KYMQOdlyliovpEPquKkqbwswulszzI7r0SfQrxnXdWAEqOlDCLrVSJzo+O1hAwdog2sKSQ==", + "requires": {} }, "xhr2": { "version": "0.2.1", diff --git a/package.json b/package.json index 372957c4cd..fcfa8dddee 100755 --- a/package.json +++ b/package.json @@ -28,8 +28,8 @@ "dependencies": { "@emurgo/cardano-message-signing-browser": "1.0.1", "@emurgo/cardano-message-signing-nodejs": "1.0.1", - "@emurgo/cardano-serialization-lib-browser": "^11.1.1-alpha.1", - "@emurgo/cardano-serialization-lib-nodejs": "11.1.1-alpha.1", + "@emurgo/cardano-serialization-lib-browser": "11.2.1", + "@emurgo/cardano-serialization-lib-nodejs": "11.2.1", "base64-js": "^1.5.1", "big-integer": "1.6.51", "blakejs": "1.2.1", diff --git a/test/Fixtures.purs b/test/Fixtures.purs index c28c15aa34..469c9412e6 100644 --- a/test/Fixtures.purs +++ b/test/Fixtures.purs @@ -327,8 +327,8 @@ proposedProtocolParameterUpdates1 = ProposedProtocolParameterUpdates $ , maxBlockExUnits: Just { mem: BigInt.fromInt 1, steps: BigInt.fromInt 1 } , maxValueSize: Just $ UInt.fromInt 1 - , collateralPercentage: Nothing -- Just $ UInt.fromInt 140 - , maxCollateralInputs: Nothing -- Just $ UInt.fromInt 10 + , collateralPercentage: Just $ UInt.fromInt 140 + , maxCollateralInputs: Just $ UInt.fromInt 10 } ] @@ -797,7 +797,62 @@ txBinaryFixture3 = txBinaryFixture4 :: String txBinaryFixture4 = - "84ae00818258205d677265fa5bb21ce6d8c7502aca70b9316d10e958611f3c6b758f65ad959996000182a40058390030fb3b8539951e26f034910a5a37f22cb99d94d1d409f69ddbaea9710f45aaf1b2959db6e5ff94dbb1f823bf257680c3c723ac2d49f97546011a0023e8fa028201d818418003d8185182014e4d01000033222220051200120011a30058390030fb3b8539951e26f034910a5a37f22cb99d94d1d409f69ddbaea9710f45aaf1b2959db6e5ff94dbb1f823bf257680c3c723ac2d49f97546011a000f424003d81858468200830301828200581c1c12f03c1ef2e935acc35ec2e6f96c650fd3bfba3e96550504d533618200581c30fb3b8539951e26f034910a5a37f22cb99d94d1d409f69ddbaea971021a0002b56903187b048882008200581c1730b1b700d616d51555538e83d67f13c113ad5f9b22212703482cb382018200581c1730b1b700d616d51555538e83d67f13c113ad5f9b22212703482cb383028200581c1730b1b700d616d51555538e83d67f13c113ad5f9b22212703482cb3581c1730b1b700d616d51555538e83d67f13c113ad5f9b22212703482cb38a03581c1730b1b700d616d51555538e83d67f13c113ad5f9b22212703482cb35820fbf6d41985670b9041c5bf362b5262cf34add5d265975de176d613ca05f370960101d81e820101581de11730b1b700d616d51555538e83d67f13c113ad5f9b22212703482cb381581c1730b1b700d616d51555538e83d67f13c113ad5f9b22212703482cb3838400191f90447f000001507b7b7b7b7b7b7b7b7b7b7b7b7b7b7b7b8301191f906b6578616d706c652e636f6d82026b6578616d706c652e636f6d827468747470733a2f2f6578616d706c652e636f6d2f582094b8cac47761c1140c57a48d56ab15d27a842abff041b3798b8618fa84641f5a8304581c1730b1b700d616d51555538e83d67f13c113ad5f9b22212703482cb3018405581c5d677265fa5bb21ce6d8c7502aca70b9316d10e958611f3c6b758f65581c5d677265fa5bb21ce6d8c7502aca70b9316d10e958611f3c6b758f655820fbf6d41985670b9041c5bf362b5262cf34add5d265975de176d613ca05f37096820682010182068201a18200581c1730b1b700d616d51555538e83d67f13c113ad5f9b22212703482cb30105a1581de01730b1b700d616d51555538e83d67f13c113ad5f9b22212703482cb3010682a1581c5d677265fa5bb21ce6d8c7502aca70b9316d10e958611f3c6b758f65b4000101010219271003192710041903e8050106010701080109d81e8201010ad81e8201010bd81e8201010e8201011001110112a20098a61a0003236119032c01011903e819023b00011903e8195e7104011903e818201a0001ca761928eb041959d818641959d818641959d818641959d818641959d818641959d81864186418641959d81864194c5118201a0002acfa182019b551041a000363151901ff00011a00015c3518201a000797751936f404021a0002ff941a0006ea7818dc0001011903e8196ff604021a0003bd081a00034ec5183e011a00102e0f19312a011a00032e801901a5011a0002da781903e819cf06011a00013a34182019a8f118201903e818201a00013aac0119e143041903e80a1a00030219189c011a00030219189c011a0003207c1901d9011a000330001901ff0119ccf3182019fd40182019ffd5182019581e18201940b318201a00012adf18201a0002ff941a0006ea7818dc0001011a00010f92192da7000119eabb18201a0002ff941a0006ea7818dc0001011a0002ff941a0006ea7818dc0001011a000c504e197712041a001d6af61a0001425b041a00040c660004001a00014fab18201a0003236119032c010119a0de18201a00033d7618201979f41820197fb8182019a95d1820197df718201995aa18201a009063b91903fd0a0198af1a0003236119032c01011903e819023b00011903e8195e7104011903e818201a0001ca761928eb041959d818641959d818641959d818641959d818641959d818641959d81864186418641959d81864194c5118201a0002acfa182019b551041a000363151901ff00011a00015c3518201a000797751936f404021a0002ff941a0006ea7818dc0001011903e8196ff604021a0003bd081a00034ec5183e011a00102e0f19312a011a00032e801901a5011a0002da781903e819cf06011a00013a34182019a8f118201903e818201a00013aac0119e143041903e80a1a00030219189c011a00030219189c011a0003207c1901d9011a000330001901ff0119ccf3182019fd40182019ffd5182019581e18201940b318201a00012adf18201a0002ff941a0006ea7818dc0001011a00010f92192da7000119eabb18201a0002ff941a0006ea7818dc0001011a0002ff941a0006ea7818dc0001011a0011b22c1a0005fdde00021a000c504e197712041a001d6af61a0001425b041a00040c660004001a00014fab18201a0003236119032c010119a0de18201a00033d7618201979f41820197fb8182019a95d1820197df718201995aa18201b00000004a817c8001b00000004a817c8001a009063b91903fd0a1b00000004a817c800001b00000004a817c8001382d81e820101d81e8201011482010115820101160101075820000000000000000000000000000000000000000000000000000000000000000008187c09a1581c1d6445ddeda578117f393848e685128f1e78ad0c4e48129c5964dc2ea14a4974657374546f6b656e010e81581c1c12f03c1ef2e935acc35ec2e6f96c650fd3bfba3e96550504d533610f01108258390030fb3b8539951e26f034910a5a37f22cb99d94d1d409f69ddbaea9711c12f03c1ef2e935acc35ec2e6f96c650fd3bfba3e96550504d5336100111a004c4b40a0f5f6" + "84ae00818258205d677265fa5bb21ce6d8c7502aca70b9316d10e958611f3c6b758f65ad9599\ + \96000182a40058390030fb3b8539951e26f034910a5a37f22cb99d94d1d409f69ddbaea9710f\ + \45aaf1b2959db6e5ff94dbb1f823bf257680c3c723ac2d49f97546011a0023e8fa028201d818\ + \418003d8185182014e4d01000033222220051200120011a30058390030fb3b8539951e26f034\ + \910a5a37f22cb99d94d1d409f69ddbaea9710f45aaf1b2959db6e5ff94dbb1f823bf257680c3\ + \c723ac2d49f97546011a000f424003d81858468200830301828200581c1c12f03c1ef2e935ac\ + \c35ec2e6f96c650fd3bfba3e96550504d533618200581c30fb3b8539951e26f034910a5a37f2\ + \2cb99d94d1d409f69ddbaea971021a0002b56903187b048882008200581c1730b1b700d616d5\ + \1555538e83d67f13c113ad5f9b22212703482cb382018200581c1730b1b700d616d51555538e\ + \83d67f13c113ad5f9b22212703482cb383028200581c1730b1b700d616d51555538e83d67f13\ + \c113ad5f9b22212703482cb3581c1730b1b700d616d51555538e83d67f13c113ad5f9b222127\ + \03482cb38a03581c1730b1b700d616d51555538e83d67f13c113ad5f9b22212703482cb35820\ + \fbf6d41985670b9041c5bf362b5262cf34add5d265975de176d613ca05f370960101d81e8201\ + \01581de11730b1b700d616d51555538e83d67f13c113ad5f9b22212703482cb381581c1730b1\ + \b700d616d51555538e83d67f13c113ad5f9b22212703482cb3838400191f90447f000001507b\ + \7b7b7b7b7b7b7b7b7b7b7b7b7b7b7b8301191f906b6578616d706c652e636f6d82026b657861\ + \6d706c652e636f6d827468747470733a2f2f6578616d706c652e636f6d2f582094b8cac47761\ + \c1140c57a48d56ab15d27a842abff041b3798b8618fa84641f5a8304581c1730b1b700d616d5\ + \1555538e83d67f13c113ad5f9b22212703482cb3018405581c5d677265fa5bb21ce6d8c7502a\ + \ca70b9316d10e958611f3c6b758f65581c5d677265fa5bb21ce6d8c7502aca70b9316d10e958\ + \611f3c6b758f655820fbf6d41985670b9041c5bf362b5262cf34add5d265975de176d613ca05\ + \f37096820682010182068201a18200581c1730b1b700d616d51555538e83d67f13c113ad5f9b\ + \22212703482cb30105a1581de01730b1b700d616d51555538e83d67f13c113ad5f9b22212703\ + \482cb3010682a1581c5d677265fa5bb21ce6d8c7502aca70b9316d10e958611f3c6b758f65b6\ + \000101010219271003192710041903e8050106010701080109d81e8201010ad81e8201010bd8\ + \1e8201010e8201011001110112a20098a61a0003236119032c01011903e819023b00011903e8\ + \195e7104011903e818201a0001ca761928eb041959d818641959d818641959d818641959d818\ + \641959d818641959d81864186418641959d81864194c5118201a0002acfa182019b551041a00\ + \0363151901ff00011a00015c3518201a000797751936f404021a0002ff941a0006ea7818dc00\ + \01011903e8196ff604021a0003bd081a00034ec5183e011a00102e0f19312a011a00032e8019\ + \01a5011a0002da781903e819cf06011a00013a34182019a8f118201903e818201a00013aac01\ + \19e143041903e80a1a00030219189c011a00030219189c011a0003207c1901d9011a00033000\ + \1901ff0119ccf3182019fd40182019ffd5182019581e18201940b318201a00012adf18201a00\ + \02ff941a0006ea7818dc0001011a00010f92192da7000119eabb18201a0002ff941a0006ea78\ + \18dc0001011a0002ff941a0006ea7818dc0001011a000c504e197712041a001d6af61a000142\ + \5b041a00040c660004001a00014fab18201a0003236119032c010119a0de18201a00033d7618\ + \201979f41820197fb8182019a95d1820197df718201995aa18201a009063b91903fd0a0198af\ + \1a0003236119032c01011903e819023b00011903e8195e7104011903e818201a0001ca761928\ + \eb041959d818641959d818641959d818641959d818641959d818641959d81864186418641959\ + \d81864194c5118201a0002acfa182019b551041a000363151901ff00011a00015c3518201a00\ + \0797751936f404021a0002ff941a0006ea7818dc0001011903e8196ff604021a0003bd081a00\ + \034ec5183e011a00102e0f19312a011a00032e801901a5011a0002da781903e819cf06011a00\ + \013a34182019a8f118201903e818201a00013aac0119e143041903e80a1a00030219189c011a\ + \00030219189c011a0003207c1901d9011a000330001901ff0119ccf3182019fd40182019ffd5\ + \182019581e18201940b318201a00012adf18201a0002ff941a0006ea7818dc0001011a00010f\ + \92192da7000119eabb18201a0002ff941a0006ea7818dc0001011a0002ff941a0006ea7818dc\ + \0001011a0011b22c1a0005fdde00021a000c504e197712041a001d6af61a0001425b041a0004\ + \0c660004001a00014fab18201a0003236119032c010119a0de18201a00033d7618201979f418\ + \20197fb8182019a95d1820197df718201995aa18201b00000004a817c8001b00000004a817c8\ + \001a009063b91903fd0a1b00000004a817c800001b00000004a817c8001382d81e820101d81e\ + \8201011482010115820101160117188c18180a01075820000000000000000000000000000000\ + \000000000000000000000000000000000008187c09a1581c1d6445ddeda578117f393848e685\ + \128f1e78ad0c4e48129c5964dc2ea14a4974657374546f6b656e010e81581c1c12f03c1ef2e9\ + \35acc35ec2e6f96c650fd3bfba3e96550504d533610f01108258390030fb3b8539951e26f034\ + \910a5a37f22cb99d94d1d409f69ddbaea9711c12f03c1ef2e935acc35ec2e6f96c650fd3bfba\ + \3e96550504d5336100111a004c4b40a0f5f6" txBinaryFixture5 :: String txBinaryFixture5 = From 00f1675b8aa8f5c9c7484e5992a3dfe40f81ebc7 Mon Sep 17 00:00:00 2001 From: peter Date: Mon, 19 Dec 2022 18:14:12 +0100 Subject: [PATCH 138/373] bump csl in template --- package-lock.json | 21 ++++++++- package.json | 1 + templates/ctl-scaffold/package-lock.json | 57 ++++++++++++++++++------ templates/ctl-scaffold/package.json | 4 +- 4 files changed, 65 insertions(+), 18 deletions(-) diff --git a/package-lock.json b/package-lock.json index c61e8c2a58..61874b0075 100644 --- a/package-lock.json +++ b/package-lock.json @@ -1,18 +1,19 @@ { "name": "cardano-transaction-lib", - "version": "3.0.0", + "version": "4.0.0", "lockfileVersion": 2, "requires": true, "packages": { "": { "name": "cardano-transaction-lib", - "version": "3.0.0", + "version": "4.0.0", "license": "MIT", "dependencies": { "@emurgo/cardano-message-signing-browser": "1.0.1", "@emurgo/cardano-message-signing-nodejs": "1.0.1", "@emurgo/cardano-serialization-lib-browser": "11.2.1", "@emurgo/cardano-serialization-lib-nodejs": "11.2.1", + "@mlabs-haskell/json-bigint": " 1.0.0", "@noble/secp256k1": "^1.7.0", "apply-args-browser": "0.0.1", "apply-args-nodejs": "0.0.1", @@ -118,6 +119,14 @@ "@jridgewell/sourcemap-codec": "^1.4.10" } }, + "node_modules/@mlabs-haskell/json-bigint": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/@mlabs-haskell/json-bigint/-/json-bigint-1.0.0.tgz", + "integrity": "sha512-Opo07yXP/OU9mIoGmY5VVuDy5kxmb3fBAG3U9dbC15qK1OCpVLJAlxbdOfBmLOja94SnIfZINUU2xvYtVfk65w==", + "dependencies": { + "bignumber.js": "^9.0.0" + } + }, "node_modules/@noble/secp256k1": { "version": "1.7.0", "resolved": "https://registry.npmjs.org/@noble/secp256k1/-/secp256k1-1.7.0.tgz", @@ -883,6 +892,14 @@ "node": ">=0.6" } }, + "node_modules/bignumber.js": { + "version": "9.1.1", + "resolved": "https://registry.npmjs.org/bignumber.js/-/bignumber.js-9.1.1.tgz", + "integrity": "sha512-pHm4LsMJ6lzgNGVfZHjMoO8sdoRhOzOH4MLmY65Jg70bpxCKu5iOHNJyfF6OyvYw7t8Fpf35RuzUyqnQsj8Vig==", + "engines": { + "node": "*" + } + }, "node_modules/binary-extensions": { "version": "2.2.0", "resolved": "https://registry.npmjs.org/binary-extensions/-/binary-extensions-2.2.0.tgz", diff --git a/package.json b/package.json index c916627339..f71612d5ab 100755 --- a/package.json +++ b/package.json @@ -34,6 +34,7 @@ "@emurgo/cardano-serialization-lib-browser": "11.2.1", "@emurgo/cardano-serialization-lib-nodejs": "11.2.1", "base64-js": "^1.5.1", + "@noble/secp256k1": "^1.7.0", "big-integer": "1.6.51", "blakejs": "1.2.1", "bufferutil": "4.0.5", diff --git a/templates/ctl-scaffold/package-lock.json b/templates/ctl-scaffold/package-lock.json index 61ac4dd597..1aaba77d7c 100644 --- a/templates/ctl-scaffold/package-lock.json +++ b/templates/ctl-scaffold/package-lock.json @@ -11,8 +11,10 @@ "dependencies": { "@emurgo/cardano-message-signing-browser": "1.0.1", "@emurgo/cardano-message-signing-nodejs": "1.0.1", - "@emurgo/cardano-serialization-lib-browser": "^11.1.1-alpha.1", - "@emurgo/cardano-serialization-lib-nodejs": "11.1.1-alpha.1", + "@emurgo/cardano-serialization-lib-browser": "11.2.1", + "@emurgo/cardano-serialization-lib-nodejs": "11.2.1", + "@mlabs-haskell/json-bigint": " 1.0.0", + "@noble/secp256k1": "^1.7.0", "apply-args-browser": "0.0.1", "apply-args-nodejs": "0.0.1", "base64-js": "^1.5.1", @@ -55,14 +57,33 @@ "integrity": "sha512-PoKh1tQnJX18f8iEr8Jk1KXxKCn9eqaSslMI1pyOJvYRJhQVDLCh0+9YReufjp0oFJIY1ShcrR+4/WnECVZUKQ==" }, "node_modules/@emurgo/cardano-serialization-lib-browser": { - "version": "11.1.1-alpha.1", - "resolved": "https://registry.npmjs.org/@emurgo/cardano-serialization-lib-browser/-/cardano-serialization-lib-browser-11.1.1-alpha.1.tgz", - "integrity": "sha512-R/pVuu9fvnL11eUJ/5O9UDKhwSsAZKlEqKl2hfDoq69giBcsrlFohVrhZFiDt6Nuyic9k5XfsNMCXjYxKJJ3qQ==" + "version": "11.2.1", + "resolved": "https://registry.npmjs.org/@emurgo/cardano-serialization-lib-browser/-/cardano-serialization-lib-browser-11.2.1.tgz", + "integrity": "sha512-J9Pmeta7y1GYnMCxtb3GnGCRw6zk1wiQ8EdCYQRn/Yqa/ss1zoBjd41euVi02Eb58aLuOJS81nNU+BcMLGXvUg==" }, "node_modules/@emurgo/cardano-serialization-lib-nodejs": { - "version": "11.1.1-alpha.1", - "resolved": "https://registry.npmjs.org/@emurgo/cardano-serialization-lib-nodejs/-/cardano-serialization-lib-nodejs-11.1.1-alpha.1.tgz", - "integrity": "sha512-aUwPZbRoxcFBi3aEJVowYW6AHDuzZ7Mxk4KSqa2N53JSw8CWzNWI7lx+9OCNrGGLGV+9yVqHC2skdg5P3j2bSg==" + "version": "11.2.1", + "resolved": "https://registry.npmjs.org/@emurgo/cardano-serialization-lib-nodejs/-/cardano-serialization-lib-nodejs-11.2.1.tgz", + "integrity": "sha512-+Rw35NW4Qv/9uFaPxhKtxiIPmoBEIFMAgdqQxZTw6hNT/wvBp2TvwTBPnOW8ODs7GUAA8nrO1rJJAaxF+mAG2w==" + }, + "node_modules/@mlabs-haskell/json-bigint": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/@mlabs-haskell/json-bigint/-/json-bigint-1.0.0.tgz", + "integrity": "sha512-Opo07yXP/OU9mIoGmY5VVuDy5kxmb3fBAG3U9dbC15qK1OCpVLJAlxbdOfBmLOja94SnIfZINUU2xvYtVfk65w==", + "dependencies": { + "bignumber.js": "^9.0.0" + } + }, + "node_modules/@noble/secp256k1": { + "version": "1.7.0", + "resolved": "https://registry.npmjs.org/@noble/secp256k1/-/secp256k1-1.7.0.tgz", + "integrity": "sha512-kbacwGSsH/CTout0ZnZWxnW1B+jH/7r/WAAKLBtrRJ/+CUH7lgmQzl3GTrQua3SGKWNSDsS6lmjnDpIJ5Dxyaw==", + "funding": [ + { + "type": "individual", + "url": "https://paulmillr.com/funding/" + } + ] }, "node_modules/@nodelib/fs.scandir": { "version": "2.1.5", @@ -729,6 +750,14 @@ "node": ">=0.6" } }, + "node_modules/bignumber.js": { + "version": "9.1.1", + "resolved": "https://registry.npmjs.org/bignumber.js/-/bignumber.js-9.1.1.tgz", + "integrity": "sha512-pHm4LsMJ6lzgNGVfZHjMoO8sdoRhOzOH4MLmY65Jg70bpxCKu5iOHNJyfF6OyvYw7t8Fpf35RuzUyqnQsj8Vig==", + "engines": { + "node": "*" + } + }, "node_modules/binary-extensions": { "version": "2.2.0", "resolved": "https://registry.npmjs.org/binary-extensions/-/binary-extensions-2.2.0.tgz", @@ -5609,14 +5638,14 @@ "integrity": "sha512-PoKh1tQnJX18f8iEr8Jk1KXxKCn9eqaSslMI1pyOJvYRJhQVDLCh0+9YReufjp0oFJIY1ShcrR+4/WnECVZUKQ==" }, "@emurgo/cardano-serialization-lib-browser": { - "version": "11.1.1-alpha.1", - "resolved": "https://registry.npmjs.org/@emurgo/cardano-serialization-lib-browser/-/cardano-serialization-lib-browser-11.1.1-alpha.1.tgz", - "integrity": "sha512-R/pVuu9fvnL11eUJ/5O9UDKhwSsAZKlEqKl2hfDoq69giBcsrlFohVrhZFiDt6Nuyic9k5XfsNMCXjYxKJJ3qQ==" + "version": "11.2.1", + "resolved": "https://registry.npmjs.org/@emurgo/cardano-serialization-lib-browser/-/cardano-serialization-lib-browser-11.2.1.tgz", + "integrity": "sha512-J9Pmeta7y1GYnMCxtb3GnGCRw6zk1wiQ8EdCYQRn/Yqa/ss1zoBjd41euVi02Eb58aLuOJS81nNU+BcMLGXvUg==" }, "@emurgo/cardano-serialization-lib-nodejs": { - "version": "11.1.1-alpha.1", - "resolved": "https://registry.npmjs.org/@emurgo/cardano-serialization-lib-nodejs/-/cardano-serialization-lib-nodejs-11.1.1-alpha.1.tgz", - "integrity": "sha512-aUwPZbRoxcFBi3aEJVowYW6AHDuzZ7Mxk4KSqa2N53JSw8CWzNWI7lx+9OCNrGGLGV+9yVqHC2skdg5P3j2bSg==" + "version": "11.2.1", + "resolved": "https://registry.npmjs.org/@emurgo/cardano-serialization-lib-nodejs/-/cardano-serialization-lib-nodejs-11.2.1.tgz", + "integrity": "sha512-+Rw35NW4Qv/9uFaPxhKtxiIPmoBEIFMAgdqQxZTw6hNT/wvBp2TvwTBPnOW8ODs7GUAA8nrO1rJJAaxF+mAG2w==" }, "@mlabs-haskell/json-bigint": { "version": "1.0.0", diff --git a/templates/ctl-scaffold/package.json b/templates/ctl-scaffold/package.json index 5b7d6d60f4..ef6e42b2ad 100644 --- a/templates/ctl-scaffold/package.json +++ b/templates/ctl-scaffold/package.json @@ -24,8 +24,8 @@ "apply-args-nodejs": "0.0.1", "@emurgo/cardano-message-signing-browser": "1.0.1", "@emurgo/cardano-message-signing-nodejs": "1.0.1", - "@emurgo/cardano-serialization-lib-browser": "^11.1.1-alpha.1", - "@emurgo/cardano-serialization-lib-nodejs": "11.1.1-alpha.1", + "@emurgo/cardano-serialization-lib-browser": "11.2.1", + "@emurgo/cardano-serialization-lib-nodejs": "11.2.1", "base64-js": "^1.5.1", "@noble/secp256k1": "^1.7.0", "big-integer": "1.6.51", From d25f0366b3522e8bf3273b009ac6a76c9602afcf Mon Sep 17 00:00:00 2001 From: nalane Date: Mon, 19 Dec 2022 10:21:02 -0700 Subject: [PATCH 139/373] removed newtype instance for Cip25String --- src/Internal/Metadata/Cip25/Cip25String.purs | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/src/Internal/Metadata/Cip25/Cip25String.purs b/src/Internal/Metadata/Cip25/Cip25String.purs index 0fa48c9bc9..1289e1dbe0 100644 --- a/src/Internal/Metadata/Cip25/Cip25String.purs +++ b/src/Internal/Metadata/Cip25/Cip25String.purs @@ -32,7 +32,7 @@ import Data.Array as Array import Data.Either (hush, note) import Data.Foldable (fold, foldMap) import Data.Maybe (Maybe(Nothing, Just), isJust) -import Data.Newtype (class Newtype, unwrap, wrap) +import Data.Newtype (unwrap, wrap) import Data.String.CodePoints as String import Data.TextDecoder (decodeUtf8) import Data.TextEncoder (encodeUtf8) @@ -51,8 +51,6 @@ derive newtype instance ToData Cip25String derive newtype instance FromData Cip25String derive newtype instance EncodeAeson Cip25String -derive instance newtypeCip25String :: Newtype Cip25String _ - instance Show Cip25String where show (Cip25String str) = "(unsafePartial (fromJust (mkCip25String " <> show str @@ -147,5 +145,5 @@ fromMetadataString datum = do strings :: Array Cip25String <- fromMetadata datum let bytes :: Array ByteArray - bytes = map (wrap <<< encodeUtf8 <<< unwrap) strings + bytes = map (\(Cip25String s) -> wrap $ encodeUtf8 s) strings hush $ decodeUtf8 $ unwrap $ fold bytes From 10b530c026b568898a1767df76243c37dcb2139a Mon Sep 17 00:00:00 2001 From: peter Date: Mon, 19 Dec 2022 18:28:09 +0100 Subject: [PATCH 140/373] set lockfileVersion to 1 --- package-lock.json | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/package-lock.json b/package-lock.json index 61874b0075..e50b7354b8 100644 --- a/package-lock.json +++ b/package-lock.json @@ -1,7 +1,7 @@ { "name": "cardano-transaction-lib", "version": "4.0.0", - "lockfileVersion": 2, + "lockfileVersion": 1, "requires": true, "packages": { "": { From f7ec71e3101ff39e3cdc14fbb876bfe946ff27de Mon Sep 17 00:00:00 2001 From: Bradley Date: Mon, 19 Dec 2022 12:34:40 -0500 Subject: [PATCH 141/373] Add back unreleased --- CHANGELOG.md | 34 +++++++++++++++++++++++++++------- 1 file changed, 27 insertions(+), 7 deletions(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index 6909fe75a8..c7de03366c 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -7,36 +7,56 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) -- [[v4.0.0]](#v400) +- [Unrealeased](#unrealeased) - [Added](#added) - [Changed](#changed) - [Removed](#removed) - [Fixed](#fixed) - [Runtime Dependencies](#runtime-dependencies) -- [[3.0.0] - 2022-11-21](#300---2022-11-21) +- [[v4.0.0] - 2022-12-15](#v400---2022-12-15) - [Added](#added-1) - [Changed](#changed-1) - [Removed](#removed-1) - [Fixed](#fixed-1) - [Runtime Dependencies](#runtime-dependencies-1) -- [[2.0.0] - 2022-09-12](#200---2022-09-12) +- [[3.0.0] - 2022-11-21](#300---2022-11-21) - [Added](#added-2) - [Changed](#changed-2) - [Removed](#removed-2) - [Fixed](#fixed-2) -- [[2.0.0-alpha] - 2022-07-05](#200-alpha---2022-07-05) + - [Runtime Dependencies](#runtime-dependencies-2) +- [[2.0.0] - 2022-09-12](#200---2022-09-12) - [Added](#added-3) - - [Removed](#removed-3) - [Changed](#changed-3) + - [Removed](#removed-3) - [Fixed](#fixed-3) -- [[1.1.0] - 2022-06-30](#110---2022-06-30) +- [[2.0.0-alpha] - 2022-07-05](#200-alpha---2022-07-05) + - [Added](#added-4) + - [Removed](#removed-4) + - [Changed](#changed-4) - [Fixed](#fixed-4) -- [[1.0.1] - 2022-06-17](#101---2022-06-17) +- [[1.1.0] - 2022-06-30](#110---2022-06-30) - [Fixed](#fixed-5) +- [[1.0.1] - 2022-06-17](#101---2022-06-17) + - [Fixed](#fixed-6) - [[1.0.0] - 2022-06-10](#100---2022-06-10) +## Unrealeased + +### Added + +### Changed + +### Removed + +### Fixed + +### Runtime Dependencies + +TBD + ## [v4.0.0] - 2022-12-15 ### Added From 274c20d8ce86f8bceb2fb41c74351b588393e9a3 Mon Sep 17 00:00:00 2001 From: Bradley Date: Mon, 19 Dec 2022 14:23:28 -0500 Subject: [PATCH 142/373] add kupo --- flake.nix | 6 ++++++ nix/test-nixos-configuration.nix | 9 +++++++++ 2 files changed, 15 insertions(+) diff --git a/flake.nix b/flake.nix index c8c7cf7ef4..9fe8310d2f 100644 --- a/flake.nix +++ b/flake.nix @@ -48,6 +48,7 @@ { self , nixpkgs , cardano-configurations + , kupo , ... }@inputs: let @@ -429,6 +430,11 @@ services.ogmios.package = inputs.ogmios.packages.x86_64-linux."ogmios:exe:ogmios"; } + inputs.kupo-nixos.nixosModules.kupo + { + services.kupo.package = + inputs.kupo.packages.x86_64-linux."kupo"; + } inputs.ogmios-datum-cache-nixos.nixosModules.ogmios-datum-cache { services.ogmios-datum-cache.package = diff --git a/nix/test-nixos-configuration.nix b/nix/test-nixos-configuration.nix index 740eb69497..3f1d06f85d 100644 --- a/nix/test-nixos-configuration.nix +++ b/nix/test-nixos-configuration.nix @@ -38,6 +38,15 @@ nodeSocket = "/var/run/cardano-node/node.socket"; }; + services.kupo = { + enable = true; + host = "0.0.0.0"; + user = "kupo"; + group = "kupo"; + nodeConfig = "${cardano-configurations}/network/mainnet/cardano-node/config.json"; + nodeSocket = "/var/run/cardano-node/node.socket"; + }; + services.ogmios-datum-cache = { enable = true; host = "0.0.0.0"; From 809fb896a9dc95a511c49ac902bbbc5cc31da975 Mon Sep 17 00:00:00 2001 From: Bradley Date: Mon, 19 Dec 2022 14:26:28 -0500 Subject: [PATCH 143/373] remove packages --- flake.nix | 4 ---- 1 file changed, 4 deletions(-) diff --git a/flake.nix b/flake.nix index 9fe8310d2f..83a928931c 100644 --- a/flake.nix +++ b/flake.nix @@ -431,10 +431,6 @@ inputs.ogmios.packages.x86_64-linux."ogmios:exe:ogmios"; } inputs.kupo-nixos.nixosModules.kupo - { - services.kupo.package = - inputs.kupo.packages.x86_64-linux."kupo"; - } inputs.ogmios-datum-cache-nixos.nixosModules.ogmios-datum-cache { services.ogmios-datum-cache.package = From 2652f37524a0ed67306c15b6964676ee4939a2b1 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Tue, 20 Dec 2022 10:15:09 +0000 Subject: [PATCH 144/373] Apply suggestions from code review --- nix/test-nixos-configuration.nix | 3 +++ 1 file changed, 3 insertions(+) diff --git a/nix/test-nixos-configuration.nix b/nix/test-nixos-configuration.nix index 974f8214b0..8be6a4a510 100644 --- a/nix/test-nixos-configuration.nix +++ b/nix/test-nixos-configuration.nix @@ -6,8 +6,11 @@ memorySize = 8192; diskSize = 100000; forwardPorts = [ + # TODO What is this port for? SSH? { from = "host"; host.port = 2222; guest.port = 22; } + # Ogmios { from = "host"; host.port = 1337; guest.port = 1337; } + # Ogmios Datum Cache { from = "host"; host.port = 9999; guest.port = 9999; } ]; }; From 4a252675a0b35b89f2ce5fd12a5079a7bdc953fa Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Tue, 20 Dec 2022 10:20:42 +0000 Subject: [PATCH 145/373] Apply suggestions from code review --- nix/test-nixos-configuration.nix | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/nix/test-nixos-configuration.nix b/nix/test-nixos-configuration.nix index 8be6a4a510..9b63cda494 100644 --- a/nix/test-nixos-configuration.nix +++ b/nix/test-nixos-configuration.nix @@ -6,7 +6,7 @@ memorySize = 8192; diskSize = 100000; forwardPorts = [ - # TODO What is this port for? SSH? + # SSH { from = "host"; host.port = 2222; guest.port = 22; } # Ogmios { from = "host"; host.port = 1337; guest.port = 1337; } From 620608aca411710f0e97b94f730029787cf3ab00 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Tue, 20 Dec 2022 16:29:20 +0400 Subject: [PATCH 146/373] Expand the docs --- ...p256k1-support.md => secp256k1-support.md} | 20 +++++++++++++------ 1 file changed, 14 insertions(+), 6 deletions(-) rename doc/{Secp256k1-support.md => secp256k1-support.md} (54%) diff --git a/doc/Secp256k1-support.md b/doc/secp256k1-support.md similarity index 54% rename from doc/Secp256k1-support.md rename to doc/secp256k1-support.md index 4c9bcd4d12..e6af3d1eb4 100644 --- a/doc/Secp256k1-support.md +++ b/doc/secp256k1-support.md @@ -18,7 +18,7 @@ For a more in depth oversight please see [Cip-49](https://github.com/mlabs-haske ## Usage -[Cip-49](https://github.com/mlabs-haskell/CIPs/tree/c5bdd66fe49c19c341499f86cebaa2eef9e90b74/CIP-0049) provides two new builtin functions: +[Cip-49](https://github.com/mlabs-haskell/CIPs/tree/c5bdd66fe49c19c341499f86cebaa2eef9e90b74/CIP-0049) provides two new Plutus builtin functions for signature verification. Both functions take the following as Parameters: - A verification key; @@ -29,12 +29,20 @@ The two functions are: **1. A verification function for [ECDSA](https://en.bitcoin.it/wiki/Elliptic_Curve_Digital_Signature_Algorithm) signatures.** -[ECDSA usage example](../examples/ECDSA.purs)\ +**2. A verification function for [Schnorr](https://github.com/bitcoin/bips/blob/master/bip-0340.mediawiki) signatures.** -[ECDSA source code](../src/Contract/Crypto/Secp256k1/ECDSA.purs) +CTL provides off-chain variants of these functions that work the same way (the only difference is that in CTL the arguments are typed, while in Plutus `BuiltinByteString`s are used). -**2. A verification function for [Schnorr](https://github.com/bitcoin/bips/blob/master/bip-0340.mediawiki) signatures.** +Additionally, CTL exposes functions that allow to work with private keys (derive from bytes, generate) and public keys (derive from a private key), as well as to sign arbitrary data or data hashes. + +All SECP256k1-related domain types (public keys, signatures and hashes) are made serialize-able to PlutusData to allow for simpler offchain/onchain interop. + +[Public interface for ECDSA support in CTL](../src/Contract/Crypto/Secp256k1/ECDSA.purs) + +[ECDSA verification usage example](../examples/ECDSA.purs) + +[Public interface for Schnorr support in CTL](../src/Contract/Crypto/Secp256k1/Schnorr.purs) -[Schnorr usage example](../examples/Schnorr.purs) +[Schnorr verification usage example](../examples/Schnorr.purs) -[Schnorr source code](../src/Contract/Crypto/Secp256k1/Schnorr.purs) +Both examples show how a signature that is constructed off-chain can be passed for on-chain verification. From 6cfc6c2ef6d91d708e7c44d9ae5599318f99a16b Mon Sep 17 00:00:00 2001 From: Bradley <80346526+Bradley-Heather@users.noreply.github.com> Date: Tue, 20 Dec 2022 08:35:58 -0500 Subject: [PATCH 147/373] Update CHANGELOG.md Co-authored-by: Joseph Young --- CHANGELOG.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index c7de03366c..630838fb69 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -43,7 +43,7 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) -## Unrealeased +## Unreleased ### Added From 059f0edb528ce86e53f027efc65ce5a067d5f5a4 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Tue, 20 Dec 2022 19:46:46 +0400 Subject: [PATCH 148/373] Expand documentation coverage and Reorder README sections --- CHANGELOG.md | 2 +- README.md | 65 +++++++++++++++++++++++++--------------------- doc/balancing.md | 38 +++++++++++++++++++++++++++ doc/cip-25-nfts.md | 12 +++++++++ doc/staking.md | 22 ++++++++++++++++ doc/tx-chaining.md | 14 ++++++++++ 6 files changed, 123 insertions(+), 30 deletions(-) create mode 100644 doc/balancing.md create mode 100644 doc/cip-25-nfts.md create mode 100644 doc/staking.md create mode 100644 doc/tx-chaining.md diff --git a/CHANGELOG.md b/CHANGELOG.md index 6909fe75a8..989ee98f4e 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -7,7 +7,7 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) -- [[v4.0.0]](#v400) +- [[v4.0.0] - 2022-12-15](#v400---2022-12-15) - [Added](#added) - [Changed](#changed) - [Removed](#removed) diff --git a/README.md b/README.md index d46dc97bef..565fedd152 100644 --- a/README.md +++ b/README.md @@ -2,37 +2,50 @@ [![Hercules-ci][herc badge]][herc link] [![Cachix Cache][cachix badge]][cachix link] +[![PureScript code documentation][docs badge]][docs link] [herc badge]: https://img.shields.io/badge/ci--by--hercules-green.svg [herc link]: https://hercules-ci.com/github/Plutonomicon/cardano-transaction-lib [cachix badge]: https://img.shields.io/badge/cachix-public_plutonomicon-blue.svg [cachix link]: https://public-plutonomicon.cachix.org +[docs badge]: https://img.shields.io/badge/docs-PureScript%20code%20documentation-%2377F +[docs link]: https://plutonomicon.github.io/cardano-transaction-lib/ -**cardano-transaction-lib** (CTL) is a Purescript library for building smart contract transactions on Cardano. It aims to port the functionality and interface of Plutus off-chain code to the browser environment. +**cardano-transaction-lib** (CTL) is a Purescript library for building smart contract transactions on Cardano. It aims to port the functionality and interface of Plutus off-chain code to the browser environment and NodeJS. **Table of Contents** -- [Roadmap](#roadmap) - - [Light wallet support](#light-wallet-support) - [Documentation](#documentation) + - [Light wallet support](#light-wallet-support) +- [Roadmap](#roadmap) - [Architecture](#architecture) - [Additional resources/tools:](#additional-resourcestools) - [Available support channels info](#available-support-channels-info) -## Roadmap +## Documentation -- [x] **Stage 1** Build a simple transaction in the browser that works with at least one light wallet (Nami) -- [x] **Stage 2** Once we can construct a simple user-to-user transaction, we will try to use the library to submit the tx with nami -- [x] **Stage 3** Once we have a simple working transaction, we will seek to build a Plutus smart contract transaction with datum from scratch -- [x] **Stage 4** Once we can construct Plutus smart contract transactions, we will seek to build a library/DSL/interface such that transactions can be built using constraints and lookups - as close as possible to a cut-and-paste solution from Plutus' `Contract` monad code in Haskell (but with no guarantee that code changes are not necessary) - - [x] **Stage 4.1** Investigate supporting compatibility with the Vasil hardfork and improvements to our initial `Contract` API -- [ ] **Stage 5** Once we have a basic `Contract`-style API, we will further refine its public interface, expand wallet support (see [below](#light-wallet-support)), expose a test interface (**DONE** - see [here](doc/plutip-testing.md)), provide a more ergonomic JS/TS API, support stake validators (**DONE**), and support CIP workflows on the public testnet (**In progress**) -- [ ] **Stage 6** Once CTL's `Contract` interface has been stabilized, we will add support for even more wallets and attempt to deprecate CTL's currently required Haskell server (**DONE**) +Please explore our documentation to discover how to use CTL, how to set up its runtime, and how it compares to Plutus/PAB: + +- [Super quick start](./doc/getting-started.md#setting-up-a-new-project) +- [Adding CTL as a dependency](./doc/ctl-as-dependency.md) +- [CTL's runtime dependencies](./doc/runtime.md) +- [Getting started writing CTL contracts](./doc/getting-started.md) +- [Migrating from Plutus to CTL](./doc/plutus-comparison.md) +- [Testing contracts with Plutip](./doc/plutip-testing.md) +- [End-to-end testing with headless browsers](./doc/e2e-testing.md) +- [CIP-25 NFT standard support](./doc/cip-25-nfts.md) +- [Transaction balancing](./doc/balancing.md) +- [Transaction chaining](./doc/tx-chaining.md) +- [Ada staking support](./doc/staking.md) +- [FAQs](./doc/faq.md) +- [Development workflows for CTL](./doc/development.md) + +You can also access [PureScript documentation for CTL and its dependencies](https://plutonomicon.github.io/cardano-transaction-lib/) for the most recent `develop` version, or [generate it yourself](./doc/development.md#generating-ps-documentation). ### Light wallet support @@ -48,20 +61,15 @@ Support is planned for the following light wallets: - [ ] [Typhon](https://typhonwallet.io/) - [ ] [Yoroi](https://yoroi-wallet.com/) -## Documentation - -Please explore our documentation to discover how to use CTL, how to set up its runtime, and how it compares to Plutus/PAB: - -- [Super quick start](./doc/getting-started.md#setting-up-a-new-project) -- [FAQs](./doc/faq.md) -- [Migrating from Plutus to CTL](./doc/plutus-comparison.md) -- [Adding CTL as a dependency](./doc/ctl-as-dependency.md) -- [Getting started writing CTL contracts](./doc/getting-started.md) -- [CTL's runtime dependencies](./doc/runtime.md) -- [Developing on CTL](./doc/development.md) -- [Testing contracts with Plutip](./doc/plutip-testing.md) +## Roadmap -You can also access [PureScript documentation for CTL and its dependencies](https://plutonomicon.github.io/cardano-transaction-lib/) for the most recent `develop` version, or [generate it yourself](./doc/development.md#generating-ps-documentation). +- [x] **Stage 1** Build a simple transaction in the browser that works with at least one light wallet (Nami) +- [x] **Stage 2** Once we can construct a simple user-to-user transaction, we will try to use the library to submit the tx with nami +- [x] **Stage 3** Once we have a simple working transaction, we will seek to build a Plutus smart contract transaction with datum from scratch +- [x] **Stage 4** Once we can construct Plutus smart contract transactions, we will seek to build a library/DSL/interface such that transactions can be built using constraints and lookups - as close as possible to a cut-and-paste solution from Plutus' `Contract` monad code in Haskell (but with no guarantee that code changes are not necessary) + - [x] **Stage 4.1** Investigate supporting compatibility with the Vasil hardfork and improvements to our initial `Contract` API +- [ ] **Stage 5** Once we have a basic `Contract`-style API, we will further refine its public interface, expand wallet support (see [below](#light-wallet-support)), expose a test interface (**DONE** - see [here](doc/plutip-testing.md)), provide a more ergonomic JS/TS API, support stake validators (**DONE**), and support CIP workflows on the public testnet (**In progress**) +- [ ] **Stage 6** Once CTL's `Contract` interface has been stabilized, we will add support for even more wallets and attempt to deprecate CTL's currently required Haskell server (**DONE**) ## Architecture @@ -71,16 +79,15 @@ CTL is directly inspired by the Plutus Application Backend (PAB). Unlike PAB, ho - This is handled by `cardano-serialization-lib`, a Rust library available as WASM 2. How do we query the chain? - This has been solved using Ogmios & Kupo - - We will support an alternative BlockFrost backend as well in the future + - We [will support](https://cardano.ideascale.com/c/idea/420791) an alternative [BlockFrost](https://blockfrost.io/) backend as well in the future 3. How do we query for datums (i.e. the datums themselves and not just their hashes)? - `ogmios-datum-cache` solves this problem -4. How do we submit the transaction? +4. How do we get wallet data? - This is done via browser-based light wallet integration in the browser based on CIP-30 5. How closely should we follow Plutus' `Contract` API? - CTL's `Contract` model is **significantly** less restrictive than Plutus' and allows for arbitrary effects within the `Contract` monad - - Certain features cannot be directly translated into Purescript from Haskell due to differences between the two languages (e.g. CTL's `DatumType` and `RedeemerType` are type class with fundeps, as Purescript lacks any notion of type families/type-level functions) -6. A lingering concern remains around storage solutions, if needed - - This can be in memory, in various browser storage solutions, or a decentralized DB like Fluree + - Certain features cannot be directly translated into Purescript from Haskell due to differences between the two languages + - Some of the Plutus conventions do not make sense for us, due to differences between on-chain and off-chain ## Additional resources/tools: diff --git a/doc/balancing.md b/doc/balancing.md new file mode 100644 index 0000000000..924af5f68d --- /dev/null +++ b/doc/balancing.md @@ -0,0 +1,38 @@ + + + +- [Configuring balancing process](#configuring-balancing-process) + - [Balancer constraints](#balancer-constraints) + - [Concurrent spending](#concurrent-spending) + - [Balancing process limitations](#balancing-process-limitations) + + + +# Configuring balancing process + +Transaction balancing in Cardano is the process of finding a set of inputs and outputs that that sum up to zero, covering all the required fees for the transaction to be valid. + +## Balancer constraints + +CTL allows to tweak the default balancer behavior by letting the user impose constraints on the UTxO set that is used in the process (`balanceTxWithConstraints`): + +- providing additional UTxOs to use: `mustUseUtxosAtAddresses` / `mustUseUtxosAtAddress` / `mustUseAdditionalUtxos` +- overriding change address: `mustSendChangeToAddress` +- prevent certain UTxOs from being spent: `mustNotSpendUtxosWithOutRefs` / `mustNotSpendUtxoWithOutRef` +- distribute token outputs equally between change UTxOs: `mustGenChangeOutsWithMaxTokenQuantity` + +## Concurrent spending + +Attempting to spend UTxOs concurrently leads to some of the transactions being rejected. To ensure that no concurrent spending is happening, CTL uses it's own UTxO locking machinery. `balanceTxs` and `balanceTxsWithConstraints` functions can be used to construct multiple transactions at once, ensuring that the sets of inputs do not intersect. + +Obviously, the number of available UTxOs must be greater than the number of transactions. CTL will throw an exception if it's not the case. + +## Balancing process limitations + +It may be surprising at first, but balancing a transaction on Cardano is generally undecidable. + +This is because transaction fees depend on execution unit budgets of the validator scripts, and the execution paths of the scripts depend on the set of inputs, that the balancer attempts to provide to, in turn, cover the fees. It is a recursive process that continues until the cycle of adding new inputs, evaluating the fees and generating change outputs converges to some configuration of inputs and outputs, where sum of all inputs and outputs minus fees is zero. + +It is possible to intentionally craft a script with execution fees depending on the number of inputs in a non-trivial way, causing the balancer to enter a potentially infinite loop. + +Another problem is that the intermediate evaluations of the script that happen during balancer may fail. The balancer provides a guarantee that all script executions will only run on "pre-balanced" transactions (in our terminology). That means that CTL supports the scripts that rely on the transaction contexts they validate to be balanced. diff --git a/doc/cip-25-nfts.md b/doc/cip-25-nfts.md new file mode 100644 index 0000000000..2e74f92225 --- /dev/null +++ b/doc/cip-25-nfts.md @@ -0,0 +1,12 @@ + + + +- [CIP-25 NFT Metadata standard](#cip-25-nft-metadata-standard) + + + +# CIP-25 NFT Metadata standard + +CTL includes [CIP-25](https://cips.cardano.org/cips/cip25/) (v2) domain type definitions that enable creation of standard-compliant applications with ease. The definitions abstract away conversions between PlutusData and PureScript types. + +See [`Contract.Metadata`](https://plutonomicon.github.io/cardano-transaction-lib/Contract.Metadata.html#t:Cip25MetadataEntry) module. diff --git a/doc/staking.md b/doc/staking.md new file mode 100644 index 0000000000..ba26633026 --- /dev/null +++ b/doc/staking.md @@ -0,0 +1,22 @@ + + + +- [Staking constraints in CTL](#staking-constraints-in-ctl) + + + +# Staking constraints in CTL + +[Staking](https://cardano.org/stake-pool-delegation/) is the process of delegation of Ada claimed by a stake key or a script to a staking pool. Staking is an important part of Cardano operation, because it incentivizes block validators to actually perform their work. + +[The explainer from Plutonomicon](https://github.com/Plutonomicon/plutonomicon/blob/main/stake-scripts.md) show how staking works from a more technical perspective. + +CTL supports all operations with stake: + +- Registration/Deregistration of stake credentials (pubkeys, plutus and native scripts) +- Registration/Retirement of a stake pool +- Delegation of ADA to a stake pool +- Receiving rewards +- Withdrawing rewards + +[Our tests](./test/Plutip/Staking.purs) include examples for each of the supported cases. diff --git a/doc/tx-chaining.md b/doc/tx-chaining.md new file mode 100644 index 0000000000..c7f65fb181 --- /dev/null +++ b/doc/tx-chaining.md @@ -0,0 +1,14 @@ + + + +- [Transaction chaining with CTL](#transaction-chaining-with-ctl) + + + +# Transaction chaining with CTL + +Transaction chaining on Cardano is the ability to send transactions that depend on each other in quick succession, without waiting for the previous transactions to be confirmed (not to be confused with transaction batching). + +In case the transactions come from multiple actors, some off-chain data delivery mechanism should be used - it's up to the application developers to implement it. + +The only piece of data that is actually needed is the additional UTxOs that the CTL query layer is not (yet) aware of. `mustUseAdditionalUtxos` [balancer constraint](./balancing.md) can be used for that, as shown in the [transaction chaining example](https://github.com/Plutonomicon/cardano-transaction-lib/blob/develop/examples/TxChaining.purs). From f2d38aa5e69ef1d665a21437aa573bdf3d4d24e8 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Tue, 20 Dec 2022 19:51:21 +0400 Subject: [PATCH 149/373] Do not generate TOCs in small doc files --- doc/cip-25-nfts.md | 7 +------ doc/staking.md | 7 +------ doc/tx-chaining.md | 7 +------ 3 files changed, 3 insertions(+), 18 deletions(-) diff --git a/doc/cip-25-nfts.md b/doc/cip-25-nfts.md index 2e74f92225..4111512317 100644 --- a/doc/cip-25-nfts.md +++ b/doc/cip-25-nfts.md @@ -1,9 +1,4 @@ - - - -- [CIP-25 NFT Metadata standard](#cip-25-nft-metadata-standard) - - + # CIP-25 NFT Metadata standard diff --git a/doc/staking.md b/doc/staking.md index ba26633026..33d1b81349 100644 --- a/doc/staking.md +++ b/doc/staking.md @@ -1,9 +1,4 @@ - - - -- [Staking constraints in CTL](#staking-constraints-in-ctl) - - + # Staking constraints in CTL diff --git a/doc/tx-chaining.md b/doc/tx-chaining.md index c7f65fb181..5722d776e2 100644 --- a/doc/tx-chaining.md +++ b/doc/tx-chaining.md @@ -1,9 +1,4 @@ - - - -- [Transaction chaining with CTL](#transaction-chaining-with-ctl) - - + # Transaction chaining with CTL From 3f4139a5d9b382d3d9744a7abeee2acb622c7285 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Tue, 20 Dec 2022 19:54:37 +0400 Subject: [PATCH 150/373] Fix broken link --- doc/staking.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/doc/staking.md b/doc/staking.md index 33d1b81349..fa09023bbf 100644 --- a/doc/staking.md +++ b/doc/staking.md @@ -14,4 +14,4 @@ CTL supports all operations with stake: - Receiving rewards - Withdrawing rewards -[Our tests](./test/Plutip/Staking.purs) include examples for each of the supported cases. +[Our tests](../test/Plutip/Staking.purs) include examples for each of the supported cases. From 49182c8889daa7765320853f371c90f9a10d4e57 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Tue, 20 Dec 2022 15:57:30 +0000 Subject: [PATCH 151/373] Run `npm i --package-lock-only` --- package-lock.json | 6753 +--------------------- templates/ctl-scaffold/package-lock.json | 5804 +------------------ 2 files changed, 246 insertions(+), 12311 deletions(-) diff --git a/package-lock.json b/package-lock.json index e50b7354b8..124655e7ed 100644 --- a/package-lock.json +++ b/package-lock.json @@ -3,6578 +3,6 @@ "version": "4.0.0", "lockfileVersion": 1, "requires": true, - "packages": { - "": { - "name": "cardano-transaction-lib", - "version": "4.0.0", - "license": "MIT", - "dependencies": { - "@emurgo/cardano-message-signing-browser": "1.0.1", - "@emurgo/cardano-message-signing-nodejs": "1.0.1", - "@emurgo/cardano-serialization-lib-browser": "11.2.1", - "@emurgo/cardano-serialization-lib-nodejs": "11.2.1", - "@mlabs-haskell/json-bigint": " 1.0.0", - "@noble/secp256k1": "^1.7.0", - "apply-args-browser": "0.0.1", - "apply-args-nodejs": "0.0.1", - "base64-js": "^1.5.1", - "big-integer": "1.6.51", - "blakejs": "1.2.1", - "bufferutil": "4.0.5", - "jssha": "3.2.0", - "node-polyfill-webpack-plugin": "1.1.4", - "puppeteer-core": "^15.3.2", - "reconnecting-websocket": "4.4.0", - "uniqid": "5.4.0", - "ws": "8.4.0", - "xhr2": "0.2.1" - }, - "devDependencies": { - "buffer": "6.0.3", - "doctoc": "^2.2.1", - "html-webpack-plugin": "5.5.0", - "webpack": "5.67.0", - "webpack-cli": "4.10", - "webpack-dev-server": "4.7.4" - } - }, - "node_modules/@discoveryjs/json-ext": { - "version": "0.5.7", - "resolved": "https://registry.npmjs.org/@discoveryjs/json-ext/-/json-ext-0.5.7.tgz", - "integrity": "sha512-dBVuXR082gk3jsFp7Rd/JI4kytwGHecnCoTtXFb7DB6CNHp4rg5k1bhg0nWdLGLnOV71lmDzGQaLMy8iPLY0pw==", - "dev": true, - "engines": { - "node": ">=10.0.0" - } - }, - "node_modules/@emurgo/cardano-message-signing-browser": { - "version": "1.0.1", - "resolved": "https://registry.npmjs.org/@emurgo/cardano-message-signing-browser/-/cardano-message-signing-browser-1.0.1.tgz", - "integrity": "sha512-yC4Ymq44WR0bXO1wzxCoyc2W/RD1KSAla0oYhin7IYoVkp2raGp8wt7QNF4pDdNnTcejn5fyPyYY9dL4666H1w==" - }, - "node_modules/@emurgo/cardano-message-signing-nodejs": { - "version": "1.0.1", - "resolved": "https://registry.npmjs.org/@emurgo/cardano-message-signing-nodejs/-/cardano-message-signing-nodejs-1.0.1.tgz", - "integrity": "sha512-PoKh1tQnJX18f8iEr8Jk1KXxKCn9eqaSslMI1pyOJvYRJhQVDLCh0+9YReufjp0oFJIY1ShcrR+4/WnECVZUKQ==" - }, - "node_modules/@emurgo/cardano-serialization-lib-browser": { - "version": "11.2.1", - "resolved": "https://registry.npmjs.org/@emurgo/cardano-serialization-lib-browser/-/cardano-serialization-lib-browser-11.2.1.tgz", - "integrity": "sha512-J9Pmeta7y1GYnMCxtb3GnGCRw6zk1wiQ8EdCYQRn/Yqa/ss1zoBjd41euVi02Eb58aLuOJS81nNU+BcMLGXvUg==" - }, - "node_modules/@emurgo/cardano-serialization-lib-nodejs": { - "version": "11.2.1", - "resolved": "https://registry.npmjs.org/@emurgo/cardano-serialization-lib-nodejs/-/cardano-serialization-lib-nodejs-11.2.1.tgz", - "integrity": "sha512-+Rw35NW4Qv/9uFaPxhKtxiIPmoBEIFMAgdqQxZTw6hNT/wvBp2TvwTBPnOW8ODs7GUAA8nrO1rJJAaxF+mAG2w==" - }, - "node_modules/@jridgewell/gen-mapping": { - "version": "0.3.2", - "resolved": "https://registry.npmjs.org/@jridgewell/gen-mapping/-/gen-mapping-0.3.2.tgz", - "integrity": "sha512-mh65xKQAzI6iBcFzwv28KVWSmCkdRBWoOh+bYQGW3+6OZvbbN3TqMGo5hqYxQniRcH9F2VZIoJCm4pa3BPDK/A==", - "dependencies": { - "@jridgewell/set-array": "^1.0.1", - "@jridgewell/sourcemap-codec": "^1.4.10", - "@jridgewell/trace-mapping": "^0.3.9" - }, - "engines": { - "node": ">=6.0.0" - } - }, - "node_modules/@jridgewell/resolve-uri": { - "version": "3.0.7", - "resolved": "https://registry.npmjs.org/@jridgewell/resolve-uri/-/resolve-uri-3.0.7.tgz", - "integrity": "sha512-8cXDaBBHOr2pQ7j77Y6Vp5VDT2sIqWyWQ56TjEq4ih/a4iST3dItRe8Q9fp0rrIl9DoKhWQtUQz/YpOxLkXbNA==", - "engines": { - "node": ">=6.0.0" - } - }, - "node_modules/@jridgewell/set-array": { - "version": "1.1.2", - "resolved": "https://registry.npmjs.org/@jridgewell/set-array/-/set-array-1.1.2.tgz", - "integrity": "sha512-xnkseuNADM0gt2bs+BvhO0p78Mk762YnZdsuzFV018NoG1Sj1SCQvpSqa7XUaTam5vAGasABV9qXASMKnFMwMw==", - "engines": { - "node": ">=6.0.0" - } - }, - "node_modules/@jridgewell/source-map": { - "version": "0.3.2", - "resolved": "https://registry.npmjs.org/@jridgewell/source-map/-/source-map-0.3.2.tgz", - "integrity": "sha512-m7O9o2uR8k2ObDysZYzdfhb08VuEml5oWGiosa1VdaPZ/A6QyPkAJuwN0Q1lhULOf6B7MtQmHENS743hWtCrgw==", - "dependencies": { - "@jridgewell/gen-mapping": "^0.3.0", - "@jridgewell/trace-mapping": "^0.3.9" - } - }, - "node_modules/@jridgewell/sourcemap-codec": { - "version": "1.4.13", - "resolved": "https://registry.npmjs.org/@jridgewell/sourcemap-codec/-/sourcemap-codec-1.4.13.tgz", - "integrity": "sha512-GryiOJmNcWbovBxTfZSF71V/mXbgcV3MewDe3kIMCLyIh5e7SKAeUZs+rMnJ8jkMolZ/4/VsdBmMrw3l+VdZ3w==" - }, - "node_modules/@jridgewell/trace-mapping": { - "version": "0.3.13", - "resolved": "https://registry.npmjs.org/@jridgewell/trace-mapping/-/trace-mapping-0.3.13.tgz", - "integrity": "sha512-o1xbKhp9qnIAoHJSWd6KlCZfqslL4valSF81H8ImioOAxluWYWOpWkpyktY2vnt4tbrX9XYaxovq6cgowaJp2w==", - "dependencies": { - "@jridgewell/resolve-uri": "^3.0.3", - "@jridgewell/sourcemap-codec": "^1.4.10" - } - }, - "node_modules/@mlabs-haskell/json-bigint": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/@mlabs-haskell/json-bigint/-/json-bigint-1.0.0.tgz", - "integrity": "sha512-Opo07yXP/OU9mIoGmY5VVuDy5kxmb3fBAG3U9dbC15qK1OCpVLJAlxbdOfBmLOja94SnIfZINUU2xvYtVfk65w==", - "dependencies": { - "bignumber.js": "^9.0.0" - } - }, - "node_modules/@noble/secp256k1": { - "version": "1.7.0", - "resolved": "https://registry.npmjs.org/@noble/secp256k1/-/secp256k1-1.7.0.tgz", - "integrity": "sha512-kbacwGSsH/CTout0ZnZWxnW1B+jH/7r/WAAKLBtrRJ/+CUH7lgmQzl3GTrQua3SGKWNSDsS6lmjnDpIJ5Dxyaw==", - "funding": [ - { - "type": "individual", - "url": "https://paulmillr.com/funding/" - } - ] - }, - "node_modules/@nodelib/fs.scandir": { - "version": "2.1.5", - "resolved": "https://registry.npmjs.org/@nodelib/fs.scandir/-/fs.scandir-2.1.5.tgz", - "integrity": "sha512-vq24Bq3ym5HEQm2NKCr3yXDwjc7vTsEThRDnkp2DK9p1uqLR+DHurm/NOTo0KG7HYHU7eppKZj3MyqYuMBf62g==", - "dev": true, - "dependencies": { - "@nodelib/fs.stat": "2.0.5", - "run-parallel": "^1.1.9" - }, - "engines": { - "node": ">= 8" - } - }, - "node_modules/@nodelib/fs.stat": { - "version": "2.0.5", - "resolved": "https://registry.npmjs.org/@nodelib/fs.stat/-/fs.stat-2.0.5.tgz", - "integrity": "sha512-RkhPPp2zrqDAQA/2jNhnztcPAlv64XdhIp7a7454A5ovI7Bukxgt7MX7udwAu3zg1DcpPU0rz3VV1SeaqvY4+A==", - "dev": true, - "engines": { - "node": ">= 8" - } - }, - "node_modules/@nodelib/fs.walk": { - "version": "1.2.8", - "resolved": "https://registry.npmjs.org/@nodelib/fs.walk/-/fs.walk-1.2.8.tgz", - "integrity": "sha512-oGB+UxlgWcgQkgwo8GcEGwemoTFt3FIO9ababBmaGwXIoBKZ+GTy0pP185beGg7Llih/NSHSV2XAs1lnznocSg==", - "dev": true, - "dependencies": { - "@nodelib/fs.scandir": "2.1.5", - "fastq": "^1.6.0" - }, - "engines": { - "node": ">= 8" - } - }, - "node_modules/@textlint/ast-node-types": { - "version": "12.2.2", - "resolved": "https://registry.npmjs.org/@textlint/ast-node-types/-/ast-node-types-12.2.2.tgz", - "integrity": "sha512-VQAXUSGdmEajHXrMxeM9ZTS8UBJSVB0ghJFHpFfqYKlcDsjIqClSmTprY6521HoCoSLoUIGBxTC3jQyUMJFIWw==", - "dev": true - }, - "node_modules/@textlint/markdown-to-ast": { - "version": "12.2.3", - "resolved": "https://registry.npmjs.org/@textlint/markdown-to-ast/-/markdown-to-ast-12.2.3.tgz", - "integrity": "sha512-omZqcZV1Q8t9K0IKvlHNIdTV3SKNaS2P5qkbTjzDj7PuTuvG20JFqL9Naiwwi9ty3NzTzq+W8lLG3H2HgX0WvA==", - "dev": true, - "dependencies": { - "@textlint/ast-node-types": "^12.2.2", - "debug": "^4.3.4", - "mdast-util-gfm-autolink-literal": "^0.1.3", - "remark-footnotes": "^3.0.0", - "remark-frontmatter": "^3.0.0", - "remark-gfm": "^1.0.0", - "remark-parse": "^9.0.0", - "traverse": "^0.6.7", - "unified": "^9.2.2" - } - }, - "node_modules/@textlint/markdown-to-ast/node_modules/debug": { - "version": "4.3.4", - "resolved": "https://registry.npmjs.org/debug/-/debug-4.3.4.tgz", - "integrity": "sha512-PRWFHuSU3eDtQJPvnNY7Jcket1j0t5OuOsFzPPzsekD52Zl8qUfFIPEiswXqIvHWGVHOgX+7G/vCNNhehwxfkQ==", - "dev": true, - "dependencies": { - "ms": "2.1.2" - }, - "engines": { - "node": ">=6.0" - }, - "peerDependenciesMeta": { - "supports-color": { - "optional": true - } - } - }, - "node_modules/@textlint/markdown-to-ast/node_modules/ms": { - "version": "2.1.2", - "resolved": "https://registry.npmjs.org/ms/-/ms-2.1.2.tgz", - "integrity": "sha512-sGkPx+VjMtmA6MX27oA4FBFELFCZZ4S4XqeGOXCv68tT+jb3vk/RyaKWP0PTKyWtmLSM0b+adUTEvbs1PEaH2w==", - "dev": true - }, - "node_modules/@types/body-parser": { - "version": "1.19.2", - "resolved": "https://registry.npmjs.org/@types/body-parser/-/body-parser-1.19.2.tgz", - "integrity": "sha512-ALYone6pm6QmwZoAgeyNksccT9Q4AWZQ6PvfwR37GT6r6FWUPguq6sUmNGSMV2Wr761oQoBxwGGa6DR5o1DC9g==", - "dev": true, - "dependencies": { - "@types/connect": "*", - "@types/node": "*" - } - }, - "node_modules/@types/bonjour": { - "version": "3.5.10", - "resolved": "https://registry.npmjs.org/@types/bonjour/-/bonjour-3.5.10.tgz", - "integrity": "sha512-p7ienRMiS41Nu2/igbJxxLDWrSZ0WxM8UQgCeO9KhoVF7cOVFkrKsiDr1EsJIla8vV3oEEjGcz11jc5yimhzZw==", - "dev": true, - "dependencies": { - "@types/node": "*" - } - }, - "node_modules/@types/connect": { - "version": "3.4.35", - "resolved": "https://registry.npmjs.org/@types/connect/-/connect-3.4.35.tgz", - "integrity": "sha512-cdeYyv4KWoEgpBISTxWvqYsVy444DOqehiF3fM3ne10AmJ62RSyNkUnxMJXHQWRQQX2eR94m5y1IZyDwBjV9FQ==", - "dev": true, - "dependencies": { - "@types/node": "*" - } - }, - "node_modules/@types/connect-history-api-fallback": { - "version": "1.3.5", - "resolved": "https://registry.npmjs.org/@types/connect-history-api-fallback/-/connect-history-api-fallback-1.3.5.tgz", - "integrity": "sha512-h8QJa8xSb1WD4fpKBDcATDNGXghFj6/3GRWG6dhmRcu0RX1Ubasur2Uvx5aeEwlf0MwblEC2bMzzMQntxnw/Cw==", - "dev": true, - "dependencies": { - "@types/express-serve-static-core": "*", - "@types/node": "*" - } - }, - "node_modules/@types/eslint": { - "version": "8.4.3", - "resolved": "https://registry.npmjs.org/@types/eslint/-/eslint-8.4.3.tgz", - "integrity": "sha512-YP1S7YJRMPs+7KZKDb9G63n8YejIwW9BALq7a5j2+H4yl6iOv9CB29edho+cuFRrvmJbbaH2yiVChKLJVysDGw==", - "dependencies": { - "@types/estree": "*", - "@types/json-schema": "*" - } - }, - "node_modules/@types/eslint-scope": { - "version": "3.7.3", - "resolved": "https://registry.npmjs.org/@types/eslint-scope/-/eslint-scope-3.7.3.tgz", - "integrity": "sha512-PB3ldyrcnAicT35TWPs5IcwKD8S333HMaa2VVv4+wdvebJkjWuW/xESoB8IwRcog8HYVYamb1g/R31Qv5Bx03g==", - "dependencies": { - "@types/eslint": "*", - "@types/estree": "*" - } - }, - "node_modules/@types/estree": { - "version": "0.0.50", - "resolved": "https://registry.npmjs.org/@types/estree/-/estree-0.0.50.tgz", - "integrity": "sha512-C6N5s2ZFtuZRj54k2/zyRhNDjJwwcViAM3Nbm8zjBpbqAdZ00mr0CFxvSKeO8Y/e03WVFLpQMdHYVfUd6SB+Hw==" - }, - "node_modules/@types/express": { - "version": "4.17.13", - "resolved": "https://registry.npmjs.org/@types/express/-/express-4.17.13.tgz", - "integrity": "sha512-6bSZTPaTIACxn48l50SR+axgrqm6qXFIxrdAKaG6PaJk3+zuUr35hBlgT7vOmJcum+OEaIBLtHV/qloEAFITeA==", - "dev": true, - "dependencies": { - "@types/body-parser": "*", - "@types/express-serve-static-core": "^4.17.18", - "@types/qs": "*", - "@types/serve-static": "*" - } - }, - "node_modules/@types/express-serve-static-core": { - "version": "4.17.29", - "resolved": "https://registry.npmjs.org/@types/express-serve-static-core/-/express-serve-static-core-4.17.29.tgz", - "integrity": "sha512-uMd++6dMKS32EOuw1Uli3e3BPgdLIXmezcfHv7N4c1s3gkhikBplORPpMq3fuWkxncZN1reb16d5n8yhQ80x7Q==", - "dev": true, - "dependencies": { - "@types/node": "*", - "@types/qs": "*", - "@types/range-parser": "*" - } - }, - "node_modules/@types/html-minifier-terser": { - "version": "6.1.0", - "resolved": "https://registry.npmjs.org/@types/html-minifier-terser/-/html-minifier-terser-6.1.0.tgz", - "integrity": "sha512-oh/6byDPnL1zeNXFrDXFLyZjkr1MsBG667IM792caf1L2UPOOMf65NFzjUH/ltyfwjAGfs1rsX1eftK0jC/KIg==", - "dev": true - }, - "node_modules/@types/http-proxy": { - "version": "1.17.9", - "resolved": "https://registry.npmjs.org/@types/http-proxy/-/http-proxy-1.17.9.tgz", - "integrity": "sha512-QsbSjA/fSk7xB+UXlCT3wHBy5ai9wOcNDWwZAtud+jXhwOM3l+EYZh8Lng4+/6n8uar0J7xILzqftJdJ/Wdfkw==", - "dev": true, - "dependencies": { - "@types/node": "*" - } - }, - "node_modules/@types/json-schema": { - "version": "7.0.11", - "resolved": "https://registry.npmjs.org/@types/json-schema/-/json-schema-7.0.11.tgz", - "integrity": "sha512-wOuvG1SN4Us4rez+tylwwwCV1psiNVOkJeM3AUWUNWg/jDQY2+HE/444y5gc+jBmRqASOm2Oeh5c1axHobwRKQ==" - }, - "node_modules/@types/mdast": { - "version": "3.0.10", - "resolved": "https://registry.npmjs.org/@types/mdast/-/mdast-3.0.10.tgz", - "integrity": "sha512-W864tg/Osz1+9f4lrGTZpCSO5/z4608eUp19tbozkq2HJK6i3z1kT0H9tlADXuYIb1YYOBByU4Jsqkk75q48qA==", - "dev": true, - "dependencies": { - "@types/unist": "*" - } - }, - "node_modules/@types/mime": { - "version": "1.3.2", - "resolved": "https://registry.npmjs.org/@types/mime/-/mime-1.3.2.tgz", - "integrity": "sha512-YATxVxgRqNH6nHEIsvg6k2Boc1JHI9ZbH5iWFFv/MTkchz3b1ieGDa5T0a9RznNdI0KhVbdbWSN+KWWrQZRxTw==", - "dev": true - }, - "node_modules/@types/node": { - "version": "17.0.35", - "resolved": "https://registry.npmjs.org/@types/node/-/node-17.0.35.tgz", - "integrity": "sha512-vu1SrqBjbbZ3J6vwY17jBs8Sr/BKA+/a/WtjRG+whKg1iuLFOosq872EXS0eXWILdO36DHQQeku/ZcL6hz2fpg==" - }, - "node_modules/@types/qs": { - "version": "6.9.7", - "resolved": "https://registry.npmjs.org/@types/qs/-/qs-6.9.7.tgz", - "integrity": "sha512-FGa1F62FT09qcrueBA6qYTrJPVDzah9a+493+o2PCXsesWHIn27G98TsSMs3WPNbZIEj4+VJf6saSFpvD+3Zsw==", - "dev": true - }, - "node_modules/@types/range-parser": { - "version": "1.2.4", - "resolved": "https://registry.npmjs.org/@types/range-parser/-/range-parser-1.2.4.tgz", - "integrity": "sha512-EEhsLsD6UsDM1yFhAvy0Cjr6VwmpMWqFBCb9w07wVugF7w9nfajxLuVmngTIpgS6svCnm6Vaw+MZhoDCKnOfsw==", - "dev": true - }, - "node_modules/@types/retry": { - "version": "0.12.0", - "resolved": "https://registry.npmjs.org/@types/retry/-/retry-0.12.0.tgz", - "integrity": "sha512-wWKOClTTiizcZhXnPY4wikVAwmdYHp8q6DmC+EJUzAMsycb7HB32Kh9RN4+0gExjmPmZSAQjgURXIGATPegAvA==", - "dev": true - }, - "node_modules/@types/serve-index": { - "version": "1.9.1", - "resolved": "https://registry.npmjs.org/@types/serve-index/-/serve-index-1.9.1.tgz", - "integrity": "sha512-d/Hs3nWDxNL2xAczmOVZNj92YZCS6RGxfBPjKzuu/XirCgXdpKEb88dYNbrYGint6IVWLNP+yonwVAuRC0T2Dg==", - "dev": true, - "dependencies": { - "@types/express": "*" - } - }, - "node_modules/@types/serve-static": { - "version": "1.13.10", - "resolved": "https://registry.npmjs.org/@types/serve-static/-/serve-static-1.13.10.tgz", - "integrity": "sha512-nCkHGI4w7ZgAdNkrEu0bv+4xNV/XDqW+DydknebMOQwkpDGx8G+HTlj7R7ABI8i8nKxVw0wtKPi1D+lPOkh4YQ==", - "dev": true, - "dependencies": { - "@types/mime": "^1", - "@types/node": "*" - } - }, - "node_modules/@types/sockjs": { - "version": "0.3.33", - "resolved": "https://registry.npmjs.org/@types/sockjs/-/sockjs-0.3.33.tgz", - "integrity": "sha512-f0KEEe05NvUnat+boPTZ0dgaLZ4SfSouXUgv5noUiefG2ajgKjmETo9ZJyuqsl7dfl2aHlLJUiki6B4ZYldiiw==", - "dev": true, - "dependencies": { - "@types/node": "*" - } - }, - "node_modules/@types/unist": { - "version": "2.0.6", - "resolved": "https://registry.npmjs.org/@types/unist/-/unist-2.0.6.tgz", - "integrity": "sha512-PBjIUxZHOuj0R15/xuwJYjFi+KZdNFrehocChv4g5hu6aFroHue8m0lBP0POdK2nKzbw0cgV1mws8+V/JAcEkQ==", - "dev": true - }, - "node_modules/@types/ws": { - "version": "8.5.3", - "resolved": "https://registry.npmjs.org/@types/ws/-/ws-8.5.3.tgz", - "integrity": "sha512-6YOoWjruKj1uLf3INHH7D3qTXwFfEsg1kf3c0uDdSBJwfa/llkwIjrAGV7j7mVgGNbzTQ3HiHKKDXl6bJPD97w==", - "dev": true, - "dependencies": { - "@types/node": "*" - } - }, - "node_modules/@types/yauzl": { - "version": "2.10.0", - "resolved": "https://registry.npmjs.org/@types/yauzl/-/yauzl-2.10.0.tgz", - "integrity": "sha512-Cn6WYCm0tXv8p6k+A8PvbDG763EDpBoTzHdA+Q/MF6H3sapGjCm9NzoaJncJS9tUKSuCoDs9XHxYYsQDgxR6kw==", - "optional": true, - "dependencies": { - "@types/node": "*" - } - }, - "node_modules/@webassemblyjs/ast": { - "version": "1.11.1", - "resolved": "https://registry.npmjs.org/@webassemblyjs/ast/-/ast-1.11.1.tgz", - "integrity": "sha512-ukBh14qFLjxTQNTXocdyksN5QdM28S1CxHt2rdskFyL+xFV7VremuBLVbmCePj+URalXBENx/9Lm7lnhihtCSw==", - "dependencies": { - "@webassemblyjs/helper-numbers": "1.11.1", - "@webassemblyjs/helper-wasm-bytecode": "1.11.1" - } - }, - "node_modules/@webassemblyjs/floating-point-hex-parser": { - "version": "1.11.1", - "resolved": "https://registry.npmjs.org/@webassemblyjs/floating-point-hex-parser/-/floating-point-hex-parser-1.11.1.tgz", - "integrity": "sha512-iGRfyc5Bq+NnNuX8b5hwBrRjzf0ocrJPI6GWFodBFzmFnyvrQ83SHKhmilCU/8Jv67i4GJZBMhEzltxzcNagtQ==" - }, - "node_modules/@webassemblyjs/helper-api-error": { - "version": "1.11.1", - "resolved": "https://registry.npmjs.org/@webassemblyjs/helper-api-error/-/helper-api-error-1.11.1.tgz", - "integrity": "sha512-RlhS8CBCXfRUR/cwo2ho9bkheSXG0+NwooXcc3PAILALf2QLdFyj7KGsKRbVc95hZnhnERon4kW/D3SZpp6Tcg==" - }, - "node_modules/@webassemblyjs/helper-buffer": { - "version": "1.11.1", - "resolved": "https://registry.npmjs.org/@webassemblyjs/helper-buffer/-/helper-buffer-1.11.1.tgz", - "integrity": "sha512-gwikF65aDNeeXa8JxXa2BAk+REjSyhrNC9ZwdT0f8jc4dQQeDQ7G4m0f2QCLPJiMTTO6wfDmRmj/pW0PsUvIcA==" - }, - "node_modules/@webassemblyjs/helper-numbers": { - "version": "1.11.1", - "resolved": "https://registry.npmjs.org/@webassemblyjs/helper-numbers/-/helper-numbers-1.11.1.tgz", - "integrity": "sha512-vDkbxiB8zfnPdNK9Rajcey5C0w+QJugEglN0of+kmO8l7lDb77AnlKYQF7aarZuCrv+l0UvqL+68gSDr3k9LPQ==", - "dependencies": { - "@webassemblyjs/floating-point-hex-parser": "1.11.1", - "@webassemblyjs/helper-api-error": "1.11.1", - "@xtuc/long": "4.2.2" - } - }, - "node_modules/@webassemblyjs/helper-wasm-bytecode": { - "version": "1.11.1", - "resolved": "https://registry.npmjs.org/@webassemblyjs/helper-wasm-bytecode/-/helper-wasm-bytecode-1.11.1.tgz", - "integrity": "sha512-PvpoOGiJwXeTrSf/qfudJhwlvDQxFgelbMqtq52WWiXC6Xgg1IREdngmPN3bs4RoO83PnL/nFrxucXj1+BX62Q==" - }, - "node_modules/@webassemblyjs/helper-wasm-section": { - "version": "1.11.1", - "resolved": "https://registry.npmjs.org/@webassemblyjs/helper-wasm-section/-/helper-wasm-section-1.11.1.tgz", - "integrity": "sha512-10P9No29rYX1j7F3EVPX3JvGPQPae+AomuSTPiF9eBQeChHI6iqjMIwR9JmOJXwpnn/oVGDk7I5IlskuMwU/pg==", - "dependencies": { - "@webassemblyjs/ast": "1.11.1", - "@webassemblyjs/helper-buffer": "1.11.1", - "@webassemblyjs/helper-wasm-bytecode": "1.11.1", - "@webassemblyjs/wasm-gen": "1.11.1" - } - }, - "node_modules/@webassemblyjs/ieee754": { - "version": "1.11.1", - "resolved": "https://registry.npmjs.org/@webassemblyjs/ieee754/-/ieee754-1.11.1.tgz", - "integrity": "sha512-hJ87QIPtAMKbFq6CGTkZYJivEwZDbQUgYd3qKSadTNOhVY7p+gfP6Sr0lLRVTaG1JjFj+r3YchoqRYxNH3M0GQ==", - "dependencies": { - "@xtuc/ieee754": "^1.2.0" - } - }, - "node_modules/@webassemblyjs/leb128": { - "version": "1.11.1", - "resolved": "https://registry.npmjs.org/@webassemblyjs/leb128/-/leb128-1.11.1.tgz", - "integrity": "sha512-BJ2P0hNZ0u+Th1YZXJpzW6miwqQUGcIHT1G/sf72gLVD9DZ5AdYTqPNbHZh6K1M5VmKvFXwGSWZADz+qBWxeRw==", - "dependencies": { - "@xtuc/long": "4.2.2" - } - }, - "node_modules/@webassemblyjs/utf8": { - "version": "1.11.1", - "resolved": "https://registry.npmjs.org/@webassemblyjs/utf8/-/utf8-1.11.1.tgz", - "integrity": "sha512-9kqcxAEdMhiwQkHpkNiorZzqpGrodQQ2IGrHHxCy+Ozng0ofyMA0lTqiLkVs1uzTRejX+/O0EOT7KxqVPuXosQ==" - }, - "node_modules/@webassemblyjs/wasm-edit": { - "version": "1.11.1", - "resolved": "https://registry.npmjs.org/@webassemblyjs/wasm-edit/-/wasm-edit-1.11.1.tgz", - "integrity": "sha512-g+RsupUC1aTHfR8CDgnsVRVZFJqdkFHpsHMfJuWQzWU3tvnLC07UqHICfP+4XyL2tnr1amvl1Sdp06TnYCmVkA==", - "dependencies": { - "@webassemblyjs/ast": "1.11.1", - "@webassemblyjs/helper-buffer": "1.11.1", - "@webassemblyjs/helper-wasm-bytecode": "1.11.1", - "@webassemblyjs/helper-wasm-section": "1.11.1", - "@webassemblyjs/wasm-gen": "1.11.1", - "@webassemblyjs/wasm-opt": "1.11.1", - "@webassemblyjs/wasm-parser": "1.11.1", - "@webassemblyjs/wast-printer": "1.11.1" - } - }, - "node_modules/@webassemblyjs/wasm-gen": { - "version": "1.11.1", - "resolved": "https://registry.npmjs.org/@webassemblyjs/wasm-gen/-/wasm-gen-1.11.1.tgz", - "integrity": "sha512-F7QqKXwwNlMmsulj6+O7r4mmtAlCWfO/0HdgOxSklZfQcDu0TpLiD1mRt/zF25Bk59FIjEuGAIyn5ei4yMfLhA==", - "dependencies": { - "@webassemblyjs/ast": "1.11.1", - "@webassemblyjs/helper-wasm-bytecode": "1.11.1", - "@webassemblyjs/ieee754": "1.11.1", - "@webassemblyjs/leb128": "1.11.1", - "@webassemblyjs/utf8": "1.11.1" - } - }, - "node_modules/@webassemblyjs/wasm-opt": { - "version": "1.11.1", - "resolved": "https://registry.npmjs.org/@webassemblyjs/wasm-opt/-/wasm-opt-1.11.1.tgz", - "integrity": "sha512-VqnkNqnZlU5EB64pp1l7hdm3hmQw7Vgqa0KF/KCNO9sIpI6Fk6brDEiX+iCOYrvMuBWDws0NkTOxYEb85XQHHw==", - "dependencies": { - "@webassemblyjs/ast": "1.11.1", - "@webassemblyjs/helper-buffer": "1.11.1", - "@webassemblyjs/wasm-gen": "1.11.1", - "@webassemblyjs/wasm-parser": "1.11.1" - } - }, - "node_modules/@webassemblyjs/wasm-parser": { - "version": "1.11.1", - "resolved": "https://registry.npmjs.org/@webassemblyjs/wasm-parser/-/wasm-parser-1.11.1.tgz", - "integrity": "sha512-rrBujw+dJu32gYB7/Lup6UhdkPx9S9SnobZzRVL7VcBH9Bt9bCBLEuX/YXOOtBsOZ4NQrRykKhffRWHvigQvOA==", - "dependencies": { - "@webassemblyjs/ast": "1.11.1", - "@webassemblyjs/helper-api-error": "1.11.1", - "@webassemblyjs/helper-wasm-bytecode": "1.11.1", - "@webassemblyjs/ieee754": "1.11.1", - "@webassemblyjs/leb128": "1.11.1", - "@webassemblyjs/utf8": "1.11.1" - } - }, - "node_modules/@webassemblyjs/wast-printer": { - "version": "1.11.1", - "resolved": "https://registry.npmjs.org/@webassemblyjs/wast-printer/-/wast-printer-1.11.1.tgz", - "integrity": "sha512-IQboUWM4eKzWW+N/jij2sRatKMh99QEelo3Eb2q0qXkvPRISAj8Qxtmw5itwqK+TTkBuUIE45AxYPToqPtL5gg==", - "dependencies": { - "@webassemblyjs/ast": "1.11.1", - "@xtuc/long": "4.2.2" - } - }, - "node_modules/@webpack-cli/configtest": { - "version": "1.2.0", - "resolved": "https://registry.npmjs.org/@webpack-cli/configtest/-/configtest-1.2.0.tgz", - "integrity": "sha512-4FB8Tj6xyVkyqjj1OaTqCjXYULB9FMkqQ8yGrZjRDrYh0nOE+7Lhs45WioWQQMV+ceFlE368Ukhe6xdvJM9Egg==", - "dev": true, - "peerDependencies": { - "webpack": "4.x.x || 5.x.x", - "webpack-cli": "4.x.x" - } - }, - "node_modules/@webpack-cli/info": { - "version": "1.5.0", - "resolved": "https://registry.npmjs.org/@webpack-cli/info/-/info-1.5.0.tgz", - "integrity": "sha512-e8tSXZpw2hPl2uMJY6fsMswaok5FdlGNRTktvFk2sD8RjH0hE2+XistawJx1vmKteh4NmGmNUrp+Tb2w+udPcQ==", - "dev": true, - "dependencies": { - "envinfo": "^7.7.3" - }, - "peerDependencies": { - "webpack-cli": "4.x.x" - } - }, - "node_modules/@webpack-cli/serve": { - "version": "1.7.0", - "resolved": "https://registry.npmjs.org/@webpack-cli/serve/-/serve-1.7.0.tgz", - "integrity": "sha512-oxnCNGj88fL+xzV+dacXs44HcDwf1ovs3AuEzvP7mqXw7fQntqIhQ1BRmynh4qEKQSSSRSWVyXRjmTbZIX9V2Q==", - "dev": true, - "peerDependencies": { - "webpack-cli": "4.x.x" - }, - "peerDependenciesMeta": { - "webpack-dev-server": { - "optional": true - } - } - }, - "node_modules/@xtuc/ieee754": { - "version": "1.2.0", - "resolved": "https://registry.npmjs.org/@xtuc/ieee754/-/ieee754-1.2.0.tgz", - "integrity": "sha512-DX8nKgqcGwsc0eJSqYt5lwP4DH5FlHnmuWWBRy7X0NcaGR0ZtuyeESgMwTYVEtxmsNGY+qit4QYT/MIYTOTPeA==" - }, - "node_modules/@xtuc/long": { - "version": "4.2.2", - "resolved": "https://registry.npmjs.org/@xtuc/long/-/long-4.2.2.tgz", - "integrity": "sha512-NuHqBY1PB/D8xU6s/thBgOAiAP7HOYDQ32+BFZILJ8ivkUkAHQnWfn6WhL79Owj1qmUnoN/YPhktdIoucipkAQ==" - }, - "node_modules/accepts": { - "version": "1.3.8", - "resolved": "https://registry.npmjs.org/accepts/-/accepts-1.3.8.tgz", - "integrity": "sha512-PYAthTa2m2VKxuvSD3DPC/Gy+U+sOA1LAuT8mkmRuvw+NACSaeXEQ+NHcVF7rONl6qcaxV3Uuemwawk+7+SJLw==", - "dev": true, - "dependencies": { - "mime-types": "~2.1.34", - "negotiator": "0.6.3" - }, - "engines": { - "node": ">= 0.6" - } - }, - "node_modules/acorn": { - "version": "8.7.1", - "resolved": "https://registry.npmjs.org/acorn/-/acorn-8.7.1.tgz", - "integrity": "sha512-Xx54uLJQZ19lKygFXOWsscKUbsBZW0CPykPhVQdhIeIwrbPmJzqeASDInc8nKBnp/JT6igTs82qPXz069H8I/A==", - "bin": { - "acorn": "bin/acorn" - }, - "engines": { - "node": ">=0.4.0" - } - }, - "node_modules/acorn-import-assertions": { - "version": "1.8.0", - "resolved": "https://registry.npmjs.org/acorn-import-assertions/-/acorn-import-assertions-1.8.0.tgz", - "integrity": "sha512-m7VZ3jwz4eK6A4Vtt8Ew1/mNbP24u0FhdyfA7fSvnJR6LMdfOYnmuIrrJAgrYfYJ10F/otaHTtrtrtmHdMNzEw==", - "peerDependencies": { - "acorn": "^8" - } - }, - "node_modules/agent-base": { - "version": "6.0.2", - "resolved": "https://registry.npmjs.org/agent-base/-/agent-base-6.0.2.tgz", - "integrity": "sha512-RZNwNclF7+MS/8bDg70amg32dyeZGZxiDuQmZxKLAlQjr3jGyLx+4Kkk58UO7D2QdgFIQCovuSuZESne6RG6XQ==", - "dependencies": { - "debug": "4" - }, - "engines": { - "node": ">= 6.0.0" - } - }, - "node_modules/agent-base/node_modules/debug": { - "version": "4.3.4", - "resolved": "https://registry.npmjs.org/debug/-/debug-4.3.4.tgz", - "integrity": "sha512-PRWFHuSU3eDtQJPvnNY7Jcket1j0t5OuOsFzPPzsekD52Zl8qUfFIPEiswXqIvHWGVHOgX+7G/vCNNhehwxfkQ==", - "dependencies": { - "ms": "2.1.2" - }, - "engines": { - "node": ">=6.0" - }, - "peerDependenciesMeta": { - "supports-color": { - "optional": true - } - } - }, - "node_modules/agent-base/node_modules/ms": { - "version": "2.1.2", - "resolved": "https://registry.npmjs.org/ms/-/ms-2.1.2.tgz", - "integrity": "sha512-sGkPx+VjMtmA6MX27oA4FBFELFCZZ4S4XqeGOXCv68tT+jb3vk/RyaKWP0PTKyWtmLSM0b+adUTEvbs1PEaH2w==" - }, - "node_modules/aggregate-error": { - "version": "3.1.0", - "resolved": "https://registry.npmjs.org/aggregate-error/-/aggregate-error-3.1.0.tgz", - "integrity": "sha512-4I7Td01quW/RpocfNayFdFVk1qSuoh0E7JrbRJ16nH01HhKFQ88INq9Sd+nd72zqRySlr9BmDA8xlEJ6vJMrYA==", - "dev": true, - "dependencies": { - "clean-stack": "^2.0.0", - "indent-string": "^4.0.0" - }, - "engines": { - "node": ">=8" - } - }, - "node_modules/ajv": { - "version": "6.12.6", - "resolved": "https://registry.npmjs.org/ajv/-/ajv-6.12.6.tgz", - "integrity": "sha512-j3fVLgvTo527anyYyJOGTYJbG+vnnQYvE0m5mmkc1TK+nxAppkCLMIL0aZ4dblVCNoGShhm+kzE4ZUykBoMg4g==", - "dependencies": { - "fast-deep-equal": "^3.1.1", - "fast-json-stable-stringify": "^2.0.0", - "json-schema-traverse": "^0.4.1", - "uri-js": "^4.2.2" - }, - "funding": { - "type": "github", - "url": "https://github.com/sponsors/epoberezkin" - } - }, - "node_modules/ajv-formats": { - "version": "2.1.1", - "resolved": "https://registry.npmjs.org/ajv-formats/-/ajv-formats-2.1.1.tgz", - "integrity": "sha512-Wx0Kx52hxE7C18hkMEggYlEifqWZtYaRgouJor+WMdPnQyEK13vgEWyVNup7SoeeoLMsr4kf5h6dOW11I15MUA==", - "dev": true, - "dependencies": { - "ajv": "^8.0.0" - }, - "peerDependencies": { - "ajv": "^8.0.0" - }, - "peerDependenciesMeta": { - "ajv": { - "optional": true - } - } - }, - "node_modules/ajv-formats/node_modules/ajv": { - "version": "8.11.0", - "resolved": "https://registry.npmjs.org/ajv/-/ajv-8.11.0.tgz", - "integrity": "sha512-wGgprdCvMalC0BztXvitD2hC04YffAvtsUn93JbGXYLAtCUO4xd17mCCZQxUOItiBwZvJScWo8NIvQMQ71rdpg==", - "dev": true, - "dependencies": { - "fast-deep-equal": "^3.1.1", - "json-schema-traverse": "^1.0.0", - "require-from-string": "^2.0.2", - "uri-js": "^4.2.2" - }, - "funding": { - "type": "github", - "url": "https://github.com/sponsors/epoberezkin" - } - }, - "node_modules/ajv-formats/node_modules/json-schema-traverse": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/json-schema-traverse/-/json-schema-traverse-1.0.0.tgz", - "integrity": "sha512-NM8/P9n3XjXhIZn1lLhkFaACTOURQXjWhV4BA/RnOv8xvgqtqpAX9IO4mRQxSx1Rlo4tqzeqb0sOlruaOy3dug==", - "dev": true - }, - "node_modules/ajv-keywords": { - "version": "3.5.2", - "resolved": "https://registry.npmjs.org/ajv-keywords/-/ajv-keywords-3.5.2.tgz", - "integrity": "sha512-5p6WTN0DdTGVQk6VjcEju19IgaHudalcfabD7yhDGeA6bcQnmL+CpveLJq/3hvfwd1aof6L386Ougkx6RfyMIQ==", - "peerDependencies": { - "ajv": "^6.9.1" - } - }, - "node_modules/anchor-markdown-header": { - "version": "0.6.0", - "resolved": "https://registry.npmjs.org/anchor-markdown-header/-/anchor-markdown-header-0.6.0.tgz", - "integrity": "sha512-v7HJMtE1X7wTpNFseRhxsY/pivP4uAJbidVhPT+yhz4i/vV1+qx371IXuV9V7bN6KjFtheLJxqaSm0Y/8neJTA==", - "dev": true, - "dependencies": { - "emoji-regex": "~10.1.0" - } - }, - "node_modules/ansi-html-community": { - "version": "0.0.8", - "resolved": "https://registry.npmjs.org/ansi-html-community/-/ansi-html-community-0.0.8.tgz", - "integrity": "sha512-1APHAyr3+PCamwNw3bXCPp4HFLONZt/yIH0sZp0/469KWNTEy+qN5jQ3GVX6DMZ1UXAi34yVwtTeaG/HpBuuzw==", - "dev": true, - "engines": [ - "node >= 0.8.0" - ], - "bin": { - "ansi-html": "bin/ansi-html" - } - }, - "node_modules/ansi-regex": { - "version": "5.0.1", - "resolved": "https://registry.npmjs.org/ansi-regex/-/ansi-regex-5.0.1.tgz", - "integrity": "sha512-quJQXlTSUGL2LH9SUXo8VwsY4soanhgo6LNSm84E1LBcE8s3O0wpdiRzyR9z/ZZJMlMWv37qOOb9pdJlMUEKFQ==", - "dev": true, - "engines": { - "node": ">=8" - } - }, - "node_modules/anymatch": { - "version": "3.1.2", - "resolved": "https://registry.npmjs.org/anymatch/-/anymatch-3.1.2.tgz", - "integrity": "sha512-P43ePfOAIupkguHUycrc4qJ9kz8ZiuOUijaETwX7THt0Y/GNK7v0aa8rY816xWjZ7rJdA5XdMcpVFTKMq+RvWg==", - "dev": true, - "dependencies": { - "normalize-path": "^3.0.0", - "picomatch": "^2.0.4" - }, - "engines": { - "node": ">= 8" - } - }, - "node_modules/apply-args-browser": { - "version": "0.0.1", - "resolved": "https://registry.npmjs.org/apply-args-browser/-/apply-args-browser-0.0.1.tgz", - "integrity": "sha512-gq4ldo4Fk5SEVpeW/0yBe0v5g3VDEWAm9LB80zGarYtDvojTD7ar0Y/WvIy9gYAkKmlE3USu5wYwKKCqOXfNkg==" - }, - "node_modules/apply-args-nodejs": { - "version": "0.0.1", - "resolved": "https://registry.npmjs.org/apply-args-nodejs/-/apply-args-nodejs-0.0.1.tgz", - "integrity": "sha512-JwZPEvEDrL+4y16Un6FcNjDSITpsBykchgwPh8UtxnziYrbxKAc2BUfyC5uvA6ZVIhQjiO4r+Kg1MQ3nqWk+1Q==" - }, - "node_modules/array-flatten": { - "version": "2.1.2", - "resolved": "https://registry.npmjs.org/array-flatten/-/array-flatten-2.1.2.tgz", - "integrity": "sha512-hNfzcOV8W4NdualtqBFPyVO+54DSJuZGY9qT4pRroB6S9e3iiido2ISIC5h9R2sPJ8H3FHCIiEnsv1lPXO3KtQ==", - "dev": true - }, - "node_modules/array-union": { - "version": "2.1.0", - "resolved": "https://registry.npmjs.org/array-union/-/array-union-2.1.0.tgz", - "integrity": "sha512-HGyxoOTYUyCM6stUe6EJgnd4EoewAI7zMdfqO+kGjnlZmBDz/cR5pf8r/cR4Wq60sL/p0IkcjUEEPwS3GFrIyw==", - "dev": true, - "engines": { - "node": ">=8" - } - }, - "node_modules/asn1.js": { - "version": "5.4.1", - "resolved": "https://registry.npmjs.org/asn1.js/-/asn1.js-5.4.1.tgz", - "integrity": "sha512-+I//4cYPccV8LdmBLiX8CYvf9Sp3vQsrqu2QNXRcrbiWvcx/UdlFiqUJJzxRQxgsZmvhXhn4cSKeSmoFjVdupA==", - "dependencies": { - "bn.js": "^4.0.0", - "inherits": "^2.0.1", - "minimalistic-assert": "^1.0.0", - "safer-buffer": "^2.1.0" - } - }, - "node_modules/asn1.js/node_modules/bn.js": { - "version": "4.12.0", - "resolved": "https://registry.npmjs.org/bn.js/-/bn.js-4.12.0.tgz", - "integrity": "sha512-c98Bf3tPniI+scsdk237ku1Dc3ujXQTSgyiPUDEOe7tRkhrqridvh8klBv0HCEso1OLOYcHuCv/cS6DNxKH+ZA==" - }, - "node_modules/assert": { - "version": "2.0.0", - "resolved": "https://registry.npmjs.org/assert/-/assert-2.0.0.tgz", - "integrity": "sha512-se5Cd+js9dXJnu6Ag2JFc00t+HmHOen+8Q+L7O9zI0PqQXr20uk2J0XQqMxZEeo5U50o8Nvmmx7dZrl+Ufr35A==", - "dependencies": { - "es6-object-assign": "^1.1.0", - "is-nan": "^1.2.1", - "object-is": "^1.0.1", - "util": "^0.12.0" - } - }, - "node_modules/async": { - "version": "2.6.4", - "resolved": "https://registry.npmjs.org/async/-/async-2.6.4.tgz", - "integrity": "sha512-mzo5dfJYwAn29PeiJ0zvwTo04zj8HDJj0Mn8TD7sno7q12prdbnasKJHhkm2c1LgrhlJ0teaea8860oxi51mGA==", - "dev": true, - "dependencies": { - "lodash": "^4.17.14" - } - }, - "node_modules/available-typed-arrays": { - "version": "1.0.5", - "resolved": "https://registry.npmjs.org/available-typed-arrays/-/available-typed-arrays-1.0.5.tgz", - "integrity": "sha512-DMD0KiN46eipeziST1LPP/STfDU0sufISXmjSgvVsoU2tqxctQeASejWcfNtxYKqETM1UxQ8sp2OrSBWpHY6sw==", - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/bail": { - "version": "1.0.5", - "resolved": "https://registry.npmjs.org/bail/-/bail-1.0.5.tgz", - "integrity": "sha512-xFbRxM1tahm08yHBP16MMjVUAvDaBMD38zsM9EMAUN61omwLmKlOpB/Zku5QkjZ8TZ4vn53pj+t518cH0S03RQ==", - "dev": true, - "funding": { - "type": "github", - "url": "https://github.com/sponsors/wooorm" - } - }, - "node_modules/balanced-match": { - "version": "1.0.2", - "resolved": "https://registry.npmjs.org/balanced-match/-/balanced-match-1.0.2.tgz", - "integrity": "sha512-3oSeUO0TMV67hN1AmbXsK4yaqU7tjiHlbxRDZOpH0KW9+CeX4bRAaX0Anxt0tx2MrpRpWwQaPwIlISEJhYU5Pw==" - }, - "node_modules/base64-js": { - "version": "1.5.1", - "resolved": "https://registry.npmjs.org/base64-js/-/base64-js-1.5.1.tgz", - "integrity": "sha512-AKpaYlHn8t4SVbOHCy+b5+KKgvR4vrsD8vbvrbiQJps7fKDTkjkDry6ji0rUJjC0kzbNePLwzxq8iypo41qeWA==", - "funding": [ - { - "type": "github", - "url": "https://github.com/sponsors/feross" - }, - { - "type": "patreon", - "url": "https://www.patreon.com/feross" - }, - { - "type": "consulting", - "url": "https://feross.org/support" - } - ] - }, - "node_modules/batch": { - "version": "0.6.1", - "resolved": "https://registry.npmjs.org/batch/-/batch-0.6.1.tgz", - "integrity": "sha1-3DQxT05nkxgJP8dgJyUl+UvyXBY=", - "dev": true - }, - "node_modules/big-integer": { - "version": "1.6.51", - "resolved": "https://registry.npmjs.org/big-integer/-/big-integer-1.6.51.tgz", - "integrity": "sha512-GPEid2Y9QU1Exl1rpO9B2IPJGHPSupF5GnVIP0blYvNOMer2bTvSWs1jGOUg04hTmu67nmLsQ9TBo1puaotBHg==", - "engines": { - "node": ">=0.6" - } - }, - "node_modules/bignumber.js": { - "version": "9.1.1", - "resolved": "https://registry.npmjs.org/bignumber.js/-/bignumber.js-9.1.1.tgz", - "integrity": "sha512-pHm4LsMJ6lzgNGVfZHjMoO8sdoRhOzOH4MLmY65Jg70bpxCKu5iOHNJyfF6OyvYw7t8Fpf35RuzUyqnQsj8Vig==", - "engines": { - "node": "*" - } - }, - "node_modules/binary-extensions": { - "version": "2.2.0", - "resolved": "https://registry.npmjs.org/binary-extensions/-/binary-extensions-2.2.0.tgz", - "integrity": "sha512-jDctJ/IVQbZoJykoeHbhXpOlNBqGNcwXJKJog42E5HDPUwQTSdjCHdihjj0DlnheQ7blbT6dHOafNAiS8ooQKA==", - "dev": true, - "engines": { - "node": ">=8" - } - }, - "node_modules/bl": { - "version": "4.1.0", - "resolved": "https://registry.npmjs.org/bl/-/bl-4.1.0.tgz", - "integrity": "sha512-1W07cM9gS6DcLperZfFSj+bWLtaPGSOHWhPiGzXmvVJbRLdG82sH/Kn8EtW1VqWVA54AKf2h5k5BbnIbwF3h6w==", - "dependencies": { - "buffer": "^5.5.0", - "inherits": "^2.0.4", - "readable-stream": "^3.4.0" - } - }, - "node_modules/bl/node_modules/buffer": { - "version": "5.7.1", - "resolved": "https://registry.npmjs.org/buffer/-/buffer-5.7.1.tgz", - "integrity": "sha512-EHcyIPBQ4BSGlvjB16k5KgAJ27CIsHY/2JBmCRReo48y9rQ3MaUzWX3KVlBa4U7MyX02HdVj0K7C3WaB3ju7FQ==", - "funding": [ - { - "type": "github", - "url": "https://github.com/sponsors/feross" - }, - { - "type": "patreon", - "url": "https://www.patreon.com/feross" - }, - { - "type": "consulting", - "url": "https://feross.org/support" - } - ], - "dependencies": { - "base64-js": "^1.3.1", - "ieee754": "^1.1.13" - } - }, - "node_modules/blakejs": { - "version": "1.2.1", - "resolved": "https://registry.npmjs.org/blakejs/-/blakejs-1.2.1.tgz", - "integrity": "sha512-QXUSXI3QVc/gJME0dBpXrag1kbzOqCjCX8/b54ntNyW6sjtoqxqRk3LTmXzaJoh71zMsDCjM+47jS7XiwN/+fQ==" - }, - "node_modules/bn.js": { - "version": "5.2.1", - "resolved": "https://registry.npmjs.org/bn.js/-/bn.js-5.2.1.tgz", - "integrity": "sha512-eXRvHzWyYPBuB4NBy0cmYQjGitUrtqwbvlzP3G6VFnNRbsZQIxQ10PbKKHt8gZ/HW/D/747aDl+QkDqg3KQLMQ==" - }, - "node_modules/body-parser": { - "version": "1.20.0", - "resolved": "https://registry.npmjs.org/body-parser/-/body-parser-1.20.0.tgz", - "integrity": "sha512-DfJ+q6EPcGKZD1QWUjSpqp+Q7bDQTsQIF4zfUAtZ6qk+H/3/QRhg9CEp39ss+/T2vw0+HaidC0ecJj/DRLIaKg==", - "dev": true, - "dependencies": { - "bytes": "3.1.2", - "content-type": "~1.0.4", - "debug": "2.6.9", - "depd": "2.0.0", - "destroy": "1.2.0", - "http-errors": "2.0.0", - "iconv-lite": "0.4.24", - "on-finished": "2.4.1", - "qs": "6.10.3", - "raw-body": "2.5.1", - "type-is": "~1.6.18", - "unpipe": "1.0.0" - }, - "engines": { - "node": ">= 0.8", - "npm": "1.2.8000 || >= 1.4.16" - } - }, - "node_modules/body-parser/node_modules/bytes": { - "version": "3.1.2", - "resolved": "https://registry.npmjs.org/bytes/-/bytes-3.1.2.tgz", - "integrity": "sha512-/Nf7TyzTx6S3yRJObOAV7956r8cr2+Oj8AC5dt8wSP3BQAoeX58NoHyCU8P8zGkNXStjTSi6fzO6F0pBdcYbEg==", - "dev": true, - "engines": { - "node": ">= 0.8" - } - }, - "node_modules/bonjour": { - "version": "3.5.0", - "resolved": "https://registry.npmjs.org/bonjour/-/bonjour-3.5.0.tgz", - "integrity": "sha1-jokKGD2O6aI5OzhExpGkK897yfU=", - "dev": true, - "dependencies": { - "array-flatten": "^2.1.0", - "deep-equal": "^1.0.1", - "dns-equal": "^1.0.0", - "dns-txt": "^2.0.2", - "multicast-dns": "^6.0.1", - "multicast-dns-service-types": "^1.1.0" - } - }, - "node_modules/boolbase": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/boolbase/-/boolbase-1.0.0.tgz", - "integrity": "sha1-aN/1++YMUes3cl6p4+0xDcwed24=", - "dev": true - }, - "node_modules/brace-expansion": { - "version": "1.1.11", - "resolved": "https://registry.npmjs.org/brace-expansion/-/brace-expansion-1.1.11.tgz", - "integrity": "sha512-iCuPHDFgrHX7H2vEI/5xpz07zSHB00TpugqhmYtVmMO6518mCuRMoOYFldEBl0g187ufozdaHgWKcYFb61qGiA==", - "dependencies": { - "balanced-match": "^1.0.0", - "concat-map": "0.0.1" - } - }, - "node_modules/braces": { - "version": "3.0.2", - "resolved": "https://registry.npmjs.org/braces/-/braces-3.0.2.tgz", - "integrity": "sha512-b8um+L1RzM3WDSzvhm6gIz1yfTbBt6YTlcEKAvsmqCZZFw46z626lVj9j1yEPW33H5H+lBQpZMP1k8l+78Ha0A==", - "dev": true, - "dependencies": { - "fill-range": "^7.0.1" - }, - "engines": { - "node": ">=8" - } - }, - "node_modules/brorand": { - "version": "1.1.0", - "resolved": "https://registry.npmjs.org/brorand/-/brorand-1.1.0.tgz", - "integrity": "sha1-EsJe/kCkXjwyPrhnWgoM5XsiNx8=" - }, - "node_modules/browserify-aes": { - "version": "1.2.0", - "resolved": "https://registry.npmjs.org/browserify-aes/-/browserify-aes-1.2.0.tgz", - "integrity": "sha512-+7CHXqGuspUn/Sl5aO7Ea0xWGAtETPXNSAjHo48JfLdPWcMng33Xe4znFvQweqc/uzk5zSOI3H52CYnjCfb5hA==", - "dependencies": { - "buffer-xor": "^1.0.3", - "cipher-base": "^1.0.0", - "create-hash": "^1.1.0", - "evp_bytestokey": "^1.0.3", - "inherits": "^2.0.1", - "safe-buffer": "^5.0.1" - } - }, - "node_modules/browserify-cipher": { - "version": "1.0.1", - "resolved": "https://registry.npmjs.org/browserify-cipher/-/browserify-cipher-1.0.1.tgz", - "integrity": "sha512-sPhkz0ARKbf4rRQt2hTpAHqn47X3llLkUGn+xEJzLjwY8LRs2p0v7ljvI5EyoRO/mexrNunNECisZs+gw2zz1w==", - "dependencies": { - "browserify-aes": "^1.0.4", - "browserify-des": "^1.0.0", - "evp_bytestokey": "^1.0.0" - } - }, - "node_modules/browserify-des": { - "version": "1.0.2", - "resolved": "https://registry.npmjs.org/browserify-des/-/browserify-des-1.0.2.tgz", - "integrity": "sha512-BioO1xf3hFwz4kc6iBhI3ieDFompMhrMlnDFC4/0/vd5MokpuAc3R+LYbwTA9A5Yc9pq9UYPqffKpW2ObuwX5A==", - "dependencies": { - "cipher-base": "^1.0.1", - "des.js": "^1.0.0", - "inherits": "^2.0.1", - "safe-buffer": "^5.1.2" - } - }, - "node_modules/browserify-rsa": { - "version": "4.1.0", - "resolved": "https://registry.npmjs.org/browserify-rsa/-/browserify-rsa-4.1.0.tgz", - "integrity": "sha512-AdEER0Hkspgno2aR97SAf6vi0y0k8NuOpGnVH3O99rcA5Q6sh8QxcngtHuJ6uXwnfAXNM4Gn1Gb7/MV1+Ymbog==", - "dependencies": { - "bn.js": "^5.0.0", - "randombytes": "^2.0.1" - } - }, - "node_modules/browserify-sign": { - "version": "4.2.1", - "resolved": "https://registry.npmjs.org/browserify-sign/-/browserify-sign-4.2.1.tgz", - "integrity": "sha512-/vrA5fguVAKKAVTNJjgSm1tRQDHUU6DbwO9IROu/0WAzC8PKhucDSh18J0RMvVeHAn5puMd+QHC2erPRNf8lmg==", - "dependencies": { - "bn.js": "^5.1.1", - "browserify-rsa": "^4.0.1", - "create-hash": "^1.2.0", - "create-hmac": "^1.1.7", - "elliptic": "^6.5.3", - "inherits": "^2.0.4", - "parse-asn1": "^5.1.5", - "readable-stream": "^3.6.0", - "safe-buffer": "^5.2.0" - } - }, - "node_modules/browserify-zlib": { - "version": "0.2.0", - "resolved": "https://registry.npmjs.org/browserify-zlib/-/browserify-zlib-0.2.0.tgz", - "integrity": "sha512-Z942RysHXmJrhqk88FmKBVq/v5tqmSkDz7p54G/MGyjMnCFFnC79XWNbg+Vta8W6Wb2qtSZTSxIGkJrRpCFEiA==", - "dependencies": { - "pako": "~1.0.5" - } - }, - "node_modules/browserslist": { - "version": "4.21.0", - "resolved": "https://registry.npmjs.org/browserslist/-/browserslist-4.21.0.tgz", - "integrity": "sha512-UQxE0DIhRB5z/zDz9iA03BOfxaN2+GQdBYH/2WrSIWEUrnpzTPJbhqt+umq6r3acaPRTW1FNTkrcp0PXgtFkvA==", - "funding": [ - { - "type": "opencollective", - "url": "https://opencollective.com/browserslist" - }, - { - "type": "tidelift", - "url": "https://tidelift.com/funding/github/npm/browserslist" - } - ], - "dependencies": { - "caniuse-lite": "^1.0.30001358", - "electron-to-chromium": "^1.4.164", - "node-releases": "^2.0.5", - "update-browserslist-db": "^1.0.0" - }, - "bin": { - "browserslist": "cli.js" - }, - "engines": { - "node": "^6 || ^7 || ^8 || ^9 || ^10 || ^11 || ^12 || >=13.7" - } - }, - "node_modules/buffer": { - "version": "6.0.3", - "resolved": "https://registry.npmjs.org/buffer/-/buffer-6.0.3.tgz", - "integrity": "sha512-FTiCpNxtwiZZHEZbcbTIcZjERVICn9yq/pDFkTl95/AxzD1naBctN7YO68riM/gLSDY7sdrMby8hofADYuuqOA==", - "funding": [ - { - "type": "github", - "url": "https://github.com/sponsors/feross" - }, - { - "type": "patreon", - "url": "https://www.patreon.com/feross" - }, - { - "type": "consulting", - "url": "https://feross.org/support" - } - ], - "dependencies": { - "base64-js": "^1.3.1", - "ieee754": "^1.2.1" - } - }, - "node_modules/buffer-crc32": { - "version": "0.2.13", - "resolved": "https://registry.npmjs.org/buffer-crc32/-/buffer-crc32-0.2.13.tgz", - "integrity": "sha512-VO9Ht/+p3SN7SKWqcrgEzjGbRSJYTx+Q1pTQC0wrWqHx0vpJraQ6GtHx8tvcg1rlK1byhU5gccxgOgj7B0TDkQ==", - "engines": { - "node": "*" - } - }, - "node_modules/buffer-from": { - "version": "1.1.2", - "resolved": "https://registry.npmjs.org/buffer-from/-/buffer-from-1.1.2.tgz", - "integrity": "sha512-E+XQCRwSbaaiChtv6k6Dwgc+bx+Bs6vuKJHHl5kox/BaKbhiXzqQOwK4cO22yElGp2OCmjwVhT3HmxgyPGnJfQ==" - }, - "node_modules/buffer-indexof": { - "version": "1.1.1", - "resolved": "https://registry.npmjs.org/buffer-indexof/-/buffer-indexof-1.1.1.tgz", - "integrity": "sha512-4/rOEg86jivtPTeOUUT61jJO1Ya1TrR/OkqCSZDyq84WJh3LuuiphBYJN+fm5xufIk4XAFcEwte/8WzC8If/1g==", - "dev": true - }, - "node_modules/buffer-xor": { - "version": "1.0.3", - "resolved": "https://registry.npmjs.org/buffer-xor/-/buffer-xor-1.0.3.tgz", - "integrity": "sha1-JuYe0UIvtw3ULm42cp7VHYVf6Nk=" - }, - "node_modules/bufferutil": { - "version": "4.0.5", - "resolved": "https://registry.npmjs.org/bufferutil/-/bufferutil-4.0.5.tgz", - "integrity": "sha512-HTm14iMQKK2FjFLRTM5lAVcyaUzOnqbPtesFIvREgXpJHdQm8bWS+GkQgIkfaBYRHuCnea7w8UVNfwiAQhlr9A==", - "hasInstallScript": true, - "dependencies": { - "node-gyp-build": "^4.3.0" - }, - "engines": { - "node": ">=6.14.2" - } - }, - "node_modules/builtin-status-codes": { - "version": "3.0.0", - "resolved": "https://registry.npmjs.org/builtin-status-codes/-/builtin-status-codes-3.0.0.tgz", - "integrity": "sha1-hZgoeOIbmOHGZCXgPQF0eI9Wnug=" - }, - "node_modules/bytes": { - "version": "3.0.0", - "resolved": "https://registry.npmjs.org/bytes/-/bytes-3.0.0.tgz", - "integrity": "sha1-0ygVQE1olpn4Wk6k+odV3ROpYEg=", - "dev": true, - "engines": { - "node": ">= 0.8" - } - }, - "node_modules/call-bind": { - "version": "1.0.2", - "resolved": "https://registry.npmjs.org/call-bind/-/call-bind-1.0.2.tgz", - "integrity": "sha512-7O+FbCihrB5WGbFYesctwmTKae6rOiIzmz1icreWJ+0aA7LJfuqhEso2T9ncpcFtzMQtzXf2QGGueWJGTYsqrA==", - "dependencies": { - "function-bind": "^1.1.1", - "get-intrinsic": "^1.0.2" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/camel-case": { - "version": "4.1.2", - "resolved": "https://registry.npmjs.org/camel-case/-/camel-case-4.1.2.tgz", - "integrity": "sha512-gxGWBrTT1JuMx6R+o5PTXMmUnhnVzLQ9SNutD4YqKtI6ap897t3tKECYla6gCWEkplXnlNybEkZg9GEGxKFCgw==", - "dev": true, - "dependencies": { - "pascal-case": "^3.1.2", - "tslib": "^2.0.3" - } - }, - "node_modules/caniuse-lite": { - "version": "1.0.30001358", - "resolved": "https://registry.npmjs.org/caniuse-lite/-/caniuse-lite-1.0.30001358.tgz", - "integrity": "sha512-hvp8PSRymk85R20bsDra7ZTCpSVGN/PAz9pSAjPSjKC+rNmnUk5vCRgJwiTT/O4feQ/yu/drvZYpKxxhbFuChw==", - "funding": [ - { - "type": "opencollective", - "url": "https://opencollective.com/browserslist" - }, - { - "type": "tidelift", - "url": "https://tidelift.com/funding/github/npm/caniuse-lite" - } - ] - }, - "node_modules/ccount": { - "version": "1.1.0", - "resolved": "https://registry.npmjs.org/ccount/-/ccount-1.1.0.tgz", - "integrity": "sha512-vlNK021QdI7PNeiUh/lKkC/mNHHfV0m/Ad5JoI0TYtlBnJAslM/JIkm/tGC88bkLIwO6OQ5uV6ztS6kVAtCDlg==", - "dev": true, - "funding": { - "type": "github", - "url": "https://github.com/sponsors/wooorm" - } - }, - "node_modules/character-entities": { - "version": "1.2.4", - "resolved": "https://registry.npmjs.org/character-entities/-/character-entities-1.2.4.tgz", - "integrity": "sha512-iBMyeEHxfVnIakwOuDXpVkc54HijNgCyQB2w0VfGQThle6NXn50zU6V/u+LDhxHcDUPojn6Kpga3PTAD8W1bQw==", - "dev": true, - "funding": { - "type": "github", - "url": "https://github.com/sponsors/wooorm" - } - }, - "node_modules/character-entities-legacy": { - "version": "1.1.4", - "resolved": "https://registry.npmjs.org/character-entities-legacy/-/character-entities-legacy-1.1.4.tgz", - "integrity": "sha512-3Xnr+7ZFS1uxeiUDvV02wQ+QDbc55o97tIV5zHScSPJpcLm/r0DFPcoY3tYRp+VZukxuMeKgXYmsXQHO05zQeA==", - "dev": true, - "funding": { - "type": "github", - "url": "https://github.com/sponsors/wooorm" - } - }, - "node_modules/character-reference-invalid": { - "version": "1.1.4", - "resolved": "https://registry.npmjs.org/character-reference-invalid/-/character-reference-invalid-1.1.4.tgz", - "integrity": "sha512-mKKUkUbhPpQlCOfIuZkvSEgktjPFIsZKRRbC6KWVEMvlzblj3i3asQv5ODsrwt0N3pHAEvjP8KTQPHkp0+6jOg==", - "dev": true, - "funding": { - "type": "github", - "url": "https://github.com/sponsors/wooorm" - } - }, - "node_modules/chokidar": { - "version": "3.5.3", - "resolved": "https://registry.npmjs.org/chokidar/-/chokidar-3.5.3.tgz", - "integrity": "sha512-Dr3sfKRP6oTcjf2JmUmFJfeVMvXBdegxB0iVQ5eb2V10uFJUCAS8OByZdVAyVb8xXNz3GjjTgj9kLWsZTqE6kw==", - "dev": true, - "funding": [ - { - "type": "individual", - "url": "https://paulmillr.com/funding/" - } - ], - "dependencies": { - "anymatch": "~3.1.2", - "braces": "~3.0.2", - "glob-parent": "~5.1.2", - "is-binary-path": "~2.1.0", - "is-glob": "~4.0.1", - "normalize-path": "~3.0.0", - "readdirp": "~3.6.0" - }, - "engines": { - "node": ">= 8.10.0" - }, - "optionalDependencies": { - "fsevents": "~2.3.2" - } - }, - "node_modules/chownr": { - "version": "1.1.4", - "resolved": "https://registry.npmjs.org/chownr/-/chownr-1.1.4.tgz", - "integrity": "sha512-jJ0bqzaylmJtVnNgzTeSOs8DPavpbYgEr/b0YL8/2GO3xJEhInFmhKMUnEJQjZumK7KXGFhUy89PrsJWlakBVg==" - }, - "node_modules/chrome-trace-event": { - "version": "1.0.3", - "resolved": "https://registry.npmjs.org/chrome-trace-event/-/chrome-trace-event-1.0.3.tgz", - "integrity": "sha512-p3KULyQg4S7NIHixdwbGX+nFHkoBiA4YQmyWtjb8XngSKV124nJmRysgAeujbUVb15vh+RvFUfCPqU7rXk+hZg==", - "engines": { - "node": ">=6.0" - } - }, - "node_modules/cipher-base": { - "version": "1.0.4", - "resolved": "https://registry.npmjs.org/cipher-base/-/cipher-base-1.0.4.tgz", - "integrity": "sha512-Kkht5ye6ZGmwv40uUDZztayT2ThLQGfnj/T71N/XzeZeo3nf8foyW7zGTsPYkEya3m5f3cAypH+qe7YOrM1U2Q==", - "dependencies": { - "inherits": "^2.0.1", - "safe-buffer": "^5.0.1" - } - }, - "node_modules/clean-css": { - "version": "5.3.0", - "resolved": "https://registry.npmjs.org/clean-css/-/clean-css-5.3.0.tgz", - "integrity": "sha512-YYuuxv4H/iNb1Z/5IbMRoxgrzjWGhOEFfd+groZ5dMCVkpENiMZmwspdrzBo9286JjM1gZJPAyL7ZIdzuvu2AQ==", - "dev": true, - "dependencies": { - "source-map": "~0.6.0" - }, - "engines": { - "node": ">= 10.0" - } - }, - "node_modules/clean-stack": { - "version": "2.2.0", - "resolved": "https://registry.npmjs.org/clean-stack/-/clean-stack-2.2.0.tgz", - "integrity": "sha512-4diC9HaTE+KRAMWhDhrGOECgWZxoevMc5TlkObMqNSsVU62PYzXZ/SMTjzyGAFF1YusgxGcSWTEXBhp0CPwQ1A==", - "dev": true, - "engines": { - "node": ">=6" - } - }, - "node_modules/clone-deep": { - "version": "4.0.1", - "resolved": "https://registry.npmjs.org/clone-deep/-/clone-deep-4.0.1.tgz", - "integrity": "sha512-neHB9xuzh/wk0dIHweyAXv2aPGZIVk3pLMe+/RNzINf17fe0OG96QroktYAUm7SM1PBnzTabaLboqqxDyMU+SQ==", - "dev": true, - "dependencies": { - "is-plain-object": "^2.0.4", - "kind-of": "^6.0.2", - "shallow-clone": "^3.0.0" - }, - "engines": { - "node": ">=6" - } - }, - "node_modules/colorette": { - "version": "2.0.19", - "resolved": "https://registry.npmjs.org/colorette/-/colorette-2.0.19.tgz", - "integrity": "sha512-3tlv/dIP7FWvj3BsbHrGLJ6l/oKh1O3TcgBqMn+yyCagOxc23fyzDS6HypQbgxWbkpDnf52p1LuR4eWDQ/K9WQ==", - "dev": true - }, - "node_modules/commander": { - "version": "8.3.0", - "resolved": "https://registry.npmjs.org/commander/-/commander-8.3.0.tgz", - "integrity": "sha512-OkTL9umf+He2DZkUq8f8J9of7yL6RJKI24dVITBmNfZBmri9zYZQrKkuXiKhyfPSu8tUhnVBB1iKXevvnlR4Ww==", - "dev": true, - "engines": { - "node": ">= 12" - } - }, - "node_modules/compressible": { - "version": "2.0.18", - "resolved": "https://registry.npmjs.org/compressible/-/compressible-2.0.18.tgz", - "integrity": "sha512-AF3r7P5dWxL8MxyITRMlORQNaOA2IkAFaTr4k7BUumjPtRpGDTZpl0Pb1XCO6JeDCBdp126Cgs9sMxqSjgYyRg==", - "dev": true, - "dependencies": { - "mime-db": ">= 1.43.0 < 2" - }, - "engines": { - "node": ">= 0.6" - } - }, - "node_modules/compression": { - "version": "1.7.4", - "resolved": "https://registry.npmjs.org/compression/-/compression-1.7.4.tgz", - "integrity": "sha512-jaSIDzP9pZVS4ZfQ+TzvtiWhdpFhE2RDHz8QJkpX9SIpLq88VueF5jJw6t+6CUQcAoA6t+x89MLrWAqpfDE8iQ==", - "dev": true, - "dependencies": { - "accepts": "~1.3.5", - "bytes": "3.0.0", - "compressible": "~2.0.16", - "debug": "2.6.9", - "on-headers": "~1.0.2", - "safe-buffer": "5.1.2", - "vary": "~1.1.2" - }, - "engines": { - "node": ">= 0.8.0" - } - }, - "node_modules/compression/node_modules/safe-buffer": { - "version": "5.1.2", - "resolved": "https://registry.npmjs.org/safe-buffer/-/safe-buffer-5.1.2.tgz", - "integrity": "sha512-Gd2UZBJDkXlY7GbJxfsE8/nvKkUEU1G38c1siN6QP6a9PT9MmHB8GnpscSmMJSoF8LOIrt8ud/wPtojys4G6+g==", - "dev": true - }, - "node_modules/concat-map": { - "version": "0.0.1", - "resolved": "https://registry.npmjs.org/concat-map/-/concat-map-0.0.1.tgz", - "integrity": "sha512-/Srv4dswyQNBfohGpz9o6Yb3Gz3SrUDqBH5rTuhGR7ahtlbYKnVxw2bCFMRljaA7EXHaXZ8wsHdodFvbkhKmqg==" - }, - "node_modules/connect-history-api-fallback": { - "version": "1.6.0", - "resolved": "https://registry.npmjs.org/connect-history-api-fallback/-/connect-history-api-fallback-1.6.0.tgz", - "integrity": "sha512-e54B99q/OUoH64zYYRf3HBP5z24G38h5D3qXu23JGRoigpX5Ss4r9ZnDk3g0Z8uQC2x2lPaJ+UlWBc1ZWBWdLg==", - "dev": true, - "engines": { - "node": ">=0.8" - } - }, - "node_modules/console-browserify": { - "version": "1.2.0", - "resolved": "https://registry.npmjs.org/console-browserify/-/console-browserify-1.2.0.tgz", - "integrity": "sha512-ZMkYO/LkF17QvCPqM0gxw8yUzigAOZOSWSHg91FH6orS7vcEj5dVZTidN2fQ14yBSdg97RqhSNwLUXInd52OTA==" - }, - "node_modules/constants-browserify": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/constants-browserify/-/constants-browserify-1.0.0.tgz", - "integrity": "sha1-wguW2MYXdIqvHBYCF2DNJ/y4y3U=" - }, - "node_modules/content-disposition": { - "version": "0.5.4", - "resolved": "https://registry.npmjs.org/content-disposition/-/content-disposition-0.5.4.tgz", - "integrity": "sha512-FveZTNuGw04cxlAiWbzi6zTAL/lhehaWbTtgluJh4/E95DqMwTmha3KZN1aAWA8cFIhHzMZUvLevkw5Rqk+tSQ==", - "dev": true, - "dependencies": { - "safe-buffer": "5.2.1" - }, - "engines": { - "node": ">= 0.6" - } - }, - "node_modules/content-type": { - "version": "1.0.4", - "resolved": "https://registry.npmjs.org/content-type/-/content-type-1.0.4.tgz", - "integrity": "sha512-hIP3EEPs8tB9AT1L+NUqtwOAps4mk2Zob89MWXMHjHWg9milF/j4osnnQLXBCBFBk/tvIG/tUc9mOUJiPBhPXA==", - "dev": true, - "engines": { - "node": ">= 0.6" - } - }, - "node_modules/cookie": { - "version": "0.5.0", - "resolved": "https://registry.npmjs.org/cookie/-/cookie-0.5.0.tgz", - "integrity": "sha512-YZ3GUyn/o8gfKJlnlX7g7xq4gyO6OSuhGPKaaGssGB2qgDUS0gPgtTvoyZLTt9Ab6dC4hfc9dV5arkvc/OCmrw==", - "dev": true, - "engines": { - "node": ">= 0.6" - } - }, - "node_modules/cookie-signature": { - "version": "1.0.6", - "resolved": "https://registry.npmjs.org/cookie-signature/-/cookie-signature-1.0.6.tgz", - "integrity": "sha1-4wOogrNCzD7oylE6eZmXNNqzriw=", - "dev": true - }, - "node_modules/core-util-is": { - "version": "1.0.3", - "resolved": "https://registry.npmjs.org/core-util-is/-/core-util-is-1.0.3.tgz", - "integrity": "sha512-ZQBvi1DcpJ4GDqanjucZ2Hj3wEO5pZDS89BWbkcrvdxksJorwUDDZamX9ldFkp9aw2lmBDLgkObEA4DWNJ9FYQ==", - "dev": true - }, - "node_modules/create-ecdh": { - "version": "4.0.4", - "resolved": "https://registry.npmjs.org/create-ecdh/-/create-ecdh-4.0.4.tgz", - "integrity": "sha512-mf+TCx8wWc9VpuxfP2ht0iSISLZnt0JgWlrOKZiNqyUZWnjIaCIVNQArMHnCZKfEYRg6IM7A+NeJoN8gf/Ws0A==", - "dependencies": { - "bn.js": "^4.1.0", - "elliptic": "^6.5.3" - } - }, - "node_modules/create-ecdh/node_modules/bn.js": { - "version": "4.12.0", - "resolved": "https://registry.npmjs.org/bn.js/-/bn.js-4.12.0.tgz", - "integrity": "sha512-c98Bf3tPniI+scsdk237ku1Dc3ujXQTSgyiPUDEOe7tRkhrqridvh8klBv0HCEso1OLOYcHuCv/cS6DNxKH+ZA==" - }, - "node_modules/create-hash": { - "version": "1.2.0", - "resolved": "https://registry.npmjs.org/create-hash/-/create-hash-1.2.0.tgz", - "integrity": "sha512-z00bCGNHDG8mHAkP7CtT1qVu+bFQUPjYq/4Iv3C3kWjTFV10zIjfSoeqXo9Asws8gwSHDGj/hl2u4OGIjapeCg==", - "dependencies": { - "cipher-base": "^1.0.1", - "inherits": "^2.0.1", - "md5.js": "^1.3.4", - "ripemd160": "^2.0.1", - "sha.js": "^2.4.0" - } - }, - "node_modules/create-hmac": { - "version": "1.1.7", - "resolved": "https://registry.npmjs.org/create-hmac/-/create-hmac-1.1.7.tgz", - "integrity": "sha512-MJG9liiZ+ogc4TzUwuvbER1JRdgvUFSB5+VR/g5h82fGaIRWMWddtKBHi7/sVhfjQZ6SehlyhvQYrcYkaUIpLg==", - "dependencies": { - "cipher-base": "^1.0.3", - "create-hash": "^1.1.0", - "inherits": "^2.0.1", - "ripemd160": "^2.0.0", - "safe-buffer": "^5.0.1", - "sha.js": "^2.4.8" - } - }, - "node_modules/cross-fetch": { - "version": "3.1.5", - "resolved": "https://registry.npmjs.org/cross-fetch/-/cross-fetch-3.1.5.tgz", - "integrity": "sha512-lvb1SBsI0Z7GDwmuid+mU3kWVBwTVUbe7S0H52yaaAdQOXq2YktTCZdlAcNKFzE6QtRz0snpw9bNiPeOIkkQvw==", - "dependencies": { - "node-fetch": "2.6.7" - } - }, - "node_modules/cross-spawn": { - "version": "7.0.3", - "resolved": "https://registry.npmjs.org/cross-spawn/-/cross-spawn-7.0.3.tgz", - "integrity": "sha512-iRDPJKUPVEND7dHPO8rkbOnPpyDygcDFtWjpeWNCgy8WP2rXcxXL8TskReQl6OrB2G7+UJrags1q15Fudc7G6w==", - "dev": true, - "dependencies": { - "path-key": "^3.1.0", - "shebang-command": "^2.0.0", - "which": "^2.0.1" - }, - "engines": { - "node": ">= 8" - } - }, - "node_modules/crypto-browserify": { - "version": "3.12.0", - "resolved": "https://registry.npmjs.org/crypto-browserify/-/crypto-browserify-3.12.0.tgz", - "integrity": "sha512-fz4spIh+znjO2VjL+IdhEpRJ3YN6sMzITSBijk6FK2UvTqruSQW+/cCZTSNsMiZNvUeq0CqurF+dAbyiGOY6Wg==", - "dependencies": { - "browserify-cipher": "^1.0.0", - "browserify-sign": "^4.0.0", - "create-ecdh": "^4.0.0", - "create-hash": "^1.1.0", - "create-hmac": "^1.1.0", - "diffie-hellman": "^5.0.0", - "inherits": "^2.0.1", - "pbkdf2": "^3.0.3", - "public-encrypt": "^4.0.0", - "randombytes": "^2.0.0", - "randomfill": "^1.0.3" - }, - "engines": { - "node": "*" - } - }, - "node_modules/css-select": { - "version": "4.3.0", - "resolved": "https://registry.npmjs.org/css-select/-/css-select-4.3.0.tgz", - "integrity": "sha512-wPpOYtnsVontu2mODhA19JrqWxNsfdatRKd64kmpRbQgh1KtItko5sTnEpPdpSaJszTOhEMlF/RPz28qj4HqhQ==", - "dev": true, - "dependencies": { - "boolbase": "^1.0.0", - "css-what": "^6.0.1", - "domhandler": "^4.3.1", - "domutils": "^2.8.0", - "nth-check": "^2.0.1" - }, - "funding": { - "url": "https://github.com/sponsors/fb55" - } - }, - "node_modules/css-what": { - "version": "6.1.0", - "resolved": "https://registry.npmjs.org/css-what/-/css-what-6.1.0.tgz", - "integrity": "sha512-HTUrgRJ7r4dsZKU6GjmpfRK1O76h97Z8MfS1G0FozR+oF2kG6Vfe8JE6zwrkbxigziPHinCJ+gCPjA9EaBDtRw==", - "dev": true, - "engines": { - "node": ">= 6" - }, - "funding": { - "url": "https://github.com/sponsors/fb55" - } - }, - "node_modules/debug": { - "version": "2.6.9", - "resolved": "https://registry.npmjs.org/debug/-/debug-2.6.9.tgz", - "integrity": "sha512-bC7ElrdJaJnPbAP+1EotYvqZsb3ecl5wi6Bfi6BJTUcNowp6cvspg0jXznRTKDjm/E7AdgFBVeAPVMNcKGsHMA==", - "dev": true, - "dependencies": { - "ms": "2.0.0" - } - }, - "node_modules/deep-equal": { - "version": "1.1.1", - "resolved": "https://registry.npmjs.org/deep-equal/-/deep-equal-1.1.1.tgz", - "integrity": "sha512-yd9c5AdiqVcR+JjcwUQb9DkhJc8ngNr0MahEBGvDiJw8puWab2yZlh+nkasOnZP+EGTAP6rRp2JzJhJZzvNF8g==", - "dev": true, - "dependencies": { - "is-arguments": "^1.0.4", - "is-date-object": "^1.0.1", - "is-regex": "^1.0.4", - "object-is": "^1.0.1", - "object-keys": "^1.1.1", - "regexp.prototype.flags": "^1.2.0" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/default-gateway": { - "version": "6.0.3", - "resolved": "https://registry.npmjs.org/default-gateway/-/default-gateway-6.0.3.tgz", - "integrity": "sha512-fwSOJsbbNzZ/CUFpqFBqYfYNLj1NbMPm8MMCIzHjC83iSJRBEGmDUxU+WP661BaBQImeC2yHwXtz+P/O9o+XEg==", - "dev": true, - "dependencies": { - "execa": "^5.0.0" - }, - "engines": { - "node": ">= 10" - } - }, - "node_modules/define-lazy-prop": { - "version": "2.0.0", - "resolved": "https://registry.npmjs.org/define-lazy-prop/-/define-lazy-prop-2.0.0.tgz", - "integrity": "sha512-Ds09qNh8yw3khSjiJjiUInaGX9xlqZDY7JVryGxdxV7NPeuqQfplOpQ66yJFZut3jLa5zOwkXw1g9EI2uKh4Og==", - "dev": true, - "engines": { - "node": ">=8" - } - }, - "node_modules/define-properties": { - "version": "1.1.4", - "resolved": "https://registry.npmjs.org/define-properties/-/define-properties-1.1.4.tgz", - "integrity": "sha512-uckOqKcfaVvtBdsVkdPv3XjveQJsNQqmhXgRi8uhvWWuPYZCNlzT8qAyblUgNoXdHdjMTzAqeGjAoli8f+bzPA==", - "dependencies": { - "has-property-descriptors": "^1.0.0", - "object-keys": "^1.1.1" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/del": { - "version": "6.1.1", - "resolved": "https://registry.npmjs.org/del/-/del-6.1.1.tgz", - "integrity": "sha512-ua8BhapfP0JUJKC/zV9yHHDW/rDoDxP4Zhn3AkA6/xT6gY7jYXJiaeyBZznYVujhZZET+UgcbZiQ7sN3WqcImg==", - "dev": true, - "dependencies": { - "globby": "^11.0.1", - "graceful-fs": "^4.2.4", - "is-glob": "^4.0.1", - "is-path-cwd": "^2.2.0", - "is-path-inside": "^3.0.2", - "p-map": "^4.0.0", - "rimraf": "^3.0.2", - "slash": "^3.0.0" - }, - "engines": { - "node": ">=10" - }, - "funding": { - "url": "https://github.com/sponsors/sindresorhus" - } - }, - "node_modules/depd": { - "version": "2.0.0", - "resolved": "https://registry.npmjs.org/depd/-/depd-2.0.0.tgz", - "integrity": "sha512-g7nH6P6dyDioJogAAGprGpCtVImJhpPk/roCzdb3fIh61/s/nPsfR6onyMwkCAR/OlC3yBC0lESvUoQEAssIrw==", - "dev": true, - "engines": { - "node": ">= 0.8" - } - }, - "node_modules/des.js": { - "version": "1.0.1", - "resolved": "https://registry.npmjs.org/des.js/-/des.js-1.0.1.tgz", - "integrity": "sha512-Q0I4pfFrv2VPd34/vfLrFOoRmlYj3OV50i7fskps1jZWK1kApMWWT9G6RRUeYedLcBDIhnSDaUvJMb3AhUlaEA==", - "dependencies": { - "inherits": "^2.0.1", - "minimalistic-assert": "^1.0.0" - } - }, - "node_modules/destroy": { - "version": "1.2.0", - "resolved": "https://registry.npmjs.org/destroy/-/destroy-1.2.0.tgz", - "integrity": "sha512-2sJGJTaXIIaR1w4iJSNoN0hnMY7Gpc/n8D4qSCJw8QqFWXf7cuAgnEHxBpweaVcPevC2l3KpjYCx3NypQQgaJg==", - "dev": true, - "engines": { - "node": ">= 0.8", - "npm": "1.2.8000 || >= 1.4.16" - } - }, - "node_modules/detect-node": { - "version": "2.1.0", - "resolved": "https://registry.npmjs.org/detect-node/-/detect-node-2.1.0.tgz", - "integrity": "sha512-T0NIuQpnTvFDATNuHN5roPwSBG83rFsuO+MXXH9/3N1eFbn4wcPjttvjMLEPWJ0RGUYgQE7cGgS3tNxbqCGM7g==", - "dev": true - }, - "node_modules/devtools-protocol": { - "version": "0.0.1011705", - "resolved": "https://registry.npmjs.org/devtools-protocol/-/devtools-protocol-0.0.1011705.tgz", - "integrity": "sha512-OKvTvu9n3swmgYshvsyVHYX0+aPzCoYUnyXUacfQMmFtBtBKewV/gT4I9jkAbpTqtTi2E4S9MXLlvzBDUlqg0Q==" - }, - "node_modules/diffie-hellman": { - "version": "5.0.3", - "resolved": "https://registry.npmjs.org/diffie-hellman/-/diffie-hellman-5.0.3.tgz", - "integrity": "sha512-kqag/Nl+f3GwyK25fhUMYj81BUOrZ9IuJsjIcDE5icNM9FJHAVm3VcUDxdLPoQtTuUylWm6ZIknYJwwaPxsUzg==", - "dependencies": { - "bn.js": "^4.1.0", - "miller-rabin": "^4.0.0", - "randombytes": "^2.0.0" - } - }, - "node_modules/diffie-hellman/node_modules/bn.js": { - "version": "4.12.0", - "resolved": "https://registry.npmjs.org/bn.js/-/bn.js-4.12.0.tgz", - "integrity": "sha512-c98Bf3tPniI+scsdk237ku1Dc3ujXQTSgyiPUDEOe7tRkhrqridvh8klBv0HCEso1OLOYcHuCv/cS6DNxKH+ZA==" - }, - "node_modules/dir-glob": { - "version": "3.0.1", - "resolved": "https://registry.npmjs.org/dir-glob/-/dir-glob-3.0.1.tgz", - "integrity": "sha512-WkrWp9GR4KXfKGYzOLmTuGVi1UWFfws377n9cc55/tb6DuqyF6pcQ5AbiHEshaDpY9v6oaSr2XCDidGmMwdzIA==", - "dev": true, - "dependencies": { - "path-type": "^4.0.0" - }, - "engines": { - "node": ">=8" - } - }, - "node_modules/dns-equal": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/dns-equal/-/dns-equal-1.0.0.tgz", - "integrity": "sha512-z+paD6YUQsk+AbGCEM4PrOXSss5gd66QfcVBFTKR/HpFL9jCqikS94HYwKww6fQyO7IxrIIyUu+g0Ka9tUS2Cg==", - "dev": true - }, - "node_modules/dns-packet": { - "version": "1.3.4", - "resolved": "https://registry.npmjs.org/dns-packet/-/dns-packet-1.3.4.tgz", - "integrity": "sha512-BQ6F4vycLXBvdrJZ6S3gZewt6rcrks9KBgM9vrhW+knGRqc8uEdT7fuCwloc7nny5xNoMJ17HGH0R/6fpo8ECA==", - "dev": true, - "dependencies": { - "ip": "^1.1.0", - "safe-buffer": "^5.0.1" - } - }, - "node_modules/dns-txt": { - "version": "2.0.2", - "resolved": "https://registry.npmjs.org/dns-txt/-/dns-txt-2.0.2.tgz", - "integrity": "sha512-Ix5PrWjphuSoUXV/Zv5gaFHjnaJtb02F2+Si3Ht9dyJ87+Z/lMmy+dpNHtTGraNK958ndXq2i+GLkWsWHcKaBQ==", - "dev": true, - "dependencies": { - "buffer-indexof": "^1.0.0" - } - }, - "node_modules/doctoc": { - "version": "2.2.1", - "resolved": "https://registry.npmjs.org/doctoc/-/doctoc-2.2.1.tgz", - "integrity": "sha512-qNJ1gsuo7hH40vlXTVVrADm6pdg30bns/Mo7Nv1SxuXSM1bwF9b4xQ40a6EFT/L1cI+Yylbyi8MPI4G4y7XJzQ==", - "dev": true, - "dependencies": { - "@textlint/markdown-to-ast": "^12.1.1", - "anchor-markdown-header": "^0.6.0", - "htmlparser2": "^7.2.0", - "minimist": "^1.2.6", - "underscore": "^1.13.2", - "update-section": "^0.3.3" - }, - "bin": { - "doctoc": "doctoc.js" - } - }, - "node_modules/doctoc/node_modules/entities": { - "version": "3.0.1", - "resolved": "https://registry.npmjs.org/entities/-/entities-3.0.1.tgz", - "integrity": "sha512-WiyBqoomrwMdFG1e0kqvASYfnlb0lp8M5o5Fw2OFq1hNZxxcNk8Ik0Xm7LxzBhuidnZB/UtBqVCgUz3kBOP51Q==", - "dev": true, - "engines": { - "node": ">=0.12" - }, - "funding": { - "url": "https://github.com/fb55/entities?sponsor=1" - } - }, - "node_modules/doctoc/node_modules/htmlparser2": { - "version": "7.2.0", - "resolved": "https://registry.npmjs.org/htmlparser2/-/htmlparser2-7.2.0.tgz", - "integrity": "sha512-H7MImA4MS6cw7nbyURtLPO1Tms7C5H602LRETv95z1MxO/7CP7rDVROehUYeYBUYEON94NXXDEPmZuq+hX4sog==", - "dev": true, - "funding": [ - "https://github.com/fb55/htmlparser2?sponsor=1", - { - "type": "github", - "url": "https://github.com/sponsors/fb55" - } - ], - "dependencies": { - "domelementtype": "^2.0.1", - "domhandler": "^4.2.2", - "domutils": "^2.8.0", - "entities": "^3.0.1" - } - }, - "node_modules/dom-converter": { - "version": "0.2.0", - "resolved": "https://registry.npmjs.org/dom-converter/-/dom-converter-0.2.0.tgz", - "integrity": "sha512-gd3ypIPfOMr9h5jIKq8E3sHOTCjeirnl0WK5ZdS1AW0Odt0b1PaWaHdJ4Qk4klv+YB9aJBS7mESXjFoDQPu6DA==", - "dev": true, - "dependencies": { - "utila": "~0.4" - } - }, - "node_modules/dom-serializer": { - "version": "1.4.1", - "resolved": "https://registry.npmjs.org/dom-serializer/-/dom-serializer-1.4.1.tgz", - "integrity": "sha512-VHwB3KfrcOOkelEG2ZOfxqLZdfkil8PtJi4P8N2MMXucZq2yLp75ClViUlOVwyoHEDjYU433Aq+5zWP61+RGag==", - "dev": true, - "dependencies": { - "domelementtype": "^2.0.1", - "domhandler": "^4.2.0", - "entities": "^2.0.0" - }, - "funding": { - "url": "https://github.com/cheeriojs/dom-serializer?sponsor=1" - } - }, - "node_modules/domain-browser": { - "version": "4.22.0", - "resolved": "https://registry.npmjs.org/domain-browser/-/domain-browser-4.22.0.tgz", - "integrity": "sha512-IGBwjF7tNk3cwypFNH/7bfzBcgSCbaMOD3GsaY1AU/JRrnHnYgEM0+9kQt52iZxjNsjBtJYtao146V+f8jFZNw==", - "engines": { - "node": ">=10" - }, - "funding": { - "url": "https://bevry.me/fund" - } - }, - "node_modules/domelementtype": { - "version": "2.3.0", - "resolved": "https://registry.npmjs.org/domelementtype/-/domelementtype-2.3.0.tgz", - "integrity": "sha512-OLETBj6w0OsagBwdXnPdN0cnMfF9opN69co+7ZrbfPGrdpPVNBUj02spi6B1N7wChLQiPn4CSH/zJvXw56gmHw==", - "dev": true, - "funding": [ - { - "type": "github", - "url": "https://github.com/sponsors/fb55" - } - ] - }, - "node_modules/domhandler": { - "version": "4.3.1", - "resolved": "https://registry.npmjs.org/domhandler/-/domhandler-4.3.1.tgz", - "integrity": "sha512-GrwoxYN+uWlzO8uhUXRl0P+kHE4GtVPfYzVLcUxPL7KNdHKj66vvlhiweIHqYYXWlw+T8iLMp42Lm67ghw4WMQ==", - "dev": true, - "dependencies": { - "domelementtype": "^2.2.0" - }, - "engines": { - "node": ">= 4" - }, - "funding": { - "url": "https://github.com/fb55/domhandler?sponsor=1" - } - }, - "node_modules/domutils": { - "version": "2.8.0", - "resolved": "https://registry.npmjs.org/domutils/-/domutils-2.8.0.tgz", - "integrity": "sha512-w96Cjofp72M5IIhpjgobBimYEfoPjx1Vx0BSX9P30WBdZW2WIKU0T1Bd0kz2eNZ9ikjKgHbEyKx8BB6H1L3h3A==", - "dev": true, - "dependencies": { - "dom-serializer": "^1.0.1", - "domelementtype": "^2.2.0", - "domhandler": "^4.2.0" - }, - "funding": { - "url": "https://github.com/fb55/domutils?sponsor=1" - } - }, - "node_modules/dot-case": { - "version": "3.0.4", - "resolved": "https://registry.npmjs.org/dot-case/-/dot-case-3.0.4.tgz", - "integrity": "sha512-Kv5nKlh6yRrdrGvxeJ2e5y2eRUpkUosIW4A2AS38zwSz27zu7ufDwQPi5Jhs3XAlGNetl3bmnGhQsMtkKJnj3w==", - "dev": true, - "dependencies": { - "no-case": "^3.0.4", - "tslib": "^2.0.3" - } - }, - "node_modules/ee-first": { - "version": "1.1.1", - "resolved": "https://registry.npmjs.org/ee-first/-/ee-first-1.1.1.tgz", - "integrity": "sha512-WMwm9LhRUo+WUaRN+vRuETqG89IgZphVSNkdFgeb6sS/E4OrDIN7t48CAewSHXc6C8lefD8KKfr5vY61brQlow==", - "dev": true - }, - "node_modules/electron-to-chromium": { - "version": "1.4.167", - "resolved": "https://registry.npmjs.org/electron-to-chromium/-/electron-to-chromium-1.4.167.tgz", - "integrity": "sha512-lPHuHXBwpkr4RcfaZBKm6TKOWG/1N9mVggUpP4fY3l1JIUU2x4fkM8928smYdZ5lF+6KCTAxo1aK9JmqT+X71Q==" - }, - "node_modules/elliptic": { - "version": "6.5.4", - "resolved": "https://registry.npmjs.org/elliptic/-/elliptic-6.5.4.tgz", - "integrity": "sha512-iLhC6ULemrljPZb+QutR5TQGB+pdW6KGD5RSegS+8sorOZT+rdQFbsQFJgvN3eRqNALqJer4oQ16YvJHlU8hzQ==", - "dependencies": { - "bn.js": "^4.11.9", - "brorand": "^1.1.0", - "hash.js": "^1.0.0", - "hmac-drbg": "^1.0.1", - "inherits": "^2.0.4", - "minimalistic-assert": "^1.0.1", - "minimalistic-crypto-utils": "^1.0.1" - } - }, - "node_modules/elliptic/node_modules/bn.js": { - "version": "4.12.0", - "resolved": "https://registry.npmjs.org/bn.js/-/bn.js-4.12.0.tgz", - "integrity": "sha512-c98Bf3tPniI+scsdk237ku1Dc3ujXQTSgyiPUDEOe7tRkhrqridvh8klBv0HCEso1OLOYcHuCv/cS6DNxKH+ZA==" - }, - "node_modules/emoji-regex": { - "version": "10.1.0", - "resolved": "https://registry.npmjs.org/emoji-regex/-/emoji-regex-10.1.0.tgz", - "integrity": "sha512-xAEnNCT3w2Tg6MA7ly6QqYJvEoY1tm9iIjJ3yMKK9JPlWuRHAMoe5iETwQnx3M9TVbFMfsrBgWKR+IsmswwNjg==", - "dev": true - }, - "node_modules/encodeurl": { - "version": "1.0.2", - "resolved": "https://registry.npmjs.org/encodeurl/-/encodeurl-1.0.2.tgz", - "integrity": "sha512-TPJXq8JqFaVYm2CWmPvnP2Iyo4ZSM7/QKcSmuMLDObfpH5fi7RUGmd/rTDf+rut/saiDiQEeVTNgAmJEdAOx0w==", - "dev": true, - "engines": { - "node": ">= 0.8" - } - }, - "node_modules/end-of-stream": { - "version": "1.4.4", - "resolved": "https://registry.npmjs.org/end-of-stream/-/end-of-stream-1.4.4.tgz", - "integrity": "sha512-+uw1inIHVPQoaVuHzRyXd21icM+cnt4CzD5rW+NC1wjOUSTOs+Te7FOv7AhN7vS9x/oIyhLP5PR1H+phQAHu5Q==", - "dependencies": { - "once": "^1.4.0" - } - }, - "node_modules/enhanced-resolve": { - "version": "5.9.3", - "resolved": "https://registry.npmjs.org/enhanced-resolve/-/enhanced-resolve-5.9.3.tgz", - "integrity": "sha512-Bq9VSor+kjvW3f9/MiiR4eE3XYgOl7/rS8lnSxbRbF3kS0B2r+Y9w5krBWxZgDxASVZbdYrn5wT4j/Wb0J9qow==", - "dependencies": { - "graceful-fs": "^4.2.4", - "tapable": "^2.2.0" - }, - "engines": { - "node": ">=10.13.0" - } - }, - "node_modules/entities": { - "version": "2.2.0", - "resolved": "https://registry.npmjs.org/entities/-/entities-2.2.0.tgz", - "integrity": "sha512-p92if5Nz619I0w+akJrLZH0MX0Pb5DX39XOwQTtXSdQQOaYH03S1uIQp4mhOZtAXrxq4ViO67YTiLBo2638o9A==", - "dev": true, - "funding": { - "url": "https://github.com/fb55/entities?sponsor=1" - } - }, - "node_modules/envinfo": { - "version": "7.8.1", - "resolved": "https://registry.npmjs.org/envinfo/-/envinfo-7.8.1.tgz", - "integrity": "sha512-/o+BXHmB7ocbHEAs6F2EnG0ogybVVUdkRunTT2glZU9XAaGmhqskrvKwqXuDfNjEO0LZKWdejEEpnq8aM0tOaw==", - "dev": true, - "bin": { - "envinfo": "dist/cli.js" - }, - "engines": { - "node": ">=4" - } - }, - "node_modules/es-abstract": { - "version": "1.20.1", - "resolved": "https://registry.npmjs.org/es-abstract/-/es-abstract-1.20.1.tgz", - "integrity": "sha512-WEm2oBhfoI2sImeM4OF2zE2V3BYdSF+KnSi9Sidz51fQHd7+JuF8Xgcj9/0o+OWeIeIS/MiuNnlruQrJf16GQA==", - "dependencies": { - "call-bind": "^1.0.2", - "es-to-primitive": "^1.2.1", - "function-bind": "^1.1.1", - "function.prototype.name": "^1.1.5", - "get-intrinsic": "^1.1.1", - "get-symbol-description": "^1.0.0", - "has": "^1.0.3", - "has-property-descriptors": "^1.0.0", - "has-symbols": "^1.0.3", - "internal-slot": "^1.0.3", - "is-callable": "^1.2.4", - "is-negative-zero": "^2.0.2", - "is-regex": "^1.1.4", - "is-shared-array-buffer": "^1.0.2", - "is-string": "^1.0.7", - "is-weakref": "^1.0.2", - "object-inspect": "^1.12.0", - "object-keys": "^1.1.1", - "object.assign": "^4.1.2", - "regexp.prototype.flags": "^1.4.3", - "string.prototype.trimend": "^1.0.5", - "string.prototype.trimstart": "^1.0.5", - "unbox-primitive": "^1.0.2" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/es-module-lexer": { - "version": "0.9.3", - "resolved": "https://registry.npmjs.org/es-module-lexer/-/es-module-lexer-0.9.3.tgz", - "integrity": "sha512-1HQ2M2sPtxwnvOvT1ZClHyQDiggdNjURWpY2we6aMKCQiUVxTmVs2UYPLIrD84sS+kMdUwfBSylbJPwNnBrnHQ==" - }, - "node_modules/es-to-primitive": { - "version": "1.2.1", - "resolved": "https://registry.npmjs.org/es-to-primitive/-/es-to-primitive-1.2.1.tgz", - "integrity": "sha512-QCOllgZJtaUo9miYBcLChTUaHNjJF3PYs1VidD7AwiEj1kYxKeQTctLAezAOH5ZKRH0g2IgPn6KwB4IT8iRpvA==", - "dependencies": { - "is-callable": "^1.1.4", - "is-date-object": "^1.0.1", - "is-symbol": "^1.0.2" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/es6-object-assign": { - "version": "1.1.0", - "resolved": "https://registry.npmjs.org/es6-object-assign/-/es6-object-assign-1.1.0.tgz", - "integrity": "sha512-MEl9uirslVwqQU369iHNWZXsI8yaZYGg/D65aOgZkeyFJwHYSxilf7rQzXKI7DdDuBPrBXbfk3sl9hJhmd5AUw==" - }, - "node_modules/escalade": { - "version": "3.1.1", - "resolved": "https://registry.npmjs.org/escalade/-/escalade-3.1.1.tgz", - "integrity": "sha512-k0er2gUkLf8O0zKJiAhmkTnJlTvINGv7ygDNPbeIsX/TJjGJZHuh9B2UxbsaEkmlEo9MfhrSzmhIlhRlI2GXnw==", - "engines": { - "node": ">=6" - } - }, - "node_modules/escape-html": { - "version": "1.0.3", - "resolved": "https://registry.npmjs.org/escape-html/-/escape-html-1.0.3.tgz", - "integrity": "sha512-NiSupZ4OeuGwr68lGIeym/ksIZMJodUGOSCZ/FSnTxcrekbvqrgdUxlJOMpijaKZVjAJrWrGs/6Jy8OMuyj9ow==", - "dev": true - }, - "node_modules/escape-string-regexp": { - "version": "4.0.0", - "resolved": "https://registry.npmjs.org/escape-string-regexp/-/escape-string-regexp-4.0.0.tgz", - "integrity": "sha512-TtpcNJ3XAzx3Gq8sWRzJaVajRs0uVxA2YAkdb1jm2YkPz4G6egUFAyA3n5vtEIZefPk5Wa4UXbKuS5fKkJWdgA==", - "dev": true, - "engines": { - "node": ">=10" - }, - "funding": { - "url": "https://github.com/sponsors/sindresorhus" - } - }, - "node_modules/eslint-scope": { - "version": "5.1.1", - "resolved": "https://registry.npmjs.org/eslint-scope/-/eslint-scope-5.1.1.tgz", - "integrity": "sha512-2NxwbF/hZ0KpepYN0cNbo+FN6XoK7GaHlQhgx/hIZl6Va0bF45RQOOwhLIy8lQDbuCiadSLCBnH2CFYquit5bw==", - "dependencies": { - "esrecurse": "^4.3.0", - "estraverse": "^4.1.1" - }, - "engines": { - "node": ">=8.0.0" - } - }, - "node_modules/esrecurse": { - "version": "4.3.0", - "resolved": "https://registry.npmjs.org/esrecurse/-/esrecurse-4.3.0.tgz", - "integrity": "sha512-KmfKL3b6G+RXvP8N1vr3Tq1kL/oCFgn2NYXEtqP8/L3pKapUA4G8cFVaoF3SU323CD4XypR/ffioHmkti6/Tag==", - "dependencies": { - "estraverse": "^5.2.0" - }, - "engines": { - "node": ">=4.0" - } - }, - "node_modules/esrecurse/node_modules/estraverse": { - "version": "5.3.0", - "resolved": "https://registry.npmjs.org/estraverse/-/estraverse-5.3.0.tgz", - "integrity": "sha512-MMdARuVEQziNTeJD8DgMqmhwR11BRQ/cBP+pLtYdSTnf3MIO8fFeiINEbX36ZdNlfU/7A9f3gUw49B3oQsvwBA==", - "engines": { - "node": ">=4.0" - } - }, - "node_modules/estraverse": { - "version": "4.3.0", - "resolved": "https://registry.npmjs.org/estraverse/-/estraverse-4.3.0.tgz", - "integrity": "sha512-39nnKffWz8xN1BU/2c79n9nB9HDzo0niYUqx6xyqUnyoAnQyyWpOTdZEeiCch8BBu515t4wp9ZmgVfVhn9EBpw==", - "engines": { - "node": ">=4.0" - } - }, - "node_modules/etag": { - "version": "1.8.1", - "resolved": "https://registry.npmjs.org/etag/-/etag-1.8.1.tgz", - "integrity": "sha512-aIL5Fx7mawVa300al2BnEE4iNvo1qETxLrPI/o05L7z6go7fCw1J6EQmbK4FmJ2AS7kgVF/KEZWufBfdClMcPg==", - "dev": true, - "engines": { - "node": ">= 0.6" - } - }, - "node_modules/eventemitter3": { - "version": "4.0.7", - "resolved": "https://registry.npmjs.org/eventemitter3/-/eventemitter3-4.0.7.tgz", - "integrity": "sha512-8guHBZCwKnFhYdHr2ysuRWErTwhoN2X8XELRlrRwpmfeY2jjuUN4taQMsULKUVo1K4DvZl+0pgfyoysHxvmvEw==", - "dev": true - }, - "node_modules/events": { - "version": "3.3.0", - "resolved": "https://registry.npmjs.org/events/-/events-3.3.0.tgz", - "integrity": "sha512-mQw+2fkQbALzQ7V0MY0IqdnXNOeTtP4r0lN9z7AAawCXgqea7bDii20AYrIBrFd/Hx0M2Ocz6S111CaFkUcb0Q==", - "engines": { - "node": ">=0.8.x" - } - }, - "node_modules/evp_bytestokey": { - "version": "1.0.3", - "resolved": "https://registry.npmjs.org/evp_bytestokey/-/evp_bytestokey-1.0.3.tgz", - "integrity": "sha512-/f2Go4TognH/KvCISP7OUsHn85hT9nUkxxA9BEWxFn+Oj9o8ZNLm/40hdlgSLyuOimsrTKLUMEorQexp/aPQeA==", - "dependencies": { - "md5.js": "^1.3.4", - "safe-buffer": "^5.1.1" - } - }, - "node_modules/execa": { - "version": "5.1.1", - "resolved": "https://registry.npmjs.org/execa/-/execa-5.1.1.tgz", - "integrity": "sha512-8uSpZZocAZRBAPIEINJj3Lo9HyGitllczc27Eh5YYojjMFMn8yHMDMaUHE2Jqfq05D/wucwI4JGURyXt1vchyg==", - "dev": true, - "dependencies": { - "cross-spawn": "^7.0.3", - "get-stream": "^6.0.0", - "human-signals": "^2.1.0", - "is-stream": "^2.0.0", - "merge-stream": "^2.0.0", - "npm-run-path": "^4.0.1", - "onetime": "^5.1.2", - "signal-exit": "^3.0.3", - "strip-final-newline": "^2.0.0" - }, - "engines": { - "node": ">=10" - }, - "funding": { - "url": "https://github.com/sindresorhus/execa?sponsor=1" - } - }, - "node_modules/express": { - "version": "4.18.1", - "resolved": "https://registry.npmjs.org/express/-/express-4.18.1.tgz", - "integrity": "sha512-zZBcOX9TfehHQhtupq57OF8lFZ3UZi08Y97dwFCkD8p9d/d2Y3M+ykKcwaMDEL+4qyUolgBDX6AblpR3fL212Q==", - "dev": true, - "dependencies": { - "accepts": "~1.3.8", - "array-flatten": "1.1.1", - "body-parser": "1.20.0", - "content-disposition": "0.5.4", - "content-type": "~1.0.4", - "cookie": "0.5.0", - "cookie-signature": "1.0.6", - "debug": "2.6.9", - "depd": "2.0.0", - "encodeurl": "~1.0.2", - "escape-html": "~1.0.3", - "etag": "~1.8.1", - "finalhandler": "1.2.0", - "fresh": "0.5.2", - "http-errors": "2.0.0", - "merge-descriptors": "1.0.1", - "methods": "~1.1.2", - "on-finished": "2.4.1", - "parseurl": "~1.3.3", - "path-to-regexp": "0.1.7", - "proxy-addr": "~2.0.7", - "qs": "6.10.3", - "range-parser": "~1.2.1", - "safe-buffer": "5.2.1", - "send": "0.18.0", - "serve-static": "1.15.0", - "setprototypeof": "1.2.0", - "statuses": "2.0.1", - "type-is": "~1.6.18", - "utils-merge": "1.0.1", - "vary": "~1.1.2" - }, - "engines": { - "node": ">= 0.10.0" - } - }, - "node_modules/express/node_modules/array-flatten": { - "version": "1.1.1", - "resolved": "https://registry.npmjs.org/array-flatten/-/array-flatten-1.1.1.tgz", - "integrity": "sha512-PCVAQswWemu6UdxsDFFX/+gVeYqKAod3D3UVm91jHwynguOwAvYPhx8nNlM++NqRcK6CxxpUafjmhIdKiHibqg==", - "dev": true - }, - "node_modules/extend": { - "version": "3.0.2", - "resolved": "https://registry.npmjs.org/extend/-/extend-3.0.2.tgz", - "integrity": "sha512-fjquC59cD7CyW6urNXK0FBufkZcoiGG80wTuPujX590cB5Ttln20E2UB4S/WARVqhXffZl2LNgS+gQdPIIim/g==", - "dev": true - }, - "node_modules/extract-zip": { - "version": "2.0.1", - "resolved": "https://registry.npmjs.org/extract-zip/-/extract-zip-2.0.1.tgz", - "integrity": "sha512-GDhU9ntwuKyGXdZBUgTIe+vXnWj0fppUEtMDL0+idd5Sta8TGpHssn/eusA9mrPr9qNDym6SxAYZjNvCn/9RBg==", - "dependencies": { - "debug": "^4.1.1", - "get-stream": "^5.1.0", - "yauzl": "^2.10.0" - }, - "bin": { - "extract-zip": "cli.js" - }, - "engines": { - "node": ">= 10.17.0" - }, - "optionalDependencies": { - "@types/yauzl": "^2.9.1" - } - }, - "node_modules/extract-zip/node_modules/debug": { - "version": "4.3.4", - "resolved": "https://registry.npmjs.org/debug/-/debug-4.3.4.tgz", - "integrity": "sha512-PRWFHuSU3eDtQJPvnNY7Jcket1j0t5OuOsFzPPzsekD52Zl8qUfFIPEiswXqIvHWGVHOgX+7G/vCNNhehwxfkQ==", - "dependencies": { - "ms": "2.1.2" - }, - "engines": { - "node": ">=6.0" - }, - "peerDependenciesMeta": { - "supports-color": { - "optional": true - } - } - }, - "node_modules/extract-zip/node_modules/get-stream": { - "version": "5.2.0", - "resolved": "https://registry.npmjs.org/get-stream/-/get-stream-5.2.0.tgz", - "integrity": "sha512-nBF+F1rAZVCu/p7rjzgA+Yb4lfYXrpl7a6VmJrU8wF9I1CKvP/QwPNZHnOlwbTkY6dvtFIzFMSyQXbLoTQPRpA==", - "dependencies": { - "pump": "^3.0.0" - }, - "engines": { - "node": ">=8" - }, - "funding": { - "url": "https://github.com/sponsors/sindresorhus" - } - }, - "node_modules/extract-zip/node_modules/ms": { - "version": "2.1.2", - "resolved": "https://registry.npmjs.org/ms/-/ms-2.1.2.tgz", - "integrity": "sha512-sGkPx+VjMtmA6MX27oA4FBFELFCZZ4S4XqeGOXCv68tT+jb3vk/RyaKWP0PTKyWtmLSM0b+adUTEvbs1PEaH2w==" - }, - "node_modules/fast-deep-equal": { - "version": "3.1.3", - "resolved": "https://registry.npmjs.org/fast-deep-equal/-/fast-deep-equal-3.1.3.tgz", - "integrity": "sha512-f3qQ9oQy9j2AhBe/H9VC91wLmKBCCU/gDOnKNAYG5hswO7BLKj09Hc5HYNz9cGI++xlpDCIgDaitVs03ATR84Q==" - }, - "node_modules/fast-glob": { - "version": "3.2.11", - "resolved": "https://registry.npmjs.org/fast-glob/-/fast-glob-3.2.11.tgz", - "integrity": "sha512-xrO3+1bxSo3ZVHAnqzyuewYT6aMFHRAd4Kcs92MAonjwQZLsK9d0SF1IyQ3k5PoirxTW0Oe/RqFgMQ6TcNE5Ew==", - "dev": true, - "dependencies": { - "@nodelib/fs.stat": "^2.0.2", - "@nodelib/fs.walk": "^1.2.3", - "glob-parent": "^5.1.2", - "merge2": "^1.3.0", - "micromatch": "^4.0.4" - }, - "engines": { - "node": ">=8.6.0" - } - }, - "node_modules/fast-json-stable-stringify": { - "version": "2.1.0", - "resolved": "https://registry.npmjs.org/fast-json-stable-stringify/-/fast-json-stable-stringify-2.1.0.tgz", - "integrity": "sha512-lhd/wF+Lk98HZoTCtlVraHtfh5XYijIjalXck7saUtuanSDyLMxnHhSXEDJqHxD7msR8D0uCmqlkwjCV8xvwHw==" - }, - "node_modules/fastest-levenshtein": { - "version": "1.0.14", - "resolved": "https://registry.npmjs.org/fastest-levenshtein/-/fastest-levenshtein-1.0.14.tgz", - "integrity": "sha512-tFfWHjnuUfKE186Tfgr+jtaFc0mZTApEgKDOeyN+FwOqRkO/zK/3h1AiRd8u8CY53owL3CUmGr/oI9p/RdyLTA==", - "dev": true, - "engines": { - "node": ">= 4.9.1" - } - }, - "node_modules/fastq": { - "version": "1.13.0", - "resolved": "https://registry.npmjs.org/fastq/-/fastq-1.13.0.tgz", - "integrity": "sha512-YpkpUnK8od0o1hmeSc7UUs/eB/vIPWJYjKck2QKIzAf71Vm1AAQ3EbuZB3g2JIy+pg+ERD0vqI79KyZiB2e2Nw==", - "dev": true, - "dependencies": { - "reusify": "^1.0.4" - } - }, - "node_modules/fault": { - "version": "1.0.4", - "resolved": "https://registry.npmjs.org/fault/-/fault-1.0.4.tgz", - "integrity": "sha512-CJ0HCB5tL5fYTEA7ToAq5+kTwd++Borf1/bifxd9iT70QcXr4MRrO3Llf8Ifs70q+SJcGHFtnIE/Nw6giCtECA==", - "dev": true, - "dependencies": { - "format": "^0.2.0" - }, - "funding": { - "type": "github", - "url": "https://github.com/sponsors/wooorm" - } - }, - "node_modules/faye-websocket": { - "version": "0.11.4", - "resolved": "https://registry.npmjs.org/faye-websocket/-/faye-websocket-0.11.4.tgz", - "integrity": "sha512-CzbClwlXAuiRQAlUyfqPgvPoNKTckTPGfwZV4ZdAhVcP2lh9KUxJg2b5GkE7XbjKQ3YJnQ9z6D9ntLAlB+tP8g==", - "dev": true, - "dependencies": { - "websocket-driver": ">=0.5.1" - }, - "engines": { - "node": ">=0.8.0" - } - }, - "node_modules/fd-slicer": { - "version": "1.1.0", - "resolved": "https://registry.npmjs.org/fd-slicer/-/fd-slicer-1.1.0.tgz", - "integrity": "sha512-cE1qsB/VwyQozZ+q1dGxR8LBYNZeofhEdUNGSMbQD3Gw2lAzX9Zb3uIU6Ebc/Fmyjo9AWWfnn0AUCHqtevs/8g==", - "dependencies": { - "pend": "~1.2.0" - } - }, - "node_modules/fill-range": { - "version": "7.0.1", - "resolved": "https://registry.npmjs.org/fill-range/-/fill-range-7.0.1.tgz", - "integrity": "sha512-qOo9F+dMUmC2Lcb4BbVvnKJxTPjCm+RRpe4gDuGrzkL7mEVl/djYSu2OdQ2Pa302N4oqkSg9ir6jaLWJ2USVpQ==", - "dev": true, - "dependencies": { - "to-regex-range": "^5.0.1" - }, - "engines": { - "node": ">=8" - } - }, - "node_modules/filter-obj": { - "version": "2.0.2", - "resolved": "https://registry.npmjs.org/filter-obj/-/filter-obj-2.0.2.tgz", - "integrity": "sha512-lO3ttPjHZRfjMcxWKb1j1eDhTFsu4meeR3lnMcnBFhk6RuLhvEiuALu2TlfL310ph4lCYYwgF/ElIjdP739tdg==", - "engines": { - "node": ">=8" - } - }, - "node_modules/finalhandler": { - "version": "1.2.0", - "resolved": "https://registry.npmjs.org/finalhandler/-/finalhandler-1.2.0.tgz", - "integrity": "sha512-5uXcUVftlQMFnWC9qu/svkWv3GTd2PfUhK/3PLkYNAe7FbqJMt3515HaxE6eRL74GdsriiwujiawdaB1BpEISg==", - "dev": true, - "dependencies": { - "debug": "2.6.9", - "encodeurl": "~1.0.2", - "escape-html": "~1.0.3", - "on-finished": "2.4.1", - "parseurl": "~1.3.3", - "statuses": "2.0.1", - "unpipe": "~1.0.0" - }, - "engines": { - "node": ">= 0.8" - } - }, - "node_modules/find-up": { - "version": "4.1.0", - "resolved": "https://registry.npmjs.org/find-up/-/find-up-4.1.0.tgz", - "integrity": "sha512-PpOwAdQ/YlXQ2vj8a3h8IipDuYRi3wceVQQGYWxNINccq40Anw7BlsEXCMbt1Zt+OLA6Fq9suIpIWD0OsnISlw==", - "dependencies": { - "locate-path": "^5.0.0", - "path-exists": "^4.0.0" - }, - "engines": { - "node": ">=8" - } - }, - "node_modules/follow-redirects": { - "version": "1.15.1", - "resolved": "https://registry.npmjs.org/follow-redirects/-/follow-redirects-1.15.1.tgz", - "integrity": "sha512-yLAMQs+k0b2m7cVxpS1VKJVvoz7SS9Td1zss3XRwXj+ZDH00RJgnuLx7E44wx02kQLrdM3aOOy+FpzS7+8OizA==", - "dev": true, - "funding": [ - { - "type": "individual", - "url": "https://github.com/sponsors/RubenVerborgh" - } - ], - "engines": { - "node": ">=4.0" - }, - "peerDependenciesMeta": { - "debug": { - "optional": true - } - } - }, - "node_modules/for-each": { - "version": "0.3.3", - "resolved": "https://registry.npmjs.org/for-each/-/for-each-0.3.3.tgz", - "integrity": "sha512-jqYfLp7mo9vIyQf8ykW2v7A+2N4QjeCeI5+Dz9XraiO1ign81wjiH7Fb9vSOWvQfNtmSa4H2RoQTrrXivdUZmw==", - "dependencies": { - "is-callable": "^1.1.3" - } - }, - "node_modules/format": { - "version": "0.2.2", - "resolved": "https://registry.npmjs.org/format/-/format-0.2.2.tgz", - "integrity": "sha512-wzsgA6WOq+09wrU1tsJ09udeR/YZRaeArL9e1wPbFg3GG2yDnC2ldKpxs4xunpFF9DgqCqOIra3bc1HWrJ37Ww==", - "dev": true, - "engines": { - "node": ">=0.4.x" - } - }, - "node_modules/forwarded": { - "version": "0.2.0", - "resolved": "https://registry.npmjs.org/forwarded/-/forwarded-0.2.0.tgz", - "integrity": "sha512-buRG0fpBtRHSTCOASe6hD258tEubFoRLb4ZNA6NxMVHNw2gOcwHo9wyablzMzOA5z9xA9L1KNjk/Nt6MT9aYow==", - "dev": true, - "engines": { - "node": ">= 0.6" - } - }, - "node_modules/fresh": { - "version": "0.5.2", - "resolved": "https://registry.npmjs.org/fresh/-/fresh-0.5.2.tgz", - "integrity": "sha512-zJ2mQYM18rEFOudeV4GShTGIQ7RbzA7ozbU9I/XBpm7kqgMywgmylMwXHxZJmkVoYkna9d2pVXVXPdYTP9ej8Q==", - "dev": true, - "engines": { - "node": ">= 0.6" - } - }, - "node_modules/fs-constants": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/fs-constants/-/fs-constants-1.0.0.tgz", - "integrity": "sha512-y6OAwoSIf7FyjMIv94u+b5rdheZEjzR63GTyZJm5qh4Bi+2YgwLCcI/fPFZkL5PSixOt6ZNKm+w+Hfp/Bciwow==" - }, - "node_modules/fs-monkey": { - "version": "1.0.3", - "resolved": "https://registry.npmjs.org/fs-monkey/-/fs-monkey-1.0.3.tgz", - "integrity": "sha512-cybjIfiiE+pTWicSCLFHSrXZ6EilF30oh91FDP9S2B051prEa7QWfrVTQm10/dDpswBDXZugPa1Ogu8Yh+HV0Q==", - "dev": true - }, - "node_modules/fs.realpath": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/fs.realpath/-/fs.realpath-1.0.0.tgz", - "integrity": "sha512-OO0pH2lK6a0hZnAdau5ItzHPI6pUlvI7jMVnxUQRtw4owF2wk8lOSabtGDCTP4Ggrg2MbGnWO9X8K1t4+fGMDw==" - }, - "node_modules/fsevents": { - "version": "2.3.2", - "resolved": "https://registry.npmjs.org/fsevents/-/fsevents-2.3.2.tgz", - "integrity": "sha512-xiqMQR4xAeHTuB9uWm+fFRcIOgKBMiOBP+eXiyT7jsgVCq1bkVygt00oASowB7EdtpOHaaPgKt812P9ab+DDKA==", - "dev": true, - "hasInstallScript": true, - "optional": true, - "os": [ - "darwin" - ], - "engines": { - "node": "^8.16.0 || ^10.6.0 || >=11.0.0" - } - }, - "node_modules/function-bind": { - "version": "1.1.1", - "resolved": "https://registry.npmjs.org/function-bind/-/function-bind-1.1.1.tgz", - "integrity": "sha512-yIovAzMX49sF8Yl58fSCWJ5svSLuaibPxXQJFLmBObTuCr0Mf1KiPopGM9NiFjiYBCbfaa2Fh6breQ6ANVTI0A==" - }, - "node_modules/function.prototype.name": { - "version": "1.1.5", - "resolved": "https://registry.npmjs.org/function.prototype.name/-/function.prototype.name-1.1.5.tgz", - "integrity": "sha512-uN7m/BzVKQnCUF/iW8jYea67v++2u7m5UgENbHRtdDVclOUP+FMPlCNdmk0h/ysGyo2tavMJEDqJAkJdRa1vMA==", - "dependencies": { - "call-bind": "^1.0.2", - "define-properties": "^1.1.3", - "es-abstract": "^1.19.0", - "functions-have-names": "^1.2.2" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/functions-have-names": { - "version": "1.2.3", - "resolved": "https://registry.npmjs.org/functions-have-names/-/functions-have-names-1.2.3.tgz", - "integrity": "sha512-xckBUXyTIqT97tq2x2AMb+g163b5JFysYk0x4qxNFwbfQkmNZoiRHb6sPzI9/QV33WeuvVYBUIiD4NzNIyqaRQ==", - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/get-intrinsic": { - "version": "1.1.1", - "resolved": "https://registry.npmjs.org/get-intrinsic/-/get-intrinsic-1.1.1.tgz", - "integrity": "sha512-kWZrnVM42QCiEA2Ig1bG8zjoIMOgxWwYCEeNdwY6Tv/cOSeGpcoX4pXHfKUxNKVoArnrEr2e9srnAxxGIraS9Q==", - "dependencies": { - "function-bind": "^1.1.1", - "has": "^1.0.3", - "has-symbols": "^1.0.1" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/get-stream": { - "version": "6.0.1", - "resolved": "https://registry.npmjs.org/get-stream/-/get-stream-6.0.1.tgz", - "integrity": "sha512-ts6Wi+2j3jQjqi70w5AlN8DFnkSwC+MqmxEzdEALB2qXZYV3X/b1CTfgPLGJNMeAWxdPfU8FO1ms3NUfaHCPYg==", - "dev": true, - "engines": { - "node": ">=10" - }, - "funding": { - "url": "https://github.com/sponsors/sindresorhus" - } - }, - "node_modules/get-symbol-description": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/get-symbol-description/-/get-symbol-description-1.0.0.tgz", - "integrity": "sha512-2EmdH1YvIQiZpltCNgkuiUnyukzxM/R6NDJX31Ke3BG1Nq5b0S2PhX59UKi9vZpPDQVdqn+1IcaAwnzTT5vCjw==", - "dependencies": { - "call-bind": "^1.0.2", - "get-intrinsic": "^1.1.1" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/glob": { - "version": "7.2.3", - "resolved": "https://registry.npmjs.org/glob/-/glob-7.2.3.tgz", - "integrity": "sha512-nFR0zLpU2YCaRxwoCJvL6UvCH2JFyFVIvwTLsIf21AuHlMskA1hhTdk+LlYJtOlYt9v6dvszD2BGRqBL+iQK9Q==", - "dependencies": { - "fs.realpath": "^1.0.0", - "inflight": "^1.0.4", - "inherits": "2", - "minimatch": "^3.1.1", - "once": "^1.3.0", - "path-is-absolute": "^1.0.0" - }, - "engines": { - "node": "*" - }, - "funding": { - "url": "https://github.com/sponsors/isaacs" - } - }, - "node_modules/glob-parent": { - "version": "5.1.2", - "resolved": "https://registry.npmjs.org/glob-parent/-/glob-parent-5.1.2.tgz", - "integrity": "sha512-AOIgSQCepiJYwP3ARnGx+5VnTu2HBYdzbGP45eLw1vr3zB3vZLeyed1sC9hnbcOc9/SrMyM5RPQrkGz4aS9Zow==", - "dev": true, - "dependencies": { - "is-glob": "^4.0.1" - }, - "engines": { - "node": ">= 6" - } - }, - "node_modules/glob-to-regexp": { - "version": "0.4.1", - "resolved": "https://registry.npmjs.org/glob-to-regexp/-/glob-to-regexp-0.4.1.tgz", - "integrity": "sha512-lkX1HJXwyMcprw/5YUZc2s7DrpAiHB21/V+E1rHUrVNokkvB6bqMzT0VfV6/86ZNabt1k14YOIaT7nDvOX3Iiw==" - }, - "node_modules/globby": { - "version": "11.1.0", - "resolved": "https://registry.npmjs.org/globby/-/globby-11.1.0.tgz", - "integrity": "sha512-jhIXaOzy1sb8IyocaruWSn1TjmnBVs8Ayhcy83rmxNJ8q2uWKCAj3CnJY+KpGSXCueAPc0i05kVvVKtP1t9S3g==", - "dev": true, - "dependencies": { - "array-union": "^2.1.0", - "dir-glob": "^3.0.1", - "fast-glob": "^3.2.9", - "ignore": "^5.2.0", - "merge2": "^1.4.1", - "slash": "^3.0.0" - }, - "engines": { - "node": ">=10" - }, - "funding": { - "url": "https://github.com/sponsors/sindresorhus" - } - }, - "node_modules/graceful-fs": { - "version": "4.2.10", - "resolved": "https://registry.npmjs.org/graceful-fs/-/graceful-fs-4.2.10.tgz", - "integrity": "sha512-9ByhssR2fPVsNZj478qUUbKfmL0+t5BDVyjShtyZZLiK7ZDAArFFfopyOTj0M05wE2tJPisA4iTnnXl2YoPvOA==" - }, - "node_modules/handle-thing": { - "version": "2.0.1", - "resolved": "https://registry.npmjs.org/handle-thing/-/handle-thing-2.0.1.tgz", - "integrity": "sha512-9Qn4yBxelxoh2Ow62nP+Ka/kMnOXRi8BXnRaUwezLNhqelnN49xKz4F/dPP8OYLxLxq6JDtZb2i9XznUQbNPTg==", - "dev": true - }, - "node_modules/has": { - "version": "1.0.3", - "resolved": "https://registry.npmjs.org/has/-/has-1.0.3.tgz", - "integrity": "sha512-f2dvO0VU6Oej7RkWJGrehjbzMAjFp5/VKPp5tTpWIV4JHHZK1/BxbFRtf/siA2SWTe09caDmVtYYzWEIbBS4zw==", - "dependencies": { - "function-bind": "^1.1.1" - }, - "engines": { - "node": ">= 0.4.0" - } - }, - "node_modules/has-bigints": { - "version": "1.0.2", - "resolved": "https://registry.npmjs.org/has-bigints/-/has-bigints-1.0.2.tgz", - "integrity": "sha512-tSvCKtBr9lkF0Ex0aQiP9N+OpV4zi2r/Nee5VkRDbaqv35RLYMzbwQfFSZZH0kR+Rd6302UJZ2p/bJCEoR3VoQ==", - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/has-flag": { - "version": "4.0.0", - "resolved": "https://registry.npmjs.org/has-flag/-/has-flag-4.0.0.tgz", - "integrity": "sha512-EykJT/Q1KjTWctppgIAgfSO0tKVuZUjhgMr17kqTumMl6Afv3EISleU7qZUzoXDFTAHTDC4NOoG/ZxU3EvlMPQ==", - "engines": { - "node": ">=8" - } - }, - "node_modules/has-property-descriptors": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/has-property-descriptors/-/has-property-descriptors-1.0.0.tgz", - "integrity": "sha512-62DVLZGoiEBDHQyqG4w9xCuZ7eJEwNmJRWw2VY84Oedb7WFcA27fiEVe8oUQx9hAUJ4ekurquucTGwsyO1XGdQ==", - "dependencies": { - "get-intrinsic": "^1.1.1" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/has-symbols": { - "version": "1.0.3", - "resolved": "https://registry.npmjs.org/has-symbols/-/has-symbols-1.0.3.tgz", - "integrity": "sha512-l3LCuF6MgDNwTDKkdYGEihYjt5pRPbEg46rtlmnSPlUbgmB8LOIrKJbYYFBSbnPaJexMKtiPO8hmeRjRz2Td+A==", - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/has-tostringtag": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/has-tostringtag/-/has-tostringtag-1.0.0.tgz", - "integrity": "sha512-kFjcSNhnlGV1kyoGk7OXKSawH5JOb/LzUc5w9B02hOTO0dfFRjbHQKvg1d6cf3HbeUmtU9VbbV3qzZ2Teh97WQ==", - "dependencies": { - "has-symbols": "^1.0.2" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/hash-base": { - "version": "3.1.0", - "resolved": "https://registry.npmjs.org/hash-base/-/hash-base-3.1.0.tgz", - "integrity": "sha512-1nmYp/rhMDiE7AYkDw+lLwlAzz0AntGIe51F3RfFfEqyQ3feY2eI/NcwC6umIQVOASPMsWJLJScWKSSvzL9IVA==", - "dependencies": { - "inherits": "^2.0.4", - "readable-stream": "^3.6.0", - "safe-buffer": "^5.2.0" - }, - "engines": { - "node": ">=4" - } - }, - "node_modules/hash.js": { - "version": "1.1.7", - "resolved": "https://registry.npmjs.org/hash.js/-/hash.js-1.1.7.tgz", - "integrity": "sha512-taOaskGt4z4SOANNseOviYDvjEJinIkRgmp7LbKP2YTTmVxWBl87s/uzK9r+44BclBSp2X7K1hqeNfz9JbBeXA==", - "dependencies": { - "inherits": "^2.0.3", - "minimalistic-assert": "^1.0.1" - } - }, - "node_modules/he": { - "version": "1.2.0", - "resolved": "https://registry.npmjs.org/he/-/he-1.2.0.tgz", - "integrity": "sha512-F/1DnUGPopORZi0ni+CvrCgHQ5FyEAHRLSApuYWMmrbSwoN2Mn/7k+Gl38gJnR7yyDZk6WLXwiGod1JOWNDKGw==", - "dev": true, - "bin": { - "he": "bin/he" - } - }, - "node_modules/hmac-drbg": { - "version": "1.0.1", - "resolved": "https://registry.npmjs.org/hmac-drbg/-/hmac-drbg-1.0.1.tgz", - "integrity": "sha512-Tti3gMqLdZfhOQY1Mzf/AanLiqh1WTiJgEj26ZuYQ9fbkLomzGchCws4FyrSd4VkpBfiNhaE1On+lOz894jvXg==", - "dependencies": { - "hash.js": "^1.0.3", - "minimalistic-assert": "^1.0.0", - "minimalistic-crypto-utils": "^1.0.1" - } - }, - "node_modules/hpack.js": { - "version": "2.1.6", - "resolved": "https://registry.npmjs.org/hpack.js/-/hpack.js-2.1.6.tgz", - "integrity": "sha512-zJxVehUdMGIKsRaNt7apO2Gqp0BdqW5yaiGHXXmbpvxgBYVZnAql+BJb4RO5ad2MgpbZKn5G6nMnegrH1FcNYQ==", - "dev": true, - "dependencies": { - "inherits": "^2.0.1", - "obuf": "^1.0.0", - "readable-stream": "^2.0.1", - "wbuf": "^1.1.0" - } - }, - "node_modules/hpack.js/node_modules/readable-stream": { - "version": "2.3.7", - "resolved": "https://registry.npmjs.org/readable-stream/-/readable-stream-2.3.7.tgz", - "integrity": "sha512-Ebho8K4jIbHAxnuxi7o42OrZgF/ZTNcsZj6nRKyUmkhLFq8CHItp/fy6hQZuZmP/n3yZ9VBUbp4zz/mX8hmYPw==", - "dev": true, - "dependencies": { - "core-util-is": "~1.0.0", - "inherits": "~2.0.3", - "isarray": "~1.0.0", - "process-nextick-args": "~2.0.0", - "safe-buffer": "~5.1.1", - "string_decoder": "~1.1.1", - "util-deprecate": "~1.0.1" - } - }, - "node_modules/hpack.js/node_modules/safe-buffer": { - "version": "5.1.2", - "resolved": "https://registry.npmjs.org/safe-buffer/-/safe-buffer-5.1.2.tgz", - "integrity": "sha512-Gd2UZBJDkXlY7GbJxfsE8/nvKkUEU1G38c1siN6QP6a9PT9MmHB8GnpscSmMJSoF8LOIrt8ud/wPtojys4G6+g==", - "dev": true - }, - "node_modules/hpack.js/node_modules/string_decoder": { - "version": "1.1.1", - "resolved": "https://registry.npmjs.org/string_decoder/-/string_decoder-1.1.1.tgz", - "integrity": "sha512-n/ShnvDi6FHbbVfviro+WojiFzv+s8MPMHBczVePfUpDJLwoLT0ht1l4YwBCbi8pJAveEEdnkHyPyTP/mzRfwg==", - "dev": true, - "dependencies": { - "safe-buffer": "~5.1.0" - } - }, - "node_modules/html-entities": { - "version": "2.3.3", - "resolved": "https://registry.npmjs.org/html-entities/-/html-entities-2.3.3.tgz", - "integrity": "sha512-DV5Ln36z34NNTDgnz0EWGBLZENelNAtkiFA4kyNOG2tDI6Mz1uSWiq1wAKdyjnJwyDiDO7Fa2SO1CTxPXL8VxA==", - "dev": true - }, - "node_modules/html-minifier-terser": { - "version": "6.1.0", - "resolved": "https://registry.npmjs.org/html-minifier-terser/-/html-minifier-terser-6.1.0.tgz", - "integrity": "sha512-YXxSlJBZTP7RS3tWnQw74ooKa6L9b9i9QYXY21eUEvhZ3u9XLfv6OnFsQq6RxkhHygsaUMvYsZRV5rU/OVNZxw==", - "dev": true, - "dependencies": { - "camel-case": "^4.1.2", - "clean-css": "^5.2.2", - "commander": "^8.3.0", - "he": "^1.2.0", - "param-case": "^3.0.4", - "relateurl": "^0.2.7", - "terser": "^5.10.0" - }, - "bin": { - "html-minifier-terser": "cli.js" - }, - "engines": { - "node": ">=12" - } - }, - "node_modules/html-webpack-plugin": { - "version": "5.5.0", - "resolved": "https://registry.npmjs.org/html-webpack-plugin/-/html-webpack-plugin-5.5.0.tgz", - "integrity": "sha512-sy88PC2cRTVxvETRgUHFrL4No3UxvcH8G1NepGhqaTT+GXN2kTamqasot0inS5hXeg1cMbFDt27zzo9p35lZVw==", - "dev": true, - "dependencies": { - "@types/html-minifier-terser": "^6.0.0", - "html-minifier-terser": "^6.0.2", - "lodash": "^4.17.21", - "pretty-error": "^4.0.0", - "tapable": "^2.0.0" - }, - "engines": { - "node": ">=10.13.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/html-webpack-plugin" - }, - "peerDependencies": { - "webpack": "^5.20.0" - } - }, - "node_modules/htmlparser2": { - "version": "6.1.0", - "resolved": "https://registry.npmjs.org/htmlparser2/-/htmlparser2-6.1.0.tgz", - "integrity": "sha512-gyyPk6rgonLFEDGoeRgQNaEUvdJ4ktTmmUh/h2t7s+M8oPpIPxgNACWa+6ESR57kXstwqPiCut0V8NRpcwgU7A==", - "dev": true, - "funding": [ - "https://github.com/fb55/htmlparser2?sponsor=1", - { - "type": "github", - "url": "https://github.com/sponsors/fb55" - } - ], - "dependencies": { - "domelementtype": "^2.0.1", - "domhandler": "^4.0.0", - "domutils": "^2.5.2", - "entities": "^2.0.0" - } - }, - "node_modules/http-deceiver": { - "version": "1.2.7", - "resolved": "https://registry.npmjs.org/http-deceiver/-/http-deceiver-1.2.7.tgz", - "integrity": "sha512-LmpOGxTfbpgtGVxJrj5k7asXHCgNZp5nLfp+hWc8QQRqtb7fUy6kRY3BO1h9ddF6yIPYUARgxGOwB42DnxIaNw==", - "dev": true - }, - "node_modules/http-errors": { - "version": "2.0.0", - "resolved": "https://registry.npmjs.org/http-errors/-/http-errors-2.0.0.tgz", - "integrity": "sha512-FtwrG/euBzaEjYeRqOgly7G0qviiXoJWnvEH2Z1plBdXgbyjv34pHTSb9zoeHMyDy33+DWy5Wt9Wo+TURtOYSQ==", - "dev": true, - "dependencies": { - "depd": "2.0.0", - "inherits": "2.0.4", - "setprototypeof": "1.2.0", - "statuses": "2.0.1", - "toidentifier": "1.0.1" - }, - "engines": { - "node": ">= 0.8" - } - }, - "node_modules/http-parser-js": { - "version": "0.5.6", - "resolved": "https://registry.npmjs.org/http-parser-js/-/http-parser-js-0.5.6.tgz", - "integrity": "sha512-vDlkRPDJn93swjcjqMSaGSPABbIarsr1TLAui/gLDXzV5VsJNdXNzMYDyNBLQkjWQCJ1uizu8T2oDMhmGt0PRA==", - "dev": true - }, - "node_modules/http-proxy": { - "version": "1.18.1", - "resolved": "https://registry.npmjs.org/http-proxy/-/http-proxy-1.18.1.tgz", - "integrity": "sha512-7mz/721AbnJwIVbnaSv1Cz3Am0ZLT/UBwkC92VlxhXv/k/BBQfM2fXElQNC27BVGr0uwUpplYPQM9LnaBMR5NQ==", - "dev": true, - "dependencies": { - "eventemitter3": "^4.0.0", - "follow-redirects": "^1.0.0", - "requires-port": "^1.0.0" - }, - "engines": { - "node": ">=8.0.0" - } - }, - "node_modules/http-proxy-middleware": { - "version": "2.0.6", - "resolved": "https://registry.npmjs.org/http-proxy-middleware/-/http-proxy-middleware-2.0.6.tgz", - "integrity": "sha512-ya/UeJ6HVBYxrgYotAZo1KvPWlgB48kUJLDePFeneHsVujFaW5WNj2NgWCAE//B1Dl02BIfYlpNgBy8Kf8Rjmw==", - "dev": true, - "dependencies": { - "@types/http-proxy": "^1.17.8", - "http-proxy": "^1.18.1", - "is-glob": "^4.0.1", - "is-plain-obj": "^3.0.0", - "micromatch": "^4.0.2" - }, - "engines": { - "node": ">=12.0.0" - }, - "peerDependencies": { - "@types/express": "^4.17.13" - }, - "peerDependenciesMeta": { - "@types/express": { - "optional": true - } - } - }, - "node_modules/https-browserify": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/https-browserify/-/https-browserify-1.0.0.tgz", - "integrity": "sha512-J+FkSdyD+0mA0N+81tMotaRMfSL9SGi+xpD3T6YApKsc3bGSXJlfXri3VyFOeYkfLRQisDk1W+jIFFKBeUBbBg==" - }, - "node_modules/https-proxy-agent": { - "version": "5.0.1", - "resolved": "https://registry.npmjs.org/https-proxy-agent/-/https-proxy-agent-5.0.1.tgz", - "integrity": "sha512-dFcAjpTQFgoLMzC2VwU+C/CbS7uRL0lWmxDITmqm7C+7F0Odmj6s9l6alZc6AELXhrnggM2CeWSXHGOdX2YtwA==", - "dependencies": { - "agent-base": "6", - "debug": "4" - }, - "engines": { - "node": ">= 6" - } - }, - "node_modules/https-proxy-agent/node_modules/debug": { - "version": "4.3.4", - "resolved": "https://registry.npmjs.org/debug/-/debug-4.3.4.tgz", - "integrity": "sha512-PRWFHuSU3eDtQJPvnNY7Jcket1j0t5OuOsFzPPzsekD52Zl8qUfFIPEiswXqIvHWGVHOgX+7G/vCNNhehwxfkQ==", - "dependencies": { - "ms": "2.1.2" - }, - "engines": { - "node": ">=6.0" - }, - "peerDependenciesMeta": { - "supports-color": { - "optional": true - } - } - }, - "node_modules/https-proxy-agent/node_modules/ms": { - "version": "2.1.2", - "resolved": "https://registry.npmjs.org/ms/-/ms-2.1.2.tgz", - "integrity": "sha512-sGkPx+VjMtmA6MX27oA4FBFELFCZZ4S4XqeGOXCv68tT+jb3vk/RyaKWP0PTKyWtmLSM0b+adUTEvbs1PEaH2w==" - }, - "node_modules/human-signals": { - "version": "2.1.0", - "resolved": "https://registry.npmjs.org/human-signals/-/human-signals-2.1.0.tgz", - "integrity": "sha512-B4FFZ6q/T2jhhksgkbEW3HBvWIfDW85snkQgawt07S7J5QXTk6BkNV+0yAeZrM5QpMAdYlocGoljn0sJ/WQkFw==", - "dev": true, - "engines": { - "node": ">=10.17.0" - } - }, - "node_modules/iconv-lite": { - "version": "0.4.24", - "resolved": "https://registry.npmjs.org/iconv-lite/-/iconv-lite-0.4.24.tgz", - "integrity": "sha512-v3MXnZAcvnywkTUEZomIActle7RXXeedOR31wwl7VlyoXO4Qi9arvSenNQWne1TcRwhCL1HwLI21bEqdpj8/rA==", - "dev": true, - "dependencies": { - "safer-buffer": ">= 2.1.2 < 3" - }, - "engines": { - "node": ">=0.10.0" - } - }, - "node_modules/ieee754": { - "version": "1.2.1", - "resolved": "https://registry.npmjs.org/ieee754/-/ieee754-1.2.1.tgz", - "integrity": "sha512-dcyqhDvX1C46lXZcVqCpK+FtMRQVdIMN6/Df5js2zouUsqG7I6sFxitIC+7KYK29KdXOLHdu9zL4sFnoVQnqaA==", - "funding": [ - { - "type": "github", - "url": "https://github.com/sponsors/feross" - }, - { - "type": "patreon", - "url": "https://www.patreon.com/feross" - }, - { - "type": "consulting", - "url": "https://feross.org/support" - } - ] - }, - "node_modules/ignore": { - "version": "5.2.0", - "resolved": "https://registry.npmjs.org/ignore/-/ignore-5.2.0.tgz", - "integrity": "sha512-CmxgYGiEPCLhfLnpPp1MoRmifwEIOgjcHXxOBjv7mY96c+eWScsOP9c112ZyLdWHi0FxHjI+4uVhKYp/gcdRmQ==", - "dev": true, - "engines": { - "node": ">= 4" - } - }, - "node_modules/import-local": { - "version": "3.1.0", - "resolved": "https://registry.npmjs.org/import-local/-/import-local-3.1.0.tgz", - "integrity": "sha512-ASB07uLtnDs1o6EHjKpX34BKYDSqnFerfTOJL2HvMqF70LnxpjkzDB8J44oT9pu4AMPkQwf8jl6szgvNd2tRIg==", - "dev": true, - "dependencies": { - "pkg-dir": "^4.2.0", - "resolve-cwd": "^3.0.0" - }, - "bin": { - "import-local-fixture": "fixtures/cli.js" - }, - "engines": { - "node": ">=8" - }, - "funding": { - "url": "https://github.com/sponsors/sindresorhus" - } - }, - "node_modules/indent-string": { - "version": "4.0.0", - "resolved": "https://registry.npmjs.org/indent-string/-/indent-string-4.0.0.tgz", - "integrity": "sha512-EdDDZu4A2OyIK7Lr/2zG+w5jmbuk1DVBnEwREQvBzspBJkCEbRa8GxU1lghYcaGJCnRWibjDXlq779X1/y5xwg==", - "dev": true, - "engines": { - "node": ">=8" - } - }, - "node_modules/inflight": { - "version": "1.0.6", - "resolved": "https://registry.npmjs.org/inflight/-/inflight-1.0.6.tgz", - "integrity": "sha512-k92I/b08q4wvFscXCLvqfsHCrjrF7yiXsQuIVvVE7N82W3+aqpzuUdBbfhWcy/FZR3/4IgflMgKLOsvPDrGCJA==", - "dependencies": { - "once": "^1.3.0", - "wrappy": "1" - } - }, - "node_modules/inherits": { - "version": "2.0.4", - "resolved": "https://registry.npmjs.org/inherits/-/inherits-2.0.4.tgz", - "integrity": "sha512-k/vGaX4/Yla3WzyMCvTQOXYeIHvqOKtnqBduzTHpzpQZzAskKMhZ2K+EnBiSM9zGSoIFeMpXKxa4dYeZIQqewQ==" - }, - "node_modules/internal-slot": { - "version": "1.0.3", - "resolved": "https://registry.npmjs.org/internal-slot/-/internal-slot-1.0.3.tgz", - "integrity": "sha512-O0DB1JC/sPyZl7cIo78n5dR7eUSwwpYPiXRhTzNxZVAMUuB8vlnRFyLxdrVToks6XPLVnFfbzaVd5WLjhgg+vA==", - "dependencies": { - "get-intrinsic": "^1.1.0", - "has": "^1.0.3", - "side-channel": "^1.0.4" - }, - "engines": { - "node": ">= 0.4" - } - }, - "node_modules/interpret": { - "version": "2.2.0", - "resolved": "https://registry.npmjs.org/interpret/-/interpret-2.2.0.tgz", - "integrity": "sha512-Ju0Bz/cEia55xDwUWEa8+olFpCiQoypjnQySseKtmjNrnps3P+xfpUmGr90T7yjlVJmOtybRvPXhKMbHr+fWnw==", - "dev": true, - "engines": { - "node": ">= 0.10" - } - }, - "node_modules/ip": { - "version": "1.1.8", - "resolved": "https://registry.npmjs.org/ip/-/ip-1.1.8.tgz", - "integrity": "sha512-PuExPYUiu6qMBQb4l06ecm6T6ujzhmh+MeJcW9wa89PoAz5pvd4zPgN5WJV104mb6S2T1AwNIAaB70JNrLQWhg==", - "dev": true - }, - "node_modules/ipaddr.js": { - "version": "2.0.1", - "resolved": "https://registry.npmjs.org/ipaddr.js/-/ipaddr.js-2.0.1.tgz", - "integrity": "sha512-1qTgH9NG+IIJ4yfKs2e6Pp1bZg8wbDbKHT21HrLIeYBTRLgMYKnMTPAuI3Lcs61nfx5h1xlXnbJtH1kX5/d/ng==", - "dev": true, - "engines": { - "node": ">= 10" - } - }, - "node_modules/is-alphabetical": { - "version": "1.0.4", - "resolved": "https://registry.npmjs.org/is-alphabetical/-/is-alphabetical-1.0.4.tgz", - "integrity": "sha512-DwzsA04LQ10FHTZuL0/grVDk4rFoVH1pjAToYwBrHSxcrBIGQuXrQMtD5U1b0U2XVgKZCTLLP8u2Qxqhy3l2Vg==", - "dev": true, - "funding": { - "type": "github", - "url": "https://github.com/sponsors/wooorm" - } - }, - "node_modules/is-alphanumerical": { - "version": "1.0.4", - "resolved": "https://registry.npmjs.org/is-alphanumerical/-/is-alphanumerical-1.0.4.tgz", - "integrity": "sha512-UzoZUr+XfVz3t3v4KyGEniVL9BDRoQtY7tOyrRybkVNjDFWyo1yhXNGrrBTQxp3ib9BLAWs7k2YKBQsFRkZG9A==", - "dev": true, - "dependencies": { - "is-alphabetical": "^1.0.0", - "is-decimal": "^1.0.0" - }, - "funding": { - "type": "github", - "url": "https://github.com/sponsors/wooorm" - } - }, - "node_modules/is-arguments": { - "version": "1.1.1", - "resolved": "https://registry.npmjs.org/is-arguments/-/is-arguments-1.1.1.tgz", - "integrity": "sha512-8Q7EARjzEnKpt/PCD7e1cgUS0a6X8u5tdSiMqXhojOdoV9TsMsiO+9VLC5vAmO8N7/GmXn7yjR8qnA6bVAEzfA==", - "dependencies": { - "call-bind": "^1.0.2", - "has-tostringtag": "^1.0.0" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/is-bigint": { - "version": "1.0.4", - "resolved": "https://registry.npmjs.org/is-bigint/-/is-bigint-1.0.4.tgz", - "integrity": "sha512-zB9CruMamjym81i2JZ3UMn54PKGsQzsJeo6xvN3HJJ4CAsQNB6iRutp2To77OfCNuoxspsIhzaPoO1zyCEhFOg==", - "dependencies": { - "has-bigints": "^1.0.1" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/is-binary-path": { - "version": "2.1.0", - "resolved": "https://registry.npmjs.org/is-binary-path/-/is-binary-path-2.1.0.tgz", - "integrity": "sha512-ZMERYes6pDydyuGidse7OsHxtbI7WVeUEozgR/g7rd0xUimYNlvZRE/K2MgZTjWy725IfelLeVcEM97mmtRGXw==", - "dev": true, - "dependencies": { - "binary-extensions": "^2.0.0" - }, - "engines": { - "node": ">=8" - } - }, - "node_modules/is-boolean-object": { - "version": "1.1.2", - "resolved": "https://registry.npmjs.org/is-boolean-object/-/is-boolean-object-1.1.2.tgz", - "integrity": "sha512-gDYaKHJmnj4aWxyj6YHyXVpdQawtVLHU5cb+eztPGczf6cjuTdwve5ZIEfgXqH4e57An1D1AKf8CZ3kYrQRqYA==", - "dependencies": { - "call-bind": "^1.0.2", - "has-tostringtag": "^1.0.0" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/is-buffer": { - "version": "2.0.5", - "resolved": "https://registry.npmjs.org/is-buffer/-/is-buffer-2.0.5.tgz", - "integrity": "sha512-i2R6zNFDwgEHJyQUtJEk0XFi1i0dPFn/oqjK3/vPCcDeJvW5NQ83V8QbicfF1SupOaB0h8ntgBC2YiE7dfyctQ==", - "dev": true, - "funding": [ - { - "type": "github", - "url": "https://github.com/sponsors/feross" - }, - { - "type": "patreon", - "url": "https://www.patreon.com/feross" - }, - { - "type": "consulting", - "url": "https://feross.org/support" - } - ], - "engines": { - "node": ">=4" - } - }, - "node_modules/is-callable": { - "version": "1.2.4", - "resolved": "https://registry.npmjs.org/is-callable/-/is-callable-1.2.4.tgz", - "integrity": "sha512-nsuwtxZfMX67Oryl9LCQ+upnC0Z0BgpwntpS89m1H/TLF0zNfzfLMV/9Wa/6MZsj0acpEjAO0KF1xT6ZdLl95w==", - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/is-core-module": { - "version": "2.9.0", - "resolved": "https://registry.npmjs.org/is-core-module/-/is-core-module-2.9.0.tgz", - "integrity": "sha512-+5FPy5PnwmO3lvfMb0AsoPaBG+5KHUI0wYFXOtYPnVVVspTFUuMZNfNaNVRt3FZadstu2c8x23vykRW/NBoU6A==", - "dev": true, - "dependencies": { - "has": "^1.0.3" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/is-date-object": { - "version": "1.0.5", - "resolved": "https://registry.npmjs.org/is-date-object/-/is-date-object-1.0.5.tgz", - "integrity": "sha512-9YQaSxsAiSwcvS33MBk3wTCVnWK+HhF8VZR2jRxehM16QcVOdHqPn4VPHmRK4lSr38n9JriurInLcP90xsYNfQ==", - "dependencies": { - "has-tostringtag": "^1.0.0" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/is-decimal": { - "version": "1.0.4", - "resolved": "https://registry.npmjs.org/is-decimal/-/is-decimal-1.0.4.tgz", - "integrity": "sha512-RGdriMmQQvZ2aqaQq3awNA6dCGtKpiDFcOzrTWrDAT2MiWrKQVPmxLGHl7Y2nNu6led0kEyoX0enY0qXYsv9zw==", - "dev": true, - "funding": { - "type": "github", - "url": "https://github.com/sponsors/wooorm" - } - }, - "node_modules/is-docker": { - "version": "2.2.1", - "resolved": "https://registry.npmjs.org/is-docker/-/is-docker-2.2.1.tgz", - "integrity": "sha512-F+i2BKsFrH66iaUFc0woD8sLy8getkwTwtOBjvs56Cx4CgJDeKQeqfz8wAYiSb8JOprWhHH5p77PbmYCvvUuXQ==", - "dev": true, - "bin": { - "is-docker": "cli.js" - }, - "engines": { - "node": ">=8" - }, - "funding": { - "url": "https://github.com/sponsors/sindresorhus" - } - }, - "node_modules/is-extglob": { - "version": "2.1.1", - "resolved": "https://registry.npmjs.org/is-extglob/-/is-extglob-2.1.1.tgz", - "integrity": "sha512-SbKbANkN603Vi4jEZv49LeVJMn4yGwsbzZworEoyEiutsN3nJYdbO36zfhGJ6QEDpOZIFkDtnq5JRxmvl3jsoQ==", - "dev": true, - "engines": { - "node": ">=0.10.0" - } - }, - "node_modules/is-generator-function": { - "version": "1.0.10", - "resolved": "https://registry.npmjs.org/is-generator-function/-/is-generator-function-1.0.10.tgz", - "integrity": "sha512-jsEjy9l3yiXEQ+PsXdmBwEPcOxaXWLspKdplFUVI9vq1iZgIekeC0L167qeu86czQaxed3q/Uzuw0swL0irL8A==", - "dependencies": { - "has-tostringtag": "^1.0.0" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/is-glob": { - "version": "4.0.3", - "resolved": "https://registry.npmjs.org/is-glob/-/is-glob-4.0.3.tgz", - "integrity": "sha512-xelSayHH36ZgE7ZWhli7pW34hNbNl8Ojv5KVmkJD4hBdD3th8Tfk9vYasLM+mXWOZhFkgZfxhLSnrwRr4elSSg==", - "dev": true, - "dependencies": { - "is-extglob": "^2.1.1" - }, - "engines": { - "node": ">=0.10.0" - } - }, - "node_modules/is-hexadecimal": { - "version": "1.0.4", - "resolved": "https://registry.npmjs.org/is-hexadecimal/-/is-hexadecimal-1.0.4.tgz", - "integrity": "sha512-gyPJuv83bHMpocVYoqof5VDiZveEoGoFL8m3BXNb2VW8Xs+rz9kqO8LOQ5DH6EsuvilT1ApazU0pyl+ytbPtlw==", - "dev": true, - "funding": { - "type": "github", - "url": "https://github.com/sponsors/wooorm" - } - }, - "node_modules/is-nan": { - "version": "1.3.2", - "resolved": "https://registry.npmjs.org/is-nan/-/is-nan-1.3.2.tgz", - "integrity": "sha512-E+zBKpQ2t6MEo1VsonYmluk9NxGrbzpeeLC2xIViuO2EjU2xsXsBPwTr3Ykv9l08UYEVEdWeRZNouaZqF6RN0w==", - "dependencies": { - "call-bind": "^1.0.0", - "define-properties": "^1.1.3" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/is-negative-zero": { - "version": "2.0.2", - "resolved": "https://registry.npmjs.org/is-negative-zero/-/is-negative-zero-2.0.2.tgz", - "integrity": "sha512-dqJvarLawXsFbNDeJW7zAz8ItJ9cd28YufuuFzh0G8pNHjJMnY08Dv7sYX2uF5UpQOwieAeOExEYAWWfu7ZZUA==", - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/is-number": { - "version": "7.0.0", - "resolved": "https://registry.npmjs.org/is-number/-/is-number-7.0.0.tgz", - "integrity": "sha512-41Cifkg6e8TylSpdtTpeLVMqvSBEVzTttHvERD741+pnZ8ANv0004MRL43QKPDlK9cGvNp6NZWZUBlbGXYxxng==", - "dev": true, - "engines": { - "node": ">=0.12.0" - } - }, - "node_modules/is-number-object": { - "version": "1.0.7", - "resolved": "https://registry.npmjs.org/is-number-object/-/is-number-object-1.0.7.tgz", - "integrity": "sha512-k1U0IRzLMo7ZlYIfzRu23Oh6MiIFasgpb9X76eqfFZAqwH44UI4KTBvBYIZ1dSL9ZzChTB9ShHfLkR4pdW5krQ==", - "dependencies": { - "has-tostringtag": "^1.0.0" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/is-path-cwd": { - "version": "2.2.0", - "resolved": "https://registry.npmjs.org/is-path-cwd/-/is-path-cwd-2.2.0.tgz", - "integrity": "sha512-w942bTcih8fdJPJmQHFzkS76NEP8Kzzvmw92cXsazb8intwLqPibPPdXf4ANdKV3rYMuuQYGIWtvz9JilB3NFQ==", - "dev": true, - "engines": { - "node": ">=6" - } - }, - "node_modules/is-path-inside": { - "version": "3.0.3", - "resolved": "https://registry.npmjs.org/is-path-inside/-/is-path-inside-3.0.3.tgz", - "integrity": "sha512-Fd4gABb+ycGAmKou8eMftCupSir5lRxqf4aD/vd0cD2qc4HL07OjCeuHMr8Ro4CoMaeCKDB0/ECBOVWjTwUvPQ==", - "dev": true, - "engines": { - "node": ">=8" - } - }, - "node_modules/is-plain-obj": { - "version": "3.0.0", - "resolved": "https://registry.npmjs.org/is-plain-obj/-/is-plain-obj-3.0.0.tgz", - "integrity": "sha512-gwsOE28k+23GP1B6vFl1oVh/WOzmawBrKwo5Ev6wMKzPkaXaCDIQKzLnvsA42DRlbVTWorkgTKIviAKCWkfUwA==", - "dev": true, - "engines": { - "node": ">=10" - }, - "funding": { - "url": "https://github.com/sponsors/sindresorhus" - } - }, - "node_modules/is-plain-object": { - "version": "2.0.4", - "resolved": "https://registry.npmjs.org/is-plain-object/-/is-plain-object-2.0.4.tgz", - "integrity": "sha512-h5PpgXkWitc38BBMYawTYMWJHFZJVnBquFE57xFpjB8pJFiF6gZ+bU+WyI/yqXiFR5mdLsgYNaPe8uao6Uv9Og==", - "dev": true, - "dependencies": { - "isobject": "^3.0.1" - }, - "engines": { - "node": ">=0.10.0" - } - }, - "node_modules/is-regex": { - "version": "1.1.4", - "resolved": "https://registry.npmjs.org/is-regex/-/is-regex-1.1.4.tgz", - "integrity": "sha512-kvRdxDsxZjhzUX07ZnLydzS1TU/TJlTUHHY4YLL87e37oUA49DfkLqgy+VjFocowy29cKvcSiu+kIv728jTTVg==", - "dependencies": { - "call-bind": "^1.0.2", - "has-tostringtag": "^1.0.0" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/is-shared-array-buffer": { - "version": "1.0.2", - "resolved": "https://registry.npmjs.org/is-shared-array-buffer/-/is-shared-array-buffer-1.0.2.tgz", - "integrity": "sha512-sqN2UDu1/0y6uvXyStCOzyhAjCSlHceFoMKJW8W9EU9cvic/QdsZ0kEU93HEy3IUEFZIiH/3w+AH/UQbPHNdhA==", - "dependencies": { - "call-bind": "^1.0.2" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/is-stream": { - "version": "2.0.1", - "resolved": "https://registry.npmjs.org/is-stream/-/is-stream-2.0.1.tgz", - "integrity": "sha512-hFoiJiTl63nn+kstHGBtewWSKnQLpyb155KHheA1l39uvtO9nWIop1p3udqPcUd/xbF1VLMO4n7OI6p7RbngDg==", - "dev": true, - "engines": { - "node": ">=8" - }, - "funding": { - "url": "https://github.com/sponsors/sindresorhus" - } - }, - "node_modules/is-string": { - "version": "1.0.7", - "resolved": "https://registry.npmjs.org/is-string/-/is-string-1.0.7.tgz", - "integrity": "sha512-tE2UXzivje6ofPW7l23cjDOMa09gb7xlAqG6jG5ej6uPV32TlWP3NKPigtaGeHNu9fohccRYvIiZMfOOnOYUtg==", - "dependencies": { - "has-tostringtag": "^1.0.0" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/is-symbol": { - "version": "1.0.4", - "resolved": "https://registry.npmjs.org/is-symbol/-/is-symbol-1.0.4.tgz", - "integrity": "sha512-C/CPBqKWnvdcxqIARxyOh4v1UUEOCHpgDa0WYgpKDFMszcrPcffg5uhwSgPCLD2WWxmq6isisz87tzT01tuGhg==", - "dependencies": { - "has-symbols": "^1.0.2" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/is-typed-array": { - "version": "1.1.9", - "resolved": "https://registry.npmjs.org/is-typed-array/-/is-typed-array-1.1.9.tgz", - "integrity": "sha512-kfrlnTTn8pZkfpJMUgYD7YZ3qzeJgWUn8XfVYBARc4wnmNOmLbmuuaAs3q5fvB0UJOn6yHAKaGTPM7d6ezoD/A==", - "dependencies": { - "available-typed-arrays": "^1.0.5", - "call-bind": "^1.0.2", - "es-abstract": "^1.20.0", - "for-each": "^0.3.3", - "has-tostringtag": "^1.0.0" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/is-weakref": { - "version": "1.0.2", - "resolved": "https://registry.npmjs.org/is-weakref/-/is-weakref-1.0.2.tgz", - "integrity": "sha512-qctsuLZmIQ0+vSSMfoVvyFe2+GSEvnmZ2ezTup1SBse9+twCCeial6EEi3Nc2KFcf6+qz2FBPnjXsk8xhKSaPQ==", - "dependencies": { - "call-bind": "^1.0.2" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/is-wsl": { - "version": "2.2.0", - "resolved": "https://registry.npmjs.org/is-wsl/-/is-wsl-2.2.0.tgz", - "integrity": "sha512-fKzAra0rGJUUBwGBgNkHZuToZcn+TtXHpeCgmkMJMMYx1sQDYaCSyjJBSCa2nH1DGm7s3n1oBnohoVTBaN7Lww==", - "dev": true, - "dependencies": { - "is-docker": "^2.0.0" - }, - "engines": { - "node": ">=8" - } - }, - "node_modules/isarray": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/isarray/-/isarray-1.0.0.tgz", - "integrity": "sha512-VLghIWNM6ELQzo7zwmcg0NmTVyWKYjvIeM83yjp0wRDTmUnrM678fQbcKBo6n2CJEF0szoG//ytg+TKla89ALQ==", - "dev": true - }, - "node_modules/isexe": { - "version": "2.0.0", - "resolved": "https://registry.npmjs.org/isexe/-/isexe-2.0.0.tgz", - "integrity": "sha512-RHxMLp9lnKHGHRng9QFhRCMbYAcVpn69smSGcq3f36xjgVVWThj4qqLbTLlq7Ssj8B+fIQ1EuCEGI2lKsyQeIw==", - "dev": true - }, - "node_modules/isobject": { - "version": "3.0.1", - "resolved": "https://registry.npmjs.org/isobject/-/isobject-3.0.1.tgz", - "integrity": "sha512-WhB9zCku7EGTj/HQQRz5aUQEUeoQZH2bWcltRErOpymJ4boYE6wL9Tbr23krRPSZ+C5zqNSrSw+Cc7sZZ4b7vg==", - "dev": true, - "engines": { - "node": ">=0.10.0" - } - }, - "node_modules/jest-worker": { - "version": "27.5.1", - "resolved": "https://registry.npmjs.org/jest-worker/-/jest-worker-27.5.1.tgz", - "integrity": "sha512-7vuh85V5cdDofPyxn58nrPjBktZo0u9x1g8WtjQol+jZDaE+fhN+cIvTj11GndBnMnyfrUOG1sZQxCdjKh+DKg==", - "dependencies": { - "@types/node": "*", - "merge-stream": "^2.0.0", - "supports-color": "^8.0.0" - }, - "engines": { - "node": ">= 10.13.0" - } - }, - "node_modules/json-parse-better-errors": { - "version": "1.0.2", - "resolved": "https://registry.npmjs.org/json-parse-better-errors/-/json-parse-better-errors-1.0.2.tgz", - "integrity": "sha512-mrqyZKfX5EhL7hvqcV6WG1yYjnjeuYDzDhhcAAUrq8Po85NBQBJP+ZDUT75qZQ98IkUoBqdkExkukOU7Ts2wrw==" - }, - "node_modules/json-schema-traverse": { - "version": "0.4.1", - "resolved": "https://registry.npmjs.org/json-schema-traverse/-/json-schema-traverse-0.4.1.tgz", - "integrity": "sha512-xbbCH5dCYU5T8LcEhhuh7HJ88HXuW3qsI3Y0zOZFKfZEHcpWiHU/Jxzk629Brsab/mMiHQti9wMP+845RPe3Vg==" - }, - "node_modules/jssha": { - "version": "3.2.0", - "resolved": "https://registry.npmjs.org/jssha/-/jssha-3.2.0.tgz", - "integrity": "sha512-QuruyBENDWdN4tZwJbQq7/eAK85FqrI4oDbXjy5IBhYD+2pTJyBUWZe8ctWaCkrV0gy6AaelgOZZBMeswEa/6Q==", - "engines": { - "node": "*" - } - }, - "node_modules/kind-of": { - "version": "6.0.3", - "resolved": "https://registry.npmjs.org/kind-of/-/kind-of-6.0.3.tgz", - "integrity": "sha512-dcS1ul+9tmeD95T+x28/ehLgd9mENa3LsvDTtzm3vyBEO7RPptvAD+t44WVXaUjTBRcrpFeFlC8WCruUR456hw==", - "dev": true, - "engines": { - "node": ">=0.10.0" - } - }, - "node_modules/loader-runner": { - "version": "4.3.0", - "resolved": "https://registry.npmjs.org/loader-runner/-/loader-runner-4.3.0.tgz", - "integrity": "sha512-3R/1M+yS3j5ou80Me59j7F9IMs4PXs3VqRrm0TU3AbKPxlmpoY1TNscJV/oGJXo8qCatFGTfDbY6W6ipGOYXfg==", - "engines": { - "node": ">=6.11.5" - } - }, - "node_modules/locate-path": { - "version": "5.0.0", - "resolved": "https://registry.npmjs.org/locate-path/-/locate-path-5.0.0.tgz", - "integrity": "sha512-t7hw9pI+WvuwNJXwk5zVHpyhIqzg2qTlklJOf0mVxGSbe3Fp2VieZcduNYjaLDoy6p9uGpQEGWG87WpMKlNq8g==", - "dependencies": { - "p-locate": "^4.1.0" - }, - "engines": { - "node": ">=8" - } - }, - "node_modules/lodash": { - "version": "4.17.21", - "resolved": "https://registry.npmjs.org/lodash/-/lodash-4.17.21.tgz", - "integrity": "sha512-v2kDEe57lecTulaDIuNTPy3Ry4gLGJ6Z1O3vE1krgXZNrsQ+LFTGHVxVjcXPs17LhbZVGedAJv8XZ1tvj5FvSg==", - "dev": true - }, - "node_modules/longest-streak": { - "version": "2.0.4", - "resolved": "https://registry.npmjs.org/longest-streak/-/longest-streak-2.0.4.tgz", - "integrity": "sha512-vM6rUVCVUJJt33bnmHiZEvr7wPT78ztX7rojL+LW51bHtLh6HTjx84LA5W4+oa6aKEJA7jJu5LR6vQRBpA5DVg==", - "dev": true, - "funding": { - "type": "github", - "url": "https://github.com/sponsors/wooorm" - } - }, - "node_modules/lower-case": { - "version": "2.0.2", - "resolved": "https://registry.npmjs.org/lower-case/-/lower-case-2.0.2.tgz", - "integrity": "sha512-7fm3l3NAF9WfN6W3JOmf5drwpVqX78JtoGJ3A6W0a6ZnldM41w2fV5D490psKFTpMds8TJse/eHLFFsNHHjHgg==", - "dev": true, - "dependencies": { - "tslib": "^2.0.3" - } - }, - "node_modules/markdown-table": { - "version": "2.0.0", - "resolved": "https://registry.npmjs.org/markdown-table/-/markdown-table-2.0.0.tgz", - "integrity": "sha512-Ezda85ToJUBhM6WGaG6veasyym+Tbs3cMAw/ZhOPqXiYsr0jgocBV3j3nx+4lk47plLlIqjwuTm/ywVI+zjJ/A==", - "dev": true, - "dependencies": { - "repeat-string": "^1.0.0" - }, - "funding": { - "type": "github", - "url": "https://github.com/sponsors/wooorm" - } - }, - "node_modules/md5.js": { - "version": "1.3.5", - "resolved": "https://registry.npmjs.org/md5.js/-/md5.js-1.3.5.tgz", - "integrity": "sha512-xitP+WxNPcTTOgnTJcrhM0xvdPepipPSf3I8EIpGKeFLjt3PlJLIDG3u8EX53ZIubkb+5U2+3rELYpEhHhzdkg==", - "dependencies": { - "hash-base": "^3.0.0", - "inherits": "^2.0.1", - "safe-buffer": "^5.1.2" - } - }, - "node_modules/mdast-util-find-and-replace": { - "version": "1.1.1", - "resolved": "https://registry.npmjs.org/mdast-util-find-and-replace/-/mdast-util-find-and-replace-1.1.1.tgz", - "integrity": "sha512-9cKl33Y21lyckGzpSmEQnIDjEfeeWelN5s1kUW1LwdB0Fkuq2u+4GdqcGEygYxJE8GVqCl0741bYXHgamfWAZA==", - "dev": true, - "dependencies": { - "escape-string-regexp": "^4.0.0", - "unist-util-is": "^4.0.0", - "unist-util-visit-parents": "^3.0.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/unified" - } - }, - "node_modules/mdast-util-footnote": { - "version": "0.1.7", - "resolved": "https://registry.npmjs.org/mdast-util-footnote/-/mdast-util-footnote-0.1.7.tgz", - "integrity": "sha512-QxNdO8qSxqbO2e3m09KwDKfWiLgqyCurdWTQ198NpbZ2hxntdc+VKS4fDJCmNWbAroUdYnSthu+XbZ8ovh8C3w==", - "dev": true, - "dependencies": { - "mdast-util-to-markdown": "^0.6.0", - "micromark": "~2.11.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/unified" - } - }, - "node_modules/mdast-util-from-markdown": { - "version": "0.8.5", - "resolved": "https://registry.npmjs.org/mdast-util-from-markdown/-/mdast-util-from-markdown-0.8.5.tgz", - "integrity": "sha512-2hkTXtYYnr+NubD/g6KGBS/0mFmBcifAsI0yIWRiRo0PjVs6SSOSOdtzbp6kSGnShDN6G5aWZpKQ2lWRy27mWQ==", - "dev": true, - "dependencies": { - "@types/mdast": "^3.0.0", - "mdast-util-to-string": "^2.0.0", - "micromark": "~2.11.0", - "parse-entities": "^2.0.0", - "unist-util-stringify-position": "^2.0.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/unified" - } - }, - "node_modules/mdast-util-frontmatter": { - "version": "0.2.0", - "resolved": "https://registry.npmjs.org/mdast-util-frontmatter/-/mdast-util-frontmatter-0.2.0.tgz", - "integrity": "sha512-FHKL4w4S5fdt1KjJCwB0178WJ0evnyyQr5kXTM3wrOVpytD0hrkvd+AOOjU9Td8onOejCkmZ+HQRT3CZ3coHHQ==", - "dev": true, - "dependencies": { - "micromark-extension-frontmatter": "^0.2.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/unified" - } - }, - "node_modules/mdast-util-gfm": { - "version": "0.1.2", - "resolved": "https://registry.npmjs.org/mdast-util-gfm/-/mdast-util-gfm-0.1.2.tgz", - "integrity": "sha512-NNkhDx/qYcuOWB7xHUGWZYVXvjPFFd6afg6/e2g+SV4r9q5XUcCbV4Wfa3DLYIiD+xAEZc6K4MGaE/m0KDcPwQ==", - "dev": true, - "dependencies": { - "mdast-util-gfm-autolink-literal": "^0.1.0", - "mdast-util-gfm-strikethrough": "^0.2.0", - "mdast-util-gfm-table": "^0.1.0", - "mdast-util-gfm-task-list-item": "^0.1.0", - "mdast-util-to-markdown": "^0.6.1" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/unified" - } - }, - "node_modules/mdast-util-gfm-autolink-literal": { - "version": "0.1.3", - "resolved": "https://registry.npmjs.org/mdast-util-gfm-autolink-literal/-/mdast-util-gfm-autolink-literal-0.1.3.tgz", - "integrity": "sha512-GjmLjWrXg1wqMIO9+ZsRik/s7PLwTaeCHVB7vRxUwLntZc8mzmTsLVr6HW1yLokcnhfURsn5zmSVdi3/xWWu1A==", - "dev": true, - "dependencies": { - "ccount": "^1.0.0", - "mdast-util-find-and-replace": "^1.1.0", - "micromark": "^2.11.3" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/unified" - } - }, - "node_modules/mdast-util-gfm-strikethrough": { - "version": "0.2.3", - "resolved": "https://registry.npmjs.org/mdast-util-gfm-strikethrough/-/mdast-util-gfm-strikethrough-0.2.3.tgz", - "integrity": "sha512-5OQLXpt6qdbttcDG/UxYY7Yjj3e8P7X16LzvpX8pIQPYJ/C2Z1qFGMmcw+1PZMUM3Z8wt8NRfYTvCni93mgsgA==", - "dev": true, - "dependencies": { - "mdast-util-to-markdown": "^0.6.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/unified" - } - }, - "node_modules/mdast-util-gfm-table": { - "version": "0.1.6", - "resolved": "https://registry.npmjs.org/mdast-util-gfm-table/-/mdast-util-gfm-table-0.1.6.tgz", - "integrity": "sha512-j4yDxQ66AJSBwGkbpFEp9uG/LS1tZV3P33fN1gkyRB2LoRL+RR3f76m0HPHaby6F4Z5xr9Fv1URmATlRRUIpRQ==", - "dev": true, - "dependencies": { - "markdown-table": "^2.0.0", - "mdast-util-to-markdown": "~0.6.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/unified" - } - }, - "node_modules/mdast-util-gfm-task-list-item": { - "version": "0.1.6", - "resolved": "https://registry.npmjs.org/mdast-util-gfm-task-list-item/-/mdast-util-gfm-task-list-item-0.1.6.tgz", - "integrity": "sha512-/d51FFIfPsSmCIRNp7E6pozM9z1GYPIkSy1urQ8s/o4TC22BZ7DqfHFWiqBD23bc7J3vV1Fc9O4QIHBlfuit8A==", - "dev": true, - "dependencies": { - "mdast-util-to-markdown": "~0.6.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/unified" - } - }, - "node_modules/mdast-util-to-markdown": { - "version": "0.6.5", - "resolved": "https://registry.npmjs.org/mdast-util-to-markdown/-/mdast-util-to-markdown-0.6.5.tgz", - "integrity": "sha512-XeV9sDE7ZlOQvs45C9UKMtfTcctcaj/pGwH8YLbMHoMOXNNCn2LsqVQOqrF1+/NU8lKDAqozme9SCXWyo9oAcQ==", - "dev": true, - "dependencies": { - "@types/unist": "^2.0.0", - "longest-streak": "^2.0.0", - "mdast-util-to-string": "^2.0.0", - "parse-entities": "^2.0.0", - "repeat-string": "^1.0.0", - "zwitch": "^1.0.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/unified" - } - }, - "node_modules/mdast-util-to-string": { - "version": "2.0.0", - "resolved": "https://registry.npmjs.org/mdast-util-to-string/-/mdast-util-to-string-2.0.0.tgz", - "integrity": "sha512-AW4DRS3QbBayY/jJmD8437V1Gombjf8RSOUCMFBuo5iHi58AGEgVCKQ+ezHkZZDpAQS75hcBMpLqjpJTjtUL7w==", - "dev": true, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/unified" - } - }, - "node_modules/media-typer": { - "version": "0.3.0", - "resolved": "https://registry.npmjs.org/media-typer/-/media-typer-0.3.0.tgz", - "integrity": "sha512-dq+qelQ9akHpcOl/gUVRTxVIOkAJ1wR3QAvb4RsVjS8oVoFjDGTc679wJYmUmknUF5HwMLOgb5O+a3KxfWapPQ==", - "dev": true, - "engines": { - "node": ">= 0.6" - } - }, - "node_modules/memfs": { - "version": "3.4.6", - "resolved": "https://registry.npmjs.org/memfs/-/memfs-3.4.6.tgz", - "integrity": "sha512-rH9mjopto6Wkr7RFuH9l9dk3qb2XGOcYKr7xMhaYqfzuJqOqhRrcFvfD7JMuPj6SLmPreh5+6eAuv36NFAU+Mw==", - "dev": true, - "dependencies": { - "fs-monkey": "^1.0.3" - }, - "engines": { - "node": ">= 4.0.0" - } - }, - "node_modules/merge-descriptors": { - "version": "1.0.1", - "resolved": "https://registry.npmjs.org/merge-descriptors/-/merge-descriptors-1.0.1.tgz", - "integrity": "sha512-cCi6g3/Zr1iqQi6ySbseM1Xvooa98N0w31jzUYrXPX2xqObmFGHJ0tQ5u74H3mVh7wLouTseZyYIq39g8cNp1w==", - "dev": true - }, - "node_modules/merge-stream": { - "version": "2.0.0", - "resolved": "https://registry.npmjs.org/merge-stream/-/merge-stream-2.0.0.tgz", - "integrity": "sha512-abv/qOcuPfk3URPfDzmZU1LKmuw8kT+0nIHvKrKgFrwifol/doWcdA4ZqsWQ8ENrFKkd67Mfpo/LovbIUsbt3w==" - }, - "node_modules/merge2": { - "version": "1.4.1", - "resolved": "https://registry.npmjs.org/merge2/-/merge2-1.4.1.tgz", - "integrity": "sha512-8q7VEgMJW4J8tcfVPy8g09NcQwZdbwFEqhe/WZkoIzjn/3TGDwtOCYtXGxA3O8tPzpczCCDgv+P2P5y00ZJOOg==", - "dev": true, - "engines": { - "node": ">= 8" - } - }, - "node_modules/methods": { - "version": "1.1.2", - "resolved": "https://registry.npmjs.org/methods/-/methods-1.1.2.tgz", - "integrity": "sha512-iclAHeNqNm68zFtnZ0e+1L2yUIdvzNoauKU4WBA3VvH/vPFieF7qfRlwUZU+DA9P9bPXIS90ulxoUoCH23sV2w==", - "dev": true, - "engines": { - "node": ">= 0.6" - } - }, - "node_modules/micromark": { - "version": "2.11.4", - "resolved": "https://registry.npmjs.org/micromark/-/micromark-2.11.4.tgz", - "integrity": "sha512-+WoovN/ppKolQOFIAajxi7Lu9kInbPxFuTBVEavFcL8eAfVstoc5MocPmqBeAdBOJV00uaVjegzH4+MA0DN/uA==", - "dev": true, - "funding": [ - { - "type": "GitHub Sponsors", - "url": "https://github.com/sponsors/unifiedjs" - }, - { - "type": "OpenCollective", - "url": "https://opencollective.com/unified" - } - ], - "dependencies": { - "debug": "^4.0.0", - "parse-entities": "^2.0.0" - } - }, - "node_modules/micromark-extension-footnote": { - "version": "0.3.2", - "resolved": "https://registry.npmjs.org/micromark-extension-footnote/-/micromark-extension-footnote-0.3.2.tgz", - "integrity": "sha512-gr/BeIxbIWQoUm02cIfK7mdMZ/fbroRpLsck4kvFtjbzP4yi+OPVbnukTc/zy0i7spC2xYE/dbX1Sur8BEDJsQ==", - "dev": true, - "dependencies": { - "micromark": "~2.11.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/unified" - } - }, - "node_modules/micromark-extension-frontmatter": { - "version": "0.2.2", - "resolved": "https://registry.npmjs.org/micromark-extension-frontmatter/-/micromark-extension-frontmatter-0.2.2.tgz", - "integrity": "sha512-q6nPLFCMTLtfsctAuS0Xh4vaolxSFUWUWR6PZSrXXiRy+SANGllpcqdXFv2z07l0Xz/6Hl40hK0ffNCJPH2n1A==", - "dev": true, - "dependencies": { - "fault": "^1.0.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/unified" - } - }, - "node_modules/micromark-extension-gfm": { - "version": "0.3.3", - "resolved": "https://registry.npmjs.org/micromark-extension-gfm/-/micromark-extension-gfm-0.3.3.tgz", - "integrity": "sha512-oVN4zv5/tAIA+l3GbMi7lWeYpJ14oQyJ3uEim20ktYFAcfX1x3LNlFGGlmrZHt7u9YlKExmyJdDGaTt6cMSR/A==", - "dev": true, - "dependencies": { - "micromark": "~2.11.0", - "micromark-extension-gfm-autolink-literal": "~0.5.0", - "micromark-extension-gfm-strikethrough": "~0.6.5", - "micromark-extension-gfm-table": "~0.4.0", - "micromark-extension-gfm-tagfilter": "~0.3.0", - "micromark-extension-gfm-task-list-item": "~0.3.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/unified" - } - }, - "node_modules/micromark-extension-gfm-autolink-literal": { - "version": "0.5.7", - "resolved": "https://registry.npmjs.org/micromark-extension-gfm-autolink-literal/-/micromark-extension-gfm-autolink-literal-0.5.7.tgz", - "integrity": "sha512-ePiDGH0/lhcngCe8FtH4ARFoxKTUelMp4L7Gg2pujYD5CSMb9PbblnyL+AAMud/SNMyusbS2XDSiPIRcQoNFAw==", - "dev": true, - "dependencies": { - "micromark": "~2.11.3" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/unified" - } - }, - "node_modules/micromark-extension-gfm-strikethrough": { - "version": "0.6.5", - "resolved": "https://registry.npmjs.org/micromark-extension-gfm-strikethrough/-/micromark-extension-gfm-strikethrough-0.6.5.tgz", - "integrity": "sha512-PpOKlgokpQRwUesRwWEp+fHjGGkZEejj83k9gU5iXCbDG+XBA92BqnRKYJdfqfkrRcZRgGuPuXb7DaK/DmxOhw==", - "dev": true, - "dependencies": { - "micromark": "~2.11.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/unified" - } - }, - "node_modules/micromark-extension-gfm-table": { - "version": "0.4.3", - "resolved": "https://registry.npmjs.org/micromark-extension-gfm-table/-/micromark-extension-gfm-table-0.4.3.tgz", - "integrity": "sha512-hVGvESPq0fk6ALWtomcwmgLvH8ZSVpcPjzi0AjPclB9FsVRgMtGZkUcpE0zgjOCFAznKepF4z3hX8z6e3HODdA==", - "dev": true, - "dependencies": { - "micromark": "~2.11.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/unified" - } - }, - "node_modules/micromark-extension-gfm-tagfilter": { - "version": "0.3.0", - "resolved": "https://registry.npmjs.org/micromark-extension-gfm-tagfilter/-/micromark-extension-gfm-tagfilter-0.3.0.tgz", - "integrity": "sha512-9GU0xBatryXifL//FJH+tAZ6i240xQuFrSL7mYi8f4oZSbc+NvXjkrHemeYP0+L4ZUT+Ptz3b95zhUZnMtoi/Q==", - "dev": true, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/unified" - } - }, - "node_modules/micromark-extension-gfm-task-list-item": { - "version": "0.3.3", - "resolved": "https://registry.npmjs.org/micromark-extension-gfm-task-list-item/-/micromark-extension-gfm-task-list-item-0.3.3.tgz", - "integrity": "sha512-0zvM5iSLKrc/NQl84pZSjGo66aTGd57C1idmlWmE87lkMcXrTxg1uXa/nXomxJytoje9trP0NDLvw4bZ/Z/XCQ==", - "dev": true, - "dependencies": { - "micromark": "~2.11.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/unified" - } - }, - "node_modules/micromark/node_modules/debug": { - "version": "4.3.4", - "resolved": "https://registry.npmjs.org/debug/-/debug-4.3.4.tgz", - "integrity": "sha512-PRWFHuSU3eDtQJPvnNY7Jcket1j0t5OuOsFzPPzsekD52Zl8qUfFIPEiswXqIvHWGVHOgX+7G/vCNNhehwxfkQ==", - "dev": true, - "dependencies": { - "ms": "2.1.2" - }, - "engines": { - "node": ">=6.0" - }, - "peerDependenciesMeta": { - "supports-color": { - "optional": true - } - } - }, - "node_modules/micromark/node_modules/ms": { - "version": "2.1.2", - "resolved": "https://registry.npmjs.org/ms/-/ms-2.1.2.tgz", - "integrity": "sha512-sGkPx+VjMtmA6MX27oA4FBFELFCZZ4S4XqeGOXCv68tT+jb3vk/RyaKWP0PTKyWtmLSM0b+adUTEvbs1PEaH2w==", - "dev": true - }, - "node_modules/micromatch": { - "version": "4.0.5", - "resolved": "https://registry.npmjs.org/micromatch/-/micromatch-4.0.5.tgz", - "integrity": "sha512-DMy+ERcEW2q8Z2Po+WNXuw3c5YaUSFjAO5GsJqfEl7UjvtIuFKO6ZrKvcItdy98dwFI2N1tg3zNIdKaQT+aNdA==", - "dev": true, - "dependencies": { - "braces": "^3.0.2", - "picomatch": "^2.3.1" - }, - "engines": { - "node": ">=8.6" - } - }, - "node_modules/miller-rabin": { - "version": "4.0.1", - "resolved": "https://registry.npmjs.org/miller-rabin/-/miller-rabin-4.0.1.tgz", - "integrity": "sha512-115fLhvZVqWwHPbClyntxEVfVDfl9DLLTuJvq3g2O/Oxi8AiNouAHvDSzHS0viUJc+V5vm3eq91Xwqn9dp4jRA==", - "dependencies": { - "bn.js": "^4.0.0", - "brorand": "^1.0.1" - }, - "bin": { - "miller-rabin": "bin/miller-rabin" - } - }, - "node_modules/miller-rabin/node_modules/bn.js": { - "version": "4.12.0", - "resolved": "https://registry.npmjs.org/bn.js/-/bn.js-4.12.0.tgz", - "integrity": "sha512-c98Bf3tPniI+scsdk237ku1Dc3ujXQTSgyiPUDEOe7tRkhrqridvh8klBv0HCEso1OLOYcHuCv/cS6DNxKH+ZA==" - }, - "node_modules/mime": { - "version": "1.6.0", - "resolved": "https://registry.npmjs.org/mime/-/mime-1.6.0.tgz", - "integrity": "sha512-x0Vn8spI+wuJ1O6S7gnbaQg8Pxh4NNHb7KSINmEWKiPE4RKOplvijn+NkmYmmRgP68mc70j2EbeTFRsrswaQeg==", - "dev": true, - "bin": { - "mime": "cli.js" - }, - "engines": { - "node": ">=4" - } - }, - "node_modules/mime-db": { - "version": "1.52.0", - "resolved": "https://registry.npmjs.org/mime-db/-/mime-db-1.52.0.tgz", - "integrity": "sha512-sPU4uV7dYlvtWJxwwxHD0PuihVNiE7TyAbQ5SWxDCB9mUYvOgroQOwYQQOKPJ8CIbE+1ETVlOoK1UC2nU3gYvg==", - "engines": { - "node": ">= 0.6" - } - }, - "node_modules/mime-types": { - "version": "2.1.35", - "resolved": "https://registry.npmjs.org/mime-types/-/mime-types-2.1.35.tgz", - "integrity": "sha512-ZDY+bPm5zTTF+YpCrAU9nK0UgICYPT0QtT1NZWFv4s++TNkcgVaT0g6+4R2uI4MjQjzysHB1zxuWL50hzaeXiw==", - "dependencies": { - "mime-db": "1.52.0" - }, - "engines": { - "node": ">= 0.6" - } - }, - "node_modules/mimic-fn": { - "version": "2.1.0", - "resolved": "https://registry.npmjs.org/mimic-fn/-/mimic-fn-2.1.0.tgz", - "integrity": "sha512-OqbOk5oEQeAZ8WXWydlu9HJjz9WVdEIvamMCcXmuqUYjTknH/sqsWvhQ3vgwKFRR1HpjvNBKQ37nbJgYzGqGcg==", - "dev": true, - "engines": { - "node": ">=6" - } - }, - "node_modules/minimalistic-assert": { - "version": "1.0.1", - "resolved": "https://registry.npmjs.org/minimalistic-assert/-/minimalistic-assert-1.0.1.tgz", - "integrity": "sha512-UtJcAD4yEaGtjPezWuO9wC4nwUnVH/8/Im3yEHQP4b67cXlD/Qr9hdITCU1xDbSEXg2XKNaP8jsReV7vQd00/A==" - }, - "node_modules/minimalistic-crypto-utils": { - "version": "1.0.1", - "resolved": "https://registry.npmjs.org/minimalistic-crypto-utils/-/minimalistic-crypto-utils-1.0.1.tgz", - "integrity": "sha512-JIYlbt6g8i5jKfJ3xz7rF0LXmv2TkDxBLUkiBeZ7bAx4GnnNMr8xFpGnOxn6GhTEHx3SjRrZEoU+j04prX1ktg==" - }, - "node_modules/minimatch": { - "version": "3.1.2", - "resolved": "https://registry.npmjs.org/minimatch/-/minimatch-3.1.2.tgz", - "integrity": "sha512-J7p63hRiAjw1NDEww1W7i37+ByIrOWO5XQQAzZ3VOcL0PNybwpfmV/N05zFAzwQ9USyEcX6t3UO+K5aqBQOIHw==", - "dependencies": { - "brace-expansion": "^1.1.7" - }, - "engines": { - "node": "*" - } - }, - "node_modules/minimist": { - "version": "1.2.6", - "resolved": "https://registry.npmjs.org/minimist/-/minimist-1.2.6.tgz", - "integrity": "sha512-Jsjnk4bw3YJqYzbdyBiNsPWHPfO++UGG749Cxs6peCu5Xg4nrena6OVxOYxrQTqww0Jmwt+Ref8rggumkTLz9Q==", - "dev": true - }, - "node_modules/mkdirp": { - "version": "0.5.6", - "resolved": "https://registry.npmjs.org/mkdirp/-/mkdirp-0.5.6.tgz", - "integrity": "sha512-FP+p8RB8OWpF3YZBCrP5gtADmtXApB5AMLn+vdyA+PyxCjrCs00mjyUozssO33cwDeT3wNGdLxJ5M//YqtHAJw==", - "dev": true, - "dependencies": { - "minimist": "^1.2.6" - }, - "bin": { - "mkdirp": "bin/cmd.js" - } - }, - "node_modules/mkdirp-classic": { - "version": "0.5.3", - "resolved": "https://registry.npmjs.org/mkdirp-classic/-/mkdirp-classic-0.5.3.tgz", - "integrity": "sha512-gKLcREMhtuZRwRAfqP3RFW+TK4JqApVBtOIftVgjuABpAtpxhPGaDcfvbhNvD0B8iD1oUr/txX35NjcaY6Ns/A==" - }, - "node_modules/ms": { - "version": "2.0.0", - "resolved": "https://registry.npmjs.org/ms/-/ms-2.0.0.tgz", - "integrity": "sha512-Tpp60P6IUJDTuOq/5Z8cdskzJujfwqfOTkrwIwj7IRISpnkJnT6SyJ4PCPnGMoFjC9ddhal5KVIYtAt97ix05A==", - "dev": true - }, - "node_modules/multicast-dns": { - "version": "6.2.3", - "resolved": "https://registry.npmjs.org/multicast-dns/-/multicast-dns-6.2.3.tgz", - "integrity": "sha512-ji6J5enbMyGRHIAkAOu3WdV8nggqviKCEKtXcOqfphZZtQrmHKycfynJ2V7eVPUA4NhJ6V7Wf4TmGbTwKE9B6g==", - "dev": true, - "dependencies": { - "dns-packet": "^1.3.1", - "thunky": "^1.0.2" - }, - "bin": { - "multicast-dns": "cli.js" - } - }, - "node_modules/multicast-dns-service-types": { - "version": "1.1.0", - "resolved": "https://registry.npmjs.org/multicast-dns-service-types/-/multicast-dns-service-types-1.1.0.tgz", - "integrity": "sha512-cnAsSVxIDsYt0v7HmC0hWZFwwXSh+E6PgCrREDuN/EsjgLwA5XRmlMHhSiDPrt6HxY1gTivEa/Zh7GtODoLevQ==", - "dev": true - }, - "node_modules/negotiator": { - "version": "0.6.3", - "resolved": "https://registry.npmjs.org/negotiator/-/negotiator-0.6.3.tgz", - "integrity": "sha512-+EUsqGPLsM+j/zdChZjsnX51g4XrHFOIXwfnCVPGlQk/k5giakcKsuxCObBRu6DSm9opw/O6slWbJdghQM4bBg==", - "dev": true, - "engines": { - "node": ">= 0.6" - } - }, - "node_modules/neo-async": { - "version": "2.6.2", - "resolved": "https://registry.npmjs.org/neo-async/-/neo-async-2.6.2.tgz", - "integrity": "sha512-Yd3UES5mWCSqR+qNT93S3UoYUkqAZ9lLg8a7g9rimsWmYGK8cVToA4/sF3RrshdyV3sAGMXVUmpMYOw+dLpOuw==" - }, - "node_modules/no-case": { - "version": "3.0.4", - "resolved": "https://registry.npmjs.org/no-case/-/no-case-3.0.4.tgz", - "integrity": "sha512-fgAN3jGAh+RoxUGZHTSOLJIqUc2wmoBwGR4tbpNAKmmovFoWq0OdRkb0VkldReO2a2iBT/OEulG9XSUc10r3zg==", - "dev": true, - "dependencies": { - "lower-case": "^2.0.2", - "tslib": "^2.0.3" - } - }, - "node_modules/node-fetch": { - "version": "2.6.7", - "resolved": "https://registry.npmjs.org/node-fetch/-/node-fetch-2.6.7.tgz", - "integrity": "sha512-ZjMPFEfVx5j+y2yF35Kzx5sF7kDzxuDj6ziH4FFbOp87zKDZNx8yExJIb05OGF4Nlt9IHFIMBkRl41VdvcNdbQ==", - "dependencies": { - "whatwg-url": "^5.0.0" - }, - "engines": { - "node": "4.x || >=6.0.0" - }, - "peerDependencies": { - "encoding": "^0.1.0" - }, - "peerDependenciesMeta": { - "encoding": { - "optional": true - } - } - }, - "node_modules/node-fetch/node_modules/tr46": { - "version": "0.0.3", - "resolved": "https://registry.npmjs.org/tr46/-/tr46-0.0.3.tgz", - "integrity": "sha512-N3WMsuqV66lT30CrXNbEjx4GEwlow3v6rr4mCcv6prnfwhS01rkgyFdjPNBYd9br7LpXV1+Emh01fHnq2Gdgrw==" - }, - "node_modules/node-fetch/node_modules/webidl-conversions": { - "version": "3.0.1", - "resolved": "https://registry.npmjs.org/webidl-conversions/-/webidl-conversions-3.0.1.tgz", - "integrity": "sha512-2JAn3z8AR6rjK8Sm8orRC0h/bcl/DqL7tRPdGZ4I1CjdF+EaMLmYxBHyXuKL849eucPFhvBoxMsflfOb8kxaeQ==" - }, - "node_modules/node-fetch/node_modules/whatwg-url": { - "version": "5.0.0", - "resolved": "https://registry.npmjs.org/whatwg-url/-/whatwg-url-5.0.0.tgz", - "integrity": "sha512-saE57nupxk6v3HY35+jzBwYa0rKSy0XR8JSxZPwgLr7ys0IBzhGviA1/TUGJLmSVqs8pb9AnvICXEuOHLprYTw==", - "dependencies": { - "tr46": "~0.0.3", - "webidl-conversions": "^3.0.0" - } - }, - "node_modules/node-forge": { - "version": "1.3.1", - "resolved": "https://registry.npmjs.org/node-forge/-/node-forge-1.3.1.tgz", - "integrity": "sha512-dPEtOeMvF9VMcYV/1Wb8CPoVAXtp6MKMlcbAt4ddqmGqUJ6fQZFXkNZNkNlfevtNkGtaSoXf/vNNNSvgrdXwtA==", - "dev": true, - "engines": { - "node": ">= 6.13.0" - } - }, - "node_modules/node-gyp-build": { - "version": "4.4.0", - "resolved": "https://registry.npmjs.org/node-gyp-build/-/node-gyp-build-4.4.0.tgz", - "integrity": "sha512-amJnQCcgtRVw9SvoebO3BKGESClrfXGCUTX9hSn1OuGQTQBOZmVd0Z0OlecpuRksKvbsUqALE8jls/ErClAPuQ==", - "bin": { - "node-gyp-build": "bin.js", - "node-gyp-build-optional": "optional.js", - "node-gyp-build-test": "build-test.js" - } - }, - "node_modules/node-polyfill-webpack-plugin": { - "version": "1.1.4", - "resolved": "https://registry.npmjs.org/node-polyfill-webpack-plugin/-/node-polyfill-webpack-plugin-1.1.4.tgz", - "integrity": "sha512-Z0XTKj1wRWO8o/Vjobsw5iOJCN+Sua3EZEUc2Ziy9CyVvmHKu6o+t4gUH9GOE0czyPR94LI6ZCV/PpcM8b5yow==", - "dependencies": { - "assert": "^2.0.0", - "browserify-zlib": "^0.2.0", - "buffer": "^6.0.3", - "console-browserify": "^1.2.0", - "constants-browserify": "^1.0.0", - "crypto-browserify": "^3.12.0", - "domain-browser": "^4.19.0", - "events": "^3.3.0", - "filter-obj": "^2.0.2", - "https-browserify": "^1.0.0", - "os-browserify": "^0.3.0", - "path-browserify": "^1.0.1", - "process": "^0.11.10", - "punycode": "^2.1.1", - "querystring-es3": "^0.2.1", - "readable-stream": "^3.6.0", - "stream-browserify": "^3.0.0", - "stream-http": "^3.2.0", - "string_decoder": "^1.3.0", - "timers-browserify": "^2.0.12", - "tty-browserify": "^0.0.1", - "url": "^0.11.0", - "util": "^0.12.4", - "vm-browserify": "^1.1.2" - }, - "engines": { - "node": ">=10" - }, - "peerDependencies": { - "webpack": ">=5" - } - }, - "node_modules/node-releases": { - "version": "2.0.5", - "resolved": "https://registry.npmjs.org/node-releases/-/node-releases-2.0.5.tgz", - "integrity": "sha512-U9h1NLROZTq9uE1SNffn6WuPDg8icmi3ns4rEl/oTfIle4iLjTliCzgTsbaIFMq/Xn078/lfY/BL0GWZ+psK4Q==" - }, - "node_modules/normalize-path": { - "version": "3.0.0", - "resolved": "https://registry.npmjs.org/normalize-path/-/normalize-path-3.0.0.tgz", - "integrity": "sha512-6eZs5Ls3WtCisHWp9S2GUy8dqkpGi4BVSz3GaqiE6ezub0512ESztXUwUB6C6IKbQkY2Pnb/mD4WYojCRwcwLA==", - "dev": true, - "engines": { - "node": ">=0.10.0" - } - }, - "node_modules/npm-run-path": { - "version": "4.0.1", - "resolved": "https://registry.npmjs.org/npm-run-path/-/npm-run-path-4.0.1.tgz", - "integrity": "sha512-S48WzZW777zhNIrn7gxOlISNAqi9ZC/uQFnRdbeIHhZhCA6UqpkOT8T1G7BvfdgP4Er8gF4sUbaS0i7QvIfCWw==", - "dev": true, - "dependencies": { - "path-key": "^3.0.0" - }, - "engines": { - "node": ">=8" - } - }, - "node_modules/nth-check": { - "version": "2.1.1", - "resolved": "https://registry.npmjs.org/nth-check/-/nth-check-2.1.1.tgz", - "integrity": "sha512-lqjrjmaOoAnWfMmBPL+XNnynZh2+swxiX3WUE0s4yEHI6m+AwrK2UZOimIRl3X/4QctVqS8AiZjFqyOGrMXb/w==", - "dev": true, - "dependencies": { - "boolbase": "^1.0.0" - }, - "funding": { - "url": "https://github.com/fb55/nth-check?sponsor=1" - } - }, - "node_modules/object-inspect": { - "version": "1.12.1", - "resolved": "https://registry.npmjs.org/object-inspect/-/object-inspect-1.12.1.tgz", - "integrity": "sha512-Y/jF6vnvEtOPGiKD1+q+X0CiUYRQtEHp89MLLUJ7TUivtH8Ugn2+3A7Rynqk7BRsAoqeOQWnFnjpDrKSxDgIGA==", - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/object-is": { - "version": "1.1.5", - "resolved": "https://registry.npmjs.org/object-is/-/object-is-1.1.5.tgz", - "integrity": "sha512-3cyDsyHgtmi7I7DfSSI2LDp6SK2lwvtbg0p0R1e0RvTqF5ceGx+K2dfSjm1bKDMVCFEDAQvy+o8c6a7VujOddw==", - "dependencies": { - "call-bind": "^1.0.2", - "define-properties": "^1.1.3" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/object-keys": { - "version": "1.1.1", - "resolved": "https://registry.npmjs.org/object-keys/-/object-keys-1.1.1.tgz", - "integrity": "sha512-NuAESUOUMrlIXOfHKzD6bpPu3tYt3xvjNdRIQ+FeT0lNb4K8WR70CaDxhuNguS2XG+GjkyMwOzsN5ZktImfhLA==", - "engines": { - "node": ">= 0.4" - } - }, - "node_modules/object.assign": { - "version": "4.1.2", - "resolved": "https://registry.npmjs.org/object.assign/-/object.assign-4.1.2.tgz", - "integrity": "sha512-ixT2L5THXsApyiUPYKmW+2EHpXXe5Ii3M+f4e+aJFAHao5amFRW6J0OO6c/LU8Be47utCx2GL89hxGB6XSmKuQ==", - "dependencies": { - "call-bind": "^1.0.0", - "define-properties": "^1.1.3", - "has-symbols": "^1.0.1", - "object-keys": "^1.1.1" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/obuf": { - "version": "1.1.2", - "resolved": "https://registry.npmjs.org/obuf/-/obuf-1.1.2.tgz", - "integrity": "sha512-PX1wu0AmAdPqOL1mWhqmlOd8kOIZQwGZw6rh7uby9fTc5lhaOWFLX3I6R1hrF9k3zUY40e6igsLGkDXK92LJNg==", - "dev": true - }, - "node_modules/on-finished": { - "version": "2.4.1", - "resolved": "https://registry.npmjs.org/on-finished/-/on-finished-2.4.1.tgz", - "integrity": "sha512-oVlzkg3ENAhCk2zdv7IJwd/QUD4z2RxRwpkcGY8psCVcCYZNq4wYnVWALHM+brtuJjePWiYF/ClmuDr8Ch5+kg==", - "dev": true, - "dependencies": { - "ee-first": "1.1.1" - }, - "engines": { - "node": ">= 0.8" - } - }, - "node_modules/on-headers": { - "version": "1.0.2", - "resolved": "https://registry.npmjs.org/on-headers/-/on-headers-1.0.2.tgz", - "integrity": "sha512-pZAE+FJLoyITytdqK0U5s+FIpjN0JP3OzFi/u8Rx+EV5/W+JTWGXG8xFzevE7AjBfDqHv/8vL8qQsIhHnqRkrA==", - "dev": true, - "engines": { - "node": ">= 0.8" - } - }, - "node_modules/once": { - "version": "1.4.0", - "resolved": "https://registry.npmjs.org/once/-/once-1.4.0.tgz", - "integrity": "sha512-lNaJgI+2Q5URQBkccEKHTQOPaXdUxnZZElQTZY0MFUAuaEqe1E+Nyvgdz/aIyNi6Z9MzO5dv1H8n58/GELp3+w==", - "dependencies": { - "wrappy": "1" - } - }, - "node_modules/onetime": { - "version": "5.1.2", - "resolved": "https://registry.npmjs.org/onetime/-/onetime-5.1.2.tgz", - "integrity": "sha512-kbpaSSGJTWdAY5KPVeMOKXSrPtr8C8C7wodJbcsd51jRnmD+GZu8Y0VoU6Dm5Z4vWr0Ig/1NKuWRKf7j5aaYSg==", - "dev": true, - "dependencies": { - "mimic-fn": "^2.1.0" - }, - "engines": { - "node": ">=6" - }, - "funding": { - "url": "https://github.com/sponsors/sindresorhus" - } - }, - "node_modules/open": { - "version": "8.4.0", - "resolved": "https://registry.npmjs.org/open/-/open-8.4.0.tgz", - "integrity": "sha512-XgFPPM+B28FtCCgSb9I+s9szOC1vZRSwgWsRUA5ylIxRTgKozqjOCrVOqGsYABPYK5qnfqClxZTFBa8PKt2v6Q==", - "dev": true, - "dependencies": { - "define-lazy-prop": "^2.0.0", - "is-docker": "^2.1.1", - "is-wsl": "^2.2.0" - }, - "engines": { - "node": ">=12" - }, - "funding": { - "url": "https://github.com/sponsors/sindresorhus" - } - }, - "node_modules/os-browserify": { - "version": "0.3.0", - "resolved": "https://registry.npmjs.org/os-browserify/-/os-browserify-0.3.0.tgz", - "integrity": "sha512-gjcpUc3clBf9+210TRaDWbf+rZZZEshZ+DlXMRCeAjp0xhTrnQsKHypIy1J3d5hKdUzj69t708EHtU8P6bUn0A==" - }, - "node_modules/p-limit": { - "version": "2.3.0", - "resolved": "https://registry.npmjs.org/p-limit/-/p-limit-2.3.0.tgz", - "integrity": "sha512-//88mFWSJx8lxCzwdAABTJL2MyWB12+eIY7MDL2SqLmAkeKU9qxRvWuSyTjm3FUmpBEMuFfckAIqEaVGUDxb6w==", - "dependencies": { - "p-try": "^2.0.0" - }, - "engines": { - "node": ">=6" - }, - "funding": { - "url": "https://github.com/sponsors/sindresorhus" - } - }, - "node_modules/p-locate": { - "version": "4.1.0", - "resolved": "https://registry.npmjs.org/p-locate/-/p-locate-4.1.0.tgz", - "integrity": "sha512-R79ZZ/0wAxKGu3oYMlz8jy/kbhsNrS7SKZ7PxEHBgJ5+F2mtFW2fK2cOtBh1cHYkQsbzFV7I+EoRKe6Yt0oK7A==", - "dependencies": { - "p-limit": "^2.2.0" - }, - "engines": { - "node": ">=8" - } - }, - "node_modules/p-map": { - "version": "4.0.0", - "resolved": "https://registry.npmjs.org/p-map/-/p-map-4.0.0.tgz", - "integrity": "sha512-/bjOqmgETBYB5BoEeGVea8dmvHb2m9GLy1E9W43yeyfP6QQCZGFNa+XRceJEuDB6zqr+gKpIAmlLebMpykw/MQ==", - "dev": true, - "dependencies": { - "aggregate-error": "^3.0.0" - }, - "engines": { - "node": ">=10" - }, - "funding": { - "url": "https://github.com/sponsors/sindresorhus" - } - }, - "node_modules/p-retry": { - "version": "4.6.2", - "resolved": "https://registry.npmjs.org/p-retry/-/p-retry-4.6.2.tgz", - "integrity": "sha512-312Id396EbJdvRONlngUx0NydfrIQ5lsYu0znKVUzVvArzEIt08V1qhtyESbGVd1FGX7UKtiFp5uwKZdM8wIuQ==", - "dev": true, - "dependencies": { - "@types/retry": "0.12.0", - "retry": "^0.13.1" - }, - "engines": { - "node": ">=8" - } - }, - "node_modules/p-try": { - "version": "2.2.0", - "resolved": "https://registry.npmjs.org/p-try/-/p-try-2.2.0.tgz", - "integrity": "sha512-R4nPAVTAU0B9D35/Gk3uJf/7XYbQcyohSKdvAxIRSNghFl4e71hVoGnBNQz9cWaXxO2I10KTC+3jMdvvoKw6dQ==", - "engines": { - "node": ">=6" - } - }, - "node_modules/pako": { - "version": "1.0.11", - "resolved": "https://registry.npmjs.org/pako/-/pako-1.0.11.tgz", - "integrity": "sha512-4hLB8Py4zZce5s4yd9XzopqwVv/yGNhV1Bl8NTmCq1763HeK2+EwVTv+leGeL13Dnh2wfbqowVPXCIO0z4taYw==" - }, - "node_modules/param-case": { - "version": "3.0.4", - "resolved": "https://registry.npmjs.org/param-case/-/param-case-3.0.4.tgz", - "integrity": "sha512-RXlj7zCYokReqWpOPH9oYivUzLYZ5vAPIfEmCTNViosC78F8F0H9y7T7gG2M39ymgutxF5gcFEsyZQSph9Bp3A==", - "dev": true, - "dependencies": { - "dot-case": "^3.0.4", - "tslib": "^2.0.3" - } - }, - "node_modules/parse-asn1": { - "version": "5.1.6", - "resolved": "https://registry.npmjs.org/parse-asn1/-/parse-asn1-5.1.6.tgz", - "integrity": "sha512-RnZRo1EPU6JBnra2vGHj0yhp6ebyjBZpmUCLHWiFhxlzvBCCpAuZ7elsBp1PVAbQN0/04VD/19rfzlBSwLstMw==", - "dependencies": { - "asn1.js": "^5.2.0", - "browserify-aes": "^1.0.0", - "evp_bytestokey": "^1.0.0", - "pbkdf2": "^3.0.3", - "safe-buffer": "^5.1.1" - } - }, - "node_modules/parse-entities": { - "version": "2.0.0", - "resolved": "https://registry.npmjs.org/parse-entities/-/parse-entities-2.0.0.tgz", - "integrity": "sha512-kkywGpCcRYhqQIchaWqZ875wzpS/bMKhz5HnN3p7wveJTkTtyAB/AlnS0f8DFSqYW1T82t6yEAkEcB+A1I3MbQ==", - "dev": true, - "dependencies": { - "character-entities": "^1.0.0", - "character-entities-legacy": "^1.0.0", - "character-reference-invalid": "^1.0.0", - "is-alphanumerical": "^1.0.0", - "is-decimal": "^1.0.0", - "is-hexadecimal": "^1.0.0" - }, - "funding": { - "type": "github", - "url": "https://github.com/sponsors/wooorm" - } - }, - "node_modules/parseurl": { - "version": "1.3.3", - "resolved": "https://registry.npmjs.org/parseurl/-/parseurl-1.3.3.tgz", - "integrity": "sha512-CiyeOxFT/JZyN5m0z9PfXw4SCBJ6Sygz1Dpl0wqjlhDEGGBP1GnsUVEL0p63hoG1fcj3fHynXi9NYO4nWOL+qQ==", - "dev": true, - "engines": { - "node": ">= 0.8" - } - }, - "node_modules/pascal-case": { - "version": "3.1.2", - "resolved": "https://registry.npmjs.org/pascal-case/-/pascal-case-3.1.2.tgz", - "integrity": "sha512-uWlGT3YSnK9x3BQJaOdcZwrnV6hPpd8jFH1/ucpiLRPh/2zCVJKS19E4GvYHvaCcACn3foXZ0cLB9Wrx1KGe5g==", - "dev": true, - "dependencies": { - "no-case": "^3.0.4", - "tslib": "^2.0.3" - } - }, - "node_modules/path-browserify": { - "version": "1.0.1", - "resolved": "https://registry.npmjs.org/path-browserify/-/path-browserify-1.0.1.tgz", - "integrity": "sha512-b7uo2UCUOYZcnF/3ID0lulOJi/bafxa1xPe7ZPsammBSpjSWQkjNxlt635YGS2MiR9GjvuXCtz2emr3jbsz98g==" - }, - "node_modules/path-exists": { - "version": "4.0.0", - "resolved": "https://registry.npmjs.org/path-exists/-/path-exists-4.0.0.tgz", - "integrity": "sha512-ak9Qy5Q7jYb2Wwcey5Fpvg2KoAc/ZIhLSLOSBmRmygPsGwkVVt0fZa0qrtMz+m6tJTAHfZQ8FnmB4MG4LWy7/w==", - "engines": { - "node": ">=8" - } - }, - "node_modules/path-is-absolute": { - "version": "1.0.1", - "resolved": "https://registry.npmjs.org/path-is-absolute/-/path-is-absolute-1.0.1.tgz", - "integrity": "sha512-AVbw3UJ2e9bq64vSaS9Am0fje1Pa8pbGqTTsmXfaIiMpnr5DlDhfJOuLj9Sf95ZPVDAUerDfEk88MPmPe7UCQg==", - "engines": { - "node": ">=0.10.0" - } - }, - "node_modules/path-key": { - "version": "3.1.1", - "resolved": "https://registry.npmjs.org/path-key/-/path-key-3.1.1.tgz", - "integrity": "sha512-ojmeN0qd+y0jszEtoY48r0Peq5dwMEkIlCOu6Q5f41lfkswXuKtYrhgoTpLnyIcHm24Uhqx+5Tqm2InSwLhE6Q==", - "dev": true, - "engines": { - "node": ">=8" - } - }, - "node_modules/path-parse": { - "version": "1.0.7", - "resolved": "https://registry.npmjs.org/path-parse/-/path-parse-1.0.7.tgz", - "integrity": "sha512-LDJzPVEEEPR+y48z93A0Ed0yXb8pAByGWo/k5YYdYgpY2/2EsOsksJrq7lOHxryrVOn1ejG6oAp8ahvOIQD8sw==", - "dev": true - }, - "node_modules/path-to-regexp": { - "version": "0.1.7", - "resolved": "https://registry.npmjs.org/path-to-regexp/-/path-to-regexp-0.1.7.tgz", - "integrity": "sha512-5DFkuoqlv1uYQKxy8omFBeJPQcdoE07Kv2sferDCrAq1ohOU+MSDswDIbnx3YAM60qIOnYa53wBhXW0EbMonrQ==", - "dev": true - }, - "node_modules/path-type": { - "version": "4.0.0", - "resolved": "https://registry.npmjs.org/path-type/-/path-type-4.0.0.tgz", - "integrity": "sha512-gDKb8aZMDeD/tZWs9P6+q0J9Mwkdl6xMV8TjnGP3qJVJ06bdMgkbBlLU8IdfOsIsFz2BW1rNVT3XuNEl8zPAvw==", - "dev": true, - "engines": { - "node": ">=8" - } - }, - "node_modules/pbkdf2": { - "version": "3.1.2", - "resolved": "https://registry.npmjs.org/pbkdf2/-/pbkdf2-3.1.2.tgz", - "integrity": "sha512-iuh7L6jA7JEGu2WxDwtQP1ddOpaJNC4KlDEFfdQajSGgGPNi4OyDc2R7QnbY2bR9QjBVGwgvTdNJZoE7RaxUMA==", - "dependencies": { - "create-hash": "^1.1.2", - "create-hmac": "^1.1.4", - "ripemd160": "^2.0.1", - "safe-buffer": "^5.0.1", - "sha.js": "^2.4.8" - }, - "engines": { - "node": ">=0.12" - } - }, - "node_modules/pend": { - "version": "1.2.0", - "resolved": "https://registry.npmjs.org/pend/-/pend-1.2.0.tgz", - "integrity": "sha512-F3asv42UuXchdzt+xXqfW1OGlVBe+mxa2mqI0pg5yAHZPvFmY3Y6drSf/GQ1A86WgWEN9Kzh/WrgKa6iGcHXLg==" - }, - "node_modules/picocolors": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/picocolors/-/picocolors-1.0.0.tgz", - "integrity": "sha512-1fygroTLlHu66zi26VoTDv8yRgm0Fccecssto+MhsZ0D/DGW2sm8E8AjW7NU5VVTRt5GxbeZ5qBuJr+HyLYkjQ==" - }, - "node_modules/picomatch": { - "version": "2.3.1", - "resolved": "https://registry.npmjs.org/picomatch/-/picomatch-2.3.1.tgz", - "integrity": "sha512-JU3teHTNjmE2VCGFzuY8EXzCDVwEqB2a8fsIvwaStHhAWJEeVd1o1QD80CU6+ZdEXXSLbSsuLwJjkCBWqRQUVA==", - "dev": true, - "engines": { - "node": ">=8.6" - }, - "funding": { - "url": "https://github.com/sponsors/jonschlinkert" - } - }, - "node_modules/pkg-dir": { - "version": "4.2.0", - "resolved": "https://registry.npmjs.org/pkg-dir/-/pkg-dir-4.2.0.tgz", - "integrity": "sha512-HRDzbaKjC+AOWVXxAU/x54COGeIv9eb+6CkDSQoNTt4XyWoIJvuPsXizxu/Fr23EiekbtZwmh1IcIG/l/a10GQ==", - "dependencies": { - "find-up": "^4.0.0" - }, - "engines": { - "node": ">=8" - } - }, - "node_modules/portfinder": { - "version": "1.0.28", - "resolved": "https://registry.npmjs.org/portfinder/-/portfinder-1.0.28.tgz", - "integrity": "sha512-Se+2isanIcEqf2XMHjyUKskczxbPH7dQnlMjXX6+dybayyHvAf/TCgyMRlzf/B6QDhAEFOGes0pzRo3by4AbMA==", - "dev": true, - "dependencies": { - "async": "^2.6.2", - "debug": "^3.1.1", - "mkdirp": "^0.5.5" - }, - "engines": { - "node": ">= 0.12.0" - } - }, - "node_modules/portfinder/node_modules/debug": { - "version": "3.2.7", - "resolved": "https://registry.npmjs.org/debug/-/debug-3.2.7.tgz", - "integrity": "sha512-CFjzYYAi4ThfiQvizrFQevTTXHtnCqWfe7x1AhgEscTz6ZbLbfoLRLPugTQyBth6f8ZERVUSyWHFD/7Wu4t1XQ==", - "dev": true, - "dependencies": { - "ms": "^2.1.1" - } - }, - "node_modules/portfinder/node_modules/ms": { - "version": "2.1.3", - "resolved": "https://registry.npmjs.org/ms/-/ms-2.1.3.tgz", - "integrity": "sha512-6FlzubTLZG3J2a/NVCAleEhjzq5oxgHyaCU9yYXvcLsvoVaHJq/s5xXI6/XXP6tz7R9xAOtHnSO/tXtF3WRTlA==", - "dev": true - }, - "node_modules/pretty-error": { - "version": "4.0.0", - "resolved": "https://registry.npmjs.org/pretty-error/-/pretty-error-4.0.0.tgz", - "integrity": "sha512-AoJ5YMAcXKYxKhuJGdcvse+Voc6v1RgnsR3nWcYU7q4t6z0Q6T86sv5Zq8VIRbOWWFpvdGE83LtdSMNd+6Y0xw==", - "dev": true, - "dependencies": { - "lodash": "^4.17.20", - "renderkid": "^3.0.0" - } - }, - "node_modules/process": { - "version": "0.11.10", - "resolved": "https://registry.npmjs.org/process/-/process-0.11.10.tgz", - "integrity": "sha512-cdGef/drWFoydD1JsMzuFf8100nZl+GT+yacc2bEced5f9Rjk4z+WtFUTBu9PhOi9j/jfmBPu0mMEY4wIdAF8A==", - "engines": { - "node": ">= 0.6.0" - } - }, - "node_modules/process-nextick-args": { - "version": "2.0.1", - "resolved": "https://registry.npmjs.org/process-nextick-args/-/process-nextick-args-2.0.1.tgz", - "integrity": "sha512-3ouUOpQhtgrbOa17J7+uxOTpITYWaGP7/AhoR3+A+/1e9skrzelGi/dXzEYyvbxubEF6Wn2ypscTKiKJFFn1ag==", - "dev": true - }, - "node_modules/progress": { - "version": "2.0.3", - "resolved": "https://registry.npmjs.org/progress/-/progress-2.0.3.tgz", - "integrity": "sha512-7PiHtLll5LdnKIMw100I+8xJXR5gW2QwWYkT6iJva0bXitZKa/XMrSbdmg3r2Xnaidz9Qumd0VPaMrZlF9V9sA==", - "engines": { - "node": ">=0.4.0" - } - }, - "node_modules/proxy-addr": { - "version": "2.0.7", - "resolved": "https://registry.npmjs.org/proxy-addr/-/proxy-addr-2.0.7.tgz", - "integrity": "sha512-llQsMLSUDUPT44jdrU/O37qlnifitDP+ZwrmmZcoSKyLKvtZxpyV0n2/bD/N4tBAAZ/gJEdZU7KMraoK1+XYAg==", - "dev": true, - "dependencies": { - "forwarded": "0.2.0", - "ipaddr.js": "1.9.1" - }, - "engines": { - "node": ">= 0.10" - } - }, - "node_modules/proxy-addr/node_modules/ipaddr.js": { - "version": "1.9.1", - "resolved": "https://registry.npmjs.org/ipaddr.js/-/ipaddr.js-1.9.1.tgz", - "integrity": "sha512-0KI/607xoxSToH7GjN1FfSbLoU0+btTicjsQSWQlh/hZykN8KpmMf7uYwPW3R+akZ6R/w18ZlXSHBYXiYUPO3g==", - "dev": true, - "engines": { - "node": ">= 0.10" - } - }, - "node_modules/proxy-from-env": { - "version": "1.1.0", - "resolved": "https://registry.npmjs.org/proxy-from-env/-/proxy-from-env-1.1.0.tgz", - "integrity": "sha512-D+zkORCbA9f1tdWRK0RaCR3GPv50cMxcrz4X8k5LTSUD1Dkw47mKJEZQNunItRTkWwgtaUSo1RVFRIG9ZXiFYg==" - }, - "node_modules/public-encrypt": { - "version": "4.0.3", - "resolved": "https://registry.npmjs.org/public-encrypt/-/public-encrypt-4.0.3.tgz", - "integrity": "sha512-zVpa8oKZSz5bTMTFClc1fQOnyyEzpl5ozpi1B5YcvBrdohMjH2rfsBtyXcuNuwjsDIXmBYlF2N5FlJYhR29t8Q==", - "dependencies": { - "bn.js": "^4.1.0", - "browserify-rsa": "^4.0.0", - "create-hash": "^1.1.0", - "parse-asn1": "^5.0.0", - "randombytes": "^2.0.1", - "safe-buffer": "^5.1.2" - } - }, - "node_modules/public-encrypt/node_modules/bn.js": { - "version": "4.12.0", - "resolved": "https://registry.npmjs.org/bn.js/-/bn.js-4.12.0.tgz", - "integrity": "sha512-c98Bf3tPniI+scsdk237ku1Dc3ujXQTSgyiPUDEOe7tRkhrqridvh8klBv0HCEso1OLOYcHuCv/cS6DNxKH+ZA==" - }, - "node_modules/pump": { - "version": "3.0.0", - "resolved": "https://registry.npmjs.org/pump/-/pump-3.0.0.tgz", - "integrity": "sha512-LwZy+p3SFs1Pytd/jYct4wpv49HiYCqd9Rlc5ZVdk0V+8Yzv6jR5Blk3TRmPL1ft69TxP0IMZGJ+WPFU2BFhww==", - "dependencies": { - "end-of-stream": "^1.1.0", - "once": "^1.3.1" - } - }, - "node_modules/punycode": { - "version": "2.1.1", - "resolved": "https://registry.npmjs.org/punycode/-/punycode-2.1.1.tgz", - "integrity": "sha512-XRsRjdf+j5ml+y/6GKHPZbrF/8p2Yga0JPtdqTIY2Xe5ohJPD9saDJJLPvp9+NSBprVvevdXZybnj2cv8OEd0A==", - "engines": { - "node": ">=6" - } - }, - "node_modules/puppeteer-core": { - "version": "15.3.2", - "resolved": "https://registry.npmjs.org/puppeteer-core/-/puppeteer-core-15.3.2.tgz", - "integrity": "sha512-Fmca9UzXmJkRrvGBgUmrffGD2BlulUTfsVefV1+vqfNm4PnlZ/U1bfD6X8XQ0nftyyg520tmSKd81yH3Z2tszg==", - "dependencies": { - "cross-fetch": "3.1.5", - "debug": "4.3.4", - "devtools-protocol": "0.0.1011705", - "extract-zip": "2.0.1", - "https-proxy-agent": "5.0.1", - "pkg-dir": "4.2.0", - "progress": "2.0.3", - "proxy-from-env": "1.1.0", - "rimraf": "3.0.2", - "tar-fs": "2.1.1", - "unbzip2-stream": "1.4.3", - "ws": "8.8.0" - }, - "engines": { - "node": ">=14.1.0" - } - }, - "node_modules/puppeteer-core/node_modules/debug": { - "version": "4.3.4", - "resolved": "https://registry.npmjs.org/debug/-/debug-4.3.4.tgz", - "integrity": "sha512-PRWFHuSU3eDtQJPvnNY7Jcket1j0t5OuOsFzPPzsekD52Zl8qUfFIPEiswXqIvHWGVHOgX+7G/vCNNhehwxfkQ==", - "dependencies": { - "ms": "2.1.2" - }, - "engines": { - "node": ">=6.0" - }, - "peerDependenciesMeta": { - "supports-color": { - "optional": true - } - } - }, - "node_modules/puppeteer-core/node_modules/ms": { - "version": "2.1.2", - "resolved": "https://registry.npmjs.org/ms/-/ms-2.1.2.tgz", - "integrity": "sha512-sGkPx+VjMtmA6MX27oA4FBFELFCZZ4S4XqeGOXCv68tT+jb3vk/RyaKWP0PTKyWtmLSM0b+adUTEvbs1PEaH2w==" - }, - "node_modules/puppeteer-core/node_modules/ws": { - "version": "8.8.0", - "resolved": "https://registry.npmjs.org/ws/-/ws-8.8.0.tgz", - "integrity": "sha512-JDAgSYQ1ksuwqfChJusw1LSJ8BizJ2e/vVu5Lxjq3YvNJNlROv1ui4i+c/kUUrPheBvQl4c5UbERhTwKa6QBJQ==", - "engines": { - "node": ">=10.0.0" - }, - "peerDependencies": { - "bufferutil": "^4.0.1", - "utf-8-validate": "^5.0.2" - }, - "peerDependenciesMeta": { - "bufferutil": { - "optional": true - }, - "utf-8-validate": { - "optional": true - } - } - }, - "node_modules/qs": { - "version": "6.10.3", - "resolved": "https://registry.npmjs.org/qs/-/qs-6.10.3.tgz", - "integrity": "sha512-wr7M2E0OFRfIfJZjKGieI8lBKb7fRCH4Fv5KNPEs7gJ8jadvotdsS08PzOKR7opXhZ/Xkjtt3WF9g38drmyRqQ==", - "dev": true, - "dependencies": { - "side-channel": "^1.0.4" - }, - "engines": { - "node": ">=0.6" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/querystring": { - "version": "0.2.0", - "resolved": "https://registry.npmjs.org/querystring/-/querystring-0.2.0.tgz", - "integrity": "sha512-X/xY82scca2tau62i9mDyU9K+I+djTMUsvwf7xnUX5GLvVzgJybOJf4Y6o9Zx3oJK/LSXg5tTZBjwzqVPaPO2g==", - "deprecated": "The querystring API is considered Legacy. new code should use the URLSearchParams API instead.", - "engines": { - "node": ">=0.4.x" - } - }, - "node_modules/querystring-es3": { - "version": "0.2.1", - "resolved": "https://registry.npmjs.org/querystring-es3/-/querystring-es3-0.2.1.tgz", - "integrity": "sha512-773xhDQnZBMFobEiztv8LIl70ch5MSF/jUQVlhwFyBILqq96anmoctVIYz+ZRp0qbCKATTn6ev02M3r7Ga5vqA==", - "engines": { - "node": ">=0.4.x" - } - }, - "node_modules/queue-microtask": { - "version": "1.2.3", - "resolved": "https://registry.npmjs.org/queue-microtask/-/queue-microtask-1.2.3.tgz", - "integrity": "sha512-NuaNSa6flKT5JaSYQzJok04JzTL1CA6aGhv5rfLW3PgqA+M2ChpZQnAC8h8i4ZFkBS8X5RqkDBHA7r4hej3K9A==", - "dev": true, - "funding": [ - { - "type": "github", - "url": "https://github.com/sponsors/feross" - }, - { - "type": "patreon", - "url": "https://www.patreon.com/feross" - }, - { - "type": "consulting", - "url": "https://feross.org/support" - } - ] - }, - "node_modules/randombytes": { - "version": "2.1.0", - "resolved": "https://registry.npmjs.org/randombytes/-/randombytes-2.1.0.tgz", - "integrity": "sha512-vYl3iOX+4CKUWuxGi9Ukhie6fsqXqS9FE2Zaic4tNFD2N2QQaXOMFbuKK4QmDHC0JO6B1Zp41J0LpT0oR68amQ==", - "dependencies": { - "safe-buffer": "^5.1.0" - } - }, - "node_modules/randomfill": { - "version": "1.0.4", - "resolved": "https://registry.npmjs.org/randomfill/-/randomfill-1.0.4.tgz", - "integrity": "sha512-87lcbR8+MhcWcUiQ+9e+Rwx8MyR2P7qnt15ynUlbm3TU/fjbgz4GsvfSUDTemtCCtVCqb4ZcEFlyPNTh9bBTLw==", - "dependencies": { - "randombytes": "^2.0.5", - "safe-buffer": "^5.1.0" - } - }, - "node_modules/range-parser": { - "version": "1.2.1", - "resolved": "https://registry.npmjs.org/range-parser/-/range-parser-1.2.1.tgz", - "integrity": "sha512-Hrgsx+orqoygnmhFbKaHE6c296J+HTAQXoxEF6gNupROmmGJRoyzfG3ccAveqCBrwr/2yxQ5BVd/GTl5agOwSg==", - "dev": true, - "engines": { - "node": ">= 0.6" - } - }, - "node_modules/raw-body": { - "version": "2.5.1", - "resolved": "https://registry.npmjs.org/raw-body/-/raw-body-2.5.1.tgz", - "integrity": "sha512-qqJBtEyVgS0ZmPGdCFPWJ3FreoqvG4MVQln/kCgF7Olq95IbOp0/BWyMwbdtn4VTvkM8Y7khCQ2Xgk/tcrCXig==", - "dev": true, - "dependencies": { - "bytes": "3.1.2", - "http-errors": "2.0.0", - "iconv-lite": "0.4.24", - "unpipe": "1.0.0" - }, - "engines": { - "node": ">= 0.8" - } - }, - "node_modules/raw-body/node_modules/bytes": { - "version": "3.1.2", - "resolved": "https://registry.npmjs.org/bytes/-/bytes-3.1.2.tgz", - "integrity": "sha512-/Nf7TyzTx6S3yRJObOAV7956r8cr2+Oj8AC5dt8wSP3BQAoeX58NoHyCU8P8zGkNXStjTSi6fzO6F0pBdcYbEg==", - "dev": true, - "engines": { - "node": ">= 0.8" - } - }, - "node_modules/readable-stream": { - "version": "3.6.0", - "resolved": "https://registry.npmjs.org/readable-stream/-/readable-stream-3.6.0.tgz", - "integrity": "sha512-BViHy7LKeTz4oNnkcLJ+lVSL6vpiFeX6/d3oSH8zCW7UxP2onchk+vTGB143xuFjHS3deTgkKoXXymXqymiIdA==", - "dependencies": { - "inherits": "^2.0.3", - "string_decoder": "^1.1.1", - "util-deprecate": "^1.0.1" - }, - "engines": { - "node": ">= 6" - } - }, - "node_modules/readdirp": { - "version": "3.6.0", - "resolved": "https://registry.npmjs.org/readdirp/-/readdirp-3.6.0.tgz", - "integrity": "sha512-hOS089on8RduqdbhvQ5Z37A0ESjsqz6qnRcffsMU3495FuTdqSm+7bhJ29JvIOsBDEEnan5DPu9t3To9VRlMzA==", - "dev": true, - "dependencies": { - "picomatch": "^2.2.1" - }, - "engines": { - "node": ">=8.10.0" - } - }, - "node_modules/rechoir": { - "version": "0.7.1", - "resolved": "https://registry.npmjs.org/rechoir/-/rechoir-0.7.1.tgz", - "integrity": "sha512-/njmZ8s1wVeR6pjTZ+0nCnv8SpZNRMT2D1RLOJQESlYFDBvwpTA4KWJpZ+sBJ4+vhjILRcK7JIFdGCdxEAAitg==", - "dev": true, - "dependencies": { - "resolve": "^1.9.0" - }, - "engines": { - "node": ">= 0.10" - } - }, - "node_modules/reconnecting-websocket": { - "version": "4.4.0", - "resolved": "https://registry.npmjs.org/reconnecting-websocket/-/reconnecting-websocket-4.4.0.tgz", - "integrity": "sha512-D2E33ceRPga0NvTDhJmphEgJ7FUYF0v4lr1ki0csq06OdlxKfugGzN0dSkxM/NfqCxYELK4KcaTOUOjTV6Dcng==" - }, - "node_modules/regexp.prototype.flags": { - "version": "1.4.3", - "resolved": "https://registry.npmjs.org/regexp.prototype.flags/-/regexp.prototype.flags-1.4.3.tgz", - "integrity": "sha512-fjggEOO3slI6Wvgjwflkc4NFRCTZAu5CnNfBd5qOMYhWdn67nJBBu34/TkD++eeFmd8C9r9jfXJ27+nSiRkSUA==", - "dependencies": { - "call-bind": "^1.0.2", - "define-properties": "^1.1.3", - "functions-have-names": "^1.2.2" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/relateurl": { - "version": "0.2.7", - "resolved": "https://registry.npmjs.org/relateurl/-/relateurl-0.2.7.tgz", - "integrity": "sha512-G08Dxvm4iDN3MLM0EsP62EDV9IuhXPR6blNz6Utcp7zyV3tr4HVNINt6MpaRWbxoOHT3Q7YN2P+jaHX8vUbgog==", - "dev": true, - "engines": { - "node": ">= 0.10" - } - }, - "node_modules/remark-footnotes": { - "version": "3.0.0", - "resolved": "https://registry.npmjs.org/remark-footnotes/-/remark-footnotes-3.0.0.tgz", - "integrity": "sha512-ZssAvH9FjGYlJ/PBVKdSmfyPc3Cz4rTWgZLI4iE/SX8Nt5l3o3oEjv3wwG5VD7xOjktzdwp5coac+kJV9l4jgg==", - "dev": true, - "dependencies": { - "mdast-util-footnote": "^0.1.0", - "micromark-extension-footnote": "^0.3.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/unified" - } - }, - "node_modules/remark-frontmatter": { - "version": "3.0.0", - "resolved": "https://registry.npmjs.org/remark-frontmatter/-/remark-frontmatter-3.0.0.tgz", - "integrity": "sha512-mSuDd3svCHs+2PyO29h7iijIZx4plX0fheacJcAoYAASfgzgVIcXGYSq9GFyYocFLftQs8IOmmkgtOovs6d4oA==", - "dev": true, - "dependencies": { - "mdast-util-frontmatter": "^0.2.0", - "micromark-extension-frontmatter": "^0.2.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/unified" - } - }, - "node_modules/remark-gfm": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/remark-gfm/-/remark-gfm-1.0.0.tgz", - "integrity": "sha512-KfexHJCiqvrdBZVbQ6RopMZGwaXz6wFJEfByIuEwGf0arvITHjiKKZ1dpXujjH9KZdm1//XJQwgfnJ3lmXaDPA==", - "dev": true, - "dependencies": { - "mdast-util-gfm": "^0.1.0", - "micromark-extension-gfm": "^0.3.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/unified" - } - }, - "node_modules/remark-parse": { - "version": "9.0.0", - "resolved": "https://registry.npmjs.org/remark-parse/-/remark-parse-9.0.0.tgz", - "integrity": "sha512-geKatMwSzEXKHuzBNU1z676sGcDcFoChMK38TgdHJNAYfFtsfHDQG7MoJAjs6sgYMqyLduCYWDIWZIxiPeafEw==", - "dev": true, - "dependencies": { - "mdast-util-from-markdown": "^0.8.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/unified" - } - }, - "node_modules/renderkid": { - "version": "3.0.0", - "resolved": "https://registry.npmjs.org/renderkid/-/renderkid-3.0.0.tgz", - "integrity": "sha512-q/7VIQA8lmM1hF+jn+sFSPWGlMkSAeNYcPLmDQx2zzuiDfaLrOmumR8iaUKlenFgh0XRPIUeSPlH3A+AW3Z5pg==", - "dev": true, - "dependencies": { - "css-select": "^4.1.3", - "dom-converter": "^0.2.0", - "htmlparser2": "^6.1.0", - "lodash": "^4.17.21", - "strip-ansi": "^6.0.1" - } - }, - "node_modules/repeat-string": { - "version": "1.6.1", - "resolved": "https://registry.npmjs.org/repeat-string/-/repeat-string-1.6.1.tgz", - "integrity": "sha512-PV0dzCYDNfRi1jCDbJzpW7jNNDRuCOG/jI5ctQcGKt/clZD+YcPS3yIlWuTJMmESC8aevCFmWJy5wjAFgNqN6w==", - "dev": true, - "engines": { - "node": ">=0.10" - } - }, - "node_modules/require-from-string": { - "version": "2.0.2", - "resolved": "https://registry.npmjs.org/require-from-string/-/require-from-string-2.0.2.tgz", - "integrity": "sha512-Xf0nWe6RseziFMu+Ap9biiUbmplq6S9/p+7w7YXP/JBHhrUDDUhwa+vANyubuqfZWTveU//DYVGsDG7RKL/vEw==", - "dev": true, - "engines": { - "node": ">=0.10.0" - } - }, - "node_modules/requires-port": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/requires-port/-/requires-port-1.0.0.tgz", - "integrity": "sha512-KigOCHcocU3XODJxsu8i/j8T9tzT4adHiecwORRQ0ZZFcp7ahwXuRU1m+yuO90C5ZUyGeGfocHDI14M3L3yDAQ==", - "dev": true - }, - "node_modules/resolve": { - "version": "1.22.1", - "resolved": "https://registry.npmjs.org/resolve/-/resolve-1.22.1.tgz", - "integrity": "sha512-nBpuuYuY5jFsli/JIs1oldw6fOQCBioohqWZg/2hiaOybXOft4lonv85uDOKXdf8rhyK159cxU5cDcK/NKk8zw==", - "dev": true, - "dependencies": { - "is-core-module": "^2.9.0", - "path-parse": "^1.0.7", - "supports-preserve-symlinks-flag": "^1.0.0" - }, - "bin": { - "resolve": "bin/resolve" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/resolve-cwd": { - "version": "3.0.0", - "resolved": "https://registry.npmjs.org/resolve-cwd/-/resolve-cwd-3.0.0.tgz", - "integrity": "sha512-OrZaX2Mb+rJCpH/6CpSqt9xFVpN++x01XnN2ie9g6P5/3xelLAkXWVADpdz1IHD/KFfEXyE6V0U01OQ3UO2rEg==", - "dev": true, - "dependencies": { - "resolve-from": "^5.0.0" - }, - "engines": { - "node": ">=8" - } - }, - "node_modules/resolve-from": { - "version": "5.0.0", - "resolved": "https://registry.npmjs.org/resolve-from/-/resolve-from-5.0.0.tgz", - "integrity": "sha512-qYg9KP24dD5qka9J47d0aVky0N+b4fTU89LN9iDnjB5waksiC49rvMB0PrUJQGoTmH50XPiqOvAjDfaijGxYZw==", - "dev": true, - "engines": { - "node": ">=8" - } - }, - "node_modules/retry": { - "version": "0.13.1", - "resolved": "https://registry.npmjs.org/retry/-/retry-0.13.1.tgz", - "integrity": "sha512-XQBQ3I8W1Cge0Seh+6gjj03LbmRFWuoszgK9ooCpwYIrhhoO80pfq4cUkU5DkknwfOfFteRwlZ56PYOGYyFWdg==", - "dev": true, - "engines": { - "node": ">= 4" - } - }, - "node_modules/reusify": { - "version": "1.0.4", - "resolved": "https://registry.npmjs.org/reusify/-/reusify-1.0.4.tgz", - "integrity": "sha512-U9nH88a3fc/ekCF1l0/UP1IosiuIjyTh7hBvXVMHYgVcfGvt897Xguj2UOLDeI5BG2m7/uwyaLVT6fbtCwTyzw==", - "dev": true, - "engines": { - "iojs": ">=1.0.0", - "node": ">=0.10.0" - } - }, - "node_modules/rimraf": { - "version": "3.0.2", - "resolved": "https://registry.npmjs.org/rimraf/-/rimraf-3.0.2.tgz", - "integrity": "sha512-JZkJMZkAGFFPP2YqXZXPbMlMBgsxzE8ILs4lMIX/2o0L9UBw9O/Y3o6wFw/i9YLapcUJWwqbi3kdxIPdC62TIA==", - "dependencies": { - "glob": "^7.1.3" - }, - "bin": { - "rimraf": "bin.js" - }, - "funding": { - "url": "https://github.com/sponsors/isaacs" - } - }, - "node_modules/ripemd160": { - "version": "2.0.2", - "resolved": "https://registry.npmjs.org/ripemd160/-/ripemd160-2.0.2.tgz", - "integrity": "sha512-ii4iagi25WusVoiC4B4lq7pbXfAp3D9v5CwfkY33vffw2+pkDjY1D8GaN7spsxvCSx8dkPqOZCEZyfxcmJG2IA==", - "dependencies": { - "hash-base": "^3.0.0", - "inherits": "^2.0.1" - } - }, - "node_modules/run-parallel": { - "version": "1.2.0", - "resolved": "https://registry.npmjs.org/run-parallel/-/run-parallel-1.2.0.tgz", - "integrity": "sha512-5l4VyZR86LZ/lDxZTR6jqL8AFE2S0IFLMP26AbjsLVADxHdhB/c0GUsH+y39UfCi3dzz8OlQuPmnaJOMoDHQBA==", - "dev": true, - "funding": [ - { - "type": "github", - "url": "https://github.com/sponsors/feross" - }, - { - "type": "patreon", - "url": "https://www.patreon.com/feross" - }, - { - "type": "consulting", - "url": "https://feross.org/support" - } - ], - "dependencies": { - "queue-microtask": "^1.2.2" - } - }, - "node_modules/safe-buffer": { - "version": "5.2.1", - "resolved": "https://registry.npmjs.org/safe-buffer/-/safe-buffer-5.2.1.tgz", - "integrity": "sha512-rp3So07KcdmmKbGvgaNxQSJr7bGVSVk5S9Eq1F+ppbRo70+YeaDxkw5Dd8NPN+GD6bjnYm2VuPuCXmpuYvmCXQ==", - "funding": [ - { - "type": "github", - "url": "https://github.com/sponsors/feross" - }, - { - "type": "patreon", - "url": "https://www.patreon.com/feross" - }, - { - "type": "consulting", - "url": "https://feross.org/support" - } - ] - }, - "node_modules/safer-buffer": { - "version": "2.1.2", - "resolved": "https://registry.npmjs.org/safer-buffer/-/safer-buffer-2.1.2.tgz", - "integrity": "sha512-YZo3K82SD7Riyi0E1EQPojLz7kpepnSQI9IyPbHHg1XXXevb5dJI7tpyN2ADxGcQbHG7vcyRHk0cbwqcQriUtg==" - }, - "node_modules/schema-utils": { - "version": "3.1.1", - "resolved": "https://registry.npmjs.org/schema-utils/-/schema-utils-3.1.1.tgz", - "integrity": "sha512-Y5PQxS4ITlC+EahLuXaY86TXfR7Dc5lw294alXOq86JAHCihAIZfqv8nNCWvaEJvaC51uN9hbLGeV0cFBdH+Fw==", - "dependencies": { - "@types/json-schema": "^7.0.8", - "ajv": "^6.12.5", - "ajv-keywords": "^3.5.2" - }, - "engines": { - "node": ">= 10.13.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/webpack" - } - }, - "node_modules/select-hose": { - "version": "2.0.0", - "resolved": "https://registry.npmjs.org/select-hose/-/select-hose-2.0.0.tgz", - "integrity": "sha512-mEugaLK+YfkijB4fx0e6kImuJdCIt2LxCRcbEYPqRGCs4F2ogyfZU5IAZRdjCP8JPq2AtdNoC/Dux63d9Kiryg==", - "dev": true - }, - "node_modules/selfsigned": { - "version": "2.0.1", - "resolved": "https://registry.npmjs.org/selfsigned/-/selfsigned-2.0.1.tgz", - "integrity": "sha512-LmME957M1zOsUhG+67rAjKfiWFox3SBxE/yymatMZsAx+oMrJ0YQ8AToOnyCm7xbeg2ep37IHLxdu0o2MavQOQ==", - "dev": true, - "dependencies": { - "node-forge": "^1" - }, - "engines": { - "node": ">=10" - } - }, - "node_modules/send": { - "version": "0.18.0", - "resolved": "https://registry.npmjs.org/send/-/send-0.18.0.tgz", - "integrity": "sha512-qqWzuOjSFOuqPjFe4NOsMLafToQQwBSOEpS+FwEt3A2V3vKubTquT3vmLTQpFgMXp8AlFWFuP1qKaJZOtPpVXg==", - "dev": true, - "dependencies": { - "debug": "2.6.9", - "depd": "2.0.0", - "destroy": "1.2.0", - "encodeurl": "~1.0.2", - "escape-html": "~1.0.3", - "etag": "~1.8.1", - "fresh": "0.5.2", - "http-errors": "2.0.0", - "mime": "1.6.0", - "ms": "2.1.3", - "on-finished": "2.4.1", - "range-parser": "~1.2.1", - "statuses": "2.0.1" - }, - "engines": { - "node": ">= 0.8.0" - } - }, - "node_modules/send/node_modules/ms": { - "version": "2.1.3", - "resolved": "https://registry.npmjs.org/ms/-/ms-2.1.3.tgz", - "integrity": "sha512-6FlzubTLZG3J2a/NVCAleEhjzq5oxgHyaCU9yYXvcLsvoVaHJq/s5xXI6/XXP6tz7R9xAOtHnSO/tXtF3WRTlA==", - "dev": true - }, - "node_modules/serialize-javascript": { - "version": "6.0.0", - "resolved": "https://registry.npmjs.org/serialize-javascript/-/serialize-javascript-6.0.0.tgz", - "integrity": "sha512-Qr3TosvguFt8ePWqsvRfrKyQXIiW+nGbYpy8XK24NQHE83caxWt+mIymTT19DGFbNWNLfEwsrkSmN64lVWB9ag==", - "dependencies": { - "randombytes": "^2.1.0" - } - }, - "node_modules/serve-index": { - "version": "1.9.1", - "resolved": "https://registry.npmjs.org/serve-index/-/serve-index-1.9.1.tgz", - "integrity": "sha512-pXHfKNP4qujrtteMrSBb0rc8HJ9Ms/GrXwcUtUtD5s4ewDJI8bT3Cz2zTVRMKtri49pLx2e0Ya8ziP5Ya2pZZw==", - "dev": true, - "dependencies": { - "accepts": "~1.3.4", - "batch": "0.6.1", - "debug": "2.6.9", - "escape-html": "~1.0.3", - "http-errors": "~1.6.2", - "mime-types": "~2.1.17", - "parseurl": "~1.3.2" - }, - "engines": { - "node": ">= 0.8.0" - } - }, - "node_modules/serve-index/node_modules/depd": { - "version": "1.1.2", - "resolved": "https://registry.npmjs.org/depd/-/depd-1.1.2.tgz", - "integrity": "sha512-7emPTl6Dpo6JRXOXjLRxck+FlLRX5847cLKEn00PLAgc3g2hTZZgr+e4c2v6QpSmLeFP3n5yUo7ft6avBK/5jQ==", - "dev": true, - "engines": { - "node": ">= 0.6" - } - }, - "node_modules/serve-index/node_modules/http-errors": { - "version": "1.6.3", - "resolved": "https://registry.npmjs.org/http-errors/-/http-errors-1.6.3.tgz", - "integrity": "sha512-lks+lVC8dgGyh97jxvxeYTWQFvh4uw4yC12gVl63Cg30sjPX4wuGcdkICVXDAESr6OJGjqGA8Iz5mkeN6zlD7A==", - "dev": true, - "dependencies": { - "depd": "~1.1.2", - "inherits": "2.0.3", - "setprototypeof": "1.1.0", - "statuses": ">= 1.4.0 < 2" - }, - "engines": { - "node": ">= 0.6" - } - }, - "node_modules/serve-index/node_modules/inherits": { - "version": "2.0.3", - "resolved": "https://registry.npmjs.org/inherits/-/inherits-2.0.3.tgz", - "integrity": "sha512-x00IRNXNy63jwGkJmzPigoySHbaqpNuzKbBOmzK+g2OdZpQ9w+sxCN+VSB3ja7IAge2OP2qpfxTjeNcyjmW1uw==", - "dev": true - }, - "node_modules/serve-index/node_modules/setprototypeof": { - "version": "1.1.0", - "resolved": "https://registry.npmjs.org/setprototypeof/-/setprototypeof-1.1.0.tgz", - "integrity": "sha512-BvE/TwpZX4FXExxOxZyRGQQv651MSwmWKZGqvmPcRIjDqWub67kTKuIMx43cZZrS/cBBzwBcNDWoFxt2XEFIpQ==", - "dev": true - }, - "node_modules/serve-index/node_modules/statuses": { - "version": "1.5.0", - "resolved": "https://registry.npmjs.org/statuses/-/statuses-1.5.0.tgz", - "integrity": "sha512-OpZ3zP+jT1PI7I8nemJX4AKmAX070ZkYPVWV/AaKTJl+tXCTGyVdC1a4SL8RUQYEwk/f34ZX8UTykN68FwrqAA==", - "dev": true, - "engines": { - "node": ">= 0.6" - } - }, - "node_modules/serve-static": { - "version": "1.15.0", - "resolved": "https://registry.npmjs.org/serve-static/-/serve-static-1.15.0.tgz", - "integrity": "sha512-XGuRDNjXUijsUL0vl6nSD7cwURuzEgglbOaFuZM9g3kwDXOWVTck0jLzjPzGD+TazWbboZYu52/9/XPdUgne9g==", - "dev": true, - "dependencies": { - "encodeurl": "~1.0.2", - "escape-html": "~1.0.3", - "parseurl": "~1.3.3", - "send": "0.18.0" - }, - "engines": { - "node": ">= 0.8.0" - } - }, - "node_modules/setimmediate": { - "version": "1.0.5", - "resolved": "https://registry.npmjs.org/setimmediate/-/setimmediate-1.0.5.tgz", - "integrity": "sha512-MATJdZp8sLqDl/68LfQmbP8zKPLQNV6BIZoIgrscFDQ+RsvK/BxeDQOgyxKKoh0y/8h3BqVFnCqQ/gd+reiIXA==" - }, - "node_modules/setprototypeof": { - "version": "1.2.0", - "resolved": "https://registry.npmjs.org/setprototypeof/-/setprototypeof-1.2.0.tgz", - "integrity": "sha512-E5LDX7Wrp85Kil5bhZv46j8jOeboKq5JMmYM3gVGdGH8xFpPWXUMsNrlODCrkoxMEeNi/XZIwuRvY4XNwYMJpw==", - "dev": true - }, - "node_modules/sha.js": { - "version": "2.4.11", - "resolved": "https://registry.npmjs.org/sha.js/-/sha.js-2.4.11.tgz", - "integrity": "sha512-QMEp5B7cftE7APOjk5Y6xgrbWu+WkLVQwk8JNjZ8nKRciZaByEW6MubieAiToS7+dwvrjGhH8jRXz3MVd0AYqQ==", - "dependencies": { - "inherits": "^2.0.1", - "safe-buffer": "^5.0.1" - }, - "bin": { - "sha.js": "bin.js" - } - }, - "node_modules/shallow-clone": { - "version": "3.0.1", - "resolved": "https://registry.npmjs.org/shallow-clone/-/shallow-clone-3.0.1.tgz", - "integrity": "sha512-/6KqX+GVUdqPuPPd2LxDDxzX6CAbjJehAAOKlNpqqUpAqPM6HeL8f+o3a+JsyGjn2lv0WY8UsTgUJjU9Ok55NA==", - "dev": true, - "dependencies": { - "kind-of": "^6.0.2" - }, - "engines": { - "node": ">=8" - } - }, - "node_modules/shebang-command": { - "version": "2.0.0", - "resolved": "https://registry.npmjs.org/shebang-command/-/shebang-command-2.0.0.tgz", - "integrity": "sha512-kHxr2zZpYtdmrN1qDjrrX/Z1rR1kG8Dx+gkpK1G4eXmvXswmcE1hTWBWYUzlraYw1/yZp6YuDY77YtvbN0dmDA==", - "dev": true, - "dependencies": { - "shebang-regex": "^3.0.0" - }, - "engines": { - "node": ">=8" - } - }, - "node_modules/shebang-regex": { - "version": "3.0.0", - "resolved": "https://registry.npmjs.org/shebang-regex/-/shebang-regex-3.0.0.tgz", - "integrity": "sha512-7++dFhtcx3353uBaq8DDR4NuxBetBzC7ZQOhmTQInHEd6bSrXdiEyzCvG07Z44UYdLShWUyXt5M/yhz8ekcb1A==", - "dev": true, - "engines": { - "node": ">=8" - } - }, - "node_modules/side-channel": { - "version": "1.0.4", - "resolved": "https://registry.npmjs.org/side-channel/-/side-channel-1.0.4.tgz", - "integrity": "sha512-q5XPytqFEIKHkGdiMIrY10mvLRvnQh42/+GoBlFW3b2LXLE2xxJpZFdm94we0BaoV3RwJyGqg5wS7epxTv0Zvw==", - "dependencies": { - "call-bind": "^1.0.0", - "get-intrinsic": "^1.0.2", - "object-inspect": "^1.9.0" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/signal-exit": { - "version": "3.0.7", - "resolved": "https://registry.npmjs.org/signal-exit/-/signal-exit-3.0.7.tgz", - "integrity": "sha512-wnD2ZE+l+SPC/uoS0vXeE9L1+0wuaMqKlfz9AMUo38JsyLSBWSFcHR1Rri62LZc12vLr1gb3jl7iwQhgwpAbGQ==", - "dev": true - }, - "node_modules/slash": { - "version": "3.0.0", - "resolved": "https://registry.npmjs.org/slash/-/slash-3.0.0.tgz", - "integrity": "sha512-g9Q1haeby36OSStwb4ntCGGGaKsaVSjQ68fBxoQcutl5fS1vuY18H3wSt3jFyFtrkx+Kz0V1G85A4MyAdDMi2Q==", - "dev": true, - "engines": { - "node": ">=8" - } - }, - "node_modules/sockjs": { - "version": "0.3.24", - "resolved": "https://registry.npmjs.org/sockjs/-/sockjs-0.3.24.tgz", - "integrity": "sha512-GJgLTZ7vYb/JtPSSZ10hsOYIvEYsjbNU+zPdIHcUaWVNUEPivzxku31865sSSud0Da0W4lEeOPlmw93zLQchuQ==", - "dev": true, - "dependencies": { - "faye-websocket": "^0.11.3", - "uuid": "^8.3.2", - "websocket-driver": "^0.7.4" - } - }, - "node_modules/source-map": { - "version": "0.6.1", - "resolved": "https://registry.npmjs.org/source-map/-/source-map-0.6.1.tgz", - "integrity": "sha512-UjgapumWlbMhkBgzT7Ykc5YXUT46F0iKu8SGXq0bcwP5dz/h0Plj6enJqjz1Zbq2l5WaqYnrVbwWOWMyF3F47g==", - "engines": { - "node": ">=0.10.0" - } - }, - "node_modules/source-map-support": { - "version": "0.5.21", - "resolved": "https://registry.npmjs.org/source-map-support/-/source-map-support-0.5.21.tgz", - "integrity": "sha512-uBHU3L3czsIyYXKX88fdrGovxdSCoTGDRZ6SYXtSRxLZUzHg5P/66Ht6uoUlHu9EZod+inXhKo3qQgwXUT/y1w==", - "dependencies": { - "buffer-from": "^1.0.0", - "source-map": "^0.6.0" - } - }, - "node_modules/spdy": { - "version": "4.0.2", - "resolved": "https://registry.npmjs.org/spdy/-/spdy-4.0.2.tgz", - "integrity": "sha512-r46gZQZQV+Kl9oItvl1JZZqJKGr+oEkB08A6BzkiR7593/7IbtuncXHd2YoYeTsG4157ZssMu9KYvUHLcjcDoA==", - "dev": true, - "dependencies": { - "debug": "^4.1.0", - "handle-thing": "^2.0.0", - "http-deceiver": "^1.2.7", - "select-hose": "^2.0.0", - "spdy-transport": "^3.0.0" - }, - "engines": { - "node": ">=6.0.0" - } - }, - "node_modules/spdy-transport": { - "version": "3.0.0", - "resolved": "https://registry.npmjs.org/spdy-transport/-/spdy-transport-3.0.0.tgz", - "integrity": "sha512-hsLVFE5SjA6TCisWeJXFKniGGOpBgMLmerfO2aCyCU5s7nJ/rpAepqmFifv/GCbSbueEeAJJnmSQ2rKC/g8Fcw==", - "dev": true, - "dependencies": { - "debug": "^4.1.0", - "detect-node": "^2.0.4", - "hpack.js": "^2.1.6", - "obuf": "^1.1.2", - "readable-stream": "^3.0.6", - "wbuf": "^1.7.3" - } - }, - "node_modules/spdy-transport/node_modules/debug": { - "version": "4.3.4", - "resolved": "https://registry.npmjs.org/debug/-/debug-4.3.4.tgz", - "integrity": "sha512-PRWFHuSU3eDtQJPvnNY7Jcket1j0t5OuOsFzPPzsekD52Zl8qUfFIPEiswXqIvHWGVHOgX+7G/vCNNhehwxfkQ==", - "dev": true, - "dependencies": { - "ms": "2.1.2" - }, - "engines": { - "node": ">=6.0" - }, - "peerDependenciesMeta": { - "supports-color": { - "optional": true - } - } - }, - "node_modules/spdy-transport/node_modules/ms": { - "version": "2.1.2", - "resolved": "https://registry.npmjs.org/ms/-/ms-2.1.2.tgz", - "integrity": "sha512-sGkPx+VjMtmA6MX27oA4FBFELFCZZ4S4XqeGOXCv68tT+jb3vk/RyaKWP0PTKyWtmLSM0b+adUTEvbs1PEaH2w==", - "dev": true - }, - "node_modules/spdy/node_modules/debug": { - "version": "4.3.4", - "resolved": "https://registry.npmjs.org/debug/-/debug-4.3.4.tgz", - "integrity": "sha512-PRWFHuSU3eDtQJPvnNY7Jcket1j0t5OuOsFzPPzsekD52Zl8qUfFIPEiswXqIvHWGVHOgX+7G/vCNNhehwxfkQ==", - "dev": true, - "dependencies": { - "ms": "2.1.2" - }, - "engines": { - "node": ">=6.0" - }, - "peerDependenciesMeta": { - "supports-color": { - "optional": true - } - } - }, - "node_modules/spdy/node_modules/ms": { - "version": "2.1.2", - "resolved": "https://registry.npmjs.org/ms/-/ms-2.1.2.tgz", - "integrity": "sha512-sGkPx+VjMtmA6MX27oA4FBFELFCZZ4S4XqeGOXCv68tT+jb3vk/RyaKWP0PTKyWtmLSM0b+adUTEvbs1PEaH2w==", - "dev": true - }, - "node_modules/statuses": { - "version": "2.0.1", - "resolved": "https://registry.npmjs.org/statuses/-/statuses-2.0.1.tgz", - "integrity": "sha512-RwNA9Z/7PrK06rYLIzFMlaF+l73iwpzsqRIFgbMLbTcLD6cOao82TaWefPXQvB2fOC4AjuYSEndS7N/mTCbkdQ==", - "dev": true, - "engines": { - "node": ">= 0.8" - } - }, - "node_modules/stream-browserify": { - "version": "3.0.0", - "resolved": "https://registry.npmjs.org/stream-browserify/-/stream-browserify-3.0.0.tgz", - "integrity": "sha512-H73RAHsVBapbim0tU2JwwOiXUj+fikfiaoYAKHF3VJfA0pe2BCzkhAHBlLG6REzE+2WNZcxOXjK7lkso+9euLA==", - "dependencies": { - "inherits": "~2.0.4", - "readable-stream": "^3.5.0" - } - }, - "node_modules/stream-http": { - "version": "3.2.0", - "resolved": "https://registry.npmjs.org/stream-http/-/stream-http-3.2.0.tgz", - "integrity": "sha512-Oq1bLqisTyK3TSCXpPbT4sdeYNdmyZJv1LxpEm2vu1ZhK89kSE5YXwZc3cWk0MagGaKriBh9mCFbVGtO+vY29A==", - "dependencies": { - "builtin-status-codes": "^3.0.0", - "inherits": "^2.0.4", - "readable-stream": "^3.6.0", - "xtend": "^4.0.2" - } - }, - "node_modules/string_decoder": { - "version": "1.3.0", - "resolved": "https://registry.npmjs.org/string_decoder/-/string_decoder-1.3.0.tgz", - "integrity": "sha512-hkRX8U1WjJFd8LsDJ2yQ/wWWxaopEsABU1XfkM8A+j0+85JAGppt16cr1Whg6KIbb4okU6Mql6BOj+uup/wKeA==", - "dependencies": { - "safe-buffer": "~5.2.0" - } - }, - "node_modules/string.prototype.trimend": { - "version": "1.0.5", - "resolved": "https://registry.npmjs.org/string.prototype.trimend/-/string.prototype.trimend-1.0.5.tgz", - "integrity": "sha512-I7RGvmjV4pJ7O3kdf+LXFpVfdNOxtCW/2C8f6jNiW4+PQchwxkCDzlk1/7p+Wl4bqFIZeF47qAHXLuHHWKAxog==", - "dependencies": { - "call-bind": "^1.0.2", - "define-properties": "^1.1.4", - "es-abstract": "^1.19.5" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/string.prototype.trimstart": { - "version": "1.0.5", - "resolved": "https://registry.npmjs.org/string.prototype.trimstart/-/string.prototype.trimstart-1.0.5.tgz", - "integrity": "sha512-THx16TJCGlsN0o6dl2o6ncWUsdgnLRSA23rRE5pyGBw/mLr3Ej/R2LaqCtgP8VNMGZsvMWnf9ooZPyY2bHvUFg==", - "dependencies": { - "call-bind": "^1.0.2", - "define-properties": "^1.1.4", - "es-abstract": "^1.19.5" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/strip-ansi": { - "version": "6.0.1", - "resolved": "https://registry.npmjs.org/strip-ansi/-/strip-ansi-6.0.1.tgz", - "integrity": "sha512-Y38VPSHcqkFrCpFnQ9vuSXmquuv5oXOKpGeT6aGrr3o3Gc9AlVa6JBfUSOCnbxGGZF+/0ooI7KrPuUSztUdU5A==", - "dev": true, - "dependencies": { - "ansi-regex": "^5.0.1" - }, - "engines": { - "node": ">=8" - } - }, - "node_modules/strip-final-newline": { - "version": "2.0.0", - "resolved": "https://registry.npmjs.org/strip-final-newline/-/strip-final-newline-2.0.0.tgz", - "integrity": "sha512-BrpvfNAE3dcvq7ll3xVumzjKjZQ5tI1sEUIKr3Uoks0XUl45St3FlatVqef9prk4jRDzhW6WZg+3bk93y6pLjA==", - "dev": true, - "engines": { - "node": ">=6" - } - }, - "node_modules/supports-color": { - "version": "8.1.1", - "resolved": "https://registry.npmjs.org/supports-color/-/supports-color-8.1.1.tgz", - "integrity": "sha512-MpUEN2OodtUzxvKQl72cUF7RQ5EiHsGvSsVG0ia9c5RbWGL2CI4C7EpPS8UTBIplnlzZiNuV56w+FuNxy3ty2Q==", - "dependencies": { - "has-flag": "^4.0.0" - }, - "engines": { - "node": ">=10" - }, - "funding": { - "url": "https://github.com/chalk/supports-color?sponsor=1" - } - }, - "node_modules/supports-preserve-symlinks-flag": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/supports-preserve-symlinks-flag/-/supports-preserve-symlinks-flag-1.0.0.tgz", - "integrity": "sha512-ot0WnXS9fgdkgIcePe6RHNk1WA8+muPa6cSjeR3V8K27q9BB1rTE3R1p7Hv0z1ZyAc8s6Vvv8DIyWf681MAt0w==", - "dev": true, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/tapable": { - "version": "2.2.1", - "resolved": "https://registry.npmjs.org/tapable/-/tapable-2.2.1.tgz", - "integrity": "sha512-GNzQvQTOIP6RyTfE2Qxb8ZVlNmw0n88vp1szwWRimP02mnTsx3Wtn5qRdqY9w2XduFNUgvOwhNnQsjwCp+kqaQ==", - "engines": { - "node": ">=6" - } - }, - "node_modules/tar-fs": { - "version": "2.1.1", - "resolved": "https://registry.npmjs.org/tar-fs/-/tar-fs-2.1.1.tgz", - "integrity": "sha512-V0r2Y9scmbDRLCNex/+hYzvp/zyYjvFbHPNgVTKfQvVrb6guiE/fxP+XblDNR011utopbkex2nM4dHNV6GDsng==", - "dependencies": { - "chownr": "^1.1.1", - "mkdirp-classic": "^0.5.2", - "pump": "^3.0.0", - "tar-stream": "^2.1.4" - } - }, - "node_modules/tar-stream": { - "version": "2.2.0", - "resolved": "https://registry.npmjs.org/tar-stream/-/tar-stream-2.2.0.tgz", - "integrity": "sha512-ujeqbceABgwMZxEJnk2HDY2DlnUZ+9oEcb1KzTVfYHio0UE6dG71n60d8D2I4qNvleWrrXpmjpt7vZeF1LnMZQ==", - "dependencies": { - "bl": "^4.0.3", - "end-of-stream": "^1.4.1", - "fs-constants": "^1.0.0", - "inherits": "^2.0.3", - "readable-stream": "^3.1.1" - }, - "engines": { - "node": ">=6" - } - }, - "node_modules/terser": { - "version": "5.15.1", - "resolved": "https://registry.npmjs.org/terser/-/terser-5.15.1.tgz", - "integrity": "sha512-K1faMUvpm/FBxjBXud0LWVAGxmvoPbZbfTCYbSgaaYQaIXI3/TdI7a7ZGA73Zrou6Q8Zmz3oeUTsp/dj+ag2Xw==", - "dependencies": { - "@jridgewell/source-map": "^0.3.2", - "acorn": "^8.5.0", - "commander": "^2.20.0", - "source-map-support": "~0.5.20" - }, - "bin": { - "terser": "bin/terser" - }, - "engines": { - "node": ">=10" - } - }, - "node_modules/terser-webpack-plugin": { - "version": "5.3.3", - "resolved": "https://registry.npmjs.org/terser-webpack-plugin/-/terser-webpack-plugin-5.3.3.tgz", - "integrity": "sha512-Fx60G5HNYknNTNQnzQ1VePRuu89ZVYWfjRAeT5rITuCY/1b08s49e5kSQwHDirKZWuoKOBRFS98EUUoZ9kLEwQ==", - "dependencies": { - "@jridgewell/trace-mapping": "^0.3.7", - "jest-worker": "^27.4.5", - "schema-utils": "^3.1.1", - "serialize-javascript": "^6.0.0", - "terser": "^5.7.2" - }, - "engines": { - "node": ">= 10.13.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/webpack" - }, - "peerDependencies": { - "webpack": "^5.1.0" - }, - "peerDependenciesMeta": { - "@swc/core": { - "optional": true - }, - "esbuild": { - "optional": true - }, - "uglify-js": { - "optional": true - } - } - }, - "node_modules/terser/node_modules/commander": { - "version": "2.20.3", - "resolved": "https://registry.npmjs.org/commander/-/commander-2.20.3.tgz", - "integrity": "sha512-GpVkmM8vF2vQUkj2LvZmD35JxeJOLCwJ9cUkugyk2nuhbv3+mJvpLYYt+0+USMxE+oj+ey/lJEnhZw75x/OMcQ==" - }, - "node_modules/through": { - "version": "2.3.8", - "resolved": "https://registry.npmjs.org/through/-/through-2.3.8.tgz", - "integrity": "sha512-w89qg7PI8wAdvX60bMDP+bFoD5Dvhm9oLheFp5O4a2QF0cSBGsBX4qZmadPMvVqlLJBBci+WqGGOAPvcDeNSVg==" - }, - "node_modules/thunky": { - "version": "1.1.0", - "resolved": "https://registry.npmjs.org/thunky/-/thunky-1.1.0.tgz", - "integrity": "sha512-eHY7nBftgThBqOyHGVN+l8gF0BucP09fMo0oO/Lb0w1OF80dJv+lDVpXG60WMQvkcxAkNybKsrEIE3ZtKGmPrA==", - "dev": true - }, - "node_modules/timers-browserify": { - "version": "2.0.12", - "resolved": "https://registry.npmjs.org/timers-browserify/-/timers-browserify-2.0.12.tgz", - "integrity": "sha512-9phl76Cqm6FhSX9Xe1ZUAMLtm1BLkKj2Qd5ApyWkXzsMRaA7dgr81kf4wJmQf/hAvg8EEyJxDo3du/0KlhPiKQ==", - "dependencies": { - "setimmediate": "^1.0.4" - }, - "engines": { - "node": ">=0.6.0" - } - }, - "node_modules/to-regex-range": { - "version": "5.0.1", - "resolved": "https://registry.npmjs.org/to-regex-range/-/to-regex-range-5.0.1.tgz", - "integrity": "sha512-65P7iz6X5yEr1cwcgvQxbbIw7Uk3gOy5dIdtZ4rDveLqhrdJP+Li/Hx6tyK0NEb+2GCyneCMJiGqrADCSNk8sQ==", - "dev": true, - "dependencies": { - "is-number": "^7.0.0" - }, - "engines": { - "node": ">=8.0" - } - }, - "node_modules/toidentifier": { - "version": "1.0.1", - "resolved": "https://registry.npmjs.org/toidentifier/-/toidentifier-1.0.1.tgz", - "integrity": "sha512-o5sSPKEkg/DIQNmH43V0/uerLrpzVedkUh8tGNvaeXpfpuwjKenlSox/2O/BTlZUtEe+JG7s5YhEz608PlAHRA==", - "dev": true, - "engines": { - "node": ">=0.6" - } - }, - "node_modules/traverse": { - "version": "0.6.7", - "resolved": "https://registry.npmjs.org/traverse/-/traverse-0.6.7.tgz", - "integrity": "sha512-/y956gpUo9ZNCb99YjxG7OaslxZWHfCHAUUfshwqOXmxUIvqLjVO581BT+gM59+QV9tFe6/CGG53tsA1Y7RSdg==", - "dev": true, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/trough": { - "version": "1.0.5", - "resolved": "https://registry.npmjs.org/trough/-/trough-1.0.5.tgz", - "integrity": "sha512-rvuRbTarPXmMb79SmzEp8aqXNKcK+y0XaB298IXueQ8I2PsrATcPBCSPyK/dDNa2iWOhKlfNnOjdAOTBU/nkFA==", - "dev": true, - "funding": { - "type": "github", - "url": "https://github.com/sponsors/wooorm" - } - }, - "node_modules/tslib": { - "version": "2.4.0", - "resolved": "https://registry.npmjs.org/tslib/-/tslib-2.4.0.tgz", - "integrity": "sha512-d6xOpEDfsi2CZVlPQzGeux8XMwLT9hssAsaPYExaQMuYskwb+x1x7J371tWlbBdWHroy99KnVB6qIkUbs5X3UQ==", - "dev": true - }, - "node_modules/tty-browserify": { - "version": "0.0.1", - "resolved": "https://registry.npmjs.org/tty-browserify/-/tty-browserify-0.0.1.tgz", - "integrity": "sha512-C3TaO7K81YvjCgQH9Q1S3R3P3BtN3RIM8n+OvX4il1K1zgE8ZhI0op7kClgkxtutIE8hQrcrHBXvIheqKUUCxw==" - }, - "node_modules/type-is": { - "version": "1.6.18", - "resolved": "https://registry.npmjs.org/type-is/-/type-is-1.6.18.tgz", - "integrity": "sha512-TkRKr9sUTxEH8MdfuCSP7VizJyzRNMjj2J2do2Jr3Kym598JVdEksuzPQCnlFPW4ky9Q+iA+ma9BGm06XQBy8g==", - "dev": true, - "dependencies": { - "media-typer": "0.3.0", - "mime-types": "~2.1.24" - }, - "engines": { - "node": ">= 0.6" - } - }, - "node_modules/unbox-primitive": { - "version": "1.0.2", - "resolved": "https://registry.npmjs.org/unbox-primitive/-/unbox-primitive-1.0.2.tgz", - "integrity": "sha512-61pPlCD9h51VoreyJ0BReideM3MDKMKnh6+V9L08331ipq6Q8OFXZYiqP6n/tbHx4s5I9uRhcye6BrbkizkBDw==", - "dependencies": { - "call-bind": "^1.0.2", - "has-bigints": "^1.0.2", - "has-symbols": "^1.0.3", - "which-boxed-primitive": "^1.0.2" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/unbzip2-stream": { - "version": "1.4.3", - "resolved": "https://registry.npmjs.org/unbzip2-stream/-/unbzip2-stream-1.4.3.tgz", - "integrity": "sha512-mlExGW4w71ebDJviH16lQLtZS32VKqsSfk80GCfUlwT/4/hNRFsoscrF/c++9xinkMzECL1uL9DDwXqFWkruPg==", - "dependencies": { - "buffer": "^5.2.1", - "through": "^2.3.8" - } - }, - "node_modules/unbzip2-stream/node_modules/buffer": { - "version": "5.7.1", - "resolved": "https://registry.npmjs.org/buffer/-/buffer-5.7.1.tgz", - "integrity": "sha512-EHcyIPBQ4BSGlvjB16k5KgAJ27CIsHY/2JBmCRReo48y9rQ3MaUzWX3KVlBa4U7MyX02HdVj0K7C3WaB3ju7FQ==", - "funding": [ - { - "type": "github", - "url": "https://github.com/sponsors/feross" - }, - { - "type": "patreon", - "url": "https://www.patreon.com/feross" - }, - { - "type": "consulting", - "url": "https://feross.org/support" - } - ], - "dependencies": { - "base64-js": "^1.3.1", - "ieee754": "^1.1.13" - } - }, - "node_modules/underscore": { - "version": "1.13.6", - "resolved": "https://registry.npmjs.org/underscore/-/underscore-1.13.6.tgz", - "integrity": "sha512-+A5Sja4HP1M08MaXya7p5LvjuM7K6q/2EaC0+iovj/wOcMsTzMvDFbasi/oSapiwOlt252IqsKqPjCl7huKS0A==", - "dev": true - }, - "node_modules/unified": { - "version": "9.2.2", - "resolved": "https://registry.npmjs.org/unified/-/unified-9.2.2.tgz", - "integrity": "sha512-Sg7j110mtefBD+qunSLO1lqOEKdrwBFBrR6Qd8f4uwkhWNlbkaqwHse6e7QvD3AP/MNoJdEDLaf8OxYyoWgorQ==", - "dev": true, - "dependencies": { - "bail": "^1.0.0", - "extend": "^3.0.0", - "is-buffer": "^2.0.0", - "is-plain-obj": "^2.0.0", - "trough": "^1.0.0", - "vfile": "^4.0.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/unified" - } - }, - "node_modules/unified/node_modules/is-plain-obj": { - "version": "2.1.0", - "resolved": "https://registry.npmjs.org/is-plain-obj/-/is-plain-obj-2.1.0.tgz", - "integrity": "sha512-YWnfyRwxL/+SsrWYfOpUtz5b3YD+nyfkHvjbcanzk8zgyO4ASD67uVMRt8k5bM4lLMDnXfriRhOpemw+NfT1eA==", - "dev": true, - "engines": { - "node": ">=8" - } - }, - "node_modules/uniqid": { - "version": "5.4.0", - "resolved": "https://registry.npmjs.org/uniqid/-/uniqid-5.4.0.tgz", - "integrity": "sha512-38JRbJ4Fj94VmnC7G/J/5n5SC7Ab46OM5iNtSstB/ko3l1b5g7ALt4qzHFgGciFkyiRNtDXtLNb+VsxtMSE77A==" - }, - "node_modules/unist-util-is": { - "version": "4.1.0", - "resolved": "https://registry.npmjs.org/unist-util-is/-/unist-util-is-4.1.0.tgz", - "integrity": "sha512-ZOQSsnce92GrxSqlnEEseX0gi7GH9zTJZ0p9dtu87WRb/37mMPO2Ilx1s/t9vBHrFhbgweUwb+t7cIn5dxPhZg==", - "dev": true, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/unified" - } - }, - "node_modules/unist-util-stringify-position": { - "version": "2.0.3", - "resolved": "https://registry.npmjs.org/unist-util-stringify-position/-/unist-util-stringify-position-2.0.3.tgz", - "integrity": "sha512-3faScn5I+hy9VleOq/qNbAd6pAx7iH5jYBMS9I1HgQVijz/4mv5Bvw5iw1sC/90CODiKo81G/ps8AJrISn687g==", - "dev": true, - "dependencies": { - "@types/unist": "^2.0.2" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/unified" - } - }, - "node_modules/unist-util-visit-parents": { - "version": "3.1.1", - "resolved": "https://registry.npmjs.org/unist-util-visit-parents/-/unist-util-visit-parents-3.1.1.tgz", - "integrity": "sha512-1KROIZWo6bcMrZEwiH2UrXDyalAa0uqzWCxCJj6lPOvTve2WkfgCytoDTPaMnodXh1WrXOq0haVYHj99ynJlsg==", - "dev": true, - "dependencies": { - "@types/unist": "^2.0.0", - "unist-util-is": "^4.0.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/unified" - } - }, - "node_modules/unpipe": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/unpipe/-/unpipe-1.0.0.tgz", - "integrity": "sha512-pjy2bYhSsufwWlKwPc+l3cN7+wuJlK6uz0YdJEOlQDbl6jo/YlPi4mb8agUkVC8BF7V8NuzeyPNqRksA3hztKQ==", - "dev": true, - "engines": { - "node": ">= 0.8" - } - }, - "node_modules/update-browserslist-db": { - "version": "1.0.3", - "resolved": "https://registry.npmjs.org/update-browserslist-db/-/update-browserslist-db-1.0.3.tgz", - "integrity": "sha512-ufSazemeh9Gty0qiWtoRpJ9F5Q5W3xdIPm1UZQqYQv/q0Nyb9EMHUB2lu+O9x1re9WsorpMAUu4Y6Lxcs5n+XQ==", - "funding": [ - { - "type": "opencollective", - "url": "https://opencollective.com/browserslist" - }, - { - "type": "tidelift", - "url": "https://tidelift.com/funding/github/npm/browserslist" - } - ], - "dependencies": { - "escalade": "^3.1.1", - "picocolors": "^1.0.0" - }, - "bin": { - "browserslist-lint": "cli.js" - }, - "peerDependencies": { - "browserslist": ">= 4.21.0" - } - }, - "node_modules/update-section": { - "version": "0.3.3", - "resolved": "https://registry.npmjs.org/update-section/-/update-section-0.3.3.tgz", - "integrity": "sha512-BpRZMZpgXLuTiKeiu7kK0nIPwGdyrqrs6EDSaXtjD/aQ2T+qVo9a5hRC3HN3iJjCMxNT/VxoLGQ7E/OzE5ucnw==", - "dev": true - }, - "node_modules/uri-js": { - "version": "4.4.1", - "resolved": "https://registry.npmjs.org/uri-js/-/uri-js-4.4.1.tgz", - "integrity": "sha512-7rKUyy33Q1yc98pQ1DAmLtwX109F7TIfWlW1Ydo8Wl1ii1SeHieeh0HHfPeL2fMXK6z0s8ecKs9frCuLJvndBg==", - "dependencies": { - "punycode": "^2.1.0" - } - }, - "node_modules/url": { - "version": "0.11.0", - "resolved": "https://registry.npmjs.org/url/-/url-0.11.0.tgz", - "integrity": "sha512-kbailJa29QrtXnxgq+DdCEGlbTeYM2eJUxsz6vjZavrCYPMIFHMKQmSKYAIuUK2i7hgPm28a8piX5NTUtM/LKQ==", - "dependencies": { - "punycode": "1.3.2", - "querystring": "0.2.0" - } - }, - "node_modules/url/node_modules/punycode": { - "version": "1.3.2", - "resolved": "https://registry.npmjs.org/punycode/-/punycode-1.3.2.tgz", - "integrity": "sha512-RofWgt/7fL5wP1Y7fxE7/EmTLzQVnB0ycyibJ0OOHIlJqTNzglYFxVwETOcIoJqJmpDXJ9xImDv+Fq34F/d4Dw==" - }, - "node_modules/util": { - "version": "0.12.4", - "resolved": "https://registry.npmjs.org/util/-/util-0.12.4.tgz", - "integrity": "sha512-bxZ9qtSlGUWSOy9Qa9Xgk11kSslpuZwaxCg4sNIDj6FLucDab2JxnHwyNTCpHMtK1MjoQiWQ6DiUMZYbSrO+Sw==", - "dependencies": { - "inherits": "^2.0.3", - "is-arguments": "^1.0.4", - "is-generator-function": "^1.0.7", - "is-typed-array": "^1.1.3", - "safe-buffer": "^5.1.2", - "which-typed-array": "^1.1.2" - } - }, - "node_modules/util-deprecate": { - "version": "1.0.2", - "resolved": "https://registry.npmjs.org/util-deprecate/-/util-deprecate-1.0.2.tgz", - "integrity": "sha512-EPD5q1uXyFxJpCrLnCc1nHnq3gOa6DZBocAIiI2TaSCA7VCJ1UJDMagCzIkXNsUYfD1daK//LTEQ8xiIbrHtcw==" - }, - "node_modules/utila": { - "version": "0.4.0", - "resolved": "https://registry.npmjs.org/utila/-/utila-0.4.0.tgz", - "integrity": "sha512-Z0DbgELS9/L/75wZbro8xAnT50pBVFQZ+hUEueGDU5FN51YSCYM+jdxsfCiHjwNP/4LCDD0i/graKpeBnOXKRA==", - "dev": true - }, - "node_modules/utils-merge": { - "version": "1.0.1", - "resolved": "https://registry.npmjs.org/utils-merge/-/utils-merge-1.0.1.tgz", - "integrity": "sha512-pMZTvIkT1d+TFGvDOqodOclx0QWkkgi6Tdoa8gC8ffGAAqz9pzPTZWAybbsHHoED/ztMtkv/VoYTYyShUn81hA==", - "dev": true, - "engines": { - "node": ">= 0.4.0" - } - }, - "node_modules/uuid": { - "version": "8.3.2", - "resolved": "https://registry.npmjs.org/uuid/-/uuid-8.3.2.tgz", - "integrity": "sha512-+NYs2QeMWy+GWFOEm9xnn6HCDp0l7QBD7ml8zLUmJ+93Q5NF0NocErnwkTkXVFNiX3/fpC6afS8Dhb/gz7R7eg==", - "dev": true, - "bin": { - "uuid": "dist/bin/uuid" - } - }, - "node_modules/vary": { - "version": "1.1.2", - "resolved": "https://registry.npmjs.org/vary/-/vary-1.1.2.tgz", - "integrity": "sha512-BNGbWLfd0eUPabhkXUVm0j8uuvREyTh5ovRa/dyow/BqAbZJyC+5fU+IzQOzmAKzYqYRAISoRhdQr3eIZ/PXqg==", - "dev": true, - "engines": { - "node": ">= 0.8" - } - }, - "node_modules/vfile": { - "version": "4.2.1", - "resolved": "https://registry.npmjs.org/vfile/-/vfile-4.2.1.tgz", - "integrity": "sha512-O6AE4OskCG5S1emQ/4gl8zK586RqA3srz3nfK/Viy0UPToBc5Trp9BVFb1u0CjsKrAWwnpr4ifM/KBXPWwJbCA==", - "dev": true, - "dependencies": { - "@types/unist": "^2.0.0", - "is-buffer": "^2.0.0", - "unist-util-stringify-position": "^2.0.0", - "vfile-message": "^2.0.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/unified" - } - }, - "node_modules/vfile-message": { - "version": "2.0.4", - "resolved": "https://registry.npmjs.org/vfile-message/-/vfile-message-2.0.4.tgz", - "integrity": "sha512-DjssxRGkMvifUOJre00juHoP9DPWuzjxKuMDrhNbk2TdaYYBNMStsNhEOt3idrtI12VQYM/1+iM0KOzXi4pxwQ==", - "dev": true, - "dependencies": { - "@types/unist": "^2.0.0", - "unist-util-stringify-position": "^2.0.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/unified" - } - }, - "node_modules/vm-browserify": { - "version": "1.1.2", - "resolved": "https://registry.npmjs.org/vm-browserify/-/vm-browserify-1.1.2.tgz", - "integrity": "sha512-2ham8XPWTONajOR0ohOKOHXkm3+gaBmGut3SRuu75xLd/RRaY6vqgh8NBYYk7+RW3u5AtzPQZG8F10LHkl0lAQ==" - }, - "node_modules/watchpack": { - "version": "2.3.1", - "resolved": "https://registry.npmjs.org/watchpack/-/watchpack-2.3.1.tgz", - "integrity": "sha512-x0t0JuydIo8qCNctdDrn1OzH/qDzk2+rdCOC3YzumZ42fiMqmQ7T3xQurykYMhYfHaPHTp4ZxAx2NfUo1K6QaA==", - "dependencies": { - "glob-to-regexp": "^0.4.1", - "graceful-fs": "^4.1.2" - }, - "engines": { - "node": ">=10.13.0" - } - }, - "node_modules/wbuf": { - "version": "1.7.3", - "resolved": "https://registry.npmjs.org/wbuf/-/wbuf-1.7.3.tgz", - "integrity": "sha512-O84QOnr0icsbFGLS0O3bI5FswxzRr8/gHwWkDlQFskhSPryQXvrTMxjxGP4+iWYoauLoBvfDpkrOauZ+0iZpDA==", - "dev": true, - "dependencies": { - "minimalistic-assert": "^1.0.0" - } - }, - "node_modules/webpack": { - "version": "5.67.0", - "resolved": "https://registry.npmjs.org/webpack/-/webpack-5.67.0.tgz", - "integrity": "sha512-LjFbfMh89xBDpUMgA1W9Ur6Rn/gnr2Cq1jjHFPo4v6a79/ypznSYbAyPgGhwsxBtMIaEmDD1oJoA7BEYw/Fbrw==", - "dependencies": { - "@types/eslint-scope": "^3.7.0", - "@types/estree": "^0.0.50", - "@webassemblyjs/ast": "1.11.1", - "@webassemblyjs/wasm-edit": "1.11.1", - "@webassemblyjs/wasm-parser": "1.11.1", - "acorn": "^8.4.1", - "acorn-import-assertions": "^1.7.6", - "browserslist": "^4.14.5", - "chrome-trace-event": "^1.0.2", - "enhanced-resolve": "^5.8.3", - "es-module-lexer": "^0.9.0", - "eslint-scope": "5.1.1", - "events": "^3.2.0", - "glob-to-regexp": "^0.4.1", - "graceful-fs": "^4.2.9", - "json-parse-better-errors": "^1.0.2", - "loader-runner": "^4.2.0", - "mime-types": "^2.1.27", - "neo-async": "^2.6.2", - "schema-utils": "^3.1.0", - "tapable": "^2.1.1", - "terser-webpack-plugin": "^5.1.3", - "watchpack": "^2.3.1", - "webpack-sources": "^3.2.3" - }, - "bin": { - "webpack": "bin/webpack.js" - }, - "engines": { - "node": ">=10.13.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/webpack" - }, - "peerDependenciesMeta": { - "webpack-cli": { - "optional": true - } - } - }, - "node_modules/webpack-cli": { - "version": "4.10.0", - "resolved": "https://registry.npmjs.org/webpack-cli/-/webpack-cli-4.10.0.tgz", - "integrity": "sha512-NLhDfH/h4O6UOy+0LSso42xvYypClINuMNBVVzX4vX98TmTaTUxwRbXdhucbFMd2qLaCTcLq/PdYrvi8onw90w==", - "dev": true, - "dependencies": { - "@discoveryjs/json-ext": "^0.5.0", - "@webpack-cli/configtest": "^1.2.0", - "@webpack-cli/info": "^1.5.0", - "@webpack-cli/serve": "^1.7.0", - "colorette": "^2.0.14", - "commander": "^7.0.0", - "cross-spawn": "^7.0.3", - "fastest-levenshtein": "^1.0.12", - "import-local": "^3.0.2", - "interpret": "^2.2.0", - "rechoir": "^0.7.0", - "webpack-merge": "^5.7.3" - }, - "bin": { - "webpack-cli": "bin/cli.js" - }, - "engines": { - "node": ">=10.13.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/webpack" - }, - "peerDependencies": { - "webpack": "4.x.x || 5.x.x" - }, - "peerDependenciesMeta": { - "@webpack-cli/generators": { - "optional": true - }, - "@webpack-cli/migrate": { - "optional": true - }, - "webpack-bundle-analyzer": { - "optional": true - }, - "webpack-dev-server": { - "optional": true - } - } - }, - "node_modules/webpack-cli/node_modules/commander": { - "version": "7.2.0", - "resolved": "https://registry.npmjs.org/commander/-/commander-7.2.0.tgz", - "integrity": "sha512-QrWXB+ZQSVPmIWIhtEO9H+gwHaMGYiF5ChvoJ+K9ZGHG/sVsa6yiesAD1GC/x46sET00Xlwo1u49RVVVzvcSkw==", - "dev": true, - "engines": { - "node": ">= 10" - } - }, - "node_modules/webpack-dev-middleware": { - "version": "5.3.3", - "resolved": "https://registry.npmjs.org/webpack-dev-middleware/-/webpack-dev-middleware-5.3.3.tgz", - "integrity": "sha512-hj5CYrY0bZLB+eTO+x/j67Pkrquiy7kWepMHmUMoPsmcUaeEnQJqFzHJOyxgWlq746/wUuA64p9ta34Kyb01pA==", - "dev": true, - "dependencies": { - "colorette": "^2.0.10", - "memfs": "^3.4.3", - "mime-types": "^2.1.31", - "range-parser": "^1.2.1", - "schema-utils": "^4.0.0" - }, - "engines": { - "node": ">= 12.13.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/webpack" - }, - "peerDependencies": { - "webpack": "^4.0.0 || ^5.0.0" - } - }, - "node_modules/webpack-dev-middleware/node_modules/ajv": { - "version": "8.11.0", - "resolved": "https://registry.npmjs.org/ajv/-/ajv-8.11.0.tgz", - "integrity": "sha512-wGgprdCvMalC0BztXvitD2hC04YffAvtsUn93JbGXYLAtCUO4xd17mCCZQxUOItiBwZvJScWo8NIvQMQ71rdpg==", - "dev": true, - "dependencies": { - "fast-deep-equal": "^3.1.1", - "json-schema-traverse": "^1.0.0", - "require-from-string": "^2.0.2", - "uri-js": "^4.2.2" - }, - "funding": { - "type": "github", - "url": "https://github.com/sponsors/epoberezkin" - } - }, - "node_modules/webpack-dev-middleware/node_modules/ajv-keywords": { - "version": "5.1.0", - "resolved": "https://registry.npmjs.org/ajv-keywords/-/ajv-keywords-5.1.0.tgz", - "integrity": "sha512-YCS/JNFAUyr5vAuhk1DWm1CBxRHW9LbJ2ozWeemrIqpbsqKjHVxYPyi5GC0rjZIT5JxJ3virVTS8wk4i/Z+krw==", - "dev": true, - "dependencies": { - "fast-deep-equal": "^3.1.3" - }, - "peerDependencies": { - "ajv": "^8.8.2" - } - }, - "node_modules/webpack-dev-middleware/node_modules/json-schema-traverse": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/json-schema-traverse/-/json-schema-traverse-1.0.0.tgz", - "integrity": "sha512-NM8/P9n3XjXhIZn1lLhkFaACTOURQXjWhV4BA/RnOv8xvgqtqpAX9IO4mRQxSx1Rlo4tqzeqb0sOlruaOy3dug==", - "dev": true - }, - "node_modules/webpack-dev-middleware/node_modules/schema-utils": { - "version": "4.0.0", - "resolved": "https://registry.npmjs.org/schema-utils/-/schema-utils-4.0.0.tgz", - "integrity": "sha512-1edyXKgh6XnJsJSQ8mKWXnN/BVaIbFMLpouRUrXgVq7WYne5kw3MW7UPhO44uRXQSIpTSXoJbmrR2X0w9kUTyg==", - "dev": true, - "dependencies": { - "@types/json-schema": "^7.0.9", - "ajv": "^8.8.0", - "ajv-formats": "^2.1.1", - "ajv-keywords": "^5.0.0" - }, - "engines": { - "node": ">= 12.13.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/webpack" - } - }, - "node_modules/webpack-dev-server": { - "version": "4.7.4", - "resolved": "https://registry.npmjs.org/webpack-dev-server/-/webpack-dev-server-4.7.4.tgz", - "integrity": "sha512-nfdsb02Zi2qzkNmgtZjkrMOcXnYZ6FLKcQwpxT7MvmHKc+oTtDsBju8j+NMyAygZ9GW1jMEUpy3itHtqgEhe1A==", - "dev": true, - "dependencies": { - "@types/bonjour": "^3.5.9", - "@types/connect-history-api-fallback": "^1.3.5", - "@types/express": "^4.17.13", - "@types/serve-index": "^1.9.1", - "@types/sockjs": "^0.3.33", - "@types/ws": "^8.2.2", - "ansi-html-community": "^0.0.8", - "bonjour": "^3.5.0", - "chokidar": "^3.5.3", - "colorette": "^2.0.10", - "compression": "^1.7.4", - "connect-history-api-fallback": "^1.6.0", - "default-gateway": "^6.0.3", - "del": "^6.0.0", - "express": "^4.17.1", - "graceful-fs": "^4.2.6", - "html-entities": "^2.3.2", - "http-proxy-middleware": "^2.0.0", - "ipaddr.js": "^2.0.1", - "open": "^8.0.9", - "p-retry": "^4.5.0", - "portfinder": "^1.0.28", - "schema-utils": "^4.0.0", - "selfsigned": "^2.0.0", - "serve-index": "^1.9.1", - "sockjs": "^0.3.21", - "spdy": "^4.0.2", - "strip-ansi": "^7.0.0", - "webpack-dev-middleware": "^5.3.1", - "ws": "^8.4.2" - }, - "bin": { - "webpack-dev-server": "bin/webpack-dev-server.js" - }, - "engines": { - "node": ">= 12.13.0" - }, - "peerDependencies": { - "webpack": "^4.37.0 || ^5.0.0" - }, - "peerDependenciesMeta": { - "webpack-cli": { - "optional": true - } - } - }, - "node_modules/webpack-dev-server/node_modules/ajv": { - "version": "8.11.0", - "resolved": "https://registry.npmjs.org/ajv/-/ajv-8.11.0.tgz", - "integrity": "sha512-wGgprdCvMalC0BztXvitD2hC04YffAvtsUn93JbGXYLAtCUO4xd17mCCZQxUOItiBwZvJScWo8NIvQMQ71rdpg==", - "dev": true, - "dependencies": { - "fast-deep-equal": "^3.1.1", - "json-schema-traverse": "^1.0.0", - "require-from-string": "^2.0.2", - "uri-js": "^4.2.2" - }, - "funding": { - "type": "github", - "url": "https://github.com/sponsors/epoberezkin" - } - }, - "node_modules/webpack-dev-server/node_modules/ajv-keywords": { - "version": "5.1.0", - "resolved": "https://registry.npmjs.org/ajv-keywords/-/ajv-keywords-5.1.0.tgz", - "integrity": "sha512-YCS/JNFAUyr5vAuhk1DWm1CBxRHW9LbJ2ozWeemrIqpbsqKjHVxYPyi5GC0rjZIT5JxJ3virVTS8wk4i/Z+krw==", - "dev": true, - "dependencies": { - "fast-deep-equal": "^3.1.3" - }, - "peerDependencies": { - "ajv": "^8.8.2" - } - }, - "node_modules/webpack-dev-server/node_modules/ansi-regex": { - "version": "6.0.1", - "resolved": "https://registry.npmjs.org/ansi-regex/-/ansi-regex-6.0.1.tgz", - "integrity": "sha512-n5M855fKb2SsfMIiFFoVrABHJC8QtHwVx+mHWP3QcEqBHYienj5dHSgjbxtC0WEZXYt4wcD6zrQElDPhFuZgfA==", - "dev": true, - "engines": { - "node": ">=12" - }, - "funding": { - "url": "https://github.com/chalk/ansi-regex?sponsor=1" - } - }, - "node_modules/webpack-dev-server/node_modules/json-schema-traverse": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/json-schema-traverse/-/json-schema-traverse-1.0.0.tgz", - "integrity": "sha512-NM8/P9n3XjXhIZn1lLhkFaACTOURQXjWhV4BA/RnOv8xvgqtqpAX9IO4mRQxSx1Rlo4tqzeqb0sOlruaOy3dug==", - "dev": true - }, - "node_modules/webpack-dev-server/node_modules/schema-utils": { - "version": "4.0.0", - "resolved": "https://registry.npmjs.org/schema-utils/-/schema-utils-4.0.0.tgz", - "integrity": "sha512-1edyXKgh6XnJsJSQ8mKWXnN/BVaIbFMLpouRUrXgVq7WYne5kw3MW7UPhO44uRXQSIpTSXoJbmrR2X0w9kUTyg==", - "dev": true, - "dependencies": { - "@types/json-schema": "^7.0.9", - "ajv": "^8.8.0", - "ajv-formats": "^2.1.1", - "ajv-keywords": "^5.0.0" - }, - "engines": { - "node": ">= 12.13.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/webpack" - } - }, - "node_modules/webpack-dev-server/node_modules/strip-ansi": { - "version": "7.0.1", - "resolved": "https://registry.npmjs.org/strip-ansi/-/strip-ansi-7.0.1.tgz", - "integrity": "sha512-cXNxvT8dFNRVfhVME3JAe98mkXDYN2O1l7jmcwMnOslDeESg1rF/OZMtK0nRAhiari1unG5cD4jG3rapUAkLbw==", - "dev": true, - "dependencies": { - "ansi-regex": "^6.0.1" - }, - "engines": { - "node": ">=12" - }, - "funding": { - "url": "https://github.com/chalk/strip-ansi?sponsor=1" - } - }, - "node_modules/webpack-dev-server/node_modules/ws": { - "version": "8.6.0", - "resolved": "https://registry.npmjs.org/ws/-/ws-8.6.0.tgz", - "integrity": "sha512-AzmM3aH3gk0aX7/rZLYvjdvZooofDu3fFOzGqcSnQ1tOcTWwhM/o+q++E8mAyVVIyUdajrkzWUGftaVSDLn1bw==", - "dev": true, - "engines": { - "node": ">=10.0.0" - }, - "peerDependencies": { - "bufferutil": "^4.0.1", - "utf-8-validate": "^5.0.2" - }, - "peerDependenciesMeta": { - "bufferutil": { - "optional": true - }, - "utf-8-validate": { - "optional": true - } - } - }, - "node_modules/webpack-merge": { - "version": "5.8.0", - "resolved": "https://registry.npmjs.org/webpack-merge/-/webpack-merge-5.8.0.tgz", - "integrity": "sha512-/SaI7xY0831XwP6kzuwhKWVKDP9t1QY1h65lAFLbZqMPIuYcD9QAW4u9STIbU9kaJbPBB/geU/gLr1wDjOhQ+Q==", - "dev": true, - "dependencies": { - "clone-deep": "^4.0.1", - "wildcard": "^2.0.0" - }, - "engines": { - "node": ">=10.0.0" - } - }, - "node_modules/webpack-sources": { - "version": "3.2.3", - "resolved": "https://registry.npmjs.org/webpack-sources/-/webpack-sources-3.2.3.tgz", - "integrity": "sha512-/DyMEOrDgLKKIG0fmvtz+4dUX/3Ghozwgm6iPp8KRhvn+eQf9+Q7GWxVNMk3+uCPWfdXYC4ExGBckIXdFEfH1w==", - "engines": { - "node": ">=10.13.0" - } - }, - "node_modules/websocket-driver": { - "version": "0.7.4", - "resolved": "https://registry.npmjs.org/websocket-driver/-/websocket-driver-0.7.4.tgz", - "integrity": "sha512-b17KeDIQVjvb0ssuSDF2cYXSg2iztliJ4B9WdsuB6J952qCPKmnVq4DyW5motImXHDC1cBT/1UezrJVsKw5zjg==", - "dev": true, - "dependencies": { - "http-parser-js": ">=0.5.1", - "safe-buffer": ">=5.1.0", - "websocket-extensions": ">=0.1.1" - }, - "engines": { - "node": ">=0.8.0" - } - }, - "node_modules/websocket-extensions": { - "version": "0.1.4", - "resolved": "https://registry.npmjs.org/websocket-extensions/-/websocket-extensions-0.1.4.tgz", - "integrity": "sha512-OqedPIGOfsDlo31UNwYbCFMSaO9m9G/0faIHj5/dZFDMFqPTcx6UwqyOy3COEaEOg/9VsGIpdqn62W5KhoKSpg==", - "dev": true, - "engines": { - "node": ">=0.8.0" - } - }, - "node_modules/which": { - "version": "2.0.2", - "resolved": "https://registry.npmjs.org/which/-/which-2.0.2.tgz", - "integrity": "sha512-BLI3Tl1TW3Pvl70l3yq3Y64i+awpwXqsGBYWkkqMtnbXgrMD+yj7rhW0kuEDxzJaYXGjEW5ogapKNMEKNMjibA==", - "dev": true, - "dependencies": { - "isexe": "^2.0.0" - }, - "bin": { - "node-which": "bin/node-which" - }, - "engines": { - "node": ">= 8" - } - }, - "node_modules/which-boxed-primitive": { - "version": "1.0.2", - "resolved": "https://registry.npmjs.org/which-boxed-primitive/-/which-boxed-primitive-1.0.2.tgz", - "integrity": "sha512-bwZdv0AKLpplFY2KZRX6TvyuN7ojjr7lwkg6ml0roIy9YeuSr7JS372qlNW18UQYzgYK9ziGcerWqZOmEn9VNg==", - "dependencies": { - "is-bigint": "^1.0.1", - "is-boolean-object": "^1.1.0", - "is-number-object": "^1.0.4", - "is-string": "^1.0.5", - "is-symbol": "^1.0.3" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/which-typed-array": { - "version": "1.1.8", - "resolved": "https://registry.npmjs.org/which-typed-array/-/which-typed-array-1.1.8.tgz", - "integrity": "sha512-Jn4e5PItbcAHyLoRDwvPj1ypu27DJbtdYXUa5zsinrUx77Uvfb0cXwwnGMTn7cjUfhhqgVQnVJCwF+7cgU7tpw==", - "dependencies": { - "available-typed-arrays": "^1.0.5", - "call-bind": "^1.0.2", - "es-abstract": "^1.20.0", - "for-each": "^0.3.3", - "has-tostringtag": "^1.0.0", - "is-typed-array": "^1.1.9" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/wildcard": { - "version": "2.0.0", - "resolved": "https://registry.npmjs.org/wildcard/-/wildcard-2.0.0.tgz", - "integrity": "sha512-JcKqAHLPxcdb9KM49dufGXn2x3ssnfjbcaQdLlfZsL9rH9wgDQjUtDxbo8NE0F6SFvydeu1VhZe7hZuHsB2/pw==", - "dev": true - }, - "node_modules/wrappy": { - "version": "1.0.2", - "resolved": "https://registry.npmjs.org/wrappy/-/wrappy-1.0.2.tgz", - "integrity": "sha1-tSQ9jz7BqjXxNkYFvA0QNuMKtp8=" - }, - "node_modules/ws": { - "version": "8.4.0", - "resolved": "https://registry.npmjs.org/ws/-/ws-8.4.0.tgz", - "integrity": "sha512-IHVsKe2pjajSUIl4KYMQOdlyliovpEPquKkqbwswulszzI7r0SfQrxnXdWAEqOlDCLrVSJzo+O1hAwdog2sKSQ==", - "engines": { - "node": ">=10.0.0" - }, - "peerDependencies": { - "bufferutil": "^4.0.1", - "utf-8-validate": "^5.0.2" - }, - "peerDependenciesMeta": { - "bufferutil": { - "optional": true - }, - "utf-8-validate": { - "optional": true - } - } - }, - "node_modules/xhr2": { - "version": "0.2.1", - "resolved": "https://registry.npmjs.org/xhr2/-/xhr2-0.2.1.tgz", - "integrity": "sha512-sID0rrVCqkVNUn8t6xuv9+6FViXjUVXq8H5rWOH2rz9fDNQEd4g0EA2XlcEdJXRz5BMEn4O1pJFdT+z4YHhoWw==", - "engines": { - "node": ">= 6" - } - }, - "node_modules/xtend": { - "version": "4.0.2", - "resolved": "https://registry.npmjs.org/xtend/-/xtend-4.0.2.tgz", - "integrity": "sha512-LKYU1iAXJXUgAXn9URjiu+MWhyUXHsvfp7mcuYm9dSUKK0/CjtrUwFAxD82/mCWbtLsGjFIad0wIsod4zrTAEQ==", - "engines": { - "node": ">=0.4" - } - }, - "node_modules/yauzl": { - "version": "2.10.0", - "resolved": "https://registry.npmjs.org/yauzl/-/yauzl-2.10.0.tgz", - "integrity": "sha512-p4a9I6X6nu6IhoGmBqAcbJy1mlC4j27vEPZX9F4L4/vZT3Lyq1VkFHw/V/PUcB9Buo+DG3iHkT0x3Qya58zc3g==", - "dependencies": { - "buffer-crc32": "~0.2.3", - "fd-slicer": "~1.1.0" - } - }, - "node_modules/zwitch": { - "version": "1.0.5", - "resolved": "https://registry.npmjs.org/zwitch/-/zwitch-1.0.5.tgz", - "integrity": "sha512-V50KMwwzqJV0NpZIZFwfOD5/lyny3WlSzRiXgA0G7VUnRlqttta1L6UQIHzd6EuBY/cHGfwTIck7w1yH6Q5zUw==", - "dev": true, - "funding": { - "type": "github", - "url": "https://github.com/sponsors/wooorm" - } - } - }, "dependencies": { "@discoveryjs/json-ext": { "version": "0.5.7", @@ -6606,6 +34,7 @@ "version": "0.3.2", "resolved": "https://registry.npmjs.org/@jridgewell/gen-mapping/-/gen-mapping-0.3.2.tgz", "integrity": "sha512-mh65xKQAzI6iBcFzwv28KVWSmCkdRBWoOh+bYQGW3+6OZvbbN3TqMGo5hqYxQniRcH9F2VZIoJCm4pa3BPDK/A==", + "dev": true, "requires": { "@jridgewell/set-array": "^1.0.1", "@jridgewell/sourcemap-codec": "^1.4.10", @@ -6615,17 +44,20 @@ "@jridgewell/resolve-uri": { "version": "3.0.7", "resolved": "https://registry.npmjs.org/@jridgewell/resolve-uri/-/resolve-uri-3.0.7.tgz", - "integrity": "sha512-8cXDaBBHOr2pQ7j77Y6Vp5VDT2sIqWyWQ56TjEq4ih/a4iST3dItRe8Q9fp0rrIl9DoKhWQtUQz/YpOxLkXbNA==" + "integrity": "sha512-8cXDaBBHOr2pQ7j77Y6Vp5VDT2sIqWyWQ56TjEq4ih/a4iST3dItRe8Q9fp0rrIl9DoKhWQtUQz/YpOxLkXbNA==", + "dev": true }, "@jridgewell/set-array": { "version": "1.1.2", "resolved": "https://registry.npmjs.org/@jridgewell/set-array/-/set-array-1.1.2.tgz", - "integrity": "sha512-xnkseuNADM0gt2bs+BvhO0p78Mk762YnZdsuzFV018NoG1Sj1SCQvpSqa7XUaTam5vAGasABV9qXASMKnFMwMw==" + "integrity": "sha512-xnkseuNADM0gt2bs+BvhO0p78Mk762YnZdsuzFV018NoG1Sj1SCQvpSqa7XUaTam5vAGasABV9qXASMKnFMwMw==", + "dev": true }, "@jridgewell/source-map": { "version": "0.3.2", "resolved": "https://registry.npmjs.org/@jridgewell/source-map/-/source-map-0.3.2.tgz", "integrity": "sha512-m7O9o2uR8k2ObDysZYzdfhb08VuEml5oWGiosa1VdaPZ/A6QyPkAJuwN0Q1lhULOf6B7MtQmHENS743hWtCrgw==", + "dev": true, "requires": { "@jridgewell/gen-mapping": "^0.3.0", "@jridgewell/trace-mapping": "^0.3.9" @@ -6634,12 +66,14 @@ "@jridgewell/sourcemap-codec": { "version": "1.4.13", "resolved": "https://registry.npmjs.org/@jridgewell/sourcemap-codec/-/sourcemap-codec-1.4.13.tgz", - "integrity": "sha512-GryiOJmNcWbovBxTfZSF71V/mXbgcV3MewDe3kIMCLyIh5e7SKAeUZs+rMnJ8jkMolZ/4/VsdBmMrw3l+VdZ3w==" + "integrity": "sha512-GryiOJmNcWbovBxTfZSF71V/mXbgcV3MewDe3kIMCLyIh5e7SKAeUZs+rMnJ8jkMolZ/4/VsdBmMrw3l+VdZ3w==", + "dev": true }, "@jridgewell/trace-mapping": { "version": "0.3.13", "resolved": "https://registry.npmjs.org/@jridgewell/trace-mapping/-/trace-mapping-0.3.13.tgz", "integrity": "sha512-o1xbKhp9qnIAoHJSWd6KlCZfqslL4valSF81H8ImioOAxluWYWOpWkpyktY2vnt4tbrX9XYaxovq6cgowaJp2w==", + "dev": true, "requires": { "@jridgewell/resolve-uri": "^3.0.3", "@jridgewell/sourcemap-codec": "^1.4.10" @@ -6766,6 +200,7 @@ "version": "8.4.3", "resolved": "https://registry.npmjs.org/@types/eslint/-/eslint-8.4.3.tgz", "integrity": "sha512-YP1S7YJRMPs+7KZKDb9G63n8YejIwW9BALq7a5j2+H4yl6iOv9CB29edho+cuFRrvmJbbaH2yiVChKLJVysDGw==", + "dev": true, "requires": { "@types/estree": "*", "@types/json-schema": "*" @@ -6775,6 +210,7 @@ "version": "3.7.3", "resolved": "https://registry.npmjs.org/@types/eslint-scope/-/eslint-scope-3.7.3.tgz", "integrity": "sha512-PB3ldyrcnAicT35TWPs5IcwKD8S333HMaa2VVv4+wdvebJkjWuW/xESoB8IwRcog8HYVYamb1g/R31Qv5Bx03g==", + "dev": true, "requires": { "@types/eslint": "*", "@types/estree": "*" @@ -6783,7 +219,8 @@ "@types/estree": { "version": "0.0.50", "resolved": "https://registry.npmjs.org/@types/estree/-/estree-0.0.50.tgz", - "integrity": "sha512-C6N5s2ZFtuZRj54k2/zyRhNDjJwwcViAM3Nbm8zjBpbqAdZ00mr0CFxvSKeO8Y/e03WVFLpQMdHYVfUd6SB+Hw==" + "integrity": "sha512-C6N5s2ZFtuZRj54k2/zyRhNDjJwwcViAM3Nbm8zjBpbqAdZ00mr0CFxvSKeO8Y/e03WVFLpQMdHYVfUd6SB+Hw==", + "dev": true }, "@types/express": { "version": "4.17.13", @@ -6826,7 +263,8 @@ "@types/json-schema": { "version": "7.0.11", "resolved": "https://registry.npmjs.org/@types/json-schema/-/json-schema-7.0.11.tgz", - "integrity": "sha512-wOuvG1SN4Us4rez+tylwwwCV1psiNVOkJeM3AUWUNWg/jDQY2+HE/444y5gc+jBmRqASOm2Oeh5c1axHobwRKQ==" + "integrity": "sha512-wOuvG1SN4Us4rez+tylwwwCV1psiNVOkJeM3AUWUNWg/jDQY2+HE/444y5gc+jBmRqASOm2Oeh5c1axHobwRKQ==", + "dev": true }, "@types/mdast": { "version": "3.0.10", @@ -6922,6 +360,7 @@ "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/ast/-/ast-1.11.1.tgz", "integrity": "sha512-ukBh14qFLjxTQNTXocdyksN5QdM28S1CxHt2rdskFyL+xFV7VremuBLVbmCePj+URalXBENx/9Lm7lnhihtCSw==", + "dev": true, "requires": { "@webassemblyjs/helper-numbers": "1.11.1", "@webassemblyjs/helper-wasm-bytecode": "1.11.1" @@ -6930,22 +369,26 @@ "@webassemblyjs/floating-point-hex-parser": { "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/floating-point-hex-parser/-/floating-point-hex-parser-1.11.1.tgz", - "integrity": "sha512-iGRfyc5Bq+NnNuX8b5hwBrRjzf0ocrJPI6GWFodBFzmFnyvrQ83SHKhmilCU/8Jv67i4GJZBMhEzltxzcNagtQ==" + "integrity": "sha512-iGRfyc5Bq+NnNuX8b5hwBrRjzf0ocrJPI6GWFodBFzmFnyvrQ83SHKhmilCU/8Jv67i4GJZBMhEzltxzcNagtQ==", + "dev": true }, "@webassemblyjs/helper-api-error": { "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/helper-api-error/-/helper-api-error-1.11.1.tgz", - "integrity": "sha512-RlhS8CBCXfRUR/cwo2ho9bkheSXG0+NwooXcc3PAILALf2QLdFyj7KGsKRbVc95hZnhnERon4kW/D3SZpp6Tcg==" + "integrity": "sha512-RlhS8CBCXfRUR/cwo2ho9bkheSXG0+NwooXcc3PAILALf2QLdFyj7KGsKRbVc95hZnhnERon4kW/D3SZpp6Tcg==", + "dev": true }, "@webassemblyjs/helper-buffer": { "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/helper-buffer/-/helper-buffer-1.11.1.tgz", - "integrity": "sha512-gwikF65aDNeeXa8JxXa2BAk+REjSyhrNC9ZwdT0f8jc4dQQeDQ7G4m0f2QCLPJiMTTO6wfDmRmj/pW0PsUvIcA==" + "integrity": "sha512-gwikF65aDNeeXa8JxXa2BAk+REjSyhrNC9ZwdT0f8jc4dQQeDQ7G4m0f2QCLPJiMTTO6wfDmRmj/pW0PsUvIcA==", + "dev": true }, "@webassemblyjs/helper-numbers": { "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/helper-numbers/-/helper-numbers-1.11.1.tgz", "integrity": "sha512-vDkbxiB8zfnPdNK9Rajcey5C0w+QJugEglN0of+kmO8l7lDb77AnlKYQF7aarZuCrv+l0UvqL+68gSDr3k9LPQ==", + "dev": true, "requires": { "@webassemblyjs/floating-point-hex-parser": "1.11.1", "@webassemblyjs/helper-api-error": "1.11.1", @@ -6955,12 +398,14 @@ "@webassemblyjs/helper-wasm-bytecode": { "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/helper-wasm-bytecode/-/helper-wasm-bytecode-1.11.1.tgz", - "integrity": "sha512-PvpoOGiJwXeTrSf/qfudJhwlvDQxFgelbMqtq52WWiXC6Xgg1IREdngmPN3bs4RoO83PnL/nFrxucXj1+BX62Q==" + "integrity": "sha512-PvpoOGiJwXeTrSf/qfudJhwlvDQxFgelbMqtq52WWiXC6Xgg1IREdngmPN3bs4RoO83PnL/nFrxucXj1+BX62Q==", + "dev": true }, "@webassemblyjs/helper-wasm-section": { "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/helper-wasm-section/-/helper-wasm-section-1.11.1.tgz", "integrity": "sha512-10P9No29rYX1j7F3EVPX3JvGPQPae+AomuSTPiF9eBQeChHI6iqjMIwR9JmOJXwpnn/oVGDk7I5IlskuMwU/pg==", + "dev": true, "requires": { "@webassemblyjs/ast": "1.11.1", "@webassemblyjs/helper-buffer": "1.11.1", @@ -6972,6 +417,7 @@ "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/ieee754/-/ieee754-1.11.1.tgz", "integrity": "sha512-hJ87QIPtAMKbFq6CGTkZYJivEwZDbQUgYd3qKSadTNOhVY7p+gfP6Sr0lLRVTaG1JjFj+r3YchoqRYxNH3M0GQ==", + "dev": true, "requires": { "@xtuc/ieee754": "^1.2.0" } @@ -6980,6 +426,7 @@ "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/leb128/-/leb128-1.11.1.tgz", "integrity": "sha512-BJ2P0hNZ0u+Th1YZXJpzW6miwqQUGcIHT1G/sf72gLVD9DZ5AdYTqPNbHZh6K1M5VmKvFXwGSWZADz+qBWxeRw==", + "dev": true, "requires": { "@xtuc/long": "4.2.2" } @@ -6987,12 +434,14 @@ "@webassemblyjs/utf8": { "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/utf8/-/utf8-1.11.1.tgz", - "integrity": "sha512-9kqcxAEdMhiwQkHpkNiorZzqpGrodQQ2IGrHHxCy+Ozng0ofyMA0lTqiLkVs1uzTRejX+/O0EOT7KxqVPuXosQ==" + "integrity": "sha512-9kqcxAEdMhiwQkHpkNiorZzqpGrodQQ2IGrHHxCy+Ozng0ofyMA0lTqiLkVs1uzTRejX+/O0EOT7KxqVPuXosQ==", + "dev": true }, "@webassemblyjs/wasm-edit": { "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/wasm-edit/-/wasm-edit-1.11.1.tgz", "integrity": "sha512-g+RsupUC1aTHfR8CDgnsVRVZFJqdkFHpsHMfJuWQzWU3tvnLC07UqHICfP+4XyL2tnr1amvl1Sdp06TnYCmVkA==", + "dev": true, "requires": { "@webassemblyjs/ast": "1.11.1", "@webassemblyjs/helper-buffer": "1.11.1", @@ -7008,6 +457,7 @@ "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/wasm-gen/-/wasm-gen-1.11.1.tgz", "integrity": "sha512-F7QqKXwwNlMmsulj6+O7r4mmtAlCWfO/0HdgOxSklZfQcDu0TpLiD1mRt/zF25Bk59FIjEuGAIyn5ei4yMfLhA==", + "dev": true, "requires": { "@webassemblyjs/ast": "1.11.1", "@webassemblyjs/helper-wasm-bytecode": "1.11.1", @@ -7020,6 +470,7 @@ "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/wasm-opt/-/wasm-opt-1.11.1.tgz", "integrity": "sha512-VqnkNqnZlU5EB64pp1l7hdm3hmQw7Vgqa0KF/KCNO9sIpI6Fk6brDEiX+iCOYrvMuBWDws0NkTOxYEb85XQHHw==", + "dev": true, "requires": { "@webassemblyjs/ast": "1.11.1", "@webassemblyjs/helper-buffer": "1.11.1", @@ -7031,6 +482,7 @@ "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/wasm-parser/-/wasm-parser-1.11.1.tgz", "integrity": "sha512-rrBujw+dJu32gYB7/Lup6UhdkPx9S9SnobZzRVL7VcBH9Bt9bCBLEuX/YXOOtBsOZ4NQrRykKhffRWHvigQvOA==", + "dev": true, "requires": { "@webassemblyjs/ast": "1.11.1", "@webassemblyjs/helper-api-error": "1.11.1", @@ -7044,6 +496,7 @@ "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/wast-printer/-/wast-printer-1.11.1.tgz", "integrity": "sha512-IQboUWM4eKzWW+N/jij2sRatKMh99QEelo3Eb2q0qXkvPRISAj8Qxtmw5itwqK+TTkBuUIE45AxYPToqPtL5gg==", + "dev": true, "requires": { "@webassemblyjs/ast": "1.11.1", "@xtuc/long": "4.2.2" @@ -7053,8 +506,7 @@ "version": "1.2.0", "resolved": "https://registry.npmjs.org/@webpack-cli/configtest/-/configtest-1.2.0.tgz", "integrity": "sha512-4FB8Tj6xyVkyqjj1OaTqCjXYULB9FMkqQ8yGrZjRDrYh0nOE+7Lhs45WioWQQMV+ceFlE368Ukhe6xdvJM9Egg==", - "dev": true, - "requires": {} + "dev": true }, "@webpack-cli/info": { "version": "1.5.0", @@ -7069,18 +521,19 @@ "version": "1.7.0", "resolved": "https://registry.npmjs.org/@webpack-cli/serve/-/serve-1.7.0.tgz", "integrity": "sha512-oxnCNGj88fL+xzV+dacXs44HcDwf1ovs3AuEzvP7mqXw7fQntqIhQ1BRmynh4qEKQSSSRSWVyXRjmTbZIX9V2Q==", - "dev": true, - "requires": {} + "dev": true }, "@xtuc/ieee754": { "version": "1.2.0", "resolved": "https://registry.npmjs.org/@xtuc/ieee754/-/ieee754-1.2.0.tgz", - "integrity": "sha512-DX8nKgqcGwsc0eJSqYt5lwP4DH5FlHnmuWWBRy7X0NcaGR0ZtuyeESgMwTYVEtxmsNGY+qit4QYT/MIYTOTPeA==" + "integrity": "sha512-DX8nKgqcGwsc0eJSqYt5lwP4DH5FlHnmuWWBRy7X0NcaGR0ZtuyeESgMwTYVEtxmsNGY+qit4QYT/MIYTOTPeA==", + "dev": true }, "@xtuc/long": { "version": "4.2.2", "resolved": "https://registry.npmjs.org/@xtuc/long/-/long-4.2.2.tgz", - "integrity": "sha512-NuHqBY1PB/D8xU6s/thBgOAiAP7HOYDQ32+BFZILJ8ivkUkAHQnWfn6WhL79Owj1qmUnoN/YPhktdIoucipkAQ==" + "integrity": "sha512-NuHqBY1PB/D8xU6s/thBgOAiAP7HOYDQ32+BFZILJ8ivkUkAHQnWfn6WhL79Owj1qmUnoN/YPhktdIoucipkAQ==", + "dev": true }, "accepts": { "version": "1.3.8", @@ -7095,13 +548,14 @@ "acorn": { "version": "8.7.1", "resolved": "https://registry.npmjs.org/acorn/-/acorn-8.7.1.tgz", - "integrity": "sha512-Xx54uLJQZ19lKygFXOWsscKUbsBZW0CPykPhVQdhIeIwrbPmJzqeASDInc8nKBnp/JT6igTs82qPXz069H8I/A==" + "integrity": "sha512-Xx54uLJQZ19lKygFXOWsscKUbsBZW0CPykPhVQdhIeIwrbPmJzqeASDInc8nKBnp/JT6igTs82qPXz069H8I/A==", + "dev": true }, "acorn-import-assertions": { "version": "1.8.0", "resolved": "https://registry.npmjs.org/acorn-import-assertions/-/acorn-import-assertions-1.8.0.tgz", "integrity": "sha512-m7VZ3jwz4eK6A4Vtt8Ew1/mNbP24u0FhdyfA7fSvnJR6LMdfOYnmuIrrJAgrYfYJ10F/otaHTtrtrtmHdMNzEw==", - "requires": {} + "dev": true }, "agent-base": { "version": "6.0.2", @@ -7140,6 +594,7 @@ "version": "6.12.6", "resolved": "https://registry.npmjs.org/ajv/-/ajv-6.12.6.tgz", "integrity": "sha512-j3fVLgvTo527anyYyJOGTYJbG+vnnQYvE0m5mmkc1TK+nxAppkCLMIL0aZ4dblVCNoGShhm+kzE4ZUykBoMg4g==", + "dev": true, "requires": { "fast-deep-equal": "^3.1.1", "fast-json-stable-stringify": "^2.0.0", @@ -7180,7 +635,7 @@ "version": "3.5.2", "resolved": "https://registry.npmjs.org/ajv-keywords/-/ajv-keywords-3.5.2.tgz", "integrity": "sha512-5p6WTN0DdTGVQk6VjcEju19IgaHudalcfabD7yhDGeA6bcQnmL+CpveLJq/3hvfwd1aof6L386Ougkx6RfyMIQ==", - "requires": {} + "dev": true }, "anchor-markdown-header": { "version": "0.6.0", @@ -7489,6 +944,7 @@ "version": "4.21.0", "resolved": "https://registry.npmjs.org/browserslist/-/browserslist-4.21.0.tgz", "integrity": "sha512-UQxE0DIhRB5z/zDz9iA03BOfxaN2+GQdBYH/2WrSIWEUrnpzTPJbhqt+umq6r3acaPRTW1FNTkrcp0PXgtFkvA==", + "dev": true, "requires": { "caniuse-lite": "^1.0.30001358", "electron-to-chromium": "^1.4.164", @@ -7513,7 +969,8 @@ "buffer-from": { "version": "1.1.2", "resolved": "https://registry.npmjs.org/buffer-from/-/buffer-from-1.1.2.tgz", - "integrity": "sha512-E+XQCRwSbaaiChtv6k6Dwgc+bx+Bs6vuKJHHl5kox/BaKbhiXzqQOwK4cO22yElGp2OCmjwVhT3HmxgyPGnJfQ==" + "integrity": "sha512-E+XQCRwSbaaiChtv6k6Dwgc+bx+Bs6vuKJHHl5kox/BaKbhiXzqQOwK4cO22yElGp2OCmjwVhT3HmxgyPGnJfQ==", + "dev": true }, "buffer-indexof": { "version": "1.1.1", @@ -7567,7 +1024,8 @@ "caniuse-lite": { "version": "1.0.30001358", "resolved": "https://registry.npmjs.org/caniuse-lite/-/caniuse-lite-1.0.30001358.tgz", - "integrity": "sha512-hvp8PSRymk85R20bsDra7ZTCpSVGN/PAz9pSAjPSjKC+rNmnUk5vCRgJwiTT/O4feQ/yu/drvZYpKxxhbFuChw==" + "integrity": "sha512-hvp8PSRymk85R20bsDra7ZTCpSVGN/PAz9pSAjPSjKC+rNmnUk5vCRgJwiTT/O4feQ/yu/drvZYpKxxhbFuChw==", + "dev": true }, "ccount": { "version": "1.1.0", @@ -7617,7 +1075,8 @@ "chrome-trace-event": { "version": "1.0.3", "resolved": "https://registry.npmjs.org/chrome-trace-event/-/chrome-trace-event-1.0.3.tgz", - "integrity": "sha512-p3KULyQg4S7NIHixdwbGX+nFHkoBiA4YQmyWtjb8XngSKV124nJmRysgAeujbUVb15vh+RvFUfCPqU7rXk+hZg==" + "integrity": "sha512-p3KULyQg4S7NIHixdwbGX+nFHkoBiA4YQmyWtjb8XngSKV124nJmRysgAeujbUVb15vh+RvFUfCPqU7rXk+hZg==", + "dev": true }, "cipher-base": { "version": "1.0.4", @@ -8099,7 +1558,8 @@ "electron-to-chromium": { "version": "1.4.167", "resolved": "https://registry.npmjs.org/electron-to-chromium/-/electron-to-chromium-1.4.167.tgz", - "integrity": "sha512-lPHuHXBwpkr4RcfaZBKm6TKOWG/1N9mVggUpP4fY3l1JIUU2x4fkM8928smYdZ5lF+6KCTAxo1aK9JmqT+X71Q==" + "integrity": "sha512-lPHuHXBwpkr4RcfaZBKm6TKOWG/1N9mVggUpP4fY3l1JIUU2x4fkM8928smYdZ5lF+6KCTAxo1aK9JmqT+X71Q==", + "dev": true }, "elliptic": { "version": "6.5.4", @@ -8146,6 +1606,7 @@ "version": "5.9.3", "resolved": "https://registry.npmjs.org/enhanced-resolve/-/enhanced-resolve-5.9.3.tgz", "integrity": "sha512-Bq9VSor+kjvW3f9/MiiR4eE3XYgOl7/rS8lnSxbRbF3kS0B2r+Y9w5krBWxZgDxASVZbdYrn5wT4j/Wb0J9qow==", + "dev": true, "requires": { "graceful-fs": "^4.2.4", "tapable": "^2.2.0" @@ -8196,7 +1657,8 @@ "es-module-lexer": { "version": "0.9.3", "resolved": "https://registry.npmjs.org/es-module-lexer/-/es-module-lexer-0.9.3.tgz", - "integrity": "sha512-1HQ2M2sPtxwnvOvT1ZClHyQDiggdNjURWpY2we6aMKCQiUVxTmVs2UYPLIrD84sS+kMdUwfBSylbJPwNnBrnHQ==" + "integrity": "sha512-1HQ2M2sPtxwnvOvT1ZClHyQDiggdNjURWpY2we6aMKCQiUVxTmVs2UYPLIrD84sS+kMdUwfBSylbJPwNnBrnHQ==", + "dev": true }, "es-to-primitive": { "version": "1.2.1", @@ -8216,7 +1678,8 @@ "escalade": { "version": "3.1.1", "resolved": "https://registry.npmjs.org/escalade/-/escalade-3.1.1.tgz", - "integrity": "sha512-k0er2gUkLf8O0zKJiAhmkTnJlTvINGv7ygDNPbeIsX/TJjGJZHuh9B2UxbsaEkmlEo9MfhrSzmhIlhRlI2GXnw==" + "integrity": "sha512-k0er2gUkLf8O0zKJiAhmkTnJlTvINGv7ygDNPbeIsX/TJjGJZHuh9B2UxbsaEkmlEo9MfhrSzmhIlhRlI2GXnw==", + "dev": true }, "escape-html": { "version": "1.0.3", @@ -8234,6 +1697,7 @@ "version": "5.1.1", "resolved": "https://registry.npmjs.org/eslint-scope/-/eslint-scope-5.1.1.tgz", "integrity": "sha512-2NxwbF/hZ0KpepYN0cNbo+FN6XoK7GaHlQhgx/hIZl6Va0bF45RQOOwhLIy8lQDbuCiadSLCBnH2CFYquit5bw==", + "dev": true, "requires": { "esrecurse": "^4.3.0", "estraverse": "^4.1.1" @@ -8243,6 +1707,7 @@ "version": "4.3.0", "resolved": "https://registry.npmjs.org/esrecurse/-/esrecurse-4.3.0.tgz", "integrity": "sha512-KmfKL3b6G+RXvP8N1vr3Tq1kL/oCFgn2NYXEtqP8/L3pKapUA4G8cFVaoF3SU323CD4XypR/ffioHmkti6/Tag==", + "dev": true, "requires": { "estraverse": "^5.2.0" }, @@ -8250,14 +1715,16 @@ "estraverse": { "version": "5.3.0", "resolved": "https://registry.npmjs.org/estraverse/-/estraverse-5.3.0.tgz", - "integrity": "sha512-MMdARuVEQziNTeJD8DgMqmhwR11BRQ/cBP+pLtYdSTnf3MIO8fFeiINEbX36ZdNlfU/7A9f3gUw49B3oQsvwBA==" + "integrity": "sha512-MMdARuVEQziNTeJD8DgMqmhwR11BRQ/cBP+pLtYdSTnf3MIO8fFeiINEbX36ZdNlfU/7A9f3gUw49B3oQsvwBA==", + "dev": true } } }, "estraverse": { "version": "4.3.0", "resolved": "https://registry.npmjs.org/estraverse/-/estraverse-4.3.0.tgz", - "integrity": "sha512-39nnKffWz8xN1BU/2c79n9nB9HDzo0niYUqx6xyqUnyoAnQyyWpOTdZEeiCch8BBu515t4wp9ZmgVfVhn9EBpw==" + "integrity": "sha512-39nnKffWz8xN1BU/2c79n9nB9HDzo0niYUqx6xyqUnyoAnQyyWpOTdZEeiCch8BBu515t4wp9ZmgVfVhn9EBpw==", + "dev": true }, "etag": { "version": "1.8.1", @@ -8392,7 +1859,8 @@ "fast-deep-equal": { "version": "3.1.3", "resolved": "https://registry.npmjs.org/fast-deep-equal/-/fast-deep-equal-3.1.3.tgz", - "integrity": "sha512-f3qQ9oQy9j2AhBe/H9VC91wLmKBCCU/gDOnKNAYG5hswO7BLKj09Hc5HYNz9cGI++xlpDCIgDaitVs03ATR84Q==" + "integrity": "sha512-f3qQ9oQy9j2AhBe/H9VC91wLmKBCCU/gDOnKNAYG5hswO7BLKj09Hc5HYNz9cGI++xlpDCIgDaitVs03ATR84Q==", + "dev": true }, "fast-glob": { "version": "3.2.11", @@ -8410,7 +1878,8 @@ "fast-json-stable-stringify": { "version": "2.1.0", "resolved": "https://registry.npmjs.org/fast-json-stable-stringify/-/fast-json-stable-stringify-2.1.0.tgz", - "integrity": "sha512-lhd/wF+Lk98HZoTCtlVraHtfh5XYijIjalXck7saUtuanSDyLMxnHhSXEDJqHxD7msR8D0uCmqlkwjCV8xvwHw==" + "integrity": "sha512-lhd/wF+Lk98HZoTCtlVraHtfh5XYijIjalXck7saUtuanSDyLMxnHhSXEDJqHxD7msR8D0uCmqlkwjCV8xvwHw==", + "dev": true }, "fastest-levenshtein": { "version": "1.0.14", @@ -8617,7 +2086,8 @@ "glob-to-regexp": { "version": "0.4.1", "resolved": "https://registry.npmjs.org/glob-to-regexp/-/glob-to-regexp-0.4.1.tgz", - "integrity": "sha512-lkX1HJXwyMcprw/5YUZc2s7DrpAiHB21/V+E1rHUrVNokkvB6bqMzT0VfV6/86ZNabt1k14YOIaT7nDvOX3Iiw==" + "integrity": "sha512-lkX1HJXwyMcprw/5YUZc2s7DrpAiHB21/V+E1rHUrVNokkvB6bqMzT0VfV6/86ZNabt1k14YOIaT7nDvOX3Iiw==", + "dev": true }, "globby": { "version": "11.1.0", @@ -8636,7 +2106,8 @@ "graceful-fs": { "version": "4.2.10", "resolved": "https://registry.npmjs.org/graceful-fs/-/graceful-fs-4.2.10.tgz", - "integrity": "sha512-9ByhssR2fPVsNZj478qUUbKfmL0+t5BDVyjShtyZZLiK7ZDAArFFfopyOTj0M05wE2tJPisA4iTnnXl2YoPvOA==" + "integrity": "sha512-9ByhssR2fPVsNZj478qUUbKfmL0+t5BDVyjShtyZZLiK7ZDAArFFfopyOTj0M05wE2tJPisA4iTnnXl2YoPvOA==", + "dev": true }, "handle-thing": { "version": "2.0.1", @@ -8660,7 +2131,8 @@ "has-flag": { "version": "4.0.0", "resolved": "https://registry.npmjs.org/has-flag/-/has-flag-4.0.0.tgz", - "integrity": "sha512-EykJT/Q1KjTWctppgIAgfSO0tKVuZUjhgMr17kqTumMl6Afv3EISleU7qZUzoXDFTAHTDC4NOoG/ZxU3EvlMPQ==" + "integrity": "sha512-EykJT/Q1KjTWctppgIAgfSO0tKVuZUjhgMr17kqTumMl6Afv3EISleU7qZUzoXDFTAHTDC4NOoG/ZxU3EvlMPQ==", + "dev": true }, "has-property-descriptors": { "version": "1.0.0", @@ -9235,6 +2707,7 @@ "version": "27.5.1", "resolved": "https://registry.npmjs.org/jest-worker/-/jest-worker-27.5.1.tgz", "integrity": "sha512-7vuh85V5cdDofPyxn58nrPjBktZo0u9x1g8WtjQol+jZDaE+fhN+cIvTj11GndBnMnyfrUOG1sZQxCdjKh+DKg==", + "dev": true, "requires": { "@types/node": "*", "merge-stream": "^2.0.0", @@ -9244,12 +2717,14 @@ "json-parse-better-errors": { "version": "1.0.2", "resolved": "https://registry.npmjs.org/json-parse-better-errors/-/json-parse-better-errors-1.0.2.tgz", - "integrity": "sha512-mrqyZKfX5EhL7hvqcV6WG1yYjnjeuYDzDhhcAAUrq8Po85NBQBJP+ZDUT75qZQ98IkUoBqdkExkukOU7Ts2wrw==" + "integrity": "sha512-mrqyZKfX5EhL7hvqcV6WG1yYjnjeuYDzDhhcAAUrq8Po85NBQBJP+ZDUT75qZQ98IkUoBqdkExkukOU7Ts2wrw==", + "dev": true }, "json-schema-traverse": { "version": "0.4.1", "resolved": "https://registry.npmjs.org/json-schema-traverse/-/json-schema-traverse-0.4.1.tgz", - "integrity": "sha512-xbbCH5dCYU5T8LcEhhuh7HJ88HXuW3qsI3Y0zOZFKfZEHcpWiHU/Jxzk629Brsab/mMiHQti9wMP+845RPe3Vg==" + "integrity": "sha512-xbbCH5dCYU5T8LcEhhuh7HJ88HXuW3qsI3Y0zOZFKfZEHcpWiHU/Jxzk629Brsab/mMiHQti9wMP+845RPe3Vg==", + "dev": true }, "jssha": { "version": "3.2.0", @@ -9265,7 +2740,8 @@ "loader-runner": { "version": "4.3.0", "resolved": "https://registry.npmjs.org/loader-runner/-/loader-runner-4.3.0.tgz", - "integrity": "sha512-3R/1M+yS3j5ou80Me59j7F9IMs4PXs3VqRrm0TU3AbKPxlmpoY1TNscJV/oGJXo8qCatFGTfDbY6W6ipGOYXfg==" + "integrity": "sha512-3R/1M+yS3j5ou80Me59j7F9IMs4PXs3VqRrm0TU3AbKPxlmpoY1TNscJV/oGJXo8qCatFGTfDbY6W6ipGOYXfg==", + "dev": true }, "locate-path": { "version": "5.0.0", @@ -9454,7 +2930,8 @@ "merge-stream": { "version": "2.0.0", "resolved": "https://registry.npmjs.org/merge-stream/-/merge-stream-2.0.0.tgz", - "integrity": "sha512-abv/qOcuPfk3URPfDzmZU1LKmuw8kT+0nIHvKrKgFrwifol/doWcdA4ZqsWQ8ENrFKkd67Mfpo/LovbIUsbt3w==" + "integrity": "sha512-abv/qOcuPfk3URPfDzmZU1LKmuw8kT+0nIHvKrKgFrwifol/doWcdA4ZqsWQ8ENrFKkd67Mfpo/LovbIUsbt3w==", + "dev": true }, "merge2": { "version": "1.4.1", @@ -9604,12 +3081,14 @@ "mime-db": { "version": "1.52.0", "resolved": "https://registry.npmjs.org/mime-db/-/mime-db-1.52.0.tgz", - "integrity": "sha512-sPU4uV7dYlvtWJxwwxHD0PuihVNiE7TyAbQ5SWxDCB9mUYvOgroQOwYQQOKPJ8CIbE+1ETVlOoK1UC2nU3gYvg==" + "integrity": "sha512-sPU4uV7dYlvtWJxwwxHD0PuihVNiE7TyAbQ5SWxDCB9mUYvOgroQOwYQQOKPJ8CIbE+1ETVlOoK1UC2nU3gYvg==", + "dev": true }, "mime-types": { "version": "2.1.35", "resolved": "https://registry.npmjs.org/mime-types/-/mime-types-2.1.35.tgz", "integrity": "sha512-ZDY+bPm5zTTF+YpCrAU9nK0UgICYPT0QtT1NZWFv4s++TNkcgVaT0g6+4R2uI4MjQjzysHB1zxuWL50hzaeXiw==", + "dev": true, "requires": { "mime-db": "1.52.0" } @@ -9689,7 +3168,8 @@ "neo-async": { "version": "2.6.2", "resolved": "https://registry.npmjs.org/neo-async/-/neo-async-2.6.2.tgz", - "integrity": "sha512-Yd3UES5mWCSqR+qNT93S3UoYUkqAZ9lLg8a7g9rimsWmYGK8cVToA4/sF3RrshdyV3sAGMXVUmpMYOw+dLpOuw==" + "integrity": "sha512-Yd3UES5mWCSqR+qNT93S3UoYUkqAZ9lLg8a7g9rimsWmYGK8cVToA4/sF3RrshdyV3sAGMXVUmpMYOw+dLpOuw==", + "dev": true }, "no-case": { "version": "3.0.4", @@ -9775,7 +3255,8 @@ "node-releases": { "version": "2.0.5", "resolved": "https://registry.npmjs.org/node-releases/-/node-releases-2.0.5.tgz", - "integrity": "sha512-U9h1NLROZTq9uE1SNffn6WuPDg8icmi3ns4rEl/oTfIle4iLjTliCzgTsbaIFMq/Xn078/lfY/BL0GWZ+psK4Q==" + "integrity": "sha512-U9h1NLROZTq9uE1SNffn6WuPDg8icmi3ns4rEl/oTfIle4iLjTliCzgTsbaIFMq/Xn078/lfY/BL0GWZ+psK4Q==", + "dev": true }, "normalize-path": { "version": "3.0.0", @@ -10041,7 +3522,8 @@ "picocolors": { "version": "1.0.0", "resolved": "https://registry.npmjs.org/picocolors/-/picocolors-1.0.0.tgz", - "integrity": "sha512-1fygroTLlHu66zi26VoTDv8yRgm0Fccecssto+MhsZ0D/DGW2sm8E8AjW7NU5VVTRt5GxbeZ5qBuJr+HyLYkjQ==" + "integrity": "sha512-1fygroTLlHu66zi26VoTDv8yRgm0Fccecssto+MhsZ0D/DGW2sm8E8AjW7NU5VVTRt5GxbeZ5qBuJr+HyLYkjQ==", + "dev": true }, "picomatch": { "version": "2.3.1", @@ -10203,8 +3685,7 @@ "ws": { "version": "8.8.0", "resolved": "https://registry.npmjs.org/ws/-/ws-8.8.0.tgz", - "integrity": "sha512-JDAgSYQ1ksuwqfChJusw1LSJ8BizJ2e/vVu5Lxjq3YvNJNlROv1ui4i+c/kUUrPheBvQl4c5UbERhTwKa6QBJQ==", - "requires": {} + "integrity": "sha512-JDAgSYQ1ksuwqfChJusw1LSJ8BizJ2e/vVu5Lxjq3YvNJNlROv1ui4i+c/kUUrPheBvQl4c5UbERhTwKa6QBJQ==" } } }, @@ -10473,6 +3954,7 @@ "version": "3.1.1", "resolved": "https://registry.npmjs.org/schema-utils/-/schema-utils-3.1.1.tgz", "integrity": "sha512-Y5PQxS4ITlC+EahLuXaY86TXfR7Dc5lw294alXOq86JAHCihAIZfqv8nNCWvaEJvaC51uN9hbLGeV0cFBdH+Fw==", + "dev": true, "requires": { "@types/json-schema": "^7.0.8", "ajv": "^6.12.5", @@ -10527,6 +4009,7 @@ "version": "6.0.0", "resolved": "https://registry.npmjs.org/serialize-javascript/-/serialize-javascript-6.0.0.tgz", "integrity": "sha512-Qr3TosvguFt8ePWqsvRfrKyQXIiW+nGbYpy8XK24NQHE83caxWt+mIymTT19DGFbNWNLfEwsrkSmN64lVWB9ag==", + "dev": true, "requires": { "randombytes": "^2.1.0" } @@ -10676,12 +4159,14 @@ "source-map": { "version": "0.6.1", "resolved": "https://registry.npmjs.org/source-map/-/source-map-0.6.1.tgz", - "integrity": "sha512-UjgapumWlbMhkBgzT7Ykc5YXUT46F0iKu8SGXq0bcwP5dz/h0Plj6enJqjz1Zbq2l5WaqYnrVbwWOWMyF3F47g==" + "integrity": "sha512-UjgapumWlbMhkBgzT7Ykc5YXUT46F0iKu8SGXq0bcwP5dz/h0Plj6enJqjz1Zbq2l5WaqYnrVbwWOWMyF3F47g==", + "dev": true }, "source-map-support": { "version": "0.5.21", "resolved": "https://registry.npmjs.org/source-map-support/-/source-map-support-0.5.21.tgz", "integrity": "sha512-uBHU3L3czsIyYXKX88fdrGovxdSCoTGDRZ6SYXtSRxLZUzHg5P/66Ht6uoUlHu9EZod+inXhKo3qQgwXUT/y1w==", + "dev": true, "requires": { "buffer-from": "^1.0.0", "source-map": "^0.6.0" @@ -10774,14 +4259,6 @@ "xtend": "^4.0.2" } }, - "string_decoder": { - "version": "1.3.0", - "resolved": "https://registry.npmjs.org/string_decoder/-/string_decoder-1.3.0.tgz", - "integrity": "sha512-hkRX8U1WjJFd8LsDJ2yQ/wWWxaopEsABU1XfkM8A+j0+85JAGppt16cr1Whg6KIbb4okU6Mql6BOj+uup/wKeA==", - "requires": { - "safe-buffer": "~5.2.0" - } - }, "string.prototype.trimend": { "version": "1.0.5", "resolved": "https://registry.npmjs.org/string.prototype.trimend/-/string.prototype.trimend-1.0.5.tgz", @@ -10802,6 +4279,14 @@ "es-abstract": "^1.19.5" } }, + "string_decoder": { + "version": "1.3.0", + "resolved": "https://registry.npmjs.org/string_decoder/-/string_decoder-1.3.0.tgz", + "integrity": "sha512-hkRX8U1WjJFd8LsDJ2yQ/wWWxaopEsABU1XfkM8A+j0+85JAGppt16cr1Whg6KIbb4okU6Mql6BOj+uup/wKeA==", + "requires": { + "safe-buffer": "~5.2.0" + } + }, "strip-ansi": { "version": "6.0.1", "resolved": "https://registry.npmjs.org/strip-ansi/-/strip-ansi-6.0.1.tgz", @@ -10821,6 +4306,7 @@ "version": "8.1.1", "resolved": "https://registry.npmjs.org/supports-color/-/supports-color-8.1.1.tgz", "integrity": "sha512-MpUEN2OodtUzxvKQl72cUF7RQ5EiHsGvSsVG0ia9c5RbWGL2CI4C7EpPS8UTBIplnlzZiNuV56w+FuNxy3ty2Q==", + "dev": true, "requires": { "has-flag": "^4.0.0" } @@ -10834,7 +4320,8 @@ "tapable": { "version": "2.2.1", "resolved": "https://registry.npmjs.org/tapable/-/tapable-2.2.1.tgz", - "integrity": "sha512-GNzQvQTOIP6RyTfE2Qxb8ZVlNmw0n88vp1szwWRimP02mnTsx3Wtn5qRdqY9w2XduFNUgvOwhNnQsjwCp+kqaQ==" + "integrity": "sha512-GNzQvQTOIP6RyTfE2Qxb8ZVlNmw0n88vp1szwWRimP02mnTsx3Wtn5qRdqY9w2XduFNUgvOwhNnQsjwCp+kqaQ==", + "dev": true }, "tar-fs": { "version": "2.1.1", @@ -10863,6 +4350,7 @@ "version": "5.15.1", "resolved": "https://registry.npmjs.org/terser/-/terser-5.15.1.tgz", "integrity": "sha512-K1faMUvpm/FBxjBXud0LWVAGxmvoPbZbfTCYbSgaaYQaIXI3/TdI7a7ZGA73Zrou6Q8Zmz3oeUTsp/dj+ag2Xw==", + "dev": true, "requires": { "@jridgewell/source-map": "^0.3.2", "acorn": "^8.5.0", @@ -10873,7 +4361,8 @@ "commander": { "version": "2.20.3", "resolved": "https://registry.npmjs.org/commander/-/commander-2.20.3.tgz", - "integrity": "sha512-GpVkmM8vF2vQUkj2LvZmD35JxeJOLCwJ9cUkugyk2nuhbv3+mJvpLYYt+0+USMxE+oj+ey/lJEnhZw75x/OMcQ==" + "integrity": "sha512-GpVkmM8vF2vQUkj2LvZmD35JxeJOLCwJ9cUkugyk2nuhbv3+mJvpLYYt+0+USMxE+oj+ey/lJEnhZw75x/OMcQ==", + "dev": true } } }, @@ -10881,6 +4370,7 @@ "version": "5.3.3", "resolved": "https://registry.npmjs.org/terser-webpack-plugin/-/terser-webpack-plugin-5.3.3.tgz", "integrity": "sha512-Fx60G5HNYknNTNQnzQ1VePRuu89ZVYWfjRAeT5rITuCY/1b08s49e5kSQwHDirKZWuoKOBRFS98EUUoZ9kLEwQ==", + "dev": true, "requires": { "@jridgewell/trace-mapping": "^0.3.7", "jest-worker": "^27.4.5", @@ -11055,6 +4545,7 @@ "version": "1.0.3", "resolved": "https://registry.npmjs.org/update-browserslist-db/-/update-browserslist-db-1.0.3.tgz", "integrity": "sha512-ufSazemeh9Gty0qiWtoRpJ9F5Q5W3xdIPm1UZQqYQv/q0Nyb9EMHUB2lu+O9x1re9WsorpMAUu4Y6Lxcs5n+XQ==", + "dev": true, "requires": { "escalade": "^3.1.1", "picocolors": "^1.0.0" @@ -11070,6 +4561,7 @@ "version": "4.4.1", "resolved": "https://registry.npmjs.org/uri-js/-/uri-js-4.4.1.tgz", "integrity": "sha512-7rKUyy33Q1yc98pQ1DAmLtwX109F7TIfWlW1Ydo8Wl1ii1SeHieeh0HHfPeL2fMXK6z0s8ecKs9frCuLJvndBg==", + "dev": true, "requires": { "punycode": "^2.1.0" } @@ -11163,6 +4655,7 @@ "version": "2.3.1", "resolved": "https://registry.npmjs.org/watchpack/-/watchpack-2.3.1.tgz", "integrity": "sha512-x0t0JuydIo8qCNctdDrn1OzH/qDzk2+rdCOC3YzumZ42fiMqmQ7T3xQurykYMhYfHaPHTp4ZxAx2NfUo1K6QaA==", + "dev": true, "requires": { "glob-to-regexp": "^0.4.1", "graceful-fs": "^4.1.2" @@ -11181,6 +4674,7 @@ "version": "5.67.0", "resolved": "https://registry.npmjs.org/webpack/-/webpack-5.67.0.tgz", "integrity": "sha512-LjFbfMh89xBDpUMgA1W9Ur6Rn/gnr2Cq1jjHFPo4v6a79/ypznSYbAyPgGhwsxBtMIaEmDD1oJoA7BEYw/Fbrw==", + "dev": true, "requires": { "@types/eslint-scope": "^3.7.0", "@types/estree": "^0.0.50", @@ -11386,8 +4880,7 @@ "version": "8.6.0", "resolved": "https://registry.npmjs.org/ws/-/ws-8.6.0.tgz", "integrity": "sha512-AzmM3aH3gk0aX7/rZLYvjdvZooofDu3fFOzGqcSnQ1tOcTWwhM/o+q++E8mAyVVIyUdajrkzWUGftaVSDLn1bw==", - "dev": true, - "requires": {} + "dev": true } } }, @@ -11404,7 +4897,8 @@ "webpack-sources": { "version": "3.2.3", "resolved": "https://registry.npmjs.org/webpack-sources/-/webpack-sources-3.2.3.tgz", - "integrity": "sha512-/DyMEOrDgLKKIG0fmvtz+4dUX/3Ghozwgm6iPp8KRhvn+eQf9+Q7GWxVNMk3+uCPWfdXYC4ExGBckIXdFEfH1w==" + "integrity": "sha512-/DyMEOrDgLKKIG0fmvtz+4dUX/3Ghozwgm6iPp8KRhvn+eQf9+Q7GWxVNMk3+uCPWfdXYC4ExGBckIXdFEfH1w==", + "dev": true }, "websocket-driver": { "version": "0.7.4", @@ -11471,8 +4965,7 @@ "ws": { "version": "8.4.0", "resolved": "https://registry.npmjs.org/ws/-/ws-8.4.0.tgz", - "integrity": "sha512-IHVsKe2pjajSUIl4KYMQOdlyliovpEPquKkqbwswulszzI7r0SfQrxnXdWAEqOlDCLrVSJzo+O1hAwdog2sKSQ==", - "requires": {} + "integrity": "sha512-IHVsKe2pjajSUIl4KYMQOdlyliovpEPquKkqbwswulszzI7r0SfQrxnXdWAEqOlDCLrVSJzo+O1hAwdog2sKSQ==" }, "xhr2": { "version": "0.2.1", diff --git a/templates/ctl-scaffold/package-lock.json b/templates/ctl-scaffold/package-lock.json index 1aaba77d7c..251da939e8 100644 --- a/templates/ctl-scaffold/package-lock.json +++ b/templates/ctl-scaffold/package-lock.json @@ -1,5625 +1,8 @@ { "name": "ctl-scaffold", "version": "0.1.0", - "lockfileVersion": 2, + "lockfileVersion": 1, "requires": true, - "packages": { - "": { - "name": "ctl-scaffold", - "version": "0.1.0", - "license": "MIT", - "dependencies": { - "@emurgo/cardano-message-signing-browser": "1.0.1", - "@emurgo/cardano-message-signing-nodejs": "1.0.1", - "@emurgo/cardano-serialization-lib-browser": "11.2.1", - "@emurgo/cardano-serialization-lib-nodejs": "11.2.1", - "@mlabs-haskell/json-bigint": " 1.0.0", - "@noble/secp256k1": "^1.7.0", - "apply-args-browser": "0.0.1", - "apply-args-nodejs": "0.0.1", - "base64-js": "^1.5.1", - "big-integer": "1.6.51", - "blakejs": "1.2.1", - "bufferutil": "4.0.5", - "jssha": "3.2.0", - "node-polyfill-webpack-plugin": "1.1.4", - "puppeteer-core": "^15.3.2", - "reconnecting-websocket": "4.4.0", - "uniqid": "5.4.0", - "ws": "8.4.0", - "xhr2": "0.2.1" - }, - "devDependencies": { - "buffer": "6.0.3", - "html-webpack-plugin": "5.5.0", - "webpack": "5.67.0", - "webpack-cli": "4.10", - "webpack-dev-server": "4.7.4" - } - }, - "node_modules/@discoveryjs/json-ext": { - "version": "0.5.7", - "resolved": "https://registry.npmjs.org/@discoveryjs/json-ext/-/json-ext-0.5.7.tgz", - "integrity": "sha512-dBVuXR082gk3jsFp7Rd/JI4kytwGHecnCoTtXFb7DB6CNHp4rg5k1bhg0nWdLGLnOV71lmDzGQaLMy8iPLY0pw==", - "dev": true, - "engines": { - "node": ">=10.0.0" - } - }, - "node_modules/@emurgo/cardano-message-signing-browser": { - "version": "1.0.1", - "resolved": "https://registry.npmjs.org/@emurgo/cardano-message-signing-browser/-/cardano-message-signing-browser-1.0.1.tgz", - "integrity": "sha512-yC4Ymq44WR0bXO1wzxCoyc2W/RD1KSAla0oYhin7IYoVkp2raGp8wt7QNF4pDdNnTcejn5fyPyYY9dL4666H1w==" - }, - "node_modules/@emurgo/cardano-message-signing-nodejs": { - "version": "1.0.1", - "resolved": "https://registry.npmjs.org/@emurgo/cardano-message-signing-nodejs/-/cardano-message-signing-nodejs-1.0.1.tgz", - "integrity": "sha512-PoKh1tQnJX18f8iEr8Jk1KXxKCn9eqaSslMI1pyOJvYRJhQVDLCh0+9YReufjp0oFJIY1ShcrR+4/WnECVZUKQ==" - }, - "node_modules/@emurgo/cardano-serialization-lib-browser": { - "version": "11.2.1", - "resolved": "https://registry.npmjs.org/@emurgo/cardano-serialization-lib-browser/-/cardano-serialization-lib-browser-11.2.1.tgz", - "integrity": "sha512-J9Pmeta7y1GYnMCxtb3GnGCRw6zk1wiQ8EdCYQRn/Yqa/ss1zoBjd41euVi02Eb58aLuOJS81nNU+BcMLGXvUg==" - }, - "node_modules/@emurgo/cardano-serialization-lib-nodejs": { - "version": "11.2.1", - "resolved": "https://registry.npmjs.org/@emurgo/cardano-serialization-lib-nodejs/-/cardano-serialization-lib-nodejs-11.2.1.tgz", - "integrity": "sha512-+Rw35NW4Qv/9uFaPxhKtxiIPmoBEIFMAgdqQxZTw6hNT/wvBp2TvwTBPnOW8ODs7GUAA8nrO1rJJAaxF+mAG2w==" - }, - "node_modules/@mlabs-haskell/json-bigint": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/@mlabs-haskell/json-bigint/-/json-bigint-1.0.0.tgz", - "integrity": "sha512-Opo07yXP/OU9mIoGmY5VVuDy5kxmb3fBAG3U9dbC15qK1OCpVLJAlxbdOfBmLOja94SnIfZINUU2xvYtVfk65w==", - "dependencies": { - "bignumber.js": "^9.0.0" - } - }, - "node_modules/@noble/secp256k1": { - "version": "1.7.0", - "resolved": "https://registry.npmjs.org/@noble/secp256k1/-/secp256k1-1.7.0.tgz", - "integrity": "sha512-kbacwGSsH/CTout0ZnZWxnW1B+jH/7r/WAAKLBtrRJ/+CUH7lgmQzl3GTrQua3SGKWNSDsS6lmjnDpIJ5Dxyaw==", - "funding": [ - { - "type": "individual", - "url": "https://paulmillr.com/funding/" - } - ] - }, - "node_modules/@nodelib/fs.scandir": { - "version": "2.1.5", - "resolved": "https://registry.npmjs.org/@nodelib/fs.scandir/-/fs.scandir-2.1.5.tgz", - "integrity": "sha512-vq24Bq3ym5HEQm2NKCr3yXDwjc7vTsEThRDnkp2DK9p1uqLR+DHurm/NOTo0KG7HYHU7eppKZj3MyqYuMBf62g==", - "dev": true, - "dependencies": { - "@nodelib/fs.stat": "2.0.5", - "run-parallel": "^1.1.9" - }, - "engines": { - "node": ">= 8" - } - }, - "node_modules/@nodelib/fs.stat": { - "version": "2.0.5", - "resolved": "https://registry.npmjs.org/@nodelib/fs.stat/-/fs.stat-2.0.5.tgz", - "integrity": "sha512-RkhPPp2zrqDAQA/2jNhnztcPAlv64XdhIp7a7454A5ovI7Bukxgt7MX7udwAu3zg1DcpPU0rz3VV1SeaqvY4+A==", - "dev": true, - "engines": { - "node": ">= 8" - } - }, - "node_modules/@nodelib/fs.walk": { - "version": "1.2.8", - "resolved": "https://registry.npmjs.org/@nodelib/fs.walk/-/fs.walk-1.2.8.tgz", - "integrity": "sha512-oGB+UxlgWcgQkgwo8GcEGwemoTFt3FIO9ababBmaGwXIoBKZ+GTy0pP185beGg7Llih/NSHSV2XAs1lnznocSg==", - "dev": true, - "dependencies": { - "@nodelib/fs.scandir": "2.1.5", - "fastq": "^1.6.0" - }, - "engines": { - "node": ">= 8" - } - }, - "node_modules/@types/body-parser": { - "version": "1.19.2", - "resolved": "https://registry.npmjs.org/@types/body-parser/-/body-parser-1.19.2.tgz", - "integrity": "sha512-ALYone6pm6QmwZoAgeyNksccT9Q4AWZQ6PvfwR37GT6r6FWUPguq6sUmNGSMV2Wr761oQoBxwGGa6DR5o1DC9g==", - "dev": true, - "dependencies": { - "@types/connect": "*", - "@types/node": "*" - } - }, - "node_modules/@types/bonjour": { - "version": "3.5.10", - "resolved": "https://registry.npmjs.org/@types/bonjour/-/bonjour-3.5.10.tgz", - "integrity": "sha512-p7ienRMiS41Nu2/igbJxxLDWrSZ0WxM8UQgCeO9KhoVF7cOVFkrKsiDr1EsJIla8vV3oEEjGcz11jc5yimhzZw==", - "dev": true, - "dependencies": { - "@types/node": "*" - } - }, - "node_modules/@types/connect": { - "version": "3.4.35", - "resolved": "https://registry.npmjs.org/@types/connect/-/connect-3.4.35.tgz", - "integrity": "sha512-cdeYyv4KWoEgpBISTxWvqYsVy444DOqehiF3fM3ne10AmJ62RSyNkUnxMJXHQWRQQX2eR94m5y1IZyDwBjV9FQ==", - "dev": true, - "dependencies": { - "@types/node": "*" - } - }, - "node_modules/@types/connect-history-api-fallback": { - "version": "1.3.5", - "resolved": "https://registry.npmjs.org/@types/connect-history-api-fallback/-/connect-history-api-fallback-1.3.5.tgz", - "integrity": "sha512-h8QJa8xSb1WD4fpKBDcATDNGXghFj6/3GRWG6dhmRcu0RX1Ubasur2Uvx5aeEwlf0MwblEC2bMzzMQntxnw/Cw==", - "dev": true, - "dependencies": { - "@types/express-serve-static-core": "*", - "@types/node": "*" - } - }, - "node_modules/@types/eslint": { - "version": "8.4.1", - "resolved": "https://registry.npmjs.org/@types/eslint/-/eslint-8.4.1.tgz", - "integrity": "sha512-GE44+DNEyxxh2Kc6ro/VkIj+9ma0pO0bwv9+uHSyBrikYOHr8zYcdPvnBOp1aw8s+CjRvuSx7CyWqRrNFQ59mA==", - "dependencies": { - "@types/estree": "*", - "@types/json-schema": "*" - } - }, - "node_modules/@types/eslint-scope": { - "version": "3.7.3", - "resolved": "https://registry.npmjs.org/@types/eslint-scope/-/eslint-scope-3.7.3.tgz", - "integrity": "sha512-PB3ldyrcnAicT35TWPs5IcwKD8S333HMaa2VVv4+wdvebJkjWuW/xESoB8IwRcog8HYVYamb1g/R31Qv5Bx03g==", - "dependencies": { - "@types/eslint": "*", - "@types/estree": "*" - } - }, - "node_modules/@types/estree": { - "version": "0.0.50", - "resolved": "https://registry.npmjs.org/@types/estree/-/estree-0.0.50.tgz", - "integrity": "sha512-C6N5s2ZFtuZRj54k2/zyRhNDjJwwcViAM3Nbm8zjBpbqAdZ00mr0CFxvSKeO8Y/e03WVFLpQMdHYVfUd6SB+Hw==" - }, - "node_modules/@types/express": { - "version": "4.17.13", - "resolved": "https://registry.npmjs.org/@types/express/-/express-4.17.13.tgz", - "integrity": "sha512-6bSZTPaTIACxn48l50SR+axgrqm6qXFIxrdAKaG6PaJk3+zuUr35hBlgT7vOmJcum+OEaIBLtHV/qloEAFITeA==", - "dev": true, - "dependencies": { - "@types/body-parser": "*", - "@types/express-serve-static-core": "^4.17.18", - "@types/qs": "*", - "@types/serve-static": "*" - } - }, - "node_modules/@types/express-serve-static-core": { - "version": "4.17.28", - "resolved": "https://registry.npmjs.org/@types/express-serve-static-core/-/express-serve-static-core-4.17.28.tgz", - "integrity": "sha512-P1BJAEAW3E2DJUlkgq4tOL3RyMunoWXqbSCygWo5ZIWTjUgN1YnaXWW4VWl/oc8vs/XoYibEGBKP0uZyF4AHig==", - "dev": true, - "dependencies": { - "@types/node": "*", - "@types/qs": "*", - "@types/range-parser": "*" - } - }, - "node_modules/@types/html-minifier-terser": { - "version": "6.1.0", - "resolved": "https://registry.npmjs.org/@types/html-minifier-terser/-/html-minifier-terser-6.1.0.tgz", - "integrity": "sha512-oh/6byDPnL1zeNXFrDXFLyZjkr1MsBG667IM792caf1L2UPOOMf65NFzjUH/ltyfwjAGfs1rsX1eftK0jC/KIg==", - "dev": true - }, - "node_modules/@types/http-proxy": { - "version": "1.17.8", - "resolved": "https://registry.npmjs.org/@types/http-proxy/-/http-proxy-1.17.8.tgz", - "integrity": "sha512-5kPLG5BKpWYkw/LVOGWpiq3nEVqxiN32rTgI53Sk12/xHFQ2rG3ehI9IO+O3W2QoKeyB92dJkoka8SUm6BX1pA==", - "dev": true, - "dependencies": { - "@types/node": "*" - } - }, - "node_modules/@types/json-schema": { - "version": "7.0.9", - "resolved": "https://registry.npmjs.org/@types/json-schema/-/json-schema-7.0.9.tgz", - "integrity": "sha512-qcUXuemtEu+E5wZSJHNxUXeCZhAfXKQ41D+duX+VYPde7xyEVZci+/oXKJL13tnRs9lR2pr4fod59GT6/X1/yQ==" - }, - "node_modules/@types/mime": { - "version": "1.3.2", - "resolved": "https://registry.npmjs.org/@types/mime/-/mime-1.3.2.tgz", - "integrity": "sha512-YATxVxgRqNH6nHEIsvg6k2Boc1JHI9ZbH5iWFFv/MTkchz3b1ieGDa5T0a9RznNdI0KhVbdbWSN+KWWrQZRxTw==", - "dev": true - }, - "node_modules/@types/node": { - "version": "17.0.14", - "resolved": "https://registry.npmjs.org/@types/node/-/node-17.0.14.tgz", - "integrity": "sha512-SbjLmERksKOGzWzPNuW7fJM7fk3YXVTFiZWB/Hs99gwhk+/dnrQRPBQjPW9aO+fi1tAffi9PrwFvsmOKmDTyng==" - }, - "node_modules/@types/qs": { - "version": "6.9.7", - "resolved": "https://registry.npmjs.org/@types/qs/-/qs-6.9.7.tgz", - "integrity": "sha512-FGa1F62FT09qcrueBA6qYTrJPVDzah9a+493+o2PCXsesWHIn27G98TsSMs3WPNbZIEj4+VJf6saSFpvD+3Zsw==", - "dev": true - }, - "node_modules/@types/range-parser": { - "version": "1.2.4", - "resolved": "https://registry.npmjs.org/@types/range-parser/-/range-parser-1.2.4.tgz", - "integrity": "sha512-EEhsLsD6UsDM1yFhAvy0Cjr6VwmpMWqFBCb9w07wVugF7w9nfajxLuVmngTIpgS6svCnm6Vaw+MZhoDCKnOfsw==", - "dev": true - }, - "node_modules/@types/retry": { - "version": "0.12.1", - "resolved": "https://registry.npmjs.org/@types/retry/-/retry-0.12.1.tgz", - "integrity": "sha512-xoDlM2S4ortawSWORYqsdU+2rxdh4LRW9ytc3zmT37RIKQh6IHyKwwtKhKis9ah8ol07DCkZxPt8BBvPjC6v4g==", - "dev": true - }, - "node_modules/@types/serve-index": { - "version": "1.9.1", - "resolved": "https://registry.npmjs.org/@types/serve-index/-/serve-index-1.9.1.tgz", - "integrity": "sha512-d/Hs3nWDxNL2xAczmOVZNj92YZCS6RGxfBPjKzuu/XirCgXdpKEb88dYNbrYGint6IVWLNP+yonwVAuRC0T2Dg==", - "dev": true, - "dependencies": { - "@types/express": "*" - } - }, - "node_modules/@types/serve-static": { - "version": "1.13.10", - "resolved": "https://registry.npmjs.org/@types/serve-static/-/serve-static-1.13.10.tgz", - "integrity": "sha512-nCkHGI4w7ZgAdNkrEu0bv+4xNV/XDqW+DydknebMOQwkpDGx8G+HTlj7R7ABI8i8nKxVw0wtKPi1D+lPOkh4YQ==", - "dev": true, - "dependencies": { - "@types/mime": "^1", - "@types/node": "*" - } - }, - "node_modules/@types/sockjs": { - "version": "0.3.33", - "resolved": "https://registry.npmjs.org/@types/sockjs/-/sockjs-0.3.33.tgz", - "integrity": "sha512-f0KEEe05NvUnat+boPTZ0dgaLZ4SfSouXUgv5noUiefG2ajgKjmETo9ZJyuqsl7dfl2aHlLJUiki6B4ZYldiiw==", - "dev": true, - "dependencies": { - "@types/node": "*" - } - }, - "node_modules/@types/ws": { - "version": "8.2.2", - "resolved": "https://registry.npmjs.org/@types/ws/-/ws-8.2.2.tgz", - "integrity": "sha512-NOn5eIcgWLOo6qW8AcuLZ7G8PycXu0xTxxkS6Q18VWFxgPUSOwV0pBj2a/4viNZVu25i7RIB7GttdkAIUUXOOg==", - "dev": true, - "dependencies": { - "@types/node": "*" - } - }, - "node_modules/@types/yauzl": { - "version": "2.10.0", - "resolved": "https://registry.npmjs.org/@types/yauzl/-/yauzl-2.10.0.tgz", - "integrity": "sha512-Cn6WYCm0tXv8p6k+A8PvbDG763EDpBoTzHdA+Q/MF6H3sapGjCm9NzoaJncJS9tUKSuCoDs9XHxYYsQDgxR6kw==", - "optional": true, - "dependencies": { - "@types/node": "*" - } - }, - "node_modules/@webassemblyjs/ast": { - "version": "1.11.1", - "resolved": "https://registry.npmjs.org/@webassemblyjs/ast/-/ast-1.11.1.tgz", - "integrity": "sha512-ukBh14qFLjxTQNTXocdyksN5QdM28S1CxHt2rdskFyL+xFV7VremuBLVbmCePj+URalXBENx/9Lm7lnhihtCSw==", - "dependencies": { - "@webassemblyjs/helper-numbers": "1.11.1", - "@webassemblyjs/helper-wasm-bytecode": "1.11.1" - } - }, - "node_modules/@webassemblyjs/floating-point-hex-parser": { - "version": "1.11.1", - "resolved": "https://registry.npmjs.org/@webassemblyjs/floating-point-hex-parser/-/floating-point-hex-parser-1.11.1.tgz", - "integrity": "sha512-iGRfyc5Bq+NnNuX8b5hwBrRjzf0ocrJPI6GWFodBFzmFnyvrQ83SHKhmilCU/8Jv67i4GJZBMhEzltxzcNagtQ==" - }, - "node_modules/@webassemblyjs/helper-api-error": { - "version": "1.11.1", - "resolved": "https://registry.npmjs.org/@webassemblyjs/helper-api-error/-/helper-api-error-1.11.1.tgz", - "integrity": "sha512-RlhS8CBCXfRUR/cwo2ho9bkheSXG0+NwooXcc3PAILALf2QLdFyj7KGsKRbVc95hZnhnERon4kW/D3SZpp6Tcg==" - }, - "node_modules/@webassemblyjs/helper-buffer": { - "version": "1.11.1", - "resolved": "https://registry.npmjs.org/@webassemblyjs/helper-buffer/-/helper-buffer-1.11.1.tgz", - "integrity": "sha512-gwikF65aDNeeXa8JxXa2BAk+REjSyhrNC9ZwdT0f8jc4dQQeDQ7G4m0f2QCLPJiMTTO6wfDmRmj/pW0PsUvIcA==" - }, - "node_modules/@webassemblyjs/helper-numbers": { - "version": "1.11.1", - "resolved": "https://registry.npmjs.org/@webassemblyjs/helper-numbers/-/helper-numbers-1.11.1.tgz", - "integrity": "sha512-vDkbxiB8zfnPdNK9Rajcey5C0w+QJugEglN0of+kmO8l7lDb77AnlKYQF7aarZuCrv+l0UvqL+68gSDr3k9LPQ==", - "dependencies": { - "@webassemblyjs/floating-point-hex-parser": "1.11.1", - "@webassemblyjs/helper-api-error": "1.11.1", - "@xtuc/long": "4.2.2" - } - }, - "node_modules/@webassemblyjs/helper-wasm-bytecode": { - "version": "1.11.1", - "resolved": "https://registry.npmjs.org/@webassemblyjs/helper-wasm-bytecode/-/helper-wasm-bytecode-1.11.1.tgz", - "integrity": "sha512-PvpoOGiJwXeTrSf/qfudJhwlvDQxFgelbMqtq52WWiXC6Xgg1IREdngmPN3bs4RoO83PnL/nFrxucXj1+BX62Q==" - }, - "node_modules/@webassemblyjs/helper-wasm-section": { - "version": "1.11.1", - "resolved": "https://registry.npmjs.org/@webassemblyjs/helper-wasm-section/-/helper-wasm-section-1.11.1.tgz", - "integrity": "sha512-10P9No29rYX1j7F3EVPX3JvGPQPae+AomuSTPiF9eBQeChHI6iqjMIwR9JmOJXwpnn/oVGDk7I5IlskuMwU/pg==", - "dependencies": { - "@webassemblyjs/ast": "1.11.1", - "@webassemblyjs/helper-buffer": "1.11.1", - "@webassemblyjs/helper-wasm-bytecode": "1.11.1", - "@webassemblyjs/wasm-gen": "1.11.1" - } - }, - "node_modules/@webassemblyjs/ieee754": { - "version": "1.11.1", - "resolved": "https://registry.npmjs.org/@webassemblyjs/ieee754/-/ieee754-1.11.1.tgz", - "integrity": "sha512-hJ87QIPtAMKbFq6CGTkZYJivEwZDbQUgYd3qKSadTNOhVY7p+gfP6Sr0lLRVTaG1JjFj+r3YchoqRYxNH3M0GQ==", - "dependencies": { - "@xtuc/ieee754": "^1.2.0" - } - }, - "node_modules/@webassemblyjs/leb128": { - "version": "1.11.1", - "resolved": "https://registry.npmjs.org/@webassemblyjs/leb128/-/leb128-1.11.1.tgz", - "integrity": "sha512-BJ2P0hNZ0u+Th1YZXJpzW6miwqQUGcIHT1G/sf72gLVD9DZ5AdYTqPNbHZh6K1M5VmKvFXwGSWZADz+qBWxeRw==", - "dependencies": { - "@xtuc/long": "4.2.2" - } - }, - "node_modules/@webassemblyjs/utf8": { - "version": "1.11.1", - "resolved": "https://registry.npmjs.org/@webassemblyjs/utf8/-/utf8-1.11.1.tgz", - "integrity": "sha512-9kqcxAEdMhiwQkHpkNiorZzqpGrodQQ2IGrHHxCy+Ozng0ofyMA0lTqiLkVs1uzTRejX+/O0EOT7KxqVPuXosQ==" - }, - "node_modules/@webassemblyjs/wasm-edit": { - "version": "1.11.1", - "resolved": "https://registry.npmjs.org/@webassemblyjs/wasm-edit/-/wasm-edit-1.11.1.tgz", - "integrity": "sha512-g+RsupUC1aTHfR8CDgnsVRVZFJqdkFHpsHMfJuWQzWU3tvnLC07UqHICfP+4XyL2tnr1amvl1Sdp06TnYCmVkA==", - "dependencies": { - "@webassemblyjs/ast": "1.11.1", - "@webassemblyjs/helper-buffer": "1.11.1", - "@webassemblyjs/helper-wasm-bytecode": "1.11.1", - "@webassemblyjs/helper-wasm-section": "1.11.1", - "@webassemblyjs/wasm-gen": "1.11.1", - "@webassemblyjs/wasm-opt": "1.11.1", - "@webassemblyjs/wasm-parser": "1.11.1", - "@webassemblyjs/wast-printer": "1.11.1" - } - }, - "node_modules/@webassemblyjs/wasm-gen": { - "version": "1.11.1", - "resolved": "https://registry.npmjs.org/@webassemblyjs/wasm-gen/-/wasm-gen-1.11.1.tgz", - "integrity": "sha512-F7QqKXwwNlMmsulj6+O7r4mmtAlCWfO/0HdgOxSklZfQcDu0TpLiD1mRt/zF25Bk59FIjEuGAIyn5ei4yMfLhA==", - "dependencies": { - "@webassemblyjs/ast": "1.11.1", - "@webassemblyjs/helper-wasm-bytecode": "1.11.1", - "@webassemblyjs/ieee754": "1.11.1", - "@webassemblyjs/leb128": "1.11.1", - "@webassemblyjs/utf8": "1.11.1" - } - }, - "node_modules/@webassemblyjs/wasm-opt": { - "version": "1.11.1", - "resolved": "https://registry.npmjs.org/@webassemblyjs/wasm-opt/-/wasm-opt-1.11.1.tgz", - "integrity": "sha512-VqnkNqnZlU5EB64pp1l7hdm3hmQw7Vgqa0KF/KCNO9sIpI6Fk6brDEiX+iCOYrvMuBWDws0NkTOxYEb85XQHHw==", - "dependencies": { - "@webassemblyjs/ast": "1.11.1", - "@webassemblyjs/helper-buffer": "1.11.1", - "@webassemblyjs/wasm-gen": "1.11.1", - "@webassemblyjs/wasm-parser": "1.11.1" - } - }, - "node_modules/@webassemblyjs/wasm-parser": { - "version": "1.11.1", - "resolved": "https://registry.npmjs.org/@webassemblyjs/wasm-parser/-/wasm-parser-1.11.1.tgz", - "integrity": "sha512-rrBujw+dJu32gYB7/Lup6UhdkPx9S9SnobZzRVL7VcBH9Bt9bCBLEuX/YXOOtBsOZ4NQrRykKhffRWHvigQvOA==", - "dependencies": { - "@webassemblyjs/ast": "1.11.1", - "@webassemblyjs/helper-api-error": "1.11.1", - "@webassemblyjs/helper-wasm-bytecode": "1.11.1", - "@webassemblyjs/ieee754": "1.11.1", - "@webassemblyjs/leb128": "1.11.1", - "@webassemblyjs/utf8": "1.11.1" - } - }, - "node_modules/@webassemblyjs/wast-printer": { - "version": "1.11.1", - "resolved": "https://registry.npmjs.org/@webassemblyjs/wast-printer/-/wast-printer-1.11.1.tgz", - "integrity": "sha512-IQboUWM4eKzWW+N/jij2sRatKMh99QEelo3Eb2q0qXkvPRISAj8Qxtmw5itwqK+TTkBuUIE45AxYPToqPtL5gg==", - "dependencies": { - "@webassemblyjs/ast": "1.11.1", - "@xtuc/long": "4.2.2" - } - }, - "node_modules/@webpack-cli/configtest": { - "version": "1.2.0", - "resolved": "https://registry.npmjs.org/@webpack-cli/configtest/-/configtest-1.2.0.tgz", - "integrity": "sha512-4FB8Tj6xyVkyqjj1OaTqCjXYULB9FMkqQ8yGrZjRDrYh0nOE+7Lhs45WioWQQMV+ceFlE368Ukhe6xdvJM9Egg==", - "dev": true, - "peerDependencies": { - "webpack": "4.x.x || 5.x.x", - "webpack-cli": "4.x.x" - } - }, - "node_modules/@webpack-cli/info": { - "version": "1.5.0", - "resolved": "https://registry.npmjs.org/@webpack-cli/info/-/info-1.5.0.tgz", - "integrity": "sha512-e8tSXZpw2hPl2uMJY6fsMswaok5FdlGNRTktvFk2sD8RjH0hE2+XistawJx1vmKteh4NmGmNUrp+Tb2w+udPcQ==", - "dev": true, - "dependencies": { - "envinfo": "^7.7.3" - }, - "peerDependencies": { - "webpack-cli": "4.x.x" - } - }, - "node_modules/@webpack-cli/serve": { - "version": "1.7.0", - "resolved": "https://registry.npmjs.org/@webpack-cli/serve/-/serve-1.7.0.tgz", - "integrity": "sha512-oxnCNGj88fL+xzV+dacXs44HcDwf1ovs3AuEzvP7mqXw7fQntqIhQ1BRmynh4qEKQSSSRSWVyXRjmTbZIX9V2Q==", - "dev": true, - "peerDependencies": { - "webpack-cli": "4.x.x" - }, - "peerDependenciesMeta": { - "webpack-dev-server": { - "optional": true - } - } - }, - "node_modules/@xtuc/ieee754": { - "version": "1.2.0", - "resolved": "https://registry.npmjs.org/@xtuc/ieee754/-/ieee754-1.2.0.tgz", - "integrity": "sha512-DX8nKgqcGwsc0eJSqYt5lwP4DH5FlHnmuWWBRy7X0NcaGR0ZtuyeESgMwTYVEtxmsNGY+qit4QYT/MIYTOTPeA==" - }, - "node_modules/@xtuc/long": { - "version": "4.2.2", - "resolved": "https://registry.npmjs.org/@xtuc/long/-/long-4.2.2.tgz", - "integrity": "sha512-NuHqBY1PB/D8xU6s/thBgOAiAP7HOYDQ32+BFZILJ8ivkUkAHQnWfn6WhL79Owj1qmUnoN/YPhktdIoucipkAQ==" - }, - "node_modules/accepts": { - "version": "1.3.8", - "resolved": "https://registry.npmjs.org/accepts/-/accepts-1.3.8.tgz", - "integrity": "sha512-PYAthTa2m2VKxuvSD3DPC/Gy+U+sOA1LAuT8mkmRuvw+NACSaeXEQ+NHcVF7rONl6qcaxV3Uuemwawk+7+SJLw==", - "dev": true, - "dependencies": { - "mime-types": "~2.1.34", - "negotiator": "0.6.3" - }, - "engines": { - "node": ">= 0.6" - } - }, - "node_modules/acorn": { - "version": "8.7.0", - "resolved": "https://registry.npmjs.org/acorn/-/acorn-8.7.0.tgz", - "integrity": "sha512-V/LGr1APy+PXIwKebEWrkZPwoeoF+w1jiOBUmuxuiUIaOHtob8Qc9BTrYo7VuI5fR8tqsy+buA2WFooR5olqvQ==", - "bin": { - "acorn": "bin/acorn" - }, - "engines": { - "node": ">=0.4.0" - } - }, - "node_modules/acorn-import-assertions": { - "version": "1.8.0", - "resolved": "https://registry.npmjs.org/acorn-import-assertions/-/acorn-import-assertions-1.8.0.tgz", - "integrity": "sha512-m7VZ3jwz4eK6A4Vtt8Ew1/mNbP24u0FhdyfA7fSvnJR6LMdfOYnmuIrrJAgrYfYJ10F/otaHTtrtrtmHdMNzEw==", - "peerDependencies": { - "acorn": "^8" - } - }, - "node_modules/agent-base": { - "version": "6.0.2", - "resolved": "https://registry.npmjs.org/agent-base/-/agent-base-6.0.2.tgz", - "integrity": "sha512-RZNwNclF7+MS/8bDg70amg32dyeZGZxiDuQmZxKLAlQjr3jGyLx+4Kkk58UO7D2QdgFIQCovuSuZESne6RG6XQ==", - "dependencies": { - "debug": "4" - }, - "engines": { - "node": ">= 6.0.0" - } - }, - "node_modules/agent-base/node_modules/debug": { - "version": "4.3.4", - "resolved": "https://registry.npmjs.org/debug/-/debug-4.3.4.tgz", - "integrity": "sha512-PRWFHuSU3eDtQJPvnNY7Jcket1j0t5OuOsFzPPzsekD52Zl8qUfFIPEiswXqIvHWGVHOgX+7G/vCNNhehwxfkQ==", - "dependencies": { - "ms": "2.1.2" - }, - "engines": { - "node": ">=6.0" - }, - "peerDependenciesMeta": { - "supports-color": { - "optional": true - } - } - }, - "node_modules/agent-base/node_modules/ms": { - "version": "2.1.2", - "resolved": "https://registry.npmjs.org/ms/-/ms-2.1.2.tgz", - "integrity": "sha512-sGkPx+VjMtmA6MX27oA4FBFELFCZZ4S4XqeGOXCv68tT+jb3vk/RyaKWP0PTKyWtmLSM0b+adUTEvbs1PEaH2w==" - }, - "node_modules/aggregate-error": { - "version": "3.1.0", - "resolved": "https://registry.npmjs.org/aggregate-error/-/aggregate-error-3.1.0.tgz", - "integrity": "sha512-4I7Td01quW/RpocfNayFdFVk1qSuoh0E7JrbRJ16nH01HhKFQ88INq9Sd+nd72zqRySlr9BmDA8xlEJ6vJMrYA==", - "dev": true, - "dependencies": { - "clean-stack": "^2.0.0", - "indent-string": "^4.0.0" - }, - "engines": { - "node": ">=8" - } - }, - "node_modules/ajv": { - "version": "6.12.6", - "resolved": "https://registry.npmjs.org/ajv/-/ajv-6.12.6.tgz", - "integrity": "sha512-j3fVLgvTo527anyYyJOGTYJbG+vnnQYvE0m5mmkc1TK+nxAppkCLMIL0aZ4dblVCNoGShhm+kzE4ZUykBoMg4g==", - "dependencies": { - "fast-deep-equal": "^3.1.1", - "fast-json-stable-stringify": "^2.0.0", - "json-schema-traverse": "^0.4.1", - "uri-js": "^4.2.2" - }, - "funding": { - "type": "github", - "url": "https://github.com/sponsors/epoberezkin" - } - }, - "node_modules/ajv-formats": { - "version": "2.1.1", - "resolved": "https://registry.npmjs.org/ajv-formats/-/ajv-formats-2.1.1.tgz", - "integrity": "sha512-Wx0Kx52hxE7C18hkMEggYlEifqWZtYaRgouJor+WMdPnQyEK13vgEWyVNup7SoeeoLMsr4kf5h6dOW11I15MUA==", - "dev": true, - "dependencies": { - "ajv": "^8.0.0" - }, - "peerDependencies": { - "ajv": "^8.0.0" - }, - "peerDependenciesMeta": { - "ajv": { - "optional": true - } - } - }, - "node_modules/ajv-formats/node_modules/ajv": { - "version": "8.9.0", - "resolved": "https://registry.npmjs.org/ajv/-/ajv-8.9.0.tgz", - "integrity": "sha512-qOKJyNj/h+OWx7s5DePL6Zu1KeM9jPZhwBqs+7DzP6bGOvqzVCSf0xueYmVuaC/oQ/VtS2zLMLHdQFbkka+XDQ==", - "dev": true, - "dependencies": { - "fast-deep-equal": "^3.1.1", - "json-schema-traverse": "^1.0.0", - "require-from-string": "^2.0.2", - "uri-js": "^4.2.2" - }, - "funding": { - "type": "github", - "url": "https://github.com/sponsors/epoberezkin" - } - }, - "node_modules/ajv-formats/node_modules/json-schema-traverse": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/json-schema-traverse/-/json-schema-traverse-1.0.0.tgz", - "integrity": "sha512-NM8/P9n3XjXhIZn1lLhkFaACTOURQXjWhV4BA/RnOv8xvgqtqpAX9IO4mRQxSx1Rlo4tqzeqb0sOlruaOy3dug==", - "dev": true - }, - "node_modules/ajv-keywords": { - "version": "3.5.2", - "resolved": "https://registry.npmjs.org/ajv-keywords/-/ajv-keywords-3.5.2.tgz", - "integrity": "sha512-5p6WTN0DdTGVQk6VjcEju19IgaHudalcfabD7yhDGeA6bcQnmL+CpveLJq/3hvfwd1aof6L386Ougkx6RfyMIQ==", - "peerDependencies": { - "ajv": "^6.9.1" - } - }, - "node_modules/ansi-html-community": { - "version": "0.0.8", - "resolved": "https://registry.npmjs.org/ansi-html-community/-/ansi-html-community-0.0.8.tgz", - "integrity": "sha512-1APHAyr3+PCamwNw3bXCPp4HFLONZt/yIH0sZp0/469KWNTEy+qN5jQ3GVX6DMZ1UXAi34yVwtTeaG/HpBuuzw==", - "dev": true, - "engines": [ - "node >= 0.8.0" - ], - "bin": { - "ansi-html": "bin/ansi-html" - } - }, - "node_modules/ansi-regex": { - "version": "5.0.1", - "resolved": "https://registry.npmjs.org/ansi-regex/-/ansi-regex-5.0.1.tgz", - "integrity": "sha512-quJQXlTSUGL2LH9SUXo8VwsY4soanhgo6LNSm84E1LBcE8s3O0wpdiRzyR9z/ZZJMlMWv37qOOb9pdJlMUEKFQ==", - "dev": true, - "engines": { - "node": ">=8" - } - }, - "node_modules/anymatch": { - "version": "3.1.2", - "resolved": "https://registry.npmjs.org/anymatch/-/anymatch-3.1.2.tgz", - "integrity": "sha512-P43ePfOAIupkguHUycrc4qJ9kz8ZiuOUijaETwX7THt0Y/GNK7v0aa8rY816xWjZ7rJdA5XdMcpVFTKMq+RvWg==", - "dev": true, - "dependencies": { - "normalize-path": "^3.0.0", - "picomatch": "^2.0.4" - }, - "engines": { - "node": ">= 8" - } - }, - "node_modules/apply-args-browser": { - "version": "0.0.1", - "resolved": "https://registry.npmjs.org/apply-args-browser/-/apply-args-browser-0.0.1.tgz", - "integrity": "sha512-gq4ldo4Fk5SEVpeW/0yBe0v5g3VDEWAm9LB80zGarYtDvojTD7ar0Y/WvIy9gYAkKmlE3USu5wYwKKCqOXfNkg==" - }, - "node_modules/apply-args-nodejs": { - "version": "0.0.1", - "resolved": "https://registry.npmjs.org/apply-args-nodejs/-/apply-args-nodejs-0.0.1.tgz", - "integrity": "sha512-JwZPEvEDrL+4y16Un6FcNjDSITpsBykchgwPh8UtxnziYrbxKAc2BUfyC5uvA6ZVIhQjiO4r+Kg1MQ3nqWk+1Q==" - }, - "node_modules/array-flatten": { - "version": "2.1.2", - "resolved": "https://registry.npmjs.org/array-flatten/-/array-flatten-2.1.2.tgz", - "integrity": "sha512-hNfzcOV8W4NdualtqBFPyVO+54DSJuZGY9qT4pRroB6S9e3iiido2ISIC5h9R2sPJ8H3FHCIiEnsv1lPXO3KtQ==", - "dev": true - }, - "node_modules/asn1.js": { - "version": "5.4.1", - "resolved": "https://registry.npmjs.org/asn1.js/-/asn1.js-5.4.1.tgz", - "integrity": "sha512-+I//4cYPccV8LdmBLiX8CYvf9Sp3vQsrqu2QNXRcrbiWvcx/UdlFiqUJJzxRQxgsZmvhXhn4cSKeSmoFjVdupA==", - "dependencies": { - "bn.js": "^4.0.0", - "inherits": "^2.0.1", - "minimalistic-assert": "^1.0.0", - "safer-buffer": "^2.1.0" - } - }, - "node_modules/asn1.js/node_modules/bn.js": { - "version": "4.12.0", - "resolved": "https://registry.npmjs.org/bn.js/-/bn.js-4.12.0.tgz", - "integrity": "sha512-c98Bf3tPniI+scsdk237ku1Dc3ujXQTSgyiPUDEOe7tRkhrqridvh8klBv0HCEso1OLOYcHuCv/cS6DNxKH+ZA==" - }, - "node_modules/assert": { - "version": "2.0.0", - "resolved": "https://registry.npmjs.org/assert/-/assert-2.0.0.tgz", - "integrity": "sha512-se5Cd+js9dXJnu6Ag2JFc00t+HmHOen+8Q+L7O9zI0PqQXr20uk2J0XQqMxZEeo5U50o8Nvmmx7dZrl+Ufr35A==", - "dependencies": { - "es6-object-assign": "^1.1.0", - "is-nan": "^1.2.1", - "object-is": "^1.0.1", - "util": "^0.12.0" - } - }, - "node_modules/async": { - "version": "2.6.3", - "resolved": "https://registry.npmjs.org/async/-/async-2.6.3.tgz", - "integrity": "sha512-zflvls11DCy+dQWzTW2dzuilv8Z5X/pjfmZOWba6TNIVDm+2UDaJmXSOXlasHKfNBs8oo3M0aT50fDEWfKZjXg==", - "dev": true, - "dependencies": { - "lodash": "^4.17.14" - } - }, - "node_modules/available-typed-arrays": { - "version": "1.0.5", - "resolved": "https://registry.npmjs.org/available-typed-arrays/-/available-typed-arrays-1.0.5.tgz", - "integrity": "sha512-DMD0KiN46eipeziST1LPP/STfDU0sufISXmjSgvVsoU2tqxctQeASejWcfNtxYKqETM1UxQ8sp2OrSBWpHY6sw==", - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/balanced-match": { - "version": "1.0.2", - "resolved": "https://registry.npmjs.org/balanced-match/-/balanced-match-1.0.2.tgz", - "integrity": "sha512-3oSeUO0TMV67hN1AmbXsK4yaqU7tjiHlbxRDZOpH0KW9+CeX4bRAaX0Anxt0tx2MrpRpWwQaPwIlISEJhYU5Pw==" - }, - "node_modules/base64-js": { - "version": "1.5.1", - "resolved": "https://registry.npmjs.org/base64-js/-/base64-js-1.5.1.tgz", - "integrity": "sha512-AKpaYlHn8t4SVbOHCy+b5+KKgvR4vrsD8vbvrbiQJps7fKDTkjkDry6ji0rUJjC0kzbNePLwzxq8iypo41qeWA==", - "funding": [ - { - "type": "github", - "url": "https://github.com/sponsors/feross" - }, - { - "type": "patreon", - "url": "https://www.patreon.com/feross" - }, - { - "type": "consulting", - "url": "https://feross.org/support" - } - ] - }, - "node_modules/batch": { - "version": "0.6.1", - "resolved": "https://registry.npmjs.org/batch/-/batch-0.6.1.tgz", - "integrity": "sha1-3DQxT05nkxgJP8dgJyUl+UvyXBY=", - "dev": true - }, - "node_modules/big-integer": { - "version": "1.6.51", - "resolved": "https://registry.npmjs.org/big-integer/-/big-integer-1.6.51.tgz", - "integrity": "sha512-GPEid2Y9QU1Exl1rpO9B2IPJGHPSupF5GnVIP0blYvNOMer2bTvSWs1jGOUg04hTmu67nmLsQ9TBo1puaotBHg==", - "engines": { - "node": ">=0.6" - } - }, - "node_modules/bignumber.js": { - "version": "9.1.1", - "resolved": "https://registry.npmjs.org/bignumber.js/-/bignumber.js-9.1.1.tgz", - "integrity": "sha512-pHm4LsMJ6lzgNGVfZHjMoO8sdoRhOzOH4MLmY65Jg70bpxCKu5iOHNJyfF6OyvYw7t8Fpf35RuzUyqnQsj8Vig==", - "engines": { - "node": "*" - } - }, - "node_modules/binary-extensions": { - "version": "2.2.0", - "resolved": "https://registry.npmjs.org/binary-extensions/-/binary-extensions-2.2.0.tgz", - "integrity": "sha512-jDctJ/IVQbZoJykoeHbhXpOlNBqGNcwXJKJog42E5HDPUwQTSdjCHdihjj0DlnheQ7blbT6dHOafNAiS8ooQKA==", - "dev": true, - "engines": { - "node": ">=8" - } - }, - "node_modules/bl": { - "version": "4.1.0", - "resolved": "https://registry.npmjs.org/bl/-/bl-4.1.0.tgz", - "integrity": "sha512-1W07cM9gS6DcLperZfFSj+bWLtaPGSOHWhPiGzXmvVJbRLdG82sH/Kn8EtW1VqWVA54AKf2h5k5BbnIbwF3h6w==", - "dependencies": { - "buffer": "^5.5.0", - "inherits": "^2.0.4", - "readable-stream": "^3.4.0" - } - }, - "node_modules/bl/node_modules/buffer": { - "version": "5.7.1", - "resolved": "https://registry.npmjs.org/buffer/-/buffer-5.7.1.tgz", - "integrity": "sha512-EHcyIPBQ4BSGlvjB16k5KgAJ27CIsHY/2JBmCRReo48y9rQ3MaUzWX3KVlBa4U7MyX02HdVj0K7C3WaB3ju7FQ==", - "funding": [ - { - "type": "github", - "url": "https://github.com/sponsors/feross" - }, - { - "type": "patreon", - "url": "https://www.patreon.com/feross" - }, - { - "type": "consulting", - "url": "https://feross.org/support" - } - ], - "dependencies": { - "base64-js": "^1.3.1", - "ieee754": "^1.1.13" - } - }, - "node_modules/blakejs": { - "version": "1.2.1", - "resolved": "https://registry.npmjs.org/blakejs/-/blakejs-1.2.1.tgz", - "integrity": "sha512-QXUSXI3QVc/gJME0dBpXrag1kbzOqCjCX8/b54ntNyW6sjtoqxqRk3LTmXzaJoh71zMsDCjM+47jS7XiwN/+fQ==" - }, - "node_modules/bn.js": { - "version": "5.2.0", - "resolved": "https://registry.npmjs.org/bn.js/-/bn.js-5.2.0.tgz", - "integrity": "sha512-D7iWRBvnZE8ecXiLj/9wbxH7Tk79fAh8IHaTNq1RWRixsS02W+5qS+iE9yq6RYl0asXx5tw0bLhmT5pIfbSquw==" - }, - "node_modules/body-parser": { - "version": "1.19.1", - "resolved": "https://registry.npmjs.org/body-parser/-/body-parser-1.19.1.tgz", - "integrity": "sha512-8ljfQi5eBk8EJfECMrgqNGWPEY5jWP+1IzkzkGdFFEwFQZZyaZ21UqdaHktgiMlH0xLHqIFtE/u2OYE5dOtViA==", - "dev": true, - "dependencies": { - "bytes": "3.1.1", - "content-type": "~1.0.4", - "debug": "2.6.9", - "depd": "~1.1.2", - "http-errors": "1.8.1", - "iconv-lite": "0.4.24", - "on-finished": "~2.3.0", - "qs": "6.9.6", - "raw-body": "2.4.2", - "type-is": "~1.6.18" - }, - "engines": { - "node": ">= 0.8" - } - }, - "node_modules/body-parser/node_modules/bytes": { - "version": "3.1.1", - "resolved": "https://registry.npmjs.org/bytes/-/bytes-3.1.1.tgz", - "integrity": "sha512-dWe4nWO/ruEOY7HkUJ5gFt1DCFV9zPRoJr8pV0/ASQermOZjtq8jMjOprC0Kd10GLN+l7xaUPvxzJFWtxGu8Fg==", - "dev": true, - "engines": { - "node": ">= 0.8" - } - }, - "node_modules/bonjour": { - "version": "3.5.0", - "resolved": "https://registry.npmjs.org/bonjour/-/bonjour-3.5.0.tgz", - "integrity": "sha1-jokKGD2O6aI5OzhExpGkK897yfU=", - "dev": true, - "dependencies": { - "array-flatten": "^2.1.0", - "deep-equal": "^1.0.1", - "dns-equal": "^1.0.0", - "dns-txt": "^2.0.2", - "multicast-dns": "^6.0.1", - "multicast-dns-service-types": "^1.1.0" - } - }, - "node_modules/boolbase": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/boolbase/-/boolbase-1.0.0.tgz", - "integrity": "sha1-aN/1++YMUes3cl6p4+0xDcwed24=", - "dev": true - }, - "node_modules/brace-expansion": { - "version": "1.1.11", - "resolved": "https://registry.npmjs.org/brace-expansion/-/brace-expansion-1.1.11.tgz", - "integrity": "sha512-iCuPHDFgrHX7H2vEI/5xpz07zSHB00TpugqhmYtVmMO6518mCuRMoOYFldEBl0g187ufozdaHgWKcYFb61qGiA==", - "dependencies": { - "balanced-match": "^1.0.0", - "concat-map": "0.0.1" - } - }, - "node_modules/braces": { - "version": "3.0.2", - "resolved": "https://registry.npmjs.org/braces/-/braces-3.0.2.tgz", - "integrity": "sha512-b8um+L1RzM3WDSzvhm6gIz1yfTbBt6YTlcEKAvsmqCZZFw46z626lVj9j1yEPW33H5H+lBQpZMP1k8l+78Ha0A==", - "dev": true, - "dependencies": { - "fill-range": "^7.0.1" - }, - "engines": { - "node": ">=8" - } - }, - "node_modules/brorand": { - "version": "1.1.0", - "resolved": "https://registry.npmjs.org/brorand/-/brorand-1.1.0.tgz", - "integrity": "sha1-EsJe/kCkXjwyPrhnWgoM5XsiNx8=" - }, - "node_modules/browserify-aes": { - "version": "1.2.0", - "resolved": "https://registry.npmjs.org/browserify-aes/-/browserify-aes-1.2.0.tgz", - "integrity": "sha512-+7CHXqGuspUn/Sl5aO7Ea0xWGAtETPXNSAjHo48JfLdPWcMng33Xe4znFvQweqc/uzk5zSOI3H52CYnjCfb5hA==", - "dependencies": { - "buffer-xor": "^1.0.3", - "cipher-base": "^1.0.0", - "create-hash": "^1.1.0", - "evp_bytestokey": "^1.0.3", - "inherits": "^2.0.1", - "safe-buffer": "^5.0.1" - } - }, - "node_modules/browserify-cipher": { - "version": "1.0.1", - "resolved": "https://registry.npmjs.org/browserify-cipher/-/browserify-cipher-1.0.1.tgz", - "integrity": "sha512-sPhkz0ARKbf4rRQt2hTpAHqn47X3llLkUGn+xEJzLjwY8LRs2p0v7ljvI5EyoRO/mexrNunNECisZs+gw2zz1w==", - "dependencies": { - "browserify-aes": "^1.0.4", - "browserify-des": "^1.0.0", - "evp_bytestokey": "^1.0.0" - } - }, - "node_modules/browserify-des": { - "version": "1.0.2", - "resolved": "https://registry.npmjs.org/browserify-des/-/browserify-des-1.0.2.tgz", - "integrity": "sha512-BioO1xf3hFwz4kc6iBhI3ieDFompMhrMlnDFC4/0/vd5MokpuAc3R+LYbwTA9A5Yc9pq9UYPqffKpW2ObuwX5A==", - "dependencies": { - "cipher-base": "^1.0.1", - "des.js": "^1.0.0", - "inherits": "^2.0.1", - "safe-buffer": "^5.1.2" - } - }, - "node_modules/browserify-rsa": { - "version": "4.1.0", - "resolved": "https://registry.npmjs.org/browserify-rsa/-/browserify-rsa-4.1.0.tgz", - "integrity": "sha512-AdEER0Hkspgno2aR97SAf6vi0y0k8NuOpGnVH3O99rcA5Q6sh8QxcngtHuJ6uXwnfAXNM4Gn1Gb7/MV1+Ymbog==", - "dependencies": { - "bn.js": "^5.0.0", - "randombytes": "^2.0.1" - } - }, - "node_modules/browserify-sign": { - "version": "4.2.1", - "resolved": "https://registry.npmjs.org/browserify-sign/-/browserify-sign-4.2.1.tgz", - "integrity": "sha512-/vrA5fguVAKKAVTNJjgSm1tRQDHUU6DbwO9IROu/0WAzC8PKhucDSh18J0RMvVeHAn5puMd+QHC2erPRNf8lmg==", - "dependencies": { - "bn.js": "^5.1.1", - "browserify-rsa": "^4.0.1", - "create-hash": "^1.2.0", - "create-hmac": "^1.1.7", - "elliptic": "^6.5.3", - "inherits": "^2.0.4", - "parse-asn1": "^5.1.5", - "readable-stream": "^3.6.0", - "safe-buffer": "^5.2.0" - } - }, - "node_modules/browserify-zlib": { - "version": "0.2.0", - "resolved": "https://registry.npmjs.org/browserify-zlib/-/browserify-zlib-0.2.0.tgz", - "integrity": "sha512-Z942RysHXmJrhqk88FmKBVq/v5tqmSkDz7p54G/MGyjMnCFFnC79XWNbg+Vta8W6Wb2qtSZTSxIGkJrRpCFEiA==", - "dependencies": { - "pako": "~1.0.5" - } - }, - "node_modules/browserslist": { - "version": "4.19.1", - "resolved": "https://registry.npmjs.org/browserslist/-/browserslist-4.19.1.tgz", - "integrity": "sha512-u2tbbG5PdKRTUoctO3NBD8FQ5HdPh1ZXPHzp1rwaa5jTc+RV9/+RlWiAIKmjRPQF+xbGM9Kklj5bZQFa2s/38A==", - "dependencies": { - "caniuse-lite": "^1.0.30001286", - "electron-to-chromium": "^1.4.17", - "escalade": "^3.1.1", - "node-releases": "^2.0.1", - "picocolors": "^1.0.0" - }, - "bin": { - "browserslist": "cli.js" - }, - "engines": { - "node": "^6 || ^7 || ^8 || ^9 || ^10 || ^11 || ^12 || >=13.7" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/browserslist" - } - }, - "node_modules/buffer": { - "version": "6.0.3", - "resolved": "https://registry.npmjs.org/buffer/-/buffer-6.0.3.tgz", - "integrity": "sha512-FTiCpNxtwiZZHEZbcbTIcZjERVICn9yq/pDFkTl95/AxzD1naBctN7YO68riM/gLSDY7sdrMby8hofADYuuqOA==", - "funding": [ - { - "type": "github", - "url": "https://github.com/sponsors/feross" - }, - { - "type": "patreon", - "url": "https://www.patreon.com/feross" - }, - { - "type": "consulting", - "url": "https://feross.org/support" - } - ], - "dependencies": { - "base64-js": "^1.3.1", - "ieee754": "^1.2.1" - } - }, - "node_modules/buffer-crc32": { - "version": "0.2.13", - "resolved": "https://registry.npmjs.org/buffer-crc32/-/buffer-crc32-0.2.13.tgz", - "integrity": "sha512-VO9Ht/+p3SN7SKWqcrgEzjGbRSJYTx+Q1pTQC0wrWqHx0vpJraQ6GtHx8tvcg1rlK1byhU5gccxgOgj7B0TDkQ==", - "engines": { - "node": "*" - } - }, - "node_modules/buffer-from": { - "version": "1.1.2", - "resolved": "https://registry.npmjs.org/buffer-from/-/buffer-from-1.1.2.tgz", - "integrity": "sha512-E+XQCRwSbaaiChtv6k6Dwgc+bx+Bs6vuKJHHl5kox/BaKbhiXzqQOwK4cO22yElGp2OCmjwVhT3HmxgyPGnJfQ==" - }, - "node_modules/buffer-indexof": { - "version": "1.1.1", - "resolved": "https://registry.npmjs.org/buffer-indexof/-/buffer-indexof-1.1.1.tgz", - "integrity": "sha512-4/rOEg86jivtPTeOUUT61jJO1Ya1TrR/OkqCSZDyq84WJh3LuuiphBYJN+fm5xufIk4XAFcEwte/8WzC8If/1g==", - "dev": true - }, - "node_modules/buffer-xor": { - "version": "1.0.3", - "resolved": "https://registry.npmjs.org/buffer-xor/-/buffer-xor-1.0.3.tgz", - "integrity": "sha1-JuYe0UIvtw3ULm42cp7VHYVf6Nk=" - }, - "node_modules/bufferutil": { - "version": "4.0.5", - "resolved": "https://registry.npmjs.org/bufferutil/-/bufferutil-4.0.5.tgz", - "integrity": "sha512-HTm14iMQKK2FjFLRTM5lAVcyaUzOnqbPtesFIvREgXpJHdQm8bWS+GkQgIkfaBYRHuCnea7w8UVNfwiAQhlr9A==", - "hasInstallScript": true, - "dependencies": { - "node-gyp-build": "^4.3.0" - }, - "engines": { - "node": ">=6.14.2" - } - }, - "node_modules/bufferutil/node_modules/node-gyp-build": { - "version": "4.3.0", - "resolved": "https://registry.npmjs.org/node-gyp-build/-/node-gyp-build-4.3.0.tgz", - "integrity": "sha512-iWjXZvmboq0ja1pUGULQBexmxq8CV4xBhX7VDOTbL7ZR4FOowwY/VOtRxBN/yKxmdGoIp4j5ysNT4u3S2pDQ3Q==", - "bin": { - "node-gyp-build": "bin.js", - "node-gyp-build-optional": "optional.js", - "node-gyp-build-test": "build-test.js" - } - }, - "node_modules/builtin-status-codes": { - "version": "3.0.0", - "resolved": "https://registry.npmjs.org/builtin-status-codes/-/builtin-status-codes-3.0.0.tgz", - "integrity": "sha1-hZgoeOIbmOHGZCXgPQF0eI9Wnug=" - }, - "node_modules/bytes": { - "version": "3.0.0", - "resolved": "https://registry.npmjs.org/bytes/-/bytes-3.0.0.tgz", - "integrity": "sha1-0ygVQE1olpn4Wk6k+odV3ROpYEg=", - "dev": true, - "engines": { - "node": ">= 0.8" - } - }, - "node_modules/call-bind": { - "version": "1.0.2", - "resolved": "https://registry.npmjs.org/call-bind/-/call-bind-1.0.2.tgz", - "integrity": "sha512-7O+FbCihrB5WGbFYesctwmTKae6rOiIzmz1icreWJ+0aA7LJfuqhEso2T9ncpcFtzMQtzXf2QGGueWJGTYsqrA==", - "dependencies": { - "function-bind": "^1.1.1", - "get-intrinsic": "^1.0.2" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/camel-case": { - "version": "4.1.2", - "resolved": "https://registry.npmjs.org/camel-case/-/camel-case-4.1.2.tgz", - "integrity": "sha512-gxGWBrTT1JuMx6R+o5PTXMmUnhnVzLQ9SNutD4YqKtI6ap897t3tKECYla6gCWEkplXnlNybEkZg9GEGxKFCgw==", - "dev": true, - "dependencies": { - "pascal-case": "^3.1.2", - "tslib": "^2.0.3" - } - }, - "node_modules/caniuse-lite": { - "version": "1.0.30001305", - "resolved": "https://registry.npmjs.org/caniuse-lite/-/caniuse-lite-1.0.30001305.tgz", - "integrity": "sha512-p7d9YQMji8haf0f+5rbcv9WlQ+N5jMPfRAnUmZRlNxsNeBO3Yr7RYG6M2uTY1h9tCVdlkJg6YNNc4kiAiBLdWA==", - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/browserslist" - } - }, - "node_modules/chokidar": { - "version": "3.5.3", - "resolved": "https://registry.npmjs.org/chokidar/-/chokidar-3.5.3.tgz", - "integrity": "sha512-Dr3sfKRP6oTcjf2JmUmFJfeVMvXBdegxB0iVQ5eb2V10uFJUCAS8OByZdVAyVb8xXNz3GjjTgj9kLWsZTqE6kw==", - "dev": true, - "funding": [ - { - "type": "individual", - "url": "https://paulmillr.com/funding/" - } - ], - "dependencies": { - "anymatch": "~3.1.2", - "braces": "~3.0.2", - "glob-parent": "~5.1.2", - "is-binary-path": "~2.1.0", - "is-glob": "~4.0.1", - "normalize-path": "~3.0.0", - "readdirp": "~3.6.0" - }, - "engines": { - "node": ">= 8.10.0" - }, - "optionalDependencies": { - "fsevents": "~2.3.2" - } - }, - "node_modules/chownr": { - "version": "1.1.4", - "resolved": "https://registry.npmjs.org/chownr/-/chownr-1.1.4.tgz", - "integrity": "sha512-jJ0bqzaylmJtVnNgzTeSOs8DPavpbYgEr/b0YL8/2GO3xJEhInFmhKMUnEJQjZumK7KXGFhUy89PrsJWlakBVg==" - }, - "node_modules/chrome-trace-event": { - "version": "1.0.3", - "resolved": "https://registry.npmjs.org/chrome-trace-event/-/chrome-trace-event-1.0.3.tgz", - "integrity": "sha512-p3KULyQg4S7NIHixdwbGX+nFHkoBiA4YQmyWtjb8XngSKV124nJmRysgAeujbUVb15vh+RvFUfCPqU7rXk+hZg==", - "engines": { - "node": ">=6.0" - } - }, - "node_modules/cipher-base": { - "version": "1.0.4", - "resolved": "https://registry.npmjs.org/cipher-base/-/cipher-base-1.0.4.tgz", - "integrity": "sha512-Kkht5ye6ZGmwv40uUDZztayT2ThLQGfnj/T71N/XzeZeo3nf8foyW7zGTsPYkEya3m5f3cAypH+qe7YOrM1U2Q==", - "dependencies": { - "inherits": "^2.0.1", - "safe-buffer": "^5.0.1" - } - }, - "node_modules/clean-css": { - "version": "5.2.4", - "resolved": "https://registry.npmjs.org/clean-css/-/clean-css-5.2.4.tgz", - "integrity": "sha512-nKseG8wCzEuji/4yrgM/5cthL9oTDc5UOQyFMvW/Q53oP6gLH690o1NbuTh6Y18nujr7BxlsFuS7gXLnLzKJGg==", - "dev": true, - "dependencies": { - "source-map": "~0.6.0" - }, - "engines": { - "node": ">= 10.0" - } - }, - "node_modules/clean-stack": { - "version": "2.2.0", - "resolved": "https://registry.npmjs.org/clean-stack/-/clean-stack-2.2.0.tgz", - "integrity": "sha512-4diC9HaTE+KRAMWhDhrGOECgWZxoevMc5TlkObMqNSsVU62PYzXZ/SMTjzyGAFF1YusgxGcSWTEXBhp0CPwQ1A==", - "dev": true, - "engines": { - "node": ">=6" - } - }, - "node_modules/clone-deep": { - "version": "4.0.1", - "resolved": "https://registry.npmjs.org/clone-deep/-/clone-deep-4.0.1.tgz", - "integrity": "sha512-neHB9xuzh/wk0dIHweyAXv2aPGZIVk3pLMe+/RNzINf17fe0OG96QroktYAUm7SM1PBnzTabaLboqqxDyMU+SQ==", - "dev": true, - "dependencies": { - "is-plain-object": "^2.0.4", - "kind-of": "^6.0.2", - "shallow-clone": "^3.0.0" - }, - "engines": { - "node": ">=6" - } - }, - "node_modules/colorette": { - "version": "2.0.16", - "resolved": "https://registry.npmjs.org/colorette/-/colorette-2.0.16.tgz", - "integrity": "sha512-hUewv7oMjCp+wkBv5Rm0v87eJhq4woh5rSR+42YSQJKecCqgIqNkZ6lAlQms/BwHPJA5NKMRlpxPRv0n8HQW6g==", - "dev": true - }, - "node_modules/commander": { - "version": "8.3.0", - "resolved": "https://registry.npmjs.org/commander/-/commander-8.3.0.tgz", - "integrity": "sha512-OkTL9umf+He2DZkUq8f8J9of7yL6RJKI24dVITBmNfZBmri9zYZQrKkuXiKhyfPSu8tUhnVBB1iKXevvnlR4Ww==", - "dev": true, - "engines": { - "node": ">= 12" - } - }, - "node_modules/compressible": { - "version": "2.0.18", - "resolved": "https://registry.npmjs.org/compressible/-/compressible-2.0.18.tgz", - "integrity": "sha512-AF3r7P5dWxL8MxyITRMlORQNaOA2IkAFaTr4k7BUumjPtRpGDTZpl0Pb1XCO6JeDCBdp126Cgs9sMxqSjgYyRg==", - "dev": true, - "dependencies": { - "mime-db": ">= 1.43.0 < 2" - }, - "engines": { - "node": ">= 0.6" - } - }, - "node_modules/compression": { - "version": "1.7.4", - "resolved": "https://registry.npmjs.org/compression/-/compression-1.7.4.tgz", - "integrity": "sha512-jaSIDzP9pZVS4ZfQ+TzvtiWhdpFhE2RDHz8QJkpX9SIpLq88VueF5jJw6t+6CUQcAoA6t+x89MLrWAqpfDE8iQ==", - "dev": true, - "dependencies": { - "accepts": "~1.3.5", - "bytes": "3.0.0", - "compressible": "~2.0.16", - "debug": "2.6.9", - "on-headers": "~1.0.2", - "safe-buffer": "5.1.2", - "vary": "~1.1.2" - }, - "engines": { - "node": ">= 0.8.0" - } - }, - "node_modules/compression/node_modules/safe-buffer": { - "version": "5.1.2", - "resolved": "https://registry.npmjs.org/safe-buffer/-/safe-buffer-5.1.2.tgz", - "integrity": "sha512-Gd2UZBJDkXlY7GbJxfsE8/nvKkUEU1G38c1siN6QP6a9PT9MmHB8GnpscSmMJSoF8LOIrt8ud/wPtojys4G6+g==", - "dev": true - }, - "node_modules/concat-map": { - "version": "0.0.1", - "resolved": "https://registry.npmjs.org/concat-map/-/concat-map-0.0.1.tgz", - "integrity": "sha1-2Klr13/Wjfd5OnMDajug1UBdR3s=" - }, - "node_modules/connect-history-api-fallback": { - "version": "1.6.0", - "resolved": "https://registry.npmjs.org/connect-history-api-fallback/-/connect-history-api-fallback-1.6.0.tgz", - "integrity": "sha512-e54B99q/OUoH64zYYRf3HBP5z24G38h5D3qXu23JGRoigpX5Ss4r9ZnDk3g0Z8uQC2x2lPaJ+UlWBc1ZWBWdLg==", - "dev": true, - "engines": { - "node": ">=0.8" - } - }, - "node_modules/console-browserify": { - "version": "1.2.0", - "resolved": "https://registry.npmjs.org/console-browserify/-/console-browserify-1.2.0.tgz", - "integrity": "sha512-ZMkYO/LkF17QvCPqM0gxw8yUzigAOZOSWSHg91FH6orS7vcEj5dVZTidN2fQ14yBSdg97RqhSNwLUXInd52OTA==" - }, - "node_modules/constants-browserify": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/constants-browserify/-/constants-browserify-1.0.0.tgz", - "integrity": "sha1-wguW2MYXdIqvHBYCF2DNJ/y4y3U=" - }, - "node_modules/content-disposition": { - "version": "0.5.4", - "resolved": "https://registry.npmjs.org/content-disposition/-/content-disposition-0.5.4.tgz", - "integrity": "sha512-FveZTNuGw04cxlAiWbzi6zTAL/lhehaWbTtgluJh4/E95DqMwTmha3KZN1aAWA8cFIhHzMZUvLevkw5Rqk+tSQ==", - "dev": true, - "dependencies": { - "safe-buffer": "5.2.1" - }, - "engines": { - "node": ">= 0.6" - } - }, - "node_modules/content-type": { - "version": "1.0.4", - "resolved": "https://registry.npmjs.org/content-type/-/content-type-1.0.4.tgz", - "integrity": "sha512-hIP3EEPs8tB9AT1L+NUqtwOAps4mk2Zob89MWXMHjHWg9milF/j4osnnQLXBCBFBk/tvIG/tUc9mOUJiPBhPXA==", - "dev": true, - "engines": { - "node": ">= 0.6" - } - }, - "node_modules/cookie": { - "version": "0.4.1", - "resolved": "https://registry.npmjs.org/cookie/-/cookie-0.4.1.tgz", - "integrity": "sha512-ZwrFkGJxUR3EIoXtO+yVE69Eb7KlixbaeAWfBQB9vVsNn/o+Yw69gBWSSDK825hQNdN+wF8zELf3dFNl/kxkUA==", - "dev": true, - "engines": { - "node": ">= 0.6" - } - }, - "node_modules/cookie-signature": { - "version": "1.0.6", - "resolved": "https://registry.npmjs.org/cookie-signature/-/cookie-signature-1.0.6.tgz", - "integrity": "sha1-4wOogrNCzD7oylE6eZmXNNqzriw=", - "dev": true - }, - "node_modules/core-util-is": { - "version": "1.0.3", - "resolved": "https://registry.npmjs.org/core-util-is/-/core-util-is-1.0.3.tgz", - "integrity": "sha512-ZQBvi1DcpJ4GDqanjucZ2Hj3wEO5pZDS89BWbkcrvdxksJorwUDDZamX9ldFkp9aw2lmBDLgkObEA4DWNJ9FYQ==", - "dev": true - }, - "node_modules/create-ecdh": { - "version": "4.0.4", - "resolved": "https://registry.npmjs.org/create-ecdh/-/create-ecdh-4.0.4.tgz", - "integrity": "sha512-mf+TCx8wWc9VpuxfP2ht0iSISLZnt0JgWlrOKZiNqyUZWnjIaCIVNQArMHnCZKfEYRg6IM7A+NeJoN8gf/Ws0A==", - "dependencies": { - "bn.js": "^4.1.0", - "elliptic": "^6.5.3" - } - }, - "node_modules/create-ecdh/node_modules/bn.js": { - "version": "4.12.0", - "resolved": "https://registry.npmjs.org/bn.js/-/bn.js-4.12.0.tgz", - "integrity": "sha512-c98Bf3tPniI+scsdk237ku1Dc3ujXQTSgyiPUDEOe7tRkhrqridvh8klBv0HCEso1OLOYcHuCv/cS6DNxKH+ZA==" - }, - "node_modules/create-hash": { - "version": "1.2.0", - "resolved": "https://registry.npmjs.org/create-hash/-/create-hash-1.2.0.tgz", - "integrity": "sha512-z00bCGNHDG8mHAkP7CtT1qVu+bFQUPjYq/4Iv3C3kWjTFV10zIjfSoeqXo9Asws8gwSHDGj/hl2u4OGIjapeCg==", - "dependencies": { - "cipher-base": "^1.0.1", - "inherits": "^2.0.1", - "md5.js": "^1.3.4", - "ripemd160": "^2.0.1", - "sha.js": "^2.4.0" - } - }, - "node_modules/create-hmac": { - "version": "1.1.7", - "resolved": "https://registry.npmjs.org/create-hmac/-/create-hmac-1.1.7.tgz", - "integrity": "sha512-MJG9liiZ+ogc4TzUwuvbER1JRdgvUFSB5+VR/g5h82fGaIRWMWddtKBHi7/sVhfjQZ6SehlyhvQYrcYkaUIpLg==", - "dependencies": { - "cipher-base": "^1.0.3", - "create-hash": "^1.1.0", - "inherits": "^2.0.1", - "ripemd160": "^2.0.0", - "safe-buffer": "^5.0.1", - "sha.js": "^2.4.8" - } - }, - "node_modules/cross-fetch": { - "version": "3.1.5", - "resolved": "https://registry.npmjs.org/cross-fetch/-/cross-fetch-3.1.5.tgz", - "integrity": "sha512-lvb1SBsI0Z7GDwmuid+mU3kWVBwTVUbe7S0H52yaaAdQOXq2YktTCZdlAcNKFzE6QtRz0snpw9bNiPeOIkkQvw==", - "dependencies": { - "node-fetch": "2.6.7" - } - }, - "node_modules/cross-spawn": { - "version": "7.0.3", - "resolved": "https://registry.npmjs.org/cross-spawn/-/cross-spawn-7.0.3.tgz", - "integrity": "sha512-iRDPJKUPVEND7dHPO8rkbOnPpyDygcDFtWjpeWNCgy8WP2rXcxXL8TskReQl6OrB2G7+UJrags1q15Fudc7G6w==", - "dev": true, - "dependencies": { - "path-key": "^3.1.0", - "shebang-command": "^2.0.0", - "which": "^2.0.1" - }, - "engines": { - "node": ">= 8" - } - }, - "node_modules/crypto-browserify": { - "version": "3.12.0", - "resolved": "https://registry.npmjs.org/crypto-browserify/-/crypto-browserify-3.12.0.tgz", - "integrity": "sha512-fz4spIh+znjO2VjL+IdhEpRJ3YN6sMzITSBijk6FK2UvTqruSQW+/cCZTSNsMiZNvUeq0CqurF+dAbyiGOY6Wg==", - "dependencies": { - "browserify-cipher": "^1.0.0", - "browserify-sign": "^4.0.0", - "create-ecdh": "^4.0.0", - "create-hash": "^1.1.0", - "create-hmac": "^1.1.0", - "diffie-hellman": "^5.0.0", - "inherits": "^2.0.1", - "pbkdf2": "^3.0.3", - "public-encrypt": "^4.0.0", - "randombytes": "^2.0.0", - "randomfill": "^1.0.3" - }, - "engines": { - "node": "*" - } - }, - "node_modules/css-select": { - "version": "4.2.1", - "resolved": "https://registry.npmjs.org/css-select/-/css-select-4.2.1.tgz", - "integrity": "sha512-/aUslKhzkTNCQUB2qTX84lVmfia9NyjP3WpDGtj/WxhwBzWBYUV3DgUpurHTme8UTPcPlAD1DJ+b0nN/t50zDQ==", - "dev": true, - "dependencies": { - "boolbase": "^1.0.0", - "css-what": "^5.1.0", - "domhandler": "^4.3.0", - "domutils": "^2.8.0", - "nth-check": "^2.0.1" - }, - "funding": { - "url": "https://github.com/sponsors/fb55" - } - }, - "node_modules/css-what": { - "version": "5.1.0", - "resolved": "https://registry.npmjs.org/css-what/-/css-what-5.1.0.tgz", - "integrity": "sha512-arSMRWIIFY0hV8pIxZMEfmMI47Wj3R/aWpZDDxWYCPEiOMv6tfOrnpDtgxBYPEQD4V0Y/958+1TdC3iWTFcUPw==", - "dev": true, - "engines": { - "node": ">= 6" - }, - "funding": { - "url": "https://github.com/sponsors/fb55" - } - }, - "node_modules/debug": { - "version": "2.6.9", - "resolved": "https://registry.npmjs.org/debug/-/debug-2.6.9.tgz", - "integrity": "sha512-bC7ElrdJaJnPbAP+1EotYvqZsb3ecl5wi6Bfi6BJTUcNowp6cvspg0jXznRTKDjm/E7AdgFBVeAPVMNcKGsHMA==", - "dev": true, - "dependencies": { - "ms": "2.0.0" - } - }, - "node_modules/deep-equal": { - "version": "1.1.1", - "resolved": "https://registry.npmjs.org/deep-equal/-/deep-equal-1.1.1.tgz", - "integrity": "sha512-yd9c5AdiqVcR+JjcwUQb9DkhJc8ngNr0MahEBGvDiJw8puWab2yZlh+nkasOnZP+EGTAP6rRp2JzJhJZzvNF8g==", - "dev": true, - "dependencies": { - "is-arguments": "^1.0.4", - "is-date-object": "^1.0.1", - "is-regex": "^1.0.4", - "object-is": "^1.0.1", - "object-keys": "^1.1.1", - "regexp.prototype.flags": "^1.2.0" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/default-gateway": { - "version": "6.0.3", - "resolved": "https://registry.npmjs.org/default-gateway/-/default-gateway-6.0.3.tgz", - "integrity": "sha512-fwSOJsbbNzZ/CUFpqFBqYfYNLj1NbMPm8MMCIzHjC83iSJRBEGmDUxU+WP661BaBQImeC2yHwXtz+P/O9o+XEg==", - "dev": true, - "dependencies": { - "execa": "^5.0.0" - }, - "engines": { - "node": ">= 10" - } - }, - "node_modules/define-lazy-prop": { - "version": "2.0.0", - "resolved": "https://registry.npmjs.org/define-lazy-prop/-/define-lazy-prop-2.0.0.tgz", - "integrity": "sha512-Ds09qNh8yw3khSjiJjiUInaGX9xlqZDY7JVryGxdxV7NPeuqQfplOpQ66yJFZut3jLa5zOwkXw1g9EI2uKh4Og==", - "dev": true, - "engines": { - "node": ">=8" - } - }, - "node_modules/define-properties": { - "version": "1.1.3", - "resolved": "https://registry.npmjs.org/define-properties/-/define-properties-1.1.3.tgz", - "integrity": "sha512-3MqfYKj2lLzdMSf8ZIZE/V+Zuy+BgD6f164e8K2w7dgnpKArBDerGYpM46IYYcjnkdPNMjPk9A6VFB8+3SKlXQ==", - "dependencies": { - "object-keys": "^1.0.12" - }, - "engines": { - "node": ">= 0.4" - } - }, - "node_modules/del": { - "version": "6.0.0", - "resolved": "https://registry.npmjs.org/del/-/del-6.0.0.tgz", - "integrity": "sha512-1shh9DQ23L16oXSZKB2JxpL7iMy2E0S9d517ptA1P8iw0alkPtQcrKH7ru31rYtKwF499HkTu+DRzq3TCKDFRQ==", - "dev": true, - "dependencies": { - "globby": "^11.0.1", - "graceful-fs": "^4.2.4", - "is-glob": "^4.0.1", - "is-path-cwd": "^2.2.0", - "is-path-inside": "^3.0.2", - "p-map": "^4.0.0", - "rimraf": "^3.0.2", - "slash": "^3.0.0" - }, - "engines": { - "node": ">=10" - }, - "funding": { - "url": "https://github.com/sponsors/sindresorhus" - } - }, - "node_modules/del/node_modules/array-union": { - "version": "2.1.0", - "resolved": "https://registry.npmjs.org/array-union/-/array-union-2.1.0.tgz", - "integrity": "sha512-HGyxoOTYUyCM6stUe6EJgnd4EoewAI7zMdfqO+kGjnlZmBDz/cR5pf8r/cR4Wq60sL/p0IkcjUEEPwS3GFrIyw==", - "dev": true, - "engines": { - "node": ">=8" - } - }, - "node_modules/del/node_modules/globby": { - "version": "11.1.0", - "resolved": "https://registry.npmjs.org/globby/-/globby-11.1.0.tgz", - "integrity": "sha512-jhIXaOzy1sb8IyocaruWSn1TjmnBVs8Ayhcy83rmxNJ8q2uWKCAj3CnJY+KpGSXCueAPc0i05kVvVKtP1t9S3g==", - "dev": true, - "dependencies": { - "array-union": "^2.1.0", - "dir-glob": "^3.0.1", - "fast-glob": "^3.2.9", - "ignore": "^5.2.0", - "merge2": "^1.4.1", - "slash": "^3.0.0" - }, - "engines": { - "node": ">=10" - }, - "funding": { - "url": "https://github.com/sponsors/sindresorhus" - } - }, - "node_modules/depd": { - "version": "1.1.2", - "resolved": "https://registry.npmjs.org/depd/-/depd-1.1.2.tgz", - "integrity": "sha1-m81S4UwJd2PnSbJ0xDRu0uVgtak=", - "dev": true, - "engines": { - "node": ">= 0.6" - } - }, - "node_modules/des.js": { - "version": "1.0.1", - "resolved": "https://registry.npmjs.org/des.js/-/des.js-1.0.1.tgz", - "integrity": "sha512-Q0I4pfFrv2VPd34/vfLrFOoRmlYj3OV50i7fskps1jZWK1kApMWWT9G6RRUeYedLcBDIhnSDaUvJMb3AhUlaEA==", - "dependencies": { - "inherits": "^2.0.1", - "minimalistic-assert": "^1.0.0" - } - }, - "node_modules/destroy": { - "version": "1.0.4", - "resolved": "https://registry.npmjs.org/destroy/-/destroy-1.0.4.tgz", - "integrity": "sha1-l4hXRCxEdJ5CBmE+N5RiBYJqvYA=", - "dev": true - }, - "node_modules/detect-node": { - "version": "2.1.0", - "resolved": "https://registry.npmjs.org/detect-node/-/detect-node-2.1.0.tgz", - "integrity": "sha512-T0NIuQpnTvFDATNuHN5roPwSBG83rFsuO+MXXH9/3N1eFbn4wcPjttvjMLEPWJ0RGUYgQE7cGgS3tNxbqCGM7g==", - "dev": true - }, - "node_modules/devtools-protocol": { - "version": "0.0.1019158", - "resolved": "https://registry.npmjs.org/devtools-protocol/-/devtools-protocol-0.0.1019158.tgz", - "integrity": "sha512-wvq+KscQ7/6spEV7czhnZc9RM/woz1AY+/Vpd8/h2HFMwJSdTliu7f/yr1A6vDdJfKICZsShqsYpEQbdhg8AFQ==" - }, - "node_modules/diffie-hellman": { - "version": "5.0.3", - "resolved": "https://registry.npmjs.org/diffie-hellman/-/diffie-hellman-5.0.3.tgz", - "integrity": "sha512-kqag/Nl+f3GwyK25fhUMYj81BUOrZ9IuJsjIcDE5icNM9FJHAVm3VcUDxdLPoQtTuUylWm6ZIknYJwwaPxsUzg==", - "dependencies": { - "bn.js": "^4.1.0", - "miller-rabin": "^4.0.0", - "randombytes": "^2.0.0" - } - }, - "node_modules/diffie-hellman/node_modules/bn.js": { - "version": "4.12.0", - "resolved": "https://registry.npmjs.org/bn.js/-/bn.js-4.12.0.tgz", - "integrity": "sha512-c98Bf3tPniI+scsdk237ku1Dc3ujXQTSgyiPUDEOe7tRkhrqridvh8klBv0HCEso1OLOYcHuCv/cS6DNxKH+ZA==" - }, - "node_modules/dir-glob": { - "version": "3.0.1", - "resolved": "https://registry.npmjs.org/dir-glob/-/dir-glob-3.0.1.tgz", - "integrity": "sha512-WkrWp9GR4KXfKGYzOLmTuGVi1UWFfws377n9cc55/tb6DuqyF6pcQ5AbiHEshaDpY9v6oaSr2XCDidGmMwdzIA==", - "dev": true, - "dependencies": { - "path-type": "^4.0.0" - }, - "engines": { - "node": ">=8" - } - }, - "node_modules/dns-equal": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/dns-equal/-/dns-equal-1.0.0.tgz", - "integrity": "sha1-s55/HabrCnW6nBcySzR1PEfgZU0=", - "dev": true - }, - "node_modules/dns-packet": { - "version": "1.3.4", - "resolved": "https://registry.npmjs.org/dns-packet/-/dns-packet-1.3.4.tgz", - "integrity": "sha512-BQ6F4vycLXBvdrJZ6S3gZewt6rcrks9KBgM9vrhW+knGRqc8uEdT7fuCwloc7nny5xNoMJ17HGH0R/6fpo8ECA==", - "dev": true, - "dependencies": { - "ip": "^1.1.0", - "safe-buffer": "^5.0.1" - } - }, - "node_modules/dns-txt": { - "version": "2.0.2", - "resolved": "https://registry.npmjs.org/dns-txt/-/dns-txt-2.0.2.tgz", - "integrity": "sha1-uR2Ab10nGI5Ks+fRB9iBocxGQrY=", - "dev": true, - "dependencies": { - "buffer-indexof": "^1.0.0" - } - }, - "node_modules/dom-converter": { - "version": "0.2.0", - "resolved": "https://registry.npmjs.org/dom-converter/-/dom-converter-0.2.0.tgz", - "integrity": "sha512-gd3ypIPfOMr9h5jIKq8E3sHOTCjeirnl0WK5ZdS1AW0Odt0b1PaWaHdJ4Qk4klv+YB9aJBS7mESXjFoDQPu6DA==", - "dev": true, - "dependencies": { - "utila": "~0.4" - } - }, - "node_modules/dom-serializer": { - "version": "1.3.2", - "resolved": "https://registry.npmjs.org/dom-serializer/-/dom-serializer-1.3.2.tgz", - "integrity": "sha512-5c54Bk5Dw4qAxNOI1pFEizPSjVsx5+bpJKmL2kPn8JhBUq2q09tTCa3mjijun2NfK78NMouDYNMBkOrPZiS+ig==", - "dev": true, - "dependencies": { - "domelementtype": "^2.0.1", - "domhandler": "^4.2.0", - "entities": "^2.0.0" - }, - "funding": { - "url": "https://github.com/cheeriojs/dom-serializer?sponsor=1" - } - }, - "node_modules/domain-browser": { - "version": "4.22.0", - "resolved": "https://registry.npmjs.org/domain-browser/-/domain-browser-4.22.0.tgz", - "integrity": "sha512-IGBwjF7tNk3cwypFNH/7bfzBcgSCbaMOD3GsaY1AU/JRrnHnYgEM0+9kQt52iZxjNsjBtJYtao146V+f8jFZNw==", - "engines": { - "node": ">=10" - }, - "funding": { - "url": "https://bevry.me/fund" - } - }, - "node_modules/domelementtype": { - "version": "2.2.0", - "resolved": "https://registry.npmjs.org/domelementtype/-/domelementtype-2.2.0.tgz", - "integrity": "sha512-DtBMo82pv1dFtUmHyr48beiuq792Sxohr+8Hm9zoxklYPfa6n0Z3Byjj2IV7bmr2IyqClnqEQhfgHJJ5QF0R5A==", - "dev": true, - "funding": [ - { - "type": "github", - "url": "https://github.com/sponsors/fb55" - } - ] - }, - "node_modules/domhandler": { - "version": "4.3.0", - "resolved": "https://registry.npmjs.org/domhandler/-/domhandler-4.3.0.tgz", - "integrity": "sha512-fC0aXNQXqKSFTr2wDNZDhsEYjCiYsDWl3D01kwt25hm1YIPyDGHvvi3rw+PLqHAl/m71MaiF7d5zvBr0p5UB2g==", - "dev": true, - "dependencies": { - "domelementtype": "^2.2.0" - }, - "engines": { - "node": ">= 4" - }, - "funding": { - "url": "https://github.com/fb55/domhandler?sponsor=1" - } - }, - "node_modules/domutils": { - "version": "2.8.0", - "resolved": "https://registry.npmjs.org/domutils/-/domutils-2.8.0.tgz", - "integrity": "sha512-w96Cjofp72M5IIhpjgobBimYEfoPjx1Vx0BSX9P30WBdZW2WIKU0T1Bd0kz2eNZ9ikjKgHbEyKx8BB6H1L3h3A==", - "dev": true, - "dependencies": { - "dom-serializer": "^1.0.1", - "domelementtype": "^2.2.0", - "domhandler": "^4.2.0" - }, - "funding": { - "url": "https://github.com/fb55/domutils?sponsor=1" - } - }, - "node_modules/dot-case": { - "version": "3.0.4", - "resolved": "https://registry.npmjs.org/dot-case/-/dot-case-3.0.4.tgz", - "integrity": "sha512-Kv5nKlh6yRrdrGvxeJ2e5y2eRUpkUosIW4A2AS38zwSz27zu7ufDwQPi5Jhs3XAlGNetl3bmnGhQsMtkKJnj3w==", - "dev": true, - "dependencies": { - "no-case": "^3.0.4", - "tslib": "^2.0.3" - } - }, - "node_modules/ee-first": { - "version": "1.1.1", - "resolved": "https://registry.npmjs.org/ee-first/-/ee-first-1.1.1.tgz", - "integrity": "sha1-WQxhFWsK4vTwJVcyoViyZrxWsh0=", - "dev": true - }, - "node_modules/electron-to-chromium": { - "version": "1.4.63", - "resolved": "https://registry.npmjs.org/electron-to-chromium/-/electron-to-chromium-1.4.63.tgz", - "integrity": "sha512-e0PX/LRJPFRU4kzJKLvTobxyFdnANCvcoDCe8XcyTqP58nTWIwdsHvXLIl1RkB39X5yaosLaroMASWB0oIsgCA==" - }, - "node_modules/elliptic": { - "version": "6.5.4", - "resolved": "https://registry.npmjs.org/elliptic/-/elliptic-6.5.4.tgz", - "integrity": "sha512-iLhC6ULemrljPZb+QutR5TQGB+pdW6KGD5RSegS+8sorOZT+rdQFbsQFJgvN3eRqNALqJer4oQ16YvJHlU8hzQ==", - "dependencies": { - "bn.js": "^4.11.9", - "brorand": "^1.1.0", - "hash.js": "^1.0.0", - "hmac-drbg": "^1.0.1", - "inherits": "^2.0.4", - "minimalistic-assert": "^1.0.1", - "minimalistic-crypto-utils": "^1.0.1" - } - }, - "node_modules/elliptic/node_modules/bn.js": { - "version": "4.12.0", - "resolved": "https://registry.npmjs.org/bn.js/-/bn.js-4.12.0.tgz", - "integrity": "sha512-c98Bf3tPniI+scsdk237ku1Dc3ujXQTSgyiPUDEOe7tRkhrqridvh8klBv0HCEso1OLOYcHuCv/cS6DNxKH+ZA==" - }, - "node_modules/encodeurl": { - "version": "1.0.2", - "resolved": "https://registry.npmjs.org/encodeurl/-/encodeurl-1.0.2.tgz", - "integrity": "sha1-rT/0yG7C0CkyL1oCw6mmBslbP1k=", - "dev": true, - "engines": { - "node": ">= 0.8" - } - }, - "node_modules/end-of-stream": { - "version": "1.4.4", - "resolved": "https://registry.npmjs.org/end-of-stream/-/end-of-stream-1.4.4.tgz", - "integrity": "sha512-+uw1inIHVPQoaVuHzRyXd21icM+cnt4CzD5rW+NC1wjOUSTOs+Te7FOv7AhN7vS9x/oIyhLP5PR1H+phQAHu5Q==", - "dependencies": { - "once": "^1.4.0" - } - }, - "node_modules/enhanced-resolve": { - "version": "5.8.3", - "resolved": "https://registry.npmjs.org/enhanced-resolve/-/enhanced-resolve-5.8.3.tgz", - "integrity": "sha512-EGAbGvH7j7Xt2nc0E7D99La1OiEs8LnyimkRgwExpUMScN6O+3x9tIWs7PLQZVNx4YD+00skHXPXi1yQHpAmZA==", - "dependencies": { - "graceful-fs": "^4.2.4", - "tapable": "^2.2.0" - }, - "engines": { - "node": ">=10.13.0" - } - }, - "node_modules/entities": { - "version": "2.2.0", - "resolved": "https://registry.npmjs.org/entities/-/entities-2.2.0.tgz", - "integrity": "sha512-p92if5Nz619I0w+akJrLZH0MX0Pb5DX39XOwQTtXSdQQOaYH03S1uIQp4mhOZtAXrxq4ViO67YTiLBo2638o9A==", - "dev": true, - "funding": { - "url": "https://github.com/fb55/entities?sponsor=1" - } - }, - "node_modules/envinfo": { - "version": "7.8.1", - "resolved": "https://registry.npmjs.org/envinfo/-/envinfo-7.8.1.tgz", - "integrity": "sha512-/o+BXHmB7ocbHEAs6F2EnG0ogybVVUdkRunTT2glZU9XAaGmhqskrvKwqXuDfNjEO0LZKWdejEEpnq8aM0tOaw==", - "dev": true, - "bin": { - "envinfo": "dist/cli.js" - }, - "engines": { - "node": ">=4" - } - }, - "node_modules/es-abstract": { - "version": "1.19.1", - "resolved": "https://registry.npmjs.org/es-abstract/-/es-abstract-1.19.1.tgz", - "integrity": "sha512-2vJ6tjA/UfqLm2MPs7jxVybLoB8i1t1Jd9R3kISld20sIxPcTbLuggQOUxeWeAvIUkduv/CfMjuh4WmiXr2v9w==", - "dependencies": { - "call-bind": "^1.0.2", - "es-to-primitive": "^1.2.1", - "function-bind": "^1.1.1", - "get-intrinsic": "^1.1.1", - "get-symbol-description": "^1.0.0", - "has": "^1.0.3", - "has-symbols": "^1.0.2", - "internal-slot": "^1.0.3", - "is-callable": "^1.2.4", - "is-negative-zero": "^2.0.1", - "is-regex": "^1.1.4", - "is-shared-array-buffer": "^1.0.1", - "is-string": "^1.0.7", - "is-weakref": "^1.0.1", - "object-inspect": "^1.11.0", - "object-keys": "^1.1.1", - "object.assign": "^4.1.2", - "string.prototype.trimend": "^1.0.4", - "string.prototype.trimstart": "^1.0.4", - "unbox-primitive": "^1.0.1" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/es-module-lexer": { - "version": "0.9.3", - "resolved": "https://registry.npmjs.org/es-module-lexer/-/es-module-lexer-0.9.3.tgz", - "integrity": "sha512-1HQ2M2sPtxwnvOvT1ZClHyQDiggdNjURWpY2we6aMKCQiUVxTmVs2UYPLIrD84sS+kMdUwfBSylbJPwNnBrnHQ==" - }, - "node_modules/es-to-primitive": { - "version": "1.2.1", - "resolved": "https://registry.npmjs.org/es-to-primitive/-/es-to-primitive-1.2.1.tgz", - "integrity": "sha512-QCOllgZJtaUo9miYBcLChTUaHNjJF3PYs1VidD7AwiEj1kYxKeQTctLAezAOH5ZKRH0g2IgPn6KwB4IT8iRpvA==", - "dependencies": { - "is-callable": "^1.1.4", - "is-date-object": "^1.0.1", - "is-symbol": "^1.0.2" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/es6-object-assign": { - "version": "1.1.0", - "resolved": "https://registry.npmjs.org/es6-object-assign/-/es6-object-assign-1.1.0.tgz", - "integrity": "sha1-wsNYJlYkfDnqEHyx5mUrb58kUjw=" - }, - "node_modules/escalade": { - "version": "3.1.1", - "resolved": "https://registry.npmjs.org/escalade/-/escalade-3.1.1.tgz", - "integrity": "sha512-k0er2gUkLf8O0zKJiAhmkTnJlTvINGv7ygDNPbeIsX/TJjGJZHuh9B2UxbsaEkmlEo9MfhrSzmhIlhRlI2GXnw==", - "engines": { - "node": ">=6" - } - }, - "node_modules/escape-html": { - "version": "1.0.3", - "resolved": "https://registry.npmjs.org/escape-html/-/escape-html-1.0.3.tgz", - "integrity": "sha1-Aljq5NPQwJdN4cFpGI7wBR0dGYg=", - "dev": true - }, - "node_modules/eslint-scope": { - "version": "5.1.1", - "resolved": "https://registry.npmjs.org/eslint-scope/-/eslint-scope-5.1.1.tgz", - "integrity": "sha512-2NxwbF/hZ0KpepYN0cNbo+FN6XoK7GaHlQhgx/hIZl6Va0bF45RQOOwhLIy8lQDbuCiadSLCBnH2CFYquit5bw==", - "dependencies": { - "esrecurse": "^4.3.0", - "estraverse": "^4.1.1" - }, - "engines": { - "node": ">=8.0.0" - } - }, - "node_modules/esrecurse": { - "version": "4.3.0", - "resolved": "https://registry.npmjs.org/esrecurse/-/esrecurse-4.3.0.tgz", - "integrity": "sha512-KmfKL3b6G+RXvP8N1vr3Tq1kL/oCFgn2NYXEtqP8/L3pKapUA4G8cFVaoF3SU323CD4XypR/ffioHmkti6/Tag==", - "dependencies": { - "estraverse": "^5.2.0" - }, - "engines": { - "node": ">=4.0" - } - }, - "node_modules/esrecurse/node_modules/estraverse": { - "version": "5.3.0", - "resolved": "https://registry.npmjs.org/estraverse/-/estraverse-5.3.0.tgz", - "integrity": "sha512-MMdARuVEQziNTeJD8DgMqmhwR11BRQ/cBP+pLtYdSTnf3MIO8fFeiINEbX36ZdNlfU/7A9f3gUw49B3oQsvwBA==", - "engines": { - "node": ">=4.0" - } - }, - "node_modules/estraverse": { - "version": "4.3.0", - "resolved": "https://registry.npmjs.org/estraverse/-/estraverse-4.3.0.tgz", - "integrity": "sha512-39nnKffWz8xN1BU/2c79n9nB9HDzo0niYUqx6xyqUnyoAnQyyWpOTdZEeiCch8BBu515t4wp9ZmgVfVhn9EBpw==", - "engines": { - "node": ">=4.0" - } - }, - "node_modules/etag": { - "version": "1.8.1", - "resolved": "https://registry.npmjs.org/etag/-/etag-1.8.1.tgz", - "integrity": "sha1-Qa4u62XvpiJorr/qg6x9eSmbCIc=", - "dev": true, - "engines": { - "node": ">= 0.6" - } - }, - "node_modules/eventemitter3": { - "version": "4.0.7", - "resolved": "https://registry.npmjs.org/eventemitter3/-/eventemitter3-4.0.7.tgz", - "integrity": "sha512-8guHBZCwKnFhYdHr2ysuRWErTwhoN2X8XELRlrRwpmfeY2jjuUN4taQMsULKUVo1K4DvZl+0pgfyoysHxvmvEw==", - "dev": true - }, - "node_modules/events": { - "version": "3.3.0", - "resolved": "https://registry.npmjs.org/events/-/events-3.3.0.tgz", - "integrity": "sha512-mQw+2fkQbALzQ7V0MY0IqdnXNOeTtP4r0lN9z7AAawCXgqea7bDii20AYrIBrFd/Hx0M2Ocz6S111CaFkUcb0Q==", - "engines": { - "node": ">=0.8.x" - } - }, - "node_modules/evp_bytestokey": { - "version": "1.0.3", - "resolved": "https://registry.npmjs.org/evp_bytestokey/-/evp_bytestokey-1.0.3.tgz", - "integrity": "sha512-/f2Go4TognH/KvCISP7OUsHn85hT9nUkxxA9BEWxFn+Oj9o8ZNLm/40hdlgSLyuOimsrTKLUMEorQexp/aPQeA==", - "dependencies": { - "md5.js": "^1.3.4", - "safe-buffer": "^5.1.1" - } - }, - "node_modules/execa": { - "version": "5.1.1", - "resolved": "https://registry.npmjs.org/execa/-/execa-5.1.1.tgz", - "integrity": "sha512-8uSpZZocAZRBAPIEINJj3Lo9HyGitllczc27Eh5YYojjMFMn8yHMDMaUHE2Jqfq05D/wucwI4JGURyXt1vchyg==", - "dev": true, - "dependencies": { - "cross-spawn": "^7.0.3", - "get-stream": "^6.0.0", - "human-signals": "^2.1.0", - "is-stream": "^2.0.0", - "merge-stream": "^2.0.0", - "npm-run-path": "^4.0.1", - "onetime": "^5.1.2", - "signal-exit": "^3.0.3", - "strip-final-newline": "^2.0.0" - }, - "engines": { - "node": ">=10" - }, - "funding": { - "url": "https://github.com/sindresorhus/execa?sponsor=1" - } - }, - "node_modules/execa/node_modules/cross-spawn": { - "version": "7.0.3", - "resolved": "https://registry.npmjs.org/cross-spawn/-/cross-spawn-7.0.3.tgz", - "integrity": "sha512-iRDPJKUPVEND7dHPO8rkbOnPpyDygcDFtWjpeWNCgy8WP2rXcxXL8TskReQl6OrB2G7+UJrags1q15Fudc7G6w==", - "dev": true, - "dependencies": { - "path-key": "^3.1.0", - "shebang-command": "^2.0.0", - "which": "^2.0.1" - }, - "engines": { - "node": ">= 8" - } - }, - "node_modules/execa/node_modules/which": { - "version": "2.0.2", - "resolved": "https://registry.npmjs.org/which/-/which-2.0.2.tgz", - "integrity": "sha512-BLI3Tl1TW3Pvl70l3yq3Y64i+awpwXqsGBYWkkqMtnbXgrMD+yj7rhW0kuEDxzJaYXGjEW5ogapKNMEKNMjibA==", - "dev": true, - "dependencies": { - "isexe": "^2.0.0" - }, - "bin": { - "node-which": "bin/node-which" - }, - "engines": { - "node": ">= 8" - } - }, - "node_modules/express": { - "version": "4.17.2", - "resolved": "https://registry.npmjs.org/express/-/express-4.17.2.tgz", - "integrity": "sha512-oxlxJxcQlYwqPWKVJJtvQiwHgosH/LrLSPA+H4UxpyvSS6jC5aH+5MoHFM+KABgTOt0APue4w66Ha8jCUo9QGg==", - "dev": true, - "dependencies": { - "accepts": "~1.3.7", - "array-flatten": "1.1.1", - "body-parser": "1.19.1", - "content-disposition": "0.5.4", - "content-type": "~1.0.4", - "cookie": "0.4.1", - "cookie-signature": "1.0.6", - "debug": "2.6.9", - "depd": "~1.1.2", - "encodeurl": "~1.0.2", - "escape-html": "~1.0.3", - "etag": "~1.8.1", - "finalhandler": "~1.1.2", - "fresh": "0.5.2", - "merge-descriptors": "1.0.1", - "methods": "~1.1.2", - "on-finished": "~2.3.0", - "parseurl": "~1.3.3", - "path-to-regexp": "0.1.7", - "proxy-addr": "~2.0.7", - "qs": "6.9.6", - "range-parser": "~1.2.1", - "safe-buffer": "5.2.1", - "send": "0.17.2", - "serve-static": "1.14.2", - "setprototypeof": "1.2.0", - "statuses": "~1.5.0", - "type-is": "~1.6.18", - "utils-merge": "1.0.1", - "vary": "~1.1.2" - }, - "engines": { - "node": ">= 0.10.0" - } - }, - "node_modules/express/node_modules/array-flatten": { - "version": "1.1.1", - "resolved": "https://registry.npmjs.org/array-flatten/-/array-flatten-1.1.1.tgz", - "integrity": "sha1-ml9pkFGx5wczKPKgCJaLZOopVdI=", - "dev": true - }, - "node_modules/extract-zip": { - "version": "2.0.1", - "resolved": "https://registry.npmjs.org/extract-zip/-/extract-zip-2.0.1.tgz", - "integrity": "sha512-GDhU9ntwuKyGXdZBUgTIe+vXnWj0fppUEtMDL0+idd5Sta8TGpHssn/eusA9mrPr9qNDym6SxAYZjNvCn/9RBg==", - "dependencies": { - "debug": "^4.1.1", - "get-stream": "^5.1.0", - "yauzl": "^2.10.0" - }, - "bin": { - "extract-zip": "cli.js" - }, - "engines": { - "node": ">= 10.17.0" - }, - "optionalDependencies": { - "@types/yauzl": "^2.9.1" - } - }, - "node_modules/extract-zip/node_modules/debug": { - "version": "4.3.4", - "resolved": "https://registry.npmjs.org/debug/-/debug-4.3.4.tgz", - "integrity": "sha512-PRWFHuSU3eDtQJPvnNY7Jcket1j0t5OuOsFzPPzsekD52Zl8qUfFIPEiswXqIvHWGVHOgX+7G/vCNNhehwxfkQ==", - "dependencies": { - "ms": "2.1.2" - }, - "engines": { - "node": ">=6.0" - }, - "peerDependenciesMeta": { - "supports-color": { - "optional": true - } - } - }, - "node_modules/extract-zip/node_modules/get-stream": { - "version": "5.2.0", - "resolved": "https://registry.npmjs.org/get-stream/-/get-stream-5.2.0.tgz", - "integrity": "sha512-nBF+F1rAZVCu/p7rjzgA+Yb4lfYXrpl7a6VmJrU8wF9I1CKvP/QwPNZHnOlwbTkY6dvtFIzFMSyQXbLoTQPRpA==", - "dependencies": { - "pump": "^3.0.0" - }, - "engines": { - "node": ">=8" - }, - "funding": { - "url": "https://github.com/sponsors/sindresorhus" - } - }, - "node_modules/extract-zip/node_modules/ms": { - "version": "2.1.2", - "resolved": "https://registry.npmjs.org/ms/-/ms-2.1.2.tgz", - "integrity": "sha512-sGkPx+VjMtmA6MX27oA4FBFELFCZZ4S4XqeGOXCv68tT+jb3vk/RyaKWP0PTKyWtmLSM0b+adUTEvbs1PEaH2w==" - }, - "node_modules/fast-deep-equal": { - "version": "3.1.3", - "resolved": "https://registry.npmjs.org/fast-deep-equal/-/fast-deep-equal-3.1.3.tgz", - "integrity": "sha512-f3qQ9oQy9j2AhBe/H9VC91wLmKBCCU/gDOnKNAYG5hswO7BLKj09Hc5HYNz9cGI++xlpDCIgDaitVs03ATR84Q==" - }, - "node_modules/fast-glob": { - "version": "3.2.11", - "resolved": "https://registry.npmjs.org/fast-glob/-/fast-glob-3.2.11.tgz", - "integrity": "sha512-xrO3+1bxSo3ZVHAnqzyuewYT6aMFHRAd4Kcs92MAonjwQZLsK9d0SF1IyQ3k5PoirxTW0Oe/RqFgMQ6TcNE5Ew==", - "dev": true, - "dependencies": { - "@nodelib/fs.stat": "^2.0.2", - "@nodelib/fs.walk": "^1.2.3", - "glob-parent": "^5.1.2", - "merge2": "^1.3.0", - "micromatch": "^4.0.4" - }, - "engines": { - "node": ">=8.6.0" - } - }, - "node_modules/fast-json-stable-stringify": { - "version": "2.1.0", - "resolved": "https://registry.npmjs.org/fast-json-stable-stringify/-/fast-json-stable-stringify-2.1.0.tgz", - "integrity": "sha512-lhd/wF+Lk98HZoTCtlVraHtfh5XYijIjalXck7saUtuanSDyLMxnHhSXEDJqHxD7msR8D0uCmqlkwjCV8xvwHw==" - }, - "node_modules/fastest-levenshtein": { - "version": "1.0.14", - "resolved": "https://registry.npmjs.org/fastest-levenshtein/-/fastest-levenshtein-1.0.14.tgz", - "integrity": "sha512-tFfWHjnuUfKE186Tfgr+jtaFc0mZTApEgKDOeyN+FwOqRkO/zK/3h1AiRd8u8CY53owL3CUmGr/oI9p/RdyLTA==", - "dev": true, - "engines": { - "node": ">= 4.9.1" - } - }, - "node_modules/fastq": { - "version": "1.13.0", - "resolved": "https://registry.npmjs.org/fastq/-/fastq-1.13.0.tgz", - "integrity": "sha512-YpkpUnK8od0o1hmeSc7UUs/eB/vIPWJYjKck2QKIzAf71Vm1AAQ3EbuZB3g2JIy+pg+ERD0vqI79KyZiB2e2Nw==", - "dev": true, - "dependencies": { - "reusify": "^1.0.4" - } - }, - "node_modules/faye-websocket": { - "version": "0.11.4", - "resolved": "https://registry.npmjs.org/faye-websocket/-/faye-websocket-0.11.4.tgz", - "integrity": "sha512-CzbClwlXAuiRQAlUyfqPgvPoNKTckTPGfwZV4ZdAhVcP2lh9KUxJg2b5GkE7XbjKQ3YJnQ9z6D9ntLAlB+tP8g==", - "dev": true, - "dependencies": { - "websocket-driver": ">=0.5.1" - }, - "engines": { - "node": ">=0.8.0" - } - }, - "node_modules/fd-slicer": { - "version": "1.1.0", - "resolved": "https://registry.npmjs.org/fd-slicer/-/fd-slicer-1.1.0.tgz", - "integrity": "sha512-cE1qsB/VwyQozZ+q1dGxR8LBYNZeofhEdUNGSMbQD3Gw2lAzX9Zb3uIU6Ebc/Fmyjo9AWWfnn0AUCHqtevs/8g==", - "dependencies": { - "pend": "~1.2.0" - } - }, - "node_modules/fill-range": { - "version": "7.0.1", - "resolved": "https://registry.npmjs.org/fill-range/-/fill-range-7.0.1.tgz", - "integrity": "sha512-qOo9F+dMUmC2Lcb4BbVvnKJxTPjCm+RRpe4gDuGrzkL7mEVl/djYSu2OdQ2Pa302N4oqkSg9ir6jaLWJ2USVpQ==", - "dev": true, - "dependencies": { - "to-regex-range": "^5.0.1" - }, - "engines": { - "node": ">=8" - } - }, - "node_modules/filter-obj": { - "version": "2.0.2", - "resolved": "https://registry.npmjs.org/filter-obj/-/filter-obj-2.0.2.tgz", - "integrity": "sha512-lO3ttPjHZRfjMcxWKb1j1eDhTFsu4meeR3lnMcnBFhk6RuLhvEiuALu2TlfL310ph4lCYYwgF/ElIjdP739tdg==", - "engines": { - "node": ">=8" - } - }, - "node_modules/finalhandler": { - "version": "1.1.2", - "resolved": "https://registry.npmjs.org/finalhandler/-/finalhandler-1.1.2.tgz", - "integrity": "sha512-aAWcW57uxVNrQZqFXjITpW3sIUQmHGG3qSb9mUah9MgMC4NeWhNOlNjXEYq3HjRAvL6arUviZGGJsBg6z0zsWA==", - "dev": true, - "dependencies": { - "debug": "2.6.9", - "encodeurl": "~1.0.2", - "escape-html": "~1.0.3", - "on-finished": "~2.3.0", - "parseurl": "~1.3.3", - "statuses": "~1.5.0", - "unpipe": "~1.0.0" - }, - "engines": { - "node": ">= 0.8" - } - }, - "node_modules/find-up": { - "version": "4.1.0", - "resolved": "https://registry.npmjs.org/find-up/-/find-up-4.1.0.tgz", - "integrity": "sha512-PpOwAdQ/YlXQ2vj8a3h8IipDuYRi3wceVQQGYWxNINccq40Anw7BlsEXCMbt1Zt+OLA6Fq9suIpIWD0OsnISlw==", - "dependencies": { - "locate-path": "^5.0.0", - "path-exists": "^4.0.0" - }, - "engines": { - "node": ">=8" - } - }, - "node_modules/follow-redirects": { - "version": "1.14.7", - "resolved": "https://registry.npmjs.org/follow-redirects/-/follow-redirects-1.14.7.tgz", - "integrity": "sha512-+hbxoLbFMbRKDwohX8GkTataGqO6Jb7jGwpAlwgy2bIz25XtRm7KEzJM76R1WiNT5SwZkX4Y75SwBolkpmE7iQ==", - "dev": true, - "funding": [ - { - "type": "individual", - "url": "https://github.com/sponsors/RubenVerborgh" - } - ], - "engines": { - "node": ">=4.0" - }, - "peerDependenciesMeta": { - "debug": { - "optional": true - } - } - }, - "node_modules/foreach": { - "version": "2.0.5", - "resolved": "https://registry.npmjs.org/foreach/-/foreach-2.0.5.tgz", - "integrity": "sha1-C+4AUBiusmDQo6865ljdATbsG5k=" - }, - "node_modules/forwarded": { - "version": "0.2.0", - "resolved": "https://registry.npmjs.org/forwarded/-/forwarded-0.2.0.tgz", - "integrity": "sha512-buRG0fpBtRHSTCOASe6hD258tEubFoRLb4ZNA6NxMVHNw2gOcwHo9wyablzMzOA5z9xA9L1KNjk/Nt6MT9aYow==", - "dev": true, - "engines": { - "node": ">= 0.6" - } - }, - "node_modules/fresh": { - "version": "0.5.2", - "resolved": "https://registry.npmjs.org/fresh/-/fresh-0.5.2.tgz", - "integrity": "sha1-PYyt2Q2XZWn6g1qx+OSyOhBWBac=", - "dev": true, - "engines": { - "node": ">= 0.6" - } - }, - "node_modules/fs-constants": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/fs-constants/-/fs-constants-1.0.0.tgz", - "integrity": "sha512-y6OAwoSIf7FyjMIv94u+b5rdheZEjzR63GTyZJm5qh4Bi+2YgwLCcI/fPFZkL5PSixOt6ZNKm+w+Hfp/Bciwow==" - }, - "node_modules/fs-monkey": { - "version": "1.0.3", - "resolved": "https://registry.npmjs.org/fs-monkey/-/fs-monkey-1.0.3.tgz", - "integrity": "sha512-cybjIfiiE+pTWicSCLFHSrXZ6EilF30oh91FDP9S2B051prEa7QWfrVTQm10/dDpswBDXZugPa1Ogu8Yh+HV0Q==", - "dev": true - }, - "node_modules/fs.realpath": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/fs.realpath/-/fs.realpath-1.0.0.tgz", - "integrity": "sha1-FQStJSMVjKpA20onh8sBQRmU6k8=" - }, - "node_modules/fsevents": { - "version": "2.3.2", - "resolved": "https://registry.npmjs.org/fsevents/-/fsevents-2.3.2.tgz", - "integrity": "sha512-xiqMQR4xAeHTuB9uWm+fFRcIOgKBMiOBP+eXiyT7jsgVCq1bkVygt00oASowB7EdtpOHaaPgKt812P9ab+DDKA==", - "dev": true, - "hasInstallScript": true, - "optional": true, - "os": [ - "darwin" - ], - "engines": { - "node": "^8.16.0 || ^10.6.0 || >=11.0.0" - } - }, - "node_modules/function-bind": { - "version": "1.1.1", - "resolved": "https://registry.npmjs.org/function-bind/-/function-bind-1.1.1.tgz", - "integrity": "sha512-yIovAzMX49sF8Yl58fSCWJ5svSLuaibPxXQJFLmBObTuCr0Mf1KiPopGM9NiFjiYBCbfaa2Fh6breQ6ANVTI0A==" - }, - "node_modules/get-intrinsic": { - "version": "1.1.1", - "resolved": "https://registry.npmjs.org/get-intrinsic/-/get-intrinsic-1.1.1.tgz", - "integrity": "sha512-kWZrnVM42QCiEA2Ig1bG8zjoIMOgxWwYCEeNdwY6Tv/cOSeGpcoX4pXHfKUxNKVoArnrEr2e9srnAxxGIraS9Q==", - "dependencies": { - "function-bind": "^1.1.1", - "has": "^1.0.3", - "has-symbols": "^1.0.1" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/get-stream": { - "version": "6.0.1", - "resolved": "https://registry.npmjs.org/get-stream/-/get-stream-6.0.1.tgz", - "integrity": "sha512-ts6Wi+2j3jQjqi70w5AlN8DFnkSwC+MqmxEzdEALB2qXZYV3X/b1CTfgPLGJNMeAWxdPfU8FO1ms3NUfaHCPYg==", - "dev": true, - "engines": { - "node": ">=10" - }, - "funding": { - "url": "https://github.com/sponsors/sindresorhus" - } - }, - "node_modules/get-symbol-description": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/get-symbol-description/-/get-symbol-description-1.0.0.tgz", - "integrity": "sha512-2EmdH1YvIQiZpltCNgkuiUnyukzxM/R6NDJX31Ke3BG1Nq5b0S2PhX59UKi9vZpPDQVdqn+1IcaAwnzTT5vCjw==", - "dependencies": { - "call-bind": "^1.0.2", - "get-intrinsic": "^1.1.1" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/glob-parent": { - "version": "5.1.2", - "resolved": "https://registry.npmjs.org/glob-parent/-/glob-parent-5.1.2.tgz", - "integrity": "sha512-AOIgSQCepiJYwP3ARnGx+5VnTu2HBYdzbGP45eLw1vr3zB3vZLeyed1sC9hnbcOc9/SrMyM5RPQrkGz4aS9Zow==", - "dev": true, - "dependencies": { - "is-glob": "^4.0.1" - }, - "engines": { - "node": ">= 6" - } - }, - "node_modules/glob-to-regexp": { - "version": "0.4.1", - "resolved": "https://registry.npmjs.org/glob-to-regexp/-/glob-to-regexp-0.4.1.tgz", - "integrity": "sha512-lkX1HJXwyMcprw/5YUZc2s7DrpAiHB21/V+E1rHUrVNokkvB6bqMzT0VfV6/86ZNabt1k14YOIaT7nDvOX3Iiw==" - }, - "node_modules/graceful-fs": { - "version": "4.2.9", - "resolved": "https://registry.npmjs.org/graceful-fs/-/graceful-fs-4.2.9.tgz", - "integrity": "sha512-NtNxqUcXgpW2iMrfqSfR73Glt39K+BLwWsPs94yR63v45T0Wbej7eRmL5cWfwEgqXnmjQp3zaJTshdRW/qC2ZQ==" - }, - "node_modules/handle-thing": { - "version": "2.0.1", - "resolved": "https://registry.npmjs.org/handle-thing/-/handle-thing-2.0.1.tgz", - "integrity": "sha512-9Qn4yBxelxoh2Ow62nP+Ka/kMnOXRi8BXnRaUwezLNhqelnN49xKz4F/dPP8OYLxLxq6JDtZb2i9XznUQbNPTg==", - "dev": true - }, - "node_modules/has": { - "version": "1.0.3", - "resolved": "https://registry.npmjs.org/has/-/has-1.0.3.tgz", - "integrity": "sha512-f2dvO0VU6Oej7RkWJGrehjbzMAjFp5/VKPp5tTpWIV4JHHZK1/BxbFRtf/siA2SWTe09caDmVtYYzWEIbBS4zw==", - "dependencies": { - "function-bind": "^1.1.1" - }, - "engines": { - "node": ">= 0.4.0" - } - }, - "node_modules/has-bigints": { - "version": "1.0.1", - "resolved": "https://registry.npmjs.org/has-bigints/-/has-bigints-1.0.1.tgz", - "integrity": "sha512-LSBS2LjbNBTf6287JEbEzvJgftkF5qFkmCo9hDRpAzKhUOlJ+hx8dd4USs00SgsUNwc4617J9ki5YtEClM2ffA==", - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/has-flag": { - "version": "4.0.0", - "resolved": "https://registry.npmjs.org/has-flag/-/has-flag-4.0.0.tgz", - "integrity": "sha512-EykJT/Q1KjTWctppgIAgfSO0tKVuZUjhgMr17kqTumMl6Afv3EISleU7qZUzoXDFTAHTDC4NOoG/ZxU3EvlMPQ==", - "engines": { - "node": ">=8" - } - }, - "node_modules/has-symbols": { - "version": "1.0.2", - "resolved": "https://registry.npmjs.org/has-symbols/-/has-symbols-1.0.2.tgz", - "integrity": "sha512-chXa79rL/UC2KlX17jo3vRGz0azaWEx5tGqZg5pO3NUyEJVB17dMruQlzCCOfUvElghKcm5194+BCRvi2Rv/Gw==", - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/has-tostringtag": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/has-tostringtag/-/has-tostringtag-1.0.0.tgz", - "integrity": "sha512-kFjcSNhnlGV1kyoGk7OXKSawH5JOb/LzUc5w9B02hOTO0dfFRjbHQKvg1d6cf3HbeUmtU9VbbV3qzZ2Teh97WQ==", - "dependencies": { - "has-symbols": "^1.0.2" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/hash-base": { - "version": "3.1.0", - "resolved": "https://registry.npmjs.org/hash-base/-/hash-base-3.1.0.tgz", - "integrity": "sha512-1nmYp/rhMDiE7AYkDw+lLwlAzz0AntGIe51F3RfFfEqyQ3feY2eI/NcwC6umIQVOASPMsWJLJScWKSSvzL9IVA==", - "dependencies": { - "inherits": "^2.0.4", - "readable-stream": "^3.6.0", - "safe-buffer": "^5.2.0" - }, - "engines": { - "node": ">=4" - } - }, - "node_modules/hash.js": { - "version": "1.1.7", - "resolved": "https://registry.npmjs.org/hash.js/-/hash.js-1.1.7.tgz", - "integrity": "sha512-taOaskGt4z4SOANNseOviYDvjEJinIkRgmp7LbKP2YTTmVxWBl87s/uzK9r+44BclBSp2X7K1hqeNfz9JbBeXA==", - "dependencies": { - "inherits": "^2.0.3", - "minimalistic-assert": "^1.0.1" - } - }, - "node_modules/he": { - "version": "1.2.0", - "resolved": "https://registry.npmjs.org/he/-/he-1.2.0.tgz", - "integrity": "sha512-F/1DnUGPopORZi0ni+CvrCgHQ5FyEAHRLSApuYWMmrbSwoN2Mn/7k+Gl38gJnR7yyDZk6WLXwiGod1JOWNDKGw==", - "dev": true, - "bin": { - "he": "bin/he" - } - }, - "node_modules/hmac-drbg": { - "version": "1.0.1", - "resolved": "https://registry.npmjs.org/hmac-drbg/-/hmac-drbg-1.0.1.tgz", - "integrity": "sha1-0nRXAQJabHdabFRXk+1QL8DGSaE=", - "dependencies": { - "hash.js": "^1.0.3", - "minimalistic-assert": "^1.0.0", - "minimalistic-crypto-utils": "^1.0.1" - } - }, - "node_modules/hpack.js": { - "version": "2.1.6", - "resolved": "https://registry.npmjs.org/hpack.js/-/hpack.js-2.1.6.tgz", - "integrity": "sha1-h3dMCUnlE/QuhFdbPEVoH63ioLI=", - "dev": true, - "dependencies": { - "inherits": "^2.0.1", - "obuf": "^1.0.0", - "readable-stream": "^2.0.1", - "wbuf": "^1.1.0" - } - }, - "node_modules/hpack.js/node_modules/readable-stream": { - "version": "2.3.7", - "resolved": "https://registry.npmjs.org/readable-stream/-/readable-stream-2.3.7.tgz", - "integrity": "sha512-Ebho8K4jIbHAxnuxi7o42OrZgF/ZTNcsZj6nRKyUmkhLFq8CHItp/fy6hQZuZmP/n3yZ9VBUbp4zz/mX8hmYPw==", - "dev": true, - "dependencies": { - "core-util-is": "~1.0.0", - "inherits": "~2.0.3", - "isarray": "~1.0.0", - "process-nextick-args": "~2.0.0", - "safe-buffer": "~5.1.1", - "string_decoder": "~1.1.1", - "util-deprecate": "~1.0.1" - } - }, - "node_modules/hpack.js/node_modules/safe-buffer": { - "version": "5.1.2", - "resolved": "https://registry.npmjs.org/safe-buffer/-/safe-buffer-5.1.2.tgz", - "integrity": "sha512-Gd2UZBJDkXlY7GbJxfsE8/nvKkUEU1G38c1siN6QP6a9PT9MmHB8GnpscSmMJSoF8LOIrt8ud/wPtojys4G6+g==", - "dev": true - }, - "node_modules/html-entities": { - "version": "2.3.2", - "resolved": "https://registry.npmjs.org/html-entities/-/html-entities-2.3.2.tgz", - "integrity": "sha512-c3Ab/url5ksaT0WyleslpBEthOzWhrjQbg75y7XUsfSzi3Dgzt0l8w5e7DylRn15MTlMMD58dTfzddNS2kcAjQ==", - "dev": true - }, - "node_modules/html-minifier-terser": { - "version": "6.1.0", - "resolved": "https://registry.npmjs.org/html-minifier-terser/-/html-minifier-terser-6.1.0.tgz", - "integrity": "sha512-YXxSlJBZTP7RS3tWnQw74ooKa6L9b9i9QYXY21eUEvhZ3u9XLfv6OnFsQq6RxkhHygsaUMvYsZRV5rU/OVNZxw==", - "dev": true, - "dependencies": { - "camel-case": "^4.1.2", - "clean-css": "^5.2.2", - "commander": "^8.3.0", - "he": "^1.2.0", - "param-case": "^3.0.4", - "relateurl": "^0.2.7", - "terser": "^5.10.0" - }, - "bin": { - "html-minifier-terser": "cli.js" - }, - "engines": { - "node": ">=12" - } - }, - "node_modules/html-webpack-plugin": { - "version": "5.5.0", - "resolved": "https://registry.npmjs.org/html-webpack-plugin/-/html-webpack-plugin-5.5.0.tgz", - "integrity": "sha512-sy88PC2cRTVxvETRgUHFrL4No3UxvcH8G1NepGhqaTT+GXN2kTamqasot0inS5hXeg1cMbFDt27zzo9p35lZVw==", - "dev": true, - "dependencies": { - "@types/html-minifier-terser": "^6.0.0", - "html-minifier-terser": "^6.0.2", - "lodash": "^4.17.21", - "pretty-error": "^4.0.0", - "tapable": "^2.0.0" - }, - "engines": { - "node": ">=10.13.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/html-webpack-plugin" - }, - "peerDependencies": { - "webpack": "^5.20.0" - } - }, - "node_modules/htmlparser2": { - "version": "6.1.0", - "resolved": "https://registry.npmjs.org/htmlparser2/-/htmlparser2-6.1.0.tgz", - "integrity": "sha512-gyyPk6rgonLFEDGoeRgQNaEUvdJ4ktTmmUh/h2t7s+M8oPpIPxgNACWa+6ESR57kXstwqPiCut0V8NRpcwgU7A==", - "dev": true, - "funding": [ - "https://github.com/fb55/htmlparser2?sponsor=1", - { - "type": "github", - "url": "https://github.com/sponsors/fb55" - } - ], - "dependencies": { - "domelementtype": "^2.0.1", - "domhandler": "^4.0.0", - "domutils": "^2.5.2", - "entities": "^2.0.0" - } - }, - "node_modules/http-deceiver": { - "version": "1.2.7", - "resolved": "https://registry.npmjs.org/http-deceiver/-/http-deceiver-1.2.7.tgz", - "integrity": "sha1-+nFolEq5pRnTN8sL7HKE3D5yPYc=", - "dev": true - }, - "node_modules/http-errors": { - "version": "1.8.1", - "resolved": "https://registry.npmjs.org/http-errors/-/http-errors-1.8.1.tgz", - "integrity": "sha512-Kpk9Sm7NmI+RHhnj6OIWDI1d6fIoFAtFt9RLaTMRlg/8w49juAStsrBgp0Dp4OdxdVbRIeKhtCUvoi/RuAhO4g==", - "dev": true, - "dependencies": { - "depd": "~1.1.2", - "inherits": "2.0.4", - "setprototypeof": "1.2.0", - "statuses": ">= 1.5.0 < 2", - "toidentifier": "1.0.1" - }, - "engines": { - "node": ">= 0.6" - } - }, - "node_modules/http-parser-js": { - "version": "0.5.5", - "resolved": "https://registry.npmjs.org/http-parser-js/-/http-parser-js-0.5.5.tgz", - "integrity": "sha512-x+JVEkO2PoM8qqpbPbOL3cqHPwerep7OwzK7Ay+sMQjKzaKCqWvjoXm5tqMP9tXWWTnTzAjIhXg+J99XYuPhPA==", - "dev": true - }, - "node_modules/http-proxy": { - "version": "1.18.1", - "resolved": "https://registry.npmjs.org/http-proxy/-/http-proxy-1.18.1.tgz", - "integrity": "sha512-7mz/721AbnJwIVbnaSv1Cz3Am0ZLT/UBwkC92VlxhXv/k/BBQfM2fXElQNC27BVGr0uwUpplYPQM9LnaBMR5NQ==", - "dev": true, - "dependencies": { - "eventemitter3": "^4.0.0", - "follow-redirects": "^1.0.0", - "requires-port": "^1.0.0" - }, - "engines": { - "node": ">=8.0.0" - } - }, - "node_modules/http-proxy-middleware": { - "version": "2.0.2", - "resolved": "https://registry.npmjs.org/http-proxy-middleware/-/http-proxy-middleware-2.0.2.tgz", - "integrity": "sha512-XtmDN5w+vdFTBZaYhdJAbMqn0DP/EhkUaAeo963mojwpKMMbw6nivtFKw07D7DDOH745L5k0VL0P8KRYNEVF/g==", - "dev": true, - "dependencies": { - "@types/http-proxy": "^1.17.8", - "http-proxy": "^1.18.1", - "is-glob": "^4.0.1", - "is-plain-obj": "^3.0.0", - "micromatch": "^4.0.2" - }, - "engines": { - "node": ">=12.0.0" - }, - "peerDependencies": { - "@types/express": "^4.17.13" - } - }, - "node_modules/https-browserify": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/https-browserify/-/https-browserify-1.0.0.tgz", - "integrity": "sha1-7AbBDgo0wPL68Zn3/X/Hj//QPHM=" - }, - "node_modules/https-proxy-agent": { - "version": "5.0.1", - "resolved": "https://registry.npmjs.org/https-proxy-agent/-/https-proxy-agent-5.0.1.tgz", - "integrity": "sha512-dFcAjpTQFgoLMzC2VwU+C/CbS7uRL0lWmxDITmqm7C+7F0Odmj6s9l6alZc6AELXhrnggM2CeWSXHGOdX2YtwA==", - "dependencies": { - "agent-base": "6", - "debug": "4" - }, - "engines": { - "node": ">= 6" - } - }, - "node_modules/https-proxy-agent/node_modules/debug": { - "version": "4.3.4", - "resolved": "https://registry.npmjs.org/debug/-/debug-4.3.4.tgz", - "integrity": "sha512-PRWFHuSU3eDtQJPvnNY7Jcket1j0t5OuOsFzPPzsekD52Zl8qUfFIPEiswXqIvHWGVHOgX+7G/vCNNhehwxfkQ==", - "dependencies": { - "ms": "2.1.2" - }, - "engines": { - "node": ">=6.0" - }, - "peerDependenciesMeta": { - "supports-color": { - "optional": true - } - } - }, - "node_modules/https-proxy-agent/node_modules/ms": { - "version": "2.1.2", - "resolved": "https://registry.npmjs.org/ms/-/ms-2.1.2.tgz", - "integrity": "sha512-sGkPx+VjMtmA6MX27oA4FBFELFCZZ4S4XqeGOXCv68tT+jb3vk/RyaKWP0PTKyWtmLSM0b+adUTEvbs1PEaH2w==" - }, - "node_modules/human-signals": { - "version": "2.1.0", - "resolved": "https://registry.npmjs.org/human-signals/-/human-signals-2.1.0.tgz", - "integrity": "sha512-B4FFZ6q/T2jhhksgkbEW3HBvWIfDW85snkQgawt07S7J5QXTk6BkNV+0yAeZrM5QpMAdYlocGoljn0sJ/WQkFw==", - "dev": true, - "engines": { - "node": ">=10.17.0" - } - }, - "node_modules/iconv-lite": { - "version": "0.4.24", - "resolved": "https://registry.npmjs.org/iconv-lite/-/iconv-lite-0.4.24.tgz", - "integrity": "sha512-v3MXnZAcvnywkTUEZomIActle7RXXeedOR31wwl7VlyoXO4Qi9arvSenNQWne1TcRwhCL1HwLI21bEqdpj8/rA==", - "dev": true, - "dependencies": { - "safer-buffer": ">= 2.1.2 < 3" - }, - "engines": { - "node": ">=0.10.0" - } - }, - "node_modules/ieee754": { - "version": "1.2.1", - "resolved": "https://registry.npmjs.org/ieee754/-/ieee754-1.2.1.tgz", - "integrity": "sha512-dcyqhDvX1C46lXZcVqCpK+FtMRQVdIMN6/Df5js2zouUsqG7I6sFxitIC+7KYK29KdXOLHdu9zL4sFnoVQnqaA==", - "funding": [ - { - "type": "github", - "url": "https://github.com/sponsors/feross" - }, - { - "type": "patreon", - "url": "https://www.patreon.com/feross" - }, - { - "type": "consulting", - "url": "https://feross.org/support" - } - ] - }, - "node_modules/ignore": { - "version": "5.2.0", - "resolved": "https://registry.npmjs.org/ignore/-/ignore-5.2.0.tgz", - "integrity": "sha512-CmxgYGiEPCLhfLnpPp1MoRmifwEIOgjcHXxOBjv7mY96c+eWScsOP9c112ZyLdWHi0FxHjI+4uVhKYp/gcdRmQ==", - "dev": true, - "engines": { - "node": ">= 4" - } - }, - "node_modules/import-local": { - "version": "3.1.0", - "resolved": "https://registry.npmjs.org/import-local/-/import-local-3.1.0.tgz", - "integrity": "sha512-ASB07uLtnDs1o6EHjKpX34BKYDSqnFerfTOJL2HvMqF70LnxpjkzDB8J44oT9pu4AMPkQwf8jl6szgvNd2tRIg==", - "dev": true, - "dependencies": { - "pkg-dir": "^4.2.0", - "resolve-cwd": "^3.0.0" - }, - "bin": { - "import-local-fixture": "fixtures/cli.js" - }, - "engines": { - "node": ">=8" - }, - "funding": { - "url": "https://github.com/sponsors/sindresorhus" - } - }, - "node_modules/indent-string": { - "version": "4.0.0", - "resolved": "https://registry.npmjs.org/indent-string/-/indent-string-4.0.0.tgz", - "integrity": "sha512-EdDDZu4A2OyIK7Lr/2zG+w5jmbuk1DVBnEwREQvBzspBJkCEbRa8GxU1lghYcaGJCnRWibjDXlq779X1/y5xwg==", - "dev": true, - "engines": { - "node": ">=8" - } - }, - "node_modules/inflight": { - "version": "1.0.6", - "resolved": "https://registry.npmjs.org/inflight/-/inflight-1.0.6.tgz", - "integrity": "sha1-Sb1jMdfQLQwJvJEKEHW6gWW1bfk=", - "dependencies": { - "once": "^1.3.0", - "wrappy": "1" - } - }, - "node_modules/inherits": { - "version": "2.0.4", - "resolved": "https://registry.npmjs.org/inherits/-/inherits-2.0.4.tgz", - "integrity": "sha512-k/vGaX4/Yla3WzyMCvTQOXYeIHvqOKtnqBduzTHpzpQZzAskKMhZ2K+EnBiSM9zGSoIFeMpXKxa4dYeZIQqewQ==" - }, - "node_modules/internal-slot": { - "version": "1.0.3", - "resolved": "https://registry.npmjs.org/internal-slot/-/internal-slot-1.0.3.tgz", - "integrity": "sha512-O0DB1JC/sPyZl7cIo78n5dR7eUSwwpYPiXRhTzNxZVAMUuB8vlnRFyLxdrVToks6XPLVnFfbzaVd5WLjhgg+vA==", - "dependencies": { - "get-intrinsic": "^1.1.0", - "has": "^1.0.3", - "side-channel": "^1.0.4" - }, - "engines": { - "node": ">= 0.4" - } - }, - "node_modules/interpret": { - "version": "2.2.0", - "resolved": "https://registry.npmjs.org/interpret/-/interpret-2.2.0.tgz", - "integrity": "sha512-Ju0Bz/cEia55xDwUWEa8+olFpCiQoypjnQySseKtmjNrnps3P+xfpUmGr90T7yjlVJmOtybRvPXhKMbHr+fWnw==", - "dev": true, - "engines": { - "node": ">= 0.10" - } - }, - "node_modules/ip": { - "version": "1.1.5", - "resolved": "https://registry.npmjs.org/ip/-/ip-1.1.5.tgz", - "integrity": "sha1-vd7XARQpCCjAoDnnLvJfWq7ENUo=", - "dev": true - }, - "node_modules/ipaddr.js": { - "version": "2.0.1", - "resolved": "https://registry.npmjs.org/ipaddr.js/-/ipaddr.js-2.0.1.tgz", - "integrity": "sha512-1qTgH9NG+IIJ4yfKs2e6Pp1bZg8wbDbKHT21HrLIeYBTRLgMYKnMTPAuI3Lcs61nfx5h1xlXnbJtH1kX5/d/ng==", - "dev": true, - "engines": { - "node": ">= 10" - } - }, - "node_modules/is-arguments": { - "version": "1.1.1", - "resolved": "https://registry.npmjs.org/is-arguments/-/is-arguments-1.1.1.tgz", - "integrity": "sha512-8Q7EARjzEnKpt/PCD7e1cgUS0a6X8u5tdSiMqXhojOdoV9TsMsiO+9VLC5vAmO8N7/GmXn7yjR8qnA6bVAEzfA==", - "dependencies": { - "call-bind": "^1.0.2", - "has-tostringtag": "^1.0.0" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/is-bigint": { - "version": "1.0.4", - "resolved": "https://registry.npmjs.org/is-bigint/-/is-bigint-1.0.4.tgz", - "integrity": "sha512-zB9CruMamjym81i2JZ3UMn54PKGsQzsJeo6xvN3HJJ4CAsQNB6iRutp2To77OfCNuoxspsIhzaPoO1zyCEhFOg==", - "dependencies": { - "has-bigints": "^1.0.1" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/is-binary-path": { - "version": "2.1.0", - "resolved": "https://registry.npmjs.org/is-binary-path/-/is-binary-path-2.1.0.tgz", - "integrity": "sha512-ZMERYes6pDydyuGidse7OsHxtbI7WVeUEozgR/g7rd0xUimYNlvZRE/K2MgZTjWy725IfelLeVcEM97mmtRGXw==", - "dev": true, - "dependencies": { - "binary-extensions": "^2.0.0" - }, - "engines": { - "node": ">=8" - } - }, - "node_modules/is-boolean-object": { - "version": "1.1.2", - "resolved": "https://registry.npmjs.org/is-boolean-object/-/is-boolean-object-1.1.2.tgz", - "integrity": "sha512-gDYaKHJmnj4aWxyj6YHyXVpdQawtVLHU5cb+eztPGczf6cjuTdwve5ZIEfgXqH4e57An1D1AKf8CZ3kYrQRqYA==", - "dependencies": { - "call-bind": "^1.0.2", - "has-tostringtag": "^1.0.0" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/is-callable": { - "version": "1.2.4", - "resolved": "https://registry.npmjs.org/is-callable/-/is-callable-1.2.4.tgz", - "integrity": "sha512-nsuwtxZfMX67Oryl9LCQ+upnC0Z0BgpwntpS89m1H/TLF0zNfzfLMV/9Wa/6MZsj0acpEjAO0KF1xT6ZdLl95w==", - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/is-core-module": { - "version": "2.9.0", - "resolved": "https://registry.npmjs.org/is-core-module/-/is-core-module-2.9.0.tgz", - "integrity": "sha512-+5FPy5PnwmO3lvfMb0AsoPaBG+5KHUI0wYFXOtYPnVVVspTFUuMZNfNaNVRt3FZadstu2c8x23vykRW/NBoU6A==", - "dev": true, - "dependencies": { - "has": "^1.0.3" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/is-date-object": { - "version": "1.0.5", - "resolved": "https://registry.npmjs.org/is-date-object/-/is-date-object-1.0.5.tgz", - "integrity": "sha512-9YQaSxsAiSwcvS33MBk3wTCVnWK+HhF8VZR2jRxehM16QcVOdHqPn4VPHmRK4lSr38n9JriurInLcP90xsYNfQ==", - "dependencies": { - "has-tostringtag": "^1.0.0" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/is-docker": { - "version": "2.2.1", - "resolved": "https://registry.npmjs.org/is-docker/-/is-docker-2.2.1.tgz", - "integrity": "sha512-F+i2BKsFrH66iaUFc0woD8sLy8getkwTwtOBjvs56Cx4CgJDeKQeqfz8wAYiSb8JOprWhHH5p77PbmYCvvUuXQ==", - "dev": true, - "bin": { - "is-docker": "cli.js" - }, - "engines": { - "node": ">=8" - }, - "funding": { - "url": "https://github.com/sponsors/sindresorhus" - } - }, - "node_modules/is-extglob": { - "version": "2.1.1", - "resolved": "https://registry.npmjs.org/is-extglob/-/is-extglob-2.1.1.tgz", - "integrity": "sha1-qIwCU1eR8C7TfHahueqXc8gz+MI=", - "dev": true, - "engines": { - "node": ">=0.10.0" - } - }, - "node_modules/is-generator-function": { - "version": "1.0.10", - "resolved": "https://registry.npmjs.org/is-generator-function/-/is-generator-function-1.0.10.tgz", - "integrity": "sha512-jsEjy9l3yiXEQ+PsXdmBwEPcOxaXWLspKdplFUVI9vq1iZgIekeC0L167qeu86czQaxed3q/Uzuw0swL0irL8A==", - "dependencies": { - "has-tostringtag": "^1.0.0" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/is-glob": { - "version": "4.0.3", - "resolved": "https://registry.npmjs.org/is-glob/-/is-glob-4.0.3.tgz", - "integrity": "sha512-xelSayHH36ZgE7ZWhli7pW34hNbNl8Ojv5KVmkJD4hBdD3th8Tfk9vYasLM+mXWOZhFkgZfxhLSnrwRr4elSSg==", - "dev": true, - "dependencies": { - "is-extglob": "^2.1.1" - }, - "engines": { - "node": ">=0.10.0" - } - }, - "node_modules/is-nan": { - "version": "1.3.2", - "resolved": "https://registry.npmjs.org/is-nan/-/is-nan-1.3.2.tgz", - "integrity": "sha512-E+zBKpQ2t6MEo1VsonYmluk9NxGrbzpeeLC2xIViuO2EjU2xsXsBPwTr3Ykv9l08UYEVEdWeRZNouaZqF6RN0w==", - "dependencies": { - "call-bind": "^1.0.0", - "define-properties": "^1.1.3" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/is-negative-zero": { - "version": "2.0.2", - "resolved": "https://registry.npmjs.org/is-negative-zero/-/is-negative-zero-2.0.2.tgz", - "integrity": "sha512-dqJvarLawXsFbNDeJW7zAz8ItJ9cd28YufuuFzh0G8pNHjJMnY08Dv7sYX2uF5UpQOwieAeOExEYAWWfu7ZZUA==", - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/is-number": { - "version": "7.0.0", - "resolved": "https://registry.npmjs.org/is-number/-/is-number-7.0.0.tgz", - "integrity": "sha512-41Cifkg6e8TylSpdtTpeLVMqvSBEVzTttHvERD741+pnZ8ANv0004MRL43QKPDlK9cGvNp6NZWZUBlbGXYxxng==", - "dev": true, - "engines": { - "node": ">=0.12.0" - } - }, - "node_modules/is-number-object": { - "version": "1.0.6", - "resolved": "https://registry.npmjs.org/is-number-object/-/is-number-object-1.0.6.tgz", - "integrity": "sha512-bEVOqiRcvo3zO1+G2lVMy+gkkEm9Yh7cDMRusKKu5ZJKPUYSJwICTKZrNKHA2EbSP0Tu0+6B/emsYNHZyn6K8g==", - "dependencies": { - "has-tostringtag": "^1.0.0" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/is-path-cwd": { - "version": "2.2.0", - "resolved": "https://registry.npmjs.org/is-path-cwd/-/is-path-cwd-2.2.0.tgz", - "integrity": "sha512-w942bTcih8fdJPJmQHFzkS76NEP8Kzzvmw92cXsazb8intwLqPibPPdXf4ANdKV3rYMuuQYGIWtvz9JilB3NFQ==", - "dev": true, - "engines": { - "node": ">=6" - } - }, - "node_modules/is-path-inside": { - "version": "3.0.3", - "resolved": "https://registry.npmjs.org/is-path-inside/-/is-path-inside-3.0.3.tgz", - "integrity": "sha512-Fd4gABb+ycGAmKou8eMftCupSir5lRxqf4aD/vd0cD2qc4HL07OjCeuHMr8Ro4CoMaeCKDB0/ECBOVWjTwUvPQ==", - "dev": true, - "engines": { - "node": ">=8" - } - }, - "node_modules/is-plain-obj": { - "version": "3.0.0", - "resolved": "https://registry.npmjs.org/is-plain-obj/-/is-plain-obj-3.0.0.tgz", - "integrity": "sha512-gwsOE28k+23GP1B6vFl1oVh/WOzmawBrKwo5Ev6wMKzPkaXaCDIQKzLnvsA42DRlbVTWorkgTKIviAKCWkfUwA==", - "dev": true, - "engines": { - "node": ">=10" - }, - "funding": { - "url": "https://github.com/sponsors/sindresorhus" - } - }, - "node_modules/is-plain-object": { - "version": "2.0.4", - "resolved": "https://registry.npmjs.org/is-plain-object/-/is-plain-object-2.0.4.tgz", - "integrity": "sha512-h5PpgXkWitc38BBMYawTYMWJHFZJVnBquFE57xFpjB8pJFiF6gZ+bU+WyI/yqXiFR5mdLsgYNaPe8uao6Uv9Og==", - "dev": true, - "dependencies": { - "isobject": "^3.0.1" - }, - "engines": { - "node": ">=0.10.0" - } - }, - "node_modules/is-regex": { - "version": "1.1.4", - "resolved": "https://registry.npmjs.org/is-regex/-/is-regex-1.1.4.tgz", - "integrity": "sha512-kvRdxDsxZjhzUX07ZnLydzS1TU/TJlTUHHY4YLL87e37oUA49DfkLqgy+VjFocowy29cKvcSiu+kIv728jTTVg==", - "dependencies": { - "call-bind": "^1.0.2", - "has-tostringtag": "^1.0.0" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/is-shared-array-buffer": { - "version": "1.0.1", - "resolved": "https://registry.npmjs.org/is-shared-array-buffer/-/is-shared-array-buffer-1.0.1.tgz", - "integrity": "sha512-IU0NmyknYZN0rChcKhRO1X8LYz5Isj/Fsqh8NJOSf+N/hCOTwy29F32Ik7a+QszE63IdvmwdTPDd6cZ5pg4cwA==", - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/is-stream": { - "version": "2.0.1", - "resolved": "https://registry.npmjs.org/is-stream/-/is-stream-2.0.1.tgz", - "integrity": "sha512-hFoiJiTl63nn+kstHGBtewWSKnQLpyb155KHheA1l39uvtO9nWIop1p3udqPcUd/xbF1VLMO4n7OI6p7RbngDg==", - "dev": true, - "engines": { - "node": ">=8" - }, - "funding": { - "url": "https://github.com/sponsors/sindresorhus" - } - }, - "node_modules/is-string": { - "version": "1.0.7", - "resolved": "https://registry.npmjs.org/is-string/-/is-string-1.0.7.tgz", - "integrity": "sha512-tE2UXzivje6ofPW7l23cjDOMa09gb7xlAqG6jG5ej6uPV32TlWP3NKPigtaGeHNu9fohccRYvIiZMfOOnOYUtg==", - "dependencies": { - "has-tostringtag": "^1.0.0" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/is-symbol": { - "version": "1.0.4", - "resolved": "https://registry.npmjs.org/is-symbol/-/is-symbol-1.0.4.tgz", - "integrity": "sha512-C/CPBqKWnvdcxqIARxyOh4v1UUEOCHpgDa0WYgpKDFMszcrPcffg5uhwSgPCLD2WWxmq6isisz87tzT01tuGhg==", - "dependencies": { - "has-symbols": "^1.0.2" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/is-typed-array": { - "version": "1.1.8", - "resolved": "https://registry.npmjs.org/is-typed-array/-/is-typed-array-1.1.8.tgz", - "integrity": "sha512-HqH41TNZq2fgtGT8WHVFVJhBVGuY3AnP3Q36K8JKXUxSxRgk/d+7NjmwG2vo2mYmXK8UYZKu0qH8bVP5gEisjA==", - "dependencies": { - "available-typed-arrays": "^1.0.5", - "call-bind": "^1.0.2", - "es-abstract": "^1.18.5", - "foreach": "^2.0.5", - "has-tostringtag": "^1.0.0" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/is-weakref": { - "version": "1.0.2", - "resolved": "https://registry.npmjs.org/is-weakref/-/is-weakref-1.0.2.tgz", - "integrity": "sha512-qctsuLZmIQ0+vSSMfoVvyFe2+GSEvnmZ2ezTup1SBse9+twCCeial6EEi3Nc2KFcf6+qz2FBPnjXsk8xhKSaPQ==", - "dependencies": { - "call-bind": "^1.0.2" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/is-wsl": { - "version": "2.2.0", - "resolved": "https://registry.npmjs.org/is-wsl/-/is-wsl-2.2.0.tgz", - "integrity": "sha512-fKzAra0rGJUUBwGBgNkHZuToZcn+TtXHpeCgmkMJMMYx1sQDYaCSyjJBSCa2nH1DGm7s3n1oBnohoVTBaN7Lww==", - "dev": true, - "dependencies": { - "is-docker": "^2.0.0" - }, - "engines": { - "node": ">=8" - } - }, - "node_modules/isarray": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/isarray/-/isarray-1.0.0.tgz", - "integrity": "sha1-u5NdSFgsuhaMBoNJV6VKPgcSTxE=", - "dev": true - }, - "node_modules/isexe": { - "version": "2.0.0", - "resolved": "https://registry.npmjs.org/isexe/-/isexe-2.0.0.tgz", - "integrity": "sha1-6PvzdNxVb/iUehDcsFctYz8s+hA=", - "dev": true - }, - "node_modules/isobject": { - "version": "3.0.1", - "resolved": "https://registry.npmjs.org/isobject/-/isobject-3.0.1.tgz", - "integrity": "sha512-WhB9zCku7EGTj/HQQRz5aUQEUeoQZH2bWcltRErOpymJ4boYE6wL9Tbr23krRPSZ+C5zqNSrSw+Cc7sZZ4b7vg==", - "dev": true, - "engines": { - "node": ">=0.10.0" - } - }, - "node_modules/jest-worker": { - "version": "27.4.6", - "resolved": "https://registry.npmjs.org/jest-worker/-/jest-worker-27.4.6.tgz", - "integrity": "sha512-gHWJF/6Xi5CTG5QCvROr6GcmpIqNYpDJyc8A1h/DyXqH1tD6SnRCM0d3U5msV31D2LB/U+E0M+W4oyvKV44oNw==", - "dependencies": { - "@types/node": "*", - "merge-stream": "^2.0.0", - "supports-color": "^8.0.0" - }, - "engines": { - "node": ">= 10.13.0" - } - }, - "node_modules/jest-worker/node_modules/supports-color": { - "version": "8.1.1", - "resolved": "https://registry.npmjs.org/supports-color/-/supports-color-8.1.1.tgz", - "integrity": "sha512-MpUEN2OodtUzxvKQl72cUF7RQ5EiHsGvSsVG0ia9c5RbWGL2CI4C7EpPS8UTBIplnlzZiNuV56w+FuNxy3ty2Q==", - "dependencies": { - "has-flag": "^4.0.0" - }, - "engines": { - "node": ">=10" - }, - "funding": { - "url": "https://github.com/chalk/supports-color?sponsor=1" - } - }, - "node_modules/json-parse-better-errors": { - "version": "1.0.2", - "resolved": "https://registry.npmjs.org/json-parse-better-errors/-/json-parse-better-errors-1.0.2.tgz", - "integrity": "sha512-mrqyZKfX5EhL7hvqcV6WG1yYjnjeuYDzDhhcAAUrq8Po85NBQBJP+ZDUT75qZQ98IkUoBqdkExkukOU7Ts2wrw==" - }, - "node_modules/json-schema-traverse": { - "version": "0.4.1", - "resolved": "https://registry.npmjs.org/json-schema-traverse/-/json-schema-traverse-0.4.1.tgz", - "integrity": "sha512-xbbCH5dCYU5T8LcEhhuh7HJ88HXuW3qsI3Y0zOZFKfZEHcpWiHU/Jxzk629Brsab/mMiHQti9wMP+845RPe3Vg==" - }, - "node_modules/jssha": { - "version": "3.2.0", - "resolved": "https://registry.npmjs.org/jssha/-/jssha-3.2.0.tgz", - "integrity": "sha512-QuruyBENDWdN4tZwJbQq7/eAK85FqrI4oDbXjy5IBhYD+2pTJyBUWZe8ctWaCkrV0gy6AaelgOZZBMeswEa/6Q==", - "engines": { - "node": "*" - } - }, - "node_modules/kind-of": { - "version": "6.0.3", - "resolved": "https://registry.npmjs.org/kind-of/-/kind-of-6.0.3.tgz", - "integrity": "sha512-dcS1ul+9tmeD95T+x28/ehLgd9mENa3LsvDTtzm3vyBEO7RPptvAD+t44WVXaUjTBRcrpFeFlC8WCruUR456hw==", - "dev": true, - "engines": { - "node": ">=0.10.0" - } - }, - "node_modules/loader-runner": { - "version": "4.2.0", - "resolved": "https://registry.npmjs.org/loader-runner/-/loader-runner-4.2.0.tgz", - "integrity": "sha512-92+huvxMvYlMzMt0iIOukcwYBFpkYJdpl2xsZ7LrlayO7E8SOv+JJUEK17B/dJIHAOLMfh2dZZ/Y18WgmGtYNw==", - "engines": { - "node": ">=6.11.5" - } - }, - "node_modules/locate-path": { - "version": "5.0.0", - "resolved": "https://registry.npmjs.org/locate-path/-/locate-path-5.0.0.tgz", - "integrity": "sha512-t7hw9pI+WvuwNJXwk5zVHpyhIqzg2qTlklJOf0mVxGSbe3Fp2VieZcduNYjaLDoy6p9uGpQEGWG87WpMKlNq8g==", - "dependencies": { - "p-locate": "^4.1.0" - }, - "engines": { - "node": ">=8" - } - }, - "node_modules/lodash": { - "version": "4.17.21", - "resolved": "https://registry.npmjs.org/lodash/-/lodash-4.17.21.tgz", - "integrity": "sha512-v2kDEe57lecTulaDIuNTPy3Ry4gLGJ6Z1O3vE1krgXZNrsQ+LFTGHVxVjcXPs17LhbZVGedAJv8XZ1tvj5FvSg==", - "dev": true - }, - "node_modules/lower-case": { - "version": "2.0.2", - "resolved": "https://registry.npmjs.org/lower-case/-/lower-case-2.0.2.tgz", - "integrity": "sha512-7fm3l3NAF9WfN6W3JOmf5drwpVqX78JtoGJ3A6W0a6ZnldM41w2fV5D490psKFTpMds8TJse/eHLFFsNHHjHgg==", - "dev": true, - "dependencies": { - "tslib": "^2.0.3" - } - }, - "node_modules/md5.js": { - "version": "1.3.5", - "resolved": "https://registry.npmjs.org/md5.js/-/md5.js-1.3.5.tgz", - "integrity": "sha512-xitP+WxNPcTTOgnTJcrhM0xvdPepipPSf3I8EIpGKeFLjt3PlJLIDG3u8EX53ZIubkb+5U2+3rELYpEhHhzdkg==", - "dependencies": { - "hash-base": "^3.0.0", - "inherits": "^2.0.1", - "safe-buffer": "^5.1.2" - } - }, - "node_modules/media-typer": { - "version": "0.3.0", - "resolved": "https://registry.npmjs.org/media-typer/-/media-typer-0.3.0.tgz", - "integrity": "sha1-hxDXrwqmJvj/+hzgAWhUUmMlV0g=", - "dev": true, - "engines": { - "node": ">= 0.6" - } - }, - "node_modules/memfs": { - "version": "3.4.1", - "resolved": "https://registry.npmjs.org/memfs/-/memfs-3.4.1.tgz", - "integrity": "sha512-1c9VPVvW5P7I85c35zAdEr1TD5+F11IToIHIlrVIcflfnzPkJa0ZoYEoEdYDP8KgPFoSZ/opDrUsAoZWym3mtw==", - "dev": true, - "dependencies": { - "fs-monkey": "1.0.3" - }, - "engines": { - "node": ">= 4.0.0" - } - }, - "node_modules/merge-descriptors": { - "version": "1.0.1", - "resolved": "https://registry.npmjs.org/merge-descriptors/-/merge-descriptors-1.0.1.tgz", - "integrity": "sha1-sAqqVW3YtEVoFQ7J0blT8/kMu2E=", - "dev": true - }, - "node_modules/merge-stream": { - "version": "2.0.0", - "resolved": "https://registry.npmjs.org/merge-stream/-/merge-stream-2.0.0.tgz", - "integrity": "sha512-abv/qOcuPfk3URPfDzmZU1LKmuw8kT+0nIHvKrKgFrwifol/doWcdA4ZqsWQ8ENrFKkd67Mfpo/LovbIUsbt3w==" - }, - "node_modules/merge2": { - "version": "1.4.1", - "resolved": "https://registry.npmjs.org/merge2/-/merge2-1.4.1.tgz", - "integrity": "sha512-8q7VEgMJW4J8tcfVPy8g09NcQwZdbwFEqhe/WZkoIzjn/3TGDwtOCYtXGxA3O8tPzpczCCDgv+P2P5y00ZJOOg==", - "dev": true, - "engines": { - "node": ">= 8" - } - }, - "node_modules/methods": { - "version": "1.1.2", - "resolved": "https://registry.npmjs.org/methods/-/methods-1.1.2.tgz", - "integrity": "sha1-VSmk1nZUE07cxSZmVoNbD4Ua/O4=", - "dev": true, - "engines": { - "node": ">= 0.6" - } - }, - "node_modules/micromatch": { - "version": "4.0.4", - "resolved": "https://registry.npmjs.org/micromatch/-/micromatch-4.0.4.tgz", - "integrity": "sha512-pRmzw/XUcwXGpD9aI9q/0XOwLNygjETJ8y0ao0wdqprrzDa4YnxLcz7fQRZr8voh8V10kGhABbNcHVk5wHgWwg==", - "dev": true, - "dependencies": { - "braces": "^3.0.1", - "picomatch": "^2.2.3" - }, - "engines": { - "node": ">=8.6" - } - }, - "node_modules/miller-rabin": { - "version": "4.0.1", - "resolved": "https://registry.npmjs.org/miller-rabin/-/miller-rabin-4.0.1.tgz", - "integrity": "sha512-115fLhvZVqWwHPbClyntxEVfVDfl9DLLTuJvq3g2O/Oxi8AiNouAHvDSzHS0viUJc+V5vm3eq91Xwqn9dp4jRA==", - "dependencies": { - "bn.js": "^4.0.0", - "brorand": "^1.0.1" - }, - "bin": { - "miller-rabin": "bin/miller-rabin" - } - }, - "node_modules/miller-rabin/node_modules/bn.js": { - "version": "4.12.0", - "resolved": "https://registry.npmjs.org/bn.js/-/bn.js-4.12.0.tgz", - "integrity": "sha512-c98Bf3tPniI+scsdk237ku1Dc3ujXQTSgyiPUDEOe7tRkhrqridvh8klBv0HCEso1OLOYcHuCv/cS6DNxKH+ZA==" - }, - "node_modules/mime": { - "version": "1.6.0", - "resolved": "https://registry.npmjs.org/mime/-/mime-1.6.0.tgz", - "integrity": "sha512-x0Vn8spI+wuJ1O6S7gnbaQg8Pxh4NNHb7KSINmEWKiPE4RKOplvijn+NkmYmmRgP68mc70j2EbeTFRsrswaQeg==", - "dev": true, - "bin": { - "mime": "cli.js" - }, - "engines": { - "node": ">=4" - } - }, - "node_modules/mime-db": { - "version": "1.51.0", - "resolved": "https://registry.npmjs.org/mime-db/-/mime-db-1.51.0.tgz", - "integrity": "sha512-5y8A56jg7XVQx2mbv1lu49NR4dokRnhZYTtL+KGfaa27uq4pSTXkwQkFJl4pkRMyNFz/EtYDSkiiEHx3F7UN6g==", - "engines": { - "node": ">= 0.6" - } - }, - "node_modules/mime-types": { - "version": "2.1.34", - "resolved": "https://registry.npmjs.org/mime-types/-/mime-types-2.1.34.tgz", - "integrity": "sha512-6cP692WwGIs9XXdOO4++N+7qjqv0rqxxVvJ3VHPh/Sc9mVZcQP+ZGhkKiTvWMQRr2tbHkJP/Yn7Y0npb3ZBs4A==", - "dependencies": { - "mime-db": "1.51.0" - }, - "engines": { - "node": ">= 0.6" - } - }, - "node_modules/mimic-fn": { - "version": "2.1.0", - "resolved": "https://registry.npmjs.org/mimic-fn/-/mimic-fn-2.1.0.tgz", - "integrity": "sha512-OqbOk5oEQeAZ8WXWydlu9HJjz9WVdEIvamMCcXmuqUYjTknH/sqsWvhQ3vgwKFRR1HpjvNBKQ37nbJgYzGqGcg==", - "dev": true, - "engines": { - "node": ">=6" - } - }, - "node_modules/minimalistic-assert": { - "version": "1.0.1", - "resolved": "https://registry.npmjs.org/minimalistic-assert/-/minimalistic-assert-1.0.1.tgz", - "integrity": "sha512-UtJcAD4yEaGtjPezWuO9wC4nwUnVH/8/Im3yEHQP4b67cXlD/Qr9hdITCU1xDbSEXg2XKNaP8jsReV7vQd00/A==" - }, - "node_modules/minimalistic-crypto-utils": { - "version": "1.0.1", - "resolved": "https://registry.npmjs.org/minimalistic-crypto-utils/-/minimalistic-crypto-utils-1.0.1.tgz", - "integrity": "sha1-9sAMHAsIIkblxNmd+4x8CDsrWCo=" - }, - "node_modules/minimatch": { - "version": "3.0.4", - "resolved": "https://registry.npmjs.org/minimatch/-/minimatch-3.0.4.tgz", - "integrity": "sha512-yJHVQEhyqPLUTgt9B83PXu6W3rx4MvvHvSUvToogpwoGDOUQ+yDrR0HRot+yOCdCO7u4hX3pWft6kWBBcqh0UA==", - "dependencies": { - "brace-expansion": "^1.1.7" - }, - "engines": { - "node": "*" - } - }, - "node_modules/minimist": { - "version": "1.2.5", - "resolved": "https://registry.npmjs.org/minimist/-/minimist-1.2.5.tgz", - "integrity": "sha512-FM9nNUYrRBAELZQT3xeZQ7fmMOBg6nWNmJKTcgsJeaLstP/UODVpGsr5OhXhhXg6f+qtJ8uiZ+PUxkDWcgIXLw==", - "dev": true - }, - "node_modules/mkdirp": { - "version": "0.5.5", - "resolved": "https://registry.npmjs.org/mkdirp/-/mkdirp-0.5.5.tgz", - "integrity": "sha512-NKmAlESf6jMGym1++R0Ra7wvhV+wFW63FaSOFPwRahvea0gMUcGUhVeAg/0BC0wiv9ih5NYPB1Wn1UEI1/L+xQ==", - "dev": true, - "dependencies": { - "minimist": "^1.2.5" - }, - "bin": { - "mkdirp": "bin/cmd.js" - } - }, - "node_modules/mkdirp-classic": { - "version": "0.5.3", - "resolved": "https://registry.npmjs.org/mkdirp-classic/-/mkdirp-classic-0.5.3.tgz", - "integrity": "sha512-gKLcREMhtuZRwRAfqP3RFW+TK4JqApVBtOIftVgjuABpAtpxhPGaDcfvbhNvD0B8iD1oUr/txX35NjcaY6Ns/A==" - }, - "node_modules/ms": { - "version": "2.0.0", - "resolved": "https://registry.npmjs.org/ms/-/ms-2.0.0.tgz", - "integrity": "sha1-VgiurfwAvmwpAd9fmGF4jeDVl8g=", - "dev": true - }, - "node_modules/multicast-dns": { - "version": "6.2.3", - "resolved": "https://registry.npmjs.org/multicast-dns/-/multicast-dns-6.2.3.tgz", - "integrity": "sha512-ji6J5enbMyGRHIAkAOu3WdV8nggqviKCEKtXcOqfphZZtQrmHKycfynJ2V7eVPUA4NhJ6V7Wf4TmGbTwKE9B6g==", - "dev": true, - "dependencies": { - "dns-packet": "^1.3.1", - "thunky": "^1.0.2" - }, - "bin": { - "multicast-dns": "cli.js" - } - }, - "node_modules/multicast-dns-service-types": { - "version": "1.1.0", - "resolved": "https://registry.npmjs.org/multicast-dns-service-types/-/multicast-dns-service-types-1.1.0.tgz", - "integrity": "sha1-iZ8R2WhuXgXLkbNdXw5jt3PPyQE=", - "dev": true - }, - "node_modules/negotiator": { - "version": "0.6.3", - "resolved": "https://registry.npmjs.org/negotiator/-/negotiator-0.6.3.tgz", - "integrity": "sha512-+EUsqGPLsM+j/zdChZjsnX51g4XrHFOIXwfnCVPGlQk/k5giakcKsuxCObBRu6DSm9opw/O6slWbJdghQM4bBg==", - "dev": true, - "engines": { - "node": ">= 0.6" - } - }, - "node_modules/neo-async": { - "version": "2.6.2", - "resolved": "https://registry.npmjs.org/neo-async/-/neo-async-2.6.2.tgz", - "integrity": "sha512-Yd3UES5mWCSqR+qNT93S3UoYUkqAZ9lLg8a7g9rimsWmYGK8cVToA4/sF3RrshdyV3sAGMXVUmpMYOw+dLpOuw==" - }, - "node_modules/no-case": { - "version": "3.0.4", - "resolved": "https://registry.npmjs.org/no-case/-/no-case-3.0.4.tgz", - "integrity": "sha512-fgAN3jGAh+RoxUGZHTSOLJIqUc2wmoBwGR4tbpNAKmmovFoWq0OdRkb0VkldReO2a2iBT/OEulG9XSUc10r3zg==", - "dev": true, - "dependencies": { - "lower-case": "^2.0.2", - "tslib": "^2.0.3" - } - }, - "node_modules/node-fetch": { - "version": "2.6.7", - "resolved": "https://registry.npmjs.org/node-fetch/-/node-fetch-2.6.7.tgz", - "integrity": "sha512-ZjMPFEfVx5j+y2yF35Kzx5sF7kDzxuDj6ziH4FFbOp87zKDZNx8yExJIb05OGF4Nlt9IHFIMBkRl41VdvcNdbQ==", - "dependencies": { - "whatwg-url": "^5.0.0" - }, - "engines": { - "node": "4.x || >=6.0.0" - }, - "peerDependencies": { - "encoding": "^0.1.0" - }, - "peerDependenciesMeta": { - "encoding": { - "optional": true - } - } - }, - "node_modules/node-forge": { - "version": "1.2.1", - "resolved": "https://registry.npmjs.org/node-forge/-/node-forge-1.2.1.tgz", - "integrity": "sha512-Fcvtbb+zBcZXbTTVwqGA5W+MKBj56UjVRevvchv5XrcyXbmNdesfZL37nlcWOfpgHhgmxApw3tQbTr4CqNmX4w==", - "dev": true, - "engines": { - "node": ">= 6.13.0" - } - }, - "node_modules/node-polyfill-webpack-plugin": { - "version": "1.1.4", - "resolved": "https://registry.npmjs.org/node-polyfill-webpack-plugin/-/node-polyfill-webpack-plugin-1.1.4.tgz", - "integrity": "sha512-Z0XTKj1wRWO8o/Vjobsw5iOJCN+Sua3EZEUc2Ziy9CyVvmHKu6o+t4gUH9GOE0czyPR94LI6ZCV/PpcM8b5yow==", - "dependencies": { - "assert": "^2.0.0", - "browserify-zlib": "^0.2.0", - "buffer": "^6.0.3", - "console-browserify": "^1.2.0", - "constants-browserify": "^1.0.0", - "crypto-browserify": "^3.12.0", - "domain-browser": "^4.19.0", - "events": "^3.3.0", - "filter-obj": "^2.0.2", - "https-browserify": "^1.0.0", - "os-browserify": "^0.3.0", - "path-browserify": "^1.0.1", - "process": "^0.11.10", - "punycode": "^2.1.1", - "querystring-es3": "^0.2.1", - "readable-stream": "^3.6.0", - "stream-browserify": "^3.0.0", - "stream-http": "^3.2.0", - "string_decoder": "^1.3.0", - "timers-browserify": "^2.0.12", - "tty-browserify": "^0.0.1", - "url": "^0.11.0", - "util": "^0.12.4", - "vm-browserify": "^1.1.2" - }, - "engines": { - "node": ">=10" - }, - "peerDependencies": { - "webpack": ">=5" - } - }, - "node_modules/node-polyfill-webpack-plugin/node_modules/string_decoder": { - "version": "1.3.0", - "resolved": "https://registry.npmjs.org/string_decoder/-/string_decoder-1.3.0.tgz", - "integrity": "sha512-hkRX8U1WjJFd8LsDJ2yQ/wWWxaopEsABU1XfkM8A+j0+85JAGppt16cr1Whg6KIbb4okU6Mql6BOj+uup/wKeA==", - "dependencies": { - "safe-buffer": "~5.2.0" - } - }, - "node_modules/node-releases": { - "version": "2.0.1", - "resolved": "https://registry.npmjs.org/node-releases/-/node-releases-2.0.1.tgz", - "integrity": "sha512-CqyzN6z7Q6aMeF/ktcMVTzhAHCEpf8SOarwpzpf8pNBY2k5/oM34UHldUwp8VKI7uxct2HxSRdJjBaZeESzcxA==" - }, - "node_modules/normalize-path": { - "version": "3.0.0", - "resolved": "https://registry.npmjs.org/normalize-path/-/normalize-path-3.0.0.tgz", - "integrity": "sha512-6eZs5Ls3WtCisHWp9S2GUy8dqkpGi4BVSz3GaqiE6ezub0512ESztXUwUB6C6IKbQkY2Pnb/mD4WYojCRwcwLA==", - "dev": true, - "engines": { - "node": ">=0.10.0" - } - }, - "node_modules/npm-run-path": { - "version": "4.0.1", - "resolved": "https://registry.npmjs.org/npm-run-path/-/npm-run-path-4.0.1.tgz", - "integrity": "sha512-S48WzZW777zhNIrn7gxOlISNAqi9ZC/uQFnRdbeIHhZhCA6UqpkOT8T1G7BvfdgP4Er8gF4sUbaS0i7QvIfCWw==", - "dev": true, - "dependencies": { - "path-key": "^3.0.0" - }, - "engines": { - "node": ">=8" - } - }, - "node_modules/nth-check": { - "version": "2.0.1", - "resolved": "https://registry.npmjs.org/nth-check/-/nth-check-2.0.1.tgz", - "integrity": "sha512-it1vE95zF6dTT9lBsYbxvqh0Soy4SPowchj0UBGj/V6cTPnXXtQOPUbhZ6CmGzAD/rW22LQK6E96pcdJXk4A4w==", - "dev": true, - "dependencies": { - "boolbase": "^1.0.0" - }, - "funding": { - "url": "https://github.com/fb55/nth-check?sponsor=1" - } - }, - "node_modules/object-inspect": { - "version": "1.12.0", - "resolved": "https://registry.npmjs.org/object-inspect/-/object-inspect-1.12.0.tgz", - "integrity": "sha512-Ho2z80bVIvJloH+YzRmpZVQe87+qASmBUKZDWgx9cu+KDrX2ZDH/3tMy+gXbZETVGs2M8YdxObOh7XAtim9Y0g==", - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/object-is": { - "version": "1.1.5", - "resolved": "https://registry.npmjs.org/object-is/-/object-is-1.1.5.tgz", - "integrity": "sha512-3cyDsyHgtmi7I7DfSSI2LDp6SK2lwvtbg0p0R1e0RvTqF5ceGx+K2dfSjm1bKDMVCFEDAQvy+o8c6a7VujOddw==", - "dependencies": { - "call-bind": "^1.0.2", - "define-properties": "^1.1.3" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/object-keys": { - "version": "1.1.1", - "resolved": "https://registry.npmjs.org/object-keys/-/object-keys-1.1.1.tgz", - "integrity": "sha512-NuAESUOUMrlIXOfHKzD6bpPu3tYt3xvjNdRIQ+FeT0lNb4K8WR70CaDxhuNguS2XG+GjkyMwOzsN5ZktImfhLA==", - "engines": { - "node": ">= 0.4" - } - }, - "node_modules/object.assign": { - "version": "4.1.2", - "resolved": "https://registry.npmjs.org/object.assign/-/object.assign-4.1.2.tgz", - "integrity": "sha512-ixT2L5THXsApyiUPYKmW+2EHpXXe5Ii3M+f4e+aJFAHao5amFRW6J0OO6c/LU8Be47utCx2GL89hxGB6XSmKuQ==", - "dependencies": { - "call-bind": "^1.0.0", - "define-properties": "^1.1.3", - "has-symbols": "^1.0.1", - "object-keys": "^1.1.1" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/obuf": { - "version": "1.1.2", - "resolved": "https://registry.npmjs.org/obuf/-/obuf-1.1.2.tgz", - "integrity": "sha512-PX1wu0AmAdPqOL1mWhqmlOd8kOIZQwGZw6rh7uby9fTc5lhaOWFLX3I6R1hrF9k3zUY40e6igsLGkDXK92LJNg==", - "dev": true - }, - "node_modules/on-finished": { - "version": "2.3.0", - "resolved": "https://registry.npmjs.org/on-finished/-/on-finished-2.3.0.tgz", - "integrity": "sha1-IPEzZIGwg811M3mSoWlxqi2QaUc=", - "dev": true, - "dependencies": { - "ee-first": "1.1.1" - }, - "engines": { - "node": ">= 0.8" - } - }, - "node_modules/on-headers": { - "version": "1.0.2", - "resolved": "https://registry.npmjs.org/on-headers/-/on-headers-1.0.2.tgz", - "integrity": "sha512-pZAE+FJLoyITytdqK0U5s+FIpjN0JP3OzFi/u8Rx+EV5/W+JTWGXG8xFzevE7AjBfDqHv/8vL8qQsIhHnqRkrA==", - "dev": true, - "engines": { - "node": ">= 0.8" - } - }, - "node_modules/once": { - "version": "1.4.0", - "resolved": "https://registry.npmjs.org/once/-/once-1.4.0.tgz", - "integrity": "sha1-WDsap3WWHUsROsF9nFC6753Xa9E=", - "dependencies": { - "wrappy": "1" - } - }, - "node_modules/onetime": { - "version": "5.1.2", - "resolved": "https://registry.npmjs.org/onetime/-/onetime-5.1.2.tgz", - "integrity": "sha512-kbpaSSGJTWdAY5KPVeMOKXSrPtr8C8C7wodJbcsd51jRnmD+GZu8Y0VoU6Dm5Z4vWr0Ig/1NKuWRKf7j5aaYSg==", - "dev": true, - "dependencies": { - "mimic-fn": "^2.1.0" - }, - "engines": { - "node": ">=6" - }, - "funding": { - "url": "https://github.com/sponsors/sindresorhus" - } - }, - "node_modules/open": { - "version": "8.4.0", - "resolved": "https://registry.npmjs.org/open/-/open-8.4.0.tgz", - "integrity": "sha512-XgFPPM+B28FtCCgSb9I+s9szOC1vZRSwgWsRUA5ylIxRTgKozqjOCrVOqGsYABPYK5qnfqClxZTFBa8PKt2v6Q==", - "dev": true, - "dependencies": { - "define-lazy-prop": "^2.0.0", - "is-docker": "^2.1.1", - "is-wsl": "^2.2.0" - }, - "engines": { - "node": ">=12" - }, - "funding": { - "url": "https://github.com/sponsors/sindresorhus" - } - }, - "node_modules/os-browserify": { - "version": "0.3.0", - "resolved": "https://registry.npmjs.org/os-browserify/-/os-browserify-0.3.0.tgz", - "integrity": "sha1-hUNzx/XCMVkU/Jv8a9gjj92h7Cc=" - }, - "node_modules/p-limit": { - "version": "2.3.0", - "resolved": "https://registry.npmjs.org/p-limit/-/p-limit-2.3.0.tgz", - "integrity": "sha512-//88mFWSJx8lxCzwdAABTJL2MyWB12+eIY7MDL2SqLmAkeKU9qxRvWuSyTjm3FUmpBEMuFfckAIqEaVGUDxb6w==", - "dependencies": { - "p-try": "^2.0.0" - }, - "engines": { - "node": ">=6" - }, - "funding": { - "url": "https://github.com/sponsors/sindresorhus" - } - }, - "node_modules/p-locate": { - "version": "4.1.0", - "resolved": "https://registry.npmjs.org/p-locate/-/p-locate-4.1.0.tgz", - "integrity": "sha512-R79ZZ/0wAxKGu3oYMlz8jy/kbhsNrS7SKZ7PxEHBgJ5+F2mtFW2fK2cOtBh1cHYkQsbzFV7I+EoRKe6Yt0oK7A==", - "dependencies": { - "p-limit": "^2.2.0" - }, - "engines": { - "node": ">=8" - } - }, - "node_modules/p-map": { - "version": "4.0.0", - "resolved": "https://registry.npmjs.org/p-map/-/p-map-4.0.0.tgz", - "integrity": "sha512-/bjOqmgETBYB5BoEeGVea8dmvHb2m9GLy1E9W43yeyfP6QQCZGFNa+XRceJEuDB6zqr+gKpIAmlLebMpykw/MQ==", - "dev": true, - "dependencies": { - "aggregate-error": "^3.0.0" - }, - "engines": { - "node": ">=10" - }, - "funding": { - "url": "https://github.com/sponsors/sindresorhus" - } - }, - "node_modules/p-retry": { - "version": "4.6.1", - "resolved": "https://registry.npmjs.org/p-retry/-/p-retry-4.6.1.tgz", - "integrity": "sha512-e2xXGNhZOZ0lfgR9kL34iGlU8N/KO0xZnQxVEwdeOvpqNDQfdnxIYizvWtK8RglUa3bGqI8g0R/BdfzLMxRkiA==", - "dev": true, - "dependencies": { - "@types/retry": "^0.12.0", - "retry": "^0.13.1" - }, - "engines": { - "node": ">=8" - } - }, - "node_modules/p-retry/node_modules/retry": { - "version": "0.13.1", - "resolved": "https://registry.npmjs.org/retry/-/retry-0.13.1.tgz", - "integrity": "sha512-XQBQ3I8W1Cge0Seh+6gjj03LbmRFWuoszgK9ooCpwYIrhhoO80pfq4cUkU5DkknwfOfFteRwlZ56PYOGYyFWdg==", - "dev": true, - "engines": { - "node": ">= 4" - } - }, - "node_modules/p-try": { - "version": "2.2.0", - "resolved": "https://registry.npmjs.org/p-try/-/p-try-2.2.0.tgz", - "integrity": "sha512-R4nPAVTAU0B9D35/Gk3uJf/7XYbQcyohSKdvAxIRSNghFl4e71hVoGnBNQz9cWaXxO2I10KTC+3jMdvvoKw6dQ==", - "engines": { - "node": ">=6" - } - }, - "node_modules/pako": { - "version": "1.0.11", - "resolved": "https://registry.npmjs.org/pako/-/pako-1.0.11.tgz", - "integrity": "sha512-4hLB8Py4zZce5s4yd9XzopqwVv/yGNhV1Bl8NTmCq1763HeK2+EwVTv+leGeL13Dnh2wfbqowVPXCIO0z4taYw==" - }, - "node_modules/param-case": { - "version": "3.0.4", - "resolved": "https://registry.npmjs.org/param-case/-/param-case-3.0.4.tgz", - "integrity": "sha512-RXlj7zCYokReqWpOPH9oYivUzLYZ5vAPIfEmCTNViosC78F8F0H9y7T7gG2M39ymgutxF5gcFEsyZQSph9Bp3A==", - "dev": true, - "dependencies": { - "dot-case": "^3.0.4", - "tslib": "^2.0.3" - } - }, - "node_modules/parse-asn1": { - "version": "5.1.6", - "resolved": "https://registry.npmjs.org/parse-asn1/-/parse-asn1-5.1.6.tgz", - "integrity": "sha512-RnZRo1EPU6JBnra2vGHj0yhp6ebyjBZpmUCLHWiFhxlzvBCCpAuZ7elsBp1PVAbQN0/04VD/19rfzlBSwLstMw==", - "dependencies": { - "asn1.js": "^5.2.0", - "browserify-aes": "^1.0.0", - "evp_bytestokey": "^1.0.0", - "pbkdf2": "^3.0.3", - "safe-buffer": "^5.1.1" - } - }, - "node_modules/parseurl": { - "version": "1.3.3", - "resolved": "https://registry.npmjs.org/parseurl/-/parseurl-1.3.3.tgz", - "integrity": "sha512-CiyeOxFT/JZyN5m0z9PfXw4SCBJ6Sygz1Dpl0wqjlhDEGGBP1GnsUVEL0p63hoG1fcj3fHynXi9NYO4nWOL+qQ==", - "dev": true, - "engines": { - "node": ">= 0.8" - } - }, - "node_modules/pascal-case": { - "version": "3.1.2", - "resolved": "https://registry.npmjs.org/pascal-case/-/pascal-case-3.1.2.tgz", - "integrity": "sha512-uWlGT3YSnK9x3BQJaOdcZwrnV6hPpd8jFH1/ucpiLRPh/2zCVJKS19E4GvYHvaCcACn3foXZ0cLB9Wrx1KGe5g==", - "dev": true, - "dependencies": { - "no-case": "^3.0.4", - "tslib": "^2.0.3" - } - }, - "node_modules/path-browserify": { - "version": "1.0.1", - "resolved": "https://registry.npmjs.org/path-browserify/-/path-browserify-1.0.1.tgz", - "integrity": "sha512-b7uo2UCUOYZcnF/3ID0lulOJi/bafxa1xPe7ZPsammBSpjSWQkjNxlt635YGS2MiR9GjvuXCtz2emr3jbsz98g==" - }, - "node_modules/path-exists": { - "version": "4.0.0", - "resolved": "https://registry.npmjs.org/path-exists/-/path-exists-4.0.0.tgz", - "integrity": "sha512-ak9Qy5Q7jYb2Wwcey5Fpvg2KoAc/ZIhLSLOSBmRmygPsGwkVVt0fZa0qrtMz+m6tJTAHfZQ8FnmB4MG4LWy7/w==", - "engines": { - "node": ">=8" - } - }, - "node_modules/path-is-absolute": { - "version": "1.0.1", - "resolved": "https://registry.npmjs.org/path-is-absolute/-/path-is-absolute-1.0.1.tgz", - "integrity": "sha1-F0uSaHNVNP+8es5r9TpanhtcX18=", - "engines": { - "node": ">=0.10.0" - } - }, - "node_modules/path-key": { - "version": "3.1.1", - "resolved": "https://registry.npmjs.org/path-key/-/path-key-3.1.1.tgz", - "integrity": "sha512-ojmeN0qd+y0jszEtoY48r0Peq5dwMEkIlCOu6Q5f41lfkswXuKtYrhgoTpLnyIcHm24Uhqx+5Tqm2InSwLhE6Q==", - "dev": true, - "engines": { - "node": ">=8" - } - }, - "node_modules/path-parse": { - "version": "1.0.7", - "resolved": "https://registry.npmjs.org/path-parse/-/path-parse-1.0.7.tgz", - "integrity": "sha512-LDJzPVEEEPR+y48z93A0Ed0yXb8pAByGWo/k5YYdYgpY2/2EsOsksJrq7lOHxryrVOn1ejG6oAp8ahvOIQD8sw==", - "dev": true - }, - "node_modules/path-to-regexp": { - "version": "0.1.7", - "resolved": "https://registry.npmjs.org/path-to-regexp/-/path-to-regexp-0.1.7.tgz", - "integrity": "sha1-32BBeABfUi8V60SQ5yR6G/qmf4w=", - "dev": true - }, - "node_modules/path-type": { - "version": "4.0.0", - "resolved": "https://registry.npmjs.org/path-type/-/path-type-4.0.0.tgz", - "integrity": "sha512-gDKb8aZMDeD/tZWs9P6+q0J9Mwkdl6xMV8TjnGP3qJVJ06bdMgkbBlLU8IdfOsIsFz2BW1rNVT3XuNEl8zPAvw==", - "dev": true, - "engines": { - "node": ">=8" - } - }, - "node_modules/pbkdf2": { - "version": "3.1.2", - "resolved": "https://registry.npmjs.org/pbkdf2/-/pbkdf2-3.1.2.tgz", - "integrity": "sha512-iuh7L6jA7JEGu2WxDwtQP1ddOpaJNC4KlDEFfdQajSGgGPNi4OyDc2R7QnbY2bR9QjBVGwgvTdNJZoE7RaxUMA==", - "dependencies": { - "create-hash": "^1.1.2", - "create-hmac": "^1.1.4", - "ripemd160": "^2.0.1", - "safe-buffer": "^5.0.1", - "sha.js": "^2.4.8" - }, - "engines": { - "node": ">=0.12" - } - }, - "node_modules/pend": { - "version": "1.2.0", - "resolved": "https://registry.npmjs.org/pend/-/pend-1.2.0.tgz", - "integrity": "sha512-F3asv42UuXchdzt+xXqfW1OGlVBe+mxa2mqI0pg5yAHZPvFmY3Y6drSf/GQ1A86WgWEN9Kzh/WrgKa6iGcHXLg==" - }, - "node_modules/picocolors": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/picocolors/-/picocolors-1.0.0.tgz", - "integrity": "sha512-1fygroTLlHu66zi26VoTDv8yRgm0Fccecssto+MhsZ0D/DGW2sm8E8AjW7NU5VVTRt5GxbeZ5qBuJr+HyLYkjQ==" - }, - "node_modules/picomatch": { - "version": "2.3.1", - "resolved": "https://registry.npmjs.org/picomatch/-/picomatch-2.3.1.tgz", - "integrity": "sha512-JU3teHTNjmE2VCGFzuY8EXzCDVwEqB2a8fsIvwaStHhAWJEeVd1o1QD80CU6+ZdEXXSLbSsuLwJjkCBWqRQUVA==", - "dev": true, - "engines": { - "node": ">=8.6" - }, - "funding": { - "url": "https://github.com/sponsors/jonschlinkert" - } - }, - "node_modules/pkg-dir": { - "version": "4.2.0", - "resolved": "https://registry.npmjs.org/pkg-dir/-/pkg-dir-4.2.0.tgz", - "integrity": "sha512-HRDzbaKjC+AOWVXxAU/x54COGeIv9eb+6CkDSQoNTt4XyWoIJvuPsXizxu/Fr23EiekbtZwmh1IcIG/l/a10GQ==", - "dependencies": { - "find-up": "^4.0.0" - }, - "engines": { - "node": ">=8" - } - }, - "node_modules/portfinder": { - "version": "1.0.28", - "resolved": "https://registry.npmjs.org/portfinder/-/portfinder-1.0.28.tgz", - "integrity": "sha512-Se+2isanIcEqf2XMHjyUKskczxbPH7dQnlMjXX6+dybayyHvAf/TCgyMRlzf/B6QDhAEFOGes0pzRo3by4AbMA==", - "dev": true, - "dependencies": { - "async": "^2.6.2", - "debug": "^3.1.1", - "mkdirp": "^0.5.5" - }, - "engines": { - "node": ">= 0.12.0" - } - }, - "node_modules/portfinder/node_modules/debug": { - "version": "3.2.7", - "resolved": "https://registry.npmjs.org/debug/-/debug-3.2.7.tgz", - "integrity": "sha512-CFjzYYAi4ThfiQvizrFQevTTXHtnCqWfe7x1AhgEscTz6ZbLbfoLRLPugTQyBth6f8ZERVUSyWHFD/7Wu4t1XQ==", - "dev": true, - "dependencies": { - "ms": "^2.1.1" - } - }, - "node_modules/portfinder/node_modules/ms": { - "version": "2.1.3", - "resolved": "https://registry.npmjs.org/ms/-/ms-2.1.3.tgz", - "integrity": "sha512-6FlzubTLZG3J2a/NVCAleEhjzq5oxgHyaCU9yYXvcLsvoVaHJq/s5xXI6/XXP6tz7R9xAOtHnSO/tXtF3WRTlA==", - "dev": true - }, - "node_modules/pretty-error": { - "version": "4.0.0", - "resolved": "https://registry.npmjs.org/pretty-error/-/pretty-error-4.0.0.tgz", - "integrity": "sha512-AoJ5YMAcXKYxKhuJGdcvse+Voc6v1RgnsR3nWcYU7q4t6z0Q6T86sv5Zq8VIRbOWWFpvdGE83LtdSMNd+6Y0xw==", - "dev": true, - "dependencies": { - "lodash": "^4.17.20", - "renderkid": "^3.0.0" - } - }, - "node_modules/process": { - "version": "0.11.10", - "resolved": "https://registry.npmjs.org/process/-/process-0.11.10.tgz", - "integrity": "sha1-czIwDoQBYb2j5podHZGn1LwW8YI=", - "engines": { - "node": ">= 0.6.0" - } - }, - "node_modules/process-nextick-args": { - "version": "2.0.1", - "resolved": "https://registry.npmjs.org/process-nextick-args/-/process-nextick-args-2.0.1.tgz", - "integrity": "sha512-3ouUOpQhtgrbOa17J7+uxOTpITYWaGP7/AhoR3+A+/1e9skrzelGi/dXzEYyvbxubEF6Wn2ypscTKiKJFFn1ag==", - "dev": true - }, - "node_modules/progress": { - "version": "2.0.3", - "resolved": "https://registry.npmjs.org/progress/-/progress-2.0.3.tgz", - "integrity": "sha512-7PiHtLll5LdnKIMw100I+8xJXR5gW2QwWYkT6iJva0bXitZKa/XMrSbdmg3r2Xnaidz9Qumd0VPaMrZlF9V9sA==", - "engines": { - "node": ">=0.4.0" - } - }, - "node_modules/proxy-addr": { - "version": "2.0.7", - "resolved": "https://registry.npmjs.org/proxy-addr/-/proxy-addr-2.0.7.tgz", - "integrity": "sha512-llQsMLSUDUPT44jdrU/O37qlnifitDP+ZwrmmZcoSKyLKvtZxpyV0n2/bD/N4tBAAZ/gJEdZU7KMraoK1+XYAg==", - "dev": true, - "dependencies": { - "forwarded": "0.2.0", - "ipaddr.js": "1.9.1" - }, - "engines": { - "node": ">= 0.10" - } - }, - "node_modules/proxy-addr/node_modules/ipaddr.js": { - "version": "1.9.1", - "resolved": "https://registry.npmjs.org/ipaddr.js/-/ipaddr.js-1.9.1.tgz", - "integrity": "sha512-0KI/607xoxSToH7GjN1FfSbLoU0+btTicjsQSWQlh/hZykN8KpmMf7uYwPW3R+akZ6R/w18ZlXSHBYXiYUPO3g==", - "dev": true, - "engines": { - "node": ">= 0.10" - } - }, - "node_modules/proxy-from-env": { - "version": "1.1.0", - "resolved": "https://registry.npmjs.org/proxy-from-env/-/proxy-from-env-1.1.0.tgz", - "integrity": "sha512-D+zkORCbA9f1tdWRK0RaCR3GPv50cMxcrz4X8k5LTSUD1Dkw47mKJEZQNunItRTkWwgtaUSo1RVFRIG9ZXiFYg==" - }, - "node_modules/public-encrypt": { - "version": "4.0.3", - "resolved": "https://registry.npmjs.org/public-encrypt/-/public-encrypt-4.0.3.tgz", - "integrity": "sha512-zVpa8oKZSz5bTMTFClc1fQOnyyEzpl5ozpi1B5YcvBrdohMjH2rfsBtyXcuNuwjsDIXmBYlF2N5FlJYhR29t8Q==", - "dependencies": { - "bn.js": "^4.1.0", - "browserify-rsa": "^4.0.0", - "create-hash": "^1.1.0", - "parse-asn1": "^5.0.0", - "randombytes": "^2.0.1", - "safe-buffer": "^5.1.2" - } - }, - "node_modules/public-encrypt/node_modules/bn.js": { - "version": "4.12.0", - "resolved": "https://registry.npmjs.org/bn.js/-/bn.js-4.12.0.tgz", - "integrity": "sha512-c98Bf3tPniI+scsdk237ku1Dc3ujXQTSgyiPUDEOe7tRkhrqridvh8klBv0HCEso1OLOYcHuCv/cS6DNxKH+ZA==" - }, - "node_modules/pump": { - "version": "3.0.0", - "resolved": "https://registry.npmjs.org/pump/-/pump-3.0.0.tgz", - "integrity": "sha512-LwZy+p3SFs1Pytd/jYct4wpv49HiYCqd9Rlc5ZVdk0V+8Yzv6jR5Blk3TRmPL1ft69TxP0IMZGJ+WPFU2BFhww==", - "dependencies": { - "end-of-stream": "^1.1.0", - "once": "^1.3.1" - } - }, - "node_modules/punycode": { - "version": "2.1.1", - "resolved": "https://registry.npmjs.org/punycode/-/punycode-2.1.1.tgz", - "integrity": "sha512-XRsRjdf+j5ml+y/6GKHPZbrF/8p2Yga0JPtdqTIY2Xe5ohJPD9saDJJLPvp9+NSBprVvevdXZybnj2cv8OEd0A==", - "engines": { - "node": ">=6" - } - }, - "node_modules/puppeteer-core": { - "version": "15.5.0", - "resolved": "https://registry.npmjs.org/puppeteer-core/-/puppeteer-core-15.5.0.tgz", - "integrity": "sha512-5Q8EmF++MARczJD1JcRehVePlctxGG2TFHSxdCV8NqPOk44/cMySmZw2nETn+lwUOyp0L9afosMFTnT4KgmWgw==", - "dependencies": { - "cross-fetch": "3.1.5", - "debug": "4.3.4", - "devtools-protocol": "0.0.1019158", - "extract-zip": "2.0.1", - "https-proxy-agent": "5.0.1", - "pkg-dir": "4.2.0", - "progress": "2.0.3", - "proxy-from-env": "1.1.0", - "rimraf": "3.0.2", - "tar-fs": "2.1.1", - "unbzip2-stream": "1.4.3", - "ws": "8.8.0" - }, - "engines": { - "node": ">=14.1.0" - } - }, - "node_modules/puppeteer-core/node_modules/debug": { - "version": "4.3.4", - "resolved": "https://registry.npmjs.org/debug/-/debug-4.3.4.tgz", - "integrity": "sha512-PRWFHuSU3eDtQJPvnNY7Jcket1j0t5OuOsFzPPzsekD52Zl8qUfFIPEiswXqIvHWGVHOgX+7G/vCNNhehwxfkQ==", - "dependencies": { - "ms": "2.1.2" - }, - "engines": { - "node": ">=6.0" - }, - "peerDependenciesMeta": { - "supports-color": { - "optional": true - } - } - }, - "node_modules/puppeteer-core/node_modules/ms": { - "version": "2.1.2", - "resolved": "https://registry.npmjs.org/ms/-/ms-2.1.2.tgz", - "integrity": "sha512-sGkPx+VjMtmA6MX27oA4FBFELFCZZ4S4XqeGOXCv68tT+jb3vk/RyaKWP0PTKyWtmLSM0b+adUTEvbs1PEaH2w==" - }, - "node_modules/puppeteer-core/node_modules/ws": { - "version": "8.8.0", - "resolved": "https://registry.npmjs.org/ws/-/ws-8.8.0.tgz", - "integrity": "sha512-JDAgSYQ1ksuwqfChJusw1LSJ8BizJ2e/vVu5Lxjq3YvNJNlROv1ui4i+c/kUUrPheBvQl4c5UbERhTwKa6QBJQ==", - "engines": { - "node": ">=10.0.0" - }, - "peerDependencies": { - "bufferutil": "^4.0.1", - "utf-8-validate": "^5.0.2" - }, - "peerDependenciesMeta": { - "bufferutil": { - "optional": true - }, - "utf-8-validate": { - "optional": true - } - } - }, - "node_modules/qs": { - "version": "6.9.6", - "resolved": "https://registry.npmjs.org/qs/-/qs-6.9.6.tgz", - "integrity": "sha512-TIRk4aqYLNoJUbd+g2lEdz5kLWIuTMRagAXxl78Q0RiVjAOugHmeKNGdd3cwo/ktpf9aL9epCfFqWDEKysUlLQ==", - "dev": true, - "engines": { - "node": ">=0.6" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/querystring": { - "version": "0.2.0", - "resolved": "https://registry.npmjs.org/querystring/-/querystring-0.2.0.tgz", - "integrity": "sha1-sgmEkgO7Jd+CDadW50cAWHhSFiA=", - "deprecated": "The querystring API is considered Legacy. new code should use the URLSearchParams API instead.", - "engines": { - "node": ">=0.4.x" - } - }, - "node_modules/querystring-es3": { - "version": "0.2.1", - "resolved": "https://registry.npmjs.org/querystring-es3/-/querystring-es3-0.2.1.tgz", - "integrity": "sha1-nsYfeQSYdXB9aUFFlv2Qek1xHnM=", - "engines": { - "node": ">=0.4.x" - } - }, - "node_modules/queue-microtask": { - "version": "1.2.3", - "resolved": "https://registry.npmjs.org/queue-microtask/-/queue-microtask-1.2.3.tgz", - "integrity": "sha512-NuaNSa6flKT5JaSYQzJok04JzTL1CA6aGhv5rfLW3PgqA+M2ChpZQnAC8h8i4ZFkBS8X5RqkDBHA7r4hej3K9A==", - "dev": true, - "funding": [ - { - "type": "github", - "url": "https://github.com/sponsors/feross" - }, - { - "type": "patreon", - "url": "https://www.patreon.com/feross" - }, - { - "type": "consulting", - "url": "https://feross.org/support" - } - ] - }, - "node_modules/randombytes": { - "version": "2.1.0", - "resolved": "https://registry.npmjs.org/randombytes/-/randombytes-2.1.0.tgz", - "integrity": "sha512-vYl3iOX+4CKUWuxGi9Ukhie6fsqXqS9FE2Zaic4tNFD2N2QQaXOMFbuKK4QmDHC0JO6B1Zp41J0LpT0oR68amQ==", - "dependencies": { - "safe-buffer": "^5.1.0" - } - }, - "node_modules/randomfill": { - "version": "1.0.4", - "resolved": "https://registry.npmjs.org/randomfill/-/randomfill-1.0.4.tgz", - "integrity": "sha512-87lcbR8+MhcWcUiQ+9e+Rwx8MyR2P7qnt15ynUlbm3TU/fjbgz4GsvfSUDTemtCCtVCqb4ZcEFlyPNTh9bBTLw==", - "dependencies": { - "randombytes": "^2.0.5", - "safe-buffer": "^5.1.0" - } - }, - "node_modules/range-parser": { - "version": "1.2.1", - "resolved": "https://registry.npmjs.org/range-parser/-/range-parser-1.2.1.tgz", - "integrity": "sha512-Hrgsx+orqoygnmhFbKaHE6c296J+HTAQXoxEF6gNupROmmGJRoyzfG3ccAveqCBrwr/2yxQ5BVd/GTl5agOwSg==", - "dev": true, - "engines": { - "node": ">= 0.6" - } - }, - "node_modules/raw-body": { - "version": "2.4.2", - "resolved": "https://registry.npmjs.org/raw-body/-/raw-body-2.4.2.tgz", - "integrity": "sha512-RPMAFUJP19WIet/99ngh6Iv8fzAbqum4Li7AD6DtGaW2RpMB/11xDoalPiJMTbu6I3hkbMVkATvZrqb9EEqeeQ==", - "dev": true, - "dependencies": { - "bytes": "3.1.1", - "http-errors": "1.8.1", - "iconv-lite": "0.4.24", - "unpipe": "1.0.0" - }, - "engines": { - "node": ">= 0.8" - } - }, - "node_modules/raw-body/node_modules/bytes": { - "version": "3.1.1", - "resolved": "https://registry.npmjs.org/bytes/-/bytes-3.1.1.tgz", - "integrity": "sha512-dWe4nWO/ruEOY7HkUJ5gFt1DCFV9zPRoJr8pV0/ASQermOZjtq8jMjOprC0Kd10GLN+l7xaUPvxzJFWtxGu8Fg==", - "dev": true, - "engines": { - "node": ">= 0.8" - } - }, - "node_modules/readable-stream": { - "version": "3.6.0", - "resolved": "https://registry.npmjs.org/readable-stream/-/readable-stream-3.6.0.tgz", - "integrity": "sha512-BViHy7LKeTz4oNnkcLJ+lVSL6vpiFeX6/d3oSH8zCW7UxP2onchk+vTGB143xuFjHS3deTgkKoXXymXqymiIdA==", - "dependencies": { - "inherits": "^2.0.3", - "string_decoder": "^1.1.1", - "util-deprecate": "^1.0.1" - }, - "engines": { - "node": ">= 6" - } - }, - "node_modules/readdirp": { - "version": "3.6.0", - "resolved": "https://registry.npmjs.org/readdirp/-/readdirp-3.6.0.tgz", - "integrity": "sha512-hOS089on8RduqdbhvQ5Z37A0ESjsqz6qnRcffsMU3495FuTdqSm+7bhJ29JvIOsBDEEnan5DPu9t3To9VRlMzA==", - "dev": true, - "dependencies": { - "picomatch": "^2.2.1" - }, - "engines": { - "node": ">=8.10.0" - } - }, - "node_modules/rechoir": { - "version": "0.7.1", - "resolved": "https://registry.npmjs.org/rechoir/-/rechoir-0.7.1.tgz", - "integrity": "sha512-/njmZ8s1wVeR6pjTZ+0nCnv8SpZNRMT2D1RLOJQESlYFDBvwpTA4KWJpZ+sBJ4+vhjILRcK7JIFdGCdxEAAitg==", - "dev": true, - "dependencies": { - "resolve": "^1.9.0" - }, - "engines": { - "node": ">= 0.10" - } - }, - "node_modules/reconnecting-websocket": { - "version": "4.4.0", - "resolved": "https://registry.npmjs.org/reconnecting-websocket/-/reconnecting-websocket-4.4.0.tgz", - "integrity": "sha512-D2E33ceRPga0NvTDhJmphEgJ7FUYF0v4lr1ki0csq06OdlxKfugGzN0dSkxM/NfqCxYELK4KcaTOUOjTV6Dcng==" - }, - "node_modules/regexp.prototype.flags": { - "version": "1.4.1", - "resolved": "https://registry.npmjs.org/regexp.prototype.flags/-/regexp.prototype.flags-1.4.1.tgz", - "integrity": "sha512-pMR7hBVUUGI7PMA37m2ofIdQCsomVnas+Jn5UPGAHQ+/LlwKm/aTLJHdasmHRzlfeZwHiAOaRSo2rbBDm3nNUQ==", - "dev": true, - "dependencies": { - "call-bind": "^1.0.2", - "define-properties": "^1.1.3" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/relateurl": { - "version": "0.2.7", - "resolved": "https://registry.npmjs.org/relateurl/-/relateurl-0.2.7.tgz", - "integrity": "sha1-VNvzd+UUQKypCkzSdGANP/LYiKk=", - "dev": true, - "engines": { - "node": ">= 0.10" - } - }, - "node_modules/renderkid": { - "version": "3.0.0", - "resolved": "https://registry.npmjs.org/renderkid/-/renderkid-3.0.0.tgz", - "integrity": "sha512-q/7VIQA8lmM1hF+jn+sFSPWGlMkSAeNYcPLmDQx2zzuiDfaLrOmumR8iaUKlenFgh0XRPIUeSPlH3A+AW3Z5pg==", - "dev": true, - "dependencies": { - "css-select": "^4.1.3", - "dom-converter": "^0.2.0", - "htmlparser2": "^6.1.0", - "lodash": "^4.17.21", - "strip-ansi": "^6.0.1" - } - }, - "node_modules/require-from-string": { - "version": "2.0.2", - "resolved": "https://registry.npmjs.org/require-from-string/-/require-from-string-2.0.2.tgz", - "integrity": "sha512-Xf0nWe6RseziFMu+Ap9biiUbmplq6S9/p+7w7YXP/JBHhrUDDUhwa+vANyubuqfZWTveU//DYVGsDG7RKL/vEw==", - "dev": true, - "engines": { - "node": ">=0.10.0" - } - }, - "node_modules/requires-port": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/requires-port/-/requires-port-1.0.0.tgz", - "integrity": "sha1-kl0mAdOaxIXgkc8NpcbmlNw9yv8=", - "dev": true - }, - "node_modules/resolve": { - "version": "1.22.1", - "resolved": "https://registry.npmjs.org/resolve/-/resolve-1.22.1.tgz", - "integrity": "sha512-nBpuuYuY5jFsli/JIs1oldw6fOQCBioohqWZg/2hiaOybXOft4lonv85uDOKXdf8rhyK159cxU5cDcK/NKk8zw==", - "dev": true, - "dependencies": { - "is-core-module": "^2.9.0", - "path-parse": "^1.0.7", - "supports-preserve-symlinks-flag": "^1.0.0" - }, - "bin": { - "resolve": "bin/resolve" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/resolve-cwd": { - "version": "3.0.0", - "resolved": "https://registry.npmjs.org/resolve-cwd/-/resolve-cwd-3.0.0.tgz", - "integrity": "sha512-OrZaX2Mb+rJCpH/6CpSqt9xFVpN++x01XnN2ie9g6P5/3xelLAkXWVADpdz1IHD/KFfEXyE6V0U01OQ3UO2rEg==", - "dev": true, - "dependencies": { - "resolve-from": "^5.0.0" - }, - "engines": { - "node": ">=8" - } - }, - "node_modules/resolve-from": { - "version": "5.0.0", - "resolved": "https://registry.npmjs.org/resolve-from/-/resolve-from-5.0.0.tgz", - "integrity": "sha512-qYg9KP24dD5qka9J47d0aVky0N+b4fTU89LN9iDnjB5waksiC49rvMB0PrUJQGoTmH50XPiqOvAjDfaijGxYZw==", - "dev": true, - "engines": { - "node": ">=8" - } - }, - "node_modules/reusify": { - "version": "1.0.4", - "resolved": "https://registry.npmjs.org/reusify/-/reusify-1.0.4.tgz", - "integrity": "sha512-U9nH88a3fc/ekCF1l0/UP1IosiuIjyTh7hBvXVMHYgVcfGvt897Xguj2UOLDeI5BG2m7/uwyaLVT6fbtCwTyzw==", - "dev": true, - "engines": { - "iojs": ">=1.0.0", - "node": ">=0.10.0" - } - }, - "node_modules/rimraf": { - "version": "3.0.2", - "resolved": "https://registry.npmjs.org/rimraf/-/rimraf-3.0.2.tgz", - "integrity": "sha512-JZkJMZkAGFFPP2YqXZXPbMlMBgsxzE8ILs4lMIX/2o0L9UBw9O/Y3o6wFw/i9YLapcUJWwqbi3kdxIPdC62TIA==", - "dependencies": { - "glob": "^7.1.3" - }, - "bin": { - "rimraf": "bin.js" - }, - "funding": { - "url": "https://github.com/sponsors/isaacs" - } - }, - "node_modules/rimraf/node_modules/glob": { - "version": "7.2.0", - "resolved": "https://registry.npmjs.org/glob/-/glob-7.2.0.tgz", - "integrity": "sha512-lmLf6gtyrPq8tTjSmrO94wBeQbFR3HbLHbuyD69wuyQkImp2hWqMGB47OX65FBkPffO641IP9jWa1z4ivqG26Q==", - "dependencies": { - "fs.realpath": "^1.0.0", - "inflight": "^1.0.4", - "inherits": "2", - "minimatch": "^3.0.4", - "once": "^1.3.0", - "path-is-absolute": "^1.0.0" - }, - "engines": { - "node": "*" - }, - "funding": { - "url": "https://github.com/sponsors/isaacs" - } - }, - "node_modules/ripemd160": { - "version": "2.0.2", - "resolved": "https://registry.npmjs.org/ripemd160/-/ripemd160-2.0.2.tgz", - "integrity": "sha512-ii4iagi25WusVoiC4B4lq7pbXfAp3D9v5CwfkY33vffw2+pkDjY1D8GaN7spsxvCSx8dkPqOZCEZyfxcmJG2IA==", - "dependencies": { - "hash-base": "^3.0.0", - "inherits": "^2.0.1" - } - }, - "node_modules/run-parallel": { - "version": "1.2.0", - "resolved": "https://registry.npmjs.org/run-parallel/-/run-parallel-1.2.0.tgz", - "integrity": "sha512-5l4VyZR86LZ/lDxZTR6jqL8AFE2S0IFLMP26AbjsLVADxHdhB/c0GUsH+y39UfCi3dzz8OlQuPmnaJOMoDHQBA==", - "dev": true, - "funding": [ - { - "type": "github", - "url": "https://github.com/sponsors/feross" - }, - { - "type": "patreon", - "url": "https://www.patreon.com/feross" - }, - { - "type": "consulting", - "url": "https://feross.org/support" - } - ], - "dependencies": { - "queue-microtask": "^1.2.2" - } - }, - "node_modules/safe-buffer": { - "version": "5.2.1", - "resolved": "https://registry.npmjs.org/safe-buffer/-/safe-buffer-5.2.1.tgz", - "integrity": "sha512-rp3So07KcdmmKbGvgaNxQSJr7bGVSVk5S9Eq1F+ppbRo70+YeaDxkw5Dd8NPN+GD6bjnYm2VuPuCXmpuYvmCXQ==", - "funding": [ - { - "type": "github", - "url": "https://github.com/sponsors/feross" - }, - { - "type": "patreon", - "url": "https://www.patreon.com/feross" - }, - { - "type": "consulting", - "url": "https://feross.org/support" - } - ] - }, - "node_modules/safer-buffer": { - "version": "2.1.2", - "resolved": "https://registry.npmjs.org/safer-buffer/-/safer-buffer-2.1.2.tgz", - "integrity": "sha512-YZo3K82SD7Riyi0E1EQPojLz7kpepnSQI9IyPbHHg1XXXevb5dJI7tpyN2ADxGcQbHG7vcyRHk0cbwqcQriUtg==" - }, - "node_modules/schema-utils": { - "version": "3.1.1", - "resolved": "https://registry.npmjs.org/schema-utils/-/schema-utils-3.1.1.tgz", - "integrity": "sha512-Y5PQxS4ITlC+EahLuXaY86TXfR7Dc5lw294alXOq86JAHCihAIZfqv8nNCWvaEJvaC51uN9hbLGeV0cFBdH+Fw==", - "dependencies": { - "@types/json-schema": "^7.0.8", - "ajv": "^6.12.5", - "ajv-keywords": "^3.5.2" - }, - "engines": { - "node": ">= 10.13.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/webpack" - } - }, - "node_modules/select-hose": { - "version": "2.0.0", - "resolved": "https://registry.npmjs.org/select-hose/-/select-hose-2.0.0.tgz", - "integrity": "sha1-Yl2GWPhlr0Psliv8N2o3NZpJlMo=", - "dev": true - }, - "node_modules/selfsigned": { - "version": "2.0.0", - "resolved": "https://registry.npmjs.org/selfsigned/-/selfsigned-2.0.0.tgz", - "integrity": "sha512-cUdFiCbKoa1mZ6osuJs2uDHrs0k0oprsKveFiiaBKCNq3SYyb5gs2HxhQyDNLCmL51ZZThqi4YNDpCK6GOP1iQ==", - "dev": true, - "dependencies": { - "node-forge": "^1.2.0" - }, - "engines": { - "node": ">=10" - } - }, - "node_modules/send": { - "version": "0.17.2", - "resolved": "https://registry.npmjs.org/send/-/send-0.17.2.tgz", - "integrity": "sha512-UJYB6wFSJE3G00nEivR5rgWp8c2xXvJ3OPWPhmuteU0IKj8nKbG3DrjiOmLwpnHGYWAVwA69zmTm++YG0Hmwww==", - "dev": true, - "dependencies": { - "debug": "2.6.9", - "depd": "~1.1.2", - "destroy": "~1.0.4", - "encodeurl": "~1.0.2", - "escape-html": "~1.0.3", - "etag": "~1.8.1", - "fresh": "0.5.2", - "http-errors": "1.8.1", - "mime": "1.6.0", - "ms": "2.1.3", - "on-finished": "~2.3.0", - "range-parser": "~1.2.1", - "statuses": "~1.5.0" - }, - "engines": { - "node": ">= 0.8.0" - } - }, - "node_modules/send/node_modules/ms": { - "version": "2.1.3", - "resolved": "https://registry.npmjs.org/ms/-/ms-2.1.3.tgz", - "integrity": "sha512-6FlzubTLZG3J2a/NVCAleEhjzq5oxgHyaCU9yYXvcLsvoVaHJq/s5xXI6/XXP6tz7R9xAOtHnSO/tXtF3WRTlA==", - "dev": true - }, - "node_modules/serialize-javascript": { - "version": "6.0.0", - "resolved": "https://registry.npmjs.org/serialize-javascript/-/serialize-javascript-6.0.0.tgz", - "integrity": "sha512-Qr3TosvguFt8ePWqsvRfrKyQXIiW+nGbYpy8XK24NQHE83caxWt+mIymTT19DGFbNWNLfEwsrkSmN64lVWB9ag==", - "dependencies": { - "randombytes": "^2.1.0" - } - }, - "node_modules/serve-index": { - "version": "1.9.1", - "resolved": "https://registry.npmjs.org/serve-index/-/serve-index-1.9.1.tgz", - "integrity": "sha1-03aNabHn2C5c4FD/9bRTvqEqkjk=", - "dev": true, - "dependencies": { - "accepts": "~1.3.4", - "batch": "0.6.1", - "debug": "2.6.9", - "escape-html": "~1.0.3", - "http-errors": "~1.6.2", - "mime-types": "~2.1.17", - "parseurl": "~1.3.2" - }, - "engines": { - "node": ">= 0.8.0" - } - }, - "node_modules/serve-index/node_modules/http-errors": { - "version": "1.6.3", - "resolved": "https://registry.npmjs.org/http-errors/-/http-errors-1.6.3.tgz", - "integrity": "sha1-i1VoC7S+KDoLW/TqLjhYC+HZMg0=", - "dev": true, - "dependencies": { - "depd": "~1.1.2", - "inherits": "2.0.3", - "setprototypeof": "1.1.0", - "statuses": ">= 1.4.0 < 2" - }, - "engines": { - "node": ">= 0.6" - } - }, - "node_modules/serve-index/node_modules/inherits": { - "version": "2.0.3", - "resolved": "https://registry.npmjs.org/inherits/-/inherits-2.0.3.tgz", - "integrity": "sha1-Yzwsg+PaQqUC9SRmAiSA9CCCYd4=", - "dev": true - }, - "node_modules/serve-index/node_modules/setprototypeof": { - "version": "1.1.0", - "resolved": "https://registry.npmjs.org/setprototypeof/-/setprototypeof-1.1.0.tgz", - "integrity": "sha512-BvE/TwpZX4FXExxOxZyRGQQv651MSwmWKZGqvmPcRIjDqWub67kTKuIMx43cZZrS/cBBzwBcNDWoFxt2XEFIpQ==", - "dev": true - }, - "node_modules/serve-static": { - "version": "1.14.2", - "resolved": "https://registry.npmjs.org/serve-static/-/serve-static-1.14.2.tgz", - "integrity": "sha512-+TMNA9AFxUEGuC0z2mevogSnn9MXKb4fa7ngeRMJaaGv8vTwnIEkKi+QGvPt33HSnf8pRS+WGM0EbMtCJLKMBQ==", - "dev": true, - "dependencies": { - "encodeurl": "~1.0.2", - "escape-html": "~1.0.3", - "parseurl": "~1.3.3", - "send": "0.17.2" - }, - "engines": { - "node": ">= 0.8.0" - } - }, - "node_modules/setimmediate": { - "version": "1.0.5", - "resolved": "https://registry.npmjs.org/setimmediate/-/setimmediate-1.0.5.tgz", - "integrity": "sha1-KQy7Iy4waULX1+qbg3Mqt4VvgoU=" - }, - "node_modules/setprototypeof": { - "version": "1.2.0", - "resolved": "https://registry.npmjs.org/setprototypeof/-/setprototypeof-1.2.0.tgz", - "integrity": "sha512-E5LDX7Wrp85Kil5bhZv46j8jOeboKq5JMmYM3gVGdGH8xFpPWXUMsNrlODCrkoxMEeNi/XZIwuRvY4XNwYMJpw==", - "dev": true - }, - "node_modules/sha.js": { - "version": "2.4.11", - "resolved": "https://registry.npmjs.org/sha.js/-/sha.js-2.4.11.tgz", - "integrity": "sha512-QMEp5B7cftE7APOjk5Y6xgrbWu+WkLVQwk8JNjZ8nKRciZaByEW6MubieAiToS7+dwvrjGhH8jRXz3MVd0AYqQ==", - "dependencies": { - "inherits": "^2.0.1", - "safe-buffer": "^5.0.1" - }, - "bin": { - "sha.js": "bin.js" - } - }, - "node_modules/shallow-clone": { - "version": "3.0.1", - "resolved": "https://registry.npmjs.org/shallow-clone/-/shallow-clone-3.0.1.tgz", - "integrity": "sha512-/6KqX+GVUdqPuPPd2LxDDxzX6CAbjJehAAOKlNpqqUpAqPM6HeL8f+o3a+JsyGjn2lv0WY8UsTgUJjU9Ok55NA==", - "dev": true, - "dependencies": { - "kind-of": "^6.0.2" - }, - "engines": { - "node": ">=8" - } - }, - "node_modules/shebang-command": { - "version": "2.0.0", - "resolved": "https://registry.npmjs.org/shebang-command/-/shebang-command-2.0.0.tgz", - "integrity": "sha512-kHxr2zZpYtdmrN1qDjrrX/Z1rR1kG8Dx+gkpK1G4eXmvXswmcE1hTWBWYUzlraYw1/yZp6YuDY77YtvbN0dmDA==", - "dev": true, - "dependencies": { - "shebang-regex": "^3.0.0" - }, - "engines": { - "node": ">=8" - } - }, - "node_modules/shebang-regex": { - "version": "3.0.0", - "resolved": "https://registry.npmjs.org/shebang-regex/-/shebang-regex-3.0.0.tgz", - "integrity": "sha512-7++dFhtcx3353uBaq8DDR4NuxBetBzC7ZQOhmTQInHEd6bSrXdiEyzCvG07Z44UYdLShWUyXt5M/yhz8ekcb1A==", - "dev": true, - "engines": { - "node": ">=8" - } - }, - "node_modules/side-channel": { - "version": "1.0.4", - "resolved": "https://registry.npmjs.org/side-channel/-/side-channel-1.0.4.tgz", - "integrity": "sha512-q5XPytqFEIKHkGdiMIrY10mvLRvnQh42/+GoBlFW3b2LXLE2xxJpZFdm94we0BaoV3RwJyGqg5wS7epxTv0Zvw==", - "dependencies": { - "call-bind": "^1.0.0", - "get-intrinsic": "^1.0.2", - "object-inspect": "^1.9.0" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/signal-exit": { - "version": "3.0.6", - "resolved": "https://registry.npmjs.org/signal-exit/-/signal-exit-3.0.6.tgz", - "integrity": "sha512-sDl4qMFpijcGw22U5w63KmD3cZJfBuFlVNbVMKje2keoKML7X2UzWbc4XrmEbDwg0NXJc3yv4/ox7b+JWb57kQ==", - "dev": true - }, - "node_modules/slash": { - "version": "3.0.0", - "resolved": "https://registry.npmjs.org/slash/-/slash-3.0.0.tgz", - "integrity": "sha512-g9Q1haeby36OSStwb4ntCGGGaKsaVSjQ68fBxoQcutl5fS1vuY18H3wSt3jFyFtrkx+Kz0V1G85A4MyAdDMi2Q==", - "dev": true, - "engines": { - "node": ">=8" - } - }, - "node_modules/sockjs": { - "version": "0.3.24", - "resolved": "https://registry.npmjs.org/sockjs/-/sockjs-0.3.24.tgz", - "integrity": "sha512-GJgLTZ7vYb/JtPSSZ10hsOYIvEYsjbNU+zPdIHcUaWVNUEPivzxku31865sSSud0Da0W4lEeOPlmw93zLQchuQ==", - "dev": true, - "dependencies": { - "faye-websocket": "^0.11.3", - "uuid": "^8.3.2", - "websocket-driver": "^0.7.4" - } - }, - "node_modules/source-map": { - "version": "0.6.1", - "resolved": "https://registry.npmjs.org/source-map/-/source-map-0.6.1.tgz", - "integrity": "sha512-UjgapumWlbMhkBgzT7Ykc5YXUT46F0iKu8SGXq0bcwP5dz/h0Plj6enJqjz1Zbq2l5WaqYnrVbwWOWMyF3F47g==", - "engines": { - "node": ">=0.10.0" - } - }, - "node_modules/source-map-support": { - "version": "0.5.21", - "resolved": "https://registry.npmjs.org/source-map-support/-/source-map-support-0.5.21.tgz", - "integrity": "sha512-uBHU3L3czsIyYXKX88fdrGovxdSCoTGDRZ6SYXtSRxLZUzHg5P/66Ht6uoUlHu9EZod+inXhKo3qQgwXUT/y1w==", - "dependencies": { - "buffer-from": "^1.0.0", - "source-map": "^0.6.0" - } - }, - "node_modules/spdy": { - "version": "4.0.2", - "resolved": "https://registry.npmjs.org/spdy/-/spdy-4.0.2.tgz", - "integrity": "sha512-r46gZQZQV+Kl9oItvl1JZZqJKGr+oEkB08A6BzkiR7593/7IbtuncXHd2YoYeTsG4157ZssMu9KYvUHLcjcDoA==", - "dev": true, - "dependencies": { - "debug": "^4.1.0", - "handle-thing": "^2.0.0", - "http-deceiver": "^1.2.7", - "select-hose": "^2.0.0", - "spdy-transport": "^3.0.0" - }, - "engines": { - "node": ">=6.0.0" - } - }, - "node_modules/spdy-transport": { - "version": "3.0.0", - "resolved": "https://registry.npmjs.org/spdy-transport/-/spdy-transport-3.0.0.tgz", - "integrity": "sha512-hsLVFE5SjA6TCisWeJXFKniGGOpBgMLmerfO2aCyCU5s7nJ/rpAepqmFifv/GCbSbueEeAJJnmSQ2rKC/g8Fcw==", - "dev": true, - "dependencies": { - "debug": "^4.1.0", - "detect-node": "^2.0.4", - "hpack.js": "^2.1.6", - "obuf": "^1.1.2", - "readable-stream": "^3.0.6", - "wbuf": "^1.7.3" - } - }, - "node_modules/spdy-transport/node_modules/debug": { - "version": "4.3.3", - "resolved": "https://registry.npmjs.org/debug/-/debug-4.3.3.tgz", - "integrity": "sha512-/zxw5+vh1Tfv+4Qn7a5nsbcJKPaSvCDhojn6FEl9vupwK2VCSDtEiEtqr8DFtzYFOdz63LBkxec7DYuc2jon6Q==", - "dev": true, - "dependencies": { - "ms": "2.1.2" - }, - "engines": { - "node": ">=6.0" - }, - "peerDependenciesMeta": { - "supports-color": { - "optional": true - } - } - }, - "node_modules/spdy-transport/node_modules/ms": { - "version": "2.1.2", - "resolved": "https://registry.npmjs.org/ms/-/ms-2.1.2.tgz", - "integrity": "sha512-sGkPx+VjMtmA6MX27oA4FBFELFCZZ4S4XqeGOXCv68tT+jb3vk/RyaKWP0PTKyWtmLSM0b+adUTEvbs1PEaH2w==", - "dev": true - }, - "node_modules/spdy/node_modules/debug": { - "version": "4.3.3", - "resolved": "https://registry.npmjs.org/debug/-/debug-4.3.3.tgz", - "integrity": "sha512-/zxw5+vh1Tfv+4Qn7a5nsbcJKPaSvCDhojn6FEl9vupwK2VCSDtEiEtqr8DFtzYFOdz63LBkxec7DYuc2jon6Q==", - "dev": true, - "dependencies": { - "ms": "2.1.2" - }, - "engines": { - "node": ">=6.0" - }, - "peerDependenciesMeta": { - "supports-color": { - "optional": true - } - } - }, - "node_modules/spdy/node_modules/ms": { - "version": "2.1.2", - "resolved": "https://registry.npmjs.org/ms/-/ms-2.1.2.tgz", - "integrity": "sha512-sGkPx+VjMtmA6MX27oA4FBFELFCZZ4S4XqeGOXCv68tT+jb3vk/RyaKWP0PTKyWtmLSM0b+adUTEvbs1PEaH2w==", - "dev": true - }, - "node_modules/statuses": { - "version": "1.5.0", - "resolved": "https://registry.npmjs.org/statuses/-/statuses-1.5.0.tgz", - "integrity": "sha1-Fhx9rBd2Wf2YEfQ3cfqZOBR4Yow=", - "dev": true, - "engines": { - "node": ">= 0.6" - } - }, - "node_modules/stream-browserify": { - "version": "3.0.0", - "resolved": "https://registry.npmjs.org/stream-browserify/-/stream-browserify-3.0.0.tgz", - "integrity": "sha512-H73RAHsVBapbim0tU2JwwOiXUj+fikfiaoYAKHF3VJfA0pe2BCzkhAHBlLG6REzE+2WNZcxOXjK7lkso+9euLA==", - "dependencies": { - "inherits": "~2.0.4", - "readable-stream": "^3.5.0" - } - }, - "node_modules/stream-http": { - "version": "3.2.0", - "resolved": "https://registry.npmjs.org/stream-http/-/stream-http-3.2.0.tgz", - "integrity": "sha512-Oq1bLqisTyK3TSCXpPbT4sdeYNdmyZJv1LxpEm2vu1ZhK89kSE5YXwZc3cWk0MagGaKriBh9mCFbVGtO+vY29A==", - "dependencies": { - "builtin-status-codes": "^3.0.0", - "inherits": "^2.0.4", - "readable-stream": "^3.6.0", - "xtend": "^4.0.2" - } - }, - "node_modules/string_decoder": { - "version": "1.1.1", - "resolved": "https://registry.npmjs.org/string_decoder/-/string_decoder-1.1.1.tgz", - "integrity": "sha512-n/ShnvDi6FHbbVfviro+WojiFzv+s8MPMHBczVePfUpDJLwoLT0ht1l4YwBCbi8pJAveEEdnkHyPyTP/mzRfwg==", - "dependencies": { - "safe-buffer": "~5.1.0" - } - }, - "node_modules/string_decoder/node_modules/safe-buffer": { - "version": "5.1.2", - "resolved": "https://registry.npmjs.org/safe-buffer/-/safe-buffer-5.1.2.tgz", - "integrity": "sha512-Gd2UZBJDkXlY7GbJxfsE8/nvKkUEU1G38c1siN6QP6a9PT9MmHB8GnpscSmMJSoF8LOIrt8ud/wPtojys4G6+g==" - }, - "node_modules/string.prototype.trimend": { - "version": "1.0.4", - "resolved": "https://registry.npmjs.org/string.prototype.trimend/-/string.prototype.trimend-1.0.4.tgz", - "integrity": "sha512-y9xCjw1P23Awk8EvTpcyL2NIr1j7wJ39f+k6lvRnSMz+mz9CGz9NYPelDk42kOz6+ql8xjfK8oYzy3jAP5QU5A==", - "dependencies": { - "call-bind": "^1.0.2", - "define-properties": "^1.1.3" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/string.prototype.trimstart": { - "version": "1.0.4", - "resolved": "https://registry.npmjs.org/string.prototype.trimstart/-/string.prototype.trimstart-1.0.4.tgz", - "integrity": "sha512-jh6e984OBfvxS50tdY2nRZnoC5/mLFKOREQfw8t5yytkoUsJRNxvI/E39qu1sD0OtWI3OC0XgKSmcWwziwYuZw==", - "dependencies": { - "call-bind": "^1.0.2", - "define-properties": "^1.1.3" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/strip-ansi": { - "version": "6.0.1", - "resolved": "https://registry.npmjs.org/strip-ansi/-/strip-ansi-6.0.1.tgz", - "integrity": "sha512-Y38VPSHcqkFrCpFnQ9vuSXmquuv5oXOKpGeT6aGrr3o3Gc9AlVa6JBfUSOCnbxGGZF+/0ooI7KrPuUSztUdU5A==", - "dev": true, - "dependencies": { - "ansi-regex": "^5.0.1" - }, - "engines": { - "node": ">=8" - } - }, - "node_modules/strip-final-newline": { - "version": "2.0.0", - "resolved": "https://registry.npmjs.org/strip-final-newline/-/strip-final-newline-2.0.0.tgz", - "integrity": "sha512-BrpvfNAE3dcvq7ll3xVumzjKjZQ5tI1sEUIKr3Uoks0XUl45St3FlatVqef9prk4jRDzhW6WZg+3bk93y6pLjA==", - "dev": true, - "engines": { - "node": ">=6" - } - }, - "node_modules/supports-preserve-symlinks-flag": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/supports-preserve-symlinks-flag/-/supports-preserve-symlinks-flag-1.0.0.tgz", - "integrity": "sha512-ot0WnXS9fgdkgIcePe6RHNk1WA8+muPa6cSjeR3V8K27q9BB1rTE3R1p7Hv0z1ZyAc8s6Vvv8DIyWf681MAt0w==", - "dev": true, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/tapable": { - "version": "2.2.1", - "resolved": "https://registry.npmjs.org/tapable/-/tapable-2.2.1.tgz", - "integrity": "sha512-GNzQvQTOIP6RyTfE2Qxb8ZVlNmw0n88vp1szwWRimP02mnTsx3Wtn5qRdqY9w2XduFNUgvOwhNnQsjwCp+kqaQ==", - "engines": { - "node": ">=6" - } - }, - "node_modules/tar-fs": { - "version": "2.1.1", - "resolved": "https://registry.npmjs.org/tar-fs/-/tar-fs-2.1.1.tgz", - "integrity": "sha512-V0r2Y9scmbDRLCNex/+hYzvp/zyYjvFbHPNgVTKfQvVrb6guiE/fxP+XblDNR011utopbkex2nM4dHNV6GDsng==", - "dependencies": { - "chownr": "^1.1.1", - "mkdirp-classic": "^0.5.2", - "pump": "^3.0.0", - "tar-stream": "^2.1.4" - } - }, - "node_modules/tar-stream": { - "version": "2.2.0", - "resolved": "https://registry.npmjs.org/tar-stream/-/tar-stream-2.2.0.tgz", - "integrity": "sha512-ujeqbceABgwMZxEJnk2HDY2DlnUZ+9oEcb1KzTVfYHio0UE6dG71n60d8D2I4qNvleWrrXpmjpt7vZeF1LnMZQ==", - "dependencies": { - "bl": "^4.0.3", - "end-of-stream": "^1.4.1", - "fs-constants": "^1.0.0", - "inherits": "^2.0.3", - "readable-stream": "^3.1.1" - }, - "engines": { - "node": ">=6" - } - }, - "node_modules/terser": { - "version": "5.10.0", - "resolved": "https://registry.npmjs.org/terser/-/terser-5.10.0.tgz", - "integrity": "sha512-AMmF99DMfEDiRJfxfY5jj5wNH/bYO09cniSqhfoyxc8sFoYIgkJy86G04UoZU5VjlpnplVu0K6Tx6E9b5+DlHA==", - "dependencies": { - "commander": "^2.20.0", - "source-map": "~0.7.2", - "source-map-support": "~0.5.20" - }, - "bin": { - "terser": "bin/terser" - }, - "engines": { - "node": ">=10" - }, - "peerDependencies": { - "acorn": "^8.5.0" - }, - "peerDependenciesMeta": { - "acorn": { - "optional": true - } - } - }, - "node_modules/terser-webpack-plugin": { - "version": "5.3.1", - "resolved": "https://registry.npmjs.org/terser-webpack-plugin/-/terser-webpack-plugin-5.3.1.tgz", - "integrity": "sha512-GvlZdT6wPQKbDNW/GDQzZFg/j4vKU96yl2q6mcUkzKOgW4gwf1Z8cZToUCrz31XHlPWH8MVb1r2tFtdDtTGJ7g==", - "dependencies": { - "jest-worker": "^27.4.5", - "schema-utils": "^3.1.1", - "serialize-javascript": "^6.0.0", - "source-map": "^0.6.1", - "terser": "^5.7.2" - }, - "engines": { - "node": ">= 10.13.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/webpack" - }, - "peerDependencies": { - "webpack": "^5.1.0" - }, - "peerDependenciesMeta": { - "@swc/core": { - "optional": true - }, - "esbuild": { - "optional": true - }, - "uglify-js": { - "optional": true - } - } - }, - "node_modules/terser/node_modules/commander": { - "version": "2.20.3", - "resolved": "https://registry.npmjs.org/commander/-/commander-2.20.3.tgz", - "integrity": "sha512-GpVkmM8vF2vQUkj2LvZmD35JxeJOLCwJ9cUkugyk2nuhbv3+mJvpLYYt+0+USMxE+oj+ey/lJEnhZw75x/OMcQ==" - }, - "node_modules/terser/node_modules/source-map": { - "version": "0.7.3", - "resolved": "https://registry.npmjs.org/source-map/-/source-map-0.7.3.tgz", - "integrity": "sha512-CkCj6giN3S+n9qrYiBTX5gystlENnRW5jZeNLHpe6aue+SrHcG5VYwujhW9s4dY31mEGsxBDrHR6oI69fTXsaQ==", - "engines": { - "node": ">= 8" - } - }, - "node_modules/through": { - "version": "2.3.8", - "resolved": "https://registry.npmjs.org/through/-/through-2.3.8.tgz", - "integrity": "sha512-w89qg7PI8wAdvX60bMDP+bFoD5Dvhm9oLheFp5O4a2QF0cSBGsBX4qZmadPMvVqlLJBBci+WqGGOAPvcDeNSVg==" - }, - "node_modules/thunky": { - "version": "1.1.0", - "resolved": "https://registry.npmjs.org/thunky/-/thunky-1.1.0.tgz", - "integrity": "sha512-eHY7nBftgThBqOyHGVN+l8gF0BucP09fMo0oO/Lb0w1OF80dJv+lDVpXG60WMQvkcxAkNybKsrEIE3ZtKGmPrA==", - "dev": true - }, - "node_modules/timers-browserify": { - "version": "2.0.12", - "resolved": "https://registry.npmjs.org/timers-browserify/-/timers-browserify-2.0.12.tgz", - "integrity": "sha512-9phl76Cqm6FhSX9Xe1ZUAMLtm1BLkKj2Qd5ApyWkXzsMRaA7dgr81kf4wJmQf/hAvg8EEyJxDo3du/0KlhPiKQ==", - "dependencies": { - "setimmediate": "^1.0.4" - }, - "engines": { - "node": ">=0.6.0" - } - }, - "node_modules/to-regex-range": { - "version": "5.0.1", - "resolved": "https://registry.npmjs.org/to-regex-range/-/to-regex-range-5.0.1.tgz", - "integrity": "sha512-65P7iz6X5yEr1cwcgvQxbbIw7Uk3gOy5dIdtZ4rDveLqhrdJP+Li/Hx6tyK0NEb+2GCyneCMJiGqrADCSNk8sQ==", - "dev": true, - "dependencies": { - "is-number": "^7.0.0" - }, - "engines": { - "node": ">=8.0" - } - }, - "node_modules/toidentifier": { - "version": "1.0.1", - "resolved": "https://registry.npmjs.org/toidentifier/-/toidentifier-1.0.1.tgz", - "integrity": "sha512-o5sSPKEkg/DIQNmH43V0/uerLrpzVedkUh8tGNvaeXpfpuwjKenlSox/2O/BTlZUtEe+JG7s5YhEz608PlAHRA==", - "dev": true, - "engines": { - "node": ">=0.6" - } - }, - "node_modules/tr46": { - "version": "0.0.3", - "resolved": "https://registry.npmjs.org/tr46/-/tr46-0.0.3.tgz", - "integrity": "sha512-N3WMsuqV66lT30CrXNbEjx4GEwlow3v6rr4mCcv6prnfwhS01rkgyFdjPNBYd9br7LpXV1+Emh01fHnq2Gdgrw==" - }, - "node_modules/tslib": { - "version": "2.3.1", - "resolved": "https://registry.npmjs.org/tslib/-/tslib-2.3.1.tgz", - "integrity": "sha512-77EbyPPpMz+FRFRuAFlWMtmgUWGe9UOG2Z25NqCwiIjRhOf5iKGuzSe5P2w1laq+FkRy4p+PCuVkJSGkzTEKVw==", - "dev": true - }, - "node_modules/tty-browserify": { - "version": "0.0.1", - "resolved": "https://registry.npmjs.org/tty-browserify/-/tty-browserify-0.0.1.tgz", - "integrity": "sha512-C3TaO7K81YvjCgQH9Q1S3R3P3BtN3RIM8n+OvX4il1K1zgE8ZhI0op7kClgkxtutIE8hQrcrHBXvIheqKUUCxw==" - }, - "node_modules/type-is": { - "version": "1.6.18", - "resolved": "https://registry.npmjs.org/type-is/-/type-is-1.6.18.tgz", - "integrity": "sha512-TkRKr9sUTxEH8MdfuCSP7VizJyzRNMjj2J2do2Jr3Kym598JVdEksuzPQCnlFPW4ky9Q+iA+ma9BGm06XQBy8g==", - "dev": true, - "dependencies": { - "media-typer": "0.3.0", - "mime-types": "~2.1.24" - }, - "engines": { - "node": ">= 0.6" - } - }, - "node_modules/unbox-primitive": { - "version": "1.0.1", - "resolved": "https://registry.npmjs.org/unbox-primitive/-/unbox-primitive-1.0.1.tgz", - "integrity": "sha512-tZU/3NqK3dA5gpE1KtyiJUrEB0lxnGkMFHptJ7q6ewdZ8s12QrODwNbhIJStmJkd1QDXa1NRA8aF2A1zk/Ypyw==", - "dependencies": { - "function-bind": "^1.1.1", - "has-bigints": "^1.0.1", - "has-symbols": "^1.0.2", - "which-boxed-primitive": "^1.0.2" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/unbzip2-stream": { - "version": "1.4.3", - "resolved": "https://registry.npmjs.org/unbzip2-stream/-/unbzip2-stream-1.4.3.tgz", - "integrity": "sha512-mlExGW4w71ebDJviH16lQLtZS32VKqsSfk80GCfUlwT/4/hNRFsoscrF/c++9xinkMzECL1uL9DDwXqFWkruPg==", - "dependencies": { - "buffer": "^5.2.1", - "through": "^2.3.8" - } - }, - "node_modules/unbzip2-stream/node_modules/buffer": { - "version": "5.7.1", - "resolved": "https://registry.npmjs.org/buffer/-/buffer-5.7.1.tgz", - "integrity": "sha512-EHcyIPBQ4BSGlvjB16k5KgAJ27CIsHY/2JBmCRReo48y9rQ3MaUzWX3KVlBa4U7MyX02HdVj0K7C3WaB3ju7FQ==", - "funding": [ - { - "type": "github", - "url": "https://github.com/sponsors/feross" - }, - { - "type": "patreon", - "url": "https://www.patreon.com/feross" - }, - { - "type": "consulting", - "url": "https://feross.org/support" - } - ], - "dependencies": { - "base64-js": "^1.3.1", - "ieee754": "^1.1.13" - } - }, - "node_modules/uniqid": { - "version": "5.4.0", - "resolved": "https://registry.npmjs.org/uniqid/-/uniqid-5.4.0.tgz", - "integrity": "sha512-38JRbJ4Fj94VmnC7G/J/5n5SC7Ab46OM5iNtSstB/ko3l1b5g7ALt4qzHFgGciFkyiRNtDXtLNb+VsxtMSE77A==" - }, - "node_modules/unpipe": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/unpipe/-/unpipe-1.0.0.tgz", - "integrity": "sha1-sr9O6FFKrmFltIF4KdIbLvSZBOw=", - "dev": true, - "engines": { - "node": ">= 0.8" - } - }, - "node_modules/uri-js": { - "version": "4.4.1", - "resolved": "https://registry.npmjs.org/uri-js/-/uri-js-4.4.1.tgz", - "integrity": "sha512-7rKUyy33Q1yc98pQ1DAmLtwX109F7TIfWlW1Ydo8Wl1ii1SeHieeh0HHfPeL2fMXK6z0s8ecKs9frCuLJvndBg==", - "dependencies": { - "punycode": "^2.1.0" - } - }, - "node_modules/url": { - "version": "0.11.0", - "resolved": "https://registry.npmjs.org/url/-/url-0.11.0.tgz", - "integrity": "sha1-ODjpfPxgUh63PFJajlW/3Z4uKPE=", - "dependencies": { - "punycode": "1.3.2", - "querystring": "0.2.0" - } - }, - "node_modules/url/node_modules/punycode": { - "version": "1.3.2", - "resolved": "https://registry.npmjs.org/punycode/-/punycode-1.3.2.tgz", - "integrity": "sha1-llOgNvt8HuQjQvIyXM7v6jkmxI0=" - }, - "node_modules/util": { - "version": "0.12.4", - "resolved": "https://registry.npmjs.org/util/-/util-0.12.4.tgz", - "integrity": "sha512-bxZ9qtSlGUWSOy9Qa9Xgk11kSslpuZwaxCg4sNIDj6FLucDab2JxnHwyNTCpHMtK1MjoQiWQ6DiUMZYbSrO+Sw==", - "dependencies": { - "inherits": "^2.0.3", - "is-arguments": "^1.0.4", - "is-generator-function": "^1.0.7", - "is-typed-array": "^1.1.3", - "safe-buffer": "^5.1.2", - "which-typed-array": "^1.1.2" - } - }, - "node_modules/util-deprecate": { - "version": "1.0.2", - "resolved": "https://registry.npmjs.org/util-deprecate/-/util-deprecate-1.0.2.tgz", - "integrity": "sha1-RQ1Nyfpw3nMnYvvS1KKJgUGaDM8=" - }, - "node_modules/utila": { - "version": "0.4.0", - "resolved": "https://registry.npmjs.org/utila/-/utila-0.4.0.tgz", - "integrity": "sha1-ihagXURWV6Oupe7MWxKk+lN5dyw=", - "dev": true - }, - "node_modules/utils-merge": { - "version": "1.0.1", - "resolved": "https://registry.npmjs.org/utils-merge/-/utils-merge-1.0.1.tgz", - "integrity": "sha1-n5VxD1CiZ5R7LMwSR0HBAoQn5xM=", - "dev": true, - "engines": { - "node": ">= 0.4.0" - } - }, - "node_modules/uuid": { - "version": "8.3.2", - "resolved": "https://registry.npmjs.org/uuid/-/uuid-8.3.2.tgz", - "integrity": "sha512-+NYs2QeMWy+GWFOEm9xnn6HCDp0l7QBD7ml8zLUmJ+93Q5NF0NocErnwkTkXVFNiX3/fpC6afS8Dhb/gz7R7eg==", - "dev": true, - "bin": { - "uuid": "dist/bin/uuid" - } - }, - "node_modules/vary": { - "version": "1.1.2", - "resolved": "https://registry.npmjs.org/vary/-/vary-1.1.2.tgz", - "integrity": "sha1-IpnwLG3tMNSllhsLn3RSShj2NPw=", - "dev": true, - "engines": { - "node": ">= 0.8" - } - }, - "node_modules/vm-browserify": { - "version": "1.1.2", - "resolved": "https://registry.npmjs.org/vm-browserify/-/vm-browserify-1.1.2.tgz", - "integrity": "sha512-2ham8XPWTONajOR0ohOKOHXkm3+gaBmGut3SRuu75xLd/RRaY6vqgh8NBYYk7+RW3u5AtzPQZG8F10LHkl0lAQ==" - }, - "node_modules/watchpack": { - "version": "2.3.1", - "resolved": "https://registry.npmjs.org/watchpack/-/watchpack-2.3.1.tgz", - "integrity": "sha512-x0t0JuydIo8qCNctdDrn1OzH/qDzk2+rdCOC3YzumZ42fiMqmQ7T3xQurykYMhYfHaPHTp4ZxAx2NfUo1K6QaA==", - "dependencies": { - "glob-to-regexp": "^0.4.1", - "graceful-fs": "^4.1.2" - }, - "engines": { - "node": ">=10.13.0" - } - }, - "node_modules/wbuf": { - "version": "1.7.3", - "resolved": "https://registry.npmjs.org/wbuf/-/wbuf-1.7.3.tgz", - "integrity": "sha512-O84QOnr0icsbFGLS0O3bI5FswxzRr8/gHwWkDlQFskhSPryQXvrTMxjxGP4+iWYoauLoBvfDpkrOauZ+0iZpDA==", - "dev": true, - "dependencies": { - "minimalistic-assert": "^1.0.0" - } - }, - "node_modules/webidl-conversions": { - "version": "3.0.1", - "resolved": "https://registry.npmjs.org/webidl-conversions/-/webidl-conversions-3.0.1.tgz", - "integrity": "sha512-2JAn3z8AR6rjK8Sm8orRC0h/bcl/DqL7tRPdGZ4I1CjdF+EaMLmYxBHyXuKL849eucPFhvBoxMsflfOb8kxaeQ==" - }, - "node_modules/webpack": { - "version": "5.67.0", - "resolved": "https://registry.npmjs.org/webpack/-/webpack-5.67.0.tgz", - "integrity": "sha512-LjFbfMh89xBDpUMgA1W9Ur6Rn/gnr2Cq1jjHFPo4v6a79/ypznSYbAyPgGhwsxBtMIaEmDD1oJoA7BEYw/Fbrw==", - "dependencies": { - "@types/eslint-scope": "^3.7.0", - "@types/estree": "^0.0.50", - "@webassemblyjs/ast": "1.11.1", - "@webassemblyjs/wasm-edit": "1.11.1", - "@webassemblyjs/wasm-parser": "1.11.1", - "acorn": "^8.4.1", - "acorn-import-assertions": "^1.7.6", - "browserslist": "^4.14.5", - "chrome-trace-event": "^1.0.2", - "enhanced-resolve": "^5.8.3", - "es-module-lexer": "^0.9.0", - "eslint-scope": "5.1.1", - "events": "^3.2.0", - "glob-to-regexp": "^0.4.1", - "graceful-fs": "^4.2.9", - "json-parse-better-errors": "^1.0.2", - "loader-runner": "^4.2.0", - "mime-types": "^2.1.27", - "neo-async": "^2.6.2", - "schema-utils": "^3.1.0", - "tapable": "^2.1.1", - "terser-webpack-plugin": "^5.1.3", - "watchpack": "^2.3.1", - "webpack-sources": "^3.2.3" - }, - "bin": { - "webpack": "bin/webpack.js" - }, - "engines": { - "node": ">=10.13.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/webpack" - }, - "peerDependenciesMeta": { - "webpack-cli": { - "optional": true - } - } - }, - "node_modules/webpack-cli": { - "version": "4.10.0", - "resolved": "https://registry.npmjs.org/webpack-cli/-/webpack-cli-4.10.0.tgz", - "integrity": "sha512-NLhDfH/h4O6UOy+0LSso42xvYypClINuMNBVVzX4vX98TmTaTUxwRbXdhucbFMd2qLaCTcLq/PdYrvi8onw90w==", - "dev": true, - "dependencies": { - "@discoveryjs/json-ext": "^0.5.0", - "@webpack-cli/configtest": "^1.2.0", - "@webpack-cli/info": "^1.5.0", - "@webpack-cli/serve": "^1.7.0", - "colorette": "^2.0.14", - "commander": "^7.0.0", - "cross-spawn": "^7.0.3", - "fastest-levenshtein": "^1.0.12", - "import-local": "^3.0.2", - "interpret": "^2.2.0", - "rechoir": "^0.7.0", - "webpack-merge": "^5.7.3" - }, - "bin": { - "webpack-cli": "bin/cli.js" - }, - "engines": { - "node": ">=10.13.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/webpack" - }, - "peerDependencies": { - "webpack": "4.x.x || 5.x.x" - }, - "peerDependenciesMeta": { - "@webpack-cli/generators": { - "optional": true - }, - "@webpack-cli/migrate": { - "optional": true - }, - "webpack-bundle-analyzer": { - "optional": true - }, - "webpack-dev-server": { - "optional": true - } - } - }, - "node_modules/webpack-cli/node_modules/commander": { - "version": "7.2.0", - "resolved": "https://registry.npmjs.org/commander/-/commander-7.2.0.tgz", - "integrity": "sha512-QrWXB+ZQSVPmIWIhtEO9H+gwHaMGYiF5ChvoJ+K9ZGHG/sVsa6yiesAD1GC/x46sET00Xlwo1u49RVVVzvcSkw==", - "dev": true, - "engines": { - "node": ">= 10" - } - }, - "node_modules/webpack-dev-middleware": { - "version": "5.3.1", - "resolved": "https://registry.npmjs.org/webpack-dev-middleware/-/webpack-dev-middleware-5.3.1.tgz", - "integrity": "sha512-81EujCKkyles2wphtdrnPg/QqegC/AtqNH//mQkBYSMqwFVCQrxM6ktB2O/SPlZy7LqeEfTbV3cZARGQz6umhg==", - "dev": true, - "dependencies": { - "colorette": "^2.0.10", - "memfs": "^3.4.1", - "mime-types": "^2.1.31", - "range-parser": "^1.2.1", - "schema-utils": "^4.0.0" - }, - "engines": { - "node": ">= 12.13.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/webpack" - }, - "peerDependencies": { - "webpack": "^4.0.0 || ^5.0.0" - } - }, - "node_modules/webpack-dev-middleware/node_modules/ajv": { - "version": "8.9.0", - "resolved": "https://registry.npmjs.org/ajv/-/ajv-8.9.0.tgz", - "integrity": "sha512-qOKJyNj/h+OWx7s5DePL6Zu1KeM9jPZhwBqs+7DzP6bGOvqzVCSf0xueYmVuaC/oQ/VtS2zLMLHdQFbkka+XDQ==", - "dev": true, - "dependencies": { - "fast-deep-equal": "^3.1.1", - "json-schema-traverse": "^1.0.0", - "require-from-string": "^2.0.2", - "uri-js": "^4.2.2" - }, - "funding": { - "type": "github", - "url": "https://github.com/sponsors/epoberezkin" - } - }, - "node_modules/webpack-dev-middleware/node_modules/ajv-keywords": { - "version": "5.1.0", - "resolved": "https://registry.npmjs.org/ajv-keywords/-/ajv-keywords-5.1.0.tgz", - "integrity": "sha512-YCS/JNFAUyr5vAuhk1DWm1CBxRHW9LbJ2ozWeemrIqpbsqKjHVxYPyi5GC0rjZIT5JxJ3virVTS8wk4i/Z+krw==", - "dev": true, - "dependencies": { - "fast-deep-equal": "^3.1.3" - }, - "peerDependencies": { - "ajv": "^8.8.2" - } - }, - "node_modules/webpack-dev-middleware/node_modules/json-schema-traverse": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/json-schema-traverse/-/json-schema-traverse-1.0.0.tgz", - "integrity": "sha512-NM8/P9n3XjXhIZn1lLhkFaACTOURQXjWhV4BA/RnOv8xvgqtqpAX9IO4mRQxSx1Rlo4tqzeqb0sOlruaOy3dug==", - "dev": true - }, - "node_modules/webpack-dev-middleware/node_modules/schema-utils": { - "version": "4.0.0", - "resolved": "https://registry.npmjs.org/schema-utils/-/schema-utils-4.0.0.tgz", - "integrity": "sha512-1edyXKgh6XnJsJSQ8mKWXnN/BVaIbFMLpouRUrXgVq7WYne5kw3MW7UPhO44uRXQSIpTSXoJbmrR2X0w9kUTyg==", - "dev": true, - "dependencies": { - "@types/json-schema": "^7.0.9", - "ajv": "^8.8.0", - "ajv-formats": "^2.1.1", - "ajv-keywords": "^5.0.0" - }, - "engines": { - "node": ">= 12.13.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/webpack" - } - }, - "node_modules/webpack-dev-server": { - "version": "4.7.4", - "resolved": "https://registry.npmjs.org/webpack-dev-server/-/webpack-dev-server-4.7.4.tgz", - "integrity": "sha512-nfdsb02Zi2qzkNmgtZjkrMOcXnYZ6FLKcQwpxT7MvmHKc+oTtDsBju8j+NMyAygZ9GW1jMEUpy3itHtqgEhe1A==", - "dev": true, - "dependencies": { - "@types/bonjour": "^3.5.9", - "@types/connect-history-api-fallback": "^1.3.5", - "@types/express": "^4.17.13", - "@types/serve-index": "^1.9.1", - "@types/sockjs": "^0.3.33", - "@types/ws": "^8.2.2", - "ansi-html-community": "^0.0.8", - "bonjour": "^3.5.0", - "chokidar": "^3.5.3", - "colorette": "^2.0.10", - "compression": "^1.7.4", - "connect-history-api-fallback": "^1.6.0", - "default-gateway": "^6.0.3", - "del": "^6.0.0", - "express": "^4.17.1", - "graceful-fs": "^4.2.6", - "html-entities": "^2.3.2", - "http-proxy-middleware": "^2.0.0", - "ipaddr.js": "^2.0.1", - "open": "^8.0.9", - "p-retry": "^4.5.0", - "portfinder": "^1.0.28", - "schema-utils": "^4.0.0", - "selfsigned": "^2.0.0", - "serve-index": "^1.9.1", - "sockjs": "^0.3.21", - "spdy": "^4.0.2", - "strip-ansi": "^7.0.0", - "webpack-dev-middleware": "^5.3.1", - "ws": "^8.4.2" - }, - "bin": { - "webpack-dev-server": "bin/webpack-dev-server.js" - }, - "engines": { - "node": ">= 12.13.0" - }, - "peerDependencies": { - "webpack": "^4.37.0 || ^5.0.0" - }, - "peerDependenciesMeta": { - "webpack-cli": { - "optional": true - } - } - }, - "node_modules/webpack-dev-server/node_modules/ajv": { - "version": "8.9.0", - "resolved": "https://registry.npmjs.org/ajv/-/ajv-8.9.0.tgz", - "integrity": "sha512-qOKJyNj/h+OWx7s5DePL6Zu1KeM9jPZhwBqs+7DzP6bGOvqzVCSf0xueYmVuaC/oQ/VtS2zLMLHdQFbkka+XDQ==", - "dev": true, - "dependencies": { - "fast-deep-equal": "^3.1.1", - "json-schema-traverse": "^1.0.0", - "require-from-string": "^2.0.2", - "uri-js": "^4.2.2" - }, - "funding": { - "type": "github", - "url": "https://github.com/sponsors/epoberezkin" - } - }, - "node_modules/webpack-dev-server/node_modules/ajv-keywords": { - "version": "5.1.0", - "resolved": "https://registry.npmjs.org/ajv-keywords/-/ajv-keywords-5.1.0.tgz", - "integrity": "sha512-YCS/JNFAUyr5vAuhk1DWm1CBxRHW9LbJ2ozWeemrIqpbsqKjHVxYPyi5GC0rjZIT5JxJ3virVTS8wk4i/Z+krw==", - "dev": true, - "dependencies": { - "fast-deep-equal": "^3.1.3" - }, - "peerDependencies": { - "ajv": "^8.8.2" - } - }, - "node_modules/webpack-dev-server/node_modules/ansi-regex": { - "version": "6.0.1", - "resolved": "https://registry.npmjs.org/ansi-regex/-/ansi-regex-6.0.1.tgz", - "integrity": "sha512-n5M855fKb2SsfMIiFFoVrABHJC8QtHwVx+mHWP3QcEqBHYienj5dHSgjbxtC0WEZXYt4wcD6zrQElDPhFuZgfA==", - "dev": true, - "engines": { - "node": ">=12" - }, - "funding": { - "url": "https://github.com/chalk/ansi-regex?sponsor=1" - } - }, - "node_modules/webpack-dev-server/node_modules/json-schema-traverse": { - "version": "1.0.0", - "resolved": "https://registry.npmjs.org/json-schema-traverse/-/json-schema-traverse-1.0.0.tgz", - "integrity": "sha512-NM8/P9n3XjXhIZn1lLhkFaACTOURQXjWhV4BA/RnOv8xvgqtqpAX9IO4mRQxSx1Rlo4tqzeqb0sOlruaOy3dug==", - "dev": true - }, - "node_modules/webpack-dev-server/node_modules/schema-utils": { - "version": "4.0.0", - "resolved": "https://registry.npmjs.org/schema-utils/-/schema-utils-4.0.0.tgz", - "integrity": "sha512-1edyXKgh6XnJsJSQ8mKWXnN/BVaIbFMLpouRUrXgVq7WYne5kw3MW7UPhO44uRXQSIpTSXoJbmrR2X0w9kUTyg==", - "dev": true, - "dependencies": { - "@types/json-schema": "^7.0.9", - "ajv": "^8.8.0", - "ajv-formats": "^2.1.1", - "ajv-keywords": "^5.0.0" - }, - "engines": { - "node": ">= 12.13.0" - }, - "funding": { - "type": "opencollective", - "url": "https://opencollective.com/webpack" - } - }, - "node_modules/webpack-dev-server/node_modules/strip-ansi": { - "version": "7.0.1", - "resolved": "https://registry.npmjs.org/strip-ansi/-/strip-ansi-7.0.1.tgz", - "integrity": "sha512-cXNxvT8dFNRVfhVME3JAe98mkXDYN2O1l7jmcwMnOslDeESg1rF/OZMtK0nRAhiari1unG5cD4jG3rapUAkLbw==", - "dev": true, - "dependencies": { - "ansi-regex": "^6.0.1" - }, - "engines": { - "node": ">=12" - }, - "funding": { - "url": "https://github.com/chalk/strip-ansi?sponsor=1" - } - }, - "node_modules/webpack-dev-server/node_modules/ws": { - "version": "8.4.2", - "resolved": "https://registry.npmjs.org/ws/-/ws-8.4.2.tgz", - "integrity": "sha512-Kbk4Nxyq7/ZWqr/tarI9yIt/+iNNFOjBXEWgTb4ydaNHBNGgvf2QHbS9fdfsndfjFlFwEd4Al+mw83YkaD10ZA==", - "dev": true, - "engines": { - "node": ">=10.0.0" - }, - "peerDependencies": { - "bufferutil": "^4.0.1", - "utf-8-validate": "^5.0.2" - }, - "peerDependenciesMeta": { - "bufferutil": { - "optional": true - }, - "utf-8-validate": { - "optional": true - } - } - }, - "node_modules/webpack-merge": { - "version": "5.8.0", - "resolved": "https://registry.npmjs.org/webpack-merge/-/webpack-merge-5.8.0.tgz", - "integrity": "sha512-/SaI7xY0831XwP6kzuwhKWVKDP9t1QY1h65lAFLbZqMPIuYcD9QAW4u9STIbU9kaJbPBB/geU/gLr1wDjOhQ+Q==", - "dev": true, - "dependencies": { - "clone-deep": "^4.0.1", - "wildcard": "^2.0.0" - }, - "engines": { - "node": ">=10.0.0" - } - }, - "node_modules/webpack-sources": { - "version": "3.2.3", - "resolved": "https://registry.npmjs.org/webpack-sources/-/webpack-sources-3.2.3.tgz", - "integrity": "sha512-/DyMEOrDgLKKIG0fmvtz+4dUX/3Ghozwgm6iPp8KRhvn+eQf9+Q7GWxVNMk3+uCPWfdXYC4ExGBckIXdFEfH1w==", - "engines": { - "node": ">=10.13.0" - } - }, - "node_modules/websocket-driver": { - "version": "0.7.4", - "resolved": "https://registry.npmjs.org/websocket-driver/-/websocket-driver-0.7.4.tgz", - "integrity": "sha512-b17KeDIQVjvb0ssuSDF2cYXSg2iztliJ4B9WdsuB6J952qCPKmnVq4DyW5motImXHDC1cBT/1UezrJVsKw5zjg==", - "dev": true, - "dependencies": { - "http-parser-js": ">=0.5.1", - "safe-buffer": ">=5.1.0", - "websocket-extensions": ">=0.1.1" - }, - "engines": { - "node": ">=0.8.0" - } - }, - "node_modules/websocket-extensions": { - "version": "0.1.4", - "resolved": "https://registry.npmjs.org/websocket-extensions/-/websocket-extensions-0.1.4.tgz", - "integrity": "sha512-OqedPIGOfsDlo31UNwYbCFMSaO9m9G/0faIHj5/dZFDMFqPTcx6UwqyOy3COEaEOg/9VsGIpdqn62W5KhoKSpg==", - "dev": true, - "engines": { - "node": ">=0.8.0" - } - }, - "node_modules/whatwg-url": { - "version": "5.0.0", - "resolved": "https://registry.npmjs.org/whatwg-url/-/whatwg-url-5.0.0.tgz", - "integrity": "sha512-saE57nupxk6v3HY35+jzBwYa0rKSy0XR8JSxZPwgLr7ys0IBzhGviA1/TUGJLmSVqs8pb9AnvICXEuOHLprYTw==", - "dependencies": { - "tr46": "~0.0.3", - "webidl-conversions": "^3.0.0" - } - }, - "node_modules/which": { - "version": "2.0.2", - "resolved": "https://registry.npmjs.org/which/-/which-2.0.2.tgz", - "integrity": "sha512-BLI3Tl1TW3Pvl70l3yq3Y64i+awpwXqsGBYWkkqMtnbXgrMD+yj7rhW0kuEDxzJaYXGjEW5ogapKNMEKNMjibA==", - "dev": true, - "dependencies": { - "isexe": "^2.0.0" - }, - "bin": { - "node-which": "bin/node-which" - }, - "engines": { - "node": ">= 8" - } - }, - "node_modules/which-boxed-primitive": { - "version": "1.0.2", - "resolved": "https://registry.npmjs.org/which-boxed-primitive/-/which-boxed-primitive-1.0.2.tgz", - "integrity": "sha512-bwZdv0AKLpplFY2KZRX6TvyuN7ojjr7lwkg6ml0roIy9YeuSr7JS372qlNW18UQYzgYK9ziGcerWqZOmEn9VNg==", - "dependencies": { - "is-bigint": "^1.0.1", - "is-boolean-object": "^1.1.0", - "is-number-object": "^1.0.4", - "is-string": "^1.0.5", - "is-symbol": "^1.0.3" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/which-typed-array": { - "version": "1.1.7", - "resolved": "https://registry.npmjs.org/which-typed-array/-/which-typed-array-1.1.7.tgz", - "integrity": "sha512-vjxaB4nfDqwKI0ws7wZpxIlde1XrLX5uB0ZjpfshgmapJMD7jJWhZI+yToJTqaFByF0eNBcYxbjmCzoRP7CfEw==", - "dependencies": { - "available-typed-arrays": "^1.0.5", - "call-bind": "^1.0.2", - "es-abstract": "^1.18.5", - "foreach": "^2.0.5", - "has-tostringtag": "^1.0.0", - "is-typed-array": "^1.1.7" - }, - "engines": { - "node": ">= 0.4" - }, - "funding": { - "url": "https://github.com/sponsors/ljharb" - } - }, - "node_modules/wildcard": { - "version": "2.0.0", - "resolved": "https://registry.npmjs.org/wildcard/-/wildcard-2.0.0.tgz", - "integrity": "sha512-JcKqAHLPxcdb9KM49dufGXn2x3ssnfjbcaQdLlfZsL9rH9wgDQjUtDxbo8NE0F6SFvydeu1VhZe7hZuHsB2/pw==", - "dev": true - }, - "node_modules/wrappy": { - "version": "1.0.2", - "resolved": "https://registry.npmjs.org/wrappy/-/wrappy-1.0.2.tgz", - "integrity": "sha1-tSQ9jz7BqjXxNkYFvA0QNuMKtp8=" - }, - "node_modules/ws": { - "version": "8.4.0", - "resolved": "https://registry.npmjs.org/ws/-/ws-8.4.0.tgz", - "integrity": "sha512-IHVsKe2pjajSUIl4KYMQOdlyliovpEPquKkqbwswulszzI7r0SfQrxnXdWAEqOlDCLrVSJzo+O1hAwdog2sKSQ==", - "engines": { - "node": ">=10.0.0" - }, - "peerDependencies": { - "bufferutil": "^4.0.1", - "utf-8-validate": "^5.0.2" - }, - "peerDependenciesMeta": { - "bufferutil": { - "optional": true - }, - "utf-8-validate": { - "optional": true - } - } - }, - "node_modules/xhr2": { - "version": "0.2.1", - "resolved": "https://registry.npmjs.org/xhr2/-/xhr2-0.2.1.tgz", - "integrity": "sha512-sID0rrVCqkVNUn8t6xuv9+6FViXjUVXq8H5rWOH2rz9fDNQEd4g0EA2XlcEdJXRz5BMEn4O1pJFdT+z4YHhoWw==", - "engines": { - "node": ">= 6" - } - }, - "node_modules/xtend": { - "version": "4.0.2", - "resolved": "https://registry.npmjs.org/xtend/-/xtend-4.0.2.tgz", - "integrity": "sha512-LKYU1iAXJXUgAXn9URjiu+MWhyUXHsvfp7mcuYm9dSUKK0/CjtrUwFAxD82/mCWbtLsGjFIad0wIsod4zrTAEQ==", - "engines": { - "node": ">=0.4" - } - }, - "node_modules/yauzl": { - "version": "2.10.0", - "resolved": "https://registry.npmjs.org/yauzl/-/yauzl-2.10.0.tgz", - "integrity": "sha512-p4a9I6X6nu6IhoGmBqAcbJy1mlC4j27vEPZX9F4L4/vZT3Lyq1VkFHw/V/PUcB9Buo+DG3iHkT0x3Qya58zc3g==", - "dependencies": { - "buffer-crc32": "~0.2.3", - "fd-slicer": "~1.1.0" - } - } - }, "dependencies": { "@discoveryjs/json-ext": { "version": "0.5.7", @@ -5728,6 +111,7 @@ "version": "8.4.1", "resolved": "https://registry.npmjs.org/@types/eslint/-/eslint-8.4.1.tgz", "integrity": "sha512-GE44+DNEyxxh2Kc6ro/VkIj+9ma0pO0bwv9+uHSyBrikYOHr8zYcdPvnBOp1aw8s+CjRvuSx7CyWqRrNFQ59mA==", + "dev": true, "requires": { "@types/estree": "*", "@types/json-schema": "*" @@ -5737,6 +121,7 @@ "version": "3.7.3", "resolved": "https://registry.npmjs.org/@types/eslint-scope/-/eslint-scope-3.7.3.tgz", "integrity": "sha512-PB3ldyrcnAicT35TWPs5IcwKD8S333HMaa2VVv4+wdvebJkjWuW/xESoB8IwRcog8HYVYamb1g/R31Qv5Bx03g==", + "dev": true, "requires": { "@types/eslint": "*", "@types/estree": "*" @@ -5745,7 +130,8 @@ "@types/estree": { "version": "0.0.50", "resolved": "https://registry.npmjs.org/@types/estree/-/estree-0.0.50.tgz", - "integrity": "sha512-C6N5s2ZFtuZRj54k2/zyRhNDjJwwcViAM3Nbm8zjBpbqAdZ00mr0CFxvSKeO8Y/e03WVFLpQMdHYVfUd6SB+Hw==" + "integrity": "sha512-C6N5s2ZFtuZRj54k2/zyRhNDjJwwcViAM3Nbm8zjBpbqAdZ00mr0CFxvSKeO8Y/e03WVFLpQMdHYVfUd6SB+Hw==", + "dev": true }, "@types/express": { "version": "4.17.13", @@ -5788,7 +174,8 @@ "@types/json-schema": { "version": "7.0.9", "resolved": "https://registry.npmjs.org/@types/json-schema/-/json-schema-7.0.9.tgz", - "integrity": "sha512-qcUXuemtEu+E5wZSJHNxUXeCZhAfXKQ41D+duX+VYPde7xyEVZci+/oXKJL13tnRs9lR2pr4fod59GT6/X1/yQ==" + "integrity": "sha512-qcUXuemtEu+E5wZSJHNxUXeCZhAfXKQ41D+duX+VYPde7xyEVZci+/oXKJL13tnRs9lR2pr4fod59GT6/X1/yQ==", + "dev": true }, "@types/mime": { "version": "1.3.2", @@ -5869,6 +256,7 @@ "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/ast/-/ast-1.11.1.tgz", "integrity": "sha512-ukBh14qFLjxTQNTXocdyksN5QdM28S1CxHt2rdskFyL+xFV7VremuBLVbmCePj+URalXBENx/9Lm7lnhihtCSw==", + "dev": true, "requires": { "@webassemblyjs/helper-numbers": "1.11.1", "@webassemblyjs/helper-wasm-bytecode": "1.11.1" @@ -5877,22 +265,26 @@ "@webassemblyjs/floating-point-hex-parser": { "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/floating-point-hex-parser/-/floating-point-hex-parser-1.11.1.tgz", - "integrity": "sha512-iGRfyc5Bq+NnNuX8b5hwBrRjzf0ocrJPI6GWFodBFzmFnyvrQ83SHKhmilCU/8Jv67i4GJZBMhEzltxzcNagtQ==" + "integrity": "sha512-iGRfyc5Bq+NnNuX8b5hwBrRjzf0ocrJPI6GWFodBFzmFnyvrQ83SHKhmilCU/8Jv67i4GJZBMhEzltxzcNagtQ==", + "dev": true }, "@webassemblyjs/helper-api-error": { "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/helper-api-error/-/helper-api-error-1.11.1.tgz", - "integrity": "sha512-RlhS8CBCXfRUR/cwo2ho9bkheSXG0+NwooXcc3PAILALf2QLdFyj7KGsKRbVc95hZnhnERon4kW/D3SZpp6Tcg==" + "integrity": "sha512-RlhS8CBCXfRUR/cwo2ho9bkheSXG0+NwooXcc3PAILALf2QLdFyj7KGsKRbVc95hZnhnERon4kW/D3SZpp6Tcg==", + "dev": true }, "@webassemblyjs/helper-buffer": { "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/helper-buffer/-/helper-buffer-1.11.1.tgz", - "integrity": "sha512-gwikF65aDNeeXa8JxXa2BAk+REjSyhrNC9ZwdT0f8jc4dQQeDQ7G4m0f2QCLPJiMTTO6wfDmRmj/pW0PsUvIcA==" + "integrity": "sha512-gwikF65aDNeeXa8JxXa2BAk+REjSyhrNC9ZwdT0f8jc4dQQeDQ7G4m0f2QCLPJiMTTO6wfDmRmj/pW0PsUvIcA==", + "dev": true }, "@webassemblyjs/helper-numbers": { "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/helper-numbers/-/helper-numbers-1.11.1.tgz", "integrity": "sha512-vDkbxiB8zfnPdNK9Rajcey5C0w+QJugEglN0of+kmO8l7lDb77AnlKYQF7aarZuCrv+l0UvqL+68gSDr3k9LPQ==", + "dev": true, "requires": { "@webassemblyjs/floating-point-hex-parser": "1.11.1", "@webassemblyjs/helper-api-error": "1.11.1", @@ -5902,12 +294,14 @@ "@webassemblyjs/helper-wasm-bytecode": { "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/helper-wasm-bytecode/-/helper-wasm-bytecode-1.11.1.tgz", - "integrity": "sha512-PvpoOGiJwXeTrSf/qfudJhwlvDQxFgelbMqtq52WWiXC6Xgg1IREdngmPN3bs4RoO83PnL/nFrxucXj1+BX62Q==" + "integrity": "sha512-PvpoOGiJwXeTrSf/qfudJhwlvDQxFgelbMqtq52WWiXC6Xgg1IREdngmPN3bs4RoO83PnL/nFrxucXj1+BX62Q==", + "dev": true }, "@webassemblyjs/helper-wasm-section": { "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/helper-wasm-section/-/helper-wasm-section-1.11.1.tgz", "integrity": "sha512-10P9No29rYX1j7F3EVPX3JvGPQPae+AomuSTPiF9eBQeChHI6iqjMIwR9JmOJXwpnn/oVGDk7I5IlskuMwU/pg==", + "dev": true, "requires": { "@webassemblyjs/ast": "1.11.1", "@webassemblyjs/helper-buffer": "1.11.1", @@ -5919,6 +313,7 @@ "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/ieee754/-/ieee754-1.11.1.tgz", "integrity": "sha512-hJ87QIPtAMKbFq6CGTkZYJivEwZDbQUgYd3qKSadTNOhVY7p+gfP6Sr0lLRVTaG1JjFj+r3YchoqRYxNH3M0GQ==", + "dev": true, "requires": { "@xtuc/ieee754": "^1.2.0" } @@ -5927,6 +322,7 @@ "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/leb128/-/leb128-1.11.1.tgz", "integrity": "sha512-BJ2P0hNZ0u+Th1YZXJpzW6miwqQUGcIHT1G/sf72gLVD9DZ5AdYTqPNbHZh6K1M5VmKvFXwGSWZADz+qBWxeRw==", + "dev": true, "requires": { "@xtuc/long": "4.2.2" } @@ -5934,12 +330,14 @@ "@webassemblyjs/utf8": { "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/utf8/-/utf8-1.11.1.tgz", - "integrity": "sha512-9kqcxAEdMhiwQkHpkNiorZzqpGrodQQ2IGrHHxCy+Ozng0ofyMA0lTqiLkVs1uzTRejX+/O0EOT7KxqVPuXosQ==" + "integrity": "sha512-9kqcxAEdMhiwQkHpkNiorZzqpGrodQQ2IGrHHxCy+Ozng0ofyMA0lTqiLkVs1uzTRejX+/O0EOT7KxqVPuXosQ==", + "dev": true }, "@webassemblyjs/wasm-edit": { "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/wasm-edit/-/wasm-edit-1.11.1.tgz", "integrity": "sha512-g+RsupUC1aTHfR8CDgnsVRVZFJqdkFHpsHMfJuWQzWU3tvnLC07UqHICfP+4XyL2tnr1amvl1Sdp06TnYCmVkA==", + "dev": true, "requires": { "@webassemblyjs/ast": "1.11.1", "@webassemblyjs/helper-buffer": "1.11.1", @@ -5955,6 +353,7 @@ "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/wasm-gen/-/wasm-gen-1.11.1.tgz", "integrity": "sha512-F7QqKXwwNlMmsulj6+O7r4mmtAlCWfO/0HdgOxSklZfQcDu0TpLiD1mRt/zF25Bk59FIjEuGAIyn5ei4yMfLhA==", + "dev": true, "requires": { "@webassemblyjs/ast": "1.11.1", "@webassemblyjs/helper-wasm-bytecode": "1.11.1", @@ -5967,6 +366,7 @@ "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/wasm-opt/-/wasm-opt-1.11.1.tgz", "integrity": "sha512-VqnkNqnZlU5EB64pp1l7hdm3hmQw7Vgqa0KF/KCNO9sIpI6Fk6brDEiX+iCOYrvMuBWDws0NkTOxYEb85XQHHw==", + "dev": true, "requires": { "@webassemblyjs/ast": "1.11.1", "@webassemblyjs/helper-buffer": "1.11.1", @@ -5978,6 +378,7 @@ "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/wasm-parser/-/wasm-parser-1.11.1.tgz", "integrity": "sha512-rrBujw+dJu32gYB7/Lup6UhdkPx9S9SnobZzRVL7VcBH9Bt9bCBLEuX/YXOOtBsOZ4NQrRykKhffRWHvigQvOA==", + "dev": true, "requires": { "@webassemblyjs/ast": "1.11.1", "@webassemblyjs/helper-api-error": "1.11.1", @@ -5991,6 +392,7 @@ "version": "1.11.1", "resolved": "https://registry.npmjs.org/@webassemblyjs/wast-printer/-/wast-printer-1.11.1.tgz", "integrity": "sha512-IQboUWM4eKzWW+N/jij2sRatKMh99QEelo3Eb2q0qXkvPRISAj8Qxtmw5itwqK+TTkBuUIE45AxYPToqPtL5gg==", + "dev": true, "requires": { "@webassemblyjs/ast": "1.11.1", "@xtuc/long": "4.2.2" @@ -6000,8 +402,7 @@ "version": "1.2.0", "resolved": "https://registry.npmjs.org/@webpack-cli/configtest/-/configtest-1.2.0.tgz", "integrity": "sha512-4FB8Tj6xyVkyqjj1OaTqCjXYULB9FMkqQ8yGrZjRDrYh0nOE+7Lhs45WioWQQMV+ceFlE368Ukhe6xdvJM9Egg==", - "dev": true, - "requires": {} + "dev": true }, "@webpack-cli/info": { "version": "1.5.0", @@ -6016,18 +417,19 @@ "version": "1.7.0", "resolved": "https://registry.npmjs.org/@webpack-cli/serve/-/serve-1.7.0.tgz", "integrity": "sha512-oxnCNGj88fL+xzV+dacXs44HcDwf1ovs3AuEzvP7mqXw7fQntqIhQ1BRmynh4qEKQSSSRSWVyXRjmTbZIX9V2Q==", - "dev": true, - "requires": {} + "dev": true }, "@xtuc/ieee754": { "version": "1.2.0", "resolved": "https://registry.npmjs.org/@xtuc/ieee754/-/ieee754-1.2.0.tgz", - "integrity": "sha512-DX8nKgqcGwsc0eJSqYt5lwP4DH5FlHnmuWWBRy7X0NcaGR0ZtuyeESgMwTYVEtxmsNGY+qit4QYT/MIYTOTPeA==" + "integrity": "sha512-DX8nKgqcGwsc0eJSqYt5lwP4DH5FlHnmuWWBRy7X0NcaGR0ZtuyeESgMwTYVEtxmsNGY+qit4QYT/MIYTOTPeA==", + "dev": true }, "@xtuc/long": { "version": "4.2.2", "resolved": "https://registry.npmjs.org/@xtuc/long/-/long-4.2.2.tgz", - "integrity": "sha512-NuHqBY1PB/D8xU6s/thBgOAiAP7HOYDQ32+BFZILJ8ivkUkAHQnWfn6WhL79Owj1qmUnoN/YPhktdIoucipkAQ==" + "integrity": "sha512-NuHqBY1PB/D8xU6s/thBgOAiAP7HOYDQ32+BFZILJ8ivkUkAHQnWfn6WhL79Owj1qmUnoN/YPhktdIoucipkAQ==", + "dev": true }, "accepts": { "version": "1.3.8", @@ -6042,13 +444,14 @@ "acorn": { "version": "8.7.0", "resolved": "https://registry.npmjs.org/acorn/-/acorn-8.7.0.tgz", - "integrity": "sha512-V/LGr1APy+PXIwKebEWrkZPwoeoF+w1jiOBUmuxuiUIaOHtob8Qc9BTrYo7VuI5fR8tqsy+buA2WFooR5olqvQ==" + "integrity": "sha512-V/LGr1APy+PXIwKebEWrkZPwoeoF+w1jiOBUmuxuiUIaOHtob8Qc9BTrYo7VuI5fR8tqsy+buA2WFooR5olqvQ==", + "dev": true }, "acorn-import-assertions": { "version": "1.8.0", "resolved": "https://registry.npmjs.org/acorn-import-assertions/-/acorn-import-assertions-1.8.0.tgz", "integrity": "sha512-m7VZ3jwz4eK6A4Vtt8Ew1/mNbP24u0FhdyfA7fSvnJR6LMdfOYnmuIrrJAgrYfYJ10F/otaHTtrtrtmHdMNzEw==", - "requires": {} + "dev": true }, "agent-base": { "version": "6.0.2", @@ -6087,6 +490,7 @@ "version": "6.12.6", "resolved": "https://registry.npmjs.org/ajv/-/ajv-6.12.6.tgz", "integrity": "sha512-j3fVLgvTo527anyYyJOGTYJbG+vnnQYvE0m5mmkc1TK+nxAppkCLMIL0aZ4dblVCNoGShhm+kzE4ZUykBoMg4g==", + "dev": true, "requires": { "fast-deep-equal": "^3.1.1", "fast-json-stable-stringify": "^2.0.0", @@ -6127,7 +531,7 @@ "version": "3.5.2", "resolved": "https://registry.npmjs.org/ajv-keywords/-/ajv-keywords-3.5.2.tgz", "integrity": "sha512-5p6WTN0DdTGVQk6VjcEju19IgaHudalcfabD7yhDGeA6bcQnmL+CpveLJq/3hvfwd1aof6L386Ougkx6RfyMIQ==", - "requires": {} + "dev": true }, "ansi-html-community": { "version": "0.0.8", @@ -6413,6 +817,7 @@ "version": "4.19.1", "resolved": "https://registry.npmjs.org/browserslist/-/browserslist-4.19.1.tgz", "integrity": "sha512-u2tbbG5PdKRTUoctO3NBD8FQ5HdPh1ZXPHzp1rwaa5jTc+RV9/+RlWiAIKmjRPQF+xbGM9Kklj5bZQFa2s/38A==", + "dev": true, "requires": { "caniuse-lite": "^1.0.30001286", "electron-to-chromium": "^1.4.17", @@ -6438,7 +843,8 @@ "buffer-from": { "version": "1.1.2", "resolved": "https://registry.npmjs.org/buffer-from/-/buffer-from-1.1.2.tgz", - "integrity": "sha512-E+XQCRwSbaaiChtv6k6Dwgc+bx+Bs6vuKJHHl5kox/BaKbhiXzqQOwK4cO22yElGp2OCmjwVhT3HmxgyPGnJfQ==" + "integrity": "sha512-E+XQCRwSbaaiChtv6k6Dwgc+bx+Bs6vuKJHHl5kox/BaKbhiXzqQOwK4cO22yElGp2OCmjwVhT3HmxgyPGnJfQ==", + "dev": true }, "buffer-indexof": { "version": "1.1.1", @@ -6499,7 +905,8 @@ "caniuse-lite": { "version": "1.0.30001305", "resolved": "https://registry.npmjs.org/caniuse-lite/-/caniuse-lite-1.0.30001305.tgz", - "integrity": "sha512-p7d9YQMji8haf0f+5rbcv9WlQ+N5jMPfRAnUmZRlNxsNeBO3Yr7RYG6M2uTY1h9tCVdlkJg6YNNc4kiAiBLdWA==" + "integrity": "sha512-p7d9YQMji8haf0f+5rbcv9WlQ+N5jMPfRAnUmZRlNxsNeBO3Yr7RYG6M2uTY1h9tCVdlkJg6YNNc4kiAiBLdWA==", + "dev": true }, "chokidar": { "version": "3.5.3", @@ -6525,7 +932,8 @@ "chrome-trace-event": { "version": "1.0.3", "resolved": "https://registry.npmjs.org/chrome-trace-event/-/chrome-trace-event-1.0.3.tgz", - "integrity": "sha512-p3KULyQg4S7NIHixdwbGX+nFHkoBiA4YQmyWtjb8XngSKV124nJmRysgAeujbUVb15vh+RvFUfCPqU7rXk+hZg==" + "integrity": "sha512-p3KULyQg4S7NIHixdwbGX+nFHkoBiA4YQmyWtjb8XngSKV124nJmRysgAeujbUVb15vh+RvFUfCPqU7rXk+hZg==", + "dev": true }, "cipher-base": { "version": "1.0.4", @@ -6994,7 +1402,8 @@ "electron-to-chromium": { "version": "1.4.63", "resolved": "https://registry.npmjs.org/electron-to-chromium/-/electron-to-chromium-1.4.63.tgz", - "integrity": "sha512-e0PX/LRJPFRU4kzJKLvTobxyFdnANCvcoDCe8XcyTqP58nTWIwdsHvXLIl1RkB39X5yaosLaroMASWB0oIsgCA==" + "integrity": "sha512-e0PX/LRJPFRU4kzJKLvTobxyFdnANCvcoDCe8XcyTqP58nTWIwdsHvXLIl1RkB39X5yaosLaroMASWB0oIsgCA==", + "dev": true }, "elliptic": { "version": "6.5.4", @@ -7035,6 +1444,7 @@ "version": "5.8.3", "resolved": "https://registry.npmjs.org/enhanced-resolve/-/enhanced-resolve-5.8.3.tgz", "integrity": "sha512-EGAbGvH7j7Xt2nc0E7D99La1OiEs8LnyimkRgwExpUMScN6O+3x9tIWs7PLQZVNx4YD+00skHXPXi1yQHpAmZA==", + "dev": true, "requires": { "graceful-fs": "^4.2.4", "tapable": "^2.2.0" @@ -7082,7 +1492,8 @@ "es-module-lexer": { "version": "0.9.3", "resolved": "https://registry.npmjs.org/es-module-lexer/-/es-module-lexer-0.9.3.tgz", - "integrity": "sha512-1HQ2M2sPtxwnvOvT1ZClHyQDiggdNjURWpY2we6aMKCQiUVxTmVs2UYPLIrD84sS+kMdUwfBSylbJPwNnBrnHQ==" + "integrity": "sha512-1HQ2M2sPtxwnvOvT1ZClHyQDiggdNjURWpY2we6aMKCQiUVxTmVs2UYPLIrD84sS+kMdUwfBSylbJPwNnBrnHQ==", + "dev": true }, "es-to-primitive": { "version": "1.2.1", @@ -7102,7 +1513,8 @@ "escalade": { "version": "3.1.1", "resolved": "https://registry.npmjs.org/escalade/-/escalade-3.1.1.tgz", - "integrity": "sha512-k0er2gUkLf8O0zKJiAhmkTnJlTvINGv7ygDNPbeIsX/TJjGJZHuh9B2UxbsaEkmlEo9MfhrSzmhIlhRlI2GXnw==" + "integrity": "sha512-k0er2gUkLf8O0zKJiAhmkTnJlTvINGv7ygDNPbeIsX/TJjGJZHuh9B2UxbsaEkmlEo9MfhrSzmhIlhRlI2GXnw==", + "dev": true }, "escape-html": { "version": "1.0.3", @@ -7114,6 +1526,7 @@ "version": "5.1.1", "resolved": "https://registry.npmjs.org/eslint-scope/-/eslint-scope-5.1.1.tgz", "integrity": "sha512-2NxwbF/hZ0KpepYN0cNbo+FN6XoK7GaHlQhgx/hIZl6Va0bF45RQOOwhLIy8lQDbuCiadSLCBnH2CFYquit5bw==", + "dev": true, "requires": { "esrecurse": "^4.3.0", "estraverse": "^4.1.1" @@ -7123,6 +1536,7 @@ "version": "4.3.0", "resolved": "https://registry.npmjs.org/esrecurse/-/esrecurse-4.3.0.tgz", "integrity": "sha512-KmfKL3b6G+RXvP8N1vr3Tq1kL/oCFgn2NYXEtqP8/L3pKapUA4G8cFVaoF3SU323CD4XypR/ffioHmkti6/Tag==", + "dev": true, "requires": { "estraverse": "^5.2.0" }, @@ -7130,14 +1544,16 @@ "estraverse": { "version": "5.3.0", "resolved": "https://registry.npmjs.org/estraverse/-/estraverse-5.3.0.tgz", - "integrity": "sha512-MMdARuVEQziNTeJD8DgMqmhwR11BRQ/cBP+pLtYdSTnf3MIO8fFeiINEbX36ZdNlfU/7A9f3gUw49B3oQsvwBA==" + "integrity": "sha512-MMdARuVEQziNTeJD8DgMqmhwR11BRQ/cBP+pLtYdSTnf3MIO8fFeiINEbX36ZdNlfU/7A9f3gUw49B3oQsvwBA==", + "dev": true } } }, "estraverse": { "version": "4.3.0", "resolved": "https://registry.npmjs.org/estraverse/-/estraverse-4.3.0.tgz", - "integrity": "sha512-39nnKffWz8xN1BU/2c79n9nB9HDzo0niYUqx6xyqUnyoAnQyyWpOTdZEeiCch8BBu515t4wp9ZmgVfVhn9EBpw==" + "integrity": "sha512-39nnKffWz8xN1BU/2c79n9nB9HDzo0niYUqx6xyqUnyoAnQyyWpOTdZEeiCch8BBu515t4wp9ZmgVfVhn9EBpw==", + "dev": true }, "etag": { "version": "1.8.1", @@ -7287,7 +1703,8 @@ "fast-deep-equal": { "version": "3.1.3", "resolved": "https://registry.npmjs.org/fast-deep-equal/-/fast-deep-equal-3.1.3.tgz", - "integrity": "sha512-f3qQ9oQy9j2AhBe/H9VC91wLmKBCCU/gDOnKNAYG5hswO7BLKj09Hc5HYNz9cGI++xlpDCIgDaitVs03ATR84Q==" + "integrity": "sha512-f3qQ9oQy9j2AhBe/H9VC91wLmKBCCU/gDOnKNAYG5hswO7BLKj09Hc5HYNz9cGI++xlpDCIgDaitVs03ATR84Q==", + "dev": true }, "fast-glob": { "version": "3.2.11", @@ -7305,7 +1722,8 @@ "fast-json-stable-stringify": { "version": "2.1.0", "resolved": "https://registry.npmjs.org/fast-json-stable-stringify/-/fast-json-stable-stringify-2.1.0.tgz", - "integrity": "sha512-lhd/wF+Lk98HZoTCtlVraHtfh5XYijIjalXck7saUtuanSDyLMxnHhSXEDJqHxD7msR8D0uCmqlkwjCV8xvwHw==" + "integrity": "sha512-lhd/wF+Lk98HZoTCtlVraHtfh5XYijIjalXck7saUtuanSDyLMxnHhSXEDJqHxD7msR8D0uCmqlkwjCV8xvwHw==", + "dev": true }, "fastest-levenshtein": { "version": "1.0.14", @@ -7465,12 +1883,14 @@ "glob-to-regexp": { "version": "0.4.1", "resolved": "https://registry.npmjs.org/glob-to-regexp/-/glob-to-regexp-0.4.1.tgz", - "integrity": "sha512-lkX1HJXwyMcprw/5YUZc2s7DrpAiHB21/V+E1rHUrVNokkvB6bqMzT0VfV6/86ZNabt1k14YOIaT7nDvOX3Iiw==" + "integrity": "sha512-lkX1HJXwyMcprw/5YUZc2s7DrpAiHB21/V+E1rHUrVNokkvB6bqMzT0VfV6/86ZNabt1k14YOIaT7nDvOX3Iiw==", + "dev": true }, "graceful-fs": { "version": "4.2.9", "resolved": "https://registry.npmjs.org/graceful-fs/-/graceful-fs-4.2.9.tgz", - "integrity": "sha512-NtNxqUcXgpW2iMrfqSfR73Glt39K+BLwWsPs94yR63v45T0Wbej7eRmL5cWfwEgqXnmjQp3zaJTshdRW/qC2ZQ==" + "integrity": "sha512-NtNxqUcXgpW2iMrfqSfR73Glt39K+BLwWsPs94yR63v45T0Wbej7eRmL5cWfwEgqXnmjQp3zaJTshdRW/qC2ZQ==", + "dev": true }, "handle-thing": { "version": "2.0.1", @@ -7494,7 +1914,8 @@ "has-flag": { "version": "4.0.0", "resolved": "https://registry.npmjs.org/has-flag/-/has-flag-4.0.0.tgz", - "integrity": "sha512-EykJT/Q1KjTWctppgIAgfSO0tKVuZUjhgMr17kqTumMl6Afv3EISleU7qZUzoXDFTAHTDC4NOoG/ZxU3EvlMPQ==" + "integrity": "sha512-EykJT/Q1KjTWctppgIAgfSO0tKVuZUjhgMr17kqTumMl6Afv3EISleU7qZUzoXDFTAHTDC4NOoG/ZxU3EvlMPQ==", + "dev": true }, "has-symbols": { "version": "1.0.2", @@ -8015,6 +2436,7 @@ "version": "27.4.6", "resolved": "https://registry.npmjs.org/jest-worker/-/jest-worker-27.4.6.tgz", "integrity": "sha512-gHWJF/6Xi5CTG5QCvROr6GcmpIqNYpDJyc8A1h/DyXqH1tD6SnRCM0d3U5msV31D2LB/U+E0M+W4oyvKV44oNw==", + "dev": true, "requires": { "@types/node": "*", "merge-stream": "^2.0.0", @@ -8025,6 +2447,7 @@ "version": "8.1.1", "resolved": "https://registry.npmjs.org/supports-color/-/supports-color-8.1.1.tgz", "integrity": "sha512-MpUEN2OodtUzxvKQl72cUF7RQ5EiHsGvSsVG0ia9c5RbWGL2CI4C7EpPS8UTBIplnlzZiNuV56w+FuNxy3ty2Q==", + "dev": true, "requires": { "has-flag": "^4.0.0" } @@ -8034,12 +2457,14 @@ "json-parse-better-errors": { "version": "1.0.2", "resolved": "https://registry.npmjs.org/json-parse-better-errors/-/json-parse-better-errors-1.0.2.tgz", - "integrity": "sha512-mrqyZKfX5EhL7hvqcV6WG1yYjnjeuYDzDhhcAAUrq8Po85NBQBJP+ZDUT75qZQ98IkUoBqdkExkukOU7Ts2wrw==" + "integrity": "sha512-mrqyZKfX5EhL7hvqcV6WG1yYjnjeuYDzDhhcAAUrq8Po85NBQBJP+ZDUT75qZQ98IkUoBqdkExkukOU7Ts2wrw==", + "dev": true }, "json-schema-traverse": { "version": "0.4.1", "resolved": "https://registry.npmjs.org/json-schema-traverse/-/json-schema-traverse-0.4.1.tgz", - "integrity": "sha512-xbbCH5dCYU5T8LcEhhuh7HJ88HXuW3qsI3Y0zOZFKfZEHcpWiHU/Jxzk629Brsab/mMiHQti9wMP+845RPe3Vg==" + "integrity": "sha512-xbbCH5dCYU5T8LcEhhuh7HJ88HXuW3qsI3Y0zOZFKfZEHcpWiHU/Jxzk629Brsab/mMiHQti9wMP+845RPe3Vg==", + "dev": true }, "jssha": { "version": "3.2.0", @@ -8055,7 +2480,8 @@ "loader-runner": { "version": "4.2.0", "resolved": "https://registry.npmjs.org/loader-runner/-/loader-runner-4.2.0.tgz", - "integrity": "sha512-92+huvxMvYlMzMt0iIOukcwYBFpkYJdpl2xsZ7LrlayO7E8SOv+JJUEK17B/dJIHAOLMfh2dZZ/Y18WgmGtYNw==" + "integrity": "sha512-92+huvxMvYlMzMt0iIOukcwYBFpkYJdpl2xsZ7LrlayO7E8SOv+JJUEK17B/dJIHAOLMfh2dZZ/Y18WgmGtYNw==", + "dev": true }, "locate-path": { "version": "5.0.0", @@ -8114,7 +2540,8 @@ "merge-stream": { "version": "2.0.0", "resolved": "https://registry.npmjs.org/merge-stream/-/merge-stream-2.0.0.tgz", - "integrity": "sha512-abv/qOcuPfk3URPfDzmZU1LKmuw8kT+0nIHvKrKgFrwifol/doWcdA4ZqsWQ8ENrFKkd67Mfpo/LovbIUsbt3w==" + "integrity": "sha512-abv/qOcuPfk3URPfDzmZU1LKmuw8kT+0nIHvKrKgFrwifol/doWcdA4ZqsWQ8ENrFKkd67Mfpo/LovbIUsbt3w==", + "dev": true }, "merge2": { "version": "1.4.1", @@ -8163,12 +2590,14 @@ "mime-db": { "version": "1.51.0", "resolved": "https://registry.npmjs.org/mime-db/-/mime-db-1.51.0.tgz", - "integrity": "sha512-5y8A56jg7XVQx2mbv1lu49NR4dokRnhZYTtL+KGfaa27uq4pSTXkwQkFJl4pkRMyNFz/EtYDSkiiEHx3F7UN6g==" + "integrity": "sha512-5y8A56jg7XVQx2mbv1lu49NR4dokRnhZYTtL+KGfaa27uq4pSTXkwQkFJl4pkRMyNFz/EtYDSkiiEHx3F7UN6g==", + "dev": true }, "mime-types": { "version": "2.1.34", "resolved": "https://registry.npmjs.org/mime-types/-/mime-types-2.1.34.tgz", "integrity": "sha512-6cP692WwGIs9XXdOO4++N+7qjqv0rqxxVvJ3VHPh/Sc9mVZcQP+ZGhkKiTvWMQRr2tbHkJP/Yn7Y0npb3ZBs4A==", + "dev": true, "requires": { "mime-db": "1.51.0" } @@ -8248,7 +2677,8 @@ "neo-async": { "version": "2.6.2", "resolved": "https://registry.npmjs.org/neo-async/-/neo-async-2.6.2.tgz", - "integrity": "sha512-Yd3UES5mWCSqR+qNT93S3UoYUkqAZ9lLg8a7g9rimsWmYGK8cVToA4/sF3RrshdyV3sAGMXVUmpMYOw+dLpOuw==" + "integrity": "sha512-Yd3UES5mWCSqR+qNT93S3UoYUkqAZ9lLg8a7g9rimsWmYGK8cVToA4/sF3RrshdyV3sAGMXVUmpMYOw+dLpOuw==", + "dev": true }, "no-case": { "version": "3.0.4", @@ -8318,7 +2748,8 @@ "node-releases": { "version": "2.0.1", "resolved": "https://registry.npmjs.org/node-releases/-/node-releases-2.0.1.tgz", - "integrity": "sha512-CqyzN6z7Q6aMeF/ktcMVTzhAHCEpf8SOarwpzpf8pNBY2k5/oM34UHldUwp8VKI7uxct2HxSRdJjBaZeESzcxA==" + "integrity": "sha512-CqyzN6z7Q6aMeF/ktcMVTzhAHCEpf8SOarwpzpf8pNBY2k5/oM34UHldUwp8VKI7uxct2HxSRdJjBaZeESzcxA==", + "dev": true }, "normalize-path": { "version": "3.0.0", @@ -8578,7 +3009,8 @@ "picocolors": { "version": "1.0.0", "resolved": "https://registry.npmjs.org/picocolors/-/picocolors-1.0.0.tgz", - "integrity": "sha512-1fygroTLlHu66zi26VoTDv8yRgm0Fccecssto+MhsZ0D/DGW2sm8E8AjW7NU5VVTRt5GxbeZ5qBuJr+HyLYkjQ==" + "integrity": "sha512-1fygroTLlHu66zi26VoTDv8yRgm0Fccecssto+MhsZ0D/DGW2sm8E8AjW7NU5VVTRt5GxbeZ5qBuJr+HyLYkjQ==", + "dev": true }, "picomatch": { "version": "2.3.1", @@ -8740,8 +3172,7 @@ "ws": { "version": "8.8.0", "resolved": "https://registry.npmjs.org/ws/-/ws-8.8.0.tgz", - "integrity": "sha512-JDAgSYQ1ksuwqfChJusw1LSJ8BizJ2e/vVu5Lxjq3YvNJNlROv1ui4i+c/kUUrPheBvQl4c5UbERhTwKa6QBJQ==", - "requires": {} + "integrity": "sha512-JDAgSYQ1ksuwqfChJusw1LSJ8BizJ2e/vVu5Lxjq3YvNJNlROv1ui4i+c/kUUrPheBvQl4c5UbERhTwKa6QBJQ==" } } }, @@ -8971,6 +3402,7 @@ "version": "3.1.1", "resolved": "https://registry.npmjs.org/schema-utils/-/schema-utils-3.1.1.tgz", "integrity": "sha512-Y5PQxS4ITlC+EahLuXaY86TXfR7Dc5lw294alXOq86JAHCihAIZfqv8nNCWvaEJvaC51uN9hbLGeV0cFBdH+Fw==", + "dev": true, "requires": { "@types/json-schema": "^7.0.8", "ajv": "^6.12.5", @@ -9025,6 +3457,7 @@ "version": "6.0.0", "resolved": "https://registry.npmjs.org/serialize-javascript/-/serialize-javascript-6.0.0.tgz", "integrity": "sha512-Qr3TosvguFt8ePWqsvRfrKyQXIiW+nGbYpy8XK24NQHE83caxWt+mIymTT19DGFbNWNLfEwsrkSmN64lVWB9ag==", + "dev": true, "requires": { "randombytes": "^2.1.0" } @@ -9162,12 +3595,14 @@ "source-map": { "version": "0.6.1", "resolved": "https://registry.npmjs.org/source-map/-/source-map-0.6.1.tgz", - "integrity": "sha512-UjgapumWlbMhkBgzT7Ykc5YXUT46F0iKu8SGXq0bcwP5dz/h0Plj6enJqjz1Zbq2l5WaqYnrVbwWOWMyF3F47g==" + "integrity": "sha512-UjgapumWlbMhkBgzT7Ykc5YXUT46F0iKu8SGXq0bcwP5dz/h0Plj6enJqjz1Zbq2l5WaqYnrVbwWOWMyF3F47g==", + "dev": true }, "source-map-support": { "version": "0.5.21", "resolved": "https://registry.npmjs.org/source-map-support/-/source-map-support-0.5.21.tgz", "integrity": "sha512-uBHU3L3czsIyYXKX88fdrGovxdSCoTGDRZ6SYXtSRxLZUzHg5P/66Ht6uoUlHu9EZod+inXhKo3qQgwXUT/y1w==", + "dev": true, "requires": { "buffer-from": "^1.0.0", "source-map": "^0.6.0" @@ -9260,21 +3695,6 @@ "xtend": "^4.0.2" } }, - "string_decoder": { - "version": "1.1.1", - "resolved": "https://registry.npmjs.org/string_decoder/-/string_decoder-1.1.1.tgz", - "integrity": "sha512-n/ShnvDi6FHbbVfviro+WojiFzv+s8MPMHBczVePfUpDJLwoLT0ht1l4YwBCbi8pJAveEEdnkHyPyTP/mzRfwg==", - "requires": { - "safe-buffer": "~5.1.0" - }, - "dependencies": { - "safe-buffer": { - "version": "5.1.2", - "resolved": "https://registry.npmjs.org/safe-buffer/-/safe-buffer-5.1.2.tgz", - "integrity": "sha512-Gd2UZBJDkXlY7GbJxfsE8/nvKkUEU1G38c1siN6QP6a9PT9MmHB8GnpscSmMJSoF8LOIrt8ud/wPtojys4G6+g==" - } - } - }, "string.prototype.trimend": { "version": "1.0.4", "resolved": "https://registry.npmjs.org/string.prototype.trimend/-/string.prototype.trimend-1.0.4.tgz", @@ -9293,6 +3713,21 @@ "define-properties": "^1.1.3" } }, + "string_decoder": { + "version": "1.1.1", + "resolved": "https://registry.npmjs.org/string_decoder/-/string_decoder-1.1.1.tgz", + "integrity": "sha512-n/ShnvDi6FHbbVfviro+WojiFzv+s8MPMHBczVePfUpDJLwoLT0ht1l4YwBCbi8pJAveEEdnkHyPyTP/mzRfwg==", + "requires": { + "safe-buffer": "~5.1.0" + }, + "dependencies": { + "safe-buffer": { + "version": "5.1.2", + "resolved": "https://registry.npmjs.org/safe-buffer/-/safe-buffer-5.1.2.tgz", + "integrity": "sha512-Gd2UZBJDkXlY7GbJxfsE8/nvKkUEU1G38c1siN6QP6a9PT9MmHB8GnpscSmMJSoF8LOIrt8ud/wPtojys4G6+g==" + } + } + }, "strip-ansi": { "version": "6.0.1", "resolved": "https://registry.npmjs.org/strip-ansi/-/strip-ansi-6.0.1.tgz", @@ -9317,7 +3752,8 @@ "tapable": { "version": "2.2.1", "resolved": "https://registry.npmjs.org/tapable/-/tapable-2.2.1.tgz", - "integrity": "sha512-GNzQvQTOIP6RyTfE2Qxb8ZVlNmw0n88vp1szwWRimP02mnTsx3Wtn5qRdqY9w2XduFNUgvOwhNnQsjwCp+kqaQ==" + "integrity": "sha512-GNzQvQTOIP6RyTfE2Qxb8ZVlNmw0n88vp1szwWRimP02mnTsx3Wtn5qRdqY9w2XduFNUgvOwhNnQsjwCp+kqaQ==", + "dev": true }, "tar-fs": { "version": "2.1.1", @@ -9346,6 +3782,7 @@ "version": "5.10.0", "resolved": "https://registry.npmjs.org/terser/-/terser-5.10.0.tgz", "integrity": "sha512-AMmF99DMfEDiRJfxfY5jj5wNH/bYO09cniSqhfoyxc8sFoYIgkJy86G04UoZU5VjlpnplVu0K6Tx6E9b5+DlHA==", + "dev": true, "requires": { "commander": "^2.20.0", "source-map": "~0.7.2", @@ -9355,12 +3792,14 @@ "commander": { "version": "2.20.3", "resolved": "https://registry.npmjs.org/commander/-/commander-2.20.3.tgz", - "integrity": "sha512-GpVkmM8vF2vQUkj2LvZmD35JxeJOLCwJ9cUkugyk2nuhbv3+mJvpLYYt+0+USMxE+oj+ey/lJEnhZw75x/OMcQ==" + "integrity": "sha512-GpVkmM8vF2vQUkj2LvZmD35JxeJOLCwJ9cUkugyk2nuhbv3+mJvpLYYt+0+USMxE+oj+ey/lJEnhZw75x/OMcQ==", + "dev": true }, "source-map": { "version": "0.7.3", "resolved": "https://registry.npmjs.org/source-map/-/source-map-0.7.3.tgz", - "integrity": "sha512-CkCj6giN3S+n9qrYiBTX5gystlENnRW5jZeNLHpe6aue+SrHcG5VYwujhW9s4dY31mEGsxBDrHR6oI69fTXsaQ==" + "integrity": "sha512-CkCj6giN3S+n9qrYiBTX5gystlENnRW5jZeNLHpe6aue+SrHcG5VYwujhW9s4dY31mEGsxBDrHR6oI69fTXsaQ==", + "dev": true } } }, @@ -9368,6 +3807,7 @@ "version": "5.3.1", "resolved": "https://registry.npmjs.org/terser-webpack-plugin/-/terser-webpack-plugin-5.3.1.tgz", "integrity": "sha512-GvlZdT6wPQKbDNW/GDQzZFg/j4vKU96yl2q6mcUkzKOgW4gwf1Z8cZToUCrz31XHlPWH8MVb1r2tFtdDtTGJ7g==", + "dev": true, "requires": { "jest-worker": "^27.4.5", "schema-utils": "^3.1.1", @@ -9482,6 +3922,7 @@ "version": "4.4.1", "resolved": "https://registry.npmjs.org/uri-js/-/uri-js-4.4.1.tgz", "integrity": "sha512-7rKUyy33Q1yc98pQ1DAmLtwX109F7TIfWlW1Ydo8Wl1ii1SeHieeh0HHfPeL2fMXK6z0s8ecKs9frCuLJvndBg==", + "dev": true, "requires": { "punycode": "^2.1.0" } @@ -9553,6 +3994,7 @@ "version": "2.3.1", "resolved": "https://registry.npmjs.org/watchpack/-/watchpack-2.3.1.tgz", "integrity": "sha512-x0t0JuydIo8qCNctdDrn1OzH/qDzk2+rdCOC3YzumZ42fiMqmQ7T3xQurykYMhYfHaPHTp4ZxAx2NfUo1K6QaA==", + "dev": true, "requires": { "glob-to-regexp": "^0.4.1", "graceful-fs": "^4.1.2" @@ -9576,6 +4018,7 @@ "version": "5.67.0", "resolved": "https://registry.npmjs.org/webpack/-/webpack-5.67.0.tgz", "integrity": "sha512-LjFbfMh89xBDpUMgA1W9Ur6Rn/gnr2Cq1jjHFPo4v6a79/ypznSYbAyPgGhwsxBtMIaEmDD1oJoA7BEYw/Fbrw==", + "dev": true, "requires": { "@types/eslint-scope": "^3.7.0", "@types/estree": "^0.0.50", @@ -9781,8 +4224,7 @@ "version": "8.4.2", "resolved": "https://registry.npmjs.org/ws/-/ws-8.4.2.tgz", "integrity": "sha512-Kbk4Nxyq7/ZWqr/tarI9yIt/+iNNFOjBXEWgTb4ydaNHBNGgvf2QHbS9fdfsndfjFlFwEd4Al+mw83YkaD10ZA==", - "dev": true, - "requires": {} + "dev": true } } }, @@ -9799,7 +4241,8 @@ "webpack-sources": { "version": "3.2.3", "resolved": "https://registry.npmjs.org/webpack-sources/-/webpack-sources-3.2.3.tgz", - "integrity": "sha512-/DyMEOrDgLKKIG0fmvtz+4dUX/3Ghozwgm6iPp8KRhvn+eQf9+Q7GWxVNMk3+uCPWfdXYC4ExGBckIXdFEfH1w==" + "integrity": "sha512-/DyMEOrDgLKKIG0fmvtz+4dUX/3Ghozwgm6iPp8KRhvn+eQf9+Q7GWxVNMk3+uCPWfdXYC4ExGBckIXdFEfH1w==", + "dev": true }, "websocket-driver": { "version": "0.7.4", @@ -9875,8 +4318,7 @@ "ws": { "version": "8.4.0", "resolved": "https://registry.npmjs.org/ws/-/ws-8.4.0.tgz", - "integrity": "sha512-IHVsKe2pjajSUIl4KYMQOdlyliovpEPquKkqbwswulszzI7r0SfQrxnXdWAEqOlDCLrVSJzo+O1hAwdog2sKSQ==", - "requires": {} + "integrity": "sha512-IHVsKe2pjajSUIl4KYMQOdlyliovpEPquKkqbwswulszzI7r0SfQrxnXdWAEqOlDCLrVSJzo+O1hAwdog2sKSQ==" }, "xhr2": { "version": "0.2.1", From 41c96b9b2599af5fee66d77ab21a64db92fbed8a Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Tue, 20 Dec 2022 16:06:14 +0000 Subject: [PATCH 152/373] Copy CTLs package-lock.json and rebuild the lock --- templates/ctl-scaffold/package-lock.json | 1067 ++++++++++++---------- 1 file changed, 568 insertions(+), 499 deletions(-) diff --git a/templates/ctl-scaffold/package-lock.json b/templates/ctl-scaffold/package-lock.json index 251da939e8..53725ab3d3 100644 --- a/templates/ctl-scaffold/package-lock.json +++ b/templates/ctl-scaffold/package-lock.json @@ -30,6 +30,55 @@ "resolved": "https://registry.npmjs.org/@emurgo/cardano-serialization-lib-nodejs/-/cardano-serialization-lib-nodejs-11.2.1.tgz", "integrity": "sha512-+Rw35NW4Qv/9uFaPxhKtxiIPmoBEIFMAgdqQxZTw6hNT/wvBp2TvwTBPnOW8ODs7GUAA8nrO1rJJAaxF+mAG2w==" }, + "@jridgewell/gen-mapping": { + "version": "0.3.2", + "resolved": "https://registry.npmjs.org/@jridgewell/gen-mapping/-/gen-mapping-0.3.2.tgz", + "integrity": "sha512-mh65xKQAzI6iBcFzwv28KVWSmCkdRBWoOh+bYQGW3+6OZvbbN3TqMGo5hqYxQniRcH9F2VZIoJCm4pa3BPDK/A==", + "dev": true, + "requires": { + "@jridgewell/set-array": "^1.0.1", + "@jridgewell/sourcemap-codec": "^1.4.10", + "@jridgewell/trace-mapping": "^0.3.9" + } + }, + "@jridgewell/resolve-uri": { + "version": "3.0.7", + "resolved": "https://registry.npmjs.org/@jridgewell/resolve-uri/-/resolve-uri-3.0.7.tgz", + "integrity": "sha512-8cXDaBBHOr2pQ7j77Y6Vp5VDT2sIqWyWQ56TjEq4ih/a4iST3dItRe8Q9fp0rrIl9DoKhWQtUQz/YpOxLkXbNA==", + "dev": true + }, + "@jridgewell/set-array": { + "version": "1.1.2", + "resolved": "https://registry.npmjs.org/@jridgewell/set-array/-/set-array-1.1.2.tgz", + "integrity": "sha512-xnkseuNADM0gt2bs+BvhO0p78Mk762YnZdsuzFV018NoG1Sj1SCQvpSqa7XUaTam5vAGasABV9qXASMKnFMwMw==", + "dev": true + }, + "@jridgewell/source-map": { + "version": "0.3.2", + "resolved": "https://registry.npmjs.org/@jridgewell/source-map/-/source-map-0.3.2.tgz", + "integrity": "sha512-m7O9o2uR8k2ObDysZYzdfhb08VuEml5oWGiosa1VdaPZ/A6QyPkAJuwN0Q1lhULOf6B7MtQmHENS743hWtCrgw==", + "dev": true, + "requires": { + "@jridgewell/gen-mapping": "^0.3.0", + "@jridgewell/trace-mapping": "^0.3.9" + } + }, + "@jridgewell/sourcemap-codec": { + "version": "1.4.13", + "resolved": "https://registry.npmjs.org/@jridgewell/sourcemap-codec/-/sourcemap-codec-1.4.13.tgz", + "integrity": "sha512-GryiOJmNcWbovBxTfZSF71V/mXbgcV3MewDe3kIMCLyIh5e7SKAeUZs+rMnJ8jkMolZ/4/VsdBmMrw3l+VdZ3w==", + "dev": true + }, + "@jridgewell/trace-mapping": { + "version": "0.3.13", + "resolved": "https://registry.npmjs.org/@jridgewell/trace-mapping/-/trace-mapping-0.3.13.tgz", + "integrity": "sha512-o1xbKhp9qnIAoHJSWd6KlCZfqslL4valSF81H8ImioOAxluWYWOpWkpyktY2vnt4tbrX9XYaxovq6cgowaJp2w==", + "dev": true, + "requires": { + "@jridgewell/resolve-uri": "^3.0.3", + "@jridgewell/sourcemap-codec": "^1.4.10" + } + }, "@mlabs-haskell/json-bigint": { "version": "1.0.0", "resolved": "https://registry.npmjs.org/@mlabs-haskell/json-bigint/-/json-bigint-1.0.0.tgz", @@ -108,9 +157,9 @@ } }, "@types/eslint": { - "version": "8.4.1", - "resolved": "https://registry.npmjs.org/@types/eslint/-/eslint-8.4.1.tgz", - "integrity": "sha512-GE44+DNEyxxh2Kc6ro/VkIj+9ma0pO0bwv9+uHSyBrikYOHr8zYcdPvnBOp1aw8s+CjRvuSx7CyWqRrNFQ59mA==", + "version": "8.4.3", + "resolved": "https://registry.npmjs.org/@types/eslint/-/eslint-8.4.3.tgz", + "integrity": "sha512-YP1S7YJRMPs+7KZKDb9G63n8YejIwW9BALq7a5j2+H4yl6iOv9CB29edho+cuFRrvmJbbaH2yiVChKLJVysDGw==", "dev": true, "requires": { "@types/estree": "*", @@ -146,9 +195,9 @@ } }, "@types/express-serve-static-core": { - "version": "4.17.28", - "resolved": "https://registry.npmjs.org/@types/express-serve-static-core/-/express-serve-static-core-4.17.28.tgz", - "integrity": "sha512-P1BJAEAW3E2DJUlkgq4tOL3RyMunoWXqbSCygWo5ZIWTjUgN1YnaXWW4VWl/oc8vs/XoYibEGBKP0uZyF4AHig==", + "version": "4.17.29", + "resolved": "https://registry.npmjs.org/@types/express-serve-static-core/-/express-serve-static-core-4.17.29.tgz", + "integrity": "sha512-uMd++6dMKS32EOuw1Uli3e3BPgdLIXmezcfHv7N4c1s3gkhikBplORPpMq3fuWkxncZN1reb16d5n8yhQ80x7Q==", "dev": true, "requires": { "@types/node": "*", @@ -163,18 +212,18 @@ "dev": true }, "@types/http-proxy": { - "version": "1.17.8", - "resolved": "https://registry.npmjs.org/@types/http-proxy/-/http-proxy-1.17.8.tgz", - "integrity": "sha512-5kPLG5BKpWYkw/LVOGWpiq3nEVqxiN32rTgI53Sk12/xHFQ2rG3ehI9IO+O3W2QoKeyB92dJkoka8SUm6BX1pA==", + "version": "1.17.9", + "resolved": "https://registry.npmjs.org/@types/http-proxy/-/http-proxy-1.17.9.tgz", + "integrity": "sha512-QsbSjA/fSk7xB+UXlCT3wHBy5ai9wOcNDWwZAtud+jXhwOM3l+EYZh8Lng4+/6n8uar0J7xILzqftJdJ/Wdfkw==", "dev": true, "requires": { "@types/node": "*" } }, "@types/json-schema": { - "version": "7.0.9", - "resolved": "https://registry.npmjs.org/@types/json-schema/-/json-schema-7.0.9.tgz", - "integrity": "sha512-qcUXuemtEu+E5wZSJHNxUXeCZhAfXKQ41D+duX+VYPde7xyEVZci+/oXKJL13tnRs9lR2pr4fod59GT6/X1/yQ==", + "version": "7.0.11", + "resolved": "https://registry.npmjs.org/@types/json-schema/-/json-schema-7.0.11.tgz", + "integrity": "sha512-wOuvG1SN4Us4rez+tylwwwCV1psiNVOkJeM3AUWUNWg/jDQY2+HE/444y5gc+jBmRqASOm2Oeh5c1axHobwRKQ==", "dev": true }, "@types/mime": { @@ -184,9 +233,9 @@ "dev": true }, "@types/node": { - "version": "17.0.14", - "resolved": "https://registry.npmjs.org/@types/node/-/node-17.0.14.tgz", - "integrity": "sha512-SbjLmERksKOGzWzPNuW7fJM7fk3YXVTFiZWB/Hs99gwhk+/dnrQRPBQjPW9aO+fi1tAffi9PrwFvsmOKmDTyng==" + "version": "17.0.35", + "resolved": "https://registry.npmjs.org/@types/node/-/node-17.0.35.tgz", + "integrity": "sha512-vu1SrqBjbbZ3J6vwY17jBs8Sr/BKA+/a/WtjRG+whKg1iuLFOosq872EXS0eXWILdO36DHQQeku/ZcL6hz2fpg==" }, "@types/qs": { "version": "6.9.7", @@ -201,9 +250,9 @@ "dev": true }, "@types/retry": { - "version": "0.12.1", - "resolved": "https://registry.npmjs.org/@types/retry/-/retry-0.12.1.tgz", - "integrity": "sha512-xoDlM2S4ortawSWORYqsdU+2rxdh4LRW9ytc3zmT37RIKQh6IHyKwwtKhKis9ah8ol07DCkZxPt8BBvPjC6v4g==", + "version": "0.12.0", + "resolved": "https://registry.npmjs.org/@types/retry/-/retry-0.12.0.tgz", + "integrity": "sha512-wWKOClTTiizcZhXnPY4wikVAwmdYHp8q6DmC+EJUzAMsycb7HB32Kh9RN4+0gExjmPmZSAQjgURXIGATPegAvA==", "dev": true }, "@types/serve-index": { @@ -235,9 +284,9 @@ } }, "@types/ws": { - "version": "8.2.2", - "resolved": "https://registry.npmjs.org/@types/ws/-/ws-8.2.2.tgz", - "integrity": "sha512-NOn5eIcgWLOo6qW8AcuLZ7G8PycXu0xTxxkS6Q18VWFxgPUSOwV0pBj2a/4viNZVu25i7RIB7GttdkAIUUXOOg==", + "version": "8.5.3", + "resolved": "https://registry.npmjs.org/@types/ws/-/ws-8.5.3.tgz", + "integrity": "sha512-6YOoWjruKj1uLf3INHH7D3qTXwFfEsg1kf3c0uDdSBJwfa/llkwIjrAGV7j7mVgGNbzTQ3HiHKKDXl6bJPD97w==", "dev": true, "requires": { "@types/node": "*" @@ -442,9 +491,9 @@ } }, "acorn": { - "version": "8.7.0", - "resolved": "https://registry.npmjs.org/acorn/-/acorn-8.7.0.tgz", - "integrity": "sha512-V/LGr1APy+PXIwKebEWrkZPwoeoF+w1jiOBUmuxuiUIaOHtob8Qc9BTrYo7VuI5fR8tqsy+buA2WFooR5olqvQ==", + "version": "8.7.1", + "resolved": "https://registry.npmjs.org/acorn/-/acorn-8.7.1.tgz", + "integrity": "sha512-Xx54uLJQZ19lKygFXOWsscKUbsBZW0CPykPhVQdhIeIwrbPmJzqeASDInc8nKBnp/JT6igTs82qPXz069H8I/A==", "dev": true }, "acorn-import-assertions": { @@ -508,9 +557,9 @@ }, "dependencies": { "ajv": { - "version": "8.9.0", - "resolved": "https://registry.npmjs.org/ajv/-/ajv-8.9.0.tgz", - "integrity": "sha512-qOKJyNj/h+OWx7s5DePL6Zu1KeM9jPZhwBqs+7DzP6bGOvqzVCSf0xueYmVuaC/oQ/VtS2zLMLHdQFbkka+XDQ==", + "version": "8.11.0", + "resolved": "https://registry.npmjs.org/ajv/-/ajv-8.11.0.tgz", + "integrity": "sha512-wGgprdCvMalC0BztXvitD2hC04YffAvtsUn93JbGXYLAtCUO4xd17mCCZQxUOItiBwZvJScWo8NIvQMQ71rdpg==", "dev": true, "requires": { "fast-deep-equal": "^3.1.1", @@ -571,6 +620,12 @@ "integrity": "sha512-hNfzcOV8W4NdualtqBFPyVO+54DSJuZGY9qT4pRroB6S9e3iiido2ISIC5h9R2sPJ8H3FHCIiEnsv1lPXO3KtQ==", "dev": true }, + "array-union": { + "version": "2.1.0", + "resolved": "https://registry.npmjs.org/array-union/-/array-union-2.1.0.tgz", + "integrity": "sha512-HGyxoOTYUyCM6stUe6EJgnd4EoewAI7zMdfqO+kGjnlZmBDz/cR5pf8r/cR4Wq60sL/p0IkcjUEEPwS3GFrIyw==", + "dev": true + }, "asn1.js": { "version": "5.4.1", "resolved": "https://registry.npmjs.org/asn1.js/-/asn1.js-5.4.1.tgz", @@ -601,9 +656,9 @@ } }, "async": { - "version": "2.6.3", - "resolved": "https://registry.npmjs.org/async/-/async-2.6.3.tgz", - "integrity": "sha512-zflvls11DCy+dQWzTW2dzuilv8Z5X/pjfmZOWba6TNIVDm+2UDaJmXSOXlasHKfNBs8oo3M0aT50fDEWfKZjXg==", + "version": "2.6.4", + "resolved": "https://registry.npmjs.org/async/-/async-2.6.4.tgz", + "integrity": "sha512-mzo5dfJYwAn29PeiJ0zvwTo04zj8HDJj0Mn8TD7sno7q12prdbnasKJHhkm2c1LgrhlJ0teaea8860oxi51mGA==", "dev": true, "requires": { "lodash": "^4.17.14" @@ -673,32 +728,34 @@ "integrity": "sha512-QXUSXI3QVc/gJME0dBpXrag1kbzOqCjCX8/b54ntNyW6sjtoqxqRk3LTmXzaJoh71zMsDCjM+47jS7XiwN/+fQ==" }, "bn.js": { - "version": "5.2.0", - "resolved": "https://registry.npmjs.org/bn.js/-/bn.js-5.2.0.tgz", - "integrity": "sha512-D7iWRBvnZE8ecXiLj/9wbxH7Tk79fAh8IHaTNq1RWRixsS02W+5qS+iE9yq6RYl0asXx5tw0bLhmT5pIfbSquw==" + "version": "5.2.1", + "resolved": "https://registry.npmjs.org/bn.js/-/bn.js-5.2.1.tgz", + "integrity": "sha512-eXRvHzWyYPBuB4NBy0cmYQjGitUrtqwbvlzP3G6VFnNRbsZQIxQ10PbKKHt8gZ/HW/D/747aDl+QkDqg3KQLMQ==" }, "body-parser": { - "version": "1.19.1", - "resolved": "https://registry.npmjs.org/body-parser/-/body-parser-1.19.1.tgz", - "integrity": "sha512-8ljfQi5eBk8EJfECMrgqNGWPEY5jWP+1IzkzkGdFFEwFQZZyaZ21UqdaHktgiMlH0xLHqIFtE/u2OYE5dOtViA==", + "version": "1.20.0", + "resolved": "https://registry.npmjs.org/body-parser/-/body-parser-1.20.0.tgz", + "integrity": "sha512-DfJ+q6EPcGKZD1QWUjSpqp+Q7bDQTsQIF4zfUAtZ6qk+H/3/QRhg9CEp39ss+/T2vw0+HaidC0ecJj/DRLIaKg==", "dev": true, "requires": { - "bytes": "3.1.1", + "bytes": "3.1.2", "content-type": "~1.0.4", "debug": "2.6.9", - "depd": "~1.1.2", - "http-errors": "1.8.1", + "depd": "2.0.0", + "destroy": "1.2.0", + "http-errors": "2.0.0", "iconv-lite": "0.4.24", - "on-finished": "~2.3.0", - "qs": "6.9.6", - "raw-body": "2.4.2", - "type-is": "~1.6.18" + "on-finished": "2.4.1", + "qs": "6.10.3", + "raw-body": "2.5.1", + "type-is": "~1.6.18", + "unpipe": "1.0.0" }, "dependencies": { "bytes": { - "version": "3.1.1", - "resolved": "https://registry.npmjs.org/bytes/-/bytes-3.1.1.tgz", - "integrity": "sha512-dWe4nWO/ruEOY7HkUJ5gFt1DCFV9zPRoJr8pV0/ASQermOZjtq8jMjOprC0Kd10GLN+l7xaUPvxzJFWtxGu8Fg==", + "version": "3.1.2", + "resolved": "https://registry.npmjs.org/bytes/-/bytes-3.1.2.tgz", + "integrity": "sha512-/Nf7TyzTx6S3yRJObOAV7956r8cr2+Oj8AC5dt8wSP3BQAoeX58NoHyCU8P8zGkNXStjTSi6fzO6F0pBdcYbEg==", "dev": true } } @@ -814,16 +871,15 @@ } }, "browserslist": { - "version": "4.19.1", - "resolved": "https://registry.npmjs.org/browserslist/-/browserslist-4.19.1.tgz", - "integrity": "sha512-u2tbbG5PdKRTUoctO3NBD8FQ5HdPh1ZXPHzp1rwaa5jTc+RV9/+RlWiAIKmjRPQF+xbGM9Kklj5bZQFa2s/38A==", + "version": "4.21.0", + "resolved": "https://registry.npmjs.org/browserslist/-/browserslist-4.21.0.tgz", + "integrity": "sha512-UQxE0DIhRB5z/zDz9iA03BOfxaN2+GQdBYH/2WrSIWEUrnpzTPJbhqt+umq6r3acaPRTW1FNTkrcp0PXgtFkvA==", "dev": true, "requires": { - "caniuse-lite": "^1.0.30001286", - "electron-to-chromium": "^1.4.17", - "escalade": "^3.1.1", - "node-releases": "^2.0.1", - "picocolors": "^1.0.0" + "caniuse-lite": "^1.0.30001358", + "electron-to-chromium": "^1.4.164", + "node-releases": "^2.0.5", + "update-browserslist-db": "^1.0.0" } }, "buffer": { @@ -863,13 +919,6 @@ "integrity": "sha512-HTm14iMQKK2FjFLRTM5lAVcyaUzOnqbPtesFIvREgXpJHdQm8bWS+GkQgIkfaBYRHuCnea7w8UVNfwiAQhlr9A==", "requires": { "node-gyp-build": "^4.3.0" - }, - "dependencies": { - "node-gyp-build": { - "version": "4.3.0", - "resolved": "https://registry.npmjs.org/node-gyp-build/-/node-gyp-build-4.3.0.tgz", - "integrity": "sha512-iWjXZvmboq0ja1pUGULQBexmxq8CV4xBhX7VDOTbL7ZR4FOowwY/VOtRxBN/yKxmdGoIp4j5ysNT4u3S2pDQ3Q==" - } } }, "builtin-status-codes": { @@ -903,9 +952,9 @@ } }, "caniuse-lite": { - "version": "1.0.30001305", - "resolved": "https://registry.npmjs.org/caniuse-lite/-/caniuse-lite-1.0.30001305.tgz", - "integrity": "sha512-p7d9YQMji8haf0f+5rbcv9WlQ+N5jMPfRAnUmZRlNxsNeBO3Yr7RYG6M2uTY1h9tCVdlkJg6YNNc4kiAiBLdWA==", + "version": "1.0.30001358", + "resolved": "https://registry.npmjs.org/caniuse-lite/-/caniuse-lite-1.0.30001358.tgz", + "integrity": "sha512-hvp8PSRymk85R20bsDra7ZTCpSVGN/PAz9pSAjPSjKC+rNmnUk5vCRgJwiTT/O4feQ/yu/drvZYpKxxhbFuChw==", "dev": true }, "chokidar": { @@ -945,9 +994,9 @@ } }, "clean-css": { - "version": "5.2.4", - "resolved": "https://registry.npmjs.org/clean-css/-/clean-css-5.2.4.tgz", - "integrity": "sha512-nKseG8wCzEuji/4yrgM/5cthL9oTDc5UOQyFMvW/Q53oP6gLH690o1NbuTh6Y18nujr7BxlsFuS7gXLnLzKJGg==", + "version": "5.3.0", + "resolved": "https://registry.npmjs.org/clean-css/-/clean-css-5.3.0.tgz", + "integrity": "sha512-YYuuxv4H/iNb1Z/5IbMRoxgrzjWGhOEFfd+groZ5dMCVkpENiMZmwspdrzBo9286JjM1gZJPAyL7ZIdzuvu2AQ==", "dev": true, "requires": { "source-map": "~0.6.0" @@ -971,9 +1020,9 @@ } }, "colorette": { - "version": "2.0.16", - "resolved": "https://registry.npmjs.org/colorette/-/colorette-2.0.16.tgz", - "integrity": "sha512-hUewv7oMjCp+wkBv5Rm0v87eJhq4woh5rSR+42YSQJKecCqgIqNkZ6lAlQms/BwHPJA5NKMRlpxPRv0n8HQW6g==", + "version": "2.0.19", + "resolved": "https://registry.npmjs.org/colorette/-/colorette-2.0.19.tgz", + "integrity": "sha512-3tlv/dIP7FWvj3BsbHrGLJ6l/oKh1O3TcgBqMn+yyCagOxc23fyzDS6HypQbgxWbkpDnf52p1LuR4eWDQ/K9WQ==", "dev": true }, "commander": { @@ -1017,7 +1066,7 @@ "concat-map": { "version": "0.0.1", "resolved": "https://registry.npmjs.org/concat-map/-/concat-map-0.0.1.tgz", - "integrity": "sha1-2Klr13/Wjfd5OnMDajug1UBdR3s=" + "integrity": "sha512-/Srv4dswyQNBfohGpz9o6Yb3Gz3SrUDqBH5rTuhGR7ahtlbYKnVxw2bCFMRljaA7EXHaXZ8wsHdodFvbkhKmqg==" }, "connect-history-api-fallback": { "version": "1.6.0", @@ -1051,9 +1100,9 @@ "dev": true }, "cookie": { - "version": "0.4.1", - "resolved": "https://registry.npmjs.org/cookie/-/cookie-0.4.1.tgz", - "integrity": "sha512-ZwrFkGJxUR3EIoXtO+yVE69Eb7KlixbaeAWfBQB9vVsNn/o+Yw69gBWSSDK825hQNdN+wF8zELf3dFNl/kxkUA==", + "version": "0.5.0", + "resolved": "https://registry.npmjs.org/cookie/-/cookie-0.5.0.tgz", + "integrity": "sha512-YZ3GUyn/o8gfKJlnlX7g7xq4gyO6OSuhGPKaaGssGB2qgDUS0gPgtTvoyZLTt9Ab6dC4hfc9dV5arkvc/OCmrw==", "dev": true }, "cookie-signature": { @@ -1147,22 +1196,22 @@ } }, "css-select": { - "version": "4.2.1", - "resolved": "https://registry.npmjs.org/css-select/-/css-select-4.2.1.tgz", - "integrity": "sha512-/aUslKhzkTNCQUB2qTX84lVmfia9NyjP3WpDGtj/WxhwBzWBYUV3DgUpurHTme8UTPcPlAD1DJ+b0nN/t50zDQ==", + "version": "4.3.0", + "resolved": "https://registry.npmjs.org/css-select/-/css-select-4.3.0.tgz", + "integrity": "sha512-wPpOYtnsVontu2mODhA19JrqWxNsfdatRKd64kmpRbQgh1KtItko5sTnEpPdpSaJszTOhEMlF/RPz28qj4HqhQ==", "dev": true, "requires": { "boolbase": "^1.0.0", - "css-what": "^5.1.0", - "domhandler": "^4.3.0", + "css-what": "^6.0.1", + "domhandler": "^4.3.1", "domutils": "^2.8.0", "nth-check": "^2.0.1" } }, "css-what": { - "version": "5.1.0", - "resolved": "https://registry.npmjs.org/css-what/-/css-what-5.1.0.tgz", - "integrity": "sha512-arSMRWIIFY0hV8pIxZMEfmMI47Wj3R/aWpZDDxWYCPEiOMv6tfOrnpDtgxBYPEQD4V0Y/958+1TdC3iWTFcUPw==", + "version": "6.1.0", + "resolved": "https://registry.npmjs.org/css-what/-/css-what-6.1.0.tgz", + "integrity": "sha512-HTUrgRJ7r4dsZKU6GjmpfRK1O76h97Z8MfS1G0FozR+oF2kG6Vfe8JE6zwrkbxigziPHinCJ+gCPjA9EaBDtRw==", "dev": true }, "debug": { @@ -1204,17 +1253,18 @@ "dev": true }, "define-properties": { - "version": "1.1.3", - "resolved": "https://registry.npmjs.org/define-properties/-/define-properties-1.1.3.tgz", - "integrity": "sha512-3MqfYKj2lLzdMSf8ZIZE/V+Zuy+BgD6f164e8K2w7dgnpKArBDerGYpM46IYYcjnkdPNMjPk9A6VFB8+3SKlXQ==", + "version": "1.1.4", + "resolved": "https://registry.npmjs.org/define-properties/-/define-properties-1.1.4.tgz", + "integrity": "sha512-uckOqKcfaVvtBdsVkdPv3XjveQJsNQqmhXgRi8uhvWWuPYZCNlzT8qAyblUgNoXdHdjMTzAqeGjAoli8f+bzPA==", "requires": { - "object-keys": "^1.0.12" + "has-property-descriptors": "^1.0.0", + "object-keys": "^1.1.1" } }, "del": { - "version": "6.0.0", - "resolved": "https://registry.npmjs.org/del/-/del-6.0.0.tgz", - "integrity": "sha512-1shh9DQ23L16oXSZKB2JxpL7iMy2E0S9d517ptA1P8iw0alkPtQcrKH7ru31rYtKwF499HkTu+DRzq3TCKDFRQ==", + "version": "6.1.1", + "resolved": "https://registry.npmjs.org/del/-/del-6.1.1.tgz", + "integrity": "sha512-ua8BhapfP0JUJKC/zV9yHHDW/rDoDxP4Zhn3AkA6/xT6gY7jYXJiaeyBZznYVujhZZET+UgcbZiQ7sN3WqcImg==", "dev": true, "requires": { "globby": "^11.0.1", @@ -1225,34 +1275,12 @@ "p-map": "^4.0.0", "rimraf": "^3.0.2", "slash": "^3.0.0" - }, - "dependencies": { - "array-union": { - "version": "2.1.0", - "resolved": "https://registry.npmjs.org/array-union/-/array-union-2.1.0.tgz", - "integrity": "sha512-HGyxoOTYUyCM6stUe6EJgnd4EoewAI7zMdfqO+kGjnlZmBDz/cR5pf8r/cR4Wq60sL/p0IkcjUEEPwS3GFrIyw==", - "dev": true - }, - "globby": { - "version": "11.1.0", - "resolved": "https://registry.npmjs.org/globby/-/globby-11.1.0.tgz", - "integrity": "sha512-jhIXaOzy1sb8IyocaruWSn1TjmnBVs8Ayhcy83rmxNJ8q2uWKCAj3CnJY+KpGSXCueAPc0i05kVvVKtP1t9S3g==", - "dev": true, - "requires": { - "array-union": "^2.1.0", - "dir-glob": "^3.0.1", - "fast-glob": "^3.2.9", - "ignore": "^5.2.0", - "merge2": "^1.4.1", - "slash": "^3.0.0" - } - } } }, "depd": { - "version": "1.1.2", - "resolved": "https://registry.npmjs.org/depd/-/depd-1.1.2.tgz", - "integrity": "sha1-m81S4UwJd2PnSbJ0xDRu0uVgtak=", + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/depd/-/depd-2.0.0.tgz", + "integrity": "sha512-g7nH6P6dyDioJogAAGprGpCtVImJhpPk/roCzdb3fIh61/s/nPsfR6onyMwkCAR/OlC3yBC0lESvUoQEAssIrw==", "dev": true }, "des.js": { @@ -1265,9 +1293,9 @@ } }, "destroy": { - "version": "1.0.4", - "resolved": "https://registry.npmjs.org/destroy/-/destroy-1.0.4.tgz", - "integrity": "sha1-l4hXRCxEdJ5CBmE+N5RiBYJqvYA=", + "version": "1.2.0", + "resolved": "https://registry.npmjs.org/destroy/-/destroy-1.2.0.tgz", + "integrity": "sha512-2sJGJTaXIIaR1w4iJSNoN0hnMY7Gpc/n8D4qSCJw8QqFWXf7cuAgnEHxBpweaVcPevC2l3KpjYCx3NypQQgaJg==", "dev": true }, "detect-node": { @@ -1277,9 +1305,9 @@ "dev": true }, "devtools-protocol": { - "version": "0.0.1019158", - "resolved": "https://registry.npmjs.org/devtools-protocol/-/devtools-protocol-0.0.1019158.tgz", - "integrity": "sha512-wvq+KscQ7/6spEV7czhnZc9RM/woz1AY+/Vpd8/h2HFMwJSdTliu7f/yr1A6vDdJfKICZsShqsYpEQbdhg8AFQ==" + "version": "0.0.1011705", + "resolved": "https://registry.npmjs.org/devtools-protocol/-/devtools-protocol-0.0.1011705.tgz", + "integrity": "sha512-OKvTvu9n3swmgYshvsyVHYX0+aPzCoYUnyXUacfQMmFtBtBKewV/gT4I9jkAbpTqtTi2E4S9MXLlvzBDUlqg0Q==" }, "diffie-hellman": { "version": "5.0.3", @@ -1310,7 +1338,7 @@ "dns-equal": { "version": "1.0.0", "resolved": "https://registry.npmjs.org/dns-equal/-/dns-equal-1.0.0.tgz", - "integrity": "sha1-s55/HabrCnW6nBcySzR1PEfgZU0=", + "integrity": "sha512-z+paD6YUQsk+AbGCEM4PrOXSss5gd66QfcVBFTKR/HpFL9jCqikS94HYwKww6fQyO7IxrIIyUu+g0Ka9tUS2Cg==", "dev": true }, "dns-packet": { @@ -1326,7 +1354,7 @@ "dns-txt": { "version": "2.0.2", "resolved": "https://registry.npmjs.org/dns-txt/-/dns-txt-2.0.2.tgz", - "integrity": "sha1-uR2Ab10nGI5Ks+fRB9iBocxGQrY=", + "integrity": "sha512-Ix5PrWjphuSoUXV/Zv5gaFHjnaJtb02F2+Si3Ht9dyJ87+Z/lMmy+dpNHtTGraNK958ndXq2i+GLkWsWHcKaBQ==", "dev": true, "requires": { "buffer-indexof": "^1.0.0" @@ -1342,9 +1370,9 @@ } }, "dom-serializer": { - "version": "1.3.2", - "resolved": "https://registry.npmjs.org/dom-serializer/-/dom-serializer-1.3.2.tgz", - "integrity": "sha512-5c54Bk5Dw4qAxNOI1pFEizPSjVsx5+bpJKmL2kPn8JhBUq2q09tTCa3mjijun2NfK78NMouDYNMBkOrPZiS+ig==", + "version": "1.4.1", + "resolved": "https://registry.npmjs.org/dom-serializer/-/dom-serializer-1.4.1.tgz", + "integrity": "sha512-VHwB3KfrcOOkelEG2ZOfxqLZdfkil8PtJi4P8N2MMXucZq2yLp75ClViUlOVwyoHEDjYU433Aq+5zWP61+RGag==", "dev": true, "requires": { "domelementtype": "^2.0.1", @@ -1358,15 +1386,15 @@ "integrity": "sha512-IGBwjF7tNk3cwypFNH/7bfzBcgSCbaMOD3GsaY1AU/JRrnHnYgEM0+9kQt52iZxjNsjBtJYtao146V+f8jFZNw==" }, "domelementtype": { - "version": "2.2.0", - "resolved": "https://registry.npmjs.org/domelementtype/-/domelementtype-2.2.0.tgz", - "integrity": "sha512-DtBMo82pv1dFtUmHyr48beiuq792Sxohr+8Hm9zoxklYPfa6n0Z3Byjj2IV7bmr2IyqClnqEQhfgHJJ5QF0R5A==", + "version": "2.3.0", + "resolved": "https://registry.npmjs.org/domelementtype/-/domelementtype-2.3.0.tgz", + "integrity": "sha512-OLETBj6w0OsagBwdXnPdN0cnMfF9opN69co+7ZrbfPGrdpPVNBUj02spi6B1N7wChLQiPn4CSH/zJvXw56gmHw==", "dev": true }, "domhandler": { - "version": "4.3.0", - "resolved": "https://registry.npmjs.org/domhandler/-/domhandler-4.3.0.tgz", - "integrity": "sha512-fC0aXNQXqKSFTr2wDNZDhsEYjCiYsDWl3D01kwt25hm1YIPyDGHvvi3rw+PLqHAl/m71MaiF7d5zvBr0p5UB2g==", + "version": "4.3.1", + "resolved": "https://registry.npmjs.org/domhandler/-/domhandler-4.3.1.tgz", + "integrity": "sha512-GrwoxYN+uWlzO8uhUXRl0P+kHE4GtVPfYzVLcUxPL7KNdHKj66vvlhiweIHqYYXWlw+T8iLMp42Lm67ghw4WMQ==", "dev": true, "requires": { "domelementtype": "^2.2.0" @@ -1396,13 +1424,13 @@ "ee-first": { "version": "1.1.1", "resolved": "https://registry.npmjs.org/ee-first/-/ee-first-1.1.1.tgz", - "integrity": "sha1-WQxhFWsK4vTwJVcyoViyZrxWsh0=", + "integrity": "sha512-WMwm9LhRUo+WUaRN+vRuETqG89IgZphVSNkdFgeb6sS/E4OrDIN7t48CAewSHXc6C8lefD8KKfr5vY61brQlow==", "dev": true }, "electron-to-chromium": { - "version": "1.4.63", - "resolved": "https://registry.npmjs.org/electron-to-chromium/-/electron-to-chromium-1.4.63.tgz", - "integrity": "sha512-e0PX/LRJPFRU4kzJKLvTobxyFdnANCvcoDCe8XcyTqP58nTWIwdsHvXLIl1RkB39X5yaosLaroMASWB0oIsgCA==", + "version": "1.4.167", + "resolved": "https://registry.npmjs.org/electron-to-chromium/-/electron-to-chromium-1.4.167.tgz", + "integrity": "sha512-lPHuHXBwpkr4RcfaZBKm6TKOWG/1N9mVggUpP4fY3l1JIUU2x4fkM8928smYdZ5lF+6KCTAxo1aK9JmqT+X71Q==", "dev": true }, "elliptic": { @@ -1429,7 +1457,7 @@ "encodeurl": { "version": "1.0.2", "resolved": "https://registry.npmjs.org/encodeurl/-/encodeurl-1.0.2.tgz", - "integrity": "sha1-rT/0yG7C0CkyL1oCw6mmBslbP1k=", + "integrity": "sha512-TPJXq8JqFaVYm2CWmPvnP2Iyo4ZSM7/QKcSmuMLDObfpH5fi7RUGmd/rTDf+rut/saiDiQEeVTNgAmJEdAOx0w==", "dev": true }, "end-of-stream": { @@ -1441,9 +1469,9 @@ } }, "enhanced-resolve": { - "version": "5.8.3", - "resolved": "https://registry.npmjs.org/enhanced-resolve/-/enhanced-resolve-5.8.3.tgz", - "integrity": "sha512-EGAbGvH7j7Xt2nc0E7D99La1OiEs8LnyimkRgwExpUMScN6O+3x9tIWs7PLQZVNx4YD+00skHXPXi1yQHpAmZA==", + "version": "5.9.3", + "resolved": "https://registry.npmjs.org/enhanced-resolve/-/enhanced-resolve-5.9.3.tgz", + "integrity": "sha512-Bq9VSor+kjvW3f9/MiiR4eE3XYgOl7/rS8lnSxbRbF3kS0B2r+Y9w5krBWxZgDxASVZbdYrn5wT4j/Wb0J9qow==", "dev": true, "requires": { "graceful-fs": "^4.2.4", @@ -1463,30 +1491,33 @@ "dev": true }, "es-abstract": { - "version": "1.19.1", - "resolved": "https://registry.npmjs.org/es-abstract/-/es-abstract-1.19.1.tgz", - "integrity": "sha512-2vJ6tjA/UfqLm2MPs7jxVybLoB8i1t1Jd9R3kISld20sIxPcTbLuggQOUxeWeAvIUkduv/CfMjuh4WmiXr2v9w==", + "version": "1.20.1", + "resolved": "https://registry.npmjs.org/es-abstract/-/es-abstract-1.20.1.tgz", + "integrity": "sha512-WEm2oBhfoI2sImeM4OF2zE2V3BYdSF+KnSi9Sidz51fQHd7+JuF8Xgcj9/0o+OWeIeIS/MiuNnlruQrJf16GQA==", "requires": { "call-bind": "^1.0.2", "es-to-primitive": "^1.2.1", "function-bind": "^1.1.1", + "function.prototype.name": "^1.1.5", "get-intrinsic": "^1.1.1", "get-symbol-description": "^1.0.0", "has": "^1.0.3", - "has-symbols": "^1.0.2", + "has-property-descriptors": "^1.0.0", + "has-symbols": "^1.0.3", "internal-slot": "^1.0.3", "is-callable": "^1.2.4", - "is-negative-zero": "^2.0.1", + "is-negative-zero": "^2.0.2", "is-regex": "^1.1.4", - "is-shared-array-buffer": "^1.0.1", + "is-shared-array-buffer": "^1.0.2", "is-string": "^1.0.7", - "is-weakref": "^1.0.1", - "object-inspect": "^1.11.0", + "is-weakref": "^1.0.2", + "object-inspect": "^1.12.0", "object-keys": "^1.1.1", "object.assign": "^4.1.2", - "string.prototype.trimend": "^1.0.4", - "string.prototype.trimstart": "^1.0.4", - "unbox-primitive": "^1.0.1" + "regexp.prototype.flags": "^1.4.3", + "string.prototype.trimend": "^1.0.5", + "string.prototype.trimstart": "^1.0.5", + "unbox-primitive": "^1.0.2" } }, "es-module-lexer": { @@ -1508,7 +1539,7 @@ "es6-object-assign": { "version": "1.1.0", "resolved": "https://registry.npmjs.org/es6-object-assign/-/es6-object-assign-1.1.0.tgz", - "integrity": "sha1-wsNYJlYkfDnqEHyx5mUrb58kUjw=" + "integrity": "sha512-MEl9uirslVwqQU369iHNWZXsI8yaZYGg/D65aOgZkeyFJwHYSxilf7rQzXKI7DdDuBPrBXbfk3sl9hJhmd5AUw==" }, "escalade": { "version": "3.1.1", @@ -1519,7 +1550,7 @@ "escape-html": { "version": "1.0.3", "resolved": "https://registry.npmjs.org/escape-html/-/escape-html-1.0.3.tgz", - "integrity": "sha1-Aljq5NPQwJdN4cFpGI7wBR0dGYg=", + "integrity": "sha512-NiSupZ4OeuGwr68lGIeym/ksIZMJodUGOSCZ/FSnTxcrekbvqrgdUxlJOMpijaKZVjAJrWrGs/6Jy8OMuyj9ow==", "dev": true }, "eslint-scope": { @@ -1558,7 +1589,7 @@ "etag": { "version": "1.8.1", "resolved": "https://registry.npmjs.org/etag/-/etag-1.8.1.tgz", - "integrity": "sha1-Qa4u62XvpiJorr/qg6x9eSmbCIc=", + "integrity": "sha512-aIL5Fx7mawVa300al2BnEE4iNvo1qETxLrPI/o05L7z6go7fCw1J6EQmbK4FmJ2AS7kgVF/KEZWufBfdClMcPg==", "dev": true }, "eventemitter3": { @@ -1596,63 +1627,42 @@ "onetime": "^5.1.2", "signal-exit": "^3.0.3", "strip-final-newline": "^2.0.0" - }, - "dependencies": { - "cross-spawn": { - "version": "7.0.3", - "resolved": "https://registry.npmjs.org/cross-spawn/-/cross-spawn-7.0.3.tgz", - "integrity": "sha512-iRDPJKUPVEND7dHPO8rkbOnPpyDygcDFtWjpeWNCgy8WP2rXcxXL8TskReQl6OrB2G7+UJrags1q15Fudc7G6w==", - "dev": true, - "requires": { - "path-key": "^3.1.0", - "shebang-command": "^2.0.0", - "which": "^2.0.1" - } - }, - "which": { - "version": "2.0.2", - "resolved": "https://registry.npmjs.org/which/-/which-2.0.2.tgz", - "integrity": "sha512-BLI3Tl1TW3Pvl70l3yq3Y64i+awpwXqsGBYWkkqMtnbXgrMD+yj7rhW0kuEDxzJaYXGjEW5ogapKNMEKNMjibA==", - "dev": true, - "requires": { - "isexe": "^2.0.0" - } - } } }, "express": { - "version": "4.17.2", - "resolved": "https://registry.npmjs.org/express/-/express-4.17.2.tgz", - "integrity": "sha512-oxlxJxcQlYwqPWKVJJtvQiwHgosH/LrLSPA+H4UxpyvSS6jC5aH+5MoHFM+KABgTOt0APue4w66Ha8jCUo9QGg==", + "version": "4.18.1", + "resolved": "https://registry.npmjs.org/express/-/express-4.18.1.tgz", + "integrity": "sha512-zZBcOX9TfehHQhtupq57OF8lFZ3UZi08Y97dwFCkD8p9d/d2Y3M+ykKcwaMDEL+4qyUolgBDX6AblpR3fL212Q==", "dev": true, "requires": { - "accepts": "~1.3.7", + "accepts": "~1.3.8", "array-flatten": "1.1.1", - "body-parser": "1.19.1", + "body-parser": "1.20.0", "content-disposition": "0.5.4", "content-type": "~1.0.4", - "cookie": "0.4.1", + "cookie": "0.5.0", "cookie-signature": "1.0.6", "debug": "2.6.9", - "depd": "~1.1.2", + "depd": "2.0.0", "encodeurl": "~1.0.2", "escape-html": "~1.0.3", "etag": "~1.8.1", - "finalhandler": "~1.1.2", + "finalhandler": "1.2.0", "fresh": "0.5.2", + "http-errors": "2.0.0", "merge-descriptors": "1.0.1", "methods": "~1.1.2", - "on-finished": "~2.3.0", + "on-finished": "2.4.1", "parseurl": "~1.3.3", "path-to-regexp": "0.1.7", "proxy-addr": "~2.0.7", - "qs": "6.9.6", + "qs": "6.10.3", "range-parser": "~1.2.1", "safe-buffer": "5.2.1", - "send": "0.17.2", - "serve-static": "1.14.2", + "send": "0.18.0", + "serve-static": "1.15.0", "setprototypeof": "1.2.0", - "statuses": "~1.5.0", + "statuses": "2.0.1", "type-is": "~1.6.18", "utils-merge": "1.0.1", "vary": "~1.1.2" @@ -1661,7 +1671,7 @@ "array-flatten": { "version": "1.1.1", "resolved": "https://registry.npmjs.org/array-flatten/-/array-flatten-1.1.1.tgz", - "integrity": "sha1-ml9pkFGx5wczKPKgCJaLZOopVdI=", + "integrity": "sha512-PCVAQswWemu6UdxsDFFX/+gVeYqKAod3D3UVm91jHwynguOwAvYPhx8nNlM++NqRcK6CxxpUafjmhIdKiHibqg==", "dev": true } } @@ -1772,17 +1782,17 @@ "integrity": "sha512-lO3ttPjHZRfjMcxWKb1j1eDhTFsu4meeR3lnMcnBFhk6RuLhvEiuALu2TlfL310ph4lCYYwgF/ElIjdP739tdg==" }, "finalhandler": { - "version": "1.1.2", - "resolved": "https://registry.npmjs.org/finalhandler/-/finalhandler-1.1.2.tgz", - "integrity": "sha512-aAWcW57uxVNrQZqFXjITpW3sIUQmHGG3qSb9mUah9MgMC4NeWhNOlNjXEYq3HjRAvL6arUviZGGJsBg6z0zsWA==", + "version": "1.2.0", + "resolved": "https://registry.npmjs.org/finalhandler/-/finalhandler-1.2.0.tgz", + "integrity": "sha512-5uXcUVftlQMFnWC9qu/svkWv3GTd2PfUhK/3PLkYNAe7FbqJMt3515HaxE6eRL74GdsriiwujiawdaB1BpEISg==", "dev": true, "requires": { "debug": "2.6.9", "encodeurl": "~1.0.2", "escape-html": "~1.0.3", - "on-finished": "~2.3.0", + "on-finished": "2.4.1", "parseurl": "~1.3.3", - "statuses": "~1.5.0", + "statuses": "2.0.1", "unpipe": "~1.0.0" } }, @@ -1796,15 +1806,18 @@ } }, "follow-redirects": { - "version": "1.14.7", - "resolved": "https://registry.npmjs.org/follow-redirects/-/follow-redirects-1.14.7.tgz", - "integrity": "sha512-+hbxoLbFMbRKDwohX8GkTataGqO6Jb7jGwpAlwgy2bIz25XtRm7KEzJM76R1WiNT5SwZkX4Y75SwBolkpmE7iQ==", + "version": "1.15.1", + "resolved": "https://registry.npmjs.org/follow-redirects/-/follow-redirects-1.15.1.tgz", + "integrity": "sha512-yLAMQs+k0b2m7cVxpS1VKJVvoz7SS9Td1zss3XRwXj+ZDH00RJgnuLx7E44wx02kQLrdM3aOOy+FpzS7+8OizA==", "dev": true }, - "foreach": { - "version": "2.0.5", - "resolved": "https://registry.npmjs.org/foreach/-/foreach-2.0.5.tgz", - "integrity": "sha1-C+4AUBiusmDQo6865ljdATbsG5k=" + "for-each": { + "version": "0.3.3", + "resolved": "https://registry.npmjs.org/for-each/-/for-each-0.3.3.tgz", + "integrity": "sha512-jqYfLp7mo9vIyQf8ykW2v7A+2N4QjeCeI5+Dz9XraiO1ign81wjiH7Fb9vSOWvQfNtmSa4H2RoQTrrXivdUZmw==", + "requires": { + "is-callable": "^1.1.3" + } }, "forwarded": { "version": "0.2.0", @@ -1815,7 +1828,7 @@ "fresh": { "version": "0.5.2", "resolved": "https://registry.npmjs.org/fresh/-/fresh-0.5.2.tgz", - "integrity": "sha1-PYyt2Q2XZWn6g1qx+OSyOhBWBac=", + "integrity": "sha512-zJ2mQYM18rEFOudeV4GShTGIQ7RbzA7ozbU9I/XBpm7kqgMywgmylMwXHxZJmkVoYkna9d2pVXVXPdYTP9ej8Q==", "dev": true }, "fs-constants": { @@ -1832,7 +1845,7 @@ "fs.realpath": { "version": "1.0.0", "resolved": "https://registry.npmjs.org/fs.realpath/-/fs.realpath-1.0.0.tgz", - "integrity": "sha1-FQStJSMVjKpA20onh8sBQRmU6k8=" + "integrity": "sha512-OO0pH2lK6a0hZnAdau5ItzHPI6pUlvI7jMVnxUQRtw4owF2wk8lOSabtGDCTP4Ggrg2MbGnWO9X8K1t4+fGMDw==" }, "fsevents": { "version": "2.3.2", @@ -1846,6 +1859,22 @@ "resolved": "https://registry.npmjs.org/function-bind/-/function-bind-1.1.1.tgz", "integrity": "sha512-yIovAzMX49sF8Yl58fSCWJ5svSLuaibPxXQJFLmBObTuCr0Mf1KiPopGM9NiFjiYBCbfaa2Fh6breQ6ANVTI0A==" }, + "function.prototype.name": { + "version": "1.1.5", + "resolved": "https://registry.npmjs.org/function.prototype.name/-/function.prototype.name-1.1.5.tgz", + "integrity": "sha512-uN7m/BzVKQnCUF/iW8jYea67v++2u7m5UgENbHRtdDVclOUP+FMPlCNdmk0h/ysGyo2tavMJEDqJAkJdRa1vMA==", + "requires": { + "call-bind": "^1.0.2", + "define-properties": "^1.1.3", + "es-abstract": "^1.19.0", + "functions-have-names": "^1.2.2" + } + }, + "functions-have-names": { + "version": "1.2.3", + "resolved": "https://registry.npmjs.org/functions-have-names/-/functions-have-names-1.2.3.tgz", + "integrity": "sha512-xckBUXyTIqT97tq2x2AMb+g163b5JFysYk0x4qxNFwbfQkmNZoiRHb6sPzI9/QV33WeuvVYBUIiD4NzNIyqaRQ==" + }, "get-intrinsic": { "version": "1.1.1", "resolved": "https://registry.npmjs.org/get-intrinsic/-/get-intrinsic-1.1.1.tgz", @@ -1871,6 +1900,19 @@ "get-intrinsic": "^1.1.1" } }, + "glob": { + "version": "7.2.3", + "resolved": "https://registry.npmjs.org/glob/-/glob-7.2.3.tgz", + "integrity": "sha512-nFR0zLpU2YCaRxwoCJvL6UvCH2JFyFVIvwTLsIf21AuHlMskA1hhTdk+LlYJtOlYt9v6dvszD2BGRqBL+iQK9Q==", + "requires": { + "fs.realpath": "^1.0.0", + "inflight": "^1.0.4", + "inherits": "2", + "minimatch": "^3.1.1", + "once": "^1.3.0", + "path-is-absolute": "^1.0.0" + } + }, "glob-parent": { "version": "5.1.2", "resolved": "https://registry.npmjs.org/glob-parent/-/glob-parent-5.1.2.tgz", @@ -1886,10 +1928,24 @@ "integrity": "sha512-lkX1HJXwyMcprw/5YUZc2s7DrpAiHB21/V+E1rHUrVNokkvB6bqMzT0VfV6/86ZNabt1k14YOIaT7nDvOX3Iiw==", "dev": true }, + "globby": { + "version": "11.1.0", + "resolved": "https://registry.npmjs.org/globby/-/globby-11.1.0.tgz", + "integrity": "sha512-jhIXaOzy1sb8IyocaruWSn1TjmnBVs8Ayhcy83rmxNJ8q2uWKCAj3CnJY+KpGSXCueAPc0i05kVvVKtP1t9S3g==", + "dev": true, + "requires": { + "array-union": "^2.1.0", + "dir-glob": "^3.0.1", + "fast-glob": "^3.2.9", + "ignore": "^5.2.0", + "merge2": "^1.4.1", + "slash": "^3.0.0" + } + }, "graceful-fs": { - "version": "4.2.9", - "resolved": "https://registry.npmjs.org/graceful-fs/-/graceful-fs-4.2.9.tgz", - "integrity": "sha512-NtNxqUcXgpW2iMrfqSfR73Glt39K+BLwWsPs94yR63v45T0Wbej7eRmL5cWfwEgqXnmjQp3zaJTshdRW/qC2ZQ==", + "version": "4.2.10", + "resolved": "https://registry.npmjs.org/graceful-fs/-/graceful-fs-4.2.10.tgz", + "integrity": "sha512-9ByhssR2fPVsNZj478qUUbKfmL0+t5BDVyjShtyZZLiK7ZDAArFFfopyOTj0M05wE2tJPisA4iTnnXl2YoPvOA==", "dev": true }, "handle-thing": { @@ -1907,9 +1963,9 @@ } }, "has-bigints": { - "version": "1.0.1", - "resolved": "https://registry.npmjs.org/has-bigints/-/has-bigints-1.0.1.tgz", - "integrity": "sha512-LSBS2LjbNBTf6287JEbEzvJgftkF5qFkmCo9hDRpAzKhUOlJ+hx8dd4USs00SgsUNwc4617J9ki5YtEClM2ffA==" + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/has-bigints/-/has-bigints-1.0.2.tgz", + "integrity": "sha512-tSvCKtBr9lkF0Ex0aQiP9N+OpV4zi2r/Nee5VkRDbaqv35RLYMzbwQfFSZZH0kR+Rd6302UJZ2p/bJCEoR3VoQ==" }, "has-flag": { "version": "4.0.0", @@ -1917,10 +1973,18 @@ "integrity": "sha512-EykJT/Q1KjTWctppgIAgfSO0tKVuZUjhgMr17kqTumMl6Afv3EISleU7qZUzoXDFTAHTDC4NOoG/ZxU3EvlMPQ==", "dev": true }, + "has-property-descriptors": { + "version": "1.0.0", + "resolved": "https://registry.npmjs.org/has-property-descriptors/-/has-property-descriptors-1.0.0.tgz", + "integrity": "sha512-62DVLZGoiEBDHQyqG4w9xCuZ7eJEwNmJRWw2VY84Oedb7WFcA27fiEVe8oUQx9hAUJ4ekurquucTGwsyO1XGdQ==", + "requires": { + "get-intrinsic": "^1.1.1" + } + }, "has-symbols": { - "version": "1.0.2", - "resolved": "https://registry.npmjs.org/has-symbols/-/has-symbols-1.0.2.tgz", - "integrity": "sha512-chXa79rL/UC2KlX17jo3vRGz0azaWEx5tGqZg5pO3NUyEJVB17dMruQlzCCOfUvElghKcm5194+BCRvi2Rv/Gw==" + "version": "1.0.3", + "resolved": "https://registry.npmjs.org/has-symbols/-/has-symbols-1.0.3.tgz", + "integrity": "sha512-l3LCuF6MgDNwTDKkdYGEihYjt5pRPbEg46rtlmnSPlUbgmB8LOIrKJbYYFBSbnPaJexMKtiPO8hmeRjRz2Td+A==" }, "has-tostringtag": { "version": "1.0.0", @@ -1958,7 +2022,7 @@ "hmac-drbg": { "version": "1.0.1", "resolved": "https://registry.npmjs.org/hmac-drbg/-/hmac-drbg-1.0.1.tgz", - "integrity": "sha1-0nRXAQJabHdabFRXk+1QL8DGSaE=", + "integrity": "sha512-Tti3gMqLdZfhOQY1Mzf/AanLiqh1WTiJgEj26ZuYQ9fbkLomzGchCws4FyrSd4VkpBfiNhaE1On+lOz894jvXg==", "requires": { "hash.js": "^1.0.3", "minimalistic-assert": "^1.0.0", @@ -1968,7 +2032,7 @@ "hpack.js": { "version": "2.1.6", "resolved": "https://registry.npmjs.org/hpack.js/-/hpack.js-2.1.6.tgz", - "integrity": "sha1-h3dMCUnlE/QuhFdbPEVoH63ioLI=", + "integrity": "sha512-zJxVehUdMGIKsRaNt7apO2Gqp0BdqW5yaiGHXXmbpvxgBYVZnAql+BJb4RO5ad2MgpbZKn5G6nMnegrH1FcNYQ==", "dev": true, "requires": { "inherits": "^2.0.1", @@ -1997,13 +2061,22 @@ "resolved": "https://registry.npmjs.org/safe-buffer/-/safe-buffer-5.1.2.tgz", "integrity": "sha512-Gd2UZBJDkXlY7GbJxfsE8/nvKkUEU1G38c1siN6QP6a9PT9MmHB8GnpscSmMJSoF8LOIrt8ud/wPtojys4G6+g==", "dev": true + }, + "string_decoder": { + "version": "1.1.1", + "resolved": "https://registry.npmjs.org/string_decoder/-/string_decoder-1.1.1.tgz", + "integrity": "sha512-n/ShnvDi6FHbbVfviro+WojiFzv+s8MPMHBczVePfUpDJLwoLT0ht1l4YwBCbi8pJAveEEdnkHyPyTP/mzRfwg==", + "dev": true, + "requires": { + "safe-buffer": "~5.1.0" + } } } }, "html-entities": { - "version": "2.3.2", - "resolved": "https://registry.npmjs.org/html-entities/-/html-entities-2.3.2.tgz", - "integrity": "sha512-c3Ab/url5ksaT0WyleslpBEthOzWhrjQbg75y7XUsfSzi3Dgzt0l8w5e7DylRn15MTlMMD58dTfzddNS2kcAjQ==", + "version": "2.3.3", + "resolved": "https://registry.npmjs.org/html-entities/-/html-entities-2.3.3.tgz", + "integrity": "sha512-DV5Ln36z34NNTDgnz0EWGBLZENelNAtkiFA4kyNOG2tDI6Mz1uSWiq1wAKdyjnJwyDiDO7Fa2SO1CTxPXL8VxA==", "dev": true }, "html-minifier-terser": { @@ -2049,26 +2122,26 @@ "http-deceiver": { "version": "1.2.7", "resolved": "https://registry.npmjs.org/http-deceiver/-/http-deceiver-1.2.7.tgz", - "integrity": "sha1-+nFolEq5pRnTN8sL7HKE3D5yPYc=", + "integrity": "sha512-LmpOGxTfbpgtGVxJrj5k7asXHCgNZp5nLfp+hWc8QQRqtb7fUy6kRY3BO1h9ddF6yIPYUARgxGOwB42DnxIaNw==", "dev": true }, "http-errors": { - "version": "1.8.1", - "resolved": "https://registry.npmjs.org/http-errors/-/http-errors-1.8.1.tgz", - "integrity": "sha512-Kpk9Sm7NmI+RHhnj6OIWDI1d6fIoFAtFt9RLaTMRlg/8w49juAStsrBgp0Dp4OdxdVbRIeKhtCUvoi/RuAhO4g==", + "version": "2.0.0", + "resolved": "https://registry.npmjs.org/http-errors/-/http-errors-2.0.0.tgz", + "integrity": "sha512-FtwrG/euBzaEjYeRqOgly7G0qviiXoJWnvEH2Z1plBdXgbyjv34pHTSb9zoeHMyDy33+DWy5Wt9Wo+TURtOYSQ==", "dev": true, "requires": { - "depd": "~1.1.2", + "depd": "2.0.0", "inherits": "2.0.4", "setprototypeof": "1.2.0", - "statuses": ">= 1.5.0 < 2", + "statuses": "2.0.1", "toidentifier": "1.0.1" } }, "http-parser-js": { - "version": "0.5.5", - "resolved": "https://registry.npmjs.org/http-parser-js/-/http-parser-js-0.5.5.tgz", - "integrity": "sha512-x+JVEkO2PoM8qqpbPbOL3cqHPwerep7OwzK7Ay+sMQjKzaKCqWvjoXm5tqMP9tXWWTnTzAjIhXg+J99XYuPhPA==", + "version": "0.5.6", + "resolved": "https://registry.npmjs.org/http-parser-js/-/http-parser-js-0.5.6.tgz", + "integrity": "sha512-vDlkRPDJn93swjcjqMSaGSPABbIarsr1TLAui/gLDXzV5VsJNdXNzMYDyNBLQkjWQCJ1uizu8T2oDMhmGt0PRA==", "dev": true }, "http-proxy": { @@ -2083,9 +2156,9 @@ } }, "http-proxy-middleware": { - "version": "2.0.2", - "resolved": "https://registry.npmjs.org/http-proxy-middleware/-/http-proxy-middleware-2.0.2.tgz", - "integrity": "sha512-XtmDN5w+vdFTBZaYhdJAbMqn0DP/EhkUaAeo963mojwpKMMbw6nivtFKw07D7DDOH745L5k0VL0P8KRYNEVF/g==", + "version": "2.0.6", + "resolved": "https://registry.npmjs.org/http-proxy-middleware/-/http-proxy-middleware-2.0.6.tgz", + "integrity": "sha512-ya/UeJ6HVBYxrgYotAZo1KvPWlgB48kUJLDePFeneHsVujFaW5WNj2NgWCAE//B1Dl02BIfYlpNgBy8Kf8Rjmw==", "dev": true, "requires": { "@types/http-proxy": "^1.17.8", @@ -2098,7 +2171,7 @@ "https-browserify": { "version": "1.0.0", "resolved": "https://registry.npmjs.org/https-browserify/-/https-browserify-1.0.0.tgz", - "integrity": "sha1-7AbBDgo0wPL68Zn3/X/Hj//QPHM=" + "integrity": "sha512-J+FkSdyD+0mA0N+81tMotaRMfSL9SGi+xpD3T6YApKsc3bGSXJlfXri3VyFOeYkfLRQisDk1W+jIFFKBeUBbBg==" }, "https-proxy-agent": { "version": "5.0.1", @@ -2169,7 +2242,7 @@ "inflight": { "version": "1.0.6", "resolved": "https://registry.npmjs.org/inflight/-/inflight-1.0.6.tgz", - "integrity": "sha1-Sb1jMdfQLQwJvJEKEHW6gWW1bfk=", + "integrity": "sha512-k92I/b08q4wvFscXCLvqfsHCrjrF7yiXsQuIVvVE7N82W3+aqpzuUdBbfhWcy/FZR3/4IgflMgKLOsvPDrGCJA==", "requires": { "once": "^1.3.0", "wrappy": "1" @@ -2197,9 +2270,9 @@ "dev": true }, "ip": { - "version": "1.1.5", - "resolved": "https://registry.npmjs.org/ip/-/ip-1.1.5.tgz", - "integrity": "sha1-vd7XARQpCCjAoDnnLvJfWq7ENUo=", + "version": "1.1.8", + "resolved": "https://registry.npmjs.org/ip/-/ip-1.1.8.tgz", + "integrity": "sha512-PuExPYUiu6qMBQb4l06ecm6T6ujzhmh+MeJcW9wa89PoAz5pvd4zPgN5WJV104mb6S2T1AwNIAaB70JNrLQWhg==", "dev": true }, "ipaddr.js": { @@ -2274,7 +2347,7 @@ "is-extglob": { "version": "2.1.1", "resolved": "https://registry.npmjs.org/is-extglob/-/is-extglob-2.1.1.tgz", - "integrity": "sha1-qIwCU1eR8C7TfHahueqXc8gz+MI=", + "integrity": "sha512-SbKbANkN603Vi4jEZv49LeVJMn4yGwsbzZworEoyEiutsN3nJYdbO36zfhGJ6QEDpOZIFkDtnq5JRxmvl3jsoQ==", "dev": true }, "is-generator-function": { @@ -2315,9 +2388,9 @@ "dev": true }, "is-number-object": { - "version": "1.0.6", - "resolved": "https://registry.npmjs.org/is-number-object/-/is-number-object-1.0.6.tgz", - "integrity": "sha512-bEVOqiRcvo3zO1+G2lVMy+gkkEm9Yh7cDMRusKKu5ZJKPUYSJwICTKZrNKHA2EbSP0Tu0+6B/emsYNHZyn6K8g==", + "version": "1.0.7", + "resolved": "https://registry.npmjs.org/is-number-object/-/is-number-object-1.0.7.tgz", + "integrity": "sha512-k1U0IRzLMo7ZlYIfzRu23Oh6MiIFasgpb9X76eqfFZAqwH44UI4KTBvBYIZ1dSL9ZzChTB9ShHfLkR4pdW5krQ==", "requires": { "has-tostringtag": "^1.0.0" } @@ -2359,9 +2432,12 @@ } }, "is-shared-array-buffer": { - "version": "1.0.1", - "resolved": "https://registry.npmjs.org/is-shared-array-buffer/-/is-shared-array-buffer-1.0.1.tgz", - "integrity": "sha512-IU0NmyknYZN0rChcKhRO1X8LYz5Isj/Fsqh8NJOSf+N/hCOTwy29F32Ik7a+QszE63IdvmwdTPDd6cZ5pg4cwA==" + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/is-shared-array-buffer/-/is-shared-array-buffer-1.0.2.tgz", + "integrity": "sha512-sqN2UDu1/0y6uvXyStCOzyhAjCSlHceFoMKJW8W9EU9cvic/QdsZ0kEU93HEy3IUEFZIiH/3w+AH/UQbPHNdhA==", + "requires": { + "call-bind": "^1.0.2" + } }, "is-stream": { "version": "2.0.1", @@ -2386,14 +2462,14 @@ } }, "is-typed-array": { - "version": "1.1.8", - "resolved": "https://registry.npmjs.org/is-typed-array/-/is-typed-array-1.1.8.tgz", - "integrity": "sha512-HqH41TNZq2fgtGT8WHVFVJhBVGuY3AnP3Q36K8JKXUxSxRgk/d+7NjmwG2vo2mYmXK8UYZKu0qH8bVP5gEisjA==", + "version": "1.1.9", + "resolved": "https://registry.npmjs.org/is-typed-array/-/is-typed-array-1.1.9.tgz", + "integrity": "sha512-kfrlnTTn8pZkfpJMUgYD7YZ3qzeJgWUn8XfVYBARc4wnmNOmLbmuuaAs3q5fvB0UJOn6yHAKaGTPM7d6ezoD/A==", "requires": { "available-typed-arrays": "^1.0.5", "call-bind": "^1.0.2", - "es-abstract": "^1.18.5", - "foreach": "^2.0.5", + "es-abstract": "^1.20.0", + "for-each": "^0.3.3", "has-tostringtag": "^1.0.0" } }, @@ -2417,13 +2493,13 @@ "isarray": { "version": "1.0.0", "resolved": "https://registry.npmjs.org/isarray/-/isarray-1.0.0.tgz", - "integrity": "sha1-u5NdSFgsuhaMBoNJV6VKPgcSTxE=", + "integrity": "sha512-VLghIWNM6ELQzo7zwmcg0NmTVyWKYjvIeM83yjp0wRDTmUnrM678fQbcKBo6n2CJEF0szoG//ytg+TKla89ALQ==", "dev": true }, "isexe": { "version": "2.0.0", "resolved": "https://registry.npmjs.org/isexe/-/isexe-2.0.0.tgz", - "integrity": "sha1-6PvzdNxVb/iUehDcsFctYz8s+hA=", + "integrity": "sha512-RHxMLp9lnKHGHRng9QFhRCMbYAcVpn69smSGcq3f36xjgVVWThj4qqLbTLlq7Ssj8B+fIQ1EuCEGI2lKsyQeIw==", "dev": true }, "isobject": { @@ -2433,25 +2509,14 @@ "dev": true }, "jest-worker": { - "version": "27.4.6", - "resolved": "https://registry.npmjs.org/jest-worker/-/jest-worker-27.4.6.tgz", - "integrity": "sha512-gHWJF/6Xi5CTG5QCvROr6GcmpIqNYpDJyc8A1h/DyXqH1tD6SnRCM0d3U5msV31D2LB/U+E0M+W4oyvKV44oNw==", + "version": "27.5.1", + "resolved": "https://registry.npmjs.org/jest-worker/-/jest-worker-27.5.1.tgz", + "integrity": "sha512-7vuh85V5cdDofPyxn58nrPjBktZo0u9x1g8WtjQol+jZDaE+fhN+cIvTj11GndBnMnyfrUOG1sZQxCdjKh+DKg==", "dev": true, "requires": { "@types/node": "*", "merge-stream": "^2.0.0", "supports-color": "^8.0.0" - }, - "dependencies": { - "supports-color": { - "version": "8.1.1", - "resolved": "https://registry.npmjs.org/supports-color/-/supports-color-8.1.1.tgz", - "integrity": "sha512-MpUEN2OodtUzxvKQl72cUF7RQ5EiHsGvSsVG0ia9c5RbWGL2CI4C7EpPS8UTBIplnlzZiNuV56w+FuNxy3ty2Q==", - "dev": true, - "requires": { - "has-flag": "^4.0.0" - } - } } }, "json-parse-better-errors": { @@ -2478,9 +2543,9 @@ "dev": true }, "loader-runner": { - "version": "4.2.0", - "resolved": "https://registry.npmjs.org/loader-runner/-/loader-runner-4.2.0.tgz", - "integrity": "sha512-92+huvxMvYlMzMt0iIOukcwYBFpkYJdpl2xsZ7LrlayO7E8SOv+JJUEK17B/dJIHAOLMfh2dZZ/Y18WgmGtYNw==", + "version": "4.3.0", + "resolved": "https://registry.npmjs.org/loader-runner/-/loader-runner-4.3.0.tgz", + "integrity": "sha512-3R/1M+yS3j5ou80Me59j7F9IMs4PXs3VqRrm0TU3AbKPxlmpoY1TNscJV/oGJXo8qCatFGTfDbY6W6ipGOYXfg==", "dev": true }, "locate-path": { @@ -2519,22 +2584,22 @@ "media-typer": { "version": "0.3.0", "resolved": "https://registry.npmjs.org/media-typer/-/media-typer-0.3.0.tgz", - "integrity": "sha1-hxDXrwqmJvj/+hzgAWhUUmMlV0g=", + "integrity": "sha512-dq+qelQ9akHpcOl/gUVRTxVIOkAJ1wR3QAvb4RsVjS8oVoFjDGTc679wJYmUmknUF5HwMLOgb5O+a3KxfWapPQ==", "dev": true }, "memfs": { - "version": "3.4.1", - "resolved": "https://registry.npmjs.org/memfs/-/memfs-3.4.1.tgz", - "integrity": "sha512-1c9VPVvW5P7I85c35zAdEr1TD5+F11IToIHIlrVIcflfnzPkJa0ZoYEoEdYDP8KgPFoSZ/opDrUsAoZWym3mtw==", + "version": "3.4.6", + "resolved": "https://registry.npmjs.org/memfs/-/memfs-3.4.6.tgz", + "integrity": "sha512-rH9mjopto6Wkr7RFuH9l9dk3qb2XGOcYKr7xMhaYqfzuJqOqhRrcFvfD7JMuPj6SLmPreh5+6eAuv36NFAU+Mw==", "dev": true, "requires": { - "fs-monkey": "1.0.3" + "fs-monkey": "^1.0.3" } }, "merge-descriptors": { "version": "1.0.1", "resolved": "https://registry.npmjs.org/merge-descriptors/-/merge-descriptors-1.0.1.tgz", - "integrity": "sha1-sAqqVW3YtEVoFQ7J0blT8/kMu2E=", + "integrity": "sha512-cCi6g3/Zr1iqQi6ySbseM1Xvooa98N0w31jzUYrXPX2xqObmFGHJ0tQ5u74H3mVh7wLouTseZyYIq39g8cNp1w==", "dev": true }, "merge-stream": { @@ -2552,17 +2617,17 @@ "methods": { "version": "1.1.2", "resolved": "https://registry.npmjs.org/methods/-/methods-1.1.2.tgz", - "integrity": "sha1-VSmk1nZUE07cxSZmVoNbD4Ua/O4=", + "integrity": "sha512-iclAHeNqNm68zFtnZ0e+1L2yUIdvzNoauKU4WBA3VvH/vPFieF7qfRlwUZU+DA9P9bPXIS90ulxoUoCH23sV2w==", "dev": true }, "micromatch": { - "version": "4.0.4", - "resolved": "https://registry.npmjs.org/micromatch/-/micromatch-4.0.4.tgz", - "integrity": "sha512-pRmzw/XUcwXGpD9aI9q/0XOwLNygjETJ8y0ao0wdqprrzDa4YnxLcz7fQRZr8voh8V10kGhABbNcHVk5wHgWwg==", + "version": "4.0.5", + "resolved": "https://registry.npmjs.org/micromatch/-/micromatch-4.0.5.tgz", + "integrity": "sha512-DMy+ERcEW2q8Z2Po+WNXuw3c5YaUSFjAO5GsJqfEl7UjvtIuFKO6ZrKvcItdy98dwFI2N1tg3zNIdKaQT+aNdA==", "dev": true, "requires": { - "braces": "^3.0.1", - "picomatch": "^2.2.3" + "braces": "^3.0.2", + "picomatch": "^2.3.1" } }, "miller-rabin": { @@ -2588,18 +2653,18 @@ "dev": true }, "mime-db": { - "version": "1.51.0", - "resolved": "https://registry.npmjs.org/mime-db/-/mime-db-1.51.0.tgz", - "integrity": "sha512-5y8A56jg7XVQx2mbv1lu49NR4dokRnhZYTtL+KGfaa27uq4pSTXkwQkFJl4pkRMyNFz/EtYDSkiiEHx3F7UN6g==", + "version": "1.52.0", + "resolved": "https://registry.npmjs.org/mime-db/-/mime-db-1.52.0.tgz", + "integrity": "sha512-sPU4uV7dYlvtWJxwwxHD0PuihVNiE7TyAbQ5SWxDCB9mUYvOgroQOwYQQOKPJ8CIbE+1ETVlOoK1UC2nU3gYvg==", "dev": true }, "mime-types": { - "version": "2.1.34", - "resolved": "https://registry.npmjs.org/mime-types/-/mime-types-2.1.34.tgz", - "integrity": "sha512-6cP692WwGIs9XXdOO4++N+7qjqv0rqxxVvJ3VHPh/Sc9mVZcQP+ZGhkKiTvWMQRr2tbHkJP/Yn7Y0npb3ZBs4A==", + "version": "2.1.35", + "resolved": "https://registry.npmjs.org/mime-types/-/mime-types-2.1.35.tgz", + "integrity": "sha512-ZDY+bPm5zTTF+YpCrAU9nK0UgICYPT0QtT1NZWFv4s++TNkcgVaT0g6+4R2uI4MjQjzysHB1zxuWL50hzaeXiw==", "dev": true, "requires": { - "mime-db": "1.51.0" + "mime-db": "1.52.0" } }, "mimic-fn": { @@ -2616,29 +2681,29 @@ "minimalistic-crypto-utils": { "version": "1.0.1", "resolved": "https://registry.npmjs.org/minimalistic-crypto-utils/-/minimalistic-crypto-utils-1.0.1.tgz", - "integrity": "sha1-9sAMHAsIIkblxNmd+4x8CDsrWCo=" + "integrity": "sha512-JIYlbt6g8i5jKfJ3xz7rF0LXmv2TkDxBLUkiBeZ7bAx4GnnNMr8xFpGnOxn6GhTEHx3SjRrZEoU+j04prX1ktg==" }, "minimatch": { - "version": "3.0.4", - "resolved": "https://registry.npmjs.org/minimatch/-/minimatch-3.0.4.tgz", - "integrity": "sha512-yJHVQEhyqPLUTgt9B83PXu6W3rx4MvvHvSUvToogpwoGDOUQ+yDrR0HRot+yOCdCO7u4hX3pWft6kWBBcqh0UA==", + "version": "3.1.2", + "resolved": "https://registry.npmjs.org/minimatch/-/minimatch-3.1.2.tgz", + "integrity": "sha512-J7p63hRiAjw1NDEww1W7i37+ByIrOWO5XQQAzZ3VOcL0PNybwpfmV/N05zFAzwQ9USyEcX6t3UO+K5aqBQOIHw==", "requires": { "brace-expansion": "^1.1.7" } }, "minimist": { - "version": "1.2.5", - "resolved": "https://registry.npmjs.org/minimist/-/minimist-1.2.5.tgz", - "integrity": "sha512-FM9nNUYrRBAELZQT3xeZQ7fmMOBg6nWNmJKTcgsJeaLstP/UODVpGsr5OhXhhXg6f+qtJ8uiZ+PUxkDWcgIXLw==", + "version": "1.2.6", + "resolved": "https://registry.npmjs.org/minimist/-/minimist-1.2.6.tgz", + "integrity": "sha512-Jsjnk4bw3YJqYzbdyBiNsPWHPfO++UGG749Cxs6peCu5Xg4nrena6OVxOYxrQTqww0Jmwt+Ref8rggumkTLz9Q==", "dev": true }, "mkdirp": { - "version": "0.5.5", - "resolved": "https://registry.npmjs.org/mkdirp/-/mkdirp-0.5.5.tgz", - "integrity": "sha512-NKmAlESf6jMGym1++R0Ra7wvhV+wFW63FaSOFPwRahvea0gMUcGUhVeAg/0BC0wiv9ih5NYPB1Wn1UEI1/L+xQ==", + "version": "0.5.6", + "resolved": "https://registry.npmjs.org/mkdirp/-/mkdirp-0.5.6.tgz", + "integrity": "sha512-FP+p8RB8OWpF3YZBCrP5gtADmtXApB5AMLn+vdyA+PyxCjrCs00mjyUozssO33cwDeT3wNGdLxJ5M//YqtHAJw==", "dev": true, "requires": { - "minimist": "^1.2.5" + "minimist": "^1.2.6" } }, "mkdirp-classic": { @@ -2649,7 +2714,7 @@ "ms": { "version": "2.0.0", "resolved": "https://registry.npmjs.org/ms/-/ms-2.0.0.tgz", - "integrity": "sha1-VgiurfwAvmwpAd9fmGF4jeDVl8g=", + "integrity": "sha512-Tpp60P6IUJDTuOq/5Z8cdskzJujfwqfOTkrwIwj7IRISpnkJnT6SyJ4PCPnGMoFjC9ddhal5KVIYtAt97ix05A==", "dev": true }, "multicast-dns": { @@ -2665,7 +2730,7 @@ "multicast-dns-service-types": { "version": "1.1.0", "resolved": "https://registry.npmjs.org/multicast-dns-service-types/-/multicast-dns-service-types-1.1.0.tgz", - "integrity": "sha1-iZ8R2WhuXgXLkbNdXw5jt3PPyQE=", + "integrity": "sha512-cnAsSVxIDsYt0v7HmC0hWZFwwXSh+E6PgCrREDuN/EsjgLwA5XRmlMHhSiDPrt6HxY1gTivEa/Zh7GtODoLevQ==", "dev": true }, "negotiator": { @@ -2696,14 +2761,40 @@ "integrity": "sha512-ZjMPFEfVx5j+y2yF35Kzx5sF7kDzxuDj6ziH4FFbOp87zKDZNx8yExJIb05OGF4Nlt9IHFIMBkRl41VdvcNdbQ==", "requires": { "whatwg-url": "^5.0.0" + }, + "dependencies": { + "tr46": { + "version": "0.0.3", + "resolved": "https://registry.npmjs.org/tr46/-/tr46-0.0.3.tgz", + "integrity": "sha512-N3WMsuqV66lT30CrXNbEjx4GEwlow3v6rr4mCcv6prnfwhS01rkgyFdjPNBYd9br7LpXV1+Emh01fHnq2Gdgrw==" + }, + "webidl-conversions": { + "version": "3.0.1", + "resolved": "https://registry.npmjs.org/webidl-conversions/-/webidl-conversions-3.0.1.tgz", + "integrity": "sha512-2JAn3z8AR6rjK8Sm8orRC0h/bcl/DqL7tRPdGZ4I1CjdF+EaMLmYxBHyXuKL849eucPFhvBoxMsflfOb8kxaeQ==" + }, + "whatwg-url": { + "version": "5.0.0", + "resolved": "https://registry.npmjs.org/whatwg-url/-/whatwg-url-5.0.0.tgz", + "integrity": "sha512-saE57nupxk6v3HY35+jzBwYa0rKSy0XR8JSxZPwgLr7ys0IBzhGviA1/TUGJLmSVqs8pb9AnvICXEuOHLprYTw==", + "requires": { + "tr46": "~0.0.3", + "webidl-conversions": "^3.0.0" + } + } } }, "node-forge": { - "version": "1.2.1", - "resolved": "https://registry.npmjs.org/node-forge/-/node-forge-1.2.1.tgz", - "integrity": "sha512-Fcvtbb+zBcZXbTTVwqGA5W+MKBj56UjVRevvchv5XrcyXbmNdesfZL37nlcWOfpgHhgmxApw3tQbTr4CqNmX4w==", + "version": "1.3.1", + "resolved": "https://registry.npmjs.org/node-forge/-/node-forge-1.3.1.tgz", + "integrity": "sha512-dPEtOeMvF9VMcYV/1Wb8CPoVAXtp6MKMlcbAt4ddqmGqUJ6fQZFXkNZNkNlfevtNkGtaSoXf/vNNNSvgrdXwtA==", "dev": true }, + "node-gyp-build": { + "version": "4.4.0", + "resolved": "https://registry.npmjs.org/node-gyp-build/-/node-gyp-build-4.4.0.tgz", + "integrity": "sha512-amJnQCcgtRVw9SvoebO3BKGESClrfXGCUTX9hSn1OuGQTQBOZmVd0Z0OlecpuRksKvbsUqALE8jls/ErClAPuQ==" + }, "node-polyfill-webpack-plugin": { "version": "1.1.4", "resolved": "https://registry.npmjs.org/node-polyfill-webpack-plugin/-/node-polyfill-webpack-plugin-1.1.4.tgz", @@ -2733,22 +2824,12 @@ "url": "^0.11.0", "util": "^0.12.4", "vm-browserify": "^1.1.2" - }, - "dependencies": { - "string_decoder": { - "version": "1.3.0", - "resolved": "https://registry.npmjs.org/string_decoder/-/string_decoder-1.3.0.tgz", - "integrity": "sha512-hkRX8U1WjJFd8LsDJ2yQ/wWWxaopEsABU1XfkM8A+j0+85JAGppt16cr1Whg6KIbb4okU6Mql6BOj+uup/wKeA==", - "requires": { - "safe-buffer": "~5.2.0" - } - } } }, "node-releases": { - "version": "2.0.1", - "resolved": "https://registry.npmjs.org/node-releases/-/node-releases-2.0.1.tgz", - "integrity": "sha512-CqyzN6z7Q6aMeF/ktcMVTzhAHCEpf8SOarwpzpf8pNBY2k5/oM34UHldUwp8VKI7uxct2HxSRdJjBaZeESzcxA==", + "version": "2.0.5", + "resolved": "https://registry.npmjs.org/node-releases/-/node-releases-2.0.5.tgz", + "integrity": "sha512-U9h1NLROZTq9uE1SNffn6WuPDg8icmi3ns4rEl/oTfIle4iLjTliCzgTsbaIFMq/Xn078/lfY/BL0GWZ+psK4Q==", "dev": true }, "normalize-path": { @@ -2767,18 +2848,18 @@ } }, "nth-check": { - "version": "2.0.1", - "resolved": "https://registry.npmjs.org/nth-check/-/nth-check-2.0.1.tgz", - "integrity": "sha512-it1vE95zF6dTT9lBsYbxvqh0Soy4SPowchj0UBGj/V6cTPnXXtQOPUbhZ6CmGzAD/rW22LQK6E96pcdJXk4A4w==", + "version": "2.1.1", + "resolved": "https://registry.npmjs.org/nth-check/-/nth-check-2.1.1.tgz", + "integrity": "sha512-lqjrjmaOoAnWfMmBPL+XNnynZh2+swxiX3WUE0s4yEHI6m+AwrK2UZOimIRl3X/4QctVqS8AiZjFqyOGrMXb/w==", "dev": true, "requires": { "boolbase": "^1.0.0" } }, "object-inspect": { - "version": "1.12.0", - "resolved": "https://registry.npmjs.org/object-inspect/-/object-inspect-1.12.0.tgz", - "integrity": "sha512-Ho2z80bVIvJloH+YzRmpZVQe87+qASmBUKZDWgx9cu+KDrX2ZDH/3tMy+gXbZETVGs2M8YdxObOh7XAtim9Y0g==" + "version": "1.12.1", + "resolved": "https://registry.npmjs.org/object-inspect/-/object-inspect-1.12.1.tgz", + "integrity": "sha512-Y/jF6vnvEtOPGiKD1+q+X0CiUYRQtEHp89MLLUJ7TUivtH8Ugn2+3A7Rynqk7BRsAoqeOQWnFnjpDrKSxDgIGA==" }, "object-is": { "version": "1.1.5", @@ -2812,9 +2893,9 @@ "dev": true }, "on-finished": { - "version": "2.3.0", - "resolved": "https://registry.npmjs.org/on-finished/-/on-finished-2.3.0.tgz", - "integrity": "sha1-IPEzZIGwg811M3mSoWlxqi2QaUc=", + "version": "2.4.1", + "resolved": "https://registry.npmjs.org/on-finished/-/on-finished-2.4.1.tgz", + "integrity": "sha512-oVlzkg3ENAhCk2zdv7IJwd/QUD4z2RxRwpkcGY8psCVcCYZNq4wYnVWALHM+brtuJjePWiYF/ClmuDr8Ch5+kg==", "dev": true, "requires": { "ee-first": "1.1.1" @@ -2829,7 +2910,7 @@ "once": { "version": "1.4.0", "resolved": "https://registry.npmjs.org/once/-/once-1.4.0.tgz", - "integrity": "sha1-WDsap3WWHUsROsF9nFC6753Xa9E=", + "integrity": "sha512-lNaJgI+2Q5URQBkccEKHTQOPaXdUxnZZElQTZY0MFUAuaEqe1E+Nyvgdz/aIyNi6Z9MzO5dv1H8n58/GELp3+w==", "requires": { "wrappy": "1" } @@ -2857,7 +2938,7 @@ "os-browserify": { "version": "0.3.0", "resolved": "https://registry.npmjs.org/os-browserify/-/os-browserify-0.3.0.tgz", - "integrity": "sha1-hUNzx/XCMVkU/Jv8a9gjj92h7Cc=" + "integrity": "sha512-gjcpUc3clBf9+210TRaDWbf+rZZZEshZ+DlXMRCeAjp0xhTrnQsKHypIy1J3d5hKdUzj69t708EHtU8P6bUn0A==" }, "p-limit": { "version": "2.3.0", @@ -2885,21 +2966,13 @@ } }, "p-retry": { - "version": "4.6.1", - "resolved": "https://registry.npmjs.org/p-retry/-/p-retry-4.6.1.tgz", - "integrity": "sha512-e2xXGNhZOZ0lfgR9kL34iGlU8N/KO0xZnQxVEwdeOvpqNDQfdnxIYizvWtK8RglUa3bGqI8g0R/BdfzLMxRkiA==", + "version": "4.6.2", + "resolved": "https://registry.npmjs.org/p-retry/-/p-retry-4.6.2.tgz", + "integrity": "sha512-312Id396EbJdvRONlngUx0NydfrIQ5lsYu0znKVUzVvArzEIt08V1qhtyESbGVd1FGX7UKtiFp5uwKZdM8wIuQ==", "dev": true, "requires": { - "@types/retry": "^0.12.0", + "@types/retry": "0.12.0", "retry": "^0.13.1" - }, - "dependencies": { - "retry": { - "version": "0.13.1", - "resolved": "https://registry.npmjs.org/retry/-/retry-0.13.1.tgz", - "integrity": "sha512-XQBQ3I8W1Cge0Seh+6gjj03LbmRFWuoszgK9ooCpwYIrhhoO80pfq4cUkU5DkknwfOfFteRwlZ56PYOGYyFWdg==", - "dev": true - } } }, "p-try": { @@ -2963,7 +3036,7 @@ "path-is-absolute": { "version": "1.0.1", "resolved": "https://registry.npmjs.org/path-is-absolute/-/path-is-absolute-1.0.1.tgz", - "integrity": "sha1-F0uSaHNVNP+8es5r9TpanhtcX18=" + "integrity": "sha512-AVbw3UJ2e9bq64vSaS9Am0fje1Pa8pbGqTTsmXfaIiMpnr5DlDhfJOuLj9Sf95ZPVDAUerDfEk88MPmPe7UCQg==" }, "path-key": { "version": "3.1.1", @@ -2980,7 +3053,7 @@ "path-to-regexp": { "version": "0.1.7", "resolved": "https://registry.npmjs.org/path-to-regexp/-/path-to-regexp-0.1.7.tgz", - "integrity": "sha1-32BBeABfUi8V60SQ5yR6G/qmf4w=", + "integrity": "sha512-5DFkuoqlv1uYQKxy8omFBeJPQcdoE07Kv2sferDCrAq1ohOU+MSDswDIbnx3YAM60qIOnYa53wBhXW0EbMonrQ==", "dev": true }, "path-type": { @@ -3067,7 +3140,7 @@ "process": { "version": "0.11.10", "resolved": "https://registry.npmjs.org/process/-/process-0.11.10.tgz", - "integrity": "sha1-czIwDoQBYb2j5podHZGn1LwW8YI=" + "integrity": "sha512-cdGef/drWFoydD1JsMzuFf8100nZl+GT+yacc2bEced5f9Rjk4z+WtFUTBu9PhOi9j/jfmBPu0mMEY4wIdAF8A==" }, "process-nextick-args": { "version": "2.0.1", @@ -3138,13 +3211,13 @@ "integrity": "sha512-XRsRjdf+j5ml+y/6GKHPZbrF/8p2Yga0JPtdqTIY2Xe5ohJPD9saDJJLPvp9+NSBprVvevdXZybnj2cv8OEd0A==" }, "puppeteer-core": { - "version": "15.5.0", - "resolved": "https://registry.npmjs.org/puppeteer-core/-/puppeteer-core-15.5.0.tgz", - "integrity": "sha512-5Q8EmF++MARczJD1JcRehVePlctxGG2TFHSxdCV8NqPOk44/cMySmZw2nETn+lwUOyp0L9afosMFTnT4KgmWgw==", + "version": "15.3.2", + "resolved": "https://registry.npmjs.org/puppeteer-core/-/puppeteer-core-15.3.2.tgz", + "integrity": "sha512-Fmca9UzXmJkRrvGBgUmrffGD2BlulUTfsVefV1+vqfNm4PnlZ/U1bfD6X8XQ0nftyyg520tmSKd81yH3Z2tszg==", "requires": { "cross-fetch": "3.1.5", "debug": "4.3.4", - "devtools-protocol": "0.0.1019158", + "devtools-protocol": "0.0.1011705", "extract-zip": "2.0.1", "https-proxy-agent": "5.0.1", "pkg-dir": "4.2.0", @@ -3177,20 +3250,23 @@ } }, "qs": { - "version": "6.9.6", - "resolved": "https://registry.npmjs.org/qs/-/qs-6.9.6.tgz", - "integrity": "sha512-TIRk4aqYLNoJUbd+g2lEdz5kLWIuTMRagAXxl78Q0RiVjAOugHmeKNGdd3cwo/ktpf9aL9epCfFqWDEKysUlLQ==", - "dev": true + "version": "6.10.3", + "resolved": "https://registry.npmjs.org/qs/-/qs-6.10.3.tgz", + "integrity": "sha512-wr7M2E0OFRfIfJZjKGieI8lBKb7fRCH4Fv5KNPEs7gJ8jadvotdsS08PzOKR7opXhZ/Xkjtt3WF9g38drmyRqQ==", + "dev": true, + "requires": { + "side-channel": "^1.0.4" + } }, "querystring": { "version": "0.2.0", "resolved": "https://registry.npmjs.org/querystring/-/querystring-0.2.0.tgz", - "integrity": "sha1-sgmEkgO7Jd+CDadW50cAWHhSFiA=" + "integrity": "sha512-X/xY82scca2tau62i9mDyU9K+I+djTMUsvwf7xnUX5GLvVzgJybOJf4Y6o9Zx3oJK/LSXg5tTZBjwzqVPaPO2g==" }, "querystring-es3": { "version": "0.2.1", "resolved": "https://registry.npmjs.org/querystring-es3/-/querystring-es3-0.2.1.tgz", - "integrity": "sha1-nsYfeQSYdXB9aUFFlv2Qek1xHnM=" + "integrity": "sha512-773xhDQnZBMFobEiztv8LIl70ch5MSF/jUQVlhwFyBILqq96anmoctVIYz+ZRp0qbCKATTn6ev02M3r7Ga5vqA==" }, "queue-microtask": { "version": "1.2.3", @@ -3222,21 +3298,21 @@ "dev": true }, "raw-body": { - "version": "2.4.2", - "resolved": "https://registry.npmjs.org/raw-body/-/raw-body-2.4.2.tgz", - "integrity": "sha512-RPMAFUJP19WIet/99ngh6Iv8fzAbqum4Li7AD6DtGaW2RpMB/11xDoalPiJMTbu6I3hkbMVkATvZrqb9EEqeeQ==", + "version": "2.5.1", + "resolved": "https://registry.npmjs.org/raw-body/-/raw-body-2.5.1.tgz", + "integrity": "sha512-qqJBtEyVgS0ZmPGdCFPWJ3FreoqvG4MVQln/kCgF7Olq95IbOp0/BWyMwbdtn4VTvkM8Y7khCQ2Xgk/tcrCXig==", "dev": true, "requires": { - "bytes": "3.1.1", - "http-errors": "1.8.1", + "bytes": "3.1.2", + "http-errors": "2.0.0", "iconv-lite": "0.4.24", "unpipe": "1.0.0" }, "dependencies": { "bytes": { - "version": "3.1.1", - "resolved": "https://registry.npmjs.org/bytes/-/bytes-3.1.1.tgz", - "integrity": "sha512-dWe4nWO/ruEOY7HkUJ5gFt1DCFV9zPRoJr8pV0/ASQermOZjtq8jMjOprC0Kd10GLN+l7xaUPvxzJFWtxGu8Fg==", + "version": "3.1.2", + "resolved": "https://registry.npmjs.org/bytes/-/bytes-3.1.2.tgz", + "integrity": "sha512-/Nf7TyzTx6S3yRJObOAV7956r8cr2+Oj8AC5dt8wSP3BQAoeX58NoHyCU8P8zGkNXStjTSi6fzO6F0pBdcYbEg==", "dev": true } } @@ -3275,19 +3351,19 @@ "integrity": "sha512-D2E33ceRPga0NvTDhJmphEgJ7FUYF0v4lr1ki0csq06OdlxKfugGzN0dSkxM/NfqCxYELK4KcaTOUOjTV6Dcng==" }, "regexp.prototype.flags": { - "version": "1.4.1", - "resolved": "https://registry.npmjs.org/regexp.prototype.flags/-/regexp.prototype.flags-1.4.1.tgz", - "integrity": "sha512-pMR7hBVUUGI7PMA37m2ofIdQCsomVnas+Jn5UPGAHQ+/LlwKm/aTLJHdasmHRzlfeZwHiAOaRSo2rbBDm3nNUQ==", - "dev": true, + "version": "1.4.3", + "resolved": "https://registry.npmjs.org/regexp.prototype.flags/-/regexp.prototype.flags-1.4.3.tgz", + "integrity": "sha512-fjggEOO3slI6Wvgjwflkc4NFRCTZAu5CnNfBd5qOMYhWdn67nJBBu34/TkD++eeFmd8C9r9jfXJ27+nSiRkSUA==", "requires": { "call-bind": "^1.0.2", - "define-properties": "^1.1.3" + "define-properties": "^1.1.3", + "functions-have-names": "^1.2.2" } }, "relateurl": { "version": "0.2.7", "resolved": "https://registry.npmjs.org/relateurl/-/relateurl-0.2.7.tgz", - "integrity": "sha1-VNvzd+UUQKypCkzSdGANP/LYiKk=", + "integrity": "sha512-G08Dxvm4iDN3MLM0EsP62EDV9IuhXPR6blNz6Utcp7zyV3tr4HVNINt6MpaRWbxoOHT3Q7YN2P+jaHX8vUbgog==", "dev": true }, "renderkid": { @@ -3312,7 +3388,7 @@ "requires-port": { "version": "1.0.0", "resolved": "https://registry.npmjs.org/requires-port/-/requires-port-1.0.0.tgz", - "integrity": "sha1-kl0mAdOaxIXgkc8NpcbmlNw9yv8=", + "integrity": "sha512-KigOCHcocU3XODJxsu8i/j8T9tzT4adHiecwORRQ0ZZFcp7ahwXuRU1m+yuO90C5ZUyGeGfocHDI14M3L3yDAQ==", "dev": true }, "resolve": { @@ -3341,6 +3417,12 @@ "integrity": "sha512-qYg9KP24dD5qka9J47d0aVky0N+b4fTU89LN9iDnjB5waksiC49rvMB0PrUJQGoTmH50XPiqOvAjDfaijGxYZw==", "dev": true }, + "retry": { + "version": "0.13.1", + "resolved": "https://registry.npmjs.org/retry/-/retry-0.13.1.tgz", + "integrity": "sha512-XQBQ3I8W1Cge0Seh+6gjj03LbmRFWuoszgK9ooCpwYIrhhoO80pfq4cUkU5DkknwfOfFteRwlZ56PYOGYyFWdg==", + "dev": true + }, "reusify": { "version": "1.0.4", "resolved": "https://registry.npmjs.org/reusify/-/reusify-1.0.4.tgz", @@ -3353,21 +3435,6 @@ "integrity": "sha512-JZkJMZkAGFFPP2YqXZXPbMlMBgsxzE8ILs4lMIX/2o0L9UBw9O/Y3o6wFw/i9YLapcUJWwqbi3kdxIPdC62TIA==", "requires": { "glob": "^7.1.3" - }, - "dependencies": { - "glob": { - "version": "7.2.0", - "resolved": "https://registry.npmjs.org/glob/-/glob-7.2.0.tgz", - "integrity": "sha512-lmLf6gtyrPq8tTjSmrO94wBeQbFR3HbLHbuyD69wuyQkImp2hWqMGB47OX65FBkPffO641IP9jWa1z4ivqG26Q==", - "requires": { - "fs.realpath": "^1.0.0", - "inflight": "^1.0.4", - "inherits": "2", - "minimatch": "^3.0.4", - "once": "^1.3.0", - "path-is-absolute": "^1.0.0" - } - } } }, "ripemd160": { @@ -3412,37 +3479,37 @@ "select-hose": { "version": "2.0.0", "resolved": "https://registry.npmjs.org/select-hose/-/select-hose-2.0.0.tgz", - "integrity": "sha1-Yl2GWPhlr0Psliv8N2o3NZpJlMo=", + "integrity": "sha512-mEugaLK+YfkijB4fx0e6kImuJdCIt2LxCRcbEYPqRGCs4F2ogyfZU5IAZRdjCP8JPq2AtdNoC/Dux63d9Kiryg==", "dev": true }, "selfsigned": { - "version": "2.0.0", - "resolved": "https://registry.npmjs.org/selfsigned/-/selfsigned-2.0.0.tgz", - "integrity": "sha512-cUdFiCbKoa1mZ6osuJs2uDHrs0k0oprsKveFiiaBKCNq3SYyb5gs2HxhQyDNLCmL51ZZThqi4YNDpCK6GOP1iQ==", + "version": "2.0.1", + "resolved": "https://registry.npmjs.org/selfsigned/-/selfsigned-2.0.1.tgz", + "integrity": "sha512-LmME957M1zOsUhG+67rAjKfiWFox3SBxE/yymatMZsAx+oMrJ0YQ8AToOnyCm7xbeg2ep37IHLxdu0o2MavQOQ==", "dev": true, "requires": { - "node-forge": "^1.2.0" + "node-forge": "^1" } }, "send": { - "version": "0.17.2", - "resolved": "https://registry.npmjs.org/send/-/send-0.17.2.tgz", - "integrity": "sha512-UJYB6wFSJE3G00nEivR5rgWp8c2xXvJ3OPWPhmuteU0IKj8nKbG3DrjiOmLwpnHGYWAVwA69zmTm++YG0Hmwww==", + "version": "0.18.0", + "resolved": "https://registry.npmjs.org/send/-/send-0.18.0.tgz", + "integrity": "sha512-qqWzuOjSFOuqPjFe4NOsMLafToQQwBSOEpS+FwEt3A2V3vKubTquT3vmLTQpFgMXp8AlFWFuP1qKaJZOtPpVXg==", "dev": true, "requires": { "debug": "2.6.9", - "depd": "~1.1.2", - "destroy": "~1.0.4", + "depd": "2.0.0", + "destroy": "1.2.0", "encodeurl": "~1.0.2", "escape-html": "~1.0.3", "etag": "~1.8.1", "fresh": "0.5.2", - "http-errors": "1.8.1", + "http-errors": "2.0.0", "mime": "1.6.0", "ms": "2.1.3", - "on-finished": "~2.3.0", + "on-finished": "2.4.1", "range-parser": "~1.2.1", - "statuses": "~1.5.0" + "statuses": "2.0.1" }, "dependencies": { "ms": { @@ -3465,7 +3532,7 @@ "serve-index": { "version": "1.9.1", "resolved": "https://registry.npmjs.org/serve-index/-/serve-index-1.9.1.tgz", - "integrity": "sha1-03aNabHn2C5c4FD/9bRTvqEqkjk=", + "integrity": "sha512-pXHfKNP4qujrtteMrSBb0rc8HJ9Ms/GrXwcUtUtD5s4ewDJI8bT3Cz2zTVRMKtri49pLx2e0Ya8ziP5Ya2pZZw==", "dev": true, "requires": { "accepts": "~1.3.4", @@ -3477,10 +3544,16 @@ "parseurl": "~1.3.2" }, "dependencies": { + "depd": { + "version": "1.1.2", + "resolved": "https://registry.npmjs.org/depd/-/depd-1.1.2.tgz", + "integrity": "sha512-7emPTl6Dpo6JRXOXjLRxck+FlLRX5847cLKEn00PLAgc3g2hTZZgr+e4c2v6QpSmLeFP3n5yUo7ft6avBK/5jQ==", + "dev": true + }, "http-errors": { "version": "1.6.3", "resolved": "https://registry.npmjs.org/http-errors/-/http-errors-1.6.3.tgz", - "integrity": "sha1-i1VoC7S+KDoLW/TqLjhYC+HZMg0=", + "integrity": "sha512-lks+lVC8dgGyh97jxvxeYTWQFvh4uw4yC12gVl63Cg30sjPX4wuGcdkICVXDAESr6OJGjqGA8Iz5mkeN6zlD7A==", "dev": true, "requires": { "depd": "~1.1.2", @@ -3492,7 +3565,7 @@ "inherits": { "version": "2.0.3", "resolved": "https://registry.npmjs.org/inherits/-/inherits-2.0.3.tgz", - "integrity": "sha1-Yzwsg+PaQqUC9SRmAiSA9CCCYd4=", + "integrity": "sha512-x00IRNXNy63jwGkJmzPigoySHbaqpNuzKbBOmzK+g2OdZpQ9w+sxCN+VSB3ja7IAge2OP2qpfxTjeNcyjmW1uw==", "dev": true }, "setprototypeof": { @@ -3500,25 +3573,31 @@ "resolved": "https://registry.npmjs.org/setprototypeof/-/setprototypeof-1.1.0.tgz", "integrity": "sha512-BvE/TwpZX4FXExxOxZyRGQQv651MSwmWKZGqvmPcRIjDqWub67kTKuIMx43cZZrS/cBBzwBcNDWoFxt2XEFIpQ==", "dev": true + }, + "statuses": { + "version": "1.5.0", + "resolved": "https://registry.npmjs.org/statuses/-/statuses-1.5.0.tgz", + "integrity": "sha512-OpZ3zP+jT1PI7I8nemJX4AKmAX070ZkYPVWV/AaKTJl+tXCTGyVdC1a4SL8RUQYEwk/f34ZX8UTykN68FwrqAA==", + "dev": true } } }, "serve-static": { - "version": "1.14.2", - "resolved": "https://registry.npmjs.org/serve-static/-/serve-static-1.14.2.tgz", - "integrity": "sha512-+TMNA9AFxUEGuC0z2mevogSnn9MXKb4fa7ngeRMJaaGv8vTwnIEkKi+QGvPt33HSnf8pRS+WGM0EbMtCJLKMBQ==", + "version": "1.15.0", + "resolved": "https://registry.npmjs.org/serve-static/-/serve-static-1.15.0.tgz", + "integrity": "sha512-XGuRDNjXUijsUL0vl6nSD7cwURuzEgglbOaFuZM9g3kwDXOWVTck0jLzjPzGD+TazWbboZYu52/9/XPdUgne9g==", "dev": true, "requires": { "encodeurl": "~1.0.2", "escape-html": "~1.0.3", "parseurl": "~1.3.3", - "send": "0.17.2" + "send": "0.18.0" } }, "setimmediate": { "version": "1.0.5", "resolved": "https://registry.npmjs.org/setimmediate/-/setimmediate-1.0.5.tgz", - "integrity": "sha1-KQy7Iy4waULX1+qbg3Mqt4VvgoU=" + "integrity": "sha512-MATJdZp8sLqDl/68LfQmbP8zKPLQNV6BIZoIgrscFDQ+RsvK/BxeDQOgyxKKoh0y/8h3BqVFnCqQ/gd+reiIXA==" }, "setprototypeof": { "version": "1.2.0", @@ -3570,9 +3649,9 @@ } }, "signal-exit": { - "version": "3.0.6", - "resolved": "https://registry.npmjs.org/signal-exit/-/signal-exit-3.0.6.tgz", - "integrity": "sha512-sDl4qMFpijcGw22U5w63KmD3cZJfBuFlVNbVMKje2keoKML7X2UzWbc4XrmEbDwg0NXJc3yv4/ox7b+JWb57kQ==", + "version": "3.0.7", + "resolved": "https://registry.npmjs.org/signal-exit/-/signal-exit-3.0.7.tgz", + "integrity": "sha512-wnD2ZE+l+SPC/uoS0vXeE9L1+0wuaMqKlfz9AMUo38JsyLSBWSFcHR1Rri62LZc12vLr1gb3jl7iwQhgwpAbGQ==", "dev": true }, "slash": { @@ -3622,9 +3701,9 @@ }, "dependencies": { "debug": { - "version": "4.3.3", - "resolved": "https://registry.npmjs.org/debug/-/debug-4.3.3.tgz", - "integrity": "sha512-/zxw5+vh1Tfv+4Qn7a5nsbcJKPaSvCDhojn6FEl9vupwK2VCSDtEiEtqr8DFtzYFOdz63LBkxec7DYuc2jon6Q==", + "version": "4.3.4", + "resolved": "https://registry.npmjs.org/debug/-/debug-4.3.4.tgz", + "integrity": "sha512-PRWFHuSU3eDtQJPvnNY7Jcket1j0t5OuOsFzPPzsekD52Zl8qUfFIPEiswXqIvHWGVHOgX+7G/vCNNhehwxfkQ==", "dev": true, "requires": { "ms": "2.1.2" @@ -3653,9 +3732,9 @@ }, "dependencies": { "debug": { - "version": "4.3.3", - "resolved": "https://registry.npmjs.org/debug/-/debug-4.3.3.tgz", - "integrity": "sha512-/zxw5+vh1Tfv+4Qn7a5nsbcJKPaSvCDhojn6FEl9vupwK2VCSDtEiEtqr8DFtzYFOdz63LBkxec7DYuc2jon6Q==", + "version": "4.3.4", + "resolved": "https://registry.npmjs.org/debug/-/debug-4.3.4.tgz", + "integrity": "sha512-PRWFHuSU3eDtQJPvnNY7Jcket1j0t5OuOsFzPPzsekD52Zl8qUfFIPEiswXqIvHWGVHOgX+7G/vCNNhehwxfkQ==", "dev": true, "requires": { "ms": "2.1.2" @@ -3670,9 +3749,9 @@ } }, "statuses": { - "version": "1.5.0", - "resolved": "https://registry.npmjs.org/statuses/-/statuses-1.5.0.tgz", - "integrity": "sha1-Fhx9rBd2Wf2YEfQ3cfqZOBR4Yow=", + "version": "2.0.1", + "resolved": "https://registry.npmjs.org/statuses/-/statuses-2.0.1.tgz", + "integrity": "sha512-RwNA9Z/7PrK06rYLIzFMlaF+l73iwpzsqRIFgbMLbTcLD6cOao82TaWefPXQvB2fOC4AjuYSEndS7N/mTCbkdQ==", "dev": true }, "stream-browserify": { @@ -3696,36 +3775,31 @@ } }, "string.prototype.trimend": { - "version": "1.0.4", - "resolved": "https://registry.npmjs.org/string.prototype.trimend/-/string.prototype.trimend-1.0.4.tgz", - "integrity": "sha512-y9xCjw1P23Awk8EvTpcyL2NIr1j7wJ39f+k6lvRnSMz+mz9CGz9NYPelDk42kOz6+ql8xjfK8oYzy3jAP5QU5A==", + "version": "1.0.5", + "resolved": "https://registry.npmjs.org/string.prototype.trimend/-/string.prototype.trimend-1.0.5.tgz", + "integrity": "sha512-I7RGvmjV4pJ7O3kdf+LXFpVfdNOxtCW/2C8f6jNiW4+PQchwxkCDzlk1/7p+Wl4bqFIZeF47qAHXLuHHWKAxog==", "requires": { "call-bind": "^1.0.2", - "define-properties": "^1.1.3" + "define-properties": "^1.1.4", + "es-abstract": "^1.19.5" } }, "string.prototype.trimstart": { - "version": "1.0.4", - "resolved": "https://registry.npmjs.org/string.prototype.trimstart/-/string.prototype.trimstart-1.0.4.tgz", - "integrity": "sha512-jh6e984OBfvxS50tdY2nRZnoC5/mLFKOREQfw8t5yytkoUsJRNxvI/E39qu1sD0OtWI3OC0XgKSmcWwziwYuZw==", + "version": "1.0.5", + "resolved": "https://registry.npmjs.org/string.prototype.trimstart/-/string.prototype.trimstart-1.0.5.tgz", + "integrity": "sha512-THx16TJCGlsN0o6dl2o6ncWUsdgnLRSA23rRE5pyGBw/mLr3Ej/R2LaqCtgP8VNMGZsvMWnf9ooZPyY2bHvUFg==", "requires": { "call-bind": "^1.0.2", - "define-properties": "^1.1.3" + "define-properties": "^1.1.4", + "es-abstract": "^1.19.5" } }, "string_decoder": { - "version": "1.1.1", - "resolved": "https://registry.npmjs.org/string_decoder/-/string_decoder-1.1.1.tgz", - "integrity": "sha512-n/ShnvDi6FHbbVfviro+WojiFzv+s8MPMHBczVePfUpDJLwoLT0ht1l4YwBCbi8pJAveEEdnkHyPyTP/mzRfwg==", + "version": "1.3.0", + "resolved": "https://registry.npmjs.org/string_decoder/-/string_decoder-1.3.0.tgz", + "integrity": "sha512-hkRX8U1WjJFd8LsDJ2yQ/wWWxaopEsABU1XfkM8A+j0+85JAGppt16cr1Whg6KIbb4okU6Mql6BOj+uup/wKeA==", "requires": { - "safe-buffer": "~5.1.0" - }, - "dependencies": { - "safe-buffer": { - "version": "5.1.2", - "resolved": "https://registry.npmjs.org/safe-buffer/-/safe-buffer-5.1.2.tgz", - "integrity": "sha512-Gd2UZBJDkXlY7GbJxfsE8/nvKkUEU1G38c1siN6QP6a9PT9MmHB8GnpscSmMJSoF8LOIrt8ud/wPtojys4G6+g==" - } + "safe-buffer": "~5.2.0" } }, "strip-ansi": { @@ -3743,6 +3817,15 @@ "integrity": "sha512-BrpvfNAE3dcvq7ll3xVumzjKjZQ5tI1sEUIKr3Uoks0XUl45St3FlatVqef9prk4jRDzhW6WZg+3bk93y6pLjA==", "dev": true }, + "supports-color": { + "version": "8.1.1", + "resolved": "https://registry.npmjs.org/supports-color/-/supports-color-8.1.1.tgz", + "integrity": "sha512-MpUEN2OodtUzxvKQl72cUF7RQ5EiHsGvSsVG0ia9c5RbWGL2CI4C7EpPS8UTBIplnlzZiNuV56w+FuNxy3ty2Q==", + "dev": true, + "requires": { + "has-flag": "^4.0.0" + } + }, "supports-preserve-symlinks-flag": { "version": "1.0.0", "resolved": "https://registry.npmjs.org/supports-preserve-symlinks-flag/-/supports-preserve-symlinks-flag-1.0.0.tgz", @@ -3779,13 +3862,14 @@ } }, "terser": { - "version": "5.10.0", - "resolved": "https://registry.npmjs.org/terser/-/terser-5.10.0.tgz", - "integrity": "sha512-AMmF99DMfEDiRJfxfY5jj5wNH/bYO09cniSqhfoyxc8sFoYIgkJy86G04UoZU5VjlpnplVu0K6Tx6E9b5+DlHA==", + "version": "5.15.1", + "resolved": "https://registry.npmjs.org/terser/-/terser-5.15.1.tgz", + "integrity": "sha512-K1faMUvpm/FBxjBXud0LWVAGxmvoPbZbfTCYbSgaaYQaIXI3/TdI7a7ZGA73Zrou6Q8Zmz3oeUTsp/dj+ag2Xw==", "dev": true, "requires": { + "@jridgewell/source-map": "^0.3.2", + "acorn": "^8.5.0", "commander": "^2.20.0", - "source-map": "~0.7.2", "source-map-support": "~0.5.20" }, "dependencies": { @@ -3794,25 +3878,19 @@ "resolved": "https://registry.npmjs.org/commander/-/commander-2.20.3.tgz", "integrity": "sha512-GpVkmM8vF2vQUkj2LvZmD35JxeJOLCwJ9cUkugyk2nuhbv3+mJvpLYYt+0+USMxE+oj+ey/lJEnhZw75x/OMcQ==", "dev": true - }, - "source-map": { - "version": "0.7.3", - "resolved": "https://registry.npmjs.org/source-map/-/source-map-0.7.3.tgz", - "integrity": "sha512-CkCj6giN3S+n9qrYiBTX5gystlENnRW5jZeNLHpe6aue+SrHcG5VYwujhW9s4dY31mEGsxBDrHR6oI69fTXsaQ==", - "dev": true } } }, "terser-webpack-plugin": { - "version": "5.3.1", - "resolved": "https://registry.npmjs.org/terser-webpack-plugin/-/terser-webpack-plugin-5.3.1.tgz", - "integrity": "sha512-GvlZdT6wPQKbDNW/GDQzZFg/j4vKU96yl2q6mcUkzKOgW4gwf1Z8cZToUCrz31XHlPWH8MVb1r2tFtdDtTGJ7g==", + "version": "5.3.3", + "resolved": "https://registry.npmjs.org/terser-webpack-plugin/-/terser-webpack-plugin-5.3.3.tgz", + "integrity": "sha512-Fx60G5HNYknNTNQnzQ1VePRuu89ZVYWfjRAeT5rITuCY/1b08s49e5kSQwHDirKZWuoKOBRFS98EUUoZ9kLEwQ==", "dev": true, "requires": { + "@jridgewell/trace-mapping": "^0.3.7", "jest-worker": "^27.4.5", "schema-utils": "^3.1.1", "serialize-javascript": "^6.0.0", - "source-map": "^0.6.1", "terser": "^5.7.2" } }, @@ -3850,15 +3928,10 @@ "integrity": "sha512-o5sSPKEkg/DIQNmH43V0/uerLrpzVedkUh8tGNvaeXpfpuwjKenlSox/2O/BTlZUtEe+JG7s5YhEz608PlAHRA==", "dev": true }, - "tr46": { - "version": "0.0.3", - "resolved": "https://registry.npmjs.org/tr46/-/tr46-0.0.3.tgz", - "integrity": "sha512-N3WMsuqV66lT30CrXNbEjx4GEwlow3v6rr4mCcv6prnfwhS01rkgyFdjPNBYd9br7LpXV1+Emh01fHnq2Gdgrw==" - }, "tslib": { - "version": "2.3.1", - "resolved": "https://registry.npmjs.org/tslib/-/tslib-2.3.1.tgz", - "integrity": "sha512-77EbyPPpMz+FRFRuAFlWMtmgUWGe9UOG2Z25NqCwiIjRhOf5iKGuzSe5P2w1laq+FkRy4p+PCuVkJSGkzTEKVw==", + "version": "2.4.0", + "resolved": "https://registry.npmjs.org/tslib/-/tslib-2.4.0.tgz", + "integrity": "sha512-d6xOpEDfsi2CZVlPQzGeux8XMwLT9hssAsaPYExaQMuYskwb+x1x7J371tWlbBdWHroy99KnVB6qIkUbs5X3UQ==", "dev": true }, "tty-browserify": { @@ -3877,13 +3950,13 @@ } }, "unbox-primitive": { - "version": "1.0.1", - "resolved": "https://registry.npmjs.org/unbox-primitive/-/unbox-primitive-1.0.1.tgz", - "integrity": "sha512-tZU/3NqK3dA5gpE1KtyiJUrEB0lxnGkMFHptJ7q6ewdZ8s12QrODwNbhIJStmJkd1QDXa1NRA8aF2A1zk/Ypyw==", + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/unbox-primitive/-/unbox-primitive-1.0.2.tgz", + "integrity": "sha512-61pPlCD9h51VoreyJ0BReideM3MDKMKnh6+V9L08331ipq6Q8OFXZYiqP6n/tbHx4s5I9uRhcye6BrbkizkBDw==", "requires": { - "function-bind": "^1.1.1", - "has-bigints": "^1.0.1", - "has-symbols": "^1.0.2", + "call-bind": "^1.0.2", + "has-bigints": "^1.0.2", + "has-symbols": "^1.0.3", "which-boxed-primitive": "^1.0.2" } }, @@ -3915,9 +3988,19 @@ "unpipe": { "version": "1.0.0", "resolved": "https://registry.npmjs.org/unpipe/-/unpipe-1.0.0.tgz", - "integrity": "sha1-sr9O6FFKrmFltIF4KdIbLvSZBOw=", + "integrity": "sha512-pjy2bYhSsufwWlKwPc+l3cN7+wuJlK6uz0YdJEOlQDbl6jo/YlPi4mb8agUkVC8BF7V8NuzeyPNqRksA3hztKQ==", "dev": true }, + "update-browserslist-db": { + "version": "1.0.3", + "resolved": "https://registry.npmjs.org/update-browserslist-db/-/update-browserslist-db-1.0.3.tgz", + "integrity": "sha512-ufSazemeh9Gty0qiWtoRpJ9F5Q5W3xdIPm1UZQqYQv/q0Nyb9EMHUB2lu+O9x1re9WsorpMAUu4Y6Lxcs5n+XQ==", + "dev": true, + "requires": { + "escalade": "^3.1.1", + "picocolors": "^1.0.0" + } + }, "uri-js": { "version": "4.4.1", "resolved": "https://registry.npmjs.org/uri-js/-/uri-js-4.4.1.tgz", @@ -3930,7 +4013,7 @@ "url": { "version": "0.11.0", "resolved": "https://registry.npmjs.org/url/-/url-0.11.0.tgz", - "integrity": "sha1-ODjpfPxgUh63PFJajlW/3Z4uKPE=", + "integrity": "sha512-kbailJa29QrtXnxgq+DdCEGlbTeYM2eJUxsz6vjZavrCYPMIFHMKQmSKYAIuUK2i7hgPm28a8piX5NTUtM/LKQ==", "requires": { "punycode": "1.3.2", "querystring": "0.2.0" @@ -3939,7 +4022,7 @@ "punycode": { "version": "1.3.2", "resolved": "https://registry.npmjs.org/punycode/-/punycode-1.3.2.tgz", - "integrity": "sha1-llOgNvt8HuQjQvIyXM7v6jkmxI0=" + "integrity": "sha512-RofWgt/7fL5wP1Y7fxE7/EmTLzQVnB0ycyibJ0OOHIlJqTNzglYFxVwETOcIoJqJmpDXJ9xImDv+Fq34F/d4Dw==" } } }, @@ -3959,18 +4042,18 @@ "util-deprecate": { "version": "1.0.2", "resolved": "https://registry.npmjs.org/util-deprecate/-/util-deprecate-1.0.2.tgz", - "integrity": "sha1-RQ1Nyfpw3nMnYvvS1KKJgUGaDM8=" + "integrity": "sha512-EPD5q1uXyFxJpCrLnCc1nHnq3gOa6DZBocAIiI2TaSCA7VCJ1UJDMagCzIkXNsUYfD1daK//LTEQ8xiIbrHtcw==" }, "utila": { "version": "0.4.0", "resolved": "https://registry.npmjs.org/utila/-/utila-0.4.0.tgz", - "integrity": "sha1-ihagXURWV6Oupe7MWxKk+lN5dyw=", + "integrity": "sha512-Z0DbgELS9/L/75wZbro8xAnT50pBVFQZ+hUEueGDU5FN51YSCYM+jdxsfCiHjwNP/4LCDD0i/graKpeBnOXKRA==", "dev": true }, "utils-merge": { "version": "1.0.1", "resolved": "https://registry.npmjs.org/utils-merge/-/utils-merge-1.0.1.tgz", - "integrity": "sha1-n5VxD1CiZ5R7LMwSR0HBAoQn5xM=", + "integrity": "sha512-pMZTvIkT1d+TFGvDOqodOclx0QWkkgi6Tdoa8gC8ffGAAqz9pzPTZWAybbsHHoED/ztMtkv/VoYTYyShUn81hA==", "dev": true }, "uuid": { @@ -3982,7 +4065,7 @@ "vary": { "version": "1.1.2", "resolved": "https://registry.npmjs.org/vary/-/vary-1.1.2.tgz", - "integrity": "sha1-IpnwLG3tMNSllhsLn3RSShj2NPw=", + "integrity": "sha512-BNGbWLfd0eUPabhkXUVm0j8uuvREyTh5ovRa/dyow/BqAbZJyC+5fU+IzQOzmAKzYqYRAISoRhdQr3eIZ/PXqg==", "dev": true }, "vm-browserify": { @@ -4009,11 +4092,6 @@ "minimalistic-assert": "^1.0.0" } }, - "webidl-conversions": { - "version": "3.0.1", - "resolved": "https://registry.npmjs.org/webidl-conversions/-/webidl-conversions-3.0.1.tgz", - "integrity": "sha512-2JAn3z8AR6rjK8Sm8orRC0h/bcl/DqL7tRPdGZ4I1CjdF+EaMLmYxBHyXuKL849eucPFhvBoxMsflfOb8kxaeQ==" - }, "webpack": { "version": "5.67.0", "resolved": "https://registry.npmjs.org/webpack/-/webpack-5.67.0.tgz", @@ -4075,22 +4153,22 @@ } }, "webpack-dev-middleware": { - "version": "5.3.1", - "resolved": "https://registry.npmjs.org/webpack-dev-middleware/-/webpack-dev-middleware-5.3.1.tgz", - "integrity": "sha512-81EujCKkyles2wphtdrnPg/QqegC/AtqNH//mQkBYSMqwFVCQrxM6ktB2O/SPlZy7LqeEfTbV3cZARGQz6umhg==", + "version": "5.3.3", + "resolved": "https://registry.npmjs.org/webpack-dev-middleware/-/webpack-dev-middleware-5.3.3.tgz", + "integrity": "sha512-hj5CYrY0bZLB+eTO+x/j67Pkrquiy7kWepMHmUMoPsmcUaeEnQJqFzHJOyxgWlq746/wUuA64p9ta34Kyb01pA==", "dev": true, "requires": { "colorette": "^2.0.10", - "memfs": "^3.4.1", + "memfs": "^3.4.3", "mime-types": "^2.1.31", "range-parser": "^1.2.1", "schema-utils": "^4.0.0" }, "dependencies": { "ajv": { - "version": "8.9.0", - "resolved": "https://registry.npmjs.org/ajv/-/ajv-8.9.0.tgz", - "integrity": "sha512-qOKJyNj/h+OWx7s5DePL6Zu1KeM9jPZhwBqs+7DzP6bGOvqzVCSf0xueYmVuaC/oQ/VtS2zLMLHdQFbkka+XDQ==", + "version": "8.11.0", + "resolved": "https://registry.npmjs.org/ajv/-/ajv-8.11.0.tgz", + "integrity": "sha512-wGgprdCvMalC0BztXvitD2hC04YffAvtsUn93JbGXYLAtCUO4xd17mCCZQxUOItiBwZvJScWo8NIvQMQ71rdpg==", "dev": true, "requires": { "fast-deep-equal": "^3.1.1", @@ -4167,9 +4245,9 @@ }, "dependencies": { "ajv": { - "version": "8.9.0", - "resolved": "https://registry.npmjs.org/ajv/-/ajv-8.9.0.tgz", - "integrity": "sha512-qOKJyNj/h+OWx7s5DePL6Zu1KeM9jPZhwBqs+7DzP6bGOvqzVCSf0xueYmVuaC/oQ/VtS2zLMLHdQFbkka+XDQ==", + "version": "8.11.0", + "resolved": "https://registry.npmjs.org/ajv/-/ajv-8.11.0.tgz", + "integrity": "sha512-wGgprdCvMalC0BztXvitD2hC04YffAvtsUn93JbGXYLAtCUO4xd17mCCZQxUOItiBwZvJScWo8NIvQMQ71rdpg==", "dev": true, "requires": { "fast-deep-equal": "^3.1.1", @@ -4221,9 +4299,9 @@ } }, "ws": { - "version": "8.4.2", - "resolved": "https://registry.npmjs.org/ws/-/ws-8.4.2.tgz", - "integrity": "sha512-Kbk4Nxyq7/ZWqr/tarI9yIt/+iNNFOjBXEWgTb4ydaNHBNGgvf2QHbS9fdfsndfjFlFwEd4Al+mw83YkaD10ZA==", + "version": "8.6.0", + "resolved": "https://registry.npmjs.org/ws/-/ws-8.6.0.tgz", + "integrity": "sha512-AzmM3aH3gk0aX7/rZLYvjdvZooofDu3fFOzGqcSnQ1tOcTWwhM/o+q++E8mAyVVIyUdajrkzWUGftaVSDLn1bw==", "dev": true } } @@ -4261,15 +4339,6 @@ "integrity": "sha512-OqedPIGOfsDlo31UNwYbCFMSaO9m9G/0faIHj5/dZFDMFqPTcx6UwqyOy3COEaEOg/9VsGIpdqn62W5KhoKSpg==", "dev": true }, - "whatwg-url": { - "version": "5.0.0", - "resolved": "https://registry.npmjs.org/whatwg-url/-/whatwg-url-5.0.0.tgz", - "integrity": "sha512-saE57nupxk6v3HY35+jzBwYa0rKSy0XR8JSxZPwgLr7ys0IBzhGviA1/TUGJLmSVqs8pb9AnvICXEuOHLprYTw==", - "requires": { - "tr46": "~0.0.3", - "webidl-conversions": "^3.0.0" - } - }, "which": { "version": "2.0.2", "resolved": "https://registry.npmjs.org/which/-/which-2.0.2.tgz", @@ -4292,16 +4361,16 @@ } }, "which-typed-array": { - "version": "1.1.7", - "resolved": "https://registry.npmjs.org/which-typed-array/-/which-typed-array-1.1.7.tgz", - "integrity": "sha512-vjxaB4nfDqwKI0ws7wZpxIlde1XrLX5uB0ZjpfshgmapJMD7jJWhZI+yToJTqaFByF0eNBcYxbjmCzoRP7CfEw==", + "version": "1.1.8", + "resolved": "https://registry.npmjs.org/which-typed-array/-/which-typed-array-1.1.8.tgz", + "integrity": "sha512-Jn4e5PItbcAHyLoRDwvPj1ypu27DJbtdYXUa5zsinrUx77Uvfb0cXwwnGMTn7cjUfhhqgVQnVJCwF+7cgU7tpw==", "requires": { "available-typed-arrays": "^1.0.5", "call-bind": "^1.0.2", - "es-abstract": "^1.18.5", - "foreach": "^2.0.5", + "es-abstract": "^1.20.0", + "for-each": "^0.3.3", "has-tostringtag": "^1.0.0", - "is-typed-array": "^1.1.7" + "is-typed-array": "^1.1.9" } }, "wildcard": { From 798f3b64a432f059492e6c1503aa3c651235cfba Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Tue, 20 Dec 2022 16:30:34 +0000 Subject: [PATCH 153/373] Run make format too... --- CHANGELOG.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index b3c08af1c0..8afe843a79 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -7,7 +7,7 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) -- [Unrealeased](#unrealeased) +- [Unreleased](#unreleased) - [Added](#added) - [Changed](#changed) - [Removed](#removed) From 20463883b1cc766b15a52ec1013e851fdca0c1b5 Mon Sep 17 00:00:00 2001 From: Calum Sieppert Date: Tue, 20 Dec 2022 09:45:31 -0700 Subject: [PATCH 154/373] Implement suggestions --- src/Internal/Deserialization/FromBytes.purs | 58 ++++++++++----------- src/Internal/Serialization/ToBytes.purs | 4 +- 2 files changed, 31 insertions(+), 31 deletions(-) diff --git a/src/Internal/Deserialization/FromBytes.purs b/src/Internal/Deserialization/FromBytes.purs index ebad87837b..a7c64bee9d 100644 --- a/src/Internal/Deserialization/FromBytes.purs +++ b/src/Internal/Deserialization/FromBytes.purs @@ -51,79 +51,79 @@ class FromBytes a where fromBytes' :: forall (r :: Row Type). ByteArray -> E (FromBytesError + r) a instance FromBytes Address where - fromBytes' = fromBytes'' "Address" + fromBytes' = fromBytesImpl "Address" instance FromBytes AuxiliaryDataHash where - fromBytes' = fromBytes'' "AuxiliaryDataHash" + fromBytes' = fromBytesImpl "AuxiliaryDataHash" instance FromBytes ByronAddress where - fromBytes' = fromBytes'' "ByronAddress" + fromBytes' = fromBytesImpl "ByronAddress" instance FromBytes DataHash where - fromBytes' = fromBytes'' "DataHash" + fromBytes' = fromBytesImpl "DataHash" instance FromBytes Ed25519KeyHash where - fromBytes' = fromBytes'' "Ed25519KeyHash" + fromBytes' = fromBytesImpl "Ed25519KeyHash" instance FromBytes Ed25519Signature where - fromBytes' = fromBytes'' "Ed25519Signature" + fromBytes' = fromBytesImpl "Ed25519Signature" instance FromBytes GenesisDelegateHash where - fromBytes' = fromBytes'' "GenesisDelegateHash" + fromBytes' = fromBytesImpl "GenesisDelegateHash" instance FromBytes GenesisHash where - fromBytes' = fromBytes'' "GenesisHash" + fromBytes' = fromBytesImpl "GenesisHash" instance FromBytes Mint where - fromBytes' = fromBytes'' "Mint" + fromBytes' = fromBytesImpl "Mint" instance FromBytes NativeScript where - fromBytes' = fromBytes'' "NativeScript" + fromBytes' = fromBytesImpl "NativeScript" instance FromBytes PlutusData where - fromBytes' = fromBytes'' "PlutusData" + fromBytes' = fromBytesImpl "PlutusData" instance FromBytes PoolMetadataHash where - fromBytes' = fromBytes'' "PoolMetadataHash" + fromBytes' = fromBytesImpl "PoolMetadataHash" instance FromBytes PublicKey where - fromBytes' = fromBytes'' "PublicKey" + fromBytes' = fromBytesImpl "PublicKey" instance FromBytes Redeemers where - fromBytes' = fromBytes'' "Redeemers" + fromBytes' = fromBytesImpl "Redeemers" instance FromBytes ScriptDataHash where - fromBytes' = fromBytes'' "ScriptDataHash" + fromBytes' = fromBytesImpl "ScriptDataHash" instance FromBytes ScriptHash where - fromBytes' = fromBytes'' "ScriptHash" + fromBytes' = fromBytesImpl "ScriptHash" instance FromBytes StakeCredential where - fromBytes' = fromBytes'' "StakeCredential" + fromBytes' = fromBytesImpl "StakeCredential" instance FromBytes Transaction where - fromBytes' = fromBytes'' "Transaction" + fromBytes' = fromBytesImpl "Transaction" instance FromBytes TransactionBody where - fromBytes' = fromBytes'' "TransactionBody" + fromBytes' = fromBytesImpl "TransactionBody" instance FromBytes TransactionHash where - fromBytes' = fromBytes'' "TransactionHash" + fromBytes' = fromBytesImpl "TransactionHash" instance FromBytes TransactionOutput where - fromBytes' = fromBytes'' "TransactionOutput" + fromBytes' = fromBytesImpl "TransactionOutput" instance FromBytes TransactionUnspentOutput where - fromBytes' = fromBytes'' "TransactionUnspentOutput" + fromBytes' = fromBytesImpl "TransactionUnspentOutput" instance FromBytes TransactionWitnessSet where - fromBytes' = fromBytes'' "TransactionWitnessSet" + fromBytes' = fromBytesImpl "TransactionWitnessSet" instance FromBytes Value where - fromBytes' = fromBytes'' "Value" + fromBytes' = fromBytesImpl "Value" instance FromBytes VRFKeyHash where - fromBytes' = fromBytes'' "VRFKeyHash" + fromBytes' = fromBytesImpl "VRFKeyHash" -- for backward compatibility until `Maybe` is abandoned. Then to be renamed. fromBytes :: forall (a :: Type). FromBytes a => CborBytes -> Maybe a @@ -135,18 +135,18 @@ fromBytesEffect bytes = Nothing -> throw "from_bytes() call failed" Just a -> pure a -fromBytes'' +fromBytesImpl :: forall (r :: Row Type) (a :: Type) . String -> ByteArray -> E (FromBytesError + r) a -fromBytes'' = flip _fromBytes fromBytesErrorHelper +fromBytesImpl = _fromBytes fromBytesErrorHelper ---- Foreign imports foreign import _fromBytes :: forall (r :: Row Type) (a :: Type) - . String - -> ErrorFfiHelper r + . ErrorFfiHelper r + -> String -> ByteArray -> E r a diff --git a/src/Internal/Serialization/ToBytes.purs b/src/Internal/Serialization/ToBytes.purs index 1cc86ebc17..56f6a6f10e 100644 --- a/src/Internal/Serialization/ToBytes.purs +++ b/src/Internal/Serialization/ToBytes.purs @@ -35,7 +35,7 @@ import Ctl.Internal.Types.CborBytes (CborBytes(CborBytes)) import Untagged.Castable (class Castable) import Untagged.Union (type (|+|)) -type SerializationData = Address +type SerializableData = Address |+| AuxiliaryDataHash |+| ByronAddress |+| DataHash @@ -68,7 +68,7 @@ foreign import _toBytes toBytes :: forall a - . Castable a SerializationData + . Castable a SerializableData => a -> CborBytes toBytes = CborBytes <<< _toBytes From e0b0d9fa41110f27e75d333ee05fe94b725f5f23 Mon Sep 17 00:00:00 2001 From: Calum Sieppert Date: Tue, 20 Dec 2022 09:46:30 -0700 Subject: [PATCH 155/373] Formatting --- CHANGELOG.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index b3c08af1c0..8afe843a79 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -7,7 +7,7 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) -- [Unrealeased](#unrealeased) +- [Unreleased](#unreleased) - [Added](#added) - [Changed](#changed) - [Removed](#removed) From 82898e3b36b55aa872c4352ca35fade299cda91d Mon Sep 17 00:00:00 2001 From: Nathaniel Lane Date: Tue, 20 Dec 2022 10:10:11 -0700 Subject: [PATCH 156/373] implement Joe Young's simplification suggestion Co-authored-by: Joseph Young --- src/Internal/Metadata/Cip25/Cip25String.purs | 5 +---- 1 file changed, 1 insertion(+), 4 deletions(-) diff --git a/src/Internal/Metadata/Cip25/Cip25String.purs b/src/Internal/Metadata/Cip25/Cip25String.purs index 1289e1dbe0..c1a7e6a36d 100644 --- a/src/Internal/Metadata/Cip25/Cip25String.purs +++ b/src/Internal/Metadata/Cip25/Cip25String.purs @@ -143,7 +143,4 @@ fromMetadataString :: TransactionMetadatum -> Maybe String fromMetadataString datum = do fromCip25Strings <$> (Array.singleton <$> fromMetadata datum) <|> do strings :: Array Cip25String <- fromMetadata datum - let - bytes :: Array ByteArray - bytes = map (\(Cip25String s) -> wrap $ encodeUtf8 s) strings - hush $ decodeUtf8 $ unwrap $ fold bytes + foldMap (\(Cip25String s) -> s) strings From 0178e61c3ae93b4717e524cb11002e67377d66da Mon Sep 17 00:00:00 2001 From: nalane Date: Tue, 20 Dec 2022 10:17:41 -0700 Subject: [PATCH 157/373] fixed a syntax error in fromMetadataString --- src/Internal/Metadata/Cip25/Cip25String.purs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Internal/Metadata/Cip25/Cip25String.purs b/src/Internal/Metadata/Cip25/Cip25String.purs index c1a7e6a36d..896228be1c 100644 --- a/src/Internal/Metadata/Cip25/Cip25String.purs +++ b/src/Internal/Metadata/Cip25/Cip25String.purs @@ -143,4 +143,4 @@ fromMetadataString :: TransactionMetadatum -> Maybe String fromMetadataString datum = do fromCip25Strings <$> (Array.singleton <$> fromMetadata datum) <|> do strings :: Array Cip25String <- fromMetadata datum - foldMap (\(Cip25String s) -> s) strings + pure $ foldMap (\(Cip25String s) -> s) strings From ffa165b2d4e2f94f9024b12bcabff896bf7a40e4 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Tue, 20 Dec 2022 21:25:46 +0400 Subject: [PATCH 158/373] Fix spelling --- doc/balancing.md | 2 +- doc/staking.md | 2 +- doc/tx-chaining.md | 2 +- 3 files changed, 3 insertions(+), 3 deletions(-) diff --git a/doc/balancing.md b/doc/balancing.md index 924af5f68d..a78527ea52 100644 --- a/doc/balancing.md +++ b/doc/balancing.md @@ -14,7 +14,7 @@ Transaction balancing in Cardano is the process of finding a set of inputs and o ## Balancer constraints -CTL allows to tweak the default balancer behavior by letting the user impose constraints on the UTxO set that is used in the process (`balanceTxWithConstraints`): +CTL allows tweaking the default balancer behavior by letting the user impose constraints on the UTxO set that is used in the process (`balanceTxWithConstraints`): - providing additional UTxOs to use: `mustUseUtxosAtAddresses` / `mustUseUtxosAtAddress` / `mustUseAdditionalUtxos` - overriding change address: `mustSendChangeToAddress` diff --git a/doc/staking.md b/doc/staking.md index fa09023bbf..a25f62006e 100644 --- a/doc/staking.md +++ b/doc/staking.md @@ -4,7 +4,7 @@ [Staking](https://cardano.org/stake-pool-delegation/) is the process of delegation of Ada claimed by a stake key or a script to a staking pool. Staking is an important part of Cardano operation, because it incentivizes block validators to actually perform their work. -[The explainer from Plutonomicon](https://github.com/Plutonomicon/plutonomicon/blob/main/stake-scripts.md) show how staking works from a more technical perspective. +[The explainer from Plutonomicon](https://github.com/Plutonomicon/plutonomicon/blob/main/stake-scripts.md) shows how staking works from a more technical perspective. CTL supports all operations with stake: diff --git a/doc/tx-chaining.md b/doc/tx-chaining.md index 5722d776e2..bab9329535 100644 --- a/doc/tx-chaining.md +++ b/doc/tx-chaining.md @@ -6,4 +6,4 @@ Transaction chaining on Cardano is the ability to send transactions that depend In case the transactions come from multiple actors, some off-chain data delivery mechanism should be used - it's up to the application developers to implement it. -The only piece of data that is actually needed is the additional UTxOs that the CTL query layer is not (yet) aware of. `mustUseAdditionalUtxos` [balancer constraint](./balancing.md) can be used for that, as shown in the [transaction chaining example](https://github.com/Plutonomicon/cardano-transaction-lib/blob/develop/examples/TxChaining.purs). +The only piece of data that is actually needed is the additional UTxOs that the CTL query layer is not (yet) aware of. `mustUseAdditionalUtxos` [balancer constraint](./balancing.md) can be used for that, as shown in the [transaction chaining example](../examples/TxChaining.purs). From 5cee6cccd3e314cdf5d7c0ca9df189df4ece7e0e Mon Sep 17 00:00:00 2001 From: nalane Date: Tue, 20 Dec 2022 10:35:40 -0700 Subject: [PATCH 159/373] Used Calum's `fromMetadataString` simplification --- src/Internal/Metadata/Cip25/Cip25String.purs | 7 +++---- 1 file changed, 3 insertions(+), 4 deletions(-) diff --git a/src/Internal/Metadata/Cip25/Cip25String.purs b/src/Internal/Metadata/Cip25/Cip25String.purs index 896228be1c..7e1db54d5f 100644 --- a/src/Internal/Metadata/Cip25/Cip25String.purs +++ b/src/Internal/Metadata/Cip25/Cip25String.purs @@ -140,7 +140,6 @@ toMetadataString str = case toCip25Strings str of strings -> toMetadata $ toMetadata <$> strings fromMetadataString :: TransactionMetadatum -> Maybe String -fromMetadataString datum = do - fromCip25Strings <$> (Array.singleton <$> fromMetadata datum) <|> do - strings :: Array Cip25String <- fromMetadata datum - pure $ foldMap (\(Cip25String s) -> s) strings +fromMetadataString datum = + fromCip25Strings <$> + (Array.singleton <$> fromMetadata datum <|> fromMetadata datum) From 4782e5ecf992620b655ecd3599a6cc99e3148bd2 Mon Sep 17 00:00:00 2001 From: Calum Sieppert Date: Tue, 20 Dec 2022 10:42:42 -0700 Subject: [PATCH 160/373] Reorder arguments for JS fromBytes --- src/Internal/Deserialization/FromBytes.js | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Internal/Deserialization/FromBytes.js b/src/Internal/Deserialization/FromBytes.js index 461cf900d3..a7f1f0decb 100644 --- a/src/Internal/Deserialization/FromBytes.js +++ b/src/Internal/Deserialization/FromBytes.js @@ -7,7 +7,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } -exports._fromBytes = name => helper => bytes => { +exports._fromBytes = helper => name => bytes => { try { return helper.valid(lib[name].from_bytes(bytes)); } catch (e) { From 2e2ddf0a4b97c065ff5169ca9daa2c21f2daa5f2 Mon Sep 17 00:00:00 2001 From: nalane Date: Tue, 20 Dec 2022 10:48:19 -0700 Subject: [PATCH 161/373] Added `ByteArray` fix to `fromDataString` --- src/Internal/Metadata/Cip25/Cip25String.purs | 11 ++++------- 1 file changed, 4 insertions(+), 7 deletions(-) diff --git a/src/Internal/Metadata/Cip25/Cip25String.purs b/src/Internal/Metadata/Cip25/Cip25String.purs index 7e1db54d5f..774a7218c9 100644 --- a/src/Internal/Metadata/Cip25/Cip25String.purs +++ b/src/Internal/Metadata/Cip25/Cip25String.purs @@ -129,10 +129,8 @@ toDataString str = case toCip25Strings str of strings -> toData $ toData <$> strings fromDataString :: PlutusData -> Maybe String -fromDataString datum = do - (fromCip25Strings <$> (Array.singleton <$> fromData datum)) <|> do - bytes :: Array ByteArray <- fromData datum - hush $ decodeUtf8 $ unwrap $ fold bytes +fromDataString datum = fromCip25Strings <$> + ((Array.singleton <$> fromData datum) <|> fromData datum) toMetadataString :: String -> TransactionMetadatum toMetadataString str = case toCip25Strings str of @@ -140,6 +138,5 @@ toMetadataString str = case toCip25Strings str of strings -> toMetadata $ toMetadata <$> strings fromMetadataString :: TransactionMetadatum -> Maybe String -fromMetadataString datum = - fromCip25Strings <$> - (Array.singleton <$> fromMetadata datum <|> fromMetadata datum) +fromMetadataString datum = fromCip25Strings <$> + ((Array.singleton <$> fromMetadata datum) <|> fromMetadata datum) From 2332ce88e5028320b614f7748a037cfd3195e198 Mon Sep 17 00:00:00 2001 From: nalane Date: Tue, 20 Dec 2022 11:26:29 -0700 Subject: [PATCH 162/373] Moved changelog entry to unreleased section --- CHANGELOG.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index 076035f5f9..5cff51cae1 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -52,6 +52,7 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) ### Removed ### Fixed +- CIP-25 strings are now being split into chunks whose sizes are less than or equal to 64 to adhere to the CIP-25 standard ([#1343](https://github.com/Plutonomicon/cardano-transaction-lib/issues/1343)) ### Runtime Dependencies @@ -84,7 +85,6 @@ TBD - Added missing `stakePoolTargetNum` ("`nOpt`") protocol parameter (see [CIP-9](https://cips.cardano.org/cips/cip9/)) ([#571](https://github.com/Plutonomicon/cardano-transaction-lib/issues/571)) - CIP-30 `signData` response handling ([#1289](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1289)) -- CIP-25 strings are now being split into chunks whose sizes are less than or equal to 64 to adhere to the CIP-25 standard ([#1343](https://github.com/Plutonomicon/cardano-transaction-lib/issues/1343)) ### Runtime Dependencies From c9d2395f6c18de8328b0f07a4b3391fbc94c5e0f Mon Sep 17 00:00:00 2001 From: Bradley Date: Tue, 20 Dec 2022 15:00:08 -0500 Subject: [PATCH 163/373] add in port --- flake.nix | 1 - nix/test-nixos-configuration.nix | 1 + 2 files changed, 1 insertion(+), 1 deletion(-) diff --git a/flake.nix b/flake.nix index 83a928931c..eb61f6009b 100644 --- a/flake.nix +++ b/flake.nix @@ -48,7 +48,6 @@ { self , nixpkgs , cardano-configurations - , kupo , ... }@inputs: let diff --git a/nix/test-nixos-configuration.nix b/nix/test-nixos-configuration.nix index 3f1d06f85d..1f446f7e38 100644 --- a/nix/test-nixos-configuration.nix +++ b/nix/test-nixos-configuration.nix @@ -10,6 +10,7 @@ { from = "host"; host.port = 1337; guest.port = 1337; } { from = "host"; host.port = 8081; guest.port = 8081; } { from = "host"; host.port = 9999; guest.port = 9999; } + { from = "host"; host.port = 1442; guest.port = 1442; } ]; }; From b099733b7954583f5f1a4a01e0e0db587ab8867b Mon Sep 17 00:00:00 2001 From: nalane Date: Tue, 20 Dec 2022 16:45:49 -0700 Subject: [PATCH 164/373] Removed unused imports in Cip25 files --- src/Internal/Metadata/Cip25/Cip25String.purs | 9 ++++----- src/Internal/Metadata/Cip25/V2.purs | 6 +----- 2 files changed, 5 insertions(+), 10 deletions(-) diff --git a/src/Internal/Metadata/Cip25/Cip25String.purs b/src/Internal/Metadata/Cip25/Cip25String.purs index 774a7218c9..f2cde33c4c 100644 --- a/src/Internal/Metadata/Cip25/Cip25String.purs +++ b/src/Internal/Metadata/Cip25/Cip25String.purs @@ -24,17 +24,16 @@ import Ctl.Internal.FromData (class FromData, fromData) import Ctl.Internal.Metadata.FromMetadata (class FromMetadata, fromMetadata) import Ctl.Internal.Metadata.ToMetadata (class ToMetadata, toMetadata) import Ctl.Internal.ToData (class ToData, toData) -import Ctl.Internal.Types.ByteArray (ByteArray, byteLength) +import Ctl.Internal.Types.ByteArray (byteLength) import Ctl.Internal.Types.PlutusData (PlutusData) import Ctl.Internal.Types.TransactionMetadata (TransactionMetadatum) import Data.Array ((:)) import Data.Array as Array -import Data.Either (hush, note) -import Data.Foldable (fold, foldMap) +import Data.Either (note) +import Data.Foldable (foldMap) import Data.Maybe (Maybe(Nothing, Just), isJust) -import Data.Newtype (unwrap, wrap) +import Data.Newtype (wrap) import Data.String.CodePoints as String -import Data.TextDecoder (decodeUtf8) import Data.TextEncoder (encodeUtf8) import Data.Tuple.Nested (type (/\), (/\)) diff --git a/src/Internal/Metadata/Cip25/V2.purs b/src/Internal/Metadata/Cip25/V2.purs index ffdec2cc20..5c6462b8f0 100644 --- a/src/Internal/Metadata/Cip25/V2.purs +++ b/src/Internal/Metadata/Cip25/V2.purs @@ -48,11 +48,7 @@ import Ctl.Internal.Metadata.Helpers , lookupMetadata ) import Ctl.Internal.Metadata.MetadataType (class MetadataType) -import Ctl.Internal.Metadata.ToMetadata - ( class ToMetadata - , anyToMetadata - , toMetadata - ) +import Ctl.Internal.Metadata.ToMetadata (class ToMetadata, toMetadata) import Ctl.Internal.Plutus.Types.AssocMap (Map(Map), singleton) as AssocMap import Ctl.Internal.Serialization.Hash (scriptHashFromBytes, scriptHashToBytes) import Ctl.Internal.ToData (class ToData, toData) From e495a2e0f440813948edd492b096095c70a6e8ff Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Wed, 21 Dec 2022 16:44:55 +0000 Subject: [PATCH 165/373] Disallow inline datums/script refs in selected inputs when plutusv1 scripts are used during balancing. --- CHANGELOG.md | 1 + src/Internal/BalanceTx/BalanceTx.purs | 81 ++++++++++++--- src/Internal/BalanceTx/CoinSelection.purs | 7 +- src/Internal/BalanceTx/Error.purs | 11 ++- src/Internal/Types/ScriptLookups.purs | 14 +-- test/Plutip/Contract.purs | 115 +++++++++++++++++++++- 6 files changed, 199 insertions(+), 30 deletions(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index 91907ad2a0..f11f840775 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -48,6 +48,7 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) - `blake2b224Hash` and `blake2b224HashHex` functions for computing blake2b-224 hashes of arbitrary byte arrays ([#1323](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1323)) ### Changed +- `Balancer` no longer selects UTxOs which use PlutusV2 features when the transaction contains PlutusV1 scripts ([#1349](https://github.com/Plutonomicon/cardano-transaction-lib/issues/1349)) ### Removed diff --git a/src/Internal/BalanceTx/BalanceTx.purs b/src/Internal/BalanceTx/BalanceTx.purs index 5a16cf7851..429177eaee 100644 --- a/src/Internal/BalanceTx/BalanceTx.purs +++ b/src/Internal/BalanceTx/BalanceTx.purs @@ -6,7 +6,7 @@ module Ctl.Internal.BalanceTx import Prelude -import Control.Monad.Error.Class (liftMaybe) +import Control.Monad.Error.Class (catchError, liftMaybe, throwError) import Control.Monad.Except.Trans (ExceptT(ExceptT), except, runExceptT) import Control.Monad.Logger.Class (trace) as Logger import Control.Parallel (parTraverse) @@ -51,7 +51,9 @@ import Ctl.Internal.BalanceTx.Error , CouldNotGetUtxos , UtxoLookupFailedFor , UtxoMinAdaValueCalculationFailed + , BalanceInsufficientError ) + , InvalidInContext(InvalidInContext) ) import Ctl.Internal.BalanceTx.ExUnitsAndMinFee ( evalExUnitsAndMinFee @@ -90,8 +92,10 @@ import Ctl.Internal.Cardano.Types.Transaction , _mint , _networkId , _outputs + , _plutusScripts , _referenceInputs , _withdrawals + , _witnessSet ) import Ctl.Internal.Cardano.Types.Value ( AssetClass @@ -122,8 +126,12 @@ import Ctl.Internal.QueryM.Utxos , utxosAt ) import Ctl.Internal.Serialization.Address (Address) -import Ctl.Internal.Types.OutputDatum (OutputDatum(NoOutputDatum)) +import Ctl.Internal.Types.OutputDatum (OutputDatum(NoOutputDatum, OutputDatum)) import Ctl.Internal.Types.ScriptLookups (UnattachedUnbalancedTx) +import Ctl.Internal.Types.Scripts + ( Language(PlutusV1) + , PlutusScript(PlutusScript) + ) import Ctl.Internal.Types.UnbalancedTransaction (_utxoIndex) import Data.Array as Array import Data.Array.NonEmpty (NonEmptyArray) @@ -146,7 +154,7 @@ import Data.Lens.Getter ((^.)) import Data.Lens.Setter ((%~), (.~), (?~)) import Data.Log.Tag (TagSet) import Data.Log.Tag (fromArray, tag) as TagSet -import Data.Map (empty, filterKeys, lookup, union) as Map +import Data.Map (empty, insert, lookup, toUnfoldable, union) as Map import Data.Maybe (Maybe(Nothing, Just), fromJust, fromMaybe, isJust, maybe) import Data.Newtype (class Newtype, unwrap, wrap) import Data.Set as Set @@ -265,17 +273,67 @@ data BalancerStep runBalancer :: BalancerParams -> BalanceTxM FinalizedTransaction runBalancer p = do - spendableUtxos <- getSpendableUtxos + utxos <- partitionAndFilterUtxos unbalancedTx <- addLovelacesToTransactionOutputs p.unbalancedTx - mainLoop (initBalancerState unbalancedTx spendableUtxos) + addInvalidInContext (foldMap (_.amount <<< unwrap) utxos.invalidInContext) do + mainLoop (initBalancerState unbalancedTx utxos.spendable) where - getSpendableUtxos :: BalanceTxM UtxoMap - getSpendableUtxos = + addInvalidInContext + :: forall (a :: Type). Value -> BalanceTxM a -> BalanceTxM a + addInvalidInContext invalidInContext m = catchError m $ throwError <<< + case _ of + BalanceInsufficientError e a (InvalidInContext v) -> + BalanceInsufficientError e a (InvalidInContext (v <> invalidInContext)) + e -> e + + -- We check if the transaction uses a plutusv1 script, so that we can filter + -- out utxos which use plutusv2 features if so. + txHasPlutusV1 :: Boolean + txHasPlutusV1 = do + case p.unbalancedTx ^. _transaction' ^. _witnessSet ^. _plutusScripts of + Just scripts -> flip Array.any scripts case _ of + PlutusScript (_ /\ PlutusV1) -> true + _ -> false + Nothing -> false + + partitionAndFilterUtxos + :: BalanceTxM { spendable :: UtxoMap, invalidInContext :: UtxoMap } + partitionAndFilterUtxos = asksConstraints Constraints._nonSpendableInputs <#> \nonSpendableInputs -> - flip Map.filterKeys p.utxos \oref -> not $ - Set.member oref nonSpendableInputs - || Set.member oref (p.unbalancedTx ^. _body' <<< _referenceInputs) + foldr + ( \(oref /\ output) acc -> + let + hasInlineDatum :: Boolean + hasInlineDatum = case (unwrap output).datum of + OutputDatum _ -> true + _ -> false + + hasScriptRef :: Boolean + hasScriptRef = isJust (unwrap output).scriptRef + + spendable :: Boolean + spendable = not $ Set.member oref nonSpendableInputs || + Set.member oref + (p.unbalancedTx ^. _body' <<< _referenceInputs) + + validInContext :: Boolean + validInContext = not $ txHasPlutusV1 && + (hasInlineDatum || hasScriptRef) + in + case spendable, validInContext of + true, true -> acc + { spendable = Map.insert oref output acc.spendable } + true, false -> acc + { invalidInContext = Map.insert oref output + acc.invalidInContext + } + _, _ -> acc + ) + { spendable: Map.empty + , invalidInContext: Map.empty + } + (Map.toUnfoldable p.utxos :: Array _) mainLoop :: BalancerState -> BalanceTxM FinalizedTransaction mainLoop = worker <<< PrebalanceTx @@ -292,7 +350,8 @@ runBalancer p = do true -> if (Set.isEmpty $ balancedTx ^. _body' <<< _inputs) then do selectionState <- - performMultiAssetSelection p.strategy leftoverUtxos + performMultiAssetSelection p.strategy + leftoverUtxos (lovelaceValueOf one) runNextBalancerStep $ s { transaction = diff --git a/src/Internal/BalanceTx/CoinSelection.purs b/src/Internal/BalanceTx/CoinSelection.purs index bd9f9480ac..d33fbc94dc 100644 --- a/src/Internal/BalanceTx/CoinSelection.purs +++ b/src/Internal/BalanceTx/CoinSelection.purs @@ -30,6 +30,7 @@ import Ctl.Internal.BalanceTx.Error ) , Expected(Expected) , ImpossibleError(Impossible) + , InvalidInContext(InvalidInContext) ) import Ctl.Internal.Cardano.Types.Transaction (UtxoMap) import Ctl.Internal.Cardano.Types.Value (AssetClass(AssetClass), Coin, Value) @@ -128,7 +129,10 @@ performMultiAssetSelection -> UtxoIndex -> Value -> m SelectionState -performMultiAssetSelection strategy utxoIndex requiredValue = +performMultiAssetSelection + strategy + utxoIndex + requiredValue = case requiredValue `Value.leq` availableValue of true -> runRoundRobinM (mkSelectionState utxoIndex) selectors @@ -138,6 +142,7 @@ performMultiAssetSelection strategy utxoIndex requiredValue = balanceInsufficientError :: BalanceTxError balanceInsufficientError = BalanceInsufficientError (Expected requiredValue) (Actual availableValue) + (InvalidInContext mempty) availableValue :: Value availableValue = balance (utxoIndexUniverse utxoIndex) diff --git a/src/Internal/BalanceTx/Error.purs b/src/Internal/BalanceTx/Error.purs index 0d139c37f6..70cb93c71b 100644 --- a/src/Internal/BalanceTx/Error.purs +++ b/src/Internal/BalanceTx/Error.purs @@ -3,6 +3,7 @@ -- | that may be returned from Ogmios when calculating ex units. module Ctl.Internal.BalanceTx.Error ( Actual(Actual) + , InvalidInContext(InvalidInContext) , BalanceTxError ( BalanceInsufficientError , CouldNotConvertScriptOutputToTxInput @@ -68,7 +69,7 @@ import Data.Tuple.Nested (type (/\), (/\)) -- | Errors conditions that may possibly arise during transaction balancing data BalanceTxError - = BalanceInsufficientError Expected Actual + = BalanceInsufficientError Expected Actual InvalidInContext | CouldNotConvertScriptOutputToTxInput | CouldNotGetChangeAddress | CouldNotGetCollateral @@ -97,6 +98,14 @@ derive instance Newtype Actual _ instance Show Actual where show = genericShow +newtype InvalidInContext = InvalidInContext Value + +derive instance Generic InvalidInContext _ +derive instance Newtype InvalidInContext _ + +instance Show InvalidInContext where + show = genericShow + newtype Expected = Expected Value derive instance Generic Expected _ diff --git a/src/Internal/Types/ScriptLookups.purs b/src/Internal/Types/ScriptLookups.purs index a7ffb0f682..1b72f3bacc 100644 --- a/src/Internal/Types/ScriptLookups.purs +++ b/src/Internal/Types/ScriptLookups.purs @@ -583,8 +583,6 @@ type ConstraintsM (a :: Type) (b :: Type) = -- We could use `MonadError` to clean up the `ExceptT`s below although we can't -- use the type alias because they need to be fully applied so this is perhaps -- more readable. --- Fix me: add execution units from Ogmios where this function should be --- inside QueryM https://github.com/Plutonomicon/cardano-transaction-lib/issues/174 -- | Resolve some `TxConstraints` by modifying the `UnbalancedTx` in the -- | `ConstraintProcessingState` processLookupsAndConstraints @@ -1081,20 +1079,15 @@ processConstraint mpsMap osMap = do runExceptT $ _valueSpentBalancesOutputs <>= requireValue value MustSpendPubKeyOutput txo -> runExceptT do txOut <- ExceptT $ lookupTxOutRef txo Nothing - -- Recall an Ogmios datum is a `Maybe String` where `Nothing` implies a - -- wallet address and `Just` as script address. case txOut of - TransactionOutput { amount, datum: NoOutputDatum } -> do + TransactionOutput { amount } -> do -- POTENTIAL FIX ME: Plutus has Tx.TxIn and Tx.PubKeyTxIn -- TxIn -- keeps track TransactionInput and TxInType (the input type, whether -- consuming script, public key or simple script) _cpsToTxBody <<< _inputs %= Set.insert txo _valueSpentBalancesInputs <>= provideValue amount - _ -> throwError $ TxOutRefWrongType txo MustSpendScriptOutput txo red scriptRefUnspentOut -> runExceptT do txOut <- ExceptT $ lookupTxOutRef txo scriptRefUnspentOut - -- Recall an Ogmios datum is a `Maybe String` where `Nothing` implies a - -- wallet address and `Just` as script address. case txOut of TransactionOutput { datum: NoOutputDatum } -> throwError $ TxOutRefWrongType txo @@ -1112,9 +1105,6 @@ processConstraint mpsMap osMap = do ExceptT $ processScriptRefUnspentOut vHash scriptRefUnspentOut' -- Note: Plutus uses `TxIn` to attach a redeemer and datum. -- Use the datum hash inside the lookup - -- Note: if we get `Nothing`, we have to throw eventhough that's a - -- valid input, because our `txOut` above is a Script address via - -- `Just`. case datum' of OutputDatumHash dHash -> do dat <- ExceptT do @@ -1269,8 +1259,6 @@ processConstraint mpsMap osMap = do , delegationCred: credentialToStakeCredential cred } , amount - -- TODO: save correct and scriptRef, should be done in - -- Constraints API upgrade that follows Vasil , datum: datum' , scriptRef: scriptRef } diff --git a/test/Plutip/Contract.purs b/test/Plutip/Contract.purs index 57c9c78fe2..7efe64581a 100644 --- a/test/Plutip/Contract.purs +++ b/test/Plutip/Contract.purs @@ -12,6 +12,7 @@ import Contract.Address , getWalletCollateral , ownPaymentPubKeysHashes , ownStakePubKeysHashes + , scriptHashAddress ) import Contract.BalanceTxConstraints ( BalanceTxConstraintsBuilder @@ -35,6 +36,7 @@ import Contract.PlutusData , getDatumByHash , getDatumsByHashes , getDatumsByHashesWithErrors + , unitRedeemer ) import Contract.Prelude (liftM, mconcat) import Contract.Prim.ByteArray (byteArrayFromAscii, hexToByteArrayUnsafe) @@ -57,8 +59,11 @@ import Contract.Time (getEraSummaries) import Contract.Transaction ( DataHash , NativeScript(ScriptPubkey, ScriptNOfK, ScriptAll) + , OutputDatum(OutputDatumHash, NoOutputDatum, OutputDatum) , ScriptRef(PlutusScriptRef, NativeScriptRef) - , TransactionHash + , TransactionHash(TransactionHash) + , TransactionInput(TransactionInput) + , TransactionOutput(TransactionOutput) , awaitTxConfirmed , balanceTx , balanceTxWithConstraints @@ -71,8 +76,8 @@ import Contract.Transaction ) import Contract.TxConstraints (TxConstraints) import Contract.TxConstraints as Constraints -import Contract.Utxos (getWalletBalance, utxosAt) -import Contract.Value (Coin(Coin), coinToValue) +import Contract.Utxos (UtxoMap, getWalletBalance, utxosAt) +import Contract.Value (Coin(Coin), Value, coinToValue) import Contract.Value as Value import Contract.Wallet (getWalletUtxos, isWalletAvailable, withKeyWallet) import Control.Monad.Error.Class (try) @@ -111,12 +116,14 @@ import Ctl.Examples.Schnorr as Schnorr import Ctl.Examples.SendsToken (contract) as SendsToken import Ctl.Examples.TxChaining (contract) as TxChaining import Ctl.Internal.Plutus.Conversion.Address (toPlutusAddress) +import Ctl.Internal.Plutus.Types.Address (Address, pubKeyHashAddress) import Ctl.Internal.Plutus.Types.Transaction ( TransactionOutputWithRefScript(TransactionOutputWithRefScript) ) import Ctl.Internal.Plutus.Types.TransactionUnspentOutput ( TransactionUnspentOutput(TransactionUnspentOutput) , _input + , _output , lookupTxHash ) import Ctl.Internal.Plutus.Types.Value (lovelaceValueOf) @@ -132,14 +139,16 @@ import Ctl.Internal.Wallet.Cip30Mock ) import Data.Array (head, (!!)) import Data.BigInt as BigInt -import Data.Either (Either(Right), isLeft) +import Data.Either (Either(Right), isLeft, isRight) import Data.Foldable (fold, foldM, length) import Data.Lens (view) import Data.Map as Map import Data.Maybe (Maybe(Just, Nothing), isJust) import Data.Newtype (unwrap, wrap) import Data.Traversable (traverse, traverse_) +import Data.Tuple (Tuple(Tuple)) import Data.Tuple.Nested (type (/\), (/\)) +import Data.UInt (UInt) import Effect.Class (liftEffect) import Effect.Exception (error, throw) import Mote (group, skip, test) @@ -919,6 +928,104 @@ suite = do withWallets distribution \alice -> do withKeyWallet alice SendsToken.contract + test "PlutusV1 forces balancer to select non-PlutusV2 inputs" do + let + distribution :: InitialUTxOs + distribution = [ BigInt.fromInt 5_000_000 ] + + withWallets distribution \alice -> do + alicePkh <- withKeyWallet alice do + liftedM "Could not get own PKH" (head <$> ownPaymentPubKeysHashes) + + validator <- AlwaysSucceeds.alwaysSucceedsScript + + let + vhash = validatorHash validator + scriptAddress = scriptHashAddress vhash Nothing + + let + datum42 = Datum $ Integer $ BigInt.fromInt 42 + + datum42Hash <- liftM (error "Failed to hash datum") $ datumHash datum42 + datum42Lookup <- liftM (error "Could not make lookup") $ Lookups.datum + datum42 + + let + transactionId :: TransactionHash + transactionId = TransactionHash $ hexToByteArrayUnsafe + "a6b656487601c390a3bb61958c62369cb5d5a7597a68a9dccedb3dd68a60bfdd" + + mkUtxo + :: UInt + -> Address + -> Value + -> OutputDatum + -> TransactionUnspentOutput + mkUtxo index address amount datum = + TransactionUnspentOutput + { input: TransactionInput + { index + , transactionId + } + , output: TransactionOutputWithRefScript + { scriptRef: Nothing + , output: TransactionOutput + { address + , amount + , datum + , referenceScript: Nothing + } + } + } + + aliceUtxo :: OutputDatum -> TransactionUnspentOutput + aliceUtxo = mkUtxo zero + (pubKeyHashAddress alicePkh Nothing) + (Value.lovelaceValueOf $ BigInt.fromInt 50_000_000) + + alwaysSucceedsUtxo :: TransactionUnspentOutput + alwaysSucceedsUtxo = mkUtxo one + scriptAddress + (Value.lovelaceValueOf $ BigInt.fromInt 2_000_000) + (OutputDatumHash datum42Hash) + + -- Balance a transaction which requires selecting a utxo with a + -- certain datum + balanceWithDatum datum = withKeyWallet alice do + let + additionalUtxos :: UtxoMap + additionalUtxos = + Map.fromFoldable $ (Tuple <$> view _input <*> view _output) <$> + [ alwaysSucceedsUtxo, aliceUtxo datum ] + + value :: Value.Value + value = Value.lovelaceValueOf $ BigInt.fromInt 50_000_000 + + constraints :: TxConstraints Unit Unit + constraints = fold + [ Constraints.mustSpendScriptOutput + (view _input alwaysSucceedsUtxo) + unitRedeemer + , Constraints.mustPayToPubKey alicePkh value + ] + + lookups :: Lookups.ScriptLookups PlutusData + lookups = + Lookups.validator validator + <> Lookups.unspentOutputs additionalUtxos + <> datum42Lookup + + balanceTxConstraints + :: BalanceTxConstraints.BalanceTxConstraintsBuilder + balanceTxConstraints = + BalanceTxConstraints.mustUseAdditionalUtxos additionalUtxos + + unbalancedTx <- liftedE $ Lookups.mkUnbalancedTx lookups constraints + balanceTxWithConstraints unbalancedTx balanceTxConstraints + + balanceWithDatum NoOutputDatum >>= flip shouldSatisfy isRight + balanceWithDatum (OutputDatum datum42) >>= flip shouldSatisfy isLeft + test "InlineDatum" do let distribution :: InitialUTxOs From d0a75db6abab82f2db26e4ed497ebd5481846ffa Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Wed, 21 Dec 2022 16:48:59 +0000 Subject: [PATCH 166/373] Undo old changes --- src/Internal/BalanceTx/BalanceTx.purs | 3 +-- src/Internal/BalanceTx/CoinSelection.purs | 5 +---- 2 files changed, 2 insertions(+), 6 deletions(-) diff --git a/src/Internal/BalanceTx/BalanceTx.purs b/src/Internal/BalanceTx/BalanceTx.purs index 429177eaee..2310787cc4 100644 --- a/src/Internal/BalanceTx/BalanceTx.purs +++ b/src/Internal/BalanceTx/BalanceTx.purs @@ -350,8 +350,7 @@ runBalancer p = do true -> if (Set.isEmpty $ balancedTx ^. _body' <<< _inputs) then do selectionState <- - performMultiAssetSelection p.strategy - leftoverUtxos + performMultiAssetSelection p.strategy leftoverUtxos (lovelaceValueOf one) runNextBalancerStep $ s { transaction = diff --git a/src/Internal/BalanceTx/CoinSelection.purs b/src/Internal/BalanceTx/CoinSelection.purs index d33fbc94dc..3299de2db9 100644 --- a/src/Internal/BalanceTx/CoinSelection.purs +++ b/src/Internal/BalanceTx/CoinSelection.purs @@ -129,10 +129,7 @@ performMultiAssetSelection -> UtxoIndex -> Value -> m SelectionState -performMultiAssetSelection - strategy - utxoIndex - requiredValue = +performMultiAssetSelection strategy utxoIndex requiredValue = case requiredValue `Value.leq` availableValue of true -> runRoundRobinM (mkSelectionState utxoIndex) selectors From f6ec7e20eeaece562e67e49f28e8bf9f0e9f6da2 Mon Sep 17 00:00:00 2001 From: nalane Date: Wed, 21 Dec 2022 11:19:29 -0700 Subject: [PATCH 167/373] removed AnyToMetadata --- src/Internal/Metadata/ToMetadata.purs | 37 +++------------------------ 1 file changed, 4 insertions(+), 33 deletions(-) diff --git a/src/Internal/Metadata/ToMetadata.purs b/src/Internal/Metadata/ToMetadata.purs index 562d0b9e64..bb1db286e0 100644 --- a/src/Internal/Metadata/ToMetadata.purs +++ b/src/Internal/Metadata/ToMetadata.purs @@ -1,9 +1,6 @@ module Ctl.Internal.Metadata.ToMetadata ( class ToMetadata , toMetadata - , AnyToMetadata - , class AnyToMetadataClass - , anyToMetadata ) where import Prelude @@ -17,8 +14,8 @@ import Data.Array (fromFoldable) as Array import Data.BigInt (BigInt) import Data.Foldable (class Foldable) import Data.Map (Map) -import Data.Map (catMaybes, fromFoldable, toUnfoldable) as Map -import Data.Maybe (Maybe(Just), fromJust) +import Data.Map (fromFoldable, toUnfoldable) as Map +import Data.Maybe (fromJust) import Data.NonEmpty (NonEmpty) import Data.Profunctor.Strong ((***)) import Data.Tuple (Tuple) @@ -34,10 +31,7 @@ class ToMetadata (a :: Type) where instance ToMetadata TransactionMetadatum where toMetadata = identity -instance (Ord k, ToMetadata k) => ToMetadata (Map k AnyToMetadata) where - toMetadata = - toMetadata <<< Map.catMaybes <<< map (\(AnyToMetadata f) -> f toMetadata) -else instance (ToMetadata k, ToMetadata v) => ToMetadata (Map k v) where +instance (ToMetadata k, ToMetadata v) => ToMetadata (Map k v) where toMetadata mp = let entries = Map.toUnfoldable mp :: Array (Tuple k v) @@ -45,9 +39,7 @@ else instance (ToMetadata k, ToMetadata v) => ToMetadata (Map k v) where MetadataMap <<< Map.fromFoldable $ map (toMetadata *** toMetadata) entries -instance (Ord k, ToMetadata k) => ToMetadata (Array (Tuple k AnyToMetadata)) where - toMetadata = toMetadata <<< Map.fromFoldable -else instance +instance ( Ord k , ToMetadata k , ToMetadata v @@ -73,24 +65,3 @@ instance ToMetadata ByteArray where instance ToMetadata String where toMetadata = Text - --------------------------------------------------------------------------------- --- AnyToMetadata --------------------------------------------------------------------------------- - --- | Existential wrapper over `ToMetadata` constrained types that enables --- | heterogeneous collections and is particularly useful when dealing with --- | `Maybe` values. `TransactionMetadatum` doesn't provide a way to --- | represent `Maybe` values, so the basic idea is to filter out all --- | `Nothing`s during conversion (see `ToMetadata (Map k AnyToMetadata)` --- | instance for reference). -newtype AnyToMetadata = AnyToMetadata - (forall (r :: Type). (forall (a :: Type). ToMetadata a => a -> r) -> Maybe r) - -class AnyToMetadataClass (a :: Type) where - anyToMetadata :: a -> AnyToMetadata - -instance ToMetadata a => AnyToMetadataClass (Maybe a) where - anyToMetadata a = AnyToMetadata \f -> f <$> a -else instance ToMetadata a => AnyToMetadataClass a where - anyToMetadata a = AnyToMetadata \f -> Just (f a) From b7b000070e705cdf2c1f5b28d0206124e504576a Mon Sep 17 00:00:00 2001 From: nalane Date: Wed, 21 Dec 2022 11:24:23 -0700 Subject: [PATCH 168/373] Updated changelog with AnyToMetadata removal --- CHANGELOG.md | 1 + 1 file changed, 1 insertion(+) diff --git a/CHANGELOG.md b/CHANGELOG.md index 5cff51cae1..b7e544d27f 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -50,6 +50,7 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) ### Changed ### Removed +- AnyToMetadataClass and AnyToMetadata type. Neither was really used anywhere ### Fixed - CIP-25 strings are now being split into chunks whose sizes are less than or equal to 64 to adhere to the CIP-25 standard ([#1343](https://github.com/Plutonomicon/cardano-transaction-lib/issues/1343)) From de857f5655e26d2526b6b0cfb8c2f1b59191c294 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Wed, 21 Dec 2022 22:27:57 +0400 Subject: [PATCH 169/373] Fix a concurrency problem in E2E test suite in Nix --- nix/default.nix | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/nix/default.nix b/nix/default.nix index 60cd1bfdb7..9d25c846eb 100644 --- a/nix/default.nix +++ b/nix/default.nix @@ -337,6 +337,7 @@ let # Utils needed by E2E test code which # used to check for browser availability gnutar # used unpack settings archive within E2E test code + curl # used to query for the web server to start (see below) ] ++ (args.buildInputs or [ ]); NODE_PATH = "${nodeModules}/lib/node_modules"; } // env) @@ -358,7 +359,11 @@ let export E2E_EXTRA_BROWSER_ARGS="--disable-web-security" python -m http.server 4008 --directory ${bundledPursProject}/dist & - sleep 3 # Wait for it to start serving + until curl -S http://127.0.0.1:4008/index.html &>/dev/null; do + echo "Trying to connect to webserver..."; + sleep 0.1; + done; + ${nodejs}/bin/node -e 'require("${project}/output/${testMain}").main()' e2e-test run mkdir $out From 5ebcaed41f90e5f390a006d270d9f779388fbb2d Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Wed, 21 Dec 2022 22:41:46 +0400 Subject: [PATCH 170/373] Remove unnecessary entry from CHANGELOG --- CHANGELOG.md | 1 - 1 file changed, 1 deletion(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index b7e544d27f..5cff51cae1 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -50,7 +50,6 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) ### Changed ### Removed -- AnyToMetadataClass and AnyToMetadata type. Neither was really used anywhere ### Fixed - CIP-25 strings are now being split into chunks whose sizes are less than or equal to 64 to adhere to the CIP-25 standard ([#1343](https://github.com/Plutonomicon/cardano-transaction-lib/issues/1343)) From e7f702270d8b9b505310d61796e82d44c8a61ad7 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Wed, 21 Dec 2022 22:50:02 +0400 Subject: [PATCH 171/373] Add comment for Kupo --- nix/test-nixos-configuration.nix | 1 + 1 file changed, 1 insertion(+) diff --git a/nix/test-nixos-configuration.nix b/nix/test-nixos-configuration.nix index b048c4a9b9..57fb8c7c50 100644 --- a/nix/test-nixos-configuration.nix +++ b/nix/test-nixos-configuration.nix @@ -12,6 +12,7 @@ { from = "host"; host.port = 1337; guest.port = 1337; } # Ogmios Datum Cache { from = "host"; host.port = 9999; guest.port = 9999; } + # Kupo { from = "host"; host.port = 1442; guest.port = 1442; } ]; }; From c55e36e797c42d95e594cc6f505e7364cf12d4e5 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Wed, 21 Dec 2022 20:10:05 +0000 Subject: [PATCH 172/373] Make KeyWallet defer networkId choice again. Move some wallet related code back into Contract --- src/Contract/Address.purs | 6 +- src/Contract/Wallet.purs | 7 +- src/Contract/Wallet/KeyFile.purs | 26 +----- src/Internal/Contract/Monad.purs | 23 +++-- src/Internal/Contract/Wallet.purs | 51 +++++------ src/Internal/Plutip/UtxoDistribution.purs | 7 +- src/Internal/Test/E2E/Route.purs | 2 +- src/Internal/Wallet.purs | 100 +--------------------- src/Internal/Wallet/Cip30Mock.purs | 14 +-- src/Internal/Wallet/Key.purs | 23 +++-- src/Internal/Wallet/Spec.purs | 7 +- 11 files changed, 82 insertions(+), 184 deletions(-) diff --git a/src/Contract/Address.purs b/src/Contract/Address.purs index 1a46e92dd3..6f5b457792 100644 --- a/src/Contract/Address.purs +++ b/src/Contract/Address.purs @@ -41,13 +41,13 @@ import Prelude import Contract.Monad (Contract, liftContractM, liftedM) import Contract.Prelude (liftM) import Control.Monad.Error.Class (throwError) +import Control.Monad.Reader.Class (asks) import Ctl.Internal.Address ( addressPaymentValidatorHash , addressStakeValidatorHash ) as Address import Ctl.Internal.Contract.Wallet - ( getNetworkId - , getWalletAddresses + ( getWalletAddresses , getWalletCollateral , ownPaymentPubKeyHashes , ownStakePubKeysHashes @@ -210,7 +210,7 @@ ownStakePubKeysHashes :: Contract (Array (Maybe StakePubKeyHash)) ownStakePubKeysHashes = Contract.ownStakePubKeysHashes getNetworkId :: Contract NetworkId -getNetworkId = Contract.getNetworkId +getNetworkId = asks _.networkId -------------------------------------------------------------------------------- -- Helpers via Cardano helpers, these are helpers from the CSL equivalent diff --git a/src/Contract/Wallet.purs b/src/Contract/Wallet.purs index d48182aba9..adec173313 100644 --- a/src/Contract/Wallet.purs +++ b/src/Contract/Wallet.purs @@ -78,7 +78,6 @@ withKeyWallet wallet = local _ { wallet = Just $ KeyWallet wallet } mkKeyWalletFromPrivateKeys - :: PrivatePaymentKey -> Maybe PrivateStakeKey -> Contract Wallet.KeyWallet -mkKeyWalletFromPrivateKeys payment mbStake = do - networkId <- getNetworkId - pure $ privateKeysToKeyWallet networkId payment mbStake + :: PrivatePaymentKey -> Maybe PrivateStakeKey -> Wallet.KeyWallet +mkKeyWalletFromPrivateKeys payment mbStake = privateKeysToKeyWallet payment + mbStake diff --git a/src/Contract/Wallet/KeyFile.purs b/src/Contract/Wallet/KeyFile.purs index c5a86b7436..eeec865eb4 100644 --- a/src/Contract/Wallet/KeyFile.purs +++ b/src/Contract/Wallet/KeyFile.purs @@ -1,15 +1,11 @@ -- | Node-only module. Allows working with Skeys stored in files. module Contract.Wallet.KeyFile ( mkKeyWalletFromFiles - , mkKeyWalletFromFilesAff , module Wallet.KeyFile ) where import Prelude -import Contract.Config (NetworkId) -import Control.Monad.Reader.Class (asks) -import Ctl.Internal.Contract.Monad (Contract) import Ctl.Internal.Wallet.Key (KeyWallet, privateKeysToKeyWallet) import Ctl.Internal.Wallet.KeyFile ( privatePaymentKeyFromFile @@ -26,22 +22,8 @@ import Ctl.Internal.Wallet.KeyFile import Data.Maybe (Maybe) import Data.Traversable (traverse) import Effect.Aff (Aff) -import Effect.Aff.Class (liftAff) import Node.Path (FilePath) --- | Load `PrivateKey`s from `skey` files (the files should be in JSON format as --- | accepted by cardano-cli). --- | The keys should have `PaymentSigningKeyShelley_ed25519` and --- | `StakeSigningKeyShelley_ed25519` types, respectively. --- | The stake key is optional. --- | --- | **NodeJS only** -mkKeyWalletFromFiles - :: FilePath -> Maybe FilePath -> Contract KeyWallet -mkKeyWalletFromFiles paymentKeyFile mbStakeKeyFile = do - networkId <- asks _.networkId - liftAff $ mkKeyWalletFromFilesAff networkId paymentKeyFile mbStakeKeyFile - -- | Load `PrivateKey`s from `skey` files (the files should be in JSON format as -- | accepted by cardano-cli) given a network id. -- | The keys should have `PaymentSigningKeyShelley_ed25519` and @@ -49,9 +31,9 @@ mkKeyWalletFromFiles paymentKeyFile mbStakeKeyFile = do -- | The stake key is optional. -- | -- | **NodeJS only** -mkKeyWalletFromFilesAff - :: NetworkId -> FilePath -> Maybe FilePath -> Aff KeyWallet -mkKeyWalletFromFilesAff networkId paymentKeyFile mbStakeKeyFile = - privateKeysToKeyWallet networkId +mkKeyWalletFromFiles + :: FilePath -> Maybe FilePath -> Aff KeyWallet +mkKeyWalletFromFiles paymentKeyFile mbStakeKeyFile = + privateKeysToKeyWallet <$> privatePaymentKeyFromFile paymentKeyFile <*> traverse privateStakeKeyFromFile mbStakeKeyFile diff --git a/src/Internal/Contract/Monad.purs b/src/Internal/Contract/Monad.purs index e260104d39..3334130bf9 100644 --- a/src/Internal/Contract/Monad.purs +++ b/src/Internal/Contract/Monad.purs @@ -54,10 +54,9 @@ import Ctl.Internal.QueryM import Ctl.Internal.QueryM.Kupo (isTxConfirmedAff) -- TODO: Move/translate these types into Cardano import Ctl.Internal.QueryM.Ogmios (ProtocolParameters, SystemStart) as Ogmios -import Ctl.Internal.Serialization.Address (NetworkId) +import Ctl.Internal.Serialization.Address (NetworkId(TestnetId, MainnetId)) import Ctl.Internal.Types.UsedTxOuts (UsedTxOuts, isTxOutRefUsed, newUsedTxOuts) -import Ctl.Internal.Wallet (Wallet) -import Ctl.Internal.Wallet (getNetworkId) as Wallet +import Ctl.Internal.Wallet (Wallet, actionBasedOnWallet) import Ctl.Internal.Wallet.Spec (WalletSpec, mkWalletBySpec) import Data.Either (Either(Left, Right), isRight) import Data.Log.Level (LogLevel) @@ -197,7 +196,7 @@ mkContractEnv params = do logger = mkLogger params.logLevel params.customLogger buildWallet :: Aff (Maybe Wallet) - buildWallet = traverse (mkWalletBySpec params.networkId) params.walletSpec + buildWallet = traverse mkWalletBySpec params.walletSpec constants = { networkId: params.networkId @@ -245,9 +244,13 @@ getLedgerConstants logger = case _ of -- | Ensure that `NetworkId` from wallet is the same as specified in the -- | `ContractEnv`. walletNetworkCheck :: NetworkId -> Wallet -> Aff Unit -walletNetworkCheck envNetworkId wallet = do - networkId <- Wallet.getNetworkId wallet - unless (envNetworkId == networkId) do +walletNetworkCheck envNetworkId = + actionBasedOnWallet + (\w -> check <=< intToNetworkId <=< _.getNetworkId w) + (pure $ pure unit) + where + check :: NetworkId -> Aff Unit + check networkId = unless (envNetworkId == networkId) do liftEffect $ throw $ "The networkId that is specified is not equal to the one from wallet." <> " The wallet is using " @@ -256,6 +259,12 @@ walletNetworkCheck envNetworkId wallet = do <> show envNetworkId <> " is specified in the config." + intToNetworkId :: Int -> Aff NetworkId + intToNetworkId = case _ of + 0 -> pure TestnetId + 1 -> pure MainnetId + _ -> liftEffect $ throw "Unknown network id" + -- | Finalizes a `Contract` environment. -- | Closes the connections in `ContractEnv`, effectively making it unusable. stopContractEnv :: ContractEnv -> Aff Unit diff --git a/src/Internal/Contract/Wallet.purs b/src/Internal/Contract/Wallet.purs index 2efab5afbf..31541a8e7b 100644 --- a/src/Internal/Contract/Wallet.purs +++ b/src/Internal/Contract/Wallet.purs @@ -5,11 +5,9 @@ module Ctl.Internal.Contract.Wallet , getWalletAddresses , signData , getWallet - , getNetworkId , ownPubKeyHashes , ownPaymentPubKeyHashes , ownStakePubKeysHashes - , withWalletAff , withWallet , getWalletCollateral , getWalletBalance @@ -31,7 +29,6 @@ import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.Helpers (liftM, liftedM) import Ctl.Internal.Serialization.Address ( Address - , NetworkId , addressPaymentCred , baseAddressDelegationCred , baseAddressFromAddress @@ -47,13 +44,6 @@ import Ctl.Internal.Wallet ( Wallet , actionBasedOnWallet ) -import Ctl.Internal.Wallet - ( getChangeAddress - , getRewardAddresses - , getUnusedAddresses - , getWalletAddresses - , signData - ) as Aff import Ctl.Internal.Wallet.Cip30 (DataSignature) import Data.Array (catMaybes, cons, foldMap, head) import Data.Array as Array @@ -66,32 +56,48 @@ import Data.Newtype (unwrap, wrap) import Data.Traversable (for, for_, traverse) import Data.Tuple.Nested ((/\)) import Data.UInt as UInt -import Effect.Aff (Aff) import Effect.Aff.Class (liftAff) import Effect.Class (liftEffect) import Effect.Exception (error, throw) getUnusedAddresses :: Contract (Array Address) -getUnusedAddresses = withWalletAff Aff.getUnusedAddresses +getUnusedAddresses = fold <$> do + withWallet $ actionBasedOnWallet _.getUnusedAddresses mempty getChangeAddress :: Contract (Maybe Address) -getChangeAddress = withWalletAff Aff.getChangeAddress +getChangeAddress = withWallet do + actionBasedOnWallet _.getChangeAddress + \kw -> do + networkId <- asks _.networkId + pure $ pure $ (unwrap kw).address networkId getRewardAddresses :: Contract (Array Address) -getRewardAddresses = withWalletAff Aff.getRewardAddresses +getRewardAddresses = fold <$> withWallet do + actionBasedOnWallet _.getRewardAddresses + \kw -> do + networkId <- asks _.networkId + pure $ pure $ pure $ (unwrap kw).address networkId getWalletAddresses :: Contract (Array Address) -getWalletAddresses = withWalletAff Aff.getWalletAddresses +getWalletAddresses = fold <$> withWallet do + actionBasedOnWallet _.getWalletAddresses + ( \kw -> do + networkId <- asks _.networkId + pure $ pure $ Array.singleton $ (unwrap kw).address networkId + ) signData :: Address -> RawBytes -> Contract (Maybe DataSignature) -signData address payload = withWalletAff (Aff.signData address payload) +signData address payload = + withWallet $ + actionBasedOnWallet + (\w conn -> w.signData conn address payload) + \kw -> do + networkId <- asks _.networkId + liftAff $ pure <$> (unwrap kw).signData networkId payload getWallet :: Contract (Maybe Wallet) getWallet = asks _.wallet -getNetworkId :: Contract NetworkId -getNetworkId = asks _.networkId - ownPubKeyHashes :: Contract (Array PubKeyHash) ownPubKeyHashes = catMaybes <$> do getWalletAddresses >>= traverse \address -> do @@ -118,10 +124,6 @@ ownStakePubKeysHashes = do wrap <<< wrap <$> stakeCredentialToKeyHash (baseAddressDelegationCred baseAddress) -withWalletAff - :: forall (a :: Type). (Wallet -> Aff a) -> Contract a -withWalletAff act = withWallet (liftAff <<< act) - withWallet :: forall (a :: Type). (Wallet -> Contract a) -> Contract a withWallet act = do @@ -134,7 +136,8 @@ getWalletCollateral = do mbCollateralUTxOs <- getWallet >>= maybe (pure Nothing) do actionBasedOnWallet _.getCollateral \kw -> do queryHandle <- getQueryHandle - let addr = (unwrap kw).address + networkId <- asks _.networkId + let addr = (unwrap kw).address networkId utxos <- (liftAff $ queryHandle.utxosAt addr) <#> hush >>> fromMaybe Map.empty >>= filterLockedUtxos diff --git a/src/Internal/Plutip/UtxoDistribution.purs b/src/Internal/Plutip/UtxoDistribution.purs index 40dee249fb..4536420ccb 100644 --- a/src/Internal/Plutip/UtxoDistribution.purs +++ b/src/Internal/Plutip/UtxoDistribution.purs @@ -42,7 +42,6 @@ import Ctl.Internal.Plutip.Types , UtxoAmount ) import Ctl.Internal.Plutus.Types.Transaction (UtxoMap) -import Ctl.Internal.Serialization.Address (NetworkId(MainnetId)) import Ctl.Internal.Wallet.Key ( KeyWallet , PrivatePaymentKey(PrivatePaymentKey) @@ -86,7 +85,7 @@ instance UtxoDistribution InitialUTxOs KeyWallet where decodeWallets d p = decodeWalletsDefault d p decodeWallets' _ pks = Array.uncons pks <#> \{ head: PrivateKeyResponse key, tail } -> - (privateKeysToKeyWallet MainnetId (PrivatePaymentKey key) Nothing) /\ tail + (privateKeysToKeyWallet (PrivatePaymentKey key) Nothing) /\ tail keyWallets _ wallet = [ wallet ] instance UtxoDistribution InitialUTxOsWithStakeKey KeyWallet where @@ -94,7 +93,7 @@ instance UtxoDistribution InitialUTxOsWithStakeKey KeyWallet where decodeWallets d p = decodeWalletsDefault d p decodeWallets' (InitialUTxOsWithStakeKey stake _) pks = Array.uncons pks <#> \{ head: PrivateKeyResponse key, tail } -> - privateKeysToKeyWallet MainnetId (PrivatePaymentKey key) (Just stake) /\ + privateKeysToKeyWallet (PrivatePaymentKey key) (Just stake) /\ tail keyWallets _ wallet = [ wallet ] @@ -180,7 +179,7 @@ transferFundsFromEnterpriseToBase ourKey wallets = do -- Get all utxos and key hashes at all wallets containing a stake key walletsInfo <- foldM addStakeKeyWalletInfo mempty wallets unless (null walletsInfo) do - ourWallet <- mkKeyWalletFromPrivateKeys ourKey Nothing + let ourWallet = mkKeyWalletFromPrivateKeys ourKey Nothing ourAddr <- liftedM "Could not get our address" $ head <$> withKeyWallet ourWallet getWalletAddresses ourUtxos <- utxosAt ourAddr diff --git a/src/Internal/Test/E2E/Route.purs b/src/Internal/Test/E2E/Route.purs index 48573d1e83..7b44844ee6 100644 --- a/src/Internal/Test/E2E/Route.purs +++ b/src/Internal/Test/E2E/Route.purs @@ -174,7 +174,7 @@ route configs tests = do do runContract configWithHooks $ withCip30Mock - (privateKeysToKeyWallet config.networkId paymentKey stakeKey) + (privateKeysToKeyWallet paymentKey stakeKey) mock test where diff --git a/src/Internal/Wallet.purs b/src/Internal/Wallet.purs index d63c335909..52d00b0ae0 100644 --- a/src/Internal/Wallet.purs +++ b/src/Internal/Wallet.purs @@ -30,16 +30,7 @@ module Ctl.Internal.Wallet , apiVersion , name , icon - , getNetworkId - , getUnusedAddresses - , getChangeAddress - , getRewardAddresses - , getWalletAddresses , actionBasedOnWallet - , signData - , ownPubKeyHashes - , ownPaymentPubKeyHashes - , ownStakePubKeysHashes , callCip30Wallet ) where @@ -56,27 +47,11 @@ import Ctl.Internal.Cardano.Types.Transaction , mkPublicKey ) import Ctl.Internal.Helpers ((<<>>)) -import Ctl.Internal.Helpers as Helpers -import Ctl.Internal.Serialization.Address - ( Address - , NetworkId(TestnetId, MainnetId) - , addressPaymentCred - , baseAddressDelegationCred - , baseAddressFromAddress - , stakeCredentialToKeyHash - ) import Ctl.Internal.Types.Natural (fromInt', minus) -import Ctl.Internal.Types.PubKeyHash - ( PaymentPubKeyHash - , PubKeyHash - , StakePubKeyHash - ) -import Ctl.Internal.Types.RawBytes (RawBytes) import Ctl.Internal.Wallet.Cip30 (Cip30Connection, Cip30Wallet) as Cip30Wallet import Ctl.Internal.Wallet.Cip30 ( Cip30Connection , Cip30Wallet - , DataSignature , mkCip30WalletAff ) import Ctl.Internal.Wallet.Key @@ -86,18 +61,14 @@ import Ctl.Internal.Wallet.Key , privateKeysToKeyWallet ) import Ctl.Internal.Wallet.Key (KeyWallet, privateKeysToKeyWallet) as KeyWallet -import Data.Array as Array -import Data.Foldable (fold) import Data.Int (toNumber) import Data.Maybe (Maybe(Just, Nothing), fromJust) -import Data.Newtype (over, unwrap, wrap) -import Data.Traversable (traverse) +import Data.Newtype (over, wrap) import Data.Tuple.Nested ((/\)) import Effect (Effect) import Effect.Aff (Aff, delay, error) import Effect.Aff.Class (class MonadAff, liftAff) import Effect.Class (liftEffect) -import Effect.Exception (throw) import Partial.Unsafe (unsafePartial) import Prim.TypeError (class Warn, Text) @@ -118,9 +89,8 @@ data WalletExtension | LodeWallet | NuFiWallet -mkKeyWallet :: NetworkId -> PrivatePaymentKey -> Maybe PrivateStakeKey -> Wallet -mkKeyWallet network payKey mbStakeKey = KeyWallet $ privateKeysToKeyWallet - network +mkKeyWallet :: PrivatePaymentKey -> Maybe PrivateStakeKey -> Wallet +mkKeyWallet payKey mbStakeKey = KeyWallet $ privateKeysToKeyWallet payKey mbStakeKey @@ -315,45 +285,6 @@ dummySign tx@(Transaction { witnessSet: tws@(TransactionWitnessSet ws) }) = ) ) -getNetworkId :: Wallet -> Aff NetworkId -getNetworkId = - actionBasedOnWallet - (\w -> intToNetworkId <=< _.getNetworkId w) - \kw -> pure (unwrap kw).networkId - where - intToNetworkId :: Int -> Aff NetworkId - intToNetworkId = case _ of - 0 -> pure TestnetId - 1 -> pure MainnetId - _ -> liftEffect $ throw "Unknown network id" - -getUnusedAddresses :: Wallet -> Aff (Array Address) -getUnusedAddresses wallet = fold <$> do - actionBasedOnWallet _.getUnusedAddresses mempty wallet - -getChangeAddress :: Wallet -> Aff (Maybe Address) -getChangeAddress = - actionBasedOnWallet _.getChangeAddress - \kw -> pure $ pure (unwrap kw).address - -getRewardAddresses :: Wallet -> Aff (Array Address) -getRewardAddresses wallet = fold <$> do - actionBasedOnWallet _.getRewardAddresses - (\kw -> pure $ pure $ pure (unwrap kw).address) - wallet - -getWalletAddresses :: Wallet -> Aff (Array Address) -getWalletAddresses wallet = fold <$> do - actionBasedOnWallet _.getWalletAddresses - (\kw -> pure $ pure $ Array.singleton (unwrap kw).address) - wallet - -signData :: Address -> RawBytes -> Wallet -> Aff (Maybe DataSignature) -signData address payload = - actionBasedOnWallet - (\w conn -> w.signData conn address payload) - \kw -> pure <$> (unwrap kw).signData payload - actionBasedOnWallet :: forall (m :: Type -> Type) (a :: Type) . MonadAff m @@ -371,31 +302,6 @@ actionBasedOnWallet walletAction keyWalletAction = NuFi wallet -> liftAff $ callCip30Wallet wallet walletAction KeyWallet kw -> keyWalletAction kw -ownPubKeyHashes :: Wallet -> Aff (Array PubKeyHash) -ownPubKeyHashes wallet = Array.catMaybes <$> do - getWalletAddresses wallet >>= traverse \address -> do - paymentCred <- - Helpers.liftM - ( error $ - "Unable to get payment credential from Address" - ) $ - addressPaymentCred address - pure $ stakeCredentialToKeyHash paymentCred <#> wrap - -ownPaymentPubKeyHashes :: Wallet -> Aff (Array PaymentPubKeyHash) -ownPaymentPubKeyHashes wallet = map wrap <$> ownPubKeyHashes wallet - -ownStakePubKeysHashes :: Wallet -> Aff (Array (Maybe StakePubKeyHash)) -ownStakePubKeysHashes wallet = do - addresses <- getWalletAddresses wallet - pure $ addressToMStakePubKeyHash <$> addresses - where - addressToMStakePubKeyHash :: Address -> Maybe StakePubKeyHash - addressToMStakePubKeyHash address = do - baseAddress <- baseAddressFromAddress address - wrap <<< wrap <$> stakeCredentialToKeyHash - (baseAddressDelegationCred baseAddress) - callCip30Wallet :: forall (a :: Type) . Cip30Wallet diff --git a/src/Internal/Wallet/Cip30Mock.purs b/src/Internal/Wallet/Cip30Mock.purs index c3d6944b88..fde0b35a91 100644 --- a/src/Internal/Wallet/Cip30Mock.purs +++ b/src/Internal/Wallet/Cip30Mock.purs @@ -138,10 +138,11 @@ mkCip30Mock pKey mSKey = do utxosAt address = liftMaybe (error "No UTxOs at address") <<< hush =<< do queryHandle.utxosAt address - keyWallet = privateKeysToKeyWallet env.networkId pKey mSKey + keyWallet = privateKeysToKeyWallet pKey mSKey addressHex = - byteArrayToHex $ toBytes $ asOneOf ((unwrap keyWallet).address :: Address) + byteArrayToHex $ toBytes $ asOneOf + ((unwrap keyWallet).address env.networkId :: Address) pure $ { getNetworkId: fromAff $ pure $ @@ -149,7 +150,7 @@ mkCip30Mock pKey mSKey = do TestnetId -> 0 MainnetId -> 1 , getUtxos: fromAff do - let ownAddress = (unwrap keyWallet).address + let ownAddress = (unwrap keyWallet).address env.networkId utxos <- utxosAt ownAddress collateralUtxos <- getCollateralUtxos utxos let @@ -164,7 +165,7 @@ mkCip30Mock pKey mSKey = do TransactionUnspentOutput { input, output } pure $ (byteArrayToHex <<< toBytes <<< asOneOf) <$> cslUtxos , getCollateral: fromAff do - let ownAddress = (unwrap keyWallet).address + let ownAddress = (unwrap keyWallet).address env.networkId utxos <- utxosAt ownAddress collateralUtxos <- getCollateralUtxos utxos cslUnspentOutput <- liftEffect $ traverse @@ -172,7 +173,7 @@ mkCip30Mock pKey mSKey = do collateralUtxos pure $ (byteArrayToHex <<< toBytes <<< asOneOf) <$> cslUnspentOutput , getBalance: fromAff do - let ownAddress = (unwrap keyWallet).address + let ownAddress = (unwrap keyWallet).address env.networkId utxos <- utxosAt ownAddress value <- liftEffect $ convertValue $ (foldMap (_.amount <<< unwrap) <<< Map.values) @@ -198,7 +199,8 @@ mkCip30Mock pKey mSKey = do , signData: mkFn2 \_addr msg -> unsafePerformEffect $ fromAff do msgBytes <- liftMaybe (error "Unable to convert CBOR") (hexToByteArray msg) - { key, signature } <- (unwrap keyWallet).signData (wrap msgBytes) + { key, signature } <- (unwrap keyWallet).signData env.networkId + (wrap msgBytes) pure { key: cborBytesToHex key, signature: cborBytesToHex signature } } diff --git a/src/Internal/Wallet/Key.purs b/src/Internal/Wallet/Key.purs index 3a5e0a2a0f..595557d3f1 100644 --- a/src/Internal/Wallet/Key.purs +++ b/src/Internal/Wallet/Key.purs @@ -67,17 +67,16 @@ import Effect.Class (liftEffect) -- Key backend ------------------------------------------------------------------------------- newtype KeyWallet = KeyWallet - { address :: Address + { address :: NetworkId -> Address , selectCollateral :: CoinsPerUtxoUnit -> Int -> UtxoMap -> Effect (Maybe (Array TransactionUnspentOutput)) , signTx :: Transaction -> Aff TransactionWitnessSet - , signData :: RawBytes -> Aff DataSignature + , signData :: NetworkId -> RawBytes -> Aff DataSignature , paymentKey :: PrivatePaymentKey , stakeKey :: Maybe PrivateStakeKey - , networkId :: NetworkId } derive instance Newtype KeyWallet _ @@ -145,20 +144,19 @@ privateKeysToAddress payKey mbStakeKey network = do >>> enterpriseAddressToAddress privateKeysToKeyWallet - :: NetworkId -> PrivatePaymentKey -> Maybe PrivateStakeKey -> KeyWallet -privateKeysToKeyWallet networkId payKey mbStakeKey = + :: PrivatePaymentKey -> Maybe PrivateStakeKey -> KeyWallet +privateKeysToKeyWallet payKey mbStakeKey = KeyWallet { address , selectCollateral , signTx - , signData: signData address + , signData , paymentKey: payKey , stakeKey: mbStakeKey - , networkId } where - address :: Address - address = privateKeysToAddress payKey mbStakeKey networkId + address :: NetworkId -> Address + address = privateKeysToAddress payKey mbStakeKey selectCollateral :: CoinsPerUtxoUnit @@ -183,6 +181,7 @@ privateKeysToKeyWallet networkId payKey mbStakeKey = mempty pure witnessSet' - signData :: Address -> RawBytes -> Aff DataSignature - signData addr payload = do - liftEffect $ Cip30SignData.signData (unwrap payKey) addr payload + signData :: NetworkId -> RawBytes -> Aff DataSignature + signData networkId payload = do + liftEffect $ Cip30SignData.signData (unwrap payKey) (address networkId) + payload diff --git a/src/Internal/Wallet/Spec.purs b/src/Internal/Wallet/Spec.purs index 3737fbb20a..403980bd48 100644 --- a/src/Internal/Wallet/Spec.purs +++ b/src/Internal/Wallet/Spec.purs @@ -15,7 +15,6 @@ module Ctl.Internal.Wallet.Spec import Prelude -import Ctl.Internal.Serialization.Address (NetworkId) import Ctl.Internal.Wallet ( Wallet , WalletExtension @@ -57,8 +56,8 @@ data WalletSpec | ConnectToLode | ConnectToNuFi -mkWalletBySpec :: NetworkId -> WalletSpec -> Aff Wallet -mkWalletBySpec networkId = case _ of +mkWalletBySpec :: WalletSpec -> Aff Wallet +mkWalletBySpec = case _ of UseKeys paymentKeySpec mbStakeKeySpec -> do privatePaymentKey <- case paymentKeySpec of PrivatePaymentKeyFile filePath -> @@ -67,7 +66,7 @@ mkWalletBySpec networkId = case _ of mbPrivateStakeKey <- for mbStakeKeySpec case _ of PrivateStakeKeyFile filePath -> privateStakeKeyFromFile filePath PrivateStakeKeyValue key -> pure key - pure $ mkKeyWallet networkId privatePaymentKey mbPrivateStakeKey + pure $ mkKeyWallet privatePaymentKey mbPrivateStakeKey ConnectToNami -> mkWalletAff NamiWallet ConnectToGero -> mkWalletAff GeroWallet ConnectToFlint -> mkWalletAff FlintWallet From 8d2bc0378f60bb790b679453a0f956c80c2d437d Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Thu, 22 Dec 2022 08:34:25 +0000 Subject: [PATCH 173/373] Export BalanceTx errors, convert parameters to be user-facing types. Add more explicit check of failure to balancer test --- src/Contract/Transaction.purs | 22 +++++++++++++++++++++- src/Internal/BalanceTx/BalanceTx.purs | 4 +++- src/Internal/BalanceTx/CoinSelection.purs | 7 +++++-- src/Internal/BalanceTx/Error.purs | 2 +- test/Plutip/Contract.purs | 18 +++++++++++++++--- 5 files changed, 45 insertions(+), 8 deletions(-) diff --git a/src/Contract/Transaction.purs b/src/Contract/Transaction.purs index e8817d98cd..8e332258e5 100644 --- a/src/Contract/Transaction.purs +++ b/src/Contract/Transaction.purs @@ -60,13 +60,33 @@ import Contract.TxConstraints (TxConstraints) import Control.Monad.Error.Class (catchError, throwError) import Control.Monad.Reader (ReaderT, asks, runReaderT) import Control.Monad.Reader.Class (ask) -import Ctl.Internal.BalanceTx (BalanceTxError) as BalanceTxError import Ctl.Internal.BalanceTx (FinalizedTransaction) import Ctl.Internal.BalanceTx ( FinalizedTransaction(FinalizedTransaction) ) as FinalizedTransaction import Ctl.Internal.BalanceTx (balanceTxWithConstraints) as BalanceTx import Ctl.Internal.BalanceTx.Constraints (BalanceTxConstraintsBuilder) +import Ctl.Internal.BalanceTx.Error + ( Actual(Actual) + , BalanceTxError + ( BalanceInsufficientError + , CouldNotConvertScriptOutputToTxInput + , CouldNotGetChangeAddress + , CouldNotGetCollateral + , CouldNotGetUtxos + , CollateralReturnError + , CollateralReturnMinAdaValueCalcError + , ExUnitsEvaluationFailed + , InsufficientTxInputs + , InsufficientUtxoBalanceToCoverAsset + , ReindexRedeemersError + , UtxoLookupFailedFor + , UtxoMinAdaValueCalculationFailed + ) + , Expected(Expected) + , ImpossibleError(Impossible) + , InvalidInContext(InvalidInContext) + ) as BalanceTxError import Ctl.Internal.Cardano.Types.NativeScript ( NativeScript ( ScriptPubkey diff --git a/src/Internal/BalanceTx/BalanceTx.purs b/src/Internal/BalanceTx/BalanceTx.purs index 2310787cc4..f09306c348 100644 --- a/src/Internal/BalanceTx/BalanceTx.purs +++ b/src/Internal/BalanceTx/BalanceTx.purs @@ -118,6 +118,7 @@ import Ctl.Internal.Cardano.Types.Value import Ctl.Internal.CoinSelection.UtxoIndex (UtxoIndex, buildUtxoIndex) import Ctl.Internal.Helpers ((??)) import Ctl.Internal.Partition (equipartition, partition) +import Ctl.Internal.Plutus.Conversion (toPlutusValue) import Ctl.Internal.QueryM (QueryM, getProtocolParameters) import Ctl.Internal.QueryM (getChangeAddress, getWalletAddresses) as QueryM import Ctl.Internal.QueryM.Utxos @@ -283,7 +284,8 @@ runBalancer p = do addInvalidInContext invalidInContext m = catchError m $ throwError <<< case _ of BalanceInsufficientError e a (InvalidInContext v) -> - BalanceInsufficientError e a (InvalidInContext (v <> invalidInContext)) + BalanceInsufficientError e a + (InvalidInContext (v <> toPlutusValue invalidInContext)) e -> e -- We check if the transaction uses a plutusv1 script, so that we can filter diff --git a/src/Internal/BalanceTx/CoinSelection.purs b/src/Internal/BalanceTx/CoinSelection.purs index 3299de2db9..ede499faf6 100644 --- a/src/Internal/BalanceTx/CoinSelection.purs +++ b/src/Internal/BalanceTx/CoinSelection.purs @@ -53,6 +53,7 @@ import Ctl.Internal.CoinSelection.UtxoIndex , utxoIndexPartition , utxoIndexUniverse ) +import Ctl.Internal.Plutus.Conversion (toPlutusValue) import Ctl.Internal.Types.ByteArray (byteArrayToHex) import Ctl.Internal.Types.TokenName (getTokenName) as TokenName import Ctl.Internal.Types.Transaction (TransactionInput) @@ -138,8 +139,10 @@ performMultiAssetSelection strategy utxoIndex requiredValue = where balanceInsufficientError :: BalanceTxError balanceInsufficientError = - BalanceInsufficientError (Expected requiredValue) (Actual availableValue) - (InvalidInContext mempty) + BalanceInsufficientError + (Expected $ toPlutusValue requiredValue) + (Actual $ toPlutusValue availableValue) + (InvalidInContext $ toPlutusValue mempty) availableValue :: Value availableValue = balance (utxoIndexUniverse utxoIndex) diff --git a/src/Internal/BalanceTx/Error.purs b/src/Internal/BalanceTx/Error.purs index 70cb93c71b..4030d9f993 100644 --- a/src/Internal/BalanceTx/Error.purs +++ b/src/Internal/BalanceTx/Error.purs @@ -27,7 +27,7 @@ module Ctl.Internal.BalanceTx.Error import Prelude import Ctl.Internal.Cardano.Types.Transaction (Redeemer(Redeemer)) -import Ctl.Internal.Cardano.Types.Value (Value) +import Ctl.Internal.Plutus.Types.Value (Value) import Ctl.Internal.QueryM.Ogmios ( RedeemerPointer , ScriptFailure diff --git a/test/Plutip/Contract.purs b/test/Plutip/Contract.purs index 7efe64581a..aa4f76c44c 100644 --- a/test/Plutip/Contract.purs +++ b/test/Plutip/Contract.purs @@ -57,7 +57,9 @@ import Contract.Test.Plutip ) import Contract.Time (getEraSummaries) import Contract.Transaction - ( DataHash + ( BalanceTxError(BalanceInsufficientError) + , DataHash + , InvalidInContext(InvalidInContext) , NativeScript(ScriptPubkey, ScriptNOfK, ScriptAll) , OutputDatum(OutputDatumHash, NoOutputDatum, OutputDatum) , ScriptRef(PlutusScriptRef, NativeScriptRef) @@ -139,7 +141,7 @@ import Ctl.Internal.Wallet.Cip30Mock ) import Data.Array (head, (!!)) import Data.BigInt as BigInt -import Data.Either (Either(Right), isLeft, isRight) +import Data.Either (Either(Left, Right), isLeft, isRight) import Data.Foldable (fold, foldM, length) import Data.Lens (view) import Data.Map as Map @@ -1023,8 +1025,18 @@ suite = do unbalancedTx <- liftedE $ Lookups.mkUnbalancedTx lookups constraints balanceTxWithConstraints unbalancedTx balanceTxConstraints + let + hasInsufficientBalance + :: forall (a :: Type). Either BalanceTxError a -> Boolean + hasInsufficientBalance = case _ of + Left (BalanceInsufficientError _ _ (InvalidInContext amount)) + | amount == Value.lovelaceValueOf (BigInt.fromInt 50_000_000) -> + true + _ -> false + balanceWithDatum NoOutputDatum >>= flip shouldSatisfy isRight - balanceWithDatum (OutputDatum datum42) >>= flip shouldSatisfy isLeft + balanceWithDatum (OutputDatum datum42) >>= flip shouldSatisfy + hasInsufficientBalance test "InlineDatum" do let From 08807b5bb31c8e3b10cba9b73d0a7b4e0162bea9 Mon Sep 17 00:00:00 2001 From: peter Date: Thu, 22 Dec 2022 11:58:15 +0100 Subject: [PATCH 174/373] cleanup testClusterDir on Sigint --- src/Internal/Plutip/Server.purs | 18 ++++++------------ src/Internal/Plutip/Spawn.purs | 7 ------- 2 files changed, 6 insertions(+), 19 deletions(-) diff --git a/src/Internal/Plutip/Server.purs b/src/Internal/Plutip/Server.purs index 50c52afd7e..b6a382d1b2 100644 --- a/src/Internal/Plutip/Server.purs +++ b/src/Internal/Plutip/Server.purs @@ -20,12 +20,7 @@ import Affjax.RequestBody as RequestBody import Affjax.RequestHeader as Header import Affjax.ResponseFormat as Affjax.ResponseFormat import Contract.Address (NetworkId(MainnetId)) -import Contract.Monad - ( Contract - , ContractEnv - , liftContractM - , runContractInEnv - ) +import Contract.Monad (Contract, ContractEnv, liftContractM, runContractInEnv) import Control.Monad.Error.Class (liftEither) import Control.Monad.State (State, execState, modify_) import Control.Monad.Trans.Class (lift) @@ -44,7 +39,7 @@ import Ctl.Internal.Plutip.Spawn ( ManagedProcess , NewOutputAction(Success, NoOp) , OnSignalRef - , cleanupOnSigint' + , cleanupOnSigint , cleanupTmpDir , removeOnSignal , spawn @@ -69,9 +64,7 @@ import Ctl.Internal.Plutip.UtxoDistribution , keyWallets , transferFundsFromEnterpriseToBase ) -import Ctl.Internal.QueryM - ( ClientError(ClientDecodeJsonError, ClientHttpError) - ) +import Ctl.Internal.QueryM (ClientError(ClientDecodeJsonError, ClientHttpError)) import Ctl.Internal.Test.TestPlanM (TestPlanM) import Ctl.Internal.Types.UsedTxOuts (newUsedTxOuts) import Ctl.Internal.Wallet.Key (PrivatePaymentKey(PrivatePaymentKey)) @@ -110,7 +103,7 @@ import Mote.Description (Description(Group, Test)) import Mote.Monad (MoteT(MoteT), mapTest) import Node.ChildProcess (defaultSpawnOptions) import Node.FS.Sync (exists, mkdir) as FSSync -import Node.Path (FilePath) +import Node.Path (FilePath, dirname) import Type.Prelude (Proxy(Proxy)) -- | Run a single `Contract` in Plutip environment. @@ -541,11 +534,12 @@ startKupo cfg params = do tmpDir <- liftEffect tmpdir let workdir = tmpDir <> "kupo-db" + testClusterDir = (dirname <<< dirname) params.nodeConfigPath liftEffect do workdirExists <- FSSync.exists workdir unless workdirExists (FSSync.mkdir workdir) childProcess <- spawnKupoProcess workdir - sig <- liftEffect $ cleanupOnSigint' workdir + sig <- liftEffect $ cleanupOnSigint workdir testClusterDir pure (childProcess /\ workdir /\ sig) where spawnKupoProcess :: FilePath -> Aff ManagedProcess diff --git a/src/Internal/Plutip/Spawn.purs b/src/Internal/Plutip/Spawn.purs index 48409957fc..c8f94c0059 100644 --- a/src/Internal/Plutip/Spawn.purs +++ b/src/Internal/Plutip/Spawn.purs @@ -10,7 +10,6 @@ module Ctl.Internal.Plutip.Spawn , waitForStop , cleanupTmpDir , cleanupOnSigint - , cleanupOnSigint' , removeOnSignal ) where @@ -139,12 +138,6 @@ cleanupOnSigint workingDir testClusterDir = do _rmdirSync testClusterDir pure sig -cleanupOnSigint' :: FilePath -> Effect OnSignalRef -cleanupOnSigint' workingDir = do - sig <- onSignal SIGINT do - _rmdirSync workingDir - pure sig - cleanupTmpDir :: ManagedProcess -> FilePath -> Effect Unit cleanupTmpDir (ManagedProcess _ child _) workingDir = do ChildProcess.onExit child \_ -> do From d5ba16e7c21107aedf8f450fc7ba91c48ec20f3a Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Thu, 22 Dec 2022 11:06:02 +0000 Subject: [PATCH 175/373] Change PlutusData, run make format --- src/Internal/Deserialization/NativeScript.js | 2 +- src/Internal/Deserialization/PlutusData.js | 30 +++++-- src/Internal/Deserialization/PlutusData.purs | 86 ++++++++----------- src/Internal/Deserialization/Transaction.purs | 6 +- 4 files changed, 64 insertions(+), 60 deletions(-) diff --git a/src/Internal/Deserialization/NativeScript.js b/src/Internal/Deserialization/NativeScript.js index bf3efb8215..c007a97783 100644 --- a/src/Internal/Deserialization/NativeScript.js +++ b/src/Internal/Deserialization/NativeScript.js @@ -22,7 +22,7 @@ exports._convertNativeScript = handler => ns => { case lib.NativeScriptKind.TimelockExpiry: return handler.timelockExpiry(ns.as_timelock_expiry()); default: - throw ("Impossible native script kind: " + ns.kind()); + throw "Impossible native script kind: " + ns.kind(); } }; diff --git a/src/Internal/Deserialization/PlutusData.js b/src/Internal/Deserialization/PlutusData.js index 87ec731de7..0539a1cc95 100644 --- a/src/Internal/Deserialization/PlutusData.js +++ b/src/Internal/Deserialization/PlutusData.js @@ -1,15 +1,29 @@ /* global BROWSER_RUNTIME */ -const plutusDataAs = what => helper => data => { - const res = data["as_" + what](); - return res == null ? helper.nothing : helper.just(res); +let lib; +if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { + lib = require("@emurgo/cardano-serialization-lib-browser"); +} else { + lib = require("@emurgo/cardano-serialization-lib-nodejs"); +} + +exports._convertPlutusData = handle => pd => { + switch (pd.kind()) { + case lib.PlutusDataKind.ConstrPlutusData: + return handle.constr(pd.as_constr_plutus_data()); + case lib.PlutusDataKind.Map: + return handle.map(pd.as_map()); + case lib.PlutusDataKind.List: + return handle.list(pd.as_list()); + case lib.PlutusDataKind.Integer: + return handle.integer(pd.as_integer()); + case lib.PlutusDataKind.Bytes: + return handle.bytes(pd.as_bytes()); + default: + throw "Impossible PlutusData kind: " + pd.kind(); + } }; -exports._PlutusData_constr = plutusDataAs("constr_plutus_data"); -exports._PlutusData_map = plutusDataAs("map"); -exports._PlutusData_list = plutusDataAs("list"); -exports._PlutusData_integer = plutusDataAs("integer"); -exports._PlutusData_bytes = plutusDataAs("bytes"); exports._unpackPlutusList = containerHelper => containerHelper.unpack; exports._ConstrPlutusData_alternative = x => x.alternative(); exports._ConstrPlutusData_data = x => x.data(); diff --git a/src/Internal/Deserialization/PlutusData.purs b/src/Internal/Deserialization/PlutusData.purs index 66de163a92..7a87147968 100644 --- a/src/Internal/Deserialization/PlutusData.purs +++ b/src/Internal/Deserialization/PlutusData.purs @@ -5,14 +5,11 @@ module Ctl.Internal.Deserialization.PlutusData import Prelude -import Control.Alt ((<|>)) import Ctl.Internal.Deserialization.BigInt (convertBigInt) import Ctl.Internal.Deserialization.FromBytes (fromBytes) import Ctl.Internal.FfiHelpers ( ContainerHelper - , MaybeFfiHelper , containerHelper - , maybeFfiHelper ) import Ctl.Internal.FromData (class FromData, fromData) import Ctl.Internal.Serialization.Types @@ -33,65 +30,56 @@ import Data.Tuple (Tuple(Tuple)) import Data.Tuple.Nested (type (/\), (/\)) import Partial.Unsafe (unsafePartial) --- TODO -convertPlutusData :: PlutusData -> T.PlutusData --- Unsafe fromJust here is correct, because we cover every PlutusData --- constructor, and Just will be returned by one of functions -convertPlutusData pd = unsafePartial $ fromJust $ - convertPlutusConstr pd - <|> convertPlutusMap pd - <|> convertPlutusList pd - <|> convertPlutusInteger pd - <|> convertPlutusBytes pd +type ConvertPlutusData = + { constr :: ConstrPlutusData -> T.PlutusData + , map :: PlutusMap -> T.PlutusData + , list :: PlutusList -> T.PlutusData + , integer :: BigInt -> T.PlutusData + , bytes :: ByteArray -> T.PlutusData + } -convertPlutusConstr :: PlutusData -> Maybe T.PlutusData -convertPlutusConstr pd = do - constr <- _PlutusData_constr maybeFfiHelper pd +convertPlutusData :: PlutusData -> T.PlutusData +convertPlutusData pd = _convertPlutusData + { constr: convertPlutusConstr + , map: convertPlutusMap + , list: convertPlutusList + , integer: convertPlutusInteger + , bytes: convertPlutusBytes + } + pd + +convertPlutusConstr :: ConstrPlutusData -> T.PlutusData +convertPlutusConstr constr = do let data' = convertPlutusData <$> _unpackPlutusList containerHelper (_ConstrPlutusData_data constr) alt = _ConstrPlutusData_alternative constr - pure $ T.Constr alt data' + T.Constr alt data' -convertPlutusMap :: PlutusData -> Maybe T.PlutusData -convertPlutusMap pd = do - entries <- _PlutusData_map maybeFfiHelper pd <#> - _unpackPlutusMap containerHelper Tuple >>> map - \(k /\ v) -> (convertPlutusData k /\ convertPlutusData v) +convertPlutusMap :: PlutusMap -> T.PlutusData +convertPlutusMap = + _unpackPlutusMap containerHelper Tuple + >>> map + (\(k /\ v) -> (convertPlutusData k /\ convertPlutusData v)) + >>> T.Map - pure $ T.Map entries +convertPlutusList :: PlutusList -> T.PlutusData +convertPlutusList = + _unpackPlutusList containerHelper >>> map (\d -> convertPlutusData d) >>> + T.List -convertPlutusList :: PlutusData -> Maybe T.PlutusData -convertPlutusList pd = T.List <$> do - _PlutusData_list maybeFfiHelper pd <#> - ( _unpackPlutusList containerHelper >>> - map convertPlutusData - ) +-- Unsafe fromJust here is correct, due to arbitrary sized integers +convertPlutusInteger :: BigInt -> T.PlutusData +convertPlutusInteger i = T.Integer $ unsafePartial $ fromJust $ convertBigInt i -convertPlutusInteger :: PlutusData -> Maybe T.PlutusData -convertPlutusInteger pd = T.Integer <$> do - _PlutusData_integer maybeFfiHelper pd >>= convertBigInt - -convertPlutusBytes :: PlutusData -> Maybe T.PlutusData -convertPlutusBytes pd = T.Bytes <$> _PlutusData_bytes maybeFfiHelper pd +convertPlutusBytes :: ByteArray -> T.PlutusData +convertPlutusBytes = T.Bytes deserializeData :: forall (a :: Type). FromData a => CborBytes -> Maybe a deserializeData = fromData <<< convertPlutusData <=< fromBytes -foreign import _PlutusData_constr - :: MaybeFfiHelper -> PlutusData -> Maybe ConstrPlutusData - -foreign import _PlutusData_map - :: MaybeFfiHelper -> PlutusData -> Maybe PlutusMap - -foreign import _PlutusData_list - :: MaybeFfiHelper -> PlutusData -> Maybe PlutusList - -foreign import _PlutusData_integer - :: MaybeFfiHelper -> PlutusData -> Maybe BigInt - -foreign import _PlutusData_bytes - :: MaybeFfiHelper -> PlutusData -> Maybe ByteArray +foreign import _convertPlutusData + :: ConvertPlutusData -> PlutusData -> T.PlutusData foreign import _unpackPlutusList :: ContainerHelper -> PlutusList -> Array PlutusData diff --git a/src/Internal/Deserialization/Transaction.purs b/src/Internal/Deserialization/Transaction.purs index 8ba429d25e..518e5a9080 100644 --- a/src/Internal/Deserialization/Transaction.purs +++ b/src/Internal/Deserialization/Transaction.purs @@ -237,7 +237,8 @@ convertTransaction tx = addErrTrace "convertTransaction" do convertTxBody :: forall (r :: Row Type). Csl.TransactionBody -> Err r T.TxBody convertTxBody txBody = do let - inputs = Set.fromFoldable $ convertInput <$> _txBodyInputs containerHelper txBody + inputs = Set.fromFoldable $ convertInput <$> _txBodyInputs containerHelper + txBody outputs <- _txBodyOutputs containerHelper txBody @@ -301,7 +302,8 @@ convertTxBody txBody = do , scriptDataHash: convertScriptDataHash <$> _txBodyScriptDataHash maybeFfiHelper txBody - , collateral: _txBodyCollateral containerHelper maybeFfiHelper txBody >>= map convertInput >>> pure + , collateral: _txBodyCollateral containerHelper maybeFfiHelper txBody >>= + map convertInput >>> pure , requiredSigners: _txBodyRequiredSigners containerHelper maybeFfiHelper txBody # (map <<< map) T.RequiredSigner From cfb3756bf2e588538f2a2731aa66090d9fceae89 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Thu, 22 Dec 2022 13:23:31 +0000 Subject: [PATCH 176/373] Update CHANGELOG.md --- CHANGELOG.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index f11f840775..eff8665665 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -48,7 +48,7 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) - `blake2b224Hash` and `blake2b224HashHex` functions for computing blake2b-224 hashes of arbitrary byte arrays ([#1323](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1323)) ### Changed -- `Balancer` no longer selects UTxOs which use PlutusV2 features when the transaction contains PlutusV1 scripts ([#1349](https://github.com/Plutonomicon/cardano-transaction-lib/issues/1349)) +- Balancer no longer selects UTxOs which use PlutusV2 features when the transaction contains PlutusV1 scripts ([#1349](https://github.com/Plutonomicon/cardano-transaction-lib/issues/1349)) ### Removed From c7ba5540d9f59a24dccc5abe59656e81599bf290 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Thu, 22 Dec 2022 21:06:23 +0400 Subject: [PATCH 177/373] Fix warnings --- src/Internal/ApplyArgs.purs | 5 +++-- src/Internal/Deserialization/UnspentOutput.purs | 1 - 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Internal/ApplyArgs.purs b/src/Internal/ApplyArgs.purs index f73a005fc4..6c670300a0 100644 --- a/src/Internal/ApplyArgs.purs +++ b/src/Internal/ApplyArgs.purs @@ -3,19 +3,20 @@ module Ctl.Internal.ApplyArgs , applyArgs ) where +import Prelude + import Aeson (class DecodeAeson, class EncodeAeson) -import Contract.Prelude (Either(Left, Right), bind, note, ($)) import Ctl.Internal.Deserialization.WitnessSet as D import Ctl.Internal.Serialization.PlutusData (convertPlutusData) as S import Ctl.Internal.Serialization.PlutusScript (convertPlutusScript) as S import Ctl.Internal.Serialization.Types as CSL import Ctl.Internal.Types.PlutusData (PlutusData(List)) import Ctl.Internal.Types.Scripts (PlutusScript) +import Data.Either (Either(Left, Right)) import Data.Generic.Rep (class Generic) import Data.Newtype (class Newtype) import Data.Profunctor.Choice (left) import Data.Show.Generic (genericShow) -import Prelude (class Show) foreign import apply_params_to_script :: (forall (x :: Type). x -> Either x CSL.PlutusScript) diff --git a/src/Internal/Deserialization/UnspentOutput.purs b/src/Internal/Deserialization/UnspentOutput.purs index 2ba5d74ac9..3068600eee 100644 --- a/src/Internal/Deserialization/UnspentOutput.purs +++ b/src/Internal/Deserialization/UnspentOutput.purs @@ -67,7 +67,6 @@ import Data.Traversable (for, traverse) import Data.Tuple (Tuple(Tuple)) import Data.Tuple.Nested (type (/\)) import Data.UInt (UInt) -import Data.UInt as UInt convertUnspentOutput :: TransactionUnspentOutput -> Maybe T.TransactionUnspentOutput From 17a75e1e9c8bf84d662fb88ae7389db16ecac078 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Thu, 22 Dec 2022 22:46:53 +0400 Subject: [PATCH 178/373] Fix concurrency problem in staking tests affecting CI --- src/Contract/Transaction.purs | 2 + src/Internal/Cardano/Types/Transaction.purs | 24 ++++--- test/Plutip/Staking.purs | 69 +++++++++------------ 3 files changed, 48 insertions(+), 47 deletions(-) diff --git a/src/Contract/Transaction.purs b/src/Contract/Transaction.purs index 133cd7fe4e..337210156e 100644 --- a/src/Contract/Transaction.purs +++ b/src/Contract/Transaction.purs @@ -142,6 +142,8 @@ import Ctl.Internal.Cardano.Types.Transaction , _vkeys , _withdrawals , _witnessSet + , mkPoolPubKeyHash + , poolPubKeyHashToBech32 ) as Transaction import Ctl.Internal.Cardano.Types.Transaction ( Transaction diff --git a/src/Internal/Cardano/Types/Transaction.purs b/src/Internal/Cardano/Types/Transaction.purs index 3ce257c8f2..4f12c39d92 100644 --- a/src/Internal/Cardano/Types/Transaction.purs +++ b/src/Internal/Cardano/Types/Transaction.purs @@ -31,6 +31,8 @@ module Ctl.Internal.Cardano.Types.Transaction , PoolMetadata(PoolMetadata) , PoolMetadataHash(PoolMetadataHash) , PoolPubKeyHash(PoolPubKeyHash) + , mkPoolPubKeyHash + , poolPubKeyHashToBech32 , ProposedProtocolParameterUpdates(ProposedProtocolParameterUpdates) , ProtocolParamUpdate , ProtocolVersion @@ -105,13 +107,7 @@ import Ctl.Internal.Deserialization.Keys , publicKeyFromBech32 ) import Ctl.Internal.FromData (class FromData, fromData) -import Ctl.Internal.Helpers - ( appendMap - , encodeMap - , encodeTagged' - , () - , (<<>>) - ) +import Ctl.Internal.Helpers (appendMap, encodeMap, encodeTagged', (), (<<>>)) import Ctl.Internal.Serialization.Address ( Address , NetworkId @@ -122,6 +118,7 @@ import Ctl.Internal.Serialization.Hash ( Ed25519KeyHash , ed25519KeyHashFromBech32 , ed25519KeyHashToBech32 + , ed25519KeyHashToBech32Unsafe ) import Ctl.Internal.Serialization.Keys ( bech32FromEd25519Signature @@ -154,12 +151,14 @@ import Data.Lens.Iso.Newtype (_Newtype) import Data.Lens.Record (prop) import Data.Lens.Types (Lens') import Data.Map (Map) -import Data.Maybe (Maybe(Nothing), fromJust) +import Data.Maybe (Maybe(Nothing), fromJust, isJust) import Data.Monoid (guard) import Data.Newtype (class Newtype, unwrap, wrap) import Data.Set (Set) import Data.Set (union) as Set import Data.Show.Generic (genericShow) +import Data.String.CodeUnits as String +import Data.String.Pattern (Pattern(Pattern)) import Data.Symbol (SProxy(SProxy)) import Data.Tuple (Tuple(Tuple)) import Data.Tuple.Nested (type (/\)) @@ -641,6 +640,15 @@ instance Show PoolPubKeyHash where <> show (ed25519KeyHashToBech32 "pool" kh) <> ")))" +mkPoolPubKeyHash :: Bech32String -> Maybe PoolPubKeyHash +mkPoolPubKeyHash str + | isJust (String.stripPrefix (Pattern "pool") str) = wrap <$> + ed25519KeyHashFromBech32 str + | otherwise = Nothing + +poolPubKeyHashToBech32 :: PoolPubKeyHash -> Bech32String +poolPubKeyHashToBech32 = unwrap >>> ed25519KeyHashToBech32Unsafe "pool" + data Certificate = StakeRegistration StakeCredential | StakeDeregistration StakeCredential diff --git a/test/Plutip/Staking.purs b/test/Plutip/Staking.purs index f33665d728..fa708cc181 100644 --- a/test/Plutip/Staking.purs +++ b/test/Plutip/Staking.purs @@ -42,6 +42,7 @@ import Contract.Transaction ( Epoch(Epoch) , PoolPubKeyHash(PoolPubKeyHash) , balanceTx + , mkPoolPubKeyHash , signTransaction , vrfKeyHashFromBytes ) @@ -69,11 +70,11 @@ import Contract.Wallet.Key (keyWalletPrivateStakeKey, publicKeyFromPrivateKey) import Control.Monad.Reader (asks) import Ctl.Examples.AlwaysSucceeds (alwaysSucceedsScript) import Ctl.Internal.Test.TestPlanM (TestPlanM, interpretWithConfig) -import Data.Array (head) +import Data.Array (head, (!!)) import Data.Array as Array import Data.BigInt as BigInt import Data.Foldable (for_) -import Data.Maybe (Maybe(Just, Nothing), fromJust) +import Data.Maybe (Maybe(Just, Nothing), fromJust, maybe) import Data.Newtype (unwrap) import Data.Posix.Signal (Signal(SIGINT)) import Data.Time.Duration (Seconds(Seconds)) @@ -90,7 +91,8 @@ import Effect.Aff , launchAff ) import Effect.Aff.Class (liftAff) -import Effect.Exception (error) +import Effect.Class (liftEffect) +import Effect.Exception (error, throw) import Mote (group, test) import Partial.Unsafe (unsafePartial) import Test.Ctl.Plutip.Common (config) as Common @@ -108,6 +110,26 @@ main = interruptOnSignal SIGINT =<< launchAff do suite :: TestPlanM (Aff Unit) Unit suite = do + -- We must never select this pool, because it retires at the third epoch + -- (this is Plutip internal knowledge) + -- https://github.com/mlabs-haskell/plutip/blob/7f2d59abd911dd11310404863cdedb2886902ebf/src/Test/Plutip/Internal/Cluster.hs#L692 + retiringPoolId <- liftEffect + $ maybe (throw "unable to decode poolId bech32") pure + $ mkPoolPubKeyHash + "pool1rv7ur8r2hz02lly9q8ehtwcrcydl3m2arqmndvwcqsfavgaemt6" + let + -- A routine function that filters out retiring pool from the list of available + -- pools + selectPoolId :: Contract () PoolPubKeyHash + selectPoolId = do + pools <- getPoolIds + logInfo' "Pool IDs:" + logInfo' $ show pools + for_ pools \poolId -> do + logInfo' "Pool parameters" + logInfo' <<< show =<< getPoolParameters poolId + liftM (error "unable to get any pools") + (Array.filter (_ /= retiringPoolId) pools !! 1) group "Staking" do group "Stake keys: register & deregister" do test "PubKey" do @@ -317,11 +339,6 @@ suite = do -- List pools: the pool must appear in the list do pools <- getPoolIds - logInfo' "Pool IDs:" - logInfo' $ show pools - for_ pools \poolId -> do - logInfo' "Pool parameters" - logInfo' <<< show =<< getPoolParameters poolId pools `shouldSatisfy` Array.elem poolOperator currentEpoch <- getCurrentEpoch @@ -360,11 +377,6 @@ suite = do -- List pools: the pool must not appear in the list do pools <- getPoolIds - logInfo' "Pool IDs:" - logInfo' $ show pools - for_ pools \poolId -> do - logInfo' "Pool parameters" - logInfo' <<< show =<< getPoolParameters poolId pools `shouldSatisfy` Array.notElem poolOperator test "Plutus Stake script: delegate to existing pool & withdraw rewards" do @@ -414,15 +426,8 @@ suite = do ubTx <- liftedE $ Lookups.mkUnbalancedTx lookups constraints liftedE (balanceTx ubTx) >>= signTransaction >>= submitAndLog - -- List pools - poolId <- do - pools <- getPoolIds - logInfo' "Pool IDs:" - logInfo' $ show pools - for_ pools \poolId -> do - logInfo' "Pool parameters" - logInfo' <<< show =<< getPoolParameters poolId - liftM (error "unable to get any pools") (pools Array.!! 2) + -- Select a pool + poolId <- selectPoolId -- Delegate do @@ -537,14 +542,7 @@ suite = do withKeyWallet bob do -- Select first pool - poolId <- do - pools <- getPoolIds - logInfo' "Pool IDs:" - logInfo' $ show pools - for_ pools \poolId -> do - logInfo' "Pool parameters" - logInfo' <<< show =<< getPoolParameters poolId - liftM (error "unable to get any pools") (pools Array.!! 2) + poolId <- selectPoolId -- Delegate do @@ -625,15 +623,8 @@ suite = do ubTx <- liftedE $ Lookups.mkUnbalancedTx lookups constraints liftedE (balanceTx ubTx) >>= signTransaction >>= submitAndLog - -- List pools - poolId <- do - pools <- getPoolIds - logInfo' "Pool IDs:" - logInfo' $ show pools - for_ pools \poolId -> do - logInfo' "Pool parameters" - logInfo' <<< show =<< getPoolParameters poolId - liftM (error "unable to get any pools") (head pools) + -- Select a pool ID + poolId <- selectPoolId -- Delegate do From e75da3bba01851685668aac6bd0abcf9659269fb Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Thu, 22 Dec 2022 23:01:55 +0400 Subject: [PATCH 179/373] Try increasing the number of connection attempts in E2E --- src/Internal/Test/E2E/Feedback/Node.purs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Internal/Test/E2E/Feedback/Node.purs b/src/Internal/Test/E2E/Feedback/Node.purs index e47db0bb59..6ee1692e00 100644 --- a/src/Internal/Test/E2E/Feedback/Node.purs +++ b/src/Internal/Test/E2E/Feedback/Node.purs @@ -96,7 +96,7 @@ subscribeToBrowserEvents page cont = do where -- How many times to try until we get any event? firstTimeConnectionAttempts :: Int - firstTimeConnectionAttempts = 10 + firstTimeConnectionAttempts = 30 getBrowserEvents :: Toppokki.Page -> Aff (Array BrowserEvent) From 12526815e3535745d3af31070d8d4c82535ecb6a Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Thu, 22 Dec 2022 23:12:57 +0400 Subject: [PATCH 180/373] Apply suggestions --- src/Internal/Cardano/Types/Transaction.purs | 8 +++----- test/Plutip/Staking.purs | 7 +++---- 2 files changed, 6 insertions(+), 9 deletions(-) diff --git a/src/Internal/Cardano/Types/Transaction.purs b/src/Internal/Cardano/Types/Transaction.purs index 4f12c39d92..aa389abfd1 100644 --- a/src/Internal/Cardano/Types/Transaction.purs +++ b/src/Internal/Cardano/Types/Transaction.purs @@ -151,14 +151,13 @@ import Data.Lens.Iso.Newtype (_Newtype) import Data.Lens.Record (prop) import Data.Lens.Types (Lens') import Data.Map (Map) -import Data.Maybe (Maybe(Nothing), fromJust, isJust) +import Data.Maybe (Maybe(Nothing), fromJust) import Data.Monoid (guard) import Data.Newtype (class Newtype, unwrap, wrap) import Data.Set (Set) import Data.Set (union) as Set import Data.Show.Generic (genericShow) -import Data.String.CodeUnits as String -import Data.String.Pattern (Pattern(Pattern)) +import Data.String.Utils (startsWith) import Data.Symbol (SProxy(SProxy)) import Data.Tuple (Tuple(Tuple)) import Data.Tuple.Nested (type (/\)) @@ -642,8 +641,7 @@ instance Show PoolPubKeyHash where mkPoolPubKeyHash :: Bech32String -> Maybe PoolPubKeyHash mkPoolPubKeyHash str - | isJust (String.stripPrefix (Pattern "pool") str) = wrap <$> - ed25519KeyHashFromBech32 str + | startsWith "pool" str = PoolPubKeyHash <$> ed25519KeyHashFromBech32 str | otherwise = Nothing poolPubKeyHashToBech32 :: PoolPubKeyHash -> Bech32String diff --git a/test/Plutip/Staking.purs b/test/Plutip/Staking.purs index fa708cc181..bf936e34f8 100644 --- a/test/Plutip/Staking.purs +++ b/test/Plutip/Staking.purs @@ -74,7 +74,7 @@ import Data.Array (head, (!!)) import Data.Array as Array import Data.BigInt as BigInt import Data.Foldable (for_) -import Data.Maybe (Maybe(Just, Nothing), fromJust, maybe) +import Data.Maybe (Maybe(Just, Nothing), fromJust) import Data.Newtype (unwrap) import Data.Posix.Signal (Signal(SIGINT)) import Data.Time.Duration (Seconds(Seconds)) @@ -92,7 +92,7 @@ import Effect.Aff ) import Effect.Aff.Class (liftAff) import Effect.Class (liftEffect) -import Effect.Exception (error, throw) +import Effect.Exception (error) import Mote (group, test) import Partial.Unsafe (unsafePartial) import Test.Ctl.Plutip.Common (config) as Common @@ -113,8 +113,7 @@ suite = do -- We must never select this pool, because it retires at the third epoch -- (this is Plutip internal knowledge) -- https://github.com/mlabs-haskell/plutip/blob/7f2d59abd911dd11310404863cdedb2886902ebf/src/Test/Plutip/Internal/Cluster.hs#L692 - retiringPoolId <- liftEffect - $ maybe (throw "unable to decode poolId bech32") pure + retiringPoolId <- liftEffect $ liftM (error "unable to decode poolId bech32") $ mkPoolPubKeyHash "pool1rv7ur8r2hz02lly9q8ehtwcrcydl3m2arqmndvwcqsfavgaemt6" let From a0d265828f944e3623f64738b2bc159512a12109 Mon Sep 17 00:00:00 2001 From: Amir Rad Date: Fri, 23 Dec 2022 13:06:18 +0000 Subject: [PATCH 181/373] Some rewording and spelling of contract modules --- src/Contract/Address.purs | 8 ++++---- src/Contract/AuxiliaryData.purs | 14 +++++++------- src/Internal/BalanceTx/Constraints.purs | 12 ++++++------ src/Internal/Deserialization/Error.purs | 4 +--- src/Internal/Plutus/Types/AssocMap.purs | 6 +++--- src/Internal/QueryM.purs | 1 - src/Internal/QueryM/Ogmios.purs | 6 +++--- src/Internal/Types/CborBytes.purs | 2 +- 8 files changed, 25 insertions(+), 28 deletions(-) diff --git a/src/Contract/Address.purs b/src/Contract/Address.purs index 79f36e1dbc..a785ecdf34 100644 --- a/src/Contract/Address.purs +++ b/src/Contract/Address.purs @@ -160,7 +160,7 @@ getWalletAddressWithNetworkTag => Contract r (Maybe AddressWithNetworkTag) getWalletAddressWithNetworkTag = head <$> getWalletAddressesWithNetworkTag --- | Get all the `AddressWithNetworkTag` of the browser wallet discarding errors. +-- | Get all the `AddressWithNetworkTag`s of the browser wallet discarding errors. getWalletAddressesWithNetworkTag :: forall (r :: Row Type). Contract r (Array AddressWithNetworkTag) getWalletAddressesWithNetworkTag = do @@ -176,7 +176,7 @@ getWalletAddressesWithNetworkTag = do -- | Get the collateral of the browser wallet. This collateral will vary -- | depending on the wallet. --- | E.g. Nami creates a hardcoded 5 Ada collateral. +-- | E.g. Nami creates a hard-coded 5 Ada collateral. -- | Throws on `Promise` rejection by wallet, returns `Nothing` if no collateral -- | is available. getWalletCollateral @@ -223,8 +223,8 @@ getNetworkId = wrapContract QueryM.getNetworkId -------------------------------------------------------------------------------- -- Helpers via Cardano helpers, these are helpers from the CSL equivalent --- that converts either input or output to a Plutus Address. --- Helpers by deconstructing/constructing the Plutus Address are exported under +-- that convert either input or output to a Plutus Address. +-- Helpers that deconstruct/construct the Plutus Address are exported under -- `module Address` -------------------------------------------------------------------------------- diff --git a/src/Contract/AuxiliaryData.purs b/src/Contract/AuxiliaryData.purs index 106b6b4a1a..718d930612 100644 --- a/src/Contract/AuxiliaryData.purs +++ b/src/Contract/AuxiliaryData.purs @@ -33,13 +33,13 @@ import Data.Maybe (Maybe, fromMaybe) import Data.Tuple (Tuple(Tuple)) import Effect.Class (liftEffect) --- These functions involve `UnattachedUnbalancedTx` which in turns involve --- `UnbalancedTx`, these involve `ScriptOutput` which is what is currently --- being used in more up-to-date Plutus code (as opposed to `TransactionOutput`). --- Therefore, we won't provide any conversion. It is worth noting --- `UnattachedUnbalancedTx` also includes Cardano-style Redeemers, although --- I don't think there's a way around this because they need to be reattached --- later on - see Types.ScriptLookups for more detail. +-- These functions involve `UnattachedUnbalancedTx`, +-- which in turn involve `UnbalancedTx`. These functions involve ScriptOutput, +-- which is the type currently being used in more recent Plutus code (as opposed to `TransactionOutput`). +-- As a result, no conversion will be provided. +-- It is worth noting that `UnattachedUnbalancedTx` also includes Cardano-style Redeemers, +-- which must be reattached later on (see Types.ScriptLookups for more information). +-- There does not appear to be a way around this. setAuxiliaryData :: forall (r :: Row Type) diff --git a/src/Internal/BalanceTx/Constraints.purs b/src/Internal/BalanceTx/Constraints.purs index b6e16beb09..6236f4acf4 100644 --- a/src/Internal/BalanceTx/Constraints.purs +++ b/src/Internal/BalanceTx/Constraints.purs @@ -103,7 +103,7 @@ mustSendChangeToAddress mustSendChangeToAddress = wrap <<< setJust _changeAddress <<< fromPlutusAddressWithNetworkTag --- | Tells the balancer to use utxos at given addresses. +-- | Tells the balancer to use UTxO's at given addresses. -- | If this constraint is not set, then the default addresses owned by the -- | wallet are used. -- | @@ -114,7 +114,7 @@ mustUseUtxosAtAddresses mustUseUtxosAtAddresses networkId = wrap <<< setJust _srcAddresses <<< map (fromPlutusAddress networkId) --- | Tells the balancer to use utxos at a given address. +-- | Tells the balancer to use UTxO's at a given address. -- | If this constraint is not set, then the default addresses owned by the -- | wallet are used. -- | @@ -133,18 +133,18 @@ mustGenChangeOutsWithMaxTokenQuantity :: BigInt -> BalanceTxConstraintsBuilder mustGenChangeOutsWithMaxTokenQuantity = wrap <<< setJust _maxChangeOutputTokenQuantity <<< max one --- | Tells the balancer not to spend utxos with the specified output references. +-- | Tells the balancer not to spend UTxO's with the specified output references. mustNotSpendUtxosWithOutRefs :: Set TransactionInput -> BalanceTxConstraintsBuilder mustNotSpendUtxosWithOutRefs = wrap <<< appendOver _nonSpendableInputs --- | Tells the balancer not to spend a utxo with the specified output reference. +-- | Tells the balancer not to spend a UTxO with the specified output reference. mustNotSpendUtxoWithOutRef :: TransactionInput -> BalanceTxConstraintsBuilder mustNotSpendUtxoWithOutRef = mustNotSpendUtxosWithOutRefs <<< Set.singleton --- | Tells the balancer to use the provided utxo set when evaluating script +-- | Tells the balancer to use the provided UTxO set when evaluating script -- | execution units (sets `additionalUtxoSet` of Ogmios `EvaluateTx`). --- | Note that you need to use `unspentOutputs` lookup to make these utxos +-- | Note that you need to use `unspentOutputs` lookup to make these UTxO's -- | spendable by the transaction (see `Examples.TxChaining` for reference). mustUseAdditionalUtxos :: Plutus.UtxoMap -> BalanceTxConstraintsBuilder mustUseAdditionalUtxos = wrap <<< set _additionalUtxos diff --git a/src/Internal/Deserialization/Error.purs b/src/Internal/Deserialization/Error.purs index dd425ff4b5..5edb6631e7 100644 --- a/src/Internal/Deserialization/Error.purs +++ b/src/Internal/Deserialization/Error.purs @@ -73,17 +73,15 @@ toError = error <<< match -- | FromBytesError row alias type FromBytesError r = (fromBytesError :: String | r) --- | Needed to craate a variant type +-- | Needed to create a variant type _fromBytesError = Proxy :: Proxy "fromBytesError" --- | An error to use fromBytesError :: forall (r :: Row Type) (a :: Type) . String -> E (FromBytesError + r) a fromBytesError = Left <<< inj _fromBytesError --- | An internal helper to shorten code fromBytesErrorHelper :: forall (r :: Row Type) . ErrorFfiHelper (FromBytesError + r) diff --git a/src/Internal/Plutus/Types/AssocMap.purs b/src/Internal/Plutus/Types/AssocMap.purs index 411c9b1d36..9b5bcb5f63 100644 --- a/src/Internal/Plutus/Types/AssocMap.purs +++ b/src/Internal/Plutus/Types/AssocMap.purs @@ -58,7 +58,7 @@ import Data.Tuple.Nested (type (/\), (/\)) -- toList :: Map k v -> [(k, v)]. Therefore, I will derive Generic and Newtype -- instance and export the constructor. We could potentially provide this by -- having a `fromList` in `Maybe` although we should probably try to replicate --- behaviour so that our CTL and onchain behaviours match. There doesn't even +-- behaviour so that our CTL and on-chain behaviours match. There doesn't even -- seem to be an `Ord` constraint on the keys. -- | A Plutus-style associated list `Map` of key-value pairs. newtype Map (k :: Type) (v :: Type) = Map (Array (Tuple k v)) @@ -119,11 +119,11 @@ instance (Eq k, Semigroup v) => Monoid (Map k v) where lookup :: forall (k :: Type) (v :: Type). Eq k => k -> Map k v -> Maybe v lookup k (Map xs) = Foldable.lookup k xs --- | Whether is a key is a member of a `Map` +-- | Whether given key is a member of a `Map` member :: forall (k :: Type) (v :: Type). Eq k => k -> Map k v -> Boolean member k = isJust <<< lookup k --- Insert a key, value pair into a `Map` +-- Insert a key-value pair into a `Map` insert :: forall k v. (Eq k) => k -> v -> Map k v -> Map k v insert k v m = unionWith (\_ b -> b) m $ singleton k v diff --git a/src/Internal/QueryM.purs b/src/Internal/QueryM.purs index e433cc81af..617f3702bf 100644 --- a/src/Internal/QueryM.purs +++ b/src/Internal/QueryM.purs @@ -277,7 +277,6 @@ import Effect.Exception (Error, error, throw, try) import Effect.Ref (Ref) import Effect.Ref as Ref - -- | Cluster setup contains everything that is needed to run a `Contract` on -- | a local cluster: paramters to connect to the services and private keys -- | that are pre-funded with Ada on that cluster diff --git a/src/Internal/QueryM/Ogmios.purs b/src/Internal/QueryM/Ogmios.purs index aa49b2be51..58c2e99819 100644 --- a/src/Internal/QueryM/Ogmios.purs +++ b/src/Internal/QueryM/Ogmios.purs @@ -1343,7 +1343,7 @@ instance DecodeAeson ChainTipQR where r :: (ChainOrigin |+| ChainPoint) <- decodeAeson j pure $ either CtChainOrigin CtChainPoint $ toEither1 r --- | A Blake2b 32-byte digest of an era-independent block header, serialised as +-- | A Blake2b 32-byte digest of an era-independent block header, serialized as -- CBOR in base16 newtype OgmiosBlockHeaderHash = OgmiosBlockHeaderHash String @@ -1370,7 +1370,7 @@ instance Show ChainOrigin where -- | A point on the chain, identified by a slot and a block header hash type ChainPoint = { slot :: Slot -- See https://github.com/Plutonomicon/cardano-transaction-lib/issues/632 - -- for details on why we lose a neglible amount of precision. + -- for details on why we lose a negligible amount of precision. , hash :: OgmiosBlockHeaderHash } @@ -1500,7 +1500,7 @@ aesonObject -> Either JsonDecodeError a aesonObject = caseAesonObject (Left (TypeMismatch "Expected Object")) --- helper for assumming we get an array +-- helper for assuming we get an array aesonArray :: forall (a :: Type) . (Array Aeson -> Either JsonDecodeError a) diff --git a/src/Internal/Types/CborBytes.purs b/src/Internal/Types/CborBytes.purs index 36137e7ffa..4d69c1d5e3 100644 --- a/src/Internal/Types/CborBytes.purs +++ b/src/Internal/Types/CborBytes.purs @@ -26,7 +26,7 @@ import Data.Maybe (Maybe) import Data.Newtype (class Newtype, unwrap, wrap) import Test.QuickCheck.Arbitrary (class Arbitrary) --- | An array of Bytes containing CBOR data +-- | An array of bytes containing CBOR data newtype CborBytes = CborBytes ByteArray instance Show CborBytes where From e2812a0651f792a016b56e0a8cfde2b355d41a25 Mon Sep 17 00:00:00 2001 From: Gregory Gerasev Date: Mon, 26 Dec 2022 11:51:27 +0400 Subject: [PATCH 182/373] Fix some review issues --- src/Internal/Contract/Sign.purs | 5 +---- src/Internal/Wallet/Cip30Mock.purs | 4 ++++ 2 files changed, 5 insertions(+), 4 deletions(-) diff --git a/src/Internal/Contract/Sign.purs b/src/Internal/Contract/Sign.purs index 00d84bbcaf..7fa2b3d6cf 100644 --- a/src/Internal/Contract/Sign.purs +++ b/src/Internal/Contract/Sign.purs @@ -38,10 +38,7 @@ signTransaction :: Transaction.Transaction -> Contract (Maybe Transaction.Transaction) signTransaction tx = do hooks <- asks _.hooks - let - runHook = - for_ hooks.beforeSign (void <<< liftEffect <<< try) - runHook + for_ hooks.beforeSign (void <<< liftEffect <<< try) withWallet case _ of Nami nami -> liftAff $ callCip30Wallet nami \nw -> flip nw.signTx tx Gero gero -> liftAff $ callCip30Wallet gero \nw -> flip nw.signTx tx diff --git a/src/Internal/Wallet/Cip30Mock.purs b/src/Internal/Wallet/Cip30Mock.purs index 0ffd2b95bf..9ee781ef6e 100644 --- a/src/Internal/Wallet/Cip30Mock.purs +++ b/src/Internal/Wallet/Cip30Mock.purs @@ -143,6 +143,10 @@ mkCip30Mock pKey mSKey = do byteArrayToHex $ unwrap $ toBytes ((unwrap keyWallet).address env.networkId :: Address) + ownUtxos = do + let ownAddress = (unwrap keyWallet).address env.networkId + utxosAt ownAddress + pure $ { getNetworkId: fromAff $ pure $ case env.networkId of From a1e4fa1c23e102f941a338bc4292a02cf35c4f7d Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Tue, 27 Dec 2022 12:35:57 +0000 Subject: [PATCH 183/373] Remove do. Remove case. --- src/Internal/BalanceTx/BalanceTx.purs | 2 +- src/Internal/Types/ScriptLookups.purs | 14 ++++++-------- 2 files changed, 7 insertions(+), 9 deletions(-) diff --git a/src/Internal/BalanceTx/BalanceTx.purs b/src/Internal/BalanceTx/BalanceTx.purs index f09306c348..2a25159431 100644 --- a/src/Internal/BalanceTx/BalanceTx.purs +++ b/src/Internal/BalanceTx/BalanceTx.purs @@ -291,7 +291,7 @@ runBalancer p = do -- We check if the transaction uses a plutusv1 script, so that we can filter -- out utxos which use plutusv2 features if so. txHasPlutusV1 :: Boolean - txHasPlutusV1 = do + txHasPlutusV1 = case p.unbalancedTx ^. _transaction' ^. _witnessSet ^. _plutusScripts of Just scripts -> flip Array.any scripts case _ of PlutusScript (_ /\ PlutusV1) -> true diff --git a/src/Internal/Types/ScriptLookups.purs b/src/Internal/Types/ScriptLookups.purs index 1b72f3bacc..ffdcb71ba4 100644 --- a/src/Internal/Types/ScriptLookups.purs +++ b/src/Internal/Types/ScriptLookups.purs @@ -1078,14 +1078,12 @@ processConstraint mpsMap osMap = do let value = fromPlutusValue plutusValue runExceptT $ _valueSpentBalancesOutputs <>= requireValue value MustSpendPubKeyOutput txo -> runExceptT do - txOut <- ExceptT $ lookupTxOutRef txo Nothing - case txOut of - TransactionOutput { amount } -> do - -- POTENTIAL FIX ME: Plutus has Tx.TxIn and Tx.PubKeyTxIn -- TxIn - -- keeps track TransactionInput and TxInType (the input type, whether - -- consuming script, public key or simple script) - _cpsToTxBody <<< _inputs %= Set.insert txo - _valueSpentBalancesInputs <>= provideValue amount + TransactionOutput { amount } <- ExceptT $ lookupTxOutRef txo Nothing + -- POTENTIAL FIX ME: Plutus has Tx.TxIn and Tx.PubKeyTxIn -- TxIn + -- keeps track TransactionInput and TxInType (the input type, whether + -- consuming script, public key or simple script) + _cpsToTxBody <<< _inputs %= Set.insert txo + _valueSpentBalancesInputs <>= provideValue amount MustSpendScriptOutput txo red scriptRefUnspentOut -> runExceptT do txOut <- ExceptT $ lookupTxOutRef txo scriptRefUnspentOut case txOut of From 86e8c987d6bd3244baf48770419abfb6f743d819 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Tue, 27 Dec 2022 13:37:38 +0100 Subject: [PATCH 184/373] WIP: Implement getUtxoByOref Blockfrost query --- src/Internal/Contract/QueryBackend.purs | 2 + src/Internal/Contract/QueryHandle.purs | 18 ++- src/Internal/Service/Blockfrost.purs | 197 ++++++++++++++++++++++++ src/Internal/Service/Helpers.purs | 57 +++++++ 4 files changed, 273 insertions(+), 1 deletion(-) create mode 100644 src/Internal/Service/Blockfrost.purs create mode 100644 src/Internal/Service/Helpers.purs diff --git a/src/Internal/Contract/QueryBackend.purs b/src/Internal/Contract/QueryBackend.purs index bba4f219a3..66fcb91c6a 100644 --- a/src/Internal/Contract/QueryBackend.purs +++ b/src/Internal/Contract/QueryBackend.purs @@ -35,6 +35,7 @@ type CtlBackend = type BlockfrostBackend = { blockfrostConfig :: ServerConfig + , blockfrostApiKey :: Maybe String } getCtlBackend :: QueryBackend -> Maybe CtlBackend @@ -60,6 +61,7 @@ type CtlBackendParams = type BlockfrostBackendParams = { blockfrostConfig :: ServerConfig + , blockfrostApiKey :: Maybe String } mkCtlBackendParams :: CtlBackendParams -> QueryBackendParams diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs index 800cce67d6..85f62f87bb 100644 --- a/src/Internal/Contract/QueryHandle.purs +++ b/src/Internal/Contract/QueryHandle.purs @@ -46,6 +46,8 @@ import Ctl.Internal.QueryM.Ogmios (SubmitTxR(SubmitTxSuccess), TxEvaluationR) import Ctl.Internal.Serialization (convertTransaction, toBytes) as Serialization import Ctl.Internal.Serialization.Address (Address) import Ctl.Internal.Serialization.Hash (ScriptHash) +import Ctl.Internal.Service.Blockfrost (getUtxoByOref) as Blockfrost +import Ctl.Internal.Service.Blockfrost (runBlockfrostServiceM) import Ctl.Internal.Types.Chain as Chain import Ctl.Internal.Types.Datum (DataHash, Datum) import Ctl.Internal.Types.Transaction (TransactionHash, TransactionInput) @@ -115,5 +117,19 @@ queryHandleForCtlBackend contractEnv backend = queryHandleForBlockfrostBackend :: ContractEnv -> BlockfrostBackend -> QueryHandle -queryHandleForBlockfrostBackend = undefined +queryHandleForBlockfrostBackend contractEnv backend = + { getDatumByHash: undefined + , getScriptByHash: undefined + , getUtxoByOref: + -- FIXME: remove `undefined` + undefined <<< runBlockfrostServiceM backend <<< Blockfrost.getUtxoByOref + , isTxConfirmed: undefined + , getTxMetadata: undefined + , utxosAt: undefined + , getChainTip: undefined + , getCurrentEpoch: undefined + , submitTx: undefined + , evaluateTx: undefined + , getEraSummaries: undefined + } diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs new file mode 100644 index 0000000000..6dced3ab3c --- /dev/null +++ b/src/Internal/Service/Blockfrost.purs @@ -0,0 +1,197 @@ +module Ctl.Internal.Service.Blockfrost + ( BlockfrostTransactionOutput -- TODO: should not be exported + , getUtxoByOref + , runBlockfrostServiceM + ) where + +import Prelude + +import Aeson + ( class DecodeAeson + , Aeson + , JsonDecodeError(TypeMismatch) + , decodeAeson + , getField + , getFieldOptional' + ) +import Affjax (Error, Response, URL, defaultRequest, request) as Affjax +import Affjax.RequestHeader (RequestHeader(RequestHeader)) as Affjax +import Affjax.ResponseFormat (string) as Affjax.ResponseFormat +import Control.Monad.Except.Trans (ExceptT(ExceptT), runExceptT) +import Control.Monad.Reader.Class (ask) +import Control.Monad.Reader.Trans (ReaderT, runReaderT) +import Ctl.Internal.Cardano.Types.Transaction (TransactionOutput, UtxoMap) +import Ctl.Internal.Cardano.Types.Value (Value) +import Ctl.Internal.Cardano.Types.Value + ( lovelaceValueOf + , mkSingletonNonAdaAsset + , mkValue + ) as Value +import Ctl.Internal.Contract.QueryBackend (BlockfrostBackend) +import Ctl.Internal.Deserialization.PlutusData (deserializeData) +import Ctl.Internal.QueryM (ClientError, handleAffjaxResponse) +import Ctl.Internal.QueryM.ServerConfig (ServerConfig, mkHttpUrl) +import Ctl.Internal.Serialization.Address (Address, addressFromBech32) +import Ctl.Internal.Serialization.Hash (ScriptHash) +import Ctl.Internal.Service.Helpers (aesonArray, aesonObject, decodeAssetClass) +import Ctl.Internal.Types.ByteArray (byteArrayToHex) +import Ctl.Internal.Types.OutputDatum + ( OutputDatum(NoOutputDatum, OutputDatum, OutputDatumHash) + ) +import Ctl.Internal.Types.Transaction + ( TransactionHash + , TransactionInput(TransactionInput) + ) +import Data.Array (find) as Array +import Data.Either (Either(Left), note) +import Data.Foldable (fold) +import Data.Generic.Rep (class Generic) +import Data.HTTP.Method (Method(GET)) +import Data.Maybe (Maybe(Just, Nothing), maybe) +import Data.Newtype (class Newtype, unwrap, wrap) +import Data.Show.Generic (genericShow) +import Data.String (splitAt) as String +import Data.Traversable (traverse) +import Data.Tuple (Tuple(Tuple), fst, snd) +import Data.Tuple.Nested (type (/\), (/\)) +import Effect.Aff (Aff) +import Effect.Aff.Class (liftAff) +import Foreign.Object (Object) +import Undefined (undefined) + +type BlockfrostServiceParams = + { blockfrostConfig :: ServerConfig + , blockfrostApiKey :: Maybe String + } + +type BlockfrostServiceM (a :: Type) = ReaderT BlockfrostServiceParams Aff a + +runBlockfrostServiceM + :: forall (a :: Type). BlockfrostBackend -> BlockfrostServiceM a -> Aff a +runBlockfrostServiceM backend = flip runReaderT serviceParams + where + serviceParams :: BlockfrostServiceParams + serviceParams = + { blockfrostConfig: backend.blockfrostConfig + , blockfrostApiKey: backend.blockfrostApiKey + } + +data BlockfrostEndpoint = + GetTransactionUtxos TransactionHash + +realizeEndpoint :: BlockfrostEndpoint -> Affjax.URL +realizeEndpoint endpoint = + case endpoint of + GetTransactionUtxos txHash -> + "/txs/" <> byteArrayToHex (unwrap txHash) <> "/utxos" + +blockfrostGetRequest + :: BlockfrostEndpoint + -> BlockfrostServiceM (Either Affjax.Error (Affjax.Response String)) +blockfrostGetRequest endpoint = ask >>= \params -> liftAff do + Affjax.request $ Affjax.defaultRequest + { method = Left GET + , url = mkHttpUrl params.blockfrostConfig <> realizeEndpoint endpoint + , responseFormat = Affjax.ResponseFormat.string + , headers = + maybe mempty (\apiKey -> [ Affjax.RequestHeader "project_id" apiKey ]) + params.blockfrostApiKey + } + +-------------------------------------------------------------------------------- +-- Get utxos at address / by output reference +-------------------------------------------------------------------------------- + +getUtxoByOref + :: TransactionInput + -- TODO: resolve `BlockfrostTransactionOutput` + -- -> BlockfrostServiceM (Either ClientError (Maybe TransactionOutput)) + -> BlockfrostServiceM (Either ClientError (Maybe BlockfrostTransactionOutput)) +getUtxoByOref oref@(TransactionInput { transactionId: txHash }) = runExceptT do + (blockfrostUtxoMap :: BlockfrostUtxoMap) <- + ExceptT $ handleAffjaxResponse <$> + blockfrostGetRequest (GetTransactionUtxos txHash) + pure $ snd <$> Array.find (eq oref <<< fst) (unwrap blockfrostUtxoMap) + +-------------------------------------------------------------------------------- +-- BlockfrostUtxoMap +-------------------------------------------------------------------------------- + +type BlockfrostUnspentOutput = TransactionInput /\ BlockfrostTransactionOutput + +newtype BlockfrostUtxoMap = BlockfrostUtxoMap (Array BlockfrostUnspentOutput) + +derive instance Generic BlockfrostUtxoMap _ +derive instance Newtype BlockfrostUtxoMap _ + +instance Show BlockfrostUtxoMap where + show = genericShow + +instance DecodeAeson BlockfrostUtxoMap where + decodeAeson = aesonArray (map wrap <<< traverse decodeUtxoEntry) + where + decodeUtxoEntry :: Aeson -> Either JsonDecodeError BlockfrostUnspentOutput + decodeUtxoEntry utxoAeson = + Tuple <$> decodeTxOref utxoAeson <*> decodeAeson utxoAeson + + decodeTxOref :: Aeson -> Either JsonDecodeError TransactionInput + decodeTxOref = aesonObject \obj -> do + transactionId <- getField obj "tx_hash" + index <- getField obj "output_index" + pure $ TransactionInput { transactionId, index } + +-------------------------------------------------------------------------------- +-- BlockfrostTransactionOutput +-------------------------------------------------------------------------------- + +newtype BlockfrostTransactionOutput = BlockfrostTransactionOutput + { address :: Address + , amount :: Value + , datum :: OutputDatum + , scriptHash :: Maybe ScriptHash + } + +derive instance Generic BlockfrostTransactionOutput _ +derive instance Newtype BlockfrostTransactionOutput _ + +instance Show BlockfrostTransactionOutput where + show = genericShow + +instance DecodeAeson BlockfrostTransactionOutput where + decodeAeson = aesonObject \obj -> do + address <- decodeAddress obj + amount <- decodeValue obj + datum <- decodeOutputDatum obj + scriptHash <- getFieldOptional' obj "reference_script_hash" + pure $ wrap { address, amount, datum, scriptHash } + where + decodeAddress :: Object Aeson -> Either JsonDecodeError Address + decodeAddress obj = + getField obj "address" >>= \address -> + note (TypeMismatch "Expected bech32 encoded address") + (addressFromBech32 address) + + decodeValue :: Object Aeson -> Either JsonDecodeError Value + decodeValue = + flip getField "amount" >=> aesonArray (map fold <<< traverse decodeAsset) + where + decodeAsset :: Aeson -> Either JsonDecodeError Value + decodeAsset = aesonObject \obj -> do + quantity <- getField obj "quantity" + getField obj "unit" >>= case _ of + "lovelace" -> pure $ Value.lovelaceValueOf quantity + assetString -> do + let { before: csStr, after: tnStr } = String.splitAt 56 assetString + decodeAssetClass assetString csStr tnStr <#> \(cs /\ tn) -> + Value.mkValue mempty $ Value.mkSingletonNonAdaAsset cs tn quantity + + decodeOutputDatum :: Object Aeson -> Either JsonDecodeError OutputDatum + decodeOutputDatum obj = + getFieldOptional' obj "inline_datum" >>= case _ of + Just datum -> + note (TypeMismatch "Expected CBOR encoded inline datum") + (OutputDatum <$> deserializeData datum) + Nothing -> + maybe NoOutputDatum OutputDatumHash + <$> getFieldOptional' obj "data_hash" + diff --git a/src/Internal/Service/Helpers.purs b/src/Internal/Service/Helpers.purs new file mode 100644 index 0000000000..79a43d0c1a --- /dev/null +++ b/src/Internal/Service/Helpers.purs @@ -0,0 +1,57 @@ +module Ctl.Internal.Service.Helpers + ( aesonArray + , aesonObject + , decodeAssetClass + ) where + +import Prelude + +import Aeson + ( Aeson + , JsonDecodeError(TypeMismatch) + , caseAesonArray + , caseAesonObject + ) +import Control.Apply (lift2) +import Ctl.Internal.Cardano.Types.Value (CurrencySymbol, mkCurrencySymbol) +import Ctl.Internal.Types.ByteArray (hexToByteArray) +import Ctl.Internal.Types.TokenName (TokenName, mkTokenName) +import Data.Either (Either(Left), note) +import Data.Tuple (Tuple(Tuple)) +import Data.Tuple.Nested (type (/\)) +import Foreign.Object (Object) + +aesonArray + :: forall (a :: Type) + . (Array Aeson -> Either JsonDecodeError a) + -> Aeson + -> Either JsonDecodeError a +aesonArray = caseAesonArray (Left (TypeMismatch "Expected Array")) + +aesonObject + :: forall (a :: Type) + . (Object Aeson -> Either JsonDecodeError a) + -> Aeson + -> Either JsonDecodeError a +aesonObject = caseAesonObject (Left (TypeMismatch "Expected Object")) + +decodeAssetClass + :: String + -> String + -> String + -> Either JsonDecodeError (CurrencySymbol /\ TokenName) +decodeAssetClass assetString csString tnString = + lift2 Tuple + ( note (assetStringTypeMismatch "CurrencySymbol" csString) + (mkCurrencySymbol =<< hexToByteArray csString) + ) + ( note (assetStringTypeMismatch "TokenName" tnString) + (mkTokenName =<< hexToByteArray tnString) + ) + where + assetStringTypeMismatch :: String -> String -> JsonDecodeError + assetStringTypeMismatch t actual = + TypeMismatch $ + ("In " <> assetString <> ": Expected hex-encoded " <> t) + <> (", got: " <> actual) + From 2aaf7cc5507b1ffbb3f794aaa3c4add3c76279c7 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Tue, 27 Dec 2022 13:23:24 +0000 Subject: [PATCH 185/373] Prefer getNetworkId from Contract.Address. The one from Contract.Wallet no longer represents what it used to --- examples/Cip30.purs | 2 -- examples/KeyWallet/Cip30.purs | 2 -- src/Contract/Utxos.purs | 4 ++-- src/Contract/Wallet.purs | 6 ------ 4 files changed, 2 insertions(+), 12 deletions(-) diff --git a/examples/Cip30.purs b/examples/Cip30.purs index 8d882fb4fc..42ac0c8f8a 100644 --- a/examples/Cip30.purs +++ b/examples/Cip30.purs @@ -16,7 +16,6 @@ import Contract.Wallet ( WalletExtension , apiVersion , getChangeAddress - , getNetworkId , getRewardAddresses , getUnusedAddresses , getWallet @@ -64,7 +63,6 @@ contract :: Contract Unit contract = do logInfo' "Running Examples.Cip30" logInfo' "Funtions that depend on `Contract`" - _ <- performAndLog "getNetworkId" getNetworkId _ <- performAndLog "getUnusedAddresses" getUnusedAddresses dataBytes <- liftContractAffM ("can't convert : " <> msg <> " to RawBytes") diff --git a/examples/KeyWallet/Cip30.purs b/examples/KeyWallet/Cip30.purs index b86911c352..0f1470d1db 100644 --- a/examples/KeyWallet/Cip30.purs +++ b/examples/KeyWallet/Cip30.purs @@ -11,7 +11,6 @@ import Contract.Monad (Contract) import Contract.Prim.ByteArray (RawBytes) import Contract.Wallet ( getChangeAddress - , getNetworkId , getRewardAddresses , getUnusedAddresses , signData @@ -28,7 +27,6 @@ mkContract :: RawBytes -> Contract Unit mkContract dat = do logInfo' "Running Examples.KeyWallet.Cip30" logInfo' "Funtions that depend on `Contract`" - _ <- performAndLog "getNetworkId" getNetworkId _ <- performAndLog "getUnusedAddresses" getUnusedAddresses mChangeAddress <- performAndLog "getChangeAddress" getChangeAddress changeAddress <- liftMaybe (error "can't get change address") mChangeAddress diff --git a/src/Contract/Utxos.purs b/src/Contract/Utxos.purs index ef6741150e..dc5efb8610 100644 --- a/src/Contract/Utxos.purs +++ b/src/Contract/Utxos.purs @@ -41,8 +41,8 @@ utxosAt address = do queryHandle <- getQueryHandle let cardanoAddr = fromPlutusAddress networkId (getAddress address) cardanoUtxoMap <- liftedE $ liftAff $ queryHandle.utxosAt cardanoAddr - toPlutusUtxoMap cardanoUtxoMap - # liftContractM "utxosAt: failed to convert utxos" + liftContractM "utxosAt: failed to convert utxos" + $ toPlutusUtxoMap cardanoUtxoMap -- | Queries for an utxo given a transaction input. -- | Returns `Nothing` if the output has already been spent. diff --git a/src/Contract/Wallet.purs b/src/Contract/Wallet.purs index adec173313..db283b5f4a 100644 --- a/src/Contract/Wallet.purs +++ b/src/Contract/Wallet.purs @@ -2,7 +2,6 @@ module Contract.Wallet ( mkKeyWalletFromPrivateKeys , withKeyWallet - , getNetworkId , module Contract.Address , module Contract.Utxos , module X @@ -19,7 +18,6 @@ import Contract.Address (getWalletAddress, getWalletCollateral) import Contract.Monad (Contract) import Contract.Utxos (getWalletUtxos) as Contract.Utxos import Control.Monad.Reader (local) -import Control.Monad.Reader.Class (asks) import Ctl.Internal.Contract.Wallet ( getChangeAddress , getRewardAddresses @@ -28,7 +26,6 @@ import Ctl.Internal.Contract.Wallet , signData ) as X import Ctl.Internal.Deserialization.Keys (privateKeyFromBytes) as Deserialization.Keys -import Ctl.Internal.Serialization.Address (NetworkId) import Ctl.Internal.Wallet ( Wallet(Gero, Nami, Flint, Lode, Eternl, KeyWallet) , WalletExtension @@ -66,9 +63,6 @@ import Ctl.Internal.Wallet.Spec ) import Data.Maybe (Maybe(Just)) -getNetworkId :: Contract NetworkId -getNetworkId = asks _.networkId - withKeyWallet :: forall (a :: Type) . Wallet.KeyWallet From 1032182f6c0574ef3db76df505af8d9bf3e63f32 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Tue, 27 Dec 2022 13:33:07 +0000 Subject: [PATCH 186/373] Remove extraConfig from QueryMExtended, drop the r parameter and rename to QueryMT --- src/Internal/Contract/Monad.purs | 3 +- src/Internal/QueryM.purs | 61 +++++++++++++++----------------- 2 files changed, 29 insertions(+), 35 deletions(-) diff --git a/src/Internal/Contract/Monad.purs b/src/Internal/Contract/Monad.purs index 3334130bf9..32ed135a05 100644 --- a/src/Internal/Contract/Monad.purs +++ b/src/Internal/Contract/Monad.purs @@ -347,7 +347,7 @@ runQueryM :: forall (a :: Type). ContractEnv -> CtlBackend -> QueryM a -> Aff a runQueryM contractEnv ctlBackend = flip runReaderT (mkQueryEnv contractEnv ctlBackend) <<< unwrap -mkQueryEnv :: ContractEnv -> CtlBackend -> QueryEnv () +mkQueryEnv :: ContractEnv -> CtlBackend -> QueryEnv mkQueryEnv contractEnv ctlBackend = { config: { ogmiosConfig: ctlBackend.ogmios.config @@ -364,7 +364,6 @@ mkQueryEnv contractEnv ctlBackend = , usedTxOuts: contractEnv.usedTxOuts , pparams: contractEnv.ledgerConstants.pparams } - , extraConfig: {} } -------------------------------------------------------------------------------- diff --git a/src/Internal/QueryM.purs b/src/Internal/QueryM.purs index 0a3e5055d8..578eeee7b8 100644 --- a/src/Internal/QueryM.purs +++ b/src/Internal/QueryM.purs @@ -10,14 +10,13 @@ module Ctl.Internal.QueryM , ClientOtherError ) , ClusterSetup - , DefaultQueryEnv , ListenerSet , OgmiosListeners , OgmiosWebSocket , QueryConfig , QueryM , ParQueryM - , QueryMExtended(QueryMExtended) + , QueryMT(QueryMT) , QueryEnv , QueryRuntime , SubmitTxListenerSet @@ -230,52 +229,48 @@ type QueryRuntime = } -- | `QueryEnv` contains everything needed for `QueryM` to run. -type QueryEnv (r :: Row Type) = +type QueryEnv = { config :: QueryConfig , runtime :: QueryRuntime - , extraConfig :: { | r } } -type DefaultQueryEnv = QueryEnv () +type QueryM = QueryMT Aff -type QueryM = QueryMExtended () Aff +type ParQueryM = QueryMT ParAff -type ParQueryM = QueryMExtended () ParAff +newtype QueryMT (m :: Type -> Type) (a :: Type) = + QueryMT (ReaderT QueryEnv m a) -newtype QueryMExtended (r :: Row Type) (m :: Type -> Type) (a :: Type) = - QueryMExtended - (ReaderT (QueryEnv r) m a) - -derive instance Newtype (QueryMExtended r m a) _ -derive newtype instance Functor m => Functor (QueryMExtended r m) -derive newtype instance Apply m => Apply (QueryMExtended r m) -derive newtype instance Applicative m => Applicative (QueryMExtended r m) -derive newtype instance Bind m => Bind (QueryMExtended r m) -derive newtype instance Alt m => Alt (QueryMExtended r m) -derive newtype instance Plus m => Plus (QueryMExtended r m) -derive newtype instance Alternative m => Alternative (QueryMExtended r m) -derive newtype instance Monad (QueryMExtended r Aff) -derive newtype instance MonadEffect (QueryMExtended r Aff) -derive newtype instance MonadAff (QueryMExtended r Aff) +derive instance Newtype (QueryMT m a) _ +derive newtype instance Functor m => Functor (QueryMT m) +derive newtype instance Apply m => Apply (QueryMT m) +derive newtype instance Applicative m => Applicative (QueryMT m) +derive newtype instance Bind m => Bind (QueryMT m) +derive newtype instance Alt m => Alt (QueryMT m) +derive newtype instance Plus m => Plus (QueryMT m) +derive newtype instance Alternative m => Alternative (QueryMT m) +derive newtype instance Monad (QueryMT Aff) +derive newtype instance MonadEffect (QueryMT Aff) +derive newtype instance MonadAff (QueryMT Aff) derive newtype instance ( Semigroup a , Apply m ) => - Semigroup (QueryMExtended r m a) + Semigroup (QueryMT m a) derive newtype instance ( Monoid a , Applicative m ) => - Monoid (QueryMExtended r m a) + Monoid (QueryMT m a) -derive newtype instance MonadThrow Error (QueryMExtended r Aff) -derive newtype instance MonadError Error (QueryMExtended r Aff) -derive newtype instance MonadRec (QueryMExtended r Aff) -derive newtype instance MonadAsk (QueryEnv r) (QueryMExtended r Aff) -derive newtype instance MonadReader (QueryEnv r) (QueryMExtended r Aff) +derive newtype instance MonadThrow Error (QueryMT Aff) +derive newtype instance MonadError Error (QueryMT Aff) +derive newtype instance MonadRec (QueryMT Aff) +derive newtype instance MonadAsk QueryEnv (QueryMT Aff) +derive newtype instance MonadReader QueryEnv (QueryMT Aff) -instance MonadLogger (QueryMExtended r Aff) where +instance MonadLogger (QueryMT Aff) where log msg = do config <- asks $ _.config let @@ -285,10 +280,10 @@ instance MonadLogger (QueryMExtended r Aff) where -- Newtype deriving complains about overlapping instances, so we wrap and -- unwrap manually -instance Parallel (QueryMExtended r ParAff) (QueryMExtended r Aff) where - parallel :: QueryMExtended r Aff ~> QueryMExtended r ParAff +instance Parallel (QueryMT ParAff) (QueryMT Aff) where + parallel :: QueryMT Aff ~> QueryMT ParAff parallel = wrap <<< parallel <<< unwrap - sequential :: QueryMExtended r ParAff ~> QueryMExtended r Aff + sequential :: QueryMT ParAff ~> QueryMT Aff sequential = wrap <<< sequential <<< unwrap getProtocolParametersAff From 479ad23855ede742816d8eab7473ecd389a577e5 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Tue, 27 Dec 2022 13:39:46 +0000 Subject: [PATCH 187/373] Finish refactor --- src/Internal/Wallet/Cip30Mock.purs | 19 +++++++------------ 1 file changed, 7 insertions(+), 12 deletions(-) diff --git a/src/Internal/Wallet/Cip30Mock.purs b/src/Internal/Wallet/Cip30Mock.purs index 9ee781ef6e..7bd180da83 100644 --- a/src/Internal/Wallet/Cip30Mock.purs +++ b/src/Internal/Wallet/Cip30Mock.purs @@ -134,8 +134,10 @@ mkCip30Mock pKey mSKey = do utxos <#> fold - utxosAt address = liftMaybe (error "No UTxOs at address") <<< hush =<< do - queryHandle.utxosAt address + ownUtxos = do + let ownAddress = (unwrap keyWallet).address env.networkId + liftMaybe (error "No UTxOs at address") <<< hush =<< do + queryHandle.utxosAt ownAddress keyWallet = privateKeysToKeyWallet pKey mSKey @@ -143,18 +145,13 @@ mkCip30Mock pKey mSKey = do byteArrayToHex $ unwrap $ toBytes ((unwrap keyWallet).address env.networkId :: Address) - ownUtxos = do - let ownAddress = (unwrap keyWallet).address env.networkId - utxosAt ownAddress - pure $ { getNetworkId: fromAff $ pure $ case env.networkId of TestnetId -> 0 MainnetId -> 1 , getUtxos: fromAff do - let ownAddress = (unwrap keyWallet).address env.networkId - utxos <- utxosAt ownAddress + utxos <- ownUtxos collateralUtxos <- getCollateralUtxos utxos let -- filter UTxOs that will be used as collateral @@ -168,8 +165,7 @@ mkCip30Mock pKey mSKey = do TransactionUnspentOutput { input, output } pure $ (byteArrayToHex <<< unwrap <<< toBytes) <$> cslUtxos , getCollateral: fromAff do - let ownAddress = (unwrap keyWallet).address env.networkId - utxos <- utxosAt ownAddress + utxos <- ownUtxos collateralUtxos <- getCollateralUtxos utxos cslUnspentOutput <- liftEffect $ traverse convertTransactionUnspentOutput @@ -177,8 +173,7 @@ mkCip30Mock pKey mSKey = do pure $ (byteArrayToHex <<< unwrap <<< toBytes) <$> cslUnspentOutput , getBalance: fromAff do - let ownAddress = (unwrap keyWallet).address env.networkId - utxos <- utxosAt ownAddress + utxos <- ownUtxos value <- liftEffect $ convertValue $ (foldMap (_.amount <<< unwrap) <<< Map.values) utxos From cdbd1b63dffbeb975ff1139742e3a6c81aafdd37 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Tue, 27 Dec 2022 15:59:18 +0100 Subject: [PATCH 188/373] WIP: Add utxosAt Blockfrost query, Some fixes to response decoding --- src/Contract/Config.purs | 1 + src/Internal/Contract/QueryHandle.purs | 16 +++-- src/Internal/QueryM/ServerConfig.purs | 9 +++ src/Internal/Service/Blockfrost.purs | 81 +++++++++++++++++++++----- 4 files changed, 89 insertions(+), 18 deletions(-) diff --git a/src/Contract/Config.purs b/src/Contract/Config.purs index ba28ac42ed..ef7650ce86 100644 --- a/src/Contract/Config.purs +++ b/src/Contract/Config.purs @@ -41,6 +41,7 @@ import Ctl.Internal.Deserialization.Keys (privateKeyFromBytes) import Ctl.Internal.QueryM.ServerConfig ( Host , ServerConfig + , blockfrostPublicPreviewServerConfig , defaultKupoServerConfig , defaultOgmiosWsConfig ) diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs index 85f62f87bb..55b0f2870f 100644 --- a/src/Internal/Contract/QueryHandle.purs +++ b/src/Internal/Contract/QueryHandle.purs @@ -46,8 +46,11 @@ import Ctl.Internal.QueryM.Ogmios (SubmitTxR(SubmitTxSuccess), TxEvaluationR) import Ctl.Internal.Serialization (convertTransaction, toBytes) as Serialization import Ctl.Internal.Serialization.Address (Address) import Ctl.Internal.Serialization.Hash (ScriptHash) -import Ctl.Internal.Service.Blockfrost (getUtxoByOref) as Blockfrost -import Ctl.Internal.Service.Blockfrost (runBlockfrostServiceM) +import Ctl.Internal.Service.Blockfrost + ( BlockfrostServiceM + , runBlockfrostServiceM + ) +import Ctl.Internal.Service.Blockfrost (getUtxoByOref, utxosAt) as Blockfrost import Ctl.Internal.Types.Chain as Chain import Ctl.Internal.Types.Datum (DataHash, Datum) import Ctl.Internal.Types.Transaction (TransactionHash, TransactionInput) @@ -122,14 +125,19 @@ queryHandleForBlockfrostBackend contractEnv backend = , getScriptByHash: undefined , getUtxoByOref: -- FIXME: remove `undefined` - undefined <<< runBlockfrostServiceM backend <<< Blockfrost.getUtxoByOref + undefined <<< runBlockfrostServiceM' <<< Blockfrost.getUtxoByOref , isTxConfirmed: undefined , getTxMetadata: undefined - , utxosAt: undefined + , utxosAt: + -- FIXME: remove `undefined` + undefined <<< runBlockfrostServiceM' <<< Blockfrost.utxosAt , getChainTip: undefined , getCurrentEpoch: undefined , submitTx: undefined , evaluateTx: undefined , getEraSummaries: undefined } + where + runBlockfrostServiceM' :: forall (a :: Type). BlockfrostServiceM a -> Aff a + runBlockfrostServiceM' = runBlockfrostServiceM backend diff --git a/src/Internal/QueryM/ServerConfig.purs b/src/Internal/QueryM/ServerConfig.purs index 322f7268de..0321fe8ee0 100644 --- a/src/Internal/QueryM/ServerConfig.purs +++ b/src/Internal/QueryM/ServerConfig.purs @@ -1,6 +1,7 @@ module Ctl.Internal.QueryM.ServerConfig ( Host , ServerConfig + , blockfrostPublicPreviewServerConfig , defaultKupoServerConfig , defaultOgmiosWsConfig , mkHttpUrl @@ -41,6 +42,14 @@ defaultKupoServerConfig = , path: Just "kupo" } +blockfrostPublicPreviewServerConfig :: ServerConfig +blockfrostPublicPreviewServerConfig = + { port: UInt.fromInt 443 + , host: "cardano-preview.blockfrost.io" + , secure: true + , path: Just "/api/v0" + } + mkHttpUrl :: ServerConfig -> Url mkHttpUrl = mkServerUrl "http" diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index 6dced3ab3c..eb67dd9152 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -1,7 +1,11 @@ module Ctl.Internal.Service.Blockfrost - ( BlockfrostTransactionOutput -- TODO: should not be exported + ( BlockfrostServiceM + , BlockfrostServiceParams + , BlockfrostTransactionOutput -- TODO: should not be exported + , BlockfrostUtxosAtAddress -- TODO: should not be exported , getUtxoByOref , runBlockfrostServiceM + , utxosAt ) where import Prelude @@ -31,7 +35,11 @@ import Ctl.Internal.Contract.QueryBackend (BlockfrostBackend) import Ctl.Internal.Deserialization.PlutusData (deserializeData) import Ctl.Internal.QueryM (ClientError, handleAffjaxResponse) import Ctl.Internal.QueryM.ServerConfig (ServerConfig, mkHttpUrl) -import Ctl.Internal.Serialization.Address (Address, addressFromBech32) +import Ctl.Internal.Serialization.Address + ( Address + , addressBech32 + , addressFromBech32 + ) import Ctl.Internal.Serialization.Hash (ScriptHash) import Ctl.Internal.Service.Helpers (aesonArray, aesonObject, decodeAssetClass) import Ctl.Internal.Types.ByteArray (byteArrayToHex) @@ -43,6 +51,7 @@ import Ctl.Internal.Types.Transaction , TransactionInput(TransactionInput) ) import Data.Array (find) as Array +import Data.BigInt (fromString) as BigInt import Data.Either (Either(Left), note) import Data.Foldable (fold) import Data.Generic.Rep (class Generic) @@ -76,13 +85,16 @@ runBlockfrostServiceM backend = flip runReaderT serviceParams , blockfrostApiKey: backend.blockfrostApiKey } -data BlockfrostEndpoint = - GetTransactionUtxos TransactionHash +data BlockfrostEndpoint + = GetUtxosAtAddress Address -- /addresses/{address}/utxos + | GetUtxosOfTransaction TransactionHash -- /txs/{hash}/utxos realizeEndpoint :: BlockfrostEndpoint -> Affjax.URL realizeEndpoint endpoint = case endpoint of - GetTransactionUtxos txHash -> + GetUtxosAtAddress address -> + "/addresses/" <> addressBech32 address <> "/utxos" + GetUtxosOfTransaction txHash -> "/txs/" <> byteArrayToHex (unwrap txHash) <> "/utxos" blockfrostGetRequest @@ -102,32 +114,42 @@ blockfrostGetRequest endpoint = ask >>= \params -> liftAff do -- Get utxos at address / by output reference -------------------------------------------------------------------------------- +utxosAt + :: Address + -- TODO: resolve `BlockfrostUtxosAtAddress` + -- -> BlockfrostServiceM (Either ClientError UtxoMap) + -> BlockfrostServiceM (Either ClientError BlockfrostUtxosAtAddress) +utxosAt address = + handleAffjaxResponse <$> + blockfrostGetRequest (GetUtxosAtAddress address) + getUtxoByOref :: TransactionInput -- TODO: resolve `BlockfrostTransactionOutput` -- -> BlockfrostServiceM (Either ClientError (Maybe TransactionOutput)) -> BlockfrostServiceM (Either ClientError (Maybe BlockfrostTransactionOutput)) getUtxoByOref oref@(TransactionInput { transactionId: txHash }) = runExceptT do - (blockfrostUtxoMap :: BlockfrostUtxoMap) <- + (blockfrostUtxoMap :: BlockfrostUtxosOfTransaction) <- ExceptT $ handleAffjaxResponse <$> - blockfrostGetRequest (GetTransactionUtxos txHash) + blockfrostGetRequest (GetUtxosOfTransaction txHash) pure $ snd <$> Array.find (eq oref <<< fst) (unwrap blockfrostUtxoMap) -------------------------------------------------------------------------------- --- BlockfrostUtxoMap +-- BlockfrostUtxosAtAddress / BlockfrostUtxosOfTransaction -------------------------------------------------------------------------------- type BlockfrostUnspentOutput = TransactionInput /\ BlockfrostTransactionOutput -newtype BlockfrostUtxoMap = BlockfrostUtxoMap (Array BlockfrostUnspentOutput) +newtype BlockfrostUtxosAtAddress = + BlockfrostUtxosAtAddress (Array BlockfrostUnspentOutput) -derive instance Generic BlockfrostUtxoMap _ -derive instance Newtype BlockfrostUtxoMap _ +derive instance Generic BlockfrostUtxosAtAddress _ +derive instance Newtype BlockfrostUtxosAtAddress _ -instance Show BlockfrostUtxoMap where +instance Show BlockfrostUtxosAtAddress where show = genericShow -instance DecodeAeson BlockfrostUtxoMap where +instance DecodeAeson BlockfrostUtxosAtAddress where decodeAeson = aesonArray (map wrap <<< traverse decodeUtxoEntry) where decodeUtxoEntry :: Aeson -> Either JsonDecodeError BlockfrostUnspentOutput @@ -140,6 +162,34 @@ instance DecodeAeson BlockfrostUtxoMap where index <- getField obj "output_index" pure $ TransactionInput { transactionId, index } +newtype BlockfrostUtxosOfTransaction = + BlockfrostUtxosOfTransaction (Array BlockfrostUnspentOutput) + +derive instance Generic BlockfrostUtxosOfTransaction _ +derive instance Newtype BlockfrostUtxosOfTransaction _ + +instance Show BlockfrostUtxosOfTransaction where + show = genericShow + +instance DecodeAeson BlockfrostUtxosOfTransaction where + decodeAeson = aesonObject \obj -> do + txHash <- getField obj "hash" + getField obj "outputs" + >>= aesonArray (map wrap <<< traverse (decodeUtxoEntry txHash)) + where + decodeUtxoEntry + :: TransactionHash + -> Aeson + -> Either JsonDecodeError BlockfrostUnspentOutput + decodeUtxoEntry txHash utxoAeson = + Tuple <$> decodeTxOref txHash utxoAeson <*> decodeAeson utxoAeson + + decodeTxOref + :: TransactionHash -> Aeson -> Either JsonDecodeError TransactionInput + decodeTxOref txHash = aesonObject $ + flip getField "output_index" >>> map \index -> + TransactionInput { transactionId: txHash, index } + -------------------------------------------------------------------------------- -- BlockfrostTransactionOutput -------------------------------------------------------------------------------- @@ -177,7 +227,10 @@ instance DecodeAeson BlockfrostTransactionOutput where where decodeAsset :: Aeson -> Either JsonDecodeError Value decodeAsset = aesonObject \obj -> do - quantity <- getField obj "quantity" + quantity <- + getField obj "quantity" >>= + BigInt.fromString >>> + note (TypeMismatch "Expected string repr of BigInt") getField obj "unit" >>= case _ of "lovelace" -> pure $ Value.lovelaceValueOf quantity assetString -> do From e68ae74cd7f374e0277716c53870f2c1fc63dedc Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Tue, 27 Dec 2022 16:20:52 +0100 Subject: [PATCH 189/373] Fix errors and warnings --- src/Internal/Contract/QueryHandle.purs | 2 +- src/Internal/QueryM/Kupo.purs | 5 ++--- src/Internal/Service/Blockfrost.purs | 9 +++++---- 3 files changed, 8 insertions(+), 8 deletions(-) diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs index 55b0f2870f..86cb4a87ae 100644 --- a/src/Internal/Contract/QueryHandle.purs +++ b/src/Internal/Contract/QueryHandle.purs @@ -120,7 +120,7 @@ queryHandleForCtlBackend contractEnv backend = queryHandleForBlockfrostBackend :: ContractEnv -> BlockfrostBackend -> QueryHandle -queryHandleForBlockfrostBackend contractEnv backend = +queryHandleForBlockfrostBackend _ backend = { getDatumByHash: undefined , getScriptByHash: undefined , getUtxoByOref: diff --git a/src/Internal/QueryM/Kupo.purs b/src/Internal/QueryM/Kupo.purs index 20d284f2aa..44c618b0c3 100644 --- a/src/Internal/QueryM/Kupo.purs +++ b/src/Internal/QueryM/Kupo.purs @@ -81,7 +81,7 @@ import Ctl.Internal.Types.Transaction import Ctl.Internal.Types.TransactionMetadata (GeneralTransactionMetadata) import Data.Array (uncons) import Data.BigInt (BigInt) -import Data.Either (Either(Left, Right), hush, note) +import Data.Either (Either(Left, Right), note) import Data.Foldable (fold) import Data.Generic.Rep (class Generic) import Data.HTTP.Method (Method(GET)) @@ -439,8 +439,7 @@ instance DecodeAeson KupoMetadata where TypeMismatch "Hexadecimal String" metadata <- flip note (fromBytes cbor) $ TypeMismatch "Hexadecimal encoded Metadata" - -- Conversion should always succeed, so use it as the `Just` - pure $ KupoMetadata $ hush $ convertGeneralTransactionMetadata metadata + pure $ KupoMetadata $ Just $ convertGeneralTransactionMetadata metadata [] -> Right $ KupoMetadata Nothing _ -> Left $ TypeMismatch "Singleton or Empty Array" diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index eb67dd9152..5532bc6520 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -1,8 +1,11 @@ module Ctl.Internal.Service.Blockfrost ( BlockfrostServiceM , BlockfrostServiceParams - , BlockfrostTransactionOutput -- TODO: should not be exported - , BlockfrostUtxosAtAddress -- TODO: should not be exported + -- TODO: should not be exported: + , BlockfrostTransactionOutput(BlockfrostTransactionOutput) + , BlockfrostUnspentOutput + , BlockfrostUtxosAtAddress(BlockfrostUtxosAtAddress) + -- , getUtxoByOref , runBlockfrostServiceM , utxosAt @@ -24,7 +27,6 @@ import Affjax.ResponseFormat (string) as Affjax.ResponseFormat import Control.Monad.Except.Trans (ExceptT(ExceptT), runExceptT) import Control.Monad.Reader.Class (ask) import Control.Monad.Reader.Trans (ReaderT, runReaderT) -import Ctl.Internal.Cardano.Types.Transaction (TransactionOutput, UtxoMap) import Ctl.Internal.Cardano.Types.Value (Value) import Ctl.Internal.Cardano.Types.Value ( lovelaceValueOf @@ -66,7 +68,6 @@ import Data.Tuple.Nested (type (/\), (/\)) import Effect.Aff (Aff) import Effect.Aff.Class (liftAff) import Foreign.Object (Object) -import Undefined (undefined) type BlockfrostServiceParams = { blockfrostConfig :: ServerConfig From 78c8a0d4698286a2c027e745834902c06aed58bf Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Tue, 27 Dec 2022 15:36:22 +0000 Subject: [PATCH 190/373] Fix merge --- src/Internal/QueryM/Kupo.purs | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/src/Internal/QueryM/Kupo.purs b/src/Internal/QueryM/Kupo.purs index 20d284f2aa..44c618b0c3 100644 --- a/src/Internal/QueryM/Kupo.purs +++ b/src/Internal/QueryM/Kupo.purs @@ -81,7 +81,7 @@ import Ctl.Internal.Types.Transaction import Ctl.Internal.Types.TransactionMetadata (GeneralTransactionMetadata) import Data.Array (uncons) import Data.BigInt (BigInt) -import Data.Either (Either(Left, Right), hush, note) +import Data.Either (Either(Left, Right), note) import Data.Foldable (fold) import Data.Generic.Rep (class Generic) import Data.HTTP.Method (Method(GET)) @@ -439,8 +439,7 @@ instance DecodeAeson KupoMetadata where TypeMismatch "Hexadecimal String" metadata <- flip note (fromBytes cbor) $ TypeMismatch "Hexadecimal encoded Metadata" - -- Conversion should always succeed, so use it as the `Just` - pure $ KupoMetadata $ hush $ convertGeneralTransactionMetadata metadata + pure $ KupoMetadata $ Just $ convertGeneralTransactionMetadata metadata [] -> Right $ KupoMetadata Nothing _ -> Left $ TypeMismatch "Singleton or Empty Array" From d9bdb49ec201a6242eb050d9a546444fe3963d4d Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Tue, 27 Dec 2022 17:46:39 +0000 Subject: [PATCH 191/373] Remove unused fields of QueryM runtime and config --- src/Internal/Contract/Monad.purs | 8 +------- src/Internal/QueryM.purs | 18 +----------------- src/Internal/QueryM/Config.purs | 27 --------------------------- 3 files changed, 2 insertions(+), 51 deletions(-) delete mode 100644 src/Internal/QueryM/Config.purs diff --git a/src/Internal/Contract/Monad.purs b/src/Internal/Contract/Monad.purs index 32ed135a05..185b9aa96c 100644 --- a/src/Internal/Contract/Monad.purs +++ b/src/Internal/Contract/Monad.purs @@ -350,19 +350,13 @@ runQueryM contractEnv ctlBackend = mkQueryEnv :: ContractEnv -> CtlBackend -> QueryEnv mkQueryEnv contractEnv ctlBackend = { config: - { ogmiosConfig: ctlBackend.ogmios.config - , kupoConfig: ctlBackend.kupoConfig - , networkId: contractEnv.networkId + { kupoConfig: ctlBackend.kupoConfig , logLevel: contractEnv.logLevel - , walletSpec: contractEnv.walletSpec , customLogger: contractEnv.customLogger , suppressLogs: contractEnv.suppressLogs } , runtime: { ogmiosWs: ctlBackend.ogmios.ws - , wallet: contractEnv.wallet - , usedTxOuts: contractEnv.usedTxOuts - , pparams: contractEnv.ledgerConstants.pparams } } diff --git a/src/Internal/QueryM.purs b/src/Internal/QueryM.purs index 578eeee7b8..f701c67292 100644 --- a/src/Internal/QueryM.purs +++ b/src/Internal/QueryM.purs @@ -139,17 +139,11 @@ import Ctl.Internal.QueryM.ServerConfig , mkWsUrl ) import Ctl.Internal.QueryM.UniqueId (ListenerId) -import Ctl.Internal.Serialization.Address (NetworkId) import Ctl.Internal.Types.ByteArray (byteArrayToHex) import Ctl.Internal.Types.CborBytes (CborBytes) import Ctl.Internal.Types.Chain as Chain import Ctl.Internal.Types.Scripts (PlutusScript) -import Ctl.Internal.Types.UsedTxOuts (UsedTxOuts) -import Ctl.Internal.Wallet (Wallet) import Ctl.Internal.Wallet.Key (PrivatePaymentKey, PrivateStakeKey) -import Ctl.Internal.Wallet.Spec - ( WalletSpec - ) import Data.Bifunctor (lmap) import Data.Either (Either(Left, Right), either, isRight) import Data.Foldable (foldl) @@ -201,14 +195,10 @@ type ClusterSetup = -- | - server parameters for all the services -- | - network ID -- | - logging level --- | - wallet setup instructions -- | - optional custom logger type QueryConfig = - { ogmiosConfig :: ServerConfig - , kupoConfig :: ServerConfig - , networkId :: NetworkId + { kupoConfig :: ServerConfig , logLevel :: LogLevel - , walletSpec :: Maybe WalletSpec , customLogger :: Maybe (LogLevel -> Message -> Aff Unit) , suppressLogs :: Boolean } @@ -218,14 +208,8 @@ type QueryConfig = -- | -- | Includes: -- | - WebSocket connections --- | - A wallet connection --- | - A data structure to keep UTxOs that has already been spent --- | - Current protocol parameters type QueryRuntime = { ogmiosWs :: OgmiosWebSocket - , wallet :: Maybe Wallet - , usedTxOuts :: UsedTxOuts - , pparams :: Ogmios.ProtocolParameters } -- | `QueryEnv` contains everything needed for `QueryM` to run. diff --git a/src/Internal/QueryM/Config.purs b/src/Internal/QueryM/Config.purs deleted file mode 100644 index de05056470..0000000000 --- a/src/Internal/QueryM/Config.purs +++ /dev/null @@ -1,27 +0,0 @@ -module Ctl.Internal.QueryM.Config - ( testnetTraceQueryConfig - , testnetQueryConfig - ) where - -import Ctl.Internal.QueryM (QueryConfig) -import Ctl.Internal.QueryM.ServerConfig - ( defaultKupoServerConfig - , defaultOgmiosWsConfig - ) -import Ctl.Internal.Serialization.Address (NetworkId(TestnetId)) -import Data.Log.Level (LogLevel(Error, Trace)) -import Data.Maybe (Maybe(Nothing)) - -testnetTraceQueryConfig :: QueryConfig -testnetTraceQueryConfig = - { ogmiosConfig: defaultOgmiosWsConfig - , kupoConfig: defaultKupoServerConfig - , networkId: TestnetId - , logLevel: Trace - , walletSpec: Nothing - , customLogger: Nothing - , suppressLogs: false - } - -testnetQueryConfig :: QueryConfig -testnetQueryConfig = testnetTraceQueryConfig { logLevel = Error } From b8634b5575961831560c0ff50268e85887f1b61d Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Tue, 27 Dec 2022 22:51:43 +0000 Subject: [PATCH 192/373] Implement getTxMetadata and isTxConfirmed for Blockfrost, add basic test --- src/Internal/Contract/QueryHandle.purs | 23 +++- src/Internal/Deserialization/FromBytes.purs | 4 + src/Internal/QueryM.purs | 9 +- src/Internal/QueryM/Kupo.purs | 6 +- src/Internal/Service/Blockfrost.purs | 119 +++++++++++++++++++ test/Blockfrost.purs | 124 ++++++++++++++++++++ 6 files changed, 276 insertions(+), 9 deletions(-) create mode 100644 src/Internal/Service/Blockfrost.purs create mode 100644 test/Blockfrost.purs diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs index 800cce67d6..1a04da7072 100644 --- a/src/Internal/Contract/QueryHandle.purs +++ b/src/Internal/Contract/QueryHandle.purs @@ -46,6 +46,10 @@ import Ctl.Internal.QueryM.Ogmios (SubmitTxR(SubmitTxSuccess), TxEvaluationR) import Ctl.Internal.Serialization (convertTransaction, toBytes) as Serialization import Ctl.Internal.Serialization.Address (Address) import Ctl.Internal.Serialization.Hash (ScriptHash) +import Ctl.Internal.Service.Blockfrost + ( getTxMetadata + , isTxConfirmed + ) as Blockfrost import Ctl.Internal.Types.Chain as Chain import Ctl.Internal.Types.Datum (DataHash, Datum) import Ctl.Internal.Types.Transaction (TransactionHash, TransactionInput) @@ -115,5 +119,20 @@ queryHandleForCtlBackend contractEnv backend = queryHandleForBlockfrostBackend :: ContractEnv -> BlockfrostBackend -> QueryHandle -queryHandleForBlockfrostBackend = undefined - +queryHandleForBlockfrostBackend _ backend = + { getDatumByHash: undefined + , getScriptByHash: undefined + , getUtxoByOref: undefined + , isTxConfirmed: runBlockfrost backend Nothing <<< Blockfrost.isTxConfirmed -- TODO Just + , getTxMetadata: runBlockfrost backend Nothing <<< Blockfrost.getTxMetadata -- TODO Just + , utxosAt: undefined + , getChainTip: undefined + , getCurrentEpoch: undefined + , submitTx: undefined + , evaluateTx: undefined + , getEraSummaries: undefined + } + where + runBlockfrost :: forall (a :: Type). _ -> _ -> (_ -> _ -> Aff a) -> Aff a + runBlockfrost { blockfrostConfig } mbApiKey action = action blockfrostConfig + mbApiKey diff --git a/src/Internal/Deserialization/FromBytes.purs b/src/Internal/Deserialization/FromBytes.purs index f46989185e..64619dbfbb 100644 --- a/src/Internal/Deserialization/FromBytes.purs +++ b/src/Internal/Deserialization/FromBytes.purs @@ -33,6 +33,7 @@ import Ctl.Internal.Serialization.Types , Transaction , TransactionBody , TransactionHash + , TransactionMetadatum , TransactionOutput , TransactionUnspentOutput , TransactionWitnessSet @@ -72,6 +73,9 @@ instance FromBytes Ed25519Signature where instance FromBytes GeneralTransactionMetadata where fromBytes' = fromBytesImpl "GeneralTransactionMetadata" +instance FromBytes TransactionMetadatum where + fromBytes' = fromBytesImpl "TransactionMetadatum" + instance FromBytes GenesisDelegateHash where fromBytes' = fromBytesImpl "GenesisDelegateHash" diff --git a/src/Internal/QueryM.purs b/src/Internal/QueryM.purs index 578eeee7b8..d789473d4b 100644 --- a/src/Internal/QueryM.purs +++ b/src/Internal/QueryM.purs @@ -385,7 +385,7 @@ mempoolSnapshotHasTxAff ogmiosWs logger ms = data ClientError = ClientHttpError Affjax.Error - | ClientHttpResponseError String + | ClientHttpResponseError Affjax.StatusCode.StatusCode String | ClientDecodeJsonError String JsonDecodeError | ClientEncodingError String | ClientOtherError String @@ -396,8 +396,10 @@ instance Show ClientError where "(ClientHttpError " <> Affjax.printError err <> ")" - show (ClientHttpResponseError err) = + show (ClientHttpResponseError statusCode err) = "(ClientHttpResponseError " + <> show statusCode + <> " " <> show err <> ")" show (ClientDecodeJsonError jsonStr err) = @@ -428,7 +430,8 @@ handleAffjaxResponse (Left affjaxError) = handleAffjaxResponse (Right { status: Affjax.StatusCode.StatusCode statusCode, body }) | statusCode < 200 || statusCode > 299 = - Left (ClientHttpResponseError body) + Left + (ClientHttpResponseError (Affjax.StatusCode.StatusCode statusCode) body) | otherwise = body # lmap (ClientDecodeJsonError body) <<< (decodeAeson <=< parseJsonStringToAeson) diff --git a/src/Internal/QueryM/Kupo.purs b/src/Internal/QueryM/Kupo.purs index 44c618b0c3..accb477d9b 100644 --- a/src/Internal/QueryM/Kupo.purs +++ b/src/Internal/QueryM/Kupo.purs @@ -66,7 +66,7 @@ import Ctl.Internal.Serialization.Address import Ctl.Internal.Serialization.Hash (ScriptHash, scriptHashToBytes) import Ctl.Internal.Types.BigNum (toString) as BigNum import Ctl.Internal.Types.ByteArray (ByteArray, byteArrayToHex, hexToByteArray) -import Ctl.Internal.Types.CborBytes (hexToCborBytes) +import Ctl.Internal.Types.CborBytes (CborBytes, hexToCborBytes) import Ctl.Internal.Types.Datum (DataHash(DataHash), Datum) import Ctl.Internal.Types.OutputDatum ( OutputDatum(NoOutputDatum, OutputDatumHash, OutputDatum) @@ -434,9 +434,7 @@ instance Show KupoMetadata where instance DecodeAeson KupoMetadata where decodeAeson = decodeAeson >=> case _ of - [ { raw } :: { raw :: String } ] -> do - cbor <- flip note (hexToCborBytes raw) $ - TypeMismatch "Hexadecimal String" + [ { raw: cbor } :: { raw :: CborBytes } ] -> do metadata <- flip note (fromBytes cbor) $ TypeMismatch "Hexadecimal encoded Metadata" pure $ KupoMetadata $ Just $ convertGeneralTransactionMetadata metadata diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs new file mode 100644 index 0000000000..cc5cc9e3a3 --- /dev/null +++ b/src/Internal/Service/Blockfrost.purs @@ -0,0 +1,119 @@ +module Ctl.Internal.Service.Blockfrost + ( isTxConfirmed + , getTxMetadata + ) where + +import Prelude + +import Aeson + ( class DecodeAeson + , Aeson + , JsonDecodeError(TypeMismatch) + , decodeAeson + ) +import Affjax (Error, Response, URL, defaultRequest, request) as Affjax +import Affjax.RequestHeader (RequestHeader(RequestHeader)) as Affjax +import Affjax.ResponseFormat as Affjax.ResponseFormat +import Affjax.StatusCode (StatusCode(StatusCode)) as Affjax +import Ctl.Internal.Deserialization.FromBytes (fromBytes) +import Ctl.Internal.Deserialization.Transaction + ( convertGeneralTransactionMetadata + ) +import Ctl.Internal.QueryM + ( ClientError(ClientHttpResponseError) + , handleAffjaxResponse + ) +import Ctl.Internal.QueryM.ServerConfig (ServerConfig, mkHttpUrl) +import Ctl.Internal.Types.ByteArray (byteArrayToHex) +import Ctl.Internal.Types.CborBytes (CborBytes) +import Ctl.Internal.Types.Transaction (TransactionHash) +import Ctl.Internal.Types.TransactionMetadata + ( GeneralTransactionMetadata(GeneralTransactionMetadata) + ) +import Data.Either (Either(Left, Right), note) +import Data.Foldable (foldMap) +import Data.Generic.Rep (class Generic) +import Data.HTTP.Method (Method(GET)) +import Data.Map as Map +import Data.Maybe (Maybe(Just, Nothing)) +import Data.Newtype (unwrap) +import Data.Show.Generic (genericShow) +import Data.Traversable (for) +import Effect.Aff (Aff) + +isTxConfirmed + :: TransactionHash + -> ServerConfig + -> Maybe String + -> Aff (Either ClientError Boolean) +isTxConfirmed txHash config mbApiKey = do + response :: Either ClientError Aeson <- handleAffjaxResponse <$> request + pure case response of + Right _ -> Right true + Left (ClientHttpResponseError (Affjax.StatusCode 404) _) -> Right false + Left e -> Left e + where + request :: Aff (Either Affjax.Error (Affjax.Response String)) + request = Affjax.request $ Affjax.defaultRequest + { method = Left GET + , url = mkHttpUrl config <> endpoint + , responseFormat = Affjax.ResponseFormat.string + , headers = + flip foldMap mbApiKey \apiKey -> + [ Affjax.RequestHeader "project_id" apiKey ] + } + + endpoint :: Affjax.URL + endpoint = "/txs/" <> byteArrayToHex (unwrap txHash) + +getTxMetadata + :: TransactionHash + -> ServerConfig + -> Maybe String + -> Aff (Either ClientError (Maybe GeneralTransactionMetadata)) +getTxMetadata txHash config mbApiKey = do + response :: Either ClientError _ <- handleAffjaxResponse <$> request + pure case response of + Right metadata -> Right $ Just $ unwrapBlockfrostMetadata metadata + Left (ClientHttpResponseError (Affjax.StatusCode 404) _) -> Right Nothing + Left e -> Left e + where + request :: Aff (Either Affjax.Error (Affjax.Response String)) + request = Affjax.request $ Affjax.defaultRequest + { method = Left GET + , url = mkHttpUrl config <> endpoint + , responseFormat = Affjax.ResponseFormat.string + , headers = + flip foldMap mbApiKey \apiKey -> + [ Affjax.RequestHeader "project_id" apiKey ] + } + + endpoint :: Affjax.URL + endpoint = "/txs/" <> byteArrayToHex (unwrap txHash) <> "/metadata/cbor" + +-------------------------------------------------------------------------------- +-- `getTxMetadata` reponse parsing +-------------------------------------------------------------------------------- + +newtype BlockfrostMetadata = BlockfrostMetadata + GeneralTransactionMetadata + +derive instance Generic BlockfrostMetadata _ +derive instance Eq BlockfrostMetadata + +instance Show BlockfrostMetadata where + show = genericShow + +instance DecodeAeson BlockfrostMetadata where + decodeAeson = decodeAeson >=> + \(metadatas :: Array { metadata :: CborBytes }) -> do + metadatas' <- for metadatas \{ metadata } -> do + map (unwrap <<< convertGeneralTransactionMetadata) <$> flip note + (fromBytes metadata) $ + TypeMismatch "Hexadecimal encoded Metadata" + + pure $ BlockfrostMetadata $ GeneralTransactionMetadata $ Map.unions + metadatas' + +unwrapBlockfrostMetadata :: BlockfrostMetadata -> GeneralTransactionMetadata +unwrapBlockfrostMetadata (BlockfrostMetadata metadata) = metadata diff --git a/test/Blockfrost.purs b/test/Blockfrost.purs new file mode 100644 index 0000000000..60cf638a3e --- /dev/null +++ b/test/Blockfrost.purs @@ -0,0 +1,124 @@ +module Test.Ctl.Blockfrost where + +import Prelude + +import Contract.Metadata + ( GeneralTransactionMetadata(GeneralTransactionMetadata) + , TransactionMetadatum(Text) + , TransactionMetadatumLabel(TransactionMetadatumLabel) + ) +import Contract.Prim.ByteArray (hexToByteArrayUnsafe) +import Contract.Test.Mote (TestPlanM, interpretWithConfig) +import Contract.Test.Utils (exitCode, interruptOnSignal) +import Contract.Transaction (TransactionHash(TransactionHash)) +import Ctl.Internal.Service.Blockfrost (getTxMetadata, isTxConfirmed) +import Data.BigInt as BigInt +import Data.Either (Either(Right), hush) +import Data.Map as Map +import Data.Maybe (Maybe(Just, Nothing), fromJust) +import Data.Posix.Signal (Signal(SIGINT)) +import Data.Time.Duration (Milliseconds(Milliseconds)) +import Data.Tuple.Nested ((/\)) +import Data.UInt as UInt +import Effect (Effect) +import Effect.Aff (Aff, cancelWith, effectCanceler, launchAff) +import Effect.Class.Console (log) +import Mote (group, test) +import Partial.Unsafe (unsafePartial) +import Test.Spec.Assertions (shouldEqual) +import Test.Spec.Runner (defaultConfig) + +-- Run with `spago test --main Test.Ctl.Blockfrost` +main :: Effect Unit +main = interruptOnSignal SIGINT =<< launchAff do + flip cancelWith (effectCanceler (exitCode 1)) do + interpretWithConfig + defaultConfig { timeout = Just $ Milliseconds 450_000.0, exit = true } + testPlan + +fixture1 :: { hash :: TransactionHash, metadata :: GeneralTransactionMetadata } +fixture1 = + { hash: TransactionHash $ hexToByteArrayUnsafe + "7a2aff2b7f92f6f8ec3fb2135301c7bfc36fea1489a3ca37fd6066f3155c46ff" + , metadata: + GeneralTransactionMetadata $ Map.fromFoldable $ + ( \(label /\ text) -> + TransactionMetadatumLabel + (unsafePartial $ fromJust $ BigInt.fromString label) /\ Text text + ) + <$> + [ "30" /\ "5" + , "50" /\ + "d8799f581c11185d006a64f24e9cf6da987589cd0b166718d3680e63985db370" + , "51" /\ + "3d9fd8799fd8799fd8799f581c70e60f3b5ea7153e0acc7a803e4401d44b8ed1" + , "52" /\ + "bae1c7baaad1a62a72ffd8799fd8799fd8799f581c1e78aae7c90cc36d624f7b" + , "53" /\ + "3bb6d86b52696dc84e490f343eba89005fffffffffa140d8799f00a1401a000f" + , "54" /\ + "32a0ffffd8799fd8799fd8799f581c11185d006a64f24e9cf6da987589cd0b16" + , "55" /\ + "6718d3680e63985db3703dffd8799fd8799fd8799f581cac7d463e54c43d994b" + , "56" /\ + "66d1512d5fb315c7563ae43c37610cd07977c7ffffffffa1581c4e5205e5df36" + , "57" /\ + "8030e9f814c2258c01f50c62375c55b07fbcc076c181d8799f01a0ffffffff,d" + , "58" /\ + "8799f581c11185d006a64f24e9cf6da987589cd0b166718d3680e63985db3703" + , "59" /\ + "d9fd8799fd8799fd8799f581c70e60f3b5ea7153e0acc7a803e4401d44b8ed1b" + , "60" /\ + "ae1c7baaad1a62a72ffd8799fd8799fd8799f581c1e78aae7c90cc36d624f7b3" + , "61" /\ + "bb6d86b52696dc84e490f343eba89005fffffffffa140d8799f00a1401a000f3" + , "62" /\ + "2a0ffffd8799fd8799fd8799f581c11185d006a64f24e9cf6da987589cd0b166" + , "63" /\ + "718d3680e63985db3703dffd8799fd8799fd8799f581cac7d463e54c43d994b6" + , "64" /\ + "6d1512d5fb315c7563ae43c37610cd07977c7ffffffffa1581c4e5205e5df368" + , "65" /\ + "030e9f814c2258c01f50c62375c55b07fbcc076c181d8799f01a0ffffffff,d8" + , "66" /\ + "799f581c11185d006a64f24e9cf6da987589cd0b166718d3680e63985db3703d" + , "67" /\ + "9fd8799fd8799fd8799f581c70e60f3b5ea7153e0acc7a803e4401d44b8ed1ba" + , "68" /\ + "e1c7baaad1a62a72ffd8799fd8799fd8799f581c1e78aae7c90cc36d624f7b3b" + , "69" /\ + "b6d86b52696dc84e490f343eba89005fffffffffa140d8799f00a1401a000f32" + , "70" /\ + "a0ffffd8799fd8799fd8799f581c11185d006a64f24e9cf6da987589cd0b1667" + , "71" /\ + "18d3680e63985db3703dffd8799fd8799fd8799f581cac7d463e54c43d994b66" + , "72" /\ + "d1512d5fb315c7563ae43c37610cd07977c7ffffffffa1581c4e5205e5df3680" + , "73" /\ + "30e9f814c2258c01f50c62375c55b07fbcc076c181d8799f01a0ffffffff," + , "75" /\ + "4e5205e5df368030e9f814c2258c01f50c62375c55b07fbcc076c181::00" + , "76" /\ + "4e5205e5df368030e9f814c2258c01f50c62375c55b07fbcc076c181::01" + , "77" /\ + "4e5205e5df368030e9f814c2258c01f50c62375c55b07fbcc076c181::02" + ] + } + +config = + { host: "cardano-preview.blockfrost.io" + , port: UInt.fromInt 443 + , secure: true + , path: Just "/api/v0" + } + +apiKey = Just ?help + +testPlan :: TestPlanM (Aff Unit) Unit +testPlan = group "Blockfrost" do + test "getTxMetadata success" do + metadata <- getTxMetadata fixture1.hash config apiKey + (hush metadata) `shouldEqual` (Just (Just fixture1.metadata)) + test "isTxConfirmed success" do + confirmed <- isTxConfirmed fixture1.hash config apiKey + (hush confirmed) `shouldEqual` (Just true) From cad5b9c7341c33d4df6e3a926148cf4cd38d03b0 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Tue, 27 Dec 2022 22:57:18 +0000 Subject: [PATCH 193/373] Remove ODC reference in nixos config --- nix/test-nixos-configuration.nix | 9 --------- 1 file changed, 9 deletions(-) diff --git a/nix/test-nixos-configuration.nix b/nix/test-nixos-configuration.nix index 7747d346d5..bbfe022e92 100644 --- a/nix/test-nixos-configuration.nix +++ b/nix/test-nixos-configuration.nix @@ -46,13 +46,4 @@ nodeConfig = "${cardano-configurations}/network/mainnet/cardano-node/config.json"; nodeSocket = "/var/run/cardano-node/node.socket"; }; - - services.ogmios-datum-cache = { - enable = true; - host = "0.0.0.0"; - useLatest = true; - blockSlot = 5854109; - blockHash = "85366c607a9777b887733de621aa2008aec9db4f3e6a114fb90ec2909bc06f14"; - blockFilter = builtins.toJSON { const = true; }; - }; } From 2d34cf3036bc7562184c0afd34038702fd2e9f74 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Wed, 28 Dec 2022 11:52:52 +0000 Subject: [PATCH 194/373] Improve tests, note concerns --- src/Internal/Service/Blockfrost.purs | 6 + test/Blockfrost.purs | 219 ++++++++++++++++----------- 2 files changed, 138 insertions(+), 87 deletions(-) diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index cc5cc9e3a3..21b31358ce 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -66,6 +66,12 @@ isTxConfirmed txHash config mbApiKey = do endpoint :: Affjax.URL endpoint = "/txs/" <> byteArrayToHex (unwrap txHash) +-- TODO Decide how to handle tx not found vs no metadata +-- Kupo internally first finds an output of the tx, if there are none it will return Nothing +-- But if there's no metadata, it will fail via ClientError, due to aeson parsing failing + +-- Blockfrost on the other hand will (currently) fail with Nothing if the tx doesn't exist +-- and return an empty metadata if the tx exists but had no metadata set (or the metadata was set but empty) getTxMetadata :: TransactionHash -> ServerConfig diff --git a/test/Blockfrost.purs b/test/Blockfrost.purs index 60cf638a3e..fff38cc75e 100644 --- a/test/Blockfrost.purs +++ b/test/Blockfrost.purs @@ -1,110 +1,153 @@ -module Test.Ctl.Blockfrost where +module Test.Ctl.Blockfrost (main, testPlan) where import Prelude +import Contract.Config (ServerConfig) import Contract.Metadata ( GeneralTransactionMetadata(GeneralTransactionMetadata) - , TransactionMetadatum(Text) + , TransactionMetadatum(Text, MetadataMap) , TransactionMetadatumLabel(TransactionMetadatumLabel) ) import Contract.Prim.ByteArray (hexToByteArrayUnsafe) import Contract.Test.Mote (TestPlanM, interpretWithConfig) -import Contract.Test.Utils (exitCode, interruptOnSignal) import Contract.Transaction (TransactionHash(TransactionHash)) +import Control.Monad.Error.Class (liftEither) +import Ctl.Internal.Helpers (liftedM) import Ctl.Internal.Service.Blockfrost (getTxMetadata, isTxConfirmed) +import Data.Array ((!!)) +import Data.Bifunctor (lmap) import Data.BigInt as BigInt -import Data.Either (Either(Right), hush) +import Data.FoldableWithIndex (forWithIndex_) import Data.Map as Map -import Data.Maybe (Maybe(Just, Nothing), fromJust) -import Data.Posix.Signal (Signal(SIGINT)) -import Data.Time.Duration (Milliseconds(Milliseconds)) +import Data.Maybe (Maybe(Just, Nothing)) import Data.Tuple.Nested ((/\)) import Data.UInt as UInt import Effect (Effect) -import Effect.Aff (Aff, cancelWith, effectCanceler, launchAff) -import Effect.Class.Console (log) +import Effect.Aff (Aff, error, launchAff_) import Mote (group, test) -import Partial.Unsafe (unsafePartial) +import Node.Process (argv) import Test.Spec.Assertions (shouldEqual) import Test.Spec.Runner (defaultConfig) --- Run with `spago test --main Test.Ctl.Blockfrost` +-- Run with `spago test --main Test.Ctl.Blockfrost --exec-args PREVIEW_API_KEY` main :: Effect Unit -main = interruptOnSignal SIGINT =<< launchAff do - flip cancelWith (effectCanceler (exitCode 1)) do +main = do + apiKey <- liftedM (error "ApiKey not supplied") $ (_ !! 1) <$> argv + launchAff_ do interpretWithConfig - defaultConfig { timeout = Just $ Milliseconds 450_000.0, exit = true } - testPlan + defaultConfig { exit = true } + (testPlan apiKey) -fixture1 :: { hash :: TransactionHash, metadata :: GeneralTransactionMetadata } +type Fixture = + { hash :: TransactionHash + , metadata :: Maybe GeneralTransactionMetadata + , confirmed :: Boolean + } + +fixture1 :: Fixture fixture1 = { hash: TransactionHash $ hexToByteArrayUnsafe "7a2aff2b7f92f6f8ec3fb2135301c7bfc36fea1489a3ca37fd6066f3155c46ff" , metadata: - GeneralTransactionMetadata $ Map.fromFoldable $ - ( \(label /\ text) -> - TransactionMetadatumLabel - (unsafePartial $ fromJust $ BigInt.fromString label) /\ Text text - ) - <$> - [ "30" /\ "5" - , "50" /\ - "d8799f581c11185d006a64f24e9cf6da987589cd0b166718d3680e63985db370" - , "51" /\ - "3d9fd8799fd8799fd8799f581c70e60f3b5ea7153e0acc7a803e4401d44b8ed1" - , "52" /\ - "bae1c7baaad1a62a72ffd8799fd8799fd8799f581c1e78aae7c90cc36d624f7b" - , "53" /\ - "3bb6d86b52696dc84e490f343eba89005fffffffffa140d8799f00a1401a000f" - , "54" /\ - "32a0ffffd8799fd8799fd8799f581c11185d006a64f24e9cf6da987589cd0b16" - , "55" /\ - "6718d3680e63985db3703dffd8799fd8799fd8799f581cac7d463e54c43d994b" - , "56" /\ - "66d1512d5fb315c7563ae43c37610cd07977c7ffffffffa1581c4e5205e5df36" - , "57" /\ - "8030e9f814c2258c01f50c62375c55b07fbcc076c181d8799f01a0ffffffff,d" - , "58" /\ - "8799f581c11185d006a64f24e9cf6da987589cd0b166718d3680e63985db3703" - , "59" /\ - "d9fd8799fd8799fd8799f581c70e60f3b5ea7153e0acc7a803e4401d44b8ed1b" - , "60" /\ - "ae1c7baaad1a62a72ffd8799fd8799fd8799f581c1e78aae7c90cc36d624f7b3" - , "61" /\ - "bb6d86b52696dc84e490f343eba89005fffffffffa140d8799f00a1401a000f3" - , "62" /\ - "2a0ffffd8799fd8799fd8799f581c11185d006a64f24e9cf6da987589cd0b166" - , "63" /\ - "718d3680e63985db3703dffd8799fd8799fd8799f581cac7d463e54c43d994b6" - , "64" /\ - "6d1512d5fb315c7563ae43c37610cd07977c7ffffffffa1581c4e5205e5df368" - , "65" /\ - "030e9f814c2258c01f50c62375c55b07fbcc076c181d8799f01a0ffffffff,d8" - , "66" /\ - "799f581c11185d006a64f24e9cf6da987589cd0b166718d3680e63985db3703d" - , "67" /\ - "9fd8799fd8799fd8799f581c70e60f3b5ea7153e0acc7a803e4401d44b8ed1ba" - , "68" /\ - "e1c7baaad1a62a72ffd8799fd8799fd8799f581c1e78aae7c90cc36d624f7b3b" - , "69" /\ - "b6d86b52696dc84e490f343eba89005fffffffffa140d8799f00a1401a000f32" - , "70" /\ - "a0ffffd8799fd8799fd8799f581c11185d006a64f24e9cf6da987589cd0b1667" - , "71" /\ - "18d3680e63985db3703dffd8799fd8799fd8799f581cac7d463e54c43d994b66" - , "72" /\ - "d1512d5fb315c7563ae43c37610cd07977c7ffffffffa1581c4e5205e5df3680" - , "73" /\ - "30e9f814c2258c01f50c62375c55b07fbcc076c181d8799f01a0ffffffff," - , "75" /\ - "4e5205e5df368030e9f814c2258c01f50c62375c55b07fbcc076c181::00" - , "76" /\ - "4e5205e5df368030e9f814c2258c01f50c62375c55b07fbcc076c181::01" - , "77" /\ - "4e5205e5df368030e9f814c2258c01f50c62375c55b07fbcc076c181::02" + Just $ GeneralTransactionMetadata $ Map.fromFoldable $ + [ 30 /\ "5" + , 50 /\ + "d8799f581c11185d006a64f24e9cf6da987589cd0b166718d3680e63985db370" + , 51 /\ + "3d9fd8799fd8799fd8799f581c70e60f3b5ea7153e0acc7a803e4401d44b8ed1" + , 52 /\ + "bae1c7baaad1a62a72ffd8799fd8799fd8799f581c1e78aae7c90cc36d624f7b" + , 53 /\ + "3bb6d86b52696dc84e490f343eba89005fffffffffa140d8799f00a1401a000f" + , 54 /\ + "32a0ffffd8799fd8799fd8799f581c11185d006a64f24e9cf6da987589cd0b16" + , 55 /\ + "6718d3680e63985db3703dffd8799fd8799fd8799f581cac7d463e54c43d994b" + , 56 /\ + "66d1512d5fb315c7563ae43c37610cd07977c7ffffffffa1581c4e5205e5df36" + , 57 /\ + "8030e9f814c2258c01f50c62375c55b07fbcc076c181d8799f01a0ffffffff,d" + , 58 /\ + "8799f581c11185d006a64f24e9cf6da987589cd0b166718d3680e63985db3703" + , 59 /\ + "d9fd8799fd8799fd8799f581c70e60f3b5ea7153e0acc7a803e4401d44b8ed1b" + , 60 /\ + "ae1c7baaad1a62a72ffd8799fd8799fd8799f581c1e78aae7c90cc36d624f7b3" + , 61 /\ + "bb6d86b52696dc84e490f343eba89005fffffffffa140d8799f00a1401a000f3" + , 62 /\ + "2a0ffffd8799fd8799fd8799f581c11185d006a64f24e9cf6da987589cd0b166" + , 63 /\ + "718d3680e63985db3703dffd8799fd8799fd8799f581cac7d463e54c43d994b6" + , 64 /\ + "6d1512d5fb315c7563ae43c37610cd07977c7ffffffffa1581c4e5205e5df368" + , 65 /\ + "030e9f814c2258c01f50c62375c55b07fbcc076c181d8799f01a0ffffffff,d8" + , 66 /\ + "799f581c11185d006a64f24e9cf6da987589cd0b166718d3680e63985db3703d" + , 67 /\ + "9fd8799fd8799fd8799f581c70e60f3b5ea7153e0acc7a803e4401d44b8ed1ba" + , 68 /\ + "e1c7baaad1a62a72ffd8799fd8799fd8799f581c1e78aae7c90cc36d624f7b3b" + , 69 /\ + "b6d86b52696dc84e490f343eba89005fffffffffa140d8799f00a1401a000f32" + , 70 /\ + "a0ffffd8799fd8799fd8799f581c11185d006a64f24e9cf6da987589cd0b1667" + , 71 /\ + "18d3680e63985db3703dffd8799fd8799fd8799f581cac7d463e54c43d994b66" + , 72 /\ + "d1512d5fb315c7563ae43c37610cd07977c7ffffffffa1581c4e5205e5df3680" + , 73 /\ + "30e9f814c2258c01f50c62375c55b07fbcc076c181d8799f01a0ffffffff," + , 75 /\ + "4e5205e5df368030e9f814c2258c01f50c62375c55b07fbcc076c181::00" + , 76 /\ + "4e5205e5df368030e9f814c2258c01f50c62375c55b07fbcc076c181::01" + , 77 /\ + "4e5205e5df368030e9f814c2258c01f50c62375c55b07fbcc076c181::02" + ] <#> \(label /\ text) -> + TransactionMetadatumLabel (BigInt.fromInt label) /\ Text text + , confirmed: true + } + +fixture2 :: Fixture +fixture2 = + { hash: TransactionHash $ hexToByteArrayUnsafe + "d499729695be63b4c6affb2412899a7f16390d54d97f78f51d796a5cef424126" + , metadata: + Just $ GeneralTransactionMetadata $ Map.fromFoldable $ + [ 674 /\ + [ "City" /\ "Mumbai" + , "Humidity" /\ "69.19999694824219 %" + , "Sensor" /\ "DTH22 with Raspberry Pi" + , "Temperature" /\ "27.299999237060547 C" + , "Timestamp" /\ "1672173001" ] + ] <#> \(label /\ metamap) -> + TransactionMetadatumLabel + (BigInt.fromInt label) /\ MetadataMap + (Map.fromFoldable $ metamap <#> \(k /\ v) -> Text k /\ Text v) + , confirmed: true } +fixture3 :: Fixture +fixture3 = + { hash: TransactionHash $ hexToByteArrayUnsafe + "7b458500ef7783e16dab5d9f9f282505182c316ccf3ecf75d0472f95ab31eeaa" + -- , metadata: Nothing + , metadata: Just $ GeneralTransactionMetadata $ Map.empty + , confirmed: true + } + +fixture4 :: Fixture +fixture4 = + { hash: TransactionHash $ hexToByteArrayUnsafe + "deadbeefdeadbeefdeadbeefdeadbeefdeadbeefdeadbeefdeadbeefdeadbeef" + , metadata: Nothing + , confirmed: false + } + +config :: ServerConfig config = { host: "cardano-preview.blockfrost.io" , port: UInt.fromInt 443 @@ -112,13 +155,15 @@ config = , path: Just "/api/v0" } -apiKey = Just ?help - -testPlan :: TestPlanM (Aff Unit) Unit -testPlan = group "Blockfrost" do - test "getTxMetadata success" do - metadata <- getTxMetadata fixture1.hash config apiKey - (hush metadata) `shouldEqual` (Just (Just fixture1.metadata)) - test "isTxConfirmed success" do - confirmed <- isTxConfirmed fixture1.hash config apiKey - (hush confirmed) `shouldEqual` (Just true) +testPlan :: String -> TestPlanM (Aff Unit) Unit +testPlan apiKey = group "Blockfrost" do + forWithIndex_ [ fixture1, fixture2, fixture3, fixture4 ] \i fixture -> + group ("fixture " <> show (i + 1)) do + test "getTxMetadata" do + eMetadata <- getTxMetadata fixture.hash config (Just apiKey) + metadata <- liftEither (lmap (error <<< show) eMetadata) + metadata `shouldEqual` fixture.metadata + test "isTxConfirmed" do + eConfirmed <- isTxConfirmed fixture.hash config (Just apiKey) + confirmed <- liftEither (lmap (error <<< show) eConfirmed) + confirmed `shouldEqual` fixture.confirmed From c92e78228ff6bc9b78f06f12391f97c310389bf2 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Wed, 28 Dec 2022 16:21:33 +0000 Subject: [PATCH 195/373] Change getTxMetadata query handle to use a custom error to unify the behaviour of metadata fetching in kupo and blockfrost. --- src/Contract/Test/Utils.purs | 4 +- src/Contract/Transaction.purs | 15 +++- src/Internal/Contract/QueryHandle.purs | 5 +- src/Internal/Contract/QueryHandle/Error.purs | 26 +++++++ src/Internal/QueryM.purs | 5 ++ src/Internal/QueryM/Kupo.purs | 35 ++++++--- src/Internal/Service/Blockfrost.purs | 30 ++++++-- test/Blockfrost.purs | 77 +++++++++++++------- 8 files changed, 148 insertions(+), 49 deletions(-) create mode 100644 src/Internal/Contract/QueryHandle/Error.purs diff --git a/src/Contract/Test/Utils.purs b/src/Contract/Test/Utils.purs index 1e2975ae0b..deb6a99569 100644 --- a/src/Contract/Test/Utils.purs +++ b/src/Contract/Test/Utils.purs @@ -82,7 +82,7 @@ import Ctl.Internal.Plutus.Types.Transaction import Ctl.Internal.Types.ByteArray (byteArrayToHex) import Data.Array (fromFoldable, mapWithIndex) as Array import Data.BigInt (BigInt) -import Data.Either (Either(Left, Right), isRight) +import Data.Either (Either(Left, Right), hush, isRight) import Data.Foldable (foldMap, null) import Data.Lens.Getter (view, (^.)) import Data.Map (filterKeys, lookup, values) as Map @@ -576,7 +576,7 @@ assertTxHasMetadataImpl assertTxHasMetadataImpl mdLabel txHash expectedMetadata = do generalMetadata <- assertContractM (TransactionHasNoMetadata txHash Nothing) - (getTxMetadata txHash) + (hush <$> getTxMetadata txHash) rawMetadata <- assertContractM' (TransactionHasNoMetadata txHash (Just mdLabel)) diff --git a/src/Contract/Transaction.purs b/src/Contract/Transaction.purs index b95b08b62a..78a1b50636 100644 --- a/src/Contract/Transaction.purs +++ b/src/Contract/Transaction.purs @@ -153,6 +153,14 @@ import Ctl.Internal.Contract.AwaitTxConfirmed ) as Contract import Ctl.Internal.Contract.MinFee (calculateMinFee) as Contract import Ctl.Internal.Contract.QueryHandle (getQueryHandle) +import Ctl.Internal.Contract.QueryHandle.Error (GetTxMetadataError) +import Ctl.Internal.Contract.QueryHandle.Error + ( GetTxMetadataError + ( GetTxMetadataTxNotFoundError + , GetTxMetadataMetadataEmptyOrMissingError + , GetTxMetadataClientError + ) + ) as X import Ctl.Internal.Contract.Sign (signTransaction) as Contract import Ctl.Internal.Hashing (transactionHash) as Hashing import Ctl.Internal.Plutus.Conversion @@ -491,12 +499,13 @@ getTxFinalFee :: BalancedSignedTransaction -> BigInt getTxFinalFee = unwrap <<< view (Transaction._body <<< Transaction._fee) <<< unwrap --- TODO Throw the Either errors? -- | Fetch transaction metadata. -getTxMetadata :: TransactionHash -> Contract (Maybe GeneralTransactionMetadata) +getTxMetadata + :: TransactionHash + -> Contract (Either GetTxMetadataError GeneralTransactionMetadata) getTxMetadata th = do queryHandle <- getQueryHandle - liftAff $ join <<< hush <$> queryHandle.getTxMetadata th + liftAff $ queryHandle.getTxMetadata th -- | Wait until a transaction with given hash is confirmed. -- | Use `awaitTxConfirmedWithTimeout` if you want to limit the time of waiting. diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs index 1a04da7072..090f9925f0 100644 --- a/src/Internal/Contract/QueryHandle.purs +++ b/src/Internal/Contract/QueryHandle.purs @@ -24,6 +24,7 @@ import Ctl.Internal.Contract.QueryBackend , CtlBackend , QueryBackend(BlockfrostBackend, CtlBackend) ) +import Ctl.Internal.Contract.QueryHandle.Error (GetTxMetadataError) import Ctl.Internal.Hashing (transactionHash) as Hashing import Ctl.Internal.QueryM (ClientError, QueryM) import Ctl.Internal.QueryM (evaluateTxOgmios, getChainTip, submitTxOgmios) as QueryM @@ -68,7 +69,9 @@ type AffE (a :: Type) = Aff (Either ClientError a) type QueryHandle = { getDatumByHash :: DataHash -> AffE (Maybe Datum) , getScriptByHash :: ScriptHash -> AffE (Maybe ScriptRef) - , getTxMetadata :: TransactionHash -> AffE (Maybe GeneralTransactionMetadata) + , getTxMetadata :: + TransactionHash + -> Aff (Either GetTxMetadataError GeneralTransactionMetadata) , getUtxoByOref :: TransactionInput -> AffE (Maybe TransactionOutput) , isTxConfirmed :: TransactionHash -> AffE Boolean , utxosAt :: Address -> AffE UtxoMap diff --git a/src/Internal/Contract/QueryHandle/Error.purs b/src/Internal/Contract/QueryHandle/Error.purs new file mode 100644 index 0000000000..5a6b97ac4f --- /dev/null +++ b/src/Internal/Contract/QueryHandle/Error.purs @@ -0,0 +1,26 @@ +module Ctl.Internal.Contract.QueryHandle.Error + ( GetTxMetadataError + ( GetTxMetadataTxNotFoundError + , GetTxMetadataMetadataEmptyOrMissingError + , GetTxMetadataClientError + ) + ) where + +import Prelude + +import Ctl.Internal.QueryM (ClientError) + +-- Abstracts over the differences between Kupo and Blockfrost +data GetTxMetadataError + = GetTxMetadataTxNotFoundError + | GetTxMetadataMetadataEmptyOrMissingError + | GetTxMetadataClientError ClientError + +instance Show GetTxMetadataError where + show = case _ of + GetTxMetadataTxNotFoundError -> + "GetTxMetadataTxNotFoundError" + GetTxMetadataMetadataEmptyOrMissingError -> + "GetTxMetadataMetadataEmptyOrMissingError" + GetTxMetadataClientError error -> + "(GetTxMetadataClientError " <> show error <> ")" diff --git a/src/Internal/QueryM.purs b/src/Internal/QueryM.purs index d789473d4b..a56c49e478 100644 --- a/src/Internal/QueryM.purs +++ b/src/Internal/QueryM.purs @@ -384,10 +384,15 @@ mempoolSnapshotHasTxAff ogmiosWs logger ms = -------------------------------------------------------------------------------- data ClientError + -- | Affjax error = ClientHttpError Affjax.Error + -- | Server responded with HTTP status code outside of 200-299 | ClientHttpResponseError Affjax.StatusCode.StatusCode String + -- | Failed to decode the response | ClientDecodeJsonError String JsonDecodeError + -- | Failed to encode the request | ClientEncodingError String + -- | Any other error | ClientOtherError String -- No Show instance of Affjax.Error diff --git a/src/Internal/QueryM/Kupo.purs b/src/Internal/QueryM/Kupo.purs index accb477d9b..3dd109dcbd 100644 --- a/src/Internal/QueryM/Kupo.purs +++ b/src/Internal/QueryM/Kupo.purs @@ -27,6 +27,7 @@ import Affjax (Error, Response, defaultRequest, request) as Affjax import Affjax.ResponseFormat (string) as Affjax.ResponseFormat import Control.Alt ((<|>)) import Control.Bind (bindFlipped) +import Control.Monad.Error.Class (throwError) import Control.Monad.Except.Trans (ExceptT(ExceptT), except, runExceptT) import Control.Monad.Reader.Class (asks) import Control.Parallel (parTraverse) @@ -45,6 +46,13 @@ import Ctl.Internal.Cardano.Types.Value , mkSingletonNonAdaAsset , mkValue ) +import Ctl.Internal.Contract.QueryHandle.Error + ( GetTxMetadataError + ( GetTxMetadataClientError + , GetTxMetadataTxNotFoundError + , GetTxMetadataMetadataEmptyOrMissingError + ) + ) import Ctl.Internal.Deserialization.FromBytes (fromBytes) import Ctl.Internal.Deserialization.NativeScript (convertNativeScript) import Ctl.Internal.Deserialization.PlutusData (deserializeData) @@ -78,15 +86,18 @@ import Ctl.Internal.Types.Transaction ( TransactionHash(TransactionHash) , TransactionInput(TransactionInput) ) -import Ctl.Internal.Types.TransactionMetadata (GeneralTransactionMetadata) +import Ctl.Internal.Types.TransactionMetadata + ( GeneralTransactionMetadata(GeneralTransactionMetadata) + ) import Data.Array (uncons) +import Data.Bifunctor (lmap) import Data.BigInt (BigInt) import Data.Either (Either(Left, Right), note) import Data.Foldable (fold) import Data.Generic.Rep (class Generic) import Data.HTTP.Method (Method(GET)) import Data.Map (Map) -import Data.Map (fromFoldable, lookup) as Map +import Data.Map (fromFoldable, isEmpty, lookup) as Map import Data.Maybe (Maybe(Just, Nothing), fromMaybe) import Data.Newtype (class Newtype, unwrap, wrap) import Data.Show.Generic (genericShow) @@ -159,19 +170,25 @@ isTxConfirmedAff config (TransactionHash txHash) = runExceptT do getTxMetadata :: TransactionHash - -> QueryM (Either ClientError (Maybe GeneralTransactionMetadata)) + -> QueryM (Either GetTxMetadataError GeneralTransactionMetadata) getTxMetadata txHash = runExceptT do - ExceptT (isTxConfirmed txHash) >>= case _ of - Nothing -> pure Nothing + ExceptT (lmap GetTxMetadataClientError <$> isTxConfirmed txHash) >>= case _ of + Nothing -> throwError GetTxMetadataTxNotFoundError Just slot -> do let endpoint = "/metadata/" <> BigNum.toString (unwrap slot) <> "?transaction_id=" <> byteArrayToHex (unwrap txHash) - metadata <- ExceptT $ handleAffjaxResponse <$> kupoGetRequest - endpoint - -- `KupoMetadata` will fail parsing if there is more than one response - pure $ unwrapKupoMetadata metadata + kupoMetadata <- ExceptT $ + lmap GetTxMetadataClientError <<< handleAffjaxResponse <$> + kupoGetRequest + endpoint + case unwrapKupoMetadata kupoMetadata of + Nothing -> throwError GetTxMetadataMetadataEmptyOrMissingError + Just metadata + | Map.isEmpty (unwrap metadata) -> throwError + GetTxMetadataMetadataEmptyOrMissingError + | otherwise -> pure metadata -------------------------------------------------------------------------------- -- `utxosAt` response parsing diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index 21b31358ce..f316311a00 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -15,6 +15,13 @@ import Affjax (Error, Response, URL, defaultRequest, request) as Affjax import Affjax.RequestHeader (RequestHeader(RequestHeader)) as Affjax import Affjax.ResponseFormat as Affjax.ResponseFormat import Affjax.StatusCode (StatusCode(StatusCode)) as Affjax +import Ctl.Internal.Contract.QueryHandle.Error + ( GetTxMetadataError + ( GetTxMetadataTxNotFoundError + , GetTxMetadataClientError + , GetTxMetadataMetadataEmptyOrMissingError + ) + ) import Ctl.Internal.Deserialization.FromBytes (fromBytes) import Ctl.Internal.Deserialization.Transaction ( convertGeneralTransactionMetadata @@ -35,8 +42,8 @@ import Data.Foldable (foldMap) import Data.Generic.Rep (class Generic) import Data.HTTP.Method (Method(GET)) import Data.Map as Map -import Data.Maybe (Maybe(Just, Nothing)) -import Data.Newtype (unwrap) +import Data.Maybe (Maybe) +import Data.Newtype (class Newtype, unwrap) import Data.Show.Generic (genericShow) import Data.Traversable (for) import Effect.Aff (Aff) @@ -76,13 +83,19 @@ getTxMetadata :: TransactionHash -> ServerConfig -> Maybe String - -> Aff (Either ClientError (Maybe GeneralTransactionMetadata)) + -> Aff (Either GetTxMetadataError GeneralTransactionMetadata) getTxMetadata txHash config mbApiKey = do - response :: Either ClientError _ <- handleAffjaxResponse <$> request - pure case response of - Right metadata -> Right $ Just $ unwrapBlockfrostMetadata metadata - Left (ClientHttpResponseError (Affjax.StatusCode 404) _) -> Right Nothing - Left e -> Left e + response :: Either ClientError _ <- handleAffjaxResponse <$> + request + pure case unwrapBlockfrostMetadata <$> response of + Left (ClientHttpResponseError (Affjax.StatusCode 404) _) -> + Left GetTxMetadataTxNotFoundError + Left e -> + Left (GetTxMetadataClientError e) + Right metadata + | Map.isEmpty (unwrap metadata) -> + Left GetTxMetadataMetadataEmptyOrMissingError + | otherwise -> Right metadata where request :: Aff (Either Affjax.Error (Affjax.Response String)) request = Affjax.request $ Affjax.defaultRequest @@ -106,6 +119,7 @@ newtype BlockfrostMetadata = BlockfrostMetadata derive instance Generic BlockfrostMetadata _ derive instance Eq BlockfrostMetadata +derive instance Newtype BlockfrostMetadata _ instance Show BlockfrostMetadata where show = genericShow diff --git a/test/Blockfrost.purs b/test/Blockfrost.purs index fff38cc75e..4dbb3b9791 100644 --- a/test/Blockfrost.purs +++ b/test/Blockfrost.purs @@ -10,23 +10,30 @@ import Contract.Metadata ) import Contract.Prim.ByteArray (hexToByteArrayUnsafe) import Contract.Test.Mote (TestPlanM, interpretWithConfig) -import Contract.Transaction (TransactionHash(TransactionHash)) +import Contract.Transaction + ( GetTxMetadataError + ( GetTxMetadataTxNotFoundError + , GetTxMetadataMetadataEmptyOrMissingError + ) + , TransactionHash(TransactionHash) + ) import Control.Monad.Error.Class (liftEither) import Ctl.Internal.Helpers (liftedM) import Ctl.Internal.Service.Blockfrost (getTxMetadata, isTxConfirmed) import Data.Array ((!!)) import Data.Bifunctor (lmap) import Data.BigInt as BigInt +import Data.Either (Either(Left, Right)) import Data.FoldableWithIndex (forWithIndex_) import Data.Map as Map -import Data.Maybe (Maybe(Just, Nothing)) +import Data.Maybe (Maybe(Just)) import Data.Tuple.Nested ((/\)) import Data.UInt as UInt import Effect (Effect) import Effect.Aff (Aff, error, launchAff_) import Mote (group, test) import Node.Process (argv) -import Test.Spec.Assertions (shouldEqual) +import Test.Spec.Assertions (fail, shouldEqual) import Test.Spec.Runner (defaultConfig) -- Run with `spago test --main Test.Ctl.Blockfrost --exec-args PREVIEW_API_KEY` @@ -38,18 +45,28 @@ main = do defaultConfig { exit = true } (testPlan apiKey) -type Fixture = - { hash :: TransactionHash - , metadata :: Maybe GeneralTransactionMetadata - , confirmed :: Boolean - } +data Fixture + = TxWithMetadata + { hash :: TransactionHash + , metadata :: GeneralTransactionMetadata + } + | TxWithNoMetadata + { hash :: TransactionHash } + | UnconfirmedTx + { hash :: TransactionHash } + +fixtureHash :: Fixture -> TransactionHash +fixtureHash = case _ of + TxWithMetadata { hash } -> hash + TxWithNoMetadata { hash } -> hash + UnconfirmedTx { hash } -> hash fixture1 :: Fixture -fixture1 = +fixture1 = TxWithMetadata { hash: TransactionHash $ hexToByteArrayUnsafe "7a2aff2b7f92f6f8ec3fb2135301c7bfc36fea1489a3ca37fd6066f3155c46ff" , metadata: - Just $ GeneralTransactionMetadata $ Map.fromFoldable $ + GeneralTransactionMetadata $ Map.fromFoldable $ [ 30 /\ "5" , 50 /\ "d8799f581c11185d006a64f24e9cf6da987589cd0b166718d3680e63985db370" @@ -107,15 +124,14 @@ fixture1 = "4e5205e5df368030e9f814c2258c01f50c62375c55b07fbcc076c181::02" ] <#> \(label /\ text) -> TransactionMetadatumLabel (BigInt.fromInt label) /\ Text text - , confirmed: true } fixture2 :: Fixture -fixture2 = +fixture2 = TxWithMetadata { hash: TransactionHash $ hexToByteArrayUnsafe "d499729695be63b4c6affb2412899a7f16390d54d97f78f51d796a5cef424126" , metadata: - Just $ GeneralTransactionMetadata $ Map.fromFoldable $ + GeneralTransactionMetadata $ Map.fromFoldable $ [ 674 /\ [ "City" /\ "Mumbai" , "Humidity" /\ "69.19999694824219 %" @@ -127,24 +143,18 @@ fixture2 = TransactionMetadatumLabel (BigInt.fromInt label) /\ MetadataMap (Map.fromFoldable $ metamap <#> \(k /\ v) -> Text k /\ Text v) - , confirmed: true } fixture3 :: Fixture -fixture3 = +fixture3 = TxWithNoMetadata { hash: TransactionHash $ hexToByteArrayUnsafe "7b458500ef7783e16dab5d9f9f282505182c316ccf3ecf75d0472f95ab31eeaa" - -- , metadata: Nothing - , metadata: Just $ GeneralTransactionMetadata $ Map.empty - , confirmed: true } fixture4 :: Fixture -fixture4 = +fixture4 = UnconfirmedTx { hash: TransactionHash $ hexToByteArrayUnsafe "deadbeefdeadbeefdeadbeefdeadbeefdeadbeefdeadbeefdeadbeefdeadbeef" - , metadata: Nothing - , confirmed: false } config :: ServerConfig @@ -160,10 +170,25 @@ testPlan apiKey = group "Blockfrost" do forWithIndex_ [ fixture1, fixture2, fixture3, fixture4 ] \i fixture -> group ("fixture " <> show (i + 1)) do test "getTxMetadata" do - eMetadata <- getTxMetadata fixture.hash config (Just apiKey) - metadata <- liftEither (lmap (error <<< show) eMetadata) - metadata `shouldEqual` fixture.metadata + eMetadata <- getTxMetadata (fixtureHash fixture) config (Just apiKey) + case fixture of + TxWithMetadata { metadata } -> case eMetadata of + Right metadata' -> metadata' `shouldEqual` metadata + unexpected -> fail $ show unexpected <> " ≠ (Right (" + <> show metadata + <> "))" + TxWithNoMetadata _ -> case eMetadata of + Left GetTxMetadataMetadataEmptyOrMissingError -> pure unit + unexpected -> fail $ show unexpected <> + " ≠ (Left GetTxMetadataMetadataEmptyOrMissingError)" + UnconfirmedTx _ -> case eMetadata of + Left GetTxMetadataTxNotFoundError -> pure unit + unexpected -> fail $ show unexpected <> + " ≠ (Left GetTxMetadataTxNotFoundError)" test "isTxConfirmed" do - eConfirmed <- isTxConfirmed fixture.hash config (Just apiKey) + eConfirmed <- isTxConfirmed (fixtureHash fixture) config (Just apiKey) confirmed <- liftEither (lmap (error <<< show) eConfirmed) - confirmed `shouldEqual` fixture.confirmed + confirmed `shouldEqual` case fixture of + TxWithMetadata _ -> true + TxWithNoMetadata _ -> true + UnconfirmedTx _ -> false From 76578ddad207bcf720b499d53aaafacff826287e Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Wed, 28 Dec 2022 16:23:37 +0000 Subject: [PATCH 196/373] Drop comment --- src/Internal/Service/Blockfrost.purs | 6 ------ 1 file changed, 6 deletions(-) diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index f316311a00..b81cfc0930 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -73,12 +73,6 @@ isTxConfirmed txHash config mbApiKey = do endpoint :: Affjax.URL endpoint = "/txs/" <> byteArrayToHex (unwrap txHash) --- TODO Decide how to handle tx not found vs no metadata --- Kupo internally first finds an output of the tx, if there are none it will return Nothing --- But if there's no metadata, it will fail via ClientError, due to aeson parsing failing - --- Blockfrost on the other hand will (currently) fail with Nothing if the tx doesn't exist --- and return an empty metadata if the tx exists but had no metadata set (or the metadata was set but empty) getTxMetadata :: TransactionHash -> ServerConfig From 45e2ed288a34bd02ee217c80b1c8af5553602d57 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Thu, 29 Dec 2022 09:36:27 +0000 Subject: [PATCH 197/373] Add comment --- src/Contract/Transaction.purs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Contract/Transaction.purs b/src/Contract/Transaction.purs index 78a1b50636..5c4c58034d 100644 --- a/src/Contract/Transaction.purs +++ b/src/Contract/Transaction.purs @@ -500,6 +500,7 @@ getTxFinalFee = unwrap <<< view (Transaction._body <<< Transaction._fee) <<< unwrap -- | Fetch transaction metadata. +-- | Returns `Right` when the transaction exists and metadata was non-empty getTxMetadata :: TransactionHash -> Contract (Either GetTxMetadataError GeneralTransactionMetadata) From a4b545e29e9e8f9a37823f1f37699f72660a6158 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Thu, 29 Dec 2022 11:24:25 +0000 Subject: [PATCH 198/373] Add fixtures for blockfrost metadata unit test --- ...data-05eccee76935dcdcee51bc9539a4bda0.json | 1 + ...data-0e6bc6c9bfd8ca8e76fea0c77b408c94.json | 1 + ...data-1ad015357709a4bb3605cfba6c07fcfa.json | 1 + ...data-1ffc1b00de768cc4cc1fd57789975293.json | 1 + ...data-2695bd98c71ce3787d1dd743d7c81e62.json | 1 + ...data-2994cb9e7d27a895f5ab37cac85e00c6.json | 1 + ...data-408d98ab8c07f61f60b679b4ac1146ee.json | 1 + ...data-49cc70e05a6874717534184fe8f1c51c.json | 1 + ...data-4a771176a5ee391c5ac8e1a347665af9.json | 1 + ...data-4b615bb90ca1b4236909de9d77387349.json | 1 + ...data-58e0494c51d30eb3494f7c9198986bb9.json | 1 + ...data-5ddf5020f37378695c8f425616518e96.json | 1 + ...data-5e96ef1ee339fa6acee8d236a099a50a.json | 1 + ...data-70f851fe46e3f298d181e360ab69c7ee.json | 1 + ...data-7855477c5b5ef6f22592621de4059a38.json | 1 + ...data-7d9eb3d1f1771785b008f992169a9e55.json | 1 + ...data-85651cfb9d127afad9e9189900e0e5aa.json | 1 + ...data-8acb1a1fb6dbe876f677989a8ea43e50.json | 1 + ...data-9ec42e4096428bef20a6e30e089fa290.json | 1 + ...data-a41c8fcc791f757d7ee7b8edf67089c7.json | 1 + ...data-afa0730bb6c5188054571c420609b6d1.json | 1 + ...data-b35620f81cd2aeeb63383bf4842b6ca7.json | 1 + ...data-b79202b44212de279780aebb4d1cfa4b.json | 1 + ...data-cbd4c5d5e8bd4ee7b19c7eb389d8b998.json | 1 + ...data-ce90b4f9049c1d73965810525879b038.json | 1 + ...data-d0dc1df3b35e53b71b46ecc3b644f071.json | 1 + ...data-dcd34c370d57577ad751d256ba468dc9.json | 1 + ...data-ea7ba474ed55636ee60f5425587e971d.json | 1 + src/Internal/QueryM/Kupo.purs | 4 +- src/Internal/Service/Blockfrost.purs | 1 + test/Blockfrost/Aeson.purs | 99 +++++++++++++++++++ test/Unit.purs | 2 + 32 files changed, 131 insertions(+), 3 deletions(-) create mode 100644 fixtures/test/blockfrost/getTxMetadata-05eccee76935dcdcee51bc9539a4bda0.json create mode 100644 fixtures/test/blockfrost/getTxMetadata-0e6bc6c9bfd8ca8e76fea0c77b408c94.json create mode 100644 fixtures/test/blockfrost/getTxMetadata-1ad015357709a4bb3605cfba6c07fcfa.json create mode 100644 fixtures/test/blockfrost/getTxMetadata-1ffc1b00de768cc4cc1fd57789975293.json create mode 100644 fixtures/test/blockfrost/getTxMetadata-2695bd98c71ce3787d1dd743d7c81e62.json create mode 100644 fixtures/test/blockfrost/getTxMetadata-2994cb9e7d27a895f5ab37cac85e00c6.json create mode 100644 fixtures/test/blockfrost/getTxMetadata-408d98ab8c07f61f60b679b4ac1146ee.json create mode 100644 fixtures/test/blockfrost/getTxMetadata-49cc70e05a6874717534184fe8f1c51c.json create mode 100644 fixtures/test/blockfrost/getTxMetadata-4a771176a5ee391c5ac8e1a347665af9.json create mode 100644 fixtures/test/blockfrost/getTxMetadata-4b615bb90ca1b4236909de9d77387349.json create mode 100644 fixtures/test/blockfrost/getTxMetadata-58e0494c51d30eb3494f7c9198986bb9.json create mode 100644 fixtures/test/blockfrost/getTxMetadata-5ddf5020f37378695c8f425616518e96.json create mode 100644 fixtures/test/blockfrost/getTxMetadata-5e96ef1ee339fa6acee8d236a099a50a.json create mode 100644 fixtures/test/blockfrost/getTxMetadata-70f851fe46e3f298d181e360ab69c7ee.json create mode 100644 fixtures/test/blockfrost/getTxMetadata-7855477c5b5ef6f22592621de4059a38.json create mode 100644 fixtures/test/blockfrost/getTxMetadata-7d9eb3d1f1771785b008f992169a9e55.json create mode 100644 fixtures/test/blockfrost/getTxMetadata-85651cfb9d127afad9e9189900e0e5aa.json create mode 100644 fixtures/test/blockfrost/getTxMetadata-8acb1a1fb6dbe876f677989a8ea43e50.json create mode 100644 fixtures/test/blockfrost/getTxMetadata-9ec42e4096428bef20a6e30e089fa290.json create mode 100644 fixtures/test/blockfrost/getTxMetadata-a41c8fcc791f757d7ee7b8edf67089c7.json create mode 100644 fixtures/test/blockfrost/getTxMetadata-afa0730bb6c5188054571c420609b6d1.json create mode 100644 fixtures/test/blockfrost/getTxMetadata-b35620f81cd2aeeb63383bf4842b6ca7.json create mode 100644 fixtures/test/blockfrost/getTxMetadata-b79202b44212de279780aebb4d1cfa4b.json create mode 100644 fixtures/test/blockfrost/getTxMetadata-cbd4c5d5e8bd4ee7b19c7eb389d8b998.json create mode 100644 fixtures/test/blockfrost/getTxMetadata-ce90b4f9049c1d73965810525879b038.json create mode 100644 fixtures/test/blockfrost/getTxMetadata-d0dc1df3b35e53b71b46ecc3b644f071.json create mode 100644 fixtures/test/blockfrost/getTxMetadata-dcd34c370d57577ad751d256ba468dc9.json create mode 100644 fixtures/test/blockfrost/getTxMetadata-ea7ba474ed55636ee60f5425587e971d.json create mode 100644 test/Blockfrost/Aeson.purs diff --git a/fixtures/test/blockfrost/getTxMetadata-05eccee76935dcdcee51bc9539a4bda0.json b/fixtures/test/blockfrost/getTxMetadata-05eccee76935dcdcee51bc9539a4bda0.json new file mode 100644 index 0000000000..f517199fa7 --- /dev/null +++ b/fixtures/test/blockfrost/getTxMetadata-05eccee76935dcdcee51bc9539a4bda0.json @@ -0,0 +1 @@ +[{"label":"30","cbor_metadata":"\\xa1181e6135","metadata":"a1181e6135"},{"label":"50","cbor_metadata":"\\xa11832784064383739396635383163343936363139636230333461336166306138666630363262336530333033383562356563626239646337373332633839353735336339","metadata":"a11832784064383739396635383163343936363139636230333461336166306138666630363262336530333033383562356563626239646337373332633839353735336339"},{"label":"51","cbor_metadata":"\\xa11833784039643966643837393966643837393966643837393966353831633838386665663437366539623437343333313664313331356265323961313839646665666236","metadata":"a11833784039643966643837393966643837393966643837393966353831633838386665663437366539623437343333313664313331356265323961313839646665666236"},{"label":"52","cbor_metadata":"\\xa11834784036393961663030336161343834663761353966666438373939666438373939666438373939663538316366656637646361333134396530663439373036656362","metadata":"a11834784036393961663030336161343834663761353966666438373939666438373939666438373939663538316366656637646361333134396530663439373036656362"},{"label":"53","cbor_metadata":"\\xa11835784063373231396166313863336338353933333663396437376161623861643839623232666666666666666661313430643837393966303061313430316130306534","metadata":"a11835784063373231396166313863336338353933333663396437376161623861643839623232666666666666666661313430643837393966303061313430316130306534"},{"label":"54","cbor_metadata":"\\xa11836784065316330666666666438373939666438373939666438373939663538316337306536306633623565613731353365306163633761383033653434303164343462","metadata":"a11836784065316330666666666438373939666438373939666438373939663538316337306536306633623565613731353365306163633761383033653434303164343462"},{"label":"55","cbor_metadata":"\\xa11837784038656431626165316337626161616431613632613732666664383739396664383739396664383739396635383163316537386161653763393063633336643632","metadata":"a11837784038656431626165316337626161616431613632613732666664383739396664383739396664383739396635383163316537386161653763393063633336643632"},{"label":"56","cbor_metadata":"\\xa11838784034663762336262366438366235323639366463383465343930663334336562613839303035666666666666666666613134306438373939663030613134303161","metadata":"a11838784034663762336262366438366235323639366463383465343930663334336562613839303035666666666666666666613134306438373939663030613134303161"},{"label":"57","cbor_metadata":"\\xa11839784030303562386438306666666664383739396664383739396664383739396635383163343936363139636230333461336166306138666630363262336530333033","metadata":"a11839784030303562386438306666666664383739396664383739396664383739396635383163343936363139636230333461336166306138666630363262336530333033"},{"label":"58","cbor_metadata":"\\xa1183a784038356235656362623964633737333263383935373533633939646666643837393966643837393966643837393966353831633031313032643761353866393038","metadata":"a1183a784038356235656362623964633737333263383935373533633939646666643837393966643837393966643837393966353831633031313032643761353866393038"},{"label":"59","cbor_metadata":"\\xa1183b784063343866396634323135353364663061306563396637326135633132326431383030383864653861666166666666666666666131353831633037623339613865","metadata":"a1183b784063343866396634323135353364663061306563396637326135633132326431383030383864653861666166666666666666666131353831633037623339613865"},{"label":"60","cbor_metadata":"\\xa1183c784061643065663165333035346538313661336236393130303630626561663232313066646564363366623930636531333764383739396630306131346334333463","metadata":"a1183c784061643065663165333035346538313661336236393130303630626561663232313066646564363366623930636531333764383739396630306131346334333463"},{"label":"61","cbor_metadata":"\\xa1183d781f3530343333313463343733303333333633313334303166666666666666662c","metadata":"a1183d781f3530343333313463343733303333333633313334303166666666666666662c"},{"label":"63","cbor_metadata":"\\xa1183f782a7133747232396b6863326e3579656872683676367275666833663938676d78743836377765672c2c3030","metadata":"a1183f782a7133747232396b6863326e3579656872683676367275666833663938676d78743836377765672c2c3030"}] \ No newline at end of file diff --git a/fixtures/test/blockfrost/getTxMetadata-0e6bc6c9bfd8ca8e76fea0c77b408c94.json b/fixtures/test/blockfrost/getTxMetadata-0e6bc6c9bfd8ca8e76fea0c77b408c94.json new file mode 100644 index 0000000000..4890a4a18d --- /dev/null +++ b/fixtures/test/blockfrost/getTxMetadata-0e6bc6c9bfd8ca8e76fea0c77b408c94.json @@ -0,0 +1 @@ +[{"label":"721","cbor_metadata":"\\xa11902d1a178383239613866623833313837313862643735363132346630633134346635366434623435373964633565646632646434326436363961633631a16c6675726e697368486e4e7034a96b6465736372697074696f6e781e48616e642d637261667465642062792044756e7374616e2042726f776e2e6566696c657383a3696d656469615479706569696d6167652f676966646e616d65654368657374637372637835697066733a2f2f516d61395642507a796777794a586676566f6a65723331626977636f785954636b5279684c745073376e43537a70a3696d656469615479706569696d6167652f6d7034646e616d65654368657374637372637835697066733a2f2f516d5235767a68354c6b7047326d706874593350694837397834624669636377326256504d6d6d4c447946746636a3696d656469615479706569696d6167652f6d7034646e616d65654368657374637372637835697066733a2f2f516d524262454b564e44767053516231564b52743159697535756f576938647a4472616359483261566d514b344e6b6675726e6974757265496418cd62696465486e4e703465696d6167657835697066733a2f2f516d61395642507a796777794a586676566f6a65723331626977636f785954636b5279684c745073376e43537a70646e616d65654368657374647261746564302e3938637372637835697066733a2f2f516d61395642507a796777794a586676566f6a65723331626977636f785954636b5279684c745073376e43537a70647479706569696d6167652f676966","metadata":"a11902d1a178383239613866623833313837313862643735363132346630633134346635366434623435373964633565646632646434326436363961633631a16c6675726e697368486e4e7034a96b6465736372697074696f6e781e48616e642d637261667465642062792044756e7374616e2042726f776e2e6566696c657383a3696d656469615479706569696d6167652f676966646e616d65654368657374637372637835697066733a2f2f516d61395642507a796777794a586676566f6a65723331626977636f785954636b5279684c745073376e43537a70a3696d656469615479706569696d6167652f6d7034646e616d65654368657374637372637835697066733a2f2f516d5235767a68354c6b7047326d706874593350694837397834624669636377326256504d6d6d4c447946746636a3696d656469615479706569696d6167652f6d7034646e616d65654368657374637372637835697066733a2f2f516d524262454b564e44767053516231564b52743159697535756f576938647a4472616359483261566d514b344e6b6675726e6974757265496418cd62696465486e4e703465696d6167657835697066733a2f2f516d61395642507a796777794a586676566f6a65723331626977636f785954636b5279684c745073376e43537a70646e616d65654368657374647261746564302e3938637372637835697066733a2f2f516d61395642507a796777794a586676566f6a65723331626977636f785954636b5279684c745073376e43537a70647479706569696d6167652f676966"}] \ No newline at end of file diff --git a/fixtures/test/blockfrost/getTxMetadata-1ad015357709a4bb3605cfba6c07fcfa.json b/fixtures/test/blockfrost/getTxMetadata-1ad015357709a4bb3605cfba6c07fcfa.json new file mode 100644 index 0000000000..fa1418ecfa --- /dev/null +++ b/fixtures/test/blockfrost/getTxMetadata-1ad015357709a4bb3605cfba6c07fcfa.json @@ -0,0 +1 @@ +[{"label":"0","cbor_metadata":"\\xa100581cb2861a2d5db437c5dc2b8a8adc43570aec9f6a1597e6c0afeccf32f4","metadata":"a100581cb2861a2d5db437c5dc2b8a8adc43570aec9f6a1597e6c0afeccf32f4"}] \ No newline at end of file diff --git a/fixtures/test/blockfrost/getTxMetadata-1ffc1b00de768cc4cc1fd57789975293.json b/fixtures/test/blockfrost/getTxMetadata-1ffc1b00de768cc4cc1fd57789975293.json new file mode 100644 index 0000000000..0bc967fea4 --- /dev/null +++ b/fixtures/test/blockfrost/getTxMetadata-1ffc1b00de768cc4cc1fd57789975293.json @@ -0,0 +1 @@ +[{"label":"674","cbor_metadata":"\\xa11902a2a1636d736781781c4d696e737761703a205377617020457861637420496e204f72646572","metadata":"a11902a2a1636d736781781c4d696e737761703a205377617020457861637420496e204f72646572"}] \ No newline at end of file diff --git a/fixtures/test/blockfrost/getTxMetadata-2695bd98c71ce3787d1dd743d7c81e62.json b/fixtures/test/blockfrost/getTxMetadata-2695bd98c71ce3787d1dd743d7c81e62.json new file mode 100644 index 0000000000..1769d5dde2 --- /dev/null +++ b/fixtures/test/blockfrost/getTxMetadata-2695bd98c71ce3787d1dd743d7c81e62.json @@ -0,0 +1 @@ +[{"label":"30","cbor_metadata":"\\xa1181e6135","metadata":"a1181e6135"},{"label":"50","cbor_metadata":"\\xa11832784064383739396635383163613634363336613032623432666632303230613832306637343534623634343264626232646332366534663037383031666338346232","metadata":"a11832784064383739396635383163613634363336613032623432666632303230613832306637343534623634343264626232646332366534663037383031666338346232"},{"label":"51","cbor_metadata":"\\xa11833784032383966643837393966643837393966643837393966353831633432623038323534616264626633326362613166643063303262623536343038383430393639","metadata":"a11833784032383966643837393966643837393966643837393966353831633432623038323534616264626633326362613166643063303262623536343038383430393639"},{"label":"52","cbor_metadata":"\\xa11834784065626235633263643133333534646561326366666438373939666438373939666438373939663538316365366130353238663766333564626335393761383531","metadata":"a11834784065626235633263643133333534646561326366666438373939666438373939666438373939663538316365366130353238663766333564626335393761383531"},{"label":"53","cbor_metadata":"\\xa11835784037393138336632336563303931666638633833643032363939363039396637666336666666666666666661313430643837393966303061313430316130303066","metadata":"a11835784037393138336632336563303931666638633833643032363939363039396637666336666666666666666661313430643837393966303061313430316130303066"},{"label":"54","cbor_metadata":"\\xa11836784034323430666666666438373939666438373939666438373939663538316337306536306633623565613731353365306163633761383033653434303164343462","metadata":"a11836784034323430666666666438373939666438373939666438373939663538316337306536306633623565613731353365306163633761383033653434303164343462"},{"label":"55","cbor_metadata":"\\xa11837784038656431626165316337626161616431613632613732666664383739396664383739396664383739396635383163316537386161653763393063633336643632","metadata":"a11837784038656431626165316337626161616431613632613732666664383739396664383739396664383739396635383163316537386161653763393063633336643632"},{"label":"56","cbor_metadata":"\\xa11838784034663762336262366438366235323639366463383465343930663334336562613839303035666666666666666666613134306438373939663030613134303161","metadata":"a11838784034663762336262366438366235323639366463383465343930663334336562613839303035666666666666666666613134306438373939663030613134303161"},{"label":"57","cbor_metadata":"\\xa11839784030303066343234306666666664383739396664383739396664383739396635383163613634363336613032623432666632303230613832306637343534623634","metadata":"a11839784030303066343234306666666664383739396664383739396664383739396635383163613634363336613032623432666632303230613832306637343534623634"},{"label":"58","cbor_metadata":"\\xa1183a784034326462623264633236653466303738303166633834623232386666643837393966643837393966643837393966353831633765396434366337306261396232","metadata":"a1183a784034326462623264633236653466303738303166633834623232386666643837393966643837393966643837393966353831633765396434366337306261396232"},{"label":"59","cbor_metadata":"\\xa1183b784065623838376130396665353637343963633064653935383532636137393336626133653463313936356666666666666666666131343064383739396630306131","metadata":"a1183b784065623838376130396665353637343963633064653935383532636137393336626133653463313936356666666666666666666131343064383739396630306131"},{"label":"60","cbor_metadata":"\\xa1183c7534303161303234336435383066666666666666662c","metadata":"a1183c7534303161303234336435383066666666666666662c"}] \ No newline at end of file diff --git a/fixtures/test/blockfrost/getTxMetadata-2994cb9e7d27a895f5ab37cac85e00c6.json b/fixtures/test/blockfrost/getTxMetadata-2994cb9e7d27a895f5ab37cac85e00c6.json new file mode 100644 index 0000000000..aa4be21d8f --- /dev/null +++ b/fixtures/test/blockfrost/getTxMetadata-2994cb9e7d27a895f5ab37cac85e00c6.json @@ -0,0 +1 @@ +[{"label":"0","cbor_metadata":"\\xa100581c63ce74db95d3ce2e10abd42e544a7ae7788ebe40193cec88f5eadc22","metadata":"a100581c63ce74db95d3ce2e10abd42e544a7ae7788ebe40193cec88f5eadc22"}] \ No newline at end of file diff --git a/fixtures/test/blockfrost/getTxMetadata-408d98ab8c07f61f60b679b4ac1146ee.json b/fixtures/test/blockfrost/getTxMetadata-408d98ab8c07f61f60b679b4ac1146ee.json new file mode 100644 index 0000000000..84df5e7742 --- /dev/null +++ b/fixtures/test/blockfrost/getTxMetadata-408d98ab8c07f61f60b679b4ac1146ee.json @@ -0,0 +1 @@ +[{"label":"30","cbor_metadata":"\\xa1181e6135","metadata":"a1181e6135"},{"label":"50","cbor_metadata":"\\xa11832784064383739396635383163663033663232613834303834303864383639353339346534323633393932323637386135613263383035303735343034373536313634","metadata":"a11832784064383739396635383163663033663232613834303834303864383639353339346534323633393932323637386135613263383035303735343034373536313634"},{"label":"51","cbor_metadata":"\\xa11833784065383966643837393966643837393966643837393966353831633730653630663362356561373135336530616363376138303365343430316434346238656431","metadata":"a11833784065383966643837393966643837393966643837393966353831633730653630663362356561373135336530616363376138303365343430316434346238656431"},{"label":"52","cbor_metadata":"\\xa11834784062616531633762616161643161363261373266666438373939666438373939666438373939663538316331653738616165376339306363333664363234663762","metadata":"a11834784062616531633762616161643161363261373266666438373939666438373939666438373939663538316331653738616165376339306363333664363234663762"},{"label":"53","cbor_metadata":"\\xa11835784033626236643836623532363936646338346534393066333433656261383930303566666666666666666661313430643837393966303061313430316130363134","metadata":"a11835784033626236643836623532363936646338346534393066333433656261383930303566666666666666666661313430643837393966303061313430316130363134"},{"label":"54","cbor_metadata":"\\xa11836784036353830666666666438373939666438373939666438373939663538316366303366323261383430383430386438363935333934653432363339393232363738","metadata":"a11836784036353830666666666438373939666438373939666438373939663538316366303366323261383430383430386438363935333934653432363339393232363738"},{"label":"55","cbor_metadata":"\\xa11837784061356132633830353037353430343735363136346538666664383739396664383739396664383739396635383163386332343364313466313936363161393532","metadata":"a11837784061356132633830353037353430343735363136346538666664383739396664383739396664383739396635383163386332343364313466313936363161393532"},{"label":"56","cbor_metadata":"\\xa11838784064666262383931336564313634303763353435383937663638333133646236373862383533636666666666666666613135383163393239623136333737393861","metadata":"a11838784064666262383931336564313634303763353435383937663638333133646236373862383533636666666666666666613135383163393239623136333737393861"},{"label":"57","cbor_metadata":"\\xa11839784038313562616631383963613530333963653464653935323365366231653738386237666665333665383634346438373939663030613134613432363136653662","metadata":"a11839784038313562616631383963613530333963653464653935323365366231653738386237666665333665383634346438373939663030613134613432363136653662"},{"label":"58","cbor_metadata":"\\xa1183a77373334313663373036383631303166666666666666662c","metadata":"a1183a77373334313663373036383631303166666666666666662c"},{"label":"60","cbor_metadata":"\\xa1183c782a72786a3671357575736e67657563617267676779776a6a7878613768706a64336a617a6d786a2c2c3030","metadata":"a1183c782a72786a3671357575736e67657563617267676779776a6a7878613768706a64336a617a6d786a2c2c3030"}] \ No newline at end of file diff --git a/fixtures/test/blockfrost/getTxMetadata-49cc70e05a6874717534184fe8f1c51c.json b/fixtures/test/blockfrost/getTxMetadata-49cc70e05a6874717534184fe8f1c51c.json new file mode 100644 index 0000000000..e9fa54fb01 --- /dev/null +++ b/fixtures/test/blockfrost/getTxMetadata-49cc70e05a6874717534184fe8f1c51c.json @@ -0,0 +1 @@ +[{"label":"30","cbor_metadata":"\\xa1181e6135","metadata":"a1181e6135"},{"label":"50","cbor_metadata":"\\xa11832784064383739396635383163386532366436643439633163343465336430616264646463623935646531363639303830333963666536396537613733326566646532","metadata":"a11832784064383739396635383163386532366436643439633163343465336430616264646463623935646531363639303830333963666536396537613733326566646532"},{"label":"51","cbor_metadata":"\\xa11833784031303966643837393966643837393966643837393966353831633337623134383832363430666230663264356363616239396630636664623938306466336632","metadata":"a11833784031303966643837393966643837393966643837393966353831633337623134383832363430666230663264356363616239396630636664623938306466336632"},{"label":"52","cbor_metadata":"\\xa11834784064366564373266643064653433373438626266666438373939666438373939666438373939663538316366663932316432643264333962373735386162643038","metadata":"a11834784064366564373266643064653433373438626266666438373939666438373939666438373939663538316366663932316432643264333962373735386162643038"},{"label":"53","cbor_metadata":"\\xa11835784031303862366562303630333733613961326566616265386637383730393934303866666666666666666661313430643837393966303061313430316130303761","metadata":"a11835784031303862366562303630333733613961326566616265386637383730393934303866666666666666666661313430643837393966303061313430316130303761"},{"label":"54","cbor_metadata":"\\xa11836784031323030666666666438373939666438373939666438373939663538316337306536306633623565613731353365306163633761383033653434303164343462","metadata":"a11836784031323030666666666438373939666438373939666438373939663538316337306536306633623565613731353365306163633761383033653434303164343462"},{"label":"55","cbor_metadata":"\\xa11837784038656431626165316337626161616431613632613732666664383739396664383739396664383739396635383163316537386161653763393063633336643632","metadata":"a11837784038656431626165316337626161616431613632613732666664383739396664383739396664383739396635383163316537386161653763393063633336643632"},{"label":"56","cbor_metadata":"\\xa11838784034663762336262366438366235323639366463383465343930663334336562613839303035666666666666666666613134306438373939663030613134303161","metadata":"a11838784034663762336262366438366235323639366463383465343930663334336562613839303035666666666666666666613134306438373939663030613134303161"},{"label":"57","cbor_metadata":"\\xa11839784030303066343234306666666664383739396664383739396664383739396635383163386532366436643439633163343465336430616264646463623935646531","metadata":"a11839784030303066343234306666666664383739396664383739396664383739396635383163386532366436643439633163343465336430616264646463623935646531"},{"label":"58","cbor_metadata":"\\xa1183a784036363930383033396366653639653761373332656664653231306666643837393966643837393966643837393966353831633166343538663633316631356632","metadata":"a1183a784036363930383033396366653639653761373332656664653231306666643837393966643837393966643837393966353831633166343538663633316631356632"},{"label":"59","cbor_metadata":"\\xa1183b784036633637363239623166616137656661383433333139356636373961356235386631386666326531646666666666666666666131353831633834343432333835","metadata":"a1183b784036633637363239623166616137656661383433333139356636373961356235386631386666326531646666666666666666666131353831633834343432333835"},{"label":"60","cbor_metadata":"\\xa1183c784064366337623137373931363064623636663834323739393538343364373139343866333238333532663430356266313464383739396630306131343536323634","metadata":"a1183c784064366337623137373931363064623636663834323739393538343364373139343866333238333532663430356266313464383739396630306131343536323634"},{"label":"61","cbor_metadata":"\\xa1183d71333633333339303166666666666666662c","metadata":"a1183d71333633333339303166666666666666662c"},{"label":"63","cbor_metadata":"\\xa1183f782a30706b76337933327877687478756471333734376a73637a61323964706567616e78796d35672c2c3030","metadata":"a1183f782a30706b76337933327877687478756471333734376a73637a61323964706567616e78796d35672c2c3030"}] \ No newline at end of file diff --git a/fixtures/test/blockfrost/getTxMetadata-4a771176a5ee391c5ac8e1a347665af9.json b/fixtures/test/blockfrost/getTxMetadata-4a771176a5ee391c5ac8e1a347665af9.json new file mode 100644 index 0000000000..a86dd2ccae --- /dev/null +++ b/fixtures/test/blockfrost/getTxMetadata-4a771176a5ee391c5ac8e1a347665af9.json @@ -0,0 +1 @@ +[{"label":"30","cbor_metadata":"\\xa1181e6135","metadata":"a1181e6135"},{"label":"50","cbor_metadata":"\\xa11832784064383739396635383163383131393936376139643235393730353035363838313435383137346138363839616231393235633934376434363139643066646561","metadata":"a11832784064383739396635383163383131393936376139643235393730353035363838313435383137346138363839616231393235633934376434363139643066646561"},{"label":"51","cbor_metadata":"\\xa11833784064313966643837393966643837393966643837393966353831633630366161643338666663656563306231363637396235313964613866303937616665613161","metadata":"a11833784064313966643837393966643837393966643837393966353831633630366161643338666663656563306231363637396235313964613866303937616665613161"},{"label":"52","cbor_metadata":"\\xa11834784038616230333462393264313332613839653466666438373939666438373939666438373939663538316333356631356333373261386263333866626363666433","metadata":"a11834784038616230333462393264313332613839653466666438373939666438373939666438373939663538316333356631356333373261386263333866626363666433"},{"label":"53","cbor_metadata":"\\xa11835784033326565323439613839646266383333373133376637643363316432326336313264666666666666666661313430643837393966303061313430316130323036","metadata":"a11835784033326565323439613839646266383333373133376637643363316432326336313264666666666666666661313430643837393966303061313430316130323036"},{"label":"54","cbor_metadata":"\\xa11836784063633830666666666438373939666438373939666438373939663538316337306536306633623565613731353365306163633761383033653434303164343462","metadata":"a11836784063633830666666666438373939666438373939666438373939663538316337306536306633623565613731353365306163633761383033653434303164343462"},{"label":"55","cbor_metadata":"\\xa11837784038656431626165316337626161616431613632613732666664383739396664383739396664383739396635383163316537386161653763393063633336643632","metadata":"a11837784038656431626165316337626161616431613632613732666664383739396664383739396664383739396635383163316537386161653763393063633336643632"},{"label":"56","cbor_metadata":"\\xa11838784034663762336262366438366235323639366463383465343930663334336562613839303035666666666666666666613134306438373939663030613134303161","metadata":"a11838784034663762336262366438366235323639366463383465343930663334336562613839303035666666666666666666613134306438373939663030613134303161"},{"label":"57","cbor_metadata":"\\xa11839784030303637633238306666666664383739396664383739396664383739396635383163383131393936376139643235393730353035363838313435383137346138","metadata":"a11839784030303637633238306666666664383739396664383739396664383739396635383163383131393936376139643235393730353035363838313435383137346138"},{"label":"58","cbor_metadata":"\\xa1183a784036383961623139323563393437643436313964306664656164316666643837393966643837393966643837393966353831633662626165353439323834376136","metadata":"a1183a784036383961623139323563393437643436313964306664656164316666643837393966643837393966643837393966353831633662626165353439323834376136"},{"label":"59","cbor_metadata":"\\xa1183b784036356566333964396162323531613438616130616139333964643936616564633036343833333462653266666666666666666131353831633731363736376437","metadata":"a1183b784036356566333964396162323531613438616130616139333964643936616564633036343833333462653266666666666666666131353831633731363736376437"},{"label":"60","cbor_metadata":"\\xa1183c784033636139343635313131643633633036653135373031663963386332306335306531643738643431366162653939303164383739396630306131353134663534","metadata":"a1183c784033636139343635313131643633633036653135373031663963386332306335306531643738643431366162653939303164383739396630306131353134663534"},{"label":"61","cbor_metadata":"\\xa1183d7829346234363631366436393663373934333732363537333734333833313332303166666666666666662c","metadata":"a1183d7829346234363631366436393663373934333732363537333734333833313332303166666666666666662c"},{"label":"63","cbor_metadata":"\\xa1183f782a727771647964303261713275713033743537796776726a39337661396a79746c686b6d7068642c2c3030","metadata":"a1183f782a727771647964303261713275713033743537796776726a39337661396a79746c686b6d7068642c2c3030"}] \ No newline at end of file diff --git a/fixtures/test/blockfrost/getTxMetadata-4b615bb90ca1b4236909de9d77387349.json b/fixtures/test/blockfrost/getTxMetadata-4b615bb90ca1b4236909de9d77387349.json new file mode 100644 index 0000000000..3a21595592 --- /dev/null +++ b/fixtures/test/blockfrost/getTxMetadata-4b615bb90ca1b4236909de9d77387349.json @@ -0,0 +1 @@ +[{"label":"30","cbor_metadata":"\\xa1181e6135","metadata":"a1181e6135"},{"label":"50","cbor_metadata":"\\xa11832784064383739396635383163303036663131396364666230333438653234616333666135313739373539356131616136623365323131306635386362613737393263","metadata":"a11832784064383739396635383163303036663131396364666230333438653234616333666135313739373539356131616136623365323131306635386362613737393263"},{"label":"51","cbor_metadata":"\\xa11833784063393966643837393966643837393966643837393966353831636130616466336437316637376565663136323039383732366665393732336135623939623461","metadata":"a11833784063393966643837393966643837393966643837393966353831636130616466336437316637376565663136323039383732366665393732336135623939623461"},{"label":"52","cbor_metadata":"\\xa11834784034653661326131623830303130363630393866666438373939666438373939666438373939663538316332613464366563393832616335646666626661333561","metadata":"a11834784034653661326131623830303130363630393866666438373939666438373939666438373939663538316332613464366563393832616335646666626661333561"},{"label":"53","cbor_metadata":"\\xa11835784063343062663435616438346561333438353738373866643038643537383464646337666666666666666661313430643837393966303061313430316130333933","metadata":"a11835784063343062663435616438346561333438353738373866643038643537383464646337666666666666666661313430643837393966303061313430316130333933"},{"label":"54","cbor_metadata":"\\xa11836784038373030666666666438373939666438373939666438373939663538316337306536306633623565613731353365306163633761383033653434303164343462","metadata":"a11836784038373030666666666438373939666438373939666438373939663538316337306536306633623565613731353365306163633761383033653434303164343462"},{"label":"55","cbor_metadata":"\\xa11837784038656431626165316337626161616431613632613732666664383739396664383739396664383739396635383163316537386161653763393063633336643632","metadata":"a11837784038656431626165316337626161616431613632613732666664383739396664383739396664383739396635383163316537386161653763393063633336643632"},{"label":"56","cbor_metadata":"\\xa11838784034663762336262366438366235323639366463383465343930663334336562613839303035666666666666666666613134306438373939663030613134303161","metadata":"a11838784034663762336262366438366235323639366463383465343930663334336562613839303035666666666666666666613134306438373939663030613134303161"},{"label":"57","cbor_metadata":"\\xa11839784030313665333630306666666664383739396664383739396664383739396635383163303036663131396364666230333438653234616333666135313739373539","metadata":"a11839784030313665333630306666666664383739396664383739396664383739396635383163303036663131396364666230333438653234616333666135313739373539"},{"label":"58","cbor_metadata":"\\xa1183a784035613161613662336532313130663538636261373739326363396666643837393966643837393966643837393966353831636438386333323638663731346162","metadata":"a1183a784035613161613662336532313130663538636261373739326363396666643837393966643837393966643837393966353831636438386333323638663731346162"},{"label":"59","cbor_metadata":"\\xa1183b784037373265373132343661313333623865333762376237363337636332366433623837636534616362623166666666666666666131343064383739396630306131","metadata":"a1183b784037373265373132343661313333623865333762376237363337636332366433623837636534616362623166666666666666666131343064383739396630306131"},{"label":"60","cbor_metadata":"\\xa1183c7534303161343238346366303066666666666666662c","metadata":"a1183c7534303161343238346366303066666666666666662c"}] \ No newline at end of file diff --git a/fixtures/test/blockfrost/getTxMetadata-58e0494c51d30eb3494f7c9198986bb9.json b/fixtures/test/blockfrost/getTxMetadata-58e0494c51d30eb3494f7c9198986bb9.json new file mode 100644 index 0000000000..0637a088a0 --- /dev/null +++ b/fixtures/test/blockfrost/getTxMetadata-58e0494c51d30eb3494f7c9198986bb9.json @@ -0,0 +1 @@ +[] \ No newline at end of file diff --git a/fixtures/test/blockfrost/getTxMetadata-5ddf5020f37378695c8f425616518e96.json b/fixtures/test/blockfrost/getTxMetadata-5ddf5020f37378695c8f425616518e96.json new file mode 100644 index 0000000000..fdfdd498d2 --- /dev/null +++ b/fixtures/test/blockfrost/getTxMetadata-5ddf5020f37378695c8f425616518e96.json @@ -0,0 +1 @@ +[{"label":"30","cbor_metadata":"\\xa1181e6135","metadata":"a1181e6135"},{"label":"50","cbor_metadata":"\\xa11832784064383739396635383163386532366436643439633163343465336430616264646463623935646531363639303830333963666536396537613733326566646532","metadata":"a11832784064383739396635383163386532366436643439633163343465336430616264646463623935646531363639303830333963666536396537613733326566646532"},{"label":"51","cbor_metadata":"\\xa11833784031303966643837393966643837393966643837393966353831633266366237343030336666343263333733393865376438396664653639326166616362666235","metadata":"a11833784031303966643837393966643837393966643837393966353831633266366237343030336666343263333733393865376438396664653639326166616362666235"},{"label":"52","cbor_metadata":"\\xa11834784033333662316236316561393232393665613766666438373939666438373939666438373939663538316363343630313530386362636435303237316562356565","metadata":"a11834784033333662316236316561393232393665613766666438373939666438373939666438373939663538316363343630313530386362636435303237316562356565"},{"label":"53","cbor_metadata":"\\xa11835784064663039336234363535623838313466653730663534626262376630373861326266666666666666666661313430643837393966303061313430316130303066","metadata":"a11835784064663039336234363535623838313466653730663534626262376630373861326266666666666666666661313430643837393966303061313430316130303066"},{"label":"54","cbor_metadata":"\\xa11836784032616430666666666438373939666438373939666438373939663538316337306536306633623565613731353365306163633761383033653434303164343462","metadata":"a11836784032616430666666666438373939666438373939666438373939663538316337306536306633623565613731353365306163633761383033653434303164343462"},{"label":"55","cbor_metadata":"\\xa11837784038656431626165316337626161616431613632613732666664383739396664383739396664383739396635383163316537386161653763393063633336643632","metadata":"a11837784038656431626165316337626161616431613632613732666664383739396664383739396664383739396635383163316537386161653763393063633336643632"},{"label":"56","cbor_metadata":"\\xa11838784034663762336262366438366235323639366463383465343930663334336562613839303035666666666666666666613134306438373939663030613134303161","metadata":"a11838784034663762336262366438366235323639366463383465343930663334336562613839303035666666666666666666613134306438373939663030613134303161"},{"label":"57","cbor_metadata":"\\xa11839784030303066326164306666666664383739396664383739396664383739396635383163386532366436643439633163343465336430616264646463623935646531","metadata":"a11839784030303066326164306666666664383739396664383739396664383739396635383163386532366436643439633163343465336430616264646463623935646531"},{"label":"58","cbor_metadata":"\\xa1183a784036363930383033396366653639653761373332656664653231306666643837393966643837393966643837393966353831633166343538663633316631356632","metadata":"a1183a784036363930383033396366653639653761373332656664653231306666643837393966643837393966643837393966353831633166343538663633316631356632"},{"label":"59","cbor_metadata":"\\xa1183b784036633637363239623166616137656661383433333139356636373961356235386631386666326531646666666666666666666131353831633366613466663630","metadata":"a1183b784036633637363239623166616137656661383433333139356636373961356235386631386666326531646666666666666666666131353831633366613466663630"},{"label":"60","cbor_metadata":"\\xa1183c784066376334313865333264653261346335353831363533386264393664386636313738363830386363326439333032666364383739396630306131346534313665","metadata":"a1183c784066376334313865333264653261346335353831363533386264393664386636313738363830386363326439333032666364383739396630306131346534313665"},{"label":"61","cbor_metadata":"\\xa1183d7823363736353663333033303337346336393631366536313331303166666666666666662c","metadata":"a1183d7823363736353663333033303337346336393631366536313331303166666666666666662c"},{"label":"63","cbor_metadata":"\\xa1183f782a6b306b6e333377367379376467706365666a7337787734666c707a77647a78687964617239332c2c3030","metadata":"a1183f782a6b306b6e333377367379376467706365666a7337787734666c707a77647a78687964617239332c2c3030"}] \ No newline at end of file diff --git a/fixtures/test/blockfrost/getTxMetadata-5e96ef1ee339fa6acee8d236a099a50a.json b/fixtures/test/blockfrost/getTxMetadata-5e96ef1ee339fa6acee8d236a099a50a.json new file mode 100644 index 0000000000..2df50474ba --- /dev/null +++ b/fixtures/test/blockfrost/getTxMetadata-5e96ef1ee339fa6acee8d236a099a50a.json @@ -0,0 +1 @@ +[{"label":"674","cbor_metadata":"\\xa11902a2a1636d736781724d696e737761703a205a6170204f72646572","metadata":"a11902a2a1636d736781724d696e737761703a205a6170204f72646572"}] \ No newline at end of file diff --git a/fixtures/test/blockfrost/getTxMetadata-70f851fe46e3f298d181e360ab69c7ee.json b/fixtures/test/blockfrost/getTxMetadata-70f851fe46e3f298d181e360ab69c7ee.json new file mode 100644 index 0000000000..3b723eb382 --- /dev/null +++ b/fixtures/test/blockfrost/getTxMetadata-70f851fe46e3f298d181e360ab69c7ee.json @@ -0,0 +1 @@ +[{"label":"674","cbor_metadata":"\\xa11902a2a1636d7367826f4c616d696e61722052656c61796572784039653366373635333166346439663539663363646531383536316537653937346437393739303238333433666634643664393434613333306665386265316238","metadata":"a11902a2a1636d7367826f4c616d696e61722052656c61796572784039653366373635333166346439663539663363646531383536316537653937346437393739303238333433666634643664393434613333306665386265316238"}] \ No newline at end of file diff --git a/fixtures/test/blockfrost/getTxMetadata-7855477c5b5ef6f22592621de4059a38.json b/fixtures/test/blockfrost/getTxMetadata-7855477c5b5ef6f22592621de4059a38.json new file mode 100644 index 0000000000..677306acb5 --- /dev/null +++ b/fixtures/test/blockfrost/getTxMetadata-7855477c5b5ef6f22592621de4059a38.json @@ -0,0 +1 @@ +[{"label":"30","cbor_metadata":"\\xa1181e6135","metadata":"a1181e6135"},{"label":"50","cbor_metadata":"\\xa11832784064383739396635383163383930326531636165333337376165623532623537326335343361353161316135616161353434333266353137383565333364386237","metadata":"a11832784064383739396635383163383930326531636165333337376165623532623537326335343361353161316135616161353434333266353137383565333364386237"},{"label":"51","cbor_metadata":"\\xa11833784039643966643837393966643837393966643837393966353831636330333534353963626662616634386334323734373131383031613865333165326634326363","metadata":"a11833784039643966643837393966643837393966643837393966353831636330333534353963626662616634386334323734373131383031613865333165326634326363"},{"label":"52","cbor_metadata":"\\xa11834784038353666613366336433613861306465366266666438373939666438373939666438373939663538316363613565396333623565646163316531396463376139","metadata":"a11834784038353666613366336433613861306465366266666438373939666438373939666438373939663538316363613565396333623565646163316531396463376139"},{"label":"53","cbor_metadata":"\\xa11835784035623438363035626334663738376431626330303035326333393637623766356334666666666666666661313430643837393966303061313430316130303866","metadata":"a11835784035623438363035626334663738376431626330303035326333393637623766356334666666666666666661313430643837393966303061313430316130303866"},{"label":"54","cbor_metadata":"\\xa11836784036656330666666666438373939666438373939666438373939663538316337306536306633623565613731353365306163633761383033653434303164343462","metadata":"a11836784036656330666666666438373939666438373939666438373939663538316337306536306633623565613731353365306163633761383033653434303164343462"},{"label":"55","cbor_metadata":"\\xa11837784038656431626165316337626161616431613632613732666664383739396664383739396664383739396635383163316537386161653763393063633336643632","metadata":"a11837784038656431626165316337626161616431613632613732666664383739396664383739396664383739396635383163316537386161653763393063633336643632"},{"label":"56","cbor_metadata":"\\xa11838784034663762336262366438366235323639366463383465343930663334336562613839303035666666666666666666613134306438373939663030613134303161","metadata":"a11838784034663762336262366438366235323639366463383465343930663334336562613839303035666666666666666666613134306438373939663030613134303161"},{"label":"57","cbor_metadata":"\\xa11839784030303163616663306666666664383739396664383739396664383739396635383163383930326531636165333337376165623532623537326335343361353161","metadata":"a11839784030303163616663306666666664383739396664383739396664383739396635383163383930326531636165333337376165623532623537326335343361353161"},{"label":"58","cbor_metadata":"\\xa1183a784031613561616135343433326635313738356533336438623739646666643837393966643837393966643837393966353831636237383835653134306564633238","metadata":"a1183a784031613561616135343433326635313738356533336438623739646666643837393966643837393966643837393966353831636237383835653134306564633238"},{"label":"59","cbor_metadata":"\\xa1183b784038633232666638373165303965313032633936313736363965373531663734643962666238353862623766666666666666666131343064383739396630306131","metadata":"a1183b784038633232666638373165303965313032633936313736363965373531663734643962666238353862623766666666666666666131343064383739396630306131"},{"label":"60","cbor_metadata":"\\xa1183c7534303161303465653335303066666666666666662c","metadata":"a1183c7534303161303465653335303066666666666666662c"}] \ No newline at end of file diff --git a/fixtures/test/blockfrost/getTxMetadata-7d9eb3d1f1771785b008f992169a9e55.json b/fixtures/test/blockfrost/getTxMetadata-7d9eb3d1f1771785b008f992169a9e55.json new file mode 100644 index 0000000000..1039558ba2 --- /dev/null +++ b/fixtures/test/blockfrost/getTxMetadata-7d9eb3d1f1771785b008f992169a9e55.json @@ -0,0 +1 @@ +[{"label":"30","cbor_metadata":"\\xa1181e6135","metadata":"a1181e6135"},{"label":"50","cbor_metadata":"\\xa11832784064383739396635383163636136323533643630386436396630393538626532653431613831353731373463613234663035326336313561666239613964373863","metadata":"a11832784064383739396635383163636136323533643630386436396630393538626532653431613831353731373463613234663035326336313561666239613964373863"},{"label":"51","cbor_metadata":"\\xa11833784034613966643837393966643837393966643837393966353831636537656563633932666563393361633666336535623364643130373465393932633534336134","metadata":"a11833784034613966643837393966643837393966643837393966353831636537656563633932666563393361633666336535623364643130373465393932633534336134"},{"label":"52","cbor_metadata":"\\xa11834784036376539316637646433306131383839363166666438373939666438373939666438373939663538316339626234653931313461353265663066653434396232","metadata":"a11834784036376539316637646433306131383839363166666438373939666438373939666438373939663538316339626234653931313461353265663066653434396232"},{"label":"53","cbor_metadata":"\\xa11835784062333238383166643264656431633063373165666439343630306339613661656565666666666666666661313430643837393966303061313430316130303732","metadata":"a11835784062333238383166643264656431633063373165666439343630306339613661656565666666666666666661313430643837393966303061313430316130303732"},{"label":"54","cbor_metadata":"\\xa11836784037306530666666666438373939666438373939666438373939663538316337306536306633623565613731353365306163633761383033653434303164343462","metadata":"a11836784037306530666666666438373939666438373939666438373939663538316337306536306633623565613731353365306163633761383033653434303164343462"},{"label":"55","cbor_metadata":"\\xa11837784038656431626165316337626161616431613632613732666664383739396664383739396664383739396635383163316537386161653763393063633336643632","metadata":"a11837784038656431626165316337626161616431613632613732666664383739396664383739396664383739396635383163316537386161653763393063633336643632"},{"label":"56","cbor_metadata":"\\xa11838784034663762336262366438366235323639366463383465343930663334336562613839303035666666666666666666613134306438373939663030613134303161","metadata":"a11838784034663762336262366438366235323639366463383465343930663334336562613839303035666666666666666666613134306438373939663030613134303161"},{"label":"57","cbor_metadata":"\\xa11839784030303136653336306666666664383739396664383739396664383739396635383163636136323533643630386436396630393538626532653431613831353731","metadata":"a11839784030303136653336306666666664383739396664383739396664383739396635383163636136323533643630386436396630393538626532653431613831353731"},{"label":"58","cbor_metadata":"\\xa1183a784037346361323466303532633631356166623961396437386334616666643837393966643837393966643837393966353831633739373961366139636131353234","metadata":"a1183a784037346361323466303532633631356166623961396437386334616666643837393966643837393966643837393966353831633739373961366139636131353234"},{"label":"59","cbor_metadata":"\\xa1183b784037643333616661663363663862653838336637313038383038383933643737373164393735613832396566666666666666666131353831633466356237326564","metadata":"a1183b784037643333616661663363663862653838336637313038383038383933643737373164393735613832396566666666666666666131353831633466356237326564"},{"label":"60","cbor_metadata":"\\xa1183c784066353337356230653033663464393239363164343632383836366336623261666165343339663234626630303436333564383739396630306131346234643639","metadata":"a1183c784066353337356230653033663464393239363164343632383836366336623261666165343339663234626630303436333564383739396630306131346234643639"},{"label":"61","cbor_metadata":"\\xa1183d781d366336623434363136663333333333393339303166666666666666662c","metadata":"a1183d781d366336623434363136663333333333393339303166666666666666662c"},{"label":"63","cbor_metadata":"\\xa1183f782a71713066756e707532616779666d6e717836687878386a3564796c79356c337665646b3639662c2c3030","metadata":"a1183f782a71713066756e707532616779666d6e717836687878386a3564796c79356c337665646b3639662c2c3030"}] \ No newline at end of file diff --git a/fixtures/test/blockfrost/getTxMetadata-85651cfb9d127afad9e9189900e0e5aa.json b/fixtures/test/blockfrost/getTxMetadata-85651cfb9d127afad9e9189900e0e5aa.json new file mode 100644 index 0000000000..eb74fdbd81 --- /dev/null +++ b/fixtures/test/blockfrost/getTxMetadata-85651cfb9d127afad9e9189900e0e5aa.json @@ -0,0 +1 @@ +[{"label":"30","cbor_metadata":"\\xa1181e6135","metadata":"a1181e6135"},{"label":"50","cbor_metadata":"\\xa11832784064383739396635383163633832393631313634373331316530646461663237643162646339613561326634376538336336623033623738343465313063303131","metadata":"a11832784064383739396635383163633832393631313634373331316530646461663237643162646339613561326634376538336336623033623738343465313063303131"},{"label":"51","cbor_metadata":"\\xa11833784031333966643837393966643837393966643837393966353831636130383964653535336162626363376231666630316334663531373665623539616365373864","metadata":"a11833784031333966643837393966643837393966643837393966353831636130383964653535336162626363376231666630316334663531373665623539616365373864"},{"label":"52","cbor_metadata":"\\xa11834784065663537383163346539346534663734386666666438373939666438373939666438373939663538316333396638616161333838316138333065646433326562","metadata":"a11834784065663537383163346539346534663734386666666438373939666438373939666438373939663538316333396638616161333838316138333065646433326562"},{"label":"53","cbor_metadata":"\\xa11835784038616434356533363933313664303466393730636239313361653837626533396366666666666666666661313430643837393966303061313430316132303266","metadata":"a11835784038616434356533363933313664303466393730636239313361653837626533396366666666666666666661313430643837393966303061313430316132303266"},{"label":"54","cbor_metadata":"\\xa11836784062663030666666666438373939666438373939666438373939663538316337306536306633623565613731353365306163633761383033653434303164343462","metadata":"a11836784062663030666666666438373939666438373939666438373939663538316337306536306633623565613731353365306163633761383033653434303164343462"},{"label":"55","cbor_metadata":"\\xa11837784038656431626165316337626161616431613632613732666664383739396664383739396664383739396635383163316537386161653763393063633336643632","metadata":"a11837784038656431626165316337626161616431613632613732666664383739396664383739396664383739396635383163316537386161653763393063633336643632"},{"label":"56","cbor_metadata":"\\xa11838784034663762336262366438366235323639366463383465343930663334336562613839303035666666666666666666613134306438373939663030613134303161","metadata":"a11838784034663762336262366438366235323639366463383465343930663334336562613839303035666666666666666666613134306438373939663030613134303161"},{"label":"57","cbor_metadata":"\\xa11839784030636466653630306666666664383739396664383739396664383739396635383163633832393631313634373331316530646461663237643162646339613561","metadata":"a11839784030636466653630306666666664383739396664383739396664383739396635383163633832393631313634373331316530646461663237643162646339613561"},{"label":"58","cbor_metadata":"\\xa1183a784032663437653833633662303362373834346531306330313131336666643837393966643837393966643837393966353831636533306138313766383834633538","metadata":"a1183a784032663437653833633662303362373834346531306330313131336666643837393966643837393966643837393966353831636533306138313766383834633538"},{"label":"59","cbor_metadata":"\\xa1183b784066653565313530643962313165616636333031393330356466613435643433323032396466363361303366666666666666666131343064383739396630306131","metadata":"a1183b784066653565313530643962313165616636333031393330356466613435643433323032396466363361303366666666666666666131343064383739396630306131"},{"label":"60","cbor_metadata":"\\xa1183c781d343031623030303030303032353661623437303066666666666666662c","metadata":"a1183c781d343031623030303030303032353661623437303066666666666666662c"}] \ No newline at end of file diff --git a/fixtures/test/blockfrost/getTxMetadata-8acb1a1fb6dbe876f677989a8ea43e50.json b/fixtures/test/blockfrost/getTxMetadata-8acb1a1fb6dbe876f677989a8ea43e50.json new file mode 100644 index 0000000000..573d5cd53f --- /dev/null +++ b/fixtures/test/blockfrost/getTxMetadata-8acb1a1fb6dbe876f677989a8ea43e50.json @@ -0,0 +1 @@ +[{"label":"30","cbor_metadata":"\\xa1181e6135","metadata":"a1181e6135"},{"label":"50","cbor_metadata":"\\xa11832784064383739396635383163323534656536316237336665326332313235346363363063363232336531363636303865306535333263643265353739646233303839","metadata":"a11832784064383739396635383163323534656536316237336665326332313235346363363063363232336531363636303865306535333263643265353739646233303839"},{"label":"51","cbor_metadata":"\\xa11833784065623966643837393966643837393966643837393966353831633735363633616661346562626531393065323932636436386432363866666334626637353961","metadata":"a11833784065623966643837393966643837393966643837393966353831633735363633616661346562626531393065323932636436386432363866666334626637353961"},{"label":"52","cbor_metadata":"\\xa11834784062626565336331303439323962363738313266666438373939666438373939666438373939663538316364633162623239376133366239356337323933313732","metadata":"a11834784062626565336331303439323962363738313266666438373939666438373939666438373939663538316364633162623239376133366239356337323933313732"},{"label":"53","cbor_metadata":"\\xa11835784064363533363663333530393461623461663535653862616331383561316439356336666666666666666661313430643837393966303061313430316130303461","metadata":"a11835784064363533363663333530393461623461663535653862616331383561316439356336666666666666666661313430643837393966303061313430316130303461"},{"label":"54","cbor_metadata":"\\xa11836784063346130666666666438373939666438373939666438373939663538316337306536306633623565613731353365306163633761383033653434303164343462","metadata":"a11836784063346130666666666438373939666438373939666438373939663538316337306536306633623565613731353365306163633761383033653434303164343462"},{"label":"55","cbor_metadata":"\\xa11837784038656431626165316337626161616431613632613732666664383739396664383739396664383739396635383163316537386161653763393063633336643632","metadata":"a11837784038656431626165316337626161616431613632613732666664383739396664383739396664383739396635383163316537386161653763393063633336643632"},{"label":"56","cbor_metadata":"\\xa11838784034663762336262366438366235323639366463383465343930663334336562613839303035666666666666666666613134306438373939663030613134303161","metadata":"a11838784034663762336262366438366235323639366463383465343930663334336562613839303035666666666666666666613134306438373939663030613134303161"},{"label":"57","cbor_metadata":"\\xa11839784030303164653834306666666664383739396664383739396664383739396635383163323534656536316237336665326332313235346363363063363232336531","metadata":"a11839784030303164653834306666666664383739396664383739396664383739396635383163323534656536316237336665326332313235346363363063363232336531"},{"label":"58","cbor_metadata":"\\xa1183a784036363630386530653533326364326535373964623330383965626666643837393966643837393966643837393966353831633364323130633232646234323632","metadata":"a1183a784036363630386530653533326364326535373964623330383965626666643837393966643837393966643837393966353831633364323130633232646234323632"},{"label":"59","cbor_metadata":"\\xa1183b784063376231373838393238626132316231326366323037633565636235363733366264396534393737303866666666666666666131343064383739396630306131","metadata":"a1183b784063376231373838393238626132316231326366323037633565636235363733366264396534393737303866666666666666666131343064383739396630306131"},{"label":"60","cbor_metadata":"\\xa1183c7534303161303536656166613066666666666666662c","metadata":"a1183c7534303161303536656166613066666666666666662c"}] \ No newline at end of file diff --git a/fixtures/test/blockfrost/getTxMetadata-9ec42e4096428bef20a6e30e089fa290.json b/fixtures/test/blockfrost/getTxMetadata-9ec42e4096428bef20a6e30e089fa290.json new file mode 100644 index 0000000000..cd5e88fc38 --- /dev/null +++ b/fixtures/test/blockfrost/getTxMetadata-9ec42e4096428bef20a6e30e089fa290.json @@ -0,0 +1 @@ +[{"label":"30","cbor_metadata":"\\xa1181e6135","metadata":"a1181e6135"},{"label":"50","cbor_metadata":"\\xa11832784064383739396635383163346263653835396265363036383231623563393631356639646631346463663964303139613461326166613230373135653266323662","metadata":"a11832784064383739396635383163346263653835396265363036383231623563393631356639646631346463663964303139613461326166613230373135653266323662"},{"label":"51","cbor_metadata":"\\xa11833784037373966643837393966643837393966643837393966353831633734316538656436663135366531366534366265383661343034376631616235633532323165","metadata":"a11833784037373966643837393966643837393966643837393966353831633734316538656436663135366531366534366265383661343034376631616235633532323165"},{"label":"52","cbor_metadata":"\\xa11834784037393161633033303563313466323237353266666438373939666438373939666438373939663538316364326537313936343330313462653361643265386437","metadata":"a11834784037393161633033303563313466323237353266666438373939666438373939666438373939663538316364326537313936343330313462653361643265386437"},{"label":"53","cbor_metadata":"\\xa11835784064643464366632323236303966646133363765306330623461656665373338333332666666666666666661313430643837393966303061313430316130303431","metadata":"a11835784064643464366632323236303966646133363765306330623461656665373338333332666666666666666661313430643837393966303061313430316130303431"},{"label":"54","cbor_metadata":"\\xa11836784034656330666666666438373939666438373939666438373939663538316337306536306633623565613731353365306163633761383033653434303164343462","metadata":"a11836784034656330666666666438373939666438373939666438373939663538316337306536306633623565613731353365306163633761383033653434303164343462"},{"label":"55","cbor_metadata":"\\xa11837784038656431626165316337626161616431613632613732666664383739396664383739396664383739396635383163316537386161653763393063633336643632","metadata":"a11837784038656431626165316337626161616431613632613732666664383739396664383739396664383739396635383163316537386161653763393063633336643632"},{"label":"56","cbor_metadata":"\\xa11838784034663762336262366438366235323639366463383465343930663334336562613839303035666666666666666666613134306438373939663030613134303161","metadata":"a11838784034663762336262366438366235323639366463383465343930663334336562613839303035666666666666666666613134306438373939663030613134303161"},{"label":"57","cbor_metadata":"\\xa11839784030303230613736306666666664383739396664383739396664383739396635383163346263653835396265363036383231623563393631356639646631346463","metadata":"a11839784030303230613736306666666664383739396664383739396664383739396635383163346263653835396265363036383231623563393631356639646631346463"},{"label":"58","cbor_metadata":"\\xa1183a784066396430313961346132616661323037313565326632366237376666643837393966643837393966643837393966353831633935653865636466363165316637","metadata":"a1183a784066396430313961346132616661323037313565326632366237376666643837393966643837393966643837393966353831633935653865636466363165316637"},{"label":"59","cbor_metadata":"\\xa1183b784037386663613537393337386234356330663238613161643338323730353032343030633965646234333166666666666666666131343064383739396630306131","metadata":"a1183b784037386663613537393337386234356330663238613161643338323730353032343030633965646234333166666666666666666131343064383739396630306131"},{"label":"60","cbor_metadata":"\\xa1183c7534303161303566656261613066666666666666662c","metadata":"a1183c7534303161303566656261613066666666666666662c"}] \ No newline at end of file diff --git a/fixtures/test/blockfrost/getTxMetadata-a41c8fcc791f757d7ee7b8edf67089c7.json b/fixtures/test/blockfrost/getTxMetadata-a41c8fcc791f757d7ee7b8edf67089c7.json new file mode 100644 index 0000000000..0519567a7b --- /dev/null +++ b/fixtures/test/blockfrost/getTxMetadata-a41c8fcc791f757d7ee7b8edf67089c7.json @@ -0,0 +1 @@ +[{"label":"674","cbor_metadata":"\\xa11902a2a1636d73678178244d696e537761703a2053776170205265717565737420766961204d7565736c6953776170","metadata":"a11902a2a1636d73678178244d696e537761703a2053776170205265717565737420766961204d7565736c6953776170"}] \ No newline at end of file diff --git a/fixtures/test/blockfrost/getTxMetadata-afa0730bb6c5188054571c420609b6d1.json b/fixtures/test/blockfrost/getTxMetadata-afa0730bb6c5188054571c420609b6d1.json new file mode 100644 index 0000000000..402771135d --- /dev/null +++ b/fixtures/test/blockfrost/getTxMetadata-afa0730bb6c5188054571c420609b6d1.json @@ -0,0 +1 @@ +[{"label":"674","cbor_metadata":"\\xa11902a2a1636d736785784033323339333236353330333033333330326433343332333936353264333433303332333432643632363533373330326433303332333436343633333433333330784033363335363333383763333137633631363436343732333137313339373036333737333336363665373133373636333636633730376133323637333536623636784037353634333737333638373736353739373637373661363536373635373036623730363633353330373536313662373736653736366337353634366336613637784037393635333036623737333637393637333836613731373133323732366137313737333237373761333933323634363433343736373637383336333237343735781c33303663373033343332333636313733333437613665373637363336","metadata":"a11902a2a1636d736785784033323339333236353330333033333330326433343332333936353264333433303332333432643632363533373330326433303332333436343633333433333330784033363335363333383763333137633631363436343732333137313339373036333737333336363665373133373636333636633730376133323637333536623636784037353634333737333638373736353739373637373661363536373635373036623730363633353330373536313662373736653736366337353634366336613637784037393635333036623737333637393637333836613731373133323732366137313737333237373761333933323634363433343736373637383336333237343735781c33303663373033343332333636313733333437613665373637363336"}] \ No newline at end of file diff --git a/fixtures/test/blockfrost/getTxMetadata-b35620f81cd2aeeb63383bf4842b6ca7.json b/fixtures/test/blockfrost/getTxMetadata-b35620f81cd2aeeb63383bf4842b6ca7.json new file mode 100644 index 0000000000..13466a7487 --- /dev/null +++ b/fixtures/test/blockfrost/getTxMetadata-b35620f81cd2aeeb63383bf4842b6ca7.json @@ -0,0 +1 @@ +[{"label":"721","cbor_metadata":"\\xa11902d1a278383733336136646663363063613639396261616236346336353836663464633138653263613733343232363730333439666361396235346339a174537061636550756773476c617373504334393730ab646e616d65781b5370616365205075677320476c617373202d20504320233439373065696d6167657835697066733a2f2f516d516f4d61554e3239554278776154515373566b48783748324d57627365794e6d4c78386f745a7a5167395a34696d656469615479706569696d6167652f6769666b6465736372697074696f6e606566696c657381a3646e616d6574537061636550756773476c617373504334393730696d656469615479706569766964656f2f6d7034637372637835697066733a2f2f516d57646b7231634b42345065764739784a4b76536e71336d33354a5478726771673158725742475062456f62696a4261636b67726f756e646b507572706c652046656c7463546f706e517565656e204f6620436c75627366426f74746f6d754a61636b204f662048656172747320426f74746f6d6644657369676e75323920284d616420446f672043617220436c756229664578747261737157696e73746f6e20436875726368696c6c684c69676874696e676c4e6f726d616c204c696768746776657273696f6e63312e30","metadata":"a11902d1a278383733336136646663363063613639396261616236346336353836663464633138653263613733343232363730333439666361396235346339a174537061636550756773476c617373504334393730ab646e616d65781b5370616365205075677320476c617373202d20504320233439373065696d6167657835697066733a2f2f516d516f4d61554e3239554278776154515373566b48783748324d57627365794e6d4c78386f745a7a5167395a34696d656469615479706569696d6167652f6769666b6465736372697074696f6e606566696c657381a3646e616d6574537061636550756773476c617373504334393730696d656469615479706569766964656f2f6d7034637372637835697066733a2f2f516d57646b7231634b42345065764739784a4b76536e71336d33354a5478726771673158725742475062456f62696a4261636b67726f756e646b507572706c652046656c7463546f706e517565656e204f6620436c75627366426f74746f6d754a61636b204f662048656172747320426f74746f6d6644657369676e75323920284d616420446f672043617220436c756229664578747261737157696e73746f6e20436875726368696c6c684c69676874696e676c4e6f726d616c204c696768746776657273696f6e63312e30"}] \ No newline at end of file diff --git a/fixtures/test/blockfrost/getTxMetadata-b79202b44212de279780aebb4d1cfa4b.json b/fixtures/test/blockfrost/getTxMetadata-b79202b44212de279780aebb4d1cfa4b.json new file mode 100644 index 0000000000..46415204d7 --- /dev/null +++ b/fixtures/test/blockfrost/getTxMetadata-b79202b44212de279780aebb4d1cfa4b.json @@ -0,0 +1 @@ +[{"label":"0","cbor_metadata":"\\xa100581c6cd63b84b9c5093dc00e2814d4200cfdc6f95c3f322a18de1ebfdaf9","metadata":"a100581c6cd63b84b9c5093dc00e2814d4200cfdc6f95c3f322a18de1ebfdaf9"}] \ No newline at end of file diff --git a/fixtures/test/blockfrost/getTxMetadata-cbd4c5d5e8bd4ee7b19c7eb389d8b998.json b/fixtures/test/blockfrost/getTxMetadata-cbd4c5d5e8bd4ee7b19c7eb389d8b998.json new file mode 100644 index 0000000000..c682aa5319 --- /dev/null +++ b/fixtures/test/blockfrost/getTxMetadata-cbd4c5d5e8bd4ee7b19c7eb389d8b998.json @@ -0,0 +1 @@ +[{"label":"30","cbor_metadata":"\\xa1181e6135","metadata":"a1181e6135"},{"label":"50","cbor_metadata":"\\xa11832784064383739396635383163653838393932336166313161356337313861383164656331386361363136393530626562366565613365313232643330393663366161","metadata":"a11832784064383739396635383163653838393932336166313161356337313861383164656331386361363136393530626562366565613365313232643330393663366161"},{"label":"51","cbor_metadata":"\\xa11833784066363966643837393966643837393966643837393966353831633665666363653630613339306531636361353231663464323466343538663433383963613064","metadata":"a11833784066363966643837393966643837393966643837393966353831633665666363653630613339306531636361353231663464323466343538663433383963613064"},{"label":"52","cbor_metadata":"\\xa11834784064373661353365623832646665333463663866666438373939666438373939666438373939663538316337613831626535326165396161646665613166333438","metadata":"a11834784064373661353365623832646665333463663866666438373939666438373939666438373939663538316337613831626535326165396161646665613166333438"},{"label":"53","cbor_metadata":"\\xa11835784031623666383961373336396232306263376265343361623135373032633563326664666666666666666661313430643837393966303061313430316130303066","metadata":"a11835784031623666383961373336396232306263376265343361623135373032633563326664666666666666666661313430643837393966303061313430316130303066"},{"label":"54","cbor_metadata":"\\xa11836784031623330666666666438373939666438373939666438373939663538316337306536306633623565613731353365306163633761383033653434303164343462","metadata":"a11836784031623330666666666438373939666438373939666438373939663538316337306536306633623565613731353365306163633761383033653434303164343462"},{"label":"55","cbor_metadata":"\\xa11837784038656431626165316337626161616431613632613732666664383739396664383739396664383739396635383163316537386161653763393063633336643632","metadata":"a11837784038656431626165316337626161616431613632613732666664383739396664383739396664383739396635383163316537386161653763393063633336643632"},{"label":"56","cbor_metadata":"\\xa11838784034663762336262366438366235323639366463383465343930663334336562613839303035666666666666666666613134306438373939663030613134303161","metadata":"a11838784034663762336262366438366235323639366463383465343930663334336562613839303035666666666666666666613134306438373939663030613134303161"},{"label":"57","cbor_metadata":"\\xa11839784030303066316233306666666664383739396664383739396664383739396635383163653838393932336166313161356337313861383164656331386361363136","metadata":"a11839784030303066316233306666666664383739396664383739396664383739396635383163653838393932336166313161356337313861383164656331386361363136"},{"label":"58","cbor_metadata":"\\xa1183a784039353062656236656561336531323264333039366336616166366666643837393966643837393966643837393966353831633534656465643731653132643332","metadata":"a1183a784039353062656236656561336531323264333039366336616166366666643837393966643837393966643837393966353831633534656465643731653132643332"},{"label":"59","cbor_metadata":"\\xa1183b784031343135613661356433613039636231623239306465396537643036343231666433313965653935653166666666666666666131343064383739396630306131","metadata":"a1183b784031343135613661356433613039636231623239306465396537643036343231666433313965653935653166666666666666666131343064383739396630306131"},{"label":"60","cbor_metadata":"\\xa1183c7534303161303063366162363066666666666666662c","metadata":"a1183c7534303161303063366162363066666666666666662c"}] \ No newline at end of file diff --git a/fixtures/test/blockfrost/getTxMetadata-ce90b4f9049c1d73965810525879b038.json b/fixtures/test/blockfrost/getTxMetadata-ce90b4f9049c1d73965810525879b038.json new file mode 100644 index 0000000000..d59a3168f4 --- /dev/null +++ b/fixtures/test/blockfrost/getTxMetadata-ce90b4f9049c1d73965810525879b038.json @@ -0,0 +1 @@ +[{"label":"30","cbor_metadata":"\\xa1181e6135","metadata":"a1181e6135"},{"label":"50","cbor_metadata":"\\xa11832784064383739396635383163303963323330353736653564366330363261306661393565646166623462373736306266343863393536396339343932393439393362","metadata":"a11832784064383739396635383163303963323330353736653564366330363261306661393565646166623462373736306266343863393536396339343932393439393362"},{"label":"51","cbor_metadata":"\\xa11833784065663966643837393966643837393966643837393966353831633362383639393531353961306166616637646561393662613836343532313939333361306230","metadata":"a11833784065663966643837393966643837393966643837393966353831633362383639393531353961306166616637646561393662613836343532313939333361306230"},{"label":"52","cbor_metadata":"\\xa11834784062663239356137623561643032303331343366666438373939666438373939666438373939663538316365343361353432346432313030343739616138326166","metadata":"a11834784062663239356137623561643032303331343366666438373939666438373939666438373939663538316365343361353432346432313030343739616138326166"},{"label":"53","cbor_metadata":"\\xa11835784066313034383464626332393432323432626432323864623366356465363963303639666666666666666661313430643837393966303061313430316130303533","metadata":"a11835784066313034383464626332393432323432626432323864623366356465363963303639666666666666666661313430643837393966303061313430316130303533"},{"label":"54","cbor_metadata":"\\xa11836784065633630666666666438373939666438373939666438373939663538316337306536306633623565613731353365306163633761383033653434303164343462","metadata":"a11836784065633630666666666438373939666438373939666438373939663538316337306536306633623565613731353365306163633761383033653434303164343462"},{"label":"55","cbor_metadata":"\\xa11837784038656431626165316337626161616431613632613732666664383739396664383739396664383739396635383163316537386161653763393063633336643632","metadata":"a11837784038656431626165316337626161616431613632613732666664383739396664383739396664383739396635383163316537386161653763393063633336643632"},{"label":"56","cbor_metadata":"\\xa11838784034663762336262366438366235323639366463383465343930663334336562613839303035666666666666666666613134306438373939663030613134303161","metadata":"a11838784034663762336262366438366235323639366463383465343930663334336562613839303035666666666666666666613134306438373939663030613134303161"},{"label":"57","cbor_metadata":"\\xa11839784030303130633865306666666664383739396664383739396664383739396635383163303963323330353736653564366330363261306661393565646166623462","metadata":"a11839784030303130633865306666666664383739396664383739396664383739396635383163303963323330353736653564366330363261306661393565646166623462"},{"label":"58","cbor_metadata":"\\xa1183a784037373630626634386339353639633934393239343939336265666666643837393966643837393966643837393966353831636463666663363534653566383737","metadata":"a1183a784037373630626634386339353639633934393239343939336265666666643837393966643837393966643837393966353831636463666663363534653566383737"},{"label":"59","cbor_metadata":"\\xa1183b784039336538383735643663623430636663386461323261656565636437623632646332366530333764663566666666666666666131343064383739396630306131","metadata":"a1183b784039336538383735643663623430636663386461323261656565636437623632646332366530333764663566666666666666666131343064383739396630306131"},{"label":"60","cbor_metadata":"\\xa1183c7534303161303265323836383066666666666666662c","metadata":"a1183c7534303161303265323836383066666666666666662c"}] \ No newline at end of file diff --git a/fixtures/test/blockfrost/getTxMetadata-d0dc1df3b35e53b71b46ecc3b644f071.json b/fixtures/test/blockfrost/getTxMetadata-d0dc1df3b35e53b71b46ecc3b644f071.json new file mode 100644 index 0000000000..7f6ea2814e --- /dev/null +++ b/fixtures/test/blockfrost/getTxMetadata-d0dc1df3b35e53b71b46ecc3b644f071.json @@ -0,0 +1 @@ +[{"label":"721","cbor_metadata":"\\xa11902d1a278383132666237643934313338343531643333303430333338623566396164326663323632326364373061633237306531366234313332326131a16434353739a76b6465736372697074696f6e783553746172746572204372696220666f72206c616e64206f776e657273206f6e2043617264616e6f2049736c616e642043207a6f6e656269641911e365696d6167657835697066733a2f2f516d644e444875765731527a45616b623873654c4843673864725a6d4b6b346f6548644668475579354869536270646e616d65781f43617264616e6f2043726962202d2041637265202d2043434c5443343537396473697a65654c61726765657468656d656743617264616e6f64747970657541637265202d2053756d6d6974205468656d652043656e6f6e63657036356339613438303530303464343966","metadata":"a11902d1a278383132666237643934313338343531643333303430333338623566396164326663323632326364373061633237306531366234313332326131a16434353739a76b6465736372697074696f6e783553746172746572204372696220666f72206c616e64206f776e657273206f6e2043617264616e6f2049736c616e642043207a6f6e656269641911e365696d6167657835697066733a2f2f516d644e444875765731527a45616b623873654c4843673864725a6d4b6b346f6548644668475579354869536270646e616d65781f43617264616e6f2043726962202d2041637265202d2043434c5443343537396473697a65654c61726765657468656d656743617264616e6f64747970657541637265202d2053756d6d6974205468656d652043656e6f6e63657036356339613438303530303464343966"}] \ No newline at end of file diff --git a/fixtures/test/blockfrost/getTxMetadata-dcd34c370d57577ad751d256ba468dc9.json b/fixtures/test/blockfrost/getTxMetadata-dcd34c370d57577ad751d256ba468dc9.json new file mode 100644 index 0000000000..14b755f2bd --- /dev/null +++ b/fixtures/test/blockfrost/getTxMetadata-dcd34c370d57577ad751d256ba468dc9.json @@ -0,0 +1 @@ +[{"label":"30","cbor_metadata":"\\xa1181e6135","metadata":"a1181e6135"},{"label":"50","cbor_metadata":"\\xa11832784064383739396635383163616136613136653839333630346438326634313335353264653632373965356461353030363730383931303562613062313035636530","metadata":"a11832784064383739396635383163616136613136653839333630346438326634313335353264653632373965356461353030363730383931303562613062313035636530"},{"label":"51","cbor_metadata":"\\xa11833784032303966643837393966643837393966643837393966353831633031613234316461643536326431386338353938313464336466383536343435336331343034","metadata":"a11833784032303966643837393966643837393966643837393966353831633031613234316461643536326431386338353938313464336466383536343435336331343034"},{"label":"52","cbor_metadata":"\\xa11834784064653334653337346263303637383239346666666438373939666438373939666438373939663538316339653664353134663432346265326330636264343531","metadata":"a11834784064653334653337346263303637383239346666666438373939666438373939666438373939663538316339653664353134663432346265326330636264343531"},{"label":"53","cbor_metadata":"\\xa11835784030386432336131663036613332626464646361343033373831356639343636666331666666666666666661313430643837393966303061313430316130303236","metadata":"a11835784030386432336131663036613332626464646361343033373831356639343636666331666666666666666661313430643837393966303061313430316130303236"},{"label":"54","cbor_metadata":"\\xa11836784032356130666666666438373939666438373939666438373939663538316337306536306633623565613731353365306163633761383033653434303164343462","metadata":"a11836784032356130666666666438373939666438373939666438373939663538316337306536306633623565613731353365306163633761383033653434303164343462"},{"label":"55","cbor_metadata":"\\xa11837784038656431626165316337626161616431613632613732666664383739396664383739396664383739396635383163316537386161653763393063633336643632","metadata":"a11837784038656431626165316337626161616431613632613732666664383739396664383739396664383739396635383163316537386161653763393063633336643632"},{"label":"56","cbor_metadata":"\\xa11838784034663762336262366438366235323639366463383465343930663334336562613839303035666666666666666666613134306438373939663030613134303161","metadata":"a11838784034663762336262366438366235323639366463383465343930663334336562613839303035666666666666666666613134306438373939663030613134303161"},{"label":"57","cbor_metadata":"\\xa11839784030303066343234306666666664383739396664383739396664383739396635383163616136613136653839333630346438326634313335353264653632373965","metadata":"a11839784030303066343234306666666664383739396664383739396664383739396635383163616136613136653839333630346438326634313335353264653632373965"},{"label":"58","cbor_metadata":"\\xa1183a784035646135303036373038393130356261306231303563653032306666643837393966643837393966643837393966353831633164633130363236333465383136","metadata":"a1183a784035646135303036373038393130356261306231303563653032306666643837393966643837393966643837393966353831633164633130363236333465383136"},{"label":"59","cbor_metadata":"\\xa1183b784063336534303962373964353937653434306138323665303463613036333263636263633263343233363166666666666666666131343064383739396630306131","metadata":"a1183b784063336534303962373964353937653434306138323665303463613036333263636263633263343233363166666666666666666131343064383739396630306131"},{"label":"60","cbor_metadata":"\\xa1183c7534303161303263353838613066666666666666662c","metadata":"a1183c7534303161303263353838613066666666666666662c"}] \ No newline at end of file diff --git a/fixtures/test/blockfrost/getTxMetadata-ea7ba474ed55636ee60f5425587e971d.json b/fixtures/test/blockfrost/getTxMetadata-ea7ba474ed55636ee60f5425587e971d.json new file mode 100644 index 0000000000..d2c6766990 --- /dev/null +++ b/fixtures/test/blockfrost/getTxMetadata-ea7ba474ed55636ee60f5425587e971d.json @@ -0,0 +1 @@ +[{"label":"721","cbor_metadata":"\\xa11902d1a278383130643731353263353837633234643539656365316563353636643238653536343761323464333239393261353063376632343763366536a16b6b616e6976657273653233a86a436f6c6c656374696f6e6b4b616e697665727365203266526172697479645261726566547261697473a46a4261636b67726f756e646b4c696d652053686164657364426f64796c5a6f6d62696520477265656e6445796573635265646454797065665a6f6d62696567576562736974657818687474703a2f2f7777772e4b616e6976657273652e6f72676566696c657381a3696d656469615479706569696d6167652f706e67646e616d656e5a6f6d62696520436861726c6573637372637835697066733a2f2f516d623758733843715a63345a636d616259566a754d333336565665424e71643278346b6b776e65766e6539687565696d6167657835697066733a2f2f516d623758733843715a63345a636d616259566a754d333336565665424e71643278346b6b776e65766e65396875696d656469615479706569696d6167652f706e67646e616d65704b616e697665727365202330303032336776657273696f6e63312e30","metadata":"a11902d1a278383130643731353263353837633234643539656365316563353636643238653536343761323464333239393261353063376632343763366536a16b6b616e6976657273653233a86a436f6c6c656374696f6e6b4b616e697665727365203266526172697479645261726566547261697473a46a4261636b67726f756e646b4c696d652053686164657364426f64796c5a6f6d62696520477265656e6445796573635265646454797065665a6f6d62696567576562736974657818687474703a2f2f7777772e4b616e6976657273652e6f72676566696c657381a3696d656469615479706569696d6167652f706e67646e616d656e5a6f6d62696520436861726c6573637372637835697066733a2f2f516d623758733843715a63345a636d616259566a754d333336565665424e71643278346b6b776e65766e6539687565696d6167657835697066733a2f2f516d623758733843715a63345a636d616259566a754d333336565665424e71643278346b6b776e65766e65396875696d656469615479706569696d6167652f706e67646e616d65704b616e697665727365202330303032336776657273696f6e63312e30"}] \ No newline at end of file diff --git a/src/Internal/QueryM/Kupo.purs b/src/Internal/QueryM/Kupo.purs index 3dd109dcbd..ef9cf5ca5d 100644 --- a/src/Internal/QueryM/Kupo.purs +++ b/src/Internal/QueryM/Kupo.purs @@ -86,9 +86,7 @@ import Ctl.Internal.Types.Transaction ( TransactionHash(TransactionHash) , TransactionInput(TransactionInput) ) -import Ctl.Internal.Types.TransactionMetadata - ( GeneralTransactionMetadata(GeneralTransactionMetadata) - ) +import Ctl.Internal.Types.TransactionMetadata (GeneralTransactionMetadata) import Data.Array (uncons) import Data.Bifunctor (lmap) import Data.BigInt (BigInt) diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index b81cfc0930..bb368779d8 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -1,6 +1,7 @@ module Ctl.Internal.Service.Blockfrost ( isTxConfirmed , getTxMetadata + , BlockfrostMetadata ) where import Prelude diff --git a/test/Blockfrost/Aeson.purs b/test/Blockfrost/Aeson.purs new file mode 100644 index 0000000000..ec17827a9b --- /dev/null +++ b/test/Blockfrost/Aeson.purs @@ -0,0 +1,99 @@ +module Test.Ctl.Blockfrost.Aeson + ( main + , suite + ) where + +import Prelude + +import Aeson (class DecodeAeson, Aeson, printJsonDecodeError) +import Aeson as Aeson +import Control.Monad.Error.Class (liftEither) +import Control.Monad.Trans.Class (lift) +import Control.Parallel (parTraverse) +import Ctl.Internal.Service.Blockfrost as B +import Ctl.Internal.Test.TestPlanM (TestPlanM, interpret) +import Data.Array (catMaybes, groupAllBy, nubBy) +import Data.Array.NonEmpty (NonEmptyArray, head, length, tail) +import Data.Bifunctor (bimap, lmap) +import Data.Either (hush) +import Data.Maybe (Maybe(Just, Nothing)) +import Data.String.Regex (match, regex) +import Data.String.Regex.Flags (noFlags) +import Data.Traversable (for_) +import Data.Tuple.Nested (type (/\), (/\)) +import Effect (Effect) +import Effect.Aff (Aff, error, launchAff_) +import Effect.Class (liftEffect) +import Effect.Exception (throw) +import Mote (group, test) +import Node.Encoding (Encoding(UTF8)) +import Node.FS.Aff (readTextFile, readdir) +import Node.Path (FilePath, basename, concat) +import Type.Proxy (Proxy(Proxy)) + +type Query = String + +readdir' :: FilePath -> Aff (Array FilePath) +readdir' fp = (map <<< map) (\fn -> concat [ fp, fn ]) (readdir fp) + +applyTuple + :: forall (a :: Type) (b :: Type) (c :: Type) + . (a -> b) /\ (a -> c) + -> a + -> b /\ c +applyTuple (f /\ g) a = f a /\ g a + +loadFixtures + :: Aff (Array (Query /\ NonEmptyArray { aeson :: Aeson, bn :: String })) +loadFixtures = do + let + path = concat [ "fixtures", "test", "blockfrost" ] + pattern = hush $ regex "^([a-zA-Z]+)-[0-9a-fA-F]+\\.json$" noFlags + + files <- do + ourFixtures <- readdir' path + catMaybes <$> flip parTraverse ourFixtures \fp -> do + let bn = basename fp + contents <- readTextFile UTF8 fp + aeson <- liftEither $ lmap + (error <<< ((bn <> "\n ") <> _) <<< printJsonDecodeError) + (Aeson.parseJsonStringToAeson contents) + pure case pattern >>= flip match bn >>> map tail of + Just [ Just query ] -> Just + { query + , bn + , aeson + } + _ -> Nothing + + let + groupedFiles = + map (applyTuple $ _.query <<< head /\ map \{ aeson, bn } -> { aeson, bn }) + $ groupAllBy (comparing _.query) + $ nubBy (comparing _.bn) files + + pure groupedFiles + +suite :: TestPlanM (Aff Unit) Unit +suite = group "Blockfrost Aeson tests" do + groupedFiles <- lift loadFixtures + + for_ groupedFiles \(query /\ files') -> + test (query <> " (" <> show (length files') <> ")") + $ + for_ files' \{ aeson, bn } -> do + let + handle :: forall (a :: Type). DecodeAeson a => Proxy a -> Aff Unit + handle _ = liftEither $ bimap + ( error <<< ((bn <> "\n ") <> _) <<< + printJsonDecodeError + ) + (const unit) + (Aeson.decodeAeson aeson :: _ a) + case query of + "getTxMetadata" -> handle (Proxy :: _ B.BlockfrostMetadata) + _ -> liftEffect $ throw $ "Unknown case " <> bn + +main :: Effect Unit +main = launchAff_ do + interpret suite diff --git a/test/Unit.purs b/test/Unit.purs index f6c54e9841..e26c771e16 100644 --- a/test/Unit.purs +++ b/test/Unit.purs @@ -13,6 +13,7 @@ import Effect.Class (liftEffect) import Mote.Monad (mapTest) import Test.Ctl.ApplyArgs as ApplyArgs import Test.Ctl.Base64 as Base64 +import Test.Ctl.Blockfrost.Aeson as Blockfrost.Aeson import Test.Ctl.ByteArray as ByteArray import Test.Ctl.Data as Data import Test.Ctl.Data.Interval as Ctl.Data.Interval @@ -78,6 +79,7 @@ testPlan = do Ogmios.Address.suite Ogmios.Aeson.suite Ogmios.EvaluateTx.suite + Blockfrost.Aeson.suite ProtocolParams.suite Types.TokenName.suite Types.Transaction.suite From ad205a15fdd2eea3157689f9da8a1f03f88e95c3 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Thu, 29 Dec 2022 14:18:24 +0100 Subject: [PATCH 199/373] Framework for implementing Blockfrost queries, Refactor ServerConfig --- src/Contract/Config.purs | 7 +- src/Internal/Contract/QueryBackend.purs | 4 +- src/Internal/Plutip/Types.purs | 2 +- src/Internal/QueryM.purs | 9 +- src/Internal/QueryM/Kupo.purs | 2 +- src/Internal/{QueryM => }/ServerConfig.purs | 29 ++++++- src/Internal/Service/Blockfrost.purs | 95 +++++++++++++++++++++ src/Internal/Service/Error.purs | 75 ++++++++++++++++ src/Internal/Service/Helpers.purs | 56 ++++++++++++ test/Ogmios/GenerateFixtures.purs | 2 +- 10 files changed, 268 insertions(+), 13 deletions(-) rename src/Internal/{QueryM => }/ServerConfig.purs (59%) create mode 100644 src/Internal/Service/Blockfrost.purs create mode 100644 src/Internal/Service/Error.purs create mode 100644 src/Internal/Service/Helpers.purs diff --git a/src/Contract/Config.purs b/src/Contract/Config.purs index ba28ac42ed..17250eeefe 100644 --- a/src/Contract/Config.purs +++ b/src/Contract/Config.purs @@ -20,7 +20,7 @@ module Contract.Config , module Data.Log.Level , module Data.Log.Message , module Ctl.Internal.Deserialization.Keys - , module Ctl.Internal.QueryM.ServerConfig + , module Ctl.Internal.ServerConfig , module Ctl.Internal.Wallet.Spec , module Ctl.Internal.Wallet.Key , module X @@ -38,9 +38,12 @@ import Ctl.Internal.Contract.QueryBackend , mkCtlBackendParams ) import Ctl.Internal.Deserialization.Keys (privateKeyFromBytes) -import Ctl.Internal.QueryM.ServerConfig +import Ctl.Internal.ServerConfig ( Host , ServerConfig + , blockfrostPublicMainnetServerConfig + , blockfrostPublicPreprodServerConfig + , blockfrostPublicPreviewServerConfig , defaultKupoServerConfig , defaultOgmiosWsConfig ) diff --git a/src/Internal/Contract/QueryBackend.purs b/src/Internal/Contract/QueryBackend.purs index bba4f219a3..963de6b574 100644 --- a/src/Internal/Contract/QueryBackend.purs +++ b/src/Internal/Contract/QueryBackend.purs @@ -14,7 +14,7 @@ module Ctl.Internal.Contract.QueryBackend import Prelude import Ctl.Internal.QueryM (OgmiosWebSocket) -import Ctl.Internal.QueryM.ServerConfig (ServerConfig) +import Ctl.Internal.ServerConfig (ServerConfig) import Data.Maybe (Maybe(Just, Nothing)) -------------------------------------------------------------------------------- @@ -35,6 +35,7 @@ type CtlBackend = type BlockfrostBackend = { blockfrostConfig :: ServerConfig + , blockfrostApiKey :: Maybe String } getCtlBackend :: QueryBackend -> Maybe CtlBackend @@ -60,6 +61,7 @@ type CtlBackendParams = type BlockfrostBackendParams = { blockfrostConfig :: ServerConfig + , blockfrostApiKey :: Maybe String } mkCtlBackendParams :: CtlBackendParams -> QueryBackendParams diff --git a/src/Internal/Plutip/Types.purs b/src/Internal/Plutip/Types.purs index cd4d15e592..b82868f101 100644 --- a/src/Internal/Plutip/Types.purs +++ b/src/Internal/Plutip/Types.purs @@ -36,8 +36,8 @@ import Aeson ) import Ctl.Internal.Contract.Hooks (Hooks) import Ctl.Internal.Deserialization.Keys (privateKeyFromBytes) -import Ctl.Internal.QueryM.ServerConfig (ServerConfig) import Ctl.Internal.Serialization.Types (PrivateKey) +import Ctl.Internal.ServerConfig (ServerConfig) import Ctl.Internal.Types.ByteArray (hexToByteArray) import Ctl.Internal.Types.RawBytes (RawBytes(RawBytes)) import Ctl.Internal.Wallet.Key (PrivateStakeKey) diff --git a/src/Internal/QueryM.purs b/src/Internal/QueryM.purs index f701c67292..8dde470f61 100644 --- a/src/Internal/QueryM.purs +++ b/src/Internal/QueryM.purs @@ -126,7 +126,8 @@ import Ctl.Internal.QueryM.Ogmios , aesonObject ) import Ctl.Internal.QueryM.Ogmios as Ogmios -import Ctl.Internal.QueryM.ServerConfig +import Ctl.Internal.QueryM.UniqueId (ListenerId) +import Ctl.Internal.ServerConfig ( Host , ServerConfig , defaultOgmiosWsConfig @@ -134,11 +135,7 @@ import Ctl.Internal.QueryM.ServerConfig , mkServerUrl , mkWsUrl ) as ExportServerConfig -import Ctl.Internal.QueryM.ServerConfig - ( ServerConfig - , mkWsUrl - ) -import Ctl.Internal.QueryM.UniqueId (ListenerId) +import Ctl.Internal.ServerConfig (ServerConfig, mkWsUrl) import Ctl.Internal.Types.ByteArray (byteArrayToHex) import Ctl.Internal.Types.CborBytes (CborBytes) import Ctl.Internal.Types.Chain as Chain diff --git a/src/Internal/QueryM/Kupo.purs b/src/Internal/QueryM/Kupo.purs index 44c618b0c3..c98dfee433 100644 --- a/src/Internal/QueryM/Kupo.purs +++ b/src/Internal/QueryM/Kupo.purs @@ -56,7 +56,6 @@ import Ctl.Internal.QueryM , QueryM , handleAffjaxResponse ) -import Ctl.Internal.QueryM.ServerConfig (ServerConfig, mkHttpUrl) import Ctl.Internal.Serialization.Address ( Address , Slot @@ -64,6 +63,7 @@ import Ctl.Internal.Serialization.Address , addressFromBech32 ) import Ctl.Internal.Serialization.Hash (ScriptHash, scriptHashToBytes) +import Ctl.Internal.ServerConfig (ServerConfig, mkHttpUrl) import Ctl.Internal.Types.BigNum (toString) as BigNum import Ctl.Internal.Types.ByteArray (ByteArray, byteArrayToHex, hexToByteArray) import Ctl.Internal.Types.CborBytes (hexToCborBytes) diff --git a/src/Internal/QueryM/ServerConfig.purs b/src/Internal/ServerConfig.purs similarity index 59% rename from src/Internal/QueryM/ServerConfig.purs rename to src/Internal/ServerConfig.purs index 322f7268de..0be0c767ce 100644 --- a/src/Internal/QueryM/ServerConfig.purs +++ b/src/Internal/ServerConfig.purs @@ -1,6 +1,9 @@ -module Ctl.Internal.QueryM.ServerConfig +module Ctl.Internal.ServerConfig ( Host , ServerConfig + , blockfrostPublicMainnetServerConfig + , blockfrostPublicPreprodServerConfig + , blockfrostPublicPreviewServerConfig , defaultKupoServerConfig , defaultOgmiosWsConfig , mkHttpUrl @@ -41,6 +44,30 @@ defaultKupoServerConfig = , path: Just "kupo" } +blockfrostPublicPreviewServerConfig :: ServerConfig +blockfrostPublicPreviewServerConfig = + { port: UInt.fromInt 443 + , host: "cardano-preview.blockfrost.io" + , secure: true + , path: Just "/api/v0" + } + +blockfrostPublicPreprodServerConfig :: ServerConfig +blockfrostPublicPreprodServerConfig = + { port: UInt.fromInt 443 + , host: "cardano-preprod.blockfrost.io" + , secure: true + , path: Just "/api/v0" + } + +blockfrostPublicMainnetServerConfig :: ServerConfig +blockfrostPublicMainnetServerConfig = + { port: UInt.fromInt 443 + , host: "cardano-mainnet.blockfrost.io" + , secure: true + , path: Just "/api/v0" + } + mkHttpUrl :: ServerConfig -> Url mkHttpUrl = mkServerUrl "http" diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs new file mode 100644 index 0000000000..6ece0164ed --- /dev/null +++ b/src/Internal/Service/Blockfrost.purs @@ -0,0 +1,95 @@ +module Ctl.Internal.Service.Blockfrost + ( BlockfrostServiceM + , BlockfrostServiceParams + , runBlockfrostServiceM + ) where + +import Prelude + +import Aeson (class DecodeAeson, decodeAeson, parseJsonStringToAeson) +import Affjax (Error, Response, URL, defaultRequest, request) as Affjax +import Affjax.RequestHeader (RequestHeader(RequestHeader)) as Affjax +import Affjax.ResponseFormat (string) as Affjax.ResponseFormat +import Affjax.StatusCode (StatusCode(StatusCode)) as Affjax +import Control.Monad.Reader.Class (ask) +import Control.Monad.Reader.Trans (ReaderT, runReaderT) +import Ctl.Internal.Contract.QueryBackend (BlockfrostBackend) +import Ctl.Internal.ServerConfig (ServerConfig, mkHttpUrl) +import Ctl.Internal.Service.Error + ( ClientError(ClientHttpError, ClientHttpResponseError, ClientDecodeJsonError) + , ServiceError(ServiceBlockfrostError) + ) +import Data.Bifunctor (lmap) +import Data.Either (Either(Left, Right)) +import Data.HTTP.Method (Method(GET)) +import Data.Maybe (Maybe, maybe) +import Effect.Aff (Aff) +import Effect.Aff.Class (liftAff) +import Undefined (undefined) + +-------------------------------------------------------------------------------- +-- BlockfrostServiceM +-------------------------------------------------------------------------------- + +type BlockfrostServiceParams = + { blockfrostConfig :: ServerConfig + , blockfrostApiKey :: Maybe String + } + +type BlockfrostServiceM (a :: Type) = ReaderT BlockfrostServiceParams Aff a + +runBlockfrostServiceM + :: forall (a :: Type). BlockfrostBackend -> BlockfrostServiceM a -> Aff a +runBlockfrostServiceM backend = flip runReaderT serviceParams + where + serviceParams :: BlockfrostServiceParams + serviceParams = + { blockfrostConfig: backend.blockfrostConfig + , blockfrostApiKey: backend.blockfrostApiKey + } + +-------------------------------------------------------------------------------- +-- Making requests to Blockfrost endpoints +-------------------------------------------------------------------------------- + +data BlockfrostEndpoint + +realizeEndpoint :: BlockfrostEndpoint -> Affjax.URL +realizeEndpoint endpoint = + case endpoint of + _ -> undefined + +blockfrostGetRequest + :: BlockfrostEndpoint + -> BlockfrostServiceM (Either Affjax.Error (Affjax.Response String)) +blockfrostGetRequest endpoint = ask >>= \params -> liftAff do + Affjax.request $ Affjax.defaultRequest + { method = Left GET + , url = mkHttpUrl params.blockfrostConfig <> realizeEndpoint endpoint + , responseFormat = Affjax.ResponseFormat.string + , headers = + maybe mempty (\apiKey -> [ Affjax.RequestHeader "project_id" apiKey ]) + params.blockfrostApiKey + } + +-------------------------------------------------------------------------------- +-- Blockfrost response handling +-------------------------------------------------------------------------------- + +handleBlockfrostResponse + :: forall (result :: Type) + . DecodeAeson result + => Either Affjax.Error (Affjax.Response String) + -> Either ClientError result +handleBlockfrostResponse (Left affjaxError) = + Left (ClientHttpError affjaxError) +handleBlockfrostResponse (Right { status: Affjax.StatusCode statusCode, body }) + | statusCode < 200 || statusCode > 299 = do + blockfrostError <- + body # lmap (ClientDecodeJsonError body) + <<< (decodeAeson <=< parseJsonStringToAeson) + Left $ ClientHttpResponseError (ServiceBlockfrostError blockfrostError) + | otherwise = + body # lmap (ClientDecodeJsonError body) + <<< (decodeAeson <=< parseJsonStringToAeson) + diff --git a/src/Internal/Service/Error.purs b/src/Internal/Service/Error.purs new file mode 100644 index 0000000000..b503956736 --- /dev/null +++ b/src/Internal/Service/Error.purs @@ -0,0 +1,75 @@ +module Ctl.Internal.Service.Error where + +import Prelude + +import Aeson (class DecodeAeson, JsonDecodeError, getField) +import Affjax (Error, printError) as Affjax +import Ctl.Internal.Service.Helpers (aesonObject) +import Data.Generic.Rep (class Generic) +import Data.Newtype (class Newtype) +import Data.Show.Generic (genericShow) + +-------------------------------------------------------------------------------- +-- ClientError +-------------------------------------------------------------------------------- + +data ClientError + = ClientHttpError Affjax.Error + | ClientHttpResponseError ServiceError + | ClientDecodeJsonError String JsonDecodeError + | ClientEncodingError String + | ClientOtherError String + +-- No `Show` instance of `Affjax.Error` +instance Show ClientError where + show (ClientHttpError err) = + "(ClientHttpError " + <> Affjax.printError err + <> ")" + show (ClientHttpResponseError err) = + "(ClientHttpResponseError " + <> show err + <> ")" + show (ClientDecodeJsonError jsonStr err) = + "(ClientDecodeJsonError (" <> show jsonStr <> ") " + <> show err + <> ")" + show (ClientEncodingError err) = + "(ClientEncodingError " + <> err + <> ")" + show (ClientOtherError err) = + "(ClientOtherError " + <> err + <> ")" + +-------------------------------------------------------------------------------- +-- ServiceError +-------------------------------------------------------------------------------- + +data ServiceError + = ServiceBlockfrostError BlockfrostError + | ServiceOtherError String + +derive instance Generic ServiceError _ + +instance Show ServiceError where + show = genericShow + +newtype BlockfrostError = BlockfrostError + { statusCode :: Int + , error :: String + , message :: String + } + +derive instance Generic BlockfrostError _ + +instance Show BlockfrostError where + show = genericShow + +instance DecodeAeson BlockfrostError where + decodeAeson = aesonObject \obj -> do + statusCode <- getField obj "status_code" + error <- getField obj "error" + message <- getField obj "message" + pure $ BlockfrostError { statusCode, error, message } diff --git a/src/Internal/Service/Helpers.purs b/src/Internal/Service/Helpers.purs new file mode 100644 index 0000000000..8cbac75c5e --- /dev/null +++ b/src/Internal/Service/Helpers.purs @@ -0,0 +1,56 @@ +module Ctl.Internal.Service.Helpers + ( aesonArray + , aesonObject + , decodeAssetClass + ) where + +import Prelude + +import Aeson + ( Aeson + , JsonDecodeError(TypeMismatch) + , caseAesonArray + , caseAesonObject + ) +import Control.Apply (lift2) +import Ctl.Internal.Cardano.Types.Value (CurrencySymbol, mkCurrencySymbol) +import Ctl.Internal.Types.ByteArray (hexToByteArray) +import Ctl.Internal.Types.TokenName (TokenName, mkTokenName) +import Data.Either (Either(Left), note) +import Data.Tuple (Tuple(Tuple)) +import Data.Tuple.Nested (type (/\)) +import Foreign.Object (Object) + +aesonArray + :: forall (a :: Type) + . (Array Aeson -> Either JsonDecodeError a) + -> Aeson + -> Either JsonDecodeError a +aesonArray = caseAesonArray (Left (TypeMismatch "Array")) + +aesonObject + :: forall (a :: Type) + . (Object Aeson -> Either JsonDecodeError a) + -> Aeson + -> Either JsonDecodeError a +aesonObject = caseAesonObject (Left (TypeMismatch "Object")) + +decodeAssetClass + :: String + -> String + -> String + -> Either JsonDecodeError (CurrencySymbol /\ TokenName) +decodeAssetClass assetString csString tnString = + lift2 Tuple + ( note (assetStringTypeMismatch "CurrencySymbol" csString) + (mkCurrencySymbol =<< hexToByteArray csString) + ) + ( note (assetStringTypeMismatch "TokenName" tnString) + (mkTokenName =<< hexToByteArray tnString) + ) + where + assetStringTypeMismatch :: String -> String -> JsonDecodeError + assetStringTypeMismatch t actual = + TypeMismatch $ + ("In " <> assetString <> ": Expected hex-encoded " <> t) + <> (", got: " <> actual) diff --git a/test/Ogmios/GenerateFixtures.purs b/test/Ogmios/GenerateFixtures.purs index 0b9fa4f4c7..7fa8b2812a 100644 --- a/test/Ogmios/GenerateFixtures.purs +++ b/test/Ogmios/GenerateFixtures.purs @@ -27,7 +27,7 @@ import Ctl.Internal.QueryM ) import Ctl.Internal.QueryM.JsonWsp (JsonWspCall) import Ctl.Internal.QueryM.Ogmios (mkOgmiosCallType) -import Ctl.Internal.QueryM.ServerConfig (ServerConfig, mkWsUrl) +import Ctl.Internal.ServerConfig (ServerConfig, mkWsUrl) import Data.Either (Either(Left, Right)) import Data.Log.Level (LogLevel(Trace, Debug)) import Data.Map as Map From e3aaf726b10bea222cbec40e42a06eeef9d559ea Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Thu, 29 Dec 2022 15:36:05 +0100 Subject: [PATCH 200/373] Remove QueryM.ClientError, Export errors in Contract.ClientError --- src/Contract/ClientError.purs | 16 +++++++++ src/Contract/Scripts.purs | 10 +----- src/Contract/Transaction.purs | 10 ------ src/Internal/Contract/QueryHandle.purs | 11 ++---- src/Internal/Plutip/Server.purs | 4 ++- src/Internal/QueryM.purs | 48 ++++---------------------- src/Internal/QueryM/Kupo.purs | 7 ++-- src/Internal/Service/Error.purs | 16 ++++++++- 8 files changed, 46 insertions(+), 76 deletions(-) create mode 100644 src/Contract/ClientError.purs diff --git a/src/Contract/ClientError.purs b/src/Contract/ClientError.purs new file mode 100644 index 0000000000..cbac2a82e2 --- /dev/null +++ b/src/Contract/ClientError.purs @@ -0,0 +1,16 @@ +module Contract.ClientError (module X) where + +import Ctl.Internal.Service.Error + ( BlockfrostError(BlockfrostError) + , ClientError + ( ClientHttpError + , ClientHttpResponseError + , ClientDecodeJsonError + , ClientEncodingError + , ClientOtherError + ) + , ServiceError + ( ServiceBlockfrostError + , ServiceOtherError + ) + ) as X diff --git a/src/Contract/Scripts.purs b/src/Contract/Scripts.purs index 050320622f..d9f5686fce 100644 --- a/src/Contract/Scripts.purs +++ b/src/Contract/Scripts.purs @@ -4,7 +4,6 @@ module Contract.Scripts ( getScriptByHash , getScriptsByHashes - , module ExportQueryM , module ExportScripts , module Hash , module NativeScript @@ -31,14 +30,6 @@ import Ctl.Internal.Cardano.Types.NativeScript import Ctl.Internal.Cardano.Types.ScriptRef (ScriptRef) import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.NativeScripts (NativeScriptHash(NativeScriptHash)) as X -import Ctl.Internal.QueryM (ClientError) -import Ctl.Internal.QueryM - ( ClientError - ( ClientHttpError - , ClientDecodeJsonError - , ClientEncodingError - ) - ) as ExportQueryM import Ctl.Internal.Scripts ( mintingPolicyHash , nativeScriptStakeValidatorHash @@ -47,6 +38,7 @@ import Ctl.Internal.Scripts ) as ExportScripts import Ctl.Internal.Serialization.Hash (ScriptHash) import Ctl.Internal.Serialization.Hash (ScriptHash) as Hash +import Ctl.Internal.Service.Error (ClientError) import Ctl.Internal.Types.Scripts ( MintingPolicy(PlutusMintingPolicy, NativeMintingPolicy) , MintingPolicyHash(MintingPolicyHash) diff --git a/src/Contract/Transaction.purs b/src/Contract/Transaction.purs index b95b08b62a..2c47bf9e68 100644 --- a/src/Contract/Transaction.purs +++ b/src/Contract/Transaction.purs @@ -15,7 +15,6 @@ module Contract.Transaction , createAdditionalUtxos , getTxFinalFee , module BalanceTxError - , module ExportQueryM , module FinalizedTransaction , module NativeScript , module OutputDatum @@ -173,15 +172,6 @@ import Ctl.Internal.Plutus.Types.TransactionUnspentOutput , mkTxUnspentOut ) as PTransactionUnspentOutput import Ctl.Internal.Plutus.Types.Value (Coin) -import Ctl.Internal.QueryM - ( ClientError - ( ClientHttpError - , ClientHttpResponseError - , ClientDecodeJsonError - , ClientEncodingError - , ClientOtherError - ) - ) as ExportQueryM import Ctl.Internal.ReindexRedeemers ( ReindexErrors(CannotGetTxOutRefIndexForRedeemer) ) as ReindexRedeemersExport diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs index 800cce67d6..badf2d6860 100644 --- a/src/Internal/Contract/QueryHandle.purs +++ b/src/Internal/Contract/QueryHandle.purs @@ -14,18 +14,14 @@ import Ctl.Internal.Cardano.Types.Transaction , TransactionOutput , UtxoMap ) -import Ctl.Internal.Contract.Monad - ( Contract - , ContractEnv - , runQueryM - ) +import Ctl.Internal.Contract.Monad (Contract, ContractEnv, runQueryM) import Ctl.Internal.Contract.QueryBackend ( BlockfrostBackend , CtlBackend , QueryBackend(BlockfrostBackend, CtlBackend) ) import Ctl.Internal.Hashing (transactionHash) as Hashing -import Ctl.Internal.QueryM (ClientError, QueryM) +import Ctl.Internal.QueryM (QueryM) import Ctl.Internal.QueryM (evaluateTxOgmios, getChainTip, submitTxOgmios) as QueryM import Ctl.Internal.QueryM.CurrentEpoch (getCurrentEpoch) as QueryM import Ctl.Internal.QueryM.EraSummaries (getEraSummaries) as QueryM @@ -46,6 +42,7 @@ import Ctl.Internal.QueryM.Ogmios (SubmitTxR(SubmitTxSuccess), TxEvaluationR) import Ctl.Internal.Serialization (convertTransaction, toBytes) as Serialization import Ctl.Internal.Serialization.Address (Address) import Ctl.Internal.Serialization.Hash (ScriptHash) +import Ctl.Internal.Service.Error (ClientError) import Ctl.Internal.Types.Chain as Chain import Ctl.Internal.Types.Datum (DataHash, Datum) import Ctl.Internal.Types.Transaction (TransactionHash, TransactionInput) @@ -57,8 +54,6 @@ import Effect.Aff (Aff) import Effect.Class (liftEffect) import Undefined (undefined) --- TODO Either move ClientError out of QueryM or make a new error type --- and convert from ClientError. type AffE (a :: Type) = Aff (Either ClientError a) type QueryHandle = diff --git a/src/Internal/Plutip/Server.purs b/src/Internal/Plutip/Server.purs index b6a382d1b2..c4e113d6d8 100644 --- a/src/Internal/Plutip/Server.purs +++ b/src/Internal/Plutip/Server.purs @@ -64,7 +64,9 @@ import Ctl.Internal.Plutip.UtxoDistribution , keyWallets , transferFundsFromEnterpriseToBase ) -import Ctl.Internal.QueryM (ClientError(ClientDecodeJsonError, ClientHttpError)) +import Ctl.Internal.Service.Error + ( ClientError(ClientDecodeJsonError, ClientHttpError) + ) import Ctl.Internal.Test.TestPlanM (TestPlanM) import Ctl.Internal.Types.UsedTxOuts (newUsedTxOuts) import Ctl.Internal.Wallet.Key (PrivatePaymentKey(PrivatePaymentKey)) diff --git a/src/Internal/QueryM.purs b/src/Internal/QueryM.purs index 8dde470f61..d2cde116f8 100644 --- a/src/Internal/QueryM.purs +++ b/src/Internal/QueryM.purs @@ -2,13 +2,6 @@ module Ctl.Internal.QueryM ( module ExportDispatcher , module ExportServerConfig - , ClientError - ( ClientHttpError - , ClientHttpResponseError - , ClientDecodeJsonError - , ClientEncodingError - , ClientOtherError - ) , ClusterSetup , ListenerSet , OgmiosListeners @@ -68,10 +61,7 @@ import Control.Monad.Error.Class ) import Control.Monad.Logger.Class (class MonadLogger) import Control.Monad.Reader.Class (class MonadAsk, class MonadReader) -import Control.Monad.Reader.Trans - ( ReaderT(ReaderT) - , asks - ) +import Control.Monad.Reader.Trans (ReaderT(ReaderT), asks) import Control.Monad.Rec.Class (class MonadRec) import Control.Parallel (class Parallel, parallel, sequential) import Control.Plus (class Plus) @@ -136,6 +126,10 @@ import Ctl.Internal.ServerConfig , mkWsUrl ) as ExportServerConfig import Ctl.Internal.ServerConfig (ServerConfig, mkWsUrl) +import Ctl.Internal.Service.Error + ( ClientError(ClientHttpError, ClientHttpResponseError, ClientDecodeJsonError) + , ServiceError(ServiceOtherError) + ) import Ctl.Internal.Types.ByteArray (byteArrayToHex) import Ctl.Internal.Types.CborBytes (CborBytes) import Ctl.Internal.Types.Chain as Chain @@ -364,36 +358,6 @@ mempoolSnapshotHasTxAff ogmiosWs logger ms = -- Affjax -------------------------------------------------------------------------------- -data ClientError - = ClientHttpError Affjax.Error - | ClientHttpResponseError String - | ClientDecodeJsonError String JsonDecodeError - | ClientEncodingError String - | ClientOtherError String - --- No Show instance of Affjax.Error -instance Show ClientError where - show (ClientHttpError err) = - "(ClientHttpError " - <> Affjax.printError err - <> ")" - show (ClientHttpResponseError err) = - "(ClientHttpResponseError " - <> show err - <> ")" - show (ClientDecodeJsonError jsonStr err) = - "(ClientDecodeJsonError (" <> show jsonStr <> ") " - <> show err - <> ")" - show (ClientEncodingError err) = - "(ClientEncodingError " - <> err - <> ")" - show (ClientOtherError err) = - "(ClientOtherError " - <> err - <> ")" - -- Checks response status code and returns `ClientError` in case of failure, -- otherwise attempts to decode the result. -- @@ -409,7 +373,7 @@ handleAffjaxResponse (Left affjaxError) = handleAffjaxResponse (Right { status: Affjax.StatusCode.StatusCode statusCode, body }) | statusCode < 200 || statusCode > 299 = - Left (ClientHttpResponseError body) + Left $ ClientHttpResponseError (ServiceOtherError body) | otherwise = body # lmap (ClientDecodeJsonError body) <<< (decodeAeson <=< parseJsonStringToAeson) diff --git a/src/Internal/QueryM/Kupo.purs b/src/Internal/QueryM/Kupo.purs index c98dfee433..6e8ab86590 100644 --- a/src/Internal/QueryM/Kupo.purs +++ b/src/Internal/QueryM/Kupo.purs @@ -51,11 +51,7 @@ import Ctl.Internal.Deserialization.PlutusData (deserializeData) import Ctl.Internal.Deserialization.Transaction ( convertGeneralTransactionMetadata ) -import Ctl.Internal.QueryM - ( ClientError(ClientOtherError) - , QueryM - , handleAffjaxResponse - ) +import Ctl.Internal.QueryM (QueryM, handleAffjaxResponse) import Ctl.Internal.Serialization.Address ( Address , Slot @@ -64,6 +60,7 @@ import Ctl.Internal.Serialization.Address ) import Ctl.Internal.Serialization.Hash (ScriptHash, scriptHashToBytes) import Ctl.Internal.ServerConfig (ServerConfig, mkHttpUrl) +import Ctl.Internal.Service.Error (ClientError(ClientOtherError)) import Ctl.Internal.Types.BigNum (toString) as BigNum import Ctl.Internal.Types.ByteArray (ByteArray, byteArrayToHex, hexToByteArray) import Ctl.Internal.Types.CborBytes (hexToCborBytes) diff --git a/src/Internal/Service/Error.purs b/src/Internal/Service/Error.purs index b503956736..23bd9cf578 100644 --- a/src/Internal/Service/Error.purs +++ b/src/Internal/Service/Error.purs @@ -1,4 +1,17 @@ -module Ctl.Internal.Service.Error where +module Ctl.Internal.Service.Error + ( BlockfrostError(BlockfrostError) + , ClientError + ( ClientHttpError + , ClientHttpResponseError + , ClientDecodeJsonError + , ClientEncodingError + , ClientOtherError + ) + , ServiceError + ( ServiceBlockfrostError + , ServiceOtherError + ) + ) where import Prelude @@ -62,6 +75,7 @@ newtype BlockfrostError = BlockfrostError , message :: String } +derive instance Newtype BlockfrostError _ derive instance Generic BlockfrostError _ instance Show BlockfrostError where From 5d5e8488e20a0255f6c56b241554d4f55d6e1439 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Thu, 29 Dec 2022 15:53:30 +0100 Subject: [PATCH 201/373] Add placeholders for Blockfrost query handle --- src/Internal/Contract/QueryHandle.purs | 21 ++++++++++++++++++++- src/Internal/QueryM.purs | 2 +- src/Internal/Service/Blockfrost.purs | 2 +- 3 files changed, 22 insertions(+), 3 deletions(-) diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs index badf2d6860..b742f34328 100644 --- a/src/Internal/Contract/QueryHandle.purs +++ b/src/Internal/Contract/QueryHandle.purs @@ -42,6 +42,10 @@ import Ctl.Internal.QueryM.Ogmios (SubmitTxR(SubmitTxSuccess), TxEvaluationR) import Ctl.Internal.Serialization (convertTransaction, toBytes) as Serialization import Ctl.Internal.Serialization.Address (Address) import Ctl.Internal.Serialization.Hash (ScriptHash) +import Ctl.Internal.Service.Blockfrost + ( BlockfrostServiceM + , runBlockfrostServiceM + ) import Ctl.Internal.Service.Error (ClientError) import Ctl.Internal.Types.Chain as Chain import Ctl.Internal.Types.Datum (DataHash, Datum) @@ -110,5 +114,20 @@ queryHandleForCtlBackend contractEnv backend = queryHandleForBlockfrostBackend :: ContractEnv -> BlockfrostBackend -> QueryHandle -queryHandleForBlockfrostBackend = undefined +queryHandleForBlockfrostBackend _ backend = + { getDatumByHash: runBlockfrostServiceM' <<< undefined + , getScriptByHash: runBlockfrostServiceM' <<< undefined + , getUtxoByOref: runBlockfrostServiceM' <<< undefined + , isTxConfirmed: runBlockfrostServiceM' <<< undefined + , getTxMetadata: runBlockfrostServiceM' <<< undefined + , utxosAt: runBlockfrostServiceM' <<< undefined + , getChainTip: runBlockfrostServiceM' undefined + , getCurrentEpoch: runBlockfrostServiceM' undefined + , submitTx: runBlockfrostServiceM' <<< undefined + , evaluateTx: \tx additionalUtxos -> runBlockfrostServiceM' undefined + , getEraSummaries: runBlockfrostServiceM' undefined + } + where + runBlockfrostServiceM' :: forall (a :: Type). BlockfrostServiceM a -> Aff a + runBlockfrostServiceM' = runBlockfrostServiceM backend diff --git a/src/Internal/QueryM.purs b/src/Internal/QueryM.purs index d2cde116f8..9263216eea 100644 --- a/src/Internal/QueryM.purs +++ b/src/Internal/QueryM.purs @@ -373,7 +373,7 @@ handleAffjaxResponse (Left affjaxError) = handleAffjaxResponse (Right { status: Affjax.StatusCode.StatusCode statusCode, body }) | statusCode < 200 || statusCode > 299 = - Left $ ClientHttpResponseError (ServiceOtherError body) + Left $ ClientHttpResponseError $ ServiceOtherError body | otherwise = body # lmap (ClientDecodeJsonError body) <<< (decodeAeson <=< parseJsonStringToAeson) diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index 6ece0164ed..e3e608c80c 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -88,7 +88,7 @@ handleBlockfrostResponse (Right { status: Affjax.StatusCode statusCode, body }) blockfrostError <- body # lmap (ClientDecodeJsonError body) <<< (decodeAeson <=< parseJsonStringToAeson) - Left $ ClientHttpResponseError (ServiceBlockfrostError blockfrostError) + Left $ ClientHttpResponseError $ ServiceBlockfrostError blockfrostError | otherwise = body # lmap (ClientDecodeJsonError body) <<< (decodeAeson <=< parseJsonStringToAeson) From 268b64ca5e6ba3e7cd62ab9cc8769a3fabbccd75 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Thu, 29 Dec 2022 16:58:23 +0100 Subject: [PATCH 202/373] Handle pagination for Blockfrost utxosAt query --- src/Internal/Service/Blockfrost.purs | 29 ++++++++++++++++++++-------- 1 file changed, 21 insertions(+), 8 deletions(-) diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index 7d17f4e64c..fc75576943 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -57,7 +57,7 @@ import Ctl.Internal.Types.Transaction ( TransactionHash , TransactionInput(TransactionInput) ) -import Data.Array (find) as Array +import Data.Array (find, length) as Array import Data.Bifunctor (lmap) import Data.BigInt (fromString) as BigInt import Data.Either (Either(Left, Right), note) @@ -101,14 +101,17 @@ runBlockfrostServiceM backend = flip runReaderT serviceParams -------------------------------------------------------------------------------- data BlockfrostEndpoint - = GetUtxosAtAddress Address -- /addresses/{address}/utxos - | GetUtxosOfTransaction TransactionHash -- /txs/{hash}/utxos + -- /addresses/{address}/utxos?page={page}&count={count} + = GetUtxosAtAddress Address Int Int + -- /txs/{hash}/utxos + | GetUtxosOfTransaction TransactionHash realizeEndpoint :: BlockfrostEndpoint -> Affjax.URL realizeEndpoint endpoint = case endpoint of - GetUtxosAtAddress address -> - "/addresses/" <> addressBech32 address <> "/utxos" + GetUtxosAtAddress address page count -> + "/addresses/" <> addressBech32 address <> "/utxos?page=" <> show page + <> ("&count=" <> show count) GetUtxosOfTransaction txHash -> "/txs/" <> byteArrayToHex (unwrap txHash) <> "/utxos" @@ -155,9 +158,18 @@ utxosAt -- TODO: resolve `BlockfrostUtxosAtAddress` -- -> BlockfrostServiceM (Either ClientError UtxoMap) -> BlockfrostServiceM (Either ClientError BlockfrostUtxosAtAddress) -utxosAt address = - handleBlockfrostResponse <$> - blockfrostGetRequest (GetUtxosAtAddress address) +utxosAt address = utxosAtAddressOnPage 1 + where + utxosAtAddressOnPage + :: Int -> BlockfrostServiceM (Either ClientError BlockfrostUtxosAtAddress) + utxosAtAddressOnPage page = runExceptT do + -- Maximum number of results per page supported by Blockfrost: + let maxNumResultsOnPage = 100 + utxos <- ExceptT $ handleBlockfrostResponse <$> + blockfrostGetRequest (GetUtxosAtAddress address page maxNumResultsOnPage) + case Array.length (unwrap utxos) < maxNumResultsOnPage of + true -> pure utxos + false -> append utxos <$> ExceptT (utxosAtAddressOnPage $ page + 1) getUtxoByOref :: TransactionInput @@ -181,6 +193,7 @@ newtype BlockfrostUtxosAtAddress = derive instance Generic BlockfrostUtxosAtAddress _ derive instance Newtype BlockfrostUtxosAtAddress _ +derive newtype instance Semigroup BlockfrostUtxosAtAddress instance Show BlockfrostUtxosAtAddress where show = genericShow From ddf8219aa4b28e0e8fdbce468783ff23227ddf27 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Thu, 29 Dec 2022 18:15:07 +0100 Subject: [PATCH 203/373] Apply suggested changes --- src/Internal/QueryM.purs | 2 +- src/Internal/Service/Blockfrost.purs | 29 +++++++++++++++++++++++++--- src/Internal/Service/Error.purs | 12 ++++++++++-- 3 files changed, 37 insertions(+), 6 deletions(-) diff --git a/src/Internal/QueryM.purs b/src/Internal/QueryM.purs index 9263216eea..f6fe322753 100644 --- a/src/Internal/QueryM.purs +++ b/src/Internal/QueryM.purs @@ -373,7 +373,7 @@ handleAffjaxResponse (Left affjaxError) = handleAffjaxResponse (Right { status: Affjax.StatusCode.StatusCode statusCode, body }) | statusCode < 200 || statusCode > 299 = - Left $ ClientHttpResponseError $ ServiceOtherError body + Left $ ClientHttpResponseError (wrap statusCode) $ ServiceOtherError body | otherwise = body # lmap (ClientDecodeJsonError body) <<< (decodeAeson <=< parseJsonStringToAeson) diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index e3e608c80c..65c990840b 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -8,7 +8,8 @@ import Prelude import Aeson (class DecodeAeson, decodeAeson, parseJsonStringToAeson) import Affjax (Error, Response, URL, defaultRequest, request) as Affjax -import Affjax.RequestHeader (RequestHeader(RequestHeader)) as Affjax +import Affjax.RequestBody (RequestBody) as Affjax +import Affjax.RequestHeader (RequestHeader(ContentType, RequestHeader)) as Affjax import Affjax.ResponseFormat (string) as Affjax.ResponseFormat import Affjax.StatusCode (StatusCode(StatusCode)) as Affjax import Control.Monad.Reader.Class (ask) @@ -21,8 +22,10 @@ import Ctl.Internal.Service.Error ) import Data.Bifunctor (lmap) import Data.Either (Either(Left, Right)) -import Data.HTTP.Method (Method(GET)) +import Data.HTTP.Method (Method(GET, POST)) import Data.Maybe (Maybe, maybe) +import Data.MediaType (MediaType) +import Data.Newtype (wrap) import Effect.Aff (Aff) import Effect.Aff.Class (liftAff) import Undefined (undefined) @@ -72,6 +75,25 @@ blockfrostGetRequest endpoint = ask >>= \params -> liftAff do params.blockfrostApiKey } +blockfrostPostRequest + :: BlockfrostEndpoint + -> MediaType + -> Maybe Affjax.RequestBody + -> BlockfrostServiceM (Either Affjax.Error (Affjax.Response String)) +blockfrostPostRequest endpoint mediaType mbContent = + ask >>= \params -> liftAff do + Affjax.request $ Affjax.defaultRequest + { method = Left POST + , url = mkHttpUrl params.blockfrostConfig <> realizeEndpoint endpoint + , content = mbContent + , responseFormat = Affjax.ResponseFormat.string + , headers = + [ Affjax.ContentType mediaType ] <> + maybe mempty + (\apiKey -> [ Affjax.RequestHeader "project_id" apiKey ]) + params.blockfrostApiKey + } + -------------------------------------------------------------------------------- -- Blockfrost response handling -------------------------------------------------------------------------------- @@ -88,7 +110,8 @@ handleBlockfrostResponse (Right { status: Affjax.StatusCode statusCode, body }) blockfrostError <- body # lmap (ClientDecodeJsonError body) <<< (decodeAeson <=< parseJsonStringToAeson) - Left $ ClientHttpResponseError $ ServiceBlockfrostError blockfrostError + Left $ ClientHttpResponseError (wrap statusCode) $ + ServiceBlockfrostError blockfrostError | otherwise = body # lmap (ClientDecodeJsonError body) <<< (decodeAeson <=< parseJsonStringToAeson) diff --git a/src/Internal/Service/Error.purs b/src/Internal/Service/Error.purs index 23bd9cf578..9e1a82f83a 100644 --- a/src/Internal/Service/Error.purs +++ b/src/Internal/Service/Error.purs @@ -17,6 +17,7 @@ import Prelude import Aeson (class DecodeAeson, JsonDecodeError, getField) import Affjax (Error, printError) as Affjax +import Affjax.StatusCode (StatusCode) as Affjax import Ctl.Internal.Service.Helpers (aesonObject) import Data.Generic.Rep (class Generic) import Data.Newtype (class Newtype) @@ -27,10 +28,15 @@ import Data.Show.Generic (genericShow) -------------------------------------------------------------------------------- data ClientError + -- | Affjax error = ClientHttpError Affjax.Error - | ClientHttpResponseError ServiceError + -- | Server responded with HTTP status code outside of 200-299 + | ClientHttpResponseError Affjax.StatusCode ServiceError + -- | Failed to decode the response | ClientDecodeJsonError String JsonDecodeError + -- | Failed to encode the request | ClientEncodingError String + -- | Any other error | ClientOtherError String -- No `Show` instance of `Affjax.Error` @@ -39,8 +45,10 @@ instance Show ClientError where "(ClientHttpError " <> Affjax.printError err <> ")" - show (ClientHttpResponseError err) = + show (ClientHttpResponseError statusCode err) = "(ClientHttpResponseError " + <> show statusCode + <> " " <> show err <> ")" show (ClientDecodeJsonError jsonStr err) = From 02bcbb1e2eaaae4d91b90acba27e2fd6e6c30eb1 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Thu, 29 Dec 2022 20:33:34 +0000 Subject: [PATCH 204/373] Update CHANGELOG.md --- CHANGELOG.md | 2 ++ 1 file changed, 2 insertions(+) diff --git a/CHANGELOG.md b/CHANGELOG.md index 5cff51cae1..bde79f3fbe 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -47,6 +47,8 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) ### Added +- `Contract.Transaction` exports `mkPoolPubKeyHash` and `poolPubKeyHashToBech32` for bech32 roundtripping ([#1360](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1360)) + ### Changed ### Removed From 7dbb337be55d79d724a8606f50560d4724d41ce4 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Thu, 29 Dec 2022 21:26:12 +0000 Subject: [PATCH 205/373] Fix warnings --- src/Internal/Contract/QueryHandle.purs | 3 ++- src/Internal/QueryM.purs | 2 +- src/Internal/Service/Blockfrost.purs | 5 +++++ 3 files changed, 8 insertions(+), 2 deletions(-) diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs index b742f34328..ea6d9d7a26 100644 --- a/src/Internal/Contract/QueryHandle.purs +++ b/src/Internal/Contract/QueryHandle.purs @@ -124,7 +124,8 @@ queryHandleForBlockfrostBackend _ backend = , getChainTip: runBlockfrostServiceM' undefined , getCurrentEpoch: runBlockfrostServiceM' undefined , submitTx: runBlockfrostServiceM' <<< undefined - , evaluateTx: \tx additionalUtxos -> runBlockfrostServiceM' undefined + , evaluateTx: \tx additionalUtxos -> runBlockfrostServiceM' $ undefined tx + additionalUtxos , getEraSummaries: runBlockfrostServiceM' undefined } where diff --git a/src/Internal/QueryM.purs b/src/Internal/QueryM.purs index f6fe322753..b2b26493cd 100644 --- a/src/Internal/QueryM.purs +++ b/src/Internal/QueryM.purs @@ -46,7 +46,7 @@ import Aeson , parseJsonStringToAeson , stringifyAeson ) -import Affjax (Error, Response, defaultRequest, printError, request) as Affjax +import Affjax (Error, Response, defaultRequest, request) as Affjax import Affjax.RequestBody as Affjax.RequestBody import Affjax.RequestHeader as Affjax.RequestHeader import Affjax.ResponseFormat as Affjax.ResponseFormat diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index 65c990840b..0c316c9dbd 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -2,6 +2,7 @@ module Ctl.Internal.Service.Blockfrost ( BlockfrostServiceM , BlockfrostServiceParams , runBlockfrostServiceM + , dummyExport ) where import Prelude @@ -62,6 +63,10 @@ realizeEndpoint endpoint = case endpoint of _ -> undefined +dummyExport :: Unit +dummyExport = undefined blockfrostGetRequest blockfrostPostRequest + (handleBlockfrostResponse undefined :: _ Int) + blockfrostGetRequest :: BlockfrostEndpoint -> BlockfrostServiceM (Either Affjax.Error (Affjax.Response String)) From 14d12ca126e70da8ba111dbf9307cc800ddff652 Mon Sep 17 00:00:00 2001 From: Luis Alberto Diaz Diaz <73986926+Luis-omega@users.noreply.github.com> Date: Fri, 30 Dec 2022 00:31:10 -0600 Subject: [PATCH 206/373] added fixtures and partially getCurrentEpoch --- fixtures/test/blockfrost/getCurrentEpoch.json | 12 + .../blockfrost/getProtocolParameters.json | 380 ++++++++++++++++++ src/Internal/Contract/QueryHandle.purs | 3 +- src/Internal/Service/Blockfrost.purs | 31 +- 4 files changed, 417 insertions(+), 9 deletions(-) create mode 100644 fixtures/test/blockfrost/getCurrentEpoch.json create mode 100644 fixtures/test/blockfrost/getProtocolParameters.json diff --git a/fixtures/test/blockfrost/getCurrentEpoch.json b/fixtures/test/blockfrost/getCurrentEpoch.json new file mode 100644 index 0000000000..1a02aa2ee1 --- /dev/null +++ b/fixtures/test/blockfrost/getCurrentEpoch.json @@ -0,0 +1,12 @@ +{ + "epoch": 66, + "start_time": 1672358400, + "end_time": 1672444800, + "first_block_time": 1672358422, + "last_block_time": 1672381042, + "block_count": 1060, + "tx_count": 3322, + "output": "2324588968586074", + "fees": "857566768", + "active_stake": "390058983450026" +} diff --git a/fixtures/test/blockfrost/getProtocolParameters.json b/fixtures/test/blockfrost/getProtocolParameters.json new file mode 100644 index 0000000000..2043684e9e --- /dev/null +++ b/fixtures/test/blockfrost/getProtocolParameters.json @@ -0,0 +1,380 @@ +{ + "epoch": 66, + "min_fee_a": 44, + "min_fee_b": 155381, + "max_block_size": 90112, + "max_tx_size": 16384, + "max_block_header_size": 1100, + "key_deposit": "2000000", + "pool_deposit": "500000000", + "e_max": 18, + "n_opt": 500, + "a0": 0.3, + "rho": 0.003, + "tau": 0.2, + "decentralisation_param": 0, + "extra_entropy": null, + "protocol_major_ver": 8, + "protocol_minor_ver": 0, + "min_utxo": "4310", + "min_pool_cost": "340000000", + "nonce": "59937440a6f42eda1d705df24c211a486f01c0fbd4700b77431b6922d07c06c2", + "cost_models": { + "PlutusV1": { + "addInteger-cpu-arguments-intercept": 205665, + "addInteger-cpu-arguments-slope": 812, + "addInteger-memory-arguments-intercept": 1, + "addInteger-memory-arguments-slope": 1, + "appendByteString-cpu-arguments-intercept": 1000, + "appendByteString-cpu-arguments-slope": 571, + "appendByteString-memory-arguments-intercept": 0, + "appendByteString-memory-arguments-slope": 1, + "appendString-cpu-arguments-intercept": 1000, + "appendString-cpu-arguments-slope": 24177, + "appendString-memory-arguments-intercept": 4, + "appendString-memory-arguments-slope": 1, + "bData-cpu-arguments": 1000, + "bData-memory-arguments": 32, + "blake2b_256-cpu-arguments-intercept": 117366, + "blake2b_256-cpu-arguments-slope": 10475, + "blake2b_256-memory-arguments": 4, + "cekApplyCost-exBudgetCPU": 23000, + "cekApplyCost-exBudgetMemory": 100, + "cekBuiltinCost-exBudgetCPU": 23000, + "cekBuiltinCost-exBudgetMemory": 100, + "cekConstCost-exBudgetCPU": 23000, + "cekConstCost-exBudgetMemory": 100, + "cekDelayCost-exBudgetCPU": 23000, + "cekDelayCost-exBudgetMemory": 100, + "cekForceCost-exBudgetCPU": 23000, + "cekForceCost-exBudgetMemory": 100, + "cekLamCost-exBudgetCPU": 23000, + "cekLamCost-exBudgetMemory": 100, + "cekStartupCost-exBudgetCPU": 100, + "cekStartupCost-exBudgetMemory": 100, + "cekVarCost-exBudgetCPU": 23000, + "cekVarCost-exBudgetMemory": 100, + "chooseData-cpu-arguments": 19537, + "chooseData-memory-arguments": 32, + "chooseList-cpu-arguments": 175354, + "chooseList-memory-arguments": 32, + "chooseUnit-cpu-arguments": 46417, + "chooseUnit-memory-arguments": 4, + "consByteString-cpu-arguments-intercept": 221973, + "consByteString-cpu-arguments-slope": 511, + "consByteString-memory-arguments-intercept": 0, + "consByteString-memory-arguments-slope": 1, + "constrData-cpu-arguments": 89141, + "constrData-memory-arguments": 32, + "decodeUtf8-cpu-arguments-intercept": 497525, + "decodeUtf8-cpu-arguments-slope": 14068, + "decodeUtf8-memory-arguments-intercept": 4, + "decodeUtf8-memory-arguments-slope": 2, + "divideInteger-cpu-arguments-constant": 196500, + "divideInteger-cpu-arguments-model-arguments-intercept": 453240, + "divideInteger-cpu-arguments-model-arguments-slope": 220, + "divideInteger-memory-arguments-intercept": 0, + "divideInteger-memory-arguments-minimum": 1, + "divideInteger-memory-arguments-slope": 1, + "encodeUtf8-cpu-arguments-intercept": 1000, + "encodeUtf8-cpu-arguments-slope": 28662, + "encodeUtf8-memory-arguments-intercept": 4, + "encodeUtf8-memory-arguments-slope": 2, + "equalsByteString-cpu-arguments-constant": 245000, + "equalsByteString-cpu-arguments-intercept": 216773, + "equalsByteString-cpu-arguments-slope": 62, + "equalsByteString-memory-arguments": 1, + "equalsData-cpu-arguments-intercept": 1060367, + "equalsData-cpu-arguments-slope": 12586, + "equalsData-memory-arguments": 1, + "equalsInteger-cpu-arguments-intercept": 208512, + "equalsInteger-cpu-arguments-slope": 421, + "equalsInteger-memory-arguments": 1, + "equalsString-cpu-arguments-constant": 187000, + "equalsString-cpu-arguments-intercept": 1000, + "equalsString-cpu-arguments-slope": 52998, + "equalsString-memory-arguments": 1, + "fstPair-cpu-arguments": 80436, + "fstPair-memory-arguments": 32, + "headList-cpu-arguments": 43249, + "headList-memory-arguments": 32, + "iData-cpu-arguments": 1000, + "iData-memory-arguments": 32, + "ifThenElse-cpu-arguments": 80556, + "ifThenElse-memory-arguments": 1, + "indexByteString-cpu-arguments": 57667, + "indexByteString-memory-arguments": 4, + "lengthOfByteString-cpu-arguments": 1000, + "lengthOfByteString-memory-arguments": 10, + "lessThanByteString-cpu-arguments-intercept": 197145, + "lessThanByteString-cpu-arguments-slope": 156, + "lessThanByteString-memory-arguments": 1, + "lessThanEqualsByteString-cpu-arguments-intercept": 197145, + "lessThanEqualsByteString-cpu-arguments-slope": 156, + "lessThanEqualsByteString-memory-arguments": 1, + "lessThanEqualsInteger-cpu-arguments-intercept": 204924, + "lessThanEqualsInteger-cpu-arguments-slope": 473, + "lessThanEqualsInteger-memory-arguments": 1, + "lessThanInteger-cpu-arguments-intercept": 208896, + "lessThanInteger-cpu-arguments-slope": 511, + "lessThanInteger-memory-arguments": 1, + "listData-cpu-arguments": 52467, + "listData-memory-arguments": 32, + "mapData-cpu-arguments": 64832, + "mapData-memory-arguments": 32, + "mkCons-cpu-arguments": 65493, + "mkCons-memory-arguments": 32, + "mkNilData-cpu-arguments": 22558, + "mkNilData-memory-arguments": 32, + "mkNilPairData-cpu-arguments": 16563, + "mkNilPairData-memory-arguments": 32, + "mkPairData-cpu-arguments": 76511, + "mkPairData-memory-arguments": 32, + "modInteger-cpu-arguments-constant": 196500, + "modInteger-cpu-arguments-model-arguments-intercept": 453240, + "modInteger-cpu-arguments-model-arguments-slope": 220, + "modInteger-memory-arguments-intercept": 0, + "modInteger-memory-arguments-minimum": 1, + "modInteger-memory-arguments-slope": 1, + "multiplyInteger-cpu-arguments-intercept": 69522, + "multiplyInteger-cpu-arguments-slope": 11687, + "multiplyInteger-memory-arguments-intercept": 0, + "multiplyInteger-memory-arguments-slope": 1, + "nullList-cpu-arguments": 60091, + "nullList-memory-arguments": 32, + "quotientInteger-cpu-arguments-constant": 196500, + "quotientInteger-cpu-arguments-model-arguments-intercept": 453240, + "quotientInteger-cpu-arguments-model-arguments-slope": 220, + "quotientInteger-memory-arguments-intercept": 0, + "quotientInteger-memory-arguments-minimum": 1, + "quotientInteger-memory-arguments-slope": 1, + "remainderInteger-cpu-arguments-constant": 196500, + "remainderInteger-cpu-arguments-model-arguments-intercept": 453240, + "remainderInteger-cpu-arguments-model-arguments-slope": 220, + "remainderInteger-memory-arguments-intercept": 0, + "remainderInteger-memory-arguments-minimum": 1, + "remainderInteger-memory-arguments-slope": 1, + "sha2_256-cpu-arguments-intercept": 806990, + "sha2_256-cpu-arguments-slope": 30482, + "sha2_256-memory-arguments": 4, + "sha3_256-cpu-arguments-intercept": 1927926, + "sha3_256-cpu-arguments-slope": 82523, + "sha3_256-memory-arguments": 4, + "sliceByteString-cpu-arguments-intercept": 265318, + "sliceByteString-cpu-arguments-slope": 0, + "sliceByteString-memory-arguments-intercept": 4, + "sliceByteString-memory-arguments-slope": 0, + "sndPair-cpu-arguments": 85931, + "sndPair-memory-arguments": 32, + "subtractInteger-cpu-arguments-intercept": 205665, + "subtractInteger-cpu-arguments-slope": 812, + "subtractInteger-memory-arguments-intercept": 1, + "subtractInteger-memory-arguments-slope": 1, + "tailList-cpu-arguments": 41182, + "tailList-memory-arguments": 32, + "trace-cpu-arguments": 212342, + "trace-memory-arguments": 32, + "unBData-cpu-arguments": 31220, + "unBData-memory-arguments": 32, + "unConstrData-cpu-arguments": 32696, + "unConstrData-memory-arguments": 32, + "unIData-cpu-arguments": 43357, + "unIData-memory-arguments": 32, + "unListData-cpu-arguments": 32247, + "unListData-memory-arguments": 32, + "unMapData-cpu-arguments": 38314, + "unMapData-memory-arguments": 32, + "verifyEd25519Signature-cpu-arguments-intercept": 9462713, + "verifyEd25519Signature-cpu-arguments-slope": 1021, + "verifyEd25519Signature-memory-arguments": 10 + }, + "PlutusV2": { + "addInteger-cpu-arguments-intercept": 205665, + "addInteger-cpu-arguments-slope": 812, + "addInteger-memory-arguments-intercept": 1, + "addInteger-memory-arguments-slope": 1, + "appendByteString-cpu-arguments-intercept": 1000, + "appendByteString-cpu-arguments-slope": 571, + "appendByteString-memory-arguments-intercept": 0, + "appendByteString-memory-arguments-slope": 1, + "appendString-cpu-arguments-intercept": 1000, + "appendString-cpu-arguments-slope": 24177, + "appendString-memory-arguments-intercept": 4, + "appendString-memory-arguments-slope": 1, + "bData-cpu-arguments": 1000, + "bData-memory-arguments": 32, + "blake2b_256-cpu-arguments-intercept": 117366, + "blake2b_256-cpu-arguments-slope": 10475, + "blake2b_256-memory-arguments": 4, + "cekApplyCost-exBudgetCPU": 23000, + "cekApplyCost-exBudgetMemory": 100, + "cekBuiltinCost-exBudgetCPU": 23000, + "cekBuiltinCost-exBudgetMemory": 100, + "cekConstCost-exBudgetCPU": 23000, + "cekConstCost-exBudgetMemory": 100, + "cekDelayCost-exBudgetCPU": 23000, + "cekDelayCost-exBudgetMemory": 100, + "cekForceCost-exBudgetCPU": 23000, + "cekForceCost-exBudgetMemory": 100, + "cekLamCost-exBudgetCPU": 23000, + "cekLamCost-exBudgetMemory": 100, + "cekStartupCost-exBudgetCPU": 100, + "cekStartupCost-exBudgetMemory": 100, + "cekVarCost-exBudgetCPU": 23000, + "cekVarCost-exBudgetMemory": 100, + "chooseData-cpu-arguments": 19537, + "chooseData-memory-arguments": 32, + "chooseList-cpu-arguments": 175354, + "chooseList-memory-arguments": 32, + "chooseUnit-cpu-arguments": 46417, + "chooseUnit-memory-arguments": 4, + "consByteString-cpu-arguments-intercept": 221973, + "consByteString-cpu-arguments-slope": 511, + "consByteString-memory-arguments-intercept": 0, + "consByteString-memory-arguments-slope": 1, + "constrData-cpu-arguments": 89141, + "constrData-memory-arguments": 32, + "decodeUtf8-cpu-arguments-intercept": 497525, + "decodeUtf8-cpu-arguments-slope": 14068, + "decodeUtf8-memory-arguments-intercept": 4, + "decodeUtf8-memory-arguments-slope": 2, + "divideInteger-cpu-arguments-constant": 196500, + "divideInteger-cpu-arguments-model-arguments-intercept": 453240, + "divideInteger-cpu-arguments-model-arguments-slope": 220, + "divideInteger-memory-arguments-intercept": 0, + "divideInteger-memory-arguments-minimum": 1, + "divideInteger-memory-arguments-slope": 1, + "encodeUtf8-cpu-arguments-intercept": 1000, + "encodeUtf8-cpu-arguments-slope": 28662, + "encodeUtf8-memory-arguments-intercept": 4, + "encodeUtf8-memory-arguments-slope": 2, + "equalsByteString-cpu-arguments-constant": 245000, + "equalsByteString-cpu-arguments-intercept": 216773, + "equalsByteString-cpu-arguments-slope": 62, + "equalsByteString-memory-arguments": 1, + "equalsData-cpu-arguments-intercept": 1060367, + "equalsData-cpu-arguments-slope": 12586, + "equalsData-memory-arguments": 1, + "equalsInteger-cpu-arguments-intercept": 208512, + "equalsInteger-cpu-arguments-slope": 421, + "equalsInteger-memory-arguments": 1, + "equalsString-cpu-arguments-constant": 187000, + "equalsString-cpu-arguments-intercept": 1000, + "equalsString-cpu-arguments-slope": 52998, + "equalsString-memory-arguments": 1, + "fstPair-cpu-arguments": 80436, + "fstPair-memory-arguments": 32, + "headList-cpu-arguments": 43249, + "headList-memory-arguments": 32, + "iData-cpu-arguments": 1000, + "iData-memory-arguments": 32, + "ifThenElse-cpu-arguments": 80556, + "ifThenElse-memory-arguments": 1, + "indexByteString-cpu-arguments": 57667, + "indexByteString-memory-arguments": 4, + "lengthOfByteString-cpu-arguments": 1000, + "lengthOfByteString-memory-arguments": 10, + "lessThanByteString-cpu-arguments-intercept": 197145, + "lessThanByteString-cpu-arguments-slope": 156, + "lessThanByteString-memory-arguments": 1, + "lessThanEqualsByteString-cpu-arguments-intercept": 197145, + "lessThanEqualsByteString-cpu-arguments-slope": 156, + "lessThanEqualsByteString-memory-arguments": 1, + "lessThanEqualsInteger-cpu-arguments-intercept": 204924, + "lessThanEqualsInteger-cpu-arguments-slope": 473, + "lessThanEqualsInteger-memory-arguments": 1, + "lessThanInteger-cpu-arguments-intercept": 208896, + "lessThanInteger-cpu-arguments-slope": 511, + "lessThanInteger-memory-arguments": 1, + "listData-cpu-arguments": 52467, + "listData-memory-arguments": 32, + "mapData-cpu-arguments": 64832, + "mapData-memory-arguments": 32, + "mkCons-cpu-arguments": 65493, + "mkCons-memory-arguments": 32, + "mkNilData-cpu-arguments": 22558, + "mkNilData-memory-arguments": 32, + "mkNilPairData-cpu-arguments": 16563, + "mkNilPairData-memory-arguments": 32, + "mkPairData-cpu-arguments": 76511, + "mkPairData-memory-arguments": 32, + "modInteger-cpu-arguments-constant": 196500, + "modInteger-cpu-arguments-model-arguments-intercept": 453240, + "modInteger-cpu-arguments-model-arguments-slope": 220, + "modInteger-memory-arguments-intercept": 0, + "modInteger-memory-arguments-minimum": 1, + "modInteger-memory-arguments-slope": 1, + "multiplyInteger-cpu-arguments-intercept": 69522, + "multiplyInteger-cpu-arguments-slope": 11687, + "multiplyInteger-memory-arguments-intercept": 0, + "multiplyInteger-memory-arguments-slope": 1, + "nullList-cpu-arguments": 60091, + "nullList-memory-arguments": 32, + "quotientInteger-cpu-arguments-constant": 196500, + "quotientInteger-cpu-arguments-model-arguments-intercept": 453240, + "quotientInteger-cpu-arguments-model-arguments-slope": 220, + "quotientInteger-memory-arguments-intercept": 0, + "quotientInteger-memory-arguments-minimum": 1, + "quotientInteger-memory-arguments-slope": 1, + "remainderInteger-cpu-arguments-constant": 196500, + "remainderInteger-cpu-arguments-model-arguments-intercept": 453240, + "remainderInteger-cpu-arguments-model-arguments-slope": 220, + "remainderInteger-memory-arguments-intercept": 0, + "remainderInteger-memory-arguments-minimum": 1, + "remainderInteger-memory-arguments-slope": 1, + "serialiseData-cpu-arguments-intercept": 1159724, + "serialiseData-cpu-arguments-slope": 392670, + "serialiseData-memory-arguments-intercept": 0, + "serialiseData-memory-arguments-slope": 2, + "sha2_256-cpu-arguments-intercept": 806990, + "sha2_256-cpu-arguments-slope": 30482, + "sha2_256-memory-arguments": 4, + "sha3_256-cpu-arguments-intercept": 1927926, + "sha3_256-cpu-arguments-slope": 82523, + "sha3_256-memory-arguments": 4, + "sliceByteString-cpu-arguments-intercept": 265318, + "sliceByteString-cpu-arguments-slope": 0, + "sliceByteString-memory-arguments-intercept": 4, + "sliceByteString-memory-arguments-slope": 0, + "sndPair-cpu-arguments": 85931, + "sndPair-memory-arguments": 32, + "subtractInteger-cpu-arguments-intercept": 205665, + "subtractInteger-cpu-arguments-slope": 812, + "subtractInteger-memory-arguments-intercept": 1, + "subtractInteger-memory-arguments-slope": 1, + "tailList-cpu-arguments": 41182, + "tailList-memory-arguments": 32, + "trace-cpu-arguments": 212342, + "trace-memory-arguments": 32, + "unBData-cpu-arguments": 31220, + "unBData-memory-arguments": 32, + "unConstrData-cpu-arguments": 32696, + "unConstrData-memory-arguments": 32, + "unIData-cpu-arguments": 43357, + "unIData-memory-arguments": 32, + "unListData-cpu-arguments": 32247, + "unListData-memory-arguments": 32, + "unMapData-cpu-arguments": 38314, + "unMapData-memory-arguments": 32, + "verifyEcdsaSecp256k1Signature-cpu-arguments": 35892428, + "verifyEcdsaSecp256k1Signature-memory-arguments": 10, + "verifyEd25519Signature-cpu-arguments-intercept": 9462713, + "verifyEd25519Signature-cpu-arguments-slope": 1021, + "verifyEd25519Signature-memory-arguments": 10, + "verifySchnorrSecp256k1Signature-cpu-arguments-intercept": 38887044, + "verifySchnorrSecp256k1Signature-cpu-arguments-slope": 32947, + "verifySchnorrSecp256k1Signature-memory-arguments": 10 + } + }, + "price_mem": 0.0577, + "price_step": 7.21e-05, + "max_tx_ex_mem": "14000000", + "max_tx_ex_steps": "10000000000", + "max_block_ex_mem": "62000000", + "max_block_ex_steps": "40000000000", + "max_val_size": "5000", + "collateral_percent": 150, + "max_collateral_inputs": 3, + "coins_per_utxo_size": "4310", + "coins_per_utxo_word": "4310" +} diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs index ea6d9d7a26..d552981bd6 100644 --- a/src/Internal/Contract/QueryHandle.purs +++ b/src/Internal/Contract/QueryHandle.purs @@ -44,6 +44,7 @@ import Ctl.Internal.Serialization.Address (Address) import Ctl.Internal.Serialization.Hash (ScriptHash) import Ctl.Internal.Service.Blockfrost ( BlockfrostServiceM + , getCurrentEpoch , runBlockfrostServiceM ) import Ctl.Internal.Service.Error (ClientError) @@ -122,7 +123,7 @@ queryHandleForBlockfrostBackend _ backend = , getTxMetadata: runBlockfrostServiceM' <<< undefined , utxosAt: runBlockfrostServiceM' <<< undefined , getChainTip: runBlockfrostServiceM' undefined - , getCurrentEpoch: runBlockfrostServiceM' undefined + , getCurrentEpoch: undefined $ runBlockfrostServiceM' getCurrentEpoch , submitTx: runBlockfrostServiceM' <<< undefined , evaluateTx: \tx additionalUtxos -> runBlockfrostServiceM' $ undefined tx additionalUtxos diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index 0c316c9dbd..56a9605ae9 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -1,8 +1,9 @@ module Ctl.Internal.Service.Blockfrost ( BlockfrostServiceM , BlockfrostServiceParams + , BlockfrostCurrentEpoch(BlockfrostCurrentEpoch) , runBlockfrostServiceM - , dummyExport + , getCurrentEpoch ) where import Prelude @@ -22,14 +23,16 @@ import Ctl.Internal.Service.Error , ServiceError(ServiceBlockfrostError) ) import Data.Bifunctor (lmap) +import Data.BigInt (BigInt) import Data.Either (Either(Left, Right)) +import Data.Generic.Rep (class Generic) import Data.HTTP.Method (Method(GET, POST)) import Data.Maybe (Maybe, maybe) import Data.MediaType (MediaType) -import Data.Newtype (wrap) +import Data.Newtype (class Newtype, wrap) +import Data.Show.Generic (genericShow) import Effect.Aff (Aff) import Effect.Aff.Class (liftAff) -import Undefined (undefined) -------------------------------------------------------------------------------- -- BlockfrostServiceM @@ -57,15 +60,14 @@ runBlockfrostServiceM backend = flip runReaderT serviceParams -------------------------------------------------------------------------------- data BlockfrostEndpoint + = GetCurrentEpoch + | GetProtocolParams realizeEndpoint :: BlockfrostEndpoint -> Affjax.URL realizeEndpoint endpoint = case endpoint of - _ -> undefined - -dummyExport :: Unit -dummyExport = undefined blockfrostGetRequest blockfrostPostRequest - (handleBlockfrostResponse undefined :: _ Int) + GetCurrentEpoch -> "/epochs/latest" + GetProtocolParams -> "/epochs/latest/parameters" blockfrostGetRequest :: BlockfrostEndpoint @@ -121,3 +123,16 @@ handleBlockfrostResponse (Right { status: Affjax.StatusCode statusCode, body }) body # lmap (ClientDecodeJsonError body) <<< (decodeAeson <=< parseJsonStringToAeson) +newtype BlockfrostCurrentEpoch = BlockfrostCurrentEpoch { epoch :: BigInt } + +derive instance Generic BlockfrostCurrentEpoch _ +derive instance Newtype BlockfrostCurrentEpoch _ +derive newtype instance DecodeAeson BlockfrostCurrentEpoch + +instance Show BlockfrostCurrentEpoch where + show = genericShow + +getCurrentEpoch + :: BlockfrostServiceM (Either ClientError BlockfrostCurrentEpoch) +getCurrentEpoch = blockfrostGetRequest GetCurrentEpoch + <#> handleBlockfrostResponse From 3518b824d812f7a9a642ceed5a6a3122124e6622 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Fri, 30 Dec 2022 10:47:32 +0000 Subject: [PATCH 207/373] Fix dummy export --- src/Internal/Service/Blockfrost.purs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index 0c316c9dbd..c8015bacb5 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -63,8 +63,8 @@ realizeEndpoint endpoint = case endpoint of _ -> undefined -dummyExport :: Unit -dummyExport = undefined blockfrostGetRequest blockfrostPostRequest +dummyExport :: Unit -> Unit +dummyExport _ = undefined blockfrostGetRequest blockfrostPostRequest (handleBlockfrostResponse undefined :: _ Int) blockfrostGetRequest From 1b9343e9e49f88e4ee02908b419c157a7166340b Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Fri, 30 Dec 2022 10:49:31 +0000 Subject: [PATCH 208/373] Update Blockfrost.purs --- src/Internal/Service/Blockfrost.purs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index 22460bedd2..56a9605ae9 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -68,7 +68,6 @@ realizeEndpoint endpoint = case endpoint of GetCurrentEpoch -> "/epochs/latest" GetProtocolParams -> "/epochs/latest/parameters" - _ -> undefined blockfrostGetRequest :: BlockfrostEndpoint From 89921ac18d8682e4580da7a1ce73d06ad95512bb Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Fri, 30 Dec 2022 14:41:48 +0100 Subject: [PATCH 209/373] Remove obsolete InsufficientTxInputs error, Update doc/faq.md --- doc/faq.md | 4 ++-- src/Internal/BalanceTx/BalanceTx.purs | 1 - src/Internal/BalanceTx/Error.purs | 2 -- 3 files changed, 2 insertions(+), 5 deletions(-) diff --git a/doc/faq.md b/doc/faq.md index ffe9493aae..2dc1569036 100644 --- a/doc/faq.md +++ b/doc/faq.md @@ -10,7 +10,7 @@ This document lists common problems encountered by CTL users and developers. - [Q: `lib.something` is not a function, why?](#q-libsomething-is-not-a-function-why) - [Q: I see `spago: Error: Remote host not found`, why?](#q-i-see-spago-error-remote-host-not-found-why) - [Common Contract execution problems](#common-contract-execution-problems) - - [Q: What are the common reasons behind InsufficientTxInputs error?](#q-what-are-the-common-reasons-behind-insufficienttxinputs-error) + - [Q: What are the common reasons behind BalanceInsufficientError?](#q-what-are-the-common-reasons-behind-balanceinsufficienterror) - [Time-related](#time-related) - [Q: Time-related functions behave strangely, what's the reason?](#q-time-related-functions-behave-strangely-whats-the-reason) - [Q: Time/slot conversion functions return `Nothing`. Why is that?](#q-timeslot-conversion-functions-return-nothing-why-is-that) @@ -48,7 +48,7 @@ means that the CTL overlay hasn't been properly applied. Add `ctl.overlays.spago ## Common Contract execution problems -### Q: What are the common reasons behind InsufficientTxInputs error? +### Q: What are the common reasons behind BalanceInsufficientError? Most contracts require at least two UTxOs to run (one will be used as a collateral). If you use a wallet with only one UTxO, e.g. a new wallet you just funded from the faucet, you need to send yourself at least 5 tAda to create another UTxO for the collateral. diff --git a/src/Internal/BalanceTx/BalanceTx.purs b/src/Internal/BalanceTx/BalanceTx.purs index 5a16cf7851..2118214a9b 100644 --- a/src/Internal/BalanceTx/BalanceTx.purs +++ b/src/Internal/BalanceTx/BalanceTx.purs @@ -36,7 +36,6 @@ import Ctl.Internal.BalanceTx.Error , CouldNotGetCollateral , CouldNotGetUtxos , ExUnitsEvaluationFailed - , InsufficientTxInputs , ReindexRedeemersError , UtxoLookupFailedFor , UtxoMinAdaValueCalculationFailed diff --git a/src/Internal/BalanceTx/Error.purs b/src/Internal/BalanceTx/Error.purs index 0d139c37f6..1ba651d1fa 100644 --- a/src/Internal/BalanceTx/Error.purs +++ b/src/Internal/BalanceTx/Error.purs @@ -12,7 +12,6 @@ module Ctl.Internal.BalanceTx.Error , CollateralReturnError , CollateralReturnMinAdaValueCalcError , ExUnitsEvaluationFailed - , InsufficientTxInputs , InsufficientUtxoBalanceToCoverAsset , ReindexRedeemersError , UtxoLookupFailedFor @@ -76,7 +75,6 @@ data BalanceTxError | CollateralReturnError String | CollateralReturnMinAdaValueCalcError | ExUnitsEvaluationFailed UnattachedUnbalancedTx Ogmios.TxEvaluationFailure - | InsufficientTxInputs Expected Actual | InsufficientUtxoBalanceToCoverAsset ImpossibleError String | ReindexRedeemersError ReindexErrors | UtxoLookupFailedFor TransactionInput From c66e2b431f3ad3e152d3c31f963d4375f0912235 Mon Sep 17 00:00:00 2001 From: Gregory Gerasev Date: Mon, 26 Dec 2022 09:32:33 +0400 Subject: [PATCH 210/373] Add some required tests --- doc/test-plan.md | 6 +-- test/Plutip/Contract.purs | 87 ++++++++++++++++++++++++++++++++++++++- 2 files changed, 89 insertions(+), 4 deletions(-) diff --git a/doc/test-plan.md b/doc/test-plan.md index 57829640d3..8cfb03bcd2 100644 --- a/doc/test-plan.md +++ b/doc/test-plan.md @@ -121,13 +121,13 @@ In addition to the constraints/lookups listed above, there are several other cri - [x] `signTransaction` - [x] `submit` - [x] `awaitTxConfirmed` (implies `awaitTxConfirmedWithTimeout`) - - [ ] `getTxMetadata` + - [x] `getTxMetadata` - `Contract.Scripts.*` - [x] `validatorHash` - [x] `mintingPolicy` - [x] `applyArgs` - - [ ] `getScriptByHash` - - [ ] `getScriptsByHashes` + - [x] `getScriptByHash` + - [x] `getScriptsByHashes` - `Contract.Hashing.*` - [x] `datumHash` - [x] `plutusScriptHash` diff --git a/test/Plutip/Contract.purs b/test/Plutip/Contract.purs index c371e0ae5e..fde26e563d 100644 --- a/test/Plutip/Contract.purs +++ b/test/Plutip/Contract.purs @@ -14,6 +14,7 @@ import Contract.Address , ownPaymentPubKeysHashes , ownStakePubKeysHashes ) +import Contract.AuxiliaryData (setGeneralTxMetadata) import Contract.BalanceTxConstraints ( BalanceTxConstraintsBuilder , mustUseAdditionalUtxos @@ -42,6 +43,8 @@ import Contract.ScriptLookups as Lookups import Contract.Scripts ( ValidatorHash , applyArgs + , getScriptByHash + , getScriptsByHashes , mintingPolicyHash , validatorHash ) @@ -63,6 +66,7 @@ import Contract.Transaction , balanceTx , balanceTxWithConstraints , createAdditionalUtxos + , getTxMetadata , signTransaction , submit , submitTxFromConstraints @@ -123,6 +127,11 @@ import Ctl.Internal.Plutus.Types.Value (lovelaceValueOf) import Ctl.Internal.Scripts (nativeScriptHashEnterpriseAddress) import Ctl.Internal.Test.TestPlanM (TestPlanM) import Ctl.Internal.Types.Interval (getSlotLength) +import Ctl.Internal.Types.TransactionMetadata + ( GeneralTransactionMetadata(GeneralTransactionMetadata) + , TransactionMetadatum(Text) + , TransactionMetadatumLabel(TransactionMetadatumLabel) + ) import Ctl.Internal.Wallet ( WalletExtension(NamiWallet, GeroWallet, FlintWallet, NuFiWallet) ) @@ -136,7 +145,7 @@ import Data.Either (Either(Right), isLeft) import Data.Foldable (fold, foldM, length) import Data.Lens (view) import Data.Map as Map -import Data.Maybe (Maybe(Just, Nothing), isJust) +import Data.Maybe (Maybe(Just, Nothing), fromJust, isJust) import Data.Newtype (unwrap, wrap) import Data.Traversable (traverse, traverse_) import Data.Tuple.Nested (type (/\), (/\)) @@ -144,6 +153,8 @@ import Effect.Class (liftEffect) import Effect.Exception (throw) import Mote (group, skip, test) import Mote.Monad (mapTest) +import Partial (crash) +import Partial.Unsafe (unsafePartial) import Safe.Coerce (coerce) import Test.Ctl.Fixtures ( cip25MetadataFixture1 @@ -782,6 +793,80 @@ suite = do ] ) + test "GetScriptByHash" do + let + distribution :: InitialUTxOs + distribution = [ BigInt.fromInt 2_000_000_000 ] + + withWallets distribution \alice -> do + withKeyWallet alice do + validator1 <- AlwaysSucceeds.alwaysSucceedsScript + validator2 <- alwaysSucceedsScriptV2 + let + validatorRef1 = PlutusScriptRef $ unwrap validator1 + validatorRef2 = PlutusScriptRef $ unwrap validator2 + useScriptAndGetByHash validator vhash = do + txId <- AlwaysSucceeds.payToAlwaysSucceeds vhash + awaitTxConfirmed txId + -- For Kupo (used inside) to see script, its utxo must be spent + AlwaysSucceeds.spendFromAlwaysSucceeds vhash validator txId + getScriptByHash $ unwrap vhash + + result1 <- useScriptAndGetByHash validator1 (validatorHash validator1) + result2 <- useScriptAndGetByHash validator2 (validatorHash validator2) + + let + unpackResult' :: Partial => _ + unpackResult' (Right (Just x)) = x + unpackResult' _ = crash "test fail: No script found by hash" + unpackResult x = unsafePartial $ unpackResult' x + + -- Testing getScriptByHash + (unpackResult result1) `shouldEqual` validatorRef1 + (unpackResult result2) `shouldEqual` validatorRef2 + + -- Testing getScriptsByHashes + let + scriptHash1 = unwrap (validatorHash validator1) + scriptHash2 = unwrap (validatorHash validator2) + results <- getScriptsByHashes [ scriptHash1, scriptHash2 ] + (map unpackResult results) `shouldEqual` Map.fromFoldable + [ (scriptHash1 /\ validatorRef1) + , (scriptHash2 /\ validatorRef2) + ] + + test "GetTxMetadata" do + let + distribution :: InitialUTxOs + distribution = [ BigInt.fromInt 2_000_000_000 ] + + withWallets distribution \alice -> do + withKeyWallet alice do + tn <- mkTokenName "Token name" + mp /\ _ <- mkCurrencySymbol alwaysMintsPolicy + let + constraints :: Constraints.TxConstraints Void Void + constraints = mconcat + [ Constraints.mustMintCurrency (mintingPolicyHash mp) tn one + ] + + lookups :: Lookups.ScriptLookups Void + lookups = + Lookups.mintingPolicy mp + givenMetadata = GeneralTransactionMetadata $ Map.fromFoldable + [ TransactionMetadatumLabel (BigInt.fromInt 8) /\ Text "foo" ] + + ubTx <- liftedE $ Lookups.mkUnbalancedTx lookups constraints + ubTx' <- setGeneralTxMetadata ubTx givenMetadata + bsTx <- signTransaction =<< liftedE (balanceTx ubTx') + txId <- submit bsTx + awaitTxConfirmed txId + + mMetadata <- getTxMetadata txId + let metadata = unsafePartial $ fromJust mMetadata + + metadata `shouldEqual` givenMetadata + test "MintZeroToken" do let distribution :: InitialUTxOs From cb8bd7ebca4163805fd8daae3df195e7f3d30f06 Mon Sep 17 00:00:00 2001 From: Gregory Gerasev Date: Wed, 28 Dec 2022 17:47:05 +0400 Subject: [PATCH 211/373] Apply suggestions from code review Co-authored-by: Joseph Young --- test/Plutip/Contract.purs | 15 ++++----------- 1 file changed, 4 insertions(+), 11 deletions(-) diff --git a/test/Plutip/Contract.purs b/test/Plutip/Contract.purs index fde26e563d..480c0f9bb3 100644 --- a/test/Plutip/Contract.purs +++ b/test/Plutip/Contract.purs @@ -815,15 +815,9 @@ suite = do result1 <- useScriptAndGetByHash validator1 (validatorHash validator1) result2 <- useScriptAndGetByHash validator2 (validatorHash validator2) - let - unpackResult' :: Partial => _ - unpackResult' (Right (Just x)) = x - unpackResult' _ = crash "test fail: No script found by hash" - unpackResult x = unsafePartial $ unpackResult' x - -- Testing getScriptByHash - (unpackResult result1) `shouldEqual` validatorRef1 - (unpackResult result2) `shouldEqual` validatorRef2 + result1 `shouldEqual` (Right (Just validatorRef1)) + result2 `shouldEqual` (Right (Just validatorRef2)) -- Testing getScriptsByHashes let @@ -846,9 +840,8 @@ suite = do mp /\ _ <- mkCurrencySymbol alwaysMintsPolicy let constraints :: Constraints.TxConstraints Void Void - constraints = mconcat - [ Constraints.mustMintCurrency (mintingPolicyHash mp) tn one - ] + constraints = + Constraints.mustMintCurrency (mintingPolicyHash mp) tn one lookups :: Lookups.ScriptLookups Void lookups = From 26a3b54effb8cfcd4ce2816d2dc03680d97c8157 Mon Sep 17 00:00:00 2001 From: Gregory Gerasev Date: Wed, 28 Dec 2022 18:30:17 +0400 Subject: [PATCH 212/373] Fix some review issues --- test/Plutip/Contract.purs | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/test/Plutip/Contract.purs b/test/Plutip/Contract.purs index 480c0f9bb3..28a623d97e 100644 --- a/test/Plutip/Contract.purs +++ b/test/Plutip/Contract.purs @@ -22,6 +22,11 @@ import Contract.BalanceTxConstraints import Contract.Chain (currentTime) import Contract.Hashing (datumHash, nativeScriptHash) import Contract.Log (logInfo') +import Contract.Metadata + ( GeneralTransactionMetadata(GeneralTransactionMetadata) + , TransactionMetadatum(Text) + , TransactionMetadatumLabel(TransactionMetadatumLabel) + ) import Contract.Monad ( Contract , liftContractE @@ -127,11 +132,6 @@ import Ctl.Internal.Plutus.Types.Value (lovelaceValueOf) import Ctl.Internal.Scripts (nativeScriptHashEnterpriseAddress) import Ctl.Internal.Test.TestPlanM (TestPlanM) import Ctl.Internal.Types.Interval (getSlotLength) -import Ctl.Internal.Types.TransactionMetadata - ( GeneralTransactionMetadata(GeneralTransactionMetadata) - , TransactionMetadatum(Text) - , TransactionMetadatumLabel(TransactionMetadatumLabel) - ) import Ctl.Internal.Wallet ( WalletExtension(NamiWallet, GeroWallet, FlintWallet, NuFiWallet) ) @@ -808,7 +808,7 @@ suite = do useScriptAndGetByHash validator vhash = do txId <- AlwaysSucceeds.payToAlwaysSucceeds vhash awaitTxConfirmed txId - -- For Kupo (used inside) to see script, its utxo must be spent + -- Spending utxo, to make Kupo (used inside) see the script AlwaysSucceeds.spendFromAlwaysSucceeds vhash validator txId getScriptByHash $ unwrap vhash From ad5004daca92415be94106ee7442ff98c7a67262 Mon Sep 17 00:00:00 2001 From: Gregory Gerasev Date: Thu, 29 Dec 2022 14:37:02 +0400 Subject: [PATCH 213/373] Apply suggestions from code review Co-authored-by: Joseph Young --- test/Plutip/Contract.purs | 10 ++++------ 1 file changed, 4 insertions(+), 6 deletions(-) diff --git a/test/Plutip/Contract.purs b/test/Plutip/Contract.purs index 28a623d97e..80e4c23586 100644 --- a/test/Plutip/Contract.purs +++ b/test/Plutip/Contract.purs @@ -824,9 +824,9 @@ suite = do scriptHash1 = unwrap (validatorHash validator1) scriptHash2 = unwrap (validatorHash validator2) results <- getScriptsByHashes [ scriptHash1, scriptHash2 ] - (map unpackResult results) `shouldEqual` Map.fromFoldable - [ (scriptHash1 /\ validatorRef1) - , (scriptHash2 /\ validatorRef2) + results `shouldEqual` Map.fromFoldable + [ (scriptHash1 /\ (Right (Just validatorRef1))) + , (scriptHash2 /\ (Right (Just validatorRef2))) ] test "GetTxMetadata" do @@ -856,9 +856,7 @@ suite = do awaitTxConfirmed txId mMetadata <- getTxMetadata txId - let metadata = unsafePartial $ fromJust mMetadata - - metadata `shouldEqual` givenMetadata + mMetadata `shouldEqual` (Just givenMetadata) test "MintZeroToken" do let From 33b988820705a2537a478b0171c3fc344705c156 Mon Sep 17 00:00:00 2001 From: Gregory Gerasev Date: Thu, 29 Dec 2022 14:55:24 +0400 Subject: [PATCH 214/373] Add Eq ClientError needed for tests review changes --- src/Internal/Service/Error.purs | 13 +++++++++++++ 1 file changed, 13 insertions(+) diff --git a/src/Internal/Service/Error.purs b/src/Internal/Service/Error.purs index 9e1a82f83a..bf6a6be7a3 100644 --- a/src/Internal/Service/Error.purs +++ b/src/Internal/Service/Error.purs @@ -39,6 +39,17 @@ data ClientError -- | Any other error | ClientOtherError String +instance Eq ClientError where + eq (ClientHttpError e1) (ClientHttpError e2) = + Affjax.printError e1 == Affjax.printError e2 + eq (ClientHttpResponseError sc1 e1) (ClientHttpResponseError sc2 e2) = + (sc1 == sc2) && (e1 == e2) + eq (ClientDecodeJsonError s1 e1) (ClientDecodeJsonError s2 e2) = + (s1 == s2) && (e1 == e2) + eq (ClientEncodingError s1) (ClientEncodingError s2) = s1 == s2 + eq (ClientOtherError s1) (ClientOtherError s2) = s1 == s2 + eq _ _ = false + -- No `Show` instance of `Affjax.Error` instance Show ClientError where show (ClientHttpError err) = @@ -72,6 +83,7 @@ data ServiceError = ServiceBlockfrostError BlockfrostError | ServiceOtherError String +derive instance Eq ServiceError derive instance Generic ServiceError _ instance Show ServiceError where @@ -83,6 +95,7 @@ newtype BlockfrostError = BlockfrostError , message :: String } +derive instance Eq BlockfrostError derive instance Newtype BlockfrostError _ derive instance Generic BlockfrostError _ From 602ac4ba96f5b2dc7658a50bb69e4823b93c6f1b Mon Sep 17 00:00:00 2001 From: Gregory Gerasev Date: Thu, 29 Dec 2022 14:55:51 +0400 Subject: [PATCH 215/373] Remove unneccesary details from test --- test/Plutip/Contract.purs | 12 +++--------- 1 file changed, 3 insertions(+), 9 deletions(-) diff --git a/test/Plutip/Contract.purs b/test/Plutip/Contract.purs index 80e4c23586..889b2db6ef 100644 --- a/test/Plutip/Contract.purs +++ b/test/Plutip/Contract.purs @@ -145,7 +145,7 @@ import Data.Either (Either(Right), isLeft) import Data.Foldable (fold, foldM, length) import Data.Lens (view) import Data.Map as Map -import Data.Maybe (Maybe(Just, Nothing), fromJust, isJust) +import Data.Maybe (Maybe(Just, Nothing), isJust) import Data.Newtype (unwrap, wrap) import Data.Traversable (traverse, traverse_) import Data.Tuple.Nested (type (/\), (/\)) @@ -153,8 +153,6 @@ import Effect.Class (liftEffect) import Effect.Exception (throw) import Mote (group, skip, test) import Mote.Monad (mapTest) -import Partial (crash) -import Partial.Unsafe (unsafePartial) import Safe.Coerce (coerce) import Test.Ctl.Fixtures ( cip25MetadataFixture1 @@ -836,16 +834,12 @@ suite = do withWallets distribution \alice -> do withKeyWallet alice do - tn <- mkTokenName "Token name" - mp /\ _ <- mkCurrencySymbol alwaysMintsPolicy let constraints :: Constraints.TxConstraints Void Void - constraints = - Constraints.mustMintCurrency (mintingPolicyHash mp) tn one + constraints = mempty lookups :: Lookups.ScriptLookups Void - lookups = - Lookups.mintingPolicy mp + lookups = mempty givenMetadata = GeneralTransactionMetadata $ Map.fromFoldable [ TransactionMetadatumLabel (BigInt.fromInt 8) /\ Text "foo" ] From 5f7dcdbbd3aa0d51645f8dec480912a0b50e8b02 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Mon, 2 Jan 2023 18:48:27 +0000 Subject: [PATCH 216/373] Create a blockfrost config which uses CTL as a backup, implement submitTx and evaluateTx --- src/Contract/Config.purs | 23 ++++++- src/Contract/Transaction.purs | 9 ++- src/Internal/Contract/Monad.purs | 5 +- src/Internal/Contract/QueryHandle.purs | 53 ++++++++------- src/Internal/Service/Blockfrost.purs | 93 ++++++++++++++++++++++++-- 5 files changed, 149 insertions(+), 34 deletions(-) diff --git a/src/Contract/Config.purs b/src/Contract/Config.purs index 17250eeefe..70e0747c2d 100644 --- a/src/Contract/Config.purs +++ b/src/Contract/Config.purs @@ -1,6 +1,7 @@ -- | Exposes some pre-defined Contract configurations. Re-exports all modules needed to modify `ContractParams`. module Contract.Config ( testnetConfig + , testnetBlockfrostDevConfig , testnetNamiConfig , testnetGeroConfig , testnetFlintConfig @@ -34,7 +35,7 @@ import Ctl.Internal.Contract.QueryBackend ( -- TODO Export Blockfrost once the following is stable -- https://github.com/Plutonomicon/cardano-transaction-lib/issues/1118 -- , mkBlockfrostBackendParams - QueryBackendParams(CtlBackendParams {-, BlockfrostBackendParams-} ) + QueryBackendParams(CtlBackendParams, BlockfrostBackendParams) , mkCtlBackendParams ) import Ctl.Internal.Deserialization.Keys (privateKeyFromBytes) @@ -82,6 +83,26 @@ testnetConfig = , hooks: emptyHooks } +-- | Blockfrost public preview with CTL as backup +testnetBlockfrostDevConfig :: Maybe String -> ContractParams +testnetBlockfrostDevConfig mbApiKey = + { backendParams: BlockfrostBackendParams + { blockfrostApiKey: mbApiKey + , blockfrostConfig: blockfrostPublicPreviewServerConfig + } + ( Just + { ogmiosConfig: defaultOgmiosWsConfig + , kupoConfig: defaultKupoServerConfig + } + ) + , networkId: TestnetId + , walletSpec: Nothing + , logLevel: Trace + , customLogger: Nothing + , suppressLogs: false + , hooks: emptyHooks + } + testnetNamiConfig :: ContractParams testnetNamiConfig = testnetConfig { walletSpec = Just ConnectToNami } diff --git a/src/Contract/Transaction.purs b/src/Contract/Transaction.purs index 2c47bf9e68..e444d7cdb6 100644 --- a/src/Contract/Transaction.purs +++ b/src/Contract/Transaction.purs @@ -53,7 +53,7 @@ import Contract.PlutusData (class IsData) import Contract.ScriptLookups (mkUnbalancedTx) import Contract.Scripts (class ValidatorTypes) import Contract.TxConstraints (TxConstraints) -import Control.Monad.Error.Class (catchError, throwError) +import Control.Monad.Error.Class (catchError, liftEither, throwError) import Control.Monad.Reader (ReaderT, asks, runReaderT) import Control.Monad.Reader.Class (ask) import Ctl.Internal.BalanceTx (BalanceTxError) as BalanceTxError @@ -248,6 +248,7 @@ import Ctl.Internal.Types.VRFKeyHash , vrfKeyHashToBytes ) as X import Data.Array.NonEmpty as NonEmptyArray +import Data.Bifunctor (lmap) import Data.BigInt (BigInt) import Data.Either (Either, hush) import Data.Foldable (foldl, length) @@ -262,7 +263,7 @@ import Data.Traversable (class Traversable, for_, traverse) import Data.Tuple (Tuple(Tuple), fst) import Data.Tuple.Nested (type (/\), (/\)) import Data.UInt (UInt) -import Effect.Aff (bracket) +import Effect.Aff (bracket, error) import Effect.Aff.Class (liftAff) import Effect.Class (liftEffect) @@ -285,7 +286,9 @@ submit -> Contract TransactionHash submit tx = do queryHandle <- getQueryHandle - liftedM "Failed to submit tx" $ liftAff $ queryHandle.submitTx $ unwrap tx + eiTxHash <- liftAff $ queryHandle.submitTx $ unwrap tx + liftEither $ flip lmap eiTxHash \err -> error $ + "Failed to submit tx:\n" <> show err -- | Calculate the minimum transaction fee. calculateMinFee diff --git a/src/Internal/Contract/Monad.purs b/src/Internal/Contract/Monad.purs index 185b9aa96c..0ead6d78cf 100644 --- a/src/Internal/Contract/Monad.purs +++ b/src/Internal/Contract/Monad.purs @@ -61,7 +61,7 @@ import Ctl.Internal.Wallet.Spec (WalletSpec, mkWalletBySpec) import Data.Either (Either(Left, Right), isRight) import Data.Log.Level (LogLevel) import Data.Log.Message (Message) -import Data.Maybe (Maybe(Just), fromMaybe) +import Data.Maybe (Maybe(Just, Nothing), fromMaybe) import Data.Newtype (class Newtype, unwrap, wrap) import Data.Traversable (for_, traverse, traverse_) import Effect (Effect) @@ -239,6 +239,9 @@ getLedgerConstants logger = case _ of pparams <- getProtocolParametersAff ws logger systemStart <- getSystemStartAff ws logger pure { pparams, systemStart } + -- Temporarily use CtlBackend to get constants + BlockfrostBackend _ (Just ctlBackend) -> getLedgerConstants logger + (CtlBackend ctlBackend Nothing) BlockfrostBackend _ _ -> undefined -- | Ensure that `NetworkId` from wallet is the same as specified in the diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs index ea6d9d7a26..c81c67c648 100644 --- a/src/Internal/Contract/QueryHandle.purs +++ b/src/Internal/Contract/QueryHandle.purs @@ -38,7 +38,10 @@ import Ctl.Internal.QueryM.Ogmios , CurrentEpoch , EraSummaries ) as Ogmios -import Ctl.Internal.QueryM.Ogmios (SubmitTxR(SubmitTxSuccess), TxEvaluationR) +import Ctl.Internal.QueryM.Ogmios + ( SubmitTxR(SubmitTxSuccess, SubmitFail) + , TxEvaluationR + ) import Ctl.Internal.Serialization (convertTransaction, toBytes) as Serialization import Ctl.Internal.Serialization.Address (Address) import Ctl.Internal.Serialization.Hash (ScriptHash) @@ -46,12 +49,16 @@ import Ctl.Internal.Service.Blockfrost ( BlockfrostServiceM , runBlockfrostServiceM ) -import Ctl.Internal.Service.Error (ClientError) +import Ctl.Internal.Service.Blockfrost + ( evaluateTx + , submitTx + ) as Blockfrost +import Ctl.Internal.Service.Error (ClientError(ClientOtherError)) import Ctl.Internal.Types.Chain as Chain import Ctl.Internal.Types.Datum (DataHash, Datum) import Ctl.Internal.Types.Transaction (TransactionHash, TransactionInput) import Ctl.Internal.Types.TransactionMetadata (GeneralTransactionMetadata) -import Data.Either (Either) +import Data.Either (Either(Left)) import Data.Maybe (Maybe(Just, Nothing), isJust) import Data.Newtype (unwrap, wrap) import Effect.Aff (Aff) @@ -70,7 +77,7 @@ type QueryHandle = , getChainTip :: Aff Chain.Tip , getCurrentEpoch :: Aff Ogmios.CurrentEpoch -- TODO Capture errors from all backends - , submitTx :: Transaction -> Aff (Maybe TransactionHash) + , submitTx :: Transaction -> Aff (Either ClientError TransactionHash) , evaluateTx :: Transaction -> Ogmios.AdditionalUtxoSet -> Aff TxEvaluationR , getEraSummaries :: Aff Ogmios.EraSummaries } @@ -80,8 +87,10 @@ getQueryHandle = ask <#> \contractEnv -> case contractEnv.backend of CtlBackend backend _ -> queryHandleForCtlBackend contractEnv backend - BlockfrostBackend backend _ -> - queryHandleForBlockfrostBackend contractEnv backend + BlockfrostBackend backend (Just ctlBackend) -> do + let fallback = queryHandleForCtlBackend contractEnv ctlBackend + queryHandleForBlockfrostBackend contractEnv backend fallback + BlockfrostBackend _ Nothing -> undefined queryHandleForCtlBackend :: ContractEnv -> CtlBackend -> QueryHandle queryHandleForCtlBackend contractEnv backend = @@ -100,8 +109,8 @@ queryHandleForCtlBackend contractEnv backend = let txCborBytes = Serialization.toBytes cslTx result <- QueryM.submitTxOgmios (unwrap txHash) txCborBytes case result of - SubmitTxSuccess a -> pure $ Just $ wrap a - _ -> pure Nothing + SubmitTxSuccess a -> pure $ pure $ wrap a + SubmitFail err -> pure $ Left $ ClientOtherError $ show err , evaluateTx: \tx additionalUtxos -> runQueryM' do txBytes <- Serialization.toBytes <$> liftEffect (Serialization.convertTransaction tx) @@ -113,22 +122,20 @@ queryHandleForCtlBackend contractEnv backend = runQueryM' = runQueryM contractEnv backend queryHandleForBlockfrostBackend - :: ContractEnv -> BlockfrostBackend -> QueryHandle -queryHandleForBlockfrostBackend _ backend = - { getDatumByHash: runBlockfrostServiceM' <<< undefined - , getScriptByHash: runBlockfrostServiceM' <<< undefined - , getUtxoByOref: runBlockfrostServiceM' <<< undefined - , isTxConfirmed: runBlockfrostServiceM' <<< undefined - , getTxMetadata: runBlockfrostServiceM' <<< undefined - , utxosAt: runBlockfrostServiceM' <<< undefined - , getChainTip: runBlockfrostServiceM' undefined - , getCurrentEpoch: runBlockfrostServiceM' undefined - , submitTx: runBlockfrostServiceM' <<< undefined - , evaluateTx: \tx additionalUtxos -> runBlockfrostServiceM' $ undefined tx - additionalUtxos - , getEraSummaries: runBlockfrostServiceM' undefined + :: ContractEnv -> BlockfrostBackend -> QueryHandle -> QueryHandle +queryHandleForBlockfrostBackend _ backend fallback = + { getDatumByHash: fallback.getDatumByHash + , getScriptByHash: fallback.getScriptByHash + , getUtxoByOref: fallback.getUtxoByOref + , isTxConfirmed: fallback.isTxConfirmed + , getTxMetadata: fallback.getTxMetadata + , utxosAt: fallback.utxosAt + , getChainTip: fallback.getChainTip + , getCurrentEpoch: fallback.getCurrentEpoch + , submitTx: runBlockfrostServiceM' <<< Blockfrost.submitTx + , evaluateTx: \tx _ -> runBlockfrostServiceM' $ Blockfrost.evaluateTx tx + , getEraSummaries: fallback.getEraSummaries } where runBlockfrostServiceM' :: forall (a :: Type). BlockfrostServiceM a -> Aff a runBlockfrostServiceM' = runBlockfrostServiceM backend - diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index c8015bacb5..88430235ec 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -3,32 +3,53 @@ module Ctl.Internal.Service.Blockfrost , BlockfrostServiceParams , runBlockfrostServiceM , dummyExport + , submitTx + , evaluateTx ) where import Prelude -import Aeson (class DecodeAeson, decodeAeson, parseJsonStringToAeson) +import Aeson + ( class DecodeAeson + , Aeson + , decodeAeson + , parseJsonStringToAeson + , stringifyAeson + ) import Affjax (Error, Response, URL, defaultRequest, request) as Affjax -import Affjax.RequestBody (RequestBody) as Affjax +import Affjax.RequestBody (RequestBody, arrayView, string) as Affjax import Affjax.RequestHeader (RequestHeader(ContentType, RequestHeader)) as Affjax import Affjax.ResponseFormat (string) as Affjax.ResponseFormat import Affjax.StatusCode (StatusCode(StatusCode)) as Affjax +import Control.Alt ((<|>)) +import Control.Monad.Error.Class (throwError) import Control.Monad.Reader.Class (ask) import Control.Monad.Reader.Trans (ReaderT, runReaderT) +import Ctl.Internal.Cardano.Types.Transaction + ( Transaction + ) import Ctl.Internal.Contract.QueryBackend (BlockfrostBackend) +import Ctl.Internal.QueryM.Ogmios (TxEvaluationR) +import Ctl.Internal.Serialization as Serialization import Ctl.Internal.ServerConfig (ServerConfig, mkHttpUrl) import Ctl.Internal.Service.Error ( ClientError(ClientHttpError, ClientHttpResponseError, ClientDecodeJsonError) , ServiceError(ServiceBlockfrostError) ) +import Ctl.Internal.Types.CborBytes (CborBytes, cborBytesToHex) +import Ctl.Internal.Types.Transaction (TransactionHash) import Data.Bifunctor (lmap) import Data.Either (Either(Left, Right)) +import Data.Generic.Rep (class Generic) import Data.HTTP.Method (Method(GET, POST)) -import Data.Maybe (Maybe, maybe) -import Data.MediaType (MediaType) -import Data.Newtype (wrap) +import Data.Maybe (Maybe(Just), maybe) +import Data.MediaType (MediaType(MediaType)) +import Data.Newtype (unwrap, wrap) +import Data.Show.Generic (genericShow) import Effect.Aff (Aff) import Effect.Aff.Class (liftAff) +import Effect.Class (liftEffect) +import Effect.Exception (error) import Undefined (undefined) -------------------------------------------------------------------------------- @@ -57,11 +78,14 @@ runBlockfrostServiceM backend = flip runReaderT serviceParams -------------------------------------------------------------------------------- data BlockfrostEndpoint + = SubmitTransaction + | EvaluateTransaction realizeEndpoint :: BlockfrostEndpoint -> Affjax.URL realizeEndpoint endpoint = case endpoint of - _ -> undefined + SubmitTransaction -> "/tx/submit" + EvaluateTransaction -> "/utils/txs/evaluate" dummyExport :: Unit -> Unit dummyExport _ = undefined blockfrostGetRequest blockfrostPostRequest @@ -121,3 +145,60 @@ handleBlockfrostResponse (Right { status: Affjax.StatusCode statusCode, body }) body # lmap (ClientDecodeJsonError body) <<< (decodeAeson <=< parseJsonStringToAeson) +submitTx + :: Transaction + -> BlockfrostServiceM (Either ClientError TransactionHash) +submitTx tx = do + cslTx <- liftEffect $ Serialization.convertTransaction tx + handleBlockfrostResponse <$> request (Serialization.toBytes cslTx) + where + request + :: CborBytes + -> BlockfrostServiceM (Either Affjax.Error (Affjax.Response String)) + request cbor = + blockfrostPostRequest SubmitTransaction (MediaType "application/cbor") + $ Just + $ Affjax.arrayView + $ unwrap + $ unwrap cbor + +evaluateTx :: Transaction -> BlockfrostServiceM TxEvaluationR +evaluateTx tx = do + cslTx <- liftEffect $ Serialization.convertTransaction tx + resp <- handleBlockfrostResponse <$> request (Serialization.toBytes cslTx) + case unwrapBlockfrostEvaluateTx <$> resp of + Left err -> throwError $ error $ show err + Right (Left err) -> + -- Replicate the error of QueryM's fault handler + throwError $ error $ "Server responded with `fault`: " <> stringifyAeson + err + Right (Right eval) -> pure eval + where + -- Hex encoded, not binary like submission + request + :: CborBytes + -> BlockfrostServiceM (Either Affjax.Error (Affjax.Response String)) + request cbor = + blockfrostPostRequest EvaluateTransaction (MediaType "application/cbor") + $ Just + $ Affjax.string + $ cborBytesToHex cbor + +data BlockfrostEvaluateTx = BlockfrostEvaluateTx (Either Aeson TxEvaluationR) + +derive instance Generic BlockfrostEvaluateTx _ + +instance Show BlockfrostEvaluateTx where + show = genericShow + +instance DecodeAeson BlockfrostEvaluateTx where + decodeAeson aeson = success <|> failure <#> BlockfrostEvaluateTx + where + success = do + { result } :: { result :: TxEvaluationR } <- decodeAeson aeson + pure $ Right result + + failure = pure $ Left aeson + +unwrapBlockfrostEvaluateTx :: BlockfrostEvaluateTx -> Either Aeson TxEvaluationR +unwrapBlockfrostEvaluateTx (BlockfrostEvaluateTx ei) = ei From e8e1ac0476883b18934fa5d17f702342d8d8bf21 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Mon, 2 Jan 2023 20:02:43 +0000 Subject: [PATCH 217/373] Add `Eq` to metadata error --- src/Internal/Contract/QueryHandle/Error.purs | 2 ++ test/Blockfrost.purs | 26 ++++++-------------- test/Plutip/Contract.purs | 2 +- 3 files changed, 11 insertions(+), 19 deletions(-) diff --git a/src/Internal/Contract/QueryHandle/Error.purs b/src/Internal/Contract/QueryHandle/Error.purs index 2ab549c31d..d5732f9227 100644 --- a/src/Internal/Contract/QueryHandle/Error.purs +++ b/src/Internal/Contract/QueryHandle/Error.purs @@ -16,6 +16,8 @@ data GetTxMetadataError | GetTxMetadataMetadataEmptyOrMissingError | GetTxMetadataClientError ClientError +derive instance Eq GetTxMetadataError + instance Show GetTxMetadataError where show = case _ of GetTxMetadataTxNotFoundError -> diff --git a/test/Blockfrost.purs b/test/Blockfrost.purs index a10346599c..ab259fb7d9 100644 --- a/test/Blockfrost.purs +++ b/test/Blockfrost.purs @@ -37,7 +37,7 @@ import Effect (Effect) import Effect.Aff (Aff, error, launchAff_) import Mote (group, test) import Node.Process (argv) -import Test.Spec.Assertions (fail, shouldEqual) +import Test.Spec.Assertions (shouldEqual) import Test.Spec.Runner (defaultConfig) -- Run with `spago test --main Test.Ctl.Blockfrost --exec-args PREVIEW_API_KEY` @@ -172,24 +172,14 @@ testPlan backend = group "Blockfrost" do test "getTxMetadata" do eMetadata <- runBlockfrostServiceM backend $ getTxMetadata (fixtureHash fixture) - case fixture of - TxWithMetadata { metadata } -> case eMetadata of - Right metadata' -> metadata' `shouldEqual` metadata - unexpected -> fail $ show unexpected <> " ≠ (Right (" - <> show metadata - <> "))" - TxWithNoMetadata _ -> case eMetadata of - Left GetTxMetadataMetadataEmptyOrMissingError -> pure unit - unexpected -> fail $ show unexpected <> - " ≠ (Left GetTxMetadataMetadataEmptyOrMissingError)" - UnconfirmedTx _ -> case eMetadata of - Left GetTxMetadataTxNotFoundError -> pure unit - unexpected -> fail $ show unexpected <> - " ≠ (Left GetTxMetadataTxNotFoundError)" + eMetadata `shouldEqual` case fixture of + TxWithMetadata { metadata } -> Right metadata + TxWithNoMetadata _ -> Left GetTxMetadataMetadataEmptyOrMissingError + UnconfirmedTx _ -> Left GetTxMetadataTxNotFoundError test "isTxConfirmed" do - eConfirmed <- runBlockfrostServiceM backend $ isTxConfirmed - (fixtureHash fixture) - confirmed <- liftEither (lmap (error <<< show) eConfirmed) + eConfirmed <- runBlockfrostServiceM backend $ isTxConfirmed $ + fixtureHash fixture + confirmed <- liftEither $ lmap (error <<< show) eConfirmed confirmed `shouldEqual` case fixture of TxWithMetadata _ -> true TxWithNoMetadata _ -> true diff --git a/test/Plutip/Contract.purs b/test/Plutip/Contract.purs index 889b2db6ef..7be7f5dfc4 100644 --- a/test/Plutip/Contract.purs +++ b/test/Plutip/Contract.purs @@ -850,7 +850,7 @@ suite = do awaitTxConfirmed txId mMetadata <- getTxMetadata txId - mMetadata `shouldEqual` (Just givenMetadata) + mMetadata `shouldEqual` Right givenMetadata test "MintZeroToken" do let From 8348b6d6b8ee398b1b2f69ce7a3f33e11302768d Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Mon, 2 Jan 2023 20:31:42 +0000 Subject: [PATCH 218/373] code style --- test/Blockfrost.purs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/test/Blockfrost.purs b/test/Blockfrost.purs index ab259fb7d9..d8f438731a 100644 --- a/test/Blockfrost.purs +++ b/test/Blockfrost.purs @@ -47,11 +47,10 @@ main = do launchAff_ do interpretWithConfig defaultConfig { exit = true } - ( testPlan + $ testPlan { blockfrostConfig: blockfrostPublicPreviewServerConfig , blockfrostApiKey: Just apiKey } - ) data Fixture = TxWithMetadata From 5b0d9b1f196507a3e823e613d9c97c72c82e07ab Mon Sep 17 00:00:00 2001 From: Luis Alberto Diaz Diaz <73986926+Luis-omega@users.noreply.github.com> Date: Mon, 2 Jan 2023 19:19:28 -0600 Subject: [PATCH 219/373] Save --- src/Internal/QueryM/Ogmios.purs | 1 + src/Internal/Service/Blockfrost.purs | 73 ++++++++++++++++++++++++++-- 2 files changed, 70 insertions(+), 4 deletions(-) diff --git a/src/Internal/QueryM/Ogmios.purs b/src/Internal/QueryM/Ogmios.purs index 20cecb3da4..6476a0838d 100644 --- a/src/Internal/QueryM/Ogmios.purs +++ b/src/Internal/QueryM/Ogmios.purs @@ -71,6 +71,7 @@ module Ctl.Internal.QueryM.Ogmios , submitTxCall , slotLengthFactor , parseIpv6String + , rationalToSubcoin ) where import Prelude diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index 56a9605ae9..60de099eb8 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -2,8 +2,10 @@ module Ctl.Internal.Service.Blockfrost ( BlockfrostServiceM , BlockfrostServiceParams , BlockfrostCurrentEpoch(BlockfrostCurrentEpoch) + , BlockfrostProtocolParameters(BlockfrostProtocolParameters) , runBlockfrostServiceM , getCurrentEpoch + , getProtocolParameters ) where import Prelude @@ -17,11 +19,11 @@ import Affjax.StatusCode (StatusCode(StatusCode)) as Affjax import Control.Monad.Reader.Class (ask) import Control.Monad.Reader.Trans (ReaderT, runReaderT) import Ctl.Internal.Contract.QueryBackend (BlockfrostBackend) +import Ctl.Internal.QueryM.Ogmios (PParamRational(..)) +import Ctl.Internal.QueryM.Ogmios as Ogmios import Ctl.Internal.ServerConfig (ServerConfig, mkHttpUrl) -import Ctl.Internal.Service.Error - ( ClientError(ClientHttpError, ClientHttpResponseError, ClientDecodeJsonError) - , ServiceError(ServiceBlockfrostError) - ) +import Ctl.Internal.Service.Error (ClientError(ClientHttpError, ClientHttpResponseError, ClientDecodeJsonError), ServiceError(ServiceBlockfrostError)) +import Ctl.Internal.Types.Rational (Rational) import Data.Bifunctor (lmap) import Data.BigInt (BigInt) import Data.Either (Either(Left, Right)) @@ -69,6 +71,7 @@ realizeEndpoint endpoint = GetCurrentEpoch -> "/epochs/latest" GetProtocolParams -> "/epochs/latest/parameters" + blockfrostGetRequest :: BlockfrostEndpoint -> BlockfrostServiceM (Either Affjax.Error (Affjax.Response String)) @@ -132,7 +135,69 @@ derive newtype instance DecodeAeson BlockfrostCurrentEpoch instance Show BlockfrostCurrentEpoch where show = genericShow +-- It has the same types as the QueryM.Ogmios.ProtocolParametersRaw +-- The one commented are the types whose blockfrost names I haven't found yet. +type BlockfrostProtocolParametersRaw = { + "protocol_major_ver": UInt, + "protocol_minor_ver": UInt, + "decentralisation_param": Rational, + "extra_entropy": Maybe Nonce, + "max_block_header_size": UInt, + "max_block_size": UInt, + "max_tx_size": UInt, +-- txFeeFixed +-- txFeePerByte + "key_deposit": BigInt, + "pool_deposit": BigInt, + "min_pool_cost": BigInt, +-- poolRetireMaxEpoch :: Epoch, +-- stakePoolTargetNum :: UInt, +-- poolPledgeInfluence :: Rational, +-- , monetaryExpansion :: Rational +-- , treasuryCut :: Rational + "coins_per_utxo_size": Maybe BigInt, + "coins_per_utxo_word": Maybe BigInt + "cost_models": { + "PlutusV1": { | Ogmios.CostModelV1 } +, + "PlutusV2": Maybe { | Ogmios.CostModelV2 } + }, + "price_mem": PParamRational, + "price_step": PParamRational, + "max_tx_ex_mem": BigInt, + "max_tx_ex_steps": BigInt, + "max_block_ex_mem": BigInt, + "max_block_ex_steps": BigInt, + "max_val_size": UInt, + "collateral_percent": UInt, + "max_collateral_inputs": UInt, + -- From here on I don't know If we need those or what's it name (and type) in the Ogmios.ProtocolParametersRaw + "epoch": 225, + "min_fee_a": 44, + "min_fee_b": 155381, + "e_max": 18, + "n_opt": 150, + "a0": 0.3, + "rho": 0.003, + "tau": 0.2, + "min_utxo": "1000000", + "nonce": "1a3be38bcbb7911969283716ad7aa550250226b76a61fc51cc9a9a35d9276d81", +} + getCurrentEpoch :: BlockfrostServiceM (Either ClientError BlockfrostCurrentEpoch) getCurrentEpoch = blockfrostGetRequest GetCurrentEpoch <#> handleBlockfrostResponse + +getProtocolParameters + :: BlockfrostServiceM (Either ClientError Ogmios.ProtocolParameters) +getProtocolParameters = do + rawDecoded <- blockfrostGetRequest GetCurrentEpoch + <#> handleBlockfrostResponse + let + maxTxUnits : ExUnits = {memory: rawDecoded.max_tx_ex_mem, steps: rawDecoded.max_tx_ex_steps} + maxBlocExUnits : ExUnits = {memory: rawDecoded.max_block_ex_mem, steps: rawDecoded.max_block_ex_steps} + decodePrices ps = note (TypeMismatch "ExUnitPrices") do + memPrice <- Ogmios.rationalToSubcoin rawDecoded.price_mem + stepPrice <- Ogmios.rationalToSubcoin rawDecoded.price_step + pure { memPrice, stepPrice } From 9c05c08537ae33baffe0c26b4126a6b822e90fca Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Tue, 3 Jan 2023 16:31:06 +0100 Subject: [PATCH 220/373] WIP: Implement getChainTip, getEraSummaries, getSystemStart BF queries --- src/Internal/Service/Blockfrost.purs | 144 +++++++++++++++++-- src/Internal/Types/EraSummaries.purs | 201 +++++++++++++++++++++++++++ 2 files changed, 335 insertions(+), 10 deletions(-) create mode 100644 src/Internal/Types/EraSummaries.purs diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index c8015bacb5..95bbaaf10b 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -1,35 +1,61 @@ module Ctl.Internal.Service.Blockfrost ( BlockfrostServiceM , BlockfrostServiceParams + , getChainTip + , getEraSummaries + , getSystemStart , runBlockfrostServiceM - , dummyExport ) where import Prelude -import Aeson (class DecodeAeson, decodeAeson, parseJsonStringToAeson) +import Aeson + ( class DecodeAeson + , Aeson + , JsonDecodeError(TypeMismatch) + , decodeAeson + , getField + , getFieldOptional' + , parseJsonStringToAeson + ) import Affjax (Error, Response, URL, defaultRequest, request) as Affjax import Affjax.RequestBody (RequestBody) as Affjax import Affjax.RequestHeader (RequestHeader(ContentType, RequestHeader)) as Affjax import Affjax.ResponseFormat (string) as Affjax.ResponseFormat import Affjax.StatusCode (StatusCode(StatusCode)) as Affjax +import Control.Monad.Except.Trans (ExceptT(ExceptT), runExceptT) import Control.Monad.Reader.Class (ask) import Control.Monad.Reader.Trans (ReaderT, runReaderT) import Ctl.Internal.Contract.QueryBackend (BlockfrostBackend) +import Ctl.Internal.QueryM.Ogmios (aesonObject) import Ctl.Internal.ServerConfig (ServerConfig, mkHttpUrl) import Ctl.Internal.Service.Error ( ClientError(ClientHttpError, ClientHttpResponseError, ClientDecodeJsonError) , ServiceError(ServiceBlockfrostError) ) +import Ctl.Internal.Service.Helpers (aesonArray) +import Ctl.Internal.Types.Chain (Tip(Tip, TipAtGenesis)) +import Ctl.Internal.Types.EraSummaries + ( EraSummaries + , EraSummary + , EraSummaryParameters + ) import Data.Bifunctor (lmap) -import Data.Either (Either(Left, Right)) +import Data.BigInt (toNumber) as BigInt +import Data.DateTime (DateTime) +import Data.DateTime.Instant (instant, toDateTime) +import Data.Either (Either(Left, Right), note) +import Data.Generic.Rep (class Generic) import Data.HTTP.Method (Method(GET, POST)) import Data.Maybe (Maybe, maybe) import Data.MediaType (MediaType) -import Data.Newtype (wrap) +import Data.Newtype (class Newtype, unwrap, wrap) +import Data.Show.Generic (genericShow) +import Data.Time.Duration (Seconds(Seconds), convertDuration) +import Data.Traversable (traverse) import Effect.Aff (Aff) import Effect.Aff.Class (liftAff) -import Undefined (undefined) +import Foreign.Object (Object) -------------------------------------------------------------------------------- -- BlockfrostServiceM @@ -57,15 +83,19 @@ runBlockfrostServiceM backend = flip runReaderT serviceParams -------------------------------------------------------------------------------- data BlockfrostEndpoint + -- /genesis + = GetBlockchainGenesis + -- /network/eras + | GetEraSummaries + -- /blocks/latest + | GetLatestBlock realizeEndpoint :: BlockfrostEndpoint -> Affjax.URL realizeEndpoint endpoint = case endpoint of - _ -> undefined - -dummyExport :: Unit -> Unit -dummyExport _ = undefined blockfrostGetRequest blockfrostPostRequest - (handleBlockfrostResponse undefined :: _ Int) + GetBlockchainGenesis -> "/genesis" + GetEraSummaries -> "/network/eras" + GetLatestBlock -> "/blocks/latest" blockfrostGetRequest :: BlockfrostEndpoint @@ -121,3 +151,97 @@ handleBlockfrostResponse (Right { status: Affjax.StatusCode statusCode, body }) body # lmap (ClientDecodeJsonError body) <<< (decodeAeson <=< parseJsonStringToAeson) +-------------------------------------------------------------------------------- +-- Get blockchain information +-------------------------------------------------------------------------------- + +getSystemStart :: BlockfrostServiceM (Either ClientError DateTime) +getSystemStart = runExceptT do + (systemStart :: BlockfrostSystemStart) <- + ExceptT $ handleBlockfrostResponse <$> + blockfrostGetRequest GetBlockchainGenesis + pure $ unwrap systemStart + +getChainTip :: BlockfrostServiceM (Either ClientError Tip) +getChainTip = runExceptT do + (chainTip :: BlockfrostChainTip) <- + ExceptT $ handleBlockfrostResponse <$> blockfrostGetRequest GetLatestBlock + pure $ unwrap chainTip + +getEraSummaries :: BlockfrostServiceM (Either ClientError EraSummaries) +getEraSummaries = runExceptT do + (eraSummaries :: BlockfrostEraSummaries) <- + ExceptT $ handleBlockfrostResponse <$> blockfrostGetRequest GetEraSummaries + pure $ unwrap eraSummaries + +-------------------------------------------------------------------------------- +-- BlockfrostSystemStart +-------------------------------------------------------------------------------- + +newtype BlockfrostSystemStart = BlockfrostSystemStart DateTime + +derive instance Generic BlockfrostSystemStart _ +derive instance Newtype BlockfrostSystemStart _ + +instance Show BlockfrostSystemStart where + show = genericShow + +instance DecodeAeson BlockfrostSystemStart where + decodeAeson = aesonObject \obj -> do + systemStart <- Seconds <<< BigInt.toNumber <$> getField obj "system_start" + note (TypeMismatch "Unix timestamp") + (wrap <<< toDateTime <$> instant (convertDuration systemStart)) + +-------------------------------------------------------------------------------- +-- BlockfrostChainTip +-------------------------------------------------------------------------------- + +newtype BlockfrostChainTip = BlockfrostChainTip Tip + +derive instance Generic BlockfrostChainTip _ +derive instance Newtype BlockfrostChainTip _ + +instance Show BlockfrostChainTip where + show = genericShow + +instance DecodeAeson BlockfrostChainTip where + decodeAeson = aesonObject \obj -> do + blockHeaderHash <- wrap <$> getField obj "hash" + getFieldOptional' obj "slot" + <#> wrap + <<< maybe TipAtGenesis (Tip <<< wrap <<< { blockHeaderHash, slot: _ }) + +-------------------------------------------------------------------------------- +-- BlockfrostEraSummaries +-------------------------------------------------------------------------------- + +newtype BlockfrostEraSummaries = BlockfrostEraSummaries EraSummaries + +derive instance Generic BlockfrostEraSummaries _ +derive instance Newtype BlockfrostEraSummaries _ + +instance Show BlockfrostEraSummaries where + show = genericShow + +instance DecodeAeson BlockfrostEraSummaries where + decodeAeson = aesonArray (map (wrap <<< wrap) <<< traverse decodeEraSummary) + where + decodeEraSummary :: Aeson -> Either JsonDecodeError EraSummary + decodeEraSummary = aesonObject \obj -> do + start <- getField obj "start" + end <- getField obj "end" + parameters <- decodeEraSummaryParameters =<< getField obj "parameters" + pure $ wrap { start, end, parameters } + + decodeEraSummaryParameters + :: Object Aeson -> Either JsonDecodeError EraSummaryParameters + decodeEraSummaryParameters obj = do + epochLength <- getField obj "epoch_length" + slotLength <- wrap <$> mul slotLengthFactor <$> getField obj "slot_length" + safeZone <- getField obj "safe_zone" + pure $ wrap { epochLength, slotLength, safeZone } + where + -- Blockfrost returns `slotLength` in seconds, and we use milliseconds, + -- so we need to convert between them. + slotLengthFactor :: Number + slotLengthFactor = 1000.0 diff --git a/src/Internal/Types/EraSummaries.purs b/src/Internal/Types/EraSummaries.purs new file mode 100644 index 0000000000..64bb5e7437 --- /dev/null +++ b/src/Internal/Types/EraSummaries.purs @@ -0,0 +1,201 @@ +module Ctl.Internal.Types.EraSummaries + ( Epoch(Epoch) + , EpochLength(EpochLength) + , EraSummaries(EraSummaries) + , EraSummary(EraSummary) + , EraSummaryParameters(EraSummaryParameters) + , EraSummaryTime(EraSummaryTime) + , RelativeTime(RelativeTime) + , SafeZone(SafeZone) + , SlotLength(SlotLength) + ) where + +import Prelude + +import Aeson + ( class DecodeAeson + , class EncodeAeson + , encodeAeson + , getField + , partialFiniteNumber + ) +import Ctl.Internal.Helpers (showWithParens) +import Ctl.Internal.Serialization.Address (Slot) +import Ctl.Internal.Service.Helpers (aesonObject) +import Data.BigInt (BigInt) +import Data.Generic.Rep (class Generic) +import Data.Maybe (Maybe) +import Data.Newtype (class Newtype, wrap) +import Data.Show.Generic (genericShow) +import Partial.Unsafe (unsafePartial) + +-------------------------------------------------------------------------------- +-- EraSummaries +-------------------------------------------------------------------------------- + +newtype EraSummaries = EraSummaries (Array EraSummary) + +derive instance Generic EraSummaries _ +derive instance Newtype EraSummaries _ +derive instance Eq EraSummaries + +instance Show EraSummaries where + show = genericShow + +-------------------------------------------------------------------------------- +-- EraSummary +-------------------------------------------------------------------------------- + +-- | start: Era bound which captures the time, slot and epoch at which the +-- | era starts, relative to the start of the network. +-- | +-- | end: Era bound which captures the time, slot and epoch at which the +-- | era ends, relative to the start of the network. +-- | +-- | parameters: Era parameters that can vary across hard forks. +newtype EraSummary = EraSummary + { start :: EraSummaryTime + , end :: Maybe EraSummaryTime + , parameters :: EraSummaryParameters + } + +derive instance Generic EraSummary _ +derive instance Newtype EraSummary _ +derive newtype instance Eq EraSummary + +instance Show EraSummary where + show = genericShow + +-------------------------------------------------------------------------------- +-- EraSummaryTime +-------------------------------------------------------------------------------- + +-- | time: Time in seconds relative to the start time of the network. +-- | +-- | slot: Absolute slot number. +-- | +-- | epoch: Epoch number. +newtype EraSummaryTime = EraSummaryTime + { time :: RelativeTime + , slot :: Slot + , epoch :: Epoch + } + +derive instance Generic EraSummaryTime _ +derive instance Newtype EraSummaryTime _ +derive newtype instance Eq EraSummaryTime + +instance Show EraSummaryTime where + show = genericShow + +instance DecodeAeson EraSummaryTime where + decodeAeson = aesonObject \obj -> do + time <- getField obj "time" + slot <- getField obj "slot" + epoch <- getField obj "epoch" + pure $ wrap { time, slot, epoch } + +instance EncodeAeson EraSummaryTime where + encodeAeson (EraSummaryTime { time, slot, epoch }) = + encodeAeson { "time": time, "slot": slot, "epoch": epoch } + +-------------------------------------------------------------------------------- +-- EraSummaryParameters +-------------------------------------------------------------------------------- + +-- | epochLength: Epoch length in number of slots. +-- | +-- | slotLength: Slot length in milliseconds. +-- | +-- | safe_zone: Zone in which it is guaranteed that no hard fork can take place. +newtype EraSummaryParameters = EraSummaryParameters + { epochLength :: EpochLength + , slotLength :: SlotLength + , safeZone :: SafeZone + } + +derive instance Generic EraSummaryParameters _ +derive instance Newtype EraSummaryParameters _ +derive newtype instance Eq EraSummaryParameters + +instance Show EraSummaryParameters where + show = genericShow + +-------------------------------------------------------------------------------- +-- RelativeTime, Epoch, EpochLength, SlotLength, SafeZone +-------------------------------------------------------------------------------- + +-- | A time in seconds relative to another one (typically, system start or era +-- | start). +newtype RelativeTime = RelativeTime Number + +derive instance Generic RelativeTime _ +derive instance Newtype RelativeTime _ +derive newtype instance Eq RelativeTime +derive newtype instance Ord RelativeTime +derive newtype instance DecodeAeson RelativeTime + +instance EncodeAeson RelativeTime where + encodeAeson (RelativeTime rt) = + -- We assume the numbers are finite. + encodeAeson $ unsafePartial partialFiniteNumber rt + +instance Show RelativeTime where + show (RelativeTime rt) = showWithParens "RelativeTime" rt + +-- | An epoch number or length with greater precision for Ogmios than +-- | `Cardano.Types.Epoch`. [ 0 .. 18446744073709552000 ] +newtype Epoch = Epoch BigInt + +derive instance Generic Epoch _ +derive instance Newtype Epoch _ +derive newtype instance Eq Epoch +derive newtype instance Ord Epoch +derive newtype instance DecodeAeson Epoch +derive newtype instance EncodeAeson Epoch + +instance Show Epoch where + show (Epoch epoch) = showWithParens "Epoch" epoch + +newtype EpochLength = EpochLength BigInt + +derive instance Generic EpochLength _ +derive instance Newtype EpochLength _ +derive newtype instance Eq EpochLength +derive newtype instance DecodeAeson EpochLength +derive newtype instance EncodeAeson EpochLength + +instance Show EpochLength where + show (EpochLength epochLength) = showWithParens "EpochLength" epochLength + +-- | A slot length, in milliseconds. +newtype SlotLength = SlotLength Number + +derive instance Generic SlotLength _ +derive instance Newtype SlotLength _ +derive newtype instance Eq SlotLength +derive newtype instance DecodeAeson SlotLength + +instance EncodeAeson SlotLength where + encodeAeson (SlotLength sl) = + -- We assume the numbers are finite. + encodeAeson $ unsafePartial partialFiniteNumber sl + +instance Show SlotLength where + show (SlotLength slotLength) = showWithParens "SlotLength" slotLength + +-- | Number of slots from the tip of the ledger in which it is guaranteed that +-- | no hard fork can take place. This should be (at least) the number of slots +-- | in which we are guaranteed to have k blocks. +newtype SafeZone = SafeZone BigInt + +derive instance Generic SafeZone _ +derive instance Newtype SafeZone _ +derive newtype instance Eq SafeZone +derive newtype instance Semiring SafeZone +derive newtype instance DecodeAeson SafeZone +derive newtype instance EncodeAeson SafeZone + +instance Show SafeZone where + show (SafeZone sz) = showWithParens "SafeZone" sz + From 535d7f789cedbe2bdf611886a8bd26fae4829bba Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Tue, 3 Jan 2023 21:17:08 +0000 Subject: [PATCH 221/373] Decode blockfrost protocol params --- src/Internal/Contract/QueryHandle.purs | 6 +- src/Internal/QueryM/Ogmios.purs | 1 + src/Internal/Service/Blockfrost.purs | 208 +++++++++++++++++-------- 3 files changed, 147 insertions(+), 68 deletions(-) diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs index d552981bd6..3d5a72a4bd 100644 --- a/src/Internal/Contract/QueryHandle.purs +++ b/src/Internal/Contract/QueryHandle.purs @@ -44,9 +44,11 @@ import Ctl.Internal.Serialization.Address (Address) import Ctl.Internal.Serialization.Hash (ScriptHash) import Ctl.Internal.Service.Blockfrost ( BlockfrostServiceM - , getCurrentEpoch , runBlockfrostServiceM ) +import Ctl.Internal.Service.Blockfrost + ( getCurrentEpoch + ) as Blockfrost import Ctl.Internal.Service.Error (ClientError) import Ctl.Internal.Types.Chain as Chain import Ctl.Internal.Types.Datum (DataHash, Datum) @@ -123,7 +125,7 @@ queryHandleForBlockfrostBackend _ backend = , getTxMetadata: runBlockfrostServiceM' <<< undefined , utxosAt: runBlockfrostServiceM' <<< undefined , getChainTip: runBlockfrostServiceM' undefined - , getCurrentEpoch: undefined $ runBlockfrostServiceM' getCurrentEpoch + , getCurrentEpoch: undefined $ runBlockfrostServiceM' Blockfrost.getCurrentEpoch , submitTx: runBlockfrostServiceM' <<< undefined , evaluateTx: \tx additionalUtxos -> runBlockfrostServiceM' $ undefined tx additionalUtxos diff --git a/src/Internal/QueryM/Ogmios.purs b/src/Internal/QueryM/Ogmios.purs index 6476a0838d..abd9d7123c 100644 --- a/src/Internal/QueryM/Ogmios.purs +++ b/src/Internal/QueryM/Ogmios.purs @@ -57,6 +57,7 @@ module Ctl.Internal.QueryM.Ogmios , acquireMempoolSnapshotCall , aesonArray , aesonObject + , convertCostModel , evaluateTxCall , queryPoolIdsCall , mempoolSnapshotHasTxCall diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index 60de099eb8..af35674eda 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -2,7 +2,7 @@ module Ctl.Internal.Service.Blockfrost ( BlockfrostServiceM , BlockfrostServiceParams , BlockfrostCurrentEpoch(BlockfrostCurrentEpoch) - , BlockfrostProtocolParameters(BlockfrostProtocolParameters) + -- , BlockfrostProtocolParameters(BlockfrostProtocolParameters) , runBlockfrostServiceM , getCurrentEpoch , getProtocolParameters @@ -10,29 +10,41 @@ module Ctl.Internal.Service.Blockfrost import Prelude -import Aeson (class DecodeAeson, decodeAeson, parseJsonStringToAeson) +import Aeson (class DecodeAeson, Finite, JsonDecodeError(..), decodeAeson, decodeJsonString, parseJsonStringToAeson, unpackFinite) import Affjax (Error, Response, URL, defaultRequest, request) as Affjax import Affjax.RequestBody (RequestBody) as Affjax import Affjax.RequestHeader (RequestHeader(ContentType, RequestHeader)) as Affjax import Affjax.ResponseFormat (string) as Affjax.ResponseFormat import Affjax.StatusCode (StatusCode(StatusCode)) as Affjax +import Control.Alt ((<|>)) +import Control.Monad.Except (ExceptT(ExceptT), runExceptT) import Control.Monad.Reader.Class (ask) import Control.Monad.Reader.Trans (ReaderT, runReaderT) +import Ctl.Internal.Cardano.Types.Transaction (Costmdls(..)) +import Ctl.Internal.Cardano.Types.Value (Coin(..)) import Ctl.Internal.Contract.QueryBackend (BlockfrostBackend) -import Ctl.Internal.QueryM.Ogmios (PParamRational(..)) +import Ctl.Internal.QueryM.Ogmios (CoinsPerUtxoUnit(..), CostModelV1, CostModelV2, Epoch(..), ProtocolParameters(..), rationalToSubcoin, convertCostModel) import Ctl.Internal.QueryM.Ogmios as Ogmios import Ctl.Internal.ServerConfig (ServerConfig, mkHttpUrl) import Ctl.Internal.Service.Error (ClientError(ClientHttpError, ClientHttpResponseError, ClientDecodeJsonError), ServiceError(ServiceBlockfrostError)) -import Ctl.Internal.Types.Rational (Rational) +import Ctl.Internal.Types.Rational (Rational, reduce) +import Ctl.Internal.Types.Scripts (Language(..)) import Data.Bifunctor (lmap) import Data.BigInt (BigInt) -import Data.Either (Either(Left, Right)) +import Data.BigInt as BigInt +import Data.BigNumber (BigNumber, toFraction) +import Data.BigNumber as BigNumber +import Data.Either (Either(Left, Right), note) import Data.Generic.Rep (class Generic) import Data.HTTP.Method (Method(GET, POST)) -import Data.Maybe (Maybe, maybe) +import Data.Map as Map +import Data.Maybe (Maybe(..), maybe) import Data.MediaType (MediaType) -import Data.Newtype (class Newtype, wrap) +import Data.Newtype (class Newtype, unwrap, wrap) +import Data.Number (infinity) import Data.Show.Generic (genericShow) +import Data.Tuple.Nested ((/\)) +import Data.UInt (UInt) import Effect.Aff (Aff) import Effect.Aff.Class (liftAff) @@ -71,7 +83,6 @@ realizeEndpoint endpoint = GetCurrentEpoch -> "/epochs/latest" GetProtocolParams -> "/epochs/latest/parameters" - blockfrostGetRequest :: BlockfrostEndpoint -> BlockfrostServiceM (Either Affjax.Error (Affjax.Response String)) @@ -135,54 +146,125 @@ derive newtype instance DecodeAeson BlockfrostCurrentEpoch instance Show BlockfrostCurrentEpoch where show = genericShow --- It has the same types as the QueryM.Ogmios.ProtocolParametersRaw --- The one commented are the types whose blockfrost names I haven't found yet. -type BlockfrostProtocolParametersRaw = { - "protocol_major_ver": UInt, - "protocol_minor_ver": UInt, - "decentralisation_param": Rational, - "extra_entropy": Maybe Nonce, - "max_block_header_size": UInt, - "max_block_size": UInt, - "max_tx_size": UInt, --- txFeeFixed --- txFeePerByte - "key_deposit": BigInt, - "pool_deposit": BigInt, - "min_pool_cost": BigInt, --- poolRetireMaxEpoch :: Epoch, --- stakePoolTargetNum :: UInt, --- poolPledgeInfluence :: Rational, --- , monetaryExpansion :: Rational --- , treasuryCut :: Rational - "coins_per_utxo_size": Maybe BigInt, - "coins_per_utxo_word": Maybe BigInt - "cost_models": { - "PlutusV1": { | Ogmios.CostModelV1 } -, - "PlutusV2": Maybe { | Ogmios.CostModelV2 } - }, - "price_mem": PParamRational, - "price_step": PParamRational, - "max_tx_ex_mem": BigInt, - "max_tx_ex_steps": BigInt, - "max_block_ex_mem": BigInt, - "max_block_ex_steps": BigInt, - "max_val_size": UInt, - "collateral_percent": UInt, - "max_collateral_inputs": UInt, - -- From here on I don't know If we need those or what's it name (and type) in the Ogmios.ProtocolParametersRaw - "epoch": 225, - "min_fee_a": 44, - "min_fee_b": 155381, - "e_max": 18, - "n_opt": 150, - "a0": 0.3, - "rho": 0.003, - "tau": 0.2, - "min_utxo": "1000000", - "nonce": "1a3be38bcbb7911969283716ad7aa550250226b76a61fc51cc9a9a35d9276d81", -} +-- | `Stringed a` decodes an `a` who was encoded as a `String` +newtype Stringed a = Stringed a + +derive instance Newtype (Stringed a) _ + +instance DecodeAeson a => DecodeAeson (Stringed a) where + decodeAeson = decodeAeson >=> decodeJsonString >=> Stringed >>> pure + +type BlockfrostProtocolParametersRaw = + --{ "epoch" :: BigInt + { "min_fee_a" :: UInt -- minFeeCoefficient + , "min_fee_b" :: UInt -- minFeeConstant + , "max_block_size" :: UInt -- maxBlockBodySize + , "max_tx_size" :: UInt -- maxTxSize + , "max_block_header_size" :: UInt -- maxBlockHeaderSize + , "key_deposit" :: Stringed BigInt -- stakeKeyDeposit + , "pool_deposit" :: Stringed BigInt -- poolDeposit + , "e_max" :: BigInt -- poolRetirementEpochBound + , "n_opt" :: UInt -- desiredNumberOfPools + , "a0" :: Finite BigNumber -- poolInfluence + , "rho" :: Finite BigNumber -- monetaryExpansion + , "tau" :: Finite BigNumber -- treasuryExpansion + -- Deprecated in Babbage + -- , "decentralisation_param" + -- , "extra_entropy" + , "protocol_major_ver" :: UInt -- protocolVersion.major + , "protocol_minor_ver" :: UInt -- protocolVersion.minor + -- Deprecated in Alonzo + -- , "min_utxo" + , "min_pool_cost" :: Stringed BigInt -- minPoolCost + -- , "nonce" :: String -- No ogmios version + , "cost_models" :: + { "PlutusV1" :: { | CostModelV1 } + , "PlutusV2" :: { | CostModelV2 } + } + , "price_mem" :: Finite BigNumber -- prices.memory + , "price_step" :: Finite BigNumber -- prices.steps + , "max_tx_ex_mem" :: Stringed BigInt -- maxExecutionUnitsPerTransaction.memory + , "max_tx_ex_steps" :: Stringed BigInt -- maxExecutionUnitsPerTransaction.steps + , "max_block_ex_mem" :: Stringed BigInt -- maxExecutionUnitsPerBlock.memory + , "max_block_ex_steps" :: Stringed BigInt -- maxExecutionUnitsPerBlock.steps + , "max_val_size" :: Stringed UInt -- maxValueSize + , "collateral_percent" :: UInt -- collateralPercentage + , "max_collateral_inputs" :: UInt -- maxCollateralInputs + , "coins_per_utxo_size" :: Maybe (Stringed BigInt) -- coinsPerUtxoByte + , "coins_per_utxo_word" :: Maybe (Stringed BigInt) -- coinsPerUtxoWord + } + +bigNumberToRational :: BigNumber -> Maybe Rational +bigNumberToRational bn = do + let (numerator' /\ denominator') = toFraction bn (BigNumber.fromNumber infinity) + numerator <- BigInt.fromString numerator' + denominator <- BigInt.fromString denominator' + reduce numerator denominator + +bigNumberToRational' :: BigNumber -> Either JsonDecodeError Rational +bigNumberToRational' = note (TypeMismatch "Rational") <<< bigNumberToRational + +newtype BlockfrostProtocolParameters = + BlockfrostProtocolParameters ProtocolParameters + +instance DecodeAeson BlockfrostProtocolParameters where + decodeAeson = decodeAeson >=> \(raw :: BlockfrostProtocolParametersRaw) -> do + poolPledgeInfluence <- bigNumberToRational' $ unpackFinite raw.a0 + monetaryExpansion <- bigNumberToRational' $ unpackFinite raw.rho + treasuryCut <- bigNumberToRational' $ unpackFinite raw.tau + prices <- do + let + convert bn = do + rational <- bigNumberToRational $ unpackFinite bn + rationalToSubcoin $ wrap rational + + memPrice <- note (TypeMismatch "Rational") $ convert raw.price_mem + stepPrice <- note (TypeMismatch "Rational") $ convert raw.price_step + pure { memPrice, stepPrice } + + coinsPerUtxoUnit <- + maybe + (Left $ AtKey "coinsPerUtxoByte or coinsPerUtxoWord" $ MissingValue) + pure + $ (CoinsPerUtxoByte <<< Coin <<< unwrap <$> raw.coins_per_utxo_size) <|> + (CoinsPerUtxoWord <<< Coin <<< unwrap <$> raw.coins_per_utxo_word) + + pure $ BlockfrostProtocolParameters $ ProtocolParameters + { protocolVersion: raw.protocol_major_ver /\ raw.protocol_minor_ver + -- The following two parameters were removed from Babbage + , decentralization: zero + , extraPraosEntropy: Nothing + , maxBlockHeaderSize: raw.max_block_header_size + , maxBlockBodySize: raw.max_block_size + , maxTxSize: raw.max_tx_size + , txFeeFixed: raw.min_fee_b + , txFeePerByte: raw.min_fee_a + , stakeAddressDeposit: Coin $ unwrap raw.key_deposit + , stakePoolDeposit: Coin $ unwrap raw.pool_deposit + , minPoolCost: Coin $ unwrap raw.min_pool_cost + , poolRetireMaxEpoch: Epoch raw.e_max + , stakePoolTargetNum: raw.n_opt + , poolPledgeInfluence + , monetaryExpansion + , treasuryCut + , coinsPerUtxoUnit: coinsPerUtxoUnit + , costModels: Costmdls $ Map.fromFoldable + [ PlutusV1 /\ convertCostModel raw.cost_models."PlutusV1" + , PlutusV2 /\ convertCostModel raw.cost_models."PlutusV2" + ] + , prices + , maxTxExUnits: + { mem: unwrap raw.max_tx_ex_mem + , steps: unwrap raw.max_tx_ex_steps + } + , maxBlockExUnits: + { mem: unwrap raw.max_block_ex_mem + , steps: unwrap raw.max_block_ex_steps + } + , maxValueSize: unwrap raw.max_val_size + , collateralPercent: raw.collateral_percent + , maxCollateralInputs: raw.max_collateral_inputs + } getCurrentEpoch :: BlockfrostServiceM (Either ClientError BlockfrostCurrentEpoch) @@ -191,13 +273,7 @@ getCurrentEpoch = blockfrostGetRequest GetCurrentEpoch getProtocolParameters :: BlockfrostServiceM (Either ClientError Ogmios.ProtocolParameters) -getProtocolParameters = do - rawDecoded <- blockfrostGetRequest GetCurrentEpoch - <#> handleBlockfrostResponse - let - maxTxUnits : ExUnits = {memory: rawDecoded.max_tx_ex_mem, steps: rawDecoded.max_tx_ex_steps} - maxBlocExUnits : ExUnits = {memory: rawDecoded.max_block_ex_mem, steps: rawDecoded.max_block_ex_steps} - decodePrices ps = note (TypeMismatch "ExUnitPrices") do - memPrice <- Ogmios.rationalToSubcoin rawDecoded.price_mem - stepPrice <- Ogmios.rationalToSubcoin rawDecoded.price_step - pure { memPrice, stepPrice } +getProtocolParameters = runExceptT do + BlockfrostProtocolParameters params <- ExceptT $ + blockfrostGetRequest GetProtocolParams <#> handleBlockfrostResponse + pure params From 415cc5ea75f32e0289dd6cf21b3418cbb6a60027 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Tue, 3 Jan 2023 21:19:58 +0000 Subject: [PATCH 222/373] Remove comments --- src/Internal/Service/Blockfrost.purs | 61 ++++++++++++---------------- 1 file changed, 27 insertions(+), 34 deletions(-) diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index af35674eda..002cc2b95f 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -2,7 +2,7 @@ module Ctl.Internal.Service.Blockfrost ( BlockfrostServiceM , BlockfrostServiceParams , BlockfrostCurrentEpoch(BlockfrostCurrentEpoch) - -- , BlockfrostProtocolParameters(BlockfrostProtocolParameters) + , BlockfrostProtocolParameters(BlockfrostProtocolParameters) , runBlockfrostServiceM , getCurrentEpoch , getProtocolParameters @@ -155,43 +155,36 @@ instance DecodeAeson a => DecodeAeson (Stringed a) where decodeAeson = decodeAeson >=> decodeJsonString >=> Stringed >>> pure type BlockfrostProtocolParametersRaw = - --{ "epoch" :: BigInt - { "min_fee_a" :: UInt -- minFeeCoefficient - , "min_fee_b" :: UInt -- minFeeConstant - , "max_block_size" :: UInt -- maxBlockBodySize - , "max_tx_size" :: UInt -- maxTxSize - , "max_block_header_size" :: UInt -- maxBlockHeaderSize - , "key_deposit" :: Stringed BigInt -- stakeKeyDeposit - , "pool_deposit" :: Stringed BigInt -- poolDeposit - , "e_max" :: BigInt -- poolRetirementEpochBound - , "n_opt" :: UInt -- desiredNumberOfPools - , "a0" :: Finite BigNumber -- poolInfluence - , "rho" :: Finite BigNumber -- monetaryExpansion - , "tau" :: Finite BigNumber -- treasuryExpansion - -- Deprecated in Babbage - -- , "decentralisation_param" - -- , "extra_entropy" - , "protocol_major_ver" :: UInt -- protocolVersion.major - , "protocol_minor_ver" :: UInt -- protocolVersion.minor - -- Deprecated in Alonzo - -- , "min_utxo" - , "min_pool_cost" :: Stringed BigInt -- minPoolCost - -- , "nonce" :: String -- No ogmios version + { "min_fee_a" :: UInt + , "min_fee_b" :: UInt + , "max_block_size" :: UInt + , "max_tx_size" :: UInt + , "max_block_header_size" :: UInt + , "key_deposit" :: Stringed BigInt + , "pool_deposit" :: Stringed BigInt + , "e_max" :: BigInt + , "n_opt" :: UInt + , "a0" :: Finite BigNumber + , "rho" :: Finite BigNumber + , "tau" :: Finite BigNumber + , "protocol_major_ver" :: UInt + , "protocol_minor_ver" :: UInt + , "min_pool_cost" :: Stringed BigInt , "cost_models" :: { "PlutusV1" :: { | CostModelV1 } , "PlutusV2" :: { | CostModelV2 } } - , "price_mem" :: Finite BigNumber -- prices.memory - , "price_step" :: Finite BigNumber -- prices.steps - , "max_tx_ex_mem" :: Stringed BigInt -- maxExecutionUnitsPerTransaction.memory - , "max_tx_ex_steps" :: Stringed BigInt -- maxExecutionUnitsPerTransaction.steps - , "max_block_ex_mem" :: Stringed BigInt -- maxExecutionUnitsPerBlock.memory - , "max_block_ex_steps" :: Stringed BigInt -- maxExecutionUnitsPerBlock.steps - , "max_val_size" :: Stringed UInt -- maxValueSize - , "collateral_percent" :: UInt -- collateralPercentage - , "max_collateral_inputs" :: UInt -- maxCollateralInputs - , "coins_per_utxo_size" :: Maybe (Stringed BigInt) -- coinsPerUtxoByte - , "coins_per_utxo_word" :: Maybe (Stringed BigInt) -- coinsPerUtxoWord + , "price_mem" :: Finite BigNumber + , "price_step" :: Finite BigNumber + , "max_tx_ex_mem" :: Stringed BigInt + , "max_tx_ex_steps" :: Stringed BigInt + , "max_block_ex_mem" :: Stringed BigInt + , "max_block_ex_steps" :: Stringed BigInt + , "max_val_size" :: Stringed UInt + , "collateral_percent" :: UInt + , "max_collateral_inputs" :: UInt + , "coins_per_utxo_size" :: Maybe (Stringed BigInt) + , "coins_per_utxo_word" :: Maybe (Stringed BigInt) } bigNumberToRational :: BigNumber -> Maybe Rational From 9401c3b2260b9042cbf858bf5cfb4d40369222db Mon Sep 17 00:00:00 2001 From: Gregory Gerasev Date: Wed, 4 Jan 2023 06:57:49 +0400 Subject: [PATCH 223/373] Blockfrost realization for getDatumByHash and getScriptByHash --- src/Internal/Contract/QueryHandle.purs | 5 +- .../Deserialization/NativeScript.purs | 13 ++ src/Internal/QueryM/Kupo.purs | 32 +--- src/Internal/Service/Blockfrost.purs | 149 +++++++++++++++++- src/Internal/Service/Helpers.purs | 9 ++ test/Blockfrost.purs | 66 ++++++++ 6 files changed, 236 insertions(+), 38 deletions(-) create mode 100644 test/Blockfrost.purs diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs index b742f34328..d3782e1435 100644 --- a/src/Internal/Contract/QueryHandle.purs +++ b/src/Internal/Contract/QueryHandle.purs @@ -46,6 +46,7 @@ import Ctl.Internal.Service.Blockfrost ( BlockfrostServiceM , runBlockfrostServiceM ) +import Ctl.Internal.Service.Blockfrost as Blockfrost import Ctl.Internal.Service.Error (ClientError) import Ctl.Internal.Types.Chain as Chain import Ctl.Internal.Types.Datum (DataHash, Datum) @@ -115,8 +116,8 @@ queryHandleForCtlBackend contractEnv backend = queryHandleForBlockfrostBackend :: ContractEnv -> BlockfrostBackend -> QueryHandle queryHandleForBlockfrostBackend _ backend = - { getDatumByHash: runBlockfrostServiceM' <<< undefined - , getScriptByHash: runBlockfrostServiceM' <<< undefined + { getDatumByHash: runBlockfrostServiceM' <<< Blockfrost.getDatumByHash + , getScriptByHash: runBlockfrostServiceM' <<< Blockfrost.getScriptByHash , getUtxoByOref: runBlockfrostServiceM' <<< undefined , isTxConfirmed: runBlockfrostServiceM' <<< undefined , getTxMetadata: runBlockfrostServiceM' <<< undefined diff --git a/src/Internal/Deserialization/NativeScript.purs b/src/Internal/Deserialization/NativeScript.purs index ff5c2dd591..43d9ab3050 100644 --- a/src/Internal/Deserialization/NativeScript.purs +++ b/src/Internal/Deserialization/NativeScript.purs @@ -1,10 +1,13 @@ module Ctl.Internal.Deserialization.NativeScript ( convertNativeScript + , decodeNativeScript ) where import Prelude +import Aeson (JsonDecodeError(TypeMismatch)) import Ctl.Internal.Cardano.Types.NativeScript as T +import Ctl.Internal.Deserialization.FromBytes (fromBytes) import Ctl.Internal.FfiHelpers ( ContainerHelper , containerHelper @@ -21,6 +24,9 @@ import Ctl.Internal.Serialization.Types , TimelockStart ) import Ctl.Internal.Types.BigNum (BigNum) +import Ctl.Internal.Types.ByteArray (ByteArray) +import Data.Either (Either, note) +import Data.Newtype (wrap) type ConvertNativeScript (r :: Type) = { scriptPubkey :: ScriptPubkey -> r @@ -31,6 +37,13 @@ type ConvertNativeScript (r :: Type) = , timelockExpiry :: TimelockExpiry -> r } +decodeNativeScript :: ByteArray -> Either JsonDecodeError T.NativeScript +decodeNativeScript scriptBytes = do + nativeScript <- + flip note (fromBytes $ wrap scriptBytes) $ + TypeMismatch "decodeNativeScript: from_bytes() call failed" + pure $ convertNativeScript nativeScript + convertNativeScript :: NativeScript -> T.NativeScript convertNativeScript ns = _convertNativeScript { scriptPubkey: T.ScriptPubkey <<< scriptPubkey_addr_keyhash diff --git a/src/Internal/QueryM/Kupo.purs b/src/Internal/QueryM/Kupo.purs index 6e8ab86590..705111ec51 100644 --- a/src/Internal/QueryM/Kupo.purs +++ b/src/Internal/QueryM/Kupo.purs @@ -16,7 +16,6 @@ import Aeson , JsonDecodeError(TypeMismatch) , caseAesonArray , caseAesonObject - , caseAesonString , decodeAeson , getField , getFieldOptional @@ -46,7 +45,7 @@ import Ctl.Internal.Cardano.Types.Value , mkValue ) import Ctl.Internal.Deserialization.FromBytes (fromBytes) -import Ctl.Internal.Deserialization.NativeScript (convertNativeScript) +import Ctl.Internal.Deserialization.NativeScript (decodeNativeScript) import Ctl.Internal.Deserialization.PlutusData (deserializeData) import Ctl.Internal.Deserialization.Transaction ( convertGeneralTransactionMetadata @@ -61,6 +60,7 @@ import Ctl.Internal.Serialization.Address import Ctl.Internal.Serialization.Hash (ScriptHash, scriptHashToBytes) import Ctl.Internal.ServerConfig (ServerConfig, mkHttpUrl) import Ctl.Internal.Service.Error (ClientError(ClientOtherError)) +import Ctl.Internal.Service.Helpers (aesonArray, aesonObject, aesonString) import Ctl.Internal.Types.BigNum (toString) as BigNum import Ctl.Internal.Types.ByteArray (ByteArray, byteArrayToHex, hexToByteArray) import Ctl.Internal.Types.CborBytes (hexToCborBytes) @@ -388,13 +388,6 @@ instance DecodeAeson KupoScriptRef where pure $ PlutusScriptRef $ plutusV1Script scriptBytes PlutusV2Script -> pure $ PlutusScriptRef $ plutusV2Script scriptBytes - where - decodeNativeScript :: ByteArray -> Either JsonDecodeError NativeScript - decodeNativeScript scriptBytes = do - nativeScript <- - flip note (fromBytes $ wrap scriptBytes) $ - TypeMismatch "decodeNativeScript: from_bytes() call failed" - pure $ convertNativeScript nativeScript ------------------------------------------------------------------------------- -- `isTxConfirmed` response parsing @@ -463,24 +456,3 @@ kupoGetRequestAff config endpoint = do , url = mkHttpUrl config <> endpoint , responseFormat = Affjax.ResponseFormat.string } - -aesonArray - :: forall (a :: Type) - . (Array Aeson -> Either JsonDecodeError a) - -> Aeson - -> Either JsonDecodeError a -aesonArray = caseAesonArray (Left (TypeMismatch "Expected Array")) - -aesonObject - :: forall (a :: Type) - . (Object Aeson -> Either JsonDecodeError a) - -> Aeson - -> Either JsonDecodeError a -aesonObject = caseAesonObject (Left (TypeMismatch "Expected Object")) - -aesonString - :: forall (a :: Type) - . (String -> Either JsonDecodeError a) - -> Aeson - -> Either JsonDecodeError a -aesonString = caseAesonString (Left (TypeMismatch "Expected String")) diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index 65c990840b..4c91b5fabc 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -2,33 +2,57 @@ module Ctl.Internal.Service.Blockfrost ( BlockfrostServiceM , BlockfrostServiceParams , runBlockfrostServiceM + , getDatumByHash + , getScriptByHash ) where import Prelude -import Aeson (class DecodeAeson, decodeAeson, parseJsonStringToAeson) +import Aeson + ( class DecodeAeson + , JsonDecodeError(TypeMismatch, AtKey, MissingValue) + , decodeAeson + , getFieldOptional + , isNull + , parseJsonStringToAeson + ) import Affjax (Error, Response, URL, defaultRequest, request) as Affjax import Affjax.RequestBody (RequestBody) as Affjax import Affjax.RequestHeader (RequestHeader(ContentType, RequestHeader)) as Affjax import Affjax.ResponseFormat (string) as Affjax.ResponseFormat import Affjax.StatusCode (StatusCode(StatusCode)) as Affjax +import Control.Monad.Except.Trans (ExceptT(ExceptT), runExceptT) +import Control.Monad.Maybe.Trans (MaybeT(MaybeT), runMaybeT) import Control.Monad.Reader.Class (ask) import Control.Monad.Reader.Trans (ReaderT, runReaderT) +import Ctl.Internal.Cardano.Types.ScriptRef + ( ScriptRef(NativeScriptRef, PlutusScriptRef) + ) import Ctl.Internal.Contract.QueryBackend (BlockfrostBackend) +import Ctl.Internal.Deserialization.NativeScript (decodeNativeScript) +import Ctl.Internal.Deserialization.PlutusData (deserializeData) +import Ctl.Internal.Serialization.Hash (ScriptHash, scriptHashToBytes) import Ctl.Internal.ServerConfig (ServerConfig, mkHttpUrl) import Ctl.Internal.Service.Error ( ClientError(ClientHttpError, ClientHttpResponseError, ClientDecodeJsonError) , ServiceError(ServiceBlockfrostError) ) +import Ctl.Internal.Service.Helpers (aesonObject, aesonString) +import Ctl.Internal.Types.ByteArray (ByteArray, byteArrayToHex) +import Ctl.Internal.Types.CborBytes (CborBytes) +import Ctl.Internal.Types.Datum (DataHash(DataHash), Datum) +import Ctl.Internal.Types.RawBytes (rawBytesToHex) +import Ctl.Internal.Types.Scripts (plutusV1Script, plutusV2Script) import Data.Bifunctor (lmap) -import Data.Either (Either(Left, Right)) +import Data.Either (Either(Left, Right), note) +import Data.Generic.Rep (class Generic) import Data.HTTP.Method (Method(GET, POST)) -import Data.Maybe (Maybe, maybe) +import Data.Maybe (Maybe(Nothing, Just), maybe) import Data.MediaType (MediaType) -import Data.Newtype (wrap) +import Data.Newtype (class Newtype, unwrap, wrap) +import Data.Show.Generic (genericShow) import Effect.Aff (Aff) import Effect.Aff.Class (liftAff) -import Undefined (undefined) -------------------------------------------------------------------------------- -- BlockfrostServiceM @@ -56,11 +80,22 @@ runBlockfrostServiceM backend = flip runReaderT serviceParams -------------------------------------------------------------------------------- data BlockfrostEndpoint + -- /scripts/datum/{datum_hash}/cbor + = GetDatumCbor DataHash + -- /scripts/{script_hash} + | GetScriptInfo ScriptHash + -- /scripts/{script_hash}/cbor + | GetScriptCbor ScriptHash realizeEndpoint :: BlockfrostEndpoint -> Affjax.URL realizeEndpoint endpoint = case endpoint of - _ -> undefined + GetDatumCbor (DataHash hashBytes) -> + "/scripts/datum/" <> byteArrayToHex hashBytes <> "/cbor" + GetScriptInfo scriptHash -> + "/scripts/" <> rawBytesToHex (scriptHashToBytes scriptHash) + GetScriptCbor scriptHash -> + "/scripts/" <> rawBytesToHex (scriptHashToBytes scriptHash) <> "/cbor" blockfrostGetRequest :: BlockfrostEndpoint @@ -116,3 +151,105 @@ handleBlockfrostResponse (Right { status: Affjax.StatusCode statusCode, body }) body # lmap (ClientDecodeJsonError body) <<< (decodeAeson <=< parseJsonStringToAeson) +handle404AsNothing + :: forall x. Either ClientError (Maybe x) -> Either ClientError (Maybe x) +handle404AsNothing (Left (ClientHttpResponseError (Affjax.StatusCode 404) _)) = + Right Nothing +handle404AsNothing x = x + +getDatumByHash + :: DataHash -> BlockfrostServiceM (Either ClientError (Maybe Datum)) +getDatumByHash dataHash = do + response <- blockfrostGetRequest (GetDatumCbor dataHash) + pure $ handle404AsNothing $ unwrapBlockfrostDatum <$> handleBlockfrostResponse + response + +getScriptInfo + :: ScriptHash + -> BlockfrostServiceM (Either ClientError (Maybe BlockfrostScriptInfo)) +getScriptInfo scriptHash = do + response <- blockfrostGetRequest (GetScriptInfo scriptHash) + pure $ handle404AsNothing $ handleBlockfrostResponse response + +getScriptByHash + :: ScriptHash -> BlockfrostServiceM (Either ClientError (Maybe ScriptRef)) +getScriptByHash scriptHash = runExceptT $ runMaybeT do + info <- MaybeT $ ExceptT $ getScriptInfo scriptHash + cbor <- MaybeT $ ExceptT $ do + response <- blockfrostGetRequest (GetScriptCbor scriptHash) + pure $ handle404AsNothing $ unwrapBlockfrostCbor <$> + handleBlockfrostResponse response + let + script = lmap (ClientDecodeJsonError "Error decoding script") $ + wrapScriptType (scriptInfoType info) cbor + MaybeT $ ExceptT $ pure $ Just <$> script + where + wrapScriptType scriptType x = case scriptType of + NativeScript -> NativeScriptRef <$> decodeNativeScript x + PlutusV1Script -> pure $ PlutusScriptRef $ plutusV1Script x + PlutusV2Script -> pure $ PlutusScriptRef $ plutusV2Script x + +-------------------------------------------------------------------------------- +-- `getDatumByHash` response parsing +-------------------------------------------------------------------------------- + +newtype BlockfrostDatum = BlockfrostDatum (Maybe Datum) + +derive instance Newtype BlockfrostDatum _ + +unwrapBlockfrostDatum :: BlockfrostDatum -> Maybe Datum +unwrapBlockfrostDatum = unwrap + +instance DecodeAeson BlockfrostDatum where + decodeAeson aeson + | isNull aeson = pure $ BlockfrostDatum Nothing + | otherwise = do + cbor <- aesonObject (flip getFieldOptional "cbor") aeson + pure $ BlockfrostDatum $ deserializeData =<< cbor + +-------------------------------------------------------------------------------- +-- `getScriptByHash` response parsing +-------------------------------------------------------------------------------- + +data BlockfrostScriptLanguage = NativeScript | PlutusV1Script | PlutusV2Script + +derive instance Generic BlockfrostScriptLanguage _ + +instance Show BlockfrostScriptLanguage where + show = genericShow + +instance DecodeAeson BlockfrostScriptLanguage where + decodeAeson = aesonString $ case _ of + "native" -> pure NativeScript + "plutusV1" -> pure PlutusV1Script + "plutusV2" -> pure PlutusV2Script + invalid -> + Left $ TypeMismatch $ + "language: expected 'native' or 'plutusV{1|2}', got: " <> invalid + +-- Do not parse fields other than `type`, cuz we do not need them yet +data BlockfrostScriptInfo = BlockfrostScriptInfo + { type :: BlockfrostScriptLanguage } + +instance DecodeAeson BlockfrostScriptInfo where + decodeAeson aeson = do + mType <- aesonObject (flip getFieldOptional "type") aeson + type_ <- note (AtKey "type" MissingValue) mType + pure $ BlockfrostScriptInfo { type: type_ } + +scriptInfoType :: BlockfrostScriptInfo -> BlockfrostScriptLanguage +scriptInfoType (BlockfrostScriptInfo info) = info.type + +newtype BlockfrostCbor = BlockfrostCbor (Maybe ByteArray) + +derive instance Newtype BlockfrostCbor _ + +unwrapBlockfrostCbor :: BlockfrostCbor -> Maybe ByteArray +unwrapBlockfrostCbor = unwrap + +instance DecodeAeson BlockfrostCbor where + decodeAeson aeson + | isNull aeson = pure $ BlockfrostCbor Nothing + | otherwise = do + cbor <- aesonObject (flip getFieldOptional "cbor") aeson + pure $ BlockfrostCbor cbor diff --git a/src/Internal/Service/Helpers.purs b/src/Internal/Service/Helpers.purs index 8cbac75c5e..8e389cccba 100644 --- a/src/Internal/Service/Helpers.purs +++ b/src/Internal/Service/Helpers.purs @@ -1,5 +1,6 @@ module Ctl.Internal.Service.Helpers ( aesonArray + , aesonString , aesonObject , decodeAssetClass ) where @@ -11,6 +12,7 @@ import Aeson , JsonDecodeError(TypeMismatch) , caseAesonArray , caseAesonObject + , caseAesonString ) import Control.Apply (lift2) import Ctl.Internal.Cardano.Types.Value (CurrencySymbol, mkCurrencySymbol) @@ -35,6 +37,13 @@ aesonObject -> Either JsonDecodeError a aesonObject = caseAesonObject (Left (TypeMismatch "Object")) +aesonString + :: forall (a :: Type) + . (String -> Either JsonDecodeError a) + -> Aeson + -> Either JsonDecodeError a +aesonString = caseAesonString (Left (TypeMismatch "String")) + decodeAssetClass :: String -> String diff --git a/test/Blockfrost.purs b/test/Blockfrost.purs new file mode 100644 index 0000000000..1a48e85ea8 --- /dev/null +++ b/test/Blockfrost.purs @@ -0,0 +1,66 @@ +module Test.Ctl.Blockfrost (main, testPlan) where + +import Prelude + +import Contract.Config (blockfrostPublicPreviewServerConfig) +import Contract.Prim.ByteArray (hexToByteArrayUnsafe) +import Contract.Test.Mote (TestPlanM, interpretWithConfig) +import Contract.Transaction (DataHash) +import Ctl.Internal.Contract.QueryBackend (BlockfrostBackend) +import Ctl.Internal.Helpers (liftedM) +import Ctl.Internal.Serialization.Hash (ScriptHash, scriptHashFromBytes) +import Ctl.Internal.Service.Blockfrost + ( getDatumByHash + , getScriptByHash + , runBlockfrostServiceM + ) +import Data.Array ((!!)) +import Data.Either (fromRight, isRight) +import Data.Maybe (Maybe(Just, Nothing), fromJust) +import Data.Newtype (wrap) +import Effect (Effect) +import Effect.Aff (Aff, error, launchAff_) +import Mote (group, test) +import Node.Process (argv) +import Partial.Unsafe (unsafePartial) +import Test.Spec.Assertions (shouldEqual, shouldSatisfy) +import Test.Spec.Runner (defaultConfig) + +-- Run with `spago test --main Test.Ctl.Blockfrost --exec-args PREVIEW_API_KEY` +main :: Effect Unit +main = do + apiKey <- liftedM (error "ApiKey not supplied") $ (_ !! 1) <$> argv + launchAff_ do + interpretWithConfig + defaultConfig { exit = true } + ( testPlan + { blockfrostConfig: blockfrostPublicPreviewServerConfig + , blockfrostApiKey: Just apiKey + } + ) + +testPlan :: BlockfrostBackend -> TestPlanM (Aff Unit) Unit +testPlan backend = group "Blockfrost" do + let + mkDatumHash :: String -> DataHash + mkDatumHash = wrap <<< hexToByteArrayUnsafe + + mkStringHash :: String -> ScriptHash + mkStringHash s = unsafePartial $ fromJust $ scriptHashFromBytes $ + hexToByteArrayUnsafe s + + test "getDatumByHash - not found" do + runBlockfrostServiceM backend do + datum <- getDatumByHash $ mkDatumHash + "e1457a0c47dfb7a2f6b8fbb059bdceab163c05d34f195b87b9f2b30e" + datum `shouldSatisfy` isRight + let result = fromRight Nothing datum + result `shouldEqual` Nothing + + test "getScriptByHash - not found" do + runBlockfrostServiceM backend do + script <- getScriptByHash $ mkStringHash + "e1457a0c47dfb7a2f6b8fbb059bdceab163c05d34f195b87b9f2b30e" + script `shouldSatisfy` isRight + let result = fromRight Nothing script + result `shouldEqual` Nothing From 647ff22381ff5b3088800ce4ad73d4fbea01f94e Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Wed, 4 Jan 2023 13:26:06 +0000 Subject: [PATCH 224/373] Create comparative protocol param test for blockfrost/ogmios. Upgrade purescript-bignumber & migrate our code --- ...poch-4390418473439f6cb41c582a9cea4987.json | 1 + fixtures/test/blockfrost/getCurrentEpoch.json | 12 - ...ters-7fe834fd628aa322eedeb3d8c7c1dd61.json | 1 + .../blockfrost/getProtocolParameters.json | 380 ------------------ ...ters-9f10850f285b1493955267e900008841.json | 1 + packages.dhall | 2 +- spago-packages.nix | 6 +- spago.dhall | 3 +- src/Internal/Contract/Monad.purs | 14 +- src/Internal/QueryM/Ogmios.purs | 2 + src/Internal/Service/Blockfrost.purs | 4 +- templates/ctl-scaffold/packages.dhall | 5 +- templates/ctl-scaffold/spago-packages.nix | 8 +- test/Blockfrost.purs | 32 ++ 14 files changed, 63 insertions(+), 408 deletions(-) create mode 100644 fixtures/test/blockfrost/getCurrentEpoch-4390418473439f6cb41c582a9cea4987.json delete mode 100644 fixtures/test/blockfrost/getCurrentEpoch.json create mode 100644 fixtures/test/blockfrost/getProtocolParameters-7fe834fd628aa322eedeb3d8c7c1dd61.json delete mode 100644 fixtures/test/blockfrost/getProtocolParameters.json create mode 100644 fixtures/test/ogmios/currentProtocolParameters-9f10850f285b1493955267e900008841.json create mode 100644 test/Blockfrost.purs diff --git a/fixtures/test/blockfrost/getCurrentEpoch-4390418473439f6cb41c582a9cea4987.json b/fixtures/test/blockfrost/getCurrentEpoch-4390418473439f6cb41c582a9cea4987.json new file mode 100644 index 0000000000..200631a1e2 --- /dev/null +++ b/fixtures/test/blockfrost/getCurrentEpoch-4390418473439f6cb41c582a9cea4987.json @@ -0,0 +1 @@ +{"epoch":71,"start_time":1672790400,"end_time":1672876800,"first_block_time":1672790414,"last_block_time":1672832819,"block_count":2010,"tx_count":6478,"output":"6523843519468954","fees":"1441394404","active_stake":"393159813430200"} \ No newline at end of file diff --git a/fixtures/test/blockfrost/getCurrentEpoch.json b/fixtures/test/blockfrost/getCurrentEpoch.json deleted file mode 100644 index 1a02aa2ee1..0000000000 --- a/fixtures/test/blockfrost/getCurrentEpoch.json +++ /dev/null @@ -1,12 +0,0 @@ -{ - "epoch": 66, - "start_time": 1672358400, - "end_time": 1672444800, - "first_block_time": 1672358422, - "last_block_time": 1672381042, - "block_count": 1060, - "tx_count": 3322, - "output": "2324588968586074", - "fees": "857566768", - "active_stake": "390058983450026" -} diff --git a/fixtures/test/blockfrost/getProtocolParameters-7fe834fd628aa322eedeb3d8c7c1dd61.json b/fixtures/test/blockfrost/getProtocolParameters-7fe834fd628aa322eedeb3d8c7c1dd61.json new file mode 100644 index 0000000000..0fed15880a --- /dev/null +++ b/fixtures/test/blockfrost/getProtocolParameters-7fe834fd628aa322eedeb3d8c7c1dd61.json @@ -0,0 +1 @@ +{"epoch":71,"min_fee_a":44,"min_fee_b":155381,"max_block_size":90112,"max_tx_size":16384,"max_block_header_size":1100,"key_deposit":"2000000","pool_deposit":"500000000","e_max":18,"n_opt":500,"a0":0.3,"rho":0.003,"tau":0.2,"decentralisation_param":0,"extra_entropy":null,"protocol_major_ver":8,"protocol_minor_ver":0,"min_utxo":"4310","min_pool_cost":"340000000","nonce":"e3ba06ef0f6021007739589d435432517a86e4e22723ac11b92b12f817718c77","cost_models":{"PlutusV1":{"addInteger-cpu-arguments-intercept":205665,"addInteger-cpu-arguments-slope":812,"addInteger-memory-arguments-intercept":1,"addInteger-memory-arguments-slope":1,"appendByteString-cpu-arguments-intercept":1000,"appendByteString-cpu-arguments-slope":571,"appendByteString-memory-arguments-intercept":0,"appendByteString-memory-arguments-slope":1,"appendString-cpu-arguments-intercept":1000,"appendString-cpu-arguments-slope":24177,"appendString-memory-arguments-intercept":4,"appendString-memory-arguments-slope":1,"bData-cpu-arguments":1000,"bData-memory-arguments":32,"blake2b_256-cpu-arguments-intercept":117366,"blake2b_256-cpu-arguments-slope":10475,"blake2b_256-memory-arguments":4,"cekApplyCost-exBudgetCPU":23000,"cekApplyCost-exBudgetMemory":100,"cekBuiltinCost-exBudgetCPU":23000,"cekBuiltinCost-exBudgetMemory":100,"cekConstCost-exBudgetCPU":23000,"cekConstCost-exBudgetMemory":100,"cekDelayCost-exBudgetCPU":23000,"cekDelayCost-exBudgetMemory":100,"cekForceCost-exBudgetCPU":23000,"cekForceCost-exBudgetMemory":100,"cekLamCost-exBudgetCPU":23000,"cekLamCost-exBudgetMemory":100,"cekStartupCost-exBudgetCPU":100,"cekStartupCost-exBudgetMemory":100,"cekVarCost-exBudgetCPU":23000,"cekVarCost-exBudgetMemory":100,"chooseData-cpu-arguments":19537,"chooseData-memory-arguments":32,"chooseList-cpu-arguments":175354,"chooseList-memory-arguments":32,"chooseUnit-cpu-arguments":46417,"chooseUnit-memory-arguments":4,"consByteString-cpu-arguments-intercept":221973,"consByteString-cpu-arguments-slope":511,"consByteString-memory-arguments-intercept":0,"consByteString-memory-arguments-slope":1,"constrData-cpu-arguments":89141,"constrData-memory-arguments":32,"decodeUtf8-cpu-arguments-intercept":497525,"decodeUtf8-cpu-arguments-slope":14068,"decodeUtf8-memory-arguments-intercept":4,"decodeUtf8-memory-arguments-slope":2,"divideInteger-cpu-arguments-constant":196500,"divideInteger-cpu-arguments-model-arguments-intercept":453240,"divideInteger-cpu-arguments-model-arguments-slope":220,"divideInteger-memory-arguments-intercept":0,"divideInteger-memory-arguments-minimum":1,"divideInteger-memory-arguments-slope":1,"encodeUtf8-cpu-arguments-intercept":1000,"encodeUtf8-cpu-arguments-slope":28662,"encodeUtf8-memory-arguments-intercept":4,"encodeUtf8-memory-arguments-slope":2,"equalsByteString-cpu-arguments-constant":245000,"equalsByteString-cpu-arguments-intercept":216773,"equalsByteString-cpu-arguments-slope":62,"equalsByteString-memory-arguments":1,"equalsData-cpu-arguments-intercept":1060367,"equalsData-cpu-arguments-slope":12586,"equalsData-memory-arguments":1,"equalsInteger-cpu-arguments-intercept":208512,"equalsInteger-cpu-arguments-slope":421,"equalsInteger-memory-arguments":1,"equalsString-cpu-arguments-constant":187000,"equalsString-cpu-arguments-intercept":1000,"equalsString-cpu-arguments-slope":52998,"equalsString-memory-arguments":1,"fstPair-cpu-arguments":80436,"fstPair-memory-arguments":32,"headList-cpu-arguments":43249,"headList-memory-arguments":32,"iData-cpu-arguments":1000,"iData-memory-arguments":32,"ifThenElse-cpu-arguments":80556,"ifThenElse-memory-arguments":1,"indexByteString-cpu-arguments":57667,"indexByteString-memory-arguments":4,"lengthOfByteString-cpu-arguments":1000,"lengthOfByteString-memory-arguments":10,"lessThanByteString-cpu-arguments-intercept":197145,"lessThanByteString-cpu-arguments-slope":156,"lessThanByteString-memory-arguments":1,"lessThanEqualsByteString-cpu-arguments-intercept":197145,"lessThanEqualsByteString-cpu-arguments-slope":156,"lessThanEqualsByteString-memory-arguments":1,"lessThanEqualsInteger-cpu-arguments-intercept":204924,"lessThanEqualsInteger-cpu-arguments-slope":473,"lessThanEqualsInteger-memory-arguments":1,"lessThanInteger-cpu-arguments-intercept":208896,"lessThanInteger-cpu-arguments-slope":511,"lessThanInteger-memory-arguments":1,"listData-cpu-arguments":52467,"listData-memory-arguments":32,"mapData-cpu-arguments":64832,"mapData-memory-arguments":32,"mkCons-cpu-arguments":65493,"mkCons-memory-arguments":32,"mkNilData-cpu-arguments":22558,"mkNilData-memory-arguments":32,"mkNilPairData-cpu-arguments":16563,"mkNilPairData-memory-arguments":32,"mkPairData-cpu-arguments":76511,"mkPairData-memory-arguments":32,"modInteger-cpu-arguments-constant":196500,"modInteger-cpu-arguments-model-arguments-intercept":453240,"modInteger-cpu-arguments-model-arguments-slope":220,"modInteger-memory-arguments-intercept":0,"modInteger-memory-arguments-minimum":1,"modInteger-memory-arguments-slope":1,"multiplyInteger-cpu-arguments-intercept":69522,"multiplyInteger-cpu-arguments-slope":11687,"multiplyInteger-memory-arguments-intercept":0,"multiplyInteger-memory-arguments-slope":1,"nullList-cpu-arguments":60091,"nullList-memory-arguments":32,"quotientInteger-cpu-arguments-constant":196500,"quotientInteger-cpu-arguments-model-arguments-intercept":453240,"quotientInteger-cpu-arguments-model-arguments-slope":220,"quotientInteger-memory-arguments-intercept":0,"quotientInteger-memory-arguments-minimum":1,"quotientInteger-memory-arguments-slope":1,"remainderInteger-cpu-arguments-constant":196500,"remainderInteger-cpu-arguments-model-arguments-intercept":453240,"remainderInteger-cpu-arguments-model-arguments-slope":220,"remainderInteger-memory-arguments-intercept":0,"remainderInteger-memory-arguments-minimum":1,"remainderInteger-memory-arguments-slope":1,"sha2_256-cpu-arguments-intercept":806990,"sha2_256-cpu-arguments-slope":30482,"sha2_256-memory-arguments":4,"sha3_256-cpu-arguments-intercept":1927926,"sha3_256-cpu-arguments-slope":82523,"sha3_256-memory-arguments":4,"sliceByteString-cpu-arguments-intercept":265318,"sliceByteString-cpu-arguments-slope":0,"sliceByteString-memory-arguments-intercept":4,"sliceByteString-memory-arguments-slope":0,"sndPair-cpu-arguments":85931,"sndPair-memory-arguments":32,"subtractInteger-cpu-arguments-intercept":205665,"subtractInteger-cpu-arguments-slope":812,"subtractInteger-memory-arguments-intercept":1,"subtractInteger-memory-arguments-slope":1,"tailList-cpu-arguments":41182,"tailList-memory-arguments":32,"trace-cpu-arguments":212342,"trace-memory-arguments":32,"unBData-cpu-arguments":31220,"unBData-memory-arguments":32,"unConstrData-cpu-arguments":32696,"unConstrData-memory-arguments":32,"unIData-cpu-arguments":43357,"unIData-memory-arguments":32,"unListData-cpu-arguments":32247,"unListData-memory-arguments":32,"unMapData-cpu-arguments":38314,"unMapData-memory-arguments":32,"verifyEd25519Signature-cpu-arguments-intercept":9462713,"verifyEd25519Signature-cpu-arguments-slope":1021,"verifyEd25519Signature-memory-arguments":10},"PlutusV2":{"addInteger-cpu-arguments-intercept":205665,"addInteger-cpu-arguments-slope":812,"addInteger-memory-arguments-intercept":1,"addInteger-memory-arguments-slope":1,"appendByteString-cpu-arguments-intercept":1000,"appendByteString-cpu-arguments-slope":571,"appendByteString-memory-arguments-intercept":0,"appendByteString-memory-arguments-slope":1,"appendString-cpu-arguments-intercept":1000,"appendString-cpu-arguments-slope":24177,"appendString-memory-arguments-intercept":4,"appendString-memory-arguments-slope":1,"bData-cpu-arguments":1000,"bData-memory-arguments":32,"blake2b_256-cpu-arguments-intercept":117366,"blake2b_256-cpu-arguments-slope":10475,"blake2b_256-memory-arguments":4,"cekApplyCost-exBudgetCPU":23000,"cekApplyCost-exBudgetMemory":100,"cekBuiltinCost-exBudgetCPU":23000,"cekBuiltinCost-exBudgetMemory":100,"cekConstCost-exBudgetCPU":23000,"cekConstCost-exBudgetMemory":100,"cekDelayCost-exBudgetCPU":23000,"cekDelayCost-exBudgetMemory":100,"cekForceCost-exBudgetCPU":23000,"cekForceCost-exBudgetMemory":100,"cekLamCost-exBudgetCPU":23000,"cekLamCost-exBudgetMemory":100,"cekStartupCost-exBudgetCPU":100,"cekStartupCost-exBudgetMemory":100,"cekVarCost-exBudgetCPU":23000,"cekVarCost-exBudgetMemory":100,"chooseData-cpu-arguments":19537,"chooseData-memory-arguments":32,"chooseList-cpu-arguments":175354,"chooseList-memory-arguments":32,"chooseUnit-cpu-arguments":46417,"chooseUnit-memory-arguments":4,"consByteString-cpu-arguments-intercept":221973,"consByteString-cpu-arguments-slope":511,"consByteString-memory-arguments-intercept":0,"consByteString-memory-arguments-slope":1,"constrData-cpu-arguments":89141,"constrData-memory-arguments":32,"decodeUtf8-cpu-arguments-intercept":497525,"decodeUtf8-cpu-arguments-slope":14068,"decodeUtf8-memory-arguments-intercept":4,"decodeUtf8-memory-arguments-slope":2,"divideInteger-cpu-arguments-constant":196500,"divideInteger-cpu-arguments-model-arguments-intercept":453240,"divideInteger-cpu-arguments-model-arguments-slope":220,"divideInteger-memory-arguments-intercept":0,"divideInteger-memory-arguments-minimum":1,"divideInteger-memory-arguments-slope":1,"encodeUtf8-cpu-arguments-intercept":1000,"encodeUtf8-cpu-arguments-slope":28662,"encodeUtf8-memory-arguments-intercept":4,"encodeUtf8-memory-arguments-slope":2,"equalsByteString-cpu-arguments-constant":245000,"equalsByteString-cpu-arguments-intercept":216773,"equalsByteString-cpu-arguments-slope":62,"equalsByteString-memory-arguments":1,"equalsData-cpu-arguments-intercept":1060367,"equalsData-cpu-arguments-slope":12586,"equalsData-memory-arguments":1,"equalsInteger-cpu-arguments-intercept":208512,"equalsInteger-cpu-arguments-slope":421,"equalsInteger-memory-arguments":1,"equalsString-cpu-arguments-constant":187000,"equalsString-cpu-arguments-intercept":1000,"equalsString-cpu-arguments-slope":52998,"equalsString-memory-arguments":1,"fstPair-cpu-arguments":80436,"fstPair-memory-arguments":32,"headList-cpu-arguments":43249,"headList-memory-arguments":32,"iData-cpu-arguments":1000,"iData-memory-arguments":32,"ifThenElse-cpu-arguments":80556,"ifThenElse-memory-arguments":1,"indexByteString-cpu-arguments":57667,"indexByteString-memory-arguments":4,"lengthOfByteString-cpu-arguments":1000,"lengthOfByteString-memory-arguments":10,"lessThanByteString-cpu-arguments-intercept":197145,"lessThanByteString-cpu-arguments-slope":156,"lessThanByteString-memory-arguments":1,"lessThanEqualsByteString-cpu-arguments-intercept":197145,"lessThanEqualsByteString-cpu-arguments-slope":156,"lessThanEqualsByteString-memory-arguments":1,"lessThanEqualsInteger-cpu-arguments-intercept":204924,"lessThanEqualsInteger-cpu-arguments-slope":473,"lessThanEqualsInteger-memory-arguments":1,"lessThanInteger-cpu-arguments-intercept":208896,"lessThanInteger-cpu-arguments-slope":511,"lessThanInteger-memory-arguments":1,"listData-cpu-arguments":52467,"listData-memory-arguments":32,"mapData-cpu-arguments":64832,"mapData-memory-arguments":32,"mkCons-cpu-arguments":65493,"mkCons-memory-arguments":32,"mkNilData-cpu-arguments":22558,"mkNilData-memory-arguments":32,"mkNilPairData-cpu-arguments":16563,"mkNilPairData-memory-arguments":32,"mkPairData-cpu-arguments":76511,"mkPairData-memory-arguments":32,"modInteger-cpu-arguments-constant":196500,"modInteger-cpu-arguments-model-arguments-intercept":453240,"modInteger-cpu-arguments-model-arguments-slope":220,"modInteger-memory-arguments-intercept":0,"modInteger-memory-arguments-minimum":1,"modInteger-memory-arguments-slope":1,"multiplyInteger-cpu-arguments-intercept":69522,"multiplyInteger-cpu-arguments-slope":11687,"multiplyInteger-memory-arguments-intercept":0,"multiplyInteger-memory-arguments-slope":1,"nullList-cpu-arguments":60091,"nullList-memory-arguments":32,"quotientInteger-cpu-arguments-constant":196500,"quotientInteger-cpu-arguments-model-arguments-intercept":453240,"quotientInteger-cpu-arguments-model-arguments-slope":220,"quotientInteger-memory-arguments-intercept":0,"quotientInteger-memory-arguments-minimum":1,"quotientInteger-memory-arguments-slope":1,"remainderInteger-cpu-arguments-constant":196500,"remainderInteger-cpu-arguments-model-arguments-intercept":453240,"remainderInteger-cpu-arguments-model-arguments-slope":220,"remainderInteger-memory-arguments-intercept":0,"remainderInteger-memory-arguments-minimum":1,"remainderInteger-memory-arguments-slope":1,"serialiseData-cpu-arguments-intercept":1159724,"serialiseData-cpu-arguments-slope":392670,"serialiseData-memory-arguments-intercept":0,"serialiseData-memory-arguments-slope":2,"sha2_256-cpu-arguments-intercept":806990,"sha2_256-cpu-arguments-slope":30482,"sha2_256-memory-arguments":4,"sha3_256-cpu-arguments-intercept":1927926,"sha3_256-cpu-arguments-slope":82523,"sha3_256-memory-arguments":4,"sliceByteString-cpu-arguments-intercept":265318,"sliceByteString-cpu-arguments-slope":0,"sliceByteString-memory-arguments-intercept":4,"sliceByteString-memory-arguments-slope":0,"sndPair-cpu-arguments":85931,"sndPair-memory-arguments":32,"subtractInteger-cpu-arguments-intercept":205665,"subtractInteger-cpu-arguments-slope":812,"subtractInteger-memory-arguments-intercept":1,"subtractInteger-memory-arguments-slope":1,"tailList-cpu-arguments":41182,"tailList-memory-arguments":32,"trace-cpu-arguments":212342,"trace-memory-arguments":32,"unBData-cpu-arguments":31220,"unBData-memory-arguments":32,"unConstrData-cpu-arguments":32696,"unConstrData-memory-arguments":32,"unIData-cpu-arguments":43357,"unIData-memory-arguments":32,"unListData-cpu-arguments":32247,"unListData-memory-arguments":32,"unMapData-cpu-arguments":38314,"unMapData-memory-arguments":32,"verifyEcdsaSecp256k1Signature-cpu-arguments":35892428,"verifyEcdsaSecp256k1Signature-memory-arguments":10,"verifyEd25519Signature-cpu-arguments-intercept":9462713,"verifyEd25519Signature-cpu-arguments-slope":1021,"verifyEd25519Signature-memory-arguments":10,"verifySchnorrSecp256k1Signature-cpu-arguments-intercept":38887044,"verifySchnorrSecp256k1Signature-cpu-arguments-slope":32947,"verifySchnorrSecp256k1Signature-memory-arguments":10}},"price_mem":0.0577,"price_step":0.0000721,"max_tx_ex_mem":"14000000","max_tx_ex_steps":"10000000000","max_block_ex_mem":"62000000","max_block_ex_steps":"40000000000","max_val_size":"5000","collateral_percent":150,"max_collateral_inputs":3,"coins_per_utxo_size":"4310","coins_per_utxo_word":"4310"} \ No newline at end of file diff --git a/fixtures/test/blockfrost/getProtocolParameters.json b/fixtures/test/blockfrost/getProtocolParameters.json deleted file mode 100644 index 2043684e9e..0000000000 --- a/fixtures/test/blockfrost/getProtocolParameters.json +++ /dev/null @@ -1,380 +0,0 @@ -{ - "epoch": 66, - "min_fee_a": 44, - "min_fee_b": 155381, - "max_block_size": 90112, - "max_tx_size": 16384, - "max_block_header_size": 1100, - "key_deposit": "2000000", - "pool_deposit": "500000000", - "e_max": 18, - "n_opt": 500, - "a0": 0.3, - "rho": 0.003, - "tau": 0.2, - "decentralisation_param": 0, - "extra_entropy": null, - "protocol_major_ver": 8, - "protocol_minor_ver": 0, - "min_utxo": "4310", - "min_pool_cost": "340000000", - "nonce": "59937440a6f42eda1d705df24c211a486f01c0fbd4700b77431b6922d07c06c2", - "cost_models": { - "PlutusV1": { - "addInteger-cpu-arguments-intercept": 205665, - "addInteger-cpu-arguments-slope": 812, - "addInteger-memory-arguments-intercept": 1, - "addInteger-memory-arguments-slope": 1, - "appendByteString-cpu-arguments-intercept": 1000, - "appendByteString-cpu-arguments-slope": 571, - "appendByteString-memory-arguments-intercept": 0, - "appendByteString-memory-arguments-slope": 1, - "appendString-cpu-arguments-intercept": 1000, - "appendString-cpu-arguments-slope": 24177, - "appendString-memory-arguments-intercept": 4, - "appendString-memory-arguments-slope": 1, - "bData-cpu-arguments": 1000, - "bData-memory-arguments": 32, - "blake2b_256-cpu-arguments-intercept": 117366, - "blake2b_256-cpu-arguments-slope": 10475, - "blake2b_256-memory-arguments": 4, - "cekApplyCost-exBudgetCPU": 23000, - "cekApplyCost-exBudgetMemory": 100, - "cekBuiltinCost-exBudgetCPU": 23000, - "cekBuiltinCost-exBudgetMemory": 100, - "cekConstCost-exBudgetCPU": 23000, - "cekConstCost-exBudgetMemory": 100, - "cekDelayCost-exBudgetCPU": 23000, - "cekDelayCost-exBudgetMemory": 100, - "cekForceCost-exBudgetCPU": 23000, - "cekForceCost-exBudgetMemory": 100, - "cekLamCost-exBudgetCPU": 23000, - "cekLamCost-exBudgetMemory": 100, - "cekStartupCost-exBudgetCPU": 100, - "cekStartupCost-exBudgetMemory": 100, - "cekVarCost-exBudgetCPU": 23000, - "cekVarCost-exBudgetMemory": 100, - "chooseData-cpu-arguments": 19537, - "chooseData-memory-arguments": 32, - "chooseList-cpu-arguments": 175354, - "chooseList-memory-arguments": 32, - "chooseUnit-cpu-arguments": 46417, - "chooseUnit-memory-arguments": 4, - "consByteString-cpu-arguments-intercept": 221973, - "consByteString-cpu-arguments-slope": 511, - "consByteString-memory-arguments-intercept": 0, - "consByteString-memory-arguments-slope": 1, - "constrData-cpu-arguments": 89141, - "constrData-memory-arguments": 32, - "decodeUtf8-cpu-arguments-intercept": 497525, - "decodeUtf8-cpu-arguments-slope": 14068, - "decodeUtf8-memory-arguments-intercept": 4, - "decodeUtf8-memory-arguments-slope": 2, - "divideInteger-cpu-arguments-constant": 196500, - "divideInteger-cpu-arguments-model-arguments-intercept": 453240, - "divideInteger-cpu-arguments-model-arguments-slope": 220, - "divideInteger-memory-arguments-intercept": 0, - "divideInteger-memory-arguments-minimum": 1, - "divideInteger-memory-arguments-slope": 1, - "encodeUtf8-cpu-arguments-intercept": 1000, - "encodeUtf8-cpu-arguments-slope": 28662, - "encodeUtf8-memory-arguments-intercept": 4, - "encodeUtf8-memory-arguments-slope": 2, - "equalsByteString-cpu-arguments-constant": 245000, - "equalsByteString-cpu-arguments-intercept": 216773, - "equalsByteString-cpu-arguments-slope": 62, - "equalsByteString-memory-arguments": 1, - "equalsData-cpu-arguments-intercept": 1060367, - "equalsData-cpu-arguments-slope": 12586, - "equalsData-memory-arguments": 1, - "equalsInteger-cpu-arguments-intercept": 208512, - "equalsInteger-cpu-arguments-slope": 421, - "equalsInteger-memory-arguments": 1, - "equalsString-cpu-arguments-constant": 187000, - "equalsString-cpu-arguments-intercept": 1000, - "equalsString-cpu-arguments-slope": 52998, - "equalsString-memory-arguments": 1, - "fstPair-cpu-arguments": 80436, - "fstPair-memory-arguments": 32, - "headList-cpu-arguments": 43249, - "headList-memory-arguments": 32, - "iData-cpu-arguments": 1000, - "iData-memory-arguments": 32, - "ifThenElse-cpu-arguments": 80556, - "ifThenElse-memory-arguments": 1, - "indexByteString-cpu-arguments": 57667, - "indexByteString-memory-arguments": 4, - "lengthOfByteString-cpu-arguments": 1000, - "lengthOfByteString-memory-arguments": 10, - "lessThanByteString-cpu-arguments-intercept": 197145, - "lessThanByteString-cpu-arguments-slope": 156, - "lessThanByteString-memory-arguments": 1, - "lessThanEqualsByteString-cpu-arguments-intercept": 197145, - "lessThanEqualsByteString-cpu-arguments-slope": 156, - "lessThanEqualsByteString-memory-arguments": 1, - "lessThanEqualsInteger-cpu-arguments-intercept": 204924, - "lessThanEqualsInteger-cpu-arguments-slope": 473, - "lessThanEqualsInteger-memory-arguments": 1, - "lessThanInteger-cpu-arguments-intercept": 208896, - "lessThanInteger-cpu-arguments-slope": 511, - "lessThanInteger-memory-arguments": 1, - "listData-cpu-arguments": 52467, - "listData-memory-arguments": 32, - "mapData-cpu-arguments": 64832, - "mapData-memory-arguments": 32, - "mkCons-cpu-arguments": 65493, - "mkCons-memory-arguments": 32, - "mkNilData-cpu-arguments": 22558, - "mkNilData-memory-arguments": 32, - "mkNilPairData-cpu-arguments": 16563, - "mkNilPairData-memory-arguments": 32, - "mkPairData-cpu-arguments": 76511, - "mkPairData-memory-arguments": 32, - "modInteger-cpu-arguments-constant": 196500, - "modInteger-cpu-arguments-model-arguments-intercept": 453240, - "modInteger-cpu-arguments-model-arguments-slope": 220, - "modInteger-memory-arguments-intercept": 0, - "modInteger-memory-arguments-minimum": 1, - "modInteger-memory-arguments-slope": 1, - "multiplyInteger-cpu-arguments-intercept": 69522, - "multiplyInteger-cpu-arguments-slope": 11687, - "multiplyInteger-memory-arguments-intercept": 0, - "multiplyInteger-memory-arguments-slope": 1, - "nullList-cpu-arguments": 60091, - "nullList-memory-arguments": 32, - "quotientInteger-cpu-arguments-constant": 196500, - "quotientInteger-cpu-arguments-model-arguments-intercept": 453240, - "quotientInteger-cpu-arguments-model-arguments-slope": 220, - "quotientInteger-memory-arguments-intercept": 0, - "quotientInteger-memory-arguments-minimum": 1, - "quotientInteger-memory-arguments-slope": 1, - "remainderInteger-cpu-arguments-constant": 196500, - "remainderInteger-cpu-arguments-model-arguments-intercept": 453240, - "remainderInteger-cpu-arguments-model-arguments-slope": 220, - "remainderInteger-memory-arguments-intercept": 0, - "remainderInteger-memory-arguments-minimum": 1, - "remainderInteger-memory-arguments-slope": 1, - "sha2_256-cpu-arguments-intercept": 806990, - "sha2_256-cpu-arguments-slope": 30482, - "sha2_256-memory-arguments": 4, - "sha3_256-cpu-arguments-intercept": 1927926, - "sha3_256-cpu-arguments-slope": 82523, - "sha3_256-memory-arguments": 4, - "sliceByteString-cpu-arguments-intercept": 265318, - "sliceByteString-cpu-arguments-slope": 0, - "sliceByteString-memory-arguments-intercept": 4, - "sliceByteString-memory-arguments-slope": 0, - "sndPair-cpu-arguments": 85931, - "sndPair-memory-arguments": 32, - "subtractInteger-cpu-arguments-intercept": 205665, - "subtractInteger-cpu-arguments-slope": 812, - "subtractInteger-memory-arguments-intercept": 1, - "subtractInteger-memory-arguments-slope": 1, - "tailList-cpu-arguments": 41182, - "tailList-memory-arguments": 32, - "trace-cpu-arguments": 212342, - "trace-memory-arguments": 32, - "unBData-cpu-arguments": 31220, - "unBData-memory-arguments": 32, - "unConstrData-cpu-arguments": 32696, - "unConstrData-memory-arguments": 32, - "unIData-cpu-arguments": 43357, - "unIData-memory-arguments": 32, - "unListData-cpu-arguments": 32247, - "unListData-memory-arguments": 32, - "unMapData-cpu-arguments": 38314, - "unMapData-memory-arguments": 32, - "verifyEd25519Signature-cpu-arguments-intercept": 9462713, - "verifyEd25519Signature-cpu-arguments-slope": 1021, - "verifyEd25519Signature-memory-arguments": 10 - }, - "PlutusV2": { - "addInteger-cpu-arguments-intercept": 205665, - "addInteger-cpu-arguments-slope": 812, - "addInteger-memory-arguments-intercept": 1, - "addInteger-memory-arguments-slope": 1, - "appendByteString-cpu-arguments-intercept": 1000, - "appendByteString-cpu-arguments-slope": 571, - "appendByteString-memory-arguments-intercept": 0, - "appendByteString-memory-arguments-slope": 1, - "appendString-cpu-arguments-intercept": 1000, - "appendString-cpu-arguments-slope": 24177, - "appendString-memory-arguments-intercept": 4, - "appendString-memory-arguments-slope": 1, - "bData-cpu-arguments": 1000, - "bData-memory-arguments": 32, - "blake2b_256-cpu-arguments-intercept": 117366, - "blake2b_256-cpu-arguments-slope": 10475, - "blake2b_256-memory-arguments": 4, - "cekApplyCost-exBudgetCPU": 23000, - "cekApplyCost-exBudgetMemory": 100, - "cekBuiltinCost-exBudgetCPU": 23000, - "cekBuiltinCost-exBudgetMemory": 100, - "cekConstCost-exBudgetCPU": 23000, - "cekConstCost-exBudgetMemory": 100, - "cekDelayCost-exBudgetCPU": 23000, - "cekDelayCost-exBudgetMemory": 100, - "cekForceCost-exBudgetCPU": 23000, - "cekForceCost-exBudgetMemory": 100, - "cekLamCost-exBudgetCPU": 23000, - "cekLamCost-exBudgetMemory": 100, - "cekStartupCost-exBudgetCPU": 100, - "cekStartupCost-exBudgetMemory": 100, - "cekVarCost-exBudgetCPU": 23000, - "cekVarCost-exBudgetMemory": 100, - "chooseData-cpu-arguments": 19537, - "chooseData-memory-arguments": 32, - "chooseList-cpu-arguments": 175354, - "chooseList-memory-arguments": 32, - "chooseUnit-cpu-arguments": 46417, - "chooseUnit-memory-arguments": 4, - "consByteString-cpu-arguments-intercept": 221973, - "consByteString-cpu-arguments-slope": 511, - "consByteString-memory-arguments-intercept": 0, - "consByteString-memory-arguments-slope": 1, - "constrData-cpu-arguments": 89141, - "constrData-memory-arguments": 32, - "decodeUtf8-cpu-arguments-intercept": 497525, - "decodeUtf8-cpu-arguments-slope": 14068, - "decodeUtf8-memory-arguments-intercept": 4, - "decodeUtf8-memory-arguments-slope": 2, - "divideInteger-cpu-arguments-constant": 196500, - "divideInteger-cpu-arguments-model-arguments-intercept": 453240, - "divideInteger-cpu-arguments-model-arguments-slope": 220, - "divideInteger-memory-arguments-intercept": 0, - "divideInteger-memory-arguments-minimum": 1, - "divideInteger-memory-arguments-slope": 1, - "encodeUtf8-cpu-arguments-intercept": 1000, - "encodeUtf8-cpu-arguments-slope": 28662, - "encodeUtf8-memory-arguments-intercept": 4, - "encodeUtf8-memory-arguments-slope": 2, - "equalsByteString-cpu-arguments-constant": 245000, - "equalsByteString-cpu-arguments-intercept": 216773, - "equalsByteString-cpu-arguments-slope": 62, - "equalsByteString-memory-arguments": 1, - "equalsData-cpu-arguments-intercept": 1060367, - "equalsData-cpu-arguments-slope": 12586, - "equalsData-memory-arguments": 1, - "equalsInteger-cpu-arguments-intercept": 208512, - "equalsInteger-cpu-arguments-slope": 421, - "equalsInteger-memory-arguments": 1, - "equalsString-cpu-arguments-constant": 187000, - "equalsString-cpu-arguments-intercept": 1000, - "equalsString-cpu-arguments-slope": 52998, - "equalsString-memory-arguments": 1, - "fstPair-cpu-arguments": 80436, - "fstPair-memory-arguments": 32, - "headList-cpu-arguments": 43249, - "headList-memory-arguments": 32, - "iData-cpu-arguments": 1000, - "iData-memory-arguments": 32, - "ifThenElse-cpu-arguments": 80556, - "ifThenElse-memory-arguments": 1, - "indexByteString-cpu-arguments": 57667, - "indexByteString-memory-arguments": 4, - "lengthOfByteString-cpu-arguments": 1000, - "lengthOfByteString-memory-arguments": 10, - "lessThanByteString-cpu-arguments-intercept": 197145, - "lessThanByteString-cpu-arguments-slope": 156, - "lessThanByteString-memory-arguments": 1, - "lessThanEqualsByteString-cpu-arguments-intercept": 197145, - "lessThanEqualsByteString-cpu-arguments-slope": 156, - "lessThanEqualsByteString-memory-arguments": 1, - "lessThanEqualsInteger-cpu-arguments-intercept": 204924, - "lessThanEqualsInteger-cpu-arguments-slope": 473, - "lessThanEqualsInteger-memory-arguments": 1, - "lessThanInteger-cpu-arguments-intercept": 208896, - "lessThanInteger-cpu-arguments-slope": 511, - "lessThanInteger-memory-arguments": 1, - "listData-cpu-arguments": 52467, - "listData-memory-arguments": 32, - "mapData-cpu-arguments": 64832, - "mapData-memory-arguments": 32, - "mkCons-cpu-arguments": 65493, - "mkCons-memory-arguments": 32, - "mkNilData-cpu-arguments": 22558, - "mkNilData-memory-arguments": 32, - "mkNilPairData-cpu-arguments": 16563, - "mkNilPairData-memory-arguments": 32, - "mkPairData-cpu-arguments": 76511, - "mkPairData-memory-arguments": 32, - "modInteger-cpu-arguments-constant": 196500, - "modInteger-cpu-arguments-model-arguments-intercept": 453240, - "modInteger-cpu-arguments-model-arguments-slope": 220, - "modInteger-memory-arguments-intercept": 0, - "modInteger-memory-arguments-minimum": 1, - "modInteger-memory-arguments-slope": 1, - "multiplyInteger-cpu-arguments-intercept": 69522, - "multiplyInteger-cpu-arguments-slope": 11687, - "multiplyInteger-memory-arguments-intercept": 0, - "multiplyInteger-memory-arguments-slope": 1, - "nullList-cpu-arguments": 60091, - "nullList-memory-arguments": 32, - "quotientInteger-cpu-arguments-constant": 196500, - "quotientInteger-cpu-arguments-model-arguments-intercept": 453240, - "quotientInteger-cpu-arguments-model-arguments-slope": 220, - "quotientInteger-memory-arguments-intercept": 0, - "quotientInteger-memory-arguments-minimum": 1, - "quotientInteger-memory-arguments-slope": 1, - "remainderInteger-cpu-arguments-constant": 196500, - "remainderInteger-cpu-arguments-model-arguments-intercept": 453240, - "remainderInteger-cpu-arguments-model-arguments-slope": 220, - "remainderInteger-memory-arguments-intercept": 0, - "remainderInteger-memory-arguments-minimum": 1, - "remainderInteger-memory-arguments-slope": 1, - "serialiseData-cpu-arguments-intercept": 1159724, - "serialiseData-cpu-arguments-slope": 392670, - "serialiseData-memory-arguments-intercept": 0, - "serialiseData-memory-arguments-slope": 2, - "sha2_256-cpu-arguments-intercept": 806990, - "sha2_256-cpu-arguments-slope": 30482, - "sha2_256-memory-arguments": 4, - "sha3_256-cpu-arguments-intercept": 1927926, - "sha3_256-cpu-arguments-slope": 82523, - "sha3_256-memory-arguments": 4, - "sliceByteString-cpu-arguments-intercept": 265318, - "sliceByteString-cpu-arguments-slope": 0, - "sliceByteString-memory-arguments-intercept": 4, - "sliceByteString-memory-arguments-slope": 0, - "sndPair-cpu-arguments": 85931, - "sndPair-memory-arguments": 32, - "subtractInteger-cpu-arguments-intercept": 205665, - "subtractInteger-cpu-arguments-slope": 812, - "subtractInteger-memory-arguments-intercept": 1, - "subtractInteger-memory-arguments-slope": 1, - "tailList-cpu-arguments": 41182, - "tailList-memory-arguments": 32, - "trace-cpu-arguments": 212342, - "trace-memory-arguments": 32, - "unBData-cpu-arguments": 31220, - "unBData-memory-arguments": 32, - "unConstrData-cpu-arguments": 32696, - "unConstrData-memory-arguments": 32, - "unIData-cpu-arguments": 43357, - "unIData-memory-arguments": 32, - "unListData-cpu-arguments": 32247, - "unListData-memory-arguments": 32, - "unMapData-cpu-arguments": 38314, - "unMapData-memory-arguments": 32, - "verifyEcdsaSecp256k1Signature-cpu-arguments": 35892428, - "verifyEcdsaSecp256k1Signature-memory-arguments": 10, - "verifyEd25519Signature-cpu-arguments-intercept": 9462713, - "verifyEd25519Signature-cpu-arguments-slope": 1021, - "verifyEd25519Signature-memory-arguments": 10, - "verifySchnorrSecp256k1Signature-cpu-arguments-intercept": 38887044, - "verifySchnorrSecp256k1Signature-cpu-arguments-slope": 32947, - "verifySchnorrSecp256k1Signature-memory-arguments": 10 - } - }, - "price_mem": 0.0577, - "price_step": 7.21e-05, - "max_tx_ex_mem": "14000000", - "max_tx_ex_steps": "10000000000", - "max_block_ex_mem": "62000000", - "max_block_ex_steps": "40000000000", - "max_val_size": "5000", - "collateral_percent": 150, - "max_collateral_inputs": 3, - "coins_per_utxo_size": "4310", - "coins_per_utxo_word": "4310" -} diff --git a/fixtures/test/ogmios/currentProtocolParameters-9f10850f285b1493955267e900008841.json b/fixtures/test/ogmios/currentProtocolParameters-9f10850f285b1493955267e900008841.json new file mode 100644 index 0000000000..ad617ad1fc --- /dev/null +++ b/fixtures/test/ogmios/currentProtocolParameters-9f10850f285b1493955267e900008841.json @@ -0,0 +1 @@ +{"minFeeCoefficient":44,"minFeeConstant":155381,"maxBlockBodySize":90112,"maxBlockHeaderSize":1100,"maxTxSize":16384,"stakeKeyDeposit":2000000,"poolDeposit":500000000,"poolRetirementEpochBound":18,"desiredNumberOfPools":500,"poolInfluence":"3/10","monetaryExpansion":"3/1000","treasuryExpansion":"1/5","protocolVersion":{"major":8,"minor":0},"minPoolCost":340000000,"coinsPerUtxoByte":4310,"costModels":{"plutus:v1":{"addInteger-cpu-arguments-intercept":205665,"addInteger-cpu-arguments-slope":812,"addInteger-memory-arguments-intercept":1,"addInteger-memory-arguments-slope":1,"appendByteString-cpu-arguments-intercept":1000,"appendByteString-cpu-arguments-slope":571,"appendByteString-memory-arguments-intercept":0,"appendByteString-memory-arguments-slope":1,"appendString-cpu-arguments-intercept":1000,"appendString-cpu-arguments-slope":24177,"appendString-memory-arguments-intercept":4,"appendString-memory-arguments-slope":1,"bData-cpu-arguments":1000,"bData-memory-arguments":32,"blake2b_256-cpu-arguments-intercept":117366,"blake2b_256-cpu-arguments-slope":10475,"blake2b_256-memory-arguments":4,"cekApplyCost-exBudgetCPU":23000,"cekApplyCost-exBudgetMemory":100,"cekBuiltinCost-exBudgetCPU":23000,"cekBuiltinCost-exBudgetMemory":100,"cekConstCost-exBudgetCPU":23000,"cekConstCost-exBudgetMemory":100,"cekDelayCost-exBudgetCPU":23000,"cekDelayCost-exBudgetMemory":100,"cekForceCost-exBudgetCPU":23000,"cekForceCost-exBudgetMemory":100,"cekLamCost-exBudgetCPU":23000,"cekLamCost-exBudgetMemory":100,"cekStartupCost-exBudgetCPU":100,"cekStartupCost-exBudgetMemory":100,"cekVarCost-exBudgetCPU":23000,"cekVarCost-exBudgetMemory":100,"chooseData-cpu-arguments":19537,"chooseData-memory-arguments":32,"chooseList-cpu-arguments":175354,"chooseList-memory-arguments":32,"chooseUnit-cpu-arguments":46417,"chooseUnit-memory-arguments":4,"consByteString-cpu-arguments-intercept":221973,"consByteString-cpu-arguments-slope":511,"consByteString-memory-arguments-intercept":0,"consByteString-memory-arguments-slope":1,"constrData-cpu-arguments":89141,"constrData-memory-arguments":32,"decodeUtf8-cpu-arguments-intercept":497525,"decodeUtf8-cpu-arguments-slope":14068,"decodeUtf8-memory-arguments-intercept":4,"decodeUtf8-memory-arguments-slope":2,"divideInteger-cpu-arguments-constant":196500,"divideInteger-cpu-arguments-model-arguments-intercept":453240,"divideInteger-cpu-arguments-model-arguments-slope":220,"divideInteger-memory-arguments-intercept":0,"divideInteger-memory-arguments-minimum":1,"divideInteger-memory-arguments-slope":1,"encodeUtf8-cpu-arguments-intercept":1000,"encodeUtf8-cpu-arguments-slope":28662,"encodeUtf8-memory-arguments-intercept":4,"encodeUtf8-memory-arguments-slope":2,"equalsByteString-cpu-arguments-constant":245000,"equalsByteString-cpu-arguments-intercept":216773,"equalsByteString-cpu-arguments-slope":62,"equalsByteString-memory-arguments":1,"equalsData-cpu-arguments-intercept":1060367,"equalsData-cpu-arguments-slope":12586,"equalsData-memory-arguments":1,"equalsInteger-cpu-arguments-intercept":208512,"equalsInteger-cpu-arguments-slope":421,"equalsInteger-memory-arguments":1,"equalsString-cpu-arguments-constant":187000,"equalsString-cpu-arguments-intercept":1000,"equalsString-cpu-arguments-slope":52998,"equalsString-memory-arguments":1,"fstPair-cpu-arguments":80436,"fstPair-memory-arguments":32,"headList-cpu-arguments":43249,"headList-memory-arguments":32,"iData-cpu-arguments":1000,"iData-memory-arguments":32,"ifThenElse-cpu-arguments":80556,"ifThenElse-memory-arguments":1,"indexByteString-cpu-arguments":57667,"indexByteString-memory-arguments":4,"lengthOfByteString-cpu-arguments":1000,"lengthOfByteString-memory-arguments":10,"lessThanByteString-cpu-arguments-intercept":197145,"lessThanByteString-cpu-arguments-slope":156,"lessThanByteString-memory-arguments":1,"lessThanEqualsByteString-cpu-arguments-intercept":197145,"lessThanEqualsByteString-cpu-arguments-slope":156,"lessThanEqualsByteString-memory-arguments":1,"lessThanEqualsInteger-cpu-arguments-intercept":204924,"lessThanEqualsInteger-cpu-arguments-slope":473,"lessThanEqualsInteger-memory-arguments":1,"lessThanInteger-cpu-arguments-intercept":208896,"lessThanInteger-cpu-arguments-slope":511,"lessThanInteger-memory-arguments":1,"listData-cpu-arguments":52467,"listData-memory-arguments":32,"mapData-cpu-arguments":64832,"mapData-memory-arguments":32,"mkCons-cpu-arguments":65493,"mkCons-memory-arguments":32,"mkNilData-cpu-arguments":22558,"mkNilData-memory-arguments":32,"mkNilPairData-cpu-arguments":16563,"mkNilPairData-memory-arguments":32,"mkPairData-cpu-arguments":76511,"mkPairData-memory-arguments":32,"modInteger-cpu-arguments-constant":196500,"modInteger-cpu-arguments-model-arguments-intercept":453240,"modInteger-cpu-arguments-model-arguments-slope":220,"modInteger-memory-arguments-intercept":0,"modInteger-memory-arguments-minimum":1,"modInteger-memory-arguments-slope":1,"multiplyInteger-cpu-arguments-intercept":69522,"multiplyInteger-cpu-arguments-slope":11687,"multiplyInteger-memory-arguments-intercept":0,"multiplyInteger-memory-arguments-slope":1,"nullList-cpu-arguments":60091,"nullList-memory-arguments":32,"quotientInteger-cpu-arguments-constant":196500,"quotientInteger-cpu-arguments-model-arguments-intercept":453240,"quotientInteger-cpu-arguments-model-arguments-slope":220,"quotientInteger-memory-arguments-intercept":0,"quotientInteger-memory-arguments-minimum":1,"quotientInteger-memory-arguments-slope":1,"remainderInteger-cpu-arguments-constant":196500,"remainderInteger-cpu-arguments-model-arguments-intercept":453240,"remainderInteger-cpu-arguments-model-arguments-slope":220,"remainderInteger-memory-arguments-intercept":0,"remainderInteger-memory-arguments-minimum":1,"remainderInteger-memory-arguments-slope":1,"sha2_256-cpu-arguments-intercept":806990,"sha2_256-cpu-arguments-slope":30482,"sha2_256-memory-arguments":4,"sha3_256-cpu-arguments-intercept":1927926,"sha3_256-cpu-arguments-slope":82523,"sha3_256-memory-arguments":4,"sliceByteString-cpu-arguments-intercept":265318,"sliceByteString-cpu-arguments-slope":0,"sliceByteString-memory-arguments-intercept":4,"sliceByteString-memory-arguments-slope":0,"sndPair-cpu-arguments":85931,"sndPair-memory-arguments":32,"subtractInteger-cpu-arguments-intercept":205665,"subtractInteger-cpu-arguments-slope":812,"subtractInteger-memory-arguments-intercept":1,"subtractInteger-memory-arguments-slope":1,"tailList-cpu-arguments":41182,"tailList-memory-arguments":32,"trace-cpu-arguments":212342,"trace-memory-arguments":32,"unBData-cpu-arguments":31220,"unBData-memory-arguments":32,"unConstrData-cpu-arguments":32696,"unConstrData-memory-arguments":32,"unIData-cpu-arguments":43357,"unIData-memory-arguments":32,"unListData-cpu-arguments":32247,"unListData-memory-arguments":32,"unMapData-cpu-arguments":38314,"unMapData-memory-arguments":32,"verifyEd25519Signature-cpu-arguments-intercept":9462713,"verifyEd25519Signature-cpu-arguments-slope":1021,"verifyEd25519Signature-memory-arguments":10},"plutus:v2":{"addInteger-cpu-arguments-intercept":205665,"addInteger-cpu-arguments-slope":812,"addInteger-memory-arguments-intercept":1,"addInteger-memory-arguments-slope":1,"appendByteString-cpu-arguments-intercept":1000,"appendByteString-cpu-arguments-slope":571,"appendByteString-memory-arguments-intercept":0,"appendByteString-memory-arguments-slope":1,"appendString-cpu-arguments-intercept":1000,"appendString-cpu-arguments-slope":24177,"appendString-memory-arguments-intercept":4,"appendString-memory-arguments-slope":1,"bData-cpu-arguments":1000,"bData-memory-arguments":32,"blake2b_256-cpu-arguments-intercept":117366,"blake2b_256-cpu-arguments-slope":10475,"blake2b_256-memory-arguments":4,"cekApplyCost-exBudgetCPU":23000,"cekApplyCost-exBudgetMemory":100,"cekBuiltinCost-exBudgetCPU":23000,"cekBuiltinCost-exBudgetMemory":100,"cekConstCost-exBudgetCPU":23000,"cekConstCost-exBudgetMemory":100,"cekDelayCost-exBudgetCPU":23000,"cekDelayCost-exBudgetMemory":100,"cekForceCost-exBudgetCPU":23000,"cekForceCost-exBudgetMemory":100,"cekLamCost-exBudgetCPU":23000,"cekLamCost-exBudgetMemory":100,"cekStartupCost-exBudgetCPU":100,"cekStartupCost-exBudgetMemory":100,"cekVarCost-exBudgetCPU":23000,"cekVarCost-exBudgetMemory":100,"chooseData-cpu-arguments":19537,"chooseData-memory-arguments":32,"chooseList-cpu-arguments":175354,"chooseList-memory-arguments":32,"chooseUnit-cpu-arguments":46417,"chooseUnit-memory-arguments":4,"consByteString-cpu-arguments-intercept":221973,"consByteString-cpu-arguments-slope":511,"consByteString-memory-arguments-intercept":0,"consByteString-memory-arguments-slope":1,"constrData-cpu-arguments":89141,"constrData-memory-arguments":32,"decodeUtf8-cpu-arguments-intercept":497525,"decodeUtf8-cpu-arguments-slope":14068,"decodeUtf8-memory-arguments-intercept":4,"decodeUtf8-memory-arguments-slope":2,"divideInteger-cpu-arguments-constant":196500,"divideInteger-cpu-arguments-model-arguments-intercept":453240,"divideInteger-cpu-arguments-model-arguments-slope":220,"divideInteger-memory-arguments-intercept":0,"divideInteger-memory-arguments-minimum":1,"divideInteger-memory-arguments-slope":1,"encodeUtf8-cpu-arguments-intercept":1000,"encodeUtf8-cpu-arguments-slope":28662,"encodeUtf8-memory-arguments-intercept":4,"encodeUtf8-memory-arguments-slope":2,"equalsByteString-cpu-arguments-constant":245000,"equalsByteString-cpu-arguments-intercept":216773,"equalsByteString-cpu-arguments-slope":62,"equalsByteString-memory-arguments":1,"equalsData-cpu-arguments-intercept":1060367,"equalsData-cpu-arguments-slope":12586,"equalsData-memory-arguments":1,"equalsInteger-cpu-arguments-intercept":208512,"equalsInteger-cpu-arguments-slope":421,"equalsInteger-memory-arguments":1,"equalsString-cpu-arguments-constant":187000,"equalsString-cpu-arguments-intercept":1000,"equalsString-cpu-arguments-slope":52998,"equalsString-memory-arguments":1,"fstPair-cpu-arguments":80436,"fstPair-memory-arguments":32,"headList-cpu-arguments":43249,"headList-memory-arguments":32,"iData-cpu-arguments":1000,"iData-memory-arguments":32,"ifThenElse-cpu-arguments":80556,"ifThenElse-memory-arguments":1,"indexByteString-cpu-arguments":57667,"indexByteString-memory-arguments":4,"lengthOfByteString-cpu-arguments":1000,"lengthOfByteString-memory-arguments":10,"lessThanByteString-cpu-arguments-intercept":197145,"lessThanByteString-cpu-arguments-slope":156,"lessThanByteString-memory-arguments":1,"lessThanEqualsByteString-cpu-arguments-intercept":197145,"lessThanEqualsByteString-cpu-arguments-slope":156,"lessThanEqualsByteString-memory-arguments":1,"lessThanEqualsInteger-cpu-arguments-intercept":204924,"lessThanEqualsInteger-cpu-arguments-slope":473,"lessThanEqualsInteger-memory-arguments":1,"lessThanInteger-cpu-arguments-intercept":208896,"lessThanInteger-cpu-arguments-slope":511,"lessThanInteger-memory-arguments":1,"listData-cpu-arguments":52467,"listData-memory-arguments":32,"mapData-cpu-arguments":64832,"mapData-memory-arguments":32,"mkCons-cpu-arguments":65493,"mkCons-memory-arguments":32,"mkNilData-cpu-arguments":22558,"mkNilData-memory-arguments":32,"mkNilPairData-cpu-arguments":16563,"mkNilPairData-memory-arguments":32,"mkPairData-cpu-arguments":76511,"mkPairData-memory-arguments":32,"modInteger-cpu-arguments-constant":196500,"modInteger-cpu-arguments-model-arguments-intercept":453240,"modInteger-cpu-arguments-model-arguments-slope":220,"modInteger-memory-arguments-intercept":0,"modInteger-memory-arguments-minimum":1,"modInteger-memory-arguments-slope":1,"multiplyInteger-cpu-arguments-intercept":69522,"multiplyInteger-cpu-arguments-slope":11687,"multiplyInteger-memory-arguments-intercept":0,"multiplyInteger-memory-arguments-slope":1,"nullList-cpu-arguments":60091,"nullList-memory-arguments":32,"quotientInteger-cpu-arguments-constant":196500,"quotientInteger-cpu-arguments-model-arguments-intercept":453240,"quotientInteger-cpu-arguments-model-arguments-slope":220,"quotientInteger-memory-arguments-intercept":0,"quotientInteger-memory-arguments-minimum":1,"quotientInteger-memory-arguments-slope":1,"remainderInteger-cpu-arguments-constant":196500,"remainderInteger-cpu-arguments-model-arguments-intercept":453240,"remainderInteger-cpu-arguments-model-arguments-slope":220,"remainderInteger-memory-arguments-intercept":0,"remainderInteger-memory-arguments-minimum":1,"remainderInteger-memory-arguments-slope":1,"serialiseData-cpu-arguments-intercept":1159724,"serialiseData-cpu-arguments-slope":392670,"serialiseData-memory-arguments-intercept":0,"serialiseData-memory-arguments-slope":2,"sha2_256-cpu-arguments-intercept":806990,"sha2_256-cpu-arguments-slope":30482,"sha2_256-memory-arguments":4,"sha3_256-cpu-arguments-intercept":1927926,"sha3_256-cpu-arguments-slope":82523,"sha3_256-memory-arguments":4,"sliceByteString-cpu-arguments-intercept":265318,"sliceByteString-cpu-arguments-slope":0,"sliceByteString-memory-arguments-intercept":4,"sliceByteString-memory-arguments-slope":0,"sndPair-cpu-arguments":85931,"sndPair-memory-arguments":32,"subtractInteger-cpu-arguments-intercept":205665,"subtractInteger-cpu-arguments-slope":812,"subtractInteger-memory-arguments-intercept":1,"subtractInteger-memory-arguments-slope":1,"tailList-cpu-arguments":41182,"tailList-memory-arguments":32,"trace-cpu-arguments":212342,"trace-memory-arguments":32,"unBData-cpu-arguments":31220,"unBData-memory-arguments":32,"unConstrData-cpu-arguments":32696,"unConstrData-memory-arguments":32,"unIData-cpu-arguments":43357,"unIData-memory-arguments":32,"unListData-cpu-arguments":32247,"unListData-memory-arguments":32,"unMapData-cpu-arguments":38314,"unMapData-memory-arguments":32,"verifyEcdsaSecp256k1Signature-cpu-arguments":35892428,"verifyEcdsaSecp256k1Signature-memory-arguments":10,"verifyEd25519Signature-cpu-arguments-intercept":9462713,"verifyEd25519Signature-cpu-arguments-slope":1021,"verifyEd25519Signature-memory-arguments":10,"verifySchnorrSecp256k1Signature-cpu-arguments-intercept":38887044,"verifySchnorrSecp256k1Signature-cpu-arguments-slope":32947,"verifySchnorrSecp256k1Signature-memory-arguments":10}},"prices":{"memory":"577/10000","steps":"721/10000000"},"maxExecutionUnitsPerTransaction":{"memory":14000000,"steps":10000000000},"maxExecutionUnitsPerBlock":{"memory":62000000,"steps":40000000000},"maxValueSize":5000,"collateralPercentage":150,"maxCollateralInputs":3} \ No newline at end of file diff --git a/packages.dhall b/packages.dhall index e6ccb8b440..37ee1a8d42 100644 --- a/packages.dhall +++ b/packages.dhall @@ -161,7 +161,7 @@ let additions = , "tuples" ] , repo = "https://github.com/mlabs-haskell/purescript-bignumber" - , version = "58c51448be23c05caf51cde45bb3b09cc7169447" + , version = "705923edd892a3397b90d28ce7db9a7181dcd599" } , sequences = { dependencies = diff --git a/spago-packages.nix b/spago-packages.nix index 36b16259f0..8eb333490d 100644 --- a/spago-packages.nix +++ b/spago-packages.nix @@ -199,11 +199,11 @@ let "bignumber" = pkgs.stdenv.mkDerivation { name = "bignumber"; - version = "58c51448be23c05caf51cde45bb3b09cc7169447"; + version = "705923edd892a3397b90d28ce7db9a7181dcd599"; src = pkgs.fetchgit { url = "https://github.com/mlabs-haskell/purescript-bignumber"; - rev = "58c51448be23c05caf51cde45bb3b09cc7169447"; - sha256 = "1q0zyq0ni2vcr99bnxn37ah6f1h3z9mhda4f0549x925mzm25d04"; + rev = "705923edd892a3397b90d28ce7db9a7181dcd599"; + sha256 = "0wddkx161xk457r1mb1f1r79l8qgxja0xhdvxjd1ai43nwp9cgkf"; }; phases = "installPhase"; installPhase = "ln -s $src $out"; diff --git a/spago.dhall b/spago.dhall index 71b0386eca..5ce518a582 100644 --- a/spago.dhall +++ b/spago.dhall @@ -5,17 +5,18 @@ You can edit this file as you like. { name = "cardano-transaction-lib" , dependencies = [ "aeson" - , "argonaut-codecs" , "aff" , "aff-promise" , "aff-retry" , "affjax" , "argonaut" + , "argonaut-codecs" , "arraybuffer-types" , "arrays" , "avar" , "bifunctors" , "bigints" + , "bignumber" , "checked-exceptions" , "console" , "control" diff --git a/src/Internal/Contract/Monad.purs b/src/Internal/Contract/Monad.purs index 185b9aa96c..d6db3c12f5 100644 --- a/src/Internal/Contract/Monad.purs +++ b/src/Internal/Contract/Monad.purs @@ -17,8 +17,12 @@ module Ctl.Internal.Contract.Monad import Prelude +import Contract.Prelude (liftEither) import Control.Alt (class Alt) import Control.Alternative (class Alternative) +import Data.Bifunctor (lmap) +import Ctl.Internal.Service.Blockfrost (runBlockfrostServiceM) +import Ctl.Internal.Service.Blockfrost as Blockfrost import Control.Monad.Error.Class ( class MonadError , class MonadThrow @@ -53,7 +57,7 @@ import Ctl.Internal.QueryM ) import Ctl.Internal.QueryM.Kupo (isTxConfirmedAff) -- TODO: Move/translate these types into Cardano -import Ctl.Internal.QueryM.Ogmios (ProtocolParameters, SystemStart) as Ogmios +import Ctl.Internal.QueryM.Ogmios (ProtocolParameters, SystemStart(SystemStart)) as Ogmios import Ctl.Internal.Serialization.Address (NetworkId(TestnetId, MainnetId)) import Ctl.Internal.Types.UsedTxOuts (UsedTxOuts, isTxOutRefUsed, newUsedTxOuts) import Ctl.Internal.Wallet (Wallet, actionBasedOnWallet) @@ -71,7 +75,6 @@ import Effect.Class (class MonadEffect, liftEffect) import Effect.Exception (Error, throw, try) import MedeaPrelude (class MonadAff) import Record.Builder (build, merge) -import Undefined (undefined) -------------------------------------------------------------------------------- -- Contract @@ -239,7 +242,12 @@ getLedgerConstants logger = case _ of pparams <- getProtocolParametersAff ws logger systemStart <- getSystemStartAff ws logger pure { pparams, systemStart } - BlockfrostBackend _ _ -> undefined + BlockfrostBackend blockfrost _ -> do + pparams <- runBlockfrostServiceM blockfrost Blockfrost.getProtocolParameters + >>= lmap (show >>> error) >>> liftEither + let + systemStart = Ogmios.SystemStart "2022-10-25T00:00:00Z" + pure { pparams, systemStart } -- | Ensure that `NetworkId` from wallet is the same as specified in the -- | `ContractEnv`. diff --git a/src/Internal/QueryM/Ogmios.purs b/src/Internal/QueryM/Ogmios.purs index abd9d7123c..6775e73bb6 100644 --- a/src/Internal/QueryM/Ogmios.purs +++ b/src/Internal/QueryM/Ogmios.purs @@ -1011,6 +1011,7 @@ type ProtocolParametersRaw = data CoinsPerUtxoUnit = CoinsPerUtxoByte Coin | CoinsPerUtxoWord Coin derive instance Generic CoinsPerUtxoUnit _ +derive instance Eq CoinsPerUtxoUnit instance Show CoinsPerUtxoUnit where show = genericShow @@ -1046,6 +1047,7 @@ newtype ProtocolParameters = ProtocolParameters derive instance Newtype ProtocolParameters _ derive instance Generic ProtocolParameters _ +derive instance Eq ProtocolParameters instance Show ProtocolParameters where show = genericShow diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index 002cc2b95f..56c5665680 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -190,8 +190,8 @@ type BlockfrostProtocolParametersRaw = bigNumberToRational :: BigNumber -> Maybe Rational bigNumberToRational bn = do let (numerator' /\ denominator') = toFraction bn (BigNumber.fromNumber infinity) - numerator <- BigInt.fromString numerator' - denominator <- BigInt.fromString denominator' + numerator <- BigInt.fromString $ BigNumber.toString numerator' + denominator <- BigInt.fromString $ BigNumber.toString denominator' reduce numerator denominator bigNumberToRational' :: BigNumber -> Either JsonDecodeError Rational diff --git a/templates/ctl-scaffold/packages.dhall b/templates/ctl-scaffold/packages.dhall index dcd15c5670..2899b5e525 100644 --- a/templates/ctl-scaffold/packages.dhall +++ b/templates/ctl-scaffold/packages.dhall @@ -256,8 +256,8 @@ let additions = , "prelude" , "tuples" ] - , repo = "https://github.com/mlabs-haskell/purescript-bignumber" - , version = "58c51448be23c05caf51cde45bb3b09cc7169447" + , repo = "https://github.com/jy14898/purescript-bignumber" + , version = "705923edd892a3397b90d28ce7db9a7181dcd599" } , cardano-transaction-lib = { dependencies = @@ -273,6 +273,7 @@ let additions = , "avar" , "bifunctors" , "bigints" + , "bignumber" , "checked-exceptions" , "console" , "control" diff --git a/templates/ctl-scaffold/spago-packages.nix b/templates/ctl-scaffold/spago-packages.nix index 0dd10cce14..3e95e94df3 100644 --- a/templates/ctl-scaffold/spago-packages.nix +++ b/templates/ctl-scaffold/spago-packages.nix @@ -199,11 +199,11 @@ let "bignumber" = pkgs.stdenv.mkDerivation { name = "bignumber"; - version = "58c51448be23c05caf51cde45bb3b09cc7169447"; + version = "705923edd892a3397b90d28ce7db9a7181dcd599"; src = pkgs.fetchgit { - url = "https://github.com/mlabs-haskell/purescript-bignumber"; - rev = "58c51448be23c05caf51cde45bb3b09cc7169447"; - sha256 = "1q0zyq0ni2vcr99bnxn37ah6f1h3z9mhda4f0549x925mzm25d04"; + url = "https://github.com/jy14898/purescript-bignumber"; + rev = "705923edd892a3397b90d28ce7db9a7181dcd599"; + sha256 = "0wddkx161xk457r1mb1f1r79l8qgxja0xhdvxjd1ai43nwp9cgkf"; }; phases = "installPhase"; installPhase = "ln -s $src $out"; diff --git a/test/Blockfrost.purs b/test/Blockfrost.purs new file mode 100644 index 0000000000..b4e25d532f --- /dev/null +++ b/test/Blockfrost.purs @@ -0,0 +1,32 @@ +module Test.Ctl.Blockfrost where + +import Prelude + +import Aeson (class DecodeAeson, decodeJsonString) +import Control.Monad.Error.Class (liftEither) +import Ctl.Internal.Service.Blockfrost (BlockfrostProtocolParameters(BlockfrostProtocolParameters)) +import Data.Bifunctor (lmap) +import Effect (Effect) +import Effect.Aff (Aff, error, launchAff_) +import Node.Encoding (Encoding(UTF8)) +import Node.FS.Aff (readTextFile) +import Test.Spec.Assertions (shouldEqual) + +blockfrostFixture :: String +blockfrostFixture = "blockfrost/getProtocolParameters-7fe834fd628aa322eedeb3d8c7c1dd61.json" + +ogmiosFixture :: String +ogmiosFixture = "ogmios/currentProtocolParameters-9f10850f285b1493955267e900008841.json" + +loadFixture :: forall (a :: Type). DecodeAeson a => String -> Aff a +loadFixture fixture = + readTextFile UTF8 ("fixtures/test/" <> fixture) + <#> decodeJsonString >>> lmap (show >>> error) >>= liftEither + +main :: Effect Unit +main = launchAff_ do + BlockfrostProtocolParameters blockfrostFixture' + <- loadFixture blockfrostFixture + ogmiosFixture' <- loadFixture ogmiosFixture + + blockfrostFixture' `shouldEqual` ogmiosFixture' From 8e30b06e3042a16ddcaaa4f8eb82e68751f476c8 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Wed, 4 Jan 2023 13:27:38 +0000 Subject: [PATCH 225/373] Format and add test to unit test --- src/Internal/Contract/Monad.purs | 6 ++-- src/Internal/Contract/QueryHandle.purs | 3 +- src/Internal/Service/Blockfrost.purs | 44 +++++++++++++++++++------- test/Blockfrost.purs | 17 ++++++---- test/Unit.purs | 2 ++ 5 files changed, 50 insertions(+), 22 deletions(-) diff --git a/src/Internal/Contract/Monad.purs b/src/Internal/Contract/Monad.purs index d6db3c12f5..a05d0d08e3 100644 --- a/src/Internal/Contract/Monad.purs +++ b/src/Internal/Contract/Monad.purs @@ -20,9 +20,6 @@ import Prelude import Contract.Prelude (liftEither) import Control.Alt (class Alt) import Control.Alternative (class Alternative) -import Data.Bifunctor (lmap) -import Ctl.Internal.Service.Blockfrost (runBlockfrostServiceM) -import Ctl.Internal.Service.Blockfrost as Blockfrost import Control.Monad.Error.Class ( class MonadError , class MonadThrow @@ -59,9 +56,12 @@ import Ctl.Internal.QueryM.Kupo (isTxConfirmedAff) -- TODO: Move/translate these types into Cardano import Ctl.Internal.QueryM.Ogmios (ProtocolParameters, SystemStart(SystemStart)) as Ogmios import Ctl.Internal.Serialization.Address (NetworkId(TestnetId, MainnetId)) +import Ctl.Internal.Service.Blockfrost (runBlockfrostServiceM) +import Ctl.Internal.Service.Blockfrost as Blockfrost import Ctl.Internal.Types.UsedTxOuts (UsedTxOuts, isTxOutRefUsed, newUsedTxOuts) import Ctl.Internal.Wallet (Wallet, actionBasedOnWallet) import Ctl.Internal.Wallet.Spec (WalletSpec, mkWalletBySpec) +import Data.Bifunctor (lmap) import Data.Either (Either(Left, Right), isRight) import Data.Log.Level (LogLevel) import Data.Log.Message (Message) diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs index 3d5a72a4bd..ef235f8682 100644 --- a/src/Internal/Contract/QueryHandle.purs +++ b/src/Internal/Contract/QueryHandle.purs @@ -125,7 +125,8 @@ queryHandleForBlockfrostBackend _ backend = , getTxMetadata: runBlockfrostServiceM' <<< undefined , utxosAt: runBlockfrostServiceM' <<< undefined , getChainTip: runBlockfrostServiceM' undefined - , getCurrentEpoch: undefined $ runBlockfrostServiceM' Blockfrost.getCurrentEpoch + , getCurrentEpoch: undefined $ runBlockfrostServiceM' + Blockfrost.getCurrentEpoch , submitTx: runBlockfrostServiceM' <<< undefined , evaluateTx: \tx additionalUtxos -> runBlockfrostServiceM' $ undefined tx additionalUtxos diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index 56c5665680..9e57bb06c2 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -10,7 +10,15 @@ module Ctl.Internal.Service.Blockfrost import Prelude -import Aeson (class DecodeAeson, Finite, JsonDecodeError(..), decodeAeson, decodeJsonString, parseJsonStringToAeson, unpackFinite) +import Aeson + ( class DecodeAeson + , Finite + , JsonDecodeError(..) + , decodeAeson + , decodeJsonString + , parseJsonStringToAeson + , unpackFinite + ) import Affjax (Error, Response, URL, defaultRequest, request) as Affjax import Affjax.RequestBody (RequestBody) as Affjax import Affjax.RequestHeader (RequestHeader(ContentType, RequestHeader)) as Affjax @@ -23,10 +31,21 @@ import Control.Monad.Reader.Trans (ReaderT, runReaderT) import Ctl.Internal.Cardano.Types.Transaction (Costmdls(..)) import Ctl.Internal.Cardano.Types.Value (Coin(..)) import Ctl.Internal.Contract.QueryBackend (BlockfrostBackend) -import Ctl.Internal.QueryM.Ogmios (CoinsPerUtxoUnit(..), CostModelV1, CostModelV2, Epoch(..), ProtocolParameters(..), rationalToSubcoin, convertCostModel) +import Ctl.Internal.QueryM.Ogmios + ( CoinsPerUtxoUnit(..) + , CostModelV1 + , CostModelV2 + , Epoch(..) + , ProtocolParameters(..) + , convertCostModel + , rationalToSubcoin + ) import Ctl.Internal.QueryM.Ogmios as Ogmios import Ctl.Internal.ServerConfig (ServerConfig, mkHttpUrl) -import Ctl.Internal.Service.Error (ClientError(ClientHttpError, ClientHttpResponseError, ClientDecodeJsonError), ServiceError(ServiceBlockfrostError)) +import Ctl.Internal.Service.Error + ( ClientError(ClientHttpError, ClientHttpResponseError, ClientDecodeJsonError) + , ServiceError(ServiceBlockfrostError) + ) import Ctl.Internal.Types.Rational (Rational, reduce) import Ctl.Internal.Types.Scripts (Language(..)) import Data.Bifunctor (lmap) @@ -189,7 +208,8 @@ type BlockfrostProtocolParametersRaw = bigNumberToRational :: BigNumber -> Maybe Rational bigNumberToRational bn = do - let (numerator' /\ denominator') = toFraction bn (BigNumber.fromNumber infinity) + let + (numerator' /\ denominator') = toFraction bn (BigNumber.fromNumber infinity) numerator <- BigInt.fromString $ BigNumber.toString numerator' denominator <- BigInt.fromString $ BigNumber.toString denominator' reduce numerator denominator @@ -220,8 +240,8 @@ instance DecodeAeson BlockfrostProtocolParameters where (Left $ AtKey "coinsPerUtxoByte or coinsPerUtxoWord" $ MissingValue) pure $ (CoinsPerUtxoByte <<< Coin <<< unwrap <$> raw.coins_per_utxo_size) <|> - (CoinsPerUtxoWord <<< Coin <<< unwrap <$> raw.coins_per_utxo_word) - + (CoinsPerUtxoWord <<< Coin <<< unwrap <$> raw.coins_per_utxo_word) + pure $ BlockfrostProtocolParameters $ ProtocolParameters { protocolVersion: raw.protocol_major_ver /\ raw.protocol_minor_ver -- The following two parameters were removed from Babbage @@ -247,13 +267,13 @@ instance DecodeAeson BlockfrostProtocolParameters where ] , prices , maxTxExUnits: - { mem: unwrap raw.max_tx_ex_mem - , steps: unwrap raw.max_tx_ex_steps - } + { mem: unwrap raw.max_tx_ex_mem + , steps: unwrap raw.max_tx_ex_steps + } , maxBlockExUnits: - { mem: unwrap raw.max_block_ex_mem - , steps: unwrap raw.max_block_ex_steps - } + { mem: unwrap raw.max_block_ex_mem + , steps: unwrap raw.max_block_ex_steps + } , maxValueSize: unwrap raw.max_val_size , collateralPercent: raw.collateral_percent , maxCollateralInputs: raw.max_collateral_inputs diff --git a/test/Blockfrost.purs b/test/Blockfrost.purs index b4e25d532f..824bae9ad5 100644 --- a/test/Blockfrost.purs +++ b/test/Blockfrost.purs @@ -4,7 +4,9 @@ import Prelude import Aeson (class DecodeAeson, decodeJsonString) import Control.Monad.Error.Class (liftEither) -import Ctl.Internal.Service.Blockfrost (BlockfrostProtocolParameters(BlockfrostProtocolParameters)) +import Ctl.Internal.Service.Blockfrost + ( BlockfrostProtocolParameters(BlockfrostProtocolParameters) + ) import Data.Bifunctor (lmap) import Effect (Effect) import Effect.Aff (Aff, error, launchAff_) @@ -13,20 +15,23 @@ import Node.FS.Aff (readTextFile) import Test.Spec.Assertions (shouldEqual) blockfrostFixture :: String -blockfrostFixture = "blockfrost/getProtocolParameters-7fe834fd628aa322eedeb3d8c7c1dd61.json" +blockfrostFixture = + "blockfrost/getProtocolParameters-7fe834fd628aa322eedeb3d8c7c1dd61.json" ogmiosFixture :: String -ogmiosFixture = "ogmios/currentProtocolParameters-9f10850f285b1493955267e900008841.json" +ogmiosFixture = + "ogmios/currentProtocolParameters-9f10850f285b1493955267e900008841.json" loadFixture :: forall (a :: Type). DecodeAeson a => String -> Aff a loadFixture fixture = readTextFile UTF8 ("fixtures/test/" <> fixture) - <#> decodeJsonString >>> lmap (show >>> error) >>= liftEither + <#> decodeJsonString >>> lmap (show >>> error) + >>= liftEither main :: Effect Unit main = launchAff_ do - BlockfrostProtocolParameters blockfrostFixture' - <- loadFixture blockfrostFixture + BlockfrostProtocolParameters blockfrostFixture' <- loadFixture + blockfrostFixture ogmiosFixture' <- loadFixture ogmiosFixture blockfrostFixture' `shouldEqual` ogmiosFixture' diff --git a/test/Unit.purs b/test/Unit.purs index f6c54e9841..a63144d0ca 100644 --- a/test/Unit.purs +++ b/test/Unit.purs @@ -13,6 +13,7 @@ import Effect.Class (liftEffect) import Mote.Monad (mapTest) import Test.Ctl.ApplyArgs as ApplyArgs import Test.Ctl.Base64 as Base64 +import Test.Ctl.Blockfrost as Blockfrost import Test.Ctl.ByteArray as ByteArray import Test.Ctl.Data as Data import Test.Ctl.Data.Interval as Ctl.Data.Interval @@ -78,6 +79,7 @@ testPlan = do Ogmios.Address.suite Ogmios.Aeson.suite Ogmios.EvaluateTx.suite + Blockfrost.suite ProtocolParams.suite Types.TokenName.suite Types.Transaction.suite From d5f8dfa6ecfb287b9ae6185c3ab5726180f38231 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Wed, 4 Jan 2023 17:42:51 +0400 Subject: [PATCH 226/373] Add bignumber.js to package.json, update purescript-bignumber revision --- package.json | 11 ++++++----- packages.dhall | 2 +- spago-packages.nix | 6 +++--- templates/ctl-scaffold/package.json | 11 ++++++----- templates/ctl-scaffold/packages.dhall | 2 +- templates/ctl-scaffold/spago-packages.nix | 6 +++--- 6 files changed, 20 insertions(+), 18 deletions(-) diff --git a/package.json b/package.json index f71612d5ab..40cbcebad9 100755 --- a/package.json +++ b/package.json @@ -27,15 +27,17 @@ "author": "", "license": "MIT", "dependencies": { - "apply-args-browser": "0.0.1", - "apply-args-nodejs": "0.0.1", "@emurgo/cardano-message-signing-browser": "1.0.1", "@emurgo/cardano-message-signing-nodejs": "1.0.1", "@emurgo/cardano-serialization-lib-browser": "11.2.1", "@emurgo/cardano-serialization-lib-nodejs": "11.2.1", - "base64-js": "^1.5.1", + "@mlabs-haskell/json-bigint": " 1.0.0", "@noble/secp256k1": "^1.7.0", + "apply-args-browser": "0.0.1", + "apply-args-nodejs": "0.0.1", + "base64-js": "^1.5.1", "big-integer": "1.6.51", + "bignumber.js": "^9.1.1", "blakejs": "1.2.1", "bufferutil": "4.0.5", "jssha": "3.2.0", @@ -44,8 +46,7 @@ "reconnecting-websocket": "4.4.0", "uniqid": "5.4.0", "ws": "8.4.0", - "xhr2": "0.2.1", - "@mlabs-haskell/json-bigint": " 1.0.0" + "xhr2": "0.2.1" }, "devDependencies": { "buffer": "6.0.3", diff --git a/packages.dhall b/packages.dhall index e6ccb8b440..37ee1a8d42 100644 --- a/packages.dhall +++ b/packages.dhall @@ -161,7 +161,7 @@ let additions = , "tuples" ] , repo = "https://github.com/mlabs-haskell/purescript-bignumber" - , version = "58c51448be23c05caf51cde45bb3b09cc7169447" + , version = "705923edd892a3397b90d28ce7db9a7181dcd599" } , sequences = { dependencies = diff --git a/spago-packages.nix b/spago-packages.nix index 36b16259f0..8eb333490d 100644 --- a/spago-packages.nix +++ b/spago-packages.nix @@ -199,11 +199,11 @@ let "bignumber" = pkgs.stdenv.mkDerivation { name = "bignumber"; - version = "58c51448be23c05caf51cde45bb3b09cc7169447"; + version = "705923edd892a3397b90d28ce7db9a7181dcd599"; src = pkgs.fetchgit { url = "https://github.com/mlabs-haskell/purescript-bignumber"; - rev = "58c51448be23c05caf51cde45bb3b09cc7169447"; - sha256 = "1q0zyq0ni2vcr99bnxn37ah6f1h3z9mhda4f0549x925mzm25d04"; + rev = "705923edd892a3397b90d28ce7db9a7181dcd599"; + sha256 = "0wddkx161xk457r1mb1f1r79l8qgxja0xhdvxjd1ai43nwp9cgkf"; }; phases = "installPhase"; installPhase = "ln -s $src $out"; diff --git a/templates/ctl-scaffold/package.json b/templates/ctl-scaffold/package.json index ef6e42b2ad..1f5bcdf459 100644 --- a/templates/ctl-scaffold/package.json +++ b/templates/ctl-scaffold/package.json @@ -20,15 +20,17 @@ "author": "", "license": "MIT", "dependencies": { - "apply-args-browser": "0.0.1", - "apply-args-nodejs": "0.0.1", "@emurgo/cardano-message-signing-browser": "1.0.1", "@emurgo/cardano-message-signing-nodejs": "1.0.1", "@emurgo/cardano-serialization-lib-browser": "11.2.1", "@emurgo/cardano-serialization-lib-nodejs": "11.2.1", - "base64-js": "^1.5.1", + "@mlabs-haskell/json-bigint": " 1.0.0", "@noble/secp256k1": "^1.7.0", + "apply-args-browser": "0.0.1", + "apply-args-nodejs": "0.0.1", + "base64-js": "^1.5.1", "big-integer": "1.6.51", + "bignumber.js": "^9.1.1", "blakejs": "1.2.1", "bufferutil": "4.0.5", "jssha": "3.2.0", @@ -37,8 +39,7 @@ "reconnecting-websocket": "4.4.0", "uniqid": "5.4.0", "ws": "8.4.0", - "xhr2": "0.2.1", - "@mlabs-haskell/json-bigint": " 1.0.0" + "xhr2": "0.2.1" }, "devDependencies": { "buffer": "6.0.3", diff --git a/templates/ctl-scaffold/packages.dhall b/templates/ctl-scaffold/packages.dhall index 7518057751..4b2f6f20b4 100644 --- a/templates/ctl-scaffold/packages.dhall +++ b/templates/ctl-scaffold/packages.dhall @@ -257,7 +257,7 @@ let additions = , "tuples" ] , repo = "https://github.com/mlabs-haskell/purescript-bignumber" - , version = "58c51448be23c05caf51cde45bb3b09cc7169447" + , version = "705923edd892a3397b90d28ce7db9a7181dcd599" } , cardano-transaction-lib = { dependencies = diff --git a/templates/ctl-scaffold/spago-packages.nix b/templates/ctl-scaffold/spago-packages.nix index c7cba0da4a..b449047361 100644 --- a/templates/ctl-scaffold/spago-packages.nix +++ b/templates/ctl-scaffold/spago-packages.nix @@ -199,11 +199,11 @@ let "bignumber" = pkgs.stdenv.mkDerivation { name = "bignumber"; - version = "58c51448be23c05caf51cde45bb3b09cc7169447"; + version = "705923edd892a3397b90d28ce7db9a7181dcd599"; src = pkgs.fetchgit { url = "https://github.com/mlabs-haskell/purescript-bignumber"; - rev = "58c51448be23c05caf51cde45bb3b09cc7169447"; - sha256 = "1q0zyq0ni2vcr99bnxn37ah6f1h3z9mhda4f0549x925mzm25d04"; + rev = "705923edd892a3397b90d28ce7db9a7181dcd599"; + sha256 = "0wddkx161xk457r1mb1f1r79l8qgxja0xhdvxjd1ai43nwp9cgkf"; }; phases = "installPhase"; installPhase = "ln -s $src $out"; From 3cce42f464a3b0b7caf31087e4204d62789f3757 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Wed, 4 Jan 2023 17:54:28 +0400 Subject: [PATCH 227/373] Add a changelog entry --- CHANGELOG.md | 1 + 1 file changed, 1 insertion(+) diff --git a/CHANGELOG.md b/CHANGELOG.md index bde79f3fbe..8f267ee899 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -55,6 +55,7 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) ### Fixed - CIP-25 strings are now being split into chunks whose sizes are less than or equal to 64 to adhere to the CIP-25 standard ([#1343](https://github.com/Plutonomicon/cardano-transaction-lib/issues/1343)) +- Critical upstream fix in [`purescript-bignumber`](https://github.com/mlabs-haskell/purescript-bignumber/pull/2) ### Runtime Dependencies From 139870b6517ffc0d5ec35f71244e6fea955cafe5 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Wed, 4 Jan 2023 17:57:24 +0400 Subject: [PATCH 228/373] Update purescript-aeson revision as well --- packages.dhall | 2 +- spago-packages.nix | 6 +++--- templates/ctl-scaffold/packages.dhall | 2 +- templates/ctl-scaffold/spago-packages.nix | 6 +++--- 4 files changed, 8 insertions(+), 8 deletions(-) diff --git a/packages.dhall b/packages.dhall index 37ee1a8d42..ab77a74388 100644 --- a/packages.dhall +++ b/packages.dhall @@ -146,7 +146,7 @@ let additions = , "untagged-union" ] , repo = "https://github.com/mlabs-haskell/purescript-aeson.git" - , version = "9fd6e8241881d4b8ed9dcb6a80b166d3683f87b5" + , version = "bfd8f4dcd0522a076320f9dc710c24817438e02e" } , bignumber = { dependencies = diff --git a/spago-packages.nix b/spago-packages.nix index 8eb333490d..f1d2178963 100644 --- a/spago-packages.nix +++ b/spago-packages.nix @@ -7,11 +7,11 @@ let "aeson" = pkgs.stdenv.mkDerivation { name = "aeson"; - version = "9fd6e8241881d4b8ed9dcb6a80b166d3683f87b5"; + version = "bfd8f4dcd0522a076320f9dc710c24817438e02e"; src = pkgs.fetchgit { url = "https://github.com/mlabs-haskell/purescript-aeson.git"; - rev = "9fd6e8241881d4b8ed9dcb6a80b166d3683f87b5"; - sha256 = "1rzpf861gy86k9f3iydd3d02f78dh9fv22cbw650lyn5zjm0l3an"; + rev = "bfd8f4dcd0522a076320f9dc710c24817438e02e"; + sha256 = "1ywm51wqvwjqfrmhav6m4hyl9il3h77yyhzgyhvkvg0lkc0nn575"; }; phases = "installPhase"; installPhase = "ln -s $src $out"; diff --git a/templates/ctl-scaffold/packages.dhall b/templates/ctl-scaffold/packages.dhall index 4b2f6f20b4..a07ab0fd0f 100644 --- a/templates/ctl-scaffold/packages.dhall +++ b/templates/ctl-scaffold/packages.dhall @@ -146,7 +146,7 @@ let additions = , "untagged-union" ] , repo = "https://github.com/mlabs-haskell/purescript-aeson.git" - , version = "9fd6e8241881d4b8ed9dcb6a80b166d3683f87b5" + , version = "bfd8f4dcd0522a076320f9dc710c24817438e02e" } , sequences = { dependencies = diff --git a/templates/ctl-scaffold/spago-packages.nix b/templates/ctl-scaffold/spago-packages.nix index b449047361..98025dce43 100644 --- a/templates/ctl-scaffold/spago-packages.nix +++ b/templates/ctl-scaffold/spago-packages.nix @@ -7,11 +7,11 @@ let "aeson" = pkgs.stdenv.mkDerivation { name = "aeson"; - version = "9fd6e8241881d4b8ed9dcb6a80b166d3683f87b5"; + version = "bfd8f4dcd0522a076320f9dc710c24817438e02e"; src = pkgs.fetchgit { url = "https://github.com/mlabs-haskell/purescript-aeson.git"; - rev = "9fd6e8241881d4b8ed9dcb6a80b166d3683f87b5"; - sha256 = "1rzpf861gy86k9f3iydd3d02f78dh9fv22cbw650lyn5zjm0l3an"; + rev = "bfd8f4dcd0522a076320f9dc710c24817438e02e"; + sha256 = "1ywm51wqvwjqfrmhav6m4hyl9il3h77yyhzgyhvkvg0lkc0nn575"; }; phases = "installPhase"; installPhase = "ln -s $src $out"; From d5c06fa5f4bd86baaf50917168fc5c3c28c96945 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Wed, 4 Jan 2023 15:36:18 +0000 Subject: [PATCH 229/373] Fix kind --- test/Plutip/Staking.purs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/test/Plutip/Staking.purs b/test/Plutip/Staking.purs index 184f1fe4be..525d62f5dc 100644 --- a/test/Plutip/Staking.purs +++ b/test/Plutip/Staking.purs @@ -119,7 +119,7 @@ suite = do let -- A routine function that filters out retiring pool from the list of available -- pools - selectPoolId :: Contract () PoolPubKeyHash + selectPoolId :: Contract PoolPubKeyHash selectPoolId = do pools <- getPoolIds logInfo' "Pool IDs:" From 61f07b8ddf09cb52eb09fca1e0ecd0cdd98534af Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Wed, 4 Jan 2023 16:44:15 +0100 Subject: [PATCH 230/373] Refactor SystemStart and EraSummaries --- spago-packages.nix | 24 ++ spago.dhall | 1 + src/Contract/Time.purs | 24 +- src/Internal/Contract.purs | 7 +- src/Internal/Contract/Monad.purs | 31 ++- src/Internal/Contract/QueryHandle.purs | 22 +- src/Internal/Contract/WaitUntilSlot.purs | 15 +- src/Internal/QueryM.purs | 9 +- src/Internal/QueryM/EraSummaries.purs | 8 +- src/Internal/QueryM/Ogmios.purs | 292 +++++++---------------- src/Internal/Service/Blockfrost.purs | 8 +- src/Internal/Types/EraSummaries.purs | 5 + src/Internal/Types/Interval.purs | 29 +-- src/Internal/Types/ScriptLookups.purs | 5 +- src/Internal/Types/SystemStart.purs | 60 +++++ test/Ogmios/Aeson.purs | 4 +- test/Plutus/Time.purs | 27 ++- test/Types/Interval.purs | 11 +- 18 files changed, 276 insertions(+), 306 deletions(-) create mode 100644 src/Internal/Types/SystemStart.purs diff --git a/spago-packages.nix b/spago-packages.nix index 36b16259f0..90729b5333 100644 --- a/spago-packages.nix +++ b/spago-packages.nix @@ -401,6 +401,18 @@ let installPhase = "ln -s $src $out"; }; + "fixed-points" = pkgs.stdenv.mkDerivation { + name = "fixed-points"; + version = "v6.0.0"; + src = pkgs.fetchgit { + url = "https://github.com/purescript-contrib/purescript-fixed-points.git"; + rev = "3b643d948479aee7cd3e36c95258f1f84df0c35f"; + sha256 = "0w2j0sarylzsmg8b228pmn3qndif0bzw2vmxrx30ar15qy7jdb5d"; + }; + phases = "installPhase"; + installPhase = "ln -s $src $out"; + }; + "foldable-traversable" = pkgs.stdenv.mkDerivation { name = "foldable-traversable"; version = "v5.0.1"; @@ -461,6 +473,18 @@ let installPhase = "ln -s $src $out"; }; + "formatters" = pkgs.stdenv.mkDerivation { + name = "formatters"; + version = "v6.0.0"; + src = pkgs.fetchgit { + url = "https://github.com/purescript-contrib/purescript-formatters.git"; + rev = "b2e65b2bccd09a3c17a396f07e13e5cdca90e4e4"; + sha256 = "02c43sv6ci2698mjkmvkv3cjv99ilxv8ii8x7n9wqf18r4hlmk0y"; + }; + phases = "installPhase"; + installPhase = "ln -s $src $out"; + }; + "free" = pkgs.stdenv.mkDerivation { name = "free"; version = "v6.2.0"; diff --git a/spago.dhall b/spago.dhall index 71b0386eca..f715979bbd 100644 --- a/spago.dhall +++ b/spago.dhall @@ -29,6 +29,7 @@ You can edit this file as you like. , "foldable-traversable" , "foreign" , "foreign-object" + , "formatters" , "functions" , "gen" , "heterogeneous" diff --git a/src/Contract/Time.purs b/src/Contract/Time.purs index 8d54a62152..fae17b4bc2 100644 --- a/src/Contract/Time.purs +++ b/src/Contract/Time.purs @@ -4,7 +4,9 @@ module Contract.Time , getEraSummaries , getSystemStart , module Chain + , module ExportEraSummaries , module ExportOgmios + , module ExportSystemStart , module Interval , module SerializationAddress ) where @@ -24,23 +26,19 @@ import Ctl.Internal.Contract.Monad (wrapQueryM) import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.Helpers (liftM) import Ctl.Internal.QueryM.EraSummaries (getEraSummaries) as EraSummaries -import Ctl.Internal.QueryM.Ogmios - ( CurrentEpoch(CurrentEpoch) - , EpochLength(EpochLength) +import Ctl.Internal.QueryM.Ogmios (CurrentEpoch(CurrentEpoch)) +import Ctl.Internal.QueryM.Ogmios (CurrentEpoch(CurrentEpoch)) as ExportOgmios +import Ctl.Internal.Serialization.Address (BlockId(BlockId), Slot(Slot)) as SerializationAddress +import Ctl.Internal.Types.EraSummaries + ( EpochLength(EpochLength) , EraSummaries(EraSummaries) , EraSummary(EraSummary) , EraSummaryParameters(EraSummaryParameters) , RelativeTime(RelativeTime) , SafeZone(SafeZone) , SlotLength(SlotLength) - , SystemStart(SystemStart) - ) as ExportOgmios -import Ctl.Internal.QueryM.Ogmios - ( CurrentEpoch(CurrentEpoch) - , EraSummaries - , SystemStart - ) -import Ctl.Internal.Serialization.Address (BlockId(BlockId), Slot(Slot)) as SerializationAddress + ) as ExportEraSummaries +import Ctl.Internal.Types.EraSummaries (EraSummaries) import Ctl.Internal.Types.Interval ( AbsTime(AbsTime) , Closure @@ -96,6 +94,10 @@ import Ctl.Internal.Types.Interval , toOnchainPosixTimeRange , upperBound ) as Interval +import Ctl.Internal.Types.SystemStart (SystemStart) +import Ctl.Internal.Types.SystemStart + ( SystemStart(SystemStart) + ) as ExportSystemStart import Data.BigInt as BigInt import Data.UInt as UInt import Effect.Aff.Class (liftAff) diff --git a/src/Internal/Contract.purs b/src/Internal/Contract.purs index 1543ab0a45..783af8c827 100644 --- a/src/Internal/Contract.purs +++ b/src/Internal/Contract.purs @@ -7,12 +7,17 @@ import Ctl.Internal.Contract.Monad (Contract) import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.QueryM.Ogmios (ProtocolParameters) as Ogmios import Ctl.Internal.Types.Chain (Tip) +import Data.Either (either) import Effect.Aff.Class (liftAff) +import Effect.Class (liftEffect) +import Effect.Exception (throw) getChainTip :: Contract Tip getChainTip = do queryHandle <- getQueryHandle - liftAff $ queryHandle.getChainTip + liftAff $ + queryHandle.getChainTip + >>= either (liftEffect <<< throw <<< show) pure -- | Returns the `ProtocolParameters` from the environment. -- | Note that this is not necessarily the current value from the ledger. diff --git a/src/Internal/Contract/Monad.purs b/src/Internal/Contract/Monad.purs index 185b9aa96c..ce0e98b372 100644 --- a/src/Internal/Contract/Monad.purs +++ b/src/Internal/Contract/Monad.purs @@ -1,8 +1,9 @@ module Ctl.Internal.Contract.Monad ( Contract(Contract) - , ParContract(ParContract) , ContractEnv , ContractParams + , LedgerConstants + , ParContract(ParContract) , mkContractEnv , runContract , runContractInEnv @@ -52,9 +53,9 @@ import Ctl.Internal.QueryM , underlyingWebSocket ) import Ctl.Internal.QueryM.Kupo (isTxConfirmedAff) --- TODO: Move/translate these types into Cardano -import Ctl.Internal.QueryM.Ogmios (ProtocolParameters, SystemStart) as Ogmios +import Ctl.Internal.QueryM.Ogmios (ProtocolParameters) as Ogmios import Ctl.Internal.Serialization.Address (NetworkId(TestnetId, MainnetId)) +import Ctl.Internal.Types.SystemStart (SystemStart) import Ctl.Internal.Types.UsedTxOuts (UsedTxOuts, isTxOutRefUsed, newUsedTxOuts) import Ctl.Internal.Wallet (Wallet, actionBasedOnWallet) import Ctl.Internal.Wallet.Spec (WalletSpec, mkWalletBySpec) @@ -150,6 +151,13 @@ runContractInEnv contractEnv = -- ContractEnv -------------------------------------------------------------------------------- +-- `LedgerConstants` contains values that technically may change, but we assume +-- to be constant during Contract evaluation +type LedgerConstants = + { pparams :: Ogmios.ProtocolParameters + , systemStart :: SystemStart + } + type ContractEnv = { backend :: QueryBackend , networkId :: NetworkId @@ -160,12 +168,7 @@ type ContractEnv = , hooks :: Hooks , wallet :: Maybe Wallet , usedTxOuts :: UsedTxOuts - -- ledgerConstants are values that technically may change, but we assume to be - -- constant during Contract evaluation - , ledgerConstants :: - { pparams :: Ogmios.ProtocolParameters - , systemStart :: Ogmios.SystemStart - } + , ledgerConstants :: LedgerConstants } -- | Initializes a `Contract` environment. Does not ensure finalization. @@ -226,14 +229,8 @@ buildBackend logger = case _ of , kupoConfig } --- | Query for the ledger constants, ideally using the main backend -getLedgerConstants - :: Logger - -> QueryBackend - -> Aff - { pparams :: Ogmios.ProtocolParameters - , systemStart :: Ogmios.SystemStart - } +-- | Query for the ledger constants using the main backend. +getLedgerConstants :: Logger -> QueryBackend -> Aff LedgerConstants getLedgerConstants logger = case _ of CtlBackend { ogmios: { ws } } _ -> do pparams <- getProtocolParametersAff ws logger diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs index ea6d9d7a26..f0f389f0fa 100644 --- a/src/Internal/Contract/QueryHandle.purs +++ b/src/Internal/Contract/QueryHandle.purs @@ -33,11 +33,7 @@ import Ctl.Internal.QueryM.Kupo , isTxConfirmed , utxosAt ) as Kupo -import Ctl.Internal.QueryM.Ogmios - ( AdditionalUtxoSet - , CurrentEpoch - , EraSummaries - ) as Ogmios +import Ctl.Internal.QueryM.Ogmios (AdditionalUtxoSet, CurrentEpoch) as Ogmios import Ctl.Internal.QueryM.Ogmios (SubmitTxR(SubmitTxSuccess), TxEvaluationR) import Ctl.Internal.Serialization (convertTransaction, toBytes) as Serialization import Ctl.Internal.Serialization.Address (Address) @@ -46,12 +42,14 @@ import Ctl.Internal.Service.Blockfrost ( BlockfrostServiceM , runBlockfrostServiceM ) +import Ctl.Internal.Service.Blockfrost (getChainTip, getEraSummaries) as Blockfrost import Ctl.Internal.Service.Error (ClientError) import Ctl.Internal.Types.Chain as Chain import Ctl.Internal.Types.Datum (DataHash, Datum) +import Ctl.Internal.Types.EraSummaries (EraSummaries) import Ctl.Internal.Types.Transaction (TransactionHash, TransactionInput) import Ctl.Internal.Types.TransactionMetadata (GeneralTransactionMetadata) -import Data.Either (Either) +import Data.Either (Either(Right)) import Data.Maybe (Maybe(Just, Nothing), isJust) import Data.Newtype (unwrap, wrap) import Effect.Aff (Aff) @@ -67,12 +65,12 @@ type QueryHandle = , getUtxoByOref :: TransactionInput -> AffE (Maybe TransactionOutput) , isTxConfirmed :: TransactionHash -> AffE Boolean , utxosAt :: Address -> AffE UtxoMap - , getChainTip :: Aff Chain.Tip + , getChainTip :: AffE Chain.Tip , getCurrentEpoch :: Aff Ogmios.CurrentEpoch -- TODO Capture errors from all backends , submitTx :: Transaction -> Aff (Maybe TransactionHash) , evaluateTx :: Transaction -> Ogmios.AdditionalUtxoSet -> Aff TxEvaluationR - , getEraSummaries :: Aff Ogmios.EraSummaries + , getEraSummaries :: AffE EraSummaries } getQueryHandle :: Contract QueryHandle @@ -91,7 +89,7 @@ queryHandleForCtlBackend contractEnv backend = , isTxConfirmed: runQueryM' <<< map (map isJust) <<< Kupo.isTxConfirmed , getTxMetadata: runQueryM' <<< Kupo.getTxMetadata , utxosAt: runQueryM' <<< Kupo.utxosAt - , getChainTip: runQueryM' QueryM.getChainTip + , getChainTip: Right <$> runQueryM' QueryM.getChainTip , getCurrentEpoch: runQueryM' QueryM.getCurrentEpoch , submitTx: \tx -> runQueryM' do cslTx <- liftEffect $ Serialization.convertTransaction tx @@ -106,7 +104,7 @@ queryHandleForCtlBackend contractEnv backend = txBytes <- Serialization.toBytes <$> liftEffect (Serialization.convertTransaction tx) QueryM.evaluateTxOgmios txBytes additionalUtxos - , getEraSummaries: runQueryM' QueryM.getEraSummaries + , getEraSummaries: Right <$> runQueryM' QueryM.getEraSummaries } where runQueryM' :: forall (a :: Type). QueryM a -> Aff a @@ -121,12 +119,12 @@ queryHandleForBlockfrostBackend _ backend = , isTxConfirmed: runBlockfrostServiceM' <<< undefined , getTxMetadata: runBlockfrostServiceM' <<< undefined , utxosAt: runBlockfrostServiceM' <<< undefined - , getChainTip: runBlockfrostServiceM' undefined + , getChainTip: runBlockfrostServiceM' Blockfrost.getChainTip , getCurrentEpoch: runBlockfrostServiceM' undefined , submitTx: runBlockfrostServiceM' <<< undefined , evaluateTx: \tx additionalUtxos -> runBlockfrostServiceM' $ undefined tx additionalUtxos - , getEraSummaries: runBlockfrostServiceM' undefined + , getEraSummaries: runBlockfrostServiceM' Blockfrost.getEraSummaries } where runBlockfrostServiceM' :: forall (a :: Type). BlockfrostServiceM a -> Aff a diff --git a/src/Internal/Contract/WaitUntilSlot.purs b/src/Internal/Contract/WaitUntilSlot.purs index b0b755296e..c4266223d0 100644 --- a/src/Internal/Contract/WaitUntilSlot.purs +++ b/src/Internal/Contract/WaitUntilSlot.purs @@ -14,10 +14,10 @@ import Ctl.Internal.Contract (getChainTip) import Ctl.Internal.Contract.Monad (Contract) import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.Helpers (liftM) -import Ctl.Internal.QueryM.Ogmios (EraSummaries, SystemStart) import Ctl.Internal.Serialization.Address (Slot(Slot)) import Ctl.Internal.Types.BigNum as BigNum import Ctl.Internal.Types.Chain as Chain +import Ctl.Internal.Types.EraSummaries (EraSummaries) import Ctl.Internal.Types.Interval ( POSIXTime(POSIXTime) , findSlotEraSummary @@ -26,17 +26,18 @@ import Ctl.Internal.Types.Interval ) import Ctl.Internal.Types.Natural (Natural) import Ctl.Internal.Types.Natural as Natural +import Ctl.Internal.Types.SystemStart (SystemStart) import Data.Bifunctor (lmap) import Data.BigInt as BigInt import Data.DateTime.Instant (unInstant) -import Data.Either (hush) +import Data.Either (either, hush) import Data.Int as Int import Data.Newtype (unwrap, wrap) import Data.Time.Duration (Milliseconds(Milliseconds), Seconds) import Effect.Aff (Milliseconds, delay) import Effect.Aff.Class (liftAff) import Effect.Class (liftEffect) -import Effect.Exception (error) +import Effect.Exception (error, throw) import Effect.Now (now) -- | The returned slot will be no less than the slot provided as argument. @@ -48,7 +49,9 @@ waitUntilSlot futureSlot = do | slot >= futureSlot -> pure tip | otherwise -> do { systemStart } <- asks _.ledgerConstants - eraSummaries <- liftAff $ queryHandle.getEraSummaries + eraSummaries <- liftAff $ + queryHandle.getEraSummaries + >>= either (liftEffect <<< throw <<< show) pure slotLengthMs <- map getSlotLength $ liftEither $ lmap (const $ error "Unable to get current Era summary") $ findSlotEraSummary eraSummaries slot @@ -177,7 +180,9 @@ slotToEndPOSIXTime slot = do $ wrap <$> BigNum.add (unwrap slot) (BigNum.fromInt 1) { systemStart } <- asks _.ledgerConstants queryHandle <- getQueryHandle - eraSummaries <- liftAff $ queryHandle.getEraSummaries + eraSummaries <- liftAff $ + queryHandle.getEraSummaries + >>= either (liftEffect <<< throw <<< show) pure futureTime <- liftEffect $ slotToPosixTime eraSummaries systemStart futureSlot >>= hush >>> liftM (error "Unable to convert Slot to POSIXTime") diff --git a/src/Internal/QueryM.purs b/src/Internal/QueryM.purs index b2b26493cd..aff8952a5b 100644 --- a/src/Internal/QueryM.purs +++ b/src/Internal/QueryM.purs @@ -134,6 +134,7 @@ import Ctl.Internal.Types.ByteArray (byteArrayToHex) import Ctl.Internal.Types.CborBytes (CborBytes) import Ctl.Internal.Types.Chain as Chain import Ctl.Internal.Types.Scripts (PlutusScript) +import Ctl.Internal.Types.SystemStart (SystemStart) import Ctl.Internal.Wallet.Key (PrivatePaymentKey, PrivateStakeKey) import Data.Bifunctor (lmap) import Data.Either (Either(Left, Right), either, isRight) @@ -273,9 +274,9 @@ getProtocolParametersAff ogmiosWs logger = getSystemStartAff :: OgmiosWebSocket -> (LogLevel -> String -> Effect Unit) - -> Aff Ogmios.SystemStart + -> Aff SystemStart getSystemStartAff ogmiosWs logger = - mkOgmiosRequestAff ogmiosWs logger Ogmios.querySystemStartCall + unwrap <$> mkOgmiosRequestAff ogmiosWs logger Ogmios.querySystemStartCall _.systemStart unit @@ -627,9 +628,9 @@ type OgmiosListeners = , evaluate :: ListenerSet (CborBytes /\ AdditionalUtxoSet) Ogmios.TxEvaluationR , getProtocolParameters :: ListenerSet Unit Ogmios.ProtocolParameters - , eraSummaries :: ListenerSet Unit Ogmios.EraSummaries + , eraSummaries :: ListenerSet Unit Ogmios.OgmiosEraSummaries , currentEpoch :: ListenerSet Unit Ogmios.CurrentEpoch - , systemStart :: ListenerSet Unit Ogmios.SystemStart + , systemStart :: ListenerSet Unit Ogmios.OgmiosSystemStart , acquireMempool :: ListenerSet Unit Ogmios.MempoolSnapshotAcquired , mempoolHasTx :: ListenerSet TxHash Boolean , poolIds :: ListenerSet Unit PoolIdsR diff --git a/src/Internal/QueryM/EraSummaries.purs b/src/Internal/QueryM/EraSummaries.purs index f85cfaa6cc..5710cad39b 100644 --- a/src/Internal/QueryM/EraSummaries.purs +++ b/src/Internal/QueryM/EraSummaries.purs @@ -6,10 +6,12 @@ module Ctl.Internal.QueryM.EraSummaries import Prelude import Ctl.Internal.QueryM (QueryM, mkOgmiosRequest) -import Ctl.Internal.QueryM.Ogmios (EraSummaries, queryEraSummariesCall) as Ogmios +import Ctl.Internal.QueryM.Ogmios (queryEraSummariesCall) as Ogmios +import Ctl.Internal.Types.EraSummaries (EraSummaries) +import Data.Newtype (unwrap) -- | Get `EraSummaries` as used for Slot arithemetic. Details can be found -- | https://ogmios.dev/api/ under "eraSummaries" query -getEraSummaries :: QueryM Ogmios.EraSummaries +getEraSummaries :: QueryM EraSummaries getEraSummaries = - mkOgmiosRequest Ogmios.queryEraSummariesCall _.eraSummaries unit + unwrap <$> mkOgmiosRequest Ogmios.queryEraSummariesCall _.eraSummaries unit diff --git a/src/Internal/QueryM/Ogmios.purs b/src/Internal/QueryM/Ogmios.purs index 20cecb3da4..7b362ef36e 100644 --- a/src/Internal/QueryM/Ogmios.purs +++ b/src/Internal/QueryM/Ogmios.purs @@ -9,12 +9,6 @@ module Ctl.Internal.QueryM.Ogmios , CoinsPerUtxoUnit(CoinsPerUtxoByte, CoinsPerUtxoWord) , CurrentEpoch(CurrentEpoch) , DelegationsAndRewardsR(DelegationsAndRewardsR) - , Epoch(Epoch) - , EpochLength(EpochLength) - , EraSummaries(EraSummaries) - , EraSummary(EraSummary) - , EraSummaryParameters(EraSummaryParameters) - , EraSummaryTime(EraSummaryTime) , ExecutionUnits , MempoolSnapshotAcquired , OgmiosAddress @@ -26,8 +20,6 @@ module Ctl.Internal.QueryM.Ogmios , PoolParametersR(PoolParametersR) , ProtocolParameters(ProtocolParameters) , RedeemerPointer - , RelativeTime(RelativeTime) - , SafeZone(SafeZone) , ScriptFailure ( ExtraRedeemers , MissingRequiredDatums @@ -41,12 +33,12 @@ module Ctl.Internal.QueryM.Ogmios , AdditionalUtxoSet(AdditionalUtxoSet) , OgmiosUtxoMap , OgmiosDatum + , OgmiosEraSummaries(OgmiosEraSummaries) , OgmiosScript + , OgmiosSystemStart(OgmiosSystemStart) , OgmiosTxIn , OgmiosTxId - , SlotLength(SlotLength) , SubmitTxR(SubmitTxSuccess, SubmitFail) - , SystemStart(SystemStart) , TxEvaluationFailure(UnparsedError, ScriptFailures) , TxEvaluationResult(TxEvaluationResult) , TxEvaluationR(TxEvaluationR) @@ -85,12 +77,12 @@ import Aeson , caseAesonString , decodeAeson , encodeAeson + , fromArray , getField , getFieldOptional , getFieldOptional' , isNull , isString - , partialFiniteNumber , stringifyAeson , toString , (.:) @@ -156,6 +148,12 @@ import Ctl.Internal.Types.ByteArray , hexToByteArray ) import Ctl.Internal.Types.CborBytes (CborBytes, cborBytesToHex) +import Ctl.Internal.Types.EraSummaries + ( Epoch(Epoch) + , EraSummaries(EraSummaries) + , EraSummary(EraSummary) + , EraSummaryParameters(EraSummaryParameters) + ) import Ctl.Internal.Types.Int as Csl import Ctl.Internal.Types.Natural (Natural) import Ctl.Internal.Types.Natural (fromString) as Natural @@ -168,10 +166,16 @@ import Ctl.Internal.Types.Scripts ( Language(PlutusV1, PlutusV2) , PlutusScript(PlutusScript) ) +import Ctl.Internal.Types.SystemStart + ( SystemStart + , sysStartFromOgmiosTimestamp + , sysStartToOgmiosTimestamp + ) import Ctl.Internal.Types.TokenName (TokenName, getTokenName, mkTokenName) import Ctl.Internal.Types.VRFKeyHash (VRFKeyHash(VRFKeyHash)) import Data.Array (catMaybes, index, reverse) import Data.Array (head, length, replicate) as Array +import Data.Bifunctor (lmap) import Data.BigInt (BigInt) import Data.BigInt as BigInt import Data.Either (Either(Left, Right), either, note) @@ -215,7 +219,7 @@ import Untagged.Union (type (|+|), toEither1) -------------------------------------------------------------------------------- -- | Queries Ogmios for the system start Datetime -querySystemStartCall :: JsonWspCall Unit SystemStart +querySystemStartCall :: JsonWspCall Unit OgmiosSystemStart querySystemStartCall = mkOgmiosCallType { methodname: "Query" , args: const { query: "systemStart" } @@ -229,7 +233,7 @@ queryCurrentEpochCall = mkOgmiosCallType } -- | Queries Ogmios for an array of era summaries, used for Slot arithmetic. -queryEraSummariesCall :: JsonWspCall Unit EraSummaries +queryEraSummariesCall :: JsonWspCall Unit OgmiosEraSummaries queryEraSummariesCall = mkOgmiosCallType { methodname: "Query" , args: const { query: "eraSummaries" } @@ -371,17 +375,24 @@ instance DecodeAeson SubmitTxR where ) <|> (SubmitFail <$> getField o "SubmitFail") ---------------- SYSTEM START QUERY RESPONSE & PARSING -newtype SystemStart = SystemStart String +newtype OgmiosSystemStart = OgmiosSystemStart SystemStart -derive instance Generic SystemStart _ -derive instance Newtype SystemStart _ -derive newtype instance DecodeAeson SystemStart -derive newtype instance EncodeAeson SystemStart -derive newtype instance Eq SystemStart +derive instance Generic OgmiosSystemStart _ +derive instance Newtype OgmiosSystemStart _ +derive newtype instance Eq OgmiosSystemStart +-- derive newtype instance EncodeAeson OgmiosSystemStart -instance Show SystemStart where +instance Show OgmiosSystemStart where show = genericShow +instance DecodeAeson OgmiosSystemStart where + decodeAeson = + caseAesonString (Left (TypeMismatch "Timestamp string")) + (map wrap <<< lmap TypeMismatch <<< sysStartFromOgmiosTimestamp) + +instance EncodeAeson OgmiosSystemStart where + encodeAeson = encodeAeson <<< sysStartToOgmiosTimestamp <<< unwrap + ---------------- CURRENT EPOCH QUERY RESPONSE & PARSING newtype CurrentEpoch = CurrentEpoch BigInt @@ -397,205 +408,62 @@ instance Show CurrentEpoch where ---------------- ERA SUMMARY QUERY RESPONSE & PARSING -newtype EraSummaries = EraSummaries (Array EraSummary) +newtype OgmiosEraSummaries = OgmiosEraSummaries EraSummaries -derive instance Generic EraSummaries _ -derive instance Newtype EraSummaries _ -derive newtype instance Eq EraSummaries -derive newtype instance EncodeAeson EraSummaries +derive instance Generic OgmiosEraSummaries _ +derive instance Newtype OgmiosEraSummaries _ +derive newtype instance Eq OgmiosEraSummaries -instance Show EraSummaries where +instance Show OgmiosEraSummaries where show = genericShow -instance DecodeAeson EraSummaries where - decodeAeson = aesonArray (map wrap <<< traverse decodeAeson) - --- | From Ogmios: --- | start: An era bound which captures the time, slot and epoch at which the --- | era start. The time is relative to the start time of the network. --- | --- | end: An era bound which captures the time, slot and epoch at which the --- | era start. The time is relative to the start time of the network. --- | --- | parameters: Parameters that can vary across hard forks. -newtype EraSummary = EraSummary - { start :: EraSummaryTime - , end :: Maybe EraSummaryTime - , parameters :: EraSummaryParameters - } - -derive instance Generic EraSummary _ -derive instance Newtype EraSummary _ -derive newtype instance Eq EraSummary - -instance Show EraSummary where - show = genericShow - -instance DecodeAeson EraSummary where - decodeAeson = aesonObject $ \o -> do - start <- getField o "start" - -- The field "end" is required by Ogmios API, but it can optionally return - -- Null, so we want to fail if the field is absent but make Null value - -- acceptable in presence of the field (hence why "end" is wrapped in - -- `Maybe`). - end' <- getField o "end" - end <- if isNull end' then pure Nothing else Just <$> decodeAeson end' - parameters <- getField o "parameters" - pure $ wrap { start, end, parameters } - -instance EncodeAeson EraSummary where - encodeAeson (EraSummary { start, end, parameters }) = - encodeAeson - { "start": start - , "end": end - , "parameters": parameters - } - -newtype EraSummaryTime = EraSummaryTime - { time :: RelativeTime -- The time is relative to the start time of the network. - , slot :: Slot -- An absolute slot number - -- Ogmios returns a number 0-18446744073709552000 but our `Slot` is a Rust - -- u64 which has precision up to 18446744073709551615 (note 385 difference) - -- we treat this as neglible instead of defining `AbsSlot BigInt`. See - -- https://github.com/Plutonomicon/cardano-transaction-lib/issues/632 for - -- details. - , epoch :: Epoch -- 0-18446744073709552000, an epoch number or length, don't - -- use `Cardano.Types.Epoch` because Epoch is bounded by UInt also. - } - -derive instance Generic EraSummaryTime _ -derive instance Newtype EraSummaryTime _ -derive newtype instance Eq EraSummaryTime - -instance Show EraSummaryTime where - show = genericShow - -instance DecodeAeson EraSummaryTime where - decodeAeson = aesonObject $ \o -> do - time <- getField o "time" - slot <- getField o "slot" - epoch <- getField o "epoch" - pure $ wrap { time, slot, epoch } - -instance EncodeAeson EraSummaryTime where - encodeAeson (EraSummaryTime { time, slot, epoch }) = - encodeAeson - { "time": time - , "slot": slot - , "epoch": epoch - } - --- | A time in seconds relative to another one (typically, system start or era --- | start). [ 0 .. 18446744073709552000 ] -newtype RelativeTime = RelativeTime Number - -derive instance Generic RelativeTime _ -derive instance Newtype RelativeTime _ -derive newtype instance Eq RelativeTime -derive newtype instance Ord RelativeTime -derive newtype instance DecodeAeson RelativeTime - -instance EncodeAeson RelativeTime where - encodeAeson (RelativeTime rt) = - -- We assume the numbers are finite - encodeAeson $ unsafePartial partialFiniteNumber rt - -instance Show RelativeTime where - show (RelativeTime rt) = showWithParens "RelativeTime" rt - --- | An epoch number or length with greater precision for Ogmios than --- | `Cardano.Types.Epoch`. [ 0 .. 18446744073709552000 ] -newtype Epoch = Epoch BigInt - -derive instance Generic Epoch _ -derive instance Newtype Epoch _ -derive newtype instance Eq Epoch -derive newtype instance Ord Epoch -derive newtype instance DecodeAeson Epoch -derive newtype instance EncodeAeson Epoch - -instance Show Epoch where - show (Epoch e) = showWithParens "Epoch" e - -newtype EraSummaryParameters = EraSummaryParameters - { epochLength :: EpochLength -- 0-18446744073709552000 An epoch number or length. - , slotLength :: SlotLength -- <= MAX_SAFE_INTEGER (=9,007,199,254,740,992) - -- A slot length, in milliseconds, previously it has - -- a max limit of 18446744073709552000, now removed. - , safeZone :: SafeZone -- 0-18446744073709552000 Number of slots from the tip of - -- the ledger in which it is guaranteed that no hard fork can take place. - -- This should be (at least) the number of slots in which we are guaranteed - -- to have k blocks. - } - -derive instance Generic EraSummaryParameters _ -derive instance Newtype EraSummaryParameters _ -derive newtype instance Eq EraSummaryParameters - -instance Show EraSummaryParameters where - show = genericShow +instance DecodeAeson OgmiosEraSummaries where + decodeAeson = aesonArray (map (wrap <<< wrap) <<< traverse decodeEraSummary) + where + decodeEraSummary :: Aeson -> Either JsonDecodeError EraSummary + decodeEraSummary = aesonObject \o -> do + start <- getField o "start" + -- The field "end" is required by Ogmios API, but it can optionally return + -- Null, so we want to fail if the field is absent but make Null value + -- acceptable in presence of the field (hence why "end" is wrapped in + -- `Maybe`). + end' <- getField o "end" + end <- if isNull end' then pure Nothing else Just <$> decodeAeson end' + parameters <- decodeEraSummaryParameters =<< getField o "parameters" + pure $ wrap { start, end, parameters } + + decodeEraSummaryParameters + :: Object Aeson -> Either JsonDecodeError EraSummaryParameters + decodeEraSummaryParameters o = do + epochLength <- getField o "epochLength" + slotLength <- wrap <$> ((*) slotLengthFactor <$> getField o "slotLength") + safeZone <- fromMaybe zero <$> getField o "safeZone" + pure $ wrap { epochLength, slotLength, safeZone } + +instance EncodeAeson OgmiosEraSummaries where + encodeAeson (OgmiosEraSummaries (EraSummaries eraSummaries)) = + fromArray $ map encodeEraSummary eraSummaries + where + encodeEraSummary :: EraSummary -> Aeson + encodeEraSummary (EraSummary { start, end, parameters }) = + encodeAeson + { "start": start + , "end": end + , "parameters": encodeEraSummaryParameters parameters + } -instance DecodeAeson EraSummaryParameters where - decodeAeson = aesonObject $ \o -> do - epochLength <- getField o "epochLength" - slotLength <- wrap <$> ((*) slotLengthFactor <$> getField o "slotLength") - safeZone <- fromMaybe zero <$> getField o "safeZone" - pure $ wrap { epochLength, slotLength, safeZone } + encodeEraSummaryParameters :: EraSummaryParameters -> Aeson + encodeEraSummaryParameters (EraSummaryParameters params) = + encodeAeson + { "epochLength": params.epochLength + , "slotLength": params.slotLength + , "safeZone": params.safeZone + } --- | The EraSummaryParameters uses seconds and we use miliseconds --- use it to translate between them +-- Ogmios returns `slotLength` in seconds, and we use milliseconds, +-- so we need to convert between them. slotLengthFactor :: Number -slotLengthFactor = 1e3 - -instance EncodeAeson EraSummaryParameters where - encodeAeson (EraSummaryParameters { epochLength, slotLength, safeZone }) = - encodeAeson - { "epochLength": epochLength - , "slotLength": slotLength - , "safeZone": safeZone - } - --- | An epoch number or length. [ 0 .. 18446744073709552000 ] -newtype EpochLength = EpochLength BigInt - -derive instance Generic EpochLength _ -derive instance Newtype EpochLength _ -derive newtype instance Eq EpochLength -derive newtype instance DecodeAeson EpochLength -derive newtype instance EncodeAeson EpochLength - -instance Show EpochLength where - show (EpochLength el) = showWithParens "EpochLength" el - --- | A slot length, in milliseconds -newtype SlotLength = SlotLength Number - -derive instance Generic SlotLength _ -derive instance Newtype SlotLength _ -derive newtype instance Eq SlotLength -derive newtype instance DecodeAeson SlotLength -instance EncodeAeson SlotLength where - encodeAeson (SlotLength sl) = - -- We assume the numbers are finite - encodeAeson $ unsafePartial partialFiniteNumber sl - -instance Show SlotLength where - show (SlotLength sl) = showWithParens "SlotLength" sl - --- | Number of slots from the tip of the ledger in which it is guaranteed that --- | no hard fork can take place. This should be (at least) the number of slots --- | in which we are guaranteed to have k blocks. -newtype SafeZone = SafeZone BigInt - -derive instance Generic SafeZone _ -derive instance Newtype SafeZone _ -derive newtype instance Eq SafeZone -derive newtype instance Semiring SafeZone -derive newtype instance DecodeAeson SafeZone -derive newtype instance EncodeAeson SafeZone - -instance Show SafeZone where - show (SafeZone sz) = showWithParens "SafeZone" sz +slotLengthFactor = 1000.0 ---------------- DELEGATIONS & REWARDS QUERY RESPONSE & PARSING diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index 95bbaaf10b..c5256b89c5 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -40,9 +40,9 @@ import Ctl.Internal.Types.EraSummaries , EraSummary , EraSummaryParameters ) +import Ctl.Internal.Types.SystemStart (SystemStart) import Data.Bifunctor (lmap) import Data.BigInt (toNumber) as BigInt -import Data.DateTime (DateTime) import Data.DateTime.Instant (instant, toDateTime) import Data.Either (Either(Left, Right), note) import Data.Generic.Rep (class Generic) @@ -155,7 +155,7 @@ handleBlockfrostResponse (Right { status: Affjax.StatusCode statusCode, body }) -- Get blockchain information -------------------------------------------------------------------------------- -getSystemStart :: BlockfrostServiceM (Either ClientError DateTime) +getSystemStart :: BlockfrostServiceM (Either ClientError SystemStart) getSystemStart = runExceptT do (systemStart :: BlockfrostSystemStart) <- ExceptT $ handleBlockfrostResponse <$> @@ -178,7 +178,7 @@ getEraSummaries = runExceptT do -- BlockfrostSystemStart -------------------------------------------------------------------------------- -newtype BlockfrostSystemStart = BlockfrostSystemStart DateTime +newtype BlockfrostSystemStart = BlockfrostSystemStart SystemStart derive instance Generic BlockfrostSystemStart _ derive instance Newtype BlockfrostSystemStart _ @@ -190,7 +190,7 @@ instance DecodeAeson BlockfrostSystemStart where decodeAeson = aesonObject \obj -> do systemStart <- Seconds <<< BigInt.toNumber <$> getField obj "system_start" note (TypeMismatch "Unix timestamp") - (wrap <<< toDateTime <$> instant (convertDuration systemStart)) + (wrap <<< wrap <<< toDateTime <$> instant (convertDuration systemStart)) -------------------------------------------------------------------------------- -- BlockfrostChainTip diff --git a/src/Internal/Types/EraSummaries.purs b/src/Internal/Types/EraSummaries.purs index 64bb5e7437..398a2b4ade 100644 --- a/src/Internal/Types/EraSummaries.purs +++ b/src/Internal/Types/EraSummaries.purs @@ -73,6 +73,11 @@ instance Show EraSummary where -- | time: Time in seconds relative to the start time of the network. -- | -- | slot: Absolute slot number. +-- | Ogmios returns a number 0-18446744073709552000 but our `Slot` is a Rust u64 +-- | which has precision up to 18446744073709551615 (note 385 difference). +-- | We treat this as neglible instead of defining `AbsSlot BigInt`. +-- | See https://github.com/Plutonomicon/cardano-transaction-lib/issues/632 +-- | for details. -- | -- | epoch: Epoch number. newtype EraSummaryTime = EraSummaryTime diff --git a/src/Internal/Types/Interval.purs b/src/Internal/Types/Interval.purs index c01be5c783..2b72ffc87e 100644 --- a/src/Internal/Types/Interval.purs +++ b/src/Internal/Types/Interval.purs @@ -97,13 +97,7 @@ import Ctl.Internal.Plutus.Types.DataSchema , type (@@) , PNil ) -import Ctl.Internal.QueryM.Ogmios - ( EraSummaries(EraSummaries) - , EraSummary(EraSummary) - , SystemStart - , aesonObject - , slotLengthFactor - ) +import Ctl.Internal.QueryM.Ogmios (aesonObject, slotLengthFactor) import Ctl.Internal.Serialization.Address (Slot(Slot)) import Ctl.Internal.ToData (class ToData, genericToData, toData) import Ctl.Internal.TypeLevel.Nat (S, Z) @@ -115,7 +109,12 @@ import Ctl.Internal.Types.BigNum , toBigInt , zero ) as BigNum +import Ctl.Internal.Types.EraSummaries + ( EraSummaries(EraSummaries) + , EraSummary(EraSummary) + ) import Ctl.Internal.Types.PlutusData (PlutusData(Constr)) +import Ctl.Internal.Types.SystemStart (SystemStart, sysStartUnixTime) import Data.Argonaut.Encode.Encoders (encodeString) import Data.Array (find, head, index, length) import Data.Bifunctor (bimap, lmap) @@ -123,7 +122,6 @@ import Data.BigInt (BigInt) import Data.BigInt (fromInt, fromNumber, fromString, toNumber) as BigInt import Data.Either (Either(Left, Right), note) import Data.Generic.Rep (class Generic) -import Data.JSDate (getTime, parse) import Data.Lattice ( class BoundedJoinSemilattice , class BoundedMeetSemilattice @@ -138,7 +136,6 @@ import Data.Show.Generic (genericShow) import Data.Tuple (uncurry) import Data.Tuple.Nested (type (/\), (/\)) import Effect (Effect) -import Effect.Class (liftEffect) import Foreign.Object (Object) import Math (trunc, (%)) as Math import Partial.Unsafe (unsafePartial) @@ -708,8 +705,6 @@ slotToPosixTime -> Slot -> Effect (Either SlotToPosixTimeError POSIXTime) slotToPosixTime eraSummaries sysStart slot = runExceptT do - -- Get JSDate: - sysStartD <- liftEffect $ parse $ unwrap sysStart -- Find current era: currentEra <- liftEither $ findSlotEraSummary eraSummaries slot -- Convert absolute slot (relative to System start) to relative slot of era @@ -719,9 +714,7 @@ slotToPosixTime eraSummaries sysStart slot = runExceptT do relSlot absTime <- liftEither $ absTimeFromRelTime currentEra relTime -- Get POSIX time for system start - sysStartPosix <- liftM CannotGetBigIntFromNumber - $ BigInt.fromNumber - $ getTime sysStartD + sysStartPosix <- liftM CannotGetBigIntFromNumber $ sysStartUnixTime sysStart -- Add the system start time to the absolute time relative to system start -- to get overall POSIXTime pure $ wrap $ sysStartPosix + unwrap absTime @@ -949,12 +942,8 @@ posixTimeToSlot -> POSIXTime -> Effect (Either PosixTimeToSlotError Slot) posixTimeToSlot eraSummaries sysStart pt'@(POSIXTime pt) = runExceptT do - -- Get JSDate: - sysStartD <- liftEffect $ parse $ unwrap sysStart - -- Get POSIX time for system start - sysStartPosix <- liftM CannotGetBigIntFromNumber' - $ BigInt.fromNumber - $ getTime sysStartD + -- Get POSIX time for system start: + sysStartPosix <- liftM CannotGetBigIntFromNumber' $ sysStartUnixTime sysStart -- Ensure the time we are converting is after the system start, otherwise -- we have negative slots. unless (sysStartPosix <= pt) diff --git a/src/Internal/Types/ScriptLookups.purs b/src/Internal/Types/ScriptLookups.purs index 86e4c68236..e520230681 100644 --- a/src/Internal/Types/ScriptLookups.purs +++ b/src/Internal/Types/ScriptLookups.purs @@ -270,6 +270,7 @@ import Data.Tuple.Nested (type (/\), (/\)) import Effect (Effect) import Effect.Aff.Class (liftAff) import Effect.Class (liftEffect) +import Effect.Exception (throw) import MedeaPrelude (mapMaybe) import Prelude (join) as Bind import Type.Proxy (Proxy(Proxy)) @@ -1051,7 +1052,9 @@ processConstraint mpsMap osMap c = do MustIncludeDatum dat -> addDatum dat MustValidateIn posixTimeRange -> do { systemStart } <- asks _.ledgerConstants - eraSummaries <- liftAff $ queryHandle.getEraSummaries + eraSummaries <- liftAff $ + queryHandle.getEraSummaries + >>= either (liftEffect <<< throw <<< show) pure runExceptT do ({ timeToLive, validityStartInterval }) <- ExceptT $ liftEffect $ posixTimeRangeToTransactionValidity eraSummaries diff --git a/src/Internal/Types/SystemStart.purs b/src/Internal/Types/SystemStart.purs new file mode 100644 index 0000000000..87f27e1f70 --- /dev/null +++ b/src/Internal/Types/SystemStart.purs @@ -0,0 +1,60 @@ +module Ctl.Internal.Types.SystemStart + ( SystemStart(SystemStart) + , sysStartFromOgmiosTimestamp + , sysStartFromOgmiosTimestampUnsafe + , sysStartToOgmiosTimestamp + , sysStartUnixTime + ) where + +import Prelude + +import Control.Alt ((<|>)) +import Data.BigInt (BigInt) +import Data.BigInt (fromNumber) as BigInt +import Data.DateTime (DateTime) +import Data.DateTime.Instant (fromDateTime, unInstant) +import Data.Either (Either, hush) +import Data.Formatter.DateTime (Formatter, format, parseFormatString, unformat) +import Data.Generic.Rep (class Generic) +import Data.Maybe (Maybe, fromJust) +import Data.Newtype (class Newtype, unwrap, wrap) +import Data.Show.Generic (genericShow) +import Partial.Unsafe (unsafePartial) + +newtype SystemStart = SystemStart DateTime + +derive instance Generic SystemStart _ +derive instance Newtype SystemStart _ +derive newtype instance Eq SystemStart + +instance Show SystemStart where + show = genericShow + +-- | Returns system start Unix time in milliseconds as `BigInt`. +sysStartUnixTime :: SystemStart -> Maybe BigInt +sysStartUnixTime (SystemStart dateTime) = + BigInt.fromNumber $ unwrap $ unInstant $ fromDateTime dateTime + +-- | Attempts to parse `SystemStart` from Ogmios timestamp string. +sysStartFromOgmiosTimestamp :: String -> Either String SystemStart +sysStartFromOgmiosTimestamp timestamp = + wrap <$> -- FIXME: Unit test with Ogmios fixtures fails. + ( unformat ogmiosDateTimeFormatterMsec timestamp + <|> unformat ogmiosDateTimeFormatterSec timestamp + ) + +sysStartFromOgmiosTimestampUnsafe :: String -> SystemStart +sysStartFromOgmiosTimestampUnsafe timestamp = + unsafePartial fromJust $ hush $ sysStartFromOgmiosTimestamp timestamp + +sysStartToOgmiosTimestamp :: SystemStart -> String +sysStartToOgmiosTimestamp = format ogmiosDateTimeFormatterMsec <<< unwrap + +ogmiosDateTimeFormatterSec :: Formatter +ogmiosDateTimeFormatterSec = + unsafePartial fromJust $ hush $ parseFormatString "YYYY-MM-DDTHH:mm:ssZ" + +ogmiosDateTimeFormatterMsec :: Formatter +ogmiosDateTimeFormatterMsec = + unsafePartial fromJust $ hush $ parseFormatString "YYYY-MM-DDTHH:mm:ss.SSSZ" + diff --git a/test/Ogmios/Aeson.purs b/test/Ogmios/Aeson.purs index a499f6a1bf..9a6b69c4bf 100644 --- a/test/Ogmios/Aeson.purs +++ b/test/Ogmios/Aeson.purs @@ -163,8 +163,8 @@ suite = group "Ogmios Aeson tests" do case query of "chainTip" -> handle (Proxy :: _ O.ChainTipQR) "currentEpoch" -> handle (Proxy :: _ O.CurrentEpoch) - "systemStart" -> handle (Proxy :: _ O.SystemStart) - "eraSummaries" -> handle (Proxy :: _ O.EraSummaries) + "systemStart" -> handle (Proxy :: _ O.OgmiosSystemStart) + "eraSummaries" -> handle (Proxy :: _ O.OgmiosEraSummaries) "currentProtocolParameters" -> handle (Proxy :: _ O.ProtocolParameters) "poolIds" -> handle diff --git a/test/Plutus/Time.purs b/test/Plutus/Time.purs index 120b37d2e8..f8730d92e2 100644 --- a/test/Plutus/Time.purs +++ b/test/Plutus/Time.purs @@ -5,6 +5,13 @@ module Test.Ctl.Internal.Plutus.Time import Prelude import Ctl.Internal.QueryM.Ogmios + ( OgmiosEraSummaries(OgmiosEraSummaries) + , OgmiosSystemStart + ) +import Ctl.Internal.Serialization.Address (Slot(Slot)) +import Ctl.Internal.Test.TestPlanM (TestPlanM) +import Ctl.Internal.Types.BigNum as BigNum +import Ctl.Internal.Types.EraSummaries ( Epoch(Epoch) , EpochLength(EpochLength) , EraSummaries(EraSummaries) @@ -14,11 +21,7 @@ import Ctl.Internal.QueryM.Ogmios , RelativeTime(RelativeTime) , SafeZone(SafeZone) , SlotLength(SlotLength) - , SystemStart(SystemStart) ) -import Ctl.Internal.Serialization.Address (Slot(Slot)) -import Ctl.Internal.Test.TestPlanM (TestPlanM) -import Ctl.Internal.Types.BigNum as BigNum import Ctl.Internal.Types.Interval ( AbsTime(AbsTime) , ModTime(ModTime) @@ -40,6 +43,7 @@ import Ctl.Internal.Types.Interval ) , ToOnChainPosixTimeRangeError(PosixTimeToSlotError', SlotToPosixTimeError') ) +import Ctl.Internal.Types.SystemStart (sysStartFromOgmiosTimestampUnsafe) import Data.BigInt as BigInt import Data.Int as Int import Data.Maybe (Maybe(Just, Nothing)) @@ -78,8 +82,9 @@ relSlotFixture = RelSlot $ BigInt.fromInt 12855 currentEpochFixture :: Epoch currentEpochFixture = Epoch $ BigInt.fromInt 58326646 -systemStartFixture :: SystemStart -systemStartFixture = SystemStart "2019-07-24T20:20:16Z" +systemStartFixture :: OgmiosSystemStart +systemStartFixture = + wrap $ sysStartFromOgmiosTimestampUnsafe "2019-07-24T20:20:16Z" mkRelativeTime :: Int -> RelativeTime mkRelativeTime = RelativeTime <<< BigInt.toNumber <<< BigInt.fromInt @@ -224,9 +229,9 @@ eraSummaryLengthToSeconds old@(EraSummary { parameters }) = in wrap (unwrap old) { parameters = newParameters } -eraSummariesLengthToSeconds :: EraSummaries -> EraSummaries -eraSummariesLengthToSeconds values = - wrap (eraSummaryLengthToSeconds <$> unwrap values) +eraSummariesLengthToSeconds :: OgmiosEraSummaries -> OgmiosEraSummaries +eraSummariesLengthToSeconds (OgmiosEraSummaries values) = + wrap $ wrap (eraSummaryLengthToSeconds <$> unwrap values) suite :: TestPlanM (Aff Unit) Unit suite = do @@ -257,7 +262,7 @@ suite = do toFromAesonTest "AbsTime" absTimeFixture toFromAesonTest "RelSlot" relSlotFixture toFromAesonTest "RelTime" relTimeFixture - toFromAesonTestWith "EraSummaries" eraSummariesLengthToSeconds - eraSummariesFixture + toFromAesonTestWith "EraSummaries" eraSummariesLengthToSeconds $ + OgmiosEraSummaries eraSummariesFixture toFromAesonTest "SystemStart" systemStartFixture toFromAesonTest "CurrentEpoch" currentEpochFixture diff --git a/test/Types/Interval.purs b/test/Types/Interval.purs index 61f901fc45..c06af813e9 100644 --- a/test/Types/Interval.purs +++ b/test/Types/Interval.purs @@ -9,10 +9,11 @@ import Prelude import Aeson (class DecodeAeson, decodeJsonString, printJsonDecodeError) import Control.Monad.Error.Class (liftEither) import Control.Monad.Except (throwError) -import Ctl.Internal.QueryM.Ogmios (EraSummaries, SystemStart) +import Ctl.Internal.QueryM.Ogmios (OgmiosEraSummaries, OgmiosSystemStart) import Ctl.Internal.Serialization.Address (Slot(Slot)) import Ctl.Internal.Test.TestPlanM (TestPlanM) import Ctl.Internal.Types.BigNum (fromInt) as BigNum +import Ctl.Internal.Types.EraSummaries (EraSummaries) import Ctl.Internal.Types.Interval ( Interval , POSIXTime(POSIXTime) @@ -30,10 +31,12 @@ import Ctl.Internal.Types.Interval , slotToPosixTime , to ) +import Ctl.Internal.Types.SystemStart (SystemStart) import Data.Bifunctor (lmap) import Data.BigInt (fromInt, fromString) as BigInt import Data.Either (Either(Left, Right), either) import Data.Maybe (fromJust) +import Data.Newtype (unwrap) import Data.Traversable (traverse_) import Effect (Effect) import Effect.Exception (error) @@ -82,11 +85,13 @@ loadOgmiosFixture query hash = do eraSummariesFixture :: Effect EraSummaries eraSummariesFixture = - loadOgmiosFixture "eraSummaries" "bbf8b1d7d2487e750104ec2b5a31fa86" + (unwrap :: OgmiosEraSummaries -> EraSummaries) <$> + loadOgmiosFixture "eraSummaries" "bbf8b1d7d2487e750104ec2b5a31fa86" systemStartFixture :: Effect SystemStart systemStartFixture = - loadOgmiosFixture "systemStart" "ed0caad81f6936e0c122ef6f3c7de5e8" + (unwrap :: OgmiosSystemStart -> SystemStart) <$> + loadOgmiosFixture "systemStart" "ed0caad81f6936e0c122ef6f3c7de5e8" testPosixTimeToSlot :: EraSummaries -> SystemStart -> Effect Unit testPosixTimeToSlot eraSummaries sysStart = do From e6dd647bba10f513e6a8470398342c6ee942b9a4 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Wed, 4 Jan 2023 19:48:53 +0400 Subject: [PATCH 231/373] Fix formatting --- src/Contract/AuxiliaryData.purs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Contract/AuxiliaryData.purs b/src/Contract/AuxiliaryData.purs index 718d930612..ac30da8db0 100644 --- a/src/Contract/AuxiliaryData.purs +++ b/src/Contract/AuxiliaryData.purs @@ -33,10 +33,10 @@ import Data.Maybe (Maybe, fromMaybe) import Data.Tuple (Tuple(Tuple)) import Effect.Class (liftEffect) --- These functions involve `UnattachedUnbalancedTx`, +-- These functions involve `UnattachedUnbalancedTx`, -- which in turn involve `UnbalancedTx`. These functions involve ScriptOutput, -- which is the type currently being used in more recent Plutus code (as opposed to `TransactionOutput`). --- As a result, no conversion will be provided. +-- As a result, no conversion will be provided. -- It is worth noting that `UnattachedUnbalancedTx` also includes Cardano-style Redeemers, -- which must be reattached later on (see Types.ScriptLookups for more information). -- There does not appear to be a way around this. From e8690a2b7d6ee7d65749d862a76b49253eb65b2f Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Wed, 4 Jan 2023 16:20:58 +0000 Subject: [PATCH 232/373] Fix test --- src/Internal/Contract/Monad.purs | 4 ++-- test/Blockfrost.purs | 24 +++++++++++++++++++----- 2 files changed, 21 insertions(+), 7 deletions(-) diff --git a/src/Internal/Contract/Monad.purs b/src/Internal/Contract/Monad.purs index a05d0d08e3..5cda7c6e33 100644 --- a/src/Internal/Contract/Monad.purs +++ b/src/Internal/Contract/Monad.purs @@ -242,8 +242,8 @@ getLedgerConstants logger = case _ of pparams <- getProtocolParametersAff ws logger systemStart <- getSystemStartAff ws logger pure { pparams, systemStart } - BlockfrostBackend blockfrost _ -> do - pparams <- runBlockfrostServiceM blockfrost Blockfrost.getProtocolParameters + BlockfrostBackend blockfrost _ -> runBlockfrostServiceM blockfrost do + pparams <- Blockfrost.getProtocolParameters >>= lmap (show >>> error) >>> liftEither let systemStart = Ogmios.SystemStart "2022-10-25T00:00:00Z" diff --git a/test/Blockfrost.purs b/test/Blockfrost.purs index 824bae9ad5..0664d49035 100644 --- a/test/Blockfrost.purs +++ b/test/Blockfrost.purs @@ -1,9 +1,12 @@ -module Test.Ctl.Blockfrost where +module Test.Ctl.Blockfrost (main, suite) where import Prelude import Aeson (class DecodeAeson, decodeJsonString) +import Contract.Test.Mote (TestPlanM, interpretWithConfig) import Control.Monad.Error.Class (liftEither) +import Test.Spec.Runner (defaultConfig) +import Mote (group, test) import Ctl.Internal.Service.Blockfrost ( BlockfrostProtocolParameters(BlockfrostProtocolParameters) ) @@ -14,6 +17,9 @@ import Node.Encoding (Encoding(UTF8)) import Node.FS.Aff (readTextFile) import Test.Spec.Assertions (shouldEqual) +-- These fixtures were aquired soon after each other, so we can compare their +-- parsed results + blockfrostFixture :: String blockfrostFixture = "blockfrost/getProtocolParameters-7fe834fd628aa322eedeb3d8c7c1dd61.json" @@ -30,8 +36,16 @@ loadFixture fixture = main :: Effect Unit main = launchAff_ do - BlockfrostProtocolParameters blockfrostFixture' <- loadFixture - blockfrostFixture - ogmiosFixture' <- loadFixture ogmiosFixture + interpretWithConfig + defaultConfig + suite + +suite :: TestPlanM (Aff Unit) Unit +suite = do + group "Blockfrost" do + test "ProtocolParameter parsing" do + BlockfrostProtocolParameters blockfrostFixture' <- loadFixture + blockfrostFixture + ogmiosFixture' <- loadFixture ogmiosFixture - blockfrostFixture' `shouldEqual` ogmiosFixture' + blockfrostFixture' `shouldEqual` ogmiosFixture' From 76f2d0142df03c5c02d6d023e68c1ac63b70e160 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Thu, 5 Jan 2023 00:04:34 +0400 Subject: [PATCH 233/373] Add docs section for assertions interface, improve docstrings for test utils --- doc/plutip-testing.md | 32 ++++++++++++++++++++++++++++++++ src/Contract/Test/Utils.purs | 17 +++++++++++++++-- 2 files changed, 47 insertions(+), 2 deletions(-) diff --git a/doc/plutip-testing.md b/doc/plutip-testing.md index 6a5aa7e166..d458810db5 100644 --- a/doc/plutip-testing.md +++ b/doc/plutip-testing.md @@ -13,6 +13,7 @@ - [Note on SIGINT](#note-on-sigint) - [Testing with Nix](#testing-with-nix) - [Using addresses with staking key components](#using-addresses-with-staking-key-components) +- [CTL/Plutip utilities for testing](#ctlplutip-utilities-for-testing) ## Architecture @@ -193,3 +194,34 @@ let Although stake keys serve no real purpose in plutip context, they allow to use base addresses, and thus allow to have the same code for plutip testing, in-browser tests and production. Note that CTL re-distributes tADA from payment key-only ("enterprise") addresses to base addresses, which requires a few transactions before the test can be run. Plutip can currently handle only enterprise addreses (see [this issue](https://github.com/mlabs-haskell/plutip/issues/103)). + +## CTL/Plutip utilities for testing + +`Contract.Test.Utils` module provides a DSL for assertions that accumulate error messages, instead of exiting early after the first failure. + +The interpreter is `withAssertions` function, that accepts two arrays for two kinds of assertions: + +- `ContractBasicAssertion` is simply executed at the end of `Contract` lifetime +- `ContractWrapAssertion` can inspect the state both before and after `Contract` execution, allowing to monitor for effects, e.g. monetary gains/losses at address + +`withAssertions` supports both of them via a `ContractAssertions` typeclass: + +```purescript +withAssertions + :: forall (r :: Row Type) (a :: Type) (assertions :: Type) + . ContractAssertions assertions r a + => assertions + -> Contract r a + -> Contract r a +``` + +The typeclass allows to combine multiple assertions using `Array`s and `Tuple`s. For example, `assertions` type variable from the snippet above can be instantiated with something like this: + +```purescript +Array (ContractWrapAssertion () ContractResult) + /\ Array (ContractBasicAssertion () ContractResult Unit) +``` + +Particular values can be constructed with utility functions, as demonstrated in the [ContractTestUtils example](../examples/ContractTestUtils.purs) (see `mkAssertions`). + +All the functions require `Labeled` arguments, that can be constructed with `label` function; or `noLabel`, if descriptive names in error messages are not needed. diff --git a/src/Contract/Test/Utils.purs b/src/Contract/Test/Utils.purs index c8df7b838a..b889787f2d 100644 --- a/src/Contract/Test/Utils.purs +++ b/src/Contract/Test/Utils.purs @@ -357,6 +357,8 @@ valueAtAddress valueAtAddress = map (foldMap (view (_output <<< _amount))) <<< utxosAtAddress +-- | Assert anything about `Value`s before and after `Contract` execution, as +-- | well as the `Contract` output `w`. checkBalanceDeltaAtAddress :: forall (r :: Row Type) (w :: Type) (a :: Type) . Labeled Address @@ -370,6 +372,7 @@ checkBalanceDeltaAtAddress addr contract check = do valueAfter <- valueAtAddress addr check res valueBefore valueAfter +-- | Assert anything about newly appeared UTxOs at address. checkNewUtxosAtAddress :: forall (r :: Row Type) (w :: Type) (a :: Type) . Labeled Address @@ -381,6 +384,11 @@ checkNewUtxosAtAddress addr txHash check = check $ Array.fromFoldable $ Map.values $ Map.filterKeys (\oref -> (unwrap oref).transactionId == txHash) utxos +-- | Assert that Ada delta (`after - before`) satisfies a predicate. +-- | Once the *actual difference* is computed, it is passed as the first +-- | parameter to the predicate. +-- | The *expected difference* is retrieved using the second parameter of this +-- | function, and is passed as the second parameter to the predicate. assertLovelaceDeltaAtAddress :: forall (r :: Row Type) (a :: Type) . Labeled Address @@ -443,6 +451,11 @@ assertLossAtAddress' assertLossAtAddress' addr minLoss = assertLossAtAddress addr (const $ pure minLoss) +-- | Assert that token delta (`after - before`) satisfies a predicate. +-- | Once the *actual difference* is computed, it is passed as the first +-- | parameter to the predicate. +-- | The *expected difference* is retrieved using the third parameter of this +-- | function, and is passed as the second parameter to the predicate. assertTokenDeltaAtAddress :: forall (r :: Row Type) (a :: Type) . Labeled Address @@ -632,8 +645,8 @@ checkTxHasMetadata txHash = foreign import exitCode :: Int -> Effect Unit --- | attaches a custom handler on SIGINt to kill the fiber. --- | see `doc/plutip-testing#custom-SIGINT-handlers` +-- | Attaches a custom handler on SIGINt to kill the fiber. +-- | see https://github.com/Plutonomicon/cardano-transaction-lib/blob/develop/doc/plutip-testing.md#note-on-sigint interruptOnSignal :: forall a. Signal -> Fiber a -> Effect Unit interruptOnSignal signal fiber = Process.onSignal signal do launchAff_ do From e8850156e4ccc4f743c67f7628efd36be96e234d Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Wed, 4 Jan 2023 21:26:26 +0000 Subject: [PATCH 234/373] Remove undefined from current epoch --- src/Internal/Contract/QueryHandle.purs | 8 ++++++-- src/Internal/Service/Blockfrost.purs | 8 +++++--- 2 files changed, 11 insertions(+), 5 deletions(-) diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs index ef235f8682..ac6afc2189 100644 --- a/src/Internal/Contract/QueryHandle.purs +++ b/src/Internal/Contract/QueryHandle.purs @@ -7,8 +7,11 @@ module Ctl.Internal.Contract.QueryHandle import Prelude import Contract.Log (logDebug') +import Control.Monad.Error.Class (liftEither) import Control.Monad.Reader.Class (ask) import Ctl.Internal.Cardano.Types.ScriptRef (ScriptRef) +import Effect.Exception (error) +import Data.Bifunctor (bimap) import Ctl.Internal.Cardano.Types.Transaction ( Transaction , TransactionOutput @@ -125,8 +128,9 @@ queryHandleForBlockfrostBackend _ backend = , getTxMetadata: runBlockfrostServiceM' <<< undefined , utxosAt: runBlockfrostServiceM' <<< undefined , getChainTip: runBlockfrostServiceM' undefined - , getCurrentEpoch: undefined $ runBlockfrostServiceM' - Blockfrost.getCurrentEpoch + , getCurrentEpoch: + runBlockfrostServiceM' Blockfrost.getCurrentEpoch + >>= bimap (show >>> error) wrap >>> liftEither , submitTx: runBlockfrostServiceM' <<< undefined , evaluateTx: \tx additionalUtxos -> runBlockfrostServiceM' $ undefined tx additionalUtxos diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index 9e57bb06c2..b57d529872 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -280,9 +280,11 @@ instance DecodeAeson BlockfrostProtocolParameters where } getCurrentEpoch - :: BlockfrostServiceM (Either ClientError BlockfrostCurrentEpoch) -getCurrentEpoch = blockfrostGetRequest GetCurrentEpoch - <#> handleBlockfrostResponse + :: BlockfrostServiceM (Either ClientError BigInt) +getCurrentEpoch = runExceptT do + BlockfrostCurrentEpoch { epoch } <- ExceptT $ blockfrostGetRequest GetCurrentEpoch + <#> handleBlockfrostResponse + pure epoch getProtocolParameters :: BlockfrostServiceM (Either ClientError Ogmios.ProtocolParameters) From 769f1eecf3a703099f5813633657fc9ba84e6800 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Thu, 5 Jan 2023 11:44:39 +0000 Subject: [PATCH 235/373] Rename endpoints --- src/Internal/Service/Blockfrost.purs | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index b57d529872..3874407c28 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -93,14 +93,14 @@ runBlockfrostServiceM backend = flip runReaderT serviceParams -------------------------------------------------------------------------------- data BlockfrostEndpoint - = GetCurrentEpoch - | GetProtocolParams + = LatestEpoch + | LatestProtocolParameters realizeEndpoint :: BlockfrostEndpoint -> Affjax.URL realizeEndpoint endpoint = case endpoint of - GetCurrentEpoch -> "/epochs/latest" - GetProtocolParams -> "/epochs/latest/parameters" + LatestEpoch -> "/epochs/latest" + LatestProtocolParameters -> "/epochs/latest/parameters" blockfrostGetRequest :: BlockfrostEndpoint @@ -282,7 +282,7 @@ instance DecodeAeson BlockfrostProtocolParameters where getCurrentEpoch :: BlockfrostServiceM (Either ClientError BigInt) getCurrentEpoch = runExceptT do - BlockfrostCurrentEpoch { epoch } <- ExceptT $ blockfrostGetRequest GetCurrentEpoch + BlockfrostCurrentEpoch { epoch } <- ExceptT $ blockfrostGetRequest LatestEpoch <#> handleBlockfrostResponse pure epoch @@ -290,5 +290,5 @@ getProtocolParameters :: BlockfrostServiceM (Either ClientError Ogmios.ProtocolParameters) getProtocolParameters = runExceptT do BlockfrostProtocolParameters params <- ExceptT $ - blockfrostGetRequest GetProtocolParams <#> handleBlockfrostResponse + blockfrostGetRequest LatestProtocolParameters <#> handleBlockfrostResponse pure params From 8f7d60e4097c5cef4101f63d581621ac3ce49130 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Thu, 5 Jan 2023 11:46:33 +0000 Subject: [PATCH 236/373] Rename endpoints --- src/Internal/Service/Blockfrost.purs | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index 1d0791139d..98fc7aa1be 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -88,14 +88,14 @@ runBlockfrostServiceM backend = flip runReaderT serviceParams -------------------------------------------------------------------------------- data BlockfrostEndpoint - = GetTransaction TransactionHash - | GetTransactionMetadata TransactionHash + = Transaction TransactionHash + | TransactionMetadata TransactionHash realizeEndpoint :: BlockfrostEndpoint -> Affjax.URL realizeEndpoint endpoint = case endpoint of - GetTransaction txHash -> "/txs/" <> byteArrayToHex (unwrap txHash) - GetTransactionMetadata txHash -> "/txs/" <> byteArrayToHex (unwrap txHash) + Transaction txHash -> "/txs/" <> byteArrayToHex (unwrap txHash) + TransactionMetadata txHash -> "/txs/" <> byteArrayToHex (unwrap txHash) <> "/metadata/cbor" dummyExport :: Unit -> Unit @@ -159,7 +159,7 @@ isTxConfirmed :: TransactionHash -> BlockfrostServiceM (Either ClientError Boolean) isTxConfirmed txHash = do - response <- blockfrostGetRequest $ GetTransaction txHash + response <- blockfrostGetRequest $ Transaction txHash pure case handleBlockfrostResponse response of Right (_ :: Aeson) -> Right true Left (ClientHttpResponseError (Affjax.StatusCode 404) _) -> Right false @@ -169,7 +169,7 @@ getTxMetadata :: TransactionHash -> BlockfrostServiceM (Either GetTxMetadataError GeneralTransactionMetadata) getTxMetadata txHash = do - response <- blockfrostGetRequest (GetTransactionMetadata txHash) + response <- blockfrostGetRequest (TransactionMetadata txHash) pure case unwrapBlockfrostMetadata <$> handleBlockfrostResponse response of Left (ClientHttpResponseError (Affjax.StatusCode 404) _) -> Left GetTxMetadataTxNotFoundError From 3fa69e70708f4011d3fc71b8c992cefd31dedb51 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Thu, 5 Jan 2023 16:44:05 +0100 Subject: [PATCH 237/373] Fix Ogmios systemStart timestamp string parsing --- src/Internal/Types/SystemStart.purs | 39 ++++++++++++++++++++--------- 1 file changed, 27 insertions(+), 12 deletions(-) diff --git a/src/Internal/Types/SystemStart.purs b/src/Internal/Types/SystemStart.purs index 87f27e1f70..7689c9b354 100644 --- a/src/Internal/Types/SystemStart.purs +++ b/src/Internal/Types/SystemStart.purs @@ -14,11 +14,13 @@ import Data.BigInt (fromNumber) as BigInt import Data.DateTime (DateTime) import Data.DateTime.Instant (fromDateTime, unInstant) import Data.Either (Either, hush) +import Data.Foldable (length) import Data.Formatter.DateTime (Formatter, format, parseFormatString, unformat) import Data.Generic.Rep (class Generic) import Data.Maybe (Maybe, fromJust) import Data.Newtype (class Newtype, unwrap, wrap) import Data.Show.Generic (genericShow) +import Data.String (length, take) as String import Partial.Unsafe (unsafePartial) newtype SystemStart = SystemStart DateTime @@ -37,24 +39,37 @@ sysStartUnixTime (SystemStart dateTime) = -- | Attempts to parse `SystemStart` from Ogmios timestamp string. sysStartFromOgmiosTimestamp :: String -> Either String SystemStart -sysStartFromOgmiosTimestamp timestamp = - wrap <$> -- FIXME: Unit test with Ogmios fixtures fails. - ( unformat ogmiosDateTimeFormatterMsec timestamp - <|> unformat ogmiosDateTimeFormatterSec timestamp - ) +sysStartFromOgmiosTimestamp timestamp = wrap <$> (unformatMsec <|> unformatSec) + where + unformatMsec :: Either String DateTime + unformatMsec = unformat + (mkDateTimeFormatterUnsafe ogmiosDateTimeFormatStringMsec) + (String.take (String.length ogmiosDateTimeFormatStringMsec) timestamp) + + unformatSec :: Either String DateTime + unformatSec = unformat + (mkDateTimeFormatterUnsafe ogmiosDateTimeFormatStringSec) + (String.take (String.length ogmiosDateTimeFormatStringSec) timestamp) sysStartFromOgmiosTimestampUnsafe :: String -> SystemStart sysStartFromOgmiosTimestampUnsafe timestamp = unsafePartial fromJust $ hush $ sysStartFromOgmiosTimestamp timestamp sysStartToOgmiosTimestamp :: SystemStart -> String -sysStartToOgmiosTimestamp = format ogmiosDateTimeFormatterMsec <<< unwrap +sysStartToOgmiosTimestamp = + format (mkDateTimeFormatterUnsafe ogmiosDateTimeFormatStringMsecUTC) + <<< unwrap + +mkDateTimeFormatterUnsafe :: String -> Formatter +mkDateTimeFormatterUnsafe = + unsafePartial fromJust <<< hush <<< parseFormatString + +ogmiosDateTimeFormatStringSec :: String +ogmiosDateTimeFormatStringSec = "YYYY-MM-DDTHH:mm:ss" -ogmiosDateTimeFormatterSec :: Formatter -ogmiosDateTimeFormatterSec = - unsafePartial fromJust $ hush $ parseFormatString "YYYY-MM-DDTHH:mm:ssZ" +ogmiosDateTimeFormatStringMsec :: String +ogmiosDateTimeFormatStringMsec = ogmiosDateTimeFormatStringSec <> ".SSS" -ogmiosDateTimeFormatterMsec :: Formatter -ogmiosDateTimeFormatterMsec = - unsafePartial fromJust $ hush $ parseFormatString "YYYY-MM-DDTHH:mm:ss.SSSZ" +ogmiosDateTimeFormatStringMsecUTC :: String +ogmiosDateTimeFormatStringMsecUTC = ogmiosDateTimeFormatStringMsec <> "Z" From 3349505c7469a85b9b9738ab322b65c969887bfb Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Thu, 5 Jan 2023 18:31:25 +0100 Subject: [PATCH 238/373] Use query handle for getSystemStart and getEraSummaries --- src/Contract/Time.purs | 17 +++++++---------- src/Internal/Contract/Monad.purs | 12 ++++++++++-- src/Internal/Types/SystemStart.purs | 1 - 3 files changed, 17 insertions(+), 13 deletions(-) diff --git a/src/Contract/Time.purs b/src/Contract/Time.purs index fae17b4bc2..2ad9ea7f06 100644 --- a/src/Contract/Time.purs +++ b/src/Contract/Time.purs @@ -19,13 +19,11 @@ import Contract.Chain , Tip(Tip, TipAtGenesis) , getTip ) as Chain -import Contract.Monad (Contract) +import Contract.Monad (Contract, liftedE) import Control.Monad.Reader.Class (asks) import Ctl.Internal.Cardano.Types.Transaction (Epoch(Epoch)) -import Ctl.Internal.Contract.Monad (wrapQueryM) import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.Helpers (liftM) -import Ctl.Internal.QueryM.EraSummaries (getEraSummaries) as EraSummaries import Ctl.Internal.QueryM.Ogmios (CurrentEpoch(CurrentEpoch)) import Ctl.Internal.QueryM.Ogmios (CurrentEpoch(CurrentEpoch)) as ExportOgmios import Ctl.Internal.Serialization.Address (BlockId(BlockId), Slot(Slot)) as SerializationAddress @@ -95,9 +93,7 @@ import Ctl.Internal.Types.Interval , upperBound ) as Interval import Ctl.Internal.Types.SystemStart (SystemStart) -import Ctl.Internal.Types.SystemStart - ( SystemStart(SystemStart) - ) as ExportSystemStart +import Ctl.Internal.Types.SystemStart (SystemStart(SystemStart)) as ExportSystemStart import Data.BigInt as BigInt import Data.UInt as UInt import Effect.Aff.Class (liftAff) @@ -113,11 +109,12 @@ getCurrentEpoch = do $ BigInt.toString (bigInt :: BigInt.BigInt) -- | Get `EraSummaries` as used for Slot arithemetic. --- | Details can be found https://ogmios.dev/api/ under "eraSummaries" query +-- | Details can be found https://ogmios.dev/api/ under "eraSummaries" query. getEraSummaries :: Contract EraSummaries -getEraSummaries = wrapQueryM EraSummaries.getEraSummaries +getEraSummaries = do + queryHandle <- getQueryHandle + liftedE $ liftAff $ queryHandle.getEraSummaries -- | Get the current system start time. getSystemStart :: Contract SystemStart -getSystemStart = - asks $ _.ledgerConstants >>> _.systemStart +getSystemStart = asks $ _.ledgerConstants >>> _.systemStart diff --git a/src/Internal/Contract/Monad.purs b/src/Internal/Contract/Monad.purs index ce0e98b372..1224c9993f 100644 --- a/src/Internal/Contract/Monad.purs +++ b/src/Internal/Contract/Monad.purs @@ -55,11 +55,13 @@ import Ctl.Internal.QueryM import Ctl.Internal.QueryM.Kupo (isTxConfirmedAff) import Ctl.Internal.QueryM.Ogmios (ProtocolParameters) as Ogmios import Ctl.Internal.Serialization.Address (NetworkId(TestnetId, MainnetId)) +import Ctl.Internal.Service.Blockfrost (getSystemStart) as Blockfrost +import Ctl.Internal.Service.Blockfrost (runBlockfrostServiceM) import Ctl.Internal.Types.SystemStart (SystemStart) import Ctl.Internal.Types.UsedTxOuts (UsedTxOuts, isTxOutRefUsed, newUsedTxOuts) import Ctl.Internal.Wallet (Wallet, actionBasedOnWallet) import Ctl.Internal.Wallet.Spec (WalletSpec, mkWalletBySpec) -import Data.Either (Either(Left, Right), isRight) +import Data.Either (Either(Left, Right), either, isRight) import Data.Log.Level (LogLevel) import Data.Log.Message (Message) import Data.Maybe (Maybe(Just), fromMaybe) @@ -236,7 +238,13 @@ getLedgerConstants logger = case _ of pparams <- getProtocolParametersAff ws logger systemStart <- getSystemStartAff ws logger pure { pparams, systemStart } - BlockfrostBackend _ _ -> undefined + BlockfrostBackend backend _ -> + runBlockfrostServiceM backend do + pparams <- undefined -- TODO: fetch pparams using Blockfrost + systemStart <- + Blockfrost.getSystemStart + >>= either (liftEffect <<< throw <<< show) pure + pure { pparams, systemStart } -- | Ensure that `NetworkId` from wallet is the same as specified in the -- | `ContractEnv`. diff --git a/src/Internal/Types/SystemStart.purs b/src/Internal/Types/SystemStart.purs index 7689c9b354..c1b8895c51 100644 --- a/src/Internal/Types/SystemStart.purs +++ b/src/Internal/Types/SystemStart.purs @@ -14,7 +14,6 @@ import Data.BigInt (fromNumber) as BigInt import Data.DateTime (DateTime) import Data.DateTime.Instant (fromDateTime, unInstant) import Data.Either (Either, hush) -import Data.Foldable (length) import Data.Formatter.DateTime (Formatter, format, parseFormatString, unformat) import Data.Generic.Rep (class Generic) import Data.Maybe (Maybe, fromJust) From a410ec5369157e3a569a7fd76069c6a2f486fac8 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Thu, 5 Jan 2023 22:03:11 +0400 Subject: [PATCH 239/373] Apply suggestions --- doc/plutip-testing.md | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/doc/plutip-testing.md b/doc/plutip-testing.md index d458810db5..18932db9bb 100644 --- a/doc/plutip-testing.md +++ b/doc/plutip-testing.md @@ -199,12 +199,12 @@ Note that CTL re-distributes tADA from payment key-only ("enterprise") addresses `Contract.Test.Utils` module provides a DSL for assertions that accumulate error messages, instead of exiting early after the first failure. -The interpreter is `withAssertions` function, that accepts two arrays for two kinds of assertions: +The interpreter is `withAssertions` function, that accepts two kinds of assertions: -- `ContractBasicAssertion` is simply executed at the end of `Contract` lifetime +- `ContractBasicAssertion` is simply executed at the end of the `Contract` lifetime and only needs the result of the `Сontract` - `ContractWrapAssertion` can inspect the state both before and after `Contract` execution, allowing to monitor for effects, e.g. monetary gains/losses at address -`withAssertions` supports both of them via a `ContractAssertions` typeclass: +`withAssertions` allows mixing both of them via a `ContractAssertions` typeclass: ```purescript withAssertions From 61ab0041cb7ee735d6e2288124022051532ce28f Mon Sep 17 00:00:00 2001 From: Gregory Gerasev Date: Fri, 6 Jan 2023 01:51:13 +0400 Subject: [PATCH 240/373] Apply suggestions from code review Co-authored-by: Dzmitry Shuysky --- src/Internal/Service/Blockfrost.purs | 7 +++---- 1 file changed, 3 insertions(+), 4 deletions(-) diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index 4c91b5fabc..ed0c6e27c6 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -152,7 +152,7 @@ handleBlockfrostResponse (Right { status: Affjax.StatusCode statusCode, body }) <<< (decodeAeson <=< parseJsonStringToAeson) handle404AsNothing - :: forall x. Either ClientError (Maybe x) -> Either ClientError (Maybe x) + :: forall (x :: Type). Either ClientError (Maybe x) -> Either ClientError (Maybe x) handle404AsNothing (Left (ClientHttpResponseError (Affjax.StatusCode 404) _)) = Right Nothing handle404AsNothing x = x @@ -227,14 +227,13 @@ instance DecodeAeson BlockfrostScriptLanguage where Left $ TypeMismatch $ "language: expected 'native' or 'plutusV{1|2}', got: " <> invalid --- Do not parse fields other than `type`, cuz we do not need them yet +-- Do not parse fields other than `type` because we do not need them yet data BlockfrostScriptInfo = BlockfrostScriptInfo { type :: BlockfrostScriptLanguage } instance DecodeAeson BlockfrostScriptInfo where decodeAeson aeson = do - mType <- aesonObject (flip getFieldOptional "type") aeson - type_ <- note (AtKey "type" MissingValue) mType + type_ <- aesonObject (flip getField "type") aeson pure $ BlockfrostScriptInfo { type: type_ } scriptInfoType :: BlockfrostScriptInfo -> BlockfrostScriptLanguage From 931b0ae52b95e24b92d5fc6551a553de23ddc983 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Thu, 5 Jan 2023 21:52:28 +0000 Subject: [PATCH 241/373] Add comment with concern --- src/Internal/Service/Blockfrost.purs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index 98fc7aa1be..a3f25c0651 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -89,6 +89,8 @@ runBlockfrostServiceM backend = flip runReaderT serviceParams data BlockfrostEndpoint = Transaction TransactionHash + -- TODO Check if /txs/{txhash}/metadata/cbor is paginated. + -- Documentation suggests it both is and isn't. | TransactionMetadata TransactionHash realizeEndpoint :: BlockfrostEndpoint -> Affjax.URL From 02864ee037a07743a2572cd4efcb45f40e218691 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Fri, 6 Jan 2023 15:34:21 +0400 Subject: [PATCH 242/373] Add branch name to shell prompt in nix shell --- flake.nix | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/flake.nix b/flake.nix index eb61f6009b..d61dd3ee6a 100644 --- a/flake.nix +++ b/flake.nix @@ -1,7 +1,7 @@ { description = "cardano-transaction-lib"; - nixConfig.bash-prompt = "\\[\\e[0m\\][\\[\\e[0;2m\\]nix-develop \\[\\e[0;1m\\]CTL \\[\\e[0;32m\\]\\w\\[\\e[0m\\]]\\[\\e[0m\\]$ \\[\\e[0m\\]"; + nixConfig.bash-prompt = "\\[\\e[0m\\][\\[\\e[0;2m\\]nix-develop \\[\\e[0;1m\\]CTL@\\[\\033[33m\\]$(git rev-parse --abbrev-ref HEAD) \\[\\e[0;32m\\]\\w\\[\\e[0m\\]]\\[\\e[0m\\]$ \\[\\e[0m\\]"; inputs = { nixpkgs.follows = "ogmios/nixpkgs"; From 1bb5022c11b9bc04242804bd51df281902caef02 Mon Sep 17 00:00:00 2001 From: Amir Rad Date: Fri, 6 Jan 2023 15:57:44 +0000 Subject: [PATCH 243/373] Wrap csl imports with csl-runtime-gc --- examples/MyTest.js | 24 ++++++++++++++++++ examples/MyTest.purs | 25 +++++++++++++++++++ package-lock.json | 5 ++++ package.json | 11 ++++---- src/Internal/ApplyArgs.js | 1 + src/Internal/BalanceTx/UtxoMinAda.js | 1 + src/Internal/Deserialization/FromBytes.js | 1 + src/Internal/Deserialization/Keys.js | 1 + src/Internal/Deserialization/Language.js | 1 + src/Internal/Deserialization/NativeScript.js | 1 + src/Internal/Deserialization/PlutusData.js | 1 + src/Internal/Deserialization/Transaction.js | 1 + src/Internal/Deserialization/UnspentOutput.js | 1 + src/Internal/Hashing.js | 1 + src/Internal/Serialization.js | 1 + src/Internal/Serialization/Address.js | 1 + src/Internal/Serialization/AuxiliaryData.js | 1 + src/Internal/Serialization/BigInt.js | 1 + src/Internal/Serialization/Hash.js | 1 + src/Internal/Serialization/MinFee.js | 1 + src/Internal/Serialization/NativeScript.js | 1 + src/Internal/Serialization/PlutusData.js | 1 + src/Internal/Serialization/PlutusScript.js | 1 + src/Internal/Serialization/WitnessSet.js | 1 + src/Internal/Types/BigNum.js | 1 + src/Internal/Types/Int.js | 1 + test/Wallet/Cip30/SignData.js | 1 + 27 files changed, 83 insertions(+), 5 deletions(-) create mode 100644 examples/MyTest.js create mode 100644 examples/MyTest.purs diff --git a/examples/MyTest.js b/examples/MyTest.js new file mode 100644 index 0000000000..40e0e4d5fa --- /dev/null +++ b/examples/MyTest.js @@ -0,0 +1,24 @@ +let lib; +if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { + lib = require("@emurgo/cardano-serialization-lib-browser"); +} else { + lib = require("@emurgo/cardano-serialization-lib-nodejs"); +} + +lib = require("csl-runtime-gc")(lib); + +window.cslLib = lib; + +const loopEffect = () => { + const arr = []; + console.log("looping"); + for (let i = 0; i < 20; i++) { + const x = new Uint8Array(Array(10000000).fill(0)); + const pd = lib.PlutusData.new_bytes(x); + arr.push(pd); + } + console.log(lib.__gcPointerStore.store.size); + return arr; +}; + +exports.loopEffect = loopEffect; diff --git a/examples/MyTest.purs b/examples/MyTest.purs new file mode 100644 index 0000000000..50c6aaab64 --- /dev/null +++ b/examples/MyTest.purs @@ -0,0 +1,25 @@ +module Ctl.Examples.MyTest (main) where + +import Contract.Monad (launchAff_) +import Contract.Prelude (Effect, liftEffect, log, wrap) +import Data.Array (take) +import Effect.Aff (delay) +import Prelude (Unit, bind, discard, pure, unit, ($), (+), (<>)) + +main :: Effect Unit +main = do + log "Hello, World!" + repeatedlyCreatePlutusData + pure unit + +repeatedlyCreatePlutusData :: Effect Unit +repeatedlyCreatePlutusData = launchAff_ $ aux [] 0 + where + aux _ 20 = pure unit + aux arr cnt = do + a <- liftEffect $ loopEffect + let newArr = take 10 $ a <> arr + delay $ wrap $ 100.0 + aux newArr (cnt + 1) + +foreign import loopEffect :: Effect (Array Type) diff --git a/package-lock.json b/package-lock.json index 124655e7ed..174fd6ed80 100644 --- a/package-lock.json +++ b/package-lock.json @@ -1289,6 +1289,11 @@ "randomfill": "^1.0.3" } }, + "csl-runtime-gc": { + "version": "1.0.2", + "resolved": "https://registry.npmjs.org/csl-runtime-gc/-/csl-runtime-gc-1.0.2.tgz", + "integrity": "sha512-YscBChFVI+6du9pnmYa2VYtX0EMNfrpoZU3AzXdpZCvwg4Fq4ljzqyQtLYrvsY+e5UDus3uJwy9Fa1P6s6QgEg==" + }, "css-select": { "version": "4.3.0", "resolved": "https://registry.npmjs.org/css-select/-/css-select-4.3.0.tgz", diff --git a/package.json b/package.json index f71612d5ab..ae52924bcd 100755 --- a/package.json +++ b/package.json @@ -27,25 +27,26 @@ "author": "", "license": "MIT", "dependencies": { - "apply-args-browser": "0.0.1", - "apply-args-nodejs": "0.0.1", "@emurgo/cardano-message-signing-browser": "1.0.1", "@emurgo/cardano-message-signing-nodejs": "1.0.1", "@emurgo/cardano-serialization-lib-browser": "11.2.1", "@emurgo/cardano-serialization-lib-nodejs": "11.2.1", - "base64-js": "^1.5.1", + "@mlabs-haskell/json-bigint": " 1.0.0", "@noble/secp256k1": "^1.7.0", + "apply-args-browser": "0.0.1", + "apply-args-nodejs": "0.0.1", + "base64-js": "^1.5.1", "big-integer": "1.6.51", "blakejs": "1.2.1", "bufferutil": "4.0.5", + "csl-runtime-gc": "^1.0.1", "jssha": "3.2.0", "node-polyfill-webpack-plugin": "1.1.4", "puppeteer-core": "^15.3.2", "reconnecting-websocket": "4.4.0", "uniqid": "5.4.0", "ws": "8.4.0", - "xhr2": "0.2.1", - "@mlabs-haskell/json-bigint": " 1.0.0" + "xhr2": "0.2.1" }, "devDependencies": { "buffer": "6.0.3", diff --git a/src/Internal/ApplyArgs.js b/src/Internal/ApplyArgs.js index 7e69e1e0d4..e373a7e36f 100644 --- a/src/Internal/ApplyArgs.js +++ b/src/Internal/ApplyArgs.js @@ -9,6 +9,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { lib = require("@emurgo/cardano-serialization-lib-nodejs"); apply_args = require("apply-args-nodejs"); } +lib = require("csl-runtime-gc")(lib); /** * @param {} left diff --git a/src/Internal/BalanceTx/UtxoMinAda.js b/src/Internal/BalanceTx/UtxoMinAda.js index 3b7e8982eb..97910ac48d 100644 --- a/src/Internal/BalanceTx/UtxoMinAda.js +++ b/src/Internal/BalanceTx/UtxoMinAda.js @@ -6,6 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } +lib = require("csl-runtime-gc")(lib); exports.minAdaForOutput = maybe => txOutput => dataCost => { try { diff --git a/src/Internal/Deserialization/FromBytes.js b/src/Internal/Deserialization/FromBytes.js index a7f1f0decb..ca3fce6d46 100644 --- a/src/Internal/Deserialization/FromBytes.js +++ b/src/Internal/Deserialization/FromBytes.js @@ -6,6 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } +lib = require("csl-runtime-gc")(lib); exports._fromBytes = helper => name => bytes => { try { diff --git a/src/Internal/Deserialization/Keys.js b/src/Internal/Deserialization/Keys.js index 57dbb6d55b..4ba24b9eb0 100644 --- a/src/Internal/Deserialization/Keys.js +++ b/src/Internal/Deserialization/Keys.js @@ -6,6 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } +lib = require("csl-runtime-gc")(lib); exports._publicKeyFromBech32 = maybe => bech32 => { try { diff --git a/src/Internal/Deserialization/Language.js b/src/Internal/Deserialization/Language.js index 6bb4bb73f0..1d5f172482 100644 --- a/src/Internal/Deserialization/Language.js +++ b/src/Internal/Deserialization/Language.js @@ -6,6 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } +lib = require("csl-runtime-gc")(lib); exports._convertLanguage = langCtors => cslLang => { if (cslLang.kind() == lib.LanguageKind.PlutusV1) { diff --git a/src/Internal/Deserialization/NativeScript.js b/src/Internal/Deserialization/NativeScript.js index c007a97783..7453c21a42 100644 --- a/src/Internal/Deserialization/NativeScript.js +++ b/src/Internal/Deserialization/NativeScript.js @@ -6,6 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } +lib = require("csl-runtime-gc")(lib); exports._convertNativeScript = handler => ns => { switch (ns.kind()) { diff --git a/src/Internal/Deserialization/PlutusData.js b/src/Internal/Deserialization/PlutusData.js index 0539a1cc95..eba58c1574 100644 --- a/src/Internal/Deserialization/PlutusData.js +++ b/src/Internal/Deserialization/PlutusData.js @@ -6,6 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } +lib = require("csl-runtime-gc")(lib); exports._convertPlutusData = handle => pd => { switch (pd.kind()) { diff --git a/src/Internal/Deserialization/Transaction.js b/src/Internal/Deserialization/Transaction.js index 2da96a9bec..bc1929edf3 100644 --- a/src/Internal/Deserialization/Transaction.js +++ b/src/Internal/Deserialization/Transaction.js @@ -6,6 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } +lib = require("csl-runtime-gc")(lib); const call = property => object => object[property](); const callMaybe = property => maybe => object => { diff --git a/src/Internal/Deserialization/UnspentOutput.js b/src/Internal/Deserialization/UnspentOutput.js index a6a9eee072..2a2d1c038e 100644 --- a/src/Internal/Deserialization/UnspentOutput.js +++ b/src/Internal/Deserialization/UnspentOutput.js @@ -6,6 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } +lib = require("csl-runtime-gc")(lib); const call = property => object => object[property](); const callMaybe = property => maybe => object => { diff --git a/src/Internal/Hashing.js b/src/Internal/Hashing.js index ce9c3f5c9d..a2b1654d6b 100644 --- a/src/Internal/Hashing.js +++ b/src/Internal/Hashing.js @@ -10,6 +10,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } +lib = require("csl-runtime-gc")(lib); exports.blake2b256Hash = bytesToHash => { return Blake2.blake2b(bytesToHash, null, 32); diff --git a/src/Internal/Serialization.js b/src/Internal/Serialization.js index 8cc3dd3752..2fcb6a912f 100644 --- a/src/Internal/Serialization.js +++ b/src/Internal/Serialization.js @@ -6,6 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } +lib = require("csl-runtime-gc")(lib); const setter = prop => obj => value => () => obj["set_" + prop](value); diff --git a/src/Internal/Serialization/Address.js b/src/Internal/Serialization/Address.js index 8a024c2654..7786470ecc 100644 --- a/src/Internal/Serialization/Address.js +++ b/src/Internal/Serialization/Address.js @@ -6,6 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } +lib = require("csl-runtime-gc")(lib); const callClassStaticMaybe = (classname, functionname) => maybe => input => { let ret = null; diff --git a/src/Internal/Serialization/AuxiliaryData.js b/src/Internal/Serialization/AuxiliaryData.js index 24f8da79fe..5ebb56122d 100644 --- a/src/Internal/Serialization/AuxiliaryData.js +++ b/src/Internal/Serialization/AuxiliaryData.js @@ -6,6 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } +lib = require("csl-runtime-gc")(lib); const setter = prop => obj => value => () => obj["set_" + prop](value); diff --git a/src/Internal/Serialization/BigInt.js b/src/Internal/Serialization/BigInt.js index 651b3aa6c2..a34da4510b 100644 --- a/src/Internal/Serialization/BigInt.js +++ b/src/Internal/Serialization/BigInt.js @@ -6,6 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } +lib = require("csl-runtime-gc")(lib); exports._BigInt_from_str = helper => str => { try { diff --git a/src/Internal/Serialization/Hash.js b/src/Internal/Serialization/Hash.js index 709461736c..11c51cdf53 100644 --- a/src/Internal/Serialization/Hash.js +++ b/src/Internal/Serialization/Hash.js @@ -6,6 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } +lib = require("csl-runtime-gc")(lib); exports.hashToBytes = hash => { return hash.to_bytes(); diff --git a/src/Internal/Serialization/MinFee.js b/src/Internal/Serialization/MinFee.js index 5e67f1830f..f6a9ca39df 100644 --- a/src/Internal/Serialization/MinFee.js +++ b/src/Internal/Serialization/MinFee.js @@ -6,6 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } +lib = require("csl-runtime-gc")(lib); exports._minFee = maybe => tx => txFeeFixed => txFeePerByte => { try { diff --git a/src/Internal/Serialization/NativeScript.js b/src/Internal/Serialization/NativeScript.js index 6521e7e5b2..2db3feaa49 100644 --- a/src/Internal/Serialization/NativeScript.js +++ b/src/Internal/Serialization/NativeScript.js @@ -6,6 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } +lib = require("csl-runtime-gc")(lib); const mkScript = prop => arg => lib.NativeScript[prop](arg); diff --git a/src/Internal/Serialization/PlutusData.js b/src/Internal/Serialization/PlutusData.js index cdcbcf1749..3e7f631a46 100644 --- a/src/Internal/Serialization/PlutusData.js +++ b/src/Internal/Serialization/PlutusData.js @@ -6,6 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } +lib = require("csl-runtime-gc")(lib); exports._mkPlutusData_bytes = bytes => lib.PlutusData.new_bytes(bytes); exports._mkPlutusData_list = list => lib.PlutusData.new_list(list); diff --git a/src/Internal/Serialization/PlutusScript.js b/src/Internal/Serialization/PlutusScript.js index 116066706a..ef38c2065b 100644 --- a/src/Internal/Serialization/PlutusScript.js +++ b/src/Internal/Serialization/PlutusScript.js @@ -6,6 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } +lib = require("csl-runtime-gc")(lib); exports.newPlutusV1Script = bytes => lib.PlutusScript.new(bytes); diff --git a/src/Internal/Serialization/WitnessSet.js b/src/Internal/Serialization/WitnessSet.js index 0f134b842f..25d2637480 100644 --- a/src/Internal/Serialization/WitnessSet.js +++ b/src/Internal/Serialization/WitnessSet.js @@ -6,6 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } +lib = require("csl-runtime-gc")(lib); exports.newTransactionWitnessSet = () => lib.TransactionWitnessSet.new(); diff --git a/src/Internal/Types/BigNum.js b/src/Internal/Types/BigNum.js index 216d05b53d..ca45b35f86 100644 --- a/src/Internal/Types/BigNum.js +++ b/src/Internal/Types/BigNum.js @@ -6,6 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } +lib = require("csl-runtime-gc")(lib); exports.bnCompare = lhs => rhs => lhs.compare(rhs); diff --git a/src/Internal/Types/Int.js b/src/Internal/Types/Int.js index 6dc8117b67..ce07b6e40c 100644 --- a/src/Internal/Types/Int.js +++ b/src/Internal/Types/Int.js @@ -6,6 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } +lib = require("csl-runtime-gc")(lib); exports.newPositive = lib.Int.new; exports.newNegative = lib.Int.new_negative; diff --git a/test/Wallet/Cip30/SignData.js b/test/Wallet/Cip30/SignData.js index a63c8f9201..695c25d909 100644 --- a/test/Wallet/Cip30/SignData.js +++ b/test/Wallet/Cip30/SignData.js @@ -8,6 +8,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { lib = require("@emurgo/cardano-message-signing-nodejs"); csl = require("@emurgo/cardano-serialization-lib-nodejs"); } +lib = require("csl-runtime-gc")(lib); function opt_chain(maybe, obj) { const isNothing = x => x === null || x === undefined; From da36e04df57168c11f06f66db2043c44b32b9a68 Mon Sep 17 00:00:00 2001 From: Amir Rad Date: Fri, 6 Jan 2023 17:12:52 +0000 Subject: [PATCH 244/373] Add dep to ctl-scaffold & remove test files --- examples/MyTest.js | 24 ----------------------- examples/MyTest.purs | 25 ------------------------ package-lock.json | 6 +++--- templates/ctl-scaffold/package-lock.json | 5 +++++ templates/ctl-scaffold/package.json | 1 + 5 files changed, 9 insertions(+), 52 deletions(-) delete mode 100644 examples/MyTest.js delete mode 100644 examples/MyTest.purs diff --git a/examples/MyTest.js b/examples/MyTest.js deleted file mode 100644 index 40e0e4d5fa..0000000000 --- a/examples/MyTest.js +++ /dev/null @@ -1,24 +0,0 @@ -let lib; -if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { - lib = require("@emurgo/cardano-serialization-lib-browser"); -} else { - lib = require("@emurgo/cardano-serialization-lib-nodejs"); -} - -lib = require("csl-runtime-gc")(lib); - -window.cslLib = lib; - -const loopEffect = () => { - const arr = []; - console.log("looping"); - for (let i = 0; i < 20; i++) { - const x = new Uint8Array(Array(10000000).fill(0)); - const pd = lib.PlutusData.new_bytes(x); - arr.push(pd); - } - console.log(lib.__gcPointerStore.store.size); - return arr; -}; - -exports.loopEffect = loopEffect; diff --git a/examples/MyTest.purs b/examples/MyTest.purs deleted file mode 100644 index 50c6aaab64..0000000000 --- a/examples/MyTest.purs +++ /dev/null @@ -1,25 +0,0 @@ -module Ctl.Examples.MyTest (main) where - -import Contract.Monad (launchAff_) -import Contract.Prelude (Effect, liftEffect, log, wrap) -import Data.Array (take) -import Effect.Aff (delay) -import Prelude (Unit, bind, discard, pure, unit, ($), (+), (<>)) - -main :: Effect Unit -main = do - log "Hello, World!" - repeatedlyCreatePlutusData - pure unit - -repeatedlyCreatePlutusData :: Effect Unit -repeatedlyCreatePlutusData = launchAff_ $ aux [] 0 - where - aux _ 20 = pure unit - aux arr cnt = do - a <- liftEffect $ loopEffect - let newArr = take 10 $ a <> arr - delay $ wrap $ 100.0 - aux newArr (cnt + 1) - -foreign import loopEffect :: Effect (Array Type) diff --git a/package-lock.json b/package-lock.json index 174fd6ed80..0680c44df5 100644 --- a/package-lock.json +++ b/package-lock.json @@ -1290,9 +1290,9 @@ } }, "csl-runtime-gc": { - "version": "1.0.2", - "resolved": "https://registry.npmjs.org/csl-runtime-gc/-/csl-runtime-gc-1.0.2.tgz", - "integrity": "sha512-YscBChFVI+6du9pnmYa2VYtX0EMNfrpoZU3AzXdpZCvwg4Fq4ljzqyQtLYrvsY+e5UDus3uJwy9Fa1P6s6QgEg==" + "version": "1.0.4", + "resolved": "https://registry.npmjs.org/csl-runtime-gc/-/csl-runtime-gc-1.0.4.tgz", + "integrity": "sha512-GhYvkhTaVCtRoaX7yE2QnzEkEjDqY47LmcF+x7uph+z2XyIh/cErb8bxIwpStp2ZrNntwqtWTYBVAXCpF1++Lw==" }, "css-select": { "version": "4.3.0", diff --git a/templates/ctl-scaffold/package-lock.json b/templates/ctl-scaffold/package-lock.json index 53725ab3d3..aa1cd142ef 100644 --- a/templates/ctl-scaffold/package-lock.json +++ b/templates/ctl-scaffold/package-lock.json @@ -1195,6 +1195,11 @@ "randomfill": "^1.0.3" } }, + "csl-runtime-gc": { + "version": "1.0.4", + "resolved": "https://registry.npmjs.org/csl-runtime-gc/-/csl-runtime-gc-1.0.4.tgz", + "integrity": "sha512-GhYvkhTaVCtRoaX7yE2QnzEkEjDqY47LmcF+x7uph+z2XyIh/cErb8bxIwpStp2ZrNntwqtWTYBVAXCpF1++Lw==" + }, "css-select": { "version": "4.3.0", "resolved": "https://registry.npmjs.org/css-select/-/css-select-4.3.0.tgz", diff --git a/templates/ctl-scaffold/package.json b/templates/ctl-scaffold/package.json index ef6e42b2ad..65046e8f23 100644 --- a/templates/ctl-scaffold/package.json +++ b/templates/ctl-scaffold/package.json @@ -26,6 +26,7 @@ "@emurgo/cardano-message-signing-nodejs": "1.0.1", "@emurgo/cardano-serialization-lib-browser": "11.2.1", "@emurgo/cardano-serialization-lib-nodejs": "11.2.1", + "csl-runtime-gc": "1.0.4", "base64-js": "^1.5.1", "@noble/secp256k1": "^1.7.0", "big-integer": "1.6.51", From 3e6dfdc1658a0e4f9bc676e9793b21917e5e3a08 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Sat, 7 Jan 2023 14:59:23 +0100 Subject: [PATCH 245/373] Request native scripts by hash, decode response --- src/Internal/Service/Blockfrost.purs | 75 +++++++++++++++++++++++++++- 1 file changed, 73 insertions(+), 2 deletions(-) diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index ed0c6e27c6..4364361d95 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -10,8 +10,10 @@ import Prelude import Aeson ( class DecodeAeson + , Aeson , JsonDecodeError(TypeMismatch, AtKey, MissingValue) , decodeAeson + , getField , getFieldOptional , isNull , parseJsonStringToAeson @@ -25,13 +27,27 @@ import Control.Monad.Except.Trans (ExceptT(ExceptT), runExceptT) import Control.Monad.Maybe.Trans (MaybeT(MaybeT), runMaybeT) import Control.Monad.Reader.Class (ask) import Control.Monad.Reader.Trans (ReaderT, runReaderT) +import Ctl.Internal.Cardano.Types.NativeScript + ( NativeScript + ( ScriptAll + , ScriptAny + , ScriptNOfK + , ScriptPubkey + , TimelockExpiry + , TimelockStart + ) + ) import Ctl.Internal.Cardano.Types.ScriptRef ( ScriptRef(NativeScriptRef, PlutusScriptRef) ) import Ctl.Internal.Contract.QueryBackend (BlockfrostBackend) import Ctl.Internal.Deserialization.NativeScript (decodeNativeScript) import Ctl.Internal.Deserialization.PlutusData (deserializeData) -import Ctl.Internal.Serialization.Hash (ScriptHash, scriptHashToBytes) +import Ctl.Internal.Serialization.Hash + ( ScriptHash + , ed25519KeyHashFromBytes + , scriptHashToBytes + ) import Ctl.Internal.ServerConfig (ServerConfig, mkHttpUrl) import Ctl.Internal.Service.Error ( ClientError(ClientHttpError, ClientHttpResponseError, ClientDecodeJsonError) @@ -53,6 +69,7 @@ import Data.Newtype (class Newtype, unwrap, wrap) import Data.Show.Generic (genericShow) import Effect.Aff (Aff) import Effect.Aff.Class (liftAff) +import Foreign.Object (Object) -------------------------------------------------------------------------------- -- BlockfrostServiceM @@ -86,6 +103,8 @@ data BlockfrostEndpoint | GetScriptInfo ScriptHash -- /scripts/{script_hash}/cbor | GetScriptCbor ScriptHash + -- /scripts/{script_hash}/json + | GetNativeScriptByHash ScriptHash realizeEndpoint :: BlockfrostEndpoint -> Affjax.URL realizeEndpoint endpoint = @@ -96,6 +115,8 @@ realizeEndpoint endpoint = "/scripts/" <> rawBytesToHex (scriptHashToBytes scriptHash) GetScriptCbor scriptHash -> "/scripts/" <> rawBytesToHex (scriptHashToBytes scriptHash) <> "/cbor" + GetNativeScriptByHash scriptHash -> + "/scripts/" <> rawBytesToHex (scriptHashToBytes scriptHash) <> "/json" blockfrostGetRequest :: BlockfrostEndpoint @@ -152,7 +173,9 @@ handleBlockfrostResponse (Right { status: Affjax.StatusCode statusCode, body }) <<< (decodeAeson <=< parseJsonStringToAeson) handle404AsNothing - :: forall (x :: Type). Either ClientError (Maybe x) -> Either ClientError (Maybe x) + :: forall (x :: Type) + . Either ClientError (Maybe x) + -> Either ClientError (Maybe x) handle404AsNothing (Left (ClientHttpResponseError (Affjax.StatusCode 404) _)) = Right Nothing handle404AsNothing x = x @@ -189,6 +212,54 @@ getScriptByHash scriptHash = runExceptT $ runMaybeT do PlutusV1Script -> pure $ PlutusScriptRef $ plutusV1Script x PlutusV2Script -> pure $ PlutusScriptRef $ plutusV2Script x +getNativeScriptByHash + :: ScriptHash -> BlockfrostServiceM (Either ClientError (Maybe NativeScript)) +getNativeScriptByHash scriptHash = runExceptT do + (nativeScript :: Maybe BlockfrostNativeScript) <- ExceptT do + response <- blockfrostGetRequest (GetNativeScriptByHash scriptHash) + pure $ handle404AsNothing $ handleBlockfrostResponse response + pure $ unwrap <$> nativeScript + +-------------------------------------------------------------------------------- +-- BlockfrostNativeScript +-------------------------------------------------------------------------------- + +newtype BlockfrostNativeScript = BlockfrostNativeScript NativeScript + +derive instance Generic BlockfrostNativeScript _ +derive instance Newtype BlockfrostNativeScript _ + +instance Show BlockfrostNativeScript where + show = genericShow + +instance DecodeAeson BlockfrostNativeScript where + decodeAeson = + aesonObject (flip getField "json") >=> (map wrap <<< decodeNativeScript) + where + unwrap' :: BlockfrostNativeScript -> NativeScript + unwrap' = unwrap + + decodeNativeScript :: Object Aeson -> Either JsonDecodeError NativeScript + decodeNativeScript obj = getField obj "type" >>= case _ of + "sig" -> + ScriptPubkey <$> + ( getField obj "keyHash" >>= + (note (TypeMismatch "Ed25519KeyHash") <<< ed25519KeyHashFromBytes) + ) + "before" -> + TimelockExpiry <$> getField obj "slot" + "after" -> + TimelockStart <$> getField obj "slot" + "all" -> + ScriptAll <$> map unwrap' <$> getField obj "scripts" + "any" -> + ScriptAny <$> map unwrap' <$> getField obj "scripts" + "atLeast" -> do + required <- getField obj "required" + ScriptNOfK required <$> map unwrap' <$> getField obj "scripts" + _ -> + Left $ TypeMismatch "Native script constructor" + -------------------------------------------------------------------------------- -- `getDatumByHash` response parsing -------------------------------------------------------------------------------- From 5ce7f91f108e9e9d3edc02b00db2889d1a3b49ab Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Sat, 7 Jan 2023 16:21:21 +0100 Subject: [PATCH 246/373] Decode Plutus and native scripts based on script info --- src/Internal/QueryM.purs | 2 +- src/Internal/QueryM/Kupo.purs | 3 - src/Internal/Service/Blockfrost.purs | 181 ++++++++++++++++----------- 3 files changed, 107 insertions(+), 79 deletions(-) diff --git a/src/Internal/QueryM.purs b/src/Internal/QueryM.purs index f6fe322753..b2b26493cd 100644 --- a/src/Internal/QueryM.purs +++ b/src/Internal/QueryM.purs @@ -46,7 +46,7 @@ import Aeson , parseJsonStringToAeson , stringifyAeson ) -import Affjax (Error, Response, defaultRequest, printError, request) as Affjax +import Affjax (Error, Response, defaultRequest, request) as Affjax import Affjax.RequestBody as Affjax.RequestBody import Affjax.RequestHeader as Affjax.RequestHeader import Affjax.ResponseFormat as Affjax.ResponseFormat diff --git a/src/Internal/QueryM/Kupo.purs b/src/Internal/QueryM/Kupo.purs index 705111ec51..6e118fcd67 100644 --- a/src/Internal/QueryM/Kupo.purs +++ b/src/Internal/QueryM/Kupo.purs @@ -14,8 +14,6 @@ import Aeson ( class DecodeAeson , Aeson , JsonDecodeError(TypeMismatch) - , caseAesonArray - , caseAesonObject , decodeAeson , getField , getFieldOptional @@ -29,7 +27,6 @@ import Control.Bind (bindFlipped) import Control.Monad.Except.Trans (ExceptT(ExceptT), except, runExceptT) import Control.Monad.Reader.Class (asks) import Control.Parallel (parTraverse) -import Ctl.Internal.Cardano.Types.NativeScript (NativeScript) import Ctl.Internal.Cardano.Types.ScriptRef ( ScriptRef(NativeScriptRef, PlutusScriptRef) ) diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index 4364361d95..89e16689f0 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -11,7 +11,7 @@ import Prelude import Aeson ( class DecodeAeson , Aeson - , JsonDecodeError(TypeMismatch, AtKey, MissingValue) + , JsonDecodeError(TypeMismatch) , decodeAeson , getField , getFieldOptional @@ -41,7 +41,6 @@ import Ctl.Internal.Cardano.Types.ScriptRef ( ScriptRef(NativeScriptRef, PlutusScriptRef) ) import Ctl.Internal.Contract.QueryBackend (BlockfrostBackend) -import Ctl.Internal.Deserialization.NativeScript (decodeNativeScript) import Ctl.Internal.Deserialization.PlutusData (deserializeData) import Ctl.Internal.Serialization.Hash ( ScriptHash @@ -55,7 +54,6 @@ import Ctl.Internal.Service.Error ) import Ctl.Internal.Service.Helpers (aesonObject, aesonString) import Ctl.Internal.Types.ByteArray (ByteArray, byteArrayToHex) -import Ctl.Internal.Types.CborBytes (CborBytes) import Ctl.Internal.Types.Datum (DataHash(DataHash), Datum) import Ctl.Internal.Types.RawBytes (rawBytesToHex) import Ctl.Internal.Types.Scripts (plutusV1Script, plutusV2Script) @@ -63,7 +61,7 @@ import Data.Bifunctor (lmap) import Data.Either (Either(Left, Right), note) import Data.Generic.Rep (class Generic) import Data.HTTP.Method (Method(GET, POST)) -import Data.Maybe (Maybe(Nothing, Just), maybe) +import Data.Maybe (Maybe(Nothing), maybe) import Data.MediaType (MediaType) import Data.Newtype (class Newtype, unwrap, wrap) import Data.Show.Generic (genericShow) @@ -102,7 +100,7 @@ data BlockfrostEndpoint -- /scripts/{script_hash} | GetScriptInfo ScriptHash -- /scripts/{script_hash}/cbor - | GetScriptCbor ScriptHash + | GetPlutusScriptCborByHash ScriptHash -- /scripts/{script_hash}/json | GetNativeScriptByHash ScriptHash @@ -113,7 +111,7 @@ realizeEndpoint endpoint = "/scripts/datum/" <> byteArrayToHex hashBytes <> "/cbor" GetScriptInfo scriptHash -> "/scripts/" <> rawBytesToHex (scriptHashToBytes scriptHash) - GetScriptCbor scriptHash -> + GetPlutusScriptCborByHash scriptHash -> "/scripts/" <> rawBytesToHex (scriptHashToBytes scriptHash) <> "/cbor" GetNativeScriptByHash scriptHash -> "/scripts/" <> rawBytesToHex (scriptHashToBytes scriptHash) <> "/json" @@ -180,6 +178,10 @@ handle404AsNothing (Left (ClientHttpResponseError (Affjax.StatusCode 404) _)) = Right Nothing handle404AsNothing x = x +-------------------------------------------------------------------------------- +-- Get datum by hash +-------------------------------------------------------------------------------- + getDatumByHash :: DataHash -> BlockfrostServiceM (Either ClientError (Maybe Datum)) getDatumByHash dataHash = do @@ -187,38 +189,89 @@ getDatumByHash dataHash = do pure $ handle404AsNothing $ unwrapBlockfrostDatum <$> handleBlockfrostResponse response -getScriptInfo - :: ScriptHash - -> BlockfrostServiceM (Either ClientError (Maybe BlockfrostScriptInfo)) -getScriptInfo scriptHash = do - response <- blockfrostGetRequest (GetScriptInfo scriptHash) - pure $ handle404AsNothing $ handleBlockfrostResponse response +-------------------------------------------------------------------------------- +-- Get script by hash +-------------------------------------------------------------------------------- getScriptByHash - :: ScriptHash -> BlockfrostServiceM (Either ClientError (Maybe ScriptRef)) + :: ScriptHash + -> BlockfrostServiceM (Either ClientError (Maybe ScriptRef)) getScriptByHash scriptHash = runExceptT $ runMaybeT do - info <- MaybeT $ ExceptT $ getScriptInfo scriptHash - cbor <- MaybeT $ ExceptT $ do - response <- blockfrostGetRequest (GetScriptCbor scriptHash) - pure $ handle404AsNothing $ unwrapBlockfrostCbor <$> - handleBlockfrostResponse response - let - script = lmap (ClientDecodeJsonError "Error decoding script") $ - wrapScriptType (scriptInfoType info) cbor - MaybeT $ ExceptT $ pure $ Just <$> script + scriptInfo <- MaybeT $ ExceptT getScriptInfo + case scriptLanguage scriptInfo of + NativeScript -> + NativeScriptRef <$> + (MaybeT $ ExceptT getNativeScriptByHash) + PlutusV1Script -> + PlutusScriptRef <$> plutusV1Script <$> + (MaybeT $ ExceptT getPlutusScriptCborByHash) + PlutusV2Script -> + PlutusScriptRef <$> plutusV2Script <$> + (MaybeT $ ExceptT getPlutusScriptCborByHash) where - wrapScriptType scriptType x = case scriptType of - NativeScript -> NativeScriptRef <$> decodeNativeScript x - PlutusV1Script -> pure $ PlutusScriptRef $ plutusV1Script x - PlutusV2Script -> pure $ PlutusScriptRef $ plutusV2Script x - -getNativeScriptByHash - :: ScriptHash -> BlockfrostServiceM (Either ClientError (Maybe NativeScript)) -getNativeScriptByHash scriptHash = runExceptT do - (nativeScript :: Maybe BlockfrostNativeScript) <- ExceptT do - response <- blockfrostGetRequest (GetNativeScriptByHash scriptHash) + getScriptInfo + :: BlockfrostServiceM (Either ClientError (Maybe BlockfrostScriptInfo)) + getScriptInfo = do + response <- blockfrostGetRequest (GetScriptInfo scriptHash) pure $ handle404AsNothing $ handleBlockfrostResponse response - pure $ unwrap <$> nativeScript + + getNativeScriptByHash + :: BlockfrostServiceM (Either ClientError (Maybe NativeScript)) + getNativeScriptByHash = runExceptT do + (nativeScript :: Maybe BlockfrostNativeScript) <- ExceptT do + response <- blockfrostGetRequest (GetNativeScriptByHash scriptHash) + pure $ handle404AsNothing $ handleBlockfrostResponse response + pure $ unwrap <$> nativeScript + + getPlutusScriptCborByHash + :: BlockfrostServiceM (Either ClientError (Maybe ByteArray)) + getPlutusScriptCborByHash = runExceptT do + (plutusScriptCbor :: Maybe BlockfrostCbor) <- ExceptT do + response <- blockfrostGetRequest (GetPlutusScriptCborByHash scriptHash) + pure $ handle404AsNothing $ handleBlockfrostResponse response + pure $ join $ unwrap <$> plutusScriptCbor + +-------------------------------------------------------------------------------- +-- BlockfrostScriptLanguage +-------------------------------------------------------------------------------- + +data BlockfrostScriptLanguage = NativeScript | PlutusV1Script | PlutusV2Script + +derive instance Generic BlockfrostScriptLanguage _ + +instance Show BlockfrostScriptLanguage where + show = genericShow + +instance DecodeAeson BlockfrostScriptLanguage where + decodeAeson = aesonString $ case _ of + "native" -> pure NativeScript + "plutusV1" -> pure PlutusV1Script + "plutusV2" -> pure PlutusV2Script + invalid -> + Left $ TypeMismatch $ + "language: expected 'native' or 'plutusV{1|2}', got: " <> invalid + +-------------------------------------------------------------------------------- +-- BlockfrostScriptInfo +-------------------------------------------------------------------------------- + +newtype BlockfrostScriptInfo = BlockfrostScriptInfo + { language :: BlockfrostScriptLanguage + } + +scriptLanguage :: BlockfrostScriptInfo -> BlockfrostScriptLanguage +scriptLanguage = _.language <<< unwrap + +derive instance Generic BlockfrostScriptInfo _ +derive instance Newtype BlockfrostScriptInfo _ + +instance Show BlockfrostScriptInfo where + show = genericShow + +instance DecodeAeson BlockfrostScriptInfo where + decodeAeson = aesonObject \obj -> + getField obj "type" + <#> \language -> BlockfrostScriptInfo { language } -------------------------------------------------------------------------------- -- BlockfrostNativeScript @@ -261,65 +314,43 @@ instance DecodeAeson BlockfrostNativeScript where Left $ TypeMismatch "Native script constructor" -------------------------------------------------------------------------------- --- `getDatumByHash` response parsing +-- BlockfrostCbor -------------------------------------------------------------------------------- -newtype BlockfrostDatum = BlockfrostDatum (Maybe Datum) +newtype BlockfrostCbor = BlockfrostCbor (Maybe ByteArray) -derive instance Newtype BlockfrostDatum _ +derive instance Generic BlockfrostCbor _ +derive instance Newtype BlockfrostCbor _ -unwrapBlockfrostDatum :: BlockfrostDatum -> Maybe Datum -unwrapBlockfrostDatum = unwrap +instance Show BlockfrostCbor where + show = genericShow -instance DecodeAeson BlockfrostDatum where +instance DecodeAeson BlockfrostCbor where decodeAeson aeson - | isNull aeson = pure $ BlockfrostDatum Nothing + | isNull aeson = pure $ BlockfrostCbor Nothing | otherwise = do cbor <- aesonObject (flip getFieldOptional "cbor") aeson - pure $ BlockfrostDatum $ deserializeData =<< cbor + pure $ BlockfrostCbor cbor -------------------------------------------------------------------------------- --- `getScriptByHash` response parsing +-- BlockfrostDatum -------------------------------------------------------------------------------- -data BlockfrostScriptLanguage = NativeScript | PlutusV1Script | PlutusV2Script +newtype BlockfrostDatum = BlockfrostDatum (Maybe Datum) -derive instance Generic BlockfrostScriptLanguage _ +derive instance Generic BlockfrostDatum _ +derive instance Newtype BlockfrostDatum _ -instance Show BlockfrostScriptLanguage where +instance Show BlockfrostDatum where show = genericShow -instance DecodeAeson BlockfrostScriptLanguage where - decodeAeson = aesonString $ case _ of - "native" -> pure NativeScript - "plutusV1" -> pure PlutusV1Script - "plutusV2" -> pure PlutusV2Script - invalid -> - Left $ TypeMismatch $ - "language: expected 'native' or 'plutusV{1|2}', got: " <> invalid - --- Do not parse fields other than `type` because we do not need them yet -data BlockfrostScriptInfo = BlockfrostScriptInfo - { type :: BlockfrostScriptLanguage } - -instance DecodeAeson BlockfrostScriptInfo where - decodeAeson aeson = do - type_ <- aesonObject (flip getField "type") aeson - pure $ BlockfrostScriptInfo { type: type_ } - -scriptInfoType :: BlockfrostScriptInfo -> BlockfrostScriptLanguage -scriptInfoType (BlockfrostScriptInfo info) = info.type - -newtype BlockfrostCbor = BlockfrostCbor (Maybe ByteArray) - -derive instance Newtype BlockfrostCbor _ - -unwrapBlockfrostCbor :: BlockfrostCbor -> Maybe ByteArray -unwrapBlockfrostCbor = unwrap +unwrapBlockfrostDatum :: BlockfrostDatum -> Maybe Datum +unwrapBlockfrostDatum = unwrap -instance DecodeAeson BlockfrostCbor where +instance DecodeAeson BlockfrostDatum where decodeAeson aeson - | isNull aeson = pure $ BlockfrostCbor Nothing + | isNull aeson = pure $ BlockfrostDatum Nothing | otherwise = do cbor <- aesonObject (flip getFieldOptional "cbor") aeson - pure $ BlockfrostCbor cbor + pure $ BlockfrostDatum $ deserializeData =<< cbor + From 47c570bc326531417a8f8e561235f396e6dc122e Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Sat, 7 Jan 2023 17:37:26 +0100 Subject: [PATCH 247/373] utxosAt and getUtxoByOref: Resolve reference script hashes --- src/Internal/Contract/QueryHandle.purs | 8 +-- src/Internal/Service/Blockfrost.purs | 70 ++++++++++++++++++-------- 2 files changed, 50 insertions(+), 28 deletions(-) diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs index 63ad07f84b..99d65c3c29 100644 --- a/src/Internal/Contract/QueryHandle.purs +++ b/src/Internal/Contract/QueryHandle.purs @@ -118,14 +118,10 @@ queryHandleForBlockfrostBackend queryHandleForBlockfrostBackend _ backend = { getDatumByHash: runBlockfrostServiceM' <<< Blockfrost.getDatumByHash , getScriptByHash: runBlockfrostServiceM' <<< Blockfrost.getScriptByHash - , getUtxoByOref: - -- FIXME: remove `undefined` - undefined <<< runBlockfrostServiceM' <<< Blockfrost.getUtxoByOref + , getUtxoByOref: runBlockfrostServiceM' <<< Blockfrost.getUtxoByOref , isTxConfirmed: runBlockfrostServiceM' <<< undefined , getTxMetadata: runBlockfrostServiceM' <<< undefined - , utxosAt: - -- FIXME: remove `undefined` - undefined <<< runBlockfrostServiceM' <<< Blockfrost.utxosAt + , utxosAt: runBlockfrostServiceM' <<< Blockfrost.utxosAt , getChainTip: runBlockfrostServiceM' undefined , getCurrentEpoch: runBlockfrostServiceM' undefined , submitTx: runBlockfrostServiceM' <<< undefined diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index 83ac192603..9342527cf9 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -1,13 +1,6 @@ module Ctl.Internal.Service.Blockfrost ( BlockfrostServiceM , BlockfrostServiceParams - -- TODO: should not be exported: - , BlockfrostEndpoint - , BlockfrostTransactionOutput(BlockfrostTransactionOutput) - , BlockfrostUnspentOutput - , BlockfrostUtxosAtAddress(BlockfrostUtxosAtAddress) - , blockfrostPostRequest - -- , getDatumByHash , getScriptByHash , getUtxoByOref @@ -30,15 +23,14 @@ import Aeson ) import Affjax (Error, Response, URL, defaultRequest, request) as Affjax import Affjax.RequestBody (RequestBody) as Affjax -import Affjax.RequestHeader - ( RequestHeader(ContentType, RequestHeader) - ) as Affjax +import Affjax.RequestHeader (RequestHeader(ContentType, RequestHeader)) as Affjax import Affjax.ResponseFormat (string) as Affjax.ResponseFormat import Affjax.StatusCode (StatusCode(StatusCode)) as Affjax -import Control.Monad.Except.Trans (ExceptT(ExceptT), runExceptT) +import Control.Monad.Except.Trans (ExceptT(ExceptT), except, runExceptT) import Control.Monad.Maybe.Trans (MaybeT(MaybeT), runMaybeT) import Control.Monad.Reader.Class (ask) import Control.Monad.Reader.Trans (ReaderT, runReaderT) +import Control.Parallel (parTraverse) import Ctl.Internal.Cardano.Types.NativeScript ( NativeScript ( ScriptAll @@ -52,6 +44,10 @@ import Ctl.Internal.Cardano.Types.NativeScript import Ctl.Internal.Cardano.Types.ScriptRef ( ScriptRef(NativeScriptRef, PlutusScriptRef) ) +import Ctl.Internal.Cardano.Types.Transaction + ( TransactionOutput(TransactionOutput) + , UtxoMap + ) import Ctl.Internal.Cardano.Types.Value (Value) import Ctl.Internal.Cardano.Types.Value ( lovelaceValueOf @@ -72,7 +68,12 @@ import Ctl.Internal.Serialization.Hash ) import Ctl.Internal.ServerConfig (ServerConfig, mkHttpUrl) import Ctl.Internal.Service.Error - ( ClientError(ClientHttpError, ClientHttpResponseError, ClientDecodeJsonError) + ( ClientError + ( ClientDecodeJsonError + , ClientHttpError + , ClientHttpResponseError + , ClientOtherError + ) , ServiceError(ServiceBlockfrostError) ) import Ctl.Internal.Service.Helpers @@ -99,6 +100,7 @@ import Data.Either (Either(Left, Right), note) import Data.Foldable (fold) import Data.Generic.Rep (class Generic) import Data.HTTP.Method (Method(GET, POST)) +import Data.Map (fromFoldable) as Map import Data.Maybe (Maybe(Just, Nothing), maybe) import Data.MediaType (MediaType) import Data.Newtype (class Newtype, unwrap, wrap) @@ -233,12 +235,10 @@ handle404AsNothing x = x -- Get utxos at address / by output reference -------------------------------------------------------------------------------- -utxosAt - :: Address - -- TODO: resolve `BlockfrostUtxosAtAddress` - -- -> BlockfrostServiceM (Either ClientError UtxoMap) - -> BlockfrostServiceM (Either ClientError BlockfrostUtxosAtAddress) -utxosAt address = utxosAtAddressOnPage 1 +utxosAt :: Address -> BlockfrostServiceM (Either ClientError UtxoMap) +utxosAt address = runExceptT $ + ExceptT (utxosAtAddressOnPage 1) + >>= (ExceptT <<< resolveBlockfrostUtxosAtAddress) where utxosAtAddressOnPage :: Int -> BlockfrostServiceM (Either ClientError BlockfrostUtxosAtAddress) @@ -253,14 +253,13 @@ utxosAt address = utxosAtAddressOnPage 1 getUtxoByOref :: TransactionInput - -- TODO: resolve `BlockfrostTransactionOutput` - -- -> BlockfrostServiceM (Either ClientError (Maybe TransactionOutput)) - -> BlockfrostServiceM (Either ClientError (Maybe BlockfrostTransactionOutput)) + -> BlockfrostServiceM (Either ClientError (Maybe TransactionOutput)) getUtxoByOref oref@(TransactionInput { transactionId: txHash }) = runExceptT do (blockfrostUtxoMap :: BlockfrostUtxosOfTransaction) <- ExceptT $ handleBlockfrostResponse <$> blockfrostGetRequest (GetUtxosOfTransaction txHash) - pure $ snd <$> Array.find (eq oref <<< fst) (unwrap blockfrostUtxoMap) + traverse (ExceptT <<< resolveBlockfrostTxOutput) + (snd <$> Array.find (eq oref <<< fst) (unwrap blockfrostUtxoMap)) -------------------------------------------------------------------------------- -- Get datum by hash @@ -344,6 +343,13 @@ instance DecodeAeson BlockfrostUtxosAtAddress where index <- getField obj "output_index" pure $ TransactionInput { transactionId, index } +resolveBlockfrostUtxosAtAddress + :: BlockfrostUtxosAtAddress + -> BlockfrostServiceM (Either ClientError UtxoMap) +resolveBlockfrostUtxosAtAddress (BlockfrostUtxosAtAddress utxos) = + runExceptT $ Map.fromFoldable <$> + parTraverse (traverse (ExceptT <<< resolveBlockfrostTxOutput)) utxos + newtype BlockfrostUtxosOfTransaction = BlockfrostUtxosOfTransaction (Array BlockfrostUnspentOutput) @@ -430,6 +436,26 @@ instance DecodeAeson BlockfrostTransactionOutput where maybe NoOutputDatum OutputDatumHash <$> getFieldOptional' obj "data_hash" +resolveBlockfrostTxOutput + :: BlockfrostTransactionOutput + -> BlockfrostServiceM (Either ClientError TransactionOutput) +resolveBlockfrostTxOutput + (BlockfrostTransactionOutput blockfrostTxOutput@{ address, amount, datum }) = + map mkTxOutput <$> resolveScriptRef + where + mkTxOutput :: Maybe ScriptRef -> TransactionOutput + mkTxOutput scriptRef = + TransactionOutput { address, amount, datum, scriptRef } + + resolveScriptRef :: BlockfrostServiceM (Either ClientError (Maybe ScriptRef)) + resolveScriptRef = + case blockfrostTxOutput.scriptHash of + Nothing -> pure $ Right Nothing + Just scriptHash -> runExceptT do + scriptRef <- ExceptT $ getScriptByHash scriptHash + except $ Just <$> flip note scriptRef + (ClientOtherError "Blockfrost: Failed to resolve reference script") + -------------------------------------------------------------------------------- -- BlockfrostScriptLanguage -------------------------------------------------------------------------------- From 82efe93f63e6c4494c3b4342b14da2dd2e0a67ef Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Mon, 9 Jan 2023 12:10:58 +0000 Subject: [PATCH 248/373] Remove comment --- src/Internal/Service/Blockfrost.purs | 2 -- 1 file changed, 2 deletions(-) diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index a3f25c0651..98fc7aa1be 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -89,8 +89,6 @@ runBlockfrostServiceM backend = flip runReaderT serviceParams data BlockfrostEndpoint = Transaction TransactionHash - -- TODO Check if /txs/{txhash}/metadata/cbor is paginated. - -- Documentation suggests it both is and isn't. | TransactionMetadata TransactionHash realizeEndpoint :: BlockfrostEndpoint -> Affjax.URL From 222c7b654fbabc5fd21030a24584613ae79106cf Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Mon, 9 Jan 2023 14:49:31 +0000 Subject: [PATCH 249/373] Add logger to blockfrost, warn when additional utxos are supplied --- src/Internal/Contract/QueryHandle.purs | 18 ++++++++++-------- src/Internal/Service/Blockfrost.purs | 24 ++++++++++++++++++++---- 2 files changed, 30 insertions(+), 12 deletions(-) diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs index c81c67c648..4264e4f1e3 100644 --- a/src/Internal/Contract/QueryHandle.purs +++ b/src/Internal/Contract/QueryHandle.purs @@ -6,7 +6,7 @@ module Ctl.Internal.Contract.QueryHandle import Prelude -import Contract.Log (logDebug') +import Contract.Log (logDebug', logWarn') import Control.Monad.Reader.Class (ask) import Ctl.Internal.Cardano.Types.ScriptRef (ScriptRef) import Ctl.Internal.Cardano.Types.Transaction @@ -49,16 +49,14 @@ import Ctl.Internal.Service.Blockfrost ( BlockfrostServiceM , runBlockfrostServiceM ) -import Ctl.Internal.Service.Blockfrost - ( evaluateTx - , submitTx - ) as Blockfrost +import Ctl.Internal.Service.Blockfrost (evaluateTx, submitTx) as Blockfrost import Ctl.Internal.Service.Error (ClientError(ClientOtherError)) import Ctl.Internal.Types.Chain as Chain import Ctl.Internal.Types.Datum (DataHash, Datum) import Ctl.Internal.Types.Transaction (TransactionHash, TransactionInput) import Ctl.Internal.Types.TransactionMetadata (GeneralTransactionMetadata) import Data.Either (Either(Left)) +import Data.Map as Map import Data.Maybe (Maybe(Just, Nothing), isJust) import Data.Newtype (unwrap, wrap) import Effect.Aff (Aff) @@ -123,7 +121,7 @@ queryHandleForCtlBackend contractEnv backend = queryHandleForBlockfrostBackend :: ContractEnv -> BlockfrostBackend -> QueryHandle -> QueryHandle -queryHandleForBlockfrostBackend _ backend fallback = +queryHandleForBlockfrostBackend env backend fallback = { getDatumByHash: fallback.getDatumByHash , getScriptByHash: fallback.getScriptByHash , getUtxoByOref: fallback.getUtxoByOref @@ -133,9 +131,13 @@ queryHandleForBlockfrostBackend _ backend fallback = , getChainTip: fallback.getChainTip , getCurrentEpoch: fallback.getCurrentEpoch , submitTx: runBlockfrostServiceM' <<< Blockfrost.submitTx - , evaluateTx: \tx _ -> runBlockfrostServiceM' $ Blockfrost.evaluateTx tx + , evaluateTx: \tx additionalUtxos -> runBlockfrostServiceM' do + unless (Map.isEmpty $ unwrap additionalUtxos) do + logWarn' "Blockfrost does not support explicit additional utxos" + Blockfrost.evaluateTx tx , getEraSummaries: fallback.getEraSummaries } where runBlockfrostServiceM' :: forall (a :: Type). BlockfrostServiceM a -> Aff a - runBlockfrostServiceM' = runBlockfrostServiceM backend + runBlockfrostServiceM' = runBlockfrostServiceM env.logLevel env.customLogger + backend diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index 88430235ec..09a9fbf2ac 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -23,12 +23,14 @@ import Affjax.ResponseFormat (string) as Affjax.ResponseFormat import Affjax.StatusCode (StatusCode(StatusCode)) as Affjax import Control.Alt ((<|>)) import Control.Monad.Error.Class (throwError) +import Control.Monad.Logger.Trans (LoggerT, runLoggerT) import Control.Monad.Reader.Class (ask) import Control.Monad.Reader.Trans (ReaderT, runReaderT) import Ctl.Internal.Cardano.Types.Transaction ( Transaction ) import Ctl.Internal.Contract.QueryBackend (BlockfrostBackend) +import Ctl.Internal.Helpers (logWithLevel) import Ctl.Internal.QueryM.Ogmios (TxEvaluationR) import Ctl.Internal.Serialization as Serialization import Ctl.Internal.ServerConfig (ServerConfig, mkHttpUrl) @@ -42,7 +44,9 @@ import Data.Bifunctor (lmap) import Data.Either (Either(Left, Right)) import Data.Generic.Rep (class Generic) import Data.HTTP.Method (Method(GET, POST)) -import Data.Maybe (Maybe(Just), maybe) +import Data.Log.Level (LogLevel) +import Data.Log.Message (Message) +import Data.Maybe (Maybe(Just), fromMaybe, maybe) import Data.MediaType (MediaType(MediaType)) import Data.Newtype (unwrap, wrap) import Data.Show.Generic (genericShow) @@ -61,12 +65,24 @@ type BlockfrostServiceParams = , blockfrostApiKey :: Maybe String } -type BlockfrostServiceM (a :: Type) = ReaderT BlockfrostServiceParams Aff a +type BlockfrostServiceM (a :: Type) = LoggerT + (ReaderT BlockfrostServiceParams Aff) + a runBlockfrostServiceM - :: forall (a :: Type). BlockfrostBackend -> BlockfrostServiceM a -> Aff a -runBlockfrostServiceM backend = flip runReaderT serviceParams + :: forall (a :: Type) + . LogLevel + -> Maybe (LogLevel -> Message -> Aff Unit) + -> BlockfrostBackend + -> BlockfrostServiceM a + -> Aff a +runBlockfrostServiceM logLevel customLogger backend = + flip runReaderT serviceParams <<< flip runLoggerT logger where + logger :: Message -> ReaderT BlockfrostServiceParams Aff Unit + logger = + liftAff <<< fromMaybe logWithLevel customLogger logLevel + serviceParams :: BlockfrostServiceParams serviceParams = { blockfrostConfig: backend.blockfrostConfig From 5a6e12265db44dad6f0cfe81677abdeb520d3a7f Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Mon, 9 Jan 2023 20:27:15 +0100 Subject: [PATCH 250/373] Generate fixtures for getNativeScriptByHash, Fix response decoding --- examples/Helpers.purs | 14 ++ ...Hash-40e1692a03d9635ad710945e5c347fc3.json | 1 + ...Hash-9ca299acc34a17efee6505f90dd785bf.json | 1 + ...Hash-a09f347ebcfe3e8dd336ed33a3d11cb0.json | 1 + ...Hash-b08abe1e8c639abdb29f52f0cdc8d294.json | 1 + ...Hash-b1234fba853b0b4c26e3321759d37f22.json | 1 + ...Hash-caeaea6772d641ffc3cb32f09d8c13d4.json | 1 + ...Hash-d9c09d6ca2f1edc7d141ca932a100758.json | 1 + ...Hash-dc6ad24f476b1f683c39b30aefeb362e.json | 1 + ...Hash-e3291f3b66d722a58001075beeec1871.json | 1 + src/Contract/Hashing.purs | 1 + src/Internal/Cardano/Types/NativeScript.purs | 4 +- src/Internal/QueryM/Kupo.purs | 2 +- src/Internal/Service/Blockfrost.purs | 111 ++++++++++---- .../GenerateFixtures/GetNativeScriptByHash.js | 7 + .../GetNativeScriptByHash.purs | 140 ++++++++++++++++++ 16 files changed, 259 insertions(+), 29 deletions(-) create mode 100644 fixtures/test/blockfrost/getNativeScriptByHash/getNativeScriptByHash-40e1692a03d9635ad710945e5c347fc3.json create mode 100644 fixtures/test/blockfrost/getNativeScriptByHash/getNativeScriptByHash-9ca299acc34a17efee6505f90dd785bf.json create mode 100644 fixtures/test/blockfrost/getNativeScriptByHash/getNativeScriptByHash-a09f347ebcfe3e8dd336ed33a3d11cb0.json create mode 100644 fixtures/test/blockfrost/getNativeScriptByHash/getNativeScriptByHash-b08abe1e8c639abdb29f52f0cdc8d294.json create mode 100644 fixtures/test/blockfrost/getNativeScriptByHash/getNativeScriptByHash-b1234fba853b0b4c26e3321759d37f22.json create mode 100644 fixtures/test/blockfrost/getNativeScriptByHash/getNativeScriptByHash-caeaea6772d641ffc3cb32f09d8c13d4.json create mode 100644 fixtures/test/blockfrost/getNativeScriptByHash/getNativeScriptByHash-d9c09d6ca2f1edc7d141ca932a100758.json create mode 100644 fixtures/test/blockfrost/getNativeScriptByHash/getNativeScriptByHash-dc6ad24f476b1f683c39b30aefeb362e.json create mode 100644 fixtures/test/blockfrost/getNativeScriptByHash/getNativeScriptByHash-e3291f3b66d722a58001075beeec1871.json create mode 100644 test/Blockfrost/GenerateFixtures/GetNativeScriptByHash.js create mode 100644 test/Blockfrost/GenerateFixtures/GetNativeScriptByHash.purs diff --git a/examples/Helpers.purs b/examples/Helpers.purs index 88346cb4c7..461903a66a 100644 --- a/examples/Helpers.purs +++ b/examples/Helpers.purs @@ -3,6 +3,7 @@ module Ctl.Examples.Helpers , mkTokenName , mustPayToPubKeyStakeAddress , mustPayToPubKeyStakeAddressWithDatum + , mustPayToPubKeyStakeAddressWithScriptRef , submitAndLog ) where @@ -16,6 +17,7 @@ import Contract.Prim.ByteArray (byteArrayFromAscii) import Contract.Scripts (MintingPolicy) import Contract.Transaction ( BalancedSignedTransaction + , ScriptRef , awaitTxConfirmed , submit ) @@ -61,6 +63,18 @@ mustPayToPubKeyStakeAddressWithDatum pkh Nothing datum dtp = mustPayToPubKeyStakeAddressWithDatum pkh (Just skh) datum dtp = Constraints.mustPayToPubKeyAddressWithDatum pkh skh datum dtp +mustPayToPubKeyStakeAddressWithScriptRef + :: forall (i :: Type) (o :: Type) + . PaymentPubKeyHash + -> Maybe StakePubKeyHash + -> ScriptRef + -> Value + -> Constraints.TxConstraints i o +mustPayToPubKeyStakeAddressWithScriptRef pkh Nothing scriptRef = + Constraints.mustPayToPubKeyWithScriptRef pkh scriptRef +mustPayToPubKeyStakeAddressWithScriptRef pkh (Just skh) scriptRef = + Constraints.mustPayToPubKeyAddressWithScriptRef pkh skh scriptRef + submitAndLog :: BalancedSignedTransaction -> Contract Unit submitAndLog bsTx = do diff --git a/fixtures/test/blockfrost/getNativeScriptByHash/getNativeScriptByHash-40e1692a03d9635ad710945e5c347fc3.json b/fixtures/test/blockfrost/getNativeScriptByHash/getNativeScriptByHash-40e1692a03d9635ad710945e5c347fc3.json new file mode 100644 index 0000000000..a7ac464ebb --- /dev/null +++ b/fixtures/test/blockfrost/getNativeScriptByHash/getNativeScriptByHash-40e1692a03d9635ad710945e5c347fc3.json @@ -0,0 +1 @@ +{"json":{"slot":954320,"type":"before"}} \ No newline at end of file diff --git a/fixtures/test/blockfrost/getNativeScriptByHash/getNativeScriptByHash-9ca299acc34a17efee6505f90dd785bf.json b/fixtures/test/blockfrost/getNativeScriptByHash/getNativeScriptByHash-9ca299acc34a17efee6505f90dd785bf.json new file mode 100644 index 0000000000..fe1558aa3d --- /dev/null +++ b/fixtures/test/blockfrost/getNativeScriptByHash/getNativeScriptByHash-9ca299acc34a17efee6505f90dd785bf.json @@ -0,0 +1 @@ +{"json":{"type":"all","scripts":[{"slot":609379,"type":"before"},{"type":"atLeast","scripts":[],"required":378926},{"slot":855344,"type":"after"},{"type":"atLeast","scripts":[{"slot":857220,"type":"before"},{"type":"atLeast","scripts":[],"required":783571},{"slot":121087,"type":"after"},{"type":"all","scripts":[{"type":"sig","keyHash":"1c12f03c1ef2e935acc35ec2e6f96c650fd3bfba3e96550504d53361"},{"slot":35861,"type":"after"}]},{"type":"all","scripts":[]}],"required":309781},{"slot":777907,"type":"after"}]}} \ No newline at end of file diff --git a/fixtures/test/blockfrost/getNativeScriptByHash/getNativeScriptByHash-a09f347ebcfe3e8dd336ed33a3d11cb0.json b/fixtures/test/blockfrost/getNativeScriptByHash/getNativeScriptByHash-a09f347ebcfe3e8dd336ed33a3d11cb0.json new file mode 100644 index 0000000000..62b5ce1256 --- /dev/null +++ b/fixtures/test/blockfrost/getNativeScriptByHash/getNativeScriptByHash-a09f347ebcfe3e8dd336ed33a3d11cb0.json @@ -0,0 +1 @@ +{"json":{"type":"all","scripts":[{"type":"any","scripts":[{"slot":572905,"type":"before"},{"type":"sig","keyHash":"1c12f03c1ef2e935acc35ec2e6f96c650fd3bfba3e96550504d53361"},{"slot":811283,"type":"after"},{"type":"sig","keyHash":"1c12f03c1ef2e935acc35ec2e6f96c650fd3bfba3e96550504d53361"},{"type":"any","scripts":[]}]},{"type":"atLeast","scripts":[{"type":"any","scripts":[{"type":"any","scripts":[{"type":"any","scripts":[]}]}]},{"slot":570137,"type":"after"},{"slot":548024,"type":"before"},{"type":"atLeast","scripts":[{"type":"all","scripts":[{"slot":645981,"type":"after"}]}],"required":418962}],"required":436035}]}} \ No newline at end of file diff --git a/fixtures/test/blockfrost/getNativeScriptByHash/getNativeScriptByHash-b08abe1e8c639abdb29f52f0cdc8d294.json b/fixtures/test/blockfrost/getNativeScriptByHash/getNativeScriptByHash-b08abe1e8c639abdb29f52f0cdc8d294.json new file mode 100644 index 0000000000..d625853119 --- /dev/null +++ b/fixtures/test/blockfrost/getNativeScriptByHash/getNativeScriptByHash-b08abe1e8c639abdb29f52f0cdc8d294.json @@ -0,0 +1 @@ +{"json":{"type":"all","scripts":[{"type":"all","scripts":[{"type":"any","scripts":[]},{"type":"sig","keyHash":"1c12f03c1ef2e935acc35ec2e6f96c650fd3bfba3e96550504d53361"},{"type":"atLeast","scripts":[{"slot":575878,"type":"before"},{"type":"all","scripts":[]}],"required":531675}]}]}} \ No newline at end of file diff --git a/fixtures/test/blockfrost/getNativeScriptByHash/getNativeScriptByHash-b1234fba853b0b4c26e3321759d37f22.json b/fixtures/test/blockfrost/getNativeScriptByHash/getNativeScriptByHash-b1234fba853b0b4c26e3321759d37f22.json new file mode 100644 index 0000000000..1c3f91e9f2 --- /dev/null +++ b/fixtures/test/blockfrost/getNativeScriptByHash/getNativeScriptByHash-b1234fba853b0b4c26e3321759d37f22.json @@ -0,0 +1 @@ +{"json":{"type":"all","scripts":[{"type":"all","scripts":[{"type":"atLeast","scripts":[],"required":479340},{"type":"sig","keyHash":"1c12f03c1ef2e935acc35ec2e6f96c650fd3bfba3e96550504d53361"},{"type":"any","scripts":[{"type":"atLeast","scripts":[{"type":"sig","keyHash":"1c12f03c1ef2e935acc35ec2e6f96c650fd3bfba3e96550504d53361"}],"required":239921},{"type":"all","scripts":[{"type":"sig","keyHash":"1c12f03c1ef2e935acc35ec2e6f96c650fd3bfba3e96550504d53361"}]}]},{"type":"atLeast","scripts":[{"type":"atLeast","scripts":[],"required":22611},{"slot":806908,"type":"after"}],"required":38914}]},{"type":"any","scripts":[{"type":"all","scripts":[{"type":"atLeast","scripts":[],"required":398423}]},{"type":"atLeast","scripts":[{"type":"atLeast","scripts":[],"required":913395}],"required":356642}]},{"type":"all","scripts":[{"slot":730713,"type":"before"}]},{"slot":50228,"type":"after"},{"type":"atLeast","scripts":[],"required":596995},{"slot":833384,"type":"after"}]}} \ No newline at end of file diff --git a/fixtures/test/blockfrost/getNativeScriptByHash/getNativeScriptByHash-caeaea6772d641ffc3cb32f09d8c13d4.json b/fixtures/test/blockfrost/getNativeScriptByHash/getNativeScriptByHash-caeaea6772d641ffc3cb32f09d8c13d4.json new file mode 100644 index 0000000000..1652948558 --- /dev/null +++ b/fixtures/test/blockfrost/getNativeScriptByHash/getNativeScriptByHash-caeaea6772d641ffc3cb32f09d8c13d4.json @@ -0,0 +1 @@ +{"json":{"slot":864735,"type":"after"}} \ No newline at end of file diff --git a/fixtures/test/blockfrost/getNativeScriptByHash/getNativeScriptByHash-d9c09d6ca2f1edc7d141ca932a100758.json b/fixtures/test/blockfrost/getNativeScriptByHash/getNativeScriptByHash-d9c09d6ca2f1edc7d141ca932a100758.json new file mode 100644 index 0000000000..71b0a33eeb --- /dev/null +++ b/fixtures/test/blockfrost/getNativeScriptByHash/getNativeScriptByHash-d9c09d6ca2f1edc7d141ca932a100758.json @@ -0,0 +1 @@ +{"json":{"type":"sig","keyHash":"1c12f03c1ef2e935acc35ec2e6f96c650fd3bfba3e96550504d53361"}} \ No newline at end of file diff --git a/fixtures/test/blockfrost/getNativeScriptByHash/getNativeScriptByHash-dc6ad24f476b1f683c39b30aefeb362e.json b/fixtures/test/blockfrost/getNativeScriptByHash/getNativeScriptByHash-dc6ad24f476b1f683c39b30aefeb362e.json new file mode 100644 index 0000000000..0b7042384a --- /dev/null +++ b/fixtures/test/blockfrost/getNativeScriptByHash/getNativeScriptByHash-dc6ad24f476b1f683c39b30aefeb362e.json @@ -0,0 +1 @@ +{"json":{"slot":559261,"type":"after"}} \ No newline at end of file diff --git a/fixtures/test/blockfrost/getNativeScriptByHash/getNativeScriptByHash-e3291f3b66d722a58001075beeec1871.json b/fixtures/test/blockfrost/getNativeScriptByHash/getNativeScriptByHash-e3291f3b66d722a58001075beeec1871.json new file mode 100644 index 0000000000..75925b9955 --- /dev/null +++ b/fixtures/test/blockfrost/getNativeScriptByHash/getNativeScriptByHash-e3291f3b66d722a58001075beeec1871.json @@ -0,0 +1 @@ +{"json":{"slot":398802,"type":"before"}} \ No newline at end of file diff --git a/src/Contract/Hashing.purs b/src/Contract/Hashing.purs index 2f645b428a..efd061dffb 100644 --- a/src/Contract/Hashing.purs +++ b/src/Contract/Hashing.purs @@ -8,6 +8,7 @@ import Ctl.Internal.Hashing , blake2b256HashHex , datumHash , plutusScriptHash + , scriptRefHash , sha256Hash , sha256HashHex , sha3_256Hash diff --git a/src/Internal/Cardano/Types/NativeScript.purs b/src/Internal/Cardano/Types/NativeScript.purs index 3c24525b52..4f39e1c74f 100644 --- a/src/Internal/Cardano/Types/NativeScript.purs +++ b/src/Internal/Cardano/Types/NativeScript.purs @@ -55,7 +55,9 @@ instance Arbitrary NativeScript where [ ScriptPubkey <$> (pure pk) , ScriptAll <$> sized (\i -> resize (i `div` 2) arbitrary) , ScriptAny <$> sized (\i -> resize (i `div` 2) arbitrary) - , ScriptNOfK <$> arbitrary <*> sized (\i -> resize (i `div` 2) arbitrary) + , ScriptNOfK + <$> suchThat (arbitrary :: Gen Int) (_ >= 0) + <*> sized (\i -> resize (i `div` 2) arbitrary) , TimelockStart <$> map (wrap <<< (unsafePartial $ fromJust <<< fromString <<< show)) (suchThat (arbitrary :: Gen Int) (_ > 0)) diff --git a/src/Internal/QueryM/Kupo.purs b/src/Internal/QueryM/Kupo.purs index 6e118fcd67..f3a0da0f2f 100644 --- a/src/Internal/QueryM/Kupo.purs +++ b/src/Internal/QueryM/Kupo.purs @@ -59,7 +59,7 @@ import Ctl.Internal.ServerConfig (ServerConfig, mkHttpUrl) import Ctl.Internal.Service.Error (ClientError(ClientOtherError)) import Ctl.Internal.Service.Helpers (aesonArray, aesonObject, aesonString) import Ctl.Internal.Types.BigNum (toString) as BigNum -import Ctl.Internal.Types.ByteArray (ByteArray, byteArrayToHex, hexToByteArray) +import Ctl.Internal.Types.ByteArray (byteArrayToHex, hexToByteArray) import Ctl.Internal.Types.CborBytes (hexToCborBytes) import Ctl.Internal.Types.Datum (DataHash(DataHash), Datum) import Ctl.Internal.Types.OutputDatum diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index be0a6b56d4..e7b6d93886 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -1,9 +1,18 @@ module Ctl.Internal.Service.Blockfrost - ( BlockfrostServiceM + ( BlockfrostEndpoint + ( GetDatumCbor + , GetNativeScriptByHash + , GetPlutusScriptCborByHash + , GetScriptInfo + ) + , BlockfrostRawResponses + , BlockfrostServiceM , BlockfrostServiceParams + , blockfrostPostRequest , getDatumByHash , getScriptByHash , runBlockfrostServiceM + , runBlockfrostServiceTestM ) where import Prelude @@ -25,7 +34,7 @@ import Affjax.ResponseFormat (string) as Affjax.ResponseFormat import Affjax.StatusCode (StatusCode(StatusCode)) as Affjax import Control.Monad.Except.Trans (ExceptT(ExceptT), runExceptT) import Control.Monad.Maybe.Trans (MaybeT(MaybeT), runMaybeT) -import Control.Monad.Reader.Class (ask) +import Control.Monad.Reader.Class (ask, asks) import Control.Monad.Reader.Trans (ReaderT, runReaderT) import Ctl.Internal.Cardano.Types.NativeScript ( NativeScript @@ -61,34 +70,63 @@ import Data.Bifunctor (lmap) import Data.Either (Either(Left, Right), note) import Data.Generic.Rep (class Generic) import Data.HTTP.Method (Method(GET, POST)) -import Data.Maybe (Maybe(Nothing), maybe) +import Data.Map (Map) +import Data.Map (empty, insert) as Map +import Data.Maybe (Maybe(Just, Nothing), fromJust, maybe) import Data.MediaType (MediaType) import Data.Newtype (class Newtype, unwrap, wrap) import Data.Show.Generic (genericShow) +import Data.Traversable (traverse, traverse_) +import Data.Tuple (Tuple(Tuple)) +import Data.Tuple.Nested (type (/\)) import Effect.Aff (Aff) import Effect.Aff.Class (liftAff) +import Effect.Class (liftEffect) +import Effect.Ref (Ref) +import Effect.Ref (modify_, new, read) as Ref import Foreign.Object (Object) +import Partial.Unsafe (unsafePartial) -------------------------------------------------------------------------------- -- BlockfrostServiceM -------------------------------------------------------------------------------- +type BlockfrostRawResponses = Maybe (Ref (Map BlockfrostEndpoint String)) + type BlockfrostServiceParams = { blockfrostConfig :: ServerConfig , blockfrostApiKey :: Maybe String + , blockfrostRawResponses :: BlockfrostRawResponses } type BlockfrostServiceM (a :: Type) = ReaderT BlockfrostServiceParams Aff a runBlockfrostServiceM :: forall (a :: Type). BlockfrostBackend -> BlockfrostServiceM a -> Aff a -runBlockfrostServiceM backend = flip runReaderT serviceParams +runBlockfrostServiceM = flip runReaderT <<< mkServiceParams Nothing + +runBlockfrostServiceTestM + :: forall (a :: Type) + . BlockfrostBackend + -> BlockfrostServiceM a + -> Aff (a /\ Map BlockfrostEndpoint String) +runBlockfrostServiceTestM backend action = do + rawResponsesRef <- liftEffect $ Just <$> Ref.new Map.empty + runReaderT actionWithRawResponses (mkServiceParams rawResponsesRef backend) where - serviceParams :: BlockfrostServiceParams - serviceParams = - { blockfrostConfig: backend.blockfrostConfig - , blockfrostApiKey: backend.blockfrostApiKey - } + actionWithRawResponses + :: BlockfrostServiceM (a /\ Map BlockfrostEndpoint String) + actionWithRawResponses = do + rawResponsesRef <- unsafePartial fromJust <$> asks _.blockfrostRawResponses + Tuple <$> action <*> liftEffect (Ref.read rawResponsesRef) + +mkServiceParams + :: BlockfrostRawResponses -> BlockfrostBackend -> BlockfrostServiceParams +mkServiceParams blockfrostRawResponses backend = + { blockfrostConfig: backend.blockfrostConfig + , blockfrostApiKey: backend.blockfrostApiKey + , blockfrostRawResponses + } -------------------------------------------------------------------------------- -- Making requests to Blockfrost endpoints @@ -104,6 +142,13 @@ data BlockfrostEndpoint -- /scripts/{script_hash}/json | GetNativeScriptByHash ScriptHash +derive instance Generic BlockfrostEndpoint _ +derive instance Eq BlockfrostEndpoint +derive instance Ord BlockfrostEndpoint + +instance Show BlockfrostEndpoint where + show = genericShow + realizeEndpoint :: BlockfrostEndpoint -> Affjax.URL realizeEndpoint endpoint = case endpoint of @@ -119,15 +164,27 @@ realizeEndpoint endpoint = blockfrostGetRequest :: BlockfrostEndpoint -> BlockfrostServiceM (Either Affjax.Error (Affjax.Response String)) -blockfrostGetRequest endpoint = ask >>= \params -> liftAff do - Affjax.request $ Affjax.defaultRequest - { method = Left GET - , url = mkHttpUrl params.blockfrostConfig <> realizeEndpoint endpoint - , responseFormat = Affjax.ResponseFormat.string - , headers = - maybe mempty (\apiKey -> [ Affjax.RequestHeader "project_id" apiKey ]) - params.blockfrostApiKey - } +blockfrostGetRequest endpoint = ask >>= \params -> do + result <- + liftAff $ Affjax.request $ Affjax.defaultRequest + { method = Left GET + , url = mkHttpUrl params.blockfrostConfig <> realizeEndpoint endpoint + , responseFormat = Affjax.ResponseFormat.string + , headers = + maybe mempty (\apiKey -> [ Affjax.RequestHeader "project_id" apiKey ]) + params.blockfrostApiKey + } + updateRawResponses result + pure result + where + updateRawResponses + :: Either Affjax.Error (Affjax.Response String) + -> BlockfrostServiceM Unit + updateRawResponses (Right { body: response }) = do + rawResponses <- asks _.blockfrostRawResponses + liftEffect $ + traverse_ (Ref.modify_ (Map.insert endpoint response)) rawResponses + updateRawResponses _ = pure unit blockfrostPostRequest :: BlockfrostEndpoint @@ -244,7 +301,7 @@ instance Show BlockfrostScriptLanguage where instance DecodeAeson BlockfrostScriptLanguage where decodeAeson = aesonString $ case _ of - "native" -> pure NativeScript + "timelock" -> pure NativeScript "plutusV1" -> pure PlutusV1Script "plutusV2" -> pure PlutusV2Script invalid -> @@ -289,9 +346,6 @@ instance DecodeAeson BlockfrostNativeScript where decodeAeson = aesonObject (flip getField "json") >=> (map wrap <<< decodeNativeScript) where - unwrap' :: BlockfrostNativeScript -> NativeScript - unwrap' = unwrap - decodeNativeScript :: Object Aeson -> Either JsonDecodeError NativeScript decodeNativeScript obj = getField obj "type" >>= case _ of "sig" -> @@ -304,14 +358,17 @@ instance DecodeAeson BlockfrostNativeScript where "after" -> TimelockStart <$> getField obj "slot" "all" -> - ScriptAll <$> map unwrap' <$> getField obj "scripts" + ScriptAll <$> decodeScripts "any" -> - ScriptAny <$> map unwrap' <$> getField obj "scripts" - "atLeast" -> do - required <- getField obj "required" - ScriptNOfK required <$> map unwrap' <$> getField obj "scripts" + ScriptAny <$> decodeScripts + "atLeast" -> + ScriptNOfK <$> getField obj "required" <*> decodeScripts _ -> Left $ TypeMismatch "Native script constructor" + where + decodeScripts :: Either JsonDecodeError (Array NativeScript) + decodeScripts = + getField obj "scripts" >>= traverse (aesonObject decodeNativeScript) -------------------------------------------------------------------------------- -- BlockfrostCbor diff --git a/test/Blockfrost/GenerateFixtures/GetNativeScriptByHash.js b/test/Blockfrost/GenerateFixtures/GetNativeScriptByHash.js new file mode 100644 index 0000000000..5ce72bdad6 --- /dev/null +++ b/test/Blockfrost/GenerateFixtures/GetNativeScriptByHash.js @@ -0,0 +1,7 @@ +"use strict"; + +const crypto = require("crypto"); + +exports.md5 = function (message) { + return crypto.createHash("md5").update(message).digest("hex"); +}; diff --git a/test/Blockfrost/GenerateFixtures/GetNativeScriptByHash.purs b/test/Blockfrost/GenerateFixtures/GetNativeScriptByHash.purs new file mode 100644 index 0000000000..90d6f1a9a6 --- /dev/null +++ b/test/Blockfrost/GenerateFixtures/GetNativeScriptByHash.purs @@ -0,0 +1,140 @@ +module Test.Ctl.Blockfrost.GenerateFixtures.GetNativeScriptByHash (main) where + +import Contract.Prelude + +import Contract.Address (ownPaymentPubKeyHash, ownStakePubKeyHash) +import Contract.Config + ( ContractParams + , PrivatePaymentKeySource(PrivatePaymentKeyFile) + , WalletSpec(UseKeys) + , blockfrostPublicPreviewServerConfig + , testnetConfig + ) +import Contract.Hashing (scriptRefHash) as Hashing +import Contract.Monad + ( Contract + , launchAff_ + , liftContractM + , liftedM + , runContract + ) +import Contract.ScriptLookups (ScriptLookups) as Lookups +import Contract.Scripts (NativeScript, ScriptHash) +import Contract.Transaction + ( ScriptRef(NativeScriptRef) + , awaitTxConfirmed + , submitTxFromConstraints + ) +import Contract.TxConstraints (TxConstraints) as Constraints +import Contract.Value (lovelaceValueOf) as Value +import Ctl.Examples.Helpers (mustPayToPubKeyStakeAddressWithScriptRef) +import Ctl.Internal.Contract.QueryBackend (BlockfrostBackend) +import Ctl.Internal.Service.Blockfrost + ( BlockfrostEndpoint(GetNativeScriptByHash) + , runBlockfrostServiceTestM + ) +import Ctl.Internal.Service.Blockfrost (getScriptByHash) as Blockfrost +import Data.Array (mapWithIndex) +import Data.BigInt (fromInt) as BigInt +import Data.Map (lookup) as Map +import Effect.Exception (throw) +import Node.Encoding (Encoding(UTF8)) +import Node.FS.Aff (writeTextFile) +import Node.Path (concat) +import Node.Process (lookupEnv) +import Test.QuickCheck.Arbitrary (arbitrary) +import Test.QuickCheck.Gen (randomSample') +import Test.Spec.Assertions (shouldEqual) + +foreign import md5 :: String -> String + +main :: Effect Unit +main = + contractParams >>= + (launchAff_ <<< flip runContract (generateFixtures 10)) + where + contractParams :: Effect ContractParams + contractParams = do + -- blockfrostApiKey <- lookupEnv' "BLOCKFROST_API_KEY" + skeyFilepath <- lookupEnv' "SKEY_FILEPATH" + pure $ testnetConfig + -- TODO: Configure Contract with Blockfrost as the default backend. + -- { backendParams = + -- mkBlockfrostBackendParams + -- { blockfrostConfig: blockfrostPublicPreviewServerConfig + -- , blockfrostApiKey: Just blockfrostApiKey + -- } + { logLevel = Info + , walletSpec = + Just $ UseKeys (PrivatePaymentKeyFile skeyFilepath) Nothing + } + +lookupEnv' :: String -> Effect String +lookupEnv' var = + lookupEnv var >>= + maybe (throw $ var <> " environment variable not set") pure + +generateFixtures :: Int -> Contract Unit +generateFixtures numFixtures = do + -- TODO: Remove this code and use Blockfrost as the default backend instead. + blockfrostApiKey <- liftEffect $ lookupEnv' "BLOCKFROST_API_KEY" + let + backend :: BlockfrostBackend + backend = + { blockfrostConfig: blockfrostPublicPreviewServerConfig + , blockfrostApiKey: Just blockfrostApiKey + } + -- + + nativeScripts <- liftEffect $ randomSample' numFixtures arbitrary + traverse_ (generateFixtureForScript backend) (mapWithIndex (/\) nativeScripts) + where + generateFixtureForScript + :: BlockfrostBackend -> Int /\ NativeScript -> Contract Unit + generateFixtureForScript backend (i /\ nativeScript) = do + let + nativeScriptRef :: ScriptRef + nativeScriptRef = NativeScriptRef nativeScript + + nativeScriptHash :: ScriptHash + nativeScriptHash = Hashing.scriptRefHash nativeScriptRef + + pkh <- liftedM "Failed to get own PKH" ownPaymentPubKeyHash + skh <- ownStakePubKeyHash + let + constraints :: Constraints.TxConstraints Void Void + constraints = + mustPayToPubKeyStakeAddressWithScriptRef pkh skh nativeScriptRef + (Value.lovelaceValueOf $ BigInt.fromInt 2_000_000) + + lookups :: Lookups.ScriptLookups Void + lookups = mempty + + txHash <- submitTxFromConstraints lookups constraints + awaitTxConfirmed txHash + + -- TODO: + -- backend <- liftedM "Failed to get Blockfrost backend" + -- (getBlockfrostBackend <$> asks _.backend) + + eiNativeScript /\ rawResponses <- + liftAff $ runBlockfrostServiceTestM backend + (Blockfrost.getScriptByHash nativeScriptHash) + + eiNativeScript `shouldEqual` Right (Just nativeScriptRef) + + rawResponse <- liftContractM "Could not find raw response" $ + Map.lookup (GetNativeScriptByHash nativeScriptHash) rawResponses + + liftAff $ storeFixture rawResponse + where + storeFixture :: String -> Aff Unit + storeFixture resp = + let + respHash = md5 resp + query = "getNativeScriptByHash" + filename = query <> "-" <> respHash <> ".json" + fp = concat [ "fixtures", "test", "blockfrost", query, filename ] + in + writeTextFile UTF8 fp resp + *> log ("Successfully stored fixture #" <> show i <> " to: " <> fp) From cc62cf47dae849ad54656883f1e6f3ff7df4b255 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Tue, 10 Jan 2023 13:50:55 +0100 Subject: [PATCH 251/373] Add foundation for generating Blockfrost fixtures --- src/Internal/Service/Blockfrost.purs | 97 ++++++++++++++----- test/Blockfrost/GenerateFixtures/Helpers.js | 7 ++ test/Blockfrost/GenerateFixtures/Helpers.purs | 70 +++++++++++++ 3 files changed, 151 insertions(+), 23 deletions(-) create mode 100644 test/Blockfrost/GenerateFixtures/Helpers.js create mode 100644 test/Blockfrost/GenerateFixtures/Helpers.purs diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index 98fc7aa1be..e796e3a817 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -1,10 +1,16 @@ module Ctl.Internal.Service.Blockfrost - ( isTxConfirmed - , getTxMetadata + ( BlockfrostEndpoint + ( Transaction + , TransactionMetadata + ) , BlockfrostMetadata(BlockfrostMetadata) + , BlockfrostRawResponses , BlockfrostServiceM , BlockfrostServiceParams + , getTxMetadata + , isTxConfirmed , runBlockfrostServiceM + , runBlockfrostServiceTestM , dummyExport ) where @@ -22,7 +28,7 @@ import Affjax.RequestBody (RequestBody) as Affjax import Affjax.RequestHeader (RequestHeader(ContentType, RequestHeader)) as Affjax import Affjax.ResponseFormat (string) as Affjax.ResponseFormat import Affjax.StatusCode (StatusCode(StatusCode)) as Affjax -import Control.Monad.Reader.Class (ask) +import Control.Monad.Reader.Class (ask, asks) import Control.Monad.Reader.Trans (ReaderT, runReaderT) import Ctl.Internal.Contract.QueryBackend (BlockfrostBackend) import Ctl.Internal.Contract.QueryHandle.Error @@ -41,7 +47,6 @@ import Ctl.Internal.Service.Error ( ClientError(ClientHttpError, ClientHttpResponseError, ClientDecodeJsonError) , ServiceError(ServiceBlockfrostError) ) --- import Ctl.Internal.QueryM (handleAffjaxResponse) import Ctl.Internal.Types.ByteArray (byteArrayToHex) import Ctl.Internal.Types.CborBytes (CborBytes) import Ctl.Internal.Types.Transaction (TransactionHash) @@ -52,36 +57,63 @@ import Data.Bifunctor (lmap) import Data.Either (Either(Left, Right), note) import Data.Generic.Rep (class Generic) import Data.HTTP.Method (Method(GET, POST)) +import Data.Map (Map) import Data.Map as Map -import Data.Maybe (Maybe, maybe) +import Data.Maybe (Maybe(Just, Nothing), fromJust, maybe) import Data.MediaType (MediaType) import Data.Newtype (class Newtype, unwrap, wrap) import Data.Show.Generic (genericShow) -import Data.Traversable (for) +import Data.Traversable (for, traverse_) +import Data.Tuple (Tuple(Tuple)) +import Data.Tuple.Nested (type (/\)) import Effect.Aff (Aff) import Effect.Aff.Class (liftAff) +import Effect.Class (liftEffect) +import Effect.Ref (Ref) +import Effect.Ref (modify_, new, read) as Ref +import Partial.Unsafe (unsafePartial) import Undefined (undefined) -------------------------------------------------------------------------------- -- BlockfrostServiceM -------------------------------------------------------------------------------- +type BlockfrostRawResponses = Maybe (Ref (Map BlockfrostEndpoint String)) + type BlockfrostServiceParams = { blockfrostConfig :: ServerConfig , blockfrostApiKey :: Maybe String + , blockfrostRawResponses :: BlockfrostRawResponses } type BlockfrostServiceM (a :: Type) = ReaderT BlockfrostServiceParams Aff a runBlockfrostServiceM :: forall (a :: Type). BlockfrostBackend -> BlockfrostServiceM a -> Aff a -runBlockfrostServiceM backend = flip runReaderT serviceParams +runBlockfrostServiceM = flip runReaderT <<< mkServiceParams Nothing + +runBlockfrostServiceTestM + :: forall (a :: Type) + . BlockfrostBackend + -> BlockfrostServiceM a + -> Aff (a /\ Map BlockfrostEndpoint String) +runBlockfrostServiceTestM backend action = do + rawResponsesRef <- liftEffect $ Just <$> Ref.new Map.empty + runReaderT actionWithRawResponses (mkServiceParams rawResponsesRef backend) where - serviceParams :: BlockfrostServiceParams - serviceParams = - { blockfrostConfig: backend.blockfrostConfig - , blockfrostApiKey: backend.blockfrostApiKey - } + actionWithRawResponses + :: BlockfrostServiceM (a /\ Map BlockfrostEndpoint String) + actionWithRawResponses = do + rawResponsesRef <- unsafePartial fromJust <$> asks _.blockfrostRawResponses + Tuple <$> action <*> liftEffect (Ref.read rawResponsesRef) + +mkServiceParams + :: BlockfrostRawResponses -> BlockfrostBackend -> BlockfrostServiceParams +mkServiceParams blockfrostRawResponses backend = + { blockfrostConfig: backend.blockfrostConfig + , blockfrostApiKey: backend.blockfrostApiKey + , blockfrostRawResponses + } -------------------------------------------------------------------------------- -- Making requests to Blockfrost endpoints @@ -91,6 +123,13 @@ data BlockfrostEndpoint = Transaction TransactionHash | TransactionMetadata TransactionHash +derive instance Generic BlockfrostEndpoint _ +derive instance Eq BlockfrostEndpoint +derive instance Ord BlockfrostEndpoint + +instance Show BlockfrostEndpoint where + show = genericShow + realizeEndpoint :: BlockfrostEndpoint -> Affjax.URL realizeEndpoint endpoint = case endpoint of @@ -104,23 +143,24 @@ dummyExport _ = undefined blockfrostPostRequest blockfrostGetRequest :: BlockfrostEndpoint -> BlockfrostServiceM (Either Affjax.Error (Affjax.Response String)) -blockfrostGetRequest endpoint = ask >>= \params -> liftAff do - Affjax.request $ Affjax.defaultRequest - { method = Left GET - , url = mkHttpUrl params.blockfrostConfig <> realizeEndpoint endpoint - , responseFormat = Affjax.ResponseFormat.string - , headers = - maybe mempty (\apiKey -> [ Affjax.RequestHeader "project_id" apiKey ]) - params.blockfrostApiKey - } +blockfrostGetRequest endpoint = ask >>= \params -> + updateRawResponses endpoint =<< liftAff do + Affjax.request $ Affjax.defaultRequest + { method = Left GET + , url = mkHttpUrl params.blockfrostConfig <> realizeEndpoint endpoint + , responseFormat = Affjax.ResponseFormat.string + , headers = + maybe mempty (\apiKey -> [ Affjax.RequestHeader "project_id" apiKey ]) + params.blockfrostApiKey + } blockfrostPostRequest :: BlockfrostEndpoint -> MediaType -> Maybe Affjax.RequestBody -> BlockfrostServiceM (Either Affjax.Error (Affjax.Response String)) -blockfrostPostRequest endpoint mediaType mbContent = - ask >>= \params -> liftAff do +blockfrostPostRequest endpoint mediaType mbContent = ask >>= \params -> + updateRawResponses endpoint =<< liftAff do Affjax.request $ Affjax.defaultRequest { method = Left POST , url = mkHttpUrl params.blockfrostConfig <> realizeEndpoint endpoint @@ -133,6 +173,17 @@ blockfrostPostRequest endpoint mediaType mbContent = params.blockfrostApiKey } +updateRawResponses + :: BlockfrostEndpoint + -> Either Affjax.Error (Affjax.Response String) + -> BlockfrostServiceM (Either Affjax.Error (Affjax.Response String)) +updateRawResponses endpoint result@(Right { body: response }) = do + rawResponses <- asks _.blockfrostRawResponses + liftEffect $ + traverse_ (Ref.modify_ (Map.insert endpoint response)) rawResponses + pure result +updateRawResponses _ result = pure result + -------------------------------------------------------------------------------- -- Blockfrost response handling -------------------------------------------------------------------------------- diff --git a/test/Blockfrost/GenerateFixtures/Helpers.js b/test/Blockfrost/GenerateFixtures/Helpers.js new file mode 100644 index 0000000000..5ce72bdad6 --- /dev/null +++ b/test/Blockfrost/GenerateFixtures/Helpers.js @@ -0,0 +1,7 @@ +"use strict"; + +const crypto = require("crypto"); + +exports.md5 = function (message) { + return crypto.createHash("md5").update(message).digest("hex"); +}; diff --git a/test/Blockfrost/GenerateFixtures/Helpers.purs b/test/Blockfrost/GenerateFixtures/Helpers.purs new file mode 100644 index 0000000000..8ad038b59e --- /dev/null +++ b/test/Blockfrost/GenerateFixtures/Helpers.purs @@ -0,0 +1,70 @@ +module Test.Ctl.Blockfrost.GenerateFixtures.Helpers + ( contractParams + , lookupEnv' + , md5 + , storeBlockfrostFixture + , storeBlockfrostResponse + ) where + +import Contract.Prelude + +import Contract.Config + ( ContractParams + , PrivatePaymentKeySource(PrivatePaymentKeyFile) + , WalletSpec(UseKeys) + , blockfrostPublicPreviewServerConfig + , testnetConfig + ) +import Contract.Monad (Contract, liftContractM) +import Ctl.Internal.Contract.QueryBackend (mkBlockfrostBackendParams) +import Ctl.Internal.Service.Blockfrost (BlockfrostEndpoint) +import Data.Map (Map) +import Data.Map (lookup) as Map +import Data.Maybe (Maybe(Just, Nothing), maybe) +import Effect.Exception (throw) +import Node.Encoding (Encoding(UTF8)) +import Node.FS.Aff (writeTextFile) +import Node.Path (concat) +import Node.Process (lookupEnv) + +foreign import md5 :: String -> String + +contractParams :: Effect ContractParams +contractParams = do + blockfrostApiKey <- lookupEnv' "BLOCKFROST_API_KEY" + skeyFilepath <- lookupEnv' "SKEY_FILEPATH" + pure $ testnetConfig + { backendParams = + mkBlockfrostBackendParams + { blockfrostConfig: blockfrostPublicPreviewServerConfig + , blockfrostApiKey: Just blockfrostApiKey + } + , logLevel = Info + , walletSpec = Just $ UseKeys (PrivatePaymentKeyFile skeyFilepath) Nothing + } + +lookupEnv' :: String -> Effect String +lookupEnv' var = + lookupEnv var >>= + maybe (throw $ var <> " environment variable not set") pure + +storeBlockfrostResponse + :: Map BlockfrostEndpoint String + -> Int + -> String + -> BlockfrostEndpoint + -> Contract Unit +storeBlockfrostResponse rawResponses i query endpoint = do + resp <- liftContractM "Could not find raw response" $ + Map.lookup endpoint rawResponses + liftAff $ storeBlockfrostFixture i query resp + +storeBlockfrostFixture :: Int -> String -> String -> Aff Unit +storeBlockfrostFixture i query resp = + let + respHash = md5 resp + filename = query <> "-" <> respHash <> ".json" + fp = concat [ "fixtures", "test", "blockfrost", query, filename ] + in + writeTextFile UTF8 fp resp + *> log ("Successfully saved fixture #" <> show i <> " to: " <> fp) From 3fb24d54d23123e325f1dcee9cab77d09e4bacb6 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Tue, 10 Jan 2023 16:15:58 +0100 Subject: [PATCH 252/373] Use callbacks to broadcast Blockfrost raw responses --- src/Internal/Service/Blockfrost.purs | 96 ++++++++++++------- test/Blockfrost/GenerateFixtures/Helpers.purs | 16 ---- 2 files changed, 61 insertions(+), 51 deletions(-) diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index e796e3a817..a2aade6594 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -4,9 +4,12 @@ module Ctl.Internal.Service.Blockfrost , TransactionMetadata ) , BlockfrostMetadata(BlockfrostMetadata) - , BlockfrostRawResponses + , BlockfrostRawPostResponseData + , BlockfrostRawResponse , BlockfrostServiceM , BlockfrostServiceParams + , OnBlockfrostRawGetResponseHook + , OnBlockfrostRawPostResponseHook , getTxMetadata , isTxConfirmed , runBlockfrostServiceM @@ -57,62 +60,68 @@ import Data.Bifunctor (lmap) import Data.Either (Either(Left, Right), note) import Data.Generic.Rep (class Generic) import Data.HTTP.Method (Method(GET, POST)) -import Data.Map (Map) import Data.Map as Map -import Data.Maybe (Maybe(Just, Nothing), fromJust, maybe) +import Data.Maybe (Maybe(Nothing), maybe) import Data.MediaType (MediaType) import Data.Newtype (class Newtype, unwrap, wrap) import Data.Show.Generic (genericShow) -import Data.Traversable (for, traverse_) -import Data.Tuple (Tuple(Tuple)) -import Data.Tuple.Nested (type (/\)) +import Data.Traversable (for) import Effect.Aff (Aff) import Effect.Aff.Class (liftAff) -import Effect.Class (liftEffect) -import Effect.Ref (Ref) -import Effect.Ref (modify_, new, read) as Ref -import Partial.Unsafe (unsafePartial) import Undefined (undefined) -------------------------------------------------------------------------------- -- BlockfrostServiceM -------------------------------------------------------------------------------- -type BlockfrostRawResponses = Maybe (Ref (Map BlockfrostEndpoint String)) +type BlockfrostRawResponse = String + +type BlockfrostRawPostResponseData = + { endpoint :: BlockfrostEndpoint + , mediaType :: MediaType + , requestBody :: Maybe Affjax.RequestBody + , rawResponse :: BlockfrostRawResponse + } + +type OnBlockfrostRawGetResponseHook = + Maybe (BlockfrostEndpoint -> BlockfrostRawResponse -> Aff Unit) + +type OnBlockfrostRawPostResponseHook = + Maybe (BlockfrostRawPostResponseData -> Aff Unit) type BlockfrostServiceParams = { blockfrostConfig :: ServerConfig , blockfrostApiKey :: Maybe String - , blockfrostRawResponses :: BlockfrostRawResponses + , onBlockfrostRawGetResponse :: OnBlockfrostRawGetResponseHook + , onBlockfrostRawPostResponse :: OnBlockfrostRawPostResponseHook } type BlockfrostServiceM (a :: Type) = ReaderT BlockfrostServiceParams Aff a runBlockfrostServiceM :: forall (a :: Type). BlockfrostBackend -> BlockfrostServiceM a -> Aff a -runBlockfrostServiceM = flip runReaderT <<< mkServiceParams Nothing +runBlockfrostServiceM = flip runReaderT <<< mkServiceParams Nothing Nothing runBlockfrostServiceTestM :: forall (a :: Type) . BlockfrostBackend + -> OnBlockfrostRawGetResponseHook + -> OnBlockfrostRawPostResponseHook -> BlockfrostServiceM a - -> Aff (a /\ Map BlockfrostEndpoint String) -runBlockfrostServiceTestM backend action = do - rawResponsesRef <- liftEffect $ Just <$> Ref.new Map.empty - runReaderT actionWithRawResponses (mkServiceParams rawResponsesRef backend) - where - actionWithRawResponses - :: BlockfrostServiceM (a /\ Map BlockfrostEndpoint String) - actionWithRawResponses = do - rawResponsesRef <- unsafePartial fromJust <$> asks _.blockfrostRawResponses - Tuple <$> action <*> liftEffect (Ref.read rawResponsesRef) + -> Aff a +runBlockfrostServiceTestM backend onRawGetResponse onRawPostResponse = + flip runReaderT (mkServiceParams onRawGetResponse onRawPostResponse backend) mkServiceParams - :: BlockfrostRawResponses -> BlockfrostBackend -> BlockfrostServiceParams -mkServiceParams blockfrostRawResponses backend = + :: OnBlockfrostRawGetResponseHook + -> OnBlockfrostRawPostResponseHook + -> BlockfrostBackend + -> BlockfrostServiceParams +mkServiceParams onBlockfrostRawGetResponse onBlockfrostRawPostResponse backend = { blockfrostConfig: backend.blockfrostConfig , blockfrostApiKey: backend.blockfrostApiKey - , blockfrostRawResponses + , onBlockfrostRawGetResponse + , onBlockfrostRawPostResponse } -------------------------------------------------------------------------------- @@ -144,7 +153,7 @@ blockfrostGetRequest :: BlockfrostEndpoint -> BlockfrostServiceM (Either Affjax.Error (Affjax.Response String)) blockfrostGetRequest endpoint = ask >>= \params -> - updateRawResponses endpoint =<< liftAff do + withOnRawGetResponseHook endpoint =<< liftAff do Affjax.request $ Affjax.defaultRequest { method = Left GET , url = mkHttpUrl params.blockfrostConfig <> realizeEndpoint endpoint @@ -160,7 +169,7 @@ blockfrostPostRequest -> Maybe Affjax.RequestBody -> BlockfrostServiceM (Either Affjax.Error (Affjax.Response String)) blockfrostPostRequest endpoint mediaType mbContent = ask >>= \params -> - updateRawResponses endpoint =<< liftAff do + withOnRawPostResponseHook endpoint mediaType mbContent =<< liftAff do Affjax.request $ Affjax.defaultRequest { method = Left POST , url = mkHttpUrl params.blockfrostConfig <> realizeEndpoint endpoint @@ -173,16 +182,33 @@ blockfrostPostRequest endpoint mediaType mbContent = ask >>= \params -> params.blockfrostApiKey } -updateRawResponses +withOnRawGetResponseHook + :: BlockfrostEndpoint + -> Either Affjax.Error (Affjax.Response String) + -> BlockfrostServiceM (Either Affjax.Error (Affjax.Response String)) +withOnRawGetResponseHook endpoint result = + case result of + Right { body: rawResponse } -> do + onRawGetResponse <- asks _.onBlockfrostRawGetResponse + maybe (pure unit) (\f -> liftAff $ f endpoint rawResponse) + onRawGetResponse + pure result + _ -> pure result + +withOnRawPostResponseHook :: BlockfrostEndpoint + -> MediaType + -> Maybe Affjax.RequestBody -> Either Affjax.Error (Affjax.Response String) -> BlockfrostServiceM (Either Affjax.Error (Affjax.Response String)) -updateRawResponses endpoint result@(Right { body: response }) = do - rawResponses <- asks _.blockfrostRawResponses - liftEffect $ - traverse_ (Ref.modify_ (Map.insert endpoint response)) rawResponses - pure result -updateRawResponses _ result = pure result +withOnRawPostResponseHook endpoint mediaType requestBody result = + case result of + Right { body: rawResponse } -> do + let data_ = { endpoint, mediaType, requestBody, rawResponse } + onRawPostResponse <- asks _.onBlockfrostRawPostResponse + maybe (pure unit) (\f -> liftAff $ f data_) onRawPostResponse + pure result + _ -> pure result -------------------------------------------------------------------------------- -- Blockfrost response handling diff --git a/test/Blockfrost/GenerateFixtures/Helpers.purs b/test/Blockfrost/GenerateFixtures/Helpers.purs index 8ad038b59e..9d249a3913 100644 --- a/test/Blockfrost/GenerateFixtures/Helpers.purs +++ b/test/Blockfrost/GenerateFixtures/Helpers.purs @@ -3,7 +3,6 @@ module Test.Ctl.Blockfrost.GenerateFixtures.Helpers , lookupEnv' , md5 , storeBlockfrostFixture - , storeBlockfrostResponse ) where import Contract.Prelude @@ -15,11 +14,7 @@ import Contract.Config , blockfrostPublicPreviewServerConfig , testnetConfig ) -import Contract.Monad (Contract, liftContractM) import Ctl.Internal.Contract.QueryBackend (mkBlockfrostBackendParams) -import Ctl.Internal.Service.Blockfrost (BlockfrostEndpoint) -import Data.Map (Map) -import Data.Map (lookup) as Map import Data.Maybe (Maybe(Just, Nothing), maybe) import Effect.Exception (throw) import Node.Encoding (Encoding(UTF8)) @@ -48,17 +43,6 @@ lookupEnv' var = lookupEnv var >>= maybe (throw $ var <> " environment variable not set") pure -storeBlockfrostResponse - :: Map BlockfrostEndpoint String - -> Int - -> String - -> BlockfrostEndpoint - -> Contract Unit -storeBlockfrostResponse rawResponses i query endpoint = do - resp <- liftContractM "Could not find raw response" $ - Map.lookup endpoint rawResponses - liftAff $ storeBlockfrostFixture i query resp - storeBlockfrostFixture :: Int -> String -> String -> Aff Unit storeBlockfrostFixture i query resp = let From 2db5a0e2a5cdc15db12f62af8ea3030e4b7a48ba Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Tue, 10 Jan 2023 20:47:18 +0400 Subject: [PATCH 253/373] WIP: rewrite test utils --- examples/ContractTestUtils.purs | 7 +- src/Contract/Test/Utils.purs | 583 ++++++++++++---------- src/Contract/Transaction.purs | 7 +- src/Internal/Contract/Hooks.purs | 4 +- src/Internal/Contract/QueryHandle.purs | 1 - src/Internal/Test/E2E/Feedback/Hooks.purs | 3 +- test/Plutip/Contract.purs | 14 +- 7 files changed, 348 insertions(+), 271 deletions(-) diff --git a/examples/ContractTestUtils.purs b/examples/ContractTestUtils.purs index 4d43f8c43e..381ff3c8c7 100644 --- a/examples/ContractTestUtils.purs +++ b/examples/ContractTestUtils.purs @@ -51,11 +51,12 @@ import Contract.Transaction import Contract.TxConstraints (DatumPresence(DatumWitness)) import Contract.TxConstraints as Constraints import Contract.Utxos (utxosAt) -import Contract.Value (CurrencySymbol, TokenName, Value) +import Contract.Value (CurrencySymbol, TokenName, Value, adaToken) import Contract.Value (lovelaceValueOf, singleton) as Value import Ctl.Examples.Helpers (mustPayToPubKeyStakeAddress) as Helpers import Data.Array (head) import Data.BigInt (BigInt) +import Data.BigInt as BigInt import Data.Lens (view) newtype ContractParams = ContractParams @@ -94,12 +95,14 @@ mkAssertions params@(ContractParams p) = do p.adaToSend , TestUtils.assertLossAtAddress (label senderAddress "Sender") - \{ txFinalFee } -> pure (p.adaToSend + txFinalFee) + \{ txFinalFee } -> pure (p.adaToSend + txFinalFee + txFinalFee) , TestUtils.assertTokenGainAtAddress' (label senderAddress "Sender") ( uncurry3 (\cs tn amount -> cs /\ tn /\ amount) p.tokensToMint ) + , TestUtils.assertExUnitsNotExceed + { mem: BigInt.fromInt 800, steps: BigInt.fromInt 16110 } ] /\ [ \{ txOutputUnderTest } -> diff --git a/src/Contract/Test/Utils.purs b/src/Contract/Test/Utils.purs index 1e2975ae0b..764f03500d 100644 --- a/src/Contract/Test/Utils.purs +++ b/src/Contract/Test/Utils.purs @@ -1,11 +1,11 @@ -- | This module provides an extensible interface for making various -- | assertions about `Contract`s. module Contract.Test.Utils - ( class ContractAssertions - , ContractAssertionFailure + ( ContractAssertionFailure ( CouldNotGetTxByHash , CouldNotParseMetadata , CustomFailure + , MaxExUnitsExceeded , TransactionHasNoMetadata , UnexpectedDatumInOutput , UnexpectedLovelaceDelta @@ -13,16 +13,15 @@ module Contract.Test.Utils , UnexpectedRefScriptInOutput , UnexpectedTokenDelta ) - , ContractBasicAssertion , ContractTestM , ContractWrapAssertion , ExpectedActual(ExpectedActual) , Label , Labeled(Labeled) - , assertContract , assertContractExpectedActual - , assertContractM - , assertContractM' + , assertContractTestMaybe + , assertContractTestM + , assertExUnitsNotExceed , assertGainAtAddress , assertGainAtAddress' , assertLossAtAddress @@ -36,21 +35,19 @@ module Contract.Test.Utils , assertTokenLossAtAddress , assertTokenLossAtAddress' , assertTxHasMetadata - , checkBalanceDeltaAtAddress + , assertValueDeltaAtAddress , checkNewUtxosAtAddress - , checkOutputHasDatum - , checkOutputHasRefScript - , checkTxHasMetadata + -- -- , checkOutputHasDatum + -- -- , checkOutputHasRefScript + -- -- , checkTxHasMetadata , label , exitCode , interruptOnSignal - , runContractAssertionM - , runContractAssertionM' , unlabel , utxosAtAddress , valueAtAddress , withAssertions - , wrapAndAssert + , mkSimpleAssertion ) where import Prelude @@ -67,9 +64,17 @@ import Contract.Transaction ) import Contract.Utxos (utxosAt) import Contract.Value (CurrencySymbol, TokenName, Value, valueOf, valueToCoin') -import Control.Monad.Except.Trans (ExceptT, except, runExceptT) +import Control.Monad.Error.Class (throwError) +import Control.Monad.Error.Class as E +import Control.Monad.Reader (ReaderT, ask, local, mapReaderT, runReaderT) import Control.Monad.Trans.Class (lift) -import Control.Monad.Writer.Trans (WriterT, runWriterT, tell) +import Ctl.Internal.Cardano.Types.Transaction + ( ExUnits + , Transaction + , _redeemers + , _witnessSet + ) +import Ctl.Internal.Contract.Monad (ContractEnv) import Ctl.Internal.Metadata.FromMetadata (fromMetadata) import Ctl.Internal.Metadata.MetadataType (class MetadataType, metadataLabel) import Ctl.Internal.Plutus.Types.Transaction @@ -80,24 +85,27 @@ import Ctl.Internal.Plutus.Types.Transaction , _scriptRef ) import Ctl.Internal.Types.ByteArray (byteArrayToHex) +import Data.Array (foldr) import Data.Array (fromFoldable, mapWithIndex) as Array import Data.BigInt (BigInt) -import Data.Either (Either(Left, Right), isRight) -import Data.Foldable (foldMap, null) -import Data.Lens.Getter (view, (^.)) +import Data.Either (Either(Right, Left)) +import Data.Foldable (foldMap, null, sum) +import Data.Lens (non, to, traversed, view, (%~), (^.), (^..)) +import Data.Lens.Record (prop) +import Data.List (List(Cons, Nil)) import Data.Map (filterKeys, lookup, values) as Map import Data.Maybe (Maybe(Just, Nothing), maybe) -import Data.Monoid.Endo (Endo(Endo)) -import Data.Newtype (class Newtype, ala, unwrap) +import Data.Newtype (class Newtype, unwrap) import Data.Posix.Signal (Signal) import Data.Posix.Signal as Signal -import Data.Semigroup.Last (Last(Last)) import Data.String.Common (joinWith) as String import Data.Traversable (traverse_) -import Data.Tuple (fst) import Data.Tuple.Nested (type (/\), (/\)) import Effect.Aff (Fiber, killFiber) -import Effect.Exception (error) +import Effect.Class (liftEffect) +import Effect.Exception (error, throw, try) +import Effect.Ref (Ref) +import Effect.Ref as Ref import Node.Process as Process import Type.Proxy (Proxy(Proxy)) @@ -108,47 +116,47 @@ import Type.Proxy (Proxy(Proxy)) -- | Monad allowing for accumulation of assertion failures. Should be used in -- | conjunction with `ContractAssertionM`. type ContractTestM (a :: Type) = - WriterT (Array ContractAssertionFailure) Contract a - --- | Represents computations which may fail with `ContractAssertionFailure`, --- | with the capability of storing some intermediate result, usually the result --- | of the contract under test. --- | --- | Particularly useful for assertions that can control when the contract is --- | run (`ContractWrapAssertion`s). So in case of a failure after the contract --- | has already been executed, we can return the result of the contract, thus --- | preventing the failure of subsequent assertions. -type ContractAssertionM (w :: Type) (a :: Type) = - -- ExceptT ContractAssertionFailure - -- (Writer (Maybe (Last w)) (ContractTestM)) a - ExceptT ContractAssertionFailure - ( WriterT (Maybe (Last w)) - (WriterT (Array ContractAssertionFailure) (Contract)) - ) - a - -runContractAssertionM - :: forall (a :: Type) - . ContractTestM a - -> ContractAssertionM a a - -> ContractTestM a -runContractAssertionM contract wrappedContract = - runWriterT (runExceptT wrappedContract) >>= case _ of - Right result /\ _ -> - pure result - Left failure /\ result -> - tell [ failure ] *> maybe contract (pure <<< unwrap) result - -runContractAssertionM' - :: ContractAssertionM Unit Unit - -> ContractTestM Unit -runContractAssertionM' = runContractAssertionM (pure unit) - -liftContractTestM - :: forall (w :: Type) (a :: Type) - . ContractTestM a - -> ContractAssertionM w a -liftContractTestM = lift <<< lift + ReaderT (Ref (List ContractAssertionFailure)) Contract a + +-- -- | Represents computations which may fail with `ContractAssertionFailure`, +-- -- | with the capability of storing some intermediate result, usually the result +-- -- | of the contract under test. +-- -- | +-- -- | Particularly useful for assertions that can control when the contract is +-- -- | run (`ContractWrapAssertion`s). So in case of a failure after the contract +-- -- | has already been executed, we can return the result of the contract, thus +-- -- | preventing the failure of subsequent assertions. +-- type ContractAssertionM (w :: Type) (a :: Type) = +-- -- ExceptT ContractAssertionFailure +-- -- (Writer (Maybe (Last w)) (ContractTestM)) a +-- ExceptT ContractAssertionFailure +-- ( WriterT (Maybe (Last w)) +-- (WriterT (Array ContractAssertionFailure) (Contract)) +-- ) +-- a + +-- runContractAssertionM +-- :: forall (a :: Type) +-- . ContractTestM a +-- -> ContractAssertionM a a +-- -> ContractTestM a +-- runContractAssertionM contract wrappedContract = +-- runWriterT (runExceptT wrappedContract) >>= case _ of +-- Right result /\ _ -> +-- pure result +-- Left failure /\ result -> +-- tell [ failure ] *> maybe contract (pure <<< unwrap) result + +-- runContractAssertionM' +-- :: ContractAssertionM Unit Unit +-- -> ContractTestM Unit +-- runContractAssertionM' = runContractAssertionM (pure unit) + +-- liftContractTestM +-- :: forall (w :: Type) (a :: Type) +-- . ContractTestM a +-- -> ContractAssertionM w a +-- liftContractTestM = lift <<< lift -------------------------------------------------------------------------------- -- Data types and functions for building assertion failures @@ -165,6 +173,7 @@ data ContractAssertionFailure | UnexpectedRefScriptInOutput (Labeled TransactionOutputWithRefScript) (ExpectedActual (Maybe ScriptRef)) | UnexpectedTokenDelta (Labeled Address) TokenName (ExpectedActual BigInt) + | MaxExUnitsExceeded ExUnits ExUnits | CustomFailure String newtype ContractAssertionFailures = @@ -208,6 +217,11 @@ instance Show ContractAssertionFailure where "Unexpected token delta " <> show tn <> " at address " <> (show addr <> show expectedActual) + show (MaxExUnitsExceeded maxExUnits exUnits) = + "ExUnits limit exceeded: spent " <> show exUnits + <> ", but the limit is " + <> show maxExUnits + show (CustomFailure msg) = msg showTxHash :: TransactionHash -> String @@ -242,101 +256,88 @@ instance Show a => Show (ExpectedActual a) where -- Different types of assertions, Assertion composition, Basic functions -------------------------------------------------------------------------------- --- | An assertion that only needs the result of the contract. -type ContractBasicAssertion (a :: Type) (b :: Type) = - a -> ContractTestM b - --- | An assertion that can control when the contract is run. The assertion --- | inhabiting this type should not call the contract more than once, as other --- | assertions need to be able to make this assumption to succesfully compose. -type ContractWrapAssertion (a :: Type) = - ContractTestM a -> ContractTestM a - --- | Class to unify different methods of making assertions about a contract --- | under a single interface. Note that the typechecker may need some help when --- | using this class; try providing type annotations for your assertions using --- | the type aliases for the instances of this class. -class ContractAssertions (f :: Type) (a :: Type) where - -- | Wrap a contract in an assertion. The wrapped contract itself becomes a - -- | contract which can be wrapped, allowing for composition of assertions. - -- | - -- | No guarantees are made about the order in which assertions are made. - -- | Assertions with side effects should not be used. - wrapAndAssert :: ContractTestM a -> f -> ContractTestM a - -instance ContractAssertions (ContractWrapAssertion a) a where - wrapAndAssert contract assertion = assertion contract -else instance ContractAssertions (ContractBasicAssertion a b) a where - wrapAndAssert contract assertion = contract >>= \r -> assertion r *> pure r - -instance ContractAssertions (Array (ContractWrapAssertion a)) a where - wrapAndAssert contract assertions = ala Endo foldMap assertions contract -else instance - ContractAssertions (Array (ContractBasicAssertion a b)) a where - wrapAndAssert contract assertions = - contract >>= \r -> traverse_ (_ $ r) assertions *> pure r - -instance - ( ContractAssertions f a - , ContractAssertions g a - ) => - ContractAssertions (f /\ g) a where - wrapAndAssert contract (assertionsX /\ assertionsY) = - wrapAndAssert (wrapAndAssert contract assertionsX) assertionsY - -assertContract +-- | An assertion that can control when the contract is run. +type ContractWrapAssertion a = + ContractTestM a -> ContractTestM (ContractTestM Unit /\ ContractTestM a) + +-- | Create an assertion that simply checks a `Contract` result. +-- | If a given `Contract` throws an exception, the assertion is never checked. +mkSimpleAssertion + :: forall (a :: Type). (a -> ContractTestM Unit) -> ContractWrapAssertion a +mkSimpleAssertion f contract = do + ref <- liftEffect $ Ref.new Nothing + let + run = do + res <- contract + liftEffect $ Ref.write (Just res) ref + pure res + finalize = do + liftEffect (Ref.read ref) >>= traverse_ f + pure $ finalize /\ run + +assertContractTestM :: forall (w :: Type) . ContractAssertionFailure -> Boolean - -> ContractAssertionM w Unit -assertContract failure cond + -> ContractTestM Unit +assertContractTestM failure cond | cond = pure unit - | otherwise = except (Left failure) + | otherwise = tellFailure failure -assertContractM' +assertContractTestMaybe :: forall (w :: Type) (a :: Type) . ContractAssertionFailure -> Maybe a - -> ContractAssertionM w a -assertContractM' msg = maybe (except $ Left msg) pure - -assertContractM - :: forall (w :: Type) (a :: Type) - . ContractAssertionFailure - -> Contract (Maybe a) - -> ContractAssertionM w a -assertContractM msg cm = - liftContractTestM (lift cm) >>= assertContractM' msg + -> ContractTestM a +assertContractTestMaybe msg = + maybe (liftEffect $ throw $ show msg) pure assertContractExpectedActual - :: forall (w :: Type) (a :: Type) + :: forall (a :: Type) . Eq a => (ExpectedActual a -> ContractAssertionFailure) -> a -> a - -> ContractAssertionM w Unit + -> ContractTestM Unit assertContractExpectedActual mkAssertionFailure expected actual = - assertContract (mkAssertionFailure $ ExpectedActual expected actual) + assertContractTestM (mkAssertionFailure $ ExpectedActual expected actual) (expected == actual) withAssertions :: forall (a :: Type) (assertions :: Type) - . ContractAssertions assertions a - => assertions + . Array (ContractWrapAssertion a) -> Contract a -> Contract a withAssertions assertions contract = do - result /\ failures <- - runWriterT $ wrapAndAssert (lift contract) assertions + ref <- liftEffect $ Ref.new Nil + result <- + flip runReaderT ref go + failures <- liftEffect $ Ref.read ref if null failures then pure result - else throwContractError (ContractAssertionFailures failures) + else throwContractError + (ContractAssertionFailures $ Array.fromFoldable failures) + where + go :: ContractTestM a + go = foldr + ( \assertion acc -> do + finalize /\ res <- assertion acc + E.try res >>= case _ of + Left failure -> do + finalize + throwError failure + Right success -> do + finalize + pure (success :: a) + ) + (lift contract :: ContractTestM a) + assertions -mkCheckFromAssertion - :: forall (w :: Type) (a :: Type) - . ContractAssertionM w a - -> Contract Boolean -mkCheckFromAssertion = - map (fst <<< fst) <<< runWriterT <<< runWriterT <<< map isRight <<< runExceptT +-- mkCheckFromAssertion +-- :: forall (w :: Type) (a :: Type) +-- . ContractAssertionM w a +-- -> Contract Boolean +-- mkCheckFromAssertion = +-- map (fst <<< fst) <<< runWriterT <<< runWriterT <<< map isRight <<< runExceptT -------------------------------------------------------------------------------- -- Assertions and checks @@ -345,61 +346,139 @@ mkCheckFromAssertion = utxosAtAddress :: forall (w :: Type) . Labeled Address - -> ContractAssertionM w UtxoMap -utxosAtAddress = liftContractTestM <<< lift <<< utxosAt <<< unlabel + -> ContractTestM UtxoMap +utxosAtAddress = lift <<< utxosAt <<< unlabel valueAtAddress :: forall (w :: Type) . Labeled Address - -> ContractAssertionM w Value + -> ContractTestM Value valueAtAddress = map (foldMap (view (_output <<< _amount))) <<< utxosAtAddress -checkBalanceDeltaAtAddress - :: forall (w :: Type) (a :: Type) - . Labeled Address - -> ContractTestM w - -> (w -> Value -> Value -> ContractAssertionM w a) - -> ContractAssertionM w a -checkBalanceDeltaAtAddress addr contract check = do - valueBefore <- valueAtAddress addr - res <- liftContractTestM contract - tell (Just $ Last res) - valueAfter <- valueAtAddress addr - check res valueBefore valueAfter +tellFailure + :: ContractAssertionFailure -> ContractTestM Unit +tellFailure failure = do + ask >>= liftEffect <<< Ref.modify_ (Cons failure) checkNewUtxosAtAddress :: forall (w :: Type) (a :: Type) . Labeled Address -> TransactionHash - -> (Array TransactionOutputWithRefScript -> ContractAssertionM w a) - -> ContractAssertionM w a + -> (Array TransactionOutputWithRefScript -> ContractTestM a) + -> ContractTestM a checkNewUtxosAtAddress addr txHash check = utxosAtAddress addr >>= \utxos -> check $ Array.fromFoldable $ Map.values $ Map.filterKeys (\oref -> (unwrap oref).transactionId == txHash) utxos +-- | Sets a limit on `ExUnits` budget. All ExUnits values of all submitted transactions are combined. Transactions that are constructed, but not submitted, are not considered. +-- | The execution of the `Contract` will not be interrupted in case the `ExUnits` limit is reached. +assertExUnitsNotExceed + :: forall (a :: Type) + . ExUnits + -> ContractWrapAssertion a +assertExUnitsNotExceed maxExUnits contract = do + (ref :: Ref ExUnits) <- liftEffect $ Ref.new { mem: zero, steps: zero } + let + submitHook :: Transaction -> Effect Unit + submitHook tx = do + let + (newExUnits :: ExUnits) = sum $ tx ^.. + _witnessSet + <<< _redeemers + <<< non [] + <<< traversed + <<< to (unwrap >>> _.exUnits) + Ref.modify_ (add newExUnits) ref + + setSubmitHook :: ContractEnv -> ContractEnv + setSubmitHook = + prop (Proxy :: Proxy "hooks") <<< prop (Proxy :: Proxy "onSubmit") + -- Extend a hook action if it exists, or set it to `Just submitHook` + %~ maybe (Just submitHook) + \oldHook -> Just \tx -> do + -- ignore possible exception from the old hook + void $ try $ oldHook tx + submitHook tx + + finalize :: ContractTestM Unit + finalize = do + exUnits <- liftEffect $ Ref.read ref + assertContractTestM (MaxExUnitsExceeded maxExUnits exUnits) + (maxExUnits >= exUnits) + + pure (finalize /\ mapReaderT (local setSubmitHook) contract) + +valueAtAddress' + :: forall (w :: Type) + . Labeled Address + -> ContractTestM Value +valueAtAddress' = map (foldMap (view (_output <<< _amount))) <<< lift + <<< utxosAt + <<< unlabel + +-- | Arguments are: +-- | +-- | - a labeled address +-- | - a callback that implements the assertion, accepting `Contract` execution +-- | result, and values (before and after) +assertValueDeltaAtAddress + :: forall (a :: Type) + . Labeled Address + -> (a -> Contract BigInt) + -> (a -> Value -> Value -> ContractTestM Unit) + -> ContractWrapAssertion a +assertValueDeltaAtAddress addr getExpected check contract = do + valueBefore <- valueAtAddress' addr + ref <- liftEffect $ Ref.new Nothing + let + finalize = do + valueAfter <- valueAtAddress' addr + liftEffect (Ref.read ref) >>= case _ of + Nothing -> pure unit -- tellFailure $ CustomFailure "Contract did not run" + Just res -> check res valueBefore valueAfter + contract' = do + res <- contract + liftEffect $ Ref.write (Just res) ref + pure res + pure (finalize /\ contract') + assertLovelaceDeltaAtAddress :: forall (a :: Type) . Labeled Address -> (a -> Contract BigInt) -> (BigInt -> BigInt -> Boolean) -> ContractWrapAssertion a -assertLovelaceDeltaAtAddress addr getExpected comp contract = - runContractAssertionM contract $ - checkBalanceDeltaAtAddress addr contract - \result valueBefore valueAfter -> do - expected <- liftContractTestM $ lift $ getExpected result - let - actual :: BigInt - actual = valueToCoin' valueAfter - valueToCoin' valueBefore - - unexpectedLovelaceDelta :: ContractAssertionFailure - unexpectedLovelaceDelta = - UnexpectedLovelaceDelta addr (ExpectedActual expected actual) - - assertContract unexpectedLovelaceDelta (comp actual expected) - pure result +assertLovelaceDeltaAtAddress addr getExpected comp contract = do + assertValueDeltaAtAddress addr getExpected check contract + -- valueBefore <- valueAtAddress' addr + -- ref <- liftEffect $ Ref.new Nothing + -- let + -- finalize = do + -- valueAfter <- valueAtAddress' addr + -- liftEffect (Ref.read ref) >>= case _ of + -- Nothing -> pure unit -- tellFailure $ CustomFailure "Contract did not run" + -- Just res -> check res valueBefore valueAfter + -- contract' = do + -- res <- contract + -- liftEffect $ Ref.write (Just res) ref + -- pure res + -- pure (finalize /\ contract') + where + check :: a -> Value -> Value -> ContractTestM Unit + check result valueBefore valueAfter = do + expected <- lift $ getExpected result + let + actual :: BigInt + actual = valueToCoin' valueAfter - valueToCoin' valueBefore + + unexpectedLovelaceDelta :: ContractAssertionFailure + unexpectedLovelaceDelta = + UnexpectedLovelaceDelta addr (ExpectedActual expected actual) + + assertContractTestM unexpectedLovelaceDelta (comp actual expected) + pure unit -- | Requires that the computed amount of lovelace was gained at the address -- | by calling the contract. @@ -449,20 +528,20 @@ assertTokenDeltaAtAddress -> (BigInt -> BigInt -> Boolean) -> ContractWrapAssertion a assertTokenDeltaAtAddress addr (cs /\ tn) getExpected comp contract = - runContractAssertionM contract $ - checkBalanceDeltaAtAddress addr contract - \result valueBefore valueAfter -> do - expected <- liftContractTestM $ lift $ getExpected result - let - actual :: BigInt - actual = valueOf valueAfter cs tn - valueOf valueBefore cs tn + assertValueDeltaAtAddress addr getExpected check contract + where + check :: a -> Value -> Value -> ContractTestM Unit + check result valueBefore valueAfter = do + expected <- lift $ getExpected result + let + actual :: BigInt + actual = valueOf valueAfter cs tn - valueOf valueBefore cs tn - unexpectedTokenDelta :: ContractAssertionFailure - unexpectedTokenDelta = - UnexpectedTokenDelta addr tn (ExpectedActual expected actual) + unexpectedTokenDelta :: ContractAssertionFailure + unexpectedTokenDelta = + UnexpectedTokenDelta addr tn (ExpectedActual expected actual) - assertContract unexpectedTokenDelta (comp actual expected) - pure result + assertContractTestM unexpectedTokenDelta (comp actual expected) -- | Requires that the computed number of tokens was gained at the address -- | by calling the contract. @@ -509,7 +588,7 @@ assertTokenLossAtAddress' addr (cs /\ tn /\ minLoss) = assertOutputHasDatumImpl :: OutputDatum -> Labeled TransactionOutputWithRefScript - -> ContractAssertionM Unit Unit + -> ContractTestM Unit assertOutputHasDatumImpl expectedDatum txOutput = do let actualDatum = unlabel txOutput ^. _output <<< _datum assertContractExpectedActual (UnexpectedDatumInOutput txOutput) @@ -522,28 +601,29 @@ assertOutputHasDatum :: OutputDatum -> Labeled TransactionOutputWithRefScript -> ContractTestM Unit -assertOutputHasDatum expectedDatum = - runContractAssertionM' <<< assertOutputHasDatumImpl expectedDatum - --- | Checks whether the transaction output contains the specified datum or --- | datum hash. -checkOutputHasDatum - :: OutputDatum - -> TransactionOutputWithRefScript - -> Contract Boolean -checkOutputHasDatum expectedDatum txOutput = - mkCheckFromAssertion $ - assertOutputHasDatumImpl expectedDatum (noLabel txOutput) - -assertOutputHasRefScriptImpl - :: ScriptRef - -> Labeled TransactionOutputWithRefScript - -> ContractAssertionM Unit Unit -assertOutputHasRefScriptImpl expectedRefScript txOutput = do - let actualRefScript = unlabel txOutput ^. _scriptRef - assertContractExpectedActual (UnexpectedRefScriptInOutput txOutput) - (Just expectedRefScript) - actualRefScript +assertOutputHasDatum expectedDatum = -- TODO: simplify + + assertOutputHasDatumImpl expectedDatum + +-- -- | Checks whether the transaction output contains the specified datum or +-- -- | datum hash. +-- checkOutputHasDatum +-- :: OutputDatum +-- -> TransactionOutputWithRefScript +-- -> Contract Boolean +-- checkOutputHasDatum expectedDatum txOutput = +-- mkCheckFromAssertion $ +-- assertOutputHasDatumImpl expectedDatum (noLabel txOutput) + +-- assertOutputHasRefScriptImpl +-- :: ScriptRef +-- -> Labeled TransactionOutputWithRefScript +-- -> ContractAssertionM Unit Unit +-- assertOutputHasRefScriptImpl expectedRefScript txOutput = do +-- let actualRefScript = unlabel txOutput ^. _scriptRef +-- assertContractExpectedActual (UnexpectedRefScriptInOutput txOutput) +-- (Just expectedRefScript) +-- actualRefScript -- | Requires that the transaction output contains the specified reference -- | script. @@ -551,46 +631,22 @@ assertOutputHasRefScript :: ScriptRef -> Labeled TransactionOutputWithRefScript -> ContractTestM Unit -assertOutputHasRefScript expectedRefScript = - runContractAssertionM' <<< assertOutputHasRefScriptImpl expectedRefScript - --- | Checks whether the transaction output contains the specified reference --- | script. -checkOutputHasRefScript - :: ScriptRef - -> TransactionOutputWithRefScript - -> Contract Boolean -checkOutputHasRefScript expectedRefScript txOutput = - mkCheckFromAssertion $ - assertOutputHasRefScriptImpl expectedRefScript (noLabel txOutput) - -assertTxHasMetadataImpl - :: forall (a :: Type) - . MetadataType a - => Eq a - => Show a - => Label - -> TransactionHash - -> a - -> ContractAssertionM Unit Unit -assertTxHasMetadataImpl mdLabel txHash expectedMetadata = do - generalMetadata <- - assertContractM (TransactionHasNoMetadata txHash Nothing) - (getTxMetadata txHash) - - rawMetadata <- - assertContractM' (TransactionHasNoMetadata txHash (Just mdLabel)) - (Map.lookup (metadataLabel (Proxy :: Proxy a)) (unwrap generalMetadata)) - - (metadata :: a) <- - assertContractM' (CouldNotParseMetadata mdLabel) - (fromMetadata rawMetadata) +assertOutputHasRefScript expectedRefScript txOutput = do + let actualRefScript = unlabel txOutput ^. _scriptRef + assertContractExpectedActual (UnexpectedRefScriptInOutput txOutput) + (Just expectedRefScript) + actualRefScript - let expectedActual = show <$> ExpectedActual expectedMetadata metadata - assertContract (UnexpectedMetadataValue mdLabel expectedActual) - (metadata == expectedMetadata) +-- -- | Checks whether the transaction output contains the specified reference +-- -- | script. +-- checkOutputHasRefScript +-- :: ScriptRef +-- -> TransactionOutputWithRefScript +-- -> Contract Boolean +-- checkOutputHasRefScript expectedRefScript txOutput = +-- mkCheckFromAssertion $ +-- assertOutputHasRefScriptImpl expectedRefScript (noLabel txOutput) --- | Requires that the transaction contains the specified metadata. assertTxHasMetadata :: forall (a :: Type) . MetadataType a @@ -599,21 +655,38 @@ assertTxHasMetadata => Label -> TransactionHash -> a - -> ContractTestM Unit -assertTxHasMetadata mdLabel txHash = - runContractAssertionM' <<< assertTxHasMetadataImpl mdLabel txHash - --- | Checks whether the transaction contains the specified metadata. -checkTxHasMetadata - :: forall (a :: Type) - . MetadataType a - => Eq a - => Show a - => TransactionHash - -> a - -> Contract Boolean -checkTxHasMetadata txHash = - mkCheckFromAssertion <<< assertTxHasMetadataImpl mempty txHash + -> ContractWrapAssertion a +assertTxHasMetadata mdLabel txHash expectedMetadata contract = do + pure (finalize /\ contract) + where + finalize = do + generalMetadata <- + assertContractTestMaybe (TransactionHasNoMetadata txHash Nothing) + =<< lift (getTxMetadata txHash) + + rawMetadata <- + assertContractTestMaybe (TransactionHasNoMetadata txHash (Just mdLabel)) + (Map.lookup (metadataLabel (Proxy :: Proxy a)) (unwrap generalMetadata)) + + (metadata :: a) <- + assertContractTestMaybe (CouldNotParseMetadata mdLabel) + (fromMetadata rawMetadata) + + let expectedActual = show <$> ExpectedActual expectedMetadata metadata + assertContractTestM (UnexpectedMetadataValue mdLabel expectedActual) + (metadata == expectedMetadata) + +-- -- | Checks whether the transaction contains the specified metadata. +-- checkTxHasMetadata +-- :: forall (a :: Type) +-- . MetadataType a +-- => Eq a +-- => Show a +-- => TransactionHash +-- -> a +-- -> Contract Boolean +-- checkTxHasMetadata txHash = +-- mkCheckFromAssertion <<< assertTxHasMetadataImpl mempty txHash -------------------------------------------------------------------------------- -- function to cancel aff fibers on signal diff --git a/src/Contract/Transaction.purs b/src/Contract/Transaction.purs index 39aebe584f..4f48b5a3ad 100644 --- a/src/Contract/Transaction.purs +++ b/src/Contract/Transaction.purs @@ -267,6 +267,7 @@ import Data.UInt (UInt) import Effect.Aff (bracket) import Effect.Aff.Class (liftAff) import Effect.Class (liftEffect) +import Effect.Exception (try) -- | Signs a transaction with potential failure. signTransaction @@ -287,7 +288,11 @@ submit -> Contract TransactionHash submit tx = do queryHandle <- getQueryHandle - liftedM "Failed to submit tx" $ liftAff $ queryHandle.submitTx $ unwrap tx + res <- liftedM "Failed to submit tx" $ liftAff $ queryHandle.submitTx $ unwrap + tx + void $ asks (_.hooks >>> _.onSubmit) >>= + traverse \hook -> liftEffect $ void $ try $ hook $ unwrap tx + pure res -- | Calculate the minimum transaction fee. calculateMinFee diff --git a/src/Internal/Contract/Hooks.purs b/src/Internal/Contract/Hooks.purs index a6512af72d..efd552c6c7 100644 --- a/src/Internal/Contract/Hooks.purs +++ b/src/Internal/Contract/Hooks.purs @@ -2,6 +2,7 @@ module Ctl.Internal.Contract.Hooks (Hooks, emptyHooks) where import Prelude +import Ctl.Internal.Cardano.Types.Transaction (Transaction) import Data.Maybe (Maybe(Nothing)) import Effect (Effect) import Effect.Exception (Error) @@ -11,6 +12,7 @@ type Hooks = , beforeInit :: Maybe (Effect Unit) , onSuccess :: Maybe (Effect Unit) , onError :: Maybe (Error -> Effect Unit) + , onSubmit :: Maybe (Transaction -> Effect Unit) } emptyHooks :: Hooks @@ -19,5 +21,5 @@ emptyHooks = , beforeInit: Nothing , onSuccess: Nothing , onError: Nothing + , onSubmit: Nothing } - diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs index ea6d9d7a26..6655d34563 100644 --- a/src/Internal/Contract/QueryHandle.purs +++ b/src/Internal/Contract/QueryHandle.purs @@ -131,4 +131,3 @@ queryHandleForBlockfrostBackend _ backend = where runBlockfrostServiceM' :: forall (a :: Type). BlockfrostServiceM a -> Aff a runBlockfrostServiceM' = runBlockfrostServiceM backend - diff --git a/src/Internal/Test/E2E/Feedback/Hooks.purs b/src/Internal/Test/E2E/Feedback/Hooks.purs index 3ba01fb576..01a3e38887 100644 --- a/src/Internal/Test/E2E/Feedback/Hooks.purs +++ b/src/Internal/Test/E2E/Feedback/Hooks.purs @@ -10,7 +10,7 @@ import Ctl.Internal.Test.E2E.Feedback ( BrowserEvent(Sign, ConfirmAccess, Success, Failure) ) import Ctl.Internal.Test.E2E.Feedback.Browser (pushBrowserEvent) -import Data.Maybe (Maybe(Just)) +import Data.Maybe (Maybe(Just, Nothing)) import Data.Traversable (for_) e2eFeedbackHooks :: Hooks @@ -19,6 +19,7 @@ e2eFeedbackHooks = , beforeInit: Just $ pushBrowserEvent ConfirmAccess , onSuccess: Just $ pushBrowserEvent Success , onError: Just (pushBrowserEvent <<< Failure <<< show) + , onSubmit: Nothing } addE2EFeedbackHooks :: Hooks -> Hooks diff --git a/test/Plutip/Contract.purs b/test/Plutip/Contract.purs index 889b2db6ef..7c9a0933a0 100644 --- a/test/Plutip/Contract.purs +++ b/test/Plutip/Contract.purs @@ -27,13 +27,7 @@ import Contract.Metadata , TransactionMetadatum(Text) , TransactionMetadatumLabel(TransactionMetadatumLabel) ) -import Contract.Monad - ( Contract - , liftContractE - , liftContractM - , liftedE - , liftedM - ) +import Contract.Monad (Contract, liftContractE, liftContractM, liftedE, liftedM) import Contract.PlutusData ( Datum(Datum) , PlutusData(Bytes, Integer, List) @@ -151,7 +145,7 @@ import Data.Traversable (traverse, traverse_) import Data.Tuple.Nested (type (/\), (/\)) import Effect.Class (liftEffect) import Effect.Exception (throw) -import Mote (group, skip, test) +import Mote (group, only, skip, test) import Mote.Monad (mapTest) import Safe.Coerce (coerce) import Test.Ctl.Fixtures @@ -176,7 +170,7 @@ import Test.Spec.Assertions (shouldEqual, shouldNotEqual, shouldSatisfy) suite :: TestPlanM PlutipTest Unit suite = do - group "Contract" do + only $ group "Contract" do flip mapTest QueryM.AffInterface.suite (noWallet <<< wrapQueryM) @@ -1247,7 +1241,7 @@ suite = do withWallets distribution \alice -> withKeyWallet alice PaysWithDatum.contract - test "Examples.ContractTestUtils" do + only $ test "Examples.ContractTestUtils" do let initialUtxos :: InitialUTxOs initialUtxos = From acd0ef2ac520fb50a254d676fee338f5b4473381 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Tue, 10 Jan 2023 18:07:00 +0100 Subject: [PATCH 254/373] Generate fixtures for getChainTip --- ...nTip-1cfd9633fcbe9ea24afdcee31c7cd662.json | 1 + ...nTip-3207ceb73ea5261ff64484c0565251f4.json | 1 + ...nTip-60e93aff53f01835818b98bbf21add13.json | 1 + ...nTip-63f282da8288f15a8af50e764ba3c572.json | 1 + ...nTip-734362d34bcc2cc6ad79b50d71a536c6.json | 1 + ...nTip-8116d571e220ea348bfa84b1dbf3a71b.json | 1 + ...nTip-9315383fa4044259c02340bb97d52edb.json | 1 + ...nTip-9ecb4e5de76c205ab67c24ae42982e11.json | 1 + ...nTip-ba3998985828253649728656bdc53c6d.json | 1 + ...nTip-c454ae6168d84b4cdc9d609f8b26a72f.json | 1 + .../Blockfrost/GenerateFixtures/ChainTip.purs | 46 +++++++++++++++++++ test/Blockfrost/GenerateFixtures/Helpers.purs | 33 ++++++++++--- 12 files changed, 82 insertions(+), 7 deletions(-) create mode 100644 fixtures/test/blockfrost/getChainTip/getChainTip-1cfd9633fcbe9ea24afdcee31c7cd662.json create mode 100644 fixtures/test/blockfrost/getChainTip/getChainTip-3207ceb73ea5261ff64484c0565251f4.json create mode 100644 fixtures/test/blockfrost/getChainTip/getChainTip-60e93aff53f01835818b98bbf21add13.json create mode 100644 fixtures/test/blockfrost/getChainTip/getChainTip-63f282da8288f15a8af50e764ba3c572.json create mode 100644 fixtures/test/blockfrost/getChainTip/getChainTip-734362d34bcc2cc6ad79b50d71a536c6.json create mode 100644 fixtures/test/blockfrost/getChainTip/getChainTip-8116d571e220ea348bfa84b1dbf3a71b.json create mode 100644 fixtures/test/blockfrost/getChainTip/getChainTip-9315383fa4044259c02340bb97d52edb.json create mode 100644 fixtures/test/blockfrost/getChainTip/getChainTip-9ecb4e5de76c205ab67c24ae42982e11.json create mode 100644 fixtures/test/blockfrost/getChainTip/getChainTip-ba3998985828253649728656bdc53c6d.json create mode 100644 fixtures/test/blockfrost/getChainTip/getChainTip-c454ae6168d84b4cdc9d609f8b26a72f.json create mode 100644 test/Blockfrost/GenerateFixtures/ChainTip.purs diff --git a/fixtures/test/blockfrost/getChainTip/getChainTip-1cfd9633fcbe9ea24afdcee31c7cd662.json b/fixtures/test/blockfrost/getChainTip/getChainTip-1cfd9633fcbe9ea24afdcee31c7cd662.json new file mode 100644 index 0000000000..8aed8d0314 --- /dev/null +++ b/fixtures/test/blockfrost/getChainTip/getChainTip-1cfd9633fcbe9ea24afdcee31c7cd662.json @@ -0,0 +1 @@ +{"time":1673370103,"height":321818,"hash":"43d76d40c3c35394e9d10e41fe31bd34d0de42909be14359ec41d910b6549746","slot":6714103,"epoch":77,"epoch_slot":61303,"slot_leader":"pool1grvqd4eu354qervmr62uew0nsrjqedx5kglldeqr4c29vv59rku","size":4,"tx_count":0,"output":null,"fees":null,"block_vrf":"vrf_vk166g64rmqt97szakhl7fehyrnqxac7zlxerf9dv9uczyjdtpkv9kshaxlk6","op_cert":"da6821a2bf227250145771044d5323476aa77802e013a648440422ece586c20e","op_cert_counter":"0","previous_block":"009e0ed4757e3446cd883bbcf92da14063388ac1456884ec9e0cbda07290d4ec","next_block":null,"confirmations":0} \ No newline at end of file diff --git a/fixtures/test/blockfrost/getChainTip/getChainTip-3207ceb73ea5261ff64484c0565251f4.json b/fixtures/test/blockfrost/getChainTip/getChainTip-3207ceb73ea5261ff64484c0565251f4.json new file mode 100644 index 0000000000..b6f9dba2bf --- /dev/null +++ b/fixtures/test/blockfrost/getChainTip/getChainTip-3207ceb73ea5261ff64484c0565251f4.json @@ -0,0 +1 @@ +{"time":1673370155,"height":321820,"hash":"4f9ba6d721d5eba2d3f7734a5a46a806d90b90c0e2ee48d2400beac6ae5cfde7","slot":6714155,"epoch":77,"epoch_slot":61355,"slot_leader":"pool1grvqd4eu354qervmr62uew0nsrjqedx5kglldeqr4c29vv59rku","size":4461,"tx_count":2,"output":"7001900985956","fees":"690090","block_vrf":"vrf_vk166g64rmqt97szakhl7fehyrnqxac7zlxerf9dv9uczyjdtpkv9kshaxlk6","op_cert":"da6821a2bf227250145771044d5323476aa77802e013a648440422ece586c20e","op_cert_counter":"0","previous_block":"c6c45ed1305065d03caf279ad085cbea5402a2142c7c59ed19c80f3a4ee3e705","next_block":null,"confirmations":0} \ No newline at end of file diff --git a/fixtures/test/blockfrost/getChainTip/getChainTip-60e93aff53f01835818b98bbf21add13.json b/fixtures/test/blockfrost/getChainTip/getChainTip-60e93aff53f01835818b98bbf21add13.json new file mode 100644 index 0000000000..2bba7754fc --- /dev/null +++ b/fixtures/test/blockfrost/getChainTip/getChainTip-60e93aff53f01835818b98bbf21add13.json @@ -0,0 +1 @@ +{"time":1673370099,"height":321817,"hash":"009e0ed4757e3446cd883bbcf92da14063388ac1456884ec9e0cbda07290d4ec","slot":6714099,"epoch":77,"epoch_slot":61299,"slot_leader":"pool18r62tz408lkgfu6pq5svwzkh2vslkeg6mf72qf3h8njgvzhx9ce","size":4,"tx_count":0,"output":null,"fees":null,"block_vrf":"vrf_vk1jnj37efsp2e2wkjv2wl2kucxtqmrqe32q0r9f5x69n04rgcc5xcqc2mvqv","op_cert":"e167f249c37f4e59a749c4acb81bfc240df74c4936c2e2bf80d058cee6e43567","op_cert_counter":"0","previous_block":"04ba7b74d558fa75bef65d9b6836a28effd7619bd4165e3bad9243e97f5c5a9d","next_block":null,"confirmations":0} \ No newline at end of file diff --git a/fixtures/test/blockfrost/getChainTip/getChainTip-63f282da8288f15a8af50e764ba3c572.json b/fixtures/test/blockfrost/getChainTip/getChainTip-63f282da8288f15a8af50e764ba3c572.json new file mode 100644 index 0000000000..2b1b52c9bf --- /dev/null +++ b/fixtures/test/blockfrost/getChainTip/getChainTip-63f282da8288f15a8af50e764ba3c572.json @@ -0,0 +1 @@ +{"time":1673370058,"height":321814,"hash":"61d37db7faa84d183fc371b537563105e2044d6b3022deffb347cf836d0afedb","slot":6714058,"epoch":77,"epoch_slot":61258,"slot_leader":"pool1z9nsz7wyyxc5r8zf8pf774p9gry09yxtrlqlg5tsnjndv5xupu3","size":13143,"tx_count":10,"output":"5757602367750","fees":"2413084","block_vrf":"vrf_vk1c60q47mgrqmtdggrxmdsrmad07rrw0r6afrndp6yxf0577p4cnwqefxcr7","op_cert":"94cac2653817f60061833a2f9019eaa614df6c4bd605f20951a1aa742b1ccecd","op_cert_counter":"1","previous_block":"28289cb47bb50ce0e70396bb1ab2412a33f3459de58f800cbd6e9470a8491a89","next_block":null,"confirmations":0} \ No newline at end of file diff --git a/fixtures/test/blockfrost/getChainTip/getChainTip-734362d34bcc2cc6ad79b50d71a536c6.json b/fixtures/test/blockfrost/getChainTip/getChainTip-734362d34bcc2cc6ad79b50d71a536c6.json new file mode 100644 index 0000000000..d4323bf76b --- /dev/null +++ b/fixtures/test/blockfrost/getChainTip/getChainTip-734362d34bcc2cc6ad79b50d71a536c6.json @@ -0,0 +1 @@ +{"time":1673370142,"height":321819,"hash":"c6c45ed1305065d03caf279ad085cbea5402a2142c7c59ed19c80f3a4ee3e705","slot":6714142,"epoch":77,"epoch_slot":61342,"slot_leader":"pool18r62tz408lkgfu6pq5svwzkh2vslkeg6mf72qf3h8njgvzhx9ce","size":2398,"tx_count":4,"output":"98815771785","fees":"755328","block_vrf":"vrf_vk1jnj37efsp2e2wkjv2wl2kucxtqmrqe32q0r9f5x69n04rgcc5xcqc2mvqv","op_cert":"e167f249c37f4e59a749c4acb81bfc240df74c4936c2e2bf80d058cee6e43567","op_cert_counter":"0","previous_block":"43d76d40c3c35394e9d10e41fe31bd34d0de42909be14359ec41d910b6549746","next_block":null,"confirmations":0} \ No newline at end of file diff --git a/fixtures/test/blockfrost/getChainTip/getChainTip-8116d571e220ea348bfa84b1dbf3a71b.json b/fixtures/test/blockfrost/getChainTip/getChainTip-8116d571e220ea348bfa84b1dbf3a71b.json new file mode 100644 index 0000000000..c88ef7f6c0 --- /dev/null +++ b/fixtures/test/blockfrost/getChainTip/getChainTip-8116d571e220ea348bfa84b1dbf3a71b.json @@ -0,0 +1 @@ +{"time":1673370180,"height":321823,"hash":"d7f1cc0655ad44304ecc5e59a2326b8453d40470a2dbb7f671ce1371c7272788","slot":6714180,"epoch":77,"epoch_slot":61380,"slot_leader":"pool16h8ugt8k0a4kxa5g6x062zjrgfjc7cehpw0ze8374axlul76932","size":4,"tx_count":0,"output":null,"fees":null,"block_vrf":"vrf_vk1ypg6gmql6nhqpr00dt59ww6lenghkcsyva0frgx2m4hgh3zvfw6stnnhq4","op_cert":"95c62496206f966dde4068df7b97975163b95a0289e567207d735f9388a987de","op_cert_counter":"0","previous_block":"a82841cf494bd270aeed1e2e848c326fd1843a38f510cfabf817c31d35834844","next_block":null,"confirmations":0} \ No newline at end of file diff --git a/fixtures/test/blockfrost/getChainTip/getChainTip-9315383fa4044259c02340bb97d52edb.json b/fixtures/test/blockfrost/getChainTip/getChainTip-9315383fa4044259c02340bb97d52edb.json new file mode 100644 index 0000000000..f24522e56f --- /dev/null +++ b/fixtures/test/blockfrost/getChainTip/getChainTip-9315383fa4044259c02340bb97d52edb.json @@ -0,0 +1 @@ +{"time":1673370232,"height":321824,"hash":"5192baf80a235e548f62a49913a6b47acac48a2c42cc7f7563ec4a4593071ba0","slot":6714232,"epoch":77,"epoch_slot":61432,"slot_leader":"pool18r62tz408lkgfu6pq5svwzkh2vslkeg6mf72qf3h8njgvzhx9ce","size":9289,"tx_count":9,"output":"100617134556","fees":"1999821","block_vrf":"vrf_vk1jnj37efsp2e2wkjv2wl2kucxtqmrqe32q0r9f5x69n04rgcc5xcqc2mvqv","op_cert":"e167f249c37f4e59a749c4acb81bfc240df74c4936c2e2bf80d058cee6e43567","op_cert_counter":"0","previous_block":"d7f1cc0655ad44304ecc5e59a2326b8453d40470a2dbb7f671ce1371c7272788","next_block":null,"confirmations":0} \ No newline at end of file diff --git a/fixtures/test/blockfrost/getChainTip/getChainTip-9ecb4e5de76c205ab67c24ae42982e11.json b/fixtures/test/blockfrost/getChainTip/getChainTip-9ecb4e5de76c205ab67c24ae42982e11.json new file mode 100644 index 0000000000..dceea83ff6 --- /dev/null +++ b/fixtures/test/blockfrost/getChainTip/getChainTip-9ecb4e5de76c205ab67c24ae42982e11.json @@ -0,0 +1 @@ +{"time":1673370169,"height":321822,"hash":"a82841cf494bd270aeed1e2e848c326fd1843a38f510cfabf817c31d35834844","slot":6714169,"epoch":77,"epoch_slot":61369,"slot_leader":"pool1vzqtn3mtfvvuy8ghksy34gs9g97tszj5f8mr3sn7asy5vk577ec","size":4,"tx_count":0,"output":null,"fees":null,"block_vrf":"vrf_vk1p4t8z4gytwwrlskkapvswxfjx6slcgmek6ns8x3yvyvm9jzvxnhsjpaqaw","op_cert":"b8eeb8b1f48be759455dcd33a8139e4f00b079a69bb3970b133b0042344aad88","op_cert_counter":"0","previous_block":"a325d525508f4fe7d4baa484c9064992af59b5eeefaa6217b596652cf5c98b08","next_block":null,"confirmations":0} \ No newline at end of file diff --git a/fixtures/test/blockfrost/getChainTip/getChainTip-ba3998985828253649728656bdc53c6d.json b/fixtures/test/blockfrost/getChainTip/getChainTip-ba3998985828253649728656bdc53c6d.json new file mode 100644 index 0000000000..2e4a4474ce --- /dev/null +++ b/fixtures/test/blockfrost/getChainTip/getChainTip-ba3998985828253649728656bdc53c6d.json @@ -0,0 +1 @@ +{"time":1673370006,"height":321813,"hash":"28289cb47bb50ce0e70396bb1ab2412a33f3459de58f800cbd6e9470a8491a89","slot":6714006,"epoch":77,"epoch_slot":61206,"slot_leader":"pool16h8ugt8k0a4kxa5g6x062zjrgfjc7cehpw0ze8374axlul76932","size":5799,"tx_count":10,"output":"162231061415","fees":"1895338","block_vrf":"vrf_vk1ypg6gmql6nhqpr00dt59ww6lenghkcsyva0frgx2m4hgh3zvfw6stnnhq4","op_cert":"95c62496206f966dde4068df7b97975163b95a0289e567207d735f9388a987de","op_cert_counter":"0","previous_block":"a84b73bd37ee274f6f513cea959168f23e0294313ca44a91783a0d932c2b9421","next_block":null,"confirmations":0} \ No newline at end of file diff --git a/fixtures/test/blockfrost/getChainTip/getChainTip-c454ae6168d84b4cdc9d609f8b26a72f.json b/fixtures/test/blockfrost/getChainTip/getChainTip-c454ae6168d84b4cdc9d609f8b26a72f.json new file mode 100644 index 0000000000..3f71a83111 --- /dev/null +++ b/fixtures/test/blockfrost/getChainTip/getChainTip-c454ae6168d84b4cdc9d609f8b26a72f.json @@ -0,0 +1 @@ +{"time":1673370066,"height":321815,"hash":"63b51cce5431d3fbbb68d2a56489fcd2cc8d635b39b38c4770188bab557844cf","slot":6714066,"epoch":77,"epoch_slot":61266,"slot_leader":"pool18r62tz408lkgfu6pq5svwzkh2vslkeg6mf72qf3h8njgvzhx9ce","size":5676,"tx_count":5,"output":"12592179198700","fees":"1224380","block_vrf":"vrf_vk1jnj37efsp2e2wkjv2wl2kucxtqmrqe32q0r9f5x69n04rgcc5xcqc2mvqv","op_cert":"e167f249c37f4e59a749c4acb81bfc240df74c4936c2e2bf80d058cee6e43567","op_cert_counter":"0","previous_block":"61d37db7faa84d183fc371b537563105e2044d6b3022deffb347cf836d0afedb","next_block":null,"confirmations":0} \ No newline at end of file diff --git a/test/Blockfrost/GenerateFixtures/ChainTip.purs b/test/Blockfrost/GenerateFixtures/ChainTip.purs new file mode 100644 index 0000000000..da9a83ef07 --- /dev/null +++ b/test/Blockfrost/GenerateFixtures/ChainTip.purs @@ -0,0 +1,46 @@ +module Test.Ctl.Blockfrost.GenerateFixtures.ChainTip (main) where + +import Prelude + +import Ctl.Internal.Contract.QueryBackend (BlockfrostBackend) +import Ctl.Internal.Service.Blockfrost + ( BlockfrostEndpoint(LatestBlock) + , BlockfrostRawResponse + , runBlockfrostServiceTestM + ) +import Ctl.Internal.Service.Blockfrost (getChainTip) as Blockfrost +import Ctl.Internal.Types.Chain (Tip) +import Data.Either (hush) +import Data.Maybe (Maybe(Just, Nothing)) +import Effect (Effect) +import Effect.Aff (Aff, Milliseconds(Milliseconds), delay, launchAff_) +import Effect.Class (liftEffect) +import Test.Ctl.Blockfrost.GenerateFixtures.Helpers + ( blockfrostBackend + , storeBlockfrostFixture + ) + +main :: Effect Unit +main = launchAff_ (generateFixtures 10) + +generateFixtures :: Int -> Aff Unit +generateFixtures numFixtures = do + backend <- liftEffect blockfrostBackend + worker backend zero Nothing + where + worker :: BlockfrostBackend -> Int -> Maybe Tip -> Aff Unit + worker _ i _ | i == numFixtures = pure unit + worker backend i prevChainTip = do + chainTip <- runBlockfrostServiceTestM backend (Just onBlockfrostRawResponse) + Nothing + Blockfrost.getChainTip + case prevChainTip == hush chainTip of + true -> delay (Milliseconds 5000.0) *> worker backend i (hush chainTip) + false -> worker backend (i + 1) (hush chainTip) + where + onBlockfrostRawResponse + :: BlockfrostEndpoint -> BlockfrostRawResponse -> Aff Unit + onBlockfrostRawResponse query rawResponse = + case query of + LatestBlock -> storeBlockfrostFixture i "getChainTip" rawResponse + _ -> pure unit diff --git a/test/Blockfrost/GenerateFixtures/Helpers.purs b/test/Blockfrost/GenerateFixtures/Helpers.purs index 9d249a3913..331ec541b6 100644 --- a/test/Blockfrost/GenerateFixtures/Helpers.purs +++ b/test/Blockfrost/GenerateFixtures/Helpers.purs @@ -1,5 +1,6 @@ module Test.Ctl.Blockfrost.GenerateFixtures.Helpers - ( contractParams + ( blockfrostBackend + , contractParams , lookupEnv' , md5 , storeBlockfrostFixture @@ -14,20 +15,30 @@ import Contract.Config , blockfrostPublicPreviewServerConfig , testnetConfig ) -import Ctl.Internal.Contract.QueryBackend (mkBlockfrostBackendParams) +import Ctl.Internal.Contract.QueryBackend + ( BlockfrostBackend + , mkBlockfrostBackendParams + ) import Data.Maybe (Maybe(Just, Nothing), maybe) import Effect.Exception (throw) import Node.Encoding (Encoding(UTF8)) -import Node.FS.Aff (writeTextFile) +import Node.FS.Aff (exists, writeTextFile) import Node.Path (concat) import Node.Process (lookupEnv) foreign import md5 :: String -> String +blockfrostBackend :: Effect BlockfrostBackend +blockfrostBackend = + getBlockfrostApiKeyFromEnv <#> \blockfrostApiKey -> + { blockfrostConfig: blockfrostPublicPreviewServerConfig + , blockfrostApiKey: Just blockfrostApiKey + } + contractParams :: Effect ContractParams contractParams = do - blockfrostApiKey <- lookupEnv' "BLOCKFROST_API_KEY" - skeyFilepath <- lookupEnv' "SKEY_FILEPATH" + blockfrostApiKey <- getBlockfrostApiKeyFromEnv + skeyFilepath <- getSkeyFilepathFromEnv pure $ testnetConfig { backendParams = mkBlockfrostBackendParams @@ -38,6 +49,12 @@ contractParams = do , walletSpec = Just $ UseKeys (PrivatePaymentKeyFile skeyFilepath) Nothing } +getBlockfrostApiKeyFromEnv :: Effect String +getBlockfrostApiKeyFromEnv = lookupEnv' "BLOCKFROST_API_KEY" + +getSkeyFilepathFromEnv :: Effect String +getSkeyFilepathFromEnv = lookupEnv' "SKEY_FILEPATH" + lookupEnv' :: String -> Effect String lookupEnv' var = lookupEnv var >>= @@ -50,5 +67,7 @@ storeBlockfrostFixture i query resp = filename = query <> "-" <> respHash <> ".json" fp = concat [ "fixtures", "test", "blockfrost", query, filename ] in - writeTextFile UTF8 fp resp - *> log ("Successfully saved fixture #" <> show i <> " to: " <> fp) + exists fp >>= flip unless + ( writeTextFile UTF8 fp resp + *> log ("Successfully saved fixture #" <> show i <> " to: " <> fp) + ) From 7faad6eb0af934f3ecfbb51a88f4eb4dbd6dfbe8 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Tue, 10 Jan 2023 18:14:30 +0100 Subject: [PATCH 255/373] Apply suggestions --- src/Internal/Service/Blockfrost.purs | 29 +++++++--------- test/Blockfrost/GenerateFixtures/Helpers.purs | 33 +++++++++++++++---- 2 files changed, 38 insertions(+), 24 deletions(-) diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index a2aade6594..3f38ae92d2 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -65,7 +65,7 @@ import Data.Maybe (Maybe(Nothing), maybe) import Data.MediaType (MediaType) import Data.Newtype (class Newtype, unwrap, wrap) import Data.Show.Generic (genericShow) -import Data.Traversable (for) +import Data.Traversable (for, for_) import Effect.Aff (Aff) import Effect.Aff.Class (liftAff) import Undefined (undefined) @@ -186,14 +186,11 @@ withOnRawGetResponseHook :: BlockfrostEndpoint -> Either Affjax.Error (Affjax.Response String) -> BlockfrostServiceM (Either Affjax.Error (Affjax.Response String)) -withOnRawGetResponseHook endpoint result = - case result of - Right { body: rawResponse } -> do - onRawGetResponse <- asks _.onBlockfrostRawGetResponse - maybe (pure unit) (\f -> liftAff $ f endpoint rawResponse) - onRawGetResponse - pure result - _ -> pure result +withOnRawGetResponseHook endpoint result = do + for_ result \{ body: rawResponse } -> do + onRawGetResponse <- asks _.onBlockfrostRawGetResponse + maybe (pure unit) (\f -> liftAff $ f endpoint rawResponse) onRawGetResponse + pure result withOnRawPostResponseHook :: BlockfrostEndpoint @@ -201,14 +198,12 @@ withOnRawPostResponseHook -> Maybe Affjax.RequestBody -> Either Affjax.Error (Affjax.Response String) -> BlockfrostServiceM (Either Affjax.Error (Affjax.Response String)) -withOnRawPostResponseHook endpoint mediaType requestBody result = - case result of - Right { body: rawResponse } -> do - let data_ = { endpoint, mediaType, requestBody, rawResponse } - onRawPostResponse <- asks _.onBlockfrostRawPostResponse - maybe (pure unit) (\f -> liftAff $ f data_) onRawPostResponse - pure result - _ -> pure result +withOnRawPostResponseHook endpoint mediaType requestBody result = do + for_ result \{ body: rawResponse } -> do + let data_ = { endpoint, mediaType, requestBody, rawResponse } + onRawPostResponse <- asks _.onBlockfrostRawPostResponse + maybe (pure unit) (\f -> liftAff $ f data_) onRawPostResponse + pure result -------------------------------------------------------------------------------- -- Blockfrost response handling diff --git a/test/Blockfrost/GenerateFixtures/Helpers.purs b/test/Blockfrost/GenerateFixtures/Helpers.purs index 9d249a3913..331ec541b6 100644 --- a/test/Blockfrost/GenerateFixtures/Helpers.purs +++ b/test/Blockfrost/GenerateFixtures/Helpers.purs @@ -1,5 +1,6 @@ module Test.Ctl.Blockfrost.GenerateFixtures.Helpers - ( contractParams + ( blockfrostBackend + , contractParams , lookupEnv' , md5 , storeBlockfrostFixture @@ -14,20 +15,30 @@ import Contract.Config , blockfrostPublicPreviewServerConfig , testnetConfig ) -import Ctl.Internal.Contract.QueryBackend (mkBlockfrostBackendParams) +import Ctl.Internal.Contract.QueryBackend + ( BlockfrostBackend + , mkBlockfrostBackendParams + ) import Data.Maybe (Maybe(Just, Nothing), maybe) import Effect.Exception (throw) import Node.Encoding (Encoding(UTF8)) -import Node.FS.Aff (writeTextFile) +import Node.FS.Aff (exists, writeTextFile) import Node.Path (concat) import Node.Process (lookupEnv) foreign import md5 :: String -> String +blockfrostBackend :: Effect BlockfrostBackend +blockfrostBackend = + getBlockfrostApiKeyFromEnv <#> \blockfrostApiKey -> + { blockfrostConfig: blockfrostPublicPreviewServerConfig + , blockfrostApiKey: Just blockfrostApiKey + } + contractParams :: Effect ContractParams contractParams = do - blockfrostApiKey <- lookupEnv' "BLOCKFROST_API_KEY" - skeyFilepath <- lookupEnv' "SKEY_FILEPATH" + blockfrostApiKey <- getBlockfrostApiKeyFromEnv + skeyFilepath <- getSkeyFilepathFromEnv pure $ testnetConfig { backendParams = mkBlockfrostBackendParams @@ -38,6 +49,12 @@ contractParams = do , walletSpec = Just $ UseKeys (PrivatePaymentKeyFile skeyFilepath) Nothing } +getBlockfrostApiKeyFromEnv :: Effect String +getBlockfrostApiKeyFromEnv = lookupEnv' "BLOCKFROST_API_KEY" + +getSkeyFilepathFromEnv :: Effect String +getSkeyFilepathFromEnv = lookupEnv' "SKEY_FILEPATH" + lookupEnv' :: String -> Effect String lookupEnv' var = lookupEnv var >>= @@ -50,5 +67,7 @@ storeBlockfrostFixture i query resp = filename = query <> "-" <> respHash <> ".json" fp = concat [ "fixtures", "test", "blockfrost", query, filename ] in - writeTextFile UTF8 fp resp - *> log ("Successfully saved fixture #" <> show i <> " to: " <> fp) + exists fp >>= flip unless + ( writeTextFile UTF8 fp resp + *> log ("Successfully saved fixture #" <> show i <> " to: " <> fp) + ) From 298d9d3993ae19c113f084d8ffd632727de625dc Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Tue, 10 Jan 2023 18:36:54 +0100 Subject: [PATCH 256/373] Generate fixtures for getSystemStart --- ...tart-52e5fecf2225bf4839a71a73f96c583a.json | 1 + ...tart-bd41dbe8d0db71c203c1a1a4355ba4fe.json | 1 + ...tart-e284e15119df00de6ef36e817e417277.json | 1 + .../GenerateFixtures/SystemStart.purs | 39 +++++++++++++++++++ 4 files changed, 42 insertions(+) create mode 100644 fixtures/test/blockfrost/getSystemStart/getSystemStart-52e5fecf2225bf4839a71a73f96c583a.json create mode 100644 fixtures/test/blockfrost/getSystemStart/getSystemStart-bd41dbe8d0db71c203c1a1a4355ba4fe.json create mode 100644 fixtures/test/blockfrost/getSystemStart/getSystemStart-e284e15119df00de6ef36e817e417277.json create mode 100644 test/Blockfrost/GenerateFixtures/SystemStart.purs diff --git a/fixtures/test/blockfrost/getSystemStart/getSystemStart-52e5fecf2225bf4839a71a73f96c583a.json b/fixtures/test/blockfrost/getSystemStart/getSystemStart-52e5fecf2225bf4839a71a73f96c583a.json new file mode 100644 index 0000000000..5471635a1a --- /dev/null +++ b/fixtures/test/blockfrost/getSystemStart/getSystemStart-52e5fecf2225bf4839a71a73f96c583a.json @@ -0,0 +1 @@ +{"active_slots_coefficient":0.05,"update_quorum":5,"max_lovelace_supply":"45000000000000000","network_magic":764824073,"epoch_length":432000,"system_start":1506203091,"slots_per_kes_period":129600,"slot_length":1,"max_kes_evolutions":62,"security_param":2160} \ No newline at end of file diff --git a/fixtures/test/blockfrost/getSystemStart/getSystemStart-bd41dbe8d0db71c203c1a1a4355ba4fe.json b/fixtures/test/blockfrost/getSystemStart/getSystemStart-bd41dbe8d0db71c203c1a1a4355ba4fe.json new file mode 100644 index 0000000000..c81cf7e6a3 --- /dev/null +++ b/fixtures/test/blockfrost/getSystemStart/getSystemStart-bd41dbe8d0db71c203c1a1a4355ba4fe.json @@ -0,0 +1 @@ +{"active_slots_coefficient":0.05,"update_quorum":5,"max_lovelace_supply":"45000000000000000","network_magic":2,"epoch_length":86400,"system_start":1666656000,"slots_per_kes_period":129600,"slot_length":1,"max_kes_evolutions":62,"security_param":432} \ No newline at end of file diff --git a/fixtures/test/blockfrost/getSystemStart/getSystemStart-e284e15119df00de6ef36e817e417277.json b/fixtures/test/blockfrost/getSystemStart/getSystemStart-e284e15119df00de6ef36e817e417277.json new file mode 100644 index 0000000000..6fa849fe52 --- /dev/null +++ b/fixtures/test/blockfrost/getSystemStart/getSystemStart-e284e15119df00de6ef36e817e417277.json @@ -0,0 +1 @@ +{"active_slots_coefficient":0.05,"update_quorum":5,"max_lovelace_supply":"45000000000000000","network_magic":1,"epoch_length":432000,"system_start":1654041600,"slots_per_kes_period":129600,"slot_length":1,"max_kes_evolutions":62,"security_param":2160} \ No newline at end of file diff --git a/test/Blockfrost/GenerateFixtures/SystemStart.purs b/test/Blockfrost/GenerateFixtures/SystemStart.purs new file mode 100644 index 0000000000..5dbfe02ede --- /dev/null +++ b/test/Blockfrost/GenerateFixtures/SystemStart.purs @@ -0,0 +1,39 @@ +module Test.Ctl.Blockfrost.GenerateFixtures.SystemStart (main) where + +import Prelude + +import Ctl.Internal.Service.Blockfrost + ( BlockfrostEndpoint(BlockchainGenesis) + , BlockfrostRawResponse + , runBlockfrostServiceTestM + ) +import Ctl.Internal.Service.Blockfrost (getSystemStart) as Blockfrost +import Data.Either (either) +import Data.Maybe (Maybe(Just, Nothing)) +import Effect (Effect) +import Effect.Aff (Aff, launchAff_) +import Effect.Class (liftEffect) +import Effect.Exception (throw) +import Test.Ctl.Blockfrost.GenerateFixtures.Helpers + ( blockfrostBackend + , storeBlockfrostFixture + ) + +main :: Effect Unit +main = launchAff_ generateFixture + +generateFixture :: Aff Unit +generateFixture = do + backend <- liftEffect blockfrostBackend + sysStart <- runBlockfrostServiceTestM backend (Just onBlockfrostRawResponse) + Nothing + Blockfrost.getSystemStart + either (liftEffect <<< throw <<< show) (\_ -> pure unit) sysStart + where + onBlockfrostRawResponse + :: BlockfrostEndpoint -> BlockfrostRawResponse -> Aff Unit + onBlockfrostRawResponse query rawResponse = + case query of + BlockchainGenesis -> + storeBlockfrostFixture zero "getSystemStart" rawResponse + _ -> pure unit From bd02818932b568b0f71d82889b07be14c41987b8 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Tue, 10 Jan 2023 18:51:35 +0100 Subject: [PATCH 257/373] Derive ServerConfig from Blockfrost project_id --- test/Blockfrost/GenerateFixtures/Helpers.purs | 29 ++++++++++++++++--- 1 file changed, 25 insertions(+), 4 deletions(-) diff --git a/test/Blockfrost/GenerateFixtures/Helpers.purs b/test/Blockfrost/GenerateFixtures/Helpers.purs index 331ec541b6..4ab9a2f158 100644 --- a/test/Blockfrost/GenerateFixtures/Helpers.purs +++ b/test/Blockfrost/GenerateFixtures/Helpers.purs @@ -11,7 +11,10 @@ import Contract.Prelude import Contract.Config ( ContractParams , PrivatePaymentKeySource(PrivatePaymentKeyFile) + , ServerConfig , WalletSpec(UseKeys) + , blockfrostPublicMainnetServerConfig + , blockfrostPublicPreprodServerConfig , blockfrostPublicPreviewServerConfig , testnetConfig ) @@ -20,6 +23,7 @@ import Ctl.Internal.Contract.QueryBackend , mkBlockfrostBackendParams ) import Data.Maybe (Maybe(Just, Nothing), maybe) +import Data.String (take) as String import Effect.Exception (throw) import Node.Encoding (Encoding(UTF8)) import Node.FS.Aff (exists, writeTextFile) @@ -29,9 +33,11 @@ import Node.Process (lookupEnv) foreign import md5 :: String -> String blockfrostBackend :: Effect BlockfrostBackend -blockfrostBackend = - getBlockfrostApiKeyFromEnv <#> \blockfrostApiKey -> - { blockfrostConfig: blockfrostPublicPreviewServerConfig +blockfrostBackend = do + blockfrostApiKey <- getBlockfrostApiKeyFromEnv + blockfrostConfig <- blockfrostConfigFromApiKey blockfrostApiKey + pure + { blockfrostConfig , blockfrostApiKey: Just blockfrostApiKey } @@ -39,16 +45,31 @@ contractParams :: Effect ContractParams contractParams = do blockfrostApiKey <- getBlockfrostApiKeyFromEnv skeyFilepath <- getSkeyFilepathFromEnv + blockfrostConfig <- blockfrostConfigFromApiKey blockfrostApiKey pure $ testnetConfig { backendParams = mkBlockfrostBackendParams - { blockfrostConfig: blockfrostPublicPreviewServerConfig + { blockfrostConfig , blockfrostApiKey: Just blockfrostApiKey } , logLevel = Info , walletSpec = Just $ UseKeys (PrivatePaymentKeyFile skeyFilepath) Nothing } +blockfrostConfigFromApiKey :: String -> Effect ServerConfig +blockfrostConfigFromApiKey = String.take networkPrefixLength >>> case _ of + "mainnet" -> + pure blockfrostPublicMainnetServerConfig + "preview" -> + pure blockfrostPublicPreviewServerConfig + "preprod" -> + pure blockfrostPublicPreprodServerConfig + _ -> + throw "Failed to derive server config from Blockfrost API key" + where + networkPrefixLength :: Int + networkPrefixLength = 7 + getBlockfrostApiKeyFromEnv :: Effect String getBlockfrostApiKeyFromEnv = lookupEnv' "BLOCKFROST_API_KEY" From 1d4d8efb9131c7d4df19745ecc66385533fde862 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Tue, 10 Jan 2023 19:17:52 +0100 Subject: [PATCH 258/373] Generate fixtures for getEraSummaries --- ...ries-20683e5d71f49fe48e1cc32dded9b62f.json | 1 + ...ries-6cb6a84f8e965a4a57ced00a6e074e60.json | 1 + .../GenerateFixtures/EraSummaries.purs | 40 +++++++++++++++++++ 3 files changed, 42 insertions(+) create mode 100644 fixtures/test/blockfrost/getEraSummaries/getEraSummaries-20683e5d71f49fe48e1cc32dded9b62f.json create mode 100644 fixtures/test/blockfrost/getEraSummaries/getEraSummaries-6cb6a84f8e965a4a57ced00a6e074e60.json create mode 100644 test/Blockfrost/GenerateFixtures/EraSummaries.purs diff --git a/fixtures/test/blockfrost/getEraSummaries/getEraSummaries-20683e5d71f49fe48e1cc32dded9b62f.json b/fixtures/test/blockfrost/getEraSummaries/getEraSummaries-20683e5d71f49fe48e1cc32dded9b62f.json new file mode 100644 index 0000000000..a556d7bd64 --- /dev/null +++ b/fixtures/test/blockfrost/getEraSummaries/getEraSummaries-20683e5d71f49fe48e1cc32dded9b62f.json @@ -0,0 +1 @@ +[{"start":{"time":0,"slot":0,"epoch":0},"end":{"time":1728000,"slot":86400,"epoch":4},"parameters":{"epoch_length":21600,"slot_length":20,"safe_zone":4320}},{"start":{"time":1728000,"slot":86400,"epoch":4},"end":{"time":2160000,"slot":518400,"epoch":5},"parameters":{"epoch_length":432000,"slot_length":1,"safe_zone":129600}},{"start":{"time":2160000,"slot":518400,"epoch":5},"end":{"time":2592000,"slot":950400,"epoch":6},"parameters":{"epoch_length":432000,"slot_length":1,"safe_zone":129600}},{"start":{"time":2592000,"slot":950400,"epoch":6},"end":{"time":3024000,"slot":1382400,"epoch":7},"parameters":{"epoch_length":432000,"slot_length":1,"safe_zone":129600}},{"start":{"time":3024000,"slot":1382400,"epoch":7},"end":{"time":5184000,"slot":3542400,"epoch":12},"parameters":{"epoch_length":432000,"slot_length":1,"safe_zone":129600}},{"start":{"time":5184000,"slot":3542400,"epoch":12},"end":{"time":19872000,"slot":18230400,"epoch":46},"parameters":{"epoch_length":432000,"slot_length":1,"safe_zone":129600}}] \ No newline at end of file diff --git a/fixtures/test/blockfrost/getEraSummaries/getEraSummaries-6cb6a84f8e965a4a57ced00a6e074e60.json b/fixtures/test/blockfrost/getEraSummaries/getEraSummaries-6cb6a84f8e965a4a57ced00a6e074e60.json new file mode 100644 index 0000000000..d05dbed559 --- /dev/null +++ b/fixtures/test/blockfrost/getEraSummaries/getEraSummaries-6cb6a84f8e965a4a57ced00a6e074e60.json @@ -0,0 +1 @@ +[{"start":{"time":0,"slot":0,"epoch":0},"end":{"time":0,"slot":0,"epoch":0},"parameters":{"epoch_length":4320,"slot_length":20,"safe_zone":864}},{"start":{"time":0,"slot":0,"epoch":0},"end":{"time":0,"slot":0,"epoch":0},"parameters":{"epoch_length":86400,"slot_length":1,"safe_zone":25920}},{"start":{"time":0,"slot":0,"epoch":0},"end":{"time":0,"slot":0,"epoch":0},"parameters":{"epoch_length":86400,"slot_length":1,"safe_zone":25920}},{"start":{"time":0,"slot":0,"epoch":0},"end":{"time":0,"slot":0,"epoch":0},"parameters":{"epoch_length":86400,"slot_length":1,"safe_zone":25920}},{"start":{"time":0,"slot":0,"epoch":0},"end":{"time":259200,"slot":259200,"epoch":3},"parameters":{"epoch_length":86400,"slot_length":1,"safe_zone":25920}},{"start":{"time":259200,"slot":259200,"epoch":3},"end":{"time":6825600,"slot":6825600,"epoch":79},"parameters":{"epoch_length":86400,"slot_length":1,"safe_zone":25920}}] \ No newline at end of file diff --git a/test/Blockfrost/GenerateFixtures/EraSummaries.purs b/test/Blockfrost/GenerateFixtures/EraSummaries.purs new file mode 100644 index 0000000000..8f6597938e --- /dev/null +++ b/test/Blockfrost/GenerateFixtures/EraSummaries.purs @@ -0,0 +1,40 @@ +module Test.Ctl.Blockfrost.GenerateFixtures.EraSummaries (main) where + +import Prelude + +import Ctl.Internal.Service.Blockfrost + ( BlockfrostEndpoint(EraSummaries) + , BlockfrostRawResponse + , runBlockfrostServiceTestM + ) +import Ctl.Internal.Service.Blockfrost (getEraSummaries) as Blockfrost +import Data.Either (either) +import Data.Maybe (Maybe(Just, Nothing)) +import Effect (Effect) +import Effect.Aff (Aff, launchAff_) +import Effect.Class (liftEffect) +import Effect.Exception (throw) +import Test.Ctl.Blockfrost.GenerateFixtures.Helpers + ( blockfrostBackend + , storeBlockfrostFixture + ) + +main :: Effect Unit +main = launchAff_ generateFixture + +generateFixture :: Aff Unit +generateFixture = do + backend <- liftEffect blockfrostBackend + eraSummaries <- runBlockfrostServiceTestM backend + (Just onBlockfrostRawResponse) + Nothing + Blockfrost.getEraSummaries + either (liftEffect <<< throw <<< show) (\_ -> pure unit) eraSummaries + where + onBlockfrostRawResponse + :: BlockfrostEndpoint -> BlockfrostRawResponse -> Aff Unit + onBlockfrostRawResponse query rawResponse = + case query of + EraSummaries -> + storeBlockfrostFixture zero "getEraSummaries" rawResponse + _ -> pure unit From 07e3c3e5c90ec04fbf053b97d3e19fee5ce3e21b Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Tue, 10 Jan 2023 19:57:28 +0000 Subject: [PATCH 259/373] Add a way to run existing plutip tests via ContractParams, add a util to drain wallets in a folder. --- src/Contract/Config.purs | 15 ++- src/Contract/Test/Plutip.purs | 1 + src/Internal/Deserialization/Keys.js | 4 + src/Internal/Deserialization/Keys.purs | 5 + src/Internal/Plutip/Server.purs | 165 ++++++++++++++++++++++++- test/Blockfrost/Contract.purs | 58 +++++++++ test/Plutip.purs | 13 +- test/Plutip/Contract.purs | 52 ++++---- test/Utils/DrainWallets.purs | 127 +++++++++++++++++++ 9 files changed, 396 insertions(+), 44 deletions(-) create mode 100644 test/Blockfrost/Contract.purs create mode 100644 test/Utils/DrainWallets.purs diff --git a/src/Contract/Config.purs b/src/Contract/Config.purs index 70e0747c2d..a37a1127f9 100644 --- a/src/Contract/Config.purs +++ b/src/Contract/Config.purs @@ -32,10 +32,8 @@ import Ctl.Internal.Contract.Hooks (Hooks, emptyHooks) as X import Ctl.Internal.Contract.Hooks (emptyHooks) import Ctl.Internal.Contract.Monad (ContractParams) import Ctl.Internal.Contract.QueryBackend - ( -- TODO Export Blockfrost once the following is stable - -- https://github.com/Plutonomicon/cardano-transaction-lib/issues/1118 - -- , mkBlockfrostBackendParams - QueryBackendParams(CtlBackendParams, BlockfrostBackendParams) + ( QueryBackendParams(CtlBackendParams, BlockfrostBackendParams) + , mkBlockfrostBackendParams , mkCtlBackendParams ) import Ctl.Internal.Deserialization.Keys (privateKeyFromBytes) @@ -68,6 +66,7 @@ import Ctl.Internal.Wallet.Spec import Data.Log.Level (LogLevel(Trace, Debug, Info, Warn, Error)) import Data.Log.Message (Message) import Data.Maybe (Maybe(Just, Nothing)) +import Data.UInt as UInt testnetConfig :: ContractParams testnetConfig = @@ -84,6 +83,7 @@ testnetConfig = } -- | Blockfrost public preview with CTL as backup +-- | Does not use the Kupo webpack proxy testnetBlockfrostDevConfig :: Maybe String -> ContractParams testnetBlockfrostDevConfig mbApiKey = { backendParams: BlockfrostBackendParams @@ -92,7 +92,12 @@ testnetBlockfrostDevConfig mbApiKey = } ( Just { ogmiosConfig: defaultOgmiosWsConfig - , kupoConfig: defaultKupoServerConfig + , kupoConfig: + { port: UInt.fromInt 1442 + , host: "localhost" + , secure: false + , path: Nothing + } } ) , networkId: TestnetId diff --git a/src/Contract/Test/Plutip.purs b/src/Contract/Test/Plutip.purs index beb0b21f9e..9746bc6eff 100644 --- a/src/Contract/Test/Plutip.purs +++ b/src/Contract/Test/Plutip.purs @@ -13,6 +13,7 @@ import Ctl.Internal.Plutip.Server ( PlutipTest , noWallet , runPlutipContract + , testContractsInEnv , withPlutipContractEnv , withWallets ) as X diff --git a/src/Internal/Deserialization/Keys.js b/src/Internal/Deserialization/Keys.js index 57dbb6d55b..4ba1d1d359 100644 --- a/src/Internal/Deserialization/Keys.js +++ b/src/Internal/Deserialization/Keys.js @@ -7,6 +7,10 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } +exports.freshPrivateKey = () => { + return lib.PrivateKey.generate_ed25519(); +}; + exports._publicKeyFromBech32 = maybe => bech32 => { try { return maybe.just(lib.PublicKey.from_bech32(bech32)); diff --git a/src/Internal/Deserialization/Keys.purs b/src/Internal/Deserialization/Keys.purs index d10b0c7ba8..0bd74b990b 100644 --- a/src/Internal/Deserialization/Keys.purs +++ b/src/Internal/Deserialization/Keys.purs @@ -4,6 +4,7 @@ module Ctl.Internal.Deserialization.Keys , ed25519SignatureFromBech32 , privateKeyToBech32 , privateKeyFromBech32 + , freshPrivateKey ) where import Ctl.Internal.FfiHelpers (MaybeFfiHelper, maybeFfiHelper) @@ -15,6 +16,7 @@ import Ctl.Internal.Serialization.Types import Ctl.Internal.Types.Aliases (Bech32String) import Ctl.Internal.Types.RawBytes (RawBytes) import Data.Maybe (Maybe) +import Effect (Effect) publicKeyFromBech32 :: Bech32String -> Maybe PublicKey publicKeyFromBech32 = _publicKeyFromBech32 maybeFfiHelper @@ -28,6 +30,9 @@ ed25519SignatureFromBech32 = _ed25519SignatureFromBech32 maybeFfiHelper privateKeyFromBech32 :: Bech32String -> Maybe PrivateKey privateKeyFromBech32 = _privateKeyFromBech32 maybeFfiHelper +foreign import freshPrivateKey + :: Effect PrivateKey + foreign import _ed25519SignatureFromBech32 :: MaybeFfiHelper -> Bech32String -> Maybe Ed25519Signature diff --git a/src/Internal/Plutip/Server.purs b/src/Internal/Plutip/Server.purs index c4e113d6d8..e590e9f6eb 100644 --- a/src/Internal/Plutip/Server.purs +++ b/src/Internal/Plutip/Server.purs @@ -9,6 +9,7 @@ module Ctl.Internal.Plutip.Server , testPlutipContracts , withWallets , noWallet + , testContractsInEnv , PlutipTest ) where @@ -19,9 +20,37 @@ import Affjax as Affjax import Affjax.RequestBody as RequestBody import Affjax.RequestHeader as Header import Affjax.ResponseFormat as Affjax.ResponseFormat -import Contract.Address (NetworkId(MainnetId)) -import Contract.Monad (Contract, ContractEnv, liftContractM, runContractInEnv) -import Control.Monad.Error.Class (liftEither) +import Contract.Address + ( NetworkId(MainnetId) + , getWalletAddresses + , ownPaymentPubKeysHashes + ) +import Contract.Config (ContractParams) +import Contract.Hashing (publicKeyHash) +import Contract.Monad + ( Contract + , ContractEnv + , liftContractM + , liftedE + , runContractInEnv + , withContractEnv + ) +import Contract.Transaction + ( awaitTxConfirmed + , balanceTx + , signTransaction + , submit + , submitTxFromConstraints + ) +import Contract.Utxos (utxosAt) +import Contract.Wallet (withKeyWallet) +import Contract.Wallet.Key + ( keyWalletPrivatePaymentKey + , keyWalletPrivateStakeKey + , publicKeyFromPrivateKey + ) +import Contract.Wallet.KeyFile (privatePaymentKeyToFile, privateStakeKeyToFile) +import Control.Monad.Error.Class (liftEither, liftMaybe) import Control.Monad.State (State, execState, modify_) import Control.Monad.Trans.Class (lift) import Control.Monad.Writer (censor, execWriterT, tell) @@ -32,6 +61,7 @@ import Ctl.Internal.Contract.Monad , stopContractEnv ) import Ctl.Internal.Contract.QueryBackend (mkCtlBackendParams) +import Ctl.Internal.Deserialization.Keys (freshPrivateKey) import Ctl.Internal.Helpers ((<>)) import Ctl.Internal.Logging (Logger, mkLogger, setupLogs) import Ctl.Internal.Plutip.PortCheck (isPortAvailable) @@ -55,6 +85,7 @@ import Ctl.Internal.Plutip.Types , StartClusterResponse(ClusterStartupSuccess, ClusterStartupFailure) , StopClusterRequest(StopClusterRequest) , StopClusterResponse + , UtxoAmount ) import Ctl.Internal.Plutip.Utils (tmpdir) import Ctl.Internal.Plutip.UtxoDistribution @@ -64,25 +95,37 @@ import Ctl.Internal.Plutip.UtxoDistribution , keyWallets , transferFundsFromEnterpriseToBase ) +import Ctl.Internal.Plutus.Types.Value (Value, lovelaceValueOf) +import Ctl.Internal.Serialization.Address (addressBech32) import Ctl.Internal.Service.Error ( ClientError(ClientDecodeJsonError, ClientHttpError) ) import Ctl.Internal.Test.TestPlanM (TestPlanM) +import Ctl.Internal.Types.ScriptLookups (mkUnbalancedTx, unspentOutputs) +import Ctl.Internal.Types.TxConstraints + ( TxConstraints + , mustBeSignedBy + , mustPayToPubKey + , mustPayToPubKeyAddress + , mustSpendPubKeyOutput + ) import Ctl.Internal.Types.UsedTxOuts (newUsedTxOuts) +import Ctl.Internal.Wallet (KeyWallet) import Ctl.Internal.Wallet.Key (PrivatePaymentKey(PrivatePaymentKey)) import Data.Array as Array import Data.Bifunctor (lmap) import Data.BigInt as BigInt import Data.Either (Either(Left), either, isLeft) -import Data.Foldable (sum) +import Data.Foldable (fold, sum) import Data.HTTP.Method as Method import Data.Log.Level (LogLevel) import Data.Log.Message (Message) +import Data.Map as Map import Data.Maybe (Maybe(Just, Nothing), maybe) -import Data.Newtype (over, wrap) +import Data.Newtype (over, unwrap, wrap) import Data.String.CodeUnits as String import Data.String.Pattern (Pattern(Pattern)) -import Data.Traversable (foldMap, for, for_, sequence_, traverse_) +import Data.Traversable (foldMap, for, for_, sequence_, traverse, traverse_) import Data.Tuple (fst, snd) import Data.Tuple.Nested (type (/\), (/\)) import Data.UInt (UInt) @@ -104,8 +147,10 @@ import Mote (bracket) as Mote import Mote.Description (Description(Group, Test)) import Mote.Monad (MoteT(MoteT), mapTest) import Node.ChildProcess (defaultSpawnOptions) +import Node.FS.Aff (mkdir) import Node.FS.Sync (exists, mkdir) as FSSync import Node.Path (FilePath, dirname) +import Node.Path (concat) as Path import Type.Prelude (Proxy(Proxy)) -- | Run a single `Contract` in Plutip environment. @@ -137,6 +182,114 @@ withPlutipContractEnv plutipCfg distr cont = do $ liftEither >=> \{ env, wallets, printLogs } -> whenError printLogs (cont env wallets) +-- | Run `PlutipTest`s with an existing `ContractEnv`, not necessarily one +-- | created through `Plutip`. +-- | Tests are funded by the wallet in the supplied environment. +-- | The `FilePath` parameter should point to a directory to store generated +-- | wallets, in the case where funds failed to be returned to the main wallet. +testContractsInEnv + :: ContractParams + -> FilePath + -> TestPlanM PlutipTest Unit + -> TestPlanM (Aff Unit) Unit +testContractsInEnv params backup = mapTest \(PlutipTest runPlutipTest) -> + runPlutipTest \distr mkTest -> withContractEnv params \env -> do + let + distrArray :: Array (Array UtxoAmount) + distrArray = encodeDistribution distr + + privateKeys <- liftEffect $ for distrArray \_ -> freshPrivateKey <#> + PrivateKeyResponse + + wallets <- + liftMaybe + ( error + "Impossible happened: could not decode wallets. Please report as bug" + ) + $ decodeWallets distr privateKeys + + let + walletsArray :: Array KeyWallet + walletsArray = keyWallets (pureProxy distr) wallets + + runContract :: Aff Unit + runContract = runContractInEnv env { wallet = Nothing } $ mkTest wallets + + if Array.null walletsArray then + runContract + else Aff.bracket + ( backupWallets env walletsArray *> fundWallets env walletsArray + distrArray + ) + (\_ -> returnFunds env walletsArray) + \_ -> runContract + where + pureProxy :: forall (a :: Type). a -> Proxy a + pureProxy _ = Proxy + + backupWallets :: ContractEnv -> Array KeyWallet -> Aff Unit + backupWallets env walletsArray = liftAff $ for_ walletsArray \wallet -> do + let + address = addressBech32 $ (unwrap wallet).address env.networkId + payment = keyWalletPrivatePaymentKey wallet + mbStake = keyWalletPrivateStakeKey wallet + folder = Path.concat [ backup, address ] + + mkdir folder + privatePaymentKeyToFile (Path.concat [ folder, "payment_signing_key" ]) + payment + for mbStake $ privateStakeKeyToFile + (Path.concat [ folder, "stake_signing_key" ]) + + fundWallets + :: ContractEnv -> Array KeyWallet -> Array (Array UtxoAmount) -> Aff Unit + fundWallets env walletsArray distrArray = runContractInEnv env do + let + constraints = flip foldMap (Array.zip walletsArray distrArray) + \(wallet /\ walletDistr) -> flip foldMap walletDistr + \value -> mustPayToKeyWallet wallet $ lovelaceValueOf value + + txHash <- submitTxFromConstraints (mempty :: _ Void) constraints + awaitTxConfirmed txHash + + returnFunds :: ContractEnv -> Array KeyWallet -> Aff Unit + returnFunds env walletsArray = runContractInEnv env do + utxos <- Map.unions <<< fold <$> for walletsArray + (flip withKeyWallet getWalletAddresses >=> traverse utxosAt) + pkhs <- fold <$> for walletsArray + (flip withKeyWallet ownPaymentPubKeysHashes) + + let + constraints = flip foldMap (Map.keys utxos) mustSpendPubKeyOutput + <> foldMap mustBeSignedBy pkhs + lookups = unspentOutputs utxos + + unbalancedTx <- liftedE $ mkUnbalancedTx (lookups :: _ Void) constraints + balancedTx <- liftedE $ balanceTx unbalancedTx + balancedSignedTx <- Array.foldM + (\tx wallet -> withKeyWallet wallet $ signTransaction tx) + (wrap $ unwrap balancedTx) + walletsArray + txHash <- submit balancedSignedTx + awaitTxConfirmed txHash + + mustPayToKeyWallet + :: forall (i :: Type) (o :: Type) + . KeyWallet + -> Value + -> TxConstraints i o + mustPayToKeyWallet wallet value = + let + convert = wrap <<< publicKeyHash <<< publicKeyFromPrivateKey + payment = over wrap convert $ keyWalletPrivatePaymentKey wallet + mbStake = over wrap convert <$> keyWalletPrivateStakeKey wallet + in + maybe + (mustPayToPubKey payment) + (mustPayToPubKeyAddress payment) + mbStake + value + -- | Run `Contract`s in tests in a single Plutip instance. -- | NOTE: This uses `MoteT`s bracketting, and thus has the same caveats. -- | Namely, brackets are run for each of the following groups and tests. diff --git a/test/Blockfrost/Contract.purs b/test/Blockfrost/Contract.purs new file mode 100644 index 0000000000..bf2caefa00 --- /dev/null +++ b/test/Blockfrost/Contract.purs @@ -0,0 +1,58 @@ +-- | Module to run `Test.Ctl.Plutip.Contract`s suite without Plutip, using +-- | an already running instance of Blockfrost. +module Test.Ctl.Blockfrost.Contract (main, suite) where + +import Prelude + +import Contract.Config + ( PrivatePaymentKeySource(PrivatePaymentKeyFile) + , WalletSpec(UseKeys) + , testnetBlockfrostDevConfig + ) +import Contract.Monad (launchAff_) +import Contract.Test.Mote (TestPlanM, interpretWithConfig) +import Contract.Test.Plutip (testContractsInEnv) +import Data.Maybe (Maybe(Nothing, Just)) +import Data.String (joinWith) +import Effect (Effect) +import Effect.Aff (Aff) +import Effect.Class.Console (log) +import Node.Process (argv, exit) +import Test.Ctl.Plutip.Contract as Plutip +import Test.Spec.Runner (defaultConfig) + +-- Run with `spago test --main Test.Ctl.Blockfrost.Contract --exec-args "BLOCKFROST_API_KEY PRIVATE_PAYMENT_FILE BACKUP_KEYS_DIR"` +main :: Effect Unit +main = do + argv >>= case _ of + [ _, apiKey, privateKey, backupKeys ] -> + launchAff_ do + interpretWithConfig defaultConfig { timeout = Nothing } $ suite apiKey + privateKey + backupKeys + _ -> do + log $ joinWith "\n" + [ "Wrong number of parameters provided." + , "Usage:" + , " spago test --main Test.Ctl.Blockfrost.Contract --exec-args \"BLOCKFROST_API_KEY PRIVATE_PAYMENT_FILE BACKUP_KEYS_DIR\"" + , "" + , " BLOCKFROST_API_KEY - Blockfrost preview API key" + , " PRIVATE_PAYMENT_FILE - PaymentSigningKeyShelley_ed25519 file, as produced by cardano-cli" + , " BACKUP_KEYS_DIR - An existing directory to store generated funded wallets" + ] + exit 1 + +suite :: String -> String -> String -> TestPlanM (Aff Unit) Unit +suite apiKey privateKey backupKeys = do + testContractsInEnv + config + backupKeys + Plutip.suite + where + config = + (testnetBlockfrostDevConfig (Just apiKey)) + { walletSpec = Just $ UseKeys + (PrivatePaymentKeyFile privateKey) + Nothing + , suppressLogs = true + } diff --git a/test/Plutip.purs b/test/Plutip.purs index 82f1c29f90..34e942dea5 100644 --- a/test/Plutip.purs +++ b/test/Plutip.purs @@ -4,8 +4,9 @@ module Test.Ctl.Plutip import Prelude -import Contract.Test.Plutip (testPlutipContracts) +import Contract.Test.Plutip (noWallet, testPlutipContracts) import Contract.Test.Utils (exitCode, interruptOnSignal) +import Ctl.Internal.Contract.Monad (wrapQueryM) import Ctl.Internal.Plutip.Server ( checkPlutipServer , startPlutipCluster @@ -28,10 +29,13 @@ import Effect.Aff , launchAff ) import Mote (group, test) +import Mote.Monad (mapTest) import Test.Ctl.Plutip.Common (config) import Test.Ctl.Plutip.Contract as Contract +import Test.Ctl.Plutip.Contract.NetworkId as NetworkId import Test.Ctl.Plutip.Logging as Logging import Test.Ctl.Plutip.UtxoDistribution as UtxoDistribution +import Test.Ctl.QueryM.AffInterface as QueryM.AffInterface import Test.Spec.Assertions (shouldSatisfy) import Test.Spec.Runner (defaultConfig) @@ -44,7 +48,12 @@ main = interruptOnSignal SIGINT =<< launchAff do $ group "Plutip" do Logging.suite testStartPlutipCluster - testPlutipContracts config Contract.suite + testPlutipContracts config $ do + flip mapTest QueryM.AffInterface.suite + (noWallet <<< wrapQueryM) + + NetworkId.suite + Contract.suite UtxoDistribution.suite testStartPlutipCluster :: TestPlanM (Aff Unit) Unit diff --git a/test/Plutip/Contract.purs b/test/Plutip/Contract.purs index c371e0ae5e..23b0f42aef 100644 --- a/test/Plutip/Contract.purs +++ b/test/Plutip/Contract.purs @@ -49,7 +49,6 @@ import Contract.Test.Plutip ( InitialUTxOs , InitialUTxOsWithStakeKey , PlutipTest - , noWallet , withStakeKey , withWallets ) @@ -109,7 +108,6 @@ import Ctl.Examples.PlutusV2.Scripts.AlwaysSucceeds (alwaysSucceedsScriptV2) import Ctl.Examples.Schnorr as Schnorr import Ctl.Examples.SendsToken (contract) as SendsToken import Ctl.Examples.TxChaining (contract) as TxChaining -import Ctl.Internal.Contract.Monad (wrapQueryM) import Ctl.Internal.Plutus.Conversion.Address (toPlutusAddress) import Ctl.Internal.Plutus.Types.Transaction ( TransactionOutputWithRefScript(TransactionOutputWithRefScript) @@ -143,7 +141,6 @@ import Data.Tuple.Nested (type (/\), (/\)) import Effect.Class (liftEffect) import Effect.Exception (throw) import Mote (group, skip, test) -import Mote.Monad (mapTest) import Safe.Coerce (coerce) import Test.Ctl.Fixtures ( cip25MetadataFixture1 @@ -159,20 +156,13 @@ import Test.Ctl.Fixtures , unappliedScriptFixture ) import Test.Ctl.Plutip.Common (privateStakeKey) -import Test.Ctl.Plutip.Contract.NetworkId as NetworkId import Test.Ctl.Plutip.Utils (getLockedInputs, submitAndLog) import Test.Ctl.Plutip.UtxoDistribution (checkUtxoDistribution) -import Test.Ctl.QueryM.AffInterface as QueryM.AffInterface import Test.Spec.Assertions (shouldEqual, shouldNotEqual, shouldSatisfy) suite :: TestPlanM PlutipTest Unit suite = do group "Contract" do - flip mapTest QueryM.AffInterface.suite - (noWallet <<< wrapQueryM) - - NetworkId.suite - test "Collateral" do let distribution :: InitialUTxOs /\ InitialUTxOs @@ -1620,27 +1610,27 @@ suite = do withCip30Mock alice MockNami do getWalletBalance >>= flip shouldSatisfy (eq $ Just $ coinToValue $ Coin $ BigInt.fromInt 8_000_000) - group "Plutus Crypto" do - test "ECDSA" do - let - distribution :: InitialUTxOs - distribution = - [ BigInt.fromInt 1_000_000_000 - , BigInt.fromInt 2_000_000_000 - ] - withWallets distribution \alice -> do - withKeyWallet alice do - ECDSA.contract - test "Schnorr" do - let - distribution :: InitialUTxOs - distribution = - [ BigInt.fromInt 1_000_000_000 - , BigInt.fromInt 2_000_000_000 - ] - withWallets distribution \alice -> do - withKeyWallet alice do - Schnorr.contract + group "Plutus Crypto" do + test "ECDSA" do + let + distribution :: InitialUTxOs + distribution = + [ BigInt.fromInt 1_000_000_000 + , BigInt.fromInt 2_000_000_000 + ] + withWallets distribution \alice -> do + withKeyWallet alice do + ECDSA.contract + test "Schnorr" do + let + distribution :: InitialUTxOs + distribution = + [ BigInt.fromInt 1_000_000_000 + , BigInt.fromInt 2_000_000_000 + ] + withWallets distribution \alice -> do + withKeyWallet alice do + Schnorr.contract signMultipleContract :: Contract Unit signMultipleContract = do diff --git a/test/Utils/DrainWallets.purs b/test/Utils/DrainWallets.purs new file mode 100644 index 0000000000..4326454893 --- /dev/null +++ b/test/Utils/DrainWallets.purs @@ -0,0 +1,127 @@ +module Test.Ctl.Utils.DrainWallets (main) where + +import Prelude + +import Contract.Address (getWalletAddresses, ownPaymentPubKeysHashes) +import Contract.Config + ( PrivatePaymentKeySource(PrivatePaymentKeyFile) + , WalletSpec(UseKeys) + , defaultOgmiosWsConfig + , mkCtlBackendParams + , testnetConfig + ) +import Contract.Monad (liftedE, runContract) +import Contract.ScriptLookups (ScriptLookups, mkUnbalancedTx, unspentOutputs) +import Contract.Transaction + ( awaitTxConfirmed + , balanceTx + , signTransaction + , submit + ) +import Contract.TxConstraints (mustBeSignedBy, mustSpendPubKeyOutput) +import Contract.Utxos (utxosAt) +import Contract.Wallet (privateKeysToKeyWallet, withKeyWallet) +import Contract.Wallet.KeyFile + ( privatePaymentKeyFromFile + , privateStakeKeyFromFile + ) +import Control.Monad.Error.Class (liftMaybe, try) +import Data.Array (head) +import Data.Array as Array +import Data.Either (hush) +import Data.Foldable (foldMap) +import Data.Map as Map +import Data.Maybe (Maybe(Nothing)) +import Data.Newtype (unwrap, wrap) +import Data.String (joinWith) +import Data.Traversable (for) +import Data.UInt as UInt +import Effect (Effect) +import Effect.Aff (Aff, launchAff_) +import Effect.Aff.Class (liftAff) +import Effect.Class.Console (log) +import Effect.Exception (error) +import Node.FS.Aff (readdir) +import Node.Path as Path +import Node.Process (argv, exit) + +-- Run with `spago run --main Test.Ctl.Utils.DrainWallets --exec-args "PRIVATE_PAYMENT_FILE WALLETS_DIR"` +main :: Effect Unit +main = do + argv >>= case _ of + [ _, privateKey, walletsDir ] -> + launchAff_ $ run privateKey walletsDir + _ -> do + log $ joinWith "\n" + [ "Wrong number of parameters provided." + , "Usage:" + , " spago run --main Test.Ctl.Utils.DrainWallets --exec-args \"PRIVATE_PAYMENT_FILE WALLETS_DIR\"" + , "" + , " PRIVATE_PAYMENT_FILE - PaymentSigningKeyShelley_ed25519 file, as produced by cardano-cli" + , " WALLETS_DIR - A directory of wallets" + ] + exit 1 + +run :: String -> String -> Aff Unit +run privateKey walletsDir = runContract config do + walletFolders <- liftAff $ readdir walletsDir + + wallets <- liftAff $ for walletFolders \walletFolder -> do + payment <- privatePaymentKeyFromFile $ Path.concat + [ walletsDir, walletFolder, "payment_signing_key" ] + mbStake <- hush <$> try + ( privateStakeKeyFromFile $ Path.concat + [ walletsDir, walletFolder, "stake_signing_key" ] + ) + pure $ privateKeysToKeyWallet payment mbStake + + let + merge r = + { utxos: Map.unions (_.utxos <$> r) + , usedWallets: foldMap _.usedWallets r + } + + -- parTraverse breaks kupo + { utxos, usedWallets } <- merge <$> for wallets \wallet -> withKeyWallet + wallet + do + address <- getWalletAddresses >>= head >>> liftMaybe + (error "no addresses") + pkh <- ownPaymentPubKeysHashes >>= head >>> liftMaybe (error "no PKH") + utxos <- utxosAt address + pure + { utxos + , usedWallets: if Map.isEmpty utxos then [] else [ { wallet, pkh } ] + } + + let + constraints = foldMap mustSpendPubKeyOutput (Map.keys utxos) + <> foldMap (_.pkh >>> mustBeSignedBy) usedWallets + lookups = unspentOutputs utxos + + unbalancedTx <- liftedE $ mkUnbalancedTx (lookups :: ScriptLookups Void) + constraints + + balancedTx <- liftedE $ balanceTx unbalancedTx + balancedSignedTx <- Array.foldM + (\tx wallet -> withKeyWallet wallet $ signTransaction tx) + (wrap $ unwrap balancedTx) + (_.wallet <$> usedWallets) + txHash <- submit balancedSignedTx + awaitTxConfirmed txHash + where + config = + testnetConfig + { walletSpec = pure $ UseKeys + (PrivatePaymentKeyFile privateKey) + Nothing + , backendParams = mkCtlBackendParams + { ogmiosConfig: defaultOgmiosWsConfig + , kupoConfig: + { port: UInt.fromInt 1442 + , host: "localhost" + , secure: false + , path: Nothing + } + } + } From b66f20f29636ed12384e62fa0d467d374c4f4857 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Tue, 10 Jan 2023 20:33:30 +0000 Subject: [PATCH 260/373] Fix unit tests --- test/Blockfrost/Aeson.purs | 5 ++++- test/Blockfrost/ProtocolParameters.purs | 15 +++++++-------- 2 files changed, 11 insertions(+), 9 deletions(-) diff --git a/test/Blockfrost/Aeson.purs b/test/Blockfrost/Aeson.purs index ec17827a9b..e7f6da4f30 100644 --- a/test/Blockfrost/Aeson.purs +++ b/test/Blockfrost/Aeson.purs @@ -75,7 +75,7 @@ loadFixtures = do pure groupedFiles suite :: TestPlanM (Aff Unit) Unit -suite = group "Blockfrost Aeson tests" do +suite = group "Blockfrost" $ group "Aeson" do groupedFiles <- lift loadFixtures for_ groupedFiles \(query /\ files') -> @@ -92,6 +92,9 @@ suite = group "Blockfrost Aeson tests" do (Aeson.decodeAeson aeson :: _ a) case query of "getTxMetadata" -> handle (Proxy :: _ B.BlockfrostMetadata) + "getCurrentEpoch" -> handle (Proxy :: _ B.BlockfrostCurrentEpoch) + "getProtocolParameters" -> handle + (Proxy :: _ B.BlockfrostProtocolParameters) _ -> liftEffect $ throw $ "Unknown case " <> bn main :: Effect Unit diff --git a/test/Blockfrost/ProtocolParameters.purs b/test/Blockfrost/ProtocolParameters.purs index 5c127ad3bc..8dee26bf4d 100644 --- a/test/Blockfrost/ProtocolParameters.purs +++ b/test/Blockfrost/ProtocolParameters.purs @@ -41,11 +41,10 @@ main = launchAff_ do suite suite :: TestPlanM (Aff Unit) Unit -suite = do - group "Blockfrost" do - test "ProtocolParameter parsing" do - BlockfrostProtocolParameters blockfrostFixture' <- loadFixture - blockfrostFixture - ogmiosFixture' <- loadFixture ogmiosFixture - - blockfrostFixture' `shouldEqual` ogmiosFixture' +suite = group "Blockfrost" do + test "ProtocolParameter parsing verification" do + BlockfrostProtocolParameters blockfrostFixture' <- loadFixture + blockfrostFixture + ogmiosFixture' <- loadFixture ogmiosFixture + + blockfrostFixture' `shouldEqual` ogmiosFixture' From bc82e3458048ecf46216ecad4ab3f05d2787a2dd Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Tue, 10 Jan 2023 20:35:15 +0000 Subject: [PATCH 261/373] Typo and test order --- test/Blockfrost/ProtocolParameters.purs | 2 +- test/Unit.purs | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/test/Blockfrost/ProtocolParameters.purs b/test/Blockfrost/ProtocolParameters.purs index 8dee26bf4d..e20c5ca3db 100644 --- a/test/Blockfrost/ProtocolParameters.purs +++ b/test/Blockfrost/ProtocolParameters.purs @@ -17,7 +17,7 @@ import Node.FS.Aff (readTextFile) import Test.Spec.Assertions (shouldEqual) import Test.Spec.Runner (defaultConfig) --- These fixtures were aquired soon after each other, so we can compare their +-- These fixtures were acquired soon after each other, so we can compare their -- parsed results blockfrostFixture :: String diff --git a/test/Unit.purs b/test/Unit.purs index 1953d7d5cf..f2517d8f7d 100644 --- a/test/Unit.purs +++ b/test/Unit.purs @@ -80,9 +80,9 @@ testPlan = do Ogmios.Address.suite Ogmios.Aeson.suite Ogmios.EvaluateTx.suite + ProtocolParams.suite Blockfrost.Aeson.suite Blockfrost.ProtocolParameters.suite - ProtocolParams.suite Types.TokenName.suite Types.Transaction.suite Ctl.Data.Interval.suite From a13256166fe43c29a86c3375d70beca7f7c33523 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Wed, 11 Jan 2023 12:54:05 +0000 Subject: [PATCH 262/373] Simplify runBlockfrostServiceM --- src/Internal/Contract/QueryHandle.purs | 6 ++++-- src/Internal/Service/Blockfrost.purs | 15 ++++----------- test/Blockfrost.purs | 20 +++++++++++--------- 3 files changed, 19 insertions(+), 22 deletions(-) diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs index 8a02660794..2667b0b2c8 100644 --- a/src/Internal/Contract/QueryHandle.purs +++ b/src/Internal/Contract/QueryHandle.purs @@ -22,6 +22,7 @@ import Ctl.Internal.Contract.QueryBackend ) import Ctl.Internal.Contract.QueryHandle.Error (GetTxMetadataError) import Ctl.Internal.Hashing (transactionHash) as Hashing +import Ctl.Internal.Helpers (logWithLevel) import Ctl.Internal.QueryM (QueryM) import Ctl.Internal.QueryM (evaluateTxOgmios, getChainTip, submitTxOgmios) as QueryM import Ctl.Internal.QueryM.CurrentEpoch (getCurrentEpoch) as QueryM @@ -63,7 +64,7 @@ import Ctl.Internal.Types.Transaction (TransactionHash, TransactionInput) import Ctl.Internal.Types.TransactionMetadata (GeneralTransactionMetadata) import Data.Either (Either(Left)) import Data.Map as Map -import Data.Maybe (Maybe(Just, Nothing), isJust) +import Data.Maybe (Maybe(Just, Nothing), fromMaybe, isJust) import Data.Newtype (unwrap, wrap) import Effect.Aff (Aff) import Effect.Class (liftEffect) @@ -147,5 +148,6 @@ queryHandleForBlockfrostBackend env backend fallback = } where runBlockfrostServiceM' :: forall (a :: Type). BlockfrostServiceM a -> Aff a - runBlockfrostServiceM' = runBlockfrostServiceM env.logLevel env.customLogger + runBlockfrostServiceM' = runBlockfrostServiceM + (fromMaybe logWithLevel env.customLogger env.logLevel) backend diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index ef7bc33948..1f4ef2cc4c 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -45,7 +45,6 @@ import Ctl.Internal.Deserialization.FromBytes (fromBytes) import Ctl.Internal.Deserialization.Transaction ( convertGeneralTransactionMetadata ) -import Ctl.Internal.Helpers (logWithLevel) import Ctl.Internal.QueryM.Ogmios (TxEvaluationR) import Ctl.Internal.Serialization as Serialization import Ctl.Internal.ServerConfig (ServerConfig, mkHttpUrl) @@ -64,10 +63,9 @@ import Data.Bifunctor (lmap) import Data.Either (Either(Left, Right), note) import Data.Generic.Rep (class Generic) import Data.HTTP.Method (Method(GET, POST)) -import Data.Log.Level (LogLevel) import Data.Log.Message (Message) import Data.Map as Map -import Data.Maybe (Maybe(Just), fromMaybe, maybe) +import Data.Maybe (Maybe(Just), maybe) import Data.MediaType (MediaType(MediaType)) import Data.Newtype (class Newtype, unwrap, wrap) import Data.Show.Generic (genericShow) @@ -93,18 +91,13 @@ type BlockfrostServiceM (a :: Type) = LoggerT runBlockfrostServiceM :: forall (a :: Type) - . LogLevel - -> Maybe (LogLevel -> Message -> Aff Unit) + . (Message -> Aff Unit) -> BlockfrostBackend -> BlockfrostServiceM a -> Aff a -runBlockfrostServiceM logLevel customLogger backend = - flip runReaderT serviceParams <<< flip runLoggerT logger +runBlockfrostServiceM logger backend = + flip runReaderT serviceParams <<< flip runLoggerT (liftAff <<< logger) where - logger :: Message -> ReaderT BlockfrostServiceParams Aff Unit - logger = - liftAff <<< fromMaybe logWithLevel customLogger logLevel - serviceParams :: BlockfrostServiceParams serviceParams = { blockfrostConfig: backend.blockfrostConfig diff --git a/test/Blockfrost.purs b/test/Blockfrost.purs index 24a6fba8f1..7726d18aae 100644 --- a/test/Blockfrost.purs +++ b/test/Blockfrost.purs @@ -2,7 +2,7 @@ module Test.Ctl.Blockfrost (main, testPlan) where import Prelude -import Contract.Config (LogLevel(Trace), blockfrostPublicPreviewServerConfig) +import Contract.Config (blockfrostPublicPreviewServerConfig) import Contract.Metadata ( GeneralTransactionMetadata(GeneralTransactionMetadata) , TransactionMetadatum(Text, MetadataMap) @@ -21,7 +21,8 @@ import Control.Monad.Error.Class (liftEither) import Ctl.Internal.Contract.QueryBackend (BlockfrostBackend) import Ctl.Internal.Helpers (liftedM) import Ctl.Internal.Service.Blockfrost - ( getTxMetadata + ( BlockfrostServiceM + , getTxMetadata , isTxConfirmed , runBlockfrostServiceM ) @@ -30,11 +31,13 @@ import Data.Bifunctor (lmap) import Data.BigInt as BigInt import Data.Either (Either(Left, Right)) import Data.FoldableWithIndex (forWithIndex_) +import Data.Log.Formatter.Pretty (prettyFormatter) import Data.Map as Map -import Data.Maybe (Maybe(Just, Nothing)) +import Data.Maybe (Maybe(Just)) import Data.Tuple.Nested ((/\)) import Effect (Effect) import Effect.Aff (Aff, error, launchAff_) +import Effect.Class.Console (log) import Mote (group, test) import Node.Process (argv) import Test.Spec.Assertions (shouldEqual) @@ -169,19 +172,18 @@ testPlan backend = group "Blockfrost" do forWithIndex_ [ fixture1, fixture2, fixture3, fixture4 ] \i fixture -> group ("fixture " <> show (i + 1)) do test "getTxMetadata" do - eMetadata <- runBlockfrostServiceM Trace Nothing backend $ getTxMetadata - (fixtureHash fixture) + eMetadata <- runBlockfrost $ getTxMetadata $ fixtureHash fixture eMetadata `shouldEqual` case fixture of TxWithMetadata { metadata } -> Right metadata TxWithNoMetadata _ -> Left GetTxMetadataMetadataEmptyOrMissingError UnconfirmedTx _ -> Left GetTxMetadataTxNotFoundError test "isTxConfirmed" do - eConfirmed <- runBlockfrostServiceM Trace Nothing backend - $ isTxConfirmed - $ - fixtureHash fixture + eConfirmed <- runBlockfrost $ isTxConfirmed $ fixtureHash fixture confirmed <- liftEither $ lmap (error <<< show) eConfirmed confirmed `shouldEqual` case fixture of TxWithMetadata _ -> true TxWithNoMetadata _ -> true UnconfirmedTx _ -> false + where + runBlockfrost :: forall (a :: Type). BlockfrostServiceM a -> Aff a + runBlockfrost = runBlockfrostServiceM (prettyFormatter >=> log) backend From d44a463b076260d292e1edf8563f396b8265eda9 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Wed, 11 Jan 2023 15:21:24 +0100 Subject: [PATCH 263/373] Add Aeson tests for getChainTip, getEraSummaries, and getSystemStart --- ...data-05eccee76935dcdcee51bc9539a4bda0.json | 0 ...data-0e6bc6c9bfd8ca8e76fea0c77b408c94.json | 0 ...data-1ad015357709a4bb3605cfba6c07fcfa.json | 0 ...data-1ffc1b00de768cc4cc1fd57789975293.json | 0 ...data-2695bd98c71ce3787d1dd743d7c81e62.json | 0 ...data-2994cb9e7d27a895f5ab37cac85e00c6.json | 0 ...data-408d98ab8c07f61f60b679b4ac1146ee.json | 0 ...data-49cc70e05a6874717534184fe8f1c51c.json | 0 ...data-4a771176a5ee391c5ac8e1a347665af9.json | 0 ...data-4b615bb90ca1b4236909de9d77387349.json | 0 ...data-58e0494c51d30eb3494f7c9198986bb9.json | 0 ...data-5ddf5020f37378695c8f425616518e96.json | 0 ...data-5e96ef1ee339fa6acee8d236a099a50a.json | 0 ...data-70f851fe46e3f298d181e360ab69c7ee.json | 0 ...data-7855477c5b5ef6f22592621de4059a38.json | 0 ...data-7d9eb3d1f1771785b008f992169a9e55.json | 0 ...data-85651cfb9d127afad9e9189900e0e5aa.json | 0 ...data-8acb1a1fb6dbe876f677989a8ea43e50.json | 0 ...data-9ec42e4096428bef20a6e30e089fa290.json | 0 ...data-a41c8fcc791f757d7ee7b8edf67089c7.json | 0 ...data-afa0730bb6c5188054571c420609b6d1.json | 0 ...data-b35620f81cd2aeeb63383bf4842b6ca7.json | 0 ...data-b79202b44212de279780aebb4d1cfa4b.json | 0 ...data-cbd4c5d5e8bd4ee7b19c7eb389d8b998.json | 0 ...data-ce90b4f9049c1d73965810525879b038.json | 0 ...data-d0dc1df3b35e53b71b46ecc3b644f071.json | 0 ...data-dcd34c370d57577ad751d256ba468dc9.json | 0 ...data-ea7ba474ed55636ee60f5425587e971d.json | 0 src/Internal/Service/Blockfrost.purs | 24 +++- test/Blockfrost/Aeson.purs | 99 ----------------- test/Blockfrost/Aeson/Suite.purs | 105 ++++++++++++++++++ test/Unit.purs | 2 +- 32 files changed, 125 insertions(+), 105 deletions(-) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-05eccee76935dcdcee51bc9539a4bda0.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-0e6bc6c9bfd8ca8e76fea0c77b408c94.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-1ad015357709a4bb3605cfba6c07fcfa.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-1ffc1b00de768cc4cc1fd57789975293.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-2695bd98c71ce3787d1dd743d7c81e62.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-2994cb9e7d27a895f5ab37cac85e00c6.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-408d98ab8c07f61f60b679b4ac1146ee.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-49cc70e05a6874717534184fe8f1c51c.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-4a771176a5ee391c5ac8e1a347665af9.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-4b615bb90ca1b4236909de9d77387349.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-58e0494c51d30eb3494f7c9198986bb9.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-5ddf5020f37378695c8f425616518e96.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-5e96ef1ee339fa6acee8d236a099a50a.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-70f851fe46e3f298d181e360ab69c7ee.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-7855477c5b5ef6f22592621de4059a38.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-7d9eb3d1f1771785b008f992169a9e55.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-85651cfb9d127afad9e9189900e0e5aa.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-8acb1a1fb6dbe876f677989a8ea43e50.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-9ec42e4096428bef20a6e30e089fa290.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-a41c8fcc791f757d7ee7b8edf67089c7.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-afa0730bb6c5188054571c420609b6d1.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-b35620f81cd2aeeb63383bf4842b6ca7.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-b79202b44212de279780aebb4d1cfa4b.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-cbd4c5d5e8bd4ee7b19c7eb389d8b998.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-ce90b4f9049c1d73965810525879b038.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-d0dc1df3b35e53b71b46ecc3b644f071.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-dcd34c370d57577ad751d256ba468dc9.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-ea7ba474ed55636ee60f5425587e971d.json (100%) delete mode 100644 test/Blockfrost/Aeson.purs create mode 100644 test/Blockfrost/Aeson/Suite.purs diff --git a/fixtures/test/blockfrost/getTxMetadata-05eccee76935dcdcee51bc9539a4bda0.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-05eccee76935dcdcee51bc9539a4bda0.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-05eccee76935dcdcee51bc9539a4bda0.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-05eccee76935dcdcee51bc9539a4bda0.json diff --git a/fixtures/test/blockfrost/getTxMetadata-0e6bc6c9bfd8ca8e76fea0c77b408c94.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-0e6bc6c9bfd8ca8e76fea0c77b408c94.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-0e6bc6c9bfd8ca8e76fea0c77b408c94.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-0e6bc6c9bfd8ca8e76fea0c77b408c94.json diff --git a/fixtures/test/blockfrost/getTxMetadata-1ad015357709a4bb3605cfba6c07fcfa.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-1ad015357709a4bb3605cfba6c07fcfa.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-1ad015357709a4bb3605cfba6c07fcfa.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-1ad015357709a4bb3605cfba6c07fcfa.json diff --git a/fixtures/test/blockfrost/getTxMetadata-1ffc1b00de768cc4cc1fd57789975293.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-1ffc1b00de768cc4cc1fd57789975293.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-1ffc1b00de768cc4cc1fd57789975293.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-1ffc1b00de768cc4cc1fd57789975293.json diff --git a/fixtures/test/blockfrost/getTxMetadata-2695bd98c71ce3787d1dd743d7c81e62.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-2695bd98c71ce3787d1dd743d7c81e62.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-2695bd98c71ce3787d1dd743d7c81e62.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-2695bd98c71ce3787d1dd743d7c81e62.json diff --git a/fixtures/test/blockfrost/getTxMetadata-2994cb9e7d27a895f5ab37cac85e00c6.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-2994cb9e7d27a895f5ab37cac85e00c6.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-2994cb9e7d27a895f5ab37cac85e00c6.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-2994cb9e7d27a895f5ab37cac85e00c6.json diff --git a/fixtures/test/blockfrost/getTxMetadata-408d98ab8c07f61f60b679b4ac1146ee.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-408d98ab8c07f61f60b679b4ac1146ee.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-408d98ab8c07f61f60b679b4ac1146ee.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-408d98ab8c07f61f60b679b4ac1146ee.json diff --git a/fixtures/test/blockfrost/getTxMetadata-49cc70e05a6874717534184fe8f1c51c.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-49cc70e05a6874717534184fe8f1c51c.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-49cc70e05a6874717534184fe8f1c51c.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-49cc70e05a6874717534184fe8f1c51c.json diff --git a/fixtures/test/blockfrost/getTxMetadata-4a771176a5ee391c5ac8e1a347665af9.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-4a771176a5ee391c5ac8e1a347665af9.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-4a771176a5ee391c5ac8e1a347665af9.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-4a771176a5ee391c5ac8e1a347665af9.json diff --git a/fixtures/test/blockfrost/getTxMetadata-4b615bb90ca1b4236909de9d77387349.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-4b615bb90ca1b4236909de9d77387349.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-4b615bb90ca1b4236909de9d77387349.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-4b615bb90ca1b4236909de9d77387349.json diff --git a/fixtures/test/blockfrost/getTxMetadata-58e0494c51d30eb3494f7c9198986bb9.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-58e0494c51d30eb3494f7c9198986bb9.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-58e0494c51d30eb3494f7c9198986bb9.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-58e0494c51d30eb3494f7c9198986bb9.json diff --git a/fixtures/test/blockfrost/getTxMetadata-5ddf5020f37378695c8f425616518e96.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-5ddf5020f37378695c8f425616518e96.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-5ddf5020f37378695c8f425616518e96.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-5ddf5020f37378695c8f425616518e96.json diff --git a/fixtures/test/blockfrost/getTxMetadata-5e96ef1ee339fa6acee8d236a099a50a.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-5e96ef1ee339fa6acee8d236a099a50a.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-5e96ef1ee339fa6acee8d236a099a50a.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-5e96ef1ee339fa6acee8d236a099a50a.json diff --git a/fixtures/test/blockfrost/getTxMetadata-70f851fe46e3f298d181e360ab69c7ee.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-70f851fe46e3f298d181e360ab69c7ee.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-70f851fe46e3f298d181e360ab69c7ee.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-70f851fe46e3f298d181e360ab69c7ee.json diff --git a/fixtures/test/blockfrost/getTxMetadata-7855477c5b5ef6f22592621de4059a38.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-7855477c5b5ef6f22592621de4059a38.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-7855477c5b5ef6f22592621de4059a38.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-7855477c5b5ef6f22592621de4059a38.json diff --git a/fixtures/test/blockfrost/getTxMetadata-7d9eb3d1f1771785b008f992169a9e55.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-7d9eb3d1f1771785b008f992169a9e55.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-7d9eb3d1f1771785b008f992169a9e55.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-7d9eb3d1f1771785b008f992169a9e55.json diff --git a/fixtures/test/blockfrost/getTxMetadata-85651cfb9d127afad9e9189900e0e5aa.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-85651cfb9d127afad9e9189900e0e5aa.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-85651cfb9d127afad9e9189900e0e5aa.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-85651cfb9d127afad9e9189900e0e5aa.json diff --git a/fixtures/test/blockfrost/getTxMetadata-8acb1a1fb6dbe876f677989a8ea43e50.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-8acb1a1fb6dbe876f677989a8ea43e50.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-8acb1a1fb6dbe876f677989a8ea43e50.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-8acb1a1fb6dbe876f677989a8ea43e50.json diff --git a/fixtures/test/blockfrost/getTxMetadata-9ec42e4096428bef20a6e30e089fa290.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-9ec42e4096428bef20a6e30e089fa290.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-9ec42e4096428bef20a6e30e089fa290.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-9ec42e4096428bef20a6e30e089fa290.json diff --git a/fixtures/test/blockfrost/getTxMetadata-a41c8fcc791f757d7ee7b8edf67089c7.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-a41c8fcc791f757d7ee7b8edf67089c7.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-a41c8fcc791f757d7ee7b8edf67089c7.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-a41c8fcc791f757d7ee7b8edf67089c7.json diff --git a/fixtures/test/blockfrost/getTxMetadata-afa0730bb6c5188054571c420609b6d1.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-afa0730bb6c5188054571c420609b6d1.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-afa0730bb6c5188054571c420609b6d1.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-afa0730bb6c5188054571c420609b6d1.json diff --git a/fixtures/test/blockfrost/getTxMetadata-b35620f81cd2aeeb63383bf4842b6ca7.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-b35620f81cd2aeeb63383bf4842b6ca7.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-b35620f81cd2aeeb63383bf4842b6ca7.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-b35620f81cd2aeeb63383bf4842b6ca7.json diff --git a/fixtures/test/blockfrost/getTxMetadata-b79202b44212de279780aebb4d1cfa4b.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-b79202b44212de279780aebb4d1cfa4b.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-b79202b44212de279780aebb4d1cfa4b.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-b79202b44212de279780aebb4d1cfa4b.json diff --git a/fixtures/test/blockfrost/getTxMetadata-cbd4c5d5e8bd4ee7b19c7eb389d8b998.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-cbd4c5d5e8bd4ee7b19c7eb389d8b998.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-cbd4c5d5e8bd4ee7b19c7eb389d8b998.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-cbd4c5d5e8bd4ee7b19c7eb389d8b998.json diff --git a/fixtures/test/blockfrost/getTxMetadata-ce90b4f9049c1d73965810525879b038.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-ce90b4f9049c1d73965810525879b038.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-ce90b4f9049c1d73965810525879b038.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-ce90b4f9049c1d73965810525879b038.json diff --git a/fixtures/test/blockfrost/getTxMetadata-d0dc1df3b35e53b71b46ecc3b644f071.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-d0dc1df3b35e53b71b46ecc3b644f071.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-d0dc1df3b35e53b71b46ecc3b644f071.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-d0dc1df3b35e53b71b46ecc3b644f071.json diff --git a/fixtures/test/blockfrost/getTxMetadata-dcd34c370d57577ad751d256ba468dc9.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-dcd34c370d57577ad751d256ba468dc9.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-dcd34c370d57577ad751d256ba468dc9.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-dcd34c370d57577ad751d256ba468dc9.json diff --git a/fixtures/test/blockfrost/getTxMetadata-ea7ba474ed55636ee60f5425587e971d.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-ea7ba474ed55636ee60f5425587e971d.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-ea7ba474ed55636ee60f5425587e971d.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-ea7ba474ed55636ee60f5425587e971d.json diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index c13b73c130..717354fa74 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -1,16 +1,19 @@ module Ctl.Internal.Service.Blockfrost - ( BlockfrostEndpoint + ( BlockfrostChainTip(BlockfrostChainTip) + , BlockfrostEndpoint ( BlockchainGenesis , EraSummaries , LatestBlock , Transaction , TransactionMetadata ) + , BlockfrostEraSummaries(BlockfrostEraSummaries) , BlockfrostMetadata(BlockfrostMetadata) , BlockfrostRawPostResponseData , BlockfrostRawResponse , BlockfrostServiceM , BlockfrostServiceParams + , BlockfrostSystemStart(BlockfrostSystemStart) , OnBlockfrostRawGetResponseHook , OnBlockfrostRawPostResponseHook , dummyExport @@ -27,9 +30,11 @@ import Prelude import Aeson ( class DecodeAeson + , class EncodeAeson , Aeson , JsonDecodeError(TypeMismatch) , decodeAeson + , encodeAeson , getField , getFieldOptional' , parseJsonStringToAeson @@ -68,19 +73,19 @@ import Ctl.Internal.Types.EraSummaries , EraSummary , EraSummaryParameters ) -import Ctl.Internal.Types.SystemStart (SystemStart) +import Ctl.Internal.Types.SystemStart (SystemStart(SystemStart)) import Ctl.Internal.Types.Transaction (TransactionHash) import Ctl.Internal.Types.TransactionMetadata ( GeneralTransactionMetadata(GeneralTransactionMetadata) ) import Data.Bifunctor (lmap) -import Data.BigInt (toNumber) as BigInt -import Data.DateTime.Instant (instant, toDateTime) +import Data.BigInt (fromNumber, toNumber) as BigInt +import Data.DateTime.Instant (fromDateTime, instant, toDateTime, unInstant) import Data.Either (Either(Left, Right), note) import Data.Generic.Rep (class Generic) import Data.HTTP.Method (Method(GET, POST)) import Data.Map as Map -import Data.Maybe (Maybe(Nothing), maybe) +import Data.Maybe (Maybe(Nothing), fromJust, maybe) import Data.MediaType (MediaType) import Data.Newtype (class Newtype, unwrap, wrap) import Data.Show.Generic (genericShow) @@ -89,6 +94,7 @@ import Data.Traversable (for, for_, traverse) import Effect.Aff (Aff) import Effect.Aff.Class (liftAff) import Foreign.Object (Object) +import Partial.Unsafe (unsafePartial) import Undefined (undefined) -------------------------------------------------------------------------------- @@ -333,6 +339,14 @@ instance DecodeAeson BlockfrostSystemStart where note (TypeMismatch "Unix timestamp") (wrap <<< wrap <<< toDateTime <$> instant (convertDuration systemStart)) +instance EncodeAeson BlockfrostSystemStart where + encodeAeson (BlockfrostSystemStart (SystemStart systemStart)) = + encodeAeson + (unsafePartial fromJust $ BigInt.fromNumber $ unwrap unixTimeSec) + where + unixTimeSec :: Seconds + unixTimeSec = convertDuration $ unInstant $ fromDateTime systemStart + -------------------------------------------------------------------------------- -- BlockfrostChainTip -------------------------------------------------------------------------------- diff --git a/test/Blockfrost/Aeson.purs b/test/Blockfrost/Aeson.purs deleted file mode 100644 index ec17827a9b..0000000000 --- a/test/Blockfrost/Aeson.purs +++ /dev/null @@ -1,99 +0,0 @@ -module Test.Ctl.Blockfrost.Aeson - ( main - , suite - ) where - -import Prelude - -import Aeson (class DecodeAeson, Aeson, printJsonDecodeError) -import Aeson as Aeson -import Control.Monad.Error.Class (liftEither) -import Control.Monad.Trans.Class (lift) -import Control.Parallel (parTraverse) -import Ctl.Internal.Service.Blockfrost as B -import Ctl.Internal.Test.TestPlanM (TestPlanM, interpret) -import Data.Array (catMaybes, groupAllBy, nubBy) -import Data.Array.NonEmpty (NonEmptyArray, head, length, tail) -import Data.Bifunctor (bimap, lmap) -import Data.Either (hush) -import Data.Maybe (Maybe(Just, Nothing)) -import Data.String.Regex (match, regex) -import Data.String.Regex.Flags (noFlags) -import Data.Traversable (for_) -import Data.Tuple.Nested (type (/\), (/\)) -import Effect (Effect) -import Effect.Aff (Aff, error, launchAff_) -import Effect.Class (liftEffect) -import Effect.Exception (throw) -import Mote (group, test) -import Node.Encoding (Encoding(UTF8)) -import Node.FS.Aff (readTextFile, readdir) -import Node.Path (FilePath, basename, concat) -import Type.Proxy (Proxy(Proxy)) - -type Query = String - -readdir' :: FilePath -> Aff (Array FilePath) -readdir' fp = (map <<< map) (\fn -> concat [ fp, fn ]) (readdir fp) - -applyTuple - :: forall (a :: Type) (b :: Type) (c :: Type) - . (a -> b) /\ (a -> c) - -> a - -> b /\ c -applyTuple (f /\ g) a = f a /\ g a - -loadFixtures - :: Aff (Array (Query /\ NonEmptyArray { aeson :: Aeson, bn :: String })) -loadFixtures = do - let - path = concat [ "fixtures", "test", "blockfrost" ] - pattern = hush $ regex "^([a-zA-Z]+)-[0-9a-fA-F]+\\.json$" noFlags - - files <- do - ourFixtures <- readdir' path - catMaybes <$> flip parTraverse ourFixtures \fp -> do - let bn = basename fp - contents <- readTextFile UTF8 fp - aeson <- liftEither $ lmap - (error <<< ((bn <> "\n ") <> _) <<< printJsonDecodeError) - (Aeson.parseJsonStringToAeson contents) - pure case pattern >>= flip match bn >>> map tail of - Just [ Just query ] -> Just - { query - , bn - , aeson - } - _ -> Nothing - - let - groupedFiles = - map (applyTuple $ _.query <<< head /\ map \{ aeson, bn } -> { aeson, bn }) - $ groupAllBy (comparing _.query) - $ nubBy (comparing _.bn) files - - pure groupedFiles - -suite :: TestPlanM (Aff Unit) Unit -suite = group "Blockfrost Aeson tests" do - groupedFiles <- lift loadFixtures - - for_ groupedFiles \(query /\ files') -> - test (query <> " (" <> show (length files') <> ")") - $ - for_ files' \{ aeson, bn } -> do - let - handle :: forall (a :: Type). DecodeAeson a => Proxy a -> Aff Unit - handle _ = liftEither $ bimap - ( error <<< ((bn <> "\n ") <> _) <<< - printJsonDecodeError - ) - (const unit) - (Aeson.decodeAeson aeson :: _ a) - case query of - "getTxMetadata" -> handle (Proxy :: _ B.BlockfrostMetadata) - _ -> liftEffect $ throw $ "Unknown case " <> bn - -main :: Effect Unit -main = launchAff_ do - interpret suite diff --git a/test/Blockfrost/Aeson/Suite.purs b/test/Blockfrost/Aeson/Suite.purs new file mode 100644 index 0000000000..39885324f2 --- /dev/null +++ b/test/Blockfrost/Aeson/Suite.purs @@ -0,0 +1,105 @@ +module Test.Ctl.Blockfrost.Aeson.Suite (main, suite) where + +import Prelude + +import Aeson + ( class DecodeAeson + , Aeson + , JsonDecodeError + , decodeAeson + , parseJsonStringToAeson + , printJsonDecodeError + ) +import Control.Monad.Error.Class (liftEither) +import Control.Monad.Trans.Class (lift) +import Control.Parallel (parTraverse) +import Ctl.Internal.Service.Blockfrost + ( BlockfrostChainTip + , BlockfrostEraSummaries + , BlockfrostMetadata + , BlockfrostSystemStart + ) +import Ctl.Internal.Test.TestPlanM (TestPlanM, interpret) +import Data.Array (catMaybes, length) +import Data.Array.NonEmpty (tail) +import Data.Bifunctor (bimap, lmap) +import Data.Bounded.Generic (genericBottom) +import Data.Either (Either, hush) +import Data.Enum.Generic (genericSucc) +import Data.Generic.Rep (class Generic) +import Data.Maybe (Maybe(Just, Nothing)) +import Data.String.Regex (Regex, match, regex) +import Data.String.Regex.Flags (noFlags) +import Data.Traversable (for_) +import Effect (Effect) +import Effect.Aff (Aff, error, launchAff_) +import Mote (group, test) +import Node.Encoding (Encoding(UTF8)) +import Node.FS.Aff (readTextFile, readdir) +import Node.Path (FilePath, basename, concat) +import Type.Proxy (Proxy(Proxy)) + +main :: Effect Unit +main = launchAff_ (interpret suite) + +suite :: TestPlanM (Aff Unit) Unit +suite = do + group "Blockfrost Aeson tests" (tests (Just genericBottom)) + where + tests :: Maybe Query -> TestPlanM (Aff Unit) Unit + tests Nothing = pure unit + tests (Just query) = do + fixtures <- lift $ loadFixtures (printQuery query) + test (printQuery query <> " (" <> show (length fixtures) <> ")") do + for_ fixtures \{ aeson, bn } -> do + let + handle :: forall (a :: Type). DecodeAeson a => Proxy a -> Aff Unit + handle _ = liftEither $ bimap + (error <<< ((bn <> "\n ") <> _) <<< printJsonDecodeError) + (const unit) + (decodeAeson aeson :: Either JsonDecodeError a) + case query of + GetChainTipQuery -> handle (Proxy :: Proxy BlockfrostChainTip) + GetEraSummariesQuery -> handle (Proxy :: Proxy BlockfrostEraSummaries) + GetSystemStartQuery -> handle (Proxy :: Proxy BlockfrostSystemStart) + GetTxMetadataQuery -> handle (Proxy :: Proxy BlockfrostMetadata) + tests (genericSucc query) + +data Query + = GetChainTipQuery + | GetEraSummariesQuery + | GetSystemStartQuery + | GetTxMetadataQuery + +derive instance Generic Query _ + +printQuery :: Query -> String +printQuery = case _ of + GetChainTipQuery -> "getChainTip" + GetEraSummariesQuery -> "getEraSummaries" + GetSystemStartQuery -> "getSystemStart" + GetTxMetadataQuery -> "getTxMetadata" + +loadFixtures :: FilePath -> Aff (Array { aeson :: Aeson, bn :: String }) +loadFixtures query = do + files <- readdir' path + catMaybes <$> flip parTraverse files \filepath -> do + let bn = basename filepath + case pattern >>= flip match bn >>> map tail of + Just [ Just query' ] | query' == query -> do + contents <- readTextFile UTF8 filepath + aeson <- liftEither $ lmap + (error <<< ((bn <> "\n ") <> _) <<< printJsonDecodeError) + (parseJsonStringToAeson contents) + pure $ Just { aeson, bn } + _ -> pure Nothing + where + path :: FilePath + path = concat [ "fixtures", "test", "blockfrost", query ] + + pattern :: Maybe Regex + pattern = hush $ regex "^([a-zA-Z]+)-[0-9a-fA-F]+\\.json$" noFlags + +readdir' :: FilePath -> Aff (Array FilePath) +readdir' fp = (map <<< map) (\fn -> concat [ fp, fn ]) (readdir fp) + diff --git a/test/Unit.purs b/test/Unit.purs index e26c771e16..a08067a20b 100644 --- a/test/Unit.purs +++ b/test/Unit.purs @@ -13,7 +13,7 @@ import Effect.Class (liftEffect) import Mote.Monad (mapTest) import Test.Ctl.ApplyArgs as ApplyArgs import Test.Ctl.Base64 as Base64 -import Test.Ctl.Blockfrost.Aeson as Blockfrost.Aeson +import Test.Ctl.Blockfrost.Aeson.Suite as Blockfrost.Aeson import Test.Ctl.ByteArray as ByteArray import Test.Ctl.Data as Data import Test.Ctl.Data.Interval as Ctl.Data.Interval From 22e4fd523092dc74355691951a922697e745f6fa Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Wed, 11 Jan 2023 15:24:56 +0100 Subject: [PATCH 264/373] Remove unused EncodeAeson instance --- src/Internal/Service/Blockfrost.purs | 17 +++-------------- 1 file changed, 3 insertions(+), 14 deletions(-) diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index 717354fa74..711e723346 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -30,11 +30,9 @@ import Prelude import Aeson ( class DecodeAeson - , class EncodeAeson , Aeson , JsonDecodeError(TypeMismatch) , decodeAeson - , encodeAeson , getField , getFieldOptional' , parseJsonStringToAeson @@ -79,13 +77,13 @@ import Ctl.Internal.Types.TransactionMetadata ( GeneralTransactionMetadata(GeneralTransactionMetadata) ) import Data.Bifunctor (lmap) -import Data.BigInt (fromNumber, toNumber) as BigInt -import Data.DateTime.Instant (fromDateTime, instant, toDateTime, unInstant) +import Data.BigInt (toNumber) as BigInt +import Data.DateTime.Instant (instant, toDateTime) import Data.Either (Either(Left, Right), note) import Data.Generic.Rep (class Generic) import Data.HTTP.Method (Method(GET, POST)) import Data.Map as Map -import Data.Maybe (Maybe(Nothing), fromJust, maybe) +import Data.Maybe (Maybe(Nothing), maybe) import Data.MediaType (MediaType) import Data.Newtype (class Newtype, unwrap, wrap) import Data.Show.Generic (genericShow) @@ -94,7 +92,6 @@ import Data.Traversable (for, for_, traverse) import Effect.Aff (Aff) import Effect.Aff.Class (liftAff) import Foreign.Object (Object) -import Partial.Unsafe (unsafePartial) import Undefined (undefined) -------------------------------------------------------------------------------- @@ -339,14 +336,6 @@ instance DecodeAeson BlockfrostSystemStart where note (TypeMismatch "Unix timestamp") (wrap <<< wrap <<< toDateTime <$> instant (convertDuration systemStart)) -instance EncodeAeson BlockfrostSystemStart where - encodeAeson (BlockfrostSystemStart (SystemStart systemStart)) = - encodeAeson - (unsafePartial fromJust $ BigInt.fromNumber $ unwrap unixTimeSec) - where - unixTimeSec :: Seconds - unixTimeSec = convertDuration $ unInstant $ fromDateTime systemStart - -------------------------------------------------------------------------------- -- BlockfrostChainTip -------------------------------------------------------------------------------- From dbad8920061bb4cdbb90dc5f2986a4bf7fd13a7d Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Wed, 11 Jan 2023 16:34:42 +0100 Subject: [PATCH 265/373] Apply suggestions, Update CHANGELOG.md, Update template deps --- CHANGELOG.md | 1 + src/Contract/Time.purs | 6 ++++- templates/ctl-scaffold/packages.dhall | 3 ++- templates/ctl-scaffold/spago-packages.nix | 30 ++++++++++++++++++++--- 4 files changed, 35 insertions(+), 5 deletions(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index 8f267ee899..25c57cb984 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -50,6 +50,7 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) - `Contract.Transaction` exports `mkPoolPubKeyHash` and `poolPubKeyHashToBech32` for bech32 roundtripping ([#1360](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1360)) ### Changed +- `SystemStart` now has `DateTime` (rather than `String`) as the underlying type ([#1377](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1377)) ### Removed diff --git a/src/Contract/Time.purs b/src/Contract/Time.purs index 2ad9ea7f06..3dbbb775df 100644 --- a/src/Contract/Time.purs +++ b/src/Contract/Time.purs @@ -109,7 +109,11 @@ getCurrentEpoch = do $ BigInt.toString (bigInt :: BigInt.BigInt) -- | Get `EraSummaries` as used for Slot arithemetic. --- | Details can be found https://ogmios.dev/api/ under "eraSummaries" query. +-- | +-- | More info can be found in Ogmios or Blockfrost docs (see links below). +-- | Currently we use the same data type definition. +-- | https://ogmios.dev/api/ under "eraSummaries" query +-- | https://docs.blockfrost.io/#tag/Cardano-Network/paths/~1network~1eras/get getEraSummaries :: Contract EraSummaries getEraSummaries = do queryHandle <- getQueryHandle diff --git a/templates/ctl-scaffold/packages.dhall b/templates/ctl-scaffold/packages.dhall index b03ab6aea2..e22903d42e 100644 --- a/templates/ctl-scaffold/packages.dhall +++ b/templates/ctl-scaffold/packages.dhall @@ -286,6 +286,7 @@ let additions = , "foldable-traversable" , "foreign" , "foreign-object" + , "formatters" , "functions" , "gen" , "heterogeneous" @@ -348,7 +349,7 @@ let additions = , "variant" ] , repo = "https://github.com/Plutonomicon/cardano-transaction-lib.git" - , version = "001b639606f341489968d599fb0cef2900aeb474" + , version = "22e4fd523092dc74355691951a922697e745f6fa" } , noble-secp256k1 = { dependencies = diff --git a/templates/ctl-scaffold/spago-packages.nix b/templates/ctl-scaffold/spago-packages.nix index 1ea67501d4..5195541385 100644 --- a/templates/ctl-scaffold/spago-packages.nix +++ b/templates/ctl-scaffold/spago-packages.nix @@ -211,11 +211,11 @@ let "cardano-transaction-lib" = pkgs.stdenv.mkDerivation { name = "cardano-transaction-lib"; - version = "001b639606f341489968d599fb0cef2900aeb474"; + version = "22e4fd523092dc74355691951a922697e745f6fa"; src = pkgs.fetchgit { url = "https://github.com/Plutonomicon/cardano-transaction-lib.git"; - rev = "001b639606f341489968d599fb0cef2900aeb474"; - sha256 = "1rbpq2ikndjar8h3hpq5yz4mqga7276ggdbws34ppq3miczh9czz"; + rev = "22e4fd523092dc74355691951a922697e745f6fa"; + sha256 = "1mkra59915c4wrd95mhl22bhmljdybzbqj9naz5fvvqik7biyv1n"; }; phases = "installPhase"; installPhase = "ln -s $src $out"; @@ -413,6 +413,18 @@ let installPhase = "ln -s $src $out"; }; + "fixed-points" = pkgs.stdenv.mkDerivation { + name = "fixed-points"; + version = "v6.0.0"; + src = pkgs.fetchgit { + url = "https://github.com/purescript-contrib/purescript-fixed-points.git"; + rev = "3b643d948479aee7cd3e36c95258f1f84df0c35f"; + sha256 = "0w2j0sarylzsmg8b228pmn3qndif0bzw2vmxrx30ar15qy7jdb5d"; + }; + phases = "installPhase"; + installPhase = "ln -s $src $out"; + }; + "foldable-traversable" = pkgs.stdenv.mkDerivation { name = "foldable-traversable"; version = "v5.0.1"; @@ -473,6 +485,18 @@ let installPhase = "ln -s $src $out"; }; + "formatters" = pkgs.stdenv.mkDerivation { + name = "formatters"; + version = "v6.0.0"; + src = pkgs.fetchgit { + url = "https://github.com/purescript-contrib/purescript-formatters.git"; + rev = "b2e65b2bccd09a3c17a396f07e13e5cdca90e4e4"; + sha256 = "02c43sv6ci2698mjkmvkv3cjv99ilxv8ii8x7n9wqf18r4hlmk0y"; + }; + phases = "installPhase"; + installPhase = "ln -s $src $out"; + }; + "free" = pkgs.stdenv.mkDerivation { name = "free"; version = "v6.2.0"; From 377be6aff0d0a0266ed27d820cb4ea333c5e913e Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Wed, 11 Jan 2023 16:48:38 +0100 Subject: [PATCH 266/373] Fix CTL revision in scaffold flake.nix --- templates/ctl-scaffold/flake.nix | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/templates/ctl-scaffold/flake.nix b/templates/ctl-scaffold/flake.nix index 69e179de7a..94356640c4 100644 --- a/templates/ctl-scaffold/flake.nix +++ b/templates/ctl-scaffold/flake.nix @@ -10,7 +10,7 @@ type = "github"; owner = "Plutonomicon"; repo = "cardano-transaction-lib"; - rev = "001b639606f341489968d599fb0cef2900aeb474"; + rev = "22e4fd523092dc74355691951a922697e745f6fa"; }; # To use the same version of `nixpkgs` as we do nixpkgs.follows = "ctl/nixpkgs"; From d0de3114ddaaa4087c3cf837f6f2e8247d0c6a34 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Wed, 11 Jan 2023 18:33:39 +0100 Subject: [PATCH 267/373] Minor refactoring of Blockfrost Aeson tests --- ...data-05eccee76935dcdcee51bc9539a4bda0.json | 0 ...data-0e6bc6c9bfd8ca8e76fea0c77b408c94.json | 0 ...data-1ad015357709a4bb3605cfba6c07fcfa.json | 0 ...data-1ffc1b00de768cc4cc1fd57789975293.json | 0 ...data-2695bd98c71ce3787d1dd743d7c81e62.json | 0 ...data-2994cb9e7d27a895f5ab37cac85e00c6.json | 0 ...data-408d98ab8c07f61f60b679b4ac1146ee.json | 0 ...data-49cc70e05a6874717534184fe8f1c51c.json | 0 ...data-4a771176a5ee391c5ac8e1a347665af9.json | 0 ...data-4b615bb90ca1b4236909de9d77387349.json | 0 ...data-58e0494c51d30eb3494f7c9198986bb9.json | 0 ...data-5ddf5020f37378695c8f425616518e96.json | 0 ...data-5e96ef1ee339fa6acee8d236a099a50a.json | 0 ...data-70f851fe46e3f298d181e360ab69c7ee.json | 0 ...data-7855477c5b5ef6f22592621de4059a38.json | 0 ...data-7d9eb3d1f1771785b008f992169a9e55.json | 0 ...data-85651cfb9d127afad9e9189900e0e5aa.json | 0 ...data-8acb1a1fb6dbe876f677989a8ea43e50.json | 0 ...data-9ec42e4096428bef20a6e30e089fa290.json | 0 ...data-a41c8fcc791f757d7ee7b8edf67089c7.json | 0 ...data-afa0730bb6c5188054571c420609b6d1.json | 0 ...data-b35620f81cd2aeeb63383bf4842b6ca7.json | 0 ...data-b79202b44212de279780aebb4d1cfa4b.json | 0 ...data-cbd4c5d5e8bd4ee7b19c7eb389d8b998.json | 0 ...data-ce90b4f9049c1d73965810525879b038.json | 0 ...data-d0dc1df3b35e53b71b46ecc3b644f071.json | 0 ...data-dcd34c370d57577ad751d256ba468dc9.json | 0 ...data-ea7ba474ed55636ee60f5425587e971d.json | 0 test/Blockfrost/Aeson.purs | 99 ------------------- test/Blockfrost/Aeson/Suite.purs | 89 +++++++++++++++++ test/Unit.purs | 2 +- 31 files changed, 90 insertions(+), 100 deletions(-) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-05eccee76935dcdcee51bc9539a4bda0.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-0e6bc6c9bfd8ca8e76fea0c77b408c94.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-1ad015357709a4bb3605cfba6c07fcfa.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-1ffc1b00de768cc4cc1fd57789975293.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-2695bd98c71ce3787d1dd743d7c81e62.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-2994cb9e7d27a895f5ab37cac85e00c6.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-408d98ab8c07f61f60b679b4ac1146ee.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-49cc70e05a6874717534184fe8f1c51c.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-4a771176a5ee391c5ac8e1a347665af9.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-4b615bb90ca1b4236909de9d77387349.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-58e0494c51d30eb3494f7c9198986bb9.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-5ddf5020f37378695c8f425616518e96.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-5e96ef1ee339fa6acee8d236a099a50a.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-70f851fe46e3f298d181e360ab69c7ee.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-7855477c5b5ef6f22592621de4059a38.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-7d9eb3d1f1771785b008f992169a9e55.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-85651cfb9d127afad9e9189900e0e5aa.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-8acb1a1fb6dbe876f677989a8ea43e50.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-9ec42e4096428bef20a6e30e089fa290.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-a41c8fcc791f757d7ee7b8edf67089c7.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-afa0730bb6c5188054571c420609b6d1.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-b35620f81cd2aeeb63383bf4842b6ca7.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-b79202b44212de279780aebb4d1cfa4b.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-cbd4c5d5e8bd4ee7b19c7eb389d8b998.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-ce90b4f9049c1d73965810525879b038.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-d0dc1df3b35e53b71b46ecc3b644f071.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-dcd34c370d57577ad751d256ba468dc9.json (100%) rename fixtures/test/blockfrost/{ => getTxMetadata}/getTxMetadata-ea7ba474ed55636ee60f5425587e971d.json (100%) delete mode 100644 test/Blockfrost/Aeson.purs create mode 100644 test/Blockfrost/Aeson/Suite.purs diff --git a/fixtures/test/blockfrost/getTxMetadata-05eccee76935dcdcee51bc9539a4bda0.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-05eccee76935dcdcee51bc9539a4bda0.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-05eccee76935dcdcee51bc9539a4bda0.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-05eccee76935dcdcee51bc9539a4bda0.json diff --git a/fixtures/test/blockfrost/getTxMetadata-0e6bc6c9bfd8ca8e76fea0c77b408c94.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-0e6bc6c9bfd8ca8e76fea0c77b408c94.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-0e6bc6c9bfd8ca8e76fea0c77b408c94.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-0e6bc6c9bfd8ca8e76fea0c77b408c94.json diff --git a/fixtures/test/blockfrost/getTxMetadata-1ad015357709a4bb3605cfba6c07fcfa.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-1ad015357709a4bb3605cfba6c07fcfa.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-1ad015357709a4bb3605cfba6c07fcfa.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-1ad015357709a4bb3605cfba6c07fcfa.json diff --git a/fixtures/test/blockfrost/getTxMetadata-1ffc1b00de768cc4cc1fd57789975293.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-1ffc1b00de768cc4cc1fd57789975293.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-1ffc1b00de768cc4cc1fd57789975293.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-1ffc1b00de768cc4cc1fd57789975293.json diff --git a/fixtures/test/blockfrost/getTxMetadata-2695bd98c71ce3787d1dd743d7c81e62.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-2695bd98c71ce3787d1dd743d7c81e62.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-2695bd98c71ce3787d1dd743d7c81e62.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-2695bd98c71ce3787d1dd743d7c81e62.json diff --git a/fixtures/test/blockfrost/getTxMetadata-2994cb9e7d27a895f5ab37cac85e00c6.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-2994cb9e7d27a895f5ab37cac85e00c6.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-2994cb9e7d27a895f5ab37cac85e00c6.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-2994cb9e7d27a895f5ab37cac85e00c6.json diff --git a/fixtures/test/blockfrost/getTxMetadata-408d98ab8c07f61f60b679b4ac1146ee.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-408d98ab8c07f61f60b679b4ac1146ee.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-408d98ab8c07f61f60b679b4ac1146ee.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-408d98ab8c07f61f60b679b4ac1146ee.json diff --git a/fixtures/test/blockfrost/getTxMetadata-49cc70e05a6874717534184fe8f1c51c.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-49cc70e05a6874717534184fe8f1c51c.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-49cc70e05a6874717534184fe8f1c51c.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-49cc70e05a6874717534184fe8f1c51c.json diff --git a/fixtures/test/blockfrost/getTxMetadata-4a771176a5ee391c5ac8e1a347665af9.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-4a771176a5ee391c5ac8e1a347665af9.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-4a771176a5ee391c5ac8e1a347665af9.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-4a771176a5ee391c5ac8e1a347665af9.json diff --git a/fixtures/test/blockfrost/getTxMetadata-4b615bb90ca1b4236909de9d77387349.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-4b615bb90ca1b4236909de9d77387349.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-4b615bb90ca1b4236909de9d77387349.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-4b615bb90ca1b4236909de9d77387349.json diff --git a/fixtures/test/blockfrost/getTxMetadata-58e0494c51d30eb3494f7c9198986bb9.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-58e0494c51d30eb3494f7c9198986bb9.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-58e0494c51d30eb3494f7c9198986bb9.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-58e0494c51d30eb3494f7c9198986bb9.json diff --git a/fixtures/test/blockfrost/getTxMetadata-5ddf5020f37378695c8f425616518e96.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-5ddf5020f37378695c8f425616518e96.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-5ddf5020f37378695c8f425616518e96.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-5ddf5020f37378695c8f425616518e96.json diff --git a/fixtures/test/blockfrost/getTxMetadata-5e96ef1ee339fa6acee8d236a099a50a.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-5e96ef1ee339fa6acee8d236a099a50a.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-5e96ef1ee339fa6acee8d236a099a50a.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-5e96ef1ee339fa6acee8d236a099a50a.json diff --git a/fixtures/test/blockfrost/getTxMetadata-70f851fe46e3f298d181e360ab69c7ee.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-70f851fe46e3f298d181e360ab69c7ee.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-70f851fe46e3f298d181e360ab69c7ee.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-70f851fe46e3f298d181e360ab69c7ee.json diff --git a/fixtures/test/blockfrost/getTxMetadata-7855477c5b5ef6f22592621de4059a38.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-7855477c5b5ef6f22592621de4059a38.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-7855477c5b5ef6f22592621de4059a38.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-7855477c5b5ef6f22592621de4059a38.json diff --git a/fixtures/test/blockfrost/getTxMetadata-7d9eb3d1f1771785b008f992169a9e55.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-7d9eb3d1f1771785b008f992169a9e55.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-7d9eb3d1f1771785b008f992169a9e55.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-7d9eb3d1f1771785b008f992169a9e55.json diff --git a/fixtures/test/blockfrost/getTxMetadata-85651cfb9d127afad9e9189900e0e5aa.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-85651cfb9d127afad9e9189900e0e5aa.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-85651cfb9d127afad9e9189900e0e5aa.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-85651cfb9d127afad9e9189900e0e5aa.json diff --git a/fixtures/test/blockfrost/getTxMetadata-8acb1a1fb6dbe876f677989a8ea43e50.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-8acb1a1fb6dbe876f677989a8ea43e50.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-8acb1a1fb6dbe876f677989a8ea43e50.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-8acb1a1fb6dbe876f677989a8ea43e50.json diff --git a/fixtures/test/blockfrost/getTxMetadata-9ec42e4096428bef20a6e30e089fa290.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-9ec42e4096428bef20a6e30e089fa290.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-9ec42e4096428bef20a6e30e089fa290.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-9ec42e4096428bef20a6e30e089fa290.json diff --git a/fixtures/test/blockfrost/getTxMetadata-a41c8fcc791f757d7ee7b8edf67089c7.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-a41c8fcc791f757d7ee7b8edf67089c7.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-a41c8fcc791f757d7ee7b8edf67089c7.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-a41c8fcc791f757d7ee7b8edf67089c7.json diff --git a/fixtures/test/blockfrost/getTxMetadata-afa0730bb6c5188054571c420609b6d1.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-afa0730bb6c5188054571c420609b6d1.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-afa0730bb6c5188054571c420609b6d1.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-afa0730bb6c5188054571c420609b6d1.json diff --git a/fixtures/test/blockfrost/getTxMetadata-b35620f81cd2aeeb63383bf4842b6ca7.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-b35620f81cd2aeeb63383bf4842b6ca7.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-b35620f81cd2aeeb63383bf4842b6ca7.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-b35620f81cd2aeeb63383bf4842b6ca7.json diff --git a/fixtures/test/blockfrost/getTxMetadata-b79202b44212de279780aebb4d1cfa4b.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-b79202b44212de279780aebb4d1cfa4b.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-b79202b44212de279780aebb4d1cfa4b.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-b79202b44212de279780aebb4d1cfa4b.json diff --git a/fixtures/test/blockfrost/getTxMetadata-cbd4c5d5e8bd4ee7b19c7eb389d8b998.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-cbd4c5d5e8bd4ee7b19c7eb389d8b998.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-cbd4c5d5e8bd4ee7b19c7eb389d8b998.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-cbd4c5d5e8bd4ee7b19c7eb389d8b998.json diff --git a/fixtures/test/blockfrost/getTxMetadata-ce90b4f9049c1d73965810525879b038.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-ce90b4f9049c1d73965810525879b038.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-ce90b4f9049c1d73965810525879b038.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-ce90b4f9049c1d73965810525879b038.json diff --git a/fixtures/test/blockfrost/getTxMetadata-d0dc1df3b35e53b71b46ecc3b644f071.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-d0dc1df3b35e53b71b46ecc3b644f071.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-d0dc1df3b35e53b71b46ecc3b644f071.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-d0dc1df3b35e53b71b46ecc3b644f071.json diff --git a/fixtures/test/blockfrost/getTxMetadata-dcd34c370d57577ad751d256ba468dc9.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-dcd34c370d57577ad751d256ba468dc9.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-dcd34c370d57577ad751d256ba468dc9.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-dcd34c370d57577ad751d256ba468dc9.json diff --git a/fixtures/test/blockfrost/getTxMetadata-ea7ba474ed55636ee60f5425587e971d.json b/fixtures/test/blockfrost/getTxMetadata/getTxMetadata-ea7ba474ed55636ee60f5425587e971d.json similarity index 100% rename from fixtures/test/blockfrost/getTxMetadata-ea7ba474ed55636ee60f5425587e971d.json rename to fixtures/test/blockfrost/getTxMetadata/getTxMetadata-ea7ba474ed55636ee60f5425587e971d.json diff --git a/test/Blockfrost/Aeson.purs b/test/Blockfrost/Aeson.purs deleted file mode 100644 index ec17827a9b..0000000000 --- a/test/Blockfrost/Aeson.purs +++ /dev/null @@ -1,99 +0,0 @@ -module Test.Ctl.Blockfrost.Aeson - ( main - , suite - ) where - -import Prelude - -import Aeson (class DecodeAeson, Aeson, printJsonDecodeError) -import Aeson as Aeson -import Control.Monad.Error.Class (liftEither) -import Control.Monad.Trans.Class (lift) -import Control.Parallel (parTraverse) -import Ctl.Internal.Service.Blockfrost as B -import Ctl.Internal.Test.TestPlanM (TestPlanM, interpret) -import Data.Array (catMaybes, groupAllBy, nubBy) -import Data.Array.NonEmpty (NonEmptyArray, head, length, tail) -import Data.Bifunctor (bimap, lmap) -import Data.Either (hush) -import Data.Maybe (Maybe(Just, Nothing)) -import Data.String.Regex (match, regex) -import Data.String.Regex.Flags (noFlags) -import Data.Traversable (for_) -import Data.Tuple.Nested (type (/\), (/\)) -import Effect (Effect) -import Effect.Aff (Aff, error, launchAff_) -import Effect.Class (liftEffect) -import Effect.Exception (throw) -import Mote (group, test) -import Node.Encoding (Encoding(UTF8)) -import Node.FS.Aff (readTextFile, readdir) -import Node.Path (FilePath, basename, concat) -import Type.Proxy (Proxy(Proxy)) - -type Query = String - -readdir' :: FilePath -> Aff (Array FilePath) -readdir' fp = (map <<< map) (\fn -> concat [ fp, fn ]) (readdir fp) - -applyTuple - :: forall (a :: Type) (b :: Type) (c :: Type) - . (a -> b) /\ (a -> c) - -> a - -> b /\ c -applyTuple (f /\ g) a = f a /\ g a - -loadFixtures - :: Aff (Array (Query /\ NonEmptyArray { aeson :: Aeson, bn :: String })) -loadFixtures = do - let - path = concat [ "fixtures", "test", "blockfrost" ] - pattern = hush $ regex "^([a-zA-Z]+)-[0-9a-fA-F]+\\.json$" noFlags - - files <- do - ourFixtures <- readdir' path - catMaybes <$> flip parTraverse ourFixtures \fp -> do - let bn = basename fp - contents <- readTextFile UTF8 fp - aeson <- liftEither $ lmap - (error <<< ((bn <> "\n ") <> _) <<< printJsonDecodeError) - (Aeson.parseJsonStringToAeson contents) - pure case pattern >>= flip match bn >>> map tail of - Just [ Just query ] -> Just - { query - , bn - , aeson - } - _ -> Nothing - - let - groupedFiles = - map (applyTuple $ _.query <<< head /\ map \{ aeson, bn } -> { aeson, bn }) - $ groupAllBy (comparing _.query) - $ nubBy (comparing _.bn) files - - pure groupedFiles - -suite :: TestPlanM (Aff Unit) Unit -suite = group "Blockfrost Aeson tests" do - groupedFiles <- lift loadFixtures - - for_ groupedFiles \(query /\ files') -> - test (query <> " (" <> show (length files') <> ")") - $ - for_ files' \{ aeson, bn } -> do - let - handle :: forall (a :: Type). DecodeAeson a => Proxy a -> Aff Unit - handle _ = liftEither $ bimap - ( error <<< ((bn <> "\n ") <> _) <<< - printJsonDecodeError - ) - (const unit) - (Aeson.decodeAeson aeson :: _ a) - case query of - "getTxMetadata" -> handle (Proxy :: _ B.BlockfrostMetadata) - _ -> liftEffect $ throw $ "Unknown case " <> bn - -main :: Effect Unit -main = launchAff_ do - interpret suite diff --git a/test/Blockfrost/Aeson/Suite.purs b/test/Blockfrost/Aeson/Suite.purs new file mode 100644 index 0000000000..fc3dfd0c82 --- /dev/null +++ b/test/Blockfrost/Aeson/Suite.purs @@ -0,0 +1,89 @@ +module Test.Ctl.Blockfrost.Aeson.Suite (main, suite) where + +import Prelude + +import Aeson + ( class DecodeAeson + , Aeson + , JsonDecodeError + , decodeAeson + , parseJsonStringToAeson + , printJsonDecodeError + ) +import Control.Monad.Error.Class (liftEither) +import Control.Monad.Trans.Class (lift) +import Control.Parallel (parTraverse) +import Ctl.Internal.Service.Blockfrost (BlockfrostMetadata) +import Ctl.Internal.Test.TestPlanM (TestPlanM, interpret) +import Data.Array (catMaybes, length) +import Data.Array.NonEmpty (tail) +import Data.Bifunctor (bimap, lmap) +import Data.Bounded.Generic (genericBottom) +import Data.Either (Either, hush) +import Data.Enum.Generic (genericSucc) +import Data.Generic.Rep (class Generic) +import Data.Maybe (Maybe(Just, Nothing)) +import Data.String.Regex (Regex, match, regex) +import Data.String.Regex.Flags (noFlags) +import Data.Traversable (for_) +import Effect (Effect) +import Effect.Aff (Aff, error, launchAff_) +import Mote (group, test) +import Node.Encoding (Encoding(UTF8)) +import Node.FS.Aff (readTextFile, readdir) +import Node.Path (FilePath, basename, concat) +import Type.Proxy (Proxy(Proxy)) + +main :: Effect Unit +main = launchAff_ (interpret suite) + +suite :: TestPlanM (Aff Unit) Unit +suite = do + group "Blockfrost Aeson tests" (tests (Just genericBottom)) + where + tests :: Maybe Query -> TestPlanM (Aff Unit) Unit + tests Nothing = pure unit + tests (Just query) = do + fixtures <- lift $ loadFixtures (printQuery query) + test (printQuery query <> " (" <> show (length fixtures) <> ")") do + for_ fixtures \{ aeson, bn } -> do + let + handle :: forall (a :: Type). DecodeAeson a => Proxy a -> Aff Unit + handle _ = liftEither $ bimap + (error <<< ((bn <> "\n ") <> _) <<< printJsonDecodeError) + (const unit) + (decodeAeson aeson :: Either JsonDecodeError a) + case query of + GetTxMetadataQuery -> handle (Proxy :: Proxy BlockfrostMetadata) + tests (genericSucc query) + +data Query = GetTxMetadataQuery + +derive instance Generic Query _ + +printQuery :: Query -> String +printQuery = case _ of + GetTxMetadataQuery -> "getTxMetadata" + +loadFixtures :: FilePath -> Aff (Array { aeson :: Aeson, bn :: String }) +loadFixtures query = do + files <- readdir' path + catMaybes <$> flip parTraverse files \filepath -> do + let bn = basename filepath + case pattern >>= flip match bn >>> map tail of + Just [ Just query' ] | query' == query -> do + contents <- readTextFile UTF8 filepath + aeson <- liftEither $ lmap + (error <<< ((bn <> "\n ") <> _) <<< printJsonDecodeError) + (parseJsonStringToAeson contents) + pure $ Just { aeson, bn } + _ -> pure Nothing + where + path :: FilePath + path = concat [ "fixtures", "test", "blockfrost", query ] + + pattern :: Maybe Regex + pattern = hush $ regex "^([a-zA-Z]+)-[0-9a-fA-F]+\\.json$" noFlags + +readdir' :: FilePath -> Aff (Array FilePath) +readdir' fp = (map <<< map) (\fn -> concat [ fp, fn ]) (readdir fp) diff --git a/test/Unit.purs b/test/Unit.purs index e26c771e16..a08067a20b 100644 --- a/test/Unit.purs +++ b/test/Unit.purs @@ -13,7 +13,7 @@ import Effect.Class (liftEffect) import Mote.Monad (mapTest) import Test.Ctl.ApplyArgs as ApplyArgs import Test.Ctl.Base64 as Base64 -import Test.Ctl.Blockfrost.Aeson as Blockfrost.Aeson +import Test.Ctl.Blockfrost.Aeson.Suite as Blockfrost.Aeson import Test.Ctl.ByteArray as ByteArray import Test.Ctl.Data as Data import Test.Ctl.Data.Interval as Ctl.Data.Interval From d9150ee4795f98d885034e2cfbff1752bfe6f670 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Wed, 11 Jan 2023 21:46:26 +0400 Subject: [PATCH 268/373] Rewrite Contract assertion utils --- examples/BalanceTxConstraints.purs | 55 +- examples/ContractTestUtils.purs | 75 +-- examples/OneShotMinting.purs | 30 +- examples/PaysWithDatum.purs | 75 ++- examples/PlutusV2/ReferenceInputs.purs | 57 +- src/Contract/Test/Assert.purs | 599 +++++++++++++++++++++ src/Contract/Test/Utils.purs | 685 +------------------------ 7 files changed, 751 insertions(+), 825 deletions(-) create mode 100644 src/Contract/Test/Assert.purs diff --git a/examples/BalanceTxConstraints.purs b/examples/BalanceTxConstraints.purs index 9702b6fe89..75c34f46f4 100644 --- a/examples/BalanceTxConstraints.purs +++ b/examples/BalanceTxConstraints.purs @@ -20,12 +20,15 @@ import Contract.BalanceTxConstraints import Contract.Log (logInfo') import Contract.Monad (Contract, liftedE, liftedM) import Contract.ScriptLookups as Lookups -import Contract.Test.Utils +import Contract.Test.Assert ( ContractAssertionFailure(CustomFailure) - , ContractBasicAssertion + , ContractCheck + , assertContract + , assertionToCheck + , checkNewUtxosAtAddress , label + , runChecks ) -import Contract.Test.Utils as TestUtils import Contract.Transaction ( TransactionHash , TransactionInput @@ -39,6 +42,7 @@ import Contract.Utxos (utxosAt) import Contract.Value (CurrencySymbol, TokenName, Value) import Contract.Value (singleton, valueOf) as Value import Contract.Wallet (KeyWallet, withKeyWallet) +import Control.Monad.Trans.Class (lift) import Ctl.Examples.AlwaysMints (alwaysMintsPolicy) import Ctl.Examples.Helpers (mkCurrencySymbol, mkTokenName) as Helpers import Data.Array (head) @@ -63,18 +67,18 @@ type ContractResult = -- | correctly, i.e. their token quantities do not exceed the specified upper -- | limit of 4 tokens per change output. assertChangeOutputsPartitionedCorrectly - :: ContractBasicAssertion ContractResult Unit -assertChangeOutputsPartitionedCorrectly - { txHash, changeAddress: addr, mintedToken: cs /\ tn } = do - let labeledAddr = label addr "changeAddress" - TestUtils.runContractAssertionM' $ - TestUtils.checkNewUtxosAtAddress labeledAddr txHash \changeOutputs -> do + :: ContractCheck ContractResult +assertChangeOutputsPartitionedCorrectly = assertionToCheck + "Change is correctly partitioned" + \{ txHash, changeAddress: addr, mintedToken: cs /\ tn } -> do + let labeledAddr = label addr "changeAddress" + checkNewUtxosAtAddress labeledAddr txHash \changeOutputs -> do let assertionFailure :: ContractAssertionFailure assertionFailure = CustomFailure "Change outputs were not partitioned correctly" - TestUtils.assertContract assertionFailure do + assertContract assertionFailure do let values :: Array Value values = @@ -89,20 +93,21 @@ assertChangeOutputsPartitionedCorrectly -- | Checks that the utxo with the specified output reference -- | (`nonSpendableOref`) is not consumed during transaction balancing. assertSelectedUtxoIsNotSpent - :: ContractBasicAssertion ContractResult Unit -assertSelectedUtxoIsNotSpent { changeAddress, nonSpendableOref } = - TestUtils.runContractAssertionM' do - utxos <- TestUtils.utxosAtAddress (label changeAddress "changeAddress") - let - assertionFailure :: ContractAssertionFailure - assertionFailure = - CustomFailure "The utxo marked as non-spendable has been spent" - - TestUtils.assertContract assertionFailure $ - Map.member nonSpendableOref utxos - -assertions :: Array (ContractBasicAssertion ContractResult Unit) -assertions = + :: ContractCheck ContractResult +assertSelectedUtxoIsNotSpent = + assertionToCheck "Non-spendable UTxO hasn't been spent" + \{ changeAddress, nonSpendableOref } -> do + utxos <- lift $ utxosAt changeAddress + let + assertionFailure :: ContractAssertionFailure + assertionFailure = + CustomFailure "The utxo marked as non-spendable has been spent" + + assertContract assertionFailure $ + Map.member nonSpendableOref utxos + +checks :: Array (ContractCheck ContractResult) +checks = [ assertChangeOutputsPartitionedCorrectly , assertSelectedUtxoIsNotSpent ] @@ -146,7 +151,7 @@ contract (ContractParams p) = do <> BalanceTxConstraints.mustSendChangeToAddress bobAddress <> BalanceTxConstraints.mustNotSpendUtxoWithOutRef nonSpendableOref - void $ TestUtils.withAssertions assertions do + void $ runChecks checks do unbalancedTx <- liftedE $ Lookups.mkUnbalancedTx lookups constraints diff --git a/examples/ContractTestUtils.purs b/examples/ContractTestUtils.purs index 381ff3c8c7..5e0a9e550b 100644 --- a/examples/ContractTestUtils.purs +++ b/examples/ContractTestUtils.purs @@ -29,12 +29,19 @@ import Contract.Monad (Contract, liftContractM, liftedE, liftedM) import Contract.PlutusData (Datum, OutputDatum(OutputDatumHash)) import Contract.ScriptLookups as Lookups import Contract.Scripts (MintingPolicy) -import Contract.Test.Utils - ( ContractBasicAssertion - , ContractWrapAssertion +import Contract.Test.Assert + ( ContractCheck + , assertOutputHasDatum + , assertOutputHasRefScript + , assertTxHasMetadata + , assertionToCheck + , checkExUnitsNotExceed + , checkGainAtAddress' + , checkLossAtAddress + , checkTokenGainAtAddress' , label + , runChecks ) -import Contract.Test.Utils as TestUtils import Contract.Transaction ( TransactionHash , TransactionOutputWithRefScript @@ -51,7 +58,7 @@ import Contract.Transaction import Contract.TxConstraints (DatumPresence(DatumWitness)) import Contract.TxConstraints as Constraints import Contract.Utxos (utxosAt) -import Contract.Value (CurrencySymbol, TokenName, Value, adaToken) +import Contract.Value (CurrencySymbol, TokenName, Value) import Contract.Value (lovelaceValueOf, singleton) as Value import Ctl.Examples.Helpers (mustPayToPubKeyStakeAddress) as Helpers import Data.Array (head) @@ -77,46 +84,44 @@ type ContractResult = , txOutputUnderTest :: TransactionOutputWithRefScript } -mkAssertions +mkChecks :: ContractParams - -> Contract - ( Array (ContractWrapAssertion ContractResult) - /\ Array (ContractBasicAssertion ContractResult Unit) - ) -mkAssertions params@(ContractParams p) = do + -> Contract (Array (ContractCheck ContractResult)) +mkChecks params@(ContractParams p) = do senderAddress <- liftedM "Failed to get sender address" $ head <$> getWalletAddresses receiverAddress <- liftedM "Failed to get receiver address" (getReceiverAddress params) let dhash = datumHash p.datumToAttach pure - $ - [ TestUtils.assertGainAtAddress' (label receiverAddress "Receiver") - p.adaToSend - - , TestUtils.assertLossAtAddress (label senderAddress "Sender") - \{ txFinalFee } -> pure (p.adaToSend + txFinalFee + txFinalFee) - - , TestUtils.assertTokenGainAtAddress' (label senderAddress "Sender") - ( uncurry3 (\cs tn amount -> cs /\ tn /\ amount) - p.tokensToMint - ) - , TestUtils.assertExUnitsNotExceed - { mem: BigInt.fromInt 800, steps: BigInt.fromInt 16110 } - ] - /\ - [ \{ txOutputUnderTest } -> - TestUtils.assertOutputHasDatum (OutputDatumHash dhash) + [ checkGainAtAddress' (label receiverAddress "Receiver") + p.adaToSend + + , checkLossAtAddress (label senderAddress "Sender") + \{ txFinalFee } -> pure (p.adaToSend + txFinalFee) + + , checkTokenGainAtAddress' (label senderAddress "Sender") + ( uncurry3 (\cs tn amount -> cs /\ tn /\ amount) + p.tokensToMint + ) + + , checkExUnitsNotExceed + { mem: BigInt.fromInt 800, steps: BigInt.fromInt 161100 } + + , assertionToCheck "Sender's output has a datum" + \{ txOutputUnderTest } -> + assertOutputHasDatum (OutputDatumHash dhash) (label txOutputUnderTest "Sender's output with datum hash") - , \{ txOutputUnderTest } -> - TestUtils.assertOutputHasRefScript + , assertionToCheck "Output has a reference script" + \{ txOutputUnderTest } -> + assertOutputHasRefScript (scriptRefFromMintingPolicy p.mintingPolicy) (label txOutputUnderTest "Sender's output with reference script") - , \{ txHash } -> - TestUtils.assertTxHasMetadata "CIP25 Metadata" txHash p.txMetadata - ] + , assertionToCheck "Contains CIP-25 metadata" \{ txHash } -> + assertTxHasMetadata "CIP25 Metadata" txHash p.txMetadata + ] contract :: ContractParams -> Contract Unit contract params@(ContractParams p) = do @@ -150,8 +155,8 @@ contract params@(ContractParams p) = do lookups :: Lookups.ScriptLookups Void lookups = Lookups.mintingPolicy p.mintingPolicy - assertions <- mkAssertions params - void $ TestUtils.withAssertions assertions do + checks <- mkChecks params + void $ runChecks checks do unbalancedTx <- liftedE $ Lookups.mkUnbalancedTx lookups constraints unbalancedTxWithMetadata <- setTxMetadata unbalancedTx p.txMetadata balancedTx <- liftedE $ balanceTx unbalancedTxWithMetadata diff --git a/examples/OneShotMinting.purs b/examples/OneShotMinting.purs index 06e7c8bb28..212d4d676a 100644 --- a/examples/OneShotMinting.purs +++ b/examples/OneShotMinting.purs @@ -32,8 +32,14 @@ import Contract.Scripts , PlutusScript , applyArgs ) -import Contract.Test.Utils (ContractWrapAssertion, Labeled, label) -import Contract.Test.Utils as TestUtils +import Contract.Test.Assert + ( ContractCheck + , Labeled + , checkLossAtAddress + , checkTokenGainAtAddress' + , label + , runChecks + ) import Contract.TextEnvelope (decodeTextEnvelope, plutusScriptV1FromEnvelope) import Contract.Transaction ( TransactionInput @@ -45,10 +51,7 @@ import Contract.Utxos (utxosAt) import Contract.Value (CurrencySymbol, TokenName) import Contract.Value (singleton) as Value import Control.Monad.Error.Class (liftMaybe) -import Ctl.Examples.Helpers - ( mkCurrencySymbol - , mkTokenName - ) as Helpers +import Ctl.Examples.Helpers (mkCurrencySymbol, mkTokenName) as Helpers import Data.Array (head) import Data.Array (head, singleton) as Array import Data.BigInt (BigInt) @@ -62,18 +65,18 @@ example :: ContractParams -> Effect Unit example cfg = launchAff_ do runContract cfg contract -mkAssertions +mkChecks :: Address -> (CurrencySymbol /\ TokenName /\ BigInt) - -> Array (ContractWrapAssertion { txFinalFee :: BigInt }) -mkAssertions ownAddress nft = + -> Array (ContractCheck { txFinalFee :: BigInt }) +mkChecks ownAddress nft = let labeledOwnAddress :: Labeled Address labeledOwnAddress = label ownAddress "ownAddress" in - [ TestUtils.assertTokenGainAtAddress' labeledOwnAddress nft + [ checkTokenGainAtAddress' labeledOwnAddress nft - , TestUtils.assertLossAtAddress labeledOwnAddress + , checkLossAtAddress labeledOwnAddress \{ txFinalFee } -> pure txFinalFee ] @@ -109,8 +112,8 @@ mkContractWithAssertions exampleName mkMintingPolicy = do Lookups.mintingPolicy mp <> Lookups.unspentOutputs utxos - let assertions = mkAssertions ownAddress (cs /\ tn /\ one) - void $ TestUtils.withAssertions assertions do + let checks = mkChecks ownAddress (cs /\ tn /\ one) + void $ runChecks checks do { txHash, txFinalFee } <- submitTxFromConstraintsReturningFee lookups constraints logInfo' $ "Tx ID: " <> show txHash @@ -141,4 +144,3 @@ mkOneShotMintingPolicy unappliedMintingPolicy oref = mintingPolicyArgs = Array.singleton (toData oref) in applyArgs unappliedMintingPolicy mintingPolicyArgs - diff --git a/examples/PaysWithDatum.purs b/examples/PaysWithDatum.purs index 6be3567b48..37065f5cf3 100644 --- a/examples/PaysWithDatum.purs +++ b/examples/PaysWithDatum.purs @@ -17,12 +17,7 @@ import Contract.Address import Contract.Config (ContractParams, testnetNamiConfig) import Contract.Hashing (datumHash) import Contract.Log (logInfo') -import Contract.Monad - ( Contract - , launchAff_ - , liftedM - , runContract - ) +import Contract.Monad (Contract, launchAff_, liftedM, runContract) import Contract.PlutusData ( DataHash , Datum(Datum) @@ -30,17 +25,15 @@ import Contract.PlutusData , PlutusData(Integer) ) import Contract.ScriptLookups as Lookups -import Contract.Test.Utils +import Contract.Test.Assert ( ContractAssertionFailure(CustomFailure) - , ContractBasicAssertion + , ContractCheck + , assertContract + , assertionToCheck + , checkNewUtxosAtAddress , label + , runChecks ) -import Contract.Test.Utils - ( assertContract - , checkNewUtxosAtAddress - , runContractAssertionM' - , withAssertions - ) as TestUtils import Contract.Transaction ( TransactionHash , TransactionOutputWithRefScript @@ -91,43 +84,43 @@ contract = do lookups :: Lookups.ScriptLookups Void lookups = mempty - void $ TestUtils.withAssertions assertions do + void $ runChecks checks do txHash <- submitTxFromConstraints lookups constraints awaitTxConfirmed txHash logInfo' "Tx submitted successfully!" pure { address, txHash, datum, datumHash: datumHash' } -assertions :: Array (ContractBasicAssertion ContractResult Unit) -assertions = +checks :: Array (ContractCheck ContractResult) +checks = [ assertTxCreatesOutputWithInlineDatum, assertTxCreatesOutputWithDatumHash ] assertTxCreatesOutputWithInlineDatum - :: ContractBasicAssertion ContractResult Unit -assertTxCreatesOutputWithInlineDatum { address, txHash, datum } = - let - assertionFailure :: ContractAssertionFailure - assertionFailure = - CustomFailure "Could not find output with given inline datum" - in - TestUtils.runContractAssertionM' $ - TestUtils.checkNewUtxosAtAddress (label address "ownAddress") txHash - \outputs -> - TestUtils.assertContract assertionFailure $ - hasOutputWithOutputDatum (OutputDatum datum) outputs + :: ContractCheck ContractResult +assertTxCreatesOutputWithInlineDatum = assertionToCheck + "Contains an output with inline datum" + \{ address, txHash, datum } -> do + let + assertionFailure :: ContractAssertionFailure + assertionFailure = + CustomFailure "Could not find output with given inline datum" + checkNewUtxosAtAddress (label address "ownAddress") txHash + \outputs -> + assertContract assertionFailure $ + hasOutputWithOutputDatum (OutputDatum datum) outputs assertTxCreatesOutputWithDatumHash - :: ContractBasicAssertion ContractResult Unit -assertTxCreatesOutputWithDatumHash { address, txHash, datumHash } = - let - assertionFailure :: ContractAssertionFailure - assertionFailure = - CustomFailure "Could not find output with given datum hash" - in - TestUtils.runContractAssertionM' $ - TestUtils.checkNewUtxosAtAddress (label address "ownAddress") txHash - \outputs -> - TestUtils.assertContract assertionFailure $ - hasOutputWithOutputDatum (OutputDatumHash datumHash) outputs + :: ContractCheck ContractResult +assertTxCreatesOutputWithDatumHash = assertionToCheck + "Contains an output with a given datum hash" + \{ address, txHash, datumHash } -> do + let + assertionFailure :: ContractAssertionFailure + assertionFailure = + CustomFailure "Could not find output with given datum hash" + checkNewUtxosAtAddress (label address "ownAddress") txHash + \outputs -> + assertContract assertionFailure $ + hasOutputWithOutputDatum (OutputDatumHash datumHash) outputs hasOutputWithOutputDatum :: OutputDatum -> Array TransactionOutputWithRefScript -> Boolean diff --git a/examples/PlutusV2/ReferenceInputs.purs b/examples/PlutusV2/ReferenceInputs.purs index a4852b68c3..5ff671c31f 100644 --- a/examples/PlutusV2/ReferenceInputs.purs +++ b/examples/PlutusV2/ReferenceInputs.purs @@ -19,12 +19,13 @@ import Contract.Monad , runContract ) import Contract.ScriptLookups as Lookups -import Contract.Test.Utils +import Contract.Test.Assert ( ContractAssertionFailure(CustomFailure) - , ContractBasicAssertion - , label + , ContractCheck + , assertContract + , assertionToCheck + , runChecks ) -import Contract.Test.Utils as TestUtils import Contract.Transaction ( BalancedSignedTransaction , TransactionInput @@ -38,6 +39,7 @@ import Contract.Transaction import Contract.TxConstraints as Constraints import Contract.Utxos (utxosAt) import Contract.Value (lovelaceValueOf) as Value +import Control.Monad.Trans.Class (lift) import Ctl.Examples.Helpers (mustPayToPubKeyStakeAddress) as Helpers import Data.Array (head) as Array import Data.BigInt (fromInt) as BigInt @@ -77,7 +79,7 @@ contract = do lookups :: Lookups.ScriptLookups Void lookups = mempty - void $ TestUtils.withAssertions assertions do + void $ runChecks checks do unbalancedTx <- liftedE $ Lookups.mkUnbalancedTx lookups constraints balancedSignedTx <- signTransaction =<< liftedE (balanceTx unbalancedTx) txHash <- submit balancedSignedTx @@ -93,33 +95,30 @@ type ContractResult = , balancedSignedTx :: BalancedSignedTransaction } -assertTxContainsReferenceInput :: ContractBasicAssertion ContractResult Unit -assertTxContainsReferenceInput { balancedSignedTx, referenceInput } = - let - assertionFailure :: ContractAssertionFailure - assertionFailure = - CustomFailure "Could not find given input in `referenceInputs`" - in - TestUtils.runContractAssertionM' do - TestUtils.assertContract assertionFailure do +assertTxContainsReferenceInput :: ContractCheck ContractResult +assertTxContainsReferenceInput = + assertionToCheck "Tx contains a reference input" + \{ balancedSignedTx, referenceInput } -> do + let + assertionFailure :: ContractAssertionFailure + assertionFailure = CustomFailure + "Could not find given input in `referenceInputs`" + assertContract assertionFailure do Set.member referenceInput (unwrap balancedSignedTx ^. _body <<< _referenceInputs) -assertReferenceInputNotSpent :: ContractBasicAssertion ContractResult Unit -assertReferenceInputNotSpent { ownAddress, referenceInput } = - let - assertionFailure :: ContractAssertionFailure - assertionFailure = - CustomFailure "Reference input has been spent" - in - TestUtils.runContractAssertionM' do - utxos <- TestUtils.utxosAtAddress (label ownAddress "ownAddress") - TestUtils.assertContract assertionFailure do - Map.member referenceInput utxos - -assertions :: Array (ContractBasicAssertion ContractResult Unit) -assertions = +assertReferenceInputNotSpent :: ContractCheck ContractResult +assertReferenceInputNotSpent = assertionToCheck "A reference input UTxO" + \{ ownAddress, referenceInput } -> do + let + assertionFailure :: ContractAssertionFailure + assertionFailure = CustomFailure "Reference input has been spent" + utxos <- lift $ utxosAt ownAddress + assertContract assertionFailure do + Map.member referenceInput utxos + +checks :: Array (ContractCheck ContractResult) +checks = [ assertTxContainsReferenceInput , assertReferenceInputNotSpent ] - diff --git a/src/Contract/Test/Assert.purs b/src/Contract/Test/Assert.purs new file mode 100644 index 0000000000..10cee8bf81 --- /dev/null +++ b/src/Contract/Test/Assert.purs @@ -0,0 +1,599 @@ +module Contract.Test.Assert + ( ContractAssertionFailure + ( CouldNotGetTxByHash + , CouldNotParseMetadata + , CustomFailure + , SkippedTest + , MaxExUnitsExceeded + , TransactionHasNoMetadata + , UnexpectedDatumInOutput + , UnexpectedLovelaceDelta + , UnexpectedMetadataValue + , UnexpectedRefScriptInOutput + , UnexpectedTokenDelta + ) + , ContractAssertion + , ContractCheck + , ExpectedActual(ExpectedActual) + , Label + , Labeled(Labeled) + , assertContractExpectedActual + , assertContractMaybe + , assertContract + , checkExUnitsNotExceed + , checkGainAtAddress + , checkGainAtAddress' + , checkLossAtAddress + , checkLossAtAddress' + , assertLovelaceDeltaAtAddress + , assertOutputHasDatum + , checkTokenDeltaAtAddress + , checkTokenGainAtAddress + , checkTokenGainAtAddress' + , checkTokenLossAtAddress + , checkTokenLossAtAddress' + , assertTxHasMetadata + , assertValueDeltaAtAddress + , checkNewUtxosAtAddress + , assertOutputHasRefScript + , label + , unlabel + , noLabel + , runChecks + , assertionToCheck + ) where + +import Prelude + +import Contract.Address (Address) +import Contract.Monad (Contract) +import Contract.PlutusData (OutputDatum) +import Contract.Prelude (Effect) +import Contract.Transaction + ( ScriptRef + , TransactionHash + , TransactionOutputWithRefScript + , getTxMetadata + ) +import Contract.Utxos (utxosAt) +import Contract.Value (CurrencySymbol, TokenName, Value, valueOf, valueToCoin') +import Control.Monad.Error.Class (throwError) +import Control.Monad.Error.Class as E +import Control.Monad.Reader (ReaderT, ask, local, mapReaderT, runReaderT) +import Control.Monad.Trans.Class (lift) +import Ctl.Internal.Cardano.Types.Transaction + ( ExUnits + , Transaction + , _redeemers + , _witnessSet + ) +import Ctl.Internal.Contract.Monad (ContractEnv) +import Ctl.Internal.Metadata.FromMetadata (fromMetadata) +import Ctl.Internal.Metadata.MetadataType (class MetadataType, metadataLabel) +import Ctl.Internal.Plutus.Types.Transaction + ( _amount + , _datum + , _output + , _scriptRef + ) +import Ctl.Internal.Types.ByteArray (byteArrayToHex) +import Data.Array (foldr) +import Data.Array (fromFoldable, length, mapWithIndex, partition) as Array +import Data.BigInt (BigInt) +import Data.Either (Either(Right, Left), either) +import Data.Foldable (foldMap, null, sum) +import Data.Lens (non, to, traversed, view, (%~), (^.), (^..)) +import Data.Lens.Record (prop) +import Data.List (List(Cons, Nil)) +import Data.Map (filterKeys, lookup, values) as Map +import Data.Maybe (Maybe(Just, Nothing), maybe) +import Data.Newtype (class Newtype, unwrap) +import Data.String (trim) as String +import Data.String.Common (joinWith) as String +import Data.Tuple.Nested (type (/\), (/\)) +import Effect.Class (liftEffect) +import Effect.Exception (error, throw, try) +import Effect.Ref (Ref) +import Effect.Ref as Ref +import Type.Proxy (Proxy(Proxy)) + +-- | Monad allowing for accumulation of assertion failures. +type ContractAssertion (a :: Type) = + ReaderT (Ref (List ContractAssertionFailure)) Contract a + +-------------------------------------------------------------------------------- +-- Data types and functions for building assertion failures +-------------------------------------------------------------------------------- + +data ContractAssertionFailure + = CouldNotGetTxByHash TransactionHash + | CouldNotParseMetadata Label + | TransactionHasNoMetadata TransactionHash (Maybe Label) + | UnexpectedDatumInOutput (Labeled TransactionOutputWithRefScript) + (ExpectedActual OutputDatum) + | UnexpectedLovelaceDelta (Labeled Address) (ExpectedActual BigInt) + | UnexpectedMetadataValue Label (ExpectedActual String) + | UnexpectedRefScriptInOutput (Labeled TransactionOutputWithRefScript) + (ExpectedActual (Maybe ScriptRef)) + | UnexpectedTokenDelta (Labeled Address) TokenName (ExpectedActual BigInt) + | MaxExUnitsExceeded ExUnits ExUnits + | CustomFailure String + | SkippedTest String + +newtype ContractAssertionFailures = + ContractAssertionFailures (Array ContractAssertionFailure) + +derive instance Newtype (ContractAssertionFailures) _ + +instance Show ContractAssertionFailures where + show (ContractAssertionFailures failures) = + String.trim $ errorText <> warningText + where + isWarning :: ContractAssertionFailure -> Boolean + isWarning = case _ of + SkippedTest _ -> true + _ -> false + + { yes: warnings, no: errors } = Array.partition isWarning failures + + listFailures = String.joinWith "\n\n " + <<< Array.mapWithIndex (\ix elem -> show (ix + one) <> ". " <> show elem) + errorText = + if Array.length errors > 0 then + "The following `Contract` assertions have failed: \n " + <> listFailures errors + <> "\n\n" + else "" + warningText = + if Array.length warnings > 0 then + "The following `Contract` checks have been skipped due to an exception: \n\n " + <> + listFailures warnings + else "" + +instance Show ContractAssertionFailure where + show (CouldNotGetTxByHash txHash) = + "Could not get tx by hash " <> showTxHash txHash + + show (CouldNotParseMetadata mdLabel) = + "Could not parse " <> show mdLabel <> " metadata" + + show (TransactionHasNoMetadata txHash mdLabel) = + "Tx with id " <> showTxHash txHash <> " does not hold " + <> (maybe mempty (flip append " ") (show <$> mdLabel) <> "metadata") + + show (UnexpectedDatumInOutput txOutput expectedActual) = + "Unexpected datum in output " <> show txOutput <> show expectedActual + + show (UnexpectedLovelaceDelta addr expectedActual) = + "Unexpected lovelace delta at address " + <> (show addr <> show expectedActual) + + show (UnexpectedMetadataValue mdLabel expectedActual) = + "Unexpected " <> show mdLabel <> " metadata value" <> show expectedActual + + show (UnexpectedRefScriptInOutput txOutput expectedActual) = + "Unexpected reference script in output " + <> (show txOutput <> show expectedActual) + + show (UnexpectedTokenDelta addr tn expectedActual) = + "Unexpected token delta " <> show tn <> " at address " + <> (show addr <> show expectedActual) + + show (MaxExUnitsExceeded maxExUnits exUnits) = + "ExUnits limit exceeded: spent " <> show exUnits + <> ", but the limit is " + <> show maxExUnits + + show (CustomFailure msg) = msg + show (SkippedTest msg) = msg + +showTxHash :: TransactionHash -> String +showTxHash = byteArrayToHex <<< unwrap + +type Label = String + +data Labeled (a :: Type) = Labeled a (Maybe Label) + +label :: forall (a :: Type). a -> Label -> Labeled a +label x l = Labeled x (Just l) + +unlabel :: forall (a :: Type). Labeled a -> a +unlabel (Labeled x _) = x + +noLabel :: forall (a :: Type). a -> Labeled a +noLabel = flip Labeled Nothing + +instance Show a => Show (Labeled a) where + show (Labeled _ (Just l)) = l + show (Labeled x Nothing) = show x + +data ExpectedActual (a :: Type) = ExpectedActual a a + +derive instance Functor ExpectedActual + +instance Show a => Show (ExpectedActual a) where + show (ExpectedActual expected actual) = + " (Expected: " <> show expected <> ", Actual: " <> show actual <> ")" + +-------------------------------------------------------------------------------- +-- Different types of assertions, Assertion composition, Basic functions +-------------------------------------------------------------------------------- + +-- | An check that can run some initialization code before the `Contract` is run +-- | and check the results afterwards. It is used to implement assertions that +-- | require state monitoring, e.g. checking gains at address. +type ContractCheck a = + ContractAssertion a + -> ContractAssertion (ContractAssertion a /\ ContractAssertion Unit) + +-- | Create a check that simply asserts something about a `Contract` result. +-- | +-- | If a `Contract` throws an exception, the assertion is never checked, +-- | because the result is never computed. +assertionToCheck + :: forall (a :: Type) + . String + -> (a -> ContractAssertion Unit) + -> ContractCheck a +assertionToCheck description f contract = do + putRef /\ getRef <- tieRef + let + run = do + res <- contract + putRef res + finalize = do + getRef >>= case _ of + Nothing -> tellFailure $ SkippedTest description + Just res -> f res + pure $ run /\ finalize + +assertContract + :: ContractAssertionFailure + -> Boolean + -> ContractAssertion Unit +assertContract failure cond + | cond = pure unit + | otherwise = tellFailure failure + +assertContractMaybe + :: forall (a :: Type) + . ContractAssertionFailure + -> Maybe a + -> ContractAssertion a +assertContractMaybe msg = + maybe (liftEffect $ throw $ show msg) pure + +assertContractExpectedActual + :: forall (a :: Type) + . Eq a + => (ExpectedActual a -> ContractAssertionFailure) + -> a + -> a + -> ContractAssertion Unit +assertContractExpectedActual mkAssertionFailure expected actual = + assertContract (mkAssertionFailure $ ExpectedActual expected actual) + (expected == actual) + +-- | Accepts an array of checks and interprets them into a `Contract`. +runChecks + :: forall (a :: Type) (assertions :: Type) + . Array (ContractCheck a) + -> Contract a + -> Contract a +runChecks assertions contract = do + ref <- liftEffect $ Ref.new Nil + eiResult <- E.try $ + flip runReaderT ref go + failures <- liftEffect $ Ref.read ref + if null failures then either + (liftEffect <<< throwError <<< error <<< reportException) + pure + eiResult + else do + let + errorStr = case eiResult of + Left error -> reportException error + _ -> "" + errorReport = + String.trim + ( errorStr <> "\n\n" <> + show (ContractAssertionFailures $ Array.fromFoldable failures) + ) <> "\n" + -- error trace from the exception itself will be appended here + liftEffect $ throwError $ error errorReport + where + reportException error = "\n\nAn exception has been thrown: \n\n" <> show error + + wrapAssertion :: ContractCheck a -> ContractAssertion a -> ContractAssertion a + wrapAssertion assertion acc = do + run /\ finalize <- assertion acc + E.try run >>= case _ of + Left failure -> do + finalize + throwError failure + Right success -> do + finalize + pure success + + go :: ContractAssertion a + go = foldr wrapAssertion (lift contract) assertions + +tellFailure + :: ContractAssertionFailure -> ContractAssertion Unit +tellFailure failure = do + ask >>= liftEffect <<< Ref.modify_ (Cons failure) + +checkNewUtxosAtAddress + :: forall (a :: Type) + . Labeled Address + -> TransactionHash + -> (Array TransactionOutputWithRefScript -> ContractAssertion a) + -> ContractAssertion a +checkNewUtxosAtAddress addr txHash check = + lift (utxosAt $ unlabel addr) >>= \utxos -> + check $ Array.fromFoldable $ Map.values $ + Map.filterKeys (\oref -> (unwrap oref).transactionId == txHash) utxos + +-- | Sets a limit on `ExUnits` budget. All ExUnits values of all submitted transactions are combined. Transactions that are constructed, but not submitted, are not considered. +-- | The execution of the `Contract` will not be interrupted in case the `ExUnits` limit is reached. +checkExUnitsNotExceed + :: forall (a :: Type) + . ExUnits + -> ContractCheck a +checkExUnitsNotExceed maxExUnits contract = do + (ref :: Ref ExUnits) <- liftEffect $ Ref.new { mem: zero, steps: zero } + let + submitHook :: Transaction -> Effect Unit + submitHook tx = do + let + (newExUnits :: ExUnits) = sum $ tx ^.. + _witnessSet + <<< _redeemers + <<< non [] + <<< traversed + <<< to (unwrap >>> _.exUnits) + Ref.modify_ (add newExUnits) ref + + setSubmitHook :: ContractEnv -> ContractEnv + setSubmitHook = + prop (Proxy :: Proxy "hooks") <<< prop (Proxy :: Proxy "onSubmit") + -- Extend a hook action if it exists, or set it to `Just submitHook` + %~ maybe (Just submitHook) + \oldHook -> Just \tx -> do + -- ignore possible exception from the old hook + void $ try $ oldHook tx + submitHook tx + + finalize :: ContractAssertion Unit + finalize = do + exUnits <- liftEffect $ Ref.read ref + assertContract (MaxExUnitsExceeded maxExUnits exUnits) + (maxExUnits >= exUnits) + + pure (mapReaderT (local setSubmitHook) contract /\ finalize) + +valueAtAddress' + :: Labeled Address + -> ContractAssertion Value +valueAtAddress' = map (foldMap (view (_output <<< _amount))) <<< lift + <<< utxosAt + <<< unlabel + +-- | Arguments are: +-- | +-- | - a labeled address +-- | - a callback that implements the assertion, accepting `Contract` execution +-- | result, and values (before and after) +assertValueDeltaAtAddress + :: forall (a :: Type) + . Labeled Address + -> (a -> Value -> Value -> ContractAssertion Unit) + -> ContractCheck a +assertValueDeltaAtAddress addr check contract = do + valueBefore <- valueAtAddress' addr + ref <- liftEffect $ Ref.new Nothing + let + finalize = do + valueAfter <- valueAtAddress' addr + liftEffect (Ref.read ref) >>= case _ of + Nothing -> pure unit -- tellFailure $ CustomFailure "Contract did not run" + Just res -> check res valueBefore valueAfter + run = do + res <- contract + liftEffect $ Ref.write (Just res) ref + pure res + pure (run /\ finalize) + +assertLovelaceDeltaAtAddress + :: forall (a :: Type) + . Labeled Address + -> (a -> Contract BigInt) + -> (BigInt -> BigInt -> Boolean) + -> ContractCheck a +assertLovelaceDeltaAtAddress addr getExpected comp contract = do + assertValueDeltaAtAddress addr check contract + where + check :: a -> Value -> Value -> ContractAssertion Unit + check result valueBefore valueAfter = do + expected <- lift $ getExpected result + let + actual :: BigInt + actual = valueToCoin' valueAfter - valueToCoin' valueBefore + + unexpectedLovelaceDelta :: ContractAssertionFailure + unexpectedLovelaceDelta = + UnexpectedLovelaceDelta addr (ExpectedActual expected actual) + + assertContract unexpectedLovelaceDelta (comp actual expected) + pure unit + +-- | Requires that the computed amount of lovelace was gained at the address +-- | by calling the contract. +checkGainAtAddress + :: forall (a :: Type) + . Labeled Address + -> (a -> Contract BigInt) + -> ContractCheck a +checkGainAtAddress addr getMinGain = + assertLovelaceDeltaAtAddress addr getMinGain eq + +-- | Requires that the passed amount of lovelace was gained at the address +-- | by calling the contract. +checkGainAtAddress' + :: forall (a :: Type) + . Labeled Address + -> BigInt + -> ContractCheck a +checkGainAtAddress' addr minGain = + checkGainAtAddress addr (const $ pure minGain) + +-- | Requires that the computed amount of lovelace was lost at the address +-- | by calling the contract. +checkLossAtAddress + :: forall (a :: Type) + . Labeled Address + -> (a -> Contract BigInt) + -> ContractCheck a +checkLossAtAddress addr getMinLoss = + assertLovelaceDeltaAtAddress addr (map negate <<< getMinLoss) eq + +-- | Requires that the passed amount of lovelace was lost at the address +-- | by calling the contract. +checkLossAtAddress' + :: forall (a :: Type) + . Labeled Address + -> BigInt + -> ContractCheck a +checkLossAtAddress' addr minLoss = + checkLossAtAddress addr (const $ pure minLoss) + +checkTokenDeltaAtAddress + :: forall (a :: Type) + . Labeled Address + -> (CurrencySymbol /\ TokenName) + -> (a -> Contract BigInt) + -> (BigInt -> BigInt -> Boolean) + -> ContractCheck a +checkTokenDeltaAtAddress addr (cs /\ tn) getExpected comp contract = + assertValueDeltaAtAddress addr check contract + where + check :: a -> Value -> Value -> ContractAssertion Unit + check result valueBefore valueAfter = do + expected <- lift $ getExpected result + let + actual :: BigInt + actual = valueOf valueAfter cs tn - valueOf valueBefore cs tn + + unexpectedTokenDelta :: ContractAssertionFailure + unexpectedTokenDelta = + UnexpectedTokenDelta addr tn (ExpectedActual expected actual) + + assertContract unexpectedTokenDelta (comp actual expected) + +-- | Requires that the computed number of tokens was gained at the address +-- | by calling the contract. +checkTokenGainAtAddress + :: forall (a :: Type) + . Labeled Address + -> (CurrencySymbol /\ TokenName) + -> (a -> Contract BigInt) + -> ContractCheck a +checkTokenGainAtAddress addr token getMinGain = + checkTokenDeltaAtAddress addr token getMinGain eq + +-- | Requires that the passed number of tokens was gained at the address +-- | by calling the contract. +checkTokenGainAtAddress' + :: forall (a :: Type) + . Labeled Address + -> (CurrencySymbol /\ TokenName /\ BigInt) + -> ContractCheck a +checkTokenGainAtAddress' addr (cs /\ tn /\ minGain) = + checkTokenGainAtAddress addr (cs /\ tn) (const $ pure minGain) + +-- | Requires that the computed number of tokens was lost at the address +-- | by calling the contract. +checkTokenLossAtAddress + :: forall (a :: Type) + . Labeled Address + -> (CurrencySymbol /\ TokenName) + -> (a -> Contract BigInt) + -> ContractCheck a +checkTokenLossAtAddress addr token getMinLoss = + checkTokenDeltaAtAddress addr token (map negate <<< getMinLoss) eq + +-- | Requires that the passed number of tokens was lost at the address +-- | by calling the contract. +checkTokenLossAtAddress' + :: forall (a :: Type) + . Labeled Address + -> (CurrencySymbol /\ TokenName /\ BigInt) + -> ContractCheck a +checkTokenLossAtAddress' addr (cs /\ tn /\ minLoss) = + checkTokenLossAtAddress addr (cs /\ tn) (const $ pure minLoss) + +-- | Requires that the transaction output contains the specified datum or +-- | datum hash. +assertOutputHasDatum + :: OutputDatum + -> Labeled TransactionOutputWithRefScript + -> ContractAssertion Unit +assertOutputHasDatum expectedDatum txOutput = do + let actualDatum = unlabel txOutput ^. _output <<< _datum + assertContractExpectedActual (UnexpectedDatumInOutput txOutput) + expectedDatum + actualDatum + +-- | Requires that the transaction output contains the specified reference +-- | script. +assertOutputHasRefScript + :: ScriptRef + -> Labeled TransactionOutputWithRefScript + -> ContractAssertion Unit +assertOutputHasRefScript expectedRefScript txOutput = do + let actualRefScript = unlabel txOutput ^. _scriptRef + assertContractExpectedActual (UnexpectedRefScriptInOutput txOutput) + (Just expectedRefScript) + actualRefScript + +tieRef + :: forall (a :: Type) + . ContractAssertion + ((a -> ContractAssertion a) /\ ContractAssertion (Maybe a)) +tieRef = do + ref <- liftEffect $ Ref.new Nothing + let + putResult result = do + liftEffect $ Ref.write (Just result) ref + pure result + getResult = liftEffect (Ref.read ref) + pure (putResult /\ getResult) + +assertTxHasMetadata + :: forall (metadata :: Type) (a :: Type) + . MetadataType metadata + => Eq metadata + => Show metadata + => Label + -> TransactionHash + -> metadata + -> ContractAssertion Unit +assertTxHasMetadata mdLabel txHash expectedMetadata = do + generalMetadata <- + assertContractMaybe (TransactionHasNoMetadata txHash Nothing) + =<< lift (getTxMetadata txHash) + + rawMetadata <- + assertContractMaybe (TransactionHasNoMetadata txHash (Just mdLabel)) + ( Map.lookup (metadataLabel (Proxy :: Proxy metadata)) + (unwrap generalMetadata) + ) + + (metadata :: metadata) <- + assertContractMaybe (CouldNotParseMetadata mdLabel) + (fromMetadata rawMetadata) + + let expectedActual = show <$> ExpectedActual expectedMetadata metadata + assertContract (UnexpectedMetadataValue mdLabel expectedActual) + (metadata == expectedMetadata) diff --git a/src/Contract/Test/Utils.purs b/src/Contract/Test/Utils.purs index 764f03500d..23a2bff7de 100644 --- a/src/Contract/Test/Utils.purs +++ b/src/Contract/Test/Utils.purs @@ -1,692 +1,15 @@ -- | This module provides an extensible interface for making various -- | assertions about `Contract`s. -module Contract.Test.Utils - ( ContractAssertionFailure - ( CouldNotGetTxByHash - , CouldNotParseMetadata - , CustomFailure - , MaxExUnitsExceeded - , TransactionHasNoMetadata - , UnexpectedDatumInOutput - , UnexpectedLovelaceDelta - , UnexpectedMetadataValue - , UnexpectedRefScriptInOutput - , UnexpectedTokenDelta - ) - , ContractTestM - , ContractWrapAssertion - , ExpectedActual(ExpectedActual) - , Label - , Labeled(Labeled) - , assertContractExpectedActual - , assertContractTestMaybe - , assertContractTestM - , assertExUnitsNotExceed - , assertGainAtAddress - , assertGainAtAddress' - , assertLossAtAddress - , assertLossAtAddress' - , assertLovelaceDeltaAtAddress - , assertOutputHasDatum - , assertOutputHasRefScript - , assertTokenDeltaAtAddress - , assertTokenGainAtAddress - , assertTokenGainAtAddress' - , assertTokenLossAtAddress - , assertTokenLossAtAddress' - , assertTxHasMetadata - , assertValueDeltaAtAddress - , checkNewUtxosAtAddress - -- -- , checkOutputHasDatum - -- -- , checkOutputHasRefScript - -- -- , checkTxHasMetadata - , label - , exitCode - , interruptOnSignal - , unlabel - , utxosAtAddress - , valueAtAddress - , withAssertions - , mkSimpleAssertion - ) where +module Contract.Test.Utils (exitCode, interruptOnSignal) where import Prelude -import Contract.Address (Address) -import Contract.Monad (Contract, launchAff_, throwContractError) -import Contract.PlutusData (OutputDatum) -import Contract.Prelude (Effect) -import Contract.Transaction - ( ScriptRef - , TransactionHash - , TransactionOutputWithRefScript - , getTxMetadata - ) -import Contract.Utxos (utxosAt) -import Contract.Value (CurrencySymbol, TokenName, Value, valueOf, valueToCoin') -import Control.Monad.Error.Class (throwError) -import Control.Monad.Error.Class as E -import Control.Monad.Reader (ReaderT, ask, local, mapReaderT, runReaderT) -import Control.Monad.Trans.Class (lift) -import Ctl.Internal.Cardano.Types.Transaction - ( ExUnits - , Transaction - , _redeemers - , _witnessSet - ) -import Ctl.Internal.Contract.Monad (ContractEnv) -import Ctl.Internal.Metadata.FromMetadata (fromMetadata) -import Ctl.Internal.Metadata.MetadataType (class MetadataType, metadataLabel) -import Ctl.Internal.Plutus.Types.Transaction - ( UtxoMap - , _amount - , _datum - , _output - , _scriptRef - ) -import Ctl.Internal.Types.ByteArray (byteArrayToHex) -import Data.Array (foldr) -import Data.Array (fromFoldable, mapWithIndex) as Array -import Data.BigInt (BigInt) -import Data.Either (Either(Right, Left)) -import Data.Foldable (foldMap, null, sum) -import Data.Lens (non, to, traversed, view, (%~), (^.), (^..)) -import Data.Lens.Record (prop) -import Data.List (List(Cons, Nil)) -import Data.Map (filterKeys, lookup, values) as Map -import Data.Maybe (Maybe(Just, Nothing), maybe) -import Data.Newtype (class Newtype, unwrap) import Data.Posix.Signal (Signal) import Data.Posix.Signal as Signal -import Data.String.Common (joinWith) as String -import Data.Traversable (traverse_) -import Data.Tuple.Nested (type (/\), (/\)) -import Effect.Aff (Fiber, killFiber) -import Effect.Class (liftEffect) -import Effect.Exception (error, throw, try) -import Effect.Ref (Ref) -import Effect.Ref as Ref +import Effect (Effect) +import Effect.Aff (Fiber, killFiber, launchAff_) +import Effect.Exception (error) import Node.Process as Process -import Type.Proxy (Proxy(Proxy)) - --------------------------------------------------------------------------------- --- `ContractTestM` and `ContractAssertionM` monads with related functions --------------------------------------------------------------------------------- - --- | Monad allowing for accumulation of assertion failures. Should be used in --- | conjunction with `ContractAssertionM`. -type ContractTestM (a :: Type) = - ReaderT (Ref (List ContractAssertionFailure)) Contract a - --- -- | Represents computations which may fail with `ContractAssertionFailure`, --- -- | with the capability of storing some intermediate result, usually the result --- -- | of the contract under test. --- -- | --- -- | Particularly useful for assertions that can control when the contract is --- -- | run (`ContractWrapAssertion`s). So in case of a failure after the contract --- -- | has already been executed, we can return the result of the contract, thus --- -- | preventing the failure of subsequent assertions. --- type ContractAssertionM (w :: Type) (a :: Type) = --- -- ExceptT ContractAssertionFailure --- -- (Writer (Maybe (Last w)) (ContractTestM)) a --- ExceptT ContractAssertionFailure --- ( WriterT (Maybe (Last w)) --- (WriterT (Array ContractAssertionFailure) (Contract)) --- ) --- a - --- runContractAssertionM --- :: forall (a :: Type) --- . ContractTestM a --- -> ContractAssertionM a a --- -> ContractTestM a --- runContractAssertionM contract wrappedContract = --- runWriterT (runExceptT wrappedContract) >>= case _ of --- Right result /\ _ -> --- pure result --- Left failure /\ result -> --- tell [ failure ] *> maybe contract (pure <<< unwrap) result - --- runContractAssertionM' --- :: ContractAssertionM Unit Unit --- -> ContractTestM Unit --- runContractAssertionM' = runContractAssertionM (pure unit) - --- liftContractTestM --- :: forall (w :: Type) (a :: Type) --- . ContractTestM a --- -> ContractAssertionM w a --- liftContractTestM = lift <<< lift - --------------------------------------------------------------------------------- --- Data types and functions for building assertion failures --------------------------------------------------------------------------------- - -data ContractAssertionFailure - = CouldNotGetTxByHash TransactionHash - | CouldNotParseMetadata Label - | TransactionHasNoMetadata TransactionHash (Maybe Label) - | UnexpectedDatumInOutput (Labeled TransactionOutputWithRefScript) - (ExpectedActual OutputDatum) - | UnexpectedLovelaceDelta (Labeled Address) (ExpectedActual BigInt) - | UnexpectedMetadataValue Label (ExpectedActual String) - | UnexpectedRefScriptInOutput (Labeled TransactionOutputWithRefScript) - (ExpectedActual (Maybe ScriptRef)) - | UnexpectedTokenDelta (Labeled Address) TokenName (ExpectedActual BigInt) - | MaxExUnitsExceeded ExUnits ExUnits - | CustomFailure String - -newtype ContractAssertionFailures = - ContractAssertionFailures (Array ContractAssertionFailure) - -derive instance Newtype (ContractAssertionFailures) _ - -instance Show ContractAssertionFailures where - show = - append "The following `Contract` assertions failed: \n " - <<< String.joinWith "\n\n " - <<< Array.mapWithIndex (\ix elem -> show (ix + one) <> ". " <> show elem) - <<< unwrap - -instance Show ContractAssertionFailure where - show (CouldNotGetTxByHash txHash) = - "Could not get tx by hash " <> showTxHash txHash - - show (CouldNotParseMetadata mdLabel) = - "Could not parse " <> show mdLabel <> " metadata" - - show (TransactionHasNoMetadata txHash mdLabel) = - "Tx with id " <> showTxHash txHash <> " does not hold " - <> (maybe mempty (flip append " ") (show <$> mdLabel) <> "metadata") - - show (UnexpectedDatumInOutput txOutput expectedActual) = - "Unexpected datum in output " <> show txOutput <> show expectedActual - - show (UnexpectedLovelaceDelta addr expectedActual) = - "Unexpected lovelace delta at address " - <> (show addr <> show expectedActual) - - show (UnexpectedMetadataValue mdLabel expectedActual) = - "Unexpected " <> show mdLabel <> " metadata value" <> show expectedActual - - show (UnexpectedRefScriptInOutput txOutput expectedActual) = - "Unexpected reference script in output " - <> (show txOutput <> show expectedActual) - - show (UnexpectedTokenDelta addr tn expectedActual) = - "Unexpected token delta " <> show tn <> " at address " - <> (show addr <> show expectedActual) - - show (MaxExUnitsExceeded maxExUnits exUnits) = - "ExUnits limit exceeded: spent " <> show exUnits - <> ", but the limit is " - <> show maxExUnits - - show (CustomFailure msg) = msg - -showTxHash :: TransactionHash -> String -showTxHash = byteArrayToHex <<< unwrap - -type Label = String - -data Labeled (a :: Type) = Labeled a (Maybe Label) - -label :: forall (a :: Type). a -> Label -> Labeled a -label x l = Labeled x (Just l) - -unlabel :: forall (a :: Type). Labeled a -> a -unlabel (Labeled x _) = x - -noLabel :: forall (a :: Type). a -> Labeled a -noLabel = flip Labeled Nothing - -instance Show a => Show (Labeled a) where - show (Labeled _ (Just l)) = l - show (Labeled x Nothing) = show x - -data ExpectedActual (a :: Type) = ExpectedActual a a - -derive instance Functor ExpectedActual - -instance Show a => Show (ExpectedActual a) where - show (ExpectedActual expected actual) = - " (Expected: " <> show expected <> ", Actual: " <> show actual <> ")" - --------------------------------------------------------------------------------- --- Different types of assertions, Assertion composition, Basic functions --------------------------------------------------------------------------------- - --- | An assertion that can control when the contract is run. -type ContractWrapAssertion a = - ContractTestM a -> ContractTestM (ContractTestM Unit /\ ContractTestM a) - --- | Create an assertion that simply checks a `Contract` result. --- | If a given `Contract` throws an exception, the assertion is never checked. -mkSimpleAssertion - :: forall (a :: Type). (a -> ContractTestM Unit) -> ContractWrapAssertion a -mkSimpleAssertion f contract = do - ref <- liftEffect $ Ref.new Nothing - let - run = do - res <- contract - liftEffect $ Ref.write (Just res) ref - pure res - finalize = do - liftEffect (Ref.read ref) >>= traverse_ f - pure $ finalize /\ run - -assertContractTestM - :: forall (w :: Type) - . ContractAssertionFailure - -> Boolean - -> ContractTestM Unit -assertContractTestM failure cond - | cond = pure unit - | otherwise = tellFailure failure - -assertContractTestMaybe - :: forall (w :: Type) (a :: Type) - . ContractAssertionFailure - -> Maybe a - -> ContractTestM a -assertContractTestMaybe msg = - maybe (liftEffect $ throw $ show msg) pure - -assertContractExpectedActual - :: forall (a :: Type) - . Eq a - => (ExpectedActual a -> ContractAssertionFailure) - -> a - -> a - -> ContractTestM Unit -assertContractExpectedActual mkAssertionFailure expected actual = - assertContractTestM (mkAssertionFailure $ ExpectedActual expected actual) - (expected == actual) - -withAssertions - :: forall (a :: Type) (assertions :: Type) - . Array (ContractWrapAssertion a) - -> Contract a - -> Contract a -withAssertions assertions contract = do - ref <- liftEffect $ Ref.new Nil - result <- - flip runReaderT ref go - failures <- liftEffect $ Ref.read ref - if null failures then pure result - else throwContractError - (ContractAssertionFailures $ Array.fromFoldable failures) - where - go :: ContractTestM a - go = foldr - ( \assertion acc -> do - finalize /\ res <- assertion acc - E.try res >>= case _ of - Left failure -> do - finalize - throwError failure - Right success -> do - finalize - pure (success :: a) - ) - (lift contract :: ContractTestM a) - assertions - --- mkCheckFromAssertion --- :: forall (w :: Type) (a :: Type) --- . ContractAssertionM w a --- -> Contract Boolean --- mkCheckFromAssertion = --- map (fst <<< fst) <<< runWriterT <<< runWriterT <<< map isRight <<< runExceptT - --------------------------------------------------------------------------------- --- Assertions and checks --------------------------------------------------------------------------------- - -utxosAtAddress - :: forall (w :: Type) - . Labeled Address - -> ContractTestM UtxoMap -utxosAtAddress = lift <<< utxosAt <<< unlabel - -valueAtAddress - :: forall (w :: Type) - . Labeled Address - -> ContractTestM Value -valueAtAddress = - map (foldMap (view (_output <<< _amount))) <<< utxosAtAddress - -tellFailure - :: ContractAssertionFailure -> ContractTestM Unit -tellFailure failure = do - ask >>= liftEffect <<< Ref.modify_ (Cons failure) - -checkNewUtxosAtAddress - :: forall (w :: Type) (a :: Type) - . Labeled Address - -> TransactionHash - -> (Array TransactionOutputWithRefScript -> ContractTestM a) - -> ContractTestM a -checkNewUtxosAtAddress addr txHash check = - utxosAtAddress addr >>= \utxos -> - check $ Array.fromFoldable $ Map.values $ - Map.filterKeys (\oref -> (unwrap oref).transactionId == txHash) utxos - --- | Sets a limit on `ExUnits` budget. All ExUnits values of all submitted transactions are combined. Transactions that are constructed, but not submitted, are not considered. --- | The execution of the `Contract` will not be interrupted in case the `ExUnits` limit is reached. -assertExUnitsNotExceed - :: forall (a :: Type) - . ExUnits - -> ContractWrapAssertion a -assertExUnitsNotExceed maxExUnits contract = do - (ref :: Ref ExUnits) <- liftEffect $ Ref.new { mem: zero, steps: zero } - let - submitHook :: Transaction -> Effect Unit - submitHook tx = do - let - (newExUnits :: ExUnits) = sum $ tx ^.. - _witnessSet - <<< _redeemers - <<< non [] - <<< traversed - <<< to (unwrap >>> _.exUnits) - Ref.modify_ (add newExUnits) ref - - setSubmitHook :: ContractEnv -> ContractEnv - setSubmitHook = - prop (Proxy :: Proxy "hooks") <<< prop (Proxy :: Proxy "onSubmit") - -- Extend a hook action if it exists, or set it to `Just submitHook` - %~ maybe (Just submitHook) - \oldHook -> Just \tx -> do - -- ignore possible exception from the old hook - void $ try $ oldHook tx - submitHook tx - - finalize :: ContractTestM Unit - finalize = do - exUnits <- liftEffect $ Ref.read ref - assertContractTestM (MaxExUnitsExceeded maxExUnits exUnits) - (maxExUnits >= exUnits) - - pure (finalize /\ mapReaderT (local setSubmitHook) contract) - -valueAtAddress' - :: forall (w :: Type) - . Labeled Address - -> ContractTestM Value -valueAtAddress' = map (foldMap (view (_output <<< _amount))) <<< lift - <<< utxosAt - <<< unlabel - --- | Arguments are: --- | --- | - a labeled address --- | - a callback that implements the assertion, accepting `Contract` execution --- | result, and values (before and after) -assertValueDeltaAtAddress - :: forall (a :: Type) - . Labeled Address - -> (a -> Contract BigInt) - -> (a -> Value -> Value -> ContractTestM Unit) - -> ContractWrapAssertion a -assertValueDeltaAtAddress addr getExpected check contract = do - valueBefore <- valueAtAddress' addr - ref <- liftEffect $ Ref.new Nothing - let - finalize = do - valueAfter <- valueAtAddress' addr - liftEffect (Ref.read ref) >>= case _ of - Nothing -> pure unit -- tellFailure $ CustomFailure "Contract did not run" - Just res -> check res valueBefore valueAfter - contract' = do - res <- contract - liftEffect $ Ref.write (Just res) ref - pure res - pure (finalize /\ contract') - -assertLovelaceDeltaAtAddress - :: forall (a :: Type) - . Labeled Address - -> (a -> Contract BigInt) - -> (BigInt -> BigInt -> Boolean) - -> ContractWrapAssertion a -assertLovelaceDeltaAtAddress addr getExpected comp contract = do - assertValueDeltaAtAddress addr getExpected check contract - -- valueBefore <- valueAtAddress' addr - -- ref <- liftEffect $ Ref.new Nothing - -- let - -- finalize = do - -- valueAfter <- valueAtAddress' addr - -- liftEffect (Ref.read ref) >>= case _ of - -- Nothing -> pure unit -- tellFailure $ CustomFailure "Contract did not run" - -- Just res -> check res valueBefore valueAfter - -- contract' = do - -- res <- contract - -- liftEffect $ Ref.write (Just res) ref - -- pure res - -- pure (finalize /\ contract') - where - check :: a -> Value -> Value -> ContractTestM Unit - check result valueBefore valueAfter = do - expected <- lift $ getExpected result - let - actual :: BigInt - actual = valueToCoin' valueAfter - valueToCoin' valueBefore - - unexpectedLovelaceDelta :: ContractAssertionFailure - unexpectedLovelaceDelta = - UnexpectedLovelaceDelta addr (ExpectedActual expected actual) - - assertContractTestM unexpectedLovelaceDelta (comp actual expected) - pure unit - --- | Requires that the computed amount of lovelace was gained at the address --- | by calling the contract. -assertGainAtAddress - :: forall (a :: Type) - . Labeled Address - -> (a -> Contract BigInt) - -> ContractWrapAssertion a -assertGainAtAddress addr getMinGain = - assertLovelaceDeltaAtAddress addr getMinGain eq - --- | Requires that the passed amount of lovelace was gained at the address --- | by calling the contract. -assertGainAtAddress' - :: forall (a :: Type) - . Labeled Address - -> BigInt - -> ContractWrapAssertion a -assertGainAtAddress' addr minGain = - assertGainAtAddress addr (const $ pure minGain) - --- | Requires that the computed amount of lovelace was lost at the address --- | by calling the contract. -assertLossAtAddress - :: forall (a :: Type) - . Labeled Address - -> (a -> Contract BigInt) - -> ContractWrapAssertion a -assertLossAtAddress addr getMinLoss = - assertLovelaceDeltaAtAddress addr (map negate <<< getMinLoss) eq - --- | Requires that the passed amount of lovelace was lost at the address --- | by calling the contract. -assertLossAtAddress' - :: forall (a :: Type) - . Labeled Address - -> BigInt - -> ContractWrapAssertion a -assertLossAtAddress' addr minLoss = - assertLossAtAddress addr (const $ pure minLoss) - -assertTokenDeltaAtAddress - :: forall (a :: Type) - . Labeled Address - -> (CurrencySymbol /\ TokenName) - -> (a -> Contract BigInt) - -> (BigInt -> BigInt -> Boolean) - -> ContractWrapAssertion a -assertTokenDeltaAtAddress addr (cs /\ tn) getExpected comp contract = - assertValueDeltaAtAddress addr getExpected check contract - where - check :: a -> Value -> Value -> ContractTestM Unit - check result valueBefore valueAfter = do - expected <- lift $ getExpected result - let - actual :: BigInt - actual = valueOf valueAfter cs tn - valueOf valueBefore cs tn - - unexpectedTokenDelta :: ContractAssertionFailure - unexpectedTokenDelta = - UnexpectedTokenDelta addr tn (ExpectedActual expected actual) - - assertContractTestM unexpectedTokenDelta (comp actual expected) - --- | Requires that the computed number of tokens was gained at the address --- | by calling the contract. -assertTokenGainAtAddress - :: forall (a :: Type) - . Labeled Address - -> (CurrencySymbol /\ TokenName) - -> (a -> Contract BigInt) - -> ContractWrapAssertion a -assertTokenGainAtAddress addr token getMinGain = - assertTokenDeltaAtAddress addr token getMinGain eq - --- | Requires that the passed number of tokens was gained at the address --- | by calling the contract. -assertTokenGainAtAddress' - :: forall (a :: Type) - . Labeled Address - -> (CurrencySymbol /\ TokenName /\ BigInt) - -> ContractWrapAssertion a -assertTokenGainAtAddress' addr (cs /\ tn /\ minGain) = - assertTokenGainAtAddress addr (cs /\ tn) (const $ pure minGain) - --- | Requires that the computed number of tokens was lost at the address --- | by calling the contract. -assertTokenLossAtAddress - :: forall (a :: Type) - . Labeled Address - -> (CurrencySymbol /\ TokenName) - -> (a -> Contract BigInt) - -> ContractWrapAssertion a -assertTokenLossAtAddress addr token getMinLoss = - assertTokenDeltaAtAddress addr token (map negate <<< getMinLoss) eq - --- | Requires that the passed number of tokens was lost at the address --- | by calling the contract. -assertTokenLossAtAddress' - :: forall (a :: Type) - . Labeled Address - -> (CurrencySymbol /\ TokenName /\ BigInt) - -> ContractWrapAssertion a -assertTokenLossAtAddress' addr (cs /\ tn /\ minLoss) = - assertTokenLossAtAddress addr (cs /\ tn) (const $ pure minLoss) - -assertOutputHasDatumImpl - :: OutputDatum - -> Labeled TransactionOutputWithRefScript - -> ContractTestM Unit -assertOutputHasDatumImpl expectedDatum txOutput = do - let actualDatum = unlabel txOutput ^. _output <<< _datum - assertContractExpectedActual (UnexpectedDatumInOutput txOutput) - expectedDatum - actualDatum - --- | Requires that the transaction output contains the specified datum or --- | datum hash. -assertOutputHasDatum - :: OutputDatum - -> Labeled TransactionOutputWithRefScript - -> ContractTestM Unit -assertOutputHasDatum expectedDatum = -- TODO: simplify - - assertOutputHasDatumImpl expectedDatum - --- -- | Checks whether the transaction output contains the specified datum or --- -- | datum hash. --- checkOutputHasDatum --- :: OutputDatum --- -> TransactionOutputWithRefScript --- -> Contract Boolean --- checkOutputHasDatum expectedDatum txOutput = --- mkCheckFromAssertion $ --- assertOutputHasDatumImpl expectedDatum (noLabel txOutput) - --- assertOutputHasRefScriptImpl --- :: ScriptRef --- -> Labeled TransactionOutputWithRefScript --- -> ContractAssertionM Unit Unit --- assertOutputHasRefScriptImpl expectedRefScript txOutput = do --- let actualRefScript = unlabel txOutput ^. _scriptRef --- assertContractExpectedActual (UnexpectedRefScriptInOutput txOutput) --- (Just expectedRefScript) --- actualRefScript - --- | Requires that the transaction output contains the specified reference --- | script. -assertOutputHasRefScript - :: ScriptRef - -> Labeled TransactionOutputWithRefScript - -> ContractTestM Unit -assertOutputHasRefScript expectedRefScript txOutput = do - let actualRefScript = unlabel txOutput ^. _scriptRef - assertContractExpectedActual (UnexpectedRefScriptInOutput txOutput) - (Just expectedRefScript) - actualRefScript - --- -- | Checks whether the transaction output contains the specified reference --- -- | script. --- checkOutputHasRefScript --- :: ScriptRef --- -> TransactionOutputWithRefScript --- -> Contract Boolean --- checkOutputHasRefScript expectedRefScript txOutput = --- mkCheckFromAssertion $ --- assertOutputHasRefScriptImpl expectedRefScript (noLabel txOutput) - -assertTxHasMetadata - :: forall (a :: Type) - . MetadataType a - => Eq a - => Show a - => Label - -> TransactionHash - -> a - -> ContractWrapAssertion a -assertTxHasMetadata mdLabel txHash expectedMetadata contract = do - pure (finalize /\ contract) - where - finalize = do - generalMetadata <- - assertContractTestMaybe (TransactionHasNoMetadata txHash Nothing) - =<< lift (getTxMetadata txHash) - - rawMetadata <- - assertContractTestMaybe (TransactionHasNoMetadata txHash (Just mdLabel)) - (Map.lookup (metadataLabel (Proxy :: Proxy a)) (unwrap generalMetadata)) - - (metadata :: a) <- - assertContractTestMaybe (CouldNotParseMetadata mdLabel) - (fromMetadata rawMetadata) - - let expectedActual = show <$> ExpectedActual expectedMetadata metadata - assertContractTestM (UnexpectedMetadataValue mdLabel expectedActual) - (metadata == expectedMetadata) - --- -- | Checks whether the transaction contains the specified metadata. --- checkTxHasMetadata --- :: forall (a :: Type) --- . MetadataType a --- => Eq a --- => Show a --- => TransactionHash --- -> a --- -> Contract Boolean --- checkTxHasMetadata txHash = --- mkCheckFromAssertion <<< assertTxHasMetadataImpl mempty txHash -------------------------------------------------------------------------------- -- function to cancel aff fibers on signal From 73fe71e7fae4047213f6070d5114bd047a50edc2 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Wed, 11 Jan 2023 23:00:36 +0400 Subject: [PATCH 269/373] Improve the interface of `runChecks`, add doc/test-utils.md --- README.md | 1 + doc/test-utils.md | 90 ++++++++++++++++++++++++++ examples/BalanceTxConstraints.purs | 2 +- examples/ContractTestUtils.purs | 3 +- examples/OneShotMinting.purs | 3 +- examples/PaysWithDatum.purs | 3 +- examples/PlutusV2/ReferenceInputs.purs | 2 +- src/Contract/Test/Assert.purs | 25 +++---- 8 files changed, 112 insertions(+), 17 deletions(-) create mode 100644 doc/test-utils.md diff --git a/README.md b/README.md index 2533a36bfb..068310517f 100644 --- a/README.md +++ b/README.md @@ -38,6 +38,7 @@ Please explore our documentation to discover how to use CTL, how to set up its r - [Migrating from Plutus to CTL](./doc/plutus-comparison.md) - [Testing contracts with Plutip](./doc/plutip-testing.md) - [End-to-end testing with headless browsers](./doc/e2e-testing.md) +- [Utilities for testing](./doc/test-utils.md) - [CIP-25 NFT standard support](./doc/cip-25-nfts.md) - [Transaction balancing](./doc/balancing.md) - [Transaction chaining](./doc/tx-chaining.md) diff --git a/doc/test-utils.md b/doc/test-utils.md new file mode 100644 index 0000000000..75da2010ea --- /dev/null +++ b/doc/test-utils.md @@ -0,0 +1,90 @@ + + + +- [CTL utilities for testing](#ctl-utilities-for-testing) + - [Assertions](#assertions) + - [Checks](#checks) + - [Examples](#examples) + + + +## CTL utilities for testing + +`Contract.Test.Assert` module provides a DSL for assertions that accumulate error messages, instead of exiting early after the first failure. + +There are two kinds of tests: + +- `ContractAssertion` type: assertions that can raise recoverable errors with `tellFailure` + +- `ContractCheck` type: Checks can inspect the state both before and after `Contract` execution, allowing to monitor for effects, e.g. monetary gains/losses at address + +`runChecks` function accepts an array of checks and a `Contract` action to run, lifted to `ContractAssertion` to allow for assertion accumulation (lifting can be done with `Control.Monad.Trans.Class.lift`): + +```purescript +runChecks + :: forall (a :: Type) + . Array (ContractCheck a) + -> ContractAssertion a + -> Contract a +``` + +### Assertions + +To convert an assertion into a `ContractCheck`, `Contract.Test.Assert.assertionToCheck` can be used: + +```purescript +assertionToCheck + :: forall (a :: Type) + . String + -> (a -> ContractAssertion Unit) + -> ContractCheck a +``` + +The first argument is a descriptive message that will be printed in case there is an exception thrown inside the `Contract` that is being tested. This is done because in case of an exception there's no way to get the result value of type `a`. For better developer experience all the tests skipped due to the exception will still be mentioned in the report, e.g. [for this example](../examples/ContractTestUtils.purs): + +``` + ✗ Examples.ContractTestUtils: + + Error: An exception has been thrown: + +Error: (some error message) + at Object.exports.error (/home/me/c/cardano-transaction-lib/output/Effect.Exception/foreign.js:8:10) + at Object.$$throw [as throw] (/home/me/c/cardano-transaction-lib/output/Effect.Exception/index.js:18:45) + at /home/me/c/cardano-transaction-lib/output/Ctl.Examples.ContractTestUtils/index.js:131:506 + at /home/me/c/cardano-transaction-lib/output/Control.Monad.Reader.Trans/index.js:108:34 + at run (/home/me/c/cardano-transaction-lib/output/Effect.Aff/foreign.js:278:22) + at /home/me/c/cardano-transaction-lib/output/Effect.Aff/foreign.js:348:19 + at drain (/home/me/c/cardano-transaction-lib/output/Effect.Aff/foreign.js:120:9) + at Object.enqueue (/home/me/c/cardano-transaction-lib/output/Effect.Aff/foreign.js:141:11) + at /home/me/c/cardano-transaction-lib/output/Effect.Aff/foreign.js:339:27 + at /home/me/c/cardano-transaction-lib/output/Effect.Aff.Compat/index.js:18:55 + +The following `Contract` checks have been skipped due to an exception: + + 1. Sender's output has a datum + + 2. Output has a reference script + + 3. Contains CIP-25 metadata +``` + +### Checks + +`ContractCheck` is defined as follows: + +``` +type ContractCheck a = + ContractAssertion a + -> ContractAssertion (ContractAssertion a /\ ContractAssertion Unit) +``` + +- The argument is the `Contract` to be tested itself +- The outer `ContractAssertion` can perform effects to initialize internal assertion state (e.g. creation of `Ref`s that can be used by actions in the tuple) +- The first component of the tuple is the `Contract` that is supposed to be executed. It can be modified in the outer `ContractAssertion` action, but most checks would simply return it unchanged. +- The second component of the tuple is a finalization action, that is executed after the first component is run, regardless of whether the result of execution was success or an exception. This allows to implement checks that inspect the state change before and after, as well as the mechanism of skipped assertions reporting. + +### Examples + +Particular values can be constructed with utility functions, as demonstrated in the [ContractTestUtils example](../examples/ContractTestUtils.purs) (see `mkAssertions`). + +All the functions require `Labeled` arguments, that can be constructed with `label` function; or `noLabel`, if descriptive names in error messages are not needed. diff --git a/examples/BalanceTxConstraints.purs b/examples/BalanceTxConstraints.purs index 75c34f46f4..fdbe92d120 100644 --- a/examples/BalanceTxConstraints.purs +++ b/examples/BalanceTxConstraints.purs @@ -151,7 +151,7 @@ contract (ContractParams p) = do <> BalanceTxConstraints.mustSendChangeToAddress bobAddress <> BalanceTxConstraints.mustNotSpendUtxoWithOutRef nonSpendableOref - void $ runChecks checks do + void $ runChecks checks $ lift do unbalancedTx <- liftedE $ Lookups.mkUnbalancedTx lookups constraints diff --git a/examples/ContractTestUtils.purs b/examples/ContractTestUtils.purs index 5e0a9e550b..2e4961f5e0 100644 --- a/examples/ContractTestUtils.purs +++ b/examples/ContractTestUtils.purs @@ -60,6 +60,7 @@ import Contract.TxConstraints as Constraints import Contract.Utxos (utxosAt) import Contract.Value (CurrencySymbol, TokenName, Value) import Contract.Value (lovelaceValueOf, singleton) as Value +import Control.Monad.Trans.Class (lift) import Ctl.Examples.Helpers (mustPayToPubKeyStakeAddress) as Helpers import Data.Array (head) import Data.BigInt (BigInt) @@ -156,7 +157,7 @@ contract params@(ContractParams p) = do lookups = Lookups.mintingPolicy p.mintingPolicy checks <- mkChecks params - void $ runChecks checks do + void $ runChecks checks $ lift do unbalancedTx <- liftedE $ Lookups.mkUnbalancedTx lookups constraints unbalancedTxWithMetadata <- setTxMetadata unbalancedTx p.txMetadata balancedTx <- liftedE $ balanceTx unbalancedTxWithMetadata diff --git a/examples/OneShotMinting.purs b/examples/OneShotMinting.purs index 212d4d676a..0347adefb8 100644 --- a/examples/OneShotMinting.purs +++ b/examples/OneShotMinting.purs @@ -51,6 +51,7 @@ import Contract.Utxos (utxosAt) import Contract.Value (CurrencySymbol, TokenName) import Contract.Value (singleton) as Value import Control.Monad.Error.Class (liftMaybe) +import Control.Monad.Trans.Class (lift) import Ctl.Examples.Helpers (mkCurrencySymbol, mkTokenName) as Helpers import Data.Array (head) import Data.Array (head, singleton) as Array @@ -113,7 +114,7 @@ mkContractWithAssertions exampleName mkMintingPolicy = do <> Lookups.unspentOutputs utxos let checks = mkChecks ownAddress (cs /\ tn /\ one) - void $ runChecks checks do + void $ runChecks checks $ lift do { txHash, txFinalFee } <- submitTxFromConstraintsReturningFee lookups constraints logInfo' $ "Tx ID: " <> show txHash diff --git a/examples/PaysWithDatum.purs b/examples/PaysWithDatum.purs index 37065f5cf3..6405d3f07c 100644 --- a/examples/PaysWithDatum.purs +++ b/examples/PaysWithDatum.purs @@ -44,6 +44,7 @@ import Contract.TxConstraints (DatumPresence(DatumInline, DatumWitness)) import Contract.TxConstraints as Constraints import Contract.Value (Value) import Contract.Value (lovelaceValueOf) as Value +import Control.Monad.Trans.Class (lift) import Ctl.Examples.Helpers (mustPayToPubKeyStakeAddressWithDatum) import Data.Array (head) import Data.BigInt (fromInt) as BigInt @@ -84,7 +85,7 @@ contract = do lookups :: Lookups.ScriptLookups Void lookups = mempty - void $ runChecks checks do + void $ runChecks checks $ lift do txHash <- submitTxFromConstraints lookups constraints awaitTxConfirmed txHash logInfo' "Tx submitted successfully!" diff --git a/examples/PlutusV2/ReferenceInputs.purs b/examples/PlutusV2/ReferenceInputs.purs index 5ff671c31f..8ffa03eb4a 100644 --- a/examples/PlutusV2/ReferenceInputs.purs +++ b/examples/PlutusV2/ReferenceInputs.purs @@ -79,7 +79,7 @@ contract = do lookups :: Lookups.ScriptLookups Void lookups = mempty - void $ runChecks checks do + void $ runChecks checks $ lift do unbalancedTx <- liftedE $ Lookups.mkUnbalancedTx lookups constraints balancedSignedTx <- signTransaction =<< liftedE (balanceTx unbalancedTx) txHash <- submit balancedSignedTx diff --git a/src/Contract/Test/Assert.purs b/src/Contract/Test/Assert.purs index 10cee8bf81..0d857467c9 100644 --- a/src/Contract/Test/Assert.purs +++ b/src/Contract/Test/Assert.purs @@ -18,29 +18,30 @@ module Contract.Test.Assert , Label , Labeled(Labeled) , assertContractExpectedActual - , assertContractMaybe , assertContract + , assertContractMaybe + , assertLovelaceDeltaAtAddress + , assertOutputHasDatum + , assertOutputHasRefScript + , assertTxHasMetadata + , assertValueDeltaAtAddress + , assertionToCheck , checkExUnitsNotExceed , checkGainAtAddress , checkGainAtAddress' , checkLossAtAddress , checkLossAtAddress' - , assertLovelaceDeltaAtAddress - , assertOutputHasDatum + , checkNewUtxosAtAddress , checkTokenDeltaAtAddress , checkTokenGainAtAddress , checkTokenGainAtAddress' , checkTokenLossAtAddress , checkTokenLossAtAddress' - , assertTxHasMetadata - , assertValueDeltaAtAddress - , checkNewUtxosAtAddress - , assertOutputHasRefScript , label - , unlabel , noLabel , runChecks - , assertionToCheck + , tellFailure + , unlabel ) where import Prelude @@ -277,9 +278,9 @@ assertContractExpectedActual mkAssertionFailure expected actual = -- | Accepts an array of checks and interprets them into a `Contract`. runChecks - :: forall (a :: Type) (assertions :: Type) + :: forall (a :: Type) . Array (ContractCheck a) - -> Contract a + -> ContractAssertion a -> Contract a runChecks assertions contract = do ref <- liftEffect $ Ref.new Nil @@ -317,7 +318,7 @@ runChecks assertions contract = do pure success go :: ContractAssertion a - go = foldr wrapAssertion (lift contract) assertions + go = foldr wrapAssertion contract assertions tellFailure :: ContractAssertionFailure -> ContractAssertion Unit From 0a18c9946b65f036d60b0c0d32ed553146561236 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Przemys=C5=82aw=20Kopa=C5=84ski?= Date: Wed, 11 Jan 2023 20:04:39 +0100 Subject: [PATCH 270/373] Fix OutputDatum decoding instance --- CHANGELOG.md | 1 + src/Internal/Types/OutputDatum.purs | 2 +- 2 files changed, 2 insertions(+), 1 deletion(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index 8f267ee899..5311b46438 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -56,6 +56,7 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) ### Fixed - CIP-25 strings are now being split into chunks whose sizes are less than or equal to 64 to adhere to the CIP-25 standard ([#1343](https://github.com/Plutonomicon/cardano-transaction-lib/issues/1343)) - Critical upstream fix in [`purescript-bignumber`](https://github.com/mlabs-haskell/purescript-bignumber/pull/2) +- `OutputDatum` aeson encoding now roundtrips ### Runtime Dependencies diff --git a/src/Internal/Types/OutputDatum.purs b/src/Internal/Types/OutputDatum.purs index 89828ac9ba..d86385e193 100644 --- a/src/Internal/Types/OutputDatum.purs +++ b/src/Internal/Types/OutputDatum.purs @@ -77,7 +77,7 @@ instance DecodeAeson OutputDatum where pure $ OutputDatumHash dataHash "OutputDatum" -> do datum <- obj .: "contents" - pure $ OutputDatumHash datum + pure $ OutputDatum datum tagValue -> do Left $ UnexpectedValue $ toStringifiedNumbersJson $ fromString tagValue From e80c9ad3a4e814d85539e5bd7c813043a9e3ab1d Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Przemys=C5=82aw=20Kopa=C5=84ski?= Date: Wed, 11 Jan 2023 20:06:36 +0100 Subject: [PATCH 271/373] PR number in changelog --- CHANGELOG.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index 5311b46438..b15a382ee0 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -56,7 +56,7 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) ### Fixed - CIP-25 strings are now being split into chunks whose sizes are less than or equal to 64 to adhere to the CIP-25 standard ([#1343](https://github.com/Plutonomicon/cardano-transaction-lib/issues/1343)) - Critical upstream fix in [`purescript-bignumber`](https://github.com/mlabs-haskell/purescript-bignumber/pull/2) -- `OutputDatum` aeson encoding now roundtrips +- `OutputDatum` aeson encoding now roundtrips ([#1388](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1388)) ### Runtime Dependencies From 7953f6f81f55e9925143f6c085bb393cf316a1c6 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Wed, 11 Jan 2023 23:21:21 +0400 Subject: [PATCH 272/373] Update CHANGELOG --- CHANGELOG.md | 2 ++ 1 file changed, 2 insertions(+) diff --git a/CHANGELOG.md b/CHANGELOG.md index 8f267ee899..47088aa653 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -51,6 +51,8 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) ### Changed +- Testing interface is re-implemented. Assertion functions from `Contract.Test.Utils` are moved to `Contract.Test.Assert`. See [the docs](./doc/test-utils.md) for info on the new interface. ([#1389](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1389)) + ### Removed ### Fixed From 4e074cd259008973910ce3731f3a034fd8ca4b18 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Thu, 12 Jan 2023 00:41:53 +0400 Subject: [PATCH 273/373] Try fixing kupo --- flake.lock | 178 ++++++++++++++++++++++++----------------------------- flake.nix | 6 +- 2 files changed, 84 insertions(+), 100 deletions(-) diff --git a/flake.lock b/flake.lock index 2a4c479a5e..97fc0afafe 100644 --- a/flake.lock +++ b/flake.lock @@ -2837,11 +2837,11 @@ }, "flake-utils": { "locked": { - "lastModified": 1667395993, - "narHash": "sha256-nuEHfE/LcWyuSWnS8t12N1wc105Qtau+/OdUAjtQ0rA=", + "lastModified": 1644229661, + "narHash": "sha256-1YdnJAsNy69bpcjuoKdOYQX0YxZBiCYZo4Twxerqv7k=", "owner": "numtide", "repo": "flake-utils", - "rev": "5aed5285a952e0b949eb3ba02c12fa4fcfef535f", + "rev": "3cecb5b042f7f209c56ffd8371b2711a290ec797", "type": "github" }, "original": { @@ -2851,21 +2851,6 @@ } }, "flake-utils_10": { - "locked": { - "lastModified": 1653893745, - "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "1ed9fb1935d260de5fe1c2f7ee0ebaae17ed2fa1", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "flake-utils_11": { "locked": { "lastModified": 1644229661, "narHash": "sha256-1YdnJAsNy69bpcjuoKdOYQX0YxZBiCYZo4Twxerqv7k=", @@ -2880,7 +2865,7 @@ "type": "github" } }, - "flake-utils_12": { + "flake-utils_11": { "locked": { "lastModified": 1623875721, "narHash": "sha256-A8BU7bjS5GirpAUv4QA+QnJ4CceLHkcXdRp4xITDB0s=", @@ -2895,7 +2880,7 @@ "type": "github" } }, - "flake-utils_13": { + "flake-utils_12": { "locked": { "lastModified": 1623875721, "narHash": "sha256-A8BU7bjS5GirpAUv4QA+QnJ4CceLHkcXdRp4xITDB0s=", @@ -2910,7 +2895,7 @@ "type": "github" } }, - "flake-utils_14": { + "flake-utils_13": { "locked": { "lastModified": 1623875721, "narHash": "sha256-A8BU7bjS5GirpAUv4QA+QnJ4CceLHkcXdRp4xITDB0s=", @@ -2925,7 +2910,7 @@ "type": "github" } }, - "flake-utils_15": { + "flake-utils_14": { "locked": { "lastModified": 1644229661, "narHash": "sha256-1YdnJAsNy69bpcjuoKdOYQX0YxZBiCYZo4Twxerqv7k=", @@ -2940,7 +2925,7 @@ "type": "github" } }, - "flake-utils_16": { + "flake-utils_15": { "locked": { "lastModified": 1653893745, "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", @@ -2955,7 +2940,7 @@ "type": "github" } }, - "flake-utils_17": { + "flake-utils_16": { "locked": { "lastModified": 1659877975, "narHash": "sha256-zllb8aq3YO3h8B/U0/J1WBgAL8EX5yWf5pMj3G0NAmc=", @@ -2970,7 +2955,7 @@ "type": "github" } }, - "flake-utils_18": { + "flake-utils_17": { "locked": { "lastModified": 1653893745, "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", @@ -2985,7 +2970,7 @@ "type": "github" } }, - "flake-utils_19": { + "flake-utils_18": { "locked": { "lastModified": 1644229661, "narHash": "sha256-1YdnJAsNy69bpcjuoKdOYQX0YxZBiCYZo4Twxerqv7k=", @@ -3000,13 +2985,13 @@ "type": "github" } }, - "flake-utils_2": { + "flake-utils_19": { "locked": { - "lastModified": 1644229661, - "narHash": "sha256-1YdnJAsNy69bpcjuoKdOYQX0YxZBiCYZo4Twxerqv7k=", + "lastModified": 1623875721, + "narHash": "sha256-A8BU7bjS5GirpAUv4QA+QnJ4CceLHkcXdRp4xITDB0s=", "owner": "numtide", "repo": "flake-utils", - "rev": "3cecb5b042f7f209c56ffd8371b2711a290ec797", + "rev": "f7e004a55b120c02ecb6219596820fcd32ca8772", "type": "github" }, "original": { @@ -3015,13 +3000,13 @@ "type": "github" } }, - "flake-utils_20": { + "flake-utils_2": { "locked": { - "lastModified": 1623875721, - "narHash": "sha256-A8BU7bjS5GirpAUv4QA+QnJ4CceLHkcXdRp4xITDB0s=", + "lastModified": 1644229661, + "narHash": "sha256-1YdnJAsNy69bpcjuoKdOYQX0YxZBiCYZo4Twxerqv7k=", "owner": "numtide", "repo": "flake-utils", - "rev": "f7e004a55b120c02ecb6219596820fcd32ca8772", + "rev": "3cecb5b042f7f209c56ffd8371b2711a290ec797", "type": "github" }, "original": { @@ -3030,7 +3015,7 @@ "type": "github" } }, - "flake-utils_21": { + "flake-utils_20": { "locked": { "lastModified": 1623875721, "narHash": "sha256-A8BU7bjS5GirpAUv4QA+QnJ4CceLHkcXdRp4xITDB0s=", @@ -3045,7 +3030,7 @@ "type": "github" } }, - "flake-utils_22": { + "flake-utils_21": { "locked": { "lastModified": 1623875721, "narHash": "sha256-A8BU7bjS5GirpAUv4QA+QnJ4CceLHkcXdRp4xITDB0s=", @@ -3060,7 +3045,7 @@ "type": "github" } }, - "flake-utils_23": { + "flake-utils_22": { "locked": { "lastModified": 1644229661, "narHash": "sha256-1YdnJAsNy69bpcjuoKdOYQX0YxZBiCYZo4Twxerqv7k=", @@ -3075,7 +3060,7 @@ "type": "github" } }, - "flake-utils_24": { + "flake-utils_23": { "locked": { "lastModified": 1653893745, "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", @@ -3090,7 +3075,7 @@ "type": "github" } }, - "flake-utils_25": { + "flake-utils_24": { "locked": { "lastModified": 1659877975, "narHash": "sha256-zllb8aq3YO3h8B/U0/J1WBgAL8EX5yWf5pMj3G0NAmc=", @@ -3105,7 +3090,7 @@ "type": "github" } }, - "flake-utils_26": { + "flake-utils_25": { "locked": { "lastModified": 1653893745, "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", @@ -3120,7 +3105,7 @@ "type": "github" } }, - "flake-utils_27": { + "flake-utils_26": { "locked": { "lastModified": 1644229661, "narHash": "sha256-1YdnJAsNy69bpcjuoKdOYQX0YxZBiCYZo4Twxerqv7k=", @@ -3135,7 +3120,7 @@ "type": "github" } }, - "flake-utils_28": { + "flake-utils_27": { "locked": { "lastModified": 1653893745, "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", @@ -3150,7 +3135,7 @@ "type": "github" } }, - "flake-utils_29": { + "flake-utils_28": { "locked": { "lastModified": 1659877975, "narHash": "sha256-zllb8aq3YO3h8B/U0/J1WBgAL8EX5yWf5pMj3G0NAmc=", @@ -3165,13 +3150,13 @@ "type": "github" } }, - "flake-utils_3": { + "flake-utils_29": { "locked": { - "lastModified": 1644229661, - "narHash": "sha256-1YdnJAsNy69bpcjuoKdOYQX0YxZBiCYZo4Twxerqv7k=", + "lastModified": 1653893745, + "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", "owner": "numtide", "repo": "flake-utils", - "rev": "3cecb5b042f7f209c56ffd8371b2711a290ec797", + "rev": "1ed9fb1935d260de5fe1c2f7ee0ebaae17ed2fa1", "type": "github" }, "original": { @@ -3180,13 +3165,13 @@ "type": "github" } }, - "flake-utils_30": { + "flake-utils_3": { "locked": { - "lastModified": 1653893745, - "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", + "lastModified": 1623875721, + "narHash": "sha256-A8BU7bjS5GirpAUv4QA+QnJ4CceLHkcXdRp4xITDB0s=", "owner": "numtide", "repo": "flake-utils", - "rev": "1ed9fb1935d260de5fe1c2f7ee0ebaae17ed2fa1", + "rev": "f7e004a55b120c02ecb6219596820fcd32ca8772", "type": "github" }, "original": { @@ -3227,11 +3212,11 @@ }, "flake-utils_6": { "locked": { - "lastModified": 1623875721, - "narHash": "sha256-A8BU7bjS5GirpAUv4QA+QnJ4CceLHkcXdRp4xITDB0s=", + "lastModified": 1644229661, + "narHash": "sha256-1YdnJAsNy69bpcjuoKdOYQX0YxZBiCYZo4Twxerqv7k=", "owner": "numtide", "repo": "flake-utils", - "rev": "f7e004a55b120c02ecb6219596820fcd32ca8772", + "rev": "3cecb5b042f7f209c56ffd8371b2711a290ec797", "type": "github" }, "original": { @@ -3242,11 +3227,11 @@ }, "flake-utils_7": { "locked": { - "lastModified": 1644229661, - "narHash": "sha256-1YdnJAsNy69bpcjuoKdOYQX0YxZBiCYZo4Twxerqv7k=", + "lastModified": 1653893745, + "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", "owner": "numtide", "repo": "flake-utils", - "rev": "3cecb5b042f7f209c56ffd8371b2711a290ec797", + "rev": "1ed9fb1935d260de5fe1c2f7ee0ebaae17ed2fa1", "type": "github" }, "original": { @@ -3257,11 +3242,11 @@ }, "flake-utils_8": { "locked": { - "lastModified": 1653893745, - "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", + "lastModified": 1659877975, + "narHash": "sha256-zllb8aq3YO3h8B/U0/J1WBgAL8EX5yWf5pMj3G0NAmc=", "owner": "numtide", "repo": "flake-utils", - "rev": "1ed9fb1935d260de5fe1c2f7ee0ebaae17ed2fa1", + "rev": "c0e246b9b83f637f4681389ecabcb2681b4f3af0", "type": "github" }, "original": { @@ -3272,11 +3257,11 @@ }, "flake-utils_9": { "locked": { - "lastModified": 1659877975, - "narHash": "sha256-zllb8aq3YO3h8B/U0/J1WBgAL8EX5yWf5pMj3G0NAmc=", + "lastModified": 1653893745, + "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", "owner": "numtide", "repo": "flake-utils", - "rev": "c0e246b9b83f637f4681389ecabcb2681b4f3af0", + "rev": "1ed9fb1935d260de5fe1c2f7ee0ebaae17ed2fa1", "type": "github" }, "original": { @@ -3929,7 +3914,7 @@ "cabal-34": "cabal-34", "cabal-36": "cabal-36", "cardano-shell": "cardano-shell", - "flake-utils": "flake-utils_2", + "flake-utils": "flake-utils", "ghc-8.6.5-iohk": "ghc-8.6.5-iohk", "hackage": "hackage", "hpc-coveralls": "hpc-coveralls", @@ -3970,7 +3955,7 @@ "cabal-36": "cabal-36_5", "cardano-shell": "cardano-shell_6", "flake-compat": "flake-compat_5", - "flake-utils": "flake-utils_7", + "flake-utils": "flake-utils_6", "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_6", "hackage": "hackage_5", "hpc-coveralls": "hpc-coveralls_6", @@ -4012,7 +3997,7 @@ "cabal-36": "cabal-36_9", "cardano-shell": "cardano-shell_11", "flake-compat": "flake-compat_11", - "flake-utils": "flake-utils_15", + "flake-utils": "flake-utils_14", "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_11", "hackage": "hackage_9", "hpc-coveralls": "hpc-coveralls_11", @@ -4053,7 +4038,7 @@ "cabal-36": "cabal-36_13", "cardano-shell": "cardano-shell_16", "flake-compat": "flake-compat_15", - "flake-utils": "flake-utils_23", + "flake-utils": "flake-utils_22", "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_16", "hackage": "hackage_13", "hpc-coveralls": "hpc-coveralls_16", @@ -4093,7 +4078,7 @@ "cabal-36": "cabal-36_14", "cardano-shell": "cardano-shell_17", "flake-compat": "flake-compat_18", - "flake-utils": "flake-utils_27", + "flake-utils": "flake-utils_26", "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_17", "hackage": "hackage_14", "hpc-coveralls": "hpc-coveralls_17", @@ -4134,7 +4119,7 @@ "cabal-36": "cabal-36_2", "cardano-shell": "cardano-shell_2", "flake-compat": "flake-compat_3", - "flake-utils": "flake-utils_3", + "flake-utils": "flake-utils_2", "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_2", "hackage": [ "ogmios", @@ -4177,7 +4162,7 @@ "cabal-34": "cabal-34_13", "cabal-36": "cabal-36_11", "cardano-shell": "cardano-shell_13", - "flake-utils": "flake-utils_20", + "flake-utils": "flake-utils_19", "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_13", "hackage": "hackage_10", "hpc-coveralls": "hpc-coveralls_13", @@ -4216,7 +4201,7 @@ "cabal-34": "cabal-34_14", "cabal-36": "cabal-36_12", "cardano-shell": "cardano-shell_14", - "flake-utils": "flake-utils_21", + "flake-utils": "flake-utils_20", "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_14", "hackage": "hackage_11", "hpc-coveralls": "hpc-coveralls_14", @@ -4256,7 +4241,7 @@ "cabal-32": "cabal-32_15", "cabal-34": "cabal-34_15", "cardano-shell": "cardano-shell_15", - "flake-utils": "flake-utils_22", + "flake-utils": "flake-utils_21", "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_15", "hackage": "hackage_12", "hpc-coveralls": "hpc-coveralls_15", @@ -4296,7 +4281,7 @@ "cabal-34": "cabal-34_3", "cabal-36": "cabal-36_3", "cardano-shell": "cardano-shell_3", - "flake-utils": "flake-utils_4", + "flake-utils": "flake-utils_3", "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_3", "hackage": "hackage_2", "hpc-coveralls": "hpc-coveralls_3", @@ -4335,7 +4320,7 @@ "cabal-34": "cabal-34_4", "cabal-36": "cabal-36_4", "cardano-shell": "cardano-shell_4", - "flake-utils": "flake-utils_5", + "flake-utils": "flake-utils_4", "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_4", "hackage": "hackage_3", "hpc-coveralls": "hpc-coveralls_4", @@ -4375,7 +4360,7 @@ "cabal-32": "cabal-32_5", "cabal-34": "cabal-34_5", "cardano-shell": "cardano-shell_5", - "flake-utils": "flake-utils_6", + "flake-utils": "flake-utils_5", "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_5", "hackage": "hackage_4", "hpc-coveralls": "hpc-coveralls_5", @@ -4415,7 +4400,7 @@ "cabal-34": "cabal-34_7", "cabal-36": "cabal-36_6", "cardano-shell": "cardano-shell_7", - "flake-utils": "flake-utils_11", + "flake-utils": "flake-utils_10", "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_7", "hackage": [ "ogmios-datum-cache-nixos", @@ -4460,7 +4445,7 @@ "cabal-34": "cabal-34_8", "cabal-36": "cabal-36_7", "cardano-shell": "cardano-shell_8", - "flake-utils": "flake-utils_12", + "flake-utils": "flake-utils_11", "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_8", "hackage": "hackage_6", "hpc-coveralls": "hpc-coveralls_8", @@ -4500,7 +4485,7 @@ "cabal-34": "cabal-34_9", "cabal-36": "cabal-36_8", "cardano-shell": "cardano-shell_9", - "flake-utils": "flake-utils_13", + "flake-utils": "flake-utils_12", "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_9", "hackage": "hackage_7", "hpc-coveralls": "hpc-coveralls_9", @@ -4541,7 +4526,7 @@ "cabal-32": "cabal-32_10", "cabal-34": "cabal-34_10", "cardano-shell": "cardano-shell_10", - "flake-utils": "flake-utils_14", + "flake-utils": "flake-utils_13", "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_10", "hackage": "hackage_8", "hpc-coveralls": "hpc-coveralls_10", @@ -4582,7 +4567,7 @@ "cabal-34": "cabal-34_12", "cabal-36": "cabal-36_10", "cardano-shell": "cardano-shell_12", - "flake-utils": "flake-utils_19", + "flake-utils": "flake-utils_18", "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_12", "hackage": [ "ogmios-nixos", @@ -5538,7 +5523,6 @@ }, "kupo-nixos": { "inputs": { - "flake-utils": "flake-utils", "haskell-nix": "haskell-nix", "iohk-nix": "iohk-nix", "kupo": [ @@ -5551,17 +5535,17 @@ ] }, "locked": { - "lastModified": 1667868387, - "narHash": "sha256-YDlUUkbut7Oil5t1njquiSjnu+CQLHxnNFQd2A1eWCc=", + "lastModified": 1672905539, + "narHash": "sha256-B4vryG94L7WWn/tuIQdtg9eZHAH+FaFzv35Mancd2l8=", "owner": "mlabs-haskell", "repo": "kupo-nixos", - "rev": "438799a67d0e6e17f21b7b3d0ae1b6325e505c61", + "rev": "6f89cbcc359893a2aea14dd380f9a45e04c6aa67", "type": "github" }, "original": { "owner": "mlabs-haskell", "repo": "kupo-nixos", - "rev": "438799a67d0e6e17f21b7b3d0ae1b6325e505c61", + "rev": "6f89cbcc359893a2aea14dd380f9a45e04c6aa67", "type": "github" } }, @@ -6018,7 +6002,7 @@ }, "n2c": { "inputs": { - "flake-utils": "flake-utils_10", + "flake-utils": "flake-utils_9", "nixpkgs": [ "ogmios", "haskell-nix", @@ -6043,7 +6027,7 @@ }, "n2c_2": { "inputs": { - "flake-utils": "flake-utils_18", + "flake-utils": "flake-utils_17", "nixpkgs": [ "ogmios-datum-cache-nixos", "ogmios", @@ -6069,7 +6053,7 @@ }, "n2c_3": { "inputs": { - "flake-utils": "flake-utils_26", + "flake-utils": "flake-utils_25", "nixpkgs": [ "ogmios-nixos", "haskell-nix", @@ -6094,7 +6078,7 @@ }, "n2c_4": { "inputs": { - "flake-utils": "flake-utils_30", + "flake-utils": "flake-utils_29", "nixpkgs": [ "plutip", "bot-plutus-interface", @@ -6491,7 +6475,7 @@ }, "nix2container": { "inputs": { - "flake-utils": "flake-utils_8", + "flake-utils": "flake-utils_7", "nixpkgs": "nixpkgs_9" }, "locked": { @@ -6510,7 +6494,7 @@ }, "nix2container_2": { "inputs": { - "flake-utils": "flake-utils_16", + "flake-utils": "flake-utils_15", "nixpkgs": "nixpkgs_19" }, "locked": { @@ -6529,7 +6513,7 @@ }, "nix2container_3": { "inputs": { - "flake-utils": "flake-utils_24", + "flake-utils": "flake-utils_23", "nixpkgs": "nixpkgs_27" }, "locked": { @@ -6548,7 +6532,7 @@ }, "nix2container_4": { "inputs": { - "flake-utils": "flake-utils_28", + "flake-utils": "flake-utils_27", "nixpkgs": "nixpkgs_31" }, "locked": { @@ -9847,7 +9831,7 @@ "blank": "blank_2", "devshell": "devshell", "dmerge": "dmerge", - "flake-utils": "flake-utils_9", + "flake-utils": "flake-utils_8", "makes": [ "ogmios", "haskell-nix", @@ -9887,7 +9871,7 @@ "blank": "blank_4", "devshell": "devshell_2", "dmerge": "dmerge_2", - "flake-utils": "flake-utils_17", + "flake-utils": "flake-utils_16", "makes": [ "ogmios-datum-cache-nixos", "ogmios", @@ -9929,7 +9913,7 @@ "blank": "blank_6", "devshell": "devshell_3", "dmerge": "dmerge_3", - "flake-utils": "flake-utils_25", + "flake-utils": "flake-utils_24", "makes": [ "ogmios-nixos", "haskell-nix", @@ -9969,7 +9953,7 @@ "blank": "blank_7", "devshell": "devshell_4", "dmerge": "dmerge_4", - "flake-utils": "flake-utils_29", + "flake-utils": "flake-utils_28", "makes": [ "plutip", "bot-plutus-interface", diff --git a/flake.nix b/flake.nix index d61dd3ee6a..7797ef8ea5 100644 --- a/flake.nix +++ b/flake.nix @@ -13,7 +13,7 @@ ogmios.url = "github:mlabs-haskell/ogmios/a7687bc03b446bc74564abe1873fbabfa1aac196"; plutip.url = "github:mlabs-haskell/plutip?rev=8d1795d9ac3f9c6f31381104b25c71576eeba009"; - kupo-nixos.url = "github:mlabs-haskell/kupo-nixos/438799a67d0e6e17f21b7b3d0ae1b6325e505c61"; + kupo-nixos.url = "github:mlabs-haskell/kupo-nixos/6f89cbcc359893a2aea14dd380f9a45e04c6aa67"; kupo-nixos.inputs.kupo.follows = "kupo"; kupo = { @@ -163,7 +163,7 @@ name = "ctl-e2e-test"; testMain = "Test.Ctl.E2E"; env = { OGMIOS_FIXTURES = "${ogmiosFixtures}"; }; - buildInputs = [ inputs.kupo-nixos.defaultPackage.${pkgs.system} ]; + buildInputs = [ inputs.kupo-nixos.packages.${pkgs.system}.kupo ]; }; ctl-plutip-test = project.runPlutipTest { name = "ctl-plutip-test"; @@ -238,7 +238,7 @@ ogmios-datum-cache = inputs.ogmios-datum-cache.defaultPackage.${system}; ogmios = ogmios.packages.${system}."ogmios:exe:ogmios"; - kupo = inputs.kupo-nixos.defaultPackage.${system}; + kupo = inputs.kupo-nixos.packages.${system}.kupo; buildCtlRuntime = buildCtlRuntime final; launchCtlRuntime = launchCtlRuntime final; inherit cardano-configurations; From 71a13967c27e61524f9a852235342d1e6460b0bb Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Thu, 12 Jan 2023 10:32:44 +0000 Subject: [PATCH 274/373] Add timeout --- test/Blockfrost/Contract.purs | 8 +++++--- 1 file changed, 5 insertions(+), 3 deletions(-) diff --git a/test/Blockfrost/Contract.purs b/test/Blockfrost/Contract.purs index bf2caefa00..02f34f27d4 100644 --- a/test/Blockfrost/Contract.purs +++ b/test/Blockfrost/Contract.purs @@ -14,6 +14,7 @@ import Contract.Test.Mote (TestPlanM, interpretWithConfig) import Contract.Test.Plutip (testContractsInEnv) import Data.Maybe (Maybe(Nothing, Just)) import Data.String (joinWith) +import Data.Time.Duration (Minutes(Minutes), convertDuration) import Effect (Effect) import Effect.Aff (Aff) import Effect.Class.Console (log) @@ -27,9 +28,10 @@ main = do argv >>= case _ of [ _, apiKey, privateKey, backupKeys ] -> launchAff_ do - interpretWithConfig defaultConfig { timeout = Nothing } $ suite apiKey - privateKey - backupKeys + interpretWithConfig + defaultConfig + { timeout = Just $ convertDuration $ 5.0 # Minutes } + (suite apiKey privateKey backupKeys) _ -> do log $ joinWith "\n" [ "Wrong number of parameters provided." From 8a31d4f3f62bac1eca5219add2941b355fa78f4c Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Thu, 12 Jan 2023 10:58:29 +0000 Subject: [PATCH 275/373] Fix formatting, organise blockfrost service code, speed up compilation of cost model conversion --- src/Internal/QueryM/Ogmios.purs | 14 ++- src/Internal/Service/Blockfrost.purs | 162 ++++++++++++++------------- 2 files changed, 98 insertions(+), 78 deletions(-) diff --git a/src/Internal/QueryM/Ogmios.purs b/src/Internal/QueryM/Ogmios.purs index 0edbbca383..69ba411fd3 100644 --- a/src/Internal/QueryM/Ogmios.purs +++ b/src/Internal/QueryM/Ogmios.purs @@ -58,6 +58,8 @@ module Ctl.Internal.QueryM.Ogmios , aesonArray , aesonObject , convertCostModel + , convertPlutusV1CostModel + , convertPlutusV2CostModel , evaluateTxCall , queryPoolIdsCall , mempoolSnapshotHasTxCall @@ -1082,8 +1084,8 @@ instance DecodeAeson ProtocolParameters where , treasuryCut: unwrap ps.treasuryExpansion -- Rational , coinsPerUtxoUnit: coinsPerUtxoUnit , costModels: Costmdls $ Map.fromFoldable $ catMaybes - [ pure (PlutusV1 /\ convertCostModel ps.costModels."plutus:v1") - , (PlutusV2 /\ _) <<< convertCostModel <$> ps.costModels."plutus:v2" + [ pure (PlutusV1 /\ convertPlutusV1CostModel ps.costModels."plutus:v1") + , (PlutusV2 /\ _) <<< convertPlutusV2CostModel <$> ps.costModels."plutus:v2" ] , prices: prices , maxTxExUnits: decodeExUnits ps.maxExecutionUnitsPerTransaction @@ -1299,6 +1301,14 @@ convertCostModel model = wrap $ reverse $ List.toUnfoldable $ hfoldl (mempty :: List Csl.Int) model +-- Specialized conversions to only perform the type level traversals once + +convertPlutusV1CostModel :: Record CostModelV1 -> T.CostModel +convertPlutusV1CostModel = convertCostModel + +convertPlutusV2CostModel :: Record CostModelV2 -> T.CostModel +convertPlutusV2CostModel = convertCostModel + ---------------- CHAIN TIP QUERY RESPONSE & PARSING data ChainTipQR diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index 1d4c5eea4a..60ccf7f4c5 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -33,8 +33,8 @@ import Control.Alt ((<|>)) import Control.Monad.Except (ExceptT(ExceptT), runExceptT) import Control.Monad.Reader.Class (ask) import Control.Monad.Reader.Trans (ReaderT, runReaderT) -import Ctl.Internal.Cardano.Types.Transaction (Costmdls(..)) -import Ctl.Internal.Cardano.Types.Value (Coin(..)) +import Ctl.Internal.Cardano.Types.Transaction (Costmdls(Costmdls)) +import Ctl.Internal.Cardano.Types.Value (Coin(Coin)) import Ctl.Internal.Contract.QueryBackend (BlockfrostBackend) import Ctl.Internal.Contract.QueryHandle.Error ( GetTxMetadataError @@ -48,12 +48,13 @@ import Ctl.Internal.Deserialization.Transaction ( convertGeneralTransactionMetadata ) import Ctl.Internal.QueryM.Ogmios - ( CoinsPerUtxoUnit(..) + ( CoinsPerUtxoUnit(CoinsPerUtxoWord, CoinsPerUtxoByte) , CostModelV1 , CostModelV2 - , Epoch(..) - , ProtocolParameters(..) - , convertCostModel + , Epoch(Epoch) + , ProtocolParameters(ProtocolParameters) + , convertPlutusV1CostModel + , convertPlutusV2CostModel , rationalToSubcoin ) import Ctl.Internal.QueryM.Ogmios as Ogmios @@ -66,7 +67,7 @@ import Ctl.Internal.Service.Error import Ctl.Internal.Types.ByteArray (byteArrayToHex) import Ctl.Internal.Types.CborBytes (CborBytes) import Ctl.Internal.Types.Rational (Rational, reduce) -import Ctl.Internal.Types.Scripts (Language(..)) +import Ctl.Internal.Types.Scripts (Language(PlutusV1, PlutusV2)) import Ctl.Internal.Types.Transaction (TransactionHash) import Ctl.Internal.Types.TransactionMetadata ( GeneralTransactionMetadata(GeneralTransactionMetadata) @@ -80,7 +81,7 @@ import Data.Either (Either(Left, Right), note) import Data.Generic.Rep (class Generic) import Data.HTTP.Method (Method(GET, POST)) import Data.Map as Map -import Data.Maybe (Maybe(..), maybe) +import Data.Maybe (Maybe(Nothing), maybe) import Data.MediaType (MediaType) import Data.Newtype (class Newtype, unwrap, wrap) import Data.Number (infinity) @@ -189,6 +190,77 @@ handleBlockfrostResponse (Right { status: Affjax.StatusCode statusCode, body }) body # lmap (ClientDecodeJsonError body) <<< (decodeAeson <=< parseJsonStringToAeson) +getCurrentEpoch + :: BlockfrostServiceM (Either ClientError BigInt) +getCurrentEpoch = runExceptT do + BlockfrostCurrentEpoch { epoch } <- ExceptT $ blockfrostGetRequest LatestEpoch + <#> handleBlockfrostResponse + pure epoch + +getProtocolParameters + :: BlockfrostServiceM (Either ClientError Ogmios.ProtocolParameters) +getProtocolParameters = runExceptT do + BlockfrostProtocolParameters params <- ExceptT $ + blockfrostGetRequest LatestProtocolParameters <#> handleBlockfrostResponse + pure params + +isTxConfirmed + :: TransactionHash + -> BlockfrostServiceM (Either ClientError Boolean) +isTxConfirmed txHash = do + response <- blockfrostGetRequest $ Transaction txHash + pure case handleBlockfrostResponse response of + Right (_ :: Aeson) -> Right true + Left (ClientHttpResponseError (Affjax.StatusCode 404) _) -> Right false + Left e -> Left e + +getTxMetadata + :: TransactionHash + -> BlockfrostServiceM (Either GetTxMetadataError GeneralTransactionMetadata) +getTxMetadata txHash = do + response <- blockfrostGetRequest (TransactionMetadata txHash) + pure case unwrapBlockfrostMetadata <$> handleBlockfrostResponse response of + Left (ClientHttpResponseError (Affjax.StatusCode 404) _) -> + Left GetTxMetadataTxNotFoundError + Left e -> + Left (GetTxMetadataClientError e) + Right metadata + | Map.isEmpty (unwrap metadata) -> + Left GetTxMetadataMetadataEmptyOrMissingError + | otherwise -> Right metadata + +-------------------------------------------------------------------------------- +-- `getTxMetadata` reponse parsing +-------------------------------------------------------------------------------- + +newtype BlockfrostMetadata = BlockfrostMetadata + GeneralTransactionMetadata + +derive instance Generic BlockfrostMetadata _ +derive instance Eq BlockfrostMetadata +derive instance Newtype BlockfrostMetadata _ + +instance Show BlockfrostMetadata where + show = genericShow + +instance DecodeAeson BlockfrostMetadata where + decodeAeson = decodeAeson >=> + \(metadatas :: Array { metadata :: CborBytes }) -> do + metadatas' <- for metadatas \{ metadata } -> do + map (unwrap <<< convertGeneralTransactionMetadata) <$> flip note + (fromBytes metadata) $ + TypeMismatch "Hexadecimal encoded Metadata" + + pure $ BlockfrostMetadata $ GeneralTransactionMetadata $ Map.unions + metadatas' + +unwrapBlockfrostMetadata :: BlockfrostMetadata -> GeneralTransactionMetadata +unwrapBlockfrostMetadata (BlockfrostMetadata metadata) = metadata + +-------------------------------------------------------------------------------- +-- `getCurrentEpoch` reponse parsing +-------------------------------------------------------------------------------- + newtype BlockfrostCurrentEpoch = BlockfrostCurrentEpoch { epoch :: BigInt } derive instance Generic BlockfrostCurrentEpoch _ @@ -198,6 +270,10 @@ derive newtype instance DecodeAeson BlockfrostCurrentEpoch instance Show BlockfrostCurrentEpoch where show = genericShow +-------------------------------------------------------------------------------- +-- `getProtocolParameters` reponse parsing +-------------------------------------------------------------------------------- + -- | `Stringed a` decodes an `a` who was encoded as a `String` newtype Stringed a = Stringed a @@ -295,8 +371,8 @@ instance DecodeAeson BlockfrostProtocolParameters where , treasuryCut , coinsPerUtxoUnit: coinsPerUtxoUnit , costModels: Costmdls $ Map.fromFoldable - [ PlutusV1 /\ convertCostModel raw.cost_models."PlutusV1" - , PlutusV2 /\ convertCostModel raw.cost_models."PlutusV2" + [ PlutusV1 /\ convertPlutusV1CostModel raw.cost_models."PlutusV1" + , PlutusV2 /\ convertPlutusV2CostModel raw.cost_models."PlutusV2" ] , prices , maxTxExUnits: @@ -312,69 +388,3 @@ instance DecodeAeson BlockfrostProtocolParameters where , maxCollateralInputs: raw.max_collateral_inputs } -getCurrentEpoch - :: BlockfrostServiceM (Either ClientError BigInt) -getCurrentEpoch = runExceptT do - BlockfrostCurrentEpoch { epoch } <- ExceptT $ blockfrostGetRequest LatestEpoch - <#> handleBlockfrostResponse - pure epoch - -getProtocolParameters - :: BlockfrostServiceM (Either ClientError Ogmios.ProtocolParameters) -getProtocolParameters = runExceptT do - BlockfrostProtocolParameters params <- ExceptT $ - blockfrostGetRequest LatestProtocolParameters <#> handleBlockfrostResponse - pure params - -isTxConfirmed - :: TransactionHash - -> BlockfrostServiceM (Either ClientError Boolean) -isTxConfirmed txHash = do - response <- blockfrostGetRequest $ Transaction txHash - pure case handleBlockfrostResponse response of - Right (_ :: Aeson) -> Right true - Left (ClientHttpResponseError (Affjax.StatusCode 404) _) -> Right false - Left e -> Left e - -getTxMetadata - :: TransactionHash - -> BlockfrostServiceM (Either GetTxMetadataError GeneralTransactionMetadata) -getTxMetadata txHash = do - response <- blockfrostGetRequest (TransactionMetadata txHash) - pure case unwrapBlockfrostMetadata <$> handleBlockfrostResponse response of - Left (ClientHttpResponseError (Affjax.StatusCode 404) _) -> - Left GetTxMetadataTxNotFoundError - Left e -> - Left (GetTxMetadataClientError e) - Right metadata - | Map.isEmpty (unwrap metadata) -> - Left GetTxMetadataMetadataEmptyOrMissingError - | otherwise -> Right metadata - --------------------------------------------------------------------------------- --- `getTxMetadata` reponse parsing --------------------------------------------------------------------------------- - -newtype BlockfrostMetadata = BlockfrostMetadata - GeneralTransactionMetadata - -derive instance Generic BlockfrostMetadata _ -derive instance Eq BlockfrostMetadata -derive instance Newtype BlockfrostMetadata _ - -instance Show BlockfrostMetadata where - show = genericShow - -instance DecodeAeson BlockfrostMetadata where - decodeAeson = decodeAeson >=> - \(metadatas :: Array { metadata :: CborBytes }) -> do - metadatas' <- for metadatas \{ metadata } -> do - map (unwrap <<< convertGeneralTransactionMetadata) <$> flip note - (fromBytes metadata) $ - TypeMismatch "Hexadecimal encoded Metadata" - - pure $ BlockfrostMetadata $ GeneralTransactionMetadata $ Map.unions - metadatas' - -unwrapBlockfrostMetadata :: BlockfrostMetadata -> GeneralTransactionMetadata -unwrapBlockfrostMetadata (BlockfrostMetadata metadata) = metadata From a10b437aedb86831d7adb7f073cd7bb3206d793a Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Thu, 12 Jan 2023 16:04:54 +0100 Subject: [PATCH 276/373] Apply suggestions --- src/Internal/Service/Blockfrost.purs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index 3f38ae92d2..407f6b1b3a 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -189,7 +189,7 @@ withOnRawGetResponseHook withOnRawGetResponseHook endpoint result = do for_ result \{ body: rawResponse } -> do onRawGetResponse <- asks _.onBlockfrostRawGetResponse - maybe (pure unit) (\f -> liftAff $ f endpoint rawResponse) onRawGetResponse + liftAff $ for_ onRawGetResponse \f -> f endpoint rawResponse pure result withOnRawPostResponseHook @@ -202,7 +202,7 @@ withOnRawPostResponseHook endpoint mediaType requestBody result = do for_ result \{ body: rawResponse } -> do let data_ = { endpoint, mediaType, requestBody, rawResponse } onRawPostResponse <- asks _.onBlockfrostRawPostResponse - maybe (pure unit) (\f -> liftAff $ f data_) onRawPostResponse + liftAff $ for_ onRawPostResponse \f -> f data_ pure result -------------------------------------------------------------------------------- From b7456bbcc20fa94efd776ff02848116d050ed1fe Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Thu, 12 Jan 2023 16:50:49 +0100 Subject: [PATCH 277/373] Compute md5 hash using PS lib, Expose md5HashHex in Contract.Hashing --- spago-packages.nix | 12 ++++++++++++ spago.dhall | 1 + src/Contract/Hashing.purs | 1 + src/Internal/Hashing.purs | 11 +++++++++++ test/Blockfrost/GenerateFixtures/Helpers.js | 7 ------- test/Blockfrost/GenerateFixtures/Helpers.purs | 17 +++++++---------- test/Ogmios/GenerateFixtures.js | 7 ------- test/Ogmios/GenerateFixtures.purs | 7 +++---- 8 files changed, 35 insertions(+), 28 deletions(-) delete mode 100644 test/Blockfrost/GenerateFixtures/Helpers.js delete mode 100644 test/Ogmios/GenerateFixtures.js diff --git a/spago-packages.nix b/spago-packages.nix index f1d2178963..85b417e8c5 100644 --- a/spago-packages.nix +++ b/spago-packages.nix @@ -281,6 +281,18 @@ let installPhase = "ln -s $src $out"; }; + "crypto" = pkgs.stdenv.mkDerivation { + name = "crypto"; + version = "v4.0.0"; + src = pkgs.fetchgit { + url = "https://github.com/oreshinya/purescript-crypto.git"; + rev = "cbc19e06c5e4d528e7733633e50c070b1aa0f77e"; + sha256 = "142p9f0mg1yi4bccg3jwhhyn4k4yy5fskh08p05n9sfym27ss126"; + }; + phases = "installPhase"; + installPhase = "ln -s $src $out"; + }; + "datetime" = pkgs.stdenv.mkDerivation { name = "datetime"; version = "v5.0.2"; diff --git a/spago.dhall b/spago.dhall index 71b0386eca..436a1fc8b6 100644 --- a/spago.dhall +++ b/spago.dhall @@ -19,6 +19,7 @@ You can edit this file as you like. , "checked-exceptions" , "console" , "control" + , "crypto" , "datetime" , "debug" , "effect" diff --git a/src/Contract/Hashing.purs b/src/Contract/Hashing.purs index efd061dffb..673f29f0dc 100644 --- a/src/Contract/Hashing.purs +++ b/src/Contract/Hashing.purs @@ -7,6 +7,7 @@ import Ctl.Internal.Hashing ( blake2b256Hash , blake2b256HashHex , datumHash + , md5HashHex , plutusScriptHash , scriptRefHash , sha256Hash diff --git a/src/Internal/Hashing.purs b/src/Internal/Hashing.purs index ea5ab82e37..d4db33389e 100644 --- a/src/Internal/Hashing.purs +++ b/src/Internal/Hashing.purs @@ -2,6 +2,7 @@ module Ctl.Internal.Hashing ( blake2b256Hash , blake2b256HashHex , datumHash + , md5HashHex , plutusScriptHash , sha256Hash , sha256HashHex @@ -33,6 +34,10 @@ import Ctl.Internal.Types.Datum (Datum) import Ctl.Internal.Types.Scripts (PlutusScript) import Ctl.Internal.Types.Transaction (DataHash, TransactionHash) import Data.Newtype (unwrap, wrap) +import Effect (Effect) +import Node.Buffer (fromString, toString) as Buffer +import Node.Crypto.Hash (createHash, digest, update) as Hash +import Node.Encoding (Encoding(Hex, UTF8)) foreign import blake2b256Hash :: ByteArray -> ByteArray @@ -51,6 +56,12 @@ foreign import sha3_256Hash :: ByteArray -> ByteArray foreign import sha3_256HashHex :: ByteArray -> String +md5HashHex :: String -> Effect String +md5HashHex contents = do + buf <- Buffer.fromString contents UTF8 + digest <- Hash.createHash "md5" >>= Hash.update buf >>= Hash.digest + Buffer.toString Hex digest + datumHash :: Datum -> DataHash datumHash = wrap <<< unwrap <<< toBytes <<< hashPlutusData diff --git a/test/Blockfrost/GenerateFixtures/Helpers.js b/test/Blockfrost/GenerateFixtures/Helpers.js deleted file mode 100644 index 5ce72bdad6..0000000000 --- a/test/Blockfrost/GenerateFixtures/Helpers.js +++ /dev/null @@ -1,7 +0,0 @@ -"use strict"; - -const crypto = require("crypto"); - -exports.md5 = function (message) { - return crypto.createHash("md5").update(message).digest("hex"); -}; diff --git a/test/Blockfrost/GenerateFixtures/Helpers.purs b/test/Blockfrost/GenerateFixtures/Helpers.purs index a838e19054..9dc8321dc3 100644 --- a/test/Blockfrost/GenerateFixtures/Helpers.purs +++ b/test/Blockfrost/GenerateFixtures/Helpers.purs @@ -4,7 +4,6 @@ module Test.Ctl.Blockfrost.GenerateFixtures.Helpers , getBlockfrostApiKeyFromEnv , getSkeyFilepathFromEnv , lookupEnv' - , md5 , storeBlockfrostFixture ) where @@ -24,6 +23,7 @@ import Ctl.Internal.Contract.QueryBackend ( BlockfrostBackend , mkBlockfrostBackendParams ) +import Ctl.Internal.Hashing (md5HashHex) import Data.Maybe (Maybe(Just, Nothing), maybe) import Data.String (take) as String import Effect.Exception (throw) @@ -32,8 +32,6 @@ import Node.FS.Aff (exists, writeTextFile) import Node.Path (concat) import Node.Process (lookupEnv) -foreign import md5 :: String -> String - blockfrostBackend :: Effect BlockfrostBackend blockfrostBackend = do blockfrostApiKey <- getBlockfrostApiKeyFromEnv @@ -84,13 +82,12 @@ lookupEnv' var = maybe (throw $ var <> " environment variable not set") pure storeBlockfrostFixture :: Int -> String -> String -> Aff Unit -storeBlockfrostFixture i query resp = +storeBlockfrostFixture i query resp = do + respHash <- liftEffect $ md5HashHex resp let - respHash = md5 resp filename = query <> "-" <> respHash <> ".json" fp = concat [ "fixtures", "test", "blockfrost", query, filename ] - in - exists fp >>= flip unless - ( writeTextFile UTF8 fp resp - *> log ("Successfully saved fixture #" <> show i <> " to: " <> fp) - ) + exists fp >>= flip unless + ( writeTextFile UTF8 fp resp + *> log ("Successfully saved fixture #" <> show i <> " to: " <> fp) + ) diff --git a/test/Ogmios/GenerateFixtures.js b/test/Ogmios/GenerateFixtures.js deleted file mode 100644 index 5ce72bdad6..0000000000 --- a/test/Ogmios/GenerateFixtures.js +++ /dev/null @@ -1,7 +0,0 @@ -"use strict"; - -const crypto = require("crypto"); - -exports.md5 = function (message) { - return crypto.createHash("md5").update(message).digest("hex"); -}; diff --git a/test/Ogmios/GenerateFixtures.purs b/test/Ogmios/GenerateFixtures.purs index 7fa8b2812a..3b06818f67 100644 --- a/test/Ogmios/GenerateFixtures.purs +++ b/test/Ogmios/GenerateFixtures.purs @@ -6,6 +6,7 @@ import Prelude import Aeson (class DecodeAeson, class EncodeAeson, Aeson, stringifyAeson) import Control.Parallel (parTraverse) +import Ctl.Internal.Hashing (md5HashHex) import Ctl.Internal.Helpers (logString) import Ctl.Internal.JsWebSocket ( _mkWebSocket @@ -86,8 +87,6 @@ mkWebSocketAff mkWebSocketAff lvl = makeAff <<< map (map (Canceler <<< map liftEffect)) <<< mkWebSocket lvl -foreign import md5 :: String -> String - data Query = Query (JsonWspCall Unit Aeson) String mkQuery :: forall (query :: Type). EncodeAeson query => query -> String -> Query @@ -133,9 +132,9 @@ main = pure { resp, query: shown } for_ resps \{ resp, query } -> do + let resp' = stringifyAeson resp + respMd5 <- liftEffect $ md5HashHex resp' let - resp' = stringifyAeson resp - respMd5 = md5 resp' fp = concat [ "fixtures" , "test" From 447f05c62819913dce00a74eb436d58473b03056 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Thu, 12 Jan 2023 17:01:54 +0100 Subject: [PATCH 278/373] Update template deps --- templates/ctl-scaffold/flake.nix | 2 +- templates/ctl-scaffold/packages.dhall | 3 ++- templates/ctl-scaffold/spago-packages.nix | 18 +++++++++++++++--- 3 files changed, 18 insertions(+), 5 deletions(-) diff --git a/templates/ctl-scaffold/flake.nix b/templates/ctl-scaffold/flake.nix index 69e179de7a..e477bb5f33 100644 --- a/templates/ctl-scaffold/flake.nix +++ b/templates/ctl-scaffold/flake.nix @@ -10,7 +10,7 @@ type = "github"; owner = "Plutonomicon"; repo = "cardano-transaction-lib"; - rev = "001b639606f341489968d599fb0cef2900aeb474"; + rev = "b7456bbcc20fa94efd776ff02848116d050ed1fe"; }; # To use the same version of `nixpkgs` as we do nixpkgs.follows = "ctl/nixpkgs"; diff --git a/templates/ctl-scaffold/packages.dhall b/templates/ctl-scaffold/packages.dhall index b03ab6aea2..4eeb88a300 100644 --- a/templates/ctl-scaffold/packages.dhall +++ b/templates/ctl-scaffold/packages.dhall @@ -276,6 +276,7 @@ let additions = , "checked-exceptions" , "console" , "control" + , "crypto" , "datetime" , "debug" , "effect" @@ -348,7 +349,7 @@ let additions = , "variant" ] , repo = "https://github.com/Plutonomicon/cardano-transaction-lib.git" - , version = "001b639606f341489968d599fb0cef2900aeb474" + , version = "b7456bbcc20fa94efd776ff02848116d050ed1fe" } , noble-secp256k1 = { dependencies = diff --git a/templates/ctl-scaffold/spago-packages.nix b/templates/ctl-scaffold/spago-packages.nix index 1ea67501d4..55208695ee 100644 --- a/templates/ctl-scaffold/spago-packages.nix +++ b/templates/ctl-scaffold/spago-packages.nix @@ -211,11 +211,11 @@ let "cardano-transaction-lib" = pkgs.stdenv.mkDerivation { name = "cardano-transaction-lib"; - version = "001b639606f341489968d599fb0cef2900aeb474"; + version = "b7456bbcc20fa94efd776ff02848116d050ed1fe"; src = pkgs.fetchgit { url = "https://github.com/Plutonomicon/cardano-transaction-lib.git"; - rev = "001b639606f341489968d599fb0cef2900aeb474"; - sha256 = "1rbpq2ikndjar8h3hpq5yz4mqga7276ggdbws34ppq3miczh9czz"; + rev = "b7456bbcc20fa94efd776ff02848116d050ed1fe"; + sha256 = "0h5nwmjaib1bsvv149slv3fhi8w6wlzca09fal6hng9xq049lwmy"; }; phases = "installPhase"; installPhase = "ln -s $src $out"; @@ -293,6 +293,18 @@ let installPhase = "ln -s $src $out"; }; + "crypto" = pkgs.stdenv.mkDerivation { + name = "crypto"; + version = "v4.0.0"; + src = pkgs.fetchgit { + url = "https://github.com/oreshinya/purescript-crypto.git"; + rev = "cbc19e06c5e4d528e7733633e50c070b1aa0f77e"; + sha256 = "142p9f0mg1yi4bccg3jwhhyn4k4yy5fskh08p05n9sfym27ss126"; + }; + phases = "installPhase"; + installPhase = "ln -s $src $out"; + }; + "datetime" = pkgs.stdenv.mkDerivation { name = "datetime"; version = "v5.0.2"; From 1de8acce8420dfbc9729d03197fc9a124bad6ef1 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Thu, 12 Jan 2023 17:07:36 +0100 Subject: [PATCH 279/373] Add getNativeScriptByHash to Blockfrost Aeson test suite --- src/Internal/Service/Blockfrost.purs | 1 + test/Blockfrost/Aeson/Suite.purs | 12 ++++++++++-- 2 files changed, 11 insertions(+), 2 deletions(-) diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index 45a9c57e71..c3390b4f2e 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -8,6 +8,7 @@ module Ctl.Internal.Service.Blockfrost , TransactionMetadata ) , BlockfrostMetadata(BlockfrostMetadata) + , BlockfrostNativeScript(BlockfrostNativeScript) , BlockfrostRawPostResponseData , BlockfrostRawResponse , BlockfrostServiceM diff --git a/test/Blockfrost/Aeson/Suite.purs b/test/Blockfrost/Aeson/Suite.purs index fc3dfd0c82..f228c6ef1f 100644 --- a/test/Blockfrost/Aeson/Suite.purs +++ b/test/Blockfrost/Aeson/Suite.purs @@ -13,7 +13,10 @@ import Aeson import Control.Monad.Error.Class (liftEither) import Control.Monad.Trans.Class (lift) import Control.Parallel (parTraverse) -import Ctl.Internal.Service.Blockfrost (BlockfrostMetadata) +import Ctl.Internal.Service.Blockfrost + ( BlockfrostMetadata + , BlockfrostNativeScript + ) import Ctl.Internal.Test.TestPlanM (TestPlanM, interpret) import Data.Array (catMaybes, length) import Data.Array.NonEmpty (tail) @@ -54,15 +57,20 @@ suite = do (const unit) (decodeAeson aeson :: Either JsonDecodeError a) case query of + GetNativeScriptByHashQuery -> + handle (Proxy :: Proxy BlockfrostNativeScript) GetTxMetadataQuery -> handle (Proxy :: Proxy BlockfrostMetadata) tests (genericSucc query) -data Query = GetTxMetadataQuery +data Query + = GetNativeScriptByHashQuery + | GetTxMetadataQuery derive instance Generic Query _ printQuery :: Query -> String printQuery = case _ of + GetNativeScriptByHashQuery -> "getNativeScriptByHash" GetTxMetadataQuery -> "getTxMetadata" loadFixtures :: FilePath -> Aff (Array { aeson :: Aeson, bn :: String }) From 6456744d17168dfeedc6aab6e4484eafec2c83ca Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Thu, 12 Jan 2023 18:26:07 +0100 Subject: [PATCH 280/373] Generate fixtures for getScriptInfo, Update Blockfrost Aeson test suite --- ...Info-1fc84ae3aaec37e72314209e98dfa1aa.json | 1 + ...Info-4a2e8bd330d7b940fb20b699c46ff717.json | 1 + ...Info-fadd6ab080d27c2fee183698f6cadca1.json | 1 + src/Internal/Service/Blockfrost.purs | 25 ++-- test/Blockfrost/Aeson/Suite.purs | 4 + .../GenerateFixtures/NativeScript.purs | 20 ++- .../GenerateFixtures/ScriptInfo.purs | 129 ++++++++++++++++++ 7 files changed, 164 insertions(+), 17 deletions(-) create mode 100644 fixtures/test/blockfrost/getScriptInfo/getScriptInfo-1fc84ae3aaec37e72314209e98dfa1aa.json create mode 100644 fixtures/test/blockfrost/getScriptInfo/getScriptInfo-4a2e8bd330d7b940fb20b699c46ff717.json create mode 100644 fixtures/test/blockfrost/getScriptInfo/getScriptInfo-fadd6ab080d27c2fee183698f6cadca1.json create mode 100644 test/Blockfrost/GenerateFixtures/ScriptInfo.purs diff --git a/fixtures/test/blockfrost/getScriptInfo/getScriptInfo-1fc84ae3aaec37e72314209e98dfa1aa.json b/fixtures/test/blockfrost/getScriptInfo/getScriptInfo-1fc84ae3aaec37e72314209e98dfa1aa.json new file mode 100644 index 0000000000..93de2daf38 --- /dev/null +++ b/fixtures/test/blockfrost/getScriptInfo/getScriptInfo-1fc84ae3aaec37e72314209e98dfa1aa.json @@ -0,0 +1 @@ +{"script_hash":"793f8c8cffba081b2a56462fc219cc8fe652d6a338b62c7b134876e7","type":"plutusV2","serialised_size":14} \ No newline at end of file diff --git a/fixtures/test/blockfrost/getScriptInfo/getScriptInfo-4a2e8bd330d7b940fb20b699c46ff717.json b/fixtures/test/blockfrost/getScriptInfo/getScriptInfo-4a2e8bd330d7b940fb20b699c46ff717.json new file mode 100644 index 0000000000..e157e6aa96 --- /dev/null +++ b/fixtures/test/blockfrost/getScriptInfo/getScriptInfo-4a2e8bd330d7b940fb20b699c46ff717.json @@ -0,0 +1 @@ +{"script_hash":"67f33146617a5e61936081db3b2117cbf59bd2123748f58ac9678656","type":"plutusV1","serialised_size":14} \ No newline at end of file diff --git a/fixtures/test/blockfrost/getScriptInfo/getScriptInfo-fadd6ab080d27c2fee183698f6cadca1.json b/fixtures/test/blockfrost/getScriptInfo/getScriptInfo-fadd6ab080d27c2fee183698f6cadca1.json new file mode 100644 index 0000000000..6ce51ef3d1 --- /dev/null +++ b/fixtures/test/blockfrost/getScriptInfo/getScriptInfo-fadd6ab080d27c2fee183698f6cadca1.json @@ -0,0 +1 @@ +{"script_hash":"daf17ca9dc108afc7cf69be0414b8f1a42fc8ceb7d73828d8ed57d6c","type":"timelock","serialised_size":null} \ No newline at end of file diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index c3390b4f2e..977fbd3350 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -11,13 +11,16 @@ module Ctl.Internal.Service.Blockfrost , BlockfrostNativeScript(BlockfrostNativeScript) , BlockfrostRawPostResponseData , BlockfrostRawResponse + , BlockfrostScriptInfo(BlockfrostScriptInfo) , BlockfrostServiceM , BlockfrostServiceParams + , BlockfrostScriptLanguage(NativeScript, PlutusV1Script, PlutusV2Script) , OnBlockfrostRawGetResponseHook , OnBlockfrostRawPostResponseHook , dummyExport , getDatumByHash , getScriptByHash + , getScriptInfo , getTxMetadata , isTxConfirmed , runBlockfrostServiceM @@ -309,7 +312,7 @@ getScriptByHash :: ScriptHash -> BlockfrostServiceM (Either ClientError (Maybe ScriptRef)) getScriptByHash scriptHash = runExceptT $ runMaybeT do - scriptInfo <- MaybeT $ ExceptT getScriptInfo + scriptInfo <- MaybeT $ ExceptT $ getScriptInfo scriptHash case scriptLanguage scriptInfo of NativeScript -> NativeScriptRef <$> @@ -321,12 +324,6 @@ getScriptByHash scriptHash = runExceptT $ runMaybeT do PlutusScriptRef <$> plutusV2Script <$> (MaybeT $ ExceptT getPlutusScriptCborByHash) where - getScriptInfo - :: BlockfrostServiceM (Either ClientError (Maybe BlockfrostScriptInfo)) - getScriptInfo = do - response <- blockfrostGetRequest (ScriptInfo scriptHash) - pure $ handle404AsNothing $ handleBlockfrostResponse response - getNativeScriptByHash :: BlockfrostServiceM (Either ClientError (Maybe NativeScript)) getNativeScriptByHash = runExceptT do @@ -343,6 +340,13 @@ getScriptByHash scriptHash = runExceptT $ runMaybeT do pure $ handle404AsNothing $ handleBlockfrostResponse response pure $ join $ unwrap <$> plutusScriptCbor +getScriptInfo + :: ScriptHash + -> BlockfrostServiceM (Either ClientError (Maybe BlockfrostScriptInfo)) +getScriptInfo scriptHash = do + response <- blockfrostGetRequest (ScriptInfo scriptHash) + pure $ handle404AsNothing $ handleBlockfrostResponse response + -------------------------------------------------------------------------------- -- Check transaction confirmation status -------------------------------------------------------------------------------- @@ -383,6 +387,7 @@ getTxMetadata txHash = do data BlockfrostScriptLanguage = NativeScript | PlutusV1Script | PlutusV2Script derive instance Generic BlockfrostScriptLanguage _ +derive instance Eq BlockfrostScriptLanguage instance Show BlockfrostScriptLanguage where show = genericShow @@ -409,14 +414,14 @@ scriptLanguage = _.language <<< unwrap derive instance Generic BlockfrostScriptInfo _ derive instance Newtype BlockfrostScriptInfo _ +derive instance Eq BlockfrostScriptInfo instance Show BlockfrostScriptInfo where show = genericShow instance DecodeAeson BlockfrostScriptInfo where - decodeAeson = aesonObject \obj -> - getField obj "type" - <#> \language -> BlockfrostScriptInfo { language } + decodeAeson = + aesonObject (map (wrap <<< { language: _ }) <<< flip getField "type") -------------------------------------------------------------------------------- -- BlockfrostNativeScript diff --git a/test/Blockfrost/Aeson/Suite.purs b/test/Blockfrost/Aeson/Suite.purs index f228c6ef1f..3359d28f09 100644 --- a/test/Blockfrost/Aeson/Suite.purs +++ b/test/Blockfrost/Aeson/Suite.purs @@ -16,6 +16,7 @@ import Control.Parallel (parTraverse) import Ctl.Internal.Service.Blockfrost ( BlockfrostMetadata , BlockfrostNativeScript + , BlockfrostScriptInfo ) import Ctl.Internal.Test.TestPlanM (TestPlanM, interpret) import Data.Array (catMaybes, length) @@ -59,11 +60,13 @@ suite = do case query of GetNativeScriptByHashQuery -> handle (Proxy :: Proxy BlockfrostNativeScript) + GetScriptInfoQuery -> handle (Proxy :: Proxy BlockfrostScriptInfo) GetTxMetadataQuery -> handle (Proxy :: Proxy BlockfrostMetadata) tests (genericSucc query) data Query = GetNativeScriptByHashQuery + | GetScriptInfoQuery | GetTxMetadataQuery derive instance Generic Query _ @@ -71,6 +74,7 @@ derive instance Generic Query _ printQuery :: Query -> String printQuery = case _ of GetNativeScriptByHashQuery -> "getNativeScriptByHash" + GetScriptInfoQuery -> "getScriptInfo" GetTxMetadataQuery -> "getTxMetadata" loadFixtures :: FilePath -> Aff (Array { aeson :: Aeson, bn :: String }) diff --git a/test/Blockfrost/GenerateFixtures/NativeScript.purs b/test/Blockfrost/GenerateFixtures/NativeScript.purs index 1b4b1638d9..e709a5929c 100644 --- a/test/Blockfrost/GenerateFixtures/NativeScript.purs +++ b/test/Blockfrost/GenerateFixtures/NativeScript.purs @@ -7,15 +7,13 @@ import Contract.Config ( ContractParams , PrivatePaymentKeySource(PrivatePaymentKeyFile) , WalletSpec(UseKeys) + , defaultKupoServerConfig + , defaultOgmiosWsConfig + , mkCtlBackendParams , testnetConfig ) import Contract.Hashing (scriptRefHash) as Hashing -import Contract.Monad - ( Contract - , launchAff_ - , liftedM - , runContract - ) +import Contract.Monad (Contract, launchAff_, liftedM, runContract) import Contract.ScriptLookups (ScriptLookups) as Lookups import Contract.Scripts (NativeScript, ScriptHash) import Contract.Transaction @@ -35,6 +33,7 @@ import Ctl.Internal.Service.Blockfrost import Ctl.Internal.Service.Blockfrost (getScriptByHash) as Blockfrost import Data.Array (mapWithIndex) import Data.BigInt (fromInt) as BigInt +import Data.UInt (fromInt) as UInt import Test.Ctl.Blockfrost.GenerateFixtures.Helpers ( blockfrostBackend , getSkeyFilepathFromEnv @@ -60,7 +59,14 @@ main = -- { blockfrostConfig: blockfrostPublicPreviewServerConfig -- , blockfrostApiKey: Just blockfrostApiKey -- } - { logLevel = Info + { backendParams = + mkCtlBackendParams + { ogmiosConfig: defaultOgmiosWsConfig + , kupoConfig: + defaultKupoServerConfig + { port = UInt.fromInt 1442, path = Nothing } + } + , logLevel = Info , walletSpec = Just $ UseKeys (PrivatePaymentKeyFile skeyFilepath) Nothing } diff --git a/test/Blockfrost/GenerateFixtures/ScriptInfo.purs b/test/Blockfrost/GenerateFixtures/ScriptInfo.purs new file mode 100644 index 0000000000..d9d98815b7 --- /dev/null +++ b/test/Blockfrost/GenerateFixtures/ScriptInfo.purs @@ -0,0 +1,129 @@ +module Test.Ctl.Blockfrost.GenerateFixtures.ScriptInfo (main) where + +import Contract.Prelude + +import Contract.Address (ownPaymentPubKeyHash, ownStakePubKeyHash) +import Contract.Config + ( ContractParams + , PrivatePaymentKeySource(PrivatePaymentKeyFile) + , WalletSpec(UseKeys) + , defaultKupoServerConfig + , defaultOgmiosWsConfig + , mkCtlBackendParams + , testnetConfig + ) +import Contract.Hashing (scriptRefHash) as Hashing +import Contract.Monad (Contract, launchAff_, liftedM, runContract) +import Contract.ScriptLookups (ScriptLookups) as Lookups +import Contract.Scripts (ScriptHash) +import Contract.Transaction + ( ScriptRef(NativeScriptRef, PlutusScriptRef) + , awaitTxConfirmed + , submitTxFromConstraints + ) +import Contract.TxConstraints (TxConstraints) as Constraints +import Contract.Value (Value) +import Contract.Value (lovelaceValueOf) as Value +import Ctl.Examples.AlwaysSucceeds (alwaysSucceedsScript) +import Ctl.Examples.Helpers (mustPayToPubKeyStakeAddressWithScriptRef) +import Ctl.Examples.PlutusV2.Scripts.AlwaysSucceeds (alwaysSucceedsScriptV2) +import Ctl.Internal.Service.Blockfrost + ( BlockfrostEndpoint(ScriptInfo) + , BlockfrostRawResponse + , BlockfrostScriptLanguage(NativeScript, PlutusV1Script, PlutusV2Script) + , runBlockfrostServiceTestM + ) +import Ctl.Internal.Service.Blockfrost (getScriptInfo) as Blockfrost +import Data.Array (zip) as Array +import Data.BigInt (fromInt) as BigInt +import Data.FoldableWithIndex (forWithIndex_) +import Data.UInt (fromInt) as UInt +import Test.Ctl.Blockfrost.GenerateFixtures.Helpers + ( blockfrostBackend + , getSkeyFilepathFromEnv + , storeBlockfrostFixture + ) +import Test.QuickCheck.Arbitrary (arbitrary) +import Test.QuickCheck.Gen (randomSampleOne) +import Test.Spec.Assertions (shouldEqual) + +main :: Effect Unit +main = + contractParams >>= + (launchAff_ <<< flip runContract generateFixtures) + where + contractParams :: Effect ContractParams + contractParams = do + -- blockfrostApiKey <- lookupEnv' "BLOCKFROST_API_KEY" + skeyFilepath <- getSkeyFilepathFromEnv + pure $ testnetConfig + -- TODO: Configure Contract with Blockfrost as the default backend. + -- { backendParams = + -- mkBlockfrostBackendParams + -- { blockfrostConfig: blockfrostPublicPreviewServerConfig + -- , blockfrostApiKey: Just blockfrostApiKey + -- } + { backendParams = + mkCtlBackendParams + { ogmiosConfig: defaultOgmiosWsConfig + , kupoConfig: + defaultKupoServerConfig + { port = UInt.fromInt 1442, path = Nothing } + } + , logLevel = Info + , walletSpec = + Just $ UseKeys (PrivatePaymentKeyFile skeyFilepath) Nothing + } + +generateFixtures :: Contract Unit +generateFixtures = do + -- TODO: Remove this line and use Blockfrost as the default backend instead. + backend <- liftEffect blockfrostBackend + + nativeScriptRef <- liftEffect (NativeScriptRef <$> randomSampleOne arbitrary) + v1PlutusScriptRef <- PlutusScriptRef <$> unwrap <$> alwaysSucceedsScript + v2PlutusScriptRef <- PlutusScriptRef <$> unwrap <$> alwaysSucceedsScriptV2 + + let + scriptRefs = [ nativeScriptRef, v1PlutusScriptRef, v2PlutusScriptRef ] + scriptLanguages = [ NativeScript, PlutusV1Script, PlutusV2Script ] + scriptHashes = Hashing.scriptRefHash <$> scriptRefs + hashesLanguages = Array.zip scriptHashes scriptLanguages + + pkh <- liftedM "Failed to get own PKH" ownPaymentPubKeyHash + skh <- ownStakePubKeyHash + let + value :: Value + value = Value.lovelaceValueOf $ BigInt.fromInt 2_000_000 + + constraints :: Constraints.TxConstraints Void Void + constraints = + mconcat $ scriptRefs <#> + flip (mustPayToPubKeyStakeAddressWithScriptRef pkh skh) value + + lookups :: Lookups.ScriptLookups Void + lookups = mempty + + txHash <- submitTxFromConstraints lookups constraints + awaitTxConfirmed txHash + + forWithIndex_ hashesLanguages \i (scriptHash /\ language) -> do + scriptInfo <- liftAff $ + runBlockfrostServiceTestM backend + (Just $ onBlockfrostRawResponse i scriptHash) + Nothing + (Blockfrost.getScriptInfo scriptHash) + scriptInfo `shouldEqual` Right (Just $ wrap { language }) + where + onBlockfrostRawResponse + :: Int + -> ScriptHash + -> BlockfrostEndpoint + -> BlockfrostRawResponse + -> Aff Unit + onBlockfrostRawResponse i scriptHash query rawResponse = + case query of + ScriptInfo h | h == scriptHash -> + storeBlockfrostFixture i "getScriptInfo" rawResponse + _ -> pure unit + From 34968124de8cc5b6e0390a5d767ba94ac8137165 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Thu, 12 Jan 2023 22:27:24 +0000 Subject: [PATCH 281/373] Add logs to drain wallets util --- test/Utils/DrainWallets.purs | 11 +++++++++++ 1 file changed, 11 insertions(+) diff --git a/test/Utils/DrainWallets.purs b/test/Utils/DrainWallets.purs index 4326454893..1a75136c2d 100644 --- a/test/Utils/DrainWallets.purs +++ b/test/Utils/DrainWallets.purs @@ -3,6 +3,7 @@ module Test.Ctl.Utils.DrainWallets (main) where import Prelude import Contract.Address (getWalletAddresses, ownPaymentPubKeysHashes) +import Effect.Class (liftEffect) import Contract.Config ( PrivatePaymentKeySource(PrivatePaymentKeyFile) , WalletSpec(UseKeys) @@ -94,6 +95,16 @@ run privateKey walletsDir = runContract config do , usedWallets: if Map.isEmpty utxos then [] else [ { wallet, pkh } ] } + log $ joinWith " " + [ "Checked", show $ Array.length wallets, "wallets." ] + + when (Map.isEmpty utxos) do + log "No UTxOs to spend, nothing to do." + liftEffect $ exit 0 + + log $ joinWith " " + [ "Found", show $ Map.size utxos, "in" , show $ Array.length usedWallets, "wallets." ] + let constraints = foldMap mustSpendPubKeyOutput (Map.keys utxos) <> foldMap (_.pkh >>> mustBeSignedBy) usedWallets From 611feeb7f077d3e2b72372e78eaef26347d7a891 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Fri, 13 Jan 2023 11:37:26 +0000 Subject: [PATCH 282/373] Move fixtures --- .../getCurrentEpoch-4390418473439f6cb41c582a9cea4987.json | 0 .../getProtocolParameters-7fe834fd628aa322eedeb3d8c7c1dd61.json | 0 2 files changed, 0 insertions(+), 0 deletions(-) rename fixtures/test/blockfrost/{ => getCurrentEpoch}/getCurrentEpoch-4390418473439f6cb41c582a9cea4987.json (100%) rename fixtures/test/blockfrost/{ => getProtocolParameters}/getProtocolParameters-7fe834fd628aa322eedeb3d8c7c1dd61.json (100%) diff --git a/fixtures/test/blockfrost/getCurrentEpoch-4390418473439f6cb41c582a9cea4987.json b/fixtures/test/blockfrost/getCurrentEpoch/getCurrentEpoch-4390418473439f6cb41c582a9cea4987.json similarity index 100% rename from fixtures/test/blockfrost/getCurrentEpoch-4390418473439f6cb41c582a9cea4987.json rename to fixtures/test/blockfrost/getCurrentEpoch/getCurrentEpoch-4390418473439f6cb41c582a9cea4987.json diff --git a/fixtures/test/blockfrost/getProtocolParameters-7fe834fd628aa322eedeb3d8c7c1dd61.json b/fixtures/test/blockfrost/getProtocolParameters/getProtocolParameters-7fe834fd628aa322eedeb3d8c7c1dd61.json similarity index 100% rename from fixtures/test/blockfrost/getProtocolParameters-7fe834fd628aa322eedeb3d8c7c1dd61.json rename to fixtures/test/blockfrost/getProtocolParameters/getProtocolParameters-7fe834fd628aa322eedeb3d8c7c1dd61.json From f37751382d42c836a89614e082daf006ac5b5c4d Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Fri, 13 Jan 2023 11:40:33 +0000 Subject: [PATCH 283/373] Fix pparam test --- test/Blockfrost/ProtocolParameters.purs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/test/Blockfrost/ProtocolParameters.purs b/test/Blockfrost/ProtocolParameters.purs index e20c5ca3db..a91d95be8e 100644 --- a/test/Blockfrost/ProtocolParameters.purs +++ b/test/Blockfrost/ProtocolParameters.purs @@ -22,7 +22,7 @@ import Test.Spec.Runner (defaultConfig) blockfrostFixture :: String blockfrostFixture = - "blockfrost/getProtocolParameters-7fe834fd628aa322eedeb3d8c7c1dd61.json" + "blockfrost/getProtocolParameters/getProtocolParameters-7fe834fd628aa322eedeb3d8c7c1dd61.json" ogmiosFixture :: String ogmiosFixture = From e96314e9a529addef952feb3f77e4b5ac37e3edb Mon Sep 17 00:00:00 2001 From: Emily Martins Date: Fri, 13 Jan 2023 13:45:29 +0100 Subject: [PATCH 284/373] allow keeping bundle-module output in nix bundle --- CHANGELOG.md | 2 ++ nix/default.nix | 3 +++ 2 files changed, 5 insertions(+) diff --git a/CHANGELOG.md b/CHANGELOG.md index b15a382ee0..96892d89de 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -47,6 +47,8 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) ### Added +- `bundlePursProject` allows passing of `includeBundledModule` flag to export the bundled JS module `spago bundle-module` outputs + - `Contract.Transaction` exports `mkPoolPubKeyHash` and `poolPubKeyHashToBech32` for bech32 roundtripping ([#1360](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1360)) ### Changed diff --git a/nix/default.nix b/nix/default.nix index 9d25c846eb..f3ae84a4ee 100644 --- a/nix/default.nix +++ b/nix/default.nix @@ -389,6 +389,8 @@ let # Generated `node_modules` in the Nix store. Can be passed to have better # control over individual project components , nodeModules ? projectNodeModules + # If the spago bundle-module output should be included in the derivation + , includeBundledModule ? false , ... }: pkgs.runCommand "${name}" { @@ -412,6 +414,7 @@ let spago bundle-module --no-install --no-build -m "${main}" \ --to ${bundledModuleName} mkdir ./dist + ${pkgs.lib.optionalString includeBundledModule "cp ${bundledModuleName} ./dist"} webpack --mode=production -c ${webpackConfig} -o ./dist \ --entry ./${entrypoint} mkdir $out From 90b8fc187d61e6e3b91290339dc8039190cbfece Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Fri, 13 Jan 2023 14:02:26 +0000 Subject: [PATCH 285/373] Use direct pattern --- src/Internal/Contract/QueryHandle.purs | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs index 03e3021fa6..621a6fe5f1 100644 --- a/src/Internal/Contract/QueryHandle.purs +++ b/src/Internal/Contract/QueryHandle.purs @@ -7,7 +7,7 @@ module Ctl.Internal.Contract.QueryHandle import Prelude import Contract.Log (logDebug') -import Control.Monad.Error.Class (liftEither) +import Control.Monad.Error.Class (throwError) import Control.Monad.Reader.Class (ask) import Ctl.Internal.Cardano.Types.ScriptRef (ScriptRef) import Ctl.Internal.Cardano.Types.Transaction @@ -58,8 +58,7 @@ import Ctl.Internal.Types.Chain as Chain import Ctl.Internal.Types.Datum (DataHash, Datum) import Ctl.Internal.Types.Transaction (TransactionHash, TransactionInput) import Ctl.Internal.Types.TransactionMetadata (GeneralTransactionMetadata) -import Data.Bifunctor (bimap) -import Data.Either (Either) +import Data.Either (Either(Left, Right)) import Data.Maybe (Maybe(Just, Nothing), isJust) import Data.Newtype (unwrap, wrap) import Effect.Aff (Aff) @@ -134,8 +133,9 @@ queryHandleForBlockfrostBackend _ backend = , utxosAt: runBlockfrostServiceM' <<< undefined , getChainTip: runBlockfrostServiceM' undefined , getCurrentEpoch: - runBlockfrostServiceM' Blockfrost.getCurrentEpoch - >>= bimap (show >>> error) wrap >>> liftEither + runBlockfrostServiceM' Blockfrost.getCurrentEpoch >>= case _ of + Right epoch -> pure $ wrap epoch + Left err -> throwError $ error $ show err , submitTx: runBlockfrostServiceM' <<< undefined , evaluateTx: \tx additionalUtxos -> runBlockfrostServiceM' $ undefined tx additionalUtxos From 7781dd9e814952d879ff452777796cd0e9a74844 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Fri, 13 Jan 2023 14:10:08 +0000 Subject: [PATCH 286/373] Update template --- templates/ctl-scaffold/flake.nix | 2 +- templates/ctl-scaffold/packages.dhall | 5 +++-- 2 files changed, 4 insertions(+), 3 deletions(-) diff --git a/templates/ctl-scaffold/flake.nix b/templates/ctl-scaffold/flake.nix index 69e179de7a..f28be6bdf4 100644 --- a/templates/ctl-scaffold/flake.nix +++ b/templates/ctl-scaffold/flake.nix @@ -10,7 +10,7 @@ type = "github"; owner = "Plutonomicon"; repo = "cardano-transaction-lib"; - rev = "001b639606f341489968d599fb0cef2900aeb474"; + rev = "90b8fc187d61e6e3b91290339dc8039190cbfece"; }; # To use the same version of `nixpkgs` as we do nixpkgs.follows = "ctl/nixpkgs"; diff --git a/templates/ctl-scaffold/packages.dhall b/templates/ctl-scaffold/packages.dhall index b03ab6aea2..ed09bea0a2 100644 --- a/templates/ctl-scaffold/packages.dhall +++ b/templates/ctl-scaffold/packages.dhall @@ -262,17 +262,18 @@ let additions = , cardano-transaction-lib = { dependencies = [ "aeson" - , "argonaut-codecs" , "aff" , "aff-promise" , "aff-retry" , "affjax" , "argonaut" + , "argonaut-codecs" , "arraybuffer-types" , "arrays" , "avar" , "bifunctors" , "bigints" + , "bignumber" , "checked-exceptions" , "console" , "control" @@ -348,7 +349,7 @@ let additions = , "variant" ] , repo = "https://github.com/Plutonomicon/cardano-transaction-lib.git" - , version = "001b639606f341489968d599fb0cef2900aeb474" + , version = "90b8fc187d61e6e3b91290339dc8039190cbfece" } , noble-secp256k1 = { dependencies = From 72fb77ad2b9f871810b31928c768a8575c224984 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Mon, 16 Jan 2023 14:20:47 +0100 Subject: [PATCH 287/373] Apply suggestions --- src/Internal/Service/Blockfrost.purs | 63 +++++++++++++++------------- 1 file changed, 33 insertions(+), 30 deletions(-) diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index b09028b509..47eebeb355 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -49,7 +49,8 @@ import Affjax.RequestBody (RequestBody) as Affjax import Affjax.RequestHeader (RequestHeader(ContentType, RequestHeader)) as Affjax import Affjax.ResponseFormat (string) as Affjax.ResponseFormat import Affjax.StatusCode (StatusCode(StatusCode)) as Affjax -import Control.Monad.Except.Trans (ExceptT(ExceptT), except, runExceptT) +import Control.Monad.Error.Class (liftMaybe) +import Control.Monad.Except.Trans (ExceptT(ExceptT), runExceptT) import Control.Monad.Maybe.Trans (MaybeT(MaybeT), runMaybeT) import Control.Monad.Reader.Class (ask, asks) import Control.Monad.Reader.Trans (ReaderT, runReaderT) @@ -414,10 +415,10 @@ getUtxoByOref oref@(TransactionInput { transactionId: txHash }) = runExceptT do getDatumByHash :: DataHash -> BlockfrostServiceM (Either ClientError (Maybe Datum)) -getDatumByHash dataHash = do - response <- blockfrostGetRequest (DatumCbor dataHash) - pure $ handle404AsNothing $ unwrapBlockfrostDatum <$> handleBlockfrostResponse - response +getDatumByHash dataHash = + blockfrostGetRequest (DatumCbor dataHash) <#> \response -> + handle404AsNothing + (unwrapBlockfrostDatum <$> handleBlockfrostResponse response) -------------------------------------------------------------------------------- -- Get script by hash @@ -431,36 +432,34 @@ getScriptByHash scriptHash = runExceptT $ runMaybeT do case scriptLanguage scriptInfo of NativeScript -> NativeScriptRef <$> - (MaybeT $ ExceptT getNativeScriptByHash) + MaybeT (ExceptT getNativeScriptByHash) PlutusV1Script -> - PlutusScriptRef <$> plutusV1Script <$> - (MaybeT $ ExceptT getPlutusScriptCborByHash) + PlutusScriptRef <<< plutusV1Script <$> + MaybeT (ExceptT getPlutusScriptCborByHash) PlutusV2Script -> - PlutusScriptRef <$> plutusV2Script <$> - (MaybeT $ ExceptT getPlutusScriptCborByHash) + PlutusScriptRef <<< plutusV2Script <$> + MaybeT (ExceptT getPlutusScriptCborByHash) where getNativeScriptByHash :: BlockfrostServiceM (Either ClientError (Maybe NativeScript)) - getNativeScriptByHash = runExceptT do - (nativeScript :: Maybe BlockfrostNativeScript) <- ExceptT do - response <- blockfrostGetRequest (NativeScriptByHash scriptHash) - pure $ handle404AsNothing $ handleBlockfrostResponse response - pure $ unwrap <$> nativeScript + getNativeScriptByHash = + blockfrostGetRequest (NativeScriptByHash scriptHash) <#> \response -> + map unwrapBlockfrostNativeScript <$> + handle404AsNothing (handleBlockfrostResponse response) getPlutusScriptCborByHash :: BlockfrostServiceM (Either ClientError (Maybe ByteArray)) - getPlutusScriptCborByHash = runExceptT do - (plutusScriptCbor :: Maybe BlockfrostCbor) <- ExceptT do - response <- blockfrostGetRequest (PlutusScriptCborByHash scriptHash) - pure $ handle404AsNothing $ handleBlockfrostResponse response - pure $ join $ unwrap <$> plutusScriptCbor + getPlutusScriptCborByHash = + blockfrostGetRequest (PlutusScriptCborByHash scriptHash) <#> \response -> + handle404AsNothing + (unwrapBlockfrostCbor <$> handleBlockfrostResponse response) getScriptInfo :: ScriptHash -> BlockfrostServiceM (Either ClientError (Maybe BlockfrostScriptInfo)) -getScriptInfo scriptHash = do - response <- blockfrostGetRequest (ScriptInfo scriptHash) - pure $ handle404AsNothing $ handleBlockfrostResponse response +getScriptInfo scriptHash = + blockfrostGetRequest (ScriptInfo scriptHash) <#> \response -> + handle404AsNothing (handleBlockfrostResponse response) -------------------------------------------------------------------------------- -- BlockfrostUtxosAtAddress / BlockfrostUtxosOfTransaction @@ -596,13 +595,11 @@ resolveBlockfrostTxOutput TransactionOutput { address, amount, datum, scriptRef } resolveScriptRef :: BlockfrostServiceM (Either ClientError (Maybe ScriptRef)) - resolveScriptRef = - case blockfrostTxOutput.scriptHash of - Nothing -> pure $ Right Nothing - Just scriptHash -> runExceptT do - scriptRef <- ExceptT $ getScriptByHash scriptHash - except $ Just <$> flip note scriptRef - (ClientOtherError "Blockfrost: Failed to resolve reference script") + resolveScriptRef = runExceptT do + for blockfrostTxOutput.scriptHash \scriptHash -> do + scriptRef <- ExceptT $ getScriptByHash scriptHash + flip liftMaybe scriptRef + (ClientOtherError "Blockfrost: Failed to resolve reference script") -------------------------------------------------------------------------------- -- BlockfrostScriptLanguage @@ -656,6 +653,9 @@ newtype BlockfrostNativeScript = BlockfrostNativeScript NativeScript derive instance Generic BlockfrostNativeScript _ derive instance Newtype BlockfrostNativeScript _ +unwrapBlockfrostNativeScript :: BlockfrostNativeScript -> NativeScript +unwrapBlockfrostNativeScript = unwrap + instance Show BlockfrostNativeScript where show = genericShow @@ -696,6 +696,9 @@ newtype BlockfrostCbor = BlockfrostCbor (Maybe ByteArray) derive instance Generic BlockfrostCbor _ derive instance Newtype BlockfrostCbor _ +unwrapBlockfrostCbor :: BlockfrostCbor -> Maybe ByteArray +unwrapBlockfrostCbor = unwrap + instance Show BlockfrostCbor where show = genericShow From ff361007566cdb747da0605de8c0e912b15df506 Mon Sep 17 00:00:00 2001 From: Amir Rad Date: Mon, 16 Jan 2023 13:37:24 +0000 Subject: [PATCH 288/373] Change wrapper to mlabs-scoped package & update package.json --- package-lock.json | 10 +++++----- package.json | 2 +- src/Internal/ApplyArgs.js | 3 ++- src/Internal/BalanceTx/UtxoMinAda.js | 2 +- src/Internal/Deserialization/FromBytes.js | 2 +- src/Internal/Deserialization/Keys.js | 2 +- src/Internal/Deserialization/Language.js | 2 +- src/Internal/Deserialization/NativeScript.js | 2 +- src/Internal/Deserialization/PlutusData.js | 2 +- src/Internal/Deserialization/Transaction.js | 2 +- src/Internal/Deserialization/UnspentOutput.js | 2 +- src/Internal/Hashing.js | 2 +- src/Internal/Serialization.js | 2 +- src/Internal/Serialization/Address.js | 2 +- src/Internal/Serialization/AuxiliaryData.js | 2 +- src/Internal/Serialization/BigInt.js | 2 +- src/Internal/Serialization/Hash.js | 2 +- src/Internal/Serialization/MinFee.js | 2 +- src/Internal/Serialization/NativeScript.js | 2 +- src/Internal/Serialization/PlutusData.js | 2 +- src/Internal/Serialization/PlutusScript.js | 2 +- src/Internal/Serialization/WitnessSet.js | 2 +- src/Internal/Types/BigNum.js | 2 +- src/Internal/Types/Int.js | 2 +- templates/ctl-scaffold/package-lock.json | 5 ----- templates/ctl-scaffold/package.json | 1 - test/Wallet/Cip30/SignData.js | 3 ++- 27 files changed, 31 insertions(+), 35 deletions(-) diff --git a/package-lock.json b/package-lock.json index 0680c44df5..cbfd7d8766 100644 --- a/package-lock.json +++ b/package-lock.json @@ -79,6 +79,11 @@ "@jridgewell/sourcemap-codec": "^1.4.10" } }, + "@mlabs-haskell/csl-gc-wrapper": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/@mlabs-haskell/csl-gc-wrapper/-/csl-gc-wrapper-1.0.1.tgz", + "integrity": "sha512-8pEb4BoQlD5zN+KtOCgtTg62OmLPjMa+DiJvoAzlLcWmp01P3TyJPgbEOtS+xiZpGA+1rRkdyeeLZV3wyw8Xfw==" + }, "@mlabs-haskell/json-bigint": { "version": "1.0.0", "resolved": "https://registry.npmjs.org/@mlabs-haskell/json-bigint/-/json-bigint-1.0.0.tgz", @@ -1289,11 +1294,6 @@ "randomfill": "^1.0.3" } }, - "csl-runtime-gc": { - "version": "1.0.4", - "resolved": "https://registry.npmjs.org/csl-runtime-gc/-/csl-runtime-gc-1.0.4.tgz", - "integrity": "sha512-GhYvkhTaVCtRoaX7yE2QnzEkEjDqY47LmcF+x7uph+z2XyIh/cErb8bxIwpStp2ZrNntwqtWTYBVAXCpF1++Lw==" - }, "css-select": { "version": "4.3.0", "resolved": "https://registry.npmjs.org/css-select/-/css-select-4.3.0.tgz", diff --git a/package.json b/package.json index 4b605136d2..e9443b5039 100755 --- a/package.json +++ b/package.json @@ -31,6 +31,7 @@ "@emurgo/cardano-message-signing-nodejs": "1.0.1", "@emurgo/cardano-serialization-lib-browser": "11.2.1", "@emurgo/cardano-serialization-lib-nodejs": "11.2.1", + "@mlabs-haskell/csl-gc-wrapper": "^1.0.1", "@mlabs-haskell/json-bigint": " 1.0.0", "@noble/secp256k1": "^1.7.0", "apply-args-browser": "0.0.1", @@ -40,7 +41,6 @@ "bignumber.js": "^9.1.1", "blakejs": "1.2.1", "bufferutil": "4.0.5", - "csl-runtime-gc": "^1.0.1", "jssha": "3.2.0", "node-polyfill-webpack-plugin": "1.1.4", "puppeteer-core": "^15.3.2", diff --git a/src/Internal/ApplyArgs.js b/src/Internal/ApplyArgs.js index e373a7e36f..f75586adc6 100644 --- a/src/Internal/ApplyArgs.js +++ b/src/Internal/ApplyArgs.js @@ -9,7 +9,8 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { lib = require("@emurgo/cardano-serialization-lib-nodejs"); apply_args = require("apply-args-nodejs"); } -lib = require("csl-runtime-gc")(lib); +lib = require('@mlabs-haskell/csl-gc-wrapper')(lib) +apply_args = require('@mlabs-haskell/csl-gc-wrapper')(apply_args) /** * @param {} left diff --git a/src/Internal/BalanceTx/UtxoMinAda.js b/src/Internal/BalanceTx/UtxoMinAda.js index 97910ac48d..7514d9417b 100644 --- a/src/Internal/BalanceTx/UtxoMinAda.js +++ b/src/Internal/BalanceTx/UtxoMinAda.js @@ -6,7 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } -lib = require("csl-runtime-gc")(lib); +lib = require('@mlabs-haskell/csl-gc-wrapper')(lib) exports.minAdaForOutput = maybe => txOutput => dataCost => { try { diff --git a/src/Internal/Deserialization/FromBytes.js b/src/Internal/Deserialization/FromBytes.js index ca3fce6d46..345aa09045 100644 --- a/src/Internal/Deserialization/FromBytes.js +++ b/src/Internal/Deserialization/FromBytes.js @@ -6,7 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } -lib = require("csl-runtime-gc")(lib); +lib = require('@mlabs-haskell/csl-gc-wrapper')(lib) exports._fromBytes = helper => name => bytes => { try { diff --git a/src/Internal/Deserialization/Keys.js b/src/Internal/Deserialization/Keys.js index 4ba24b9eb0..6a95249c11 100644 --- a/src/Internal/Deserialization/Keys.js +++ b/src/Internal/Deserialization/Keys.js @@ -6,7 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } -lib = require("csl-runtime-gc")(lib); +lib = require('@mlabs-haskell/csl-gc-wrapper')(lib) exports._publicKeyFromBech32 = maybe => bech32 => { try { diff --git a/src/Internal/Deserialization/Language.js b/src/Internal/Deserialization/Language.js index 1d5f172482..117d82a461 100644 --- a/src/Internal/Deserialization/Language.js +++ b/src/Internal/Deserialization/Language.js @@ -6,7 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } -lib = require("csl-runtime-gc")(lib); +lib = require('@mlabs-haskell/csl-gc-wrapper')(lib) exports._convertLanguage = langCtors => cslLang => { if (cslLang.kind() == lib.LanguageKind.PlutusV1) { diff --git a/src/Internal/Deserialization/NativeScript.js b/src/Internal/Deserialization/NativeScript.js index 7453c21a42..9214d9dc07 100644 --- a/src/Internal/Deserialization/NativeScript.js +++ b/src/Internal/Deserialization/NativeScript.js @@ -6,7 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } -lib = require("csl-runtime-gc")(lib); +lib = require('@mlabs-haskell/csl-gc-wrapper')(lib) exports._convertNativeScript = handler => ns => { switch (ns.kind()) { diff --git a/src/Internal/Deserialization/PlutusData.js b/src/Internal/Deserialization/PlutusData.js index eba58c1574..e96656408f 100644 --- a/src/Internal/Deserialization/PlutusData.js +++ b/src/Internal/Deserialization/PlutusData.js @@ -6,7 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } -lib = require("csl-runtime-gc")(lib); +lib = require('@mlabs-haskell/csl-gc-wrapper')(lib) exports._convertPlutusData = handle => pd => { switch (pd.kind()) { diff --git a/src/Internal/Deserialization/Transaction.js b/src/Internal/Deserialization/Transaction.js index bc1929edf3..375881baa0 100644 --- a/src/Internal/Deserialization/Transaction.js +++ b/src/Internal/Deserialization/Transaction.js @@ -6,7 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } -lib = require("csl-runtime-gc")(lib); +lib = require('@mlabs-haskell/csl-gc-wrapper')(lib) const call = property => object => object[property](); const callMaybe = property => maybe => object => { diff --git a/src/Internal/Deserialization/UnspentOutput.js b/src/Internal/Deserialization/UnspentOutput.js index 2a2d1c038e..95e514bf30 100644 --- a/src/Internal/Deserialization/UnspentOutput.js +++ b/src/Internal/Deserialization/UnspentOutput.js @@ -6,7 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } -lib = require("csl-runtime-gc")(lib); +lib = require('@mlabs-haskell/csl-gc-wrapper')(lib) const call = property => object => object[property](); const callMaybe = property => maybe => object => { diff --git a/src/Internal/Hashing.js b/src/Internal/Hashing.js index a2b1654d6b..4976f5fde5 100644 --- a/src/Internal/Hashing.js +++ b/src/Internal/Hashing.js @@ -10,7 +10,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } -lib = require("csl-runtime-gc")(lib); +lib = require('@mlabs-haskell/csl-gc-wrapper')(lib) exports.blake2b256Hash = bytesToHash => { return Blake2.blake2b(bytesToHash, null, 32); diff --git a/src/Internal/Serialization.js b/src/Internal/Serialization.js index 2fcb6a912f..efd17d2641 100644 --- a/src/Internal/Serialization.js +++ b/src/Internal/Serialization.js @@ -6,7 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } -lib = require("csl-runtime-gc")(lib); +lib = require('@mlabs-haskell/csl-gc-wrapper')(lib) const setter = prop => obj => value => () => obj["set_" + prop](value); diff --git a/src/Internal/Serialization/Address.js b/src/Internal/Serialization/Address.js index 7786470ecc..a48ba05c05 100644 --- a/src/Internal/Serialization/Address.js +++ b/src/Internal/Serialization/Address.js @@ -6,7 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } -lib = require("csl-runtime-gc")(lib); +lib = require('@mlabs-haskell/csl-gc-wrapper')(lib) const callClassStaticMaybe = (classname, functionname) => maybe => input => { let ret = null; diff --git a/src/Internal/Serialization/AuxiliaryData.js b/src/Internal/Serialization/AuxiliaryData.js index 5ebb56122d..8db4541393 100644 --- a/src/Internal/Serialization/AuxiliaryData.js +++ b/src/Internal/Serialization/AuxiliaryData.js @@ -6,7 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } -lib = require("csl-runtime-gc")(lib); +lib = require('@mlabs-haskell/csl-gc-wrapper')(lib) const setter = prop => obj => value => () => obj["set_" + prop](value); diff --git a/src/Internal/Serialization/BigInt.js b/src/Internal/Serialization/BigInt.js index a34da4510b..ac3ebe24a3 100644 --- a/src/Internal/Serialization/BigInt.js +++ b/src/Internal/Serialization/BigInt.js @@ -6,7 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } -lib = require("csl-runtime-gc")(lib); +lib = require('@mlabs-haskell/csl-gc-wrapper')(lib) exports._BigInt_from_str = helper => str => { try { diff --git a/src/Internal/Serialization/Hash.js b/src/Internal/Serialization/Hash.js index 11c51cdf53..7d2a4c35ca 100644 --- a/src/Internal/Serialization/Hash.js +++ b/src/Internal/Serialization/Hash.js @@ -6,7 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } -lib = require("csl-runtime-gc")(lib); +lib = require('@mlabs-haskell/csl-gc-wrapper')(lib) exports.hashToBytes = hash => { return hash.to_bytes(); diff --git a/src/Internal/Serialization/MinFee.js b/src/Internal/Serialization/MinFee.js index f6a9ca39df..e9a9c270e9 100644 --- a/src/Internal/Serialization/MinFee.js +++ b/src/Internal/Serialization/MinFee.js @@ -6,7 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } -lib = require("csl-runtime-gc")(lib); +lib = require('@mlabs-haskell/csl-gc-wrapper')(lib) exports._minFee = maybe => tx => txFeeFixed => txFeePerByte => { try { diff --git a/src/Internal/Serialization/NativeScript.js b/src/Internal/Serialization/NativeScript.js index 2db3feaa49..e464f3b8e4 100644 --- a/src/Internal/Serialization/NativeScript.js +++ b/src/Internal/Serialization/NativeScript.js @@ -6,7 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } -lib = require("csl-runtime-gc")(lib); +lib = require('@mlabs-haskell/csl-gc-wrapper')(lib) const mkScript = prop => arg => lib.NativeScript[prop](arg); diff --git a/src/Internal/Serialization/PlutusData.js b/src/Internal/Serialization/PlutusData.js index 3e7f631a46..cb20968299 100644 --- a/src/Internal/Serialization/PlutusData.js +++ b/src/Internal/Serialization/PlutusData.js @@ -6,7 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } -lib = require("csl-runtime-gc")(lib); +lib = require('@mlabs-haskell/csl-gc-wrapper')(lib) exports._mkPlutusData_bytes = bytes => lib.PlutusData.new_bytes(bytes); exports._mkPlutusData_list = list => lib.PlutusData.new_list(list); diff --git a/src/Internal/Serialization/PlutusScript.js b/src/Internal/Serialization/PlutusScript.js index ef38c2065b..32996c2184 100644 --- a/src/Internal/Serialization/PlutusScript.js +++ b/src/Internal/Serialization/PlutusScript.js @@ -6,7 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } -lib = require("csl-runtime-gc")(lib); +lib = require('@mlabs-haskell/csl-gc-wrapper')(lib) exports.newPlutusV1Script = bytes => lib.PlutusScript.new(bytes); diff --git a/src/Internal/Serialization/WitnessSet.js b/src/Internal/Serialization/WitnessSet.js index 25d2637480..b1eb85da0b 100644 --- a/src/Internal/Serialization/WitnessSet.js +++ b/src/Internal/Serialization/WitnessSet.js @@ -6,7 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } -lib = require("csl-runtime-gc")(lib); +lib = require('@mlabs-haskell/csl-gc-wrapper')(lib) exports.newTransactionWitnessSet = () => lib.TransactionWitnessSet.new(); diff --git a/src/Internal/Types/BigNum.js b/src/Internal/Types/BigNum.js index ca45b35f86..7f2b80877c 100644 --- a/src/Internal/Types/BigNum.js +++ b/src/Internal/Types/BigNum.js @@ -6,7 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } -lib = require("csl-runtime-gc")(lib); +lib = require('@mlabs-haskell/csl-gc-wrapper')(lib) exports.bnCompare = lhs => rhs => lhs.compare(rhs); diff --git a/src/Internal/Types/Int.js b/src/Internal/Types/Int.js index ce07b6e40c..4a56f197b7 100644 --- a/src/Internal/Types/Int.js +++ b/src/Internal/Types/Int.js @@ -6,7 +6,7 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { } else { lib = require("@emurgo/cardano-serialization-lib-nodejs"); } -lib = require("csl-runtime-gc")(lib); +lib = require('@mlabs-haskell/csl-gc-wrapper')(lib) exports.newPositive = lib.Int.new; exports.newNegative = lib.Int.new_negative; diff --git a/templates/ctl-scaffold/package-lock.json b/templates/ctl-scaffold/package-lock.json index aa1cd142ef..53725ab3d3 100644 --- a/templates/ctl-scaffold/package-lock.json +++ b/templates/ctl-scaffold/package-lock.json @@ -1195,11 +1195,6 @@ "randomfill": "^1.0.3" } }, - "csl-runtime-gc": { - "version": "1.0.4", - "resolved": "https://registry.npmjs.org/csl-runtime-gc/-/csl-runtime-gc-1.0.4.tgz", - "integrity": "sha512-GhYvkhTaVCtRoaX7yE2QnzEkEjDqY47LmcF+x7uph+z2XyIh/cErb8bxIwpStp2ZrNntwqtWTYBVAXCpF1++Lw==" - }, "css-select": { "version": "4.3.0", "resolved": "https://registry.npmjs.org/css-select/-/css-select-4.3.0.tgz", diff --git a/templates/ctl-scaffold/package.json b/templates/ctl-scaffold/package.json index 627043884e..1f5bcdf459 100644 --- a/templates/ctl-scaffold/package.json +++ b/templates/ctl-scaffold/package.json @@ -26,7 +26,6 @@ "@emurgo/cardano-serialization-lib-nodejs": "11.2.1", "@mlabs-haskell/json-bigint": " 1.0.0", "@noble/secp256k1": "^1.7.0", - "csl-runtime-gc": "1.0.4", "apply-args-browser": "0.0.1", "apply-args-nodejs": "0.0.1", "base64-js": "^1.5.1", diff --git a/test/Wallet/Cip30/SignData.js b/test/Wallet/Cip30/SignData.js index 695c25d909..c5135dbf82 100644 --- a/test/Wallet/Cip30/SignData.js +++ b/test/Wallet/Cip30/SignData.js @@ -8,7 +8,8 @@ if (typeof BROWSER_RUNTIME != "undefined" && BROWSER_RUNTIME) { lib = require("@emurgo/cardano-message-signing-nodejs"); csl = require("@emurgo/cardano-serialization-lib-nodejs"); } -lib = require("csl-runtime-gc")(lib); +lib = require('@mlabs-haskell/csl-gc-wrapper')(lib) +csl = require('@mlabs-haskell/csl-gc-wrapper')(csl) function opt_chain(maybe, obj) { const isNothing = x => x === null || x === undefined; From 5c146088a289df96dc26e367dbe8c36b8015ea1b Mon Sep 17 00:00:00 2001 From: Amir Rad Date: Mon, 16 Jan 2023 14:05:01 +0000 Subject: [PATCH 289/373] Add csl-gc-wrapper to template --- templates/ctl-scaffold/package-lock.json | 5 +++++ templates/ctl-scaffold/package.json | 1 + 2 files changed, 6 insertions(+) diff --git a/templates/ctl-scaffold/package-lock.json b/templates/ctl-scaffold/package-lock.json index 53725ab3d3..cc729a867c 100644 --- a/templates/ctl-scaffold/package-lock.json +++ b/templates/ctl-scaffold/package-lock.json @@ -79,6 +79,11 @@ "@jridgewell/sourcemap-codec": "^1.4.10" } }, + "@mlabs-haskell/csl-gc-wrapper": { + "version": "1.0.1", + "resolved": "https://registry.npmjs.org/@mlabs-haskell/csl-gc-wrapper/-/csl-gc-wrapper-1.0.1.tgz", + "integrity": "sha512-8pEb4BoQlD5zN+KtOCgtTg62OmLPjMa+DiJvoAzlLcWmp01P3TyJPgbEOtS+xiZpGA+1rRkdyeeLZV3wyw8Xfw==" + }, "@mlabs-haskell/json-bigint": { "version": "1.0.0", "resolved": "https://registry.npmjs.org/@mlabs-haskell/json-bigint/-/json-bigint-1.0.0.tgz", diff --git a/templates/ctl-scaffold/package.json b/templates/ctl-scaffold/package.json index 1f5bcdf459..4767cb0a03 100644 --- a/templates/ctl-scaffold/package.json +++ b/templates/ctl-scaffold/package.json @@ -24,6 +24,7 @@ "@emurgo/cardano-message-signing-nodejs": "1.0.1", "@emurgo/cardano-serialization-lib-browser": "11.2.1", "@emurgo/cardano-serialization-lib-nodejs": "11.2.1", + "@mlabs-haskell/csl-gc-wrapper": "^1.0.1", "@mlabs-haskell/json-bigint": " 1.0.0", "@noble/secp256k1": "^1.7.0", "apply-args-browser": "0.0.1", From 6ef5280bc4730c76d885f31538bf01bec36fc478 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Mon, 16 Jan 2023 21:00:50 +0000 Subject: [PATCH 290/373] Move ProtocolParameters into separate file. Apply PR suggestions --- src/Contract/ProtocolParameters.purs | 2 +- src/Internal/BalanceTx/Collateral/Select.purs | 2 +- src/Internal/BalanceTx/Types.purs | 2 +- src/Internal/BalanceTx/UtxoMinAda.purs | 6 +- src/Internal/Contract.purs | 4 +- src/Internal/Contract/Monad.purs | 10 +- src/Internal/QueryM.purs | 5 +- src/Internal/QueryM/Ogmios.purs | 294 ++--------------- src/Internal/Serialization/MinFee.purs | 4 +- src/Internal/Service/Blockfrost.purs | 112 ++++--- src/Internal/Types/ProtocolParameters.purs | 299 ++++++++++++++++++ src/Internal/Wallet/Key.purs | 2 +- test/BalanceTx/Collateral.purs | 2 +- test/Blockfrost/ProtocolParameters.purs | 5 +- test/Ogmios/Aeson.purs | 2 +- test/Plutus/Time.purs | 4 +- test/ProtocolParams.purs | 4 +- 17 files changed, 415 insertions(+), 344 deletions(-) create mode 100644 src/Internal/Types/ProtocolParameters.purs diff --git a/src/Contract/ProtocolParameters.purs b/src/Contract/ProtocolParameters.purs index 80ef6e3172..44c6a2e667 100644 --- a/src/Contract/ProtocolParameters.purs +++ b/src/Contract/ProtocolParameters.purs @@ -4,7 +4,7 @@ module Contract.ProtocolParameters import Contract.Monad (Contract) import Ctl.Internal.Contract (getProtocolParameters) as Contract -import Ctl.Internal.QueryM.Ogmios (ProtocolParameters) +import Ctl.Internal.Types.ProtocolParameters (ProtocolParameters) -- | Returns the `ProtocolParameters` from the `Contract` environment. -- | Note that this is not necessarily the current value from the ledger. diff --git a/src/Internal/BalanceTx/Collateral/Select.purs b/src/Internal/BalanceTx/Collateral/Select.purs index d009f84220..642ee1f318 100644 --- a/src/Internal/BalanceTx/Collateral/Select.purs +++ b/src/Internal/BalanceTx/Collateral/Select.purs @@ -17,7 +17,7 @@ import Ctl.Internal.Cardano.Types.TransactionUnspentOutput ) import Ctl.Internal.Cardano.Types.Value (NonAdaAsset) import Ctl.Internal.Cardano.Types.Value (getNonAdaAsset, valueToCoin') as Value -import Ctl.Internal.QueryM.Ogmios (CoinsPerUtxoUnit) +import Ctl.Internal.Types.ProtocolParameters (CoinsPerUtxoUnit) import Ctl.Internal.Types.Transaction (TransactionInput) import Data.BigInt (BigInt) import Data.BigInt (fromInt) as BigInt diff --git a/src/Internal/BalanceTx/Types.purs b/src/Internal/BalanceTx/Types.purs index 7490424e2f..2aa25fec0b 100644 --- a/src/Internal/BalanceTx/Types.purs +++ b/src/Internal/BalanceTx/Types.purs @@ -29,8 +29,8 @@ import Ctl.Internal.BalanceTx.Constraints import Ctl.Internal.BalanceTx.Error (BalanceTxError) import Ctl.Internal.Cardano.Types.Transaction (Costmdls(Costmdls), Transaction) import Ctl.Internal.Contract.Monad (Contract, ContractEnv) -import Ctl.Internal.QueryM.Ogmios (CoinsPerUtxoUnit) import Ctl.Internal.Serialization.Address (NetworkId) +import Ctl.Internal.Types.ProtocolParameters (CoinsPerUtxoUnit) import Ctl.Internal.Types.ScriptLookups (UnattachedUnbalancedTx) import Ctl.Internal.Types.Scripts (Language) import Ctl.Internal.Wallet (Cip30Wallet, cip30Wallet) diff --git a/src/Internal/BalanceTx/UtxoMinAda.purs b/src/Internal/BalanceTx/UtxoMinAda.purs index 45f5cc4b8b..8258f3017e 100644 --- a/src/Internal/BalanceTx/UtxoMinAda.purs +++ b/src/Internal/BalanceTx/UtxoMinAda.purs @@ -10,9 +10,6 @@ import Ctl.Internal.BalanceTx.FakeOutput (fakeOutputWithValue) import Ctl.Internal.Cardano.Types.Transaction (TransactionOutput) import Ctl.Internal.Cardano.Types.Value (Coin(Coin), lovelaceValueOf) import Ctl.Internal.FfiHelpers (MaybeFfiHelper, maybeFfiHelper) -import Ctl.Internal.QueryM.Ogmios - ( CoinsPerUtxoUnit(CoinsPerUtxoWord, CoinsPerUtxoByte) - ) import Ctl.Internal.Serialization (convertTxOutput) import Ctl.Internal.Serialization.Types (DataCost) import Ctl.Internal.Serialization.Types (TransactionOutput) as Csl @@ -22,6 +19,9 @@ import Ctl.Internal.Types.BigNum , maxValue , toBigInt ) as BigNum +import Ctl.Internal.Types.ProtocolParameters + ( CoinsPerUtxoUnit(CoinsPerUtxoWord, CoinsPerUtxoByte) + ) import Data.BigInt (BigInt) import Data.Maybe (Maybe, fromJust) import Effect (Effect) diff --git a/src/Internal/Contract.purs b/src/Internal/Contract.purs index 1543ab0a45..419ad125b1 100644 --- a/src/Internal/Contract.purs +++ b/src/Internal/Contract.purs @@ -5,8 +5,8 @@ import Prelude import Control.Monad.Reader.Class (asks) import Ctl.Internal.Contract.Monad (Contract) import Ctl.Internal.Contract.QueryHandle (getQueryHandle) -import Ctl.Internal.QueryM.Ogmios (ProtocolParameters) as Ogmios import Ctl.Internal.Types.Chain (Tip) +import Ctl.Internal.Types.ProtocolParameters (ProtocolParameters) import Effect.Aff.Class (liftAff) getChainTip :: Contract Tip @@ -16,7 +16,7 @@ getChainTip = do -- | Returns the `ProtocolParameters` from the environment. -- | Note that this is not necessarily the current value from the ledger. -getProtocolParameters :: Contract Ogmios.ProtocolParameters +getProtocolParameters :: Contract ProtocolParameters getProtocolParameters = asks $ _.ledgerConstants >>> _.pparams diff --git a/src/Internal/Contract/Monad.purs b/src/Internal/Contract/Monad.purs index 5cda7c6e33..c055f99096 100644 --- a/src/Internal/Contract/Monad.purs +++ b/src/Internal/Contract/Monad.purs @@ -54,10 +54,11 @@ import Ctl.Internal.QueryM ) import Ctl.Internal.QueryM.Kupo (isTxConfirmedAff) -- TODO: Move/translate these types into Cardano -import Ctl.Internal.QueryM.Ogmios (ProtocolParameters, SystemStart(SystemStart)) as Ogmios +import Ctl.Internal.QueryM.Ogmios (SystemStart(SystemStart)) as Ogmios import Ctl.Internal.Serialization.Address (NetworkId(TestnetId, MainnetId)) import Ctl.Internal.Service.Blockfrost (runBlockfrostServiceM) import Ctl.Internal.Service.Blockfrost as Blockfrost +import Ctl.Internal.Types.ProtocolParameters (ProtocolParameters) import Ctl.Internal.Types.UsedTxOuts (UsedTxOuts, isTxOutRefUsed, newUsedTxOuts) import Ctl.Internal.Wallet (Wallet, actionBasedOnWallet) import Ctl.Internal.Wallet.Spec (WalletSpec, mkWalletBySpec) @@ -166,7 +167,7 @@ type ContractEnv = -- ledgerConstants are values that technically may change, but we assume to be -- constant during Contract evaluation , ledgerConstants :: - { pparams :: Ogmios.ProtocolParameters + { pparams :: ProtocolParameters , systemStart :: Ogmios.SystemStart } } @@ -234,18 +235,19 @@ getLedgerConstants :: Logger -> QueryBackend -> Aff - { pparams :: Ogmios.ProtocolParameters + { pparams :: ProtocolParameters , systemStart :: Ogmios.SystemStart } getLedgerConstants logger = case _ of CtlBackend { ogmios: { ws } } _ -> do - pparams <- getProtocolParametersAff ws logger + pparams <- unwrap <$> getProtocolParametersAff ws logger systemStart <- getSystemStartAff ws logger pure { pparams, systemStart } BlockfrostBackend blockfrost _ -> runBlockfrostServiceM blockfrost do pparams <- Blockfrost.getProtocolParameters >>= lmap (show >>> error) >>> liftEither let + -- TODO: https://github.com/plutonomicon/cardano-transaction-lib/pull/1377 systemStart = Ogmios.SystemStart "2022-10-25T00:00:00Z" pure { pparams, systemStart } diff --git a/src/Internal/QueryM.purs b/src/Internal/QueryM.purs index 8658221247..bd858519ba 100644 --- a/src/Internal/QueryM.purs +++ b/src/Internal/QueryM.purs @@ -113,6 +113,7 @@ import Ctl.Internal.QueryM.JsonWsp as JsonWsp import Ctl.Internal.QueryM.Ogmios ( AdditionalUtxoSet , DelegationsAndRewardsR + , OgmiosProtocolParameters , PoolIdsR , PoolParametersR , TxHash @@ -262,7 +263,7 @@ instance Parallel (QueryMT ParAff) (QueryMT Aff) where getProtocolParametersAff :: OgmiosWebSocket -> (LogLevel -> String -> Effect Unit) - -> Aff Ogmios.ProtocolParameters + -> Aff OgmiosProtocolParameters getProtocolParametersAff ogmiosWs logger = mkOgmiosRequestAff ogmiosWs logger Ogmios.queryProtocolParametersCall _.getProtocolParameters @@ -624,7 +625,7 @@ type OgmiosListeners = , submit :: SubmitTxListenerSet , evaluate :: ListenerSet (CborBytes /\ AdditionalUtxoSet) Ogmios.TxEvaluationR - , getProtocolParameters :: ListenerSet Unit Ogmios.ProtocolParameters + , getProtocolParameters :: ListenerSet Unit OgmiosProtocolParameters , eraSummaries :: ListenerSet Unit Ogmios.EraSummaries , currentEpoch :: ListenerSet Unit Ogmios.CurrentEpoch , systemStart :: ListenerSet Unit Ogmios.SystemStart diff --git a/src/Internal/QueryM/Ogmios.purs b/src/Internal/QueryM/Ogmios.purs index 26a12c9869..729ef263f3 100644 --- a/src/Internal/QueryM/Ogmios.purs +++ b/src/Internal/QueryM/Ogmios.purs @@ -4,12 +4,8 @@ module Ctl.Internal.QueryM.Ogmios ( ChainOrigin(ChainOrigin) , ChainPoint , ChainTipQR(CtChainOrigin, CtChainPoint) - , CostModelV1 - , CostModelV2 - , CoinsPerUtxoUnit(CoinsPerUtxoByte, CoinsPerUtxoWord) , CurrentEpoch(CurrentEpoch) , DelegationsAndRewardsR(DelegationsAndRewardsR) - , Epoch(Epoch) , EpochLength(EpochLength) , EraSummaries(EraSummaries) , EraSummary(EraSummary) @@ -24,7 +20,7 @@ module Ctl.Internal.QueryM.Ogmios , PParamRational(PParamRational) , PoolParameters , PoolParametersR(PoolParametersR) - , ProtocolParameters(ProtocolParameters) + , OgmiosProtocolParameters(OgmiosProtocolParameters) , RedeemerPointer , RelativeTime(RelativeTime) , SafeZone(SafeZone) @@ -57,9 +53,6 @@ module Ctl.Internal.QueryM.Ogmios , acquireMempoolSnapshotCall , aesonArray , aesonObject - , convertCostModel - , convertPlutusV1CostModel - , convertPlutusV2CostModel , evaluateTxCall , queryPoolIdsCall , mempoolSnapshotHasTxCall @@ -122,7 +115,6 @@ import Ctl.Internal.Cardano.Types.Transaction , ExUnits , Ipv4(Ipv4) , Ipv6(Ipv6) - , Nonce , PoolMetadata(PoolMetadata) , PoolMetadataHash(PoolMetadataHash) , PoolPubKeyHash @@ -131,7 +123,6 @@ import Ctl.Internal.Cardano.Types.Transaction , URL(URL) , UnitInterval ) -import Ctl.Internal.Cardano.Types.Transaction as T import Ctl.Internal.Cardano.Types.Value ( Coin(Coin) , CurrencySymbol @@ -160,9 +151,17 @@ import Ctl.Internal.Types.ByteArray , hexToByteArray ) import Ctl.Internal.Types.CborBytes (CborBytes, cborBytesToHex) -import Ctl.Internal.Types.Int as Csl import Ctl.Internal.Types.Natural (Natural) import Ctl.Internal.Types.Natural (fromString) as Natural +import Ctl.Internal.Types.ProtocolParameters + ( CoinsPerUtxoUnit(CoinsPerUtxoWord, CoinsPerUtxoByte) + , CostModelV1 + , CostModelV2 + , Epoch(Epoch) + , ProtocolParameters(ProtocolParameters) + , convertPlutusV1CostModel + , convertPlutusV2CostModel + ) import Ctl.Internal.Types.Rational (Rational, (%)) import Ctl.Internal.Types.Rational as Rational import Ctl.Internal.Types.RedeemerTag (RedeemerTag) @@ -174,7 +173,7 @@ import Ctl.Internal.Types.Scripts ) import Ctl.Internal.Types.TokenName (TokenName, getTokenName, mkTokenName) import Ctl.Internal.Types.VRFKeyHash (VRFKeyHash(VRFKeyHash)) -import Data.Array (catMaybes, index, reverse) +import Data.Array (catMaybes, index) import Data.Array (head, length, replicate) as Array import Data.BigInt (BigInt) import Data.BigInt as BigInt @@ -182,8 +181,6 @@ import Data.Either (Either(Left, Right), either, note) import Data.Foldable (fold, foldl) import Data.Generic.Rep (class Generic) import Data.Int (fromString) as Int -import Data.List (List) -import Data.List as List import Data.Map (Map) import Data.Map as Map import Data.Maybe (Maybe(Just, Nothing), fromJust, fromMaybe, maybe) @@ -208,7 +205,6 @@ import Data.UInt as UInt import Foreign.Object (Object) import Foreign.Object (singleton, toUnfoldable) as ForeignObject import Foreign.Object as Object -import Heterogeneous.Folding (class HFoldl, hfoldl) import Partial.Unsafe (unsafePartial) import Untagged.TypeCheck (class HasRuntimeType) import Untagged.Union (type (|+|), toEither1) @@ -240,7 +236,7 @@ queryEraSummariesCall = mkOgmiosCallType } -- | Queries Ogmios for the current protocol parameters -queryProtocolParametersCall :: JsonWspCall Unit ProtocolParameters +queryProtocolParametersCall :: JsonWspCall Unit OgmiosProtocolParameters queryProtocolParametersCall = mkOgmiosCallType { methodname: "Query" , args: const { query: "currentProtocolParameters" } @@ -507,20 +503,6 @@ instance EncodeAeson RelativeTime where instance Show RelativeTime where show (RelativeTime rt) = showWithParens "RelativeTime" rt --- | An epoch number or length with greater precision for Ogmios than --- | `Cardano.Types.Epoch`. [ 0 .. 18446744073709552000 ] -newtype Epoch = Epoch BigInt - -derive instance Generic Epoch _ -derive instance Newtype Epoch _ -derive newtype instance Eq Epoch -derive newtype instance Ord Epoch -derive newtype instance DecodeAeson Epoch -derive newtype instance EncodeAeson Epoch - -instance Show Epoch where - show (Epoch e) = showWithParens "Epoch" e - newtype EraSummaryParameters = EraSummaryParameters { epochLength :: EpochLength -- 0-18446744073709552000 An epoch number or length. , slotLength :: SlotLength -- <= MAX_SAFE_INTEGER (=9,007,199,254,740,992) @@ -1010,51 +992,16 @@ type ProtocolParametersRaw = , "maxCollateralInputs" :: UInt } -data CoinsPerUtxoUnit = CoinsPerUtxoByte Coin | CoinsPerUtxoWord Coin +newtype OgmiosProtocolParameters = OgmiosProtocolParameters ProtocolParameters -derive instance Generic CoinsPerUtxoUnit _ -derive instance Eq CoinsPerUtxoUnit +derive instance Newtype OgmiosProtocolParameters _ +derive instance Generic OgmiosProtocolParameters _ +derive instance Eq OgmiosProtocolParameters -instance Show CoinsPerUtxoUnit where +instance Show OgmiosProtocolParameters where show = genericShow --- Based on `Cardano.Api.ProtocolParameters.ProtocolParameters` from --- `cardano-api`. -newtype ProtocolParameters = ProtocolParameters - { protocolVersion :: UInt /\ UInt - , decentralization :: Rational - , extraPraosEntropy :: Maybe Nonce - , maxBlockHeaderSize :: UInt - , maxBlockBodySize :: UInt - , maxTxSize :: UInt - , txFeeFixed :: UInt - , txFeePerByte :: UInt - , stakeAddressDeposit :: Coin - , stakePoolDeposit :: Coin - , minPoolCost :: Coin - , poolRetireMaxEpoch :: Epoch - , stakePoolTargetNum :: UInt - , poolPledgeInfluence :: Rational - , monetaryExpansion :: Rational - , treasuryCut :: Rational - , coinsPerUtxoUnit :: CoinsPerUtxoUnit - , costModels :: Costmdls - , prices :: ExUnitPrices - , maxTxExUnits :: ExUnits - , maxBlockExUnits :: ExUnits - , maxValueSize :: UInt - , collateralPercent :: UInt - , maxCollateralInputs :: UInt - } - -derive instance Newtype ProtocolParameters _ -derive instance Generic ProtocolParameters _ -derive instance Eq ProtocolParameters - -instance Show ProtocolParameters where - show = genericShow - -instance DecodeAeson ProtocolParameters where +instance DecodeAeson OgmiosProtocolParameters where decodeAeson aeson = do ps :: ProtocolParametersRaw <- decodeAeson aeson prices <- decodePrices ps @@ -1064,7 +1011,7 @@ instance DecodeAeson ProtocolParameters where pure $ (CoinsPerUtxoByte <<< Coin <$> ps.coinsPerUtxoByte) <|> (CoinsPerUtxoWord <<< Coin <$> ps.coinsPerUtxoWord) - pure $ ProtocolParameters + pure $ OgmiosProtocolParameters $ ProtocolParameters { protocolVersion: ps.protocolVersion.major /\ ps.protocolVersion.minor -- The following two parameters were removed from Babbage , decentralization: zero @@ -1108,209 +1055,6 @@ instance DecodeAeson ProtocolParameters where stepPrice <- rationalToSubcoin ps.prices.steps pure { memPrice, stepPrice } -- ExUnits --- | A type that represents a JSON-encoded Costmodel in format used by Ogmios -type CostModelV1 = - ( "addInteger-cpu-arguments-intercept" :: Csl.Int - , "addInteger-cpu-arguments-slope" :: Csl.Int - , "addInteger-memory-arguments-intercept" :: Csl.Int - , "addInteger-memory-arguments-slope" :: Csl.Int - , "appendByteString-cpu-arguments-intercept" :: Csl.Int - , "appendByteString-cpu-arguments-slope" :: Csl.Int - , "appendByteString-memory-arguments-intercept" :: Csl.Int - , "appendByteString-memory-arguments-slope" :: Csl.Int - , "appendString-cpu-arguments-intercept" :: Csl.Int - , "appendString-cpu-arguments-slope" :: Csl.Int - , "appendString-memory-arguments-intercept" :: Csl.Int - , "appendString-memory-arguments-slope" :: Csl.Int - , "bData-cpu-arguments" :: Csl.Int - , "bData-memory-arguments" :: Csl.Int - , "blake2b_256-cpu-arguments-intercept" :: Csl.Int - , "blake2b_256-cpu-arguments-slope" :: Csl.Int - , "blake2b_256-memory-arguments" :: Csl.Int - , "cekApplyCost-exBudgetCPU" :: Csl.Int - , "cekApplyCost-exBudgetMemory" :: Csl.Int - , "cekBuiltinCost-exBudgetCPU" :: Csl.Int - , "cekBuiltinCost-exBudgetMemory" :: Csl.Int - , "cekConstCost-exBudgetCPU" :: Csl.Int - , "cekConstCost-exBudgetMemory" :: Csl.Int - , "cekDelayCost-exBudgetCPU" :: Csl.Int - , "cekDelayCost-exBudgetMemory" :: Csl.Int - , "cekForceCost-exBudgetCPU" :: Csl.Int - , "cekForceCost-exBudgetMemory" :: Csl.Int - , "cekLamCost-exBudgetCPU" :: Csl.Int - , "cekLamCost-exBudgetMemory" :: Csl.Int - , "cekStartupCost-exBudgetCPU" :: Csl.Int - , "cekStartupCost-exBudgetMemory" :: Csl.Int - , "cekVarCost-exBudgetCPU" :: Csl.Int - , "cekVarCost-exBudgetMemory" :: Csl.Int - , "chooseData-cpu-arguments" :: Csl.Int - , "chooseData-memory-arguments" :: Csl.Int - , "chooseList-cpu-arguments" :: Csl.Int - , "chooseList-memory-arguments" :: Csl.Int - , "chooseUnit-cpu-arguments" :: Csl.Int - , "chooseUnit-memory-arguments" :: Csl.Int - , "consByteString-cpu-arguments-intercept" :: Csl.Int - , "consByteString-cpu-arguments-slope" :: Csl.Int - , "consByteString-memory-arguments-intercept" :: Csl.Int - , "consByteString-memory-arguments-slope" :: Csl.Int - , "constrData-cpu-arguments" :: Csl.Int - , "constrData-memory-arguments" :: Csl.Int - , "decodeUtf8-cpu-arguments-intercept" :: Csl.Int - , "decodeUtf8-cpu-arguments-slope" :: Csl.Int - , "decodeUtf8-memory-arguments-intercept" :: Csl.Int - , "decodeUtf8-memory-arguments-slope" :: Csl.Int - , "divideInteger-cpu-arguments-constant" :: Csl.Int - , "divideInteger-cpu-arguments-model-arguments-intercept" :: Csl.Int - , "divideInteger-cpu-arguments-model-arguments-slope" :: Csl.Int - , "divideInteger-memory-arguments-intercept" :: Csl.Int - , "divideInteger-memory-arguments-minimum" :: Csl.Int - , "divideInteger-memory-arguments-slope" :: Csl.Int - , "encodeUtf8-cpu-arguments-intercept" :: Csl.Int - , "encodeUtf8-cpu-arguments-slope" :: Csl.Int - , "encodeUtf8-memory-arguments-intercept" :: Csl.Int - , "encodeUtf8-memory-arguments-slope" :: Csl.Int - , "equalsByteString-cpu-arguments-constant" :: Csl.Int - , "equalsByteString-cpu-arguments-intercept" :: Csl.Int - , "equalsByteString-cpu-arguments-slope" :: Csl.Int - , "equalsByteString-memory-arguments" :: Csl.Int - , "equalsData-cpu-arguments-intercept" :: Csl.Int - , "equalsData-cpu-arguments-slope" :: Csl.Int - , "equalsData-memory-arguments" :: Csl.Int - , "equalsInteger-cpu-arguments-intercept" :: Csl.Int - , "equalsInteger-cpu-arguments-slope" :: Csl.Int - , "equalsInteger-memory-arguments" :: Csl.Int - , "equalsString-cpu-arguments-constant" :: Csl.Int - , "equalsString-cpu-arguments-intercept" :: Csl.Int - , "equalsString-cpu-arguments-slope" :: Csl.Int - , "equalsString-memory-arguments" :: Csl.Int - , "fstPair-cpu-arguments" :: Csl.Int - , "fstPair-memory-arguments" :: Csl.Int - , "headList-cpu-arguments" :: Csl.Int - , "headList-memory-arguments" :: Csl.Int - , "iData-cpu-arguments" :: Csl.Int - , "iData-memory-arguments" :: Csl.Int - , "ifThenElse-cpu-arguments" :: Csl.Int - , "ifThenElse-memory-arguments" :: Csl.Int - , "indexByteString-cpu-arguments" :: Csl.Int - , "indexByteString-memory-arguments" :: Csl.Int - , "lengthOfByteString-cpu-arguments" :: Csl.Int - , "lengthOfByteString-memory-arguments" :: Csl.Int - , "lessThanByteString-cpu-arguments-intercept" :: Csl.Int - , "lessThanByteString-cpu-arguments-slope" :: Csl.Int - , "lessThanByteString-memory-arguments" :: Csl.Int - , "lessThanEqualsByteString-cpu-arguments-intercept" :: Csl.Int - , "lessThanEqualsByteString-cpu-arguments-slope" :: Csl.Int - , "lessThanEqualsByteString-memory-arguments" :: Csl.Int - , "lessThanEqualsInteger-cpu-arguments-intercept" :: Csl.Int - , "lessThanEqualsInteger-cpu-arguments-slope" :: Csl.Int - , "lessThanEqualsInteger-memory-arguments" :: Csl.Int - , "lessThanInteger-cpu-arguments-intercept" :: Csl.Int - , "lessThanInteger-cpu-arguments-slope" :: Csl.Int - , "lessThanInteger-memory-arguments" :: Csl.Int - , "listData-cpu-arguments" :: Csl.Int - , "listData-memory-arguments" :: Csl.Int - , "mapData-cpu-arguments" :: Csl.Int - , "mapData-memory-arguments" :: Csl.Int - , "mkCons-cpu-arguments" :: Csl.Int - , "mkCons-memory-arguments" :: Csl.Int - , "mkNilData-cpu-arguments" :: Csl.Int - , "mkNilData-memory-arguments" :: Csl.Int - , "mkNilPairData-cpu-arguments" :: Csl.Int - , "mkNilPairData-memory-arguments" :: Csl.Int - , "mkPairData-cpu-arguments" :: Csl.Int - , "mkPairData-memory-arguments" :: Csl.Int - , "modInteger-cpu-arguments-constant" :: Csl.Int - , "modInteger-cpu-arguments-model-arguments-intercept" :: Csl.Int - , "modInteger-cpu-arguments-model-arguments-slope" :: Csl.Int - , "modInteger-memory-arguments-intercept" :: Csl.Int - , "modInteger-memory-arguments-minimum" :: Csl.Int - , "modInteger-memory-arguments-slope" :: Csl.Int - , "multiplyInteger-cpu-arguments-intercept" :: Csl.Int - , "multiplyInteger-cpu-arguments-slope" :: Csl.Int - , "multiplyInteger-memory-arguments-intercept" :: Csl.Int - , "multiplyInteger-memory-arguments-slope" :: Csl.Int - , "nullList-cpu-arguments" :: Csl.Int - , "nullList-memory-arguments" :: Csl.Int - , "quotientInteger-cpu-arguments-constant" :: Csl.Int - , "quotientInteger-cpu-arguments-model-arguments-intercept" :: Csl.Int - , "quotientInteger-cpu-arguments-model-arguments-slope" :: Csl.Int - , "quotientInteger-memory-arguments-intercept" :: Csl.Int - , "quotientInteger-memory-arguments-minimum" :: Csl.Int - , "quotientInteger-memory-arguments-slope" :: Csl.Int - , "remainderInteger-cpu-arguments-constant" :: Csl.Int - , "remainderInteger-cpu-arguments-model-arguments-intercept" :: Csl.Int - , "remainderInteger-cpu-arguments-model-arguments-slope" :: Csl.Int - , "remainderInteger-memory-arguments-intercept" :: Csl.Int - , "remainderInteger-memory-arguments-minimum" :: Csl.Int - , "remainderInteger-memory-arguments-slope" :: Csl.Int - , "sha2_256-cpu-arguments-intercept" :: Csl.Int - , "sha2_256-cpu-arguments-slope" :: Csl.Int - , "sha2_256-memory-arguments" :: Csl.Int - , "sha3_256-cpu-arguments-intercept" :: Csl.Int - , "sha3_256-cpu-arguments-slope" :: Csl.Int - , "sha3_256-memory-arguments" :: Csl.Int - , "sliceByteString-cpu-arguments-intercept" :: Csl.Int - , "sliceByteString-cpu-arguments-slope" :: Csl.Int - , "sliceByteString-memory-arguments-intercept" :: Csl.Int - , "sliceByteString-memory-arguments-slope" :: Csl.Int - , "sndPair-cpu-arguments" :: Csl.Int - , "sndPair-memory-arguments" :: Csl.Int - , "subtractInteger-cpu-arguments-intercept" :: Csl.Int - , "subtractInteger-cpu-arguments-slope" :: Csl.Int - , "subtractInteger-memory-arguments-intercept" :: Csl.Int - , "subtractInteger-memory-arguments-slope" :: Csl.Int - , "tailList-cpu-arguments" :: Csl.Int - , "tailList-memory-arguments" :: Csl.Int - , "trace-cpu-arguments" :: Csl.Int - , "trace-memory-arguments" :: Csl.Int - , "unBData-cpu-arguments" :: Csl.Int - , "unBData-memory-arguments" :: Csl.Int - , "unConstrData-cpu-arguments" :: Csl.Int - , "unConstrData-memory-arguments" :: Csl.Int - , "unIData-cpu-arguments" :: Csl.Int - , "unIData-memory-arguments" :: Csl.Int - , "unListData-cpu-arguments" :: Csl.Int - , "unListData-memory-arguments" :: Csl.Int - , "unMapData-cpu-arguments" :: Csl.Int - , "unMapData-memory-arguments" :: Csl.Int - , "verifyEd25519Signature-cpu-arguments-intercept" :: Csl.Int - , "verifyEd25519Signature-cpu-arguments-slope" :: Csl.Int - , "verifyEd25519Signature-memory-arguments" :: Csl.Int - ) - -type CostModelV2 = - ( "serialiseData-cpu-arguments-intercept" :: Csl.Int - , "serialiseData-cpu-arguments-slope" :: Csl.Int - , "serialiseData-memory-arguments-intercept" :: Csl.Int - , "serialiseData-memory-arguments-slope" :: Csl.Int - , "verifyEcdsaSecp256k1Signature-cpu-arguments" :: Csl.Int - , "verifyEcdsaSecp256k1Signature-memory-arguments" :: Csl.Int - , "verifySchnorrSecp256k1Signature-cpu-arguments-intercept" :: Csl.Int - , "verifySchnorrSecp256k1Signature-cpu-arguments-slope" :: Csl.Int - , "verifySchnorrSecp256k1Signature-memory-arguments" :: Csl.Int - | CostModelV1 - ) - --- This assumes that cost models are stored in lexicographical order -convertCostModel - :: forall costModel - . HFoldl (List Csl.Int -> Csl.Int -> List Csl.Int) (List Csl.Int) costModel - (List Csl.Int) - => costModel - -> T.CostModel -convertCostModel model = wrap $ reverse $ List.toUnfoldable $ hfoldl - ((\xs x -> x List.: xs) :: List Csl.Int -> Csl.Int -> List Csl.Int) - (mempty :: List Csl.Int) - model - --- Specialized conversions to only perform the type level traversals once - -convertPlutusV1CostModel :: Record CostModelV1 -> T.CostModel -convertPlutusV1CostModel = convertCostModel - -convertPlutusV2CostModel :: Record CostModelV2 -> T.CostModel -convertPlutusV2CostModel = convertCostModel - ---------------- CHAIN TIP QUERY RESPONSE & PARSING data ChainTipQR diff --git a/src/Internal/Serialization/MinFee.purs b/src/Internal/Serialization/MinFee.purs index 6ba3b9175f..12cd006944 100644 --- a/src/Internal/Serialization/MinFee.purs +++ b/src/Internal/Serialization/MinFee.purs @@ -10,12 +10,14 @@ import Ctl.Internal.Cardano.Types.Transaction as T import Ctl.Internal.Cardano.Types.Value (Coin) import Ctl.Internal.FfiHelpers (MaybeFfiHelper, maybeFfiHelper) import Ctl.Internal.NativeScripts (getMaximumSigners) -import Ctl.Internal.QueryM.Ogmios (ProtocolParameters(ProtocolParameters)) import Ctl.Internal.Serialization as Serialization import Ctl.Internal.Serialization.Hash (Ed25519KeyHash) import Ctl.Internal.Serialization.Types (ExUnitPrices, Transaction) import Ctl.Internal.Types.BigNum (BigNum) import Ctl.Internal.Types.BigNum as BigNum +import Ctl.Internal.Types.ProtocolParameters + ( ProtocolParameters(ProtocolParameters) + ) import Data.Array as Array import Data.Lens ((.~)) import Data.Maybe (Maybe(Just), fromJust, fromMaybe) diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index ef6d5cecdc..2e3c89ff4a 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -41,7 +41,6 @@ import Affjax.RequestHeader (RequestHeader(ContentType, RequestHeader)) as Affja import Affjax.ResponseFormat (string) as Affjax.ResponseFormat import Affjax.StatusCode (StatusCode(StatusCode)) as Affjax import Control.Alt ((<|>)) -import Control.Monad.Except (ExceptT(ExceptT), runExceptT) import Control.Monad.Reader.Class (ask, asks) import Control.Monad.Reader.Trans (ReaderT, runReaderT) import Ctl.Internal.Cardano.Types.Transaction (Costmdls(Costmdls)) @@ -58,7 +57,16 @@ import Ctl.Internal.Deserialization.FromBytes (fromBytes) import Ctl.Internal.Deserialization.Transaction ( convertGeneralTransactionMetadata ) -import Ctl.Internal.QueryM.Ogmios +import Ctl.Internal.ServerConfig (ServerConfig, mkHttpUrl) +import Ctl.Internal.Service.Error + ( ClientError(ClientHttpError, ClientHttpResponseError, ClientDecodeJsonError) + , ServiceError(ServiceBlockfrostError) + ) +import Ctl.Internal.Types.BigNum (BigNum) +import Ctl.Internal.Types.BigNum as BigNum +import Ctl.Internal.Types.ByteArray (byteArrayToHex) +import Ctl.Internal.Types.CborBytes (CborBytes) +import Ctl.Internal.Types.ProtocolParameters ( CoinsPerUtxoUnit(CoinsPerUtxoWord, CoinsPerUtxoByte) , CostModelV1 , CostModelV2 @@ -66,16 +74,7 @@ import Ctl.Internal.QueryM.Ogmios , ProtocolParameters(ProtocolParameters) , convertPlutusV1CostModel , convertPlutusV2CostModel - , rationalToSubcoin ) -import Ctl.Internal.QueryM.Ogmios as Ogmios -import Ctl.Internal.ServerConfig (ServerConfig, mkHttpUrl) -import Ctl.Internal.Service.Error - ( ClientError(ClientHttpError, ClientHttpResponseError, ClientDecodeJsonError) - , ServiceError(ServiceBlockfrostError) - ) -import Ctl.Internal.Types.ByteArray (byteArrayToHex) -import Ctl.Internal.Types.CborBytes (CborBytes) import Ctl.Internal.Types.Rational (Rational, reduce) import Ctl.Internal.Types.Scripts (Language(PlutusV1, PlutusV2)) import Ctl.Internal.Types.Transaction (TransactionHash) @@ -97,7 +96,7 @@ import Data.Newtype (class Newtype, unwrap, wrap) import Data.Number (infinity) import Data.Show.Generic (genericShow) import Data.Traversable (for, for_) -import Data.Tuple.Nested ((/\)) +import Data.Tuple.Nested (type (/\), (/\)) import Data.UInt (UInt) import Effect.Aff (Aff) import Effect.Aff.Class (liftAff) @@ -264,19 +263,16 @@ handleBlockfrostResponse (Right { status: Affjax.StatusCode statusCode, body }) body # lmap (ClientDecodeJsonError body) <<< (decodeAeson <=< parseJsonStringToAeson) -getCurrentEpoch - :: BlockfrostServiceM (Either ClientError BigInt) -getCurrentEpoch = runExceptT do - BlockfrostCurrentEpoch { epoch } <- ExceptT $ blockfrostGetRequest LatestEpoch - <#> handleBlockfrostResponse - pure epoch +getCurrentEpoch :: BlockfrostServiceM (Either ClientError BigInt) +getCurrentEpoch = + blockfrostGetRequest LatestEpoch <#> + handleBlockfrostResponse >>> map unwrapBlockfrostCurrentEpoch getProtocolParameters - :: BlockfrostServiceM (Either ClientError Ogmios.ProtocolParameters) -getProtocolParameters = runExceptT do - BlockfrostProtocolParameters params <- ExceptT $ - blockfrostGetRequest LatestProtocolParameters <#> handleBlockfrostResponse - pure params + :: BlockfrostServiceM (Either ClientError ProtocolParameters) +getProtocolParameters = + blockfrostGetRequest LatestProtocolParameters <#> + handleBlockfrostResponse >>> map unwrapBlockfrostProtocolParameters isTxConfirmed :: TransactionHash @@ -335,15 +331,21 @@ unwrapBlockfrostMetadata (BlockfrostMetadata metadata) = metadata -- `getCurrentEpoch` reponse parsing -------------------------------------------------------------------------------- -newtype BlockfrostCurrentEpoch = BlockfrostCurrentEpoch { epoch :: BigInt } +newtype BlockfrostCurrentEpoch = BlockfrostCurrentEpoch BigInt derive instance Generic BlockfrostCurrentEpoch _ derive instance Newtype BlockfrostCurrentEpoch _ -derive newtype instance DecodeAeson BlockfrostCurrentEpoch instance Show BlockfrostCurrentEpoch where show = genericShow +instance DecodeAeson BlockfrostCurrentEpoch where + decodeAeson a = decodeAeson a <#> + \({ epoch } :: { epoch :: BigInt }) -> wrap epoch + +unwrapBlockfrostCurrentEpoch :: BlockfrostCurrentEpoch -> BigInt +unwrapBlockfrostCurrentEpoch = unwrap + -------------------------------------------------------------------------------- -- `getProtocolParameters` reponse parsing -------------------------------------------------------------------------------- @@ -389,34 +391,52 @@ type BlockfrostProtocolParametersRaw = , "coins_per_utxo_word" :: Maybe (Stringed BigInt) } -bigNumberToRational :: BigNumber -> Maybe Rational -bigNumberToRational bn = do - let - (numerator' /\ denominator') = toFraction bn (BigNumber.fromNumber infinity) - numerator <- BigInt.fromString $ BigNumber.toString numerator' - denominator <- BigInt.fromString $ BigNumber.toString denominator' +toFraction' :: Finite BigNumber -> String /\ String +toFraction' bn = + (BigNumber.toString numerator /\ BigNumber.toString denominator) + where + (numerator /\ denominator) = toFraction (unpackFinite bn) + (BigNumber.fromNumber infinity) + +bigNumberToRational :: Finite BigNumber -> Either JsonDecodeError Rational +bigNumberToRational bn = note (TypeMismatch "Rational") do + numerator <- BigInt.fromString numerator' + denominator <- BigInt.fromString denominator' reduce numerator denominator - -bigNumberToRational' :: BigNumber -> Either JsonDecodeError Rational -bigNumberToRational' = note (TypeMismatch "Rational") <<< bigNumberToRational + where + (numerator' /\ denominator') = toFraction' bn + +bigNumberToPrice + :: Finite BigNumber + -> Either JsonDecodeError { numerator :: BigNum, denominator :: BigNum } +bigNumberToPrice bn = note (TypeMismatch "Rational") do + numerator <- BigNum.fromString numerator' + denominator <- BigNum.fromString denominator' + pure { numerator, denominator } + where + (numerator' /\ denominator') = toFraction' bn newtype BlockfrostProtocolParameters = BlockfrostProtocolParameters ProtocolParameters +derive instance Generic BlockfrostProtocolParameters _ +derive instance Newtype BlockfrostProtocolParameters _ + +unwrapBlockfrostProtocolParameters + :: BlockfrostProtocolParameters -> ProtocolParameters +unwrapBlockfrostProtocolParameters = unwrap + +instance Show BlockfrostProtocolParameters where + show = genericShow + instance DecodeAeson BlockfrostProtocolParameters where decodeAeson = decodeAeson >=> \(raw :: BlockfrostProtocolParametersRaw) -> do - poolPledgeInfluence <- bigNumberToRational' $ unpackFinite raw.a0 - monetaryExpansion <- bigNumberToRational' $ unpackFinite raw.rho - treasuryCut <- bigNumberToRational' $ unpackFinite raw.tau - prices <- do - let - convert bn = do - rational <- bigNumberToRational $ unpackFinite bn - rationalToSubcoin $ wrap rational - - memPrice <- note (TypeMismatch "Rational") $ convert raw.price_mem - stepPrice <- note (TypeMismatch "Rational") $ convert raw.price_step - pure { memPrice, stepPrice } + poolPledgeInfluence <- bigNumberToRational raw.a0 + monetaryExpansion <- bigNumberToRational raw.rho + treasuryCut <- bigNumberToRational raw.tau + memPrice <- bigNumberToPrice raw.price_mem + stepPrice <- bigNumberToPrice raw.price_step + let prices = { memPrice, stepPrice } coinsPerUtxoUnit <- maybe diff --git a/src/Internal/Types/ProtocolParameters.purs b/src/Internal/Types/ProtocolParameters.purs new file mode 100644 index 0000000000..856be9e420 --- /dev/null +++ b/src/Internal/Types/ProtocolParameters.purs @@ -0,0 +1,299 @@ +module Ctl.Internal.Types.ProtocolParameters + ( ProtocolParameters(ProtocolParameters) + , Epoch(Epoch) + , CoinsPerUtxoUnit(CoinsPerUtxoByte, CoinsPerUtxoWord) + , CostModelV1 + , CostModelV2 + , convertPlutusV1CostModel + , convertPlutusV2CostModel + ) where + +import Prelude + +import Aeson + ( class DecodeAeson + , class EncodeAeson + ) +import Ctl.Internal.Cardano.Types.Transaction + ( Costmdls + , ExUnitPrices + , ExUnits + , Nonce + ) +import Ctl.Internal.Cardano.Types.Transaction as T +import Ctl.Internal.Cardano.Types.Value (Coin) +import Ctl.Internal.Helpers (showWithParens) +import Ctl.Internal.Types.Int as Csl +import Ctl.Internal.Types.Rational (Rational) +import Data.Array (reverse) +import Data.BigInt (BigInt) +import Data.Generic.Rep (class Generic) +import Data.List (List) +import Data.List as List +import Data.Maybe (Maybe) +import Data.Newtype (class Newtype, wrap) +import Data.Show.Generic (genericShow) +import Data.Tuple.Nested (type (/\)) +import Data.UInt (UInt) +import Heterogeneous.Folding (class HFoldl, hfoldl) + +-- | An epoch number or length with greater precision for Ogmios than +-- | `Cardano.Types.Epoch`. [ 0 .. 18446744073709552000 ] +newtype Epoch = Epoch BigInt + +derive instance Generic Epoch _ +derive instance Newtype Epoch _ +derive newtype instance Eq Epoch +derive newtype instance Ord Epoch +derive newtype instance DecodeAeson Epoch +derive newtype instance EncodeAeson Epoch + +instance Show Epoch where + show (Epoch e) = showWithParens "Epoch" e + +data CoinsPerUtxoUnit = CoinsPerUtxoByte Coin | CoinsPerUtxoWord Coin + +derive instance Generic CoinsPerUtxoUnit _ +derive instance Eq CoinsPerUtxoUnit + +instance Show CoinsPerUtxoUnit where + show = genericShow + +-- Based on `Cardano.Api.ProtocolParameters.ProtocolParameters` from +-- `cardano-api`. +newtype ProtocolParameters = ProtocolParameters + { protocolVersion :: UInt /\ UInt + , decentralization :: Rational + , extraPraosEntropy :: Maybe Nonce + , maxBlockHeaderSize :: UInt + , maxBlockBodySize :: UInt + , maxTxSize :: UInt + , txFeeFixed :: UInt + , txFeePerByte :: UInt + , stakeAddressDeposit :: Coin + , stakePoolDeposit :: Coin + , minPoolCost :: Coin + , poolRetireMaxEpoch :: Epoch + , stakePoolTargetNum :: UInt + , poolPledgeInfluence :: Rational + , monetaryExpansion :: Rational + , treasuryCut :: Rational + , coinsPerUtxoUnit :: CoinsPerUtxoUnit + , costModels :: Costmdls + , prices :: ExUnitPrices + , maxTxExUnits :: ExUnits + , maxBlockExUnits :: ExUnits + , maxValueSize :: UInt + , collateralPercent :: UInt + , maxCollateralInputs :: UInt + } + +derive instance Newtype ProtocolParameters _ +derive instance Generic ProtocolParameters _ +derive instance Eq ProtocolParameters + +instance Show ProtocolParameters where + show = genericShow + +-- | A type that represents a JSON-encoded Costmodel in format used by Ogmios +type CostModelV1 = + ( "addInteger-cpu-arguments-intercept" :: Csl.Int + , "addInteger-cpu-arguments-slope" :: Csl.Int + , "addInteger-memory-arguments-intercept" :: Csl.Int + , "addInteger-memory-arguments-slope" :: Csl.Int + , "appendByteString-cpu-arguments-intercept" :: Csl.Int + , "appendByteString-cpu-arguments-slope" :: Csl.Int + , "appendByteString-memory-arguments-intercept" :: Csl.Int + , "appendByteString-memory-arguments-slope" :: Csl.Int + , "appendString-cpu-arguments-intercept" :: Csl.Int + , "appendString-cpu-arguments-slope" :: Csl.Int + , "appendString-memory-arguments-intercept" :: Csl.Int + , "appendString-memory-arguments-slope" :: Csl.Int + , "bData-cpu-arguments" :: Csl.Int + , "bData-memory-arguments" :: Csl.Int + , "blake2b_256-cpu-arguments-intercept" :: Csl.Int + , "blake2b_256-cpu-arguments-slope" :: Csl.Int + , "blake2b_256-memory-arguments" :: Csl.Int + , "cekApplyCost-exBudgetCPU" :: Csl.Int + , "cekApplyCost-exBudgetMemory" :: Csl.Int + , "cekBuiltinCost-exBudgetCPU" :: Csl.Int + , "cekBuiltinCost-exBudgetMemory" :: Csl.Int + , "cekConstCost-exBudgetCPU" :: Csl.Int + , "cekConstCost-exBudgetMemory" :: Csl.Int + , "cekDelayCost-exBudgetCPU" :: Csl.Int + , "cekDelayCost-exBudgetMemory" :: Csl.Int + , "cekForceCost-exBudgetCPU" :: Csl.Int + , "cekForceCost-exBudgetMemory" :: Csl.Int + , "cekLamCost-exBudgetCPU" :: Csl.Int + , "cekLamCost-exBudgetMemory" :: Csl.Int + , "cekStartupCost-exBudgetCPU" :: Csl.Int + , "cekStartupCost-exBudgetMemory" :: Csl.Int + , "cekVarCost-exBudgetCPU" :: Csl.Int + , "cekVarCost-exBudgetMemory" :: Csl.Int + , "chooseData-cpu-arguments" :: Csl.Int + , "chooseData-memory-arguments" :: Csl.Int + , "chooseList-cpu-arguments" :: Csl.Int + , "chooseList-memory-arguments" :: Csl.Int + , "chooseUnit-cpu-arguments" :: Csl.Int + , "chooseUnit-memory-arguments" :: Csl.Int + , "consByteString-cpu-arguments-intercept" :: Csl.Int + , "consByteString-cpu-arguments-slope" :: Csl.Int + , "consByteString-memory-arguments-intercept" :: Csl.Int + , "consByteString-memory-arguments-slope" :: Csl.Int + , "constrData-cpu-arguments" :: Csl.Int + , "constrData-memory-arguments" :: Csl.Int + , "decodeUtf8-cpu-arguments-intercept" :: Csl.Int + , "decodeUtf8-cpu-arguments-slope" :: Csl.Int + , "decodeUtf8-memory-arguments-intercept" :: Csl.Int + , "decodeUtf8-memory-arguments-slope" :: Csl.Int + , "divideInteger-cpu-arguments-constant" :: Csl.Int + , "divideInteger-cpu-arguments-model-arguments-intercept" :: Csl.Int + , "divideInteger-cpu-arguments-model-arguments-slope" :: Csl.Int + , "divideInteger-memory-arguments-intercept" :: Csl.Int + , "divideInteger-memory-arguments-minimum" :: Csl.Int + , "divideInteger-memory-arguments-slope" :: Csl.Int + , "encodeUtf8-cpu-arguments-intercept" :: Csl.Int + , "encodeUtf8-cpu-arguments-slope" :: Csl.Int + , "encodeUtf8-memory-arguments-intercept" :: Csl.Int + , "encodeUtf8-memory-arguments-slope" :: Csl.Int + , "equalsByteString-cpu-arguments-constant" :: Csl.Int + , "equalsByteString-cpu-arguments-intercept" :: Csl.Int + , "equalsByteString-cpu-arguments-slope" :: Csl.Int + , "equalsByteString-memory-arguments" :: Csl.Int + , "equalsData-cpu-arguments-intercept" :: Csl.Int + , "equalsData-cpu-arguments-slope" :: Csl.Int + , "equalsData-memory-arguments" :: Csl.Int + , "equalsInteger-cpu-arguments-intercept" :: Csl.Int + , "equalsInteger-cpu-arguments-slope" :: Csl.Int + , "equalsInteger-memory-arguments" :: Csl.Int + , "equalsString-cpu-arguments-constant" :: Csl.Int + , "equalsString-cpu-arguments-intercept" :: Csl.Int + , "equalsString-cpu-arguments-slope" :: Csl.Int + , "equalsString-memory-arguments" :: Csl.Int + , "fstPair-cpu-arguments" :: Csl.Int + , "fstPair-memory-arguments" :: Csl.Int + , "headList-cpu-arguments" :: Csl.Int + , "headList-memory-arguments" :: Csl.Int + , "iData-cpu-arguments" :: Csl.Int + , "iData-memory-arguments" :: Csl.Int + , "ifThenElse-cpu-arguments" :: Csl.Int + , "ifThenElse-memory-arguments" :: Csl.Int + , "indexByteString-cpu-arguments" :: Csl.Int + , "indexByteString-memory-arguments" :: Csl.Int + , "lengthOfByteString-cpu-arguments" :: Csl.Int + , "lengthOfByteString-memory-arguments" :: Csl.Int + , "lessThanByteString-cpu-arguments-intercept" :: Csl.Int + , "lessThanByteString-cpu-arguments-slope" :: Csl.Int + , "lessThanByteString-memory-arguments" :: Csl.Int + , "lessThanEqualsByteString-cpu-arguments-intercept" :: Csl.Int + , "lessThanEqualsByteString-cpu-arguments-slope" :: Csl.Int + , "lessThanEqualsByteString-memory-arguments" :: Csl.Int + , "lessThanEqualsInteger-cpu-arguments-intercept" :: Csl.Int + , "lessThanEqualsInteger-cpu-arguments-slope" :: Csl.Int + , "lessThanEqualsInteger-memory-arguments" :: Csl.Int + , "lessThanInteger-cpu-arguments-intercept" :: Csl.Int + , "lessThanInteger-cpu-arguments-slope" :: Csl.Int + , "lessThanInteger-memory-arguments" :: Csl.Int + , "listData-cpu-arguments" :: Csl.Int + , "listData-memory-arguments" :: Csl.Int + , "mapData-cpu-arguments" :: Csl.Int + , "mapData-memory-arguments" :: Csl.Int + , "mkCons-cpu-arguments" :: Csl.Int + , "mkCons-memory-arguments" :: Csl.Int + , "mkNilData-cpu-arguments" :: Csl.Int + , "mkNilData-memory-arguments" :: Csl.Int + , "mkNilPairData-cpu-arguments" :: Csl.Int + , "mkNilPairData-memory-arguments" :: Csl.Int + , "mkPairData-cpu-arguments" :: Csl.Int + , "mkPairData-memory-arguments" :: Csl.Int + , "modInteger-cpu-arguments-constant" :: Csl.Int + , "modInteger-cpu-arguments-model-arguments-intercept" :: Csl.Int + , "modInteger-cpu-arguments-model-arguments-slope" :: Csl.Int + , "modInteger-memory-arguments-intercept" :: Csl.Int + , "modInteger-memory-arguments-minimum" :: Csl.Int + , "modInteger-memory-arguments-slope" :: Csl.Int + , "multiplyInteger-cpu-arguments-intercept" :: Csl.Int + , "multiplyInteger-cpu-arguments-slope" :: Csl.Int + , "multiplyInteger-memory-arguments-intercept" :: Csl.Int + , "multiplyInteger-memory-arguments-slope" :: Csl.Int + , "nullList-cpu-arguments" :: Csl.Int + , "nullList-memory-arguments" :: Csl.Int + , "quotientInteger-cpu-arguments-constant" :: Csl.Int + , "quotientInteger-cpu-arguments-model-arguments-intercept" :: Csl.Int + , "quotientInteger-cpu-arguments-model-arguments-slope" :: Csl.Int + , "quotientInteger-memory-arguments-intercept" :: Csl.Int + , "quotientInteger-memory-arguments-minimum" :: Csl.Int + , "quotientInteger-memory-arguments-slope" :: Csl.Int + , "remainderInteger-cpu-arguments-constant" :: Csl.Int + , "remainderInteger-cpu-arguments-model-arguments-intercept" :: Csl.Int + , "remainderInteger-cpu-arguments-model-arguments-slope" :: Csl.Int + , "remainderInteger-memory-arguments-intercept" :: Csl.Int + , "remainderInteger-memory-arguments-minimum" :: Csl.Int + , "remainderInteger-memory-arguments-slope" :: Csl.Int + , "sha2_256-cpu-arguments-intercept" :: Csl.Int + , "sha2_256-cpu-arguments-slope" :: Csl.Int + , "sha2_256-memory-arguments" :: Csl.Int + , "sha3_256-cpu-arguments-intercept" :: Csl.Int + , "sha3_256-cpu-arguments-slope" :: Csl.Int + , "sha3_256-memory-arguments" :: Csl.Int + , "sliceByteString-cpu-arguments-intercept" :: Csl.Int + , "sliceByteString-cpu-arguments-slope" :: Csl.Int + , "sliceByteString-memory-arguments-intercept" :: Csl.Int + , "sliceByteString-memory-arguments-slope" :: Csl.Int + , "sndPair-cpu-arguments" :: Csl.Int + , "sndPair-memory-arguments" :: Csl.Int + , "subtractInteger-cpu-arguments-intercept" :: Csl.Int + , "subtractInteger-cpu-arguments-slope" :: Csl.Int + , "subtractInteger-memory-arguments-intercept" :: Csl.Int + , "subtractInteger-memory-arguments-slope" :: Csl.Int + , "tailList-cpu-arguments" :: Csl.Int + , "tailList-memory-arguments" :: Csl.Int + , "trace-cpu-arguments" :: Csl.Int + , "trace-memory-arguments" :: Csl.Int + , "unBData-cpu-arguments" :: Csl.Int + , "unBData-memory-arguments" :: Csl.Int + , "unConstrData-cpu-arguments" :: Csl.Int + , "unConstrData-memory-arguments" :: Csl.Int + , "unIData-cpu-arguments" :: Csl.Int + , "unIData-memory-arguments" :: Csl.Int + , "unListData-cpu-arguments" :: Csl.Int + , "unListData-memory-arguments" :: Csl.Int + , "unMapData-cpu-arguments" :: Csl.Int + , "unMapData-memory-arguments" :: Csl.Int + , "verifyEd25519Signature-cpu-arguments-intercept" :: Csl.Int + , "verifyEd25519Signature-cpu-arguments-slope" :: Csl.Int + , "verifyEd25519Signature-memory-arguments" :: Csl.Int + ) + +type CostModelV2 = + ( "serialiseData-cpu-arguments-intercept" :: Csl.Int + , "serialiseData-cpu-arguments-slope" :: Csl.Int + , "serialiseData-memory-arguments-intercept" :: Csl.Int + , "serialiseData-memory-arguments-slope" :: Csl.Int + , "verifyEcdsaSecp256k1Signature-cpu-arguments" :: Csl.Int + , "verifyEcdsaSecp256k1Signature-memory-arguments" :: Csl.Int + , "verifySchnorrSecp256k1Signature-cpu-arguments-intercept" :: Csl.Int + , "verifySchnorrSecp256k1Signature-cpu-arguments-slope" :: Csl.Int + , "verifySchnorrSecp256k1Signature-memory-arguments" :: Csl.Int + | CostModelV1 + ) + +-- This assumes that cost models are stored in lexicographical order +convertCostModel + :: forall costModel + . HFoldl (List Csl.Int -> Csl.Int -> List Csl.Int) (List Csl.Int) costModel + (List Csl.Int) + => costModel + -> T.CostModel +convertCostModel model = wrap $ reverse $ List.toUnfoldable $ hfoldl + ((\xs x -> x List.: xs) :: List Csl.Int -> Csl.Int -> List Csl.Int) + (mempty :: List Csl.Int) + model + +-- Specialized conversions to only perform the type level traversals once + +convertPlutusV1CostModel :: Record CostModelV1 -> T.CostModel +convertPlutusV1CostModel = convertCostModel + +convertPlutusV2CostModel :: Record CostModelV2 -> T.CostModel +convertPlutusV2CostModel = convertCostModel diff --git a/src/Internal/Wallet/Key.purs b/src/Internal/Wallet/Key.purs index 595557d3f1..7b0a56ebff 100644 --- a/src/Internal/Wallet/Key.purs +++ b/src/Internal/Wallet/Key.purs @@ -33,7 +33,6 @@ import Ctl.Internal.Deserialization.Keys , privateKeyToBech32 ) import Ctl.Internal.Deserialization.WitnessSet as Deserialization.WitnessSet -import Ctl.Internal.QueryM.Ogmios (CoinsPerUtxoUnit) import Ctl.Internal.Serialization ( publicKeyHash ) @@ -49,6 +48,7 @@ import Ctl.Internal.Serialization.Address ) import Ctl.Internal.Serialization.Keys (publicKeyFromPrivateKey) import Ctl.Internal.Serialization.Types (PrivateKey) +import Ctl.Internal.Types.ProtocolParameters (CoinsPerUtxoUnit) import Ctl.Internal.Types.RawBytes (RawBytes) import Ctl.Internal.Wallet.Cip30 (DataSignature) import Ctl.Internal.Wallet.Cip30.SignData (signData) as Cip30SignData diff --git a/test/BalanceTx/Collateral.purs b/test/BalanceTx/Collateral.purs index 2aa90ab025..152a759466 100644 --- a/test/BalanceTx/Collateral.purs +++ b/test/BalanceTx/Collateral.purs @@ -20,8 +20,8 @@ import Ctl.Internal.Cardano.Types.Value ( lovelaceValueOf , mkSingletonNonAdaAsset ) as Value -import Ctl.Internal.QueryM.Ogmios (CoinsPerUtxoUnit) import Ctl.Internal.Test.TestPlanM (TestPlanM) +import Ctl.Internal.Types.ProtocolParameters (CoinsPerUtxoUnit) import Ctl.Internal.Types.Transaction (TransactionHash, TransactionInput) import Data.Array (length, range, replicate, zipWith) as Array import Data.BigInt (fromInt) as BigInt diff --git a/test/Blockfrost/ProtocolParameters.purs b/test/Blockfrost/ProtocolParameters.purs index a91d95be8e..a7bb5c0d10 100644 --- a/test/Blockfrost/ProtocolParameters.purs +++ b/test/Blockfrost/ProtocolParameters.purs @@ -5,6 +5,9 @@ import Prelude import Aeson (class DecodeAeson, decodeJsonString) import Contract.Test.Mote (TestPlanM, interpretWithConfig) import Control.Monad.Error.Class (liftEither) +import Ctl.Internal.QueryM.Ogmios + ( OgmiosProtocolParameters(OgmiosProtocolParameters) + ) import Ctl.Internal.Service.Blockfrost ( BlockfrostProtocolParameters(BlockfrostProtocolParameters) ) @@ -45,6 +48,6 @@ suite = group "Blockfrost" do test "ProtocolParameter parsing verification" do BlockfrostProtocolParameters blockfrostFixture' <- loadFixture blockfrostFixture - ogmiosFixture' <- loadFixture ogmiosFixture + OgmiosProtocolParameters ogmiosFixture' <- loadFixture ogmiosFixture blockfrostFixture' `shouldEqual` ogmiosFixture' diff --git a/test/Ogmios/Aeson.purs b/test/Ogmios/Aeson.purs index a499f6a1bf..e38a5ac5ec 100644 --- a/test/Ogmios/Aeson.purs +++ b/test/Ogmios/Aeson.purs @@ -166,7 +166,7 @@ suite = group "Ogmios Aeson tests" do "systemStart" -> handle (Proxy :: _ O.SystemStart) "eraSummaries" -> handle (Proxy :: _ O.EraSummaries) "currentProtocolParameters" -> handle - (Proxy :: _ O.ProtocolParameters) + (Proxy :: _ O.OgmiosProtocolParameters) "poolIds" -> handle (Proxy :: _ O.PoolIdsR) "poolParameters" -> handle diff --git a/test/Plutus/Time.purs b/test/Plutus/Time.purs index 120b37d2e8..44540b6556 100644 --- a/test/Plutus/Time.purs +++ b/test/Plutus/Time.purs @@ -5,8 +5,7 @@ module Test.Ctl.Internal.Plutus.Time import Prelude import Ctl.Internal.QueryM.Ogmios - ( Epoch(Epoch) - , EpochLength(EpochLength) + ( EpochLength(EpochLength) , EraSummaries(EraSummaries) , EraSummary(EraSummary) , EraSummaryParameters(EraSummaryParameters) @@ -40,6 +39,7 @@ import Ctl.Internal.Types.Interval ) , ToOnChainPosixTimeRangeError(PosixTimeToSlotError', SlotToPosixTimeError') ) +import Ctl.Internal.Types.ProtocolParameters (Epoch(Epoch)) import Data.BigInt as BigInt import Data.Int as Int import Data.Maybe (Maybe(Just, Nothing)) diff --git a/test/ProtocolParams.purs b/test/ProtocolParams.purs index 916d8781d5..efdfc08df6 100644 --- a/test/ProtocolParams.purs +++ b/test/ProtocolParams.purs @@ -5,7 +5,7 @@ module Test.Ctl.ProtocolParams import Prelude import Aeson (decodeAeson) -import Ctl.Internal.QueryM.Ogmios (ProtocolParameters) +import Ctl.Internal.QueryM.Ogmios (OgmiosProtocolParameters) import Ctl.Internal.Test.TestPlanM (TestPlanM) import Data.Either (Either, isRight) import Effect.Aff (Aff) @@ -19,5 +19,5 @@ suite = do "./fixtures/test/ogmios/currentProtocolParameters.json" group "ProtocolParameters parser" $ do test "is able to parse ogmios response fixture" $ - (decodeAeson aeson :: Either _ ProtocolParameters) `shouldSatisfy` + (decodeAeson aeson :: Either _ OgmiosProtocolParameters) `shouldSatisfy` isRight From 13cf77fab6a9eacab5890786c29cbfb7174ed457 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Tue, 17 Jan 2023 11:04:24 +0000 Subject: [PATCH 291/373] Run spago2nix generate on template --- templates/ctl-scaffold/spago-packages.nix | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/templates/ctl-scaffold/spago-packages.nix b/templates/ctl-scaffold/spago-packages.nix index 1ea67501d4..25ee87b506 100644 --- a/templates/ctl-scaffold/spago-packages.nix +++ b/templates/ctl-scaffold/spago-packages.nix @@ -201,7 +201,7 @@ let name = "bignumber"; version = "705923edd892a3397b90d28ce7db9a7181dcd599"; src = pkgs.fetchgit { - url = "https://github.com/mlabs-haskell/purescript-bignumber"; + url = "https://github.com/jy14898/purescript-bignumber"; rev = "705923edd892a3397b90d28ce7db9a7181dcd599"; sha256 = "0wddkx161xk457r1mb1f1r79l8qgxja0xhdvxjd1ai43nwp9cgkf"; }; @@ -211,11 +211,11 @@ let "cardano-transaction-lib" = pkgs.stdenv.mkDerivation { name = "cardano-transaction-lib"; - version = "001b639606f341489968d599fb0cef2900aeb474"; + version = "90b8fc187d61e6e3b91290339dc8039190cbfece"; src = pkgs.fetchgit { url = "https://github.com/Plutonomicon/cardano-transaction-lib.git"; - rev = "001b639606f341489968d599fb0cef2900aeb474"; - sha256 = "1rbpq2ikndjar8h3hpq5yz4mqga7276ggdbws34ppq3miczh9czz"; + rev = "90b8fc187d61e6e3b91290339dc8039190cbfece"; + sha256 = "0ajvywggfy63jzf88lvjhl7wjqyzs6q6livnhr1q329qw0dhhss9"; }; phases = "installPhase"; installPhase = "ln -s $src $out"; From 8ae284cbdddf065e5b8ab534af2608dbbbf976f9 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Tue, 17 Jan 2023 11:13:37 +0000 Subject: [PATCH 292/373] Remove dummy export, add type annotations and formatting --- src/Internal/Contract/Monad.purs | 2 +- src/Internal/Service/Blockfrost.purs | 16 ++++------------ 2 files changed, 5 insertions(+), 13 deletions(-) diff --git a/src/Internal/Contract/Monad.purs b/src/Internal/Contract/Monad.purs index 0ead6d78cf..3efe61655b 100644 --- a/src/Internal/Contract/Monad.purs +++ b/src/Internal/Contract/Monad.purs @@ -239,7 +239,7 @@ getLedgerConstants logger = case _ of pparams <- getProtocolParametersAff ws logger systemStart <- getSystemStartAff ws logger pure { pparams, systemStart } - -- Temporarily use CtlBackend to get constants + -- FIXME Temporarily use CtlBackend to get constants BlockfrostBackend _ (Just ctlBackend) -> getLedgerConstants logger (CtlBackend ctlBackend Nothing) BlockfrostBackend _ _ -> undefined diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index 2f4b15dd37..27788d2668 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -16,7 +16,6 @@ module Ctl.Internal.Service.Blockfrost , isTxConfirmed , runBlockfrostServiceM , runBlockfrostServiceTestM - , dummyExport , submitTx , evaluateTx ) where @@ -84,7 +83,6 @@ import Effect.Aff (Aff) import Effect.Aff.Class (liftAff) import Effect.Class (liftEffect) import Effect.Exception (error) -import Undefined (undefined) -------------------------------------------------------------------------------- -- BlockfrostServiceM @@ -176,9 +174,6 @@ realizeEndpoint endpoint = TransactionMetadata txHash -> "/txs/" <> byteArrayToHex (unwrap txHash) <> "/metadata/cbor" -dummyExport :: Unit -> Unit -dummyExport _ = undefined blockfrostPostRequest - blockfrostGetRequest :: BlockfrostEndpoint -> BlockfrostServiceM (Either Affjax.Error (Affjax.Response String)) @@ -269,10 +264,7 @@ submitTx tx = do -> BlockfrostServiceM (Either Affjax.Error (Affjax.Response String)) request cbor = blockfrostPostRequest SubmitTransaction (MediaType "application/cbor") - $ Just - $ Affjax.arrayView - $ unwrap - $ unwrap cbor + (Just $ Affjax.arrayView $ unwrap $ unwrap cbor) evaluateTx :: Transaction -> BlockfrostServiceM TxEvaluationR evaluateTx tx = do @@ -292,9 +284,7 @@ evaluateTx tx = do -> BlockfrostServiceM (Either Affjax.Error (Affjax.Response String)) request cbor = blockfrostPostRequest EvaluateTransaction (MediaType "application/cbor") - $ Just - $ Affjax.string - $ cborBytesToHex cbor + (Just $ Affjax.string $ cborBytesToHex cbor) data BlockfrostEvaluateTx = BlockfrostEvaluateTx (Either Aeson TxEvaluationR) @@ -306,10 +296,12 @@ instance Show BlockfrostEvaluateTx where instance DecodeAeson BlockfrostEvaluateTx where decodeAeson aeson = success <|> failure <#> BlockfrostEvaluateTx where + success :: Either JsonDecodeError (Either Aeson TxEvaluationR) success = do { result } :: { result :: TxEvaluationR } <- decodeAeson aeson pure $ Right result + failure :: Either JsonDecodeError (Either Aeson TxEvaluationR) failure = pure $ Left aeson unwrapBlockfrostEvaluateTx :: BlockfrostEvaluateTx -> Either Aeson TxEvaluationR From 5facf32c4814751d06cea8a045c99d13ac5daefe Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Tue, 17 Jan 2023 15:09:22 +0100 Subject: [PATCH 293/373] Fix formatting --- templates/ctl-scaffold/flake.nix | 322 +++++++++++++++---------------- 1 file changed, 161 insertions(+), 161 deletions(-) diff --git a/templates/ctl-scaffold/flake.nix b/templates/ctl-scaffold/flake.nix index 6a5cde42be..f28be6bdf4 100644 --- a/templates/ctl-scaffold/flake.nix +++ b/templates/ctl-scaffold/flake.nix @@ -12,176 +12,176 @@ repo = "cardano-transaction-lib"; rev = "90b8fc187d61e6e3b91290339dc8039190cbfece"; }; - # To use the same version of `nixpkgs` as we do - nixpkgs.follows = "ctl/nixpkgs"; - }; + # To use the same version of `nixpkgs` as we do + nixpkgs.follows = "ctl/nixpkgs"; + }; - outputs = { self, nixpkgs, ctl, ... }@inputs: - let - supportedSystems = [ - "x86_64-linux" - "x86_64-darwin" - "aarch64-linux" - "aarch64-darwin" - ]; - perSystem = nixpkgs.lib.genAttrs supportedSystems; + outputs = { self, nixpkgs, ctl, ... }@inputs: + let + supportedSystems = [ + "x86_64-linux" + "x86_64-darwin" + "aarch64-linux" + "aarch64-darwin" + ]; + perSystem = nixpkgs.lib.genAttrs supportedSystems; - # generate `pkgs` with CTL's overlays applied. This gives you access to - # various additional packages. The versions are the same as those that CTL uses. - nixpkgsFor = system: import nixpkgs { - inherit system; - overlays = [ - ctl.overlays.purescript - ctl.overlays.runtime - ctl.overlays.spago - ]; - }; + # generate `pkgs` with CTL's overlays applied. This gives you access to + # various additional packages. The versions are the same as those that CTL uses. + nixpkgsFor = system: import nixpkgs { + inherit system; + overlays = [ + ctl.overlays.purescript + ctl.overlays.runtime + ctl.overlays.spago + ]; + }; - # The configuration for the CTL runtime, which will be passed to the - # expression that builds the JSON file used by Arion. This value can be - # shared between `buildCtlRuntime` and `launchCtlRuntime`, as shown below - # - # You can refer to the final configuration value by passing a function - # that takes a single arugment. Alternatively, you can pass an attrset - # directly. - # - # Here we demonstrate how to add `extraServices` and `extraDockerCompose`. - # For the other attributes, which have default values, - # consult `defaultConfig` in `nix/runtime.nix`. - runtimeConfig = { }; - # runtimeConfig = final: with final; { - # # You can add new services to the runtime. These should correspond to - # # Arion's `service` definition. The default is the empty attribute set - # extraServices = { - # # an image from dockerhub - # foo = { - # service = { - # image = "bar:foo"; - # command = [ - # "baz" - # "--quux" - # ]; - # }; + # The configuration for the CTL runtime, which will be passed to the + # expression that builds the JSON file used by Arion. This value can be + # shared between `buildCtlRuntime` and `launchCtlRuntime`, as shown below + # + # You can refer to the final configuration value by passing a function + # that takes a single arugment. Alternatively, you can pass an attrset + # directly. + # + # Here we demonstrate how to add `extraServices` and `extraDockerCompose`. + # For the other attributes, which have default values, + # consult `defaultConfig` in `nix/runtime.nix`. + runtimeConfig = { }; + # runtimeConfig = final: with final; { + # # You can add new services to the runtime. These should correspond to + # # Arion's `service` definition. The default is the empty attribute set + # extraServices = { + # # an image from dockerhub + # foo = { + # service = { + # image = "bar:foo"; + # command = [ + # "baz" + # "--quux" + # ]; + # }; - # # Or a Nix-based image - # foo2 = { - # service = { - # useHostStore = true; - # command = [ - # "${(nixpkgsFor system).baz}/bin/baz" - # "--quux" - # ]; - # }; - # }; - # }; - # }; - # # This corresponds to `docker-compose.raw` from Arion. You can add new - # # volumes, etc... using this - # extraDockerCompose = { volumes = { someVol = { }; }; }; + # # Or a Nix-based image + # foo2 = { + # service = { + # useHostStore = true; + # command = [ + # "${(nixpkgsFor system).baz}/bin/baz" + # "--quux" + # ]; + # }; + # }; + # }; + # }; + # # This corresponds to `docker-compose.raw` from Arion. You can add new + # # volumes, etc... using this + # extraDockerCompose = { volumes = { someVol = { }; }; }; - psProjectFor = pkgs: - pkgs.purescriptProject rec { - inherit pkgs; - projectName = "ctl-scaffold"; - packageJson = ./package.json; - packageLock = ./package-lock.json; - src = builtins.path { - path = ./.; - name = "${projectName}-src"; - # Adjust the `filter` as necessary - filter = path: ftype: !(pkgs.lib.hasSuffix ".md" path); - }; - shell = { - withRuntime = true; - packageLockOnly = true; - packages = with pkgs; [ - fd - nodePackages.eslint - nodePackages.prettier - ]; - }; + psProjectFor = pkgs: + pkgs.purescriptProject rec { + inherit pkgs; + projectName = "ctl-scaffold"; + packageJson = ./package.json; + packageLock = ./package-lock.json; + src = builtins.path { + path = ./.; + name = "${projectName}-src"; + # Adjust the `filter` as necessary + filter = path: ftype: !(pkgs.lib.hasSuffix ".md" path); + }; + shell = { + withRuntime = true; + packageLockOnly = true; + packages = with pkgs; [ + fd + nodePackages.eslint + nodePackages.prettier + ]; }; - in - { - # `buildCtlRuntime` will generate a Nix expression that, when built with - # `pkgs.arion.build`, outputs a JSON file compatible with Arion. This can - # be run directly with Arion or passed to another derivation. Or you can - # use `buildCtlRuntime` with `runArion` (from the `hercules-ci-effects`) - # library - # - # Use `nix build .#` to build. To run with Arion (i.e. in your - # shell): `arion --prebuilt-file ./result up` - packages = perSystem (system: - let - pkgs = nixpkgsFor system; - in - { - default = self.packages.${system}.ctl-scaffold-bundle-web; - ctl-scaffold-bundle-web = (psProjectFor pkgs).bundlePursProject { - main = "Scaffold.Main"; - entrypoint = "index.js"; - }; - ctl-scaffold-runtime = pkgs.buildCtlRuntime runtimeConfig; - }); + }; + in + { + # `buildCtlRuntime` will generate a Nix expression that, when built with + # `pkgs.arion.build`, outputs a JSON file compatible with Arion. This can + # be run directly with Arion or passed to another derivation. Or you can + # use `buildCtlRuntime` with `runArion` (from the `hercules-ci-effects`) + # library + # + # Use `nix build .#` to build. To run with Arion (i.e. in your + # shell): `arion --prebuilt-file ./result up` + packages = perSystem (system: + let + pkgs = nixpkgsFor system; + in + { + default = self.packages.${system}.ctl-scaffold-bundle-web; + ctl-scaffold-bundle-web = (psProjectFor pkgs).bundlePursProject { + main = "Scaffold.Main"; + entrypoint = "index.js"; + }; + ctl-scaffold-runtime = pkgs.buildCtlRuntime runtimeConfig; + }); - # `launchCtlRuntime` will generate a Nix expression from the provided - # config, build it into a JSON file, and then run it with Arion - # - # Use `nix run .#` to run the services (e.g. `nix run .#ctl-runtime`) - apps = perSystem (system: - let - pkgs = nixpkgsFor system; - in - { - default = self.apps.${system}.ctl-scaffold-runtime; - ctl-scaffold-runtime = pkgs.launchCtlRuntime runtimeConfig; - docs = (psProjectFor pkgs).launchSearchablePursDocs { }; - }); + # `launchCtlRuntime` will generate a Nix expression from the provided + # config, build it into a JSON file, and then run it with Arion + # + # Use `nix run .#` to run the services (e.g. `nix run .#ctl-runtime`) + apps = perSystem (system: + let + pkgs = nixpkgsFor system; + in + { + default = self.apps.${system}.ctl-scaffold-runtime; + ctl-scaffold-runtime = pkgs.launchCtlRuntime runtimeConfig; + docs = (psProjectFor pkgs).launchSearchablePursDocs { }; + }); - checks = perSystem (system: - let - pkgs = nixpkgsFor system; - in - { - ctl-scaffold-plutip-test = (psProjectFor pkgs).runPlutipTest { - testMain = "Test.Scaffold.Main"; - }; + checks = perSystem (system: + let + pkgs = nixpkgsFor system; + in + { + ctl-scaffold-plutip-test = (psProjectFor pkgs).runPlutipTest { + testMain = "Test.Scaffold.Main"; + }; - formatting-check = pkgs.runCommand "formatting-check" - { - nativeBuildInputs = with pkgs; [ - fd - easy-ps.purs-tidy - nixpkgs-fmt - nodePackages.prettier - ]; - } - '' - cd ${self} - purs-tidy check $(fd -epurs) - nixpkgs-fmt --check $(fd -enix --exclude='spago*') - prettier -c $(fd -ejs) - touch $out - ''; + formatting-check = pkgs.runCommand "formatting-check" + { + nativeBuildInputs = with pkgs; [ + fd + easy-ps.purs-tidy + nixpkgs-fmt + nodePackages.prettier + ]; + } + '' + cd ${self} + purs-tidy check $(fd -epurs) + nixpkgs-fmt --check $(fd -enix --exclude='spago*') + prettier -c $(fd -ejs) + touch $out + ''; - js-lint-check = pkgs.runCommand "js-lint-check" - { - nativeBuildInputs = [ pkgs.nodePackages.eslint pkgs.fd ]; - } - '' - cd ${self} - eslint $(fd -ejs) - touch $out - ''; - }); + js-lint-check = pkgs.runCommand "js-lint-check" + { + nativeBuildInputs = [ pkgs.nodePackages.eslint pkgs.fd ]; + } + '' + cd ${self} + eslint $(fd -ejs) + touch $out + ''; + }); - devShells = perSystem (system: - let - pkgs = nixpkgsFor system; - in - { - default = (psProjectFor pkgs).devShell; - }); - }; - } + devShells = perSystem (system: + let + pkgs = nixpkgsFor system; + in + { + default = (psProjectFor pkgs).devShell; + }); + }; +} From cdf3d1a41598ce216e601513dabc4efe81540cc5 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Tue, 17 Jan 2023 15:22:15 +0100 Subject: [PATCH 294/373] Move Epoch into Ctl.Internal.Types.Epoch --- src/Internal/QueryM/Ogmios.purs | 2 +- src/Internal/Service/Blockfrost.purs | 2 +- src/Internal/Types/Epoch.purs | 24 ++++++++++++++++++++++ src/Internal/Types/ProtocolParameters.purs | 22 +------------------- test/Plutus/Time.purs | 2 +- 5 files changed, 28 insertions(+), 24 deletions(-) create mode 100644 src/Internal/Types/Epoch.purs diff --git a/src/Internal/QueryM/Ogmios.purs b/src/Internal/QueryM/Ogmios.purs index 729ef263f3..55c7105fb8 100644 --- a/src/Internal/QueryM/Ogmios.purs +++ b/src/Internal/QueryM/Ogmios.purs @@ -151,13 +151,13 @@ import Ctl.Internal.Types.ByteArray , hexToByteArray ) import Ctl.Internal.Types.CborBytes (CborBytes, cborBytesToHex) +import Ctl.Internal.Types.Epoch (Epoch(Epoch)) import Ctl.Internal.Types.Natural (Natural) import Ctl.Internal.Types.Natural (fromString) as Natural import Ctl.Internal.Types.ProtocolParameters ( CoinsPerUtxoUnit(CoinsPerUtxoWord, CoinsPerUtxoByte) , CostModelV1 , CostModelV2 - , Epoch(Epoch) , ProtocolParameters(ProtocolParameters) , convertPlutusV1CostModel , convertPlutusV2CostModel diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index 228c7e714e..06c848422d 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -133,6 +133,7 @@ import Ctl.Internal.Types.BigNum as BigNum import Ctl.Internal.Types.ByteArray (ByteArray, byteArrayToHex) import Ctl.Internal.Types.CborBytes (CborBytes) import Ctl.Internal.Types.Datum (DataHash(DataHash), Datum) +import Ctl.Internal.Types.Epoch (Epoch(Epoch)) import Ctl.Internal.Types.OutputDatum ( OutputDatum(NoOutputDatum, OutputDatum, OutputDatumHash) ) @@ -140,7 +141,6 @@ import Ctl.Internal.Types.ProtocolParameters ( CoinsPerUtxoUnit(CoinsPerUtxoWord, CoinsPerUtxoByte) , CostModelV1 , CostModelV2 - , Epoch(Epoch) , ProtocolParameters(ProtocolParameters) , convertPlutusV1CostModel , convertPlutusV2CostModel diff --git a/src/Internal/Types/Epoch.purs b/src/Internal/Types/Epoch.purs new file mode 100644 index 0000000000..4b01d1a12e --- /dev/null +++ b/src/Internal/Types/Epoch.purs @@ -0,0 +1,24 @@ +module Ctl.Internal.Types.Epoch (Epoch(Epoch)) where + +import Prelude + +import Aeson (class DecodeAeson, class EncodeAeson) +import Ctl.Internal.Helpers (showWithParens) +import Data.BigInt (BigInt) +import Data.Generic.Rep (class Generic) +import Data.Newtype (class Newtype) + +-- | An epoch number or length with greater precision for Ogmios than +-- | `Cardano.Types.Epoch`. [ 0 .. 18446744073709552000 ] +newtype Epoch = Epoch BigInt + +derive instance Generic Epoch _ +derive instance Newtype Epoch _ +derive newtype instance Eq Epoch +derive newtype instance Ord Epoch +derive newtype instance DecodeAeson Epoch +derive newtype instance EncodeAeson Epoch + +instance Show Epoch where + show (Epoch e) = showWithParens "Epoch" e + diff --git a/src/Internal/Types/ProtocolParameters.purs b/src/Internal/Types/ProtocolParameters.purs index 856be9e420..4a78635594 100644 --- a/src/Internal/Types/ProtocolParameters.purs +++ b/src/Internal/Types/ProtocolParameters.purs @@ -1,6 +1,5 @@ module Ctl.Internal.Types.ProtocolParameters ( ProtocolParameters(ProtocolParameters) - , Epoch(Epoch) , CoinsPerUtxoUnit(CoinsPerUtxoByte, CoinsPerUtxoWord) , CostModelV1 , CostModelV2 @@ -10,10 +9,6 @@ module Ctl.Internal.Types.ProtocolParameters import Prelude -import Aeson - ( class DecodeAeson - , class EncodeAeson - ) import Ctl.Internal.Cardano.Types.Transaction ( Costmdls , ExUnitPrices @@ -22,11 +17,10 @@ import Ctl.Internal.Cardano.Types.Transaction ) import Ctl.Internal.Cardano.Types.Transaction as T import Ctl.Internal.Cardano.Types.Value (Coin) -import Ctl.Internal.Helpers (showWithParens) +import Ctl.Internal.Types.Epoch (Epoch) import Ctl.Internal.Types.Int as Csl import Ctl.Internal.Types.Rational (Rational) import Data.Array (reverse) -import Data.BigInt (BigInt) import Data.Generic.Rep (class Generic) import Data.List (List) import Data.List as List @@ -37,20 +31,6 @@ import Data.Tuple.Nested (type (/\)) import Data.UInt (UInt) import Heterogeneous.Folding (class HFoldl, hfoldl) --- | An epoch number or length with greater precision for Ogmios than --- | `Cardano.Types.Epoch`. [ 0 .. 18446744073709552000 ] -newtype Epoch = Epoch BigInt - -derive instance Generic Epoch _ -derive instance Newtype Epoch _ -derive newtype instance Eq Epoch -derive newtype instance Ord Epoch -derive newtype instance DecodeAeson Epoch -derive newtype instance EncodeAeson Epoch - -instance Show Epoch where - show (Epoch e) = showWithParens "Epoch" e - data CoinsPerUtxoUnit = CoinsPerUtxoByte Coin | CoinsPerUtxoWord Coin derive instance Generic CoinsPerUtxoUnit _ diff --git a/test/Plutus/Time.purs b/test/Plutus/Time.purs index 44540b6556..c28180aed2 100644 --- a/test/Plutus/Time.purs +++ b/test/Plutus/Time.purs @@ -18,6 +18,7 @@ import Ctl.Internal.QueryM.Ogmios import Ctl.Internal.Serialization.Address (Slot(Slot)) import Ctl.Internal.Test.TestPlanM (TestPlanM) import Ctl.Internal.Types.BigNum as BigNum +import Ctl.Internal.Types.Epoch (Epoch(Epoch)) import Ctl.Internal.Types.Interval ( AbsTime(AbsTime) , ModTime(ModTime) @@ -39,7 +40,6 @@ import Ctl.Internal.Types.Interval ) , ToOnChainPosixTimeRangeError(PosixTimeToSlotError', SlotToPosixTimeError') ) -import Ctl.Internal.Types.ProtocolParameters (Epoch(Epoch)) import Data.BigInt as BigInt import Data.Int as Int import Data.Maybe (Maybe(Just, Nothing)) From f062c72f1abb646147a9c7df14e6667414ecd755 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Tue, 17 Jan 2023 19:26:01 +0100 Subject: [PATCH 295/373] Apply suggestions, Update CHANGELOG.md --- CHANGELOG.md | 1 + src/Contract/Time.purs | 5 ++++- src/Internal/QueryM/Ogmios.purs | 1 - 3 files changed, 5 insertions(+), 2 deletions(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index a9263bafb4..93ef57a69d 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -51,6 +51,7 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) ### Changed - `SystemStart` now has `DateTime` (rather than `String`) as the underlying type ([#1377](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1377)) +- `EraSummaries` now does not have an `EncodeAeson` instance. Consider wrapping it in `OgmiosEraSummaries` for Aeson encoding. ([#1377](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1377)) ### Removed diff --git a/src/Contract/Time.purs b/src/Contract/Time.purs index 3dbbb775df..726fb85782 100644 --- a/src/Contract/Time.purs +++ b/src/Contract/Time.purs @@ -25,7 +25,10 @@ import Ctl.Internal.Cardano.Types.Transaction (Epoch(Epoch)) import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.Helpers (liftM) import Ctl.Internal.QueryM.Ogmios (CurrentEpoch(CurrentEpoch)) -import Ctl.Internal.QueryM.Ogmios (CurrentEpoch(CurrentEpoch)) as ExportOgmios +import Ctl.Internal.QueryM.Ogmios + ( CurrentEpoch(CurrentEpoch) + , OgmiosEraSummaries(OgmiosEraSummaries) + ) as ExportOgmios import Ctl.Internal.Serialization.Address (BlockId(BlockId), Slot(Slot)) as SerializationAddress import Ctl.Internal.Types.EraSummaries ( EpochLength(EpochLength) diff --git a/src/Internal/QueryM/Ogmios.purs b/src/Internal/QueryM/Ogmios.purs index 78e4952483..408b5ad26e 100644 --- a/src/Internal/QueryM/Ogmios.purs +++ b/src/Internal/QueryM/Ogmios.purs @@ -380,7 +380,6 @@ newtype OgmiosSystemStart = OgmiosSystemStart SystemStart derive instance Generic OgmiosSystemStart _ derive instance Newtype OgmiosSystemStart _ derive newtype instance Eq OgmiosSystemStart --- derive newtype instance EncodeAeson OgmiosSystemStart instance Show OgmiosSystemStart where show = genericShow From 3850340001ff613b6b9ebd16eff06796d15c4891 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Wed, 18 Jan 2023 12:51:59 +0000 Subject: [PATCH 296/373] Fix plutip suppressed logger --- src/Internal/Plutip/Server.purs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Internal/Plutip/Server.purs b/src/Internal/Plutip/Server.purs index 8df0b8668b..08772838cd 100644 --- a/src/Internal/Plutip/Server.purs +++ b/src/Internal/Plutip/Server.purs @@ -771,7 +771,7 @@ mkClusterContractEnv plutipCfg logger customLogger = do { ogmiosConfig: plutipCfg.ogmiosConfig , kupoConfig: plutipCfg.kupoConfig } - ledgerConstants <- getLedgerConstants plutipCfg backend + ledgerConstants <- getLedgerConstants plutipCfg { customLogger = customLogger } backend pure { backend , networkId: MainnetId From 370c313fb856600efd07bdf2da1362e93443b163 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Wed, 18 Jan 2023 17:06:24 +0400 Subject: [PATCH 297/373] Apply suggestions --- src/Contract/Test/Assert.purs | 30 +++++++++++------------------- 1 file changed, 11 insertions(+), 19 deletions(-) diff --git a/src/Contract/Test/Assert.purs b/src/Contract/Test/Assert.purs index e519a044e0..d4b6d2ae5c 100644 --- a/src/Contract/Test/Assert.purs +++ b/src/Contract/Test/Assert.purs @@ -58,7 +58,7 @@ import Contract.Transaction ) import Contract.Utxos (utxosAt) import Contract.Value (CurrencySymbol, TokenName, Value, valueOf, valueToCoin') -import Control.Monad.Error.Class (throwError) +import Control.Monad.Error.Class (liftEither, throwError) import Control.Monad.Error.Class as E import Control.Monad.Reader (ReaderT, ask, local, mapReaderT, runReaderT) import Control.Monad.Trans.Class (lift) @@ -81,7 +81,7 @@ import Ctl.Internal.Types.ByteArray (byteArrayToHex) import Data.Array (foldr) import Data.Array (fromFoldable, length, mapWithIndex, partition) as Array import Data.BigInt (BigInt) -import Data.Either (Either(Right, Left), either, hush) +import Data.Either (either, hush) import Data.Foldable (foldMap, null, sum) import Data.Lens (non, to, traversed, view, (%~), (^.), (^..)) import Data.Lens.Record (prop) @@ -93,7 +93,7 @@ import Data.String (trim) as String import Data.String.Common (joinWith) as String import Data.Tuple.Nested (type (/\), (/\)) import Effect.Class (liftEffect) -import Effect.Exception (error, throw, try) +import Effect.Exception (Error, error, throw, try) import Effect.Ref (Ref) import Effect.Ref as Ref import Type.Proxy (Proxy(Proxy)) @@ -221,7 +221,7 @@ instance Show a => Show (ExpectedActual a) where -- Different types of assertions, Assertion composition, Basic functions -------------------------------------------------------------------------------- --- | An check that can run some initialization code before the `Contract` is run +-- | A check that can run some initialization code before the `Contract` is run -- | and check the results afterwards. It is used to implement assertions that -- | require state monitoring, e.g. checking gains at address. type ContractCheck a = @@ -284,8 +284,7 @@ runChecks -> Contract a runChecks assertions contract = do ref <- liftEffect $ Ref.new Nil - eiResult <- E.try $ - flip runReaderT ref go + eiResult <- E.try $ flip runReaderT ref wrappedContract failures <- liftEffect $ Ref.read ref if null failures then either (liftEffect <<< throwError <<< error <<< reportException) @@ -293,9 +292,7 @@ runChecks assertions contract = do eiResult else do let - errorStr = case eiResult of - Left error -> reportException error - _ -> "" + errorStr = either reportException (const "") eiResult errorReport = String.trim ( errorStr <> "\n\n" <> @@ -304,21 +301,16 @@ runChecks assertions contract = do -- error trace from the exception itself will be appended here liftEffect $ throwError $ error errorReport where + reportException :: Error -> String reportException error = "\n\nAn exception has been thrown: \n\n" <> show error wrapAssertion :: ContractCheck a -> ContractAssertion a -> ContractAssertion a wrapAssertion assertion acc = do run /\ finalize <- assertion acc - E.try run >>= case _ of - Left failure -> do - finalize - throwError failure - Right success -> do - finalize - pure success + E.try run >>= \res -> finalize *> liftEither res - go :: ContractAssertion a - go = foldr wrapAssertion contract assertions + wrappedContract :: ContractAssertion a + wrappedContract = foldr wrapAssertion contract assertions tellFailure :: ContractAssertionFailure -> ContractAssertion Unit @@ -398,7 +390,7 @@ assertValueDeltaAtAddress addr check contract = do finalize = do valueAfter <- valueAtAddress' addr liftEffect (Ref.read ref) >>= case _ of - Nothing -> pure unit -- tellFailure $ CustomFailure "Contract did not run" + Nothing -> pure unit -- the result value was not produced Just res -> check res valueBefore valueAfter run = do res <- contract From ea984cb89129c0506113dc03a262cb3fb2925197 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Wed, 18 Jan 2023 22:11:26 +0400 Subject: [PATCH 298/373] Refactoring of assertion utils + tests 0. Made all Show instances lawful 1. Gains and loss assertion functions now handle the case of an exception being thrown in the Contract by accepting a Maybe 2. New tests that check textual reports character-by-character --- examples/ContractTestUtils.purs | 77 ++++++----- examples/OneShotMinting.purs | 4 +- src/Contract/Test/Assert.purs | 213 ++++++++++++++++++------------- test/Plutip.purs | 2 + test/Plutip/Contract.purs | 27 ++-- test/Plutip/Contract/Assert.purs | 195 ++++++++++++++++++++++++++++ 6 files changed, 380 insertions(+), 138 deletions(-) create mode 100644 test/Plutip/Contract/Assert.purs diff --git a/examples/ContractTestUtils.purs b/examples/ContractTestUtils.purs index 2e4961f5e0..21fec074b6 100644 --- a/examples/ContractTestUtils.purs +++ b/examples/ContractTestUtils.purs @@ -4,8 +4,9 @@ -- | address, (2) mints the specified non-Ada value (3) then sends it to the -- | owner's address with a datum attached. module Ctl.Examples.ContractTestUtils - ( ContractParams(ContractParams) - , contract + ( ContractParams + , mkContract + , mkChecks ) where import Contract.Prelude @@ -40,7 +41,6 @@ import Contract.Test.Assert , checkLossAtAddress , checkTokenGainAtAddress' , label - , runChecks ) import Contract.Transaction ( TransactionHash @@ -60,14 +60,13 @@ import Contract.TxConstraints as Constraints import Contract.Utxos (utxosAt) import Contract.Value (CurrencySymbol, TokenName, Value) import Contract.Value (lovelaceValueOf, singleton) as Value -import Control.Monad.Trans.Class (lift) import Ctl.Examples.Helpers (mustPayToPubKeyStakeAddress) as Helpers import Data.Array (head) import Data.BigInt (BigInt) import Data.BigInt as BigInt import Data.Lens (view) -newtype ContractParams = ContractParams +type ContractParams = { receiverPkh :: PaymentPubKeyHash , receiverSkh :: Maybe StakePubKeyHash , adaToSend :: BigInt @@ -77,8 +76,6 @@ newtype ContractParams = ContractParams , txMetadata :: Cip25Metadata } -derive instance Newtype ContractParams _ - type ContractResult = { txHash :: TransactionHash , txFinalFee :: BigInt @@ -88,18 +85,20 @@ type ContractResult = mkChecks :: ContractParams -> Contract (Array (ContractCheck ContractResult)) -mkChecks params@(ContractParams p) = do +mkChecks p = do senderAddress <- liftedM "Failed to get sender address" $ head <$> getWalletAddresses receiverAddress <- - liftedM "Failed to get receiver address" (getReceiverAddress params) + liftedM "Failed to get receiver address" (getReceiverAddress p) let dhash = datumHash p.datumToAttach pure [ checkGainAtAddress' (label receiverAddress "Receiver") p.adaToSend , checkLossAtAddress (label senderAddress "Sender") - \{ txFinalFee } -> pure (p.adaToSend + txFinalFee) + case _ of + Just { txFinalFee } -> pure (p.adaToSend + txFinalFee) + Nothing -> pure zero , checkTokenGainAtAddress' (label senderAddress "Sender") ( uncurry3 (\cs tn amount -> cs /\ tn /\ amount) @@ -124,8 +123,8 @@ mkChecks params@(ContractParams p) = do assertTxHasMetadata "CIP25 Metadata" txHash p.txMetadata ] -contract :: ContractParams -> Contract Unit -contract params@(ContractParams p) = do +mkContract :: ContractParams -> Contract ContractResult +mkContract p = do logInfo' "Running Examples.ContractTestUtils" ownPkh <- liftedM "Failed to get own PKH" $ head <$> ownPaymentPubKeysHashes ownSkh <- join <<< head <$> ownStakePubKeysHashes @@ -156,33 +155,31 @@ contract params@(ContractParams p) = do lookups :: Lookups.ScriptLookups Void lookups = Lookups.mintingPolicy p.mintingPolicy - checks <- mkChecks params - void $ runChecks checks $ lift do - unbalancedTx <- liftedE $ Lookups.mkUnbalancedTx lookups constraints - unbalancedTxWithMetadata <- setTxMetadata unbalancedTx p.txMetadata - balancedTx <- liftedE $ balanceTx unbalancedTxWithMetadata - balancedSignedTx <- signTransaction balancedTx - - txId <- submit balancedSignedTx - logInfo' $ "Tx ID: " <> show txId - - awaitTxConfirmed txId - logInfo' "Tx submitted successfully!" - - senderAddress <- liftedM "Failed to get sender address" $ head <$> - getWalletAddresses - utxos <- utxosAt senderAddress - - txOutputUnderTest <- - view _output <$> - liftContractM "Could not find required unspent output with datum hash" - (find hasDatumHash $ lookupTxHash txId utxos) - - pure - { txHash: txId - , txFinalFee: getTxFinalFee balancedSignedTx - , txOutputUnderTest - } + unbalancedTx <- liftedE $ Lookups.mkUnbalancedTx lookups constraints + unbalancedTxWithMetadata <- setTxMetadata unbalancedTx p.txMetadata + balancedTx <- liftedE $ balanceTx unbalancedTxWithMetadata + balancedSignedTx <- signTransaction balancedTx + + txId <- submit balancedSignedTx + logInfo' $ "Tx ID: " <> show txId + + awaitTxConfirmed txId + logInfo' "Tx submitted successfully!" + + senderAddress <- liftedM "Failed to get sender address" $ head <$> + getWalletAddresses + utxos <- utxosAt senderAddress + + txOutputUnderTest <- + view _output <$> + liftContractM "Could not find required unspent output with datum hash" + (find hasDatumHash $ lookupTxHash txId utxos) + + pure + { txHash: txId + , txFinalFee: getTxFinalFee balancedSignedTx + , txOutputUnderTest + } where hasDatumHash :: TransactionUnspentOutput -> Boolean hasDatumHash = view _output >>> unwrap >>> _.output >>> unwrap >>> _.datum >>> @@ -191,7 +188,7 @@ contract params@(ContractParams p) = do _ -> false getReceiverAddress :: ContractParams -> Contract (Maybe Address) -getReceiverAddress (ContractParams { receiverPkh, receiverSkh }) = +getReceiverAddress { receiverPkh, receiverSkh } = getNetworkId <#> \networkId -> case receiverSkh of Just skh -> diff --git a/examples/OneShotMinting.purs b/examples/OneShotMinting.purs index 0347adefb8..f9914f1589 100644 --- a/examples/OneShotMinting.purs +++ b/examples/OneShotMinting.purs @@ -78,7 +78,9 @@ mkChecks ownAddress nft = [ checkTokenGainAtAddress' labeledOwnAddress nft , checkLossAtAddress labeledOwnAddress - \{ txFinalFee } -> pure txFinalFee + case _ of + Nothing -> pure zero + Just { txFinalFee } -> pure txFinalFee ] contract :: Contract Unit diff --git a/src/Contract/Test/Assert.purs b/src/Contract/Test/Assert.purs index d4b6d2ae5c..8f46700a16 100644 --- a/src/Contract/Test/Assert.purs +++ b/src/Contract/Test/Assert.purs @@ -37,11 +37,16 @@ module Contract.Test.Assert , checkTokenGainAtAddress' , checkTokenLossAtAddress , checkTokenLossAtAddress' + , collectAssertionFailures , label , noLabel , runChecks , tellFailure , unlabel + , printLabeled + , printExpectedActual + , printContractAssertionFailure + , printContractAssertionFailures ) where import Prelude @@ -81,14 +86,16 @@ import Ctl.Internal.Types.ByteArray (byteArrayToHex) import Data.Array (foldr) import Data.Array (fromFoldable, length, mapWithIndex, partition) as Array import Data.BigInt (BigInt) -import Data.Either (either, hush) +import Data.Either (Either, either, hush) import Data.Foldable (foldMap, null, sum) +import Data.Generic.Rep (class Generic) import Data.Lens (non, to, traversed, view, (%~), (^.), (^..)) import Data.Lens.Record (prop) import Data.List (List(Cons, Nil)) import Data.Map (filterKeys, lookup, values) as Map import Data.Maybe (Maybe(Just, Nothing), maybe) -import Data.Newtype (class Newtype, unwrap) +import Data.Newtype (unwrap) +import Data.Show.Generic (genericShow) import Data.String (trim) as String import Data.String.Common (joinWith) as String import Data.Tuple.Nested (type (/\), (/\)) @@ -117,77 +124,85 @@ data ContractAssertionFailure | UnexpectedRefScriptInOutput (Labeled TransactionOutputWithRefScript) (ExpectedActual (Maybe ScriptRef)) | UnexpectedTokenDelta (Labeled Address) TokenName (ExpectedActual BigInt) - | MaxExUnitsExceeded ExUnits ExUnits + | MaxExUnitsExceeded (ExpectedActual ExUnits) | CustomFailure String | SkippedTest String -newtype ContractAssertionFailures = - ContractAssertionFailures (Array ContractAssertionFailure) - -derive instance Newtype (ContractAssertionFailures) _ - -instance Show ContractAssertionFailures where - show (ContractAssertionFailures failures) = - String.trim $ errorText <> warningText - where - isWarning :: ContractAssertionFailure -> Boolean - isWarning = case _ of - SkippedTest _ -> true - _ -> false - - { yes: warnings, no: errors } = Array.partition isWarning failures - - listFailures = String.joinWith "\n\n " - <<< Array.mapWithIndex (\ix elem -> show (ix + one) <> ". " <> show elem) - errorText = - if Array.length errors > 0 then - "The following `Contract` assertions have failed: \n " - <> listFailures errors - <> "\n\n" - else "" - warningText = - if Array.length warnings > 0 then - "The following `Contract` checks have been skipped due to an exception: \n\n " - <> - listFailures warnings - else "" +derive instance Eq ContractAssertionFailure +derive instance Generic ContractAssertionFailure _ instance Show ContractAssertionFailure where - show (CouldNotGetTxByHash txHash) = + show = genericShow + +-- | A pretty-printing function that produces a human-readable report on failures. +printContractAssertionFailures :: Array ContractAssertionFailure -> String +printContractAssertionFailures failures = + String.trim $ errorText <> warningText + where + isWarning :: ContractAssertionFailure -> Boolean + isWarning = case _ of + SkippedTest _ -> true + _ -> false + + { yes: warnings, no: errors } = Array.partition isWarning failures + + listFailures = String.joinWith "\n\n " + <<< Array.mapWithIndex + ( \ix elem -> show (ix + one) <> ". " <> printContractAssertionFailure + elem + ) + errorText = + if Array.length errors > 0 then + "The following `Contract` assertions have failed: \n " + <> listFailures errors + <> "\n\n" + else "" + warningText = + if Array.length warnings > 0 then + "The following `Contract` checks have been skipped due to an exception: \n\n " + <> + listFailures warnings + else "" + +-- | Pretty printing function that produces a human readable report for a +-- | single `ContractAssertionFailure` +printContractAssertionFailure :: ContractAssertionFailure -> String +printContractAssertionFailure = case _ of + CouldNotGetTxByHash txHash -> "Could not get tx by hash " <> showTxHash txHash - show (CouldNotParseMetadata mdLabel) = - "Could not parse " <> show mdLabel <> " metadata" + CouldNotParseMetadata mdLabel -> + "Could not parse " <> mdLabel <> " metadata" - show (TransactionHasNoMetadata txHash mdLabel) = + TransactionHasNoMetadata txHash mdLabel -> "Tx with id " <> showTxHash txHash <> " does not hold " - <> (maybe mempty (flip append " ") (show <$> mdLabel) <> "metadata") + <> (maybe mempty (flip append " ") mdLabel <> "metadata") - show (UnexpectedDatumInOutput txOutput expectedActual) = - "Unexpected datum in output " <> show txOutput <> show expectedActual + UnexpectedDatumInOutput txOutput expectedActual -> + "Unexpected datum in output " <> printLabeled txOutput <> " " <> + printExpectedActual expectedActual - show (UnexpectedLovelaceDelta addr expectedActual) = + UnexpectedLovelaceDelta addr expectedActual -> "Unexpected lovelace delta at address " - <> (show addr <> show expectedActual) + <> (printLabeled addr <> printExpectedActual expectedActual) - show (UnexpectedMetadataValue mdLabel expectedActual) = - "Unexpected " <> show mdLabel <> " metadata value" <> show expectedActual + UnexpectedMetadataValue mdLabel expectedActual -> + "Unexpected " <> mdLabel <> " metadata value" <> printExpectedActual + expectedActual - show (UnexpectedRefScriptInOutput txOutput expectedActual) = + UnexpectedRefScriptInOutput txOutput expectedActual -> "Unexpected reference script in output " - <> (show txOutput <> show expectedActual) + <> (printLabeled txOutput <> printExpectedActual expectedActual) - show (UnexpectedTokenDelta addr tn expectedActual) = + UnexpectedTokenDelta addr tn expectedActual -> "Unexpected token delta " <> show tn <> " at address " - <> (show addr <> show expectedActual) + <> (printLabeled addr <> printExpectedActual expectedActual) - show (MaxExUnitsExceeded maxExUnits exUnits) = - "ExUnits limit exceeded: spent " <> show exUnits - <> ", but the limit is " - <> show maxExUnits + MaxExUnitsExceeded expectedActual -> + "ExUnits limit exceeded: " <> printExpectedActual expectedActual - show (CustomFailure msg) = msg - show (SkippedTest msg) = msg + CustomFailure msg -> msg + SkippedTest msg -> msg showTxHash :: TransactionHash -> String showTxHash = byteArrayToHex <<< unwrap @@ -196,6 +211,13 @@ type Label = String data Labeled (a :: Type) = Labeled a (Maybe Label) +derive instance Eq a => Eq (Labeled a) +derive instance Ord a => Ord (Labeled a) +derive instance Generic (Labeled a) _ + +instance Show a => Show (Labeled a) where + show = genericShow + label :: forall (a :: Type). a -> Label -> Labeled a label x l = Labeled x (Just l) @@ -205,17 +227,24 @@ unlabel (Labeled x _) = x noLabel :: forall (a :: Type). a -> Labeled a noLabel = flip Labeled Nothing -instance Show a => Show (Labeled a) where - show (Labeled _ (Just l)) = l - show (Labeled x Nothing) = show x +printLabeled :: forall (a :: Type). Show a => Labeled a -> String +printLabeled (Labeled _ (Just l)) = l +printLabeled (Labeled x Nothing) = show x data ExpectedActual (a :: Type) = ExpectedActual a a -derive instance Functor ExpectedActual +derive instance Eq a => Eq (ExpectedActual a) +derive instance Ord a => Ord (ExpectedActual a) +derive instance Generic (ExpectedActual a) _ instance Show a => Show (ExpectedActual a) where - show (ExpectedActual expected actual) = - " (Expected: " <> show expected <> ", Actual: " <> show actual <> ")" + show = genericShow + +derive instance Functor ExpectedActual + +printExpectedActual :: forall (a :: Type). Show a => ExpectedActual a -> String +printExpectedActual (ExpectedActual expected actual) = + " (Expected: " <> show expected <> ", Actual: " <> show actual <> ")" -------------------------------------------------------------------------------- -- Different types of assertions, Assertion composition, Basic functions @@ -263,7 +292,7 @@ assertContractMaybe -> Maybe a -> ContractAssertion a assertContractMaybe msg = - maybe (liftEffect $ throw $ show msg) pure + maybe (liftEffect $ throw $ printContractAssertionFailure msg) pure assertContractExpectedActual :: forall (a :: Type) @@ -276,6 +305,27 @@ assertContractExpectedActual mkAssertionFailure expected actual = assertContract (mkAssertionFailure $ ExpectedActual expected actual) (expected == actual) +-- | Like `runChecks`, but does not throw a user-readable report, collecting +-- | the exceptions instead. +collectAssertionFailures + :: forall (a :: Type) + . Array (ContractCheck a) + -> ContractAssertion a + -> Contract (Either Error a /\ Array ContractAssertionFailure) +collectAssertionFailures assertions contract = do + ref <- liftEffect $ Ref.new Nil + eiResult <- E.try $ flip runReaderT ref wrappedContract + failures <- liftEffect $ Ref.read ref + pure (eiResult /\ Array.fromFoldable failures) + where + wrapAssertion :: ContractCheck a -> ContractAssertion a -> ContractAssertion a + wrapAssertion assertion acc = do + run /\ finalize <- assertion acc + E.try run >>= \res -> finalize *> liftEither res + + wrappedContract :: ContractAssertion a + wrappedContract = foldr wrapAssertion contract assertions + -- | Accepts an array of checks and interprets them into a `Contract`. runChecks :: forall (a :: Type) @@ -283,9 +333,7 @@ runChecks -> ContractAssertion a -> Contract a runChecks assertions contract = do - ref <- liftEffect $ Ref.new Nil - eiResult <- E.try $ flip runReaderT ref wrappedContract - failures <- liftEffect $ Ref.read ref + eiResult /\ failures <- collectAssertionFailures assertions contract if null failures then either (liftEffect <<< throwError <<< error <<< reportException) pure @@ -296,7 +344,7 @@ runChecks assertions contract = do errorReport = String.trim ( errorStr <> "\n\n" <> - show (ContractAssertionFailures $ Array.fromFoldable failures) + printContractAssertionFailures (Array.fromFoldable failures) ) <> "\n" -- error trace from the exception itself will be appended here liftEffect $ throwError $ error errorReport @@ -304,14 +352,6 @@ runChecks assertions contract = do reportException :: Error -> String reportException error = "\n\nAn exception has been thrown: \n\n" <> show error - wrapAssertion :: ContractCheck a -> ContractAssertion a -> ContractAssertion a - wrapAssertion assertion acc = do - run /\ finalize <- assertion acc - E.try run >>= \res -> finalize *> liftEither res - - wrappedContract :: ContractAssertion a - wrappedContract = foldr wrapAssertion contract assertions - tellFailure :: ContractAssertionFailure -> ContractAssertion Unit tellFailure failure = do @@ -361,7 +401,7 @@ checkExUnitsNotExceed maxExUnits contract = do finalize :: ContractAssertion Unit finalize = do exUnits <- liftEffect $ Ref.read ref - assertContract (MaxExUnitsExceeded maxExUnits exUnits) + assertContract (MaxExUnitsExceeded (ExpectedActual maxExUnits exUnits)) (maxExUnits >= exUnits) pure (mapReaderT (local setSubmitHook) contract /\ finalize) @@ -377,11 +417,12 @@ valueAtAddress' = map (foldMap (view (_output <<< _amount))) <<< lift -- | -- | - a labeled address -- | - a callback that implements the assertion, accepting `Contract` execution --- | result, and values (before and after) +-- | result, and values (before and after). The value may not be computed due +-- | to an exception, hence it's wrapped in `Maybe`. assertValueDeltaAtAddress :: forall (a :: Type) . Labeled Address - -> (a -> Value -> Value -> ContractAssertion Unit) + -> (Maybe a -> Value -> Value -> ContractAssertion Unit) -> ContractCheck a assertValueDeltaAtAddress addr check contract = do valueBefore <- valueAtAddress' addr @@ -389,9 +430,7 @@ assertValueDeltaAtAddress addr check contract = do let finalize = do valueAfter <- valueAtAddress' addr - liftEffect (Ref.read ref) >>= case _ of - Nothing -> pure unit -- the result value was not produced - Just res -> check res valueBefore valueAfter + liftEffect (Ref.read ref) >>= \res -> check res valueBefore valueAfter run = do res <- contract liftEffect $ Ref.write (Just res) ref @@ -401,13 +440,13 @@ assertValueDeltaAtAddress addr check contract = do assertLovelaceDeltaAtAddress :: forall (a :: Type) . Labeled Address - -> (a -> Contract BigInt) + -> (Maybe a -> Contract BigInt) -> (BigInt -> BigInt -> Boolean) -> ContractCheck a assertLovelaceDeltaAtAddress addr getExpected comp contract = do assertValueDeltaAtAddress addr check contract where - check :: a -> Value -> Value -> ContractAssertion Unit + check :: Maybe a -> Value -> Value -> ContractAssertion Unit check result valueBefore valueAfter = do expected <- lift $ getExpected result let @@ -426,7 +465,7 @@ assertLovelaceDeltaAtAddress addr getExpected comp contract = do checkGainAtAddress :: forall (a :: Type) . Labeled Address - -> (a -> Contract BigInt) + -> (Maybe a -> Contract BigInt) -> ContractCheck a checkGainAtAddress addr getMinGain = assertLovelaceDeltaAtAddress addr getMinGain eq @@ -446,7 +485,7 @@ checkGainAtAddress' addr minGain = checkLossAtAddress :: forall (a :: Type) . Labeled Address - -> (a -> Contract BigInt) + -> (Maybe a -> Contract BigInt) -> ContractCheck a checkLossAtAddress addr getMinLoss = assertLovelaceDeltaAtAddress addr (map negate <<< getMinLoss) eq @@ -465,13 +504,13 @@ checkTokenDeltaAtAddress :: forall (a :: Type) . Labeled Address -> (CurrencySymbol /\ TokenName) - -> (a -> Contract BigInt) + -> (Maybe a -> Contract BigInt) -> (BigInt -> BigInt -> Boolean) -> ContractCheck a checkTokenDeltaAtAddress addr (cs /\ tn) getExpected comp contract = assertValueDeltaAtAddress addr check contract where - check :: a -> Value -> Value -> ContractAssertion Unit + check :: Maybe a -> Value -> Value -> ContractAssertion Unit check result valueBefore valueAfter = do expected <- lift $ getExpected result let @@ -490,7 +529,7 @@ checkTokenGainAtAddress :: forall (a :: Type) . Labeled Address -> (CurrencySymbol /\ TokenName) - -> (a -> Contract BigInt) + -> (Maybe a -> Contract BigInt) -> ContractCheck a checkTokenGainAtAddress addr token getMinGain = checkTokenDeltaAtAddress addr token getMinGain eq @@ -511,7 +550,7 @@ checkTokenLossAtAddress :: forall (a :: Type) . Labeled Address -> (CurrencySymbol /\ TokenName) - -> (a -> Contract BigInt) + -> (Maybe a -> Contract BigInt) -> ContractCheck a checkTokenLossAtAddress addr token getMinLoss = checkTokenDeltaAtAddress addr token (map negate <<< getMinLoss) eq diff --git a/test/Plutip.purs b/test/Plutip.purs index 34e942dea5..0fa163606d 100644 --- a/test/Plutip.purs +++ b/test/Plutip.purs @@ -32,6 +32,7 @@ import Mote (group, test) import Mote.Monad (mapTest) import Test.Ctl.Plutip.Common (config) import Test.Ctl.Plutip.Contract as Contract +import Test.Ctl.Plutip.Contract.Assert as Assert import Test.Ctl.Plutip.Contract.NetworkId as NetworkId import Test.Ctl.Plutip.Logging as Logging import Test.Ctl.Plutip.UtxoDistribution as UtxoDistribution @@ -46,6 +47,7 @@ main = interruptOnSignal SIGINT =<< launchAff do Utils.interpretWithConfig defaultConfig { timeout = Just $ Milliseconds 70_000.0, exit = true } $ group "Plutip" do + testPlutipContracts config Assert.suite Logging.suite testStartPlutipCluster testPlutipContracts config $ do diff --git a/test/Plutip/Contract.purs b/test/Plutip/Contract.purs index df2d523eb0..6da5482bfa 100644 --- a/test/Plutip/Contract.purs +++ b/test/Plutip/Contract.purs @@ -47,6 +47,7 @@ import Contract.Scripts , mintingPolicyHash , validatorHash ) +import Contract.Test.Assert (runChecks) import Contract.Test.Plutip ( InitialUTxOs , InitialUTxOsWithStakeKey @@ -78,6 +79,7 @@ import Contract.Value (Coin(Coin), coinToValue) import Contract.Value as Value import Contract.Wallet (getWalletUtxos, isWalletAvailable, withKeyWallet) import Control.Monad.Error.Class (try) +import Control.Monad.Trans.Class (lift) import Control.Parallel (parallel, sequential) import Ctl.Examples.AlwaysMints (alwaysMintsPolicy) import Ctl.Examples.AlwaysSucceeds as AlwaysSucceeds @@ -1249,16 +1251,21 @@ suite = do tn <- mkTokenName "TheToken" - withKeyWallet alice $ ContractTestUtils.contract $ - ContractTestUtils.ContractParams - { receiverPkh - , receiverSkh - , adaToSend: BigInt.fromInt 5_000_000 - , mintingPolicy - , tokensToMint: cs /\ tn /\ one /\ unit - , datumToAttach: wrap $ Integer $ BigInt.fromInt 42 - , txMetadata: cip25MetadataFixture1 - } + withKeyWallet alice do + let + params = + { receiverPkh + , receiverSkh + , adaToSend: BigInt.fromInt 5_000_000 + , mintingPolicy + , tokensToMint: cs /\ tn /\ one /\ unit + , datumToAttach: wrap $ Integer $ BigInt.fromInt 42 + , txMetadata: cip25MetadataFixture1 + } + + checks <- ContractTestUtils.mkChecks params + void $ runChecks checks $ lift do + ContractTestUtils.mkContract params test "Examples.BalanceTxConstraints" do let diff --git a/test/Plutip/Contract/Assert.purs b/test/Plutip/Contract/Assert.purs new file mode 100644 index 0000000000..cafbfa53ec --- /dev/null +++ b/test/Plutip/Contract/Assert.purs @@ -0,0 +1,195 @@ +-- | Testing assertions interface provided by `Contract.Test.Assert` +module Test.Ctl.Plutip.Contract.Assert (suite) where + +import Prelude + +import Contract.Address (ownPaymentPubKeysHashes, ownStakePubKeysHashes) +import Contract.Monad (liftedM) +import Contract.PlutusData (PlutusData(Integer)) +import Contract.Test.Assert + ( checkExUnitsNotExceed + , collectAssertionFailures + , printContractAssertionFailures + ) +import Contract.Test.Plutip (InitialUTxOs, PlutipTest, withWallets) +import Contract.Wallet (withKeyWallet) +import Control.Monad.Trans.Class (lift) +import Ctl.Examples.ContractTestUtils as ContractTestUtils +import Ctl.Examples.Helpers (mkCurrencySymbol, mkTokenName) +import Ctl.Examples.PlutusV2.Scripts.AlwaysMints (alwaysMintsPolicyV2) +import Ctl.Internal.Test.TestPlanM (TestPlanM) +import Data.Array (head) +import Data.BigInt as BigInt +import Data.Either (isLeft, isRight) +import Data.Newtype (wrap) +import Data.Tuple.Nested (type (/\), (/\)) +import Effect.Class (liftEffect) +import Effect.Exception (throw) +import Mote (group, test) +import Test.Ctl.Fixtures (cip25MetadataFixture1) +import Test.Spec.Assertions (shouldEqual, shouldSatisfy) + +suite :: TestPlanM PlutipTest Unit +suite = do + group "Assertions interface" do + let + initialUtxos :: InitialUTxOs + initialUtxos = + [ BigInt.fromInt 2_000_000_000, BigInt.fromInt 2_000_000_000 ] + + distribution :: InitialUTxOs /\ InitialUTxOs + distribution = initialUtxos /\ initialUtxos + + test "Successful run" do + + withWallets distribution \(alice /\ bob) -> do + receiverPkh <- liftedM "Unable to get Bob's PKH" $ + head <$> withKeyWallet bob ownPaymentPubKeysHashes + receiverSkh <- join <<< head <$> withKeyWallet bob ownStakePubKeysHashes + + mintingPolicy /\ cs <- mkCurrencySymbol alwaysMintsPolicyV2 + + tn <- mkTokenName "TheToken" + + withKeyWallet alice do + let + params = + { receiverPkh + , receiverSkh + , adaToSend: BigInt.fromInt 5_000_000 + , mintingPolicy + , tokensToMint: cs /\ tn /\ one /\ unit + , datumToAttach: wrap $ Integer $ BigInt.fromInt 42 + , txMetadata: cip25MetadataFixture1 + } + + checks <- ContractTestUtils.mkChecks params + eiResult /\ failures <- collectAssertionFailures checks $ lift do + ContractTestUtils.mkContract params + eiResult `shouldSatisfy` isRight + failures `shouldEqual` [] + + test "Incorrect token value" do + + withWallets distribution \(alice /\ bob) -> do + receiverPkh <- liftedM "Unable to get Bob's PKH" $ + head <$> withKeyWallet bob ownPaymentPubKeysHashes + receiverSkh <- join <<< head <$> withKeyWallet bob ownStakePubKeysHashes + + mintingPolicy /\ cs <- mkCurrencySymbol alwaysMintsPolicyV2 + + tn <- mkTokenName "TheToken" + + withKeyWallet alice do + let + params = + { receiverPkh + , receiverSkh + , adaToSend: BigInt.fromInt 5_000_000 + , mintingPolicy + , tokensToMint: cs /\ tn /\ one /\ unit + , datumToAttach: wrap $ Integer $ BigInt.fromInt 42 + , txMetadata: cip25MetadataFixture1 + } + + checks <- ContractTestUtils.mkChecks params + { tokensToMint = cs /\ tn /\ (one + one) /\ unit } + eiResult /\ failures <- collectAssertionFailures checks $ lift do + ContractTestUtils.mkContract params + eiResult `shouldSatisfy` isRight + printContractAssertionFailures failures `shouldEqual` + "The following `Contract` assertions have failed: \n 1.\ + \ Unexpected token delta (TokenName (hexToRawBytesUnsafe\ + \ \"546865546f6b656e\")) at address Sender (Expected: fromString\ + \ \"2\", Actual: fromString \"1\")" + + test "ExUnits limit reached" do + + withWallets distribution \(alice /\ bob) -> do + receiverPkh <- liftedM "Unable to get Bob's PKH" $ + head <$> withKeyWallet bob ownPaymentPubKeysHashes + receiverSkh <- join <<< head <$> withKeyWallet bob ownStakePubKeysHashes + + mintingPolicy /\ cs <- mkCurrencySymbol alwaysMintsPolicyV2 + + tn <- mkTokenName "TheToken" + + withKeyWallet alice do + let + params = + { receiverPkh + , receiverSkh + , adaToSend: BigInt.fromInt 5_000_000 + , mintingPolicy + , tokensToMint: cs /\ tn /\ one /\ unit + , datumToAttach: wrap $ Integer $ BigInt.fromInt 42 + , txMetadata: cip25MetadataFixture1 + } + + checks <- ContractTestUtils.mkChecks params <#> + ( _ <> + [ checkExUnitsNotExceed + { mem: BigInt.fromInt 800, steps: BigInt.fromInt 16110 } + ] + ) + eiResult /\ failures <- collectAssertionFailures checks $ lift do + ContractTestUtils.mkContract params + eiResult `shouldSatisfy` isRight + printContractAssertionFailures failures `shouldEqual` + "The following `Contract` assertions have failed: \n \ + \1. ExUnits limit exceeded: (Expected: { mem: fromString \"800\",\ + \ steps: fromString \"16110\" }, Actual: { mem: fromString \"800\",\ + \ steps: fromString \"161100\" })" + + test "An exception is thrown - everything is reported" do + + withWallets distribution \(alice /\ bob) -> do + receiverPkh <- liftedM "Unable to get Bob's PKH" $ + head <$> withKeyWallet bob ownPaymentPubKeysHashes + receiverSkh <- join <<< head <$> withKeyWallet bob ownStakePubKeysHashes + + mintingPolicy /\ cs <- mkCurrencySymbol alwaysMintsPolicyV2 + + tn <- mkTokenName "TheToken" + + withKeyWallet alice do + let + params = + { receiverPkh + , receiverSkh + , adaToSend: BigInt.fromInt 5_000_000 + , mintingPolicy + , tokensToMint: cs /\ tn /\ one /\ unit + , datumToAttach: wrap $ Integer $ BigInt.fromInt 42 + , txMetadata: cip25MetadataFixture1 + } + + checks <- + ContractTestUtils.mkChecks params + { tokensToMint = cs /\ tn /\ (one + one) /\ unit } <#> + ( _ <> + [ checkExUnitsNotExceed + { mem: BigInt.fromInt 800, steps: BigInt.fromInt 16110 } + ] + ) + + eiResult /\ failures <- collectAssertionFailures checks $ lift do + ContractTestUtils.mkContract params <* liftEffect (throw ":(") + + eiResult `shouldSatisfy` isLeft + printContractAssertionFailures failures `shouldEqual` + "The following `Contract` assertions have failed: \n\ + \ 1. Unexpected lovelace delta at address Sender (Expected: \ + \fromString \"0\", Actual: fromString \"-5192058\")\n\n\ + \ 2. Unexpected token delta (TokenName (hexToRawBytesUnsafe\ + \ \"546865546f6b656e\")) at address Sender (Expected: \ + \fromString \"2\", Actual: fromString \"1\")\n\n\ + \ 3. ExUnits limit exceeded: (Expected: { mem: fromString\ + \ \"800\", steps: fromString \"16110\" }, Actual: { \ + \mem: fromString \"800\", steps: fromString \"161100\" \ + \})\n\n\ + \The following `Contract` checks have been skipped due to an \ + \exception: \n\n\ + \ 1. Sender's output has a datum\n\n\ + \ 2. Output has a reference script\n\n\ + \ 3. Contains CIP-25 metadata" From 7cd1356ab8ac8bda565f15352c5b5912c9d817b5 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Thu, 19 Jan 2023 20:55:04 +0400 Subject: [PATCH 299/373] Apply suggestions --- doc/test-utils.md | 2 +- src/Contract/Test/Assert.purs | 9 +++------ 2 files changed, 4 insertions(+), 7 deletions(-) diff --git a/doc/test-utils.md b/doc/test-utils.md index 75da2010ea..397afb12a1 100644 --- a/doc/test-utils.md +++ b/doc/test-utils.md @@ -40,7 +40,7 @@ assertionToCheck -> ContractCheck a ``` -The first argument is a descriptive message that will be printed in case there is an exception thrown inside the `Contract` that is being tested. This is done because in case of an exception there's no way to get the result value of type `a`. For better developer experience all the tests skipped due to the exception will still be mentioned in the report, e.g. [for this example](../examples/ContractTestUtils.purs): +The first argument is a descriptive message that will be printed in case there is an exception thrown inside the `Contract` that is being tested. This is done because in case of an exception there's no way to get the result value of type `a`. For better developer experience, all the tests skipped due to the exception will still be mentioned in the report, e.g. [for this example](../examples/ContractTestUtils.purs): ``` ✗ Examples.ContractTestUtils: diff --git a/src/Contract/Test/Assert.purs b/src/Contract/Test/Assert.purs index 8f46700a16..6715872dcf 100644 --- a/src/Contract/Test/Assert.purs +++ b/src/Contract/Test/Assert.purs @@ -176,7 +176,7 @@ printContractAssertionFailure = case _ of TransactionHasNoMetadata txHash mdLabel -> "Tx with id " <> showTxHash txHash <> " does not hold " - <> (maybe mempty (flip append " ") mdLabel <> "metadata") + <> (maybe "" (_ <> " ") mdLabel <> "metadata") UnexpectedDatumInOutput txOutput expectedActual -> "Unexpected datum in output " <> printLabeled txOutput <> " " <> @@ -282,9 +282,7 @@ assertContract :: ContractAssertionFailure -> Boolean -> ContractAssertion Unit -assertContract failure cond - | cond = pure unit - | otherwise = tellFailure failure +assertContract failure cond = unless cond $ tellFailure failure assertContractMaybe :: forall (a :: Type) @@ -402,7 +400,7 @@ checkExUnitsNotExceed maxExUnits contract = do finalize = do exUnits <- liftEffect $ Ref.read ref assertContract (MaxExUnitsExceeded (ExpectedActual maxExUnits exUnits)) - (maxExUnits >= exUnits) + (maxExUnits.mem >= exUnits.mem && maxExUnits.steps >= exUnits.steps) pure (mapReaderT (local setSubmitHook) contract /\ finalize) @@ -458,7 +456,6 @@ assertLovelaceDeltaAtAddress addr getExpected comp contract = do UnexpectedLovelaceDelta addr (ExpectedActual expected actual) assertContract unexpectedLovelaceDelta (comp actual expected) - pure unit -- | Requires that the computed amount of lovelace was gained at the address -- | by calling the contract. From a34c00877ee387505cf9585adbcf199a3775a7b8 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Thu, 19 Jan 2023 21:03:50 +0400 Subject: [PATCH 300/373] Attempt to fix bundling issues due to the use of infix tuple type constructor --- src/Internal/Plutip/UtxoDistribution.purs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Internal/Plutip/UtxoDistribution.purs b/src/Internal/Plutip/UtxoDistribution.purs index e8fe0215f7..3b6b1f130d 100644 --- a/src/Internal/Plutip/UtxoDistribution.purs +++ b/src/Internal/Plutip/UtxoDistribution.purs @@ -56,6 +56,7 @@ import Data.Map as Map import Data.Maybe (Maybe(Nothing, Just)) import Data.Newtype (unwrap) import Data.Traversable (traverse) +import Data.Tuple (Tuple) import Data.Tuple.Nested (type (/\), (/\)) import Effect.Class (liftEffect) import Effect.Ref as Ref @@ -135,7 +136,8 @@ instance ( UtxoDistribution headSpec headWallets , UtxoDistribution restSpec restWallets ) => - UtxoDistribution (headSpec /\ restSpec) (headWallets /\ restWallets) where + UtxoDistribution (Tuple headSpec restSpec) + (Tuple headWallets restWallets) where encodeDistribution (distr /\ rest) = encodeDistribution distr <> encodeDistribution rest decodeWallets d p = decodeWalletsDefault d p From ac0fe4ba1d9361d9735451ffd39c2694a33e4438 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Fri, 20 Jan 2023 11:09:03 +0000 Subject: [PATCH 301/373] Fixed 404 on utxosAt, investigating failing tests --- src/Internal/Plutip/Server.purs | 80 +++++++++++++++++++++++--- src/Internal/Service/Blockfrost.purs | 85 +++++++++++++++++++--------- test/Blockfrost/Contract.purs | 2 + test/Plutip/Contract.purs | 2 +- test/Utils/DrainWallets.purs | 2 +- 5 files changed, 134 insertions(+), 37 deletions(-) diff --git a/src/Internal/Plutip/Server.purs b/src/Internal/Plutip/Server.purs index 08772838cd..fa6b469187 100644 --- a/src/Internal/Plutip/Server.purs +++ b/src/Internal/Plutip/Server.purs @@ -27,6 +27,7 @@ import Contract.Address ) import Contract.Config (ContractParams) import Contract.Hashing (publicKeyHash) +import Contract.Log (logTrace') import Contract.Monad ( Contract , ContractEnv @@ -43,6 +44,7 @@ import Contract.Transaction , submitTxFromConstraints ) import Contract.Utxos (utxosAt) +import Contract.Value (valueToCoin') import Contract.Wallet (withKeyWallet) import Contract.Wallet.Key ( keyWalletPrivatePaymentKey @@ -95,6 +97,7 @@ import Ctl.Internal.Plutip.UtxoDistribution , keyWallets , transferFundsFromEnterpriseToBase ) +import Ctl.Internal.Plutus.Types.Transaction (_amount, _output) import Ctl.Internal.Plutus.Types.Value (Value, lovelaceValueOf) import Ctl.Internal.Serialization.Address (addressBech32) import Ctl.Internal.Service.Error @@ -114,15 +117,18 @@ import Ctl.Internal.Wallet (KeyWallet) import Ctl.Internal.Wallet.Key (PrivatePaymentKey(PrivatePaymentKey)) import Data.Array as Array import Data.Bifunctor (lmap) +import Data.BigInt (BigInt) import Data.BigInt as BigInt import Data.Either (Either(Left), either, isLeft) import Data.Foldable (fold, sum) import Data.HTTP.Method as Method +import Data.Lens ((^.)) import Data.Log.Level (LogLevel) import Data.Log.Message (Message) import Data.Map as Map import Data.Maybe (Maybe(Just, Nothing), maybe) import Data.Newtype (over, unwrap, wrap) +import Data.String (joinWith) import Data.String.CodeUnits as String import Data.String.Pattern (Pattern(Pattern)) import Data.Traversable (foldMap, for, for_, sequence_, traverse, traverse_) @@ -130,7 +136,7 @@ import Data.Tuple (fst, snd) import Data.Tuple.Nested (type (/\), (/\)) import Data.UInt (UInt) import Data.UInt as UInt -import Effect.Aff (Aff, Milliseconds(Milliseconds), try) +import Effect.Aff (Aff, Milliseconds(Milliseconds), delay, try) import Effect.Aff (bracket) as Aff import Effect.Aff.Class (liftAff) import Effect.Aff.Retry @@ -140,6 +146,7 @@ import Effect.Aff.Retry , recovering ) import Effect.Class (liftEffect) +import Effect.Class.Console (log) import Effect.Exception (error, throw) import Effect.Ref (Ref) import Effect.Ref as Ref @@ -213,7 +220,9 @@ testContractsInEnv params backup = mapTest \(PlutipTest runPlutipTest) -> walletsArray = keyWallets (pureProxy distr) wallets runContract :: Aff Unit - runContract = runContractInEnv env { wallet = Nothing } $ mkTest wallets + runContract = runContractInEnv env { wallet = Nothing } do + logTrace' "Running contract" + mkTest wallets if Array.null walletsArray then runContract @@ -221,7 +230,7 @@ testContractsInEnv params backup = mapTest \(PlutipTest runPlutipTest) -> ( backupWallets env walletsArray *> fundWallets env walletsArray distrArray ) - (\_ -> returnFunds env walletsArray) + (returnFunds env walletsArray) \_ -> runContract where pureProxy :: forall (a :: Type). a -> Proxy a @@ -242,8 +251,9 @@ testContractsInEnv params backup = mapTest \(PlutipTest runPlutipTest) -> (Path.concat [ folder, "stake_signing_key" ]) fundWallets - :: ContractEnv -> Array KeyWallet -> Array (Array UtxoAmount) -> Aff Unit + :: ContractEnv -> Array KeyWallet -> Array (Array UtxoAmount) -> Aff BigInt fundWallets env walletsArray distrArray = runContractInEnv env do + logTrace' "Funding wallets" let constraints = flip foldMap (Array.zip walletsArray distrArray) \(wallet /\ walletDistr) -> flip foldMap walletDistr @@ -251,27 +261,77 @@ testContractsInEnv params backup = mapTest \(PlutipTest runPlutipTest) -> txHash <- submitTxFromConstraints (mempty :: _ Void) constraints awaitTxConfirmed txHash + let fundTotal = Array.foldr (flip (Array.foldr (+))) zero distrArray + -- Use log so we can see, regardless of suppression + log $ joinWith " " + [ "Sent" + , show fundTotal + , "lovelace to test wallets" + ] + pure fundTotal + + returnFunds :: ContractEnv -> Array KeyWallet -> BigInt -> Aff Unit + returnFunds env walletsArray fundTotal = runContractInEnv env do + logTrace' "Returning wallet funds" + log "here1" + + -- We could delay until there's a delta? + let + go 0 = pure unit + go n = do + utxos <- Map.unions <<< fold <$> for walletsArray + (flip withKeyWallet getWalletAddresses >=> traverse utxosAt) + let + v = Array.foldr + (\txorf acc -> acc + valueToCoin' (txorf ^. _output ^. _amount)) + zero + (Array.fromFoldable $ Map.values utxos) + log $ show v + liftAff $ delay $ wrap $ 2000.0 + go (n - 1) + + go 10 - returnFunds :: ContractEnv -> Array KeyWallet -> Aff Unit - returnFunds env walletsArray = runContractInEnv env do utxos <- Map.unions <<< fold <$> for walletsArray (flip withKeyWallet getWalletAddresses >=> traverse utxosAt) + pkhs <- fold <$> for walletsArray (flip withKeyWallet ownPaymentPubKeysHashes) + log "here2" let constraints = flip foldMap (Map.keys utxos) mustSpendPubKeyOutput <> foldMap mustBeSignedBy pkhs lookups = unspentOutputs utxos unbalancedTx <- liftedE $ mkUnbalancedTx (lookups :: _ Void) constraints + log "here3" balancedTx <- liftedE $ balanceTx unbalancedTx + log "here4" balancedSignedTx <- Array.foldM (\tx wallet -> withKeyWallet wallet $ signTransaction tx) (wrap $ unwrap balancedTx) walletsArray - txHash <- submit balancedSignedTx - awaitTxConfirmed txHash + log "here5" + -- We failed to submit + txHash <- try $ submit balancedSignedTx + log "here6" + either (log <<< show) awaitTxConfirmed txHash + log "here7" + + let + (refundTotal :: BigInt) = Array.foldr + (\txorf acc -> acc + valueToCoin' (txorf ^. _output ^. _amount)) + zero + (Array.fromFoldable $ Map.values utxos) + + log $ joinWith " " + [ "Refunded" + , show refundTotal + , "of" + , show fundTotal + , "lovelace from test wallets" + ] mustPayToKeyWallet :: forall (i :: Type) (o :: Type) @@ -771,7 +831,9 @@ mkClusterContractEnv plutipCfg logger customLogger = do { ogmiosConfig: plutipCfg.ogmiosConfig , kupoConfig: plutipCfg.kupoConfig } - ledgerConstants <- getLedgerConstants plutipCfg { customLogger = customLogger } backend + ledgerConstants <- getLedgerConstants + plutipCfg { customLogger = customLogger } + backend pure { backend , networkId: MainnetId diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index c89f67de93..2df969915d 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -66,7 +66,7 @@ import Aeson , stringifyAeson , unpackFinite ) -import Affjax (Error, Response, URL, defaultRequest, request) as Affjax +import Affjax (Error, Response, URL, defaultRequest, printError, request) as Affjax import Affjax.RequestBody (RequestBody, arrayView, string) as Affjax import Affjax.RequestHeader (RequestHeader(ContentType, RequestHeader)) as Affjax import Affjax.ResponseFormat (string) as Affjax.ResponseFormat @@ -74,6 +74,7 @@ import Affjax.StatusCode (StatusCode(StatusCode)) as Affjax import Control.Alt ((<|>)) import Control.Monad.Error.Class (liftMaybe, throwError) import Control.Monad.Except.Trans (ExceptT(ExceptT), runExceptT) +import Control.Monad.Logger.Class (log) import Control.Monad.Logger.Trans (LoggerT(LoggerT), runLoggerT) import Control.Monad.Maybe.Trans (MaybeT(MaybeT), runMaybeT) import Control.Monad.Reader.Class (ask, asks) @@ -194,8 +195,10 @@ import Data.Either (Either(Left, Right), note) import Data.Foldable (fold) import Data.Generic.Rep (class Generic) import Data.HTTP.Method (Method(GET, POST)) +import Data.JSDate (now) +import Data.Log.Level (LogLevel(Trace)) import Data.Log.Message (Message) -import Data.Map (fromFoldable, isEmpty, unions) as Map +import Data.Map (empty, fromFoldable, isEmpty, unions) as Map import Data.Maybe (Maybe(Just, Nothing), maybe) import Data.MediaType (MediaType(MediaType)) import Data.Newtype (class Newtype, unwrap, wrap) @@ -358,35 +361,57 @@ realizeEndpoint endpoint = blockfrostGetRequest :: BlockfrostEndpoint -> BlockfrostServiceM (Either Affjax.Error (Affjax.Response String)) -blockfrostGetRequest endpoint = ask >>= \params -> - withOnRawGetResponseHook endpoint =<< liftAff do - Affjax.request $ Affjax.defaultRequest - { method = Left GET - , url = mkHttpUrl params.blockfrostConfig <> realizeEndpoint endpoint - , responseFormat = Affjax.ResponseFormat.string - , headers = - maybe mempty (\apiKey -> [ Affjax.RequestHeader "project_id" apiKey ]) - params.blockfrostApiKey - } +blockfrostGetRequest endpoint = do + timestamp <- liftEffect now + log { level: Trace, message: show { endpoint }, tags: Map.empty, timestamp } + resp <- ask >>= \params -> + withOnRawGetResponseHook endpoint =<< liftAff do + Affjax.request $ Affjax.defaultRequest + { method = Left GET + , url = mkHttpUrl params.blockfrostConfig <> realizeEndpoint endpoint + , responseFormat = Affjax.ResponseFormat.string + , headers = + maybe mempty + (\apiKey -> [ Affjax.RequestHeader "project_id" apiKey ]) + params.blockfrostApiKey + } + case resp of + Right r -> log { level: Trace, message: show r, tags: Map.empty, timestamp } + Left e -> log + { level: Trace, message: Affjax.printError e, tags: Map.empty, timestamp } + pure resp blockfrostPostRequest :: BlockfrostEndpoint -> MediaType -> Maybe Affjax.RequestBody -> BlockfrostServiceM (Either Affjax.Error (Affjax.Response String)) -blockfrostPostRequest endpoint mediaType mbContent = ask >>= \params -> - withOnRawPostResponseHook endpoint mediaType mbContent =<< liftAff do - Affjax.request $ Affjax.defaultRequest - { method = Left POST - , url = mkHttpUrl params.blockfrostConfig <> realizeEndpoint endpoint - , content = mbContent - , responseFormat = Affjax.ResponseFormat.string - , headers = - [ Affjax.ContentType mediaType ] <> - maybe mempty - (\apiKey -> [ Affjax.RequestHeader "project_id" apiKey ]) - params.blockfrostApiKey - } +blockfrostPostRequest endpoint mediaType mbContent = do + timestamp <- liftEffect now + log + { level: Trace + , message: show { endpoint, mediaType {-, mbContent -} } + , tags: Map.empty + , timestamp + } + resp <- ask >>= \params -> + withOnRawPostResponseHook endpoint mediaType mbContent =<< liftAff do + Affjax.request $ Affjax.defaultRequest + { method = Left POST + , url = mkHttpUrl params.blockfrostConfig <> realizeEndpoint endpoint + , content = mbContent + , responseFormat = Affjax.ResponseFormat.string + , headers = + [ Affjax.ContentType mediaType ] <> + maybe mempty + (\apiKey -> [ Affjax.RequestHeader "project_id" apiKey ]) + params.blockfrostApiKey + } + case resp of + Right r -> log { level: Trace, message: show r, tags: Map.empty, timestamp } + Left e -> log + { level: Trace, message: Affjax.printError e, tags: Map.empty, timestamp } + pure resp withOnRawGetResponseHook :: BlockfrostEndpoint @@ -455,12 +480,19 @@ utxosAt address = runExceptT $ utxosAtAddressOnPage page = runExceptT do -- Maximum number of results per page supported by Blockfrost: let maxNumResultsOnPage = 100 - utxos <- ExceptT $ handleBlockfrostResponse <$> + -- utxos <- ExceptT $ handleBlockfrostResponse <$> + -- blockfrostGetRequest (UtxosAtAddress address page maxNumResultsOnPage) + utxos <- ExceptT $ blockfrostGetRequest (UtxosAtAddress address page maxNumResultsOnPage) + <#> handleBlockfrostResponse >>> case _ of + Left (ClientHttpResponseError (Affjax.StatusCode 404) _) -> Right + mempty + e -> e case Array.length (unwrap utxos) < maxNumResultsOnPage of true -> pure utxos false -> append utxos <$> ExceptT (utxosAtAddressOnPage $ page + 1) +-- Map 404? getUtxoByOref :: TransactionInput -> BlockfrostServiceM (Either ClientError (Maybe TransactionOutput)) @@ -741,6 +773,7 @@ newtype BlockfrostUtxosAtAddress = derive instance Generic BlockfrostUtxosAtAddress _ derive instance Newtype BlockfrostUtxosAtAddress _ derive newtype instance Semigroup BlockfrostUtxosAtAddress +derive newtype instance Monoid BlockfrostUtxosAtAddress instance Show BlockfrostUtxosAtAddress where show = genericShow diff --git a/test/Blockfrost/Contract.purs b/test/Blockfrost/Contract.purs index 02f34f27d4..1cfbf92a61 100644 --- a/test/Blockfrost/Contract.purs +++ b/test/Blockfrost/Contract.purs @@ -22,6 +22,8 @@ import Node.Process (argv, exit) import Test.Ctl.Plutip.Contract as Plutip import Test.Spec.Runner (defaultConfig) +-- TODO Remove dev config + -- Run with `spago test --main Test.Ctl.Blockfrost.Contract --exec-args "BLOCKFROST_API_KEY PRIVATE_PAYMENT_FILE BACKUP_KEYS_DIR"` main :: Effect Unit main = do diff --git a/test/Plutip/Contract.purs b/test/Plutip/Contract.purs index b8217e4360..53f89956a4 100644 --- a/test/Plutip/Contract.purs +++ b/test/Plutip/Contract.purs @@ -1280,7 +1280,7 @@ suite = do BalanceTxConstraintsExample.ContractParams { aliceKeyWallet: alice, bobKeyWallet: bob } - group "Evaluation with additional UTxOs and tx chaining" do + skip $ group "Evaluation with additional UTxOs and tx chaining" do test "Examples.TxChaining" $ let distribution :: InitialUTxOs diff --git a/test/Utils/DrainWallets.purs b/test/Utils/DrainWallets.purs index 00e9a0474d..c52521b21d 100644 --- a/test/Utils/DrainWallets.purs +++ b/test/Utils/DrainWallets.purs @@ -105,7 +105,7 @@ run privateKey walletsDir = runContract config do log $ joinWith " " [ "Found" , show $ Map.size utxos - , "in" + , "UTxOs in" , show $ Array.length usedWallets , "wallets." ] From 4bfefa17072fbb27e06bbda24e6941dfa587c4bb Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Fri, 20 Jan 2023 14:21:21 +0300 Subject: [PATCH 302/373] Add info on updating the webpack config --- doc/ctl-as-dependency.md | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/doc/ctl-as-dependency.md b/doc/ctl-as-dependency.md index 67094a605d..a0d97559a5 100644 --- a/doc/ctl-as-dependency.md +++ b/doc/ctl-as-dependency.md @@ -82,6 +82,10 @@ Make sure to perform **all** of the following steps, otherwise you **will** enco - That is, avoid using the `~` or `^` prefixes (e.g use versions like `"1.6.51"` instead of `"^1.6.51"`) - If you're using a `package-lock.json` (which is _highly_ recommended), you can update the lockfile with `npm i --package-lock-only` +4. **Update your webpack config** + +- Sometimes the WebPack configuration also comes with breaking changes. Common source of problems are changes to `resolve.fallback`, `plugins` and `experiments` fields of the WebPack config. Use `git diff old-revision new-revision webpack.config.js` in the root of a cloned CTL repo, or use `git blame`. + ## Using CTL from JS ### Bundling From b0b884052d608e7edae0a73510a79644ebebb98a Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Fri, 20 Jan 2023 16:26:12 +0100 Subject: [PATCH 303/373] Refactor request / response logging code --- src/Internal/Service/Blockfrost.purs | 110 +++++++++++++++------------ 1 file changed, 63 insertions(+), 47 deletions(-) diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index 2df969915d..2bd9247d11 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -191,11 +191,11 @@ import Data.BigInt (fromString, toNumber) as BigInt import Data.BigNumber (BigNumber, toFraction) import Data.BigNumber as BigNumber import Data.DateTime.Instant (instant, toDateTime) -import Data.Either (Either(Left, Right), note) +import Data.Either (Either(Left, Right), either, note) import Data.Foldable (fold) import Data.Generic.Rep (class Generic) import Data.HTTP.Method (Method(GET, POST)) -import Data.JSDate (now) +import Data.JSDate (JSDate, now) import Data.Log.Level (LogLevel(Trace)) import Data.Log.Message (Message) import Data.Map (empty, fromFoldable, isEmpty, unions) as Map @@ -361,57 +361,46 @@ realizeEndpoint endpoint = blockfrostGetRequest :: BlockfrostEndpoint -> BlockfrostServiceM (Either Affjax.Error (Affjax.Response String)) -blockfrostGetRequest endpoint = do - timestamp <- liftEffect now - log { level: Trace, message: show { endpoint }, tags: Map.empty, timestamp } - resp <- ask >>= \params -> - withOnRawGetResponseHook endpoint =<< liftAff do - Affjax.request $ Affjax.defaultRequest - { method = Left GET - , url = mkHttpUrl params.blockfrostConfig <> realizeEndpoint endpoint - , responseFormat = Affjax.ResponseFormat.string - , headers = - maybe mempty - (\apiKey -> [ Affjax.RequestHeader "project_id" apiKey ]) - params.blockfrostApiKey - } - case resp of - Right r -> log { level: Trace, message: show r, tags: Map.empty, timestamp } - Left e -> log - { level: Trace, message: Affjax.printError e, tags: Map.empty, timestamp } - pure resp +blockfrostGetRequest endpoint = + withRequestResponseTracing + (BlockfrostGetRequestData endpoint) + ( ask >>= \params -> + withOnRawGetResponseHook endpoint =<< liftAff do + Affjax.request $ Affjax.defaultRequest + { method = Left GET + , url = + mkHttpUrl params.blockfrostConfig <> realizeEndpoint endpoint + , responseFormat = Affjax.ResponseFormat.string + , headers = + maybe mempty + (\apiKey -> [ Affjax.RequestHeader "project_id" apiKey ]) + params.blockfrostApiKey + } + ) blockfrostPostRequest :: BlockfrostEndpoint -> MediaType -> Maybe Affjax.RequestBody -> BlockfrostServiceM (Either Affjax.Error (Affjax.Response String)) -blockfrostPostRequest endpoint mediaType mbContent = do - timestamp <- liftEffect now - log - { level: Trace - , message: show { endpoint, mediaType {-, mbContent -} } - , tags: Map.empty - , timestamp - } - resp <- ask >>= \params -> - withOnRawPostResponseHook endpoint mediaType mbContent =<< liftAff do - Affjax.request $ Affjax.defaultRequest - { method = Left POST - , url = mkHttpUrl params.blockfrostConfig <> realizeEndpoint endpoint - , content = mbContent - , responseFormat = Affjax.ResponseFormat.string - , headers = - [ Affjax.ContentType mediaType ] <> - maybe mempty - (\apiKey -> [ Affjax.RequestHeader "project_id" apiKey ]) - params.blockfrostApiKey - } - case resp of - Right r -> log { level: Trace, message: show r, tags: Map.empty, timestamp } - Left e -> log - { level: Trace, message: Affjax.printError e, tags: Map.empty, timestamp } - pure resp +blockfrostPostRequest endpoint mediaType mbContent = + withRequestResponseTracing + (BlockfrostPostRequestData endpoint mediaType mbContent) + ( ask >>= \params -> + withOnRawPostResponseHook endpoint mediaType mbContent =<< liftAff do + Affjax.request $ Affjax.defaultRequest + { method = Left POST + , url = + mkHttpUrl params.blockfrostConfig <> realizeEndpoint endpoint + , content = mbContent + , responseFormat = Affjax.ResponseFormat.string + , headers = + [ Affjax.ContentType mediaType ] <> + maybe mempty + (\apiKey -> [ Affjax.RequestHeader "project_id" apiKey ]) + params.blockfrostApiKey + } + ) withOnRawGetResponseHook :: BlockfrostEndpoint @@ -436,6 +425,33 @@ withOnRawPostResponseHook endpoint mediaType requestBody result = do liftAff $ for_ onRawPostResponse \f -> f data_ pure result +data BlockfrostRequestData + = BlockfrostGetRequestData BlockfrostEndpoint + | BlockfrostPostRequestData BlockfrostEndpoint MediaType + (Maybe Affjax.RequestBody) + +withRequestResponseTracing + :: BlockfrostRequestData + -> BlockfrostServiceM (Either Affjax.Error (Affjax.Response String)) + -> BlockfrostServiceM (Either Affjax.Error (Affjax.Response String)) +withRequestResponseTracing requestData performRequest = do + timestamp <- liftEffect now + trace timestamp requestMessage + response <- performRequest + trace timestamp (either Affjax.printError show response) + pure response + where + trace :: JSDate -> String -> BlockfrostServiceM Unit + trace timestamp message = + log { level: Trace, message, tags: Map.empty, timestamp } + + requestMessage :: String + requestMessage = case requestData of + BlockfrostGetRequestData endpoint -> + show { endpoint } + BlockfrostPostRequestData endpoint mediaType _ -> + show { endpoint, mediaType {- mbContent -} } + -------------------------------------------------------------------------------- -- Blockfrost response handling -------------------------------------------------------------------------------- From 7f1806dbaf9c188e41a4e5e877955f7b8654bc6f Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Fri, 20 Jan 2023 17:06:42 +0100 Subject: [PATCH 304/373] Handle 404 error on utxosAt and getUtxoByOref --- src/Internal/Service/Blockfrost.purs | 31 +++++++++++++++------------- 1 file changed, 17 insertions(+), 14 deletions(-) diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index 2bd9247d11..a20a406d6f 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -199,7 +199,7 @@ import Data.JSDate (JSDate, now) import Data.Log.Level (LogLevel(Trace)) import Data.Log.Message (Message) import Data.Map (empty, fromFoldable, isEmpty, unions) as Map -import Data.Maybe (Maybe(Just, Nothing), maybe) +import Data.Maybe (Maybe(Just, Nothing), fromMaybe, maybe) import Data.MediaType (MediaType(MediaType)) import Data.Newtype (class Newtype, unwrap, wrap) import Data.Number (infinity) @@ -475,13 +475,20 @@ handleBlockfrostResponse (Right { status: Affjax.StatusCode statusCode, body }) <<< (decodeAeson <=< parseJsonStringToAeson) handle404AsNothing - :: forall (x :: Type) - . Either ClientError (Maybe x) - -> Either ClientError (Maybe x) + :: forall (a :: Type) + . Either ClientError (Maybe a) + -> Either ClientError (Maybe a) handle404AsNothing (Left (ClientHttpResponseError (Affjax.StatusCode 404) _)) = Right Nothing handle404AsNothing x = x +handle404AsMempty + :: forall (a :: Type) + . Monoid a + => Either ClientError (Maybe a) + -> Either ClientError a +handle404AsMempty = map (fromMaybe mempty) <<< handle404AsNothing + -------------------------------------------------------------------------------- -- Get utxos at address / by output reference -------------------------------------------------------------------------------- @@ -496,26 +503,20 @@ utxosAt address = runExceptT $ utxosAtAddressOnPage page = runExceptT do -- Maximum number of results per page supported by Blockfrost: let maxNumResultsOnPage = 100 - -- utxos <- ExceptT $ handleBlockfrostResponse <$> - -- blockfrostGetRequest (UtxosAtAddress address page maxNumResultsOnPage) utxos <- ExceptT $ blockfrostGetRequest (UtxosAtAddress address page maxNumResultsOnPage) - <#> handleBlockfrostResponse >>> case _ of - Left (ClientHttpResponseError (Affjax.StatusCode 404) _) -> Right - mempty - e -> e + <#> handle404AsMempty <<< handleBlockfrostResponse case Array.length (unwrap utxos) < maxNumResultsOnPage of true -> pure utxos false -> append utxos <$> ExceptT (utxosAtAddressOnPage $ page + 1) --- Map 404? getUtxoByOref :: TransactionInput -> BlockfrostServiceM (Either ClientError (Maybe TransactionOutput)) getUtxoByOref oref@(TransactionInput { transactionId: txHash }) = runExceptT do - (blockfrostUtxoMap :: BlockfrostUtxosOfTransaction) <- - ExceptT $ handleBlockfrostResponse <$> - blockfrostGetRequest (UtxosOfTransaction txHash) + (blockfrostUtxoMap :: BlockfrostUtxosOfTransaction) <- ExceptT $ + blockfrostGetRequest (UtxosOfTransaction txHash) + <#> handle404AsMempty <<< handleBlockfrostResponse traverse (ExceptT <<< resolveBlockfrostTxOutput) (snd <$> Array.find (eq oref <<< fst) (unwrap blockfrostUtxoMap)) @@ -827,6 +828,8 @@ newtype BlockfrostUtxosOfTransaction = derive instance Generic BlockfrostUtxosOfTransaction _ derive instance Newtype BlockfrostUtxosOfTransaction _ +derive newtype instance Semigroup BlockfrostUtxosOfTransaction +derive newtype instance Monoid BlockfrostUtxosOfTransaction instance Show BlockfrostUtxosOfTransaction where show = genericShow From 51e4953532b910d1eb7c48cfb2472a8706897efd Mon Sep 17 00:00:00 2001 From: Alexey Date: Sun, 22 Jan 2023 21:58:32 +0300 Subject: [PATCH 305/373] Show error details in startPlutipCluster error msg --- src/Internal/Plutip/Server.purs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/Internal/Plutip/Server.purs b/src/Internal/Plutip/Server.purs index 5aff7cf515..3dd618aa96 100644 --- a/src/Internal/Plutip/Server.purs +++ b/src/Internal/Plutip/Server.purs @@ -492,8 +492,9 @@ startPlutipCluster cfg keysToGenerate = do $ (decodeAeson <=< parseJsonStringToAeson) body either (liftEffect <<< throw <<< show) pure res >>= case _ of - ClusterStartupFailure _ -> do - liftEffect $ throw "Failed to start up cluster" + ClusterStartupFailure reason -> do + liftEffect $ throw $ + "Failed to start up cluster. Reason: " <> show reason ClusterStartupSuccess response@{ privateKeys } -> case Array.uncons privateKeys of Nothing -> From a7b1323090b0e8320b3d28b04111cceea59c0790 Mon Sep 17 00:00:00 2001 From: Alexey Date: Sun, 22 Jan 2023 22:05:24 +0300 Subject: [PATCH 306/373] Make CHANGELOG entry --- CHANGELOG.md | 2 ++ 1 file changed, 2 insertions(+) diff --git a/CHANGELOG.md b/CHANGELOG.md index 96892d89de..f9e87c8f0a 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -53,6 +53,8 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) ### Changed +- `startPlutipCluster` error message now includes cluster startup failure details. ([#1406](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1406)) + ### Removed ### Fixed From 8c5fd575f35028075e9157ee26130b9e1004f0ec Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Mon, 23 Jan 2023 12:34:57 +0300 Subject: [PATCH 307/373] Use correct PR number --- CHANGELOG.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index f9e87c8f0a..7a56f6cfdf 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -53,7 +53,7 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) ### Changed -- `startPlutipCluster` error message now includes cluster startup failure details. ([#1406](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1406)) +- `startPlutipCluster` error message now includes cluster startup failure details. ([#1407](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1407)) ### Removed From 298b2cdcc49141fdb63b9b323be0a57b5ef00ef0 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Mon, 23 Jan 2023 14:33:16 +0400 Subject: [PATCH 308/373] Use a fixed version of Chromium --- nix/default.nix | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/nix/default.nix b/nix/default.nix index f3ae84a4ee..ec8546f457 100644 --- a/nix/default.nix +++ b/nix/default.nix @@ -93,7 +93,7 @@ let # available in the shell environment. This can help with ensuring that # any e2e tests that you write and run with `Contract.Test.E2E` are # reproducible - , withChromium ? false + , withChromium ? true }: assert pkgs.lib.assertOneOf "formatter" formatter [ "purs-tidy" "purty" ]; with pkgs.lib; From 5e340fdff2043251d3349f88c775627bb6567e48 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Mon, 23 Jan 2023 15:34:11 +0400 Subject: [PATCH 309/373] Better organization and titles for plutip tests --- test/AffInterface.purs | 6 +- test/Plutip/Contract.purs | 629 ++++++++++++++++++++------------------ 2 files changed, 328 insertions(+), 307 deletions(-) diff --git a/test/AffInterface.purs b/test/AffInterface.purs index 22fb7d9953..02ca5859ed 100644 --- a/test/AffInterface.purs +++ b/test/AffInterface.purs @@ -49,7 +49,7 @@ addr1 = -- state, and ogmios itself. suite :: TestPlanM (QueryM Unit) Unit suite = do - group "Aff Interface" do + group "Asynchronous requests interface" do test "UtxosAt Testnet" $ testUtxosAt testnet_addr1 test "UtxosAt Mainnet" $ testUtxosAt addr1 test "Get ChainTip" testGetChainTip @@ -57,7 +57,7 @@ suite = do test "Get EraSummaries" testGetEraSummaries test "Get CurrentEpoch" testGetCurrentEpoch test "Get SystemStart" testGetSystemStart - group "Ogmios error" do + group "Ogmios error handling" do test "Ogmios fails with user-friendly message" do try testSubmitTxFailure >>= case _ of Right _ -> do @@ -66,7 +66,7 @@ suite = do Left error -> do (Pattern "Server responded with `fault`" `indexOf` show error) `shouldSatisfy` isJust - group "Ogmios datum cache" do + group "ogmios-datum-cache" do test "Can process GetDatumByHash" do testOgmiosDatumCacheGetDatumByHash test "Can process GetDatumsByHashes" do diff --git a/test/Plutip/Contract.purs b/test/Plutip/Contract.purs index e9336d704b..ce08636dd3 100644 --- a/test/Plutip/Contract.purs +++ b/test/Plutip/Contract.purs @@ -167,13 +167,13 @@ import Test.Spec.Assertions (shouldEqual, shouldNotEqual, shouldSatisfy) suite :: TestPlanM PlutipTest Unit suite = do - group "Contract" do + group "Contract interface" do flip mapTest AffInterface.suite (noWallet <<< wrapContract) NetworkId.suite - test "Collateral" do + test "Collateral selection: UTxO with lower amount is selected" do let distribution :: InitialUTxOs /\ InitialUTxOs distribution = @@ -198,7 +198,7 @@ suite = do withKeyWallet bob do pure unit -- sign, balance, submit, etc. - test "Pkh2Pkh" do + test "Payment keyhash to payment keyhash transaction (Pkh2Pkh example)" do let distribution :: InitialUTxOs distribution = @@ -212,68 +212,42 @@ suite = do stakePkh <- join <<< head <$> withKeyWallet alice ownStakePubKeysHashes withKeyWallet alice $ pkh2PkhContract pkh stakePkh - test "Pkh2Pkh with stake key" do - let - aliceUtxos = - [ BigInt.fromInt 2_000_000_000 - , BigInt.fromInt 2_000_000_000 - ] - distribution = withStakeKey privateStakeKey aliceUtxos + test + "Base Address to Base Address transaction (Pkh2Pkh example, but with stake keys)" + do + let + aliceUtxos = + [ BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 2_000_000_000 + ] + distribution = withStakeKey privateStakeKey aliceUtxos - withWallets distribution \alice -> do - checkUtxoDistribution distribution alice - pkh <- liftedM "Failed to get PKH" $ head <$> withKeyWallet alice - ownPaymentPubKeysHashes - stakePkh <- join <<< head <$> withKeyWallet alice ownStakePubKeysHashes - stakePkh `shouldSatisfy` isJust - withKeyWallet alice $ pkh2PkhContract pkh stakePkh + withWallets distribution \alice -> do + checkUtxoDistribution distribution alice + pkh <- liftedM "Failed to get PKH" $ head <$> withKeyWallet alice + ownPaymentPubKeysHashes + stakePkh <- join <<< head <$> withKeyWallet alice + ownStakePubKeysHashes + stakePkh `shouldSatisfy` isJust + withKeyWallet alice $ pkh2PkhContract pkh stakePkh - test "parallel Pkh2Pkh" do - let - aliceUtxos = - [ BigInt.fromInt 1_000_000_000 - , BigInt.fromInt 2_000_000_000 - ] - bobUtxos = - [ BigInt.fromInt 1_000_000_000 - , BigInt.fromInt 2_000_000_000 - ] + test + "Payment key hash to payment key hash Tx: running two contracts in parallel (Pkh2Pkh example)" + do + let + aliceUtxos = + [ BigInt.fromInt 1_000_000_000 + , BigInt.fromInt 2_000_000_000 + ] + bobUtxos = + [ BigInt.fromInt 1_000_000_000 + , BigInt.fromInt 2_000_000_000 + ] - distribution :: InitialUTxOs /\ InitialUTxOs - distribution = aliceUtxos /\ bobUtxos + distribution :: InitialUTxOs /\ InitialUTxOs + distribution = aliceUtxos /\ bobUtxos - withWallets distribution \wallets@(alice /\ bob) -> do - checkUtxoDistribution distribution wallets - sequential ado - parallel $ withKeyWallet alice do - pkh <- liftedM "Failed to get PKH" $ head <$> withKeyWallet bob - ownPaymentPubKeysHashes - stakePkh <- join <<< head <$> withKeyWallet bob - ownStakePubKeysHashes - pkh2PkhContract pkh stakePkh - parallel $ withKeyWallet bob do - pkh <- liftedM "Failed to get PKH" $ head <$> withKeyWallet alice - ownPaymentPubKeysHashes - stakePkh <- join <<< head <$> withKeyWallet alice - ownStakePubKeysHashes - pkh2PkhContract pkh stakePkh - in unit - - test "parallel Pkh2Pkh with stake keys" do - let - aliceUtxos = - [ BigInt.fromInt 1_000_000_000 - , BigInt.fromInt 2_000_000_000 - ] - bobUtxos = - [ BigInt.fromInt 1_000_000_000 - , BigInt.fromInt 2_000_000_000 - ] - distribution = - withStakeKey privateStakeKey aliceUtxos - /\ withStakeKey privateStakeKey bobUtxos - withWallets distribution \wallets@(alice /\ bob) -> - do + withWallets distribution \wallets@(alice /\ bob) -> do checkUtxoDistribution distribution wallets sequential ado parallel $ withKeyWallet alice do @@ -290,14 +264,48 @@ suite = do pkh2PkhContract pkh stakePkh in unit - test "awaitTxConfirmedWithTimeout fails after timeout" do + test + "Base Address to Base Address hash Tx: running two contracts in parallel (Pkh2Pkh example)" + do + let + aliceUtxos = + [ BigInt.fromInt 1_000_000_000 + , BigInt.fromInt 2_000_000_000 + ] + bobUtxos = + [ BigInt.fromInt 1_000_000_000 + , BigInt.fromInt 2_000_000_000 + ] + distribution = + withStakeKey privateStakeKey aliceUtxos + /\ withStakeKey privateStakeKey bobUtxos + withWallets distribution \wallets@(alice /\ bob) -> + do + checkUtxoDistribution distribution wallets + sequential ado + parallel $ withKeyWallet alice do + pkh <- liftedM "Failed to get PKH" $ head <$> withKeyWallet bob + ownPaymentPubKeysHashes + stakePkh <- join <<< head <$> withKeyWallet bob + ownStakePubKeysHashes + pkh2PkhContract pkh stakePkh + parallel $ withKeyWallet bob do + pkh <- liftedM "Failed to get PKH" $ head <$> withKeyWallet + alice + ownPaymentPubKeysHashes + stakePkh <- join <<< head <$> withKeyWallet alice + ownStakePubKeysHashes + pkh2PkhContract pkh stakePkh + in unit + + test "Tx confirmation fails after timeout (awaitTxConfirmedWithTimeout)" do let distribution = withStakeKey privateStakeKey [ BigInt.fromInt 1_000_000_000 ] withWallets distribution \_ -> AwaitTxConfirmedWithTimeout.contract - test "NativeScript: require all signers" do + test "NativeScript (multisig) support: require all signers" do let distribution :: InitialUTxOs /\ InitialUTxOs /\ InitialUTxOs /\ InitialUTxOs @@ -394,7 +402,7 @@ suite = do txSigned <- foldM signWithWallet tx [ alice, bob, charlie, dan ] submit txSigned >>= awaitTxConfirmed - test "NativeScript: NOfK (2)" do + test "NativeScript support: require N=2 of K=4 signers" do let distribution :: InitialUTxOs /\ InitialUTxOs /\ InitialUTxOs /\ InitialUTxOs @@ -483,7 +491,7 @@ suite = do txSigned <- foldM signWithWallet tx [ dan ] submit txSigned >>= awaitTxConfirmed - test "AlwaysMints" do + test "An always-succeeding minting policy" do let distribution :: InitialUTxOs distribution = @@ -511,7 +519,7 @@ suite = do bsTx <- signTransaction =<< liftedE (balanceTx ubTx) submitAndLog bsTx - test "mustProduceAtLeast success" do + test "mustProduceAtLeast spends native token" do let distribution :: InitialUTxOs distribution = @@ -553,7 +561,7 @@ suite = do txHash' <- submitTxFromConstraints lookups' constraints' void $ awaitTxConfirmed txHash' - test "mustProduceAtLeast fail" do + test "mustProduceAtLeast fails to produce more tokens than there is" do let distribution :: InitialUTxOs distribution = @@ -596,7 +604,7 @@ suite = do result <- balanceTx ubTx result `shouldSatisfy` isLeft - test "mustSpendAtLeast success" do + test "mustSpendAtLeast succeeds to spend" do let distribution :: InitialUTxOs distribution = @@ -638,7 +646,7 @@ suite = do txHash' <- submitTxFromConstraints lookups' constraints' void $ awaitTxConfirmed txHash' - test "mustSpendAtLeast fail" do + test "mustSpendAtLeast fails to spend more token that there is" do let distribution :: InitialUTxOs distribution = @@ -681,7 +689,7 @@ suite = do result <- balanceTx ubTx result `shouldSatisfy` isLeft - test "NativeScriptMints" do + test "Minting using NativeScript (multisig) as a policy" do let distribution :: InitialUTxOs distribution = @@ -691,7 +699,7 @@ suite = do withWallets distribution \alice -> do withKeyWallet alice NativeScriptMints.contract - test "Datums" do + test "Getting datums by hashes" do withWallets unit \_ -> do let mkDatumHash :: String -> DataHash @@ -777,7 +785,7 @@ suite = do , hash2 /\ Right datum2 ] - test "MintZeroToken" do + test "Minting zero of a token fails" do let distribution :: InitialUTxOs distribution = @@ -804,7 +812,7 @@ suite = do result <- Lookups.mkUnbalancedTx lookups constraints result `shouldSatisfy` isLeft - test "MintsMultipleTokens" do + test "Minting multiple tokens in a single transaction" do let distribution :: InitialUTxOs distribution = @@ -843,7 +851,7 @@ suite = do bsTx <- signTransaction =<< liftedE (balanceTx ubTx) submitAndLog bsTx - test "SignMultiple" do + test "Multi-signature transaction" do let distribution :: InitialUTxOs distribution = @@ -854,7 +862,7 @@ suite = do checkUtxoDistribution distribution alice withKeyWallet alice signMultipleContract - test "SignMultiple with stake key" do + test "Multi-signature transaction with BaseAddresses" do let aliceUtxos = [ BigInt.fromInt 5_000_000 @@ -865,25 +873,27 @@ suite = do checkUtxoDistribution distribution alice withKeyWallet alice signMultipleContract - test "AlwaysSucceeds" do - let - distribution :: InitialUTxOs - distribution = - [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 2_000_000_000 - ] - withWallets distribution \alice -> do - withKeyWallet alice do - validator <- AlwaysSucceeds.alwaysSucceedsScript - let vhash = validatorHash validator - logInfo' "Attempt to lock value" - txId <- AlwaysSucceeds.payToAlwaysSucceeds vhash - awaitTxConfirmed txId - logInfo' "Try to spend locked values" - AlwaysSucceeds.spendFromAlwaysSucceeds vhash validator txId + test + "Locking & unlocking on an always succeeding script (AlwaysSucceeds example)" + do + let + distribution :: InitialUTxOs + distribution = + [ BigInt.fromInt 5_000_000 + , BigInt.fromInt 2_000_000_000 + ] + withWallets distribution \alice -> do + withKeyWallet alice do + validator <- AlwaysSucceeds.alwaysSucceedsScript + let vhash = validatorHash validator + logInfo' "Attempt to lock value" + txId <- AlwaysSucceeds.payToAlwaysSucceeds vhash + awaitTxConfirmed txId + logInfo' "Try to spend locked values" + AlwaysSucceeds.spendFromAlwaysSucceeds vhash validator txId test - "AlwaysSucceeds (with stake key to test `mustPayToPubKeyAddress`)" + "AlwaysSucceeds example (with stake key to test `mustPayToPubKeyAddress`)" do let distribution :: InitialUTxOsWithStakeKey @@ -901,13 +911,13 @@ suite = do logInfo' "Try to spend locked values" AlwaysSucceeds.spendFromAlwaysSucceeds vhash validator txId - test "currentTime" do + test "Query for current time and era summaries" do withWallets unit \_ -> do void $ currentTime void $ getEraSummaries >>= unwrap >>> traverse (getSlotLength >>> show >>> logInfo') - test "SendsToken" do + test "Mints and sends a token" do let distribution :: InitialUTxOs distribution = @@ -917,81 +927,93 @@ suite = do withWallets distribution \alice -> do withKeyWallet alice SendsToken.contract - test "InlineDatum" do - let - distribution :: InitialUTxOs - distribution = - [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 2_000_000_000 - ] - withWallets distribution \alice -> do - withKeyWallet alice do - validator <- InlineDatum.checkDatumIsInlineScript - let vhash = validatorHash validator - logInfo' "Attempt to lock value with inline datum" - txId <- InlineDatum.payToCheckDatumIsInline vhash - awaitTxConfirmed txId - logInfo' "Try to spend locked values" - InlineDatum.spendFromCheckDatumIsInline vhash validator txId + group "CIP-32 InlineDatums" do + test "Use of CIP-32 InlineDatums" do + let + distribution :: InitialUTxOs + distribution = + [ BigInt.fromInt 5_000_000 + , BigInt.fromInt 2_000_000_000 + ] + withWallets distribution \alice -> do + withKeyWallet alice do + validator <- InlineDatum.checkDatumIsInlineScript + let vhash = validatorHash validator + logInfo' "Attempt to lock value with inline datum" + txId <- InlineDatum.payToCheckDatumIsInline vhash + awaitTxConfirmed txId + logInfo' "Try to spend locked values" + InlineDatum.spendFromCheckDatumIsInline vhash validator txId - test "InlineDatum Read" do - let - distribution :: InitialUTxOs - distribution = - [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 2_000_000_000 - ] - withWallets distribution \alice -> do - withKeyWallet alice do - validator <- InlineDatum.checkDatumIsInlineScript - let vhash = validatorHash validator - logInfo' "Attempt to lock value with inline datum" - txId <- InlineDatum.payToCheckDatumIsInline vhash - awaitTxConfirmed txId - logInfo' "Try to read inline datum" - InlineDatum.readFromCheckDatumIsInline vhash txId + test "Use of CIP-30 InlineDatums without spending the UTxO (readonly)" do + let + distribution :: InitialUTxOs + distribution = + [ BigInt.fromInt 5_000_000 + , BigInt.fromInt 2_000_000_000 + ] + withWallets distribution \alice -> do + withKeyWallet alice do + validator <- InlineDatum.checkDatumIsInlineScript + let vhash = validatorHash validator + logInfo' "Attempt to lock value with inline datum" + txId <- InlineDatum.payToCheckDatumIsInline vhash + awaitTxConfirmed txId + logInfo' "Try to read inline datum" + InlineDatum.readFromCheckDatumIsInline vhash txId - test "InlineDatum Failure" do - let - distribution :: InitialUTxOs - distribution = - [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 2_000_000_000 - ] - withWallets distribution \alice -> do - withKeyWallet alice do - validator <- InlineDatum.checkDatumIsInlineScript - let vhash = validatorHash validator - logInfo' "Attempt to lock value without inline datum" - txId <- InlineDatum.payToCheckDatumIsInlineWrong vhash - awaitTxConfirmed txId - logInfo' "Try to spend locked values" - eResult <- try $ InlineDatum.spendFromCheckDatumIsInline vhash - validator - txId - eResult `shouldSatisfy` isLeft + test "InlineDatum spending fails because the datum was not set inline" do + let + distribution :: InitialUTxOs + distribution = + [ BigInt.fromInt 5_000_000 + , BigInt.fromInt 2_000_000_000 + ] + withWallets distribution \alice -> do + withKeyWallet alice do + validator <- InlineDatum.checkDatumIsInlineScript + let vhash = validatorHash validator + logInfo' "Attempt to lock value without inline datum" + txId <- InlineDatum.payToCheckDatumIsInlineWrong vhash + awaitTxConfirmed txId + logInfo' "Try to spend locked values" + eResult <- try $ InlineDatum.spendFromCheckDatumIsInline vhash + validator + txId + eResult `shouldSatisfy` isLeft - test "InlineDatum Cannot Spend PlutusV1" do - let - distribution :: InitialUTxOs - distribution = - [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 2_000_000_000 - ] - withWallets distribution \alice -> do - withKeyWallet alice do - validator <- AlwaysSucceeds.alwaysSucceedsScript - let vhash = validatorHash validator - logInfo' "Attempt to lock value at plutusv1 script with inline datum" - txId <- InlineDatum.payToCheckDatumIsInline vhash - awaitTxConfirmed txId - logInfo' "Try to spend locked values" - eResult <- try $ InlineDatum.spendFromCheckDatumIsInline vhash - validator - txId - eResult `shouldSatisfy` isLeft + test "InlineDatum fails because PlutusV1 script is used" do + let + distribution :: InitialUTxOs + distribution = + [ BigInt.fromInt 5_000_000 + , BigInt.fromInt 2_000_000_000 + ] + withWallets distribution \alice -> do + withKeyWallet alice do + validator <- AlwaysSucceeds.alwaysSucceedsScript + let vhash = validatorHash validator + logInfo' + "Attempt to lock value at plutusv1 script with inline datum" + txId <- InlineDatum.payToCheckDatumIsInline vhash + awaitTxConfirmed txId + logInfo' "Try to spend locked values" + eResult <- try $ InlineDatum.spendFromCheckDatumIsInline vhash + validator + txId + eResult `shouldSatisfy` isLeft - test "IncludeDatum" do + test "Payment with inline datum" do + let + distribution :: InitialUTxOs + distribution = + [ BigInt.fromInt 5_000_000 + , BigInt.fromInt 2_000_000_000 + ] + withWallets distribution \alice -> + withKeyWallet alice PaysWithDatum.contract + + test "Lock value at a script: validator that only accepts 42 as redeemer" do let distribution :: InitialUTxOs distribution = @@ -1008,7 +1030,7 @@ suite = do logInfo' "Try to spend locked values" IncludeDatum.spendFromIncludeDatum vhash validator txId - test "AlwaysSucceeds PlutusV2" do + test "Always succeeding PlutusV2 script" do let distribution :: InitialUTxOs distribution = @@ -1025,124 +1047,132 @@ suite = do logInfo' "Try to spend locked values" AlwaysSucceeds.spendFromAlwaysSucceeds vhash validator txId - test "AlwaysFails Ada Collateral Return" do - let - distribution :: InitialUTxOs /\ InitialUTxOs - distribution = - [ BigInt.fromInt 10_000_000 - , BigInt.fromInt 2_000_000_000 - ] /\ [ BigInt.fromInt 2_000_000_000 ] - withWallets distribution \(alice /\ seed) -> do - validator <- AlwaysFails.alwaysFailsScript - let vhash = validatorHash validator - txId <- withKeyWallet seed do - logInfo' "Attempt to lock value" - txId <- AlwaysFails.payToAlwaysFails vhash - awaitTxConfirmed txId - pure txId + group "CIP-40 Collateral Output" do + test "Always failing script triggers Collateral Return (ADA-only)" do + let + distribution :: InitialUTxOs /\ InitialUTxOs + distribution = + [ BigInt.fromInt 10_000_000 + , BigInt.fromInt 2_000_000_000 + ] /\ [ BigInt.fromInt 2_000_000_000 ] + withWallets distribution \(alice /\ seed) -> do + validator <- AlwaysFails.alwaysFailsScript + let vhash = validatorHash validator + txId <- withKeyWallet seed do + logInfo' "Attempt to lock value" + txId <- AlwaysFails.payToAlwaysFails vhash + awaitTxConfirmed txId + pure txId - withKeyWallet alice do - awaitTxConfirmed txId - logInfo' "Try to spend locked values" - balanceBefore <- fold <$> getWalletBalance - AlwaysFails.spendFromAlwaysFails vhash validator txId - balance <- fold <$> getWalletBalance - let - collateralLoss = Value.lovelaceValueOf $ BigInt.fromInt $ -5_000_000 - balance `shouldEqual` (balanceBefore <> collateralLoss) + withKeyWallet alice do + awaitTxConfirmed txId + logInfo' "Try to spend locked values" + balanceBefore <- fold <$> getWalletBalance + AlwaysFails.spendFromAlwaysFails vhash validator txId + balance <- fold <$> getWalletBalance + let + collateralLoss = Value.lovelaceValueOf $ BigInt.fromInt $ + -5_000_000 + balance `shouldEqual` (balanceBefore <> collateralLoss) - test "AlwaysFails Native Asset Collateral Return" do - let - distribution :: InitialUTxOs /\ InitialUTxOs - distribution = - [] /\ [ BigInt.fromInt 2_100_000_000 ] - withWallets distribution \(alice /\ seed) -> do - alicePkh /\ aliceStakePkh <- withKeyWallet alice do - pkh <- liftedM "Failed to get PKH" $ head <$> ownPaymentPubKeysHashes - stakePkh <- join <<< head <$> ownStakePubKeysHashes - pure $ pkh /\ stakePkh - - mp <- alwaysMintsPolicy - cs <- liftContractM "Cannot get cs" $ Value.scriptCurrencySymbol mp - tn <- liftContractM "Cannot make token name" - $ byteArrayFromAscii "TheToken" >>= Value.mkTokenName - let asset = Value.singleton cs tn $ BigInt.fromInt 50 - - validator <- AlwaysFails.alwaysFailsScript - let vhash = validatorHash validator - - txId <- withKeyWallet seed do - logInfo' "Minting asset to Alice" + test "AlwaysFails script triggers Native Asset Collateral Return (tokens)" + do let - constraints :: Constraints.TxConstraints Void Void - constraints = Constraints.mustMintValue (asset <> asset) - <> mustPayToPubKeyStakeAddress alicePkh aliceStakePkh - (asset <> (Value.lovelaceValueOf $ BigInt.fromInt 10_000_000)) - <> mustPayToPubKeyStakeAddress alicePkh aliceStakePkh - ( asset <> - (Value.lovelaceValueOf $ BigInt.fromInt 2_000_000_000) - ) - - lookups :: Lookups.ScriptLookups Void - lookups = Lookups.mintingPolicy mp - - ubTx <- liftedE $ Lookups.mkUnbalancedTx lookups constraints - bsTx <- signTransaction =<< liftedE (balanceTx ubTx) - submit bsTx >>= awaitTxConfirmed - - logInfo' "Attempt to lock value" - txId <- AlwaysFails.payToAlwaysFails vhash - awaitTxConfirmed txId - pure txId + distribution :: InitialUTxOs /\ InitialUTxOs + distribution = + [] /\ [ BigInt.fromInt 2_100_000_000 ] + withWallets distribution \(alice /\ seed) -> do + alicePkh /\ aliceStakePkh <- withKeyWallet alice do + pkh <- liftedM "Failed to get PKH" $ head <$> + ownPaymentPubKeysHashes + stakePkh <- join <<< head <$> ownStakePubKeysHashes + pure $ pkh /\ stakePkh - withKeyWallet alice do - awaitTxConfirmed txId - logInfo' "Try to spend locked values" - AlwaysFails.spendFromAlwaysFails vhash validator txId + mp <- alwaysMintsPolicy + cs <- liftContractM "Cannot get cs" $ Value.scriptCurrencySymbol mp + tn <- liftContractM "Cannot make token name" + $ byteArrayFromAscii "TheToken" >>= Value.mkTokenName + let asset = Value.singleton cs tn $ BigInt.fromInt 50 - test "ReferenceScripts" do - let - distribution :: InitialUTxOs - distribution = - [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 2_000_000_000 - ] - withWallets distribution \alice -> - withKeyWallet alice ReferenceScripts.contract + validator <- AlwaysFails.alwaysFailsScript + let vhash = validatorHash validator - test - "ReferenceScripts (with StakeKey, testing `mustPayToScriptAddressWithScriptRef`)" - do + txId <- withKeyWallet seed do + logInfo' "Minting asset to Alice" + let + constraints :: Constraints.TxConstraints Void Void + constraints = Constraints.mustMintValue (asset <> asset) + <> mustPayToPubKeyStakeAddress alicePkh aliceStakePkh + ( asset <> + (Value.lovelaceValueOf $ BigInt.fromInt 10_000_000) + ) + <> mustPayToPubKeyStakeAddress alicePkh aliceStakePkh + ( asset <> + (Value.lovelaceValueOf $ BigInt.fromInt 2_000_000_000) + ) + + lookups :: Lookups.ScriptLookups Void + lookups = Lookups.mintingPolicy mp + + ubTx <- liftedE $ Lookups.mkUnbalancedTx lookups constraints + bsTx <- signTransaction =<< liftedE (balanceTx ubTx) + submit bsTx >>= awaitTxConfirmed + + logInfo' "Attempt to lock value" + txId <- AlwaysFails.payToAlwaysFails vhash + awaitTxConfirmed txId + pure txId + + withKeyWallet alice do + awaitTxConfirmed txId + logInfo' "Try to spend locked values" + AlwaysFails.spendFromAlwaysFails vhash validator txId + + group "CIP-33 Reference Scripts" do + test "Use reference scripts for spending" do let - distribution :: InitialUTxOsWithStakeKey - distribution = withStakeKey privateStakeKey + distribution :: InitialUTxOs + distribution = [ BigInt.fromInt 5_000_000 , BigInt.fromInt 2_000_000_000 ] withWallets distribution \alice -> withKeyWallet alice ReferenceScripts.contract - test "ReferenceInputs" do - let - distribution :: InitialUTxOs - distribution = - [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 2_000_000_000 - ] - withWallets distribution \alice -> - withKeyWallet alice ReferenceInputs.contract + test + "Use reference scripts for spending (with Base Address, testing `mustPayToScriptAddressWithScriptRef`)" + do + let + distribution :: InitialUTxOsWithStakeKey + distribution = withStakeKey privateStakeKey + [ BigInt.fromInt 5_000_000 + , BigInt.fromInt 2_000_000_000 + ] + withWallets distribution \alice -> + withKeyWallet alice ReferenceScripts.contract - test "ReferenceInputsAndScripts" do - let - distribution :: InitialUTxOs - distribution = - [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 2_000_000_000 - ] - withWallets distribution \alice -> - withKeyWallet alice ReferenceInputsAndScripts.contract + group "CIP-31 Reference Inputs" do + test "Use reference inputs" do + let + distribution :: InitialUTxOs + distribution = + [ BigInt.fromInt 5_000_000 + , BigInt.fromInt 2_000_000_000 + ] + withWallets distribution \alice -> + withKeyWallet alice ReferenceInputs.contract - test "OneShotMinting" do + test "Use reference inputs and reference scripts at the same time" do + let + distribution :: InitialUTxOs + distribution = + [ BigInt.fromInt 5_000_000 + , BigInt.fromInt 2_000_000_000 + ] + withWallets distribution \alice -> + withKeyWallet alice ReferenceInputsAndScripts.contract + + test "One-Shot Minting example" do let distribution :: InitialUTxOs distribution = @@ -1152,7 +1182,7 @@ suite = do withWallets distribution \alice -> withKeyWallet alice OneShotMinting.contract - test "OneShotMinting PlutusV2" do + test "One-Shot Minting using PlutusV2 scripts" do let distribution :: InitialUTxOs distribution = @@ -1162,17 +1192,7 @@ suite = do withWallets distribution \alice -> withKeyWallet alice OneShotMintingV2.contract - test "PaysWithDatum" do - let - distribution :: InitialUTxOs - distribution = - [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 2_000_000_000 - ] - withWallets distribution \alice -> - withKeyWallet alice PaysWithDatum.contract - - test "Examples.ContractTestUtils" do + test "Check assertion utilities (ContractTestUtils example)" do let initialUtxos :: InitialUTxOs initialUtxos = @@ -1201,7 +1221,7 @@ suite = do , txMetadata: cip25MetadataFixture1 } - test "Examples.BalanceTxConstraints" do + test "Transaction balancer constraints (BalanceTxConstraints example)" do let initialUtxos :: InitialUTxOs initialUtxos = @@ -1215,8 +1235,8 @@ suite = do BalanceTxConstraintsExample.ContractParams { aliceKeyWallet: alice, bobKeyWallet: bob } - group "Evaluation with additional UTxOs and tx chaining" do - test "Examples.TxChaining" $ + group "Evaluation with additional UTxOs and Tx chaining" do + test "Tx chain submits (TxChaining example)" $ let distribution :: InitialUTxOs distribution = [ BigInt.fromInt 2_500_000 ] @@ -1441,7 +1461,7 @@ suite = do awaitTxConfirmed txId0 awaitTxConfirmed txId1 - group "applyArgs" do + group "Application of arguments to parametrized scripts" do test "returns the same script when called without args" do withWallets unit \_ -> do result <- liftContractE $ applyArgs @@ -1468,7 +1488,7 @@ suite = do args result `shouldEqual` (unwrap fullyAppliedScriptFixture) - group "CIP-30 mock" do + group "CIP-30 mock interface" do test "Wallet cleanup" do let distribution :: InitialUTxOs @@ -1508,7 +1528,7 @@ suite = do try (liftEffect $ isWalletAvailable NuFiWallet) >>= flip shouldSatisfy isLeft - test "Collateral selection" do + test "Collateral selection returns UTxO with smaller amount" do let distribution :: InitialUTxOs distribution = @@ -1528,8 +1548,8 @@ suite = do (amount == lovelaceValueOf (BigInt.fromInt 1_000_000_000)) $ throw "Wrong UTxO selected as collateral" Just _ -> do - -- not a bug, but unexpected - throw "More than one UTxO in collateral" + throw $ "More than one UTxO in collateral. " <> + "Not a bug, but unexpected in this test, please update it." test "Get own UTxOs" do let @@ -1559,7 +1579,7 @@ suite = do getWalletAddresses mockAddress `shouldEqual` kwAddress - test "Pkh2Pkh" do + test "Payment key hash to payment key hash Tx" do let distribution :: InitialUTxOs distribution = @@ -1573,7 +1593,7 @@ suite = do stakePkh <- join <<< head <$> ownStakePubKeysHashes pkh2PkhContract pkh stakePkh - test "GetWalletBalance" do + test "getWalletBalance works" do let distribution :: InitialUTxOs distribution = @@ -1592,31 +1612,32 @@ suite = do BigInt.fromInt 3_000_000 ) - test "CIP-30 utilities" do + test "getWalletBalance works (2)" do let distribution :: InitialUTxOs distribution = - [ BigInt.fromInt 1_000_000_000 - , BigInt.fromInt 2_000_000_000 + [ BigInt.fromInt 5_000_000 + , BigInt.fromInt 2_000_000 + , BigInt.fromInt 1_000_000 ] withWallets distribution \alice -> do withCip30Mock alice MockNami do - Cip30.contract + getWalletBalance >>= flip shouldSatisfy + (eq $ Just $ coinToValue $ Coin $ BigInt.fromInt 8_000_000) - test "getWalletBalance" do + test "CIP-30 utilities" do let distribution :: InitialUTxOs distribution = - [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 2_000_000 - , BigInt.fromInt 1_000_000 + [ BigInt.fromInt 1_000_000_000 + , BigInt.fromInt 2_000_000_000 ] withWallets distribution \alice -> do withCip30Mock alice MockNami do - getWalletBalance >>= flip shouldSatisfy - (eq $ Just $ coinToValue $ Coin $ BigInt.fromInt 8_000_000) - group "Plutus Crypto" do - test "ECDSA" do + Cip30.contract + + group "CIP-49 Plutus Crypto Primitives" do + test "ECDSA: a script that checks a signature works" do let distribution :: InitialUTxOs distribution = @@ -1626,7 +1647,7 @@ suite = do withWallets distribution \alice -> do withKeyWallet alice do ECDSA.contract - test "Schnorr" do + test "Schnorr: a script that checks a signature works" do let distribution :: InitialUTxOs distribution = From f8777ac458cb13e8e5a094fa524a12384e346d20 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Mon, 23 Jan 2023 15:49:05 +0300 Subject: [PATCH 310/373] Update test/Plutip/Contract.purs Co-authored-by: Joseph Young --- test/Plutip/Contract.purs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/test/Plutip/Contract.purs b/test/Plutip/Contract.purs index ce08636dd3..cae0e0a668 100644 --- a/test/Plutip/Contract.purs +++ b/test/Plutip/Contract.purs @@ -1461,7 +1461,7 @@ suite = do awaitTxConfirmed txId0 awaitTxConfirmed txId1 - group "Application of arguments to parametrized scripts" do + group "Application of arguments to parameterized scripts" do test "returns the same script when called without args" do withWallets unit \_ -> do result <- liftContractE $ applyArgs From 661300c3b60f2cf776a63cb1aadd928b5a97ccf5 Mon Sep 17 00:00:00 2001 From: Dzmitry Shuysky Date: Tue, 24 Jan 2023 15:30:51 +0100 Subject: [PATCH 311/373] Add tx confirmation delay parameter to BlockfrostBackend --- src/Contract/Config.purs | 2 + src/Internal/Contract/AwaitTxConfirmed.purs | 46 ++++++++++++++----- src/Internal/Contract/QueryBackend.purs | 7 +++ test/Blockfrost.purs | 1 + test/Blockfrost/GenerateFixtures/Helpers.purs | 3 ++ 5 files changed, 47 insertions(+), 12 deletions(-) diff --git a/src/Contract/Config.purs b/src/Contract/Config.purs index a37a1127f9..8e5a5b8aa3 100644 --- a/src/Contract/Config.purs +++ b/src/Contract/Config.purs @@ -33,6 +33,7 @@ import Ctl.Internal.Contract.Hooks (emptyHooks) import Ctl.Internal.Contract.Monad (ContractParams) import Ctl.Internal.Contract.QueryBackend ( QueryBackendParams(CtlBackendParams, BlockfrostBackendParams) + , defaultConfirmTxDelay , mkBlockfrostBackendParams , mkCtlBackendParams ) @@ -89,6 +90,7 @@ testnetBlockfrostDevConfig mbApiKey = { backendParams: BlockfrostBackendParams { blockfrostApiKey: mbApiKey , blockfrostConfig: blockfrostPublicPreviewServerConfig + , confirmTxDelay: defaultConfirmTxDelay } ( Just { ogmiosConfig: defaultOgmiosWsConfig diff --git a/src/Internal/Contract/AwaitTxConfirmed.purs b/src/Internal/Contract/AwaitTxConfirmed.purs index 81cf81879f..076834303f 100644 --- a/src/Internal/Contract/AwaitTxConfirmed.purs +++ b/src/Internal/Contract/AwaitTxConfirmed.purs @@ -6,9 +6,11 @@ module Ctl.Internal.Contract.AwaitTxConfirmed import Prelude +import Control.Monad.Reader.Class (asks) import Control.Parallel (parOneOf) import Ctl.Internal.Contract (getChainTip) import Ctl.Internal.Contract.Monad (Contract) +import Ctl.Internal.Contract.QueryBackend (getBlockfrostBackend) import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.Contract.WaitUntilSlot (waitUntilSlot) import Ctl.Internal.Serialization.Address (Slot) @@ -16,7 +18,7 @@ import Ctl.Internal.Types.BigNum as BigNum import Ctl.Internal.Types.Chain as Chain import Ctl.Internal.Types.Transaction (TransactionHash) import Data.Either (either) -import Data.Maybe (maybe) +import Data.Maybe (Maybe(Just), maybe) import Data.Newtype (unwrap, wrap) import Data.Number (infinity) import Data.Time.Duration (Milliseconds, Seconds(Seconds), fromDuration) @@ -28,9 +30,11 @@ import Effect.Exception (throw) awaitTxConfirmed :: TransactionHash -> Contract Unit awaitTxConfirmed = awaitTxConfirmedWithTimeout (Seconds infinity) +-- NOTE: This function will always fail if the timeout is less than the value +-- of the Blockfrost `confirmTxDelay` parameter. awaitTxConfirmedWithTimeout :: Seconds -> TransactionHash -> Contract Unit awaitTxConfirmedWithTimeout timeoutSeconds txHash = - -- If timeout is infinity, do not use a timeout at all + -- If timeout is infinity, do not use a timeout at all. if unwrap timeoutSeconds == infinity then void findTx else do txFound <- parOneOf [ findTx, waitAndFail ] @@ -39,14 +43,7 @@ awaitTxConfirmedWithTimeout timeoutSeconds txHash = "awaitTxConfirmedWithTimeout: timeout exceeded, Transaction not \ \confirmed" where - -- Try to find the TX indefinitely, with a waiting period between each - -- request - findTx :: Contract Boolean - findTx = - isTxConfirmed txHash >>= \found -> - if found then pure true else liftAff (delay delayTime) *> findTx - - -- Wait until the timeout elapses and return false + -- Wait until the timeout elapses and return false. waitAndFail :: Contract Boolean waitAndFail = do liftAff $ delay $ timeout @@ -55,8 +52,33 @@ awaitTxConfirmedWithTimeout timeoutSeconds txHash = timeout :: Milliseconds timeout = fromDuration timeoutSeconds - delayTime :: Milliseconds - delayTime = wrap 1000.0 + -- Try to find the transaction indefinitely, with a waiting period between + -- each request. + -- + -- If `confirmTxDelay` of `BlockfrostBackend` is set, wait the specified + -- number of seconds after the transaction is confirmed, then check the + -- transaction confirmation status again to handle possible rollbacks. + findTx :: Contract Boolean + findTx = do + confirmTxDelay <- + asks _.backend <#> (getBlockfrostBackend >=> _.confirmTxDelay) + worker (fromDuration <$> confirmTxDelay) false + where + worker :: Maybe Milliseconds -> Boolean -> Contract Boolean + worker confirmTxDelay foundBefore = + isTxConfirmed txHash >>= case _ of + -- Make sure that the transaction has not been rolled back after the + -- confirmation delay. + true | foundBefore -> + pure true + true -> + confirmTxDelay # + maybe (pure true) (\d -> liftAff (delay d) *> worker (Just d) true) + false -> + liftAff (delay delayTime) *> worker confirmTxDelay false + where + delayTime :: Milliseconds + delayTime = wrap 1000.0 awaitTxConfirmedWithTimeoutSlots :: Int -> TransactionHash -> Contract Unit awaitTxConfirmedWithTimeoutSlots timeoutSlots txHash = diff --git a/src/Internal/Contract/QueryBackend.purs b/src/Internal/Contract/QueryBackend.purs index 963de6b574..711a7154a9 100644 --- a/src/Internal/Contract/QueryBackend.purs +++ b/src/Internal/Contract/QueryBackend.purs @@ -5,6 +5,7 @@ module Ctl.Internal.Contract.QueryBackend , CtlBackendParams , QueryBackend(BlockfrostBackend, CtlBackend) , QueryBackendParams(BlockfrostBackendParams, CtlBackendParams) + , defaultConfirmTxDelay , getBlockfrostBackend , getCtlBackend , mkBlockfrostBackendParams @@ -16,6 +17,7 @@ import Prelude import Ctl.Internal.QueryM (OgmiosWebSocket) import Ctl.Internal.ServerConfig (ServerConfig) import Data.Maybe (Maybe(Just, Nothing)) +import Data.Time.Duration (Seconds(Seconds)) -------------------------------------------------------------------------------- -- QueryBackend @@ -36,6 +38,7 @@ type CtlBackend = type BlockfrostBackend = { blockfrostConfig :: ServerConfig , blockfrostApiKey :: Maybe String + , confirmTxDelay :: Maybe Seconds } getCtlBackend :: QueryBackend -> Maybe CtlBackend @@ -62,8 +65,12 @@ type CtlBackendParams = type BlockfrostBackendParams = { blockfrostConfig :: ServerConfig , blockfrostApiKey :: Maybe String + , confirmTxDelay :: Maybe Seconds } +defaultConfirmTxDelay :: Maybe Seconds +defaultConfirmTxDelay = Just $ Seconds 30.0 + mkCtlBackendParams :: CtlBackendParams -> QueryBackendParams mkCtlBackendParams = flip CtlBackendParams Nothing diff --git a/test/Blockfrost.purs b/test/Blockfrost.purs index bb38bd52b0..c2efa957dd 100644 --- a/test/Blockfrost.purs +++ b/test/Blockfrost.purs @@ -56,6 +56,7 @@ main = do ( testPlan { blockfrostConfig: blockfrostPublicPreviewServerConfig , blockfrostApiKey: Just apiKey + , confirmTxDelay: Nothing } ) diff --git a/test/Blockfrost/GenerateFixtures/Helpers.purs b/test/Blockfrost/GenerateFixtures/Helpers.purs index 9dc8321dc3..a5effdce4d 100644 --- a/test/Blockfrost/GenerateFixtures/Helpers.purs +++ b/test/Blockfrost/GenerateFixtures/Helpers.purs @@ -21,6 +21,7 @@ import Contract.Config ) import Ctl.Internal.Contract.QueryBackend ( BlockfrostBackend + , defaultConfirmTxDelay , mkBlockfrostBackendParams ) import Ctl.Internal.Hashing (md5HashHex) @@ -39,6 +40,7 @@ blockfrostBackend = do pure { blockfrostConfig , blockfrostApiKey: Just blockfrostApiKey + , confirmTxDelay: defaultConfirmTxDelay } contractParams :: Effect ContractParams @@ -51,6 +53,7 @@ contractParams = do mkBlockfrostBackendParams { blockfrostConfig , blockfrostApiKey: Just blockfrostApiKey + , confirmTxDelay: defaultConfirmTxDelay } , logLevel = Info , walletSpec = Just $ UseKeys (PrivatePaymentKeyFile skeyFilepath) Nothing From 9ba6768867f524c1396a4b817794bc794a1259f8 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Tue, 24 Jan 2023 22:12:19 +0000 Subject: [PATCH 312/373] Retry fund return --- src/Internal/Plutip/Server.purs | 48 ++++++++++++--------------------- 1 file changed, 17 insertions(+), 31 deletions(-) diff --git a/src/Internal/Plutip/Server.purs b/src/Internal/Plutip/Server.purs index fa6b469187..cef162b260 100644 --- a/src/Internal/Plutip/Server.purs +++ b/src/Internal/Plutip/Server.purs @@ -230,7 +230,12 @@ testContractsInEnv params backup = mapTest \(PlutipTest runPlutipTest) -> ( backupWallets env walletsArray *> fundWallets env walletsArray distrArray ) - (returnFunds env walletsArray) + -- Retry fund returning until success or timeout. Submission will fail if + -- the node has seen the wallets utxos being spent previously, so retrying + -- will allow the wallets utxos to eventually represent a spendable set + ( \funds -> recovering returnFundsRetryPolicy ([ \_ _ -> pure true ]) + \_ -> returnFunds env walletsArray funds + ) \_ -> runContract where pureProxy :: forall (a :: Type). a -> Proxy a @@ -265,32 +270,19 @@ testContractsInEnv params backup = mapTest \(PlutipTest runPlutipTest) -> -- Use log so we can see, regardless of suppression log $ joinWith " " [ "Sent" - , show fundTotal + , BigInt.toString fundTotal , "lovelace to test wallets" ] pure fundTotal + returnFundsRetryPolicy :: RetryPolicy + returnFundsRetryPolicy = limitRetriesByCumulativeDelay + (Milliseconds 30_000.00) + (constantDelay $ Milliseconds 2_000.0) + returnFunds :: ContractEnv -> Array KeyWallet -> BigInt -> Aff Unit returnFunds env walletsArray fundTotal = runContractInEnv env do logTrace' "Returning wallet funds" - log "here1" - - -- We could delay until there's a delta? - let - go 0 = pure unit - go n = do - utxos <- Map.unions <<< fold <$> for walletsArray - (flip withKeyWallet getWalletAddresses >=> traverse utxosAt) - let - v = Array.foldr - (\txorf acc -> acc + valueToCoin' (txorf ^. _output ^. _amount)) - zero - (Array.fromFoldable $ Map.values utxos) - log $ show v - liftAff $ delay $ wrap $ 2000.0 - go (n - 1) - - go 10 utxos <- Map.unions <<< fold <$> for walletsArray (flip withKeyWallet getWalletAddresses >=> traverse utxosAt) @@ -298,26 +290,20 @@ testContractsInEnv params backup = mapTest \(PlutipTest runPlutipTest) -> pkhs <- fold <$> for walletsArray (flip withKeyWallet ownPaymentPubKeysHashes) - log "here2" let constraints = flip foldMap (Map.keys utxos) mustSpendPubKeyOutput <> foldMap mustBeSignedBy pkhs lookups = unspentOutputs utxos unbalancedTx <- liftedE $ mkUnbalancedTx (lookups :: _ Void) constraints - log "here3" balancedTx <- liftedE $ balanceTx unbalancedTx - log "here4" balancedSignedTx <- Array.foldM (\tx wallet -> withKeyWallet wallet $ signTransaction tx) (wrap $ unwrap balancedTx) walletsArray - log "here5" - -- We failed to submit - txHash <- try $ submit balancedSignedTx - log "here6" - either (log <<< show) awaitTxConfirmed txHash - log "here7" + + txHash <- submit balancedSignedTx + awaitTxConfirmed txHash let (refundTotal :: BigInt) = Array.foldr @@ -327,9 +313,9 @@ testContractsInEnv params backup = mapTest \(PlutipTest runPlutipTest) -> log $ joinWith " " [ "Refunded" - , show refundTotal + , BigInt.toString refundTotal , "of" - , show fundTotal + , BigInt.toString fundTotal , "lovelace from test wallets" ] From 4c9a0613c3a73ba66562ac79a9084711541cac7f Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Wed, 25 Jan 2023 17:03:01 +0400 Subject: [PATCH 313/373] Fix the build --- src/Contract/Transaction.purs | 1 - test/Plutip/Contract.purs | 6 ++---- 2 files changed, 2 insertions(+), 5 deletions(-) diff --git a/src/Contract/Transaction.purs b/src/Contract/Transaction.purs index bb3e5f3ede..75b544388b 100644 --- a/src/Contract/Transaction.purs +++ b/src/Contract/Transaction.purs @@ -75,7 +75,6 @@ import Ctl.Internal.BalanceTx.Error , CollateralReturnError , CollateralReturnMinAdaValueCalcError , ExUnitsEvaluationFailed - , InsufficientTxInputs , InsufficientUtxoBalanceToCoverAsset , ReindexRedeemersError , UtxoLookupFailedFor diff --git a/test/Plutip/Contract.purs b/test/Plutip/Contract.purs index 463e98f65b..1435663207 100644 --- a/test/Plutip/Contract.purs +++ b/test/Plutip/Contract.purs @@ -945,10 +945,8 @@ suite = do let datum42 = Datum $ Integer $ BigInt.fromInt 42 - - datum42Hash <- liftM (error "Failed to hash datum") $ datumHash datum42 - datum42Lookup <- liftM (error "Could not make lookup") $ Lookups.datum - datum42 + datum42Hash = datumHash datum42 + datum42Lookup = Lookups.datum datum42 let transactionId :: TransactionHash From bf8977df7e5cbc9fab1da51754d9de9ce9a2369f Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Wed, 25 Jan 2023 13:40:07 +0000 Subject: [PATCH 314/373] Simplify fold --- src/Internal/Plutip/Server.purs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Internal/Plutip/Server.purs b/src/Internal/Plutip/Server.purs index cef162b260..9ccd223d83 100644 --- a/src/Internal/Plutip/Server.purs +++ b/src/Internal/Plutip/Server.purs @@ -266,7 +266,7 @@ testContractsInEnv params backup = mapTest \(PlutipTest runPlutipTest) -> txHash <- submitTxFromConstraints (mempty :: _ Void) constraints awaitTxConfirmed txHash - let fundTotal = Array.foldr (flip (Array.foldr (+))) zero distrArray + let fundTotal = Array.foldr (+) zero $ join distrArray -- Use log so we can see, regardless of suppression log $ joinWith " " [ "Sent" From 6d8b4c54d5007686b00791b92385b8e8a05fed11 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Wed, 25 Jan 2023 13:46:38 +0000 Subject: [PATCH 315/373] foldl --- src/Internal/Plutip/Server.purs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Internal/Plutip/Server.purs b/src/Internal/Plutip/Server.purs index 9ccd223d83..b5581d0cd8 100644 --- a/src/Internal/Plutip/Server.purs +++ b/src/Internal/Plutip/Server.purs @@ -266,7 +266,7 @@ testContractsInEnv params backup = mapTest \(PlutipTest runPlutipTest) -> txHash <- submitTxFromConstraints (mempty :: _ Void) constraints awaitTxConfirmed txHash - let fundTotal = Array.foldr (+) zero $ join distrArray + let fundTotal = Array.foldl (+) zero $ join distrArray -- Use log so we can see, regardless of suppression log $ joinWith " " [ "Sent" @@ -306,8 +306,8 @@ testContractsInEnv params backup = mapTest \(PlutipTest runPlutipTest) -> awaitTxConfirmed txHash let - (refundTotal :: BigInt) = Array.foldr - (\txorf acc -> acc + valueToCoin' (txorf ^. _output ^. _amount)) + (refundTotal :: BigInt) = Array.foldl + (\acc txorf -> acc + valueToCoin' (txorf ^. _output ^. _amount)) zero (Array.fromFoldable $ Map.values utxos) @@ -675,7 +675,7 @@ startPlutipCluster cfg keysToGenerate = do ourInitialUtxos :: InitialUTxODistribution -> InitialUTxOs ourInitialUtxos utxoDistribution = let - total = Array.foldr (sum >>> add) zero utxoDistribution + total = Array.foldl (sum >>> add) zero utxoDistribution in [ -- Take the total value of the utxos and add some extra on top -- of it to cover the possible transaction fees. Also make sure From b015e849f0e7c99a5baa5bb0937dca617811a121 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Wed, 25 Jan 2023 13:56:52 +0000 Subject: [PATCH 316/373] Remove dev blockfrost config --- src/Contract/Config.purs | 28 ---------------------------- test/Blockfrost/Contract.purs | 24 +++++++++++++++--------- 2 files changed, 15 insertions(+), 37 deletions(-) diff --git a/src/Contract/Config.purs b/src/Contract/Config.purs index a37a1127f9..8e0173d18d 100644 --- a/src/Contract/Config.purs +++ b/src/Contract/Config.purs @@ -1,7 +1,6 @@ -- | Exposes some pre-defined Contract configurations. Re-exports all modules needed to modify `ContractParams`. module Contract.Config ( testnetConfig - , testnetBlockfrostDevConfig , testnetNamiConfig , testnetGeroConfig , testnetFlintConfig @@ -66,7 +65,6 @@ import Ctl.Internal.Wallet.Spec import Data.Log.Level (LogLevel(Trace, Debug, Info, Warn, Error)) import Data.Log.Message (Message) import Data.Maybe (Maybe(Just, Nothing)) -import Data.UInt as UInt testnetConfig :: ContractParams testnetConfig = @@ -82,32 +80,6 @@ testnetConfig = , hooks: emptyHooks } --- | Blockfrost public preview with CTL as backup --- | Does not use the Kupo webpack proxy -testnetBlockfrostDevConfig :: Maybe String -> ContractParams -testnetBlockfrostDevConfig mbApiKey = - { backendParams: BlockfrostBackendParams - { blockfrostApiKey: mbApiKey - , blockfrostConfig: blockfrostPublicPreviewServerConfig - } - ( Just - { ogmiosConfig: defaultOgmiosWsConfig - , kupoConfig: - { port: UInt.fromInt 1442 - , host: "localhost" - , secure: false - , path: Nothing - } - } - ) - , networkId: TestnetId - , walletSpec: Nothing - , logLevel: Trace - , customLogger: Nothing - , suppressLogs: false - , hooks: emptyHooks - } - testnetNamiConfig :: ContractParams testnetNamiConfig = testnetConfig { walletSpec = Just ConnectToNami } diff --git a/test/Blockfrost/Contract.purs b/test/Blockfrost/Contract.purs index 1cfbf92a61..8b5626790c 100644 --- a/test/Blockfrost/Contract.purs +++ b/test/Blockfrost/Contract.purs @@ -1,13 +1,16 @@ -- | Module to run `Test.Ctl.Plutip.Contract`s suite without Plutip, using --- | an already running instance of Blockfrost. +-- | an already running instance of Blockfrost (preview). module Test.Ctl.Blockfrost.Contract (main, suite) where import Prelude import Contract.Config ( PrivatePaymentKeySource(PrivatePaymentKeyFile) + , ServerConfig , WalletSpec(UseKeys) - , testnetBlockfrostDevConfig + , blockfrostPublicPreviewServerConfig + , mkBlockfrostBackendParams + , testnetConfig ) import Contract.Monad (launchAff_) import Contract.Test.Mote (TestPlanM, interpretWithConfig) @@ -22,18 +25,17 @@ import Node.Process (argv, exit) import Test.Ctl.Plutip.Contract as Plutip import Test.Spec.Runner (defaultConfig) --- TODO Remove dev config - -- Run with `spago test --main Test.Ctl.Blockfrost.Contract --exec-args "BLOCKFROST_API_KEY PRIVATE_PAYMENT_FILE BACKUP_KEYS_DIR"` main :: Effect Unit main = do + let blockfrostConfig = blockfrostPublicPreviewServerConfig argv >>= case _ of [ _, apiKey, privateKey, backupKeys ] -> launchAff_ do interpretWithConfig defaultConfig { timeout = Just $ convertDuration $ 5.0 # Minutes } - (suite apiKey privateKey backupKeys) + (suite blockfrostConfig apiKey privateKey backupKeys) _ -> do log $ joinWith "\n" [ "Wrong number of parameters provided." @@ -46,16 +48,20 @@ main = do ] exit 1 -suite :: String -> String -> String -> TestPlanM (Aff Unit) Unit -suite apiKey privateKey backupKeys = do +suite :: ServerConfig -> String -> String -> String -> TestPlanM (Aff Unit) Unit +suite blockfrostConfig apiKey privateKey backupKeys = do testContractsInEnv config backupKeys Plutip.suite where config = - (testnetBlockfrostDevConfig (Just apiKey)) - { walletSpec = Just $ UseKeys + testnetConfig + { backendParams = mkBlockfrostBackendParams + { blockfrostConfig + , blockfrostApiKey: Just apiKey + } + , walletSpec = Just $ UseKeys (PrivatePaymentKeyFile privateKey) Nothing , suppressLogs = true From 09bd94f110bef5e9e8fbc7b555c1e56ddb341c4c Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Wed, 25 Jan 2023 14:55:19 +0000 Subject: [PATCH 317/373] Add submitE back --- src/Contract/Transaction.purs | 15 +++++++++++++-- 1 file changed, 13 insertions(+), 2 deletions(-) diff --git a/src/Contract/Transaction.purs b/src/Contract/Transaction.purs index a5907423da..a54f8a2011 100644 --- a/src/Contract/Transaction.purs +++ b/src/Contract/Transaction.purs @@ -30,6 +30,7 @@ module Contract.Transaction , reindexSpentScriptRedeemers , signTransaction , submit + , submitE , submitTxFromConstraints , submitTxFromConstraintsReturningFee , withBalancedTx @@ -41,6 +42,7 @@ module Contract.Transaction import Prelude import Aeson (class EncodeAeson) +import Contract.ClientError (ClientError) import Contract.Metadata (GeneralTransactionMetadata) import Contract.Monad ( Contract @@ -295,11 +297,20 @@ submit :: BalancedSignedTransaction -> Contract TransactionHash submit tx = do - queryHandle <- getQueryHandle - eiTxHash <- liftAff $ queryHandle.submitTx $ unwrap tx + eiTxHash <- submitE tx liftEither $ flip lmap eiTxHash \err -> error $ "Failed to submit tx:\n" <> show err +-- | Submits a `BalancedSignedTransaction`, which is the output of +-- | `signTransaction`. Preserves the errors returned by the backend in +-- | the case they need to be inspected. +submitE + :: BalancedSignedTransaction + -> Contract (Either ClientError TransactionHash) +submitE tx = do + queryHandle <- getQueryHandle + liftAff $ queryHandle.submitTx $ unwrap tx + -- | Calculate the minimum transaction fee. calculateMinFee :: Transaction From d65026a0fde8ae5a6db524e12545a3f83a843c2b Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Wed, 25 Jan 2023 14:59:12 +0000 Subject: [PATCH 318/373] Add comment to additionaUtxos tests --- test/Plutip/Contract.purs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/test/Plutip/Contract.purs b/test/Plutip/Contract.purs index 53f89956a4..5ff89443da 100644 --- a/test/Plutip/Contract.purs +++ b/test/Plutip/Contract.purs @@ -1280,7 +1280,10 @@ suite = do BalanceTxConstraintsExample.ContractParams { aliceKeyWallet: alice, bobKeyWallet: bob } - skip $ group "Evaluation with additional UTxOs and tx chaining" do + -- FIXME These tests never require additionalUtxos to succeed. They do + -- not invoke a script. + -- https://github.com/Plutonomicon/cardano-transaction-lib/issues/1392 + group "Evaluation with additional UTxOs and tx chaining" do test "Examples.TxChaining" $ let distribution :: InitialUTxOs From c4ad2efa8bebaca52c2028650f8cf225ae5e6480 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Wed, 25 Jan 2023 15:04:44 +0000 Subject: [PATCH 319/373] Fix error and warning --- src/Internal/Plutip/Server.purs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Internal/Plutip/Server.purs b/src/Internal/Plutip/Server.purs index b5581d0cd8..44e95c74bd 100644 --- a/src/Internal/Plutip/Server.purs +++ b/src/Internal/Plutip/Server.purs @@ -136,7 +136,7 @@ import Data.Tuple (fst, snd) import Data.Tuple.Nested (type (/\), (/\)) import Data.UInt (UInt) import Data.UInt as UInt -import Effect.Aff (Aff, Milliseconds(Milliseconds), delay, try) +import Effect.Aff (Aff, Milliseconds(Milliseconds), try) import Effect.Aff (bracket) as Aff import Effect.Aff.Class (liftAff) import Effect.Aff.Retry @@ -675,7 +675,7 @@ startPlutipCluster cfg keysToGenerate = do ourInitialUtxos :: InitialUTxODistribution -> InitialUTxOs ourInitialUtxos utxoDistribution = let - total = Array.foldl (sum >>> add) zero utxoDistribution + total = Array.foldr (sum >>> add) zero utxoDistribution in [ -- Take the total value of the utxos and add some extra on top -- of it to cover the possible transaction fees. Also make sure From 5a9d94f611dcd381050f4fbe3f6fb177d6fb0fd8 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Wed, 25 Jan 2023 20:50:49 +0400 Subject: [PATCH 320/373] Remove the use of HashMap, replace with Map (due to a bundler bug) --- spago.dhall | 1 - src/Internal/Cardano/Types/Value.purs | 5 --- src/Internal/CoinSelection/UtxoIndex.purs | 54 ++++++++++------------- src/Internal/Types/ByteArray.purs | 4 -- src/Internal/Types/CborBytes.purs | 2 - src/Internal/Types/RawBytes.purs | 2 - src/Internal/Types/TokenName.purs | 2 - 7 files changed, 24 insertions(+), 46 deletions(-) diff --git a/spago.dhall b/spago.dhall index 699edd193c..daec95099b 100644 --- a/spago.dhall +++ b/spago.dhall @@ -88,7 +88,6 @@ You can edit this file as you like. , "uint" , "undefined" , "unfoldable" - , "unordered-collections" , "untagged-union" , "variant" ] diff --git a/src/Internal/Cardano/Types/Value.purs b/src/Internal/Cardano/Types/Value.purs index 8d29f659c8..4553bd6764 100644 --- a/src/Internal/Cardano/Types/Value.purs +++ b/src/Internal/Cardano/Types/Value.purs @@ -106,7 +106,6 @@ import Data.Foldable (any, fold, foldl, length) import Data.FoldableWithIndex (foldrWithIndex) import Data.Function (on) import Data.Generic.Rep (class Generic) -import Data.Hashable (class Hashable, hash) import Data.Int (ceil) as Int import Data.Lattice (class JoinSemilattice, class MeetSemilattice, join, meet) import Data.List (List(Nil), all, (:)) @@ -224,7 +223,6 @@ newtype CurrencySymbol = CurrencySymbol ByteArray derive newtype instance Eq CurrencySymbol derive newtype instance FromData CurrencySymbol derive newtype instance FromMetadata CurrencySymbol -derive newtype instance Hashable CurrencySymbol derive newtype instance Ord CurrencySymbol derive newtype instance ToData CurrencySymbol derive newtype instance ToMetadata CurrencySymbol @@ -541,9 +539,6 @@ instance Arbitrary AssetClass where instance Show AssetClass where show = genericShow -instance Hashable AssetClass where - hash (AssetClass cs tn) = hash (cs /\ tn) - assetToValue :: AssetClass -> BigInt -> Value assetToValue (AssetClass cs tn) quantity = mkValue mempty (mkSingletonNonAdaAsset cs tn quantity) diff --git a/src/Internal/CoinSelection/UtxoIndex.purs b/src/Internal/CoinSelection/UtxoIndex.purs index 6fdb9ae1f9..cbfe56a707 100644 --- a/src/Internal/CoinSelection/UtxoIndex.purs +++ b/src/Internal/CoinSelection/UtxoIndex.purs @@ -44,9 +44,6 @@ import Data.Foldable (all, length) as Foldable import Data.Foldable (foldl) import Data.Function (on) import Data.Generic.Rep (class Generic) -import Data.HashMap (HashMap) -import Data.HashMap (alter, empty, lookup, toArrayBy, update) as HashMap -import Data.Hashable (class Hashable, hash) import Data.Lens (Lens') import Data.Lens.Getter (view, (^.)) import Data.Lens.Iso (Iso', iso) @@ -55,7 +52,8 @@ import Data.Lens.Setter ((%~)) import Data.List (List) import Data.Map (Map) import Data.Map - ( delete + ( alter + , delete , empty , insert , intersection @@ -64,13 +62,13 @@ import Data.Map , singleton , size , toUnfoldable + , update ) as Map import Data.Maybe (Maybe(Just, Nothing), fromMaybe, maybe) import Data.Newtype (unwrap) import Data.Set (Set) import Data.Set (fromFoldable, toUnfoldable) as Set import Data.Show.Generic (genericShow) -import Data.Tuple (Tuple(Tuple)) import Data.Tuple.Nested (type (/\), (/\)) import Effect.Class (class MonadEffect, liftEffect) import Effect.Random (randomInt) as Random @@ -88,11 +86,11 @@ import Type.Proxy (Proxy(Proxy)) -- | Taken from cardano-wallet: -- | https://github.com/input-output-hk/cardano-wallet/blob/791541da69b9b3f434bb9ead43de406cc18b0373/lib/primitive/lib/Cardano/Wallet/Primitive/Types/UTxOIndex/Internal.hs#L176 type UtxoIndexRec = - { indexAnyWith :: HashMap Asset UtxoMap + { indexAnyWith :: Map Asset UtxoMap -- ^ An index of all utxos that contain the given asset. - , indexSingletons :: HashMap Asset UtxoMap + , indexSingletons :: Map Asset UtxoMap -- ^ An index of all utxos that contain the given asset and no other assets. - , indexPairs :: HashMap Asset UtxoMap + , indexPairs :: Map Asset UtxoMap -- ^ An index of all utxos that contain the given asset and exactly one -- other asset. , utxos :: UtxoMap @@ -115,14 +113,11 @@ data Asset = AssetLovelace | Asset AssetClass derive instance Generic Asset _ derive instance Eq Asset +derive instance Ord Asset instance Show Asset where show = genericShow -instance Hashable Asset where - hash AssetLovelace = hash (Nothing :: Maybe AssetClass) - hash (Asset asset) = hash (Just asset) - instance Arbitrary Asset where arbitrary = oneOf $ cons' (pure AssetLovelace) [ Asset <$> arbitrary ] @@ -145,9 +140,9 @@ valueHasAsset amount (Asset asset) = -- | An index with no entries. emptyUtxoIndex :: UtxoIndex emptyUtxoIndex = UtxoIndex - { indexAnyWith: HashMap.empty - , indexSingletons: HashMap.empty - , indexPairs: HashMap.empty + { indexAnyWith: Map.empty + , indexSingletons: Map.empty + , indexPairs: Map.empty , utxos: Map.empty } @@ -186,9 +181,9 @@ utxoIndexInsertEntry :: TxUnspentOutput -> UtxoIndex -> UtxoIndex utxoIndexInsertEntry (oref /\ out) = (_utxos %~ Map.insert oref out) <<< updateUtxoIndex out insertEntry where - insertEntry :: Asset -> HashMap Asset UtxoMap -> HashMap Asset UtxoMap + insertEntry :: Asset -> Map Asset UtxoMap -> Map Asset UtxoMap insertEntry = - HashMap.alter + Map.alter (Just <<< maybe (Map.singleton oref out) (Map.insert oref out)) -- | Taken from cardano-wallet: @@ -197,12 +192,12 @@ utxoIndexDeleteEntry :: TxUnspentOutput -> UtxoIndex -> UtxoIndex utxoIndexDeleteEntry (inp /\ out) = (_utxos %~ Map.delete inp) <<< updateUtxoIndex out deleteEntry where - deleteEntry :: Asset -> HashMap Asset UtxoMap -> HashMap Asset UtxoMap - deleteEntry = HashMap.update (Just <<< Map.delete inp) + deleteEntry :: Asset -> Map Asset UtxoMap -> Map Asset UtxoMap + deleteEntry = Map.update (Just <<< Map.delete inp) updateUtxoIndex :: TransactionOutput - -> (Asset -> HashMap Asset UtxoMap -> HashMap Asset UtxoMap) + -> (Asset -> Map Asset UtxoMap -> Map Asset UtxoMap) -> UtxoIndex -> UtxoIndex updateUtxoIndex out manageEntry = @@ -291,9 +286,9 @@ selectRandomWithFilter utxoIndex selectionFilter = SelectAnyWith asset -> asset `lookupWith` _indexAnyWith where - lookupWith :: Asset -> Lens' UtxoIndex (HashMap Asset UtxoMap) -> UtxoMap + lookupWith :: Asset -> Lens' UtxoIndex (Map Asset UtxoMap) -> UtxoMap lookupWith asset getter = - fromMaybe Map.empty $ HashMap.lookup asset (utxoIndex ^. getter) + fromMaybe Map.empty $ Map.lookup asset (utxoIndex ^. getter) -------------------------------------------------------------------------------- -- Lenses for accessing `UtxoIndex` fields @@ -302,13 +297,13 @@ selectRandomWithFilter utxoIndex selectionFilter = _UtxoIndex :: Iso' UtxoIndex UtxoIndexRec _UtxoIndex = iso (\(UtxoIndex rec) -> rec) UtxoIndex -_indexAnyWith :: Lens' UtxoIndex (HashMap Asset UtxoMap) +_indexAnyWith :: Lens' UtxoIndex (Map Asset UtxoMap) _indexAnyWith = _UtxoIndex <<< prop (Proxy :: Proxy "indexAnyWith") -_indexSingletons :: Lens' UtxoIndex (HashMap Asset UtxoMap) +_indexSingletons :: Lens' UtxoIndex (Map Asset UtxoMap) _indexSingletons = _UtxoIndex <<< prop (Proxy :: Proxy "indexSingletons") -_indexPairs :: Lens' UtxoIndex (HashMap Asset UtxoMap) +_indexPairs :: Lens' UtxoIndex (Map Asset UtxoMap) _indexPairs = _UtxoIndex <<< prop (Proxy :: Proxy "indexPairs") _utxos :: Lens' UtxoIndex UtxoMap @@ -392,10 +387,10 @@ checkUtxoIndexComplete utxoIndex = (_indexAnyWith `hasEntryForAsset` Asset asset) where hasEntryForAsset - :: Lens' UtxoIndex (HashMap Asset UtxoMap) -> Asset -> Boolean + :: Lens' UtxoIndex (Map Asset UtxoMap) -> Asset -> Boolean hasEntryForAsset getter asset = maybe false (eq out) $ - (Map.lookup oref =<< HashMap.lookup asset (utxoIndex ^. getter)) + (Map.lookup oref =<< Map.lookup asset (utxoIndex ^. getter)) -- | Check that every indexed entry is required by some entry in the map of all -- | utxos. @@ -409,12 +404,12 @@ checkUtxoIndexMinimal utxoIndex = && _indexAnyWith `testEntriesWith` txOutputHasAsset where testEntriesWith - :: Lens' UtxoIndex (HashMap Asset UtxoMap) + :: Lens' UtxoIndex (Map Asset UtxoMap) -> (TransactionOutput -> Asset -> Boolean) -> Boolean testEntriesWith subset test' = utxoIndex ^. subset - # HashMap.toArrayBy Tuple + # Map.toUnfoldable # Array.all \(asset /\ utxos) -> Array.all (entryMatches (flip test' asset)) (Map.toUnfoldable utxos) where @@ -447,4 +442,3 @@ checkUtxoIndexMinimal utxoIndex = txOutputAssetCount :: TransactionOutput -> BigInt txOutputAssetCount = Foldable.length <<< Value.valueAssets <<< _.amount <<< unwrap - diff --git a/src/Internal/Types/ByteArray.purs b/src/Internal/Types/ByteArray.purs index 9a7887b1d6..565d0e2fc7 100644 --- a/src/Internal/Types/ByteArray.purs +++ b/src/Internal/Types/ByteArray.purs @@ -27,7 +27,6 @@ import Aeson import Data.ArrayBuffer.Types (Uint8Array) import Data.Char (toCharCode) import Data.Either (Either(Left), note) -import Data.Hashable (class Hashable, hash) import Data.Maybe (Maybe(Just, Nothing)) import Data.Newtype (class Newtype) import Data.String.CodeUnits (toCharArray) @@ -59,9 +58,6 @@ instance Ord ByteArray where LT -> 1 GT -> -1 -instance Hashable ByteArray where - hash = hash <<< byteArrayToIntArray - instance Semigroup ByteArray where append = concat_ diff --git a/src/Internal/Types/CborBytes.purs b/src/Internal/Types/CborBytes.purs index f66d3f44be..4d69c1d5e3 100644 --- a/src/Internal/Types/CborBytes.purs +++ b/src/Internal/Types/CborBytes.purs @@ -22,7 +22,6 @@ import Ctl.Internal.Metadata.ToMetadata (class ToMetadata) import Ctl.Internal.Types.ByteArray (ByteArray) import Ctl.Internal.Types.ByteArray as ByteArray import Ctl.Internal.Types.RawBytes (RawBytes) -import Data.Hashable (class Hashable) import Data.Maybe (Maybe) import Data.Newtype (class Newtype, unwrap, wrap) import Test.QuickCheck.Arbitrary (class Arbitrary) @@ -38,7 +37,6 @@ derive instance Newtype CborBytes _ derive newtype instance Eq CborBytes derive newtype instance Ord CborBytes -derive newtype instance Hashable CborBytes derive newtype instance Semigroup CborBytes derive newtype instance Monoid CborBytes derive newtype instance EncodeAeson CborBytes diff --git a/src/Internal/Types/RawBytes.purs b/src/Internal/Types/RawBytes.purs index dc0235fb4b..9be49b1c37 100644 --- a/src/Internal/Types/RawBytes.purs +++ b/src/Internal/Types/RawBytes.purs @@ -21,7 +21,6 @@ import Ctl.Internal.Metadata.FromMetadata (class FromMetadata) import Ctl.Internal.Metadata.ToMetadata (class ToMetadata) import Ctl.Internal.Types.ByteArray (ByteArray) import Ctl.Internal.Types.ByteArray as BytesArray -import Data.Hashable (class Hashable) import Data.Maybe (Maybe) import Data.Newtype (class Newtype, unwrap, wrap) import Test.QuickCheck.Arbitrary (class Arbitrary) @@ -36,7 +35,6 @@ derive instance Newtype RawBytes _ derive newtype instance Eq RawBytes derive newtype instance Ord RawBytes -derive newtype instance Hashable RawBytes derive newtype instance Semigroup RawBytes derive newtype instance Monoid RawBytes derive newtype instance EncodeAeson RawBytes diff --git a/src/Internal/Types/TokenName.purs b/src/Internal/Types/TokenName.purs index 402b2acc61..a68dfe869a 100644 --- a/src/Internal/Types/TokenName.purs +++ b/src/Internal/Types/TokenName.purs @@ -30,7 +30,6 @@ import Data.ArrayBuffer.Types (Uint8Array) import Data.BigInt (BigInt) import Data.Bitraversable (ltraverse) import Data.Either (Either(Right, Left), either, note) -import Data.Hashable (class Hashable) import Data.Map (Map) import Data.Map (fromFoldable) as Map import Data.Maybe (Maybe(Nothing), fromJust) @@ -48,7 +47,6 @@ newtype TokenName = TokenName RawBytes derive newtype instance Eq TokenName derive newtype instance FromData TokenName derive newtype instance FromMetadata TokenName -derive newtype instance Hashable TokenName derive newtype instance ToMetadata TokenName derive newtype instance Ord TokenName derive newtype instance ToData TokenName From d0634e61397007f550d5092bd7729d76c3891720 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Wed, 25 Jan 2023 21:17:20 +0400 Subject: [PATCH 321/373] Update easy-purescript-nix version to 0.14.9 --- flake.lock | 22 +++++++++++----------- nix/default.nix | 2 +- 2 files changed, 12 insertions(+), 12 deletions(-) diff --git a/flake.lock b/flake.lock index 97fc0afafe..41a2b68876 100644 --- a/flake.lock +++ b/flake.lock @@ -1309,11 +1309,11 @@ "cardano-configurations": { "flake": false, "locked": { - "lastModified": 1670549339, + "lastModified": 1671845278, "narHash": "sha256-oOycxAu9kARfyUvkdjeq80Em7b+vP9XsBii8836f9yQ=", "owner": "input-output-hk", "repo": "cardano-configurations", - "rev": "c1b2b9a426a78bb5812898368714631900299701", + "rev": "36a75a920de312519c3a9086061daccb997f9cd0", "type": "github" }, "original": { @@ -2515,11 +2515,11 @@ "flake-compat": { "flake": false, "locked": { - "lastModified": 1668681692, - "narHash": "sha256-Ht91NGdewz8IQLtWZ9LCeNXMSXHUss+9COoqu6JLmXU=", + "lastModified": 1673956053, + "narHash": "sha256-4gtG9iQuiKITOjNQQeQIpoIB6b16fm+504Ch3sNKLd8=", "owner": "edolstra", "repo": "flake-compat", - "rev": "009399224d5e398d03b22badca40a37ac85412a1", + "rev": "35bb57c0c8d8b62bbfd284272c928ceb64ddbde9", "type": "github" }, "original": { @@ -5101,11 +5101,11 @@ "nixpkgs": "nixpkgs" }, "locked": { - "lastModified": 1670489000, - "narHash": "sha256-JewWjqVJSt+7eZQT9bGdhlSsS9dmsSKsMzK9g11tcLU=", + "lastModified": 1674063615, + "narHash": "sha256-xz/+7zO/O+2XrnxoFOjyEc72Sdy2ieQLpDq78XG15oI=", "owner": "input-output-hk", "repo": "iohk-nix", - "rev": "61510bb482eaca8cb7d61f40f5d375d95ea1fbf7", + "rev": "ccd5bf7d8168a0452d9ec504ea1b559ada7752df", "type": "github" }, "original": { @@ -6904,11 +6904,11 @@ }, "nixpkgs": { "locked": { - "lastModified": 1670827406, - "narHash": "sha256-nLNk7uiLbhbvb4TVz67XK7+Ezr1zcWYDWmNrWGmEUqA=", + "lastModified": 1674487464, + "narHash": "sha256-Jgq50e4S4JVCYpWLqrabBzDp/1mfaxHCh8/OOorHTy0=", "owner": "NixOS", "repo": "nixpkgs", - "rev": "ffca9ffaaafb38c8979068cee98b2644bd3f14cb", + "rev": "3954218cf613eba8e0dcefa9abe337d26bc48fd0", "type": "github" }, "original": { diff --git a/nix/default.nix b/nix/default.nix index ec8546f457..ff5187078e 100644 --- a/nix/default.nix +++ b/nix/default.nix @@ -25,7 +25,7 @@ let inherit (pkgs) system; - purs = pkgs.easy-ps.purs-0_14_5; + purs = pkgs.easy-ps.purs-0_14_9; spagoPkgs = import spagoPackages { inherit pkgs; }; From f71f031d4f16900077b38f1cdbffb4c899fe67b0 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Thu, 26 Jan 2023 13:56:14 +0400 Subject: [PATCH 322/373] Make unnecessarily effectful functions pure --- src/Internal/BalanceTx/ExUnitsAndMinFee.purs | 11 +++++------ src/Internal/ReindexRedeemers.purs | 18 +++++++----------- 2 files changed, 12 insertions(+), 17 deletions(-) diff --git a/src/Internal/BalanceTx/ExUnitsAndMinFee.purs b/src/Internal/BalanceTx/ExUnitsAndMinFee.purs index b80c90f5e4..f4254021f6 100644 --- a/src/Internal/BalanceTx/ExUnitsAndMinFee.purs +++ b/src/Internal/BalanceTx/ExUnitsAndMinFee.purs @@ -23,7 +23,6 @@ import Ctl.Internal.BalanceTx.Types , askCostModelsForLanguages , askNetworkId , asksConstraints - , liftEitherQueryM , liftQueryM ) import Ctl.Internal.Cardano.Types.ScriptRef as ScriptRef @@ -42,8 +41,8 @@ import Ctl.Internal.Cardano.Types.Transaction , _redeemers , _witnessSet ) +import Ctl.Internal.Helpers (liftEither) import Ctl.Internal.Plutus.Conversion (fromPlutusUtxoMap) -import Ctl.Internal.QueryM (QueryM) import Ctl.Internal.QueryM (evaluateTxOgmios) as QueryM import Ctl.Internal.QueryM.MinFee (calculateMinFee) as QueryM import Ctl.Internal.QueryM.Ogmios @@ -124,8 +123,8 @@ evalExUnitsAndMinFee -> BalanceTxM (UnattachedUnbalancedTx /\ BigInt) evalExUnitsAndMinFee (PrebalancedTransaction unattachedTx) allUtxos = do -- Reindex `Spent` script redeemers: - reindexedUnattachedTx <- liftEitherQueryM $ - reindexRedeemers unattachedTx <#> lmap ReindexRedeemersError + reindexedUnattachedTx <- liftEither $ + reindexRedeemers unattachedTx # lmap ReindexRedeemersError -- Reattach datums and redeemers before evaluating ex units: let attachedTx = reattachDatumsAndRedeemers reindexedUnattachedTx -- Evaluate transaction ex units: @@ -198,14 +197,14 @@ finalizeTransaction reindexedUnattachedTxWithExUnits utxos = do reindexRedeemers :: UnattachedUnbalancedTx - -> QueryM (Either ReindexErrors UnattachedUnbalancedTx) + -> Either ReindexErrors UnattachedUnbalancedTx reindexRedeemers unattachedTx@(UnattachedUnbalancedTx { redeemersTxIns }) = let inputs = Array.fromFoldable $ unattachedTx ^. _body' <<< _inputs in reindexSpentScriptRedeemers' inputs redeemersTxIns <#> - map \redeemersTxInsReindexed -> + \redeemersTxInsReindexed -> unattachedTx # _redeemersTxIns .~ redeemersTxInsReindexed reattachDatumsAndRedeemers :: UnattachedUnbalancedTx -> Transaction diff --git a/src/Internal/ReindexRedeemers.purs b/src/Internal/ReindexRedeemers.purs index cee63dde06..b695322779 100644 --- a/src/Internal/ReindexRedeemers.purs +++ b/src/Internal/ReindexRedeemers.purs @@ -8,10 +8,7 @@ module Ctl.Internal.ReindexRedeemers import Prelude -import Control.Monad.Except.Trans (ExceptT(ExceptT), except, runExceptT) import Ctl.Internal.Cardano.Types.Transaction (Redeemer(Redeemer)) as T -import Ctl.Internal.Helpers (liftEither) -import Ctl.Internal.QueryM (QueryM) import Ctl.Internal.Types.RedeemerTag (RedeemerTag(Spend)) import Ctl.Internal.Types.Transaction (TransactionInput) import Data.Array (elemIndex) @@ -42,19 +39,18 @@ type RedeemersTxIn = T.Redeemer /\ Maybe TransactionInput reindexSpentScriptRedeemers :: Array TransactionInput -> Array RedeemersTxIn - -> QueryM (Either ReindexErrors (Array T.Redeemer)) -reindexSpentScriptRedeemers inputs redeemersTxIns = runExceptT do - redeemersTxInsReindexed <- ExceptT $ + -> Either ReindexErrors (Array T.Redeemer) +reindexSpentScriptRedeemers inputs redeemersTxIns = do + redeemersTxInsReindexed <- reindexSpentScriptRedeemers' inputs redeemersTxIns - except <<< Right $ - map fst redeemersTxInsReindexed + pure $ map fst redeemersTxInsReindexed reindexSpentScriptRedeemers' :: Array TransactionInput -> Array RedeemersTxIn - -> QueryM (Either ReindexErrors (Array RedeemersTxIn)) -reindexSpentScriptRedeemers' inputs redeemersTxIns = runExceptT do - liftEither $ traverse (reindex inputs) redeemersTxIns + -> Either ReindexErrors (Array RedeemersTxIn) +reindexSpentScriptRedeemers' inputs redeemersTxIns = + traverse (reindex inputs) redeemersTxIns where reindex :: Array TransactionInput From 92c503ce3f372de75c2e91e8d851539a759cbd88 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Thu, 26 Jan 2023 14:14:29 +0400 Subject: [PATCH 323/373] Fix compile error --- src/Contract/Transaction.purs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Contract/Transaction.purs b/src/Contract/Transaction.purs index 75b544388b..67ccd67636 100644 --- a/src/Contract/Transaction.purs +++ b/src/Contract/Transaction.purs @@ -542,7 +542,8 @@ reindexSpentScriptRedeemers (Array Transaction.Redeemer) ) reindexSpentScriptRedeemers balancedTx = - wrapContract <<< ReindexRedeemers.reindexSpentScriptRedeemers balancedTx + wrapContract <<< pure <<< ReindexRedeemers.reindexSpentScriptRedeemers + balancedTx newtype BalancedSignedTransaction = BalancedSignedTransaction Transaction From 4ec051b51c83e8be08e5144115629d5b76320967 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Fri, 27 Jan 2023 13:01:03 +0000 Subject: [PATCH 324/373] Fix compilation --- test/Blockfrost/Contract.purs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/test/Blockfrost/Contract.purs b/test/Blockfrost/Contract.purs index 8b5626790c..b9fba9a927 100644 --- a/test/Blockfrost/Contract.purs +++ b/test/Blockfrost/Contract.purs @@ -4,6 +4,7 @@ module Test.Ctl.Blockfrost.Contract (main, suite) where import Prelude +import Ctl.Internal.Contract.QueryBackend (defaultConfirmTxDelay) import Contract.Config ( PrivatePaymentKeySource(PrivatePaymentKeyFile) , ServerConfig @@ -60,6 +61,7 @@ suite blockfrostConfig apiKey privateKey backupKeys = do { backendParams = mkBlockfrostBackendParams { blockfrostConfig , blockfrostApiKey: Just apiKey + , confirmTxDelay: defaultConfirmTxDelay } , walletSpec = Just $ UseKeys (PrivatePaymentKeyFile privateKey) From b07455b45761b8470a3fdbe329478636d0168172 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Sat, 28 Jan 2023 15:53:33 +0400 Subject: [PATCH 325/373] Fix Schnorr and ECDSA examples --- examples/ECDSA.purs | 31 +++++++++++++++------------ examples/Schnorr.purs | 31 +++++++++++++++------------ src/Internal/BalanceTx/BalanceTx.purs | 1 - 3 files changed, 34 insertions(+), 29 deletions(-) diff --git a/examples/ECDSA.purs b/examples/ECDSA.purs index 5d0bb46f2a..ab128b7235 100644 --- a/examples/ECDSA.purs +++ b/examples/ECDSA.purs @@ -54,8 +54,7 @@ instance ToData ECDSARedemeer where contract :: Contract () Unit contract = do - void prepTest - void testECDSA + void $ prepTest >>= testECDSA -- | Prepare the ECDSA test by locking some funds at the validator address prepTest :: Contract () TransactionHash @@ -81,8 +80,9 @@ prepTest = do pure txId -- | Attempt to unlock one utxo using an ECDSA signature -testVerification :: ECDSARedemeer -> Contract () TransactionHash -testVerification ecdsaRed = do +testVerification + :: TransactionHash -> ECDSARedemeer -> Contract () TransactionHash +testVerification txId ecdsaRed = do let red = Redeemer $ toData ecdsaRed validator <- liftContractM "Can't get validator" getValidator @@ -94,31 +94,34 @@ testVerification ecdsaRed = do scriptUtxos <- utxosAt valAddr txIn <- liftContractM "No UTxOs found at validator address" - $ Set.findMin + $ Set.toUnfoldable + $ Set.filter (unwrap >>> _.transactionId >>> eq txId) $ Map.keys scriptUtxos + let lookups :: Lookups.ScriptLookups Void lookups = Lookups.validator validator - <> Lookups.unspentOutputs scriptUtxos + <> Lookups.unspentOutputs + (Map.filterKeys ((unwrap >>> _.transactionId >>> eq txId)) scriptUtxos) constraints :: Constraints.TxConstraints Void Void constraints = Constraints.mustSpendScriptOutput txIn red - txId <- submitTxFromConstraints lookups constraints - logInfo' $ "Submitted ECDSA test verification tx: " <> show txId - awaitTxConfirmed txId - logInfo' $ "Transaction confirmed: " <> show txId - pure txId + txId' <- submitTxFromConstraints lookups constraints + logInfo' $ "Submitted ECDSA test verification tx: " <> show txId' + awaitTxConfirmed txId' + logInfo' $ "Transaction confirmed: " <> show txId' + pure txId' -- | Testing ECDSA verification function on-chain -testECDSA :: Contract () TransactionHash -testECDSA = do +testECDSA :: TransactionHash -> Contract () TransactionHash +testECDSA txId = do privateKey <- liftEffect $ randomSecp256k1PrivateKey let publicKey = deriveEcdsaSecp256k1PublicKey privateKey message = byteArrayFromIntArrayUnsafe [ 0, 1, 2, 3 ] messageHash <- liftAff $ hashMessageSha256 message signature <- liftAff $ signEcdsaSecp256k1 privateKey messageHash - testVerification $ + testVerification txId $ ECDSARedemeer { msg: messageHash , sig: signature diff --git a/examples/Schnorr.purs b/examples/Schnorr.purs index 72e50826ab..8041cf7006 100644 --- a/examples/Schnorr.purs +++ b/examples/Schnorr.purs @@ -50,8 +50,7 @@ instance ToData SchnorrRedeemer where contract :: Contract () Unit contract = do - void prepTest - void testSchnorr + void $ prepTest >>= testSchnorr -- | Prepare the ECDSA test by locking some funds at the validator address prepTest :: Contract () TransactionHash @@ -76,8 +75,9 @@ prepTest = do pure txId -- | Attempt to unlock one utxo using an ECDSA signature -testVerification :: SchnorrRedeemer -> Contract () TransactionHash -testVerification ecdsaRed = do +testVerification + :: TransactionHash -> SchnorrRedeemer -> Contract () TransactionHash +testVerification txId ecdsaRed = do let red = Redeemer $ toData ecdsaRed validator <- liftContractM "Can't get validator" getValidator @@ -89,30 +89,33 @@ testVerification ecdsaRed = do scriptUtxos <- utxosAt valAddr txIn <- liftContractM "No UTxOs found at validator address" - $ Set.findMin + $ Set.toUnfoldable + $ Set.filter (unwrap >>> _.transactionId >>> eq txId) $ Map.keys scriptUtxos + let lookups :: Lookups.ScriptLookups Void lookups = Lookups.validator validator - <> Lookups.unspentOutputs scriptUtxos + <> Lookups.unspentOutputs + (Map.filterKeys ((unwrap >>> _.transactionId >>> eq txId)) scriptUtxos) constraints :: Constraints.TxConstraints Void Void constraints = Constraints.mustSpendScriptOutput txIn red - txId <- submitTxFromConstraints lookups constraints - logInfo' $ "Submitted Schnorr test verification tx: " <> show txId - awaitTxConfirmed txId - logInfo' $ "Transaction confirmed: " <> show txId - pure txId + txId' <- submitTxFromConstraints lookups constraints + logInfo' $ "Submitted Schnorr test verification tx: " <> show txId' + awaitTxConfirmed txId' + logInfo' $ "Transaction confirmed: " <> show txId' + pure txId' -- | Testing ECDSA verification function on-chain -testSchnorr :: Contract () TransactionHash -testSchnorr = do +testSchnorr :: TransactionHash -> Contract () TransactionHash +testSchnorr txId = do privateKey <- liftEffect $ randomSecp256k1PrivateKey let publicKey = deriveSchnorrSecp256k1PublicKey privateKey message = byteArrayFromIntArrayUnsafe [ 0, 1, 2, 3 ] signature <- liftAff $ signSchnorrSecp256k1 privateKey message - testVerification $ + testVerification txId $ SchnorrRedeemer { msg: message , sig: signature diff --git a/src/Internal/BalanceTx/BalanceTx.purs b/src/Internal/BalanceTx/BalanceTx.purs index 57fc5d532b..17d0383898 100644 --- a/src/Internal/BalanceTx/BalanceTx.purs +++ b/src/Internal/BalanceTx/BalanceTx.purs @@ -780,4 +780,3 @@ logTransactionWithChange message utxos mChangeOutputs unbalancedTx = in except (getInputValue utxos txBody) >>= (flip Logger.trace (message <> ":") <<< transactionInfo) - From 653ff685e634c4263dd0937bb2dcaff7b13ea0ce Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Sat, 28 Jan 2023 16:44:19 +0400 Subject: [PATCH 326/373] Fix Schnorr and ECDSA examples --- examples/ECDSA.purs | 31 +++++++++++++++++-------------- examples/Schnorr.purs | 31 +++++++++++++++++-------------- 2 files changed, 34 insertions(+), 28 deletions(-) diff --git a/examples/ECDSA.purs b/examples/ECDSA.purs index 53f6c1de8b..37cfe5085a 100644 --- a/examples/ECDSA.purs +++ b/examples/ECDSA.purs @@ -54,8 +54,7 @@ instance ToData ECDSARedemeer where contract :: Contract Unit contract = do - void prepTest - void testECDSA + void $ prepTest >>= testECDSA -- | Prepare the ECDSA test by locking some funds at the validator address prepTest :: Contract TransactionHash @@ -81,8 +80,9 @@ prepTest = do pure txId -- | Attempt to unlock one utxo using an ECDSA signature -testVerification :: ECDSARedemeer -> Contract TransactionHash -testVerification ecdsaRed = do +testVerification + :: TransactionHash -> ECDSARedemeer -> Contract () TransactionHash +testVerification txId ecdsaRed = do let red = Redeemer $ toData ecdsaRed validator <- liftContractM "Can't get validator" getValidator @@ -94,31 +94,34 @@ testVerification ecdsaRed = do scriptUtxos <- utxosAt valAddr txIn <- liftContractM "No UTxOs found at validator address" - $ Set.findMin + $ Set.toUnfoldable + $ Set.filter (unwrap >>> _.transactionId >>> eq txId) $ Map.keys scriptUtxos + let lookups :: Lookups.ScriptLookups Void lookups = Lookups.validator validator - <> Lookups.unspentOutputs scriptUtxos + <> Lookups.unspentOutputs + (Map.filterKeys ((unwrap >>> _.transactionId >>> eq txId)) scriptUtxos) constraints :: Constraints.TxConstraints Void Void constraints = Constraints.mustSpendScriptOutput txIn red - txId <- submitTxFromConstraints lookups constraints - logInfo' $ "Submitted ECDSA test verification tx: " <> show txId - awaitTxConfirmed txId - logInfo' $ "Transaction confirmed: " <> show txId - pure txId + txId' <- submitTxFromConstraints lookups constraints + logInfo' $ "Submitted ECDSA test verification tx: " <> show txId' + awaitTxConfirmed txId' + logInfo' $ "Transaction confirmed: " <> show txId' + pure txId' -- | Testing ECDSA verification function on-chain -testECDSA :: Contract TransactionHash -testECDSA = do +testECDSA :: TransactionHash -> Contract () TransactionHash +testECDSA txId = do privateKey <- liftEffect $ randomSecp256k1PrivateKey let publicKey = deriveEcdsaSecp256k1PublicKey privateKey message = byteArrayFromIntArrayUnsafe [ 0, 1, 2, 3 ] messageHash <- liftAff $ hashMessageSha256 message signature <- liftAff $ signEcdsaSecp256k1 privateKey messageHash - testVerification $ + testVerification txId $ ECDSARedemeer { msg: messageHash , sig: signature diff --git a/examples/Schnorr.purs b/examples/Schnorr.purs index d2a72615c6..6019718f20 100644 --- a/examples/Schnorr.purs +++ b/examples/Schnorr.purs @@ -50,8 +50,7 @@ instance ToData SchnorrRedeemer where contract :: Contract Unit contract = do - void prepTest - void testSchnorr + void $ prepTest >>= testSchnorr -- | Prepare the ECDSA test by locking some funds at the validator address prepTest :: Contract TransactionHash @@ -76,8 +75,9 @@ prepTest = do pure txId -- | Attempt to unlock one utxo using an ECDSA signature -testVerification :: SchnorrRedeemer -> Contract TransactionHash -testVerification ecdsaRed = do +testVerification + :: TransactionHash -> SchnorrRedeemer -> Contract () TransactionHash +testVerification txId ecdsaRed = do let red = Redeemer $ toData ecdsaRed validator <- liftContractM "Can't get validator" getValidator @@ -89,30 +89,33 @@ testVerification ecdsaRed = do scriptUtxos <- utxosAt valAddr txIn <- liftContractM "No UTxOs found at validator address" - $ Set.findMin + $ Set.toUnfoldable + $ Set.filter (unwrap >>> _.transactionId >>> eq txId) $ Map.keys scriptUtxos + let lookups :: Lookups.ScriptLookups Void lookups = Lookups.validator validator - <> Lookups.unspentOutputs scriptUtxos + <> Lookups.unspentOutputs + (Map.filterKeys ((unwrap >>> _.transactionId >>> eq txId)) scriptUtxos) constraints :: Constraints.TxConstraints Void Void constraints = Constraints.mustSpendScriptOutput txIn red - txId <- submitTxFromConstraints lookups constraints - logInfo' $ "Submitted Schnorr test verification tx: " <> show txId - awaitTxConfirmed txId - logInfo' $ "Transaction confirmed: " <> show txId - pure txId + txId' <- submitTxFromConstraints lookups constraints + logInfo' $ "Submitted Schnorr test verification tx: " <> show txId' + awaitTxConfirmed txId' + logInfo' $ "Transaction confirmed: " <> show txId' + pure txId' -- | Testing ECDSA verification function on-chain -testSchnorr :: Contract TransactionHash -testSchnorr = do +testSchnorr :: TransactionHash -> Contract () TransactionHash +testSchnorr txId = do privateKey <- liftEffect $ randomSecp256k1PrivateKey let publicKey = deriveSchnorrSecp256k1PublicKey privateKey message = byteArrayFromIntArrayUnsafe [ 0, 1, 2, 3 ] signature <- liftAff $ signSchnorrSecp256k1 privateKey message - testVerification $ + testVerification txId $ SchnorrRedeemer { msg: message , sig: signature From 5ec6e3bbe969d0f4fe3e228c0341f77628304b8d Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Sun, 29 Jan 2023 22:46:12 +0000 Subject: [PATCH 327/373] Fix compilation and commit timeout change --- examples/ECDSA.purs | 4 ++-- examples/Schnorr.purs | 4 ++-- test/Blockfrost/Contract.purs | 2 +- 3 files changed, 5 insertions(+), 5 deletions(-) diff --git a/examples/ECDSA.purs b/examples/ECDSA.purs index 37cfe5085a..91fc5953a8 100644 --- a/examples/ECDSA.purs +++ b/examples/ECDSA.purs @@ -81,7 +81,7 @@ prepTest = do -- | Attempt to unlock one utxo using an ECDSA signature testVerification - :: TransactionHash -> ECDSARedemeer -> Contract () TransactionHash + :: TransactionHash -> ECDSARedemeer -> Contract TransactionHash testVerification txId ecdsaRed = do let red = Redeemer $ toData ecdsaRed @@ -113,7 +113,7 @@ testVerification txId ecdsaRed = do pure txId' -- | Testing ECDSA verification function on-chain -testECDSA :: TransactionHash -> Contract () TransactionHash +testECDSA :: TransactionHash -> Contract TransactionHash testECDSA txId = do privateKey <- liftEffect $ randomSecp256k1PrivateKey let diff --git a/examples/Schnorr.purs b/examples/Schnorr.purs index 6019718f20..292d248641 100644 --- a/examples/Schnorr.purs +++ b/examples/Schnorr.purs @@ -76,7 +76,7 @@ prepTest = do -- | Attempt to unlock one utxo using an ECDSA signature testVerification - :: TransactionHash -> SchnorrRedeemer -> Contract () TransactionHash + :: TransactionHash -> SchnorrRedeemer -> Contract TransactionHash testVerification txId ecdsaRed = do let red = Redeemer $ toData ecdsaRed @@ -108,7 +108,7 @@ testVerification txId ecdsaRed = do pure txId' -- | Testing ECDSA verification function on-chain -testSchnorr :: TransactionHash -> Contract () TransactionHash +testSchnorr :: TransactionHash -> Contract TransactionHash testSchnorr txId = do privateKey <- liftEffect $ randomSecp256k1PrivateKey let diff --git a/test/Blockfrost/Contract.purs b/test/Blockfrost/Contract.purs index b9fba9a927..8ab8ce4551 100644 --- a/test/Blockfrost/Contract.purs +++ b/test/Blockfrost/Contract.purs @@ -35,7 +35,7 @@ main = do launchAff_ do interpretWithConfig defaultConfig - { timeout = Just $ convertDuration $ 5.0 # Minutes } + { timeout = Just $ convertDuration $ 10.0 # Minutes } (suite blockfrostConfig apiKey privateKey backupKeys) _ -> do log $ joinWith "\n" From 1c8f96b9ad4ba2b737370886e5f3b34079ab556a Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Mon, 30 Jan 2023 13:32:22 +0400 Subject: [PATCH 328/373] Add a failing test for redeemer indexing problem in plutus stake validators --- test/Plutip/Staking.purs | 19 ++++++++++++++----- 1 file changed, 14 insertions(+), 5 deletions(-) diff --git a/test/Plutip/Staking.purs b/test/Plutip/Staking.purs index bf936e34f8..ddd2492434 100644 --- a/test/Plutip/Staking.purs +++ b/test/Plutip/Staking.purs @@ -69,6 +69,7 @@ import Contract.Wallet (withKeyWallet) import Contract.Wallet.Key (keyWalletPrivateStakeKey, publicKeyFromPrivateKey) import Control.Monad.Reader (asks) import Ctl.Examples.AlwaysSucceeds (alwaysSucceedsScript) +import Ctl.Examples.IncludeDatum (only42Script) import Ctl.Internal.Test.TestPlanM (TestPlanM, interpretWithConfig) import Data.Array (head, (!!)) import Data.Array as Array @@ -184,14 +185,19 @@ suite = do <*> liftedM "Failed to get Stake PKH" (join <<< head <$> ownStakePubKeysHashes) - validator <- alwaysSucceedsScript <#> unwrap >>> + validator1 <- alwaysSucceedsScript <#> unwrap >>> + PlutusScriptStakeValidator + validator2 <- only42Script <#> unwrap >>> PlutusScriptStakeValidator - let validatorHash = plutusScriptStakeValidatorHash validator + let + validatorHash1 = plutusScriptStakeValidatorHash validator1 + validatorHash2 = plutusScriptStakeValidatorHash validator2 -- Register do let - constraints = mustRegisterStakeScript validatorHash + constraints = mustRegisterStakeScript validatorHash1 <> + mustRegisterStakeScript validatorHash2 lookups :: Lookups.ScriptLookups Void lookups = @@ -204,8 +210,11 @@ suite = do -- Deregister stake key do let - constraints = mustDeregisterStakePlutusScript validator - unitRedeemer + constraints = + mustDeregisterStakePlutusScript validator1 + unitRedeemer + <> mustDeregisterStakePlutusScript validator2 + unitRedeemer lookups :: Lookups.ScriptLookups Void lookups = From bea915fee10b96a2ee55dde5ee82df981a06fd28 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Mon, 30 Jan 2023 13:36:53 +0400 Subject: [PATCH 329/373] Fix certificate indexing problem in constraint resolver --- src/Internal/Types/ScriptLookups.purs | 42 +++++++++++++++------------ 1 file changed, 24 insertions(+), 18 deletions(-) diff --git a/src/Internal/Types/ScriptLookups.purs b/src/Internal/Types/ScriptLookups.purs index 418ea23114..86dce5c43f 100644 --- a/src/Internal/Types/ScriptLookups.purs +++ b/src/Internal/Types/ScriptLookups.purs @@ -249,14 +249,14 @@ import Ctl.Internal.Types.UnbalancedTransaction , emptyUnbalancedTx ) import Data.Array (cons, filter, mapWithIndex, partition, toUnfoldable, zip) -import Data.Array (singleton, union, (:)) as Array +import Data.Array (length, singleton, union, (:)) as Array import Data.Bifunctor (lmap) import Data.BigInt (BigInt, fromInt) import Data.Either (Either(Left, Right), either, isRight, note) import Data.Foldable (foldM) import Data.Generic.Rep (class Generic) import Data.Lattice (join) -import Data.Lens (non, (%=), (%~), (.=), (.~), (<>=)) +import Data.Lens (non, view, (%=), (%~), (.=), (.~), (<>=)) import Data.Lens.Getter (to, use) import Data.Lens.Iso.Newtype (_Newtype) import Data.Lens.Record (prop) @@ -1299,19 +1299,19 @@ processConstraint mpsMap osMap = do if dh' == dh then addDatum dt else pure $ throwError $ DatumWrongHash dh dt MustRegisterStakePubKey skh -> runExceptT do - lift $ addCertificate + void $ lift $ addCertificate $ StakeRegistration $ keyHashCredential $ unwrap $ unwrap skh MustDeregisterStakePubKey pubKey -> runExceptT do - lift $ addCertificate + void $ lift $ addCertificate $ StakeDeregistration $ keyHashCredential $ unwrap $ unwrap pubKey MustRegisterStakeScript scriptHash -> runExceptT do - lift $ addCertificate + void $ lift $ addCertificate $ StakeRegistration $ scriptHashCredential $ unwrap scriptHash @@ -1321,29 +1321,30 @@ processConstraint mpsMap osMap = do ( scriptHashCredential $ unwrap $ plutusScriptStakeValidatorHash plutusScript ) + index <- lift $ addCertificate cert + let redeemer = T.Redeemer { tag: Cert - , index: zero -- hardcoded and tweaked after balancing. + , index: fromInt index , "data": unwrap redeemerData , exUnits: zero } ExceptT $ attachToCps attachPlutusScript (unwrap plutusScript) ExceptT $ attachToCps attachRedeemer redeemer - _redeemersTxIns <>= Array.singleton (redeemer /\ Nothing) - lift $ addCertificate cert + _redeemersTxIns <>= Array.singleton (redeemer /\ Nothing) -- TODO: is needed? MustDeregisterStakeNativeScript stakeValidator -> do - addCertificate $ StakeDeregistration + void $ addCertificate $ StakeDeregistration $ scriptHashCredential $ unwrap $ nativeScriptStakeValidatorHash stakeValidator attachToCps attachNativeScript (unwrap stakeValidator) MustRegisterPool poolParams -> runExceptT do - lift $ addCertificate $ PoolRegistration poolParams + void $ lift $ addCertificate $ PoolRegistration poolParams MustRetirePool poolKeyHash epoch -> runExceptT do - lift $ addCertificate $ PoolRetirement { poolKeyHash, epoch } + void $ lift $ addCertificate $ PoolRetirement { poolKeyHash, epoch } MustDelegateStakePubKey stakePubKeyHash poolKeyHash -> runExceptT do - lift $ addCertificate $ + void $ lift $ addCertificate $ StakeDelegation (keyHashCredential $ unwrap $ unwrap $ stakePubKeyHash) poolKeyHash MustDelegateStakePlutusScript stakeValidator redeemerData poolKeyHash -> @@ -1354,18 +1355,19 @@ processConstraint mpsMap osMap = do stakeValidator ) poolKeyHash + ix <- lift $ addCertificate cert + let redeemer = T.Redeemer { tag: Cert - , index: zero -- hardcoded and tweaked after balancing. + , index: fromInt ix , "data": unwrap redeemerData , exUnits: zero } ExceptT $ attachToCps attachPlutusScript (unwrap stakeValidator) ExceptT $ attachToCps attachRedeemer redeemer - _redeemersTxIns <>= Array.singleton (redeemer /\ Nothing) - lift $ addCertificate cert + _redeemersTxIns <>= Array.singleton (redeemer /\ Nothing) -- TODO: is needed? MustDelegateStakeNativeScript stakeValidator poolKeyHash -> do - addCertificate $ StakeDelegation + void $ addCertificate $ StakeDelegation ( scriptHashCredential $ unwrap $ nativeScriptStakeValidatorHash stakeValidator ) @@ -1483,12 +1485,16 @@ addDatum dat = runExceptT do ExceptT $ attachToCps attachDatum dat _datums <>= Array.singleton dat +-- | Returns an index pointing to the location of the newly inserted certificate +-- | in the array of transaction certificates. addCertificate :: forall (a :: Type) . Certificate - -> ConstraintsM a Unit -addCertificate cert = + -> ConstraintsM a Int +addCertificate cert = do + ix <- gets (view (_cpsToTxBody <<< _certs <<< non [] <<< to Array.length)) _cpsToTxBody <<< _certs <<< non [] %= Array.(:) cert + pure ix -- Helper to focus from `ConstraintProcessingState` down to `Transaction`. _cpsToTransaction From 1ee7595a0c5010bbb271d024f7cec7075ea3f563 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Mon, 30 Jan 2023 13:40:44 +0400 Subject: [PATCH 330/373] Update CHANGELOG --- CHANGELOG.md | 1 + 1 file changed, 1 insertion(+) diff --git a/CHANGELOG.md b/CHANGELOG.md index 7a56f6cfdf..b2ac96961a 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -61,6 +61,7 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) - CIP-25 strings are now being split into chunks whose sizes are less than or equal to 64 to adhere to the CIP-25 standard ([#1343](https://github.com/Plutonomicon/cardano-transaction-lib/issues/1343)) - Critical upstream fix in [`purescript-bignumber`](https://github.com/mlabs-haskell/purescript-bignumber/pull/2) - `OutputDatum` aeson encoding now roundtrips ([#1388](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1388)) +- Fix incorrect redeemer indexing for Plutus stake validator scripts ([#1417](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1417)) ### Runtime Dependencies From 6b3c51568323c209b95176980f8756f94c447e63 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Mon, 30 Jan 2023 10:55:56 +0000 Subject: [PATCH 331/373] Update comment --- src/Internal/Contract/AwaitTxConfirmed.purs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Internal/Contract/AwaitTxConfirmed.purs b/src/Internal/Contract/AwaitTxConfirmed.purs index 076834303f..2df2cd7820 100644 --- a/src/Internal/Contract/AwaitTxConfirmed.purs +++ b/src/Internal/Contract/AwaitTxConfirmed.purs @@ -58,6 +58,8 @@ awaitTxConfirmedWithTimeout timeoutSeconds txHash = -- If `confirmTxDelay` of `BlockfrostBackend` is set, wait the specified -- number of seconds after the transaction is confirmed, then check the -- transaction confirmation status again to handle possible rollbacks. + -- We do this due to asynchronous updates across API endpoints, the delay + -- should be enough time for the effects of the transaction to settle. findTx :: Contract Boolean findTx = do confirmTxDelay <- From d258688f2d013dc46b77a0e21025b7e552731e07 Mon Sep 17 00:00:00 2001 From: Joseph Young Date: Mon, 30 Jan 2023 10:58:52 +0000 Subject: [PATCH 332/373] Formatting --- test/Blockfrost/Contract.purs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/test/Blockfrost/Contract.purs b/test/Blockfrost/Contract.purs index 8ab8ce4551..ec4b74d852 100644 --- a/test/Blockfrost/Contract.purs +++ b/test/Blockfrost/Contract.purs @@ -4,7 +4,6 @@ module Test.Ctl.Blockfrost.Contract (main, suite) where import Prelude -import Ctl.Internal.Contract.QueryBackend (defaultConfirmTxDelay) import Contract.Config ( PrivatePaymentKeySource(PrivatePaymentKeyFile) , ServerConfig @@ -16,6 +15,7 @@ import Contract.Config import Contract.Monad (launchAff_) import Contract.Test.Mote (TestPlanM, interpretWithConfig) import Contract.Test.Plutip (testContractsInEnv) +import Ctl.Internal.Contract.QueryBackend (defaultConfirmTxDelay) import Data.Maybe (Maybe(Nothing, Just)) import Data.String (joinWith) import Data.Time.Duration (Minutes(Minutes), convertDuration) From 0555d52f776551059d1b1c73997fbe2a21de0dae Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Tue, 31 Jan 2023 17:35:08 +0400 Subject: [PATCH 333/373] Add a runner for Blockfrost test suite --- package.json | 1 + src/Contract/Config.purs | 13 ++- src/Contract/Test/Blockfrost.purs | 185 ++++++++++++++++++++++++++++++ src/Contract/Test/Plutip.purs | 2 +- src/Internal/Contract/Monad.purs | 7 +- src/Internal/Plutip/Server.purs | 13 ++- src/Internal/Test/E2E/Runner.purs | 1 + src/Internal/Wallet/KeyFile.purs | 17 ++- test-data/keys/.gitkeep | 0 test/Blockfrost.purs | 1 - test/Blockfrost/Contract.purs | 70 ++--------- test/blockfrost.env | 67 +++++++++++ 12 files changed, 303 insertions(+), 74 deletions(-) create mode 100644 src/Contract/Test/Blockfrost.purs create mode 100644 test-data/keys/.gitkeep create mode 100644 test/blockfrost.env diff --git a/package.json b/package.json index e9443b5039..de4da2cfca 100755 --- a/package.json +++ b/package.json @@ -12,6 +12,7 @@ "scripts": { "test": "npm run unit-test && npm run integration-test && npm run plutip-test && npm run staking-test", "integration-test": "spago run --main Test.Ctl.Integration", + "blockfrost-test": "source ./test/blockfrost.env && spago run --main Test.Ctl.Blockfrost.Contract", "unit-test": "spago run --main Test.Ctl.Unit", "plutip-test": "spago run --main Test.Ctl.Plutip", "staking-test": "spago run --main Test.Ctl.Plutip.Staking", diff --git a/src/Contract/Config.purs b/src/Contract/Config.purs index 8e0173d18d..9ca9e43e46 100644 --- a/src/Contract/Config.purs +++ b/src/Contract/Config.purs @@ -16,7 +16,6 @@ module Contract.Config , mainnetNuFiConfig , module Contract.Address , module Ctl.Internal.Contract.Monad - , module Ctl.Internal.Contract.QueryBackend , module Data.Log.Level , module Data.Log.Message , module Ctl.Internal.Deserialization.Keys @@ -31,10 +30,18 @@ import Ctl.Internal.Contract.Hooks (Hooks, emptyHooks) as X import Ctl.Internal.Contract.Hooks (emptyHooks) import Ctl.Internal.Contract.Monad (ContractParams) import Ctl.Internal.Contract.QueryBackend - ( QueryBackendParams(CtlBackendParams, BlockfrostBackendParams) + ( BlockfrostBackendParams + , CtlBackend + , CtlBackendParams + , QueryBackend(BlockfrostBackend, CtlBackend) + , QueryBackendParams(BlockfrostBackendParams, CtlBackendParams) + , defaultConfirmTxDelay + , getBlockfrostBackend + , getCtlBackend , mkBlockfrostBackendParams , mkCtlBackendParams - ) + ) as X +import Ctl.Internal.Contract.QueryBackend (mkCtlBackendParams) import Ctl.Internal.Deserialization.Keys (privateKeyFromBytes) import Ctl.Internal.ServerConfig ( Host diff --git a/src/Contract/Test/Blockfrost.purs b/src/Contract/Test/Blockfrost.purs new file mode 100644 index 0000000000..740f9771b6 --- /dev/null +++ b/src/Contract/Test/Blockfrost.purs @@ -0,0 +1,185 @@ +-- | Running Plutip test plans with Blockfrost +module Contract.Test.Blockfrost + ( BlockfrostKeySetup + , runPlutipTestsWithBlockfrost + , executePlutipTestsWithBlockfrost + ) where + +import Prelude + +import Contract.Config + ( BlockfrostBackendParams + , ContractParams + , CtlBackendParams + , PrivatePaymentKeySource(PrivatePaymentKeyFile) + , PrivateStakeKeySource(PrivateStakeKeyFile) + , QueryBackendParams(BlockfrostBackendParams) + , ServerConfig + , WalletSpec(UseKeys) + ) +import Contract.Test.Mote (TestPlanM, interpretWithConfig) +import Contract.Test.Plutip (PlutipTest, runPlutipTestsWithKeyDir) +import Control.Monad.Error.Class (liftMaybe) +import Ctl.Internal.Test.E2E.Runner (readBoolean) +import Data.Maybe (Maybe(Just, Nothing), isNothing, maybe) +import Data.Number as Number +import Data.Time.Duration (Seconds(Seconds)) +import Data.UInt as UInt +import Effect (Effect) +import Effect.Aff (Aff) +import Effect.Class (liftEffect) +import Effect.Console as Console +import Effect.Exception (error, throw) +import Node.Process (lookupEnv) +import Test.Spec.Runner (Config) + +-- | All parameters that are needed to run Plutip-style tests using +-- | Blockfrost API. +-- | +-- | Includes: +-- | +-- | - Private payment and (optionally) stake keys +-- | - A directory to store temporary private keys that will be used in tests. +-- | In case of a suddent test interruption, funds will not be lost since +-- | the private keys will be saved to files. +type BlockfrostKeySetup = + { privateKeySources :: + { payment :: PrivatePaymentKeySource + , stake :: Maybe PrivateStakeKeySource + } + , testKeysDirectory :: String + } + +-- | A function that interprets a Plutip test plan into an `Aff`, given a +-- | pre-funded address and a Blockfrost API endpoint. +-- | +-- | Accepts: +-- | +-- | 1. Runtime parameters for `Contract` +-- | 2. Parameters for Blockfrost backend +-- | 3. Optional parameters for CTL backend if it should be used +-- | 4. Key setup parameters - keys are used to provide funds to the test suite. +-- | Create the keys using [this guide](https://developers.cardano.org/docs/stake-pool-course/handbook/keys-addresses/) +-- | and fund them using the test ADA faucet: https://docs.cardano.org/cardano-testnet/tools/faucet +-- | 5. A test suite to run. +-- | +-- | Note that this function does not start a Plutip cluster. Instead, it +-- | substitutes it with Blockfrost. +-- | +-- | **If you are using a paid Blockfrost plan**, be careful with what you run with +-- | this function. +-- | +-- | Avoid moving the funds around too much using `withWallets` +-- | in the tests to save on both time and costs. +runPlutipTestsWithBlockfrost + :: ContractParams + -> BlockfrostBackendParams + -> Maybe CtlBackendParams + -> BlockfrostKeySetup + -> TestPlanM PlutipTest Unit + -> TestPlanM (Aff Unit) Unit +runPlutipTestsWithBlockfrost + contractParams + backendParams + mbCtlBackendParams + { privateKeySources, testKeysDirectory } + suite = + runPlutipTestsWithKeyDir + config + testKeysDirectory + suite + where + config = + contractParams + { backendParams = BlockfrostBackendParams backendParams mbCtlBackendParams + , walletSpec = Just $ UseKeys privateKeySources.payment + privateKeySources.stake + } + +-- | Reads environment variables containing Blockfrost test suite configuration +-- | and runs a given test suite using `runPlutipTestsWithBlockfrost`. +executePlutipTestsWithBlockfrost + :: Config + -> ContractParams + -> Maybe CtlBackendParams + -> TestPlanM PlutipTest Unit + -> Aff Unit +executePlutipTestsWithBlockfrost + testConfig + contractParams + mbCtlBackendParams + suite = do + blockfrostApiKey <- liftEffect $ + lookupEnv "BLOCKFROST_API_KEY" <#> notEmptyString + when (isNothing blockfrostApiKey) do + liftEffect $ Console.warn $ + "Warning: BLOCKFROST_API_KEY is not set. " <> + "If you are using a public instance, the tests will fail" + privatePaymentKeyFile <- + getEnvVariable "PRIVATE_PAYMENT_KEY_FILE" + "Please specify a payment key file" + mbPrivateStakeKeyFile <- liftEffect $ + lookupEnv "PRIVATE_STAKE_KEY_FILE" <#> notEmptyString + confirmTxDelay <- liftEffect $ + lookupEnv "TX_CONFIRMATION_DELAY_SECONDS" >>= parseConfirmationDelay + when (confirmTxDelay < Just (Seconds 20.0)) do + liftEffect $ Console.warn $ + "Warning: It is recommended to set TX_CONFIRMATION_DELAY_SECONDS to at " + <> "least 20 seconds to let the changes propagate after transaction " + <> "submission." + testKeysDirectory <- getEnvVariable "BACKUP_KEYS_DIR" + "Please specify a directory to store temporary private keys in" + blockfrostConfig <- liftEffect $ readBlockfrostServerConfig + let + backendParams = + { blockfrostConfig + , blockfrostApiKey + , confirmTxDelay + } + interpretWithConfig testConfig $ + runPlutipTestsWithBlockfrost contractParams backendParams mbCtlBackendParams + { privateKeySources: + { payment: PrivatePaymentKeyFile privatePaymentKeyFile + , stake: PrivateStakeKeyFile <$> mbPrivateStakeKeyFile + } + , testKeysDirectory + } + suite + where + getEnvVariable :: String -> String -> Aff String + getEnvVariable variable text = liftEffect do + res <- notEmptyString <$> lookupEnv variable >>= case _ of + Nothing -> throw $ text <> " (" <> variable <> ")" + Just result -> pure result + pure res + + -- Treat env variables set to "" as empty + notEmptyString :: Maybe String -> Maybe String + notEmptyString = + case _ of + Just "" -> Nothing + other -> other + + parseConfirmationDelay :: Maybe String -> Effect (Maybe Seconds) + parseConfirmationDelay = + notEmptyString >>> maybe (pure Nothing) \str -> + case Number.fromString str of + Nothing -> liftEffect $ throw + "TX_CONFIRMATION_DELAY_SECONDS must be set to a valid number" + Just number -> pure $ Just $ Seconds number + +readBlockfrostServerConfig :: Effect ServerConfig +readBlockfrostServerConfig = do + port <- lookupEnv "BLOCKFROST_PORT" >>= \mbPort -> + liftMaybe (error "Unable to read BLOCKFROST_PORT environment variable") + (mbPort >>= UInt.fromString) + host <- lookupEnv "BLOCKFROST_HOST" >>= + liftMaybe (error "Unable to read BLOCKFROST_HOST") + secure <- lookupEnv "BLOCKFROST_SECURE" >>= \mbSecure -> + liftMaybe + ( error + "Unable to read BLOCKFROST_SECURE ('true' - use HTTPS, 'false' - use HTTP)" + ) + (mbSecure >>= readBoolean) + path <- lookupEnv "BLOCKFROST_PATH" + pure { port, host, secure, path } diff --git a/src/Contract/Test/Plutip.purs b/src/Contract/Test/Plutip.purs index 9746bc6eff..d19ea4adec 100644 --- a/src/Contract/Test/Plutip.purs +++ b/src/Contract/Test/Plutip.purs @@ -13,7 +13,7 @@ import Ctl.Internal.Plutip.Server ( PlutipTest , noWallet , runPlutipContract - , testContractsInEnv + , runPlutipTestsWithKeyDir , withPlutipContractEnv , withWallets ) as X diff --git a/src/Internal/Contract/Monad.purs b/src/Internal/Contract/Monad.purs index 13bc1b6023..5b61130e0a 100644 --- a/src/Internal/Contract/Monad.purs +++ b/src/Internal/Contract/Monad.purs @@ -341,12 +341,13 @@ withContractEnv params action = do -- ContractParams -------------------------------------------------------------------------------- --- | Options to construct a `ContractEnv` indirectly. +-- | Options to construct an environment for a `Contract` to run. +-- | +-- | See `Contract.Config` for pre-defined values for testnet and mainnet. -- | -- | Use `runContract` to run a `Contract` within an implicity constructed -- | `ContractEnv` environment, or use `withContractEnv` if your application --- | contains multiple contracts that can be run in parallel, reusing the same --- | environment (see `withContractEnv`) +-- | contains multiple contracts that can reuse the same environment. type ContractParams = { backendParams :: QueryBackendParams , networkId :: NetworkId diff --git a/src/Internal/Plutip/Server.purs b/src/Internal/Plutip/Server.purs index 4675ec6df9..8503dca3e1 100644 --- a/src/Internal/Plutip/Server.purs +++ b/src/Internal/Plutip/Server.purs @@ -9,7 +9,7 @@ module Ctl.Internal.Plutip.Server , testPlutipContracts , withWallets , noWallet - , testContractsInEnv + , runPlutipTestsWithKeyDir , PlutipTest ) where @@ -189,17 +189,20 @@ withPlutipContractEnv plutipCfg distr cont = do $ liftEither >=> \{ env, wallets, printLogs } -> whenError printLogs (cont env wallets) --- | Run `PlutipTest`s with an existing `ContractEnv`, not necessarily one --- | created through `Plutip`. +-- | Run `PlutipTest`s given `ContractParams` value, not necessarily containing +-- | references to runtime services started with Plutip. +-- | This function can be used to interpret `TestPlanM PlutipTest` in any +-- | environment. +-- | -- | Tests are funded by the wallet in the supplied environment. -- | The `FilePath` parameter should point to a directory to store generated -- | wallets, in the case where funds failed to be returned to the main wallet. -testContractsInEnv +runPlutipTestsWithKeyDir :: ContractParams -> FilePath -> TestPlanM PlutipTest Unit -> TestPlanM (Aff Unit) Unit -testContractsInEnv params backup = mapTest \(PlutipTest runPlutipTest) -> +runPlutipTestsWithKeyDir params backup = mapTest \(PlutipTest runPlutipTest) -> runPlutipTest \distr mkTest -> withContractEnv params \env -> do let distrArray :: Array (Array UtxoAmount) diff --git a/src/Internal/Test/E2E/Runner.purs b/src/Internal/Test/E2E/Runner.purs index 5dcc50aa0d..ca815d12df 100644 --- a/src/Internal/Test/E2E/Runner.purs +++ b/src/Internal/Test/E2E/Runner.purs @@ -2,6 +2,7 @@ module Ctl.Internal.Test.E2E.Runner ( runE2ECommand , runE2ETests + , readBoolean ) where import Prelude diff --git a/src/Internal/Wallet/KeyFile.purs b/src/Internal/Wallet/KeyFile.purs index 0a0f3945d1..8984c54fb2 100644 --- a/src/Internal/Wallet/KeyFile.purs +++ b/src/Internal/Wallet/KeyFile.purs @@ -33,17 +33,18 @@ import Ctl.Internal.Wallet.Key ( PrivatePaymentKey(PrivatePaymentKey) , PrivateStakeKey(PrivateStakeKey) ) +import Data.Either (either) import Data.Maybe (Maybe(Nothing)) import Data.Newtype (wrap) -import Effect.Aff (Aff) +import Effect.Aff (Aff, try) import Effect.Class (liftEffect) -import Effect.Exception (error) +import Effect.Exception (error, throw) import Node.Encoding as Encoding import Node.FS.Sync (readTextFile, writeTextFile) import Node.Path (FilePath) keyFromFile :: FilePath -> TextEnvelopeType -> Aff ByteArray -keyFromFile filePath ty = do +keyFromFile filePath ty = errorHandler do fileContents <- liftEffect $ readTextFile Encoding.UTF8 filePath let errorMsg = error "Error while decoding key" liftMaybe errorMsg do @@ -51,6 +52,16 @@ keyFromFile filePath ty = do -- Check TextEnvelope type match to desirable unless (envelope.type_ == ty) Nothing pure envelope.bytes + where + errorHandler action = do + try action >>= either + ( \err -> do + liftEffect $ throw $ + "Unable to load key from file: " <> show filePath + <> ", error: " + <> show err + ) + pure privatePaymentKeyFromTextEnvelope :: TextEnvelope -> Maybe PrivatePaymentKey privatePaymentKeyFromTextEnvelope (TextEnvelope envelope) = do diff --git a/test-data/keys/.gitkeep b/test-data/keys/.gitkeep new file mode 100644 index 0000000000..e69de29bb2 diff --git a/test/Blockfrost.purs b/test/Blockfrost.purs index c2efa957dd..7cfd5d13b8 100644 --- a/test/Blockfrost.purs +++ b/test/Blockfrost.purs @@ -218,4 +218,3 @@ fixture4 = UnconfirmedTx { hash: TransactionHash $ hexToByteArrayUnsafe "deadbeefdeadbeefdeadbeefdeadbeefdeadbeefdeadbeefdeadbeefdeadbeef" } - diff --git a/test/Blockfrost/Contract.purs b/test/Blockfrost/Contract.purs index ec4b74d852..0398b83ae0 100644 --- a/test/Blockfrost/Contract.purs +++ b/test/Blockfrost/Contract.purs @@ -1,70 +1,24 @@ -- | Module to run `Test.Ctl.Plutip.Contract`s suite without Plutip, using -- | an already running instance of Blockfrost (preview). -module Test.Ctl.Blockfrost.Contract (main, suite) where +-- | +-- | Use `npm run blockfrost-test` to run. +module Test.Ctl.Blockfrost.Contract (main) where import Prelude -import Contract.Config - ( PrivatePaymentKeySource(PrivatePaymentKeyFile) - , ServerConfig - , WalletSpec(UseKeys) - , blockfrostPublicPreviewServerConfig - , mkBlockfrostBackendParams - , testnetConfig - ) +import Contract.Config (testnetConfig) import Contract.Monad (launchAff_) -import Contract.Test.Mote (TestPlanM, interpretWithConfig) -import Contract.Test.Plutip (testContractsInEnv) -import Ctl.Internal.Contract.QueryBackend (defaultConfirmTxDelay) +import Contract.Test.Blockfrost (executePlutipTestsWithBlockfrost) import Data.Maybe (Maybe(Nothing, Just)) -import Data.String (joinWith) -import Data.Time.Duration (Minutes(Minutes), convertDuration) +import Data.Time.Duration (Milliseconds(Milliseconds)) import Effect (Effect) -import Effect.Aff (Aff) -import Effect.Class.Console (log) -import Node.Process (argv, exit) import Test.Ctl.Plutip.Contract as Plutip -import Test.Spec.Runner (defaultConfig) +import Test.Spec.Runner (defaultConfig) as TestSpec --- Run with `spago test --main Test.Ctl.Blockfrost.Contract --exec-args "BLOCKFROST_API_KEY PRIVATE_PAYMENT_FILE BACKUP_KEYS_DIR"` main :: Effect Unit -main = do - let blockfrostConfig = blockfrostPublicPreviewServerConfig - argv >>= case _ of - [ _, apiKey, privateKey, backupKeys ] -> - launchAff_ do - interpretWithConfig - defaultConfig - { timeout = Just $ convertDuration $ 10.0 # Minutes } - (suite blockfrostConfig apiKey privateKey backupKeys) - _ -> do - log $ joinWith "\n" - [ "Wrong number of parameters provided." - , "Usage:" - , " spago test --main Test.Ctl.Blockfrost.Contract --exec-args \"BLOCKFROST_API_KEY PRIVATE_PAYMENT_FILE BACKUP_KEYS_DIR\"" - , "" - , " BLOCKFROST_API_KEY - Blockfrost preview API key" - , " PRIVATE_PAYMENT_FILE - PaymentSigningKeyShelley_ed25519 file, as produced by cardano-cli" - , " BACKUP_KEYS_DIR - An existing directory to store generated funded wallets" - ] - exit 1 - -suite :: ServerConfig -> String -> String -> String -> TestPlanM (Aff Unit) Unit -suite blockfrostConfig apiKey privateKey backupKeys = do - testContractsInEnv - config - backupKeys +main = launchAff_ do + executePlutipTestsWithBlockfrost + TestSpec.defaultConfig { timeout = Just $ Milliseconds 900000.0 } + testnetConfig { suppressLogs = true } + Nothing Plutip.suite - where - config = - testnetConfig - { backendParams = mkBlockfrostBackendParams - { blockfrostConfig - , blockfrostApiKey: Just apiKey - , confirmTxDelay: defaultConfirmTxDelay - } - , walletSpec = Just $ UseKeys - (PrivatePaymentKeyFile privateKey) - Nothing - , suppressLogs = true - } diff --git a/test/blockfrost.env b/test/blockfrost.env new file mode 100644 index 0000000000..6cf5e74fe5 --- /dev/null +++ b/test/blockfrost.env @@ -0,0 +1,67 @@ +# Blockfrost test suite configuration. +# +# This file specifies some environment variables that can be read by +# `executePlutipTestsWithBlockfrost` function to run plutip tests using +# Blockfrost. +# +# Follow the guide below to configure the test suite. + +# 0. Go to https://blockfrost.io to generate a new API key +export BLOCKFROST_API_KEY= + +# 1. Follow https://developers.cardano.org/docs/stake-pool-course/handbook/keys-addresses/ +# to generate a private payment key (and, optionally, a stake key). +# +# It should look like this: +# +# { +# "type": "PaymentSigningKeyShelley_ed25519", +# "description": "Payment Signing Key", +# "cborHex": "..." +# } +# +# Get the address for this payment key (and, optionally, a stake key) +# +# If you are using a testnet, replace `--mainnet` flag in the guide with +# `--testnet-magic YOUR_NETWORK_MAGIC`, where YOUR_NETWORK_MAGIC is a genesis +# parameter of the network. +# +# For public testnets, get it from cardano-configurations repo: +# +# https://github.com/input-output-hk/cardano-configurations +# +# The location is `network/YOUR_NETWORK_NAME/genesis/shelley.json`, +# look for `networkMagic` key. +# +# The common values are 1 for `preprod` and 2 for `preview` + +# 2. Fund your address using the testnet faucet: +# +# https://docs.cardano.org/cardano-testnet/tools/faucet +# +# Make sure you are sending the funds in the same network + +# 3. Set the variable below to your `payment.skey` location +export PRIVATE_PAYMENT_KEY_FILE= + +# 4. Set the variable below to your `stake.skey` location, if and only if you have used +# it for address generation +export PRIVATE_STAKE_KEY_FILE= + +# 5. Set this variable to an existing directory where the temporary keys will be stored +export BACKUP_KEYS_DIR=./test-data/keys/ + +# 6. Provide the configuration of the Blockfrost API endpoint URL below. +# Make sure that the API endpoint corresponds to the same network you used +# to fund the wallet +export BLOCKFROST_PORT=443 # https -> 443, http -> 80 +export BLOCKFROST_HOST=cardano-preview.blockfrost.io +export BLOCKFROST_SECURE=true # Use HTTPS +export BLOCKFROST_PATH="/api/v0" + +# Extra configuraiton parameters + +# If you tests are failing because the effects of the transaction do not seem +# to propagate, try increasing this delay. Blockfrost does not update the query +# layer state consistently, so this is the best workaround we can offer. +export TX_CONFIRMATION_DELAY_SECONDS=20 From 1816887c0772652f01bbd82ed42d759daa816d1d Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Tue, 31 Jan 2023 20:27:27 +0400 Subject: [PATCH 334/373] Add docs for Blockfrost test interface and add it to the template --- doc/blockfrost.md | 100 ++++++++++++++++++++ templates/ctl-scaffold/package.json | 1 + templates/ctl-scaffold/test/Blockfrost.purs | 23 +++++ templates/ctl-scaffold/test/Main.purs | 2 +- templates/ctl-scaffold/test/blockfrost.env | 17 ++++ test/Blockfrost/Contract.purs | 2 +- test/blockfrost.env | 54 +---------- 7 files changed, 145 insertions(+), 54 deletions(-) create mode 100644 doc/blockfrost.md create mode 100644 templates/ctl-scaffold/test/Blockfrost.purs create mode 100644 templates/ctl-scaffold/test/blockfrost.env diff --git a/doc/blockfrost.md b/doc/blockfrost.md new file mode 100644 index 0000000000..410f8932d1 --- /dev/null +++ b/doc/blockfrost.md @@ -0,0 +1,100 @@ +# Blockfrost backend + + + + +- [Setting up a Blockfrost-powered test suite](#setting-up-a-blockfrost-powered-test-suite) + - [1. Getting an API key](#1-getting-an-api-key) + - [2. Generating private keys](#2-generating-private-keys) + - [3. Funding your address](#3-funding-your-address) + - [4. Setting up a directory for temporary keys](#4-setting-up-a-directory-for-temporary-keys) + - [5. Providing an API endpoint URL](#5-providing-an-api-endpoint-url) + - [6. Extra configuration options](#6-extra-configuration-options) + - [7. Test suite setup on PureScript side](#7-test-suite-setup-on-purescript-side) + + + +Thanks to [Catalyst Fund9](https://cardano.ideascale.com/c/idea/420791), CTL has been extended with support for [Blockfrost](https://blockfrost.io/) as an alternative query layer. + +The users can now run CTL contracts just by providing a Blockfrost API key and some ADA for the Contract to consume. + +## Setting up a Blockfrost-powered test suite + +Public Blockfrost instances have endpoints for different networks. By default, the test suite is configured to run on `preview`. + +The configuration is stored in environment variables defined in [`test/blockfrost.env` file](../test/blockfrost.env). + +Here's how to make this configuration ready for use: + +### 1. Getting an API key + +Go to https://blockfrost.io to generate a new API key and specify it as `BLOCKFROST_API_KEY` + +### 2. Generating private keys + +Follow https://developers.cardano.org/docs/stake-pool-course/handbook/keys-addresses/ to generate a private payment key (and, optionally, a stake key). + +It should look like this: + +```json +{ + "type": "PaymentSigningKeyShelley_ed25519", + "description": "Payment Signing Key", + "cborHex": "..." +} +``` + +Get the address for this payment key (and, optionally, a stake key), following the guide above. + +If you are using a testnet, replace `--mainnet` flag in the shell command with +`--testnet-magic YOUR_NETWORK_MAGIC`, where `YOUR_NETWORK_MAGIC` is a genesis +parameter of the network. + +For public testnets, get it from [cardano-configurations repo](https://github.com/input-output-hk/cardano-configurations). The location is `network/YOUR_NETWORK_NAME/genesis/shelley.json`, look for `networkMagic` key. + +The common values are 1 for `preprod` and 2 for `preview`. + +### 3. Funding your address + +Fund your address using the [testnet faucet](https://docs.cardano.org/cardano-testnet/tools/faucet). Make sure you are sending the funds in the correct network. + +Point the test suite to your keys by setting `PRIVATE_PAYMENT_KEY_FILE` and `PRIVATE_STAKE_KEY_FILE` to the paths of your `.skey` files. + +If you are going to use an enterprise address (without a staking credential component), then do not provide the staking key file. + +### 4. Setting up a directory for temporary keys + +During testing, the test engine will move funds around according to the UTxO distribution specifications provided via `Contract.Test.Plutip.withWallets` calls in the test bodies. It will generate private keys as needed on the fly. The private keys will be stored in a special directory, to prevent loss of funds in case the test suite exits. Set `BACKUP_KEYS_DIR` to an existing directory where you would like the keys to be stored. + +### 5. Providing an API endpoint URL + +Parts of the endpoint URLs are specified separately, e.g. `https://cardano-preview.blockfrost.io/api/v0/` becomes: + +```bash +export BLOCKFROST_PORT=443 # https -> 443, http -> 80 +export BLOCKFROST_HOST=cardano-preview.blockfrost.io +export BLOCKFROST_SECURE=true # Use HTTPS +export BLOCKFROST_PATH="/api/v0" +``` + +### 6. Extra configuration options + +If your tests are failing because the effects of the transaction do not seem +to propagate, try increasing the delay after transaction submission. Blockfrost does not update the query layer state consistently, so this is the best workaround we can have. + +```bash +export TX_CONFIRMATION_DELAY_SECONDS=30 +``` + +### 7. Test suite setup on PureScript side + +`executePlutipTestsWithBlockfrost` is a helper function that reads all the variables above and takes care of contract environment setup. + +It accepts a number of arguments: + +1. A test spec config, e.g. `Test.Spec.Runner.defaultConfig` +2. A `Contract` config, e.g. `Contract.Config.testnetConfig` +3. An optional CTL runtime config +4. A Plutip test suite + +See [this example](../test/Blockfrost/Contract.purs), which can be executed with `npm run blockfrost-test` command. It will automatically load the exported variables from [`test/blockfrost.env`](../test/blockfrost.env). diff --git a/templates/ctl-scaffold/package.json b/templates/ctl-scaffold/package.json index 4767cb0a03..ae06e407aa 100644 --- a/templates/ctl-scaffold/package.json +++ b/templates/ctl-scaffold/package.json @@ -7,6 +7,7 @@ "test": "test" }, "scripts": { + "blockfrost-test": "source ./test/blockfrost.env && spago run --main Scaffold.Test.Blockfrost", "test": "spago run --main Test.Scaffold.Main", "e2e-serve": "make e2e-serve", "e2e-test": "source ./test/e2e.env && spago test --main Scaffold.Test.E2E -a 'e2e-test run'", diff --git a/templates/ctl-scaffold/test/Blockfrost.purs b/templates/ctl-scaffold/test/Blockfrost.purs new file mode 100644 index 0000000000..0a8eea34cb --- /dev/null +++ b/templates/ctl-scaffold/test/Blockfrost.purs @@ -0,0 +1,23 @@ +-- | An executable test suite that runs `Test.Scaffold.Main.suite` with +-- | Blockfrost. +-- | Use `npm run blockfrost-test` to run. +module Scaffold.Test.Blockfrost (main) where + +import Prelude + +import Contract.Config (testnetConfig) +import Contract.Monad (launchAff_) +import Contract.Test.Blockfrost (executePlutipTestsWithBlockfrost) +import Data.Maybe (Maybe(Nothing, Just)) +import Data.Time.Duration (Milliseconds(Milliseconds)) +import Effect (Effect) +import Test.Scaffold.Main (suite) +import Test.Spec.Runner (defaultConfig) as TestSpec + +main :: Effect Unit +main = launchAff_ do + executePlutipTestsWithBlockfrost + TestSpec.defaultConfig { timeout = Just $ Milliseconds 1000000.0 } + testnetConfig { suppressLogs = true } + Nothing + suite diff --git a/templates/ctl-scaffold/test/Main.purs b/templates/ctl-scaffold/test/Main.purs index a935660937..36812c88a0 100644 --- a/templates/ctl-scaffold/test/Main.purs +++ b/templates/ctl-scaffold/test/Main.purs @@ -1,6 +1,6 @@ -- | This module implements a test suite that uses Plutip to automate running -- | contracts in temporary, private networks. -module Test.Scaffold.Main (main) where +module Test.Scaffold.Main (main, suite) where import Contract.Prelude diff --git a/templates/ctl-scaffold/test/blockfrost.env b/templates/ctl-scaffold/test/blockfrost.env new file mode 100644 index 0000000000..c1cce94232 --- /dev/null +++ b/templates/ctl-scaffold/test/blockfrost.env @@ -0,0 +1,17 @@ +# Blockfrost test suite configuration. +# +# This file specifies some environment variables that can be read by +# `executePlutipTestsWithBlockfrost` function to run plutip tests using +# Blockfrost. +# +# See https://github.com/Plutonomicon/cardano-transaction-lib/blob/develop/doc/blockfrost.md for info on how to set it up + +export BLOCKFROST_API_KEY= +export PRIVATE_PAYMENT_KEY_FILE= +export PRIVATE_STAKE_KEY_FILE= +export BACKUP_KEYS_DIR=./test-data/keys/ +export BLOCKFROST_PORT=443 # https -> 443, http -> 80 +export BLOCKFROST_HOST=cardano-preview.blockfrost.io +export BLOCKFROST_SECURE=true # Use HTTPS +export BLOCKFROST_PATH="/api/v0" +export TX_CONFIRMATION_DELAY_SECONDS=30 diff --git a/test/Blockfrost/Contract.purs b/test/Blockfrost/Contract.purs index 0398b83ae0..90ba1a67e8 100644 --- a/test/Blockfrost/Contract.purs +++ b/test/Blockfrost/Contract.purs @@ -18,7 +18,7 @@ import Test.Spec.Runner (defaultConfig) as TestSpec main :: Effect Unit main = launchAff_ do executePlutipTestsWithBlockfrost - TestSpec.defaultConfig { timeout = Just $ Milliseconds 900000.0 } + TestSpec.defaultConfig { timeout = Just $ Milliseconds 1000000.0 } testnetConfig { suppressLogs = true } Nothing Plutip.suite diff --git a/test/blockfrost.env b/test/blockfrost.env index 6cf5e74fe5..d53965fa36 100644 --- a/test/blockfrost.env +++ b/test/blockfrost.env @@ -4,64 +4,14 @@ # `executePlutipTestsWithBlockfrost` function to run plutip tests using # Blockfrost. # -# Follow the guide below to configure the test suite. +# See ../doc/blockfrost.md for info on how to set it up -# 0. Go to https://blockfrost.io to generate a new API key export BLOCKFROST_API_KEY= - -# 1. Follow https://developers.cardano.org/docs/stake-pool-course/handbook/keys-addresses/ -# to generate a private payment key (and, optionally, a stake key). -# -# It should look like this: -# -# { -# "type": "PaymentSigningKeyShelley_ed25519", -# "description": "Payment Signing Key", -# "cborHex": "..." -# } -# -# Get the address for this payment key (and, optionally, a stake key) -# -# If you are using a testnet, replace `--mainnet` flag in the guide with -# `--testnet-magic YOUR_NETWORK_MAGIC`, where YOUR_NETWORK_MAGIC is a genesis -# parameter of the network. -# -# For public testnets, get it from cardano-configurations repo: -# -# https://github.com/input-output-hk/cardano-configurations -# -# The location is `network/YOUR_NETWORK_NAME/genesis/shelley.json`, -# look for `networkMagic` key. -# -# The common values are 1 for `preprod` and 2 for `preview` - -# 2. Fund your address using the testnet faucet: -# -# https://docs.cardano.org/cardano-testnet/tools/faucet -# -# Make sure you are sending the funds in the same network - -# 3. Set the variable below to your `payment.skey` location export PRIVATE_PAYMENT_KEY_FILE= - -# 4. Set the variable below to your `stake.skey` location, if and only if you have used -# it for address generation export PRIVATE_STAKE_KEY_FILE= - -# 5. Set this variable to an existing directory where the temporary keys will be stored export BACKUP_KEYS_DIR=./test-data/keys/ - -# 6. Provide the configuration of the Blockfrost API endpoint URL below. -# Make sure that the API endpoint corresponds to the same network you used -# to fund the wallet export BLOCKFROST_PORT=443 # https -> 443, http -> 80 export BLOCKFROST_HOST=cardano-preview.blockfrost.io export BLOCKFROST_SECURE=true # Use HTTPS export BLOCKFROST_PATH="/api/v0" - -# Extra configuraiton parameters - -# If you tests are failing because the effects of the transaction do not seem -# to propagate, try increasing this delay. Blockfrost does not update the query -# layer state consistently, so this is the best workaround we can offer. -export TX_CONFIRMATION_DELAY_SECONDS=20 +export TX_CONFIRMATION_DELAY_SECONDS=30 From 34930967518777efcbe4c49e48ead9049be78adf Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Tue, 31 Jan 2023 20:36:53 +0400 Subject: [PATCH 335/373] Update the template --- templates/ctl-scaffold/flake.lock | 161 +++++++++------------- templates/ctl-scaffold/flake.nix | 2 +- templates/ctl-scaffold/packages.dhall | 2 +- templates/ctl-scaffold/spago-packages.nix | 6 +- 4 files changed, 70 insertions(+), 101 deletions(-) diff --git a/templates/ctl-scaffold/flake.lock b/templates/ctl-scaffold/flake.lock index cd3bb84e2a..daec9d2394 100644 --- a/templates/ctl-scaffold/flake.lock +++ b/templates/ctl-scaffold/flake.lock @@ -1469,11 +1469,6 @@ }, "ctl": { "inputs": { - "CHaP": [ - "ctl", - "ogmios", - "CHaP" - ], "cardano-configurations": "cardano-configurations", "cardano-node": [ "ctl", @@ -1482,16 +1477,6 @@ ], "easy-purescript-nix": "easy-purescript-nix", "flake-compat": "flake-compat", - "haskell-nix": [ - "ctl", - "ogmios", - "haskell-nix" - ], - "iohk-nix": [ - "ctl", - "ogmios", - "iohk-nix" - ], "iohk-nix-environments": "iohk-nix-environments", "kupo": "kupo", "kupo-nixos": "kupo-nixos", @@ -1505,17 +1490,17 @@ "plutip": "plutip" }, "locked": { - "lastModified": 1671198807, - "narHash": "sha256-/7MEP4t14HvJ0Hy198wRRz1cyfcFXzggyko2O6PAd+U=", + "lastModified": 1675182481, + "narHash": "sha256-ciwRyjbIlkyaSQ/RMm89xu0wYlP3K2u0nbCLXH3OH+4=", "owner": "Plutonomicon", "repo": "cardano-transaction-lib", - "rev": "001b639606f341489968d599fb0cef2900aeb474", + "rev": "1816887c0772652f01bbd82ed42d759daa816d1d", "type": "github" }, "original": { "owner": "Plutonomicon", "repo": "cardano-transaction-lib", - "rev": "001b639606f341489968d599fb0cef2900aeb474", + "rev": "1816887c0772652f01bbd82ed42d759daa816d1d", "type": "github" } }, @@ -2102,11 +2087,11 @@ }, "flake-utils": { "locked": { - "lastModified": 1667395993, - "narHash": "sha256-nuEHfE/LcWyuSWnS8t12N1wc105Qtau+/OdUAjtQ0rA=", + "lastModified": 1644229661, + "narHash": "sha256-1YdnJAsNy69bpcjuoKdOYQX0YxZBiCYZo4Twxerqv7k=", "owner": "numtide", "repo": "flake-utils", - "rev": "5aed5285a952e0b949eb3ba02c12fa4fcfef535f", + "rev": "3cecb5b042f7f209c56ffd8371b2711a290ec797", "type": "github" }, "original": { @@ -2116,21 +2101,6 @@ } }, "flake-utils_10": { - "locked": { - "lastModified": 1653893745, - "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", - "owner": "numtide", - "repo": "flake-utils", - "rev": "1ed9fb1935d260de5fe1c2f7ee0ebaae17ed2fa1", - "type": "github" - }, - "original": { - "owner": "numtide", - "repo": "flake-utils", - "type": "github" - } - }, - "flake-utils_11": { "locked": { "lastModified": 1644229661, "narHash": "sha256-1YdnJAsNy69bpcjuoKdOYQX0YxZBiCYZo4Twxerqv7k=", @@ -2145,7 +2115,7 @@ "type": "github" } }, - "flake-utils_12": { + "flake-utils_11": { "locked": { "lastModified": 1623875721, "narHash": "sha256-A8BU7bjS5GirpAUv4QA+QnJ4CceLHkcXdRp4xITDB0s=", @@ -2160,7 +2130,7 @@ "type": "github" } }, - "flake-utils_13": { + "flake-utils_12": { "locked": { "lastModified": 1623875721, "narHash": "sha256-A8BU7bjS5GirpAUv4QA+QnJ4CceLHkcXdRp4xITDB0s=", @@ -2175,7 +2145,7 @@ "type": "github" } }, - "flake-utils_14": { + "flake-utils_13": { "locked": { "lastModified": 1623875721, "narHash": "sha256-A8BU7bjS5GirpAUv4QA+QnJ4CceLHkcXdRp4xITDB0s=", @@ -2190,7 +2160,7 @@ "type": "github" } }, - "flake-utils_15": { + "flake-utils_14": { "locked": { "lastModified": 1644229661, "narHash": "sha256-1YdnJAsNy69bpcjuoKdOYQX0YxZBiCYZo4Twxerqv7k=", @@ -2205,7 +2175,7 @@ "type": "github" } }, - "flake-utils_16": { + "flake-utils_15": { "locked": { "lastModified": 1653893745, "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", @@ -2220,7 +2190,7 @@ "type": "github" } }, - "flake-utils_17": { + "flake-utils_16": { "locked": { "lastModified": 1659877975, "narHash": "sha256-zllb8aq3YO3h8B/U0/J1WBgAL8EX5yWf5pMj3G0NAmc=", @@ -2235,7 +2205,7 @@ "type": "github" } }, - "flake-utils_18": { + "flake-utils_17": { "locked": { "lastModified": 1653893745, "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", @@ -2250,7 +2220,7 @@ "type": "github" } }, - "flake-utils_19": { + "flake-utils_18": { "locked": { "lastModified": 1644229661, "narHash": "sha256-1YdnJAsNy69bpcjuoKdOYQX0YxZBiCYZo4Twxerqv7k=", @@ -2265,13 +2235,13 @@ "type": "github" } }, - "flake-utils_2": { + "flake-utils_19": { "locked": { - "lastModified": 1644229661, - "narHash": "sha256-1YdnJAsNy69bpcjuoKdOYQX0YxZBiCYZo4Twxerqv7k=", + "lastModified": 1653893745, + "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", "owner": "numtide", "repo": "flake-utils", - "rev": "3cecb5b042f7f209c56ffd8371b2711a290ec797", + "rev": "1ed9fb1935d260de5fe1c2f7ee0ebaae17ed2fa1", "type": "github" }, "original": { @@ -2280,13 +2250,13 @@ "type": "github" } }, - "flake-utils_20": { + "flake-utils_2": { "locked": { - "lastModified": 1653893745, - "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", + "lastModified": 1644229661, + "narHash": "sha256-1YdnJAsNy69bpcjuoKdOYQX0YxZBiCYZo4Twxerqv7k=", "owner": "numtide", "repo": "flake-utils", - "rev": "1ed9fb1935d260de5fe1c2f7ee0ebaae17ed2fa1", + "rev": "3cecb5b042f7f209c56ffd8371b2711a290ec797", "type": "github" }, "original": { @@ -2295,7 +2265,7 @@ "type": "github" } }, - "flake-utils_21": { + "flake-utils_20": { "locked": { "lastModified": 1659877975, "narHash": "sha256-zllb8aq3YO3h8B/U0/J1WBgAL8EX5yWf5pMj3G0NAmc=", @@ -2310,7 +2280,7 @@ "type": "github" } }, - "flake-utils_22": { + "flake-utils_21": { "locked": { "lastModified": 1653893745, "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", @@ -2327,11 +2297,11 @@ }, "flake-utils_3": { "locked": { - "lastModified": 1644229661, - "narHash": "sha256-1YdnJAsNy69bpcjuoKdOYQX0YxZBiCYZo4Twxerqv7k=", + "lastModified": 1623875721, + "narHash": "sha256-A8BU7bjS5GirpAUv4QA+QnJ4CceLHkcXdRp4xITDB0s=", "owner": "numtide", "repo": "flake-utils", - "rev": "3cecb5b042f7f209c56ffd8371b2711a290ec797", + "rev": "f7e004a55b120c02ecb6219596820fcd32ca8772", "type": "github" }, "original": { @@ -2372,11 +2342,11 @@ }, "flake-utils_6": { "locked": { - "lastModified": 1623875721, - "narHash": "sha256-A8BU7bjS5GirpAUv4QA+QnJ4CceLHkcXdRp4xITDB0s=", + "lastModified": 1644229661, + "narHash": "sha256-1YdnJAsNy69bpcjuoKdOYQX0YxZBiCYZo4Twxerqv7k=", "owner": "numtide", "repo": "flake-utils", - "rev": "f7e004a55b120c02ecb6219596820fcd32ca8772", + "rev": "3cecb5b042f7f209c56ffd8371b2711a290ec797", "type": "github" }, "original": { @@ -2387,11 +2357,11 @@ }, "flake-utils_7": { "locked": { - "lastModified": 1644229661, - "narHash": "sha256-1YdnJAsNy69bpcjuoKdOYQX0YxZBiCYZo4Twxerqv7k=", + "lastModified": 1653893745, + "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", "owner": "numtide", "repo": "flake-utils", - "rev": "3cecb5b042f7f209c56ffd8371b2711a290ec797", + "rev": "1ed9fb1935d260de5fe1c2f7ee0ebaae17ed2fa1", "type": "github" }, "original": { @@ -2402,11 +2372,11 @@ }, "flake-utils_8": { "locked": { - "lastModified": 1653893745, - "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", + "lastModified": 1659877975, + "narHash": "sha256-zllb8aq3YO3h8B/U0/J1WBgAL8EX5yWf5pMj3G0NAmc=", "owner": "numtide", "repo": "flake-utils", - "rev": "1ed9fb1935d260de5fe1c2f7ee0ebaae17ed2fa1", + "rev": "c0e246b9b83f637f4681389ecabcb2681b4f3af0", "type": "github" }, "original": { @@ -2417,11 +2387,11 @@ }, "flake-utils_9": { "locked": { - "lastModified": 1659877975, - "narHash": "sha256-zllb8aq3YO3h8B/U0/J1WBgAL8EX5yWf5pMj3G0NAmc=", + "lastModified": 1653893745, + "narHash": "sha256-0jntwV3Z8//YwuOjzhV2sgJJPt+HY6KhU7VZUL0fKZQ=", "owner": "numtide", "repo": "flake-utils", - "rev": "c0e246b9b83f637f4681389ecabcb2681b4f3af0", + "rev": "1ed9fb1935d260de5fe1c2f7ee0ebaae17ed2fa1", "type": "github" }, "original": { @@ -2890,7 +2860,7 @@ "cabal-34": "cabal-34", "cabal-36": "cabal-36", "cardano-shell": "cardano-shell", - "flake-utils": "flake-utils_2", + "flake-utils": "flake-utils", "ghc-8.6.5-iohk": "ghc-8.6.5-iohk", "hackage": "hackage", "hpc-coveralls": "hpc-coveralls", @@ -2932,7 +2902,7 @@ "cabal-36": "cabal-36_5", "cardano-shell": "cardano-shell_6", "flake-compat": "flake-compat_5", - "flake-utils": "flake-utils_7", + "flake-utils": "flake-utils_6", "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_6", "hackage": "hackage_5", "hpc-coveralls": "hpc-coveralls_6", @@ -2975,7 +2945,7 @@ "cabal-36": "cabal-36_9", "cardano-shell": "cardano-shell_11", "flake-compat": "flake-compat_9", - "flake-utils": "flake-utils_15", + "flake-utils": "flake-utils_14", "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_11", "hackage": "hackage_9", "hpc-coveralls": "hpc-coveralls_11", @@ -3016,7 +2986,7 @@ "cabal-36": "cabal-36_10", "cardano-shell": "cardano-shell_12", "flake-compat": "flake-compat_12", - "flake-utils": "flake-utils_19", + "flake-utils": "flake-utils_18", "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_12", "hackage": "hackage_10", "hpc-coveralls": "hpc-coveralls_12", @@ -3058,7 +3028,7 @@ "cabal-36": "cabal-36_2", "cardano-shell": "cardano-shell_2", "flake-compat": "flake-compat_3", - "flake-utils": "flake-utils_3", + "flake-utils": "flake-utils_2", "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_2", "hackage": [ "ctl", @@ -3103,7 +3073,7 @@ "cabal-34": "cabal-34_3", "cabal-36": "cabal-36_3", "cardano-shell": "cardano-shell_3", - "flake-utils": "flake-utils_4", + "flake-utils": "flake-utils_3", "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_3", "hackage": "hackage_2", "hpc-coveralls": "hpc-coveralls_3", @@ -3143,7 +3113,7 @@ "cabal-34": "cabal-34_4", "cabal-36": "cabal-36_4", "cardano-shell": "cardano-shell_4", - "flake-utils": "flake-utils_5", + "flake-utils": "flake-utils_4", "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_4", "hackage": "hackage_3", "hpc-coveralls": "hpc-coveralls_4", @@ -3184,7 +3154,7 @@ "cabal-32": "cabal-32_5", "cabal-34": "cabal-34_5", "cardano-shell": "cardano-shell_5", - "flake-utils": "flake-utils_6", + "flake-utils": "flake-utils_5", "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_5", "hackage": "hackage_4", "hpc-coveralls": "hpc-coveralls_5", @@ -3225,7 +3195,7 @@ "cabal-34": "cabal-34_7", "cabal-36": "cabal-36_6", "cardano-shell": "cardano-shell_7", - "flake-utils": "flake-utils_11", + "flake-utils": "flake-utils_10", "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_7", "hackage": [ "ctl", @@ -3270,7 +3240,7 @@ "cabal-34": "cabal-34_8", "cabal-36": "cabal-36_7", "cardano-shell": "cardano-shell_8", - "flake-utils": "flake-utils_12", + "flake-utils": "flake-utils_11", "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_8", "hackage": "hackage_6", "hpc-coveralls": "hpc-coveralls_8", @@ -3310,7 +3280,7 @@ "cabal-34": "cabal-34_9", "cabal-36": "cabal-36_8", "cardano-shell": "cardano-shell_9", - "flake-utils": "flake-utils_13", + "flake-utils": "flake-utils_12", "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_9", "hackage": "hackage_7", "hpc-coveralls": "hpc-coveralls_9", @@ -3351,7 +3321,7 @@ "cabal-32": "cabal-32_10", "cabal-34": "cabal-34_10", "cardano-shell": "cardano-shell_10", - "flake-utils": "flake-utils_14", + "flake-utils": "flake-utils_13", "ghc-8.6.5-iohk": "ghc-8.6.5-iohk_10", "hackage": "hackage_8", "hpc-coveralls": "hpc-coveralls_10", @@ -4071,7 +4041,6 @@ }, "kupo-nixos": { "inputs": { - "flake-utils": "flake-utils", "haskell-nix": "haskell-nix", "iohk-nix": "iohk-nix", "kupo": [ @@ -4086,17 +4055,17 @@ ] }, "locked": { - "lastModified": 1667868387, - "narHash": "sha256-YDlUUkbut7Oil5t1njquiSjnu+CQLHxnNFQd2A1eWCc=", + "lastModified": 1672905539, + "narHash": "sha256-B4vryG94L7WWn/tuIQdtg9eZHAH+FaFzv35Mancd2l8=", "owner": "mlabs-haskell", "repo": "kupo-nixos", - "rev": "438799a67d0e6e17f21b7b3d0ae1b6325e505c61", + "rev": "6f89cbcc359893a2aea14dd380f9a45e04c6aa67", "type": "github" }, "original": { "owner": "mlabs-haskell", "repo": "kupo-nixos", - "rev": "438799a67d0e6e17f21b7b3d0ae1b6325e505c61", + "rev": "6f89cbcc359893a2aea14dd380f9a45e04c6aa67", "type": "github" } }, @@ -4428,7 +4397,7 @@ }, "n2c": { "inputs": { - "flake-utils": "flake-utils_10", + "flake-utils": "flake-utils_9", "nixpkgs": [ "ctl", "ogmios", @@ -4454,7 +4423,7 @@ }, "n2c_2": { "inputs": { - "flake-utils": "flake-utils_18", + "flake-utils": "flake-utils_17", "nixpkgs": [ "ctl", "ogmios-nixos", @@ -4480,7 +4449,7 @@ }, "n2c_3": { "inputs": { - "flake-utils": "flake-utils_22", + "flake-utils": "flake-utils_21", "nixpkgs": [ "ctl", "plutip", @@ -4782,7 +4751,7 @@ }, "nix2container": { "inputs": { - "flake-utils": "flake-utils_8", + "flake-utils": "flake-utils_7", "nixpkgs": "nixpkgs_9" }, "locked": { @@ -4801,7 +4770,7 @@ }, "nix2container_2": { "inputs": { - "flake-utils": "flake-utils_16", + "flake-utils": "flake-utils_15", "nixpkgs": "nixpkgs_17" }, "locked": { @@ -4820,7 +4789,7 @@ }, "nix2container_3": { "inputs": { - "flake-utils": "flake-utils_20", + "flake-utils": "flake-utils_19", "nixpkgs": "nixpkgs_21" }, "locked": { @@ -7138,7 +7107,7 @@ "blank": "blank_2", "devshell": "devshell", "dmerge": "dmerge", - "flake-utils": "flake-utils_9", + "flake-utils": "flake-utils_8", "makes": [ "ctl", "ogmios", @@ -7180,7 +7149,7 @@ "blank": "blank_4", "devshell": "devshell_2", "dmerge": "dmerge_2", - "flake-utils": "flake-utils_17", + "flake-utils": "flake-utils_16", "makes": [ "ctl", "ogmios-nixos", @@ -7222,7 +7191,7 @@ "blank": "blank_5", "devshell": "devshell_3", "dmerge": "dmerge_3", - "flake-utils": "flake-utils_21", + "flake-utils": "flake-utils_20", "makes": [ "ctl", "plutip", diff --git a/templates/ctl-scaffold/flake.nix b/templates/ctl-scaffold/flake.nix index 94356640c4..adafe61a8a 100644 --- a/templates/ctl-scaffold/flake.nix +++ b/templates/ctl-scaffold/flake.nix @@ -10,7 +10,7 @@ type = "github"; owner = "Plutonomicon"; repo = "cardano-transaction-lib"; - rev = "22e4fd523092dc74355691951a922697e745f6fa"; + rev = "1816887c0772652f01bbd82ed42d759daa816d1d"; }; # To use the same version of `nixpkgs` as we do nixpkgs.follows = "ctl/nixpkgs"; diff --git a/templates/ctl-scaffold/packages.dhall b/templates/ctl-scaffold/packages.dhall index 7b8a50ca11..1423766524 100644 --- a/templates/ctl-scaffold/packages.dhall +++ b/templates/ctl-scaffold/packages.dhall @@ -351,7 +351,7 @@ let additions = , "variant" ] , repo = "https://github.com/Plutonomicon/cardano-transaction-lib.git" - , version = "22e4fd523092dc74355691951a922697e745f6fa" + , version = "1816887c0772652f01bbd82ed42d759daa816d1d" } , noble-secp256k1 = { dependencies = diff --git a/templates/ctl-scaffold/spago-packages.nix b/templates/ctl-scaffold/spago-packages.nix index fecdd2fd7e..e8954fcd71 100644 --- a/templates/ctl-scaffold/spago-packages.nix +++ b/templates/ctl-scaffold/spago-packages.nix @@ -211,11 +211,11 @@ let "cardano-transaction-lib" = pkgs.stdenv.mkDerivation { name = "cardano-transaction-lib"; - version = "22e4fd523092dc74355691951a922697e745f6fa"; + version = "1816887c0772652f01bbd82ed42d759daa816d1d"; src = pkgs.fetchgit { url = "https://github.com/Plutonomicon/cardano-transaction-lib.git"; - rev = "22e4fd523092dc74355691951a922697e745f6fa"; - sha256 = "1mkra59915c4wrd95mhl22bhmljdybzbqj9naz5fvvqik7biyv1n"; + rev = "1816887c0772652f01bbd82ed42d759daa816d1d"; + sha256 = "1vhzrrymr2xhkns6nazpadi31vf67mpk5l8g96d4r5n86v512b3j"; }; phases = "installPhase"; installPhase = "ln -s $src $out"; From 6560e03ffea07fbb8bb4eb42817db2422276e443 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Tue, 31 Jan 2023 20:49:18 +0400 Subject: [PATCH 336/373] Update CHANGELOG --- CHANGELOG.md | 1 + 1 file changed, 1 insertion(+) diff --git a/CHANGELOG.md b/CHANGELOG.md index f54c0ab4e8..4d8408d3c3 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -50,6 +50,7 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) - `bundlePursProject` allows passing of `includeBundledModule` flag to export the bundled JS module `spago bundle-module` outputs - `Contract.Transaction` exports `mkPoolPubKeyHash` and `poolPubKeyHashToBech32` for bech32 roundtripping ([#1360](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1360)) +- A test runner interface for Blockfrost (`Contract.Test.Blockfrost`). See [`blockfrost.md`](./doc/blockfrost.md) ([#1420](https://github.com/Plutonomicon/cardano-transaction-lib/issues/1420)) ### Changed - `SystemStart` now has `DateTime` (rather than `String`) as the underlying type ([#1377](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1377)) From d0203e4452d40d5aea5d2ad461660beea77dc60e Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Wed, 1 Feb 2023 15:50:00 +0400 Subject: [PATCH 337/373] Add docs for Blockfrost runtime and mention it in README --- README.md | 1 + doc/runtime.md | 28 ++++++++++++++++++++++++++-- 2 files changed, 27 insertions(+), 2 deletions(-) diff --git a/README.md b/README.md index 068310517f..4608e54be1 100644 --- a/README.md +++ b/README.md @@ -34,6 +34,7 @@ Please explore our documentation to discover how to use CTL, how to set up its r - [Super quick start](./doc/getting-started.md#setting-up-a-new-project) - [Adding CTL as a dependency](./doc/ctl-as-dependency.md) - [CTL's runtime dependencies](./doc/runtime.md) +- [Blockfrost support](./doc/blockfrost.md) - [Getting started writing CTL contracts](./doc/getting-started.md) - [Migrating from Plutus to CTL](./doc/plutus-comparison.md) - [Testing contracts with Plutip](./doc/plutip-testing.md) diff --git a/doc/runtime.md b/doc/runtime.md index 0aecf61fad..9033696a37 100644 --- a/doc/runtime.md +++ b/doc/runtime.md @@ -1,6 +1,10 @@ # CTL's Runtime Dependencies -In order to run CTL's `Contract` effects, several services are required. These can be configured through a `ContractEnv` that holds websocket connections, information about server hosts/ports, and other requisite information. Which services are required depends on which backend you are using. +In order to run CTL's `Contract` effects, several services are required. These can be accessed through a `ContractEnv` value that holds websocket connections, information about server hosts/ports, and other requisite information. Which services are required depends on which backend you are using. + +The choice is either [Ogmios](https://ogmios.dev/)+[Kupo](https://cardanosolutions.github.io/kupo/)+cardano-node (a.k.a. "CTL backend") or [Blockfrost](https://blockfrost.io/). + +Our nix environment includes CTL backend services, but for now Blockfrost can be only used externally (either by connecting the public SaaS or the [run-your-own version](https://github.com/blockfrost/blockfrost-backend-ryo/). The self-hosted version still requires Ogmios for some of the endpoints). **Table of Contents** @@ -11,6 +15,8 @@ In order to run CTL's `Contract` effects, several services are required. These c - [Using CTL's `runtime` overlay](#using-ctls-runtime-overlay) - [Changing network configurations](#changing-network-configurations) - [Blockfrost Backend](#blockfrost-backend) + - [Blockfrost backend limitations](#blockfrost-backend-limitations) + - [Transaction confirmation delays](#transaction-confirmation-delays) - [Wallet requirements](#wallet-requirements) @@ -55,7 +61,25 @@ When changing networks, make sure that `network.magic` is correctly synchronized ## Blockfrost Backend -TODO +Blockfrost backend can be configured by providing a record of values to `mkBlockfrostBackendParams`: + +```purescript +type BlockfrostBackendParams = + { blockfrostConfig :: ServerConfig + , blockfrostApiKey :: Maybe String + , confirmTxDelay :: Maybe Seconds + } + +mkBlockfrostBackendParams :: BlockfrostBackendParams -> QueryBackendParams +``` + +Note that it is possible to use CTL runtime services alongside with Blockfrost for queries it does not support by modifying the `QueryBackendParams` value manually (`CtlBackendParams` is an optional parameter of its constructor). + +### Blockfrost backend limitations + +#### Transaction confirmation delays + +State does not propagate to the chain consistently the moment a transaction gets submitted. So, there's a certain artificial delay that gets added after each Tx submission. You can adjust it with `confirmTxDelay` parameter of `BlockfrostBackendParams`. 20-30 seconds is recommended. ## Wallet requirements From 0cc13ef884221b76da43ecad73286a85e625ef8d Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Wed, 1 Feb 2023 15:56:45 +0400 Subject: [PATCH 338/373] Add missing spago dep in template --- templates/ctl-scaffold/spago.dhall | 1 + 1 file changed, 1 insertion(+) diff --git a/templates/ctl-scaffold/spago.dhall b/templates/ctl-scaffold/spago.dhall index 9d8d74c6bb..38fe179f53 100644 --- a/templates/ctl-scaffold/spago.dhall +++ b/templates/ctl-scaffold/spago.dhall @@ -9,6 +9,7 @@ You can edit this file as you like. , "cardano-transaction-lib" , "datetime" , "effect" + , "maybe" , "mote" , "ordered-collections" , "posix-types" From 13a4ac7dabf4a2741f4c158c40812688c3d02f05 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Fri, 3 Feb 2023 13:55:51 +0300 Subject: [PATCH 339/373] Add info on env reuse --- doc/faq.md | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/doc/faq.md b/doc/faq.md index ffe9493aae..49e0ebafa3 100644 --- a/doc/faq.md +++ b/doc/faq.md @@ -112,6 +112,12 @@ We are aware of two error messages that can be show to you if you are using wayl If you are under wayland you need to add `--ozone-platform=wayland` to the arguments for the browser. You can use the `--extra-browser-args` argument for this, as in `e2e-test browser --extra-browser-args="--ozone-platform=wayland"` or the `E2E_EXTRA_BROWSER_ARGS` environment variable. +### Q: How to keep the number of WebSocket connections to a minimum? + +Use only one `ContractEnv` value. They are implicitly created every time `runContract` is called, so avoid using this function if you need to run multiple `Contract`s. + +Instead, initialize the environment with `withContractEnv` and pass it to `runContractInEnv`. The former ensures that the environment is properly finalized, but it forces the developer to follow the bracket pattern, which is not always convenient. As an alternative, `mkContractEnv` can be used. If you are initializing a contract environment with `mkContractEnv` only once during the lifeteime of your app, you should be fine, but if you re-create it dynamically and do not finalize it with `stopContractEnv`, it's fairly easy to hit the max websocket connections limit, which is 200 for Firefox, not to mention that it would be forcing the server to keep the connections. + ## Miscellaneous ### Q: Why am I getting `Error: (AtKey "coinsPerUtxoByte" MissingValue)`? From 5dcd9ac5459f821e48fa8afacb199ed7b97c4e9b Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Fri, 3 Feb 2023 14:14:55 +0300 Subject: [PATCH 340/373] Fix missing closing tag in FAQ --- doc/faq.md | 1 + 1 file changed, 1 insertion(+) diff --git a/doc/faq.md b/doc/faq.md index 49e0ebafa3..e09fa377ea 100644 --- a/doc/faq.md +++ b/doc/faq.md @@ -109,6 +109,7 @@ We are aware of two error messages that can be show to you if you are using wayl Error: Failed to launch the browser process! [76104:76104:1207/234245.704016:ERROR:ozone_platform_x11.cc(238)] Missing X server or $DISPLAY [76104:76104:1207/234245.704036:ERROR:env.cc(255)] The platform failed to initialize. Exiting. + If you are under wayland you need to add `--ozone-platform=wayland` to the arguments for the browser. You can use the `--extra-browser-args` argument for this, as in `e2e-test browser --extra-browser-args="--ozone-platform=wayland"` or the `E2E_EXTRA_BROWSER_ARGS` environment variable. From 6a6ab924fc920bd8416700e73375766ebc151fd7 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Fri, 3 Feb 2023 15:42:42 +0400 Subject: [PATCH 341/373] Move Blockfrost stuff from Plutip module. Better docs --- .gitignore | 1 + src/Contract/Test/Plutip.purs | 4 +- src/Internal/Plutip/Blockfrost.purs | 376 ++++++++++++++++++++++++++++ src/Internal/Plutip/Server.purs | 221 +--------------- 4 files changed, 390 insertions(+), 212 deletions(-) create mode 100644 src/Internal/Plutip/Blockfrost.purs diff --git a/.gitignore b/.gitignore index 8233049794..a1c3cf9e57 100644 --- a/.gitignore +++ b/.gitignore @@ -21,5 +21,6 @@ output.js .idea/ test-data/chrome-user-data test-data/preview +test-data/keys tmp node_modules diff --git a/src/Contract/Test/Plutip.purs b/src/Contract/Test/Plutip.purs index d19ea4adec..2685798cd2 100644 --- a/src/Contract/Test/Plutip.purs +++ b/src/Contract/Test/Plutip.purs @@ -9,11 +9,13 @@ import Prelude import Contract.Monad (runContractInEnv) as X import Contract.Wallet (withKeyWallet) as X +import Ctl.Internal.Plutip.Blockfrost + ( runPlutipTestsWithKeyDir + ) as X import Ctl.Internal.Plutip.Server ( PlutipTest , noWallet , runPlutipContract - , runPlutipTestsWithKeyDir , withPlutipContractEnv , withWallets ) as X diff --git a/src/Internal/Plutip/Blockfrost.purs b/src/Internal/Plutip/Blockfrost.purs new file mode 100644 index 0000000000..02e6e5899b --- /dev/null +++ b/src/Internal/Plutip/Blockfrost.purs @@ -0,0 +1,376 @@ +module Ctl.Internal.Plutip.Blockfrost + ( runPlutipTestsWithKeyDir + ) where + +import Prelude + +import Contract.Address (getWalletAddresses, ownPaymentPubKeysHashes) +import Contract.Config (ContractParams) +import Contract.Hashing (publicKeyHash) +import Contract.Log (logError', logTrace') +import Contract.Monad + ( Contract + , ContractEnv + , liftedE + , liftedM + , runContractInEnv + , withContractEnv + ) +import Contract.TextEnvelope (decodeTextEnvelope) +import Contract.Transaction + ( awaitTxConfirmed + , balanceTx + , signTransaction + , submit + , submitTxFromConstraints + ) +import Contract.Utxos (utxosAt) +import Contract.Value (valueToCoin') +import Contract.Wallet (privateKeysToKeyWallet, withKeyWallet) +import Contract.Wallet.Key + ( keyWalletPrivatePaymentKey + , keyWalletPrivateStakeKey + , publicKeyFromPrivateKey + ) +import Contract.Wallet.KeyFile + ( privatePaymentKeyFromTextEnvelope + , privatePaymentKeyToFile + , privateStakeKeyFromTextEnvelope + , privateStakeKeyToFile + ) +import Control.Monad.Error.Class (liftMaybe) +import Control.Monad.Except (throwError) +import Control.Monad.Reader (asks, local) +import Ctl.Internal.Deserialization.Keys (freshPrivateKey) +import Ctl.Internal.Helpers (logWithLevel) +import Ctl.Internal.Plutip.Server (PlutipTest(PlutipTest)) +import Ctl.Internal.Plutip.Types + ( PrivateKeyResponse(PrivateKeyResponse) + , UtxoAmount + ) +import Ctl.Internal.Plutip.UtxoDistribution + ( decodeWallets + , encodeDistribution + , keyWallets + ) +import Ctl.Internal.Plutus.Types.Transaction (_amount, _output) +import Ctl.Internal.Plutus.Types.Value (Value, lovelaceValueOf) +import Ctl.Internal.Serialization.Address (addressBech32) +import Ctl.Internal.Test.TestPlanM (TestPlanM) +import Ctl.Internal.Types.ScriptLookups (mkUnbalancedTx, unspentOutputs) +import Ctl.Internal.Types.TxConstraints + ( TxConstraint(MustPayToPubKeyAddress) + , TxConstraints + , mustBeSignedBy + , mustPayToPubKeyAddress + , mustSpendPubKeyOutput + , singleton + ) +import Ctl.Internal.Wallet (KeyWallet) +import Data.Array (catMaybes) +import Data.Array as Array +import Data.BigInt (BigInt) +import Data.BigInt as BigInt +import Data.Either (Either(Right, Left), hush) +import Data.Foldable (fold) +import Data.Lens ((^.)) +import Data.List (List(Cons, Nil)) +import Data.List as List +import Data.Map as Map +import Data.Maybe (Maybe(Just, Nothing), isNothing, maybe) +import Data.Newtype (over, unwrap, wrap) +import Data.String (joinWith) +import Data.String.Utils (startsWith) as String +import Data.Traversable (foldMap, for, for_, traverse, traverse_) +import Data.Tuple (fst, snd) +import Data.Tuple.Nested ((/\)) +import Effect.Aff (Aff, Milliseconds(Milliseconds), try) +import Effect.Aff (bracket) as Aff +import Effect.Aff.Class (liftAff) +import Effect.Aff.Retry + ( RetryPolicy + , constantDelay + , limitRetriesByCumulativeDelay + , recovering + ) +import Effect.Class (liftEffect) +import Effect.Class.Console (log) +import Effect.Console as Console +import Effect.Exception (error) +import Effect.Ref as Ref +import Mote.Monad (mapTest) +import Node.Encoding (Encoding(UTF8)) +import Node.FS.Aff (exists, mkdir, readTextFile, readdir, writeTextFile) +import Node.Path (FilePath) +import Node.Path (concat) as Path +import Type.Prelude (Proxy(Proxy)) + +-- | Run `PlutipTest`s given `ContractParams` value, not necessarily containing +-- | references to runtime services started with Plutip. +-- | This function can be used to interpret `TestPlanM PlutipTest` in any +-- | environment. +-- | +-- | Tests are funded by the wallet in the supplied environment. +-- | The `FilePath` parameter should point to a directory to store generated +-- | wallets, in the case where funds failed to be returned to the main wallet. +runPlutipTestsWithKeyDir + :: ContractParams + -> FilePath + -> TestPlanM PlutipTest Unit + -> TestPlanM (Aff Unit) Unit +runPlutipTestsWithKeyDir params backup = do + mapTest \(PlutipTest runPlutipTest) -> do + withContractEnv params \env -> do + keyWallets <- liftAff $ restoreWallets backup + when (Array.length keyWallets > 0) do + liftEffect $ Console.log + "Checking the backup wallets for leftover funds..." + returnFunds backup env keyWallets Nothing + runPlutipTest \distr mkTest -> withContractEnv params \env -> do + let + distrArray :: Array (Array UtxoAmount) + distrArray = encodeDistribution distr + + privateKeys <- liftEffect $ for distrArray \_ -> freshPrivateKey <#> + PrivateKeyResponse + + wallets <- + liftMaybe + ( error + "Impossible happened: could not decode wallets. Please report as bug" + ) + $ decodeWallets distr privateKeys + + let + walletsArray :: Array KeyWallet + walletsArray = keyWallets (pureProxy distr) wallets + + runContract :: Aff Unit + runContract = runContractInEnv env { wallet = Nothing } do + mkTest wallets + + if Array.null walletsArray then + runContract + else Aff.bracket + ( backupWallets backup env walletsArray *> fundWallets env walletsArray + distrArray + ) + -- Retry fund returning until success or timeout. Submission will fail if + -- the node has seen the wallets utxos being spent previously, so retrying + -- will allow the wallets utxos to eventually represent a spendable set + ( \funds -> recovering returnFundsRetryPolicy ([ \_ _ -> pure true ]) + \_ -> returnFunds backup env walletsArray (Just funds) *> + runContractInEnv env (markAsInactive backup walletsArray) + ) + \_ -> runContract + where + pureProxy :: forall (a :: Type). a -> Proxy a + pureProxy _ = Proxy + +-- | Marking wallet as inactive essentially says that we think that there are no +-- | funds left there, but we don't want to delete the files because there may +-- | be some blockchain state that is tied to the keys, e.g. funds locked on +-- | scripts, so we preserve the private keys for the rare occasions when the +-- | user may want to use them later. +-- | +-- | Marking wallet as inactive allows the test suite to skip it during fund +-- | recovery attempts that happen before each test run. +markAsInactive :: FilePath -> Array KeyWallet -> Contract Unit +markAsInactive backup wallets = do + for_ wallets \wallet -> do + networkId <- asks _.networkId + let + address = addressBech32 $ (unwrap wallet).address networkId + inactiveFlagFile = Path.concat [ backup, address, "inactive" ] + liftAff $ writeTextFile UTF8 inactiveFlagFile $ + "This address was marked as inactive. " + <> "The test suite assumes that there are no funds left on it. " + <> "You can check it by inspecting the address on a chain explorer." + +-- | Restore all wallets from the backups that are not marked as inactive. +-- | Normally, this function returns the wallets that have some funds of them +-- | left, e.g. those who were not emptied because the user hit Ctrl+C +restoreWallets :: FilePath -> Aff (Array KeyWallet) +restoreWallets backup = do + walletDirs <- readdir backup <#> Array.filter (String.startsWith "addr") + catMaybes <$> for walletDirs \walletDir -> do + let + paymentKeyFilePath = Path.concat + [ backup, walletDir, "payment_signing_key" ] + stakeKeyFilePath = Path.concat + [ backup, walletDir, "stake_signing_key" ] + inactiveFlagFile = Path.concat [ backup, walletDir, "inactive" ] + -- Skip this wallet if it was marked as inactive + exists inactiveFlagFile >>= case _ of + true -> pure Nothing + false -> do + paymentKeyEnvelope <- readTextFile UTF8 paymentKeyFilePath + paymentKey <- + liftMaybe + ( error $ "Unable to decode private payment key from " <> + paymentKeyFilePath + ) $ + privatePaymentKeyFromTextEnvelope =<< decodeTextEnvelope + paymentKeyEnvelope + mbStakeKey <- do + mbStakeKeyEnvelope <- hush <$> try do + readTextFile UTF8 stakeKeyFilePath + for mbStakeKeyEnvelope \stakeKeyEnvelope -> do + liftMaybe + ( error $ "Unable to decode private stake key from " <> + stakeKeyFilePath + ) $ + privateStakeKeyFromTextEnvelope =<< decodeTextEnvelope + stakeKeyEnvelope + pure $ Just $ privateKeysToKeyWallet paymentKey mbStakeKey + +-- | Save wallets to files in the backup directory for private keys +backupWallets :: FilePath -> ContractEnv -> Array KeyWallet -> Aff Unit +backupWallets backup env walletsArray = liftAff $ for_ walletsArray \wallet -> + do + let + address = addressBech32 $ (unwrap wallet).address env.networkId + payment = keyWalletPrivatePaymentKey wallet + mbStake = keyWalletPrivateStakeKey wallet + folder = Path.concat [ backup, address ] + + mkdir folder + privatePaymentKeyToFile (Path.concat [ folder, "payment_signing_key" ]) + payment + for mbStake $ privateStakeKeyToFile + (Path.concat [ folder, "stake_signing_key" ]) + +-- | Create a transaction that builds a specific UTxO distribution on the wallets. +fundWallets + :: ContractEnv -> Array KeyWallet -> Array (Array UtxoAmount) -> Aff BigInt +fundWallets env walletsArray distrArray = runContractInEnv env $ noLogs do + logTrace' "Funding wallets" + let + constraints = flip foldMap (Array.zip walletsArray distrArray) + \(wallet /\ walletDistr) -> flip foldMap walletDistr + \value -> mustPayToKeyWallet wallet $ lovelaceValueOf value + + txHash <- submitTxFromConstraints (mempty :: _ Void) constraints + awaitTxConfirmed txHash + let fundTotal = Array.foldl (+) zero $ join distrArray + -- Use log so we can see, regardless of suppression + log $ joinWith " " + [ "Sent" + , BigInt.toString fundTotal + , "lovelace to test wallets" + ] + pure fundTotal + +-- Suppress logs during wallet funding, and throw an informative exception +noLogs :: forall (a :: Type). Contract a -> Contract a +noLogs action = do + logRef <- liftEffect $ Ref.new Nil + let + voidLogger env = env + { customLogger = Just + \level message -> + liftEffect $ Ref.modify_ (Cons $ level /\ message) logRef + } + eiRes <- try $ local voidLogger action + case eiRes of + Left err -> do + logError' "-------- BEGIN LOGS FOR WALLET FUNDS REDISTRIBUTION --------" + logError' $ "The lines below are not coming from the Contract that is " + <> "under test" + liftEffect (Ref.read logRef <#> List.reverse) >>= traverse_ + \(level /\ message) -> do + liftEffect $ logWithLevel level message + logError' "--------- END LOGS FOR WALLET FUNDS REDISTRIBUTION ---------" + throwError $ error $ + "An exception has been thrown during funds redistribution in \ + \Blockfrost test suite. Most likely, the wallet ran out of funds. \ + \It is probably not a problem with the Contract that is being tested. \ + \The error was: " <> show err + Right res -> pure res + +returnFundsRetryPolicy :: RetryPolicy +returnFundsRetryPolicy = limitRetriesByCumulativeDelay + (Milliseconds 30_000.00) + (constantDelay $ Milliseconds 2_000.0) + +-- | Find all non-empty wallets and return the funds. +-- | Accepts an optional expected Lovelace number to be returned. +returnFunds + :: FilePath -> ContractEnv -> Array KeyWallet -> Maybe BigInt -> Aff Unit +returnFunds backup env allWalletsArray mbFundTotal = runContractInEnv env $ + noLogs do + nonEmptyWallets <- catMaybes <$> for allWalletsArray \wallet -> do + withKeyWallet wallet do + utxoMap <- liftedM "Failed to get utxos" $ + (getWalletAddresses <#> Array.head) >>= traverse utxosAt + if Map.isEmpty utxoMap then do + markAsInactive backup [ wallet ] + pure Nothing + else pure $ Just (utxoMap /\ wallet) + + when (Array.length nonEmptyWallets /= 0) do + -- Print the messages only if we are running during initial fund recovery + when (isNothing mbFundTotal) do + log $ "Non-empty wallets found: " <> show (Array.length nonEmptyWallets) + log $ "Trying to return the funds back to the main wallet before " <> + "starting the test suite..." + let utxos = nonEmptyWallets # map fst # Map.unions + + pkhs <- fold <$> for nonEmptyWallets + (snd >>> flip withKeyWallet ownPaymentPubKeysHashes) + + let + constraints = flip foldMap (Map.keys utxos) mustSpendPubKeyOutput + <> foldMap mustBeSignedBy pkhs + lookups = unspentOutputs utxos + + unbalancedTx <- liftedE $ mkUnbalancedTx (lookups :: _ Void) constraints + balancedTx <- liftedE $ balanceTx unbalancedTx + balancedSignedTx <- Array.foldM + (\tx wallet -> withKeyWallet wallet $ signTransaction tx) + (wrap $ unwrap balancedTx) + (nonEmptyWallets <#> snd) + + txHash <- submit balancedSignedTx + awaitTxConfirmed txHash + + let + (refundTotal :: BigInt) = Array.foldl + (\acc txorf -> acc + valueToCoin' (txorf ^. _output ^. _amount)) + zero + (Array.fromFoldable $ Map.values utxos) + + log $ joinWith " " $ + [ "Refunded" + , BigInt.toString refundTotal + , "Lovelace" + ] <> maybe [] + ( \fundTotal -> + [ "of" + , BigInt.toString fundTotal + , "Lovelace from test wallets" + ] + ) + mbFundTotal + +-- | A helper function that abstracts away conversion between `KeyWallet` and +-- | its address and just gives us a `TxConstraints` value. +mustPayToKeyWallet + :: forall (i :: Type) (o :: Type) + . KeyWallet + -> Value + -> TxConstraints i o +mustPayToKeyWallet wallet value = + let + convert = wrap <<< publicKeyHash <<< publicKeyFromPrivateKey + payment = over wrap convert $ keyWalletPrivatePaymentKey wallet + mbStake = over wrap convert <$> keyWalletPrivateStakeKey wallet + in + maybe + -- We don't use `mustPayToPubKey payment` to avoid the compile-time + -- warning that is tied to it (it should not be propagated to + -- `runPlutipTestsWithKeyDir`) + (singleton <<< MustPayToPubKeyAddress payment Nothing Nothing Nothing) + (mustPayToPubKeyAddress payment) + mbStake + value diff --git a/src/Internal/Plutip/Server.purs b/src/Internal/Plutip/Server.purs index 8503dca3e1..a325a403db 100644 --- a/src/Internal/Plutip/Server.purs +++ b/src/Internal/Plutip/Server.purs @@ -9,8 +9,8 @@ module Ctl.Internal.Plutip.Server , testPlutipContracts , withWallets , noWallet - , runPlutipTestsWithKeyDir - , PlutipTest + , PlutipTest(PlutipTest) + , PlutipTestHandler ) where import Prelude @@ -20,39 +20,9 @@ import Affjax as Affjax import Affjax.RequestBody as RequestBody import Affjax.RequestHeader as Header import Affjax.ResponseFormat as Affjax.ResponseFormat -import Contract.Address - ( NetworkId(MainnetId) - , getWalletAddresses - , ownPaymentPubKeysHashes - ) -import Contract.Config (ContractParams) -import Contract.Hashing (publicKeyHash) -import Contract.Log (logTrace') -import Contract.Monad - ( Contract - , ContractEnv - , liftContractM - , liftedE - , runContractInEnv - , withContractEnv - ) -import Contract.Transaction - ( awaitTxConfirmed - , balanceTx - , signTransaction - , submit - , submitTxFromConstraints - ) -import Contract.Utxos (utxosAt) -import Contract.Value (valueToCoin') -import Contract.Wallet (withKeyWallet) -import Contract.Wallet.Key - ( keyWalletPrivatePaymentKey - , keyWalletPrivateStakeKey - , publicKeyFromPrivateKey - ) -import Contract.Wallet.KeyFile (privatePaymentKeyToFile, privateStakeKeyToFile) -import Control.Monad.Error.Class (liftEither, liftMaybe) +import Contract.Address (NetworkId(MainnetId)) +import Contract.Monad (Contract, ContractEnv, liftContractM, runContractInEnv) +import Control.Monad.Error.Class (liftEither) import Control.Monad.State (State, execState, modify_) import Control.Monad.Trans.Class (lift) import Control.Monad.Writer (censor, execWriterT, tell) @@ -63,7 +33,6 @@ import Ctl.Internal.Contract.Monad , stopContractEnv ) import Ctl.Internal.Contract.QueryBackend (mkCtlBackendParams) -import Ctl.Internal.Deserialization.Keys (freshPrivateKey) import Ctl.Internal.Helpers ((<>)) import Ctl.Internal.Logging (Logger, mkLogger, setupLogs) import Ctl.Internal.Plutip.PortCheck (isPortAvailable) @@ -87,7 +56,6 @@ import Ctl.Internal.Plutip.Types , StartClusterResponse(ClusterStartupSuccess, ClusterStartupFailure) , StopClusterRequest(StopClusterRequest) , StopClusterResponse - , UtxoAmount ) import Ctl.Internal.Plutip.Utils (tmpdir) import Ctl.Internal.Plutip.UtxoDistribution @@ -97,41 +65,25 @@ import Ctl.Internal.Plutip.UtxoDistribution , keyWallets , transferFundsFromEnterpriseToBase ) -import Ctl.Internal.Plutus.Types.Transaction (_amount, _output) -import Ctl.Internal.Plutus.Types.Value (Value, lovelaceValueOf) -import Ctl.Internal.Serialization.Address (addressBech32) import Ctl.Internal.Service.Error ( ClientError(ClientDecodeJsonError, ClientHttpError) ) import Ctl.Internal.Test.TestPlanM (TestPlanM) -import Ctl.Internal.Types.ScriptLookups (mkUnbalancedTx, unspentOutputs) -import Ctl.Internal.Types.TxConstraints - ( TxConstraints - , mustBeSignedBy - , mustPayToPubKey - , mustPayToPubKeyAddress - , mustSpendPubKeyOutput - ) import Ctl.Internal.Types.UsedTxOuts (newUsedTxOuts) -import Ctl.Internal.Wallet (KeyWallet) import Ctl.Internal.Wallet.Key (PrivatePaymentKey(PrivatePaymentKey)) import Data.Array as Array import Data.Bifunctor (lmap) -import Data.BigInt (BigInt) import Data.BigInt as BigInt import Data.Either (Either(Left), either, isLeft) -import Data.Foldable (fold, sum) +import Data.Foldable (sum) import Data.HTTP.Method as Method -import Data.Lens ((^.)) import Data.Log.Level (LogLevel) import Data.Log.Message (Message) -import Data.Map as Map -import Data.Maybe (Maybe(Just, Nothing), maybe) -import Data.Newtype (over, unwrap, wrap) -import Data.String (joinWith) -import Data.String.CodeUnits as String +import Data.Maybe (Maybe(Nothing, Just), maybe) +import Data.Newtype (over, wrap) +import Data.String.CodeUnits (indexOf) as String import Data.String.Pattern (Pattern(Pattern)) -import Data.Traversable (foldMap, for, for_, sequence_, traverse, traverse_) +import Data.Traversable (foldMap, for, for_, sequence_, traverse_) import Data.Tuple (fst, snd) import Data.Tuple.Nested (type (/\), (/\)) import Data.UInt (UInt) @@ -146,7 +98,6 @@ import Effect.Aff.Retry , recovering ) import Effect.Class (liftEffect) -import Effect.Class.Console (log) import Effect.Exception (error, throw) import Effect.Ref (Ref) import Effect.Ref as Ref @@ -154,10 +105,8 @@ import Mote (bracket) as Mote import Mote.Description (Description(Group, Test)) import Mote.Monad (MoteT(MoteT), mapTest) import Node.ChildProcess (defaultSpawnOptions) -import Node.FS.Aff (mkdir) import Node.FS.Sync (exists, mkdir) as FSSync import Node.Path (FilePath, dirname) -import Node.Path (concat) as Path import Type.Prelude (Proxy(Proxy)) -- | Run a single `Contract` in Plutip environment. @@ -189,156 +138,6 @@ withPlutipContractEnv plutipCfg distr cont = do $ liftEither >=> \{ env, wallets, printLogs } -> whenError printLogs (cont env wallets) --- | Run `PlutipTest`s given `ContractParams` value, not necessarily containing --- | references to runtime services started with Plutip. --- | This function can be used to interpret `TestPlanM PlutipTest` in any --- | environment. --- | --- | Tests are funded by the wallet in the supplied environment. --- | The `FilePath` parameter should point to a directory to store generated --- | wallets, in the case where funds failed to be returned to the main wallet. -runPlutipTestsWithKeyDir - :: ContractParams - -> FilePath - -> TestPlanM PlutipTest Unit - -> TestPlanM (Aff Unit) Unit -runPlutipTestsWithKeyDir params backup = mapTest \(PlutipTest runPlutipTest) -> - runPlutipTest \distr mkTest -> withContractEnv params \env -> do - let - distrArray :: Array (Array UtxoAmount) - distrArray = encodeDistribution distr - - privateKeys <- liftEffect $ for distrArray \_ -> freshPrivateKey <#> - PrivateKeyResponse - - wallets <- - liftMaybe - ( error - "Impossible happened: could not decode wallets. Please report as bug" - ) - $ decodeWallets distr privateKeys - - let - walletsArray :: Array KeyWallet - walletsArray = keyWallets (pureProxy distr) wallets - - runContract :: Aff Unit - runContract = runContractInEnv env { wallet = Nothing } do - logTrace' "Running contract" - mkTest wallets - - if Array.null walletsArray then - runContract - else Aff.bracket - ( backupWallets env walletsArray *> fundWallets env walletsArray - distrArray - ) - -- Retry fund returning until success or timeout. Submission will fail if - -- the node has seen the wallets utxos being spent previously, so retrying - -- will allow the wallets utxos to eventually represent a spendable set - ( \funds -> recovering returnFundsRetryPolicy ([ \_ _ -> pure true ]) - \_ -> returnFunds env walletsArray funds - ) - \_ -> runContract - where - pureProxy :: forall (a :: Type). a -> Proxy a - pureProxy _ = Proxy - - backupWallets :: ContractEnv -> Array KeyWallet -> Aff Unit - backupWallets env walletsArray = liftAff $ for_ walletsArray \wallet -> do - let - address = addressBech32 $ (unwrap wallet).address env.networkId - payment = keyWalletPrivatePaymentKey wallet - mbStake = keyWalletPrivateStakeKey wallet - folder = Path.concat [ backup, address ] - - mkdir folder - privatePaymentKeyToFile (Path.concat [ folder, "payment_signing_key" ]) - payment - for mbStake $ privateStakeKeyToFile - (Path.concat [ folder, "stake_signing_key" ]) - - fundWallets - :: ContractEnv -> Array KeyWallet -> Array (Array UtxoAmount) -> Aff BigInt - fundWallets env walletsArray distrArray = runContractInEnv env do - logTrace' "Funding wallets" - let - constraints = flip foldMap (Array.zip walletsArray distrArray) - \(wallet /\ walletDistr) -> flip foldMap walletDistr - \value -> mustPayToKeyWallet wallet $ lovelaceValueOf value - - txHash <- submitTxFromConstraints (mempty :: _ Void) constraints - awaitTxConfirmed txHash - let fundTotal = Array.foldl (+) zero $ join distrArray - -- Use log so we can see, regardless of suppression - log $ joinWith " " - [ "Sent" - , BigInt.toString fundTotal - , "lovelace to test wallets" - ] - pure fundTotal - - returnFundsRetryPolicy :: RetryPolicy - returnFundsRetryPolicy = limitRetriesByCumulativeDelay - (Milliseconds 30_000.00) - (constantDelay $ Milliseconds 2_000.0) - - returnFunds :: ContractEnv -> Array KeyWallet -> BigInt -> Aff Unit - returnFunds env walletsArray fundTotal = runContractInEnv env do - logTrace' "Returning wallet funds" - - utxos <- Map.unions <<< fold <$> for walletsArray - (flip withKeyWallet getWalletAddresses >=> traverse utxosAt) - - pkhs <- fold <$> for walletsArray - (flip withKeyWallet ownPaymentPubKeysHashes) - - let - constraints = flip foldMap (Map.keys utxos) mustSpendPubKeyOutput - <> foldMap mustBeSignedBy pkhs - lookups = unspentOutputs utxos - - unbalancedTx <- liftedE $ mkUnbalancedTx (lookups :: _ Void) constraints - balancedTx <- liftedE $ balanceTx unbalancedTx - balancedSignedTx <- Array.foldM - (\tx wallet -> withKeyWallet wallet $ signTransaction tx) - (wrap $ unwrap balancedTx) - walletsArray - - txHash <- submit balancedSignedTx - awaitTxConfirmed txHash - - let - (refundTotal :: BigInt) = Array.foldl - (\acc txorf -> acc + valueToCoin' (txorf ^. _output ^. _amount)) - zero - (Array.fromFoldable $ Map.values utxos) - - log $ joinWith " " - [ "Refunded" - , BigInt.toString refundTotal - , "of" - , BigInt.toString fundTotal - , "lovelace from test wallets" - ] - - mustPayToKeyWallet - :: forall (i :: Type) (o :: Type) - . KeyWallet - -> Value - -> TxConstraints i o - mustPayToKeyWallet wallet value = - let - convert = wrap <<< publicKeyHash <<< publicKeyFromPrivateKey - payment = over wrap convert $ keyWalletPrivatePaymentKey wallet - mbStake = over wrap convert <$> keyWalletPrivateStakeKey wallet - in - maybe - (mustPayToPubKey payment) - (mustPayToPubKeyAddress payment) - mbStake - value - -- | Run `Contract`s in tests in a single Plutip instance. -- | NOTE: This uses `MoteT`s bracketting, and thus has the same caveats. -- | Namely, brackets are run for each of the following groups and tests. From 8c10376cd351ad95ec88d7a0b62b7a02b32541a1 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Mon, 6 Feb 2023 22:00:42 +0400 Subject: [PATCH 342/373] Set --prune-utxo flag to kupo --- nix/runtime.nix | 1 + 1 file changed, 1 insertion(+) diff --git a/nix/runtime.nix b/nix/runtime.nix index c6101e5a89..b3ba607e2e 100644 --- a/nix/runtime.nix +++ b/nix/runtime.nix @@ -154,6 +154,7 @@ rec { "0.0.0.0" "--workdir" "kupo-db" + "--prune-utxo" ]; }; }; From 62c76514aca2a52a035a5f4f7ebd0fabe68358ec Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Mon, 6 Feb 2023 22:43:39 +0400 Subject: [PATCH 343/373] Update Blockfrost docs. --- doc/blockfrost.md | 25 +++++++++++++++++++++---- 1 file changed, 21 insertions(+), 4 deletions(-) diff --git a/doc/blockfrost.md b/doc/blockfrost.md index 410f8932d1..afbb8e7eca 100644 --- a/doc/blockfrost.md +++ b/doc/blockfrost.md @@ -11,6 +11,7 @@ - [5. Providing an API endpoint URL](#5-providing-an-api-endpoint-url) - [6. Extra configuration options](#6-extra-configuration-options) - [7. Test suite setup on PureScript side](#7-test-suite-setup-on-purescript-side) +- [Running `Contract`s with Blockfrost](#running-contracts-with-blockfrost) @@ -18,17 +19,19 @@ Thanks to [Catalyst Fund9](https://cardano.ideascale.com/c/idea/420791), CTL has The users can now run CTL contracts just by providing a Blockfrost API key and some ADA for the Contract to consume. +For testing, we offer an automated test engine that allows to run with Blockfrost any test suite that was meant to be run on a [Plutip](./plutip-testing.md) cluster. + ## Setting up a Blockfrost-powered test suite Public Blockfrost instances have endpoints for different networks. By default, the test suite is configured to run on `preview`. -The configuration is stored in environment variables defined in [`test/blockfrost.env` file](../test/blockfrost.env). +The configuration is stored in environment variables defined in [`test/blockfrost.env` file](../test/blockfrost.env), or a similar one in your project if it is initialized from the template. -Here's how to make this configuration ready for use: +Here's how to populate this configuration file to be ready for use: ### 1. Getting an API key -Go to https://blockfrost.io to generate a new API key and specify it as `BLOCKFROST_API_KEY` +Go to https://blockfrost.io to generate a new API key and specify it as `BLOCKFROST_API_KEY` in the config. ### 2. Generating private keys @@ -60,7 +63,7 @@ Fund your address using the [testnet faucet](https://docs.cardano.org/cardano-te Point the test suite to your keys by setting `PRIVATE_PAYMENT_KEY_FILE` and `PRIVATE_STAKE_KEY_FILE` to the paths of your `.skey` files. -If you are going to use an enterprise address (without a staking credential component), then do not provide the staking key file. +If you are going to use an enterprise address (without a staking credential component), then do not provide the staking key file. The choice of using either type of addresses does not affect anything, because the test suite will be using the address only to distribute funds to other, temporary addresses. ### 4. Setting up a directory for temporary keys @@ -98,3 +101,17 @@ It accepts a number of arguments: 4. A Plutip test suite See [this example](../test/Blockfrost/Contract.purs), which can be executed with `npm run blockfrost-test` command. It will automatically load the exported variables from [`test/blockfrost.env`](../test/blockfrost.env). + +## Running `Contract`s with Blockfrost + +`mkBlockfrostBackendParams` can be called on a populated `BlockfrostBackendParams` to create a `QueryBackendParams` value. `backendParams` field of `ContractParams` uses a value of this type. + +``` +type BlockfrostBackendParams = + { blockfrostConfig :: ServerConfig + , blockfrostApiKey :: Maybe String + , confirmTxDelay :: Maybe Seconds + } +``` + +Use `blockfrostPublicMainnetServerConfig`, `blockfrostPublicPreviewServerConfig` or `blockfrostPublicPreprodServerConfig` for pre-configured `ServerConfig` setups. From 2e2efcaf5def76aa3153890c4e1b26b11036500c Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Tue, 7 Feb 2023 19:20:18 +0400 Subject: [PATCH 344/373] Untie distribution machinery from Plutip and rename PlutipTest to ContractTest --- CHANGELOG.md | 2 + doc/blockfrost.md | 21 +++-- src/Contract/Test.purs | 9 ++ src/Contract/Test/Blockfrost.purs | 29 +++--- src/Contract/Test/Plutip.purs | 25 +++--- src/Internal/Plutip/Server.purs | 89 +++++-------------- src/Internal/Plutip/Types.purs | 7 ++ src/Internal/Test/ContractTest.purs | 59 ++++++++++++ src/Internal/Test/E2E/Runner.purs | 2 +- .../Blockfrost.purs => Test/KeyDir.purs} | 40 ++++----- .../{Plutip => Test}/UtxoDistribution.purs | 4 +- templates/ctl-scaffold/test/Blockfrost.purs | 4 +- test/Blockfrost/Contract.purs | 4 +- test/Plutip/UtxoDistribution.purs | 2 +- 14 files changed, 171 insertions(+), 126 deletions(-) create mode 100644 src/Contract/Test.purs create mode 100644 src/Internal/Test/ContractTest.purs rename src/Internal/{Plutip/Blockfrost.purs => Test/KeyDir.purs} (94%) rename src/Internal/{Plutip => Test}/UtxoDistribution.purs (98%) diff --git a/CHANGELOG.md b/CHANGELOG.md index 4d8408d3c3..8fd078d3e8 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -60,6 +60,8 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) - `startPlutipCluster` error message now includes cluster startup failure details. ([#1407](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1407)) +- `PlutipTest` is now known as `Contract.Test.ContractTest`. It has been semantically untied from Plutip, because we now have another test runner for tests that rely on particular funds distributions - [Blockfrost](./doc/blockfrost.md). See `Contract.Test.Blockfrost.runContractTestsWithBlockfrost`. + ### Removed ### Fixed diff --git a/doc/blockfrost.md b/doc/blockfrost.md index afbb8e7eca..b121f77418 100644 --- a/doc/blockfrost.md +++ b/doc/blockfrost.md @@ -12,14 +12,15 @@ - [6. Extra configuration options](#6-extra-configuration-options) - [7. Test suite setup on PureScript side](#7-test-suite-setup-on-purescript-side) - [Running `Contract`s with Blockfrost](#running-contracts-with-blockfrost) +- [See also](#see-also) Thanks to [Catalyst Fund9](https://cardano.ideascale.com/c/idea/420791), CTL has been extended with support for [Blockfrost](https://blockfrost.io/) as an alternative query layer. -The users can now run CTL contracts just by providing a Blockfrost API key and some ADA for the Contract to consume. +The users [can now run]((#running-contracts-with-blockfrost)) CTL contracts just by providing a Blockfrost API key and some ADA for the Contract to consume. -For testing, we offer an automated test engine that allows to run with Blockfrost any test suite that was meant to be run on a [Plutip](./plutip-testing.md) cluster. +For testing, we offer an automated test engine that allows to run any `ContractTest` test suite with Blockfrost. ## Setting up a Blockfrost-powered test suite @@ -67,7 +68,7 @@ If you are going to use an enterprise address (without a staking credential comp ### 4. Setting up a directory for temporary keys -During testing, the test engine will move funds around according to the UTxO distribution specifications provided via `Contract.Test.Plutip.withWallets` calls in the test bodies. It will generate private keys as needed on the fly. The private keys will be stored in a special directory, to prevent loss of funds in case the test suite exits. Set `BACKUP_KEYS_DIR` to an existing directory where you would like the keys to be stored. +During testing, the test engine will move funds around according to the UTxO distribution specifications provided via `Contract.Test.withWallets` calls in the test bodies. It will generate private keys as needed on the fly. The private keys will be stored in a special directory, to prevent loss of funds in case the test suite exits. Set `BACKUP_KEYS_DIR` to an existing directory where you would like the keys to be stored. ### 5. Providing an API endpoint URL @@ -91,20 +92,20 @@ export TX_CONFIRMATION_DELAY_SECONDS=30 ### 7. Test suite setup on PureScript side -`executePlutipTestsWithBlockfrost` is a helper function that reads all the variables above and takes care of contract environment setup. +`executeContractTestsWithBlockfrost` is a helper function that reads all the variables above and takes care of contract environment setup. It accepts a number of arguments: -1. A test spec config, e.g. `Test.Spec.Runner.defaultConfig` +1. A test spec config, e.g. `Test.Spec.Runner.defaultConfig` - it's probably better to increase the timeout. 2. A `Contract` config, e.g. `Contract.Config.testnetConfig` 3. An optional CTL runtime config -4. A Plutip test suite +4. A `ContractTest` suite See [this example](../test/Blockfrost/Contract.purs), which can be executed with `npm run blockfrost-test` command. It will automatically load the exported variables from [`test/blockfrost.env`](../test/blockfrost.env). ## Running `Contract`s with Blockfrost -`mkBlockfrostBackendParams` can be called on a populated `BlockfrostBackendParams` to create a `QueryBackendParams` value. `backendParams` field of `ContractParams` uses a value of this type. +`mkBlockfrostBackendParams` can be called on a populated `BlockfrostBackendParams` record to create a `QueryBackendParams` value. `backendParams` field of `ContractParams` uses a value of this type. And `ContractParams` can in turn be used with `runContract`. ``` type BlockfrostBackendParams = @@ -114,4 +115,8 @@ type BlockfrostBackendParams = } ``` -Use `blockfrostPublicMainnetServerConfig`, `blockfrostPublicPreviewServerConfig` or `blockfrostPublicPreprodServerConfig` for pre-configured `ServerConfig` setups. +For convenience, use `blockfrostPublicMainnetServerConfig`, `blockfrostPublicPreviewServerConfig` or `blockfrostPublicPreprodServerConfig` for pre-configured `ServerConfig` setups. + +## See also + +- [Testing utilities for CTL](./test-utils.md). diff --git a/src/Contract/Test.purs b/src/Contract/Test.purs new file mode 100644 index 0000000000..8c07d503a0 --- /dev/null +++ b/src/Contract/Test.purs @@ -0,0 +1,9 @@ +module Contract.Test + ( module X + ) where + +import Ctl.Internal.Test.ContractTest + ( ContractTest(ContractTest) + , noWallet + , withWallets + ) as X diff --git a/src/Contract/Test/Blockfrost.purs b/src/Contract/Test/Blockfrost.purs index 740f9771b6..71e27461a0 100644 --- a/src/Contract/Test/Blockfrost.purs +++ b/src/Contract/Test/Blockfrost.purs @@ -1,8 +1,8 @@ -- | Running Plutip test plans with Blockfrost module Contract.Test.Blockfrost ( BlockfrostKeySetup - , runPlutipTestsWithBlockfrost - , executePlutipTestsWithBlockfrost + , runContractTestsWithBlockfrost + , executeContractTestsWithBlockfrost ) where import Prelude @@ -18,9 +18,10 @@ import Contract.Config , WalletSpec(UseKeys) ) import Contract.Test.Mote (TestPlanM, interpretWithConfig) -import Contract.Test.Plutip (PlutipTest, runPlutipTestsWithKeyDir) import Control.Monad.Error.Class (liftMaybe) +import Ctl.Internal.Test.ContractTest (ContractTest) import Ctl.Internal.Test.E2E.Runner (readBoolean) +import Ctl.Internal.Test.KeyDir (runContractTestsWithKeyDir) import Data.Maybe (Maybe(Just, Nothing), isNothing, maybe) import Data.Number as Number import Data.Time.Duration (Seconds(Seconds)) @@ -33,7 +34,7 @@ import Effect.Exception (error, throw) import Node.Process (lookupEnv) import Test.Spec.Runner (Config) --- | All parameters that are needed to run Plutip-style tests using +-- | All parameters that are needed to run Contract tests using -- | Blockfrost API. -- | -- | Includes: @@ -71,20 +72,20 @@ type BlockfrostKeySetup = -- | -- | Avoid moving the funds around too much using `withWallets` -- | in the tests to save on both time and costs. -runPlutipTestsWithBlockfrost +runContractTestsWithBlockfrost :: ContractParams -> BlockfrostBackendParams -> Maybe CtlBackendParams -> BlockfrostKeySetup - -> TestPlanM PlutipTest Unit + -> TestPlanM ContractTest Unit -> TestPlanM (Aff Unit) Unit -runPlutipTestsWithBlockfrost +runContractTestsWithBlockfrost contractParams backendParams mbCtlBackendParams { privateKeySources, testKeysDirectory } suite = - runPlutipTestsWithKeyDir + runContractTestsWithKeyDir config testKeysDirectory suite @@ -97,14 +98,15 @@ runPlutipTestsWithBlockfrost } -- | Reads environment variables containing Blockfrost test suite configuration --- | and runs a given test suite using `runPlutipTestsWithBlockfrost`. -executePlutipTestsWithBlockfrost +-- | parameters and runs a given test suite using +-- | `runContractTestsWithBlockfrost`. +executeContractTestsWithBlockfrost :: Config -> ContractParams -> Maybe CtlBackendParams - -> TestPlanM PlutipTest Unit + -> TestPlanM ContractTest Unit -> Aff Unit -executePlutipTestsWithBlockfrost +executeContractTestsWithBlockfrost testConfig contractParams mbCtlBackendParams @@ -137,7 +139,8 @@ executePlutipTestsWithBlockfrost , confirmTxDelay } interpretWithConfig testConfig $ - runPlutipTestsWithBlockfrost contractParams backendParams mbCtlBackendParams + runContractTestsWithBlockfrost contractParams backendParams + mbCtlBackendParams { privateKeySources: { payment: PrivatePaymentKeyFile privatePaymentKeyFile , stake: PrivateStakeKeyFile <$> mbPrivateStakeKeyFile diff --git a/src/Contract/Test/Plutip.purs b/src/Contract/Test/Plutip.purs index 2685798cd2..af7f178f22 100644 --- a/src/Contract/Test/Plutip.purs +++ b/src/Contract/Test/Plutip.purs @@ -3,23 +3,18 @@ module Contract.Test.Plutip ( testPlutipContracts , module X + , PlutipTest ) where import Prelude import Contract.Monad (runContractInEnv) as X import Contract.Wallet (withKeyWallet) as X -import Ctl.Internal.Plutip.Blockfrost - ( runPlutipTestsWithKeyDir - ) as X import Ctl.Internal.Plutip.Server - ( PlutipTest - , noWallet - , runPlutipContract + ( runPlutipContract , withPlutipContractEnv - , withWallets ) as X -import Ctl.Internal.Plutip.Server (PlutipTest, testPlutipContracts) as Server +import Ctl.Internal.Plutip.Server (testPlutipContracts) as Server import Ctl.Internal.Plutip.Types ( InitialUTxODistribution , InitialUTxOs @@ -28,16 +23,22 @@ import Ctl.Internal.Plutip.Types , UtxoAmount ) as X import Ctl.Internal.Plutip.Types (PlutipConfig) -import Ctl.Internal.Plutip.UtxoDistribution - ( class UtxoDistribution - , withStakeKey +import Ctl.Internal.Test.ContractTest (ContractTest) +import Ctl.Internal.Test.ContractTest (ContractTest) as Server +import Ctl.Internal.Test.ContractTest + ( noWallet + , withWallets ) as X +import Ctl.Internal.Test.UtxoDistribution (class UtxoDistribution, withStakeKey) as X import Effect.Aff (Aff) import Mote (MoteT) -- | Run `Contract`s in tests in a single Plutip instance. testPlutipContracts :: PlutipConfig - -> MoteT Aff Server.PlutipTest Aff Unit + -> MoteT Aff Server.ContractTest Aff Unit -> MoteT Aff (Aff Unit) Aff Unit testPlutipContracts = Server.testPlutipContracts + +-- | Type synonym for backwards compatibility. +type PlutipTest = ContractTest diff --git a/src/Internal/Plutip/Server.purs b/src/Internal/Plutip/Server.purs index a325a403db..14d12aeb05 100644 --- a/src/Internal/Plutip/Server.purs +++ b/src/Internal/Plutip/Server.purs @@ -7,10 +7,6 @@ module Ctl.Internal.Plutip.Server , checkPlutipServer , stopChildProcessWithPort , testPlutipContracts - , withWallets - , noWallet - , PlutipTest(PlutipTest) - , PlutipTestHandler ) where import Prelude @@ -58,17 +54,22 @@ import Ctl.Internal.Plutip.Types , StopClusterResponse ) import Ctl.Internal.Plutip.Utils (tmpdir) -import Ctl.Internal.Plutip.UtxoDistribution +import Ctl.Internal.Service.Error + ( ClientError(ClientDecodeJsonError, ClientHttpError) + ) +import Ctl.Internal.Test.ContractTest + ( ContractTest(ContractTest) + , ContractTestPlan(ContractTestPlan) + , ContractTestPlanHandler + ) +import Ctl.Internal.Test.TestPlanM (TestPlanM) +import Ctl.Internal.Test.UtxoDistribution ( class UtxoDistribution , decodeWallets , encodeDistribution , keyWallets , transferFundsFromEnterpriseToBase ) -import Ctl.Internal.Service.Error - ( ClientError(ClientDecodeJsonError, ClientHttpError) - ) -import Ctl.Internal.Test.TestPlanM (TestPlanM) import Ctl.Internal.Types.UsedTxOuts (newUsedTxOuts) import Ctl.Internal.Wallet.Key (PrivatePaymentKey(PrivatePaymentKey)) import Data.Array as Array @@ -146,11 +147,11 @@ withPlutipContractEnv plutipCfg distr cont = do -- | https://github.com/Plutonomicon/cardano-transaction-lib/blob/develop/doc/plutip-testing.md#testing-with-mote testPlutipContracts :: PlutipConfig - -> TestPlanM PlutipTest Unit + -> TestPlanM ContractTest Unit -> TestPlanM (Aff Unit) Unit testPlutipContracts plutipCfg tp = do - PlutipTestPlan runPlutipTestPlan <- lift $ execDistribution tp - runPlutipTestPlan \distr tests -> do + ContractTestPlan runContractTestPlan <- lift $ execDistribution tp + runContractTestPlan \distr tests -> do cleanupRef <- liftEffect $ Ref.new mempty bracket (startPlutipContractEnv plutipCfg distr cleanupRef) (runCleanup cleanupRef) @@ -190,63 +191,21 @@ whenError whenErrorAction action = do when (isLeft res) whenErrorAction liftEither res --- | Represents `Contract`s that depend on *some* wallet `UtxoDistribution` -newtype PlutipTest = PlutipTest - ( forall (r :: Type) - . ( forall (distr :: Type) (wallets :: Type) - . PlutipTestHandler distr wallets r - ) - -> r - ) - -type PlutipTestHandler :: Type -> Type -> Type -> Type -type PlutipTestHandler distr wallets r = - UtxoDistribution distr wallets => distr -> (wallets -> Contract Unit) -> r - --- | Store a wallet `UtxoDistribution` and a `Contract` that depends on those wallets -withWallets - :: forall (distr :: Type) (wallets :: Type) - . UtxoDistribution distr wallets - => distr - -> (wallets -> Contract Unit) - -> PlutipTest -withWallets distr tests = PlutipTest \h -> h distr tests - --- | Lift a `Contract` into `PlutipTest` -noWallet :: Contract Unit -> PlutipTest -noWallet = withWallets unit <<< const - --- | Represents `Contract`s in `TestPlanM` that depend on *some* wallet `UtxoDistribution` -newtype PlutipTestPlan = PlutipTestPlan - ( forall (r :: Type) - . ( forall (distr :: Type) (wallets :: Type) - . PlutipTestPlanHandler distr wallets r - ) - -> r - ) - -type PlutipTestPlanHandler :: Type -> Type -> Type -> Type -type PlutipTestPlanHandler distr wallets r = - UtxoDistribution distr wallets - => distr - -> TestPlanM (wallets -> Contract Unit) Unit - -> r - -- | Lifts the utxo distributions of each test out of Mote, into a combined -- | distribution. Adapts the tests to pick their distribution out of the -- | combined distribution. -- | NOTE: Skipped tests still have their distribution generated. -execDistribution :: TestPlanM PlutipTest Unit -> Aff PlutipTestPlan +execDistribution :: TestPlanM ContractTest Unit -> Aff ContractTestPlan execDistribution (MoteT mote) = execWriterT mote <#> go where - go :: Array (Description Aff PlutipTest) -> PlutipTestPlan - go = flip execState emptyPlutipTestPlan <<< traverse_ case _ of - Test rm { bracket, label, value: PlutipTest runPlutipTest } -> - runPlutipTest \distr test -> do + go :: Array (Description Aff ContractTest) -> ContractTestPlan + go = flip execState emptyContractTestPlan <<< traverse_ case _ of + Test rm { bracket, label, value: ContractTest runTest } -> + runTest \distr test -> do addTests distr $ MoteT (tell [ Test rm { bracket, label, value: test } ]) Group rm { bracket, label, value } -> do - let PlutipTestPlan runGroupPlan = go value + let ContractTestPlan runGroupPlan = go value runGroupPlan \distr tests -> addTests distr $ over MoteT (censor (pure <<< Group rm <<< { bracket, label, value: _ })) @@ -254,15 +213,15 @@ execDistribution (MoteT mote) = execWriterT mote <#> go addTests :: forall (distr :: Type) (wallets :: Type) - . PlutipTestPlanHandler distr wallets (State PlutipTestPlan Unit) + . ContractTestPlanHandler distr wallets (State ContractTestPlan Unit) addTests distr tests = do - modify_ \(PlutipTestPlan runPlutipTestPlan) -> runPlutipTestPlan - \distr' tests' -> PlutipTestPlan \h -> h (distr' /\ distr) do + modify_ \(ContractTestPlan runContractTestPlan) -> runContractTestPlan + \distr' tests' -> ContractTestPlan \h -> h (distr' /\ distr) do mapTest (_ <<< fst) tests' mapTest (_ <<< snd) tests - emptyPlutipTestPlan :: PlutipTestPlan - emptyPlutipTestPlan = PlutipTestPlan \h -> h unit (pure unit) + emptyContractTestPlan :: ContractTestPlan + emptyContractTestPlan = ContractTestPlan \h -> h unit (pure unit) -- | Provide a `ContractEnv` connected to Plutip. -- | Can be used to run multiple `Contract`s using `runContractInEnv`. diff --git a/src/Internal/Plutip/Types.purs b/src/Internal/Plutip/Types.purs index b82868f101..2258b0c4db 100644 --- a/src/Internal/Plutip/Types.purs +++ b/src/Internal/Plutip/Types.purs @@ -55,6 +55,9 @@ import Data.UInt (UInt) import Effect.Aff (Aff) import Partial.Unsafe (unsafePartial) +-- | A config that is used to run tests on Plutip clusters. +-- | Note that the test suite starts the services on the specified ports. +-- | It does not expect them to be running. type PlutipConfig = { host :: String , port :: UInt @@ -76,11 +79,15 @@ type ErrorMessage = String -- | UTxO amount in Lovelaces type UtxoAmount = BigInt +-- | A list of UTxOs for a single wallet type InitialUTxOs = Array UtxoAmount +-- | A wrapper that allows to specify a stake key to attach to a +-- | generated pre-funded Address. data InitialUTxOsWithStakeKey = InitialUTxOsWithStakeKey PrivateStakeKey InitialUTxOs +-- | A spec for distribution of UTxOs between wallets. type InitialUTxODistribution = Array InitialUTxOs newtype ClusterStartupRequest = ClusterStartupRequest diff --git a/src/Internal/Test/ContractTest.purs b/src/Internal/Test/ContractTest.purs new file mode 100644 index 0000000000..683a2f7bde --- /dev/null +++ b/src/Internal/Test/ContractTest.purs @@ -0,0 +1,59 @@ +module Ctl.Internal.Test.ContractTest + ( ContractTest(ContractTest) + , withWallets + , noWallet + , ContractTestHandler + , ContractTestPlan(ContractTestPlan) + , ContractTestPlanHandler + ) where + +import Prelude + +import Contract.Monad (Contract) +import Ctl.Internal.Test.TestPlanM (TestPlanM) +import Ctl.Internal.Test.UtxoDistribution (class UtxoDistribution) + +-- | Represents a `Contract` test suite that depend on *some* wallet +-- | `UtxoDistribution`. +newtype ContractTest = ContractTest + ( forall (r :: Type) + . ( forall (distr :: Type) (wallets :: Type) + . ContractTestHandler distr wallets r + ) + -> r + ) + +-- | Store a wallet `UtxoDistribution` and a `Contract` that depends on those wallets +withWallets + :: forall (distr :: Type) (wallets :: Type) + . UtxoDistribution distr wallets + => distr + -> (wallets -> Contract Unit) + -> ContractTest +withWallets distr tests = ContractTest \h -> h distr tests + +-- | Lift a `Contract` into `ContractTest` +noWallet :: Contract Unit -> ContractTest +noWallet = withWallets unit <<< const + +-- | A runner for a test suite that supports funds distribution. +type ContractTestHandler :: Type -> Type -> Type -> Type +type ContractTestHandler distr wallets r = + UtxoDistribution distr wallets => distr -> (wallets -> Contract Unit) -> r + +-- | Represents `Contract`s in `TestPlanM` that depend on *some* wallet `UtxoDistribution` +newtype ContractTestPlan = ContractTestPlan + ( forall (r :: Type) + . ( forall (distr :: Type) (wallets :: Type) + . ContractTestPlanHandler distr wallets r + ) + -> r + ) + +-- | Same as `ContractTestHandler`, but wrapped in a `TestPaln`. +type ContractTestPlanHandler :: Type -> Type -> Type -> Type +type ContractTestPlanHandler distr wallets r = + UtxoDistribution distr wallets + => distr + -> TestPlanM (wallets -> Contract Unit) Unit + -> r diff --git a/src/Internal/Test/E2E/Runner.purs b/src/Internal/Test/E2E/Runner.purs index ca815d12df..5592500953 100644 --- a/src/Internal/Test/E2E/Runner.purs +++ b/src/Internal/Test/E2E/Runner.purs @@ -19,7 +19,6 @@ import Ctl.Internal.Deserialization.Keys (privateKeyFromBytes) import Ctl.Internal.Helpers (liftedM, (<>)) import Ctl.Internal.Plutip.Server (withPlutipContractEnv) import Ctl.Internal.Plutip.Types (PlutipConfig) -import Ctl.Internal.Plutip.UtxoDistribution (withStakeKey) import Ctl.Internal.QueryM (ClusterSetup) import Ctl.Internal.Test.E2E.Browser (withBrowser) import Ctl.Internal.Test.E2E.Feedback @@ -70,6 +69,7 @@ import Ctl.Internal.Test.E2E.Wallets , namiSign ) import Ctl.Internal.Test.TestPlanM (TestPlanM, interpretWithConfig) +import Ctl.Internal.Test.UtxoDistribution (withStakeKey) import Ctl.Internal.Types.RawBytes (hexToRawBytes) import Ctl.Internal.Wallet.Key ( PrivateStakeKey diff --git a/src/Internal/Plutip/Blockfrost.purs b/src/Internal/Test/KeyDir.purs similarity index 94% rename from src/Internal/Plutip/Blockfrost.purs rename to src/Internal/Test/KeyDir.purs index 02e6e5899b..451a8890e9 100644 --- a/src/Internal/Plutip/Blockfrost.purs +++ b/src/Internal/Test/KeyDir.purs @@ -1,5 +1,5 @@ -module Ctl.Internal.Plutip.Blockfrost - ( runPlutipTestsWithKeyDir +module Ctl.Internal.Test.KeyDir + ( runContractTestsWithKeyDir ) where import Prelude @@ -43,20 +43,20 @@ import Control.Monad.Except (throwError) import Control.Monad.Reader (asks, local) import Ctl.Internal.Deserialization.Keys (freshPrivateKey) import Ctl.Internal.Helpers (logWithLevel) -import Ctl.Internal.Plutip.Server (PlutipTest(PlutipTest)) import Ctl.Internal.Plutip.Types ( PrivateKeyResponse(PrivateKeyResponse) , UtxoAmount ) -import Ctl.Internal.Plutip.UtxoDistribution - ( decodeWallets - , encodeDistribution - , keyWallets - ) import Ctl.Internal.Plutus.Types.Transaction (_amount, _output) import Ctl.Internal.Plutus.Types.Value (Value, lovelaceValueOf) import Ctl.Internal.Serialization.Address (addressBech32) +import Ctl.Internal.Test.ContractTest (ContractTest(ContractTest)) import Ctl.Internal.Test.TestPlanM (TestPlanM) +import Ctl.Internal.Test.UtxoDistribution + ( decodeWallets + , encodeDistribution + , keyWallets + ) import Ctl.Internal.Types.ScriptLookups (mkUnbalancedTx, unspentOutputs) import Ctl.Internal.Types.TxConstraints ( TxConstraint(MustPayToPubKeyAddress) @@ -105,28 +105,28 @@ import Node.Path (FilePath) import Node.Path (concat) as Path import Type.Prelude (Proxy(Proxy)) --- | Run `PlutipTest`s given `ContractParams` value, not necessarily containing --- | references to runtime services started with Plutip. --- | This function can be used to interpret `TestPlanM PlutipTest` in any +-- | Runs `ContractTest`s given a `ContractParams` value. +-- | +-- | This function can be used to interpret `TestPlanM ContractTest` in any -- | environment. -- | --- | Tests are funded by the wallet in the supplied environment. +-- | Tests are funded by the wallet in the supplied `Contract` environment. -- | The `FilePath` parameter should point to a directory to store generated --- | wallets, in the case where funds failed to be returned to the main wallet. -runPlutipTestsWithKeyDir +-- | private keys (to make sure that no funds or on-chain state are lost). +runContractTestsWithKeyDir :: ContractParams -> FilePath - -> TestPlanM PlutipTest Unit + -> TestPlanM ContractTest Unit -> TestPlanM (Aff Unit) Unit -runPlutipTestsWithKeyDir params backup = do - mapTest \(PlutipTest runPlutipTest) -> do +runContractTestsWithKeyDir params backup = do + mapTest \(ContractTest runContractTest) -> do withContractEnv params \env -> do keyWallets <- liftAff $ restoreWallets backup when (Array.length keyWallets > 0) do liftEffect $ Console.log "Checking the backup wallets for leftover funds..." returnFunds backup env keyWallets Nothing - runPlutipTest \distr mkTest -> withContractEnv params \env -> do + runContractTest \distr mkTest -> withContractEnv params \env -> do let distrArray :: Array (Array UtxoAmount) distrArray = encodeDistribution distr @@ -283,7 +283,7 @@ noLogs action = do logError' "--------- END LOGS FOR WALLET FUNDS REDISTRIBUTION ---------" throwError $ error $ "An exception has been thrown during funds redistribution in \ - \Blockfrost test suite. Most likely, the wallet ran out of funds. \ + \the test suite. Most likely, the wallet ran out of funds. \ \It is probably not a problem with the Contract that is being tested. \ \The error was: " <> show err Right res -> pure res @@ -369,7 +369,7 @@ mustPayToKeyWallet wallet value = maybe -- We don't use `mustPayToPubKey payment` to avoid the compile-time -- warning that is tied to it (it should not be propagated to - -- `runPlutipTestsWithKeyDir`) + -- `runContractTestWithKeyDir`) (singleton <<< MustPayToPubKeyAddress payment Nothing Nothing Nothing) (mustPayToPubKeyAddress payment) mbStake diff --git a/src/Internal/Plutip/UtxoDistribution.purs b/src/Internal/Test/UtxoDistribution.purs similarity index 98% rename from src/Internal/Plutip/UtxoDistribution.purs rename to src/Internal/Test/UtxoDistribution.purs index a9399627c8..e6a0aaa867 100644 --- a/src/Internal/Plutip/UtxoDistribution.purs +++ b/src/Internal/Test/UtxoDistribution.purs @@ -1,4 +1,4 @@ -module Ctl.Internal.Plutip.UtxoDistribution +module Ctl.Internal.Test.UtxoDistribution ( class UtxoDistribution , decodeWallets , decodeWallets' @@ -171,7 +171,7 @@ type WalletInfo = -- | the utxos at its enterprise address to its base address. Note -- | that this function clears the `usedTxOuts` cache, so it should -- | not be used if there could be items in the cache that shouldn't --- | be cleared (this function is intended to be used only on plutip +-- | be cleared (this function is intended to be used only on `ContractTest` -- | startup). transferFundsFromEnterpriseToBase :: PrivatePaymentKey diff --git a/templates/ctl-scaffold/test/Blockfrost.purs b/templates/ctl-scaffold/test/Blockfrost.purs index 0a8eea34cb..678568e5f6 100644 --- a/templates/ctl-scaffold/test/Blockfrost.purs +++ b/templates/ctl-scaffold/test/Blockfrost.purs @@ -7,7 +7,7 @@ import Prelude import Contract.Config (testnetConfig) import Contract.Monad (launchAff_) -import Contract.Test.Blockfrost (executePlutipTestsWithBlockfrost) +import Contract.Test.Blockfrost (executeContractTestsWithBlockfrost) import Data.Maybe (Maybe(Nothing, Just)) import Data.Time.Duration (Milliseconds(Milliseconds)) import Effect (Effect) @@ -16,7 +16,7 @@ import Test.Spec.Runner (defaultConfig) as TestSpec main :: Effect Unit main = launchAff_ do - executePlutipTestsWithBlockfrost + executeContractTestsWithBlockfrost TestSpec.defaultConfig { timeout = Just $ Milliseconds 1000000.0 } testnetConfig { suppressLogs = true } Nothing diff --git a/test/Blockfrost/Contract.purs b/test/Blockfrost/Contract.purs index 90ba1a67e8..29df2c6b5f 100644 --- a/test/Blockfrost/Contract.purs +++ b/test/Blockfrost/Contract.purs @@ -8,7 +8,7 @@ import Prelude import Contract.Config (testnetConfig) import Contract.Monad (launchAff_) -import Contract.Test.Blockfrost (executePlutipTestsWithBlockfrost) +import Contract.Test.Blockfrost (executeContractTestsWithBlockfrost) import Data.Maybe (Maybe(Nothing, Just)) import Data.Time.Duration (Milliseconds(Milliseconds)) import Effect (Effect) @@ -17,7 +17,7 @@ import Test.Spec.Runner (defaultConfig) as TestSpec main :: Effect Unit main = launchAff_ do - executePlutipTestsWithBlockfrost + executeContractTestsWithBlockfrost TestSpec.defaultConfig { timeout = Just $ Milliseconds 1000000.0 } testnetConfig { suppressLogs = true } Nothing diff --git a/test/Plutip/UtxoDistribution.purs b/test/Plutip/UtxoDistribution.purs index 81ffac3dc1..1440b7c1cd 100644 --- a/test/Plutip/UtxoDistribution.purs +++ b/test/Plutip/UtxoDistribution.purs @@ -40,9 +40,9 @@ import Control.Lazy (fix) import Ctl.Internal.Plutip.Types ( InitialUTxOsWithStakeKey(InitialUTxOsWithStakeKey) ) -import Ctl.Internal.Plutip.UtxoDistribution (encodeDistribution, keyWallets) import Ctl.Internal.Plutus.Types.Transaction (UtxoMap) import Ctl.Internal.Test.TestPlanM (TestPlanM) +import Ctl.Internal.Test.UtxoDistribution (encodeDistribution, keyWallets) import Data.Array (foldl, head, replicate, zip) import Data.BigInt (BigInt) import Data.BigInt (fromInt, toString) as BigInt From b9dd9af00c587acf26157b94b2b79663c8353d55 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Tue, 7 Feb 2023 20:44:48 +0400 Subject: [PATCH 345/373] Fix link in doc/blockfrost.md --- doc/blockfrost.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/doc/blockfrost.md b/doc/blockfrost.md index b121f77418..9238284851 100644 --- a/doc/blockfrost.md +++ b/doc/blockfrost.md @@ -18,7 +18,7 @@ Thanks to [Catalyst Fund9](https://cardano.ideascale.com/c/idea/420791), CTL has been extended with support for [Blockfrost](https://blockfrost.io/) as an alternative query layer. -The users [can now run]((#running-contracts-with-blockfrost)) CTL contracts just by providing a Blockfrost API key and some ADA for the Contract to consume. +The users [can now run](#running-contracts-with-blockfrost) CTL contracts just by providing a Blockfrost API key and some ADA for the Contract to consume. For testing, we offer an automated test engine that allows to run any `ContractTest` test suite with Blockfrost. From 5661db38556d2deb2f79532c36569d534b864cb7 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Tue, 7 Feb 2023 20:53:57 +0400 Subject: [PATCH 346/373] Apply suggestions --- src/Contract/Test/Blockfrost.purs | 2 +- src/Internal/Wallet/KeyFile.purs | 7 +++---- 2 files changed, 4 insertions(+), 5 deletions(-) diff --git a/src/Contract/Test/Blockfrost.purs b/src/Contract/Test/Blockfrost.purs index 71e27461a0..b99520840c 100644 --- a/src/Contract/Test/Blockfrost.purs +++ b/src/Contract/Test/Blockfrost.purs @@ -41,7 +41,7 @@ import Test.Spec.Runner (Config) -- | -- | - Private payment and (optionally) stake keys -- | - A directory to store temporary private keys that will be used in tests. --- | In case of a suddent test interruption, funds will not be lost since +-- | In case of a sudden test interruption, funds will not be lost because -- | the private keys will be saved to files. type BlockfrostKeySetup = { privateKeySources :: diff --git a/src/Internal/Wallet/KeyFile.purs b/src/Internal/Wallet/KeyFile.purs index 8984c54fb2..4da77b7dd5 100644 --- a/src/Internal/Wallet/KeyFile.purs +++ b/src/Internal/Wallet/KeyFile.purs @@ -15,6 +15,7 @@ import Prelude import Aeson (encodeAeson) import Control.Monad.Error.Class (liftMaybe) +import Control.Monad.Except (catchError) import Ctl.Internal.Cardano.TextEnvelope ( TextEnvelope(TextEnvelope) , TextEnvelopeType @@ -33,10 +34,9 @@ import Ctl.Internal.Wallet.Key ( PrivatePaymentKey(PrivatePaymentKey) , PrivateStakeKey(PrivateStakeKey) ) -import Data.Either (either) import Data.Maybe (Maybe(Nothing)) import Data.Newtype (wrap) -import Effect.Aff (Aff, try) +import Effect.Aff (Aff) import Effect.Class (liftEffect) import Effect.Exception (error, throw) import Node.Encoding as Encoding @@ -54,14 +54,13 @@ keyFromFile filePath ty = errorHandler do pure envelope.bytes where errorHandler action = do - try action >>= either + catchError action ( \err -> do liftEffect $ throw $ "Unable to load key from file: " <> show filePath <> ", error: " <> show err ) - pure privatePaymentKeyFromTextEnvelope :: TextEnvelope -> Maybe PrivatePaymentKey privatePaymentKeyFromTextEnvelope (TextEnvelope envelope) = do From 365f79b4ea408edd5f242d0f0498bd4e10f762d2 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Wed, 8 Feb 2023 01:08:55 +0400 Subject: [PATCH 347/373] Document test suites. --- README.md | 7 ++++--- doc/plutip-testing.md | 33 +++------------------------------ doc/testing.md | 41 +++++++++++++++++++++++++++++++++++++++++ 3 files changed, 48 insertions(+), 33 deletions(-) create mode 100644 doc/testing.md diff --git a/README.md b/README.md index 4608e54be1..516870efbd 100644 --- a/README.md +++ b/README.md @@ -37,9 +37,10 @@ Please explore our documentation to discover how to use CTL, how to set up its r - [Blockfrost support](./doc/blockfrost.md) - [Getting started writing CTL contracts](./doc/getting-started.md) - [Migrating from Plutus to CTL](./doc/plutus-comparison.md) -- [Testing contracts with Plutip](./doc/plutip-testing.md) -- [End-to-end testing with headless browsers](./doc/e2e-testing.md) -- [Utilities for testing](./doc/test-utils.md) +- [Testing overview](./doc/testing.md) + - [Testing contracts with Plutip](./doc/plutip-testing.md) + - [End-to-end testing with headless browsers](./doc/e2e-testing.md) + - [Utilities for testing](./doc/test-utils.md) - [CIP-25 NFT standard support](./doc/cip-25-nfts.md) - [Transaction balancing](./doc/balancing.md) - [Transaction chaining](./doc/tx-chaining.md) diff --git a/doc/plutip-testing.md b/doc/plutip-testing.md index 3d4160c2a1..08a1db5e2c 100644 --- a/doc/plutip-testing.md +++ b/doc/plutip-testing.md @@ -13,7 +13,7 @@ - [Note on SIGINT](#note-on-sigint) - [Testing with Nix](#testing-with-nix) - [Using addresses with staking key components](#using-addresses-with-staking-key-components) -- [CTL/Plutip utilities for testing](#ctlplutip-utilities-for-testing) + - [See also](#see-also) ## Architecture @@ -193,33 +193,6 @@ Although stake keys serve no real purpose in plutip context, they allow to use b Note that CTL re-distributes tADA from payment key-only ("enterprise") addresses to base addresses, which requires a few transactions before the test can be run. Plutip can currently handle only enterprise addreses (see [this issue](https://github.com/mlabs-haskell/plutip/issues/103)). -## CTL/Plutip utilities for testing +### See also -`Contract.Test.Utils` module provides a DSL for assertions that accumulate error messages, instead of exiting early after the first failure. - -The interpreter is `withAssertions` function, that accepts two kinds of assertions: - -- `ContractBasicAssertion` is simply executed at the end of the `Contract` lifetime and only needs the result of the `Сontract` -- `ContractWrapAssertion` can inspect the state both before and after `Contract` execution, allowing to monitor for effects, e.g. monetary gains/losses at address - -`withAssertions` allows mixing both of them via a `ContractAssertions` typeclass: - -```purescript -withAssertions - :: forall (r :: Row Type) (a :: Type) (assertions :: Type) - . ContractAssertions assertions r a - => assertions - -> Contract r a - -> Contract r a -``` - -The typeclass allows to combine multiple assertions using `Array`s and `Tuple`s. For example, `assertions` type variable from the snippet above can be instantiated with something like this: - -```purescript -Array (ContractWrapAssertion () ContractResult) - /\ Array (ContractBasicAssertion () ContractResult Unit) -``` - -Particular values can be constructed with utility functions, as demonstrated in the [ContractTestUtils example](../examples/ContractTestUtils.purs) (see `mkAssertions`). - -All the functions require `Labeled` arguments, that can be constructed with `label` function; or `noLabel`, if descriptive names in error messages are not needed. +- To actually write the test bodies, [assertions library](./test-utils.md) can be useful. diff --git a/doc/testing.md b/doc/testing.md new file mode 100644 index 0000000000..19de1f4297 --- /dev/null +++ b/doc/testing.md @@ -0,0 +1,41 @@ + + +# Testing CTL `Contract`s + +This page summarizes various approaches to testing with CTL. + +## Testing with Plutip + +Plutip is a tool that allows to manage temporary `cardano-node` clusters. CTL has a test engine that controls these clusters and runs users' `Contract`s in their disposable environment. No setup is needed. + +[See here for more info](./plutip-testing.md). + +## Testing with a headless browser (E2E testing) + +"E2E test engine", in our terminology, is a set of APIs we provide to faciliate running tests in real browsers in headless mode. The test engine handles browser startup, interaction with the page, and, most importantly, it clicks through the wallet UI when there is a need to confirm transactions. + +[See here for more info](./e2e-testing.md) + +## Key wallets + +Key wallet is a special kind of wallet that simply wraps a private key. + +See `Contract.Wallet.Key` and `Contract.Wallet.KeyFile` for its interface. + +## CIP-30 mocking + +It is possible to test `Contract`s that explicitly use wallet connections in NodeJS environment. But actual wallet calls will be replaced by mock methods. + +See `Contract.Test.Cip30Mock` module. + +## Plutip and CIP-30 mocking in headless browsers + +We also provide abilities to test `Contract`s in a headless browser using query layer of a temporary Plutip cluster as backend and CIP-30 mock instead of a wallet. This method provides stronger guarantees than just CIP-30 mocking in NodeJS, while retaining the ability to be used in Nix builds (by not depending on a real light wallet extension). + +[See here for more info](./e2e-testing.md#using-cip-30-mock-with-plutip). + +## Assertion helpers in PureScript + +Assertion utilities in PureScript can be used in any testing environment, because they work in `Contract` monad. It is possible to define dynamic properties, like asset gains or script execution budgets. + +[See here for more info](./test-utils.md) From 0ba2dc54726f7878eddd6865436b23891fd4ed08 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Thu, 9 Feb 2023 17:26:35 +0400 Subject: [PATCH 348/373] Update docs for E2E --- doc/e2e-testing.md | 11 +++++++++-- 1 file changed, 9 insertions(+), 2 deletions(-) diff --git a/doc/e2e-testing.md b/doc/e2e-testing.md index ed2e70cfed..fac4988ed9 100644 --- a/doc/e2e-testing.md +++ b/doc/e2e-testing.md @@ -8,6 +8,7 @@ CTL comes with advanced machinery for E2E testing in the browser, which can be u - [Parts Involved](#parts-involved) +- [User perspective](#user-perspective) - [How to Run the Included Examples](#how-to-run-the-included-examples) - [How Wallets are Used](#how-wallets-are-used) - [Where to Find the Installed Extensions](#where-to-find-the-installed-extensions) @@ -31,7 +32,7 @@ CTL comes with advanced machinery for E2E testing in the browser, which can be u is used to drive the tests. Supported browsers are [Chromium](https://www.chromium.org/) and Google Chrome. The browser can be run headless (default) or headful (useful during test development). -Any programs that should be tested must be deployed and running on some testserver (e.g. for the included examples we use `make run-dev`). The test suite accepts a list of URLs. +Any `Contract` that should be tested must be deployed and running on some testserver (e.g. for the included examples we use `npm run e2e-test`). The test suite accepts a list of URLs. The test suite requires a set of CRX (chrome extension) files, as well as an archive with user settings. Extension and wallet settings can optionally be configured to be fetched from a URL. @@ -39,6 +40,12 @@ Each extension should be provided with its extension ID and wallet password. For a working example see `test/E2E.purs`. It can be run conveniently using `npm run e2e-test`. +## User perspective + +- Use `npm run e2e-serve` to [serve]((#serving-the-contract-to-be-tested) the examples for testing. +- Use `npm run e2e-test` to run the test suite in headless mode or `npm run e2e-test-debug` to enable the browser UI. +- Use `npm run e2e-browser` to open the browser window with extensions pre-loaded. If you modify any setting (e.g. set a collateral), it's important to run `npm run e2e-pack-settings` **without running anything in between**. The test suite resets the settings by loading them from the settings archive before each test run. + ## How to Run the Included Examples The process is as follows: @@ -191,7 +198,7 @@ Unarchive the CRX, put the encoded public key to `key` property of `manifest.jso ### Serving the Contract to be tested -The test suite accepts URLs, which means that the Contract you want to test must be served. +The test suite accepts URLs, which means that the `Contract` you want to test must be served. It's up to the user how to set up the web server (see `make run-dev` for an example), but in order for the testing engine to "see" the contract, the configuration parameters must be changed: From 2b596df8e11cf08163efd4b1d172da13aefb7c22 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Fri, 10 Feb 2023 19:59:31 +0400 Subject: [PATCH 349/373] Implement getPoolIds for Blockfrost --- src/Contract/Staking.purs | 11 +++- src/Internal/Cardano/Types/Transaction.purs | 1 + src/Internal/Contract/QueryHandle.purs | 7 ++- src/Internal/Serialization/Address.purs | 16 ++--- src/Internal/Service/Blockfrost.purs | 69 ++++++++++++++++++++- 5 files changed, 93 insertions(+), 11 deletions(-) diff --git a/src/Contract/Staking.purs b/src/Contract/Staking.purs index 5efce834c7..3937a3364d 100644 --- a/src/Contract/Staking.purs +++ b/src/Contract/Staking.purs @@ -14,15 +14,24 @@ import Ctl.Internal.Cardano.Types.Transaction , PoolRegistrationParams ) import Ctl.Internal.Contract.Monad (wrapQueryM) +import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.QueryM.Pools (DelegationsAndRewards) import Ctl.Internal.QueryM.Pools (DelegationsAndRewards) as X import Ctl.Internal.QueryM.Pools as QueryM import Ctl.Internal.Types.PubKeyHash (StakePubKeyHash) import Ctl.Internal.Types.Scripts (StakeValidatorHash) +import Data.Either (either) import Data.Maybe (Maybe) +import Effect.Aff.Class (liftAff) +import Effect.Class (liftEffect) +import Effect.Exception (throw) getPoolIds :: Contract (Array PoolPubKeyHash) -getPoolIds = wrapQueryM QueryM.getPoolIds +getPoolIds = do + queryHandle <- getQueryHandle + liftAff $ + queryHandle.getPoolIds + >>= either (liftEffect <<< throw <<< show) pure getPoolParameters :: PoolPubKeyHash diff --git a/src/Internal/Cardano/Types/Transaction.purs b/src/Internal/Cardano/Types/Transaction.purs index aa389abfd1..c443f23fbd 100644 --- a/src/Internal/Cardano/Types/Transaction.purs +++ b/src/Internal/Cardano/Types/Transaction.purs @@ -620,6 +620,7 @@ newtype PoolPubKeyHash = PoolPubKeyHash Ed25519KeyHash derive instance Newtype PoolPubKeyHash _ derive instance Eq PoolPubKeyHash +derive instance Ord PoolPubKeyHash derive instance Generic PoolPubKeyHash _ instance EncodeAeson PoolPubKeyHash where diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs index ddd97c90c6..6e94142256 100644 --- a/src/Internal/Contract/QueryHandle.purs +++ b/src/Internal/Contract/QueryHandle.purs @@ -11,7 +11,8 @@ import Control.Monad.Error.Class (throwError) import Control.Monad.Reader.Class (ask) import Ctl.Internal.Cardano.Types.ScriptRef (ScriptRef) import Ctl.Internal.Cardano.Types.Transaction - ( Transaction + ( PoolPubKeyHash + , Transaction , TransactionOutput , UtxoMap ) @@ -41,6 +42,7 @@ import Ctl.Internal.QueryM.Ogmios ( SubmitTxR(SubmitTxSuccess, SubmitFail) , TxEvaluationR ) +import Ctl.Internal.QueryM.Pools (getPoolIds) as QueryM import Ctl.Internal.Serialization (convertTransaction, toBytes) as Serialization import Ctl.Internal.Serialization.Address (Address) import Ctl.Internal.Serialization.Hash (ScriptHash) @@ -80,6 +82,7 @@ type QueryHandle = , submitTx :: Transaction -> Aff (Either ClientError TransactionHash) , evaluateTx :: Transaction -> Ogmios.AdditionalUtxoSet -> Aff TxEvaluationR , getEraSummaries :: AffE EraSummaries + , getPoolIds :: Aff (Either ClientError (Array PoolPubKeyHash)) } getQueryHandle :: Contract QueryHandle @@ -114,6 +117,7 @@ queryHandleForCtlBackend contractEnv backend = (Serialization.convertTransaction tx) QueryM.evaluateTxOgmios txBytes additionalUtxos , getEraSummaries: Right <$> runQueryM' QueryM.getEraSummaries + , getPoolIds: Right <$> runQueryM' QueryM.getPoolIds } where runQueryM' :: forall (a :: Type). QueryM a -> Aff a @@ -139,6 +143,7 @@ queryHandleForBlockfrostBackend contractEnv backend = logWarn' "Blockfrost does not support explicit additional utxos" Blockfrost.evaluateTx tx , getEraSummaries: runBlockfrostServiceM' Blockfrost.getEraSummaries + , getPoolIds: runBlockfrostServiceM' Blockfrost.getPoolIds } where runBlockfrostServiceM' :: forall (a :: Type). BlockfrostServiceM a -> Aff a diff --git a/src/Internal/Serialization/Address.purs b/src/Internal/Serialization/Address.purs index 3cd781aadb..c4432174c8 100644 --- a/src/Internal/Serialization/Address.purs +++ b/src/Internal/Serialization/Address.purs @@ -59,7 +59,6 @@ module Ctl.Internal.Serialization.Address , enterpriseAddressNetworkId , paymentKeyHashEnterpriseAddress , scriptHashEnterpriseAddress - , networkIdtoInt , pointerAddress , pointerAddressPaymentCred , pointerAddressToAddress @@ -361,7 +360,7 @@ baseAddress , delegationCred :: StakeCredential } -> BaseAddress -baseAddress = _baseAddress networkIdtoInt +baseAddress = _baseAddress networkIdToInt foreign import baseAddressPaymentCred :: BaseAddress -> StakeCredential foreign import baseAddressDelegationCred :: BaseAddress -> StakeCredential @@ -381,8 +380,11 @@ instance EncodeAeson NetworkId where TestnetId -> encodeTagged' "TestnetId" {} MainnetId -> encodeTagged' "MainnetId" {} -networkIdtoInt :: NetworkId -> Int -networkIdtoInt = case _ of +instance Ord NetworkId where + compare = compare `on` networkIdToInt + +networkIdToInt :: NetworkId -> Int +networkIdToInt = case _ of TestnetId -> 0 MainnetId -> 1 @@ -524,7 +526,7 @@ foreign import _enterpriseAddress enterpriseAddress :: { network :: NetworkId, paymentCred :: StakeCredential } -> EnterpriseAddress -enterpriseAddress = _enterpriseAddress networkIdtoInt +enterpriseAddress = _enterpriseAddress networkIdToInt paymentKeyHashEnterpriseAddress :: NetworkId -> Ed25519KeyHash -> EnterpriseAddress @@ -580,7 +582,7 @@ pointerAddress , stakePointer :: Pointer } -> PointerAddress -pointerAddress = _pointerAddress networkIdtoInt +pointerAddress = _pointerAddress networkIdToInt paymentKeyHashPointerAddress :: NetworkId -> Ed25519KeyHash -> Pointer -> PointerAddress @@ -631,7 +633,7 @@ foreign import _rewardAddress rewardAddress :: { network :: NetworkId, paymentCred :: StakeCredential } -> RewardAddress -rewardAddress = _rewardAddress networkIdtoInt +rewardAddress = _rewardAddress networkIdToInt foreign import rewardAddressPaymentCred :: RewardAddress -> StakeCredential foreign import _rewardAddressFromAddress diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index a20a406d6f..6742a242ce 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -17,7 +17,11 @@ module Ctl.Internal.Service.Blockfrost , TransactionMetadata , UtxosAtAddress , UtxosOfTransaction + , PoolIds + , PoolParameters + , DelegationsAndRewards ) + , BlockfrostStakeCredential(BlockfrostStakeCredential) , BlockfrostEraSummaries(BlockfrostEraSummaries) , BlockfrostMetadata(BlockfrostMetadata) , BlockfrostNativeScript(BlockfrostNativeScript) @@ -47,6 +51,7 @@ module Ctl.Internal.Service.Blockfrost , runBlockfrostServiceTestM , submitTx , utxosAt + , getPoolIds ) where import Prelude @@ -95,9 +100,11 @@ import Ctl.Internal.Cardano.Types.ScriptRef ) import Ctl.Internal.Cardano.Types.Transaction ( Costmdls(Costmdls) + , PoolPubKeyHash , Transaction , TransactionOutput(TransactionOutput) , UtxoMap + , poolPubKeyHashToBech32 ) import Ctl.Internal.Cardano.Types.Value (Coin(Coin), Value) import Ctl.Internal.Cardano.Types.Value @@ -122,12 +129,15 @@ import Ctl.Internal.QueryM.Ogmios (TxEvaluationR) import Ctl.Internal.Serialization as Serialization import Ctl.Internal.Serialization.Address ( Address + , NetworkId(TestnetId, MainnetId) , addressBech32 , addressFromBech32 ) import Ctl.Internal.Serialization.Hash ( ScriptHash , ed25519KeyHashFromBytes + , ed25519KeyHashToBech32Unsafe + , scriptHashToBech32Unsafe , scriptHashToBytes ) import Ctl.Internal.ServerConfig (ServerConfig, mkHttpUrl) @@ -146,6 +156,7 @@ import Ctl.Internal.Service.Helpers , aesonString , decodeAssetClass ) +import Ctl.Internal.Types.Aliases (Bech32String) import Ctl.Internal.Types.BigNum (BigNum) import Ctl.Internal.Types.BigNum as BigNum import Ctl.Internal.Types.ByteArray (ByteArray, byteArrayToHex) @@ -169,10 +180,12 @@ import Ctl.Internal.Types.ProtocolParameters , convertPlutusV1CostModel , convertPlutusV2CostModel ) +import Ctl.Internal.Types.PubKeyHash (StakePubKeyHash) import Ctl.Internal.Types.Rational (Rational, reduce) import Ctl.Internal.Types.RawBytes (rawBytesToHex) import Ctl.Internal.Types.Scripts - ( Language(PlutusV1, PlutusV2) + ( Language(PlutusV2, PlutusV1) + , StakeValidatorHash , plutusV1Script , plutusV2Script ) @@ -315,6 +328,12 @@ data BlockfrostEndpoint | UtxosAtAddress Address Int Int -- /txs/{hash}/utxos | UtxosOfTransaction TransactionHash + -- /pools?page={page}&count={count}&order=asc + | PoolIds Int Int + -- /pools/{hash} + | PoolParameters PoolPubKeyHash + -- /accounts/{stake_address} + | DelegationsAndRewards BlockfrostStakeCredential derive instance Generic BlockfrostEndpoint _ derive instance Eq BlockfrostEndpoint @@ -357,6 +376,12 @@ realizeEndpoint endpoint = <> ("&count=" <> show count) UtxosOfTransaction txHash -> "/txs/" <> byteArrayToHex (unwrap txHash) <> "/utxos" + PoolIds page count -> + "/pools?page=" <> show page <> "&count=" <> show count <> "&order=asc" + PoolParameters poolPubKeyHash -> + "/pool/" <> poolPubKeyHashToBech32 poolPubKeyHash + DelegationsAndRewards credential -> + "/accounts/" <> blockfrostStakeCredentialToBech32 credential blockfrostGetRequest :: BlockfrostEndpoint @@ -681,6 +706,24 @@ getEraSummaries = runExceptT do ExceptT $ handleBlockfrostResponse <$> blockfrostGetRequest EraSummaries pure $ unwrap eraSummaries +-------------------------------------------------------------------------------- +-- Staking pool IDs +-------------------------------------------------------------------------------- + +getPoolIds :: BlockfrostServiceM (Either ClientError (Array PoolPubKeyHash)) +getPoolIds = runExceptT do + ExceptT (poolsOnPage 1) + where + poolsOnPage + :: Int -> BlockfrostServiceM (Either ClientError (Array PoolPubKeyHash)) + poolsOnPage page = runExceptT do + let maxResultsOnPage = 100 -- blockfrost constant + poolIds <- ExceptT $ + blockfrostGetRequest (PoolIds page maxResultsOnPage) + <#> handle404AsMempty <<< handleBlockfrostResponse + if Array.length poolIds < maxResultsOnPage then pure poolIds + else append poolIds <$> ExceptT (poolsOnPage $ page + 1) + -------------------------------------------------------------------------------- -- BlockfrostSystemStart -------------------------------------------------------------------------------- @@ -1105,6 +1148,29 @@ instance DecodeAeson BlockfrostCurrentEpoch where unwrapBlockfrostCurrentEpoch :: BlockfrostCurrentEpoch -> BigInt unwrapBlockfrostCurrentEpoch = unwrap +data BlockfrostStakeCredential = BlockfrostStakeCredential NetworkId + (Either StakePubKeyHash StakeValidatorHash) + +derive instance Generic BlockfrostStakeCredential _ + +derive instance Eq BlockfrostStakeCredential +derive instance Ord BlockfrostStakeCredential + +instance Show BlockfrostStakeCredential where + show = genericShow + +blockfrostStakeCredentialToBech32 :: BlockfrostStakeCredential -> Bech32String +blockfrostStakeCredentialToBech32 = case _ of + BlockfrostStakeCredential networkId (Left stakePubKeyHash) -> + ed25519KeyHashToBech32Unsafe ("stake" <> networkIdTag networkId) + (unwrap $ unwrap stakePubKeyHash) + BlockfrostStakeCredential networkId (Right stakeValidatorHash) -> + scriptHashToBech32Unsafe ("stake" <> networkIdTag networkId) + (unwrap stakeValidatorHash) + where + networkIdTag TestnetId = "_test" + networkIdTag MainnetId = "" + -------------------------------------------------------------------------------- -- BlockfrostProtocolParameters -------------------------------------------------------------------------------- @@ -1240,4 +1306,3 @@ instance DecodeAeson BlockfrostProtocolParameters where , collateralPercent: raw.collateral_percent , maxCollateralInputs: raw.max_collateral_inputs } - From fc1d1f59d7045212da1a4698189d122cb1aeeb44 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Sat, 11 Feb 2023 20:08:52 +0400 Subject: [PATCH 350/373] - Implemented rewards queries for Blockfrost. - Made getPoolParameters explictly Ogmios-only - Added ability to provide Blockfrost API key via localStorage in the browser - Reorganized UtxoDistribution-related modules (finally untied everything from Plutip --- CHANGELOG.md | 1 + examples/ByUrl.purs | 43 ++++++++- examples/index.html | 5 + package.json | 1 + spago.dhall | 2 + src/Contract/Backend/Ogmios.purs | 21 +++++ src/Contract/Staking.purs | 31 +++---- src/Contract/Test.purs | 9 ++ src/Contract/Test/Plutip.purs | 17 ++-- src/Internal/Contract/QueryHandle.purs | 43 +++++++-- src/Internal/Plutip/Server.purs | 8 +- src/Internal/Plutip/Types.purs | 21 +---- src/Internal/QueryM/Pools.purs | 10 +- src/Internal/Service/Blockfrost.purs | 93 ++++++++++++++++--- src/Internal/Test/KeyDir.purs | 10 +- src/Internal/Test/UtxoDistribution.purs | 42 ++++++--- src/Internal/Types/DelegationsAndRewards.purs | 13 +++ templates/ctl-scaffold/packages.dhall | 2 + test/Blockfrost/Contract.purs | 5 +- test/E2E.purs | 6 +- test/Fixtures.purs | 1 + test/Integration.purs | 43 ++++++++- test/Plutip/Contract.purs | 4 +- test/Plutip/Contract/Assert.purs | 7 +- test/Plutip/Contract/NetworkId.purs | 9 +- test/Plutip/Staking.purs | 2 +- test/Plutip/UtxoDistribution.purs | 7 +- test/QueryM/AffInterface.purs | 6 +- 28 files changed, 338 insertions(+), 124 deletions(-) create mode 100644 src/Contract/Backend/Ogmios.purs create mode 100644 src/Internal/Types/DelegationsAndRewards.purs diff --git a/CHANGELOG.md b/CHANGELOG.md index 8454a19fef..c07ec2c526 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -60,6 +60,7 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) - Balancer no longer selects UTxOs which use PlutusV2 features when the transaction contains PlutusV1 scripts ([#1349](https://github.com/Plutonomicon/cardano-transaction-lib/issues/1349)) - `startPlutipCluster` error message now includes cluster startup failure details. ([#1407](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1407)) - `PlutipTest` is now known as `Contract.Test.ContractTest`. It has been semantically untied from Plutip, because we now have another test runner for tests that rely on particular funds distributions - [Blockfrost](./doc/blockfrost.md). See `Contract.Test.Blockfrost.runContractTestsWithBlockfrost`. +- `Contract.Staking.getPoolParameters` has been moved to `Contract.Backend.Ogmios.getPoolParameters`. This function only runs with Ogmios backend, because Blockfrost [does not provide](https://github.com/blockfrost/blockfrost-backend-ryo/issues/82) all the required values. ### Removed diff --git a/examples/ByUrl.purs b/examples/ByUrl.purs index 8a1644e045..a7d5347ed6 100644 --- a/examples/ByUrl.purs +++ b/examples/ByUrl.purs @@ -4,11 +4,13 @@ import Prelude import Contract.Config ( ContractParams + , blockfrostPublicPreviewServerConfig , mainnetFlintConfig , mainnetGeroConfig , mainnetLodeConfig , mainnetNamiConfig , mainnetNuFiConfig + , mkBlockfrostBackendParams , testnetEternlConfig , testnetFlintConfig , testnetGeroConfig @@ -44,15 +46,40 @@ import Ctl.Internal.Wallet.Cip30Mock ) import Data.Map (Map) import Data.Map as Map -import Data.Maybe (Maybe(Just, Nothing)) +import Data.Maybe (Maybe(Just, Nothing), isNothing) +import Data.Time.Duration (Seconds(Seconds)) import Data.Tuple.Nested (type (/\), (/\)) import Effect (Effect) +import Effect.Console as Console import Test.Ctl.ApplyArgs as ApplyArgs +import Web.HTML (window) +import Web.HTML.Window (localStorage) +import Web.Storage.Storage (getItem) main :: Effect Unit main = do - addLinks wallets examples - route wallets examples + -- Read Blockfrost API key from the browser storage. + -- To set it up, run `npm run e2e-browser` and follow the instructions. + mbApiKey <- getBlockfrostApiKey + let + walletsWithBlockfrost = + wallets `Map.union` Map.fromFoldable + [ "blockfrost-nami-preview" /\ mkBlockfrostPreviewNamiConfig mbApiKey /\ + Nothing + ] + addLinks walletsWithBlockfrost examples + route walletsWithBlockfrost examples + +getBlockfrostApiKey :: Effect (Maybe String) +getBlockfrostApiKey = do + storage <- localStorage =<< window + res <- getItem "BLOCKFROST_API_KEY" storage + when (isNothing res) do + Console.log + "Set BLOCKFROST_API_KEY LocalStorage key to use Blockfrost services." + Console.log "Run this in the browser console:" + Console.log " localStorage.setItem('BLOCKFROST_API_KEY', 'your-key-here');" + pure res wallets :: Map E2EConfigName (ContractParams /\ Maybe WalletMock) wallets = Map.fromFoldable @@ -74,6 +101,16 @@ wallets = Map.fromFoldable , "plutip-nufi-mock" /\ mainnetNuFiConfig /\ Just MockNuFi ] +mkBlockfrostPreviewNamiConfig :: Maybe String -> ContractParams +mkBlockfrostPreviewNamiConfig apiKey = + testnetNamiConfig + { backendParams = mkBlockfrostBackendParams + { blockfrostConfig: blockfrostPublicPreviewServerConfig + , blockfrostApiKey: apiKey + , confirmTxDelay: Just (Seconds 30.0) + } + } + examples :: Map E2ETestName (Contract Unit) examples = Map.fromFoldable [ "AlwaysMints" /\ AlwaysMints.contract diff --git a/examples/index.html b/examples/index.html index 0ed11783fe..3f6e3fa21d 100644 --- a/examples/index.html +++ b/examples/index.html @@ -7,6 +7,11 @@ Examples source code is located in examples/ directory. +
+ To set a Blockfrost API key, run the following in the browser console: +
+    localStorage.setItem('BLOCKFROST_API_KEY', 'your-key-here');
+  
diff --git a/package.json b/package.json index de4da2cfca..f58a6f8e1b 100755 --- a/package.json +++ b/package.json @@ -11,6 +11,7 @@ }, "scripts": { "test": "npm run unit-test && npm run integration-test && npm run plutip-test && npm run staking-test", + "start-runtime": "nix run -L .#ctl-runtime", "integration-test": "spago run --main Test.Ctl.Integration", "blockfrost-test": "source ./test/blockfrost.env && spago run --main Test.Ctl.Blockfrost.Contract", "unit-test": "spago run --main Test.Ctl.Unit", diff --git a/spago.dhall b/spago.dhall index 6190e91436..6059312650 100644 --- a/spago.dhall +++ b/spago.dhall @@ -93,6 +93,8 @@ You can edit this file as you like. , "unfoldable" , "untagged-union" , "variant" + , "web-html" + , "web-storage" ] , packages = ./packages.dhall , sources = diff --git a/src/Contract/Backend/Ogmios.purs b/src/Contract/Backend/Ogmios.purs new file mode 100644 index 0000000000..226202c333 --- /dev/null +++ b/src/Contract/Backend/Ogmios.purs @@ -0,0 +1,21 @@ +-- | Module for backend-specific functions that only work with Ogmios/Kupo backends +module Contract.Backend.Ogmios + ( getPoolParameters + ) where + +import Prelude + +import Contract.Monad (Contract) +import Contract.Transaction (PoolPubKeyHash) +import Ctl.Internal.Cardano.Types.Transaction (PoolRegistrationParams) +import Ctl.Internal.Contract.Monad (wrapQueryM) +import Ctl.Internal.QueryM.Pools as QueryM + +-- | **This function can only run with Ogmios backend** +-- | +-- | Blockfrost does not support fetching the required data: +-- | https://github.com/blockfrost/blockfrost-backend-ryo/issues/82 +getPoolParameters + :: PoolPubKeyHash + -> Contract PoolRegistrationParams +getPoolParameters = wrapQueryM <<< QueryM.getPoolParameters diff --git a/src/Contract/Staking.purs b/src/Contract/Staking.purs index 3937a3364d..db7792e8f6 100644 --- a/src/Contract/Staking.purs +++ b/src/Contract/Staking.purs @@ -1,6 +1,5 @@ module Contract.Staking ( getPoolIds - , getPoolParameters , getPubKeyHashDelegationsAndRewards , getValidatorHashDelegationsAndRewards , module X @@ -9,15 +8,11 @@ module Contract.Staking import Prelude import Contract.Monad (Contract) -import Ctl.Internal.Cardano.Types.Transaction - ( PoolPubKeyHash - , PoolRegistrationParams - ) -import Ctl.Internal.Contract.Monad (wrapQueryM) +import Control.Monad.Reader (asks) +import Ctl.Internal.Cardano.Types.Transaction (PoolPubKeyHash) import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.QueryM.Pools (DelegationsAndRewards) import Ctl.Internal.QueryM.Pools (DelegationsAndRewards) as X -import Ctl.Internal.QueryM.Pools as QueryM import Ctl.Internal.Types.PubKeyHash (StakePubKeyHash) import Ctl.Internal.Types.Scripts (StakeValidatorHash) import Data.Either (either) @@ -33,19 +28,23 @@ getPoolIds = do queryHandle.getPoolIds >>= either (liftEffect <<< throw <<< show) pure -getPoolParameters - :: PoolPubKeyHash - -> Contract PoolRegistrationParams -getPoolParameters = wrapQueryM <<< QueryM.getPoolParameters - getPubKeyHashDelegationsAndRewards :: StakePubKeyHash -> Contract (Maybe DelegationsAndRewards) -getPubKeyHashDelegationsAndRewards = - wrapQueryM <<< QueryM.getPubKeyHashDelegationsAndRewards +getPubKeyHashDelegationsAndRewards stakePubKeyHash = do + queryHandle <- getQueryHandle + networkId <- asks _.networkId + liftAff do + queryHandle.getPubKeyHashDelegationsAndRewards networkId stakePubKeyHash + >>= either (liftEffect <<< throw <<< show) pure getValidatorHashDelegationsAndRewards :: StakeValidatorHash -> Contract (Maybe DelegationsAndRewards) -getValidatorHashDelegationsAndRewards = - wrapQueryM <<< QueryM.getValidatorHashDelegationsAndRewards +getValidatorHashDelegationsAndRewards stakeValidatorHash = do + queryHandle <- getQueryHandle + networkId <- asks _.networkId + liftAff do + queryHandle.getValidatorHashDelegationsAndRewards networkId + stakeValidatorHash + >>= either (liftEffect <<< throw <<< show) pure diff --git a/src/Contract/Test.purs b/src/Contract/Test.purs index 8c07d503a0..591ba8e5af 100644 --- a/src/Contract/Test.purs +++ b/src/Contract/Test.purs @@ -2,8 +2,17 @@ module Contract.Test ( module X ) where +import Contract.Wallet (withKeyWallet) as X import Ctl.Internal.Test.ContractTest ( ContractTest(ContractTest) , noWallet , withWallets ) as X +import Ctl.Internal.Test.UtxoDistribution + ( class UtxoDistribution + , InitialUTxODistribution + , InitialUTxOs + , InitialUTxOsWithStakeKey + , UtxoAmount + , withStakeKey + ) as X diff --git a/src/Contract/Test/Plutip.purs b/src/Contract/Test/Plutip.purs index af7f178f22..9c1371d82c 100644 --- a/src/Contract/Test/Plutip.purs +++ b/src/Contract/Test/Plutip.purs @@ -15,21 +15,24 @@ import Ctl.Internal.Plutip.Server , withPlutipContractEnv ) as X import Ctl.Internal.Plutip.Server (testPlutipContracts) as Server +import Ctl.Internal.Plutip.Types (PlutipConfig) import Ctl.Internal.Plutip.Types - ( InitialUTxODistribution - , InitialUTxOs - , InitialUTxOsWithStakeKey - , PlutipConfig - , UtxoAmount + ( PlutipConfig ) as X -import Ctl.Internal.Plutip.Types (PlutipConfig) import Ctl.Internal.Test.ContractTest (ContractTest) import Ctl.Internal.Test.ContractTest (ContractTest) as Server import Ctl.Internal.Test.ContractTest ( noWallet , withWallets ) as X -import Ctl.Internal.Test.UtxoDistribution (class UtxoDistribution, withStakeKey) as X +import Ctl.Internal.Test.UtxoDistribution + ( class UtxoDistribution + , InitialUTxODistribution + , InitialUTxOs + , InitialUTxOsWithStakeKey(InitialUTxOsWithStakeKey) + , UtxoAmount + , withStakeKey + ) as X import Effect.Aff (Aff) import Mote (MoteT) diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs index 6e94142256..faf68402d2 100644 --- a/src/Internal/Contract/QueryHandle.purs +++ b/src/Internal/Contract/QueryHandle.purs @@ -37,14 +37,20 @@ import Ctl.Internal.QueryM.Kupo , isTxConfirmed , utxosAt ) as Kupo -import Ctl.Internal.QueryM.Ogmios (AdditionalUtxoSet, CurrentEpoch) as Ogmios import Ctl.Internal.QueryM.Ogmios - ( SubmitTxR(SubmitTxSuccess, SubmitFail) + ( AdditionalUtxoSet + , CurrentEpoch + , SubmitTxR(SubmitFail, SubmitTxSuccess) , TxEvaluationR ) -import Ctl.Internal.QueryM.Pools (getPoolIds) as QueryM +import Ctl.Internal.QueryM.Pools (DelegationsAndRewards) +import Ctl.Internal.QueryM.Pools + ( getPoolIds + , getPubKeyHashDelegationsAndRewards + , getValidatorHashDelegationsAndRewards + ) as QueryM import Ctl.Internal.Serialization (convertTransaction, toBytes) as Serialization -import Ctl.Internal.Serialization.Address (Address) +import Ctl.Internal.Serialization.Address (Address, NetworkId) import Ctl.Internal.Serialization.Hash (ScriptHash) import Ctl.Internal.Service.Blockfrost ( BlockfrostServiceM @@ -55,6 +61,8 @@ import Ctl.Internal.Service.Error (ClientError(ClientOtherError)) import Ctl.Internal.Types.Chain as Chain import Ctl.Internal.Types.Datum (DataHash, Datum) import Ctl.Internal.Types.EraSummaries (EraSummaries) +import Ctl.Internal.Types.PubKeyHash (StakePubKeyHash) +import Ctl.Internal.Types.Scripts (StakeValidatorHash) import Ctl.Internal.Types.Transaction (TransactionHash, TransactionInput) import Ctl.Internal.Types.TransactionMetadata (GeneralTransactionMetadata) import Data.Either (Either(Left, Right)) @@ -77,12 +85,16 @@ type QueryHandle = , isTxConfirmed :: TransactionHash -> AffE Boolean , utxosAt :: Address -> AffE UtxoMap , getChainTip :: AffE Chain.Tip - , getCurrentEpoch :: Aff Ogmios.CurrentEpoch + , getCurrentEpoch :: Aff CurrentEpoch -- TODO Capture errors from all backends , submitTx :: Transaction -> Aff (Either ClientError TransactionHash) - , evaluateTx :: Transaction -> Ogmios.AdditionalUtxoSet -> Aff TxEvaluationR + , evaluateTx :: Transaction -> AdditionalUtxoSet -> Aff TxEvaluationR , getEraSummaries :: AffE EraSummaries - , getPoolIds :: Aff (Either ClientError (Array PoolPubKeyHash)) + , getPoolIds :: AffE (Array PoolPubKeyHash) + , getPubKeyHashDelegationsAndRewards :: + NetworkId -> StakePubKeyHash -> AffE (Maybe DelegationsAndRewards) + , getValidatorHashDelegationsAndRewards :: + NetworkId -> StakeValidatorHash -> AffE (Maybe DelegationsAndRewards) } getQueryHandle :: Contract QueryHandle @@ -118,7 +130,14 @@ queryHandleForCtlBackend contractEnv backend = QueryM.evaluateTxOgmios txBytes additionalUtxos , getEraSummaries: Right <$> runQueryM' QueryM.getEraSummaries , getPoolIds: Right <$> runQueryM' QueryM.getPoolIds + , getPubKeyHashDelegationsAndRewards: \_ pubKeyHash -> + Right <$> runQueryM' + (QueryM.getPubKeyHashDelegationsAndRewards pubKeyHash) + , getValidatorHashDelegationsAndRewards: \_ validatorHash -> + Right <$> runQueryM' + (QueryM.getValidatorHashDelegationsAndRewards validatorHash) } + where runQueryM' :: forall (a :: Type). QueryM a -> Aff a runQueryM' = runQueryM contractEnv backend @@ -144,6 +163,16 @@ queryHandleForBlockfrostBackend contractEnv backend = Blockfrost.evaluateTx tx , getEraSummaries: runBlockfrostServiceM' Blockfrost.getEraSummaries , getPoolIds: runBlockfrostServiceM' Blockfrost.getPoolIds + , getPubKeyHashDelegationsAndRewards: \networkId stakePubKeyHash -> + runBlockfrostServiceM' + ( Blockfrost.getPubKeyHashDelegationsAndRewards networkId + stakePubKeyHash + ) + , getValidatorHashDelegationsAndRewards: \networkId stakeValidatorHash -> + runBlockfrostServiceM' + ( Blockfrost.getValidatorHashDelegationsAndRewards networkId + stakeValidatorHash + ) } where runBlockfrostServiceM' :: forall (a :: Type). BlockfrostServiceM a -> Aff a diff --git a/src/Internal/Plutip/Server.purs b/src/Internal/Plutip/Server.purs index 14d12aeb05..810314c649 100644 --- a/src/Internal/Plutip/Server.purs +++ b/src/Internal/Plutip/Server.purs @@ -45,8 +45,6 @@ import Ctl.Internal.Plutip.Spawn import Ctl.Internal.Plutip.Types ( ClusterStartupParameters , ClusterStartupRequest(ClusterStartupRequest) - , InitialUTxODistribution - , InitialUTxOs , PlutipConfig , PrivateKeyResponse(PrivateKeyResponse) , StartClusterResponse(ClusterStartupSuccess, ClusterStartupFailure) @@ -65,6 +63,8 @@ import Ctl.Internal.Test.ContractTest import Ctl.Internal.Test.TestPlanM (TestPlanM) import Ctl.Internal.Test.UtxoDistribution ( class UtxoDistribution + , InitialUTxODistribution + , InitialUTxOs , decodeWallets , encodeDistribution , keyWallets @@ -81,7 +81,7 @@ import Data.HTTP.Method as Method import Data.Log.Level (LogLevel) import Data.Log.Message (Message) import Data.Maybe (Maybe(Nothing, Just), maybe) -import Data.Newtype (over, wrap) +import Data.Newtype (over, unwrap, wrap) import Data.String.CodeUnits (indexOf) as String import Data.String.Pattern (Pattern(Pattern)) import Data.Traversable (foldMap, for, for_, sequence_, traverse_) @@ -319,7 +319,7 @@ startPlutipContractEnv plutipCfg distr cleanupRef = do wallets <- liftContractM "Impossible happened: could not decode wallets. Please report as bug" - $ decodeWallets distr response.privateKeys + $ decodeWallets distr (unwrap <$> response.privateKeys) let walletsArray = keyWallets (Proxy :: Proxy distr) wallets transferFundsFromEnterpriseToBase ourKey walletsArray pure wallets diff --git a/src/Internal/Plutip/Types.purs b/src/Internal/Plutip/Types.purs index 2258b0c4db..be284cd030 100644 --- a/src/Internal/Plutip/Types.purs +++ b/src/Internal/Plutip/Types.purs @@ -2,9 +2,6 @@ module Ctl.Internal.Plutip.Types ( ClusterStartupParameters , ErrorMessage , FilePath - , InitialUTxOs - , InitialUTxODistribution - , InitialUTxOsWithStakeKey(InitialUTxOsWithStakeKey) , PlutipConfig , ClusterStartupRequest(ClusterStartupRequest) , PrivateKeyResponse(PrivateKeyResponse) @@ -19,7 +16,6 @@ module Ctl.Internal.Plutip.Types ) , StopClusterRequest(StopClusterRequest) , StopClusterResponse(StopClusterSuccess, StopClusterFailure) - , UtxoAmount ) where import Prelude @@ -38,10 +34,9 @@ import Ctl.Internal.Contract.Hooks (Hooks) import Ctl.Internal.Deserialization.Keys (privateKeyFromBytes) import Ctl.Internal.Serialization.Types (PrivateKey) import Ctl.Internal.ServerConfig (ServerConfig) +import Ctl.Internal.Test.UtxoDistribution (InitialUTxODistribution) import Ctl.Internal.Types.ByteArray (hexToByteArray) import Ctl.Internal.Types.RawBytes (RawBytes(RawBytes)) -import Ctl.Internal.Wallet.Key (PrivateStakeKey) -import Data.BigInt (BigInt) import Data.Either (Either(Left), note) import Data.Generic.Rep (class Generic) import Data.Log.Level (LogLevel) @@ -76,20 +71,6 @@ type FilePath = String type ErrorMessage = String --- | UTxO amount in Lovelaces -type UtxoAmount = BigInt - --- | A list of UTxOs for a single wallet -type InitialUTxOs = Array UtxoAmount - --- | A wrapper that allows to specify a stake key to attach to a --- | generated pre-funded Address. -data InitialUTxOsWithStakeKey = - InitialUTxOsWithStakeKey PrivateStakeKey InitialUTxOs - --- | A spec for distribution of UTxOs between wallets. -type InitialUTxODistribution = Array InitialUTxOs - newtype ClusterStartupRequest = ClusterStartupRequest { keysToGenerate :: InitialUTxODistribution , epochSize :: UInt diff --git a/src/Internal/QueryM/Pools.purs b/src/Internal/QueryM/Pools.purs index a6c66822f2..1f785cc0f0 100644 --- a/src/Internal/QueryM/Pools.purs +++ b/src/Internal/QueryM/Pools.purs @@ -3,7 +3,7 @@ module Ctl.Internal.QueryM.Pools , getPoolParameters , getPubKeyHashDelegationsAndRewards , getValidatorHashDelegationsAndRewards - , DelegationsAndRewards + , module X ) where import Prelude @@ -12,7 +12,6 @@ import Ctl.Internal.Cardano.Types.Transaction ( PoolPubKeyHash , PoolRegistrationParams ) -import Ctl.Internal.Cardano.Types.Value (Coin) import Ctl.Internal.Helpers (liftM) import Ctl.Internal.QueryM (QueryM, mkOgmiosRequest) import Ctl.Internal.QueryM.Ogmios @@ -28,6 +27,8 @@ import Ctl.Internal.Serialization.Hash , scriptHashToBytes ) import Ctl.Internal.Types.ByteArray (byteArrayToHex) +import Ctl.Internal.Types.DelegationsAndRewards (DelegationsAndRewards) +import Ctl.Internal.Types.DelegationsAndRewards (DelegationsAndRewards) as X import Ctl.Internal.Types.PubKeyHash (StakePubKeyHash) import Ctl.Internal.Types.Scripts (StakeValidatorHash) import Data.Map as Map @@ -62,11 +63,6 @@ getPoolParameters poolPubKeyHash = do ) res -type DelegationsAndRewards = - { rewards :: Maybe Coin - , delegate :: Maybe PoolPubKeyHash - } - getValidatorHashDelegationsAndRewards :: StakeValidatorHash -> QueryM (Maybe DelegationsAndRewards) getValidatorHashDelegationsAndRewards skh = do diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index 6742a242ce..17427cf92a 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -1,6 +1,7 @@ module Ctl.Internal.Service.Blockfrost ( BlockfrostChainTip(BlockfrostChainTip) , BlockfrostCurrentEpoch(BlockfrostCurrentEpoch) + , BlockfrostRewards , BlockfrostEndpoint ( BlockchainGenesis , DatumCbor @@ -52,6 +53,8 @@ module Ctl.Internal.Service.Blockfrost , submitTx , utxosAt , getPoolIds + , getPubKeyHashDelegationsAndRewards + , getValidatorHashDelegationsAndRewards ) where import Prelude @@ -60,7 +63,7 @@ import Aeson ( class DecodeAeson , Aeson , Finite - , JsonDecodeError(TypeMismatch, AtKey, MissingValue) + , JsonDecodeError(TypeMismatch, MissingValue, AtKey) , decodeAeson , decodeJsonString , getField @@ -70,12 +73,19 @@ import Aeson , parseJsonStringToAeson , stringifyAeson , unpackFinite + , (.:) + , (.:!) ) import Affjax (Error, Response, URL, defaultRequest, printError, request) as Affjax import Affjax.RequestBody (RequestBody, arrayView, string) as Affjax import Affjax.RequestHeader (RequestHeader(ContentType, RequestHeader)) as Affjax import Affjax.ResponseFormat (string) as Affjax.ResponseFormat import Affjax.StatusCode (StatusCode(StatusCode)) as Affjax +import Contract.RewardAddress + ( rewardAddressToBech32 + , stakePubKeyHashRewardAddress + , stakeValidatorHashRewardAddress + ) import Control.Alt ((<|>)) import Control.Monad.Error.Class (liftMaybe, throwError) import Control.Monad.Except.Trans (ExceptT(ExceptT), runExceptT) @@ -126,18 +136,17 @@ import Ctl.Internal.Deserialization.Transaction ( convertGeneralTransactionMetadata ) import Ctl.Internal.QueryM.Ogmios (TxEvaluationR) +import Ctl.Internal.QueryM.Pools (DelegationsAndRewards) import Ctl.Internal.Serialization as Serialization import Ctl.Internal.Serialization.Address ( Address - , NetworkId(TestnetId, MainnetId) + , NetworkId , addressBech32 , addressFromBech32 ) import Ctl.Internal.Serialization.Hash ( ScriptHash , ed25519KeyHashFromBytes - , ed25519KeyHashToBech32Unsafe - , scriptHashToBech32Unsafe , scriptHashToBytes ) import Ctl.Internal.ServerConfig (ServerConfig, mkHttpUrl) @@ -473,9 +482,10 @@ withRequestResponseTracing requestData performRequest = do requestMessage :: String requestMessage = case requestData of BlockfrostGetRequestData endpoint -> - show { endpoint } + show { endpoint, url: realizeEndpoint endpoint } BlockfrostPostRequestData endpoint mediaType _ -> - show { endpoint, mediaType {- mbContent -} } + show + { endpoint, mediaType {- mbContent -} , url: realizeEndpoint endpoint } -------------------------------------------------------------------------------- -- Blockfrost response handling @@ -724,6 +734,43 @@ getPoolIds = runExceptT do if Array.length poolIds < maxResultsOnPage then pure poolIds else append poolIds <$> ExceptT (poolsOnPage $ page + 1) +-------------------------------------------------------------------------------- +-- Delegations and rewards +-------------------------------------------------------------------------------- + +getPubKeyHashDelegationsAndRewards + :: NetworkId + -> StakePubKeyHash + -> BlockfrostServiceM (Either ClientError (Maybe DelegationsAndRewards)) +getPubKeyHashDelegationsAndRewards networkId stakePubKeyHash = runExceptT do + rewards <- ExceptT $ + blockfrostGetRequest + ( DelegationsAndRewards $ BlockfrostStakeCredential networkId + (Left stakePubKeyHash) + ) + <#> handle404AsNothing <<< handleBlockfrostResponse + pure $ rewards <#> \(BlockfrostRewards r) -> + { rewards: r.withdrawable_amount + , delegate: r.pool_id + } + +getValidatorHashDelegationsAndRewards + :: NetworkId + -> StakeValidatorHash + -> BlockfrostServiceM (Either ClientError (Maybe DelegationsAndRewards)) +getValidatorHashDelegationsAndRewards networkId stakeValidatorHash = runExceptT + do + rewards <- ExceptT $ + blockfrostGetRequest + ( DelegationsAndRewards $ BlockfrostStakeCredential networkId + (Right stakeValidatorHash) + ) + <#> handle404AsNothing <<< handleBlockfrostResponse + pure $ rewards <#> \(BlockfrostRewards r) -> + { rewards: r.withdrawable_amount + , delegate: r.pool_id + } + -------------------------------------------------------------------------------- -- BlockfrostSystemStart -------------------------------------------------------------------------------- @@ -1162,14 +1209,11 @@ instance Show BlockfrostStakeCredential where blockfrostStakeCredentialToBech32 :: BlockfrostStakeCredential -> Bech32String blockfrostStakeCredentialToBech32 = case _ of BlockfrostStakeCredential networkId (Left stakePubKeyHash) -> - ed25519KeyHashToBech32Unsafe ("stake" <> networkIdTag networkId) - (unwrap $ unwrap stakePubKeyHash) + rewardAddressToBech32 $ stakePubKeyHashRewardAddress networkId + stakePubKeyHash BlockfrostStakeCredential networkId (Right stakeValidatorHash) -> - scriptHashToBech32Unsafe ("stake" <> networkIdTag networkId) - (unwrap stakeValidatorHash) - where - networkIdTag TestnetId = "_test" - networkIdTag MainnetId = "" + rewardAddressToBech32 $ stakeValidatorHashRewardAddress networkId + stakeValidatorHash -------------------------------------------------------------------------------- -- BlockfrostProtocolParameters @@ -1306,3 +1350,26 @@ instance DecodeAeson BlockfrostProtocolParameters where , collateralPercent: raw.collateral_percent , maxCollateralInputs: raw.max_collateral_inputs } + +-------------------------------------------------------------------------------- +-- BlockfrostRewards +-------------------------------------------------------------------------------- + +newtype BlockfrostRewards = BlockfrostRewards + { pool_id :: Maybe PoolPubKeyHash + , withdrawable_amount :: Maybe Coin + } + +instance DecodeAeson BlockfrostRewards where + decodeAeson aeson = do + obj <- decodeAeson aeson + pool_id <- obj .: "pool_id" + withdrawable_amount_mb_str <- obj .:! "withdrawable_amount" + withdrawable_amount <- for withdrawable_amount_mb_str + \withdrawable_amount_str -> + note (TypeMismatch "BigInt") $ map Coin $ BigInt.fromString + withdrawable_amount_str + pure $ BlockfrostRewards + { pool_id + , withdrawable_amount + } diff --git a/src/Internal/Test/KeyDir.purs b/src/Internal/Test/KeyDir.purs index 451a8890e9..a939e13d0d 100644 --- a/src/Internal/Test/KeyDir.purs +++ b/src/Internal/Test/KeyDir.purs @@ -43,17 +43,14 @@ import Control.Monad.Except (throwError) import Control.Monad.Reader (asks, local) import Ctl.Internal.Deserialization.Keys (freshPrivateKey) import Ctl.Internal.Helpers (logWithLevel) -import Ctl.Internal.Plutip.Types - ( PrivateKeyResponse(PrivateKeyResponse) - , UtxoAmount - ) import Ctl.Internal.Plutus.Types.Transaction (_amount, _output) import Ctl.Internal.Plutus.Types.Value (Value, lovelaceValueOf) import Ctl.Internal.Serialization.Address (addressBech32) import Ctl.Internal.Test.ContractTest (ContractTest(ContractTest)) import Ctl.Internal.Test.TestPlanM (TestPlanM) import Ctl.Internal.Test.UtxoDistribution - ( decodeWallets + ( UtxoAmount + , decodeWallets , encodeDistribution , keyWallets ) @@ -131,8 +128,7 @@ runContractTestsWithKeyDir params backup = do distrArray :: Array (Array UtxoAmount) distrArray = encodeDistribution distr - privateKeys <- liftEffect $ for distrArray \_ -> freshPrivateKey <#> - PrivateKeyResponse + privateKeys <- liftEffect $ for distrArray \_ -> freshPrivateKey wallets <- liftMaybe diff --git a/src/Internal/Test/UtxoDistribution.purs b/src/Internal/Test/UtxoDistribution.purs index e6a0aaa867..6306913494 100644 --- a/src/Internal/Test/UtxoDistribution.purs +++ b/src/Internal/Test/UtxoDistribution.purs @@ -6,6 +6,10 @@ module Ctl.Internal.Test.UtxoDistribution , encodeDistribution , transferFundsFromEnterpriseToBase , withStakeKey + , InitialUTxOs + , InitialUTxODistribution + , InitialUTxOsWithStakeKey(InitialUTxOsWithStakeKey) + , UtxoAmount ) where import Prelude @@ -35,13 +39,8 @@ import Contract.Wallet (mkKeyWalletFromPrivateKeys, withKeyWallet) import Control.Alternative (guard) import Control.Monad.Reader (asks) import Control.Monad.State.Trans (StateT(StateT), runStateT) -import Ctl.Internal.Plutip.Types - ( InitialUTxOs - , InitialUTxOsWithStakeKey(InitialUTxOsWithStakeKey) - , PrivateKeyResponse(PrivateKeyResponse) - , UtxoAmount - ) import Ctl.Internal.Plutus.Types.Transaction (UtxoMap) +import Ctl.Internal.Serialization.Types (PrivateKey) import Ctl.Internal.Wallet.Key ( KeyWallet , PrivatePaymentKey(PrivatePaymentKey) @@ -50,6 +49,7 @@ import Ctl.Internal.Wallet.Key ) import Data.Array (head) import Data.Array as Array +import Data.BigInt (BigInt) import Data.FoldableWithIndex (foldMapWithIndex) import Data.List (List, (:)) import Data.Map as Map @@ -62,17 +62,31 @@ import Effect.Class (liftEffect) import Effect.Ref as Ref import Type.Prelude (Proxy(Proxy)) +-- | UTxO amount in Lovelaces +type UtxoAmount = BigInt + +-- | A list of UTxOs for a single wallet +type InitialUTxOs = Array UtxoAmount + +-- | A wrapper that allows to specify a stake key to attach to a +-- | generated pre-funded Address. +data InitialUTxOsWithStakeKey = + InitialUTxOsWithStakeKey PrivateStakeKey InitialUTxOs + +-- | A spec for distribution of UTxOs between wallets. +type InitialUTxODistribution = Array InitialUTxOs + -- | A type class that implements a type-safe interface for specifying UTXO -- | distribution for wallets. -- | Number of wallets in distribution specification matches the number of -- | wallets provided to the user. class UtxoDistribution distr wallets | distr -> wallets where encodeDistribution :: distr -> Array (Array UtxoAmount) - decodeWallets :: distr -> Array PrivateKeyResponse -> Maybe wallets + decodeWallets :: distr -> Array PrivateKey -> Maybe wallets decodeWallets' :: distr - -> Array PrivateKeyResponse - -> Maybe (wallets /\ Array PrivateKeyResponse) + -> Array PrivateKey + -> Maybe (wallets /\ Array PrivateKey) keyWallets :: Proxy distr -> wallets -> Array KeyWallet instance UtxoDistribution Unit Unit where @@ -85,7 +99,7 @@ instance UtxoDistribution InitialUTxOs KeyWallet where encodeDistribution amounts = [ amounts ] decodeWallets d p = decodeWalletsDefault d p decodeWallets' _ pks = Array.uncons pks <#> - \{ head: PrivateKeyResponse key, tail } -> + \{ head: key, tail } -> (privateKeysToKeyWallet (PrivatePaymentKey key) Nothing) /\ tail keyWallets _ wallet = [ wallet ] @@ -93,7 +107,7 @@ instance UtxoDistribution InitialUTxOsWithStakeKey KeyWallet where encodeDistribution (InitialUTxOsWithStakeKey _ amounts) = [ amounts ] decodeWallets d p = decodeWalletsDefault d p decodeWallets' (InitialUTxOsWithStakeKey stake _) pks = Array.uncons pks <#> - \{ head: PrivateKeyResponse key, tail } -> + \{ head: key, tail } -> privateKeysToKeyWallet (PrivatePaymentKey key) (Just stake) /\ tail keyWallets _ wallet = [ wallet ] @@ -121,8 +135,8 @@ decodeWallets'Array :: forall (distr :: Type) . UtxoDistribution distr KeyWallet => Array distr - -> Array PrivateKeyResponse - -> Maybe (Array KeyWallet /\ Array PrivateKeyResponse) + -> Array PrivateKey + -> Maybe (Array KeyWallet /\ Array PrivateKey) decodeWallets'Array = runStateT <<< traverse (StateT <<< decodeWallets') keyWalletsArray @@ -153,7 +167,7 @@ decodeWalletsDefault :: forall distr wallets . UtxoDistribution distr wallets => distr - -> Array PrivateKeyResponse + -> Array PrivateKey -> Maybe wallets decodeWalletsDefault d p = do wallets /\ remainingPKeys <- decodeWallets' d p diff --git a/src/Internal/Types/DelegationsAndRewards.purs b/src/Internal/Types/DelegationsAndRewards.purs new file mode 100644 index 0000000000..fbe25d1e72 --- /dev/null +++ b/src/Internal/Types/DelegationsAndRewards.purs @@ -0,0 +1,13 @@ +module Ctl.Internal.Types.DelegationsAndRewards + ( DelegationsAndRewards + ) where + +import Data.Maybe + +import Ctl.Internal.Cardano.Types.Transaction (PoolPubKeyHash) +import Ctl.Internal.Cardano.Types.Value (Coin) + +type DelegationsAndRewards = + { rewards :: Maybe Coin + , delegate :: Maybe PoolPubKeyHash + } diff --git a/templates/ctl-scaffold/packages.dhall b/templates/ctl-scaffold/packages.dhall index 1423766524..bb68739060 100644 --- a/templates/ctl-scaffold/packages.dhall +++ b/templates/ctl-scaffold/packages.dhall @@ -349,6 +349,8 @@ let additions = , "unfoldable" , "untagged-union" , "variant" + , "web-storage" + , "web-html" ] , repo = "https://github.com/Plutonomicon/cardano-transaction-lib.git" , version = "1816887c0772652f01bbd82ed42d759daa816d1d" diff --git a/test/Blockfrost/Contract.purs b/test/Blockfrost/Contract.purs index 29df2c6b5f..7d1e1a2e19 100644 --- a/test/Blockfrost/Contract.purs +++ b/test/Blockfrost/Contract.purs @@ -12,6 +12,7 @@ import Contract.Test.Blockfrost (executeContractTestsWithBlockfrost) import Data.Maybe (Maybe(Nothing, Just)) import Data.Time.Duration (Milliseconds(Milliseconds)) import Effect (Effect) +import Test.Ctl.Integration as IntegrationTest import Test.Ctl.Plutip.Contract as Plutip import Test.Spec.Runner (defaultConfig) as TestSpec @@ -21,4 +22,6 @@ main = launchAff_ do TestSpec.defaultConfig { timeout = Just $ Milliseconds 1000000.0 } testnetConfig { suppressLogs = true } Nothing - Plutip.suite + do + Plutip.suite + IntegrationTest.stakingSuite diff --git a/test/E2E.purs b/test/E2E.purs index 5152f2ae50..9ab8e894c6 100644 --- a/test/E2E.purs +++ b/test/E2E.purs @@ -3,12 +3,14 @@ module Test.Ctl.E2E (main) where import Prelude import Contract.Test.E2E (parseCliArgs, runE2ECommand) +import Contract.Test.Utils (interruptOnSignal) +import Data.Posix.Signal (Signal(SIGINT)) import Effect (Effect) -import Effect.Aff (launchAff_) +import Effect.Aff (launchAff) -- Run with `spago test --main Test.Ctl.E2E` main :: Effect Unit main = do options <- parseCliArgs - launchAff_ do + interruptOnSignal SIGINT =<< launchAff do runE2ECommand options diff --git a/test/Fixtures.purs b/test/Fixtures.purs index 6984b1df90..7a87697d10 100644 --- a/test/Fixtures.purs +++ b/test/Fixtures.purs @@ -72,6 +72,7 @@ module Test.Ctl.Fixtures , witnessSetFixture3 , witnessSetFixture3Value , witnessSetFixture4 + , ed25519KeyHash1 ) where import Prelude diff --git a/test/Integration.purs b/test/Integration.purs index d74eb3a17b..697b2fa5a7 100644 --- a/test/Integration.purs +++ b/test/Integration.purs @@ -1,27 +1,38 @@ -module Test.Ctl.Integration (main, testPlan) where +module Test.Ctl.Integration (main, testPlan, stakingSuite) where import Prelude +import Contract.Address (Ed25519KeyHash, StakePubKeyHash(StakePubKeyHash)) +import Contract.Backend.Ogmios (getPoolParameters) import Contract.Config (testnetConfig) import Contract.Monad (runContract) +import Contract.Prim.ByteArray (hexToByteArrayUnsafe) +import Contract.Staking (getPoolIds, getPubKeyHashDelegationsAndRewards) +import Contract.Test (ContractTest, noWallet) import Contract.Test.Mote (TestPlanM, interpretWithConfig) import Contract.Test.Utils (exitCode, interruptOnSignal) import Contract.Time (getEraSummaries, getSystemStart) import Ctl.Internal.Contract.Monad (wrapQueryM) -import Data.Maybe (Maybe(Just)) +import Ctl.Internal.Serialization.Hash (ed25519KeyHashFromBytes) +import Data.Maybe (Maybe(Just, Nothing), fromJust) +import Data.Newtype (wrap) import Data.Posix.Signal (Signal(SIGINT)) import Data.Time.Duration (Milliseconds(Milliseconds)) +import Data.Traversable (traverse) import Effect (Effect) import Effect.Aff (Aff, cancelWith, effectCanceler, launchAff) import Effect.Class (liftEffect) -import Mote (skip) +import Mote (group, skip, test) import Mote.Monad (mapTest) +import Partial.Unsafe (unsafePartial) import Test.Ctl.BalanceTx.Collateral as Collateral import Test.Ctl.BalanceTx.Time as BalanceTx.Time +import Test.Ctl.Fixtures (ed25519KeyHash1) import Test.Ctl.Logging as Logging import Test.Ctl.PrivateKey as PrivateKey import Test.Ctl.QueryM.AffInterface as QueryM.AffInterface import Test.Ctl.Types.Interval as Types.Interval +import Test.Spec.Assertions (shouldEqual) import Test.Spec.Runner (defaultConfig) -- Run with `spago test --main Test.Ctl.Integration` @@ -45,6 +56,11 @@ testPlan = do eraSummaries <- getEraSummaries sysStart <- getSystemStart liftEffect $ f eraSummaries sysStart + mapTest (runContract testnetConfig) do + group "Pools" do + test "get metadata for all pools" do + poolIds <- getPoolIds + void $ traverse getPoolParameters poolIds Collateral.suite PrivateKey.suite Logging.suite @@ -52,3 +68,24 @@ testPlan = do where runQueryM' = runContract (testnetConfig { suppressLogs = true }) <<< wrapQueryM + +stakingSuite :: TestPlanM ContractTest Unit +stakingSuite = do + group "Staking" do + test "getPoolIds" do + noWallet do + void $ getPoolIds + test "getPubKeyHashDelegationsAndRewards #1" do + noWallet do + res <- getPubKeyHashDelegationsAndRewards $ StakePubKeyHash $ wrap + ed25519KeyHash1 + res `shouldEqual` Nothing + test "getPubKeyHashDelegationsAndRewards #2" do + noWallet do + void $ getPubKeyHashDelegationsAndRewards $ StakePubKeyHash $ wrap + ed25519KeyHash2 + +ed25519KeyHash2 :: Ed25519KeyHash +ed25519KeyHash2 = unsafePartial $ fromJust $ ed25519KeyHashFromBytes $ + hexToByteArrayUnsafe + "541d6a23b07ebe1363671f49c833f6c33176ec968de1482fdf15cc1f" diff --git a/test/Plutip/Contract.purs b/test/Plutip/Contract.purs index 72f83ee968..cf4fe7b43c 100644 --- a/test/Plutip/Contract.purs +++ b/test/Plutip/Contract.purs @@ -49,11 +49,11 @@ import Contract.Scripts , mintingPolicyHash , validatorHash ) +import Contract.Test (ContractTest) import Contract.Test.Assert (runChecks) import Contract.Test.Plutip ( InitialUTxOs , InitialUTxOsWithStakeKey - , PlutipTest , withStakeKey , withWallets ) @@ -176,7 +176,7 @@ import Test.Ctl.Plutip.Utils (getLockedInputs, submitAndLog) import Test.Ctl.Plutip.UtxoDistribution (checkUtxoDistribution) import Test.Spec.Assertions (shouldEqual, shouldNotEqual, shouldSatisfy) -suite :: TestPlanM PlutipTest Unit +suite :: TestPlanM ContractTest Unit suite = do group "Contract interface" do test "Collateral selection: UTxO with lower amount is selected" do diff --git a/test/Plutip/Contract/Assert.purs b/test/Plutip/Contract/Assert.purs index 7e5e8717b6..e15da2f9c5 100644 --- a/test/Plutip/Contract/Assert.purs +++ b/test/Plutip/Contract/Assert.purs @@ -6,18 +6,19 @@ import Prelude import Contract.Address (ownPaymentPubKeysHashes, ownStakePubKeysHashes) import Contract.Monad (liftedM) import Contract.PlutusData (PlutusData(Integer)) +import Contract.Test (ContractTest) import Contract.Test.Assert ( checkExUnitsNotExceed , collectAssertionFailures , printContractAssertionFailures ) -import Contract.Test.Plutip (InitialUTxOs, PlutipTest, withWallets) +import Contract.Test.Mote (TestPlanM) +import Contract.Test.Plutip (InitialUTxOs, withWallets) import Contract.Wallet (withKeyWallet) import Control.Monad.Trans.Class (lift) import Ctl.Examples.ContractTestUtils as ContractTestUtils import Ctl.Examples.Helpers (mkCurrencySymbol, mkTokenName) import Ctl.Examples.PlutusV2.Scripts.AlwaysMints (alwaysMintsPolicyV2) -import Ctl.Internal.Test.TestPlanM (TestPlanM) import Data.Array (head) import Data.BigInt as BigInt import Data.Either (isLeft, isRight) @@ -29,7 +30,7 @@ import Mote (group, test) import Test.Ctl.Fixtures (cip25MetadataFixture1) import Test.Spec.Assertions (shouldEqual, shouldSatisfy) -suite :: TestPlanM PlutipTest Unit +suite :: TestPlanM ContractTest Unit suite = do group "Assertions interface" do let diff --git a/test/Plutip/Contract/NetworkId.purs b/test/Plutip/Contract/NetworkId.purs index a6b0f1f840..1a08d09fa4 100644 --- a/test/Plutip/Contract/NetworkId.purs +++ b/test/Plutip/Contract/NetworkId.purs @@ -5,18 +5,19 @@ module Test.Ctl.Plutip.Contract.NetworkId import Prelude import Contract.Address (addressFromBech32) as Address -import Contract.Test.Plutip (PlutipTest, noWallet) +import Contract.Test (ContractTest) +import Contract.Test.Mote (TestPlanM) +import Contract.Test.Plutip (noWallet) import Ctl.Internal.Plutus.Conversion.Address (fromPlutusAddress) import Ctl.Internal.Serialization.Address (NetworkId(MainnetId), addressBech32) -import Ctl.Internal.Test.TestPlanM (TestPlanM) import Mote (group, test) import Test.Spec.Assertions (shouldEqual) -suite :: TestPlanM PlutipTest Unit +suite :: TestPlanM ContractTest Unit suite = group "NetworkId Tests" $ do test "Mainnet Address in Mainnet Env" testMainnetAddress -testMainnetAddress :: PlutipTest +testMainnetAddress :: ContractTest testMainnetAddress = noWallet do let bechstr = diff --git a/test/Plutip/Staking.purs b/test/Plutip/Staking.purs index b825293415..03e43cde27 100644 --- a/test/Plutip/Staking.purs +++ b/test/Plutip/Staking.purs @@ -12,6 +12,7 @@ import Contract.Address , ownPaymentPubKeysHashes , ownStakePubKeysHashes ) +import Contract.Backend.Ogmios (getPoolParameters) import Contract.Credential (Credential(ScriptCredential)) import Contract.Hashing (plutusScriptStakeValidatorHash, publicKeyHash) import Contract.Log (logInfo') @@ -32,7 +33,6 @@ import Contract.Scripts ) import Contract.Staking ( getPoolIds - , getPoolParameters , getPubKeyHashDelegationsAndRewards , getValidatorHashDelegationsAndRewards ) diff --git a/test/Plutip/UtxoDistribution.purs b/test/Plutip/UtxoDistribution.purs index 1440b7c1cd..19bcab6692 100644 --- a/test/Plutip/UtxoDistribution.purs +++ b/test/Plutip/UtxoDistribution.purs @@ -26,6 +26,7 @@ import Contract.Monad (Contract, liftedM) import Contract.Test.Plutip ( class UtxoDistribution , InitialUTxOs + , InitialUTxOsWithStakeKey(InitialUTxOsWithStakeKey) , runPlutipContract , withStakeKey ) @@ -33,14 +34,10 @@ import Contract.Transaction ( TransactionInput , TransactionOutputWithRefScript(TransactionOutputWithRefScript) ) -import Contract.Utxos (utxosAt) +import Contract.Utxos (UtxoMap, utxosAt) import Contract.Value (Value, lovelaceValueOf) import Contract.Wallet (KeyWallet, withKeyWallet) import Control.Lazy (fix) -import Ctl.Internal.Plutip.Types - ( InitialUTxOsWithStakeKey(InitialUTxOsWithStakeKey) - ) -import Ctl.Internal.Plutus.Types.Transaction (UtxoMap) import Ctl.Internal.Test.TestPlanM (TestPlanM) import Ctl.Internal.Test.UtxoDistribution (encodeDistribution, keyWallets) import Data.Array (foldl, head, replicate, zip) diff --git a/test/QueryM/AffInterface.purs b/test/QueryM/AffInterface.purs index d575915aff..93af890c54 100644 --- a/test/QueryM/AffInterface.purs +++ b/test/QueryM/AffInterface.purs @@ -3,11 +3,7 @@ module Test.Ctl.QueryM.AffInterface (suite) where import Prelude import Control.Monad.Except (throwError) -import Ctl.Internal.QueryM - ( QueryM - , getChainTip - , submitTxOgmios - ) +import Ctl.Internal.QueryM (QueryM, getChainTip, submitTxOgmios) import Ctl.Internal.QueryM.CurrentEpoch (getCurrentEpoch) import Ctl.Internal.QueryM.EraSummaries (getEraSummaries) import Ctl.Internal.Test.TestPlanM (TestPlanM) From 0e97da1b0d709df39df37354058e93712cf9382a Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Sat, 11 Feb 2023 21:10:51 +0400 Subject: [PATCH 351/373] Add Blockfrost tests to E2E --- examples/index.html | 7 +++++++ src/Internal/BalanceTx/BalanceTx.purs | 8 ++++++-- test/e2e.env | 12 ++++++++++++ 3 files changed, 25 insertions(+), 2 deletions(-) diff --git a/examples/index.html b/examples/index.html index 3f6e3fa21d..56478cd07c 100644 --- a/examples/index.html +++ b/examples/index.html @@ -12,6 +12,13 @@
     localStorage.setItem('BLOCKFROST_API_KEY', 'your-key-here');
   
+
+ Then close the browser, and run: +
+    npm run e2e-pack-settings
+  
+
+ The key will be saved permanently to your settings archive. Sharing the archive file after that implies that the key can be leaked.
diff --git a/src/Internal/BalanceTx/BalanceTx.purs b/src/Internal/BalanceTx/BalanceTx.purs index 79ca7de5f3..ea89bc4c05 100644 --- a/src/Internal/BalanceTx/BalanceTx.purs +++ b/src/Internal/BalanceTx/BalanceTx.purs @@ -296,8 +296,12 @@ runBalancer p = do partitionAndFilterUtxos :: BalanceTxM { spendable :: UtxoMap, invalidInContext :: UtxoMap } - partitionAndFilterUtxos = - asksConstraints Constraints._nonSpendableInputs <#> + partitionAndFilterUtxos = do + -- get collateral inputs to mark them as unspendable + collateralInputs <- liftContract $ getWalletCollateral <#> + fold >>> map (unwrap >>> _.input) >>> Set.fromFoldable + asksConstraints + Constraints._nonSpendableInputs <#> append collateralInputs >>> \nonSpendableInputs -> foldr ( \(oref /\ output) acc -> diff --git a/test/e2e.env b/test/e2e.env index 6cd5366e1b..9ffb8615f5 100755 --- a/test/e2e.env +++ b/test/e2e.env @@ -29,6 +29,18 @@ nami:http://localhost:4008/?nami:OneShotMinting # nami:http://localhost:4008/?nami:AlwaysSucceeds # nami:http://localhost:4008/?nami:AlwaysSucceedsV2 + +# Uncomment these to test with Blockfrost. +# Run `npm run e2e-browser` for instructions on how to set up the API key +# nami:http://localhost:4008/?blockfrost-nami-preview:Schnorr +# nami:http://localhost:4008/?blockfrost-nami-preview:ECDSA +# nami:http://localhost:4008/?blockfrost-nami-preview:SignMultiple +# nami:http://localhost:4008/?blockfrost-nami-preview:AlwaysMints +# nami:http://localhost:4008/?blockfrost-nami-preview:Pkh2Pkh +# nami:http://localhost:4008/?blockfrost-nami-preview:SendsToken +# nami:http://localhost:4008/?blockfrost-nami-preview:MintsMultipleTokens +# nami:http://localhost:4008/?blockfrost-nami-preview:OneShotMinting + gero:http://localhost:4008/?gero:Schnorr gero:http://localhost:4008/?gero:ECDSA gero:http://localhost:4008/?gero:SignMultiple From dca1003065ed96c7a37a8e34d8a348913bb56acb Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Tue, 14 Feb 2023 15:03:33 +0300 Subject: [PATCH 352/373] Add link to CIP-49 docs --- README.md | 1 + 1 file changed, 1 insertion(+) diff --git a/README.md b/README.md index 565fedd152..5a178057ee 100644 --- a/README.md +++ b/README.md @@ -42,6 +42,7 @@ Please explore our documentation to discover how to use CTL, how to set up its r - [Transaction balancing](./doc/balancing.md) - [Transaction chaining](./doc/tx-chaining.md) - [Ada staking support](./doc/staking.md) +- [SECP256k1 support (CIP-49)](./doc/secp256k1-support.md) - [FAQs](./doc/faq.md) - [Development workflows for CTL](./doc/development.md) From 724fdd4cbb325c27bb95f5f60f526d9608807d72 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Tue, 14 Feb 2023 18:19:46 +0300 Subject: [PATCH 353/373] Add a video intro --- doc/video-intro.md | 16 ++++++++++++++++ 1 file changed, 16 insertions(+) create mode 100644 doc/video-intro.md diff --git a/doc/video-intro.md b/doc/video-intro.md new file mode 100644 index 0000000000..d61ed42d03 --- /dev/null +++ b/doc/video-intro.md @@ -0,0 +1,16 @@ +# Video introduction + +We [provide](https://drive.google.com/file/d/1ELVvL4WLKTQLg4VJMzt0yj8C0H8xsXS1/view?usp=sharing) a screencast video showcasing some features of CTL. + +Timecodes: + +- 00:00:20 - explaining bundling for the browser +- 00:06:00 - running a contract in the browser +- 00:22:05 - running tests in the browser automatically with Nami wallet (E2E test suite) +- 00:28:50 - running tests in the browser on a local plutip cluster (E2E test suite with a CIP-30 wallet mock) +- 00:36:04 - running tests in a headless browser on a local plutip cluster in a Nix build (E2E test suite on CI) +- 00:40:35 - explaining how the tests are run in Nix +- 00:44:00 - testing staking constraints interface with plutip (local cardano-node clusters), and explaining them +- 00:55:50 - how plutip test suite machinery manages local clusters +- 01:06:50 - Babbage features (explaining) +- 01:16:03 - Running E2E tests for Babbage features with Gero wallet From bcfb5fe7473d5f672afdc3b577f5fe1d5ecfaf1d Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Tue, 14 Feb 2023 18:22:00 +0300 Subject: [PATCH 354/373] Add a link to the video --- README.md | 1 + 1 file changed, 1 insertion(+) diff --git a/README.md b/README.md index 5a178057ee..7f78edac92 100644 --- a/README.md +++ b/README.md @@ -44,6 +44,7 @@ Please explore our documentation to discover how to use CTL, how to set up its r - [Ada staking support](./doc/staking.md) - [SECP256k1 support (CIP-49)](./doc/secp256k1-support.md) - [FAQs](./doc/faq.md) +- [Feature overview video](./doc/video-intro.md) - [Development workflows for CTL](./doc/development.md) You can also access [PureScript documentation for CTL and its dependencies](https://plutonomicon.github.io/cardano-transaction-lib/) for the most recent `develop` version, or [generate it yourself](./doc/development.md#generating-ps-documentation). From 694a40cece674d32f9ab81cc643347b5fdc8fcf2 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Wed, 15 Feb 2023 20:56:33 +0400 Subject: [PATCH 355/373] Add isTxConfirmed and refactored Tx confirmation module. Start using confirmation by UTxOs in Blockfrost --- CHANGELOG.md | 1 + src/Contract/Transaction.purs | 44 +----- src/Internal/Contract/AwaitTxConfirmed.purs | 153 +++++++++++++------- src/Internal/Contract/QueryHandle.purs | 6 +- src/Internal/Service/Blockfrost.purs | 6 +- test/Blockfrost.purs | 6 +- 6 files changed, 116 insertions(+), 100 deletions(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index c07ec2c526..111775fa74 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -51,6 +51,7 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) - `bundlePursProject` allows passing of `includeBundledModule` flag to export the bundled JS module `spago bundle-module` outputs - `Contract.Transaction` exports `mkPoolPubKeyHash` and `poolPubKeyHashToBech32` for bech32 roundtripping ([#1360](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1360)) - A test runner interface for Blockfrost (`Contract.Test.Blockfrost`). See [`blockfrost.md`](./doc/blockfrost.md) ([#1420](https://github.com/Plutonomicon/cardano-transaction-lib/issues/1420)) +- `Contract.isTxConfirmed` function to check if a transaction is confirmed at the moment. ### Changed diff --git a/src/Contract/Transaction.purs b/src/Contract/Transaction.purs index 0a664ada3a..4f311898af 100644 --- a/src/Contract/Transaction.purs +++ b/src/Contract/Transaction.purs @@ -2,18 +2,15 @@ -- | functionality, transaction fees, signing and submission. module Contract.Transaction ( BalancedSignedTransaction(BalancedSignedTransaction) - , awaitTxConfirmed - , awaitTxConfirmedWithTimeout - , awaitTxConfirmedWithTimeoutSlots , balanceTx + , balanceTxM , balanceTxWithConstraints , balanceTxs , balanceTxsWithConstraints - , balanceTxM , calculateMinFee - , getTxMetadata , createAdditionalUtxos , getTxFinalFee + , getTxMetadata , module BalanceTxError , module FinalizedTransaction , module NativeScript @@ -21,9 +18,9 @@ module Contract.Transaction , module PTransaction , module PTransactionUnspentOutput , module ReindexRedeemersExport - , module Scripts , module ScriptLookups , module ScriptRef + , module Scripts , module Transaction , module UnbalancedTx , module X @@ -171,7 +168,8 @@ import Ctl.Internal.Contract.AwaitTxConfirmed ( awaitTxConfirmed , awaitTxConfirmedWithTimeout , awaitTxConfirmedWithTimeoutSlots - ) as Contract + , isTxConfirmed + ) as X import Ctl.Internal.Contract.MinFee (calculateMinFee) as Contract import Ctl.Internal.Contract.QueryHandle (getQueryHandle) import Ctl.Internal.Contract.QueryHandle.Error (GetTxMetadataError) @@ -524,38 +522,6 @@ getTxMetadata th = do queryHandle <- getQueryHandle liftAff $ queryHandle.getTxMetadata th --- | Wait until a transaction with given hash is confirmed. --- | Use `awaitTxConfirmedWithTimeout` if you want to limit the time of waiting. --- | Will fail to confirm if the transaction includes no outputs on the --- | CtlBackend --- | https://github.com/Plutonomicon/cardano-transaction-lib/issues/1293 -awaitTxConfirmed - :: TransactionHash - -> Contract Unit -awaitTxConfirmed = Contract.awaitTxConfirmed - --- | Same as `awaitTxConfirmed`, but allows to specify a timeout in seconds for waiting. --- | Throws an exception on timeout. --- | Will fail to confirm if the transaction includes no outputs on the --- | CtlBackend --- | https://github.com/Plutonomicon/cardano-transaction-lib/issues/1293 -awaitTxConfirmedWithTimeout - :: Seconds - -> TransactionHash - -> Contract Unit -awaitTxConfirmedWithTimeout = Contract.awaitTxConfirmedWithTimeout - --- | Same as `awaitTxConfirmed`, but allows to specify a timeout in slots for waiting. --- | Throws an exception on timeout. --- | Will fail to confirm if the transaction includes no outputs on the --- | CtlBackend --- | https://github.com/Plutonomicon/cardano-transaction-lib/issues/1293 -awaitTxConfirmedWithTimeoutSlots - :: Int - -> TransactionHash - -> Contract Unit -awaitTxConfirmedWithTimeoutSlots = Contract.awaitTxConfirmedWithTimeoutSlots - -- | Builds an expected utxo set from transaction outputs. Predicts output -- | references (`TransactionInput`s) for each output by calculating the -- | transaction hash and indexing the outputs in the order they appear in the diff --git a/src/Internal/Contract/AwaitTxConfirmed.purs b/src/Internal/Contract/AwaitTxConfirmed.purs index 2df2cd7820..7946b16f3c 100644 --- a/src/Internal/Contract/AwaitTxConfirmed.purs +++ b/src/Internal/Contract/AwaitTxConfirmed.purs @@ -2,43 +2,59 @@ module Ctl.Internal.Contract.AwaitTxConfirmed ( awaitTxConfirmed , awaitTxConfirmedWithTimeout , awaitTxConfirmedWithTimeoutSlots + , isTxConfirmed ) where import Prelude +import Contract.Monad (liftedE) import Control.Monad.Reader.Class (asks) import Control.Parallel (parOneOf) import Ctl.Internal.Contract (getChainTip) import Ctl.Internal.Contract.Monad (Contract) import Ctl.Internal.Contract.QueryBackend (getBlockfrostBackend) import Ctl.Internal.Contract.QueryHandle (getQueryHandle) -import Ctl.Internal.Contract.WaitUntilSlot (waitUntilSlot) import Ctl.Internal.Serialization.Address (Slot) import Ctl.Internal.Types.BigNum as BigNum import Ctl.Internal.Types.Chain as Chain -import Ctl.Internal.Types.Transaction (TransactionHash) +import Ctl.Internal.Types.Transaction + ( TransactionHash + , TransactionInput(TransactionInput) + ) import Data.Either (either) -import Data.Maybe (Maybe(Just), maybe) +import Data.Maybe (isJust, maybe) import Data.Newtype (unwrap, wrap) import Data.Number (infinity) -import Data.Time.Duration (Milliseconds, Seconds(Seconds), fromDuration) +import Data.Time.Duration + ( Milliseconds(Milliseconds) + , Seconds(Seconds) + , fromDuration + ) +import Data.Traversable (for_) +import Data.UInt as UInt import Effect.Aff (delay) import Effect.Aff.Class (liftAff) import Effect.Class (liftEffect) import Effect.Exception (throw) +-- | Wait until a transaction with given hash is confirmed. +-- | Use `awaitTxConfirmedWithTimeout` if you want to limit the time of waiting. +-- | Will fail to confirm if the transaction includes no outputs. +-- | https://github.com/Plutonomicon/cardano-transaction-lib/issues/1293 awaitTxConfirmed :: TransactionHash -> Contract Unit awaitTxConfirmed = awaitTxConfirmedWithTimeout (Seconds infinity) --- NOTE: This function will always fail if the timeout is less than the value --- of the Blockfrost `confirmTxDelay` parameter. +-- | Same as `awaitTxConfirmed`, but allows to specify a timeout in seconds for waiting. +-- | Throws an exception on timeout. +-- | Will fail to confirm if the transaction includes no outputs. +-- | https://github.com/Plutonomicon/cardano-transaction-lib/issues/1293 awaitTxConfirmedWithTimeout :: Seconds -> TransactionHash -> Contract Unit awaitTxConfirmedWithTimeout timeoutSeconds txHash = -- If timeout is infinity, do not use a timeout at all. - if unwrap timeoutSeconds == infinity then void findTx + if unwrap timeoutSeconds == infinity then void waitForConfirmation else do - txFound <- parOneOf [ findTx, waitAndFail ] - if txFound then pure unit + txConfirmed <- parOneOf [ waitForConfirmation, waitAndFail ] + if txConfirmed then pure unit else liftEffect $ throw $ "awaitTxConfirmedWithTimeout: timeout exceeded, Transaction not \ \confirmed" @@ -55,37 +71,66 @@ awaitTxConfirmedWithTimeout timeoutSeconds txHash = -- Try to find the transaction indefinitely, with a waiting period between -- each request. -- - -- If `confirmTxDelay` of `BlockfrostBackend` is set, wait the specified - -- number of seconds after the transaction is confirmed, then check the - -- transaction confirmation status again to handle possible rollbacks. - -- We do this due to asynchronous updates across API endpoints, the delay - -- should be enough time for the effects of the transaction to settle. - findTx :: Contract Boolean - findTx = do + -- Assumption is that the Tx has at least one output. + -- + -- CTL backend (kupo) ensures that UTxO changes are propagated in the + -- `QueryHandle`, because it uses querying for UTxOs to check for tx + -- availability in the first place. + -- + -- But blockfrost backend performs the check for Tx existence using tx-by-hash + -- query, so we need to check for the utxos separately. + waitForConfirmation :: Contract Boolean + waitForConfirmation = do + tryUntilTrue delayTime (doesTxExist txHash) confirmTxDelay <- asks _.backend <#> (getBlockfrostBackend >=> _.confirmTxDelay) - worker (fromDuration <$> confirmTxDelay) false + isBlockfrost <- asks _.backend <#> getBlockfrostBackend >>> isJust + when isBlockfrost do + tryUntilTrue delayTime (utxosPresentForTxHash txHash) + for_ confirmTxDelay (liftAff <<< delay <<< fromDuration) + pure true where - worker :: Maybe Milliseconds -> Boolean -> Contract Boolean - worker confirmTxDelay foundBefore = - isTxConfirmed txHash >>= case _ of - -- Make sure that the transaction has not been rolled back after the - -- confirmation delay. - true | foundBefore -> - pure true - true -> - confirmTxDelay # - maybe (pure true) (\d -> liftAff (delay d) *> worker (Just d) true) - false -> - liftAff (delay delayTime) *> worker confirmTxDelay false - where - delayTime :: Milliseconds - delayTime = wrap 1000.0 + delayTime :: Milliseconds + delayTime = wrap 1000.0 + +-- Perform the check until it returns true. +tryUntilTrue :: Milliseconds -> Contract Boolean -> Contract Unit +tryUntilTrue delayTime check = go + where + go = do + res <- check + unless res do + liftAff (delay delayTime) + go + +-- | Check that UTxOs are present using `getUtxoByOref` function +utxosPresentForTxHash :: TransactionHash -> Contract Boolean +utxosPresentForTxHash txHash = do + queryHandle <- getQueryHandle + mbTxOutput <- liftedE $ liftAff $ queryHandle.getUtxoByOref + -- Here we assume that the tx has at least one output. + (TransactionInput { transactionId: txHash, index: UInt.fromInt 0 }) + pure $ isJust mbTxOutput +-- | Same as `awaitTxConfirmed`, but allows to specify a timeout in slots for waiting. +-- | Throws an exception on timeout. +-- | Will fail to confirm if the transaction includes no outputs. +-- | https://github.com/Plutonomicon/cardano-transaction-lib/issues/1293 awaitTxConfirmedWithTimeoutSlots :: Int -> TransactionHash -> Contract Unit -awaitTxConfirmedWithTimeoutSlots timeoutSlots txHash = - getCurrentSlot >>= addSlots timeoutSlots >>= go +awaitTxConfirmedWithTimeoutSlots timeoutSlots txHash = do + limitSlot <- getCurrentSlot >>= addSlots timeoutSlots + tryUntilTrue delayTime do + checkSlotLimit limitSlot + doesTxExist txHash + tryUntilTrue delayTime do + checkSlotLimit limitSlot + utxosPresentForTxHash txHash where + addSlots :: Int -> Slot -> Contract Slot + addSlots n slot = + maybe (liftEffect $ throw "Cannot determine next slot") (pure <<< wrap) $ + unwrap slot `BigNum.add` BigNum.fromInt n + getCurrentSlot :: Contract Slot getCurrentSlot = getChainTip >>= case _ of Chain.TipAtGenesis -> do @@ -93,26 +138,30 @@ awaitTxConfirmedWithTimeoutSlots timeoutSlots txHash = getCurrentSlot Chain.Tip (Chain.ChainTip { slot }) -> pure slot - addSlots :: Int -> Slot -> Contract Slot - addSlots n slot = - maybe (liftEffect $ throw "Cannot determine next slot") (pure <<< wrap) $ - unwrap slot `BigNum.add` BigNum.fromInt n + checkSlotLimit :: Slot -> Contract Unit + checkSlotLimit limitSlot = do + slot <- getCurrentSlot + when (slot >= limitSlot) do + liftEffect $ throw $ + "awaitTxConfirmedWithTimeoutSlots: \ + \ timeout exceeded, Transaction not confirmed" - go :: Slot -> Contract Unit - go timeout = - isTxConfirmed txHash >>= \found -> - unless found do - slot <- getCurrentSlot - when (slot >= timeout) do - liftEffect $ throw $ - "awaitTxConfirmedWithTimeoutSlots: \ - \ timeout exceeded, Transaction not confirmed" - void $ addSlots 1 slot >>= waitUntilSlot - go timeout + delayTime :: Milliseconds + delayTime = Milliseconds 1000.0 -isTxConfirmed :: TransactionHash -> Contract Boolean -isTxConfirmed txHash = do +-- | Checks if a Tx is known to the query layer. It may still be unconfirmed. +doesTxExist :: TransactionHash -> Contract Boolean +doesTxExist txHash = do queryHandle <- getQueryHandle - liftAff $ queryHandle.isTxConfirmed txHash + liftAff $ queryHandle.doesTxExist txHash >>= either (liftEffect <<< throw <<< show) pure +-- | Check if a transaction is confirmed at the moment, i.e. if its UTxOs +-- | are available to spend. +-- | If you want to delay until a transaction is confirmed, use +-- | `awaitTxConfirmed` or its variants. +isTxConfirmed :: TransactionHash -> Contract Boolean +isTxConfirmed txHash = do + exists <- doesTxExist txHash + if exists then utxosPresentForTxHash txHash + else pure false diff --git a/src/Internal/Contract/QueryHandle.purs b/src/Internal/Contract/QueryHandle.purs index faf68402d2..3c4ebc2555 100644 --- a/src/Internal/Contract/QueryHandle.purs +++ b/src/Internal/Contract/QueryHandle.purs @@ -82,7 +82,7 @@ type QueryHandle = TransactionHash -> Aff (Either GetTxMetadataError GeneralTransactionMetadata) , getUtxoByOref :: TransactionInput -> AffE (Maybe TransactionOutput) - , isTxConfirmed :: TransactionHash -> AffE Boolean + , doesTxExist :: TransactionHash -> AffE Boolean , utxosAt :: Address -> AffE UtxoMap , getChainTip :: AffE Chain.Tip , getCurrentEpoch :: Aff CurrentEpoch @@ -110,7 +110,7 @@ queryHandleForCtlBackend contractEnv backend = { getDatumByHash: runQueryM' <<< Kupo.getDatumByHash , getScriptByHash: runQueryM' <<< Kupo.getScriptByHash , getUtxoByOref: runQueryM' <<< Kupo.getUtxoByOref - , isTxConfirmed: runQueryM' <<< map (map isJust) <<< Kupo.isTxConfirmed + , doesTxExist: runQueryM' <<< map (map isJust) <<< Kupo.isTxConfirmed , getTxMetadata: runQueryM' <<< Kupo.getTxMetadata , utxosAt: runQueryM' <<< Kupo.utxosAt , getChainTip: Right <$> runQueryM' QueryM.getChainTip @@ -148,7 +148,7 @@ queryHandleForBlockfrostBackend contractEnv backend = { getDatumByHash: runBlockfrostServiceM' <<< Blockfrost.getDatumByHash , getScriptByHash: runBlockfrostServiceM' <<< Blockfrost.getScriptByHash , getUtxoByOref: runBlockfrostServiceM' <<< Blockfrost.getUtxoByOref - , isTxConfirmed: runBlockfrostServiceM' <<< Blockfrost.isTxConfirmed + , doesTxExist: runBlockfrostServiceM' <<< Blockfrost.doesTxExist , getTxMetadata: runBlockfrostServiceM' <<< Blockfrost.getTxMetadata , utxosAt: runBlockfrostServiceM' <<< Blockfrost.utxosAt , getChainTip: runBlockfrostServiceM' Blockfrost.getChainTip diff --git a/src/Internal/Service/Blockfrost.purs b/src/Internal/Service/Blockfrost.purs index 17427cf92a..e67014b954 100644 --- a/src/Internal/Service/Blockfrost.purs +++ b/src/Internal/Service/Blockfrost.purs @@ -47,7 +47,7 @@ module Ctl.Internal.Service.Blockfrost , getSystemStart , getTxMetadata , getUtxoByOref - , isTxConfirmed + , doesTxExist , runBlockfrostServiceM , runBlockfrostServiceTestM , submitTx @@ -649,10 +649,10 @@ evaluateTx tx = do -- Check transaction confirmation status -------------------------------------------------------------------------------- -isTxConfirmed +doesTxExist :: TransactionHash -> BlockfrostServiceM (Either ClientError Boolean) -isTxConfirmed txHash = do +doesTxExist txHash = do response <- blockfrostGetRequest $ Transaction txHash pure case handleBlockfrostResponse response of Right (_ :: Aeson) -> Right true diff --git a/test/Blockfrost.purs b/test/Blockfrost.purs index 7cfd5d13b8..287373ac8c 100644 --- a/test/Blockfrost.purs +++ b/test/Blockfrost.purs @@ -96,10 +96,10 @@ testPlan backend = group "Blockfrost" do TxWithNoMetadata _ -> Left GetTxMetadataMetadataEmptyOrMissingError UnconfirmedTx _ -> Left GetTxMetadataTxNotFoundError test "isTxConfirmed" do - eConfirmed <- runBlockfrost $ Blockfrost.isTxConfirmed $ + eExists <- runBlockfrost $ Blockfrost.doesTxExist $ fixtureHash fixture - confirmed <- liftEither $ lmap (error <<< show) eConfirmed - confirmed `shouldEqual` case fixture of + exists <- liftEither $ lmap (error <<< show) eExists + exists `shouldEqual` case fixture of TxWithMetadata _ -> true TxWithNoMetadata _ -> true UnconfirmedTx _ -> false From 7cd5316f3c6044870995af12ede534d20a438252 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Wed, 15 Feb 2023 21:54:40 +0300 Subject: [PATCH 356/373] More precise info on E2E testing --- doc/e2e-testing.md | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/doc/e2e-testing.md b/doc/e2e-testing.md index 6101fe5495..07c2dd4f7d 100644 --- a/doc/e2e-testing.md +++ b/doc/e2e-testing.md @@ -43,8 +43,9 @@ For a working example see `test/E2E.purs`. It can be run conveniently using `npm The process is as follows: -1. run `make run-dev`. -2. In another shell, run `npm run e2e-test`. +1. run `npm run e2e-serve` in one shell +2. run `nix run -L .#ctl-runtime` in another shell +3. run `npm run e2e-test` in the third shell ## How Wallets are Used From db3ee62b8de5933bc3f93a3e7eea484011d85763 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Thu, 16 Feb 2023 00:46:33 +0400 Subject: [PATCH 357/373] Add a note on BalanceInsufficientError to FAQ --- doc/faq.md | 11 ++++++++++- 1 file changed, 10 insertions(+), 1 deletion(-) diff --git a/doc/faq.md b/doc/faq.md index ad003882a4..7952665a44 100644 --- a/doc/faq.md +++ b/doc/faq.md @@ -11,6 +11,7 @@ This document lists common problems encountered by CTL users and developers. - [Q: I see `spago: Error: Remote host not found`, why?](#q-i-see-spago-error-remote-host-not-found-why) - [Common Contract execution problems](#common-contract-execution-problems) - [Q: What are the common reasons behind BalanceInsufficientError?](#q-what-are-the-common-reasons-behind-balanceinsufficienterror) + - [Q: CTL consumed my collateral](#q-ctl-consumed-my-collateral) - [Time-related](#time-related) - [Q: Time-related functions behave strangely, what's the reason?](#q-time-related-functions-behave-strangely-whats-the-reason) - [Q: Time/slot conversion functions return `Nothing`. Why is that?](#q-timeslot-conversion-functions-return-nothing-why-is-that) @@ -51,7 +52,15 @@ means that the CTL overlay hasn't been properly applied. Add `ctl.overlays.spago ### Q: What are the common reasons behind BalanceInsufficientError? -Most contracts require at least two UTxOs to run (one will be used as a collateral). If you use a wallet with only one UTxO, e.g. a new wallet you just funded from the faucet, you need to send yourself at least 5 tAda to create another UTxO for the collateral. +Most contracts require at least two UTxOs to run (one will be used as a collateral). If you use a wallet with only one UTxO, e.g. a new wallet you just funded from the faucet, you need to send yourself at least 5 Ada to create another UTxO for the collateral. + +Another thing to keep in mind is that due to [min-ada requirements](https://docs.cardano.org/native-tokens/minimum-ada-value-requirement/), the amount of Ada that is required to be *consumed* by a Tx is higher than the amount that must be *spent*, because CTL creates change UTxOs. The amount of Ada that should be present on a wallet depends on a number of factors, including the amount and quantity of tokens in the users wallet. + +### Q: CTL consumed my collateral + +CTL does not consume wallet collateral normally, but it still can happen. + +In order to get the collateral UTxO, CTL uses the wallet and then marks the returned UTxO as locked internally. But some wallets (e.g. Gero) do not return the collateral the moment it is set, waiting for Tx confirmation first. In case a collateral is set right before the contract is started, CTL can accidentally spend the collateral, because we rely on CTL's own query layer to get a list of available UTxOs, and the wallet state may lag behind it, not returning the collateral to filter out at that moment. ## Time-related From 4ec87a7d0c298044ad55cea29d49fcd6fc697e0b Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Thu, 16 Feb 2023 01:15:21 +0400 Subject: [PATCH 358/373] Use all wallets with blockfrost --- examples/ByUrl.purs | 41 ++++++++++++++++++++++++++++++++++++----- examples/index.html | 5 +---- 2 files changed, 37 insertions(+), 9 deletions(-) diff --git a/examples/ByUrl.purs b/examples/ByUrl.purs index a7d5347ed6..ec7bec66bb 100644 --- a/examples/ByUrl.purs +++ b/examples/ByUrl.purs @@ -4,6 +4,14 @@ import Prelude import Contract.Config ( ContractParams + , WalletSpec + ( ConnectToNami + , ConnectToGero + , ConnectToLode + , ConnectToEternl + , ConnectToFlint + , ConnectToNuFi + ) , blockfrostPublicPreviewServerConfig , mainnetFlintConfig , mainnetGeroConfig @@ -11,6 +19,7 @@ import Contract.Config , mainnetNamiConfig , mainnetNuFiConfig , mkBlockfrostBackendParams + , testnetConfig , testnetEternlConfig , testnetFlintConfig , testnetGeroConfig @@ -64,8 +73,30 @@ main = do let walletsWithBlockfrost = wallets `Map.union` Map.fromFoldable - [ "blockfrost-nami-preview" /\ mkBlockfrostPreviewNamiConfig mbApiKey /\ - Nothing + [ "blockfrost-nami-preview" + /\ (mkBlockfrostPreviewConfig mbApiKey) + { walletSpec = Just ConnectToNami } + /\ Nothing + , "blockfrost-gero-preview" + /\ (mkBlockfrostPreviewConfig mbApiKey) + { walletSpec = Just ConnectToGero } + /\ Nothing + , "blockfrost-eternl-preview" + /\ (mkBlockfrostPreviewConfig mbApiKey) + { walletSpec = Just ConnectToEternl } + /\ Nothing + , "blockfrost-lode-preview" + /\ (mkBlockfrostPreviewConfig mbApiKey) + { walletSpec = Just ConnectToLode } + /\ Nothing + , "blockfrost-flint-preview" + /\ (mkBlockfrostPreviewConfig mbApiKey) + { walletSpec = Just ConnectToFlint } + /\ Nothing + , "blockfrost-nufi-preview" + /\ (mkBlockfrostPreviewConfig mbApiKey) + { walletSpec = Just ConnectToNuFi } + /\ Nothing ] addLinks walletsWithBlockfrost examples route walletsWithBlockfrost examples @@ -101,9 +132,9 @@ wallets = Map.fromFoldable , "plutip-nufi-mock" /\ mainnetNuFiConfig /\ Just MockNuFi ] -mkBlockfrostPreviewNamiConfig :: Maybe String -> ContractParams -mkBlockfrostPreviewNamiConfig apiKey = - testnetNamiConfig +mkBlockfrostPreviewConfig :: Maybe String -> ContractParams +mkBlockfrostPreviewConfig apiKey = + testnetConfig { backendParams = mkBlockfrostBackendParams { blockfrostConfig: blockfrostPublicPreviewServerConfig , blockfrostApiKey: apiKey diff --git a/examples/index.html b/examples/index.html index 56478cd07c..b92b25e158 100644 --- a/examples/index.html +++ b/examples/index.html @@ -6,18 +6,15 @@ - Examples source code is located in examples/ directory. -
+ Examples source code is located in examples/ directory.
To set a Blockfrost API key, run the following in the browser console:
     localStorage.setItem('BLOCKFROST_API_KEY', 'your-key-here');
   
-
Then close the browser, and run:
     npm run e2e-pack-settings
   
-
The key will be saved permanently to your settings archive. Sharing the archive file after that implies that the key can be leaked.
From 0782a1df696e02bd0e7aa5320f74d7ab6437bb4f Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Thu, 16 Feb 2023 01:17:17 +0400 Subject: [PATCH 359/373] Use collateral return with all wallets --- src/Internal/BalanceTx/BalanceTx.purs | 5 +---- 1 file changed, 1 insertion(+), 4 deletions(-) diff --git a/src/Internal/BalanceTx/BalanceTx.purs b/src/Internal/BalanceTx/BalanceTx.purs index ea89bc4c05..be2583911e 100644 --- a/src/Internal/BalanceTx/BalanceTx.purs +++ b/src/Internal/BalanceTx/BalanceTx.purs @@ -231,10 +231,7 @@ balanceTxWithConstraints unbalancedTx constraintsBuilder = do collateral <- liftEitherContract $ note CouldNotGetCollateral <$> getWalletCollateral let collaterisedTx = addTxCollateral collateral transaction - -- Don't mess with Cip30 collateral - isCip30 <- isJust <$> askCip30Wallet - if isCip30 then pure collaterisedTx - else addTxCollateralReturn collateral collaterisedTx changeAddr + addTxCollateralReturn collateral collaterisedTx changeAddr -------------------------------------------------------------------------------- -- Balancing Algorithm From 4f268a966e924fb44bb442736790eb84001ae85f Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Thu, 16 Feb 2023 01:18:46 +0400 Subject: [PATCH 360/373] Make collateral inputs unspendable with CIP-30 --- src/Internal/BalanceTx/BalanceTx.purs | 83 ++++++++++++++------------- 1 file changed, 44 insertions(+), 39 deletions(-) diff --git a/src/Internal/BalanceTx/BalanceTx.purs b/src/Internal/BalanceTx/BalanceTx.purs index be2583911e..45da66fa5c 100644 --- a/src/Internal/BalanceTx/BalanceTx.purs +++ b/src/Internal/BalanceTx/BalanceTx.purs @@ -294,45 +294,50 @@ runBalancer p = do partitionAndFilterUtxos :: BalanceTxM { spendable :: UtxoMap, invalidInContext :: UtxoMap } partitionAndFilterUtxos = do - -- get collateral inputs to mark them as unspendable - collateralInputs <- liftContract $ getWalletCollateral <#> - fold >>> map (unwrap >>> _.input) >>> Set.fromFoldable - asksConstraints - Constraints._nonSpendableInputs <#> append collateralInputs >>> - \nonSpendableInputs -> - foldr - ( \(oref /\ output) acc -> - let - hasInlineDatum :: Boolean - hasInlineDatum = case (unwrap output).datum of - OutputDatum _ -> true - _ -> false - - hasScriptRef :: Boolean - hasScriptRef = isJust (unwrap output).scriptRef - - spendable :: Boolean - spendable = not $ Set.member oref nonSpendableInputs || - Set.member oref - (p.unbalancedTx ^. _body' <<< _referenceInputs) - - validInContext :: Boolean - validInContext = not $ txHasPlutusV1 && - (hasInlineDatum || hasScriptRef) - in - case spendable, validInContext of - true, true -> acc - { spendable = Map.insert oref output acc.spendable } - true, false -> acc - { invalidInContext = Map.insert oref output - acc.invalidInContext - } - _, _ -> acc - ) - { spendable: Map.empty - , invalidInContext: Map.empty - } - (Map.toUnfoldable p.utxos :: Array _) + isCip30 <- isJust <$> askCip30Wallet + -- Get collateral inputs to mark them as unspendable. + -- Some CIP-30 wallets don't allow to sign Txs that spend it. + nonSpendableCollateralInputs <- + if isCip30 then + liftContract $ getWalletCollateral <#> + fold >>> map (unwrap >>> _.input) >>> Set.fromFoldable + else mempty + asksConstraints Constraints._nonSpendableInputs <#> + append nonSpendableCollateralInputs >>> + \nonSpendableInputs -> + foldr + ( \(oref /\ output) acc -> + let + hasInlineDatum :: Boolean + hasInlineDatum = case (unwrap output).datum of + OutputDatum _ -> true + _ -> false + + hasScriptRef :: Boolean + hasScriptRef = isJust (unwrap output).scriptRef + + spendable :: Boolean + spendable = not $ Set.member oref nonSpendableInputs || + Set.member oref + (p.unbalancedTx ^. _body' <<< _referenceInputs) + + validInContext :: Boolean + validInContext = not $ txHasPlutusV1 && + (hasInlineDatum || hasScriptRef) + in + case spendable, validInContext of + true, true -> acc + { spendable = Map.insert oref output acc.spendable } + true, false -> acc + { invalidInContext = Map.insert oref output + acc.invalidInContext + } + _, _ -> acc + ) + { spendable: Map.empty + , invalidInContext: Map.empty + } + (Map.toUnfoldable p.utxos :: Array _) mainLoop :: BalancerState -> BalanceTxM FinalizedTransaction mainLoop = worker <<< PrebalanceTx From 63c8f3c54278c92e9e7d9c6d0d1c66a7fe4f5ab8 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Thu, 16 Feb 2023 01:31:10 +0400 Subject: [PATCH 361/373] Reduce Ada requirements in Plutip tests for use with Blockfrost --- test/Plutip/Contract.purs | 114 +++++++++++++++++++------------------- 1 file changed, 56 insertions(+), 58 deletions(-) diff --git a/test/Plutip/Contract.purs b/test/Plutip/Contract.purs index cf4fe7b43c..7328ec917b 100644 --- a/test/Plutip/Contract.purs +++ b/test/Plutip/Contract.purs @@ -413,20 +413,20 @@ suite = do distribution :: InitialUTxOs /\ InitialUTxOs /\ InitialUTxOs /\ InitialUTxOs distribution = - [ BigInt.fromInt 2_000_000_000 - , BigInt.fromInt 2_000_000_000 + [ BigInt.fromInt 50_000_000 + , BigInt.fromInt 50_000_000 ] /\ - [ BigInt.fromInt 2_000_000_000 - , BigInt.fromInt 2_000_000_000 + [ BigInt.fromInt 50_000_000 + , BigInt.fromInt 50_000_000 ] /\ - [ BigInt.fromInt 2_000_000_000 - , BigInt.fromInt 2_000_000_000 + [ BigInt.fromInt 50_000_000 + , BigInt.fromInt 50_000_000 ] /\ - [ BigInt.fromInt 2_000_000_000 - , BigInt.fromInt 2_000_000_000 + [ BigInt.fromInt 50_000_000 + , BigInt.fromInt 50_000_000 ] withWallets distribution \(alice /\ bob /\ charlie /\ dan) -> do @@ -502,7 +502,7 @@ suite = do distribution :: InitialUTxOs distribution = [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 50_000_000 ] withWallets distribution \alice -> do withKeyWallet alice do @@ -530,7 +530,7 @@ suite = do distribution :: InitialUTxOs distribution = [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 50_000_000 ] withWallets distribution \alice -> do withKeyWallet alice do @@ -572,7 +572,7 @@ suite = do distribution :: InitialUTxOs distribution = [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 50_000_000 ] withWallets distribution \alice -> do withKeyWallet alice do @@ -615,7 +615,7 @@ suite = do distribution :: InitialUTxOs distribution = [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 50_000_000 ] withWallets distribution \alice -> do withKeyWallet alice do @@ -657,7 +657,7 @@ suite = do distribution :: InitialUTxOs distribution = [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 50_000_000 ] withWallets distribution \alice -> do withKeyWallet alice do @@ -700,7 +700,7 @@ suite = do distribution :: InitialUTxOs distribution = [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 50_000_000 ] withWallets distribution \alice -> do withKeyWallet alice NativeScriptMints.contract @@ -735,7 +735,7 @@ suite = do distribution :: InitialUTxOs distribution = [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 50_000_000 ] datum1 :: Datum @@ -799,7 +799,7 @@ suite = do test "GetScriptByHash" do let distribution :: InitialUTxOs - distribution = [ BigInt.fromInt 2_000_000_000 ] + distribution = [ BigInt.fromInt 50_000_000 ] withWallets distribution \alice -> do withKeyWallet alice do @@ -835,7 +835,7 @@ suite = do test "Getting transaction metadata" do let distribution :: InitialUTxOs - distribution = [ BigInt.fromInt 2_000_000_000 ] + distribution = [ BigInt.fromInt 50_000_000 ] withWallets distribution \alice -> do withKeyWallet alice do @@ -862,7 +862,7 @@ suite = do distribution :: InitialUTxOs distribution = [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 50_000_000 ] withWallets distribution \alice -> do @@ -889,7 +889,7 @@ suite = do distribution :: InitialUTxOs distribution = [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 50_000_000 ] withWallets distribution \alice -> do withKeyWallet alice do @@ -928,7 +928,7 @@ suite = do distribution :: InitialUTxOs distribution = [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 100_000_000 + , BigInt.fromInt 50_000_000 ] withWallets distribution \alice -> do checkUtxoDistribution distribution alice @@ -938,7 +938,7 @@ suite = do let aliceUtxos = [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 100_000_000 + , BigInt.fromInt 50_000_000 ] distribution = withStakeKey privateStakeKey aliceUtxos withWallets distribution \alice -> do @@ -952,7 +952,7 @@ suite = do distribution :: InitialUTxOs distribution = [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 50_000_000 ] withWallets distribution \alice -> do withKeyWallet alice do @@ -971,7 +971,7 @@ suite = do distribution :: InitialUTxOsWithStakeKey distribution = withStakeKey privateStakeKey [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 50_000_000 ] withWallets distribution \alice -> do withKeyWallet alice do @@ -994,7 +994,7 @@ suite = do distribution :: InitialUTxOs distribution = [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 50_000_000 ] withWallets distribution \alice -> do withKeyWallet alice SendsToken.contract @@ -1110,7 +1110,7 @@ suite = do distribution :: InitialUTxOs distribution = [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 50_000_000 ] withWallets distribution \alice -> do withKeyWallet alice do @@ -1128,7 +1128,7 @@ suite = do distribution :: InitialUTxOs distribution = [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 50_000_000 ] withWallets distribution \alice -> do withKeyWallet alice do @@ -1145,7 +1145,7 @@ suite = do distribution :: InitialUTxOs distribution = [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 50_000_000 ] withWallets distribution \alice -> do withKeyWallet alice do @@ -1162,7 +1162,7 @@ suite = do distribution :: InitialUTxOs distribution = [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 50_000_000 ] withWallets distribution \alice -> do withKeyWallet alice do @@ -1182,7 +1182,7 @@ suite = do distribution :: InitialUTxOs distribution = [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 50_000_000 ] withWallets distribution \alice -> do withKeyWallet alice do @@ -1203,7 +1203,7 @@ suite = do distribution :: InitialUTxOs distribution = [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 50_000_000 ] withWallets distribution \alice -> withKeyWallet alice PaysWithDatum.contract @@ -1213,7 +1213,7 @@ suite = do distribution :: InitialUTxOs distribution = [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 50_000_000 ] withWallets distribution \alice -> do withKeyWallet alice do @@ -1230,7 +1230,7 @@ suite = do distribution :: InitialUTxOs distribution = [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 50_000_000 ] withWallets distribution \alice -> do withKeyWallet alice do @@ -1248,8 +1248,8 @@ suite = do distribution :: InitialUTxOs /\ InitialUTxOs distribution = [ BigInt.fromInt 10_000_000 - , BigInt.fromInt 2_000_000_000 - ] /\ [ BigInt.fromInt 2_000_000_000 ] + , BigInt.fromInt 50_000_000 + ] /\ [ BigInt.fromInt 50_000_000 ] withWallets distribution \(alice /\ seed) -> do validator <- AlwaysFails.alwaysFailsScript let vhash = validatorHash validator @@ -1303,7 +1303,7 @@ suite = do ) <> mustPayToPubKeyStakeAddress alicePkh aliceStakePkh ( asset <> - (Value.lovelaceValueOf $ BigInt.fromInt 2_000_000_000) + (Value.lovelaceValueOf $ BigInt.fromInt 50_000_000) ) lookups :: Lookups.ScriptLookups Void @@ -1329,7 +1329,7 @@ suite = do distribution :: InitialUTxOs distribution = [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 50_000_000 ] withWallets distribution \alice -> withKeyWallet alice ReferenceScripts.contract @@ -1341,7 +1341,7 @@ suite = do distribution :: InitialUTxOsWithStakeKey distribution = withStakeKey privateStakeKey [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 50_000_000 ] withWallets distribution \alice -> withKeyWallet alice ReferenceScripts.contract @@ -1352,7 +1352,7 @@ suite = do distribution :: InitialUTxOs distribution = [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 50_000_000 ] withWallets distribution \alice -> withKeyWallet alice ReferenceInputs.contract @@ -1362,7 +1362,7 @@ suite = do distribution :: InitialUTxOs distribution = [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 50_000_000 ] withWallets distribution \alice -> withKeyWallet alice ReferenceInputsAndScripts.contract @@ -1372,7 +1372,7 @@ suite = do distribution :: InitialUTxOs distribution = [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 50_000_000 ] withWallets distribution \alice -> withKeyWallet alice OneShotMinting.contract @@ -1382,7 +1382,7 @@ suite = do distribution :: InitialUTxOs distribution = [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 50_000_000 ] withWallets distribution \alice -> withKeyWallet alice OneShotMintingV2.contract @@ -1391,7 +1391,7 @@ suite = do let initialUtxos :: InitialUTxOs initialUtxos = - [ BigInt.fromInt 2_000_000_000, BigInt.fromInt 2_000_000_000 ] + [ BigInt.fromInt 50_000_000, BigInt.fromInt 50_000_000 ] distribution :: InitialUTxOs /\ InitialUTxOs distribution = initialUtxos /\ initialUtxos @@ -1425,7 +1425,7 @@ suite = do let initialUtxos :: InitialUTxOs initialUtxos = - [ BigInt.fromInt 2_000_000_000, BigInt.fromInt 2_000_000_000 ] + [ BigInt.fromInt 50_000_000, BigInt.fromInt 50_000_000 ] distribution :: InitialUTxOs /\ InitialUTxOs distribution = initialUtxos /\ initialUtxos @@ -1450,7 +1450,7 @@ suite = do -- TODO -- investigate why this test failed with `valueNotConserved` error -- see https://github.com/Plutonomicon/cardano-transaction-lib/issues/1174 - skip $ test "Evaluation with additional UTxOs with native scripts" do + test "Evaluation with additional UTxOs with native scripts" do let distribution :: InitialUTxOs distribution = @@ -1697,7 +1697,7 @@ suite = do distribution :: InitialUTxOs distribution = [ BigInt.fromInt 1_000_000_000 - , BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 50_000_000 ] withWallets distribution \alice -> do try (liftEffect $ isWalletAvailable NamiWallet) >>= flip shouldSatisfy @@ -1736,7 +1736,7 @@ suite = do distribution :: InitialUTxOs distribution = [ BigInt.fromInt 1_000_000_000 - , BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 50_000_000 ] withWallets distribution \alice -> do withCip30Mock alice MockNami do @@ -1748,7 +1748,7 @@ suite = do ] -> do let amount = (unwrap output).amount unless - (amount == lovelaceValueOf (BigInt.fromInt 1_000_000_000)) + (amount == lovelaceValueOf (BigInt.fromInt 50_000_000)) $ throw "Wrong UTxO selected as collateral" Just _ -> do throw $ "More than one UTxO in collateral. " <> @@ -1759,7 +1759,7 @@ suite = do distribution :: InitialUTxOs distribution = [ BigInt.fromInt 1_000_000_000 - , BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 50_000_000 ] withWallets distribution \alice -> do utxos <- withCip30Mock alice MockNami do @@ -1771,7 +1771,7 @@ suite = do distribution :: InitialUTxOs distribution = [ BigInt.fromInt 1_000_000_000 - , BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 50_000_000 ] withWallets distribution \alice -> do mockAddress <- withCip30Mock alice MockNami do @@ -1787,7 +1787,7 @@ suite = do distribution :: InitialUTxOs distribution = [ BigInt.fromInt 1_000_000_000 - , BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 50_000_000 ] withWallets distribution \alice -> do withCip30Mock alice MockNami do @@ -1801,18 +1801,16 @@ suite = do distribution :: InitialUTxOs distribution = [ BigInt.fromInt 1_000_000_000 - , BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 50_000_000 ] withWallets distribution \alice -> do withKeyWallet alice do getWalletBalance >>= flip shouldSatisfy - ( eq $ Just $ coinToValue $ Coin $ BigInt.fromInt 1000 * - BigInt.fromInt 3_000_000 + ( eq $ Just $ coinToValue $ Coin $ BigInt.fromInt 1_050_000_000 ) withCip30Mock alice MockNami do getWalletBalance >>= flip shouldSatisfy - ( eq $ Just $ coinToValue $ Coin $ BigInt.fromInt 1000 * - BigInt.fromInt 3_000_000 + ( eq $ Just $ coinToValue $ Coin $ BigInt.fromInt 1_050_000_000 ) test "getWalletBalance works (2)" do @@ -1833,7 +1831,7 @@ suite = do distribution :: InitialUTxOs distribution = [ BigInt.fromInt 1_000_000_000 - , BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 50_000_000 ] withWallets distribution \alice -> do withCip30Mock alice MockNami do @@ -1845,7 +1843,7 @@ suite = do distribution :: InitialUTxOs distribution = [ BigInt.fromInt 1_000_000_000 - , BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 50_000_000 ] withWallets distribution \alice -> do withKeyWallet alice do @@ -1855,7 +1853,7 @@ suite = do distribution :: InitialUTxOs distribution = [ BigInt.fromInt 1_000_000_000 - , BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 50_000_000 ] withWallets distribution \alice -> do withKeyWallet alice do From 8e4e9ad493b75a0ef486e1f5451e581201d2c904 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Thu, 16 Feb 2023 02:13:57 +0400 Subject: [PATCH 362/373] Improve KeyDir test engine: - exit early if no funds left - suggest skipping wallet funds redistribution if possible Improve docs --- doc/blockfrost.md | 14 +- doc/runtime.md | 2 + src/Contract/Test/Blockfrost.purs | 7 +- src/Internal/BalanceTx/Collateral.purs | 2 +- src/Internal/Test/KeyDir.purs | 247 ++++++++++++++++--------- 5 files changed, 173 insertions(+), 99 deletions(-) diff --git a/doc/blockfrost.md b/doc/blockfrost.md index 9238284851..ae23e696db 100644 --- a/doc/blockfrost.md +++ b/doc/blockfrost.md @@ -68,11 +68,17 @@ If you are going to use an enterprise address (without a staking credential comp ### 4. Setting up a directory for temporary keys -During testing, the test engine will move funds around according to the UTxO distribution specifications provided via `Contract.Test.withWallets` calls in the test bodies. It will generate private keys as needed on the fly. The private keys will be stored in a special directory, to prevent loss of funds in case the test suite exits. Set `BACKUP_KEYS_DIR` to an existing directory where you would like the keys to be stored. +During testing, the test engine will move funds around according to the UTxO distribution specifications provided via `Contract.Test.withWallets` calls in the test bodies. It will generate private keys as needed on the fly. The private keys will be stored in a special directory, to prevent loss of funds in case the test suite suddently exits. Set `BACKUP_KEYS_DIR` to an existing directory where you would like the keys to be stored. + +In this directory, keys will be stored in subdirs named as addresses that are derived from these keys. Most of these directories will contain a file named `inactive`. It indicates that the test suite assumes that there are no funds left (because they have been withdrawn successfully). + +Each test run generates fresh keys that will be stored indefinitely, and it's up to the user to decide when to delete the corresponding directories. The reason why the keys are not being disposed of automatically is because there may be some on-chain state uniquely tied to them that the user may not want to lose access to. ### 5. Providing an API endpoint URL -Parts of the endpoint URLs are specified separately, e.g. `https://cardano-preview.blockfrost.io/api/v0/` becomes: +Blockfrost dashboard provides endpoint URLs for your projects. + +In the test suite configuration, parts of the endpoint URLs are specified separately, e.g. `https://cardano-preview.blockfrost.io/api/v0/` becomes: ```bash export BLOCKFROST_PORT=443 # https -> 443, http -> 80 @@ -83,8 +89,8 @@ export BLOCKFROST_PATH="/api/v0" ### 6. Extra configuration options -If your tests are failing because the effects of the transaction do not seem -to propagate, try increasing the delay after transaction submission. Blockfrost does not update the query layer state consistently, so this is the best workaround we can have. +If the tests are failing because the effects of the transaction do not seem +to propagate, it is possible to increase the delay after transaction submission. Blockfrost does not update the query layer state atomically (proxied Ogmios eval-tx endpoint seems to lag behind the DB), so this is the best workaround we can have: ```bash export TX_CONFIRMATION_DELAY_SECONDS=30 diff --git a/doc/runtime.md b/doc/runtime.md index 9033696a37..c78c6d627f 100644 --- a/doc/runtime.md +++ b/doc/runtime.md @@ -22,6 +22,8 @@ Our nix environment includes CTL backend services, but for now Blockfrost can be ## CTL Backend +Info in this section only applies to CTL backend services. + The services that are currently **required** are: - [Ogmios](https://ogmios.dev) diff --git a/src/Contract/Test/Blockfrost.purs b/src/Contract/Test/Blockfrost.purs index b99520840c..97fdc070e5 100644 --- a/src/Contract/Test/Blockfrost.purs +++ b/src/Contract/Test/Blockfrost.purs @@ -22,7 +22,8 @@ import Control.Monad.Error.Class (liftMaybe) import Ctl.Internal.Test.ContractTest (ContractTest) import Ctl.Internal.Test.E2E.Runner (readBoolean) import Ctl.Internal.Test.KeyDir (runContractTestsWithKeyDir) -import Data.Maybe (Maybe(Just, Nothing), isNothing, maybe) +import Data.Maybe (Maybe(Just, Nothing), fromMaybe, isNothing, maybe) +import Data.Newtype (unwrap) import Data.Number as Number import Data.Time.Duration (Seconds(Seconds)) import Data.UInt as UInt @@ -128,7 +129,9 @@ executeContractTestsWithBlockfrost liftEffect $ Console.warn $ "Warning: It is recommended to set TX_CONFIRMATION_DELAY_SECONDS to at " <> "least 20 seconds to let the changes propagate after transaction " - <> "submission." + <> "submission. Current value: " + <> show (fromMaybe 0.0 (unwrap <$> confirmTxDelay)) + <> "s." testKeysDirectory <- getEnvVariable "BACKUP_KEYS_DIR" "Please specify a directory to store temporary private keys in" blockfrostConfig <- liftEffect $ readBlockfrostServerConfig diff --git a/src/Internal/BalanceTx/Collateral.purs b/src/Internal/BalanceTx/Collateral.purs index 29cb936c09..f7eccf29e5 100644 --- a/src/Internal/BalanceTx/Collateral.purs +++ b/src/Internal/BalanceTx/Collateral.purs @@ -53,7 +53,7 @@ addTxCollateral collateral transaction = -- | to `minRequiredCollateral`, returns unmodified transaction (see NOTE). -- | -- | NOTE: Collateral cannot be less than `minRequiredCollateral` when --- | selected using `selectCollateral` function in this module. +-- | selected using `selectCollateral` function addTxCollateralReturn :: Array TransactionUnspentOutput -> Transaction diff --git a/src/Internal/Test/KeyDir.purs b/src/Internal/Test/KeyDir.purs index a939e13d0d..cc2093a636 100644 --- a/src/Internal/Test/KeyDir.purs +++ b/src/Internal/Test/KeyDir.purs @@ -4,7 +4,11 @@ module Ctl.Internal.Test.KeyDir import Prelude -import Contract.Address (getWalletAddresses, ownPaymentPubKeysHashes) +import Contract.Address + ( addressToBech32 + , getWalletAddresses + , ownPaymentPubKeysHashes + ) import Contract.Config (ContractParams) import Contract.Hashing (publicKeyHash) import Contract.Log (logError', logTrace') @@ -24,7 +28,7 @@ import Contract.Transaction , submit , submitTxFromConstraints ) -import Contract.Utxos (utxosAt) +import Contract.Utxos (getWalletBalance, utxosAt) import Contract.Value (valueToCoin') import Contract.Wallet (privateKeysToKeyWallet, withKeyWallet) import Contract.Wallet.Key @@ -69,7 +73,7 @@ import Data.Array as Array import Data.BigInt (BigInt) import Data.BigInt as BigInt import Data.Either (Either(Right, Left), hush) -import Data.Foldable (fold) +import Data.Foldable (fold, sum) import Data.Lens ((^.)) import Data.List (List(Cons, Nil)) import Data.List as List @@ -91,9 +95,8 @@ import Effect.Aff.Retry , recovering ) import Effect.Class (liftEffect) -import Effect.Class.Console (log) -import Effect.Console as Console -import Effect.Exception (error) +import Effect.Class.Console (info) +import Effect.Exception (error, throw) import Effect.Ref as Ref import Mote.Monad (mapTest) import Node.Encoding (Encoding(UTF8)) @@ -118,47 +121,95 @@ runContractTestsWithKeyDir runContractTestsWithKeyDir params backup = do mapTest \(ContractTest runContractTest) -> do withContractEnv params \env -> do - keyWallets <- liftAff $ restoreWallets backup - when (Array.length keyWallets > 0) do - liftEffect $ Console.log + keyWalletArr <- liftAff $ restoreWallets backup + when (Array.length keyWalletArr > 0) do + liftEffect $ info "Checking the backup wallets for leftover funds..." - returnFunds backup env keyWallets Nothing - runContractTest \distr mkTest -> withContractEnv params \env -> do - let - distrArray :: Array (Array UtxoAmount) - distrArray = encodeDistribution distr + returnFunds backup env keyWalletArr Nothing false + runContractTest \distr mkTest -> do + addressStr /\ balance <- runContractInEnv env $ noLogs do + address <- + liftMaybe + ( error + "Impossible happened: unable to get own address" + ) =<< (getWalletAddresses <#> Array.head) + addressStr <- addressToBech32 address + balance <- getWalletBalance <#> fold + pure $ addressStr /\ balance + let + distrArray :: Array (Array UtxoAmount) + distrArray = encodeDistribution distr - privateKeys <- liftEffect $ for distrArray \_ -> freshPrivateKey + -- Check if we have enough funds to distribute them (with some extra + -- room). The fact our estimations are not precise is not a problem, + -- because it is expected that test wallets have thousands of ADA. + let + distrTotalAmount :: BigInt + distrTotalAmount = sum $ map sum distrArray - wallets <- - liftMaybe - ( error - "Impossible happened: could not decode wallets. Please report as bug" - ) - $ decodeWallets distr privateKeys + minAdaRoughEstimation :: BigInt + minAdaRoughEstimation = BigInt.fromInt 1_000_000 - let - walletsArray :: Array KeyWallet - walletsArray = keyWallets (pureProxy distr) wallets + feesToDistribute :: BigInt + feesToDistribute = + -- fees + minAda for all UTxOs, overestimated + BigInt.fromInt 2_000_000 + + minAdaRoughEstimation * BigInt.fromInt + (sum (Array.length <$> distrArray)) + + -- check if we have enough funds + when (valueToCoin' balance <= distrTotalAmount + feesToDistribute) do + liftEffect $ throw $ + "The test engine cannot satisfy the requested ADA distribution " + <> "because there are not enough funds left. \n\n" + <> "Total required value is: " + <> BigInt.toString distrTotalAmount + <> " Lovelace (estimated)\n" + <> "Total available value is: " + <> BigInt.toString (valueToCoin' balance) + <> "\nThe test suite is using this address: " + <> addressStr + <> "\nFund it to continue." + + -- generate wallets + privateKeys <- liftEffect $ for distrArray \_ -> freshPrivateKey + wallets <- + liftMaybe + ( error + "Impossible happened: could not decode wallets. Please report as bug" + ) + $ decodeWallets distr privateKeys - runContract :: Aff Unit - runContract = runContractInEnv env { wallet = Nothing } do - mkTest wallets + let + walletsArray :: Array KeyWallet + walletsArray = keyWallets (pureProxy distr) wallets - if Array.null walletsArray then - runContract - else Aff.bracket - ( backupWallets backup env walletsArray *> fundWallets env walletsArray - distrArray - ) - -- Retry fund returning until success or timeout. Submission will fail if - -- the node has seen the wallets utxos being spent previously, so retrying - -- will allow the wallets utxos to eventually represent a spendable set - ( \funds -> recovering returnFundsRetryPolicy ([ \_ _ -> pure true ]) - \_ -> returnFunds backup env walletsArray (Just funds) *> - runContractInEnv env (markAsInactive backup walletsArray) - ) - \_ -> runContract + runTheContract :: Aff Unit + runTheContract = runContractInEnv env { wallet = Nothing } do + mkTest wallets + + -- We want to distinguish between successful and non-successful runs + hasRunRef <- liftEffect $ Ref.new false + + if Array.null walletsArray then + runTheContract + else Aff.bracket + ( do + backupWallets backup env walletsArray + fundWallets env walletsArray distrArray + ) + -- Retry fund returning until success or timeout. Submission will fail if + -- the node has seen the wallets utxos being spent previously, so retrying + -- will allow the wallets utxos to eventually represent a spendable set + ( \funds -> recovering returnFundsRetryPolicy ([ \_ _ -> pure true ]) + \_ -> do + hasRun <- liftEffect $ Ref.read hasRunRef + returnFunds backup env walletsArray (Just funds) hasRun + runContractInEnv env (markAsInactive backup walletsArray) + ) + \_ -> do + runTheContract + liftEffect $ Ref.write true hasRunRef where pureProxy :: forall (a :: Type). a -> Proxy a pureProxy _ = Proxy @@ -180,7 +231,7 @@ markAsInactive backup wallets = do inactiveFlagFile = Path.concat [ backup, address, "inactive" ] liftAff $ writeTextFile UTF8 inactiveFlagFile $ "This address was marked as inactive. " - <> "The test suite assumes that there are no funds left on it. " + <> "The test engine assumes that there are no funds left on it. " <> "You can check it by inspecting the address on a chain explorer." -- | Restore all wallets from the backups that are not marked as inactive. @@ -250,7 +301,7 @@ fundWallets env walletsArray distrArray = runContractInEnv env $ noLogs do awaitTxConfirmed txHash let fundTotal = Array.foldl (+) zero $ join distrArray -- Use log so we can see, regardless of suppression - log $ joinWith " " + info $ joinWith " " [ "Sent" , BigInt.toString fundTotal , "lovelace to test wallets" @@ -292,62 +343,74 @@ returnFundsRetryPolicy = limitRetriesByCumulativeDelay -- | Find all non-empty wallets and return the funds. -- | Accepts an optional expected Lovelace number to be returned. returnFunds - :: FilePath -> ContractEnv -> Array KeyWallet -> Maybe BigInt -> Aff Unit -returnFunds backup env allWalletsArray mbFundTotal = runContractInEnv env $ - noLogs do - nonEmptyWallets <- catMaybes <$> for allWalletsArray \wallet -> do - withKeyWallet wallet do - utxoMap <- liftedM "Failed to get utxos" $ - (getWalletAddresses <#> Array.head) >>= traverse utxosAt - if Map.isEmpty utxoMap then do - markAsInactive backup [ wallet ] - pure Nothing - else pure $ Just (utxoMap /\ wallet) + :: FilePath + -> ContractEnv + -> Array KeyWallet + -> Maybe BigInt + -> Boolean + -> Aff Unit +returnFunds backup env allWalletsArray mbFundTotal hasRun = runContractInEnv env + $ + noLogs do + nonEmptyWallets <- catMaybes <$> for allWalletsArray \wallet -> do + withKeyWallet wallet do + utxoMap <- liftedM "Failed to get utxos" $ + (getWalletAddresses <#> Array.head) >>= traverse utxosAt + if Map.isEmpty utxoMap then do + markAsInactive backup [ wallet ] + pure Nothing + else pure $ Just (utxoMap /\ wallet) - when (Array.length nonEmptyWallets /= 0) do - -- Print the messages only if we are running during initial fund recovery - when (isNothing mbFundTotal) do - log $ "Non-empty wallets found: " <> show (Array.length nonEmptyWallets) - log $ "Trying to return the funds back to the main wallet before " <> - "starting the test suite..." - let utxos = nonEmptyWallets # map fst # Map.unions + when (Array.length nonEmptyWallets /= 0) do + -- Print the messages only if we are running during initial fund recovery + when (isNothing mbFundTotal) do + info $ "Non-empty wallets found: " <> show + (Array.length nonEmptyWallets) + info $ "Returning ADA back to the main wallet before " <> + "starting the test suite..." + let utxos = nonEmptyWallets # map fst # Map.unions - pkhs <- fold <$> for nonEmptyWallets - (snd >>> flip withKeyWallet ownPaymentPubKeysHashes) + pkhs <- fold <$> for nonEmptyWallets + (snd >>> flip withKeyWallet ownPaymentPubKeysHashes) - let - constraints = flip foldMap (Map.keys utxos) mustSpendPubKeyOutput - <> foldMap mustBeSignedBy pkhs - lookups = unspentOutputs utxos + let + constraints = flip foldMap (Map.keys utxos) mustSpendPubKeyOutput + <> foldMap mustBeSignedBy pkhs + lookups = unspentOutputs utxos - unbalancedTx <- liftedE $ mkUnbalancedTx (lookups :: _ Void) constraints - balancedTx <- liftedE $ balanceTx unbalancedTx - balancedSignedTx <- Array.foldM - (\tx wallet -> withKeyWallet wallet $ signTransaction tx) - (wrap $ unwrap balancedTx) - (nonEmptyWallets <#> snd) + unbalancedTx <- liftedE $ mkUnbalancedTx (lookups :: _ Void) constraints + balancedTx <- liftedE $ balanceTx unbalancedTx + balancedSignedTx <- Array.foldM + (\tx wallet -> withKeyWallet wallet $ signTransaction tx) + (wrap $ unwrap balancedTx) + (nonEmptyWallets <#> snd) - txHash <- submit balancedSignedTx - awaitTxConfirmed txHash + txHash <- submit balancedSignedTx + awaitTxConfirmed txHash - let - (refundTotal :: BigInt) = Array.foldl - (\acc txorf -> acc + valueToCoin' (txorf ^. _output ^. _amount)) - zero - (Array.fromFoldable $ Map.values utxos) + let + (refundTotal :: BigInt) = Array.foldl + (\acc txorf -> acc + valueToCoin' (txorf ^. _output ^. _amount)) + zero + (Array.fromFoldable $ Map.values utxos) - log $ joinWith " " $ - [ "Refunded" - , BigInt.toString refundTotal - , "Lovelace" - ] <> maybe [] - ( \fundTotal -> - [ "of" - , BigInt.toString fundTotal - , "Lovelace from test wallets" - ] - ) - mbFundTotal + info $ joinWith " " $ + [ "Refunded" + , BigInt.toString refundTotal + , "Lovelace" + ] <> maybe [] + ( \fundTotal -> + [ "of" + , BigInt.toString fundTotal + , "Lovelace from test wallets" + ] + ) + mbFundTotal + for_ mbFundTotal \fundTotal -> do + when (fundTotal == refundTotal && hasRun) do + info $ "The test below didn't spend any ADA. Perhaps it does not " + <> "need any funds to succeed. Consider using `noWallet` to " + <> "skip funds distribution step" -- | A helper function that abstracts away conversion between `KeyWallet` and -- | its address and just gives us a `TxConstraints` value. From bf7acb8b05521bfc2e60888ee02953b61623f4d7 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Thu, 16 Feb 2023 16:49:14 +0400 Subject: [PATCH 363/373] Lower Plutip tests ADA requirements even more --- test/Plutip/Contract.purs | 42 +++++++++++++++++++-------------------- 1 file changed, 21 insertions(+), 21 deletions(-) diff --git a/test/Plutip/Contract.purs b/test/Plutip/Contract.purs index 7328ec917b..f89c0b1def 100644 --- a/test/Plutip/Contract.purs +++ b/test/Plutip/Contract.purs @@ -183,8 +183,8 @@ suite = do let distribution :: InitialUTxOs /\ InitialUTxOs distribution = - [ BigInt.fromInt 1_000_000_000 - , BigInt.fromInt 2_000_000_000 + [ BigInt.fromInt 10_000_000 + , BigInt.fromInt 20_000_000 ] /\ [ BigInt.fromInt 2_000_000_000 ] withWallets distribution \(alice /\ bob) -> do @@ -196,7 +196,7 @@ suite = do { output: TransactionOutputWithRefScript { output } } ] -> do let amount = (unwrap output).amount - unless (amount == lovelaceValueOf (BigInt.fromInt 1_000_000_000)) + unless (amount == lovelaceValueOf (BigInt.fromInt 10_000_000)) $ throw "Wrong UTxO selected as collateral" Just _ -> do -- not a bug, but unexpected @@ -208,8 +208,8 @@ suite = do let distribution :: InitialUTxOs distribution = - [ BigInt.fromInt 1_000_000_000 - , BigInt.fromInt 2_000_000_000 + [ BigInt.fromInt 10_000_000 + , BigInt.fromInt 20_000_000 ] withWallets distribution \alice -> do checkUtxoDistribution distribution alice @@ -223,8 +223,8 @@ suite = do do let aliceUtxos = - [ BigInt.fromInt 2_000_000_000 - , BigInt.fromInt 2_000_000_000 + [ BigInt.fromInt 20_000_000 + , BigInt.fromInt 20_000_000 ] distribution = withStakeKey privateStakeKey aliceUtxos @@ -242,12 +242,12 @@ suite = do do let aliceUtxos = - [ BigInt.fromInt 1_000_000_000 - , BigInt.fromInt 2_000_000_000 + [ BigInt.fromInt 20_000_000 + , BigInt.fromInt 20_000_000 ] bobUtxos = - [ BigInt.fromInt 1_000_000_000 - , BigInt.fromInt 2_000_000_000 + [ BigInt.fromInt 20_000_000 + , BigInt.fromInt 20_000_000 ] distribution :: InitialUTxOs /\ InitialUTxOs @@ -276,11 +276,11 @@ suite = do let aliceUtxos = [ BigInt.fromInt 1_000_000_000 - , BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 20_000_000 ] bobUtxos = [ BigInt.fromInt 1_000_000_000 - , BigInt.fromInt 2_000_000_000 + , BigInt.fromInt 20_000_000 ] distribution = withStakeKey privateStakeKey aliceUtxos @@ -316,20 +316,20 @@ suite = do distribution :: InitialUTxOs /\ InitialUTxOs /\ InitialUTxOs /\ InitialUTxOs distribution = - [ BigInt.fromInt 2_000_000_000 - , BigInt.fromInt 2_000_000_000 + [ BigInt.fromInt 20_000_000 + , BigInt.fromInt 20_000_000 ] /\ - [ BigInt.fromInt 2_000_000_000 - , BigInt.fromInt 2_000_000_000 + [ BigInt.fromInt 20_000_000 + , BigInt.fromInt 20_000_000 ] /\ - [ BigInt.fromInt 2_000_000_000 - , BigInt.fromInt 2_000_000_000 + [ BigInt.fromInt 20_000_000 + , BigInt.fromInt 20_000_000 ] /\ - [ BigInt.fromInt 2_000_000_000 - , BigInt.fromInt 2_000_000_000 + [ BigInt.fromInt 20_000_000 + , BigInt.fromInt 20_000_000 ] withWallets distribution \(alice /\ bob /\ charlie /\ dan) -> do From 309ccea2395c1c8f43671351ac3768688f675a4b Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Thu, 16 Feb 2023 16:50:11 +0400 Subject: [PATCH 364/373] Document Blockfrost backend limitations and update CHANGELOG --- CHANGELOG.md | 13 ++++++++--- doc/blockfrost.md | 37 +++++++++++++++++++++++++++---- src/Contract/Test/Blockfrost.purs | 4 ++-- src/Internal/Test/KeyDir.purs | 4 ++-- 4 files changed, 47 insertions(+), 11 deletions(-) diff --git a/CHANGELOG.md b/CHANGELOG.md index 111775fa74..afdcd00a6f 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -47,24 +47,31 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/) ### Added +- **Blockfrost support** - see [`blockfrost.md`](./doc/blockfrost.md) ([#1260](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1260)) +- A test runner interface for Blockfrost (`Contract.Test.Blockfrost`). See [`blockfrost.md`](./doc/blockfrost.md) ([#1420](https://github.com/Plutonomicon/cardano-transaction-lib/issues/1420)) - `blake2b224Hash` and `blake2b224HashHex` functions for computing blake2b-224 hashes of arbitrary byte arrays ([#1323](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1323)) - `bundlePursProject` allows passing of `includeBundledModule` flag to export the bundled JS module `spago bundle-module` outputs - `Contract.Transaction` exports `mkPoolPubKeyHash` and `poolPubKeyHashToBech32` for bech32 roundtripping ([#1360](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1360)) -- A test runner interface for Blockfrost (`Contract.Test.Blockfrost`). See [`blockfrost.md`](./doc/blockfrost.md) ([#1420](https://github.com/Plutonomicon/cardano-transaction-lib/issues/1420)) - `Contract.isTxConfirmed` function to check if a transaction is confirmed at the moment. ### Changed +- **Contract interface change:** `Contract` does not have a row type parameter anymore. Use `ReaderT` or pass values explicitly to access them during runtime. +- **Contract interface change:** `ConfigParams r` is replaced by `ContractParams` with the same purpose. - `SystemStart` now has `DateTime` (rather than `String`) as the underlying type ([#1377](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1377)) - `EraSummaries` now does not have an `EncodeAeson` instance. Consider wrapping it in `OgmiosEraSummaries` for Aeson encoding. ([#1377](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1377)) - Testing interface is re-implemented. Assertion functions from `Contract.Test.Utils` are moved to `Contract.Test.Assert`. See [the docs](./doc/test-utils.md) for info on the new interface. ([#1389](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1389)) - Balancer no longer selects UTxOs which use PlutusV2 features when the transaction contains PlutusV1 scripts ([#1349](https://github.com/Plutonomicon/cardano-transaction-lib/issues/1349)) - `startPlutipCluster` error message now includes cluster startup failure details. ([#1407](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1407)) -- `PlutipTest` is now known as `Contract.Test.ContractTest`. It has been semantically untied from Plutip, because we now have another test runner for tests that rely on particular funds distributions - [Blockfrost](./doc/blockfrost.md). See `Contract.Test.Blockfrost.runContractTestsWithBlockfrost`. -- `Contract.Staking.getPoolParameters` has been moved to `Contract.Backend.Ogmios.getPoolParameters`. This function only runs with Ogmios backend, because Blockfrost [does not provide](https://github.com/blockfrost/blockfrost-backend-ryo/issues/82) all the required values. +- `PlutipTest` is now known as `Contract.Test.ContractTest`. It has been semantically untied from Plutip, because we now have another test runner for tests that rely on particular funds distributions - [Blockfrost](./doc/blockfrost.md). See `Contract.Test.Blockfrost.runContractTestsWithBlockfrost` ([#1260](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1260)) +- `Contract.Staking.getPoolParameters` has been moved to `Contract.Backend.Ogmios.getPoolParameters`. This function only runs with Ogmios backend, because Blockfrost [does not provide](https://github.com/blockfrost/blockfrost-backend-ryo/issues/82) all the required values ([#1260](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1260)) +- Use of [CIP-40](https://cips.cardano.org/cips/cip40/) collateral output is now enabled with CIP-30 wallets ([#1260](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1260)). +- `reindexSpentScriptRedeemers` is no longer in Contract (it's pure) ([#1260](https://github.com/Plutonomicon/cardano-transaction-lib/pull/1260)) ### Removed +- **Important** [Ogmios Datum Cache](https://github.com/mlabs-haskell/ogmios-datum-cache) is no longer a runtime dependency of CTL, as well as its Postgres DB - if updating, remove them from your runtime. + ### Fixed - CIP-25 strings are now being split into chunks whose sizes are less than or equal to 64 to adhere to the CIP-25 standard ([#1343](https://github.com/Plutonomicon/cardano-transaction-lib/issues/1343)) - Critical upstream fix in [`purescript-bignumber`](https://github.com/mlabs-haskell/purescript-bignumber/pull/2) diff --git a/doc/blockfrost.md b/doc/blockfrost.md index ae23e696db..1cfdca2543 100644 --- a/doc/blockfrost.md +++ b/doc/blockfrost.md @@ -9,9 +9,13 @@ - [3. Funding your address](#3-funding-your-address) - [4. Setting up a directory for temporary keys](#4-setting-up-a-directory-for-temporary-keys) - [5. Providing an API endpoint URL](#5-providing-an-api-endpoint-url) - - [6. Extra configuration options](#6-extra-configuration-options) + - [6. Setting Tx confirmation delay](#6-setting-tx-confirmation-delay) - [7. Test suite setup on PureScript side](#7-test-suite-setup-on-purescript-side) - [Running `Contract`s with Blockfrost](#running-contracts-with-blockfrost) +- [Limitations](#limitations) + - [Performance](#performance) + - [Transaction chaining](#transaction-chaining) + - [Getting pool parameters](#getting-pool-parameters) - [See also](#see-also) @@ -87,15 +91,24 @@ export BLOCKFROST_SECURE=true # Use HTTPS export BLOCKFROST_PATH="/api/v0" ``` -### 6. Extra configuration options +### 6. Setting Tx confirmation delay -If the tests are failing because the effects of the transaction do not seem -to propagate, it is possible to increase the delay after transaction submission. Blockfrost does not update the query layer state atomically (proxied Ogmios eval-tx endpoint seems to lag behind the DB), so this is the best workaround we can have: +We introduce an artificial delay after Tx confirmation to ensure that the changes propagate to Blockfrost's query layer. +Blockfrost does not update the query layer state atomically (proxied Ogmios eval-tx endpoint seems to lag behind the DB), and we have no way to query it, so this is the best workaround we can have. +If the tests are failing because the effects of the transaction do not seem to propagate (the symptom is unexpected errors from Ogmios), it is possible to increase the delay by setting the environment variable for the test suite: ```bash export TX_CONFIRMATION_DELAY_SECONDS=30 ``` +The "safe" value in practice is 30 seconds. + +If there's a problem with UTxO set syncrhonization, most commonly Blockfrost returns error code 400 on transaction submission: + +``` +[TRACE] 2023-02-16T12:26:13.019Z { body: "{\"error\":\"Bad Request\",\"message\":\"\\\"transaction submit error ShelleyTxValidationError ShelleyBasedEraBabbage (ApplyTxError [UtxowFailure (UtxoFailure (FromAlonzoUtxoFail (ValueNotConservedUTxO ... +``` + ### 7. Test suite setup on PureScript side `executeContractTestsWithBlockfrost` is a helper function that reads all the variables above and takes care of contract environment setup. @@ -123,6 +136,22 @@ type BlockfrostBackendParams = For convenience, use `blockfrostPublicMainnetServerConfig`, `blockfrostPublicPreviewServerConfig` or `blockfrostPublicPreprodServerConfig` for pre-configured `ServerConfig` setups. +## Limitations + +### Performance + +The main disadvantage of using Blockfrost in comparison with CTL backend is speed of Tx confirmation (see [here](#6-setting-tx-confirmation-delay) for explanation). + +### Transaction chaining + +Blockfrost is proxying [Ogmios](https://ogmios.dev) to provide an endpoint for execution units evaluation. This Ogmios endpoint normally [accepts a parameter](https://ogmios.dev/mini-protocols/local-tx-submission/#additional-utxo-set) that allows to specify additional UTxOs that should be considered. Transaction chaining is relying on this feature to allow Ogmios to "see" the newly created UTxOs. But Blockfrost seems to not pass this parameter to Ogmios ([issue](https://github.com/blockfrost/blockfrost-backend-ryo/issues/85)). + +### Getting pool parameters + +`getPoolParameters` function only runs with Ogmios backend, see [here](https://github.com/blockfrost/blockfrost-backend-ryo/issues/82) for more context. + +It is not used for constraints resolution, the only way to make it run is to call it manually. + ## See also - [Testing utilities for CTL](./test-utils.md). diff --git a/src/Contract/Test/Blockfrost.purs b/src/Contract/Test/Blockfrost.purs index 97fdc070e5..88c3d58027 100644 --- a/src/Contract/Test/Blockfrost.purs +++ b/src/Contract/Test/Blockfrost.purs @@ -125,10 +125,10 @@ executeContractTestsWithBlockfrost lookupEnv "PRIVATE_STAKE_KEY_FILE" <#> notEmptyString confirmTxDelay <- liftEffect $ lookupEnv "TX_CONFIRMATION_DELAY_SECONDS" >>= parseConfirmationDelay - when (confirmTxDelay < Just (Seconds 20.0)) do + when (confirmTxDelay < Just (Seconds 30.0)) do liftEffect $ Console.warn $ "Warning: It is recommended to set TX_CONFIRMATION_DELAY_SECONDS to at " - <> "least 20 seconds to let the changes propagate after transaction " + <> "least 30 seconds to let the changes propagate after transaction " <> "submission. Current value: " <> show (fromMaybe 0.0 (unwrap <$> confirmTxDelay)) <> "s." diff --git a/src/Internal/Test/KeyDir.purs b/src/Internal/Test/KeyDir.purs index cc2093a636..8b3e1bd674 100644 --- a/src/Internal/Test/KeyDir.purs +++ b/src/Internal/Test/KeyDir.purs @@ -349,8 +349,8 @@ returnFunds -> Maybe BigInt -> Boolean -> Aff Unit -returnFunds backup env allWalletsArray mbFundTotal hasRun = runContractInEnv env - $ +returnFunds backup env allWalletsArray mbFundTotal hasRun = + runContractInEnv env $ noLogs do nonEmptyWallets <- catMaybes <$> for allWalletsArray \wallet -> do withKeyWallet wallet do From e334ab6b8ac0a1ec7765a1e9d3b971c131c57000 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Thu, 16 Feb 2023 17:02:16 +0400 Subject: [PATCH 365/373] Fix warnings --- src/Contract/Transaction.purs | 1 - test/Plutip/Contract.purs | 2 +- 2 files changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Contract/Transaction.purs b/src/Contract/Transaction.purs index 4f311898af..9966627ded 100644 --- a/src/Contract/Transaction.purs +++ b/src/Contract/Transaction.purs @@ -286,7 +286,6 @@ import Data.Map (empty, insert) as Map import Data.Maybe (Maybe) import Data.Newtype (class Newtype, unwrap) import Data.Show.Generic (genericShow) -import Data.Time.Duration (Seconds) import Data.Traversable (class Traversable, for_, traverse) import Data.Tuple (Tuple(Tuple), fst) import Data.Tuple.Nested (type (/\), (/\)) diff --git a/test/Plutip/Contract.purs b/test/Plutip/Contract.purs index f89c0b1def..df9daf0846 100644 --- a/test/Plutip/Contract.purs +++ b/test/Plutip/Contract.purs @@ -156,7 +156,7 @@ import Data.Tuple.Nested (type (/\), (/\)) import Data.UInt (UInt) import Effect.Class (liftEffect) import Effect.Exception (throw) -import Mote (group, skip, test) +import Mote (group, test) import Safe.Coerce (coerce) import Test.Ctl.Fixtures ( cip25MetadataFixture1 From 5f9c7523d18c49f8895dfcd67fb36f70b19860ea Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Thu, 16 Feb 2023 17:24:03 +0400 Subject: [PATCH 366/373] Fix typo --- doc/e2e-testing.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/doc/e2e-testing.md b/doc/e2e-testing.md index b13d282e95..22818d0560 100644 --- a/doc/e2e-testing.md +++ b/doc/e2e-testing.md @@ -42,7 +42,7 @@ For a working example see `test/E2E.purs`. It can be run conveniently using `npm ## User perspective -- Use `npm run e2e-serve` to [serve]((#serving-the-contract-to-be-tested) the examples for testing. +- Use `npm run e2e-serve` to [serve](#serving-the-contract-to-be-tested) the examples for testing. - Use `npm run e2e-test` to run the test suite in headless mode or `npm run e2e-test-debug` to enable the browser UI. - Use `npm run e2e-browser` to open the browser window with extensions pre-loaded. If you modify any setting (e.g. set a collateral), it's important to run `npm run e2e-pack-settings` **without running anything in between**. The test suite resets the settings by loading them from the settings archive before each test run. From fe35e4bb77a5a5d49c9b4a03c2b551b85ee4f7e6 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Thu, 16 Feb 2023 18:16:29 +0400 Subject: [PATCH 367/373] Update template revision --- templates/ctl-scaffold/flake.lock | 8 ++++---- templates/ctl-scaffold/flake.nix | 2 +- templates/ctl-scaffold/packages.dhall | 2 +- templates/ctl-scaffold/spago-packages.nix | 6 +++--- 4 files changed, 9 insertions(+), 9 deletions(-) diff --git a/templates/ctl-scaffold/flake.lock b/templates/ctl-scaffold/flake.lock index daec9d2394..f47537a2f8 100644 --- a/templates/ctl-scaffold/flake.lock +++ b/templates/ctl-scaffold/flake.lock @@ -1490,17 +1490,17 @@ "plutip": "plutip" }, "locked": { - "lastModified": 1675182481, - "narHash": "sha256-ciwRyjbIlkyaSQ/RMm89xu0wYlP3K2u0nbCLXH3OH+4=", + "lastModified": 1676553843, + "narHash": "sha256-XRn4OdRYG2CvKzt8Oa1389mW9UzKSOkq33F/0FTBLTs=", "owner": "Plutonomicon", "repo": "cardano-transaction-lib", - "rev": "1816887c0772652f01bbd82ed42d759daa816d1d", + "rev": "5f9c7523d18c49f8895dfcd67fb36f70b19860ea", "type": "github" }, "original": { "owner": "Plutonomicon", "repo": "cardano-transaction-lib", - "rev": "1816887c0772652f01bbd82ed42d759daa816d1d", + "rev": "5f9c7523d18c49f8895dfcd67fb36f70b19860ea", "type": "github" } }, diff --git a/templates/ctl-scaffold/flake.nix b/templates/ctl-scaffold/flake.nix index adafe61a8a..3a721fe53d 100644 --- a/templates/ctl-scaffold/flake.nix +++ b/templates/ctl-scaffold/flake.nix @@ -10,7 +10,7 @@ type = "github"; owner = "Plutonomicon"; repo = "cardano-transaction-lib"; - rev = "1816887c0772652f01bbd82ed42d759daa816d1d"; + rev = "5f9c7523d18c49f8895dfcd67fb36f70b19860ea"; }; # To use the same version of `nixpkgs` as we do nixpkgs.follows = "ctl/nixpkgs"; diff --git a/templates/ctl-scaffold/packages.dhall b/templates/ctl-scaffold/packages.dhall index bb68739060..a01e4fc9cb 100644 --- a/templates/ctl-scaffold/packages.dhall +++ b/templates/ctl-scaffold/packages.dhall @@ -353,7 +353,7 @@ let additions = , "web-html" ] , repo = "https://github.com/Plutonomicon/cardano-transaction-lib.git" - , version = "1816887c0772652f01bbd82ed42d759daa816d1d" + , version = "5f9c7523d18c49f8895dfcd67fb36f70b19860ea" } , noble-secp256k1 = { dependencies = diff --git a/templates/ctl-scaffold/spago-packages.nix b/templates/ctl-scaffold/spago-packages.nix index e8954fcd71..fd3ebe7b38 100644 --- a/templates/ctl-scaffold/spago-packages.nix +++ b/templates/ctl-scaffold/spago-packages.nix @@ -211,11 +211,11 @@ let "cardano-transaction-lib" = pkgs.stdenv.mkDerivation { name = "cardano-transaction-lib"; - version = "1816887c0772652f01bbd82ed42d759daa816d1d"; + version = "5f9c7523d18c49f8895dfcd67fb36f70b19860ea"; src = pkgs.fetchgit { url = "https://github.com/Plutonomicon/cardano-transaction-lib.git"; - rev = "1816887c0772652f01bbd82ed42d759daa816d1d"; - sha256 = "1vhzrrymr2xhkns6nazpadi31vf67mpk5l8g96d4r5n86v512b3j"; + rev = "5f9c7523d18c49f8895dfcd67fb36f70b19860ea"; + sha256 = "0frdq5ad0zvivwmfjj6a9ksrdngkfynkjz1v5fpn06sqshwzh6ax"; }; phases = "installPhase"; installPhase = "ln -s $src $out"; From 83476e9bce41efdf3307a6c036b5fd78895ee0d8 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Thu, 16 Feb 2023 19:09:08 +0400 Subject: [PATCH 368/373] Keep keys directory in template in the repo. --- doc/video-intro.md | 2 ++ templates/ctl-scaffold/test-data/keys/.gitkeep | 0 2 files changed, 2 insertions(+) create mode 100644 templates/ctl-scaffold/test-data/keys/.gitkeep diff --git a/doc/video-intro.md b/doc/video-intro.md index d61ed42d03..9259d13dcb 100644 --- a/doc/video-intro.md +++ b/doc/video-intro.md @@ -1,3 +1,5 @@ + + # Video introduction We [provide](https://drive.google.com/file/d/1ELVvL4WLKTQLg4VJMzt0yj8C0H8xsXS1/view?usp=sharing) a screencast video showcasing some features of CTL. diff --git a/templates/ctl-scaffold/test-data/keys/.gitkeep b/templates/ctl-scaffold/test-data/keys/.gitkeep new file mode 100644 index 0000000000..e69de29bb2 From f6495f39e76bc456dd2080211ef7528d8ed09617 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Thu, 16 Feb 2023 19:14:42 +0400 Subject: [PATCH 369/373] Update CTL revision in template once again --- templates/ctl-scaffold/flake.lock | 8 ++++---- templates/ctl-scaffold/flake.nix | 2 +- templates/ctl-scaffold/packages.dhall | 2 +- templates/ctl-scaffold/spago-packages.nix | 6 +++--- 4 files changed, 9 insertions(+), 9 deletions(-) diff --git a/templates/ctl-scaffold/flake.lock b/templates/ctl-scaffold/flake.lock index f47537a2f8..ef15711aa0 100644 --- a/templates/ctl-scaffold/flake.lock +++ b/templates/ctl-scaffold/flake.lock @@ -1490,17 +1490,17 @@ "plutip": "plutip" }, "locked": { - "lastModified": 1676553843, - "narHash": "sha256-XRn4OdRYG2CvKzt8Oa1389mW9UzKSOkq33F/0FTBLTs=", + "lastModified": 1676560148, + "narHash": "sha256-eM+sko8wRiTb04wkNMKDFRFU0kihrBFY2UiZhusWSP0=", "owner": "Plutonomicon", "repo": "cardano-transaction-lib", - "rev": "5f9c7523d18c49f8895dfcd67fb36f70b19860ea", + "rev": "83476e9bce41efdf3307a6c036b5fd78895ee0d8", "type": "github" }, "original": { "owner": "Plutonomicon", "repo": "cardano-transaction-lib", - "rev": "5f9c7523d18c49f8895dfcd67fb36f70b19860ea", + "rev": "83476e9bce41efdf3307a6c036b5fd78895ee0d8", "type": "github" } }, diff --git a/templates/ctl-scaffold/flake.nix b/templates/ctl-scaffold/flake.nix index 3a721fe53d..d9299bf646 100644 --- a/templates/ctl-scaffold/flake.nix +++ b/templates/ctl-scaffold/flake.nix @@ -10,7 +10,7 @@ type = "github"; owner = "Plutonomicon"; repo = "cardano-transaction-lib"; - rev = "5f9c7523d18c49f8895dfcd67fb36f70b19860ea"; + rev = "83476e9bce41efdf3307a6c036b5fd78895ee0d8"; }; # To use the same version of `nixpkgs` as we do nixpkgs.follows = "ctl/nixpkgs"; diff --git a/templates/ctl-scaffold/packages.dhall b/templates/ctl-scaffold/packages.dhall index a01e4fc9cb..17962152d3 100644 --- a/templates/ctl-scaffold/packages.dhall +++ b/templates/ctl-scaffold/packages.dhall @@ -353,7 +353,7 @@ let additions = , "web-html" ] , repo = "https://github.com/Plutonomicon/cardano-transaction-lib.git" - , version = "5f9c7523d18c49f8895dfcd67fb36f70b19860ea" + , version = "83476e9bce41efdf3307a6c036b5fd78895ee0d8" } , noble-secp256k1 = { dependencies = diff --git a/templates/ctl-scaffold/spago-packages.nix b/templates/ctl-scaffold/spago-packages.nix index fd3ebe7b38..8a15943a9e 100644 --- a/templates/ctl-scaffold/spago-packages.nix +++ b/templates/ctl-scaffold/spago-packages.nix @@ -211,11 +211,11 @@ let "cardano-transaction-lib" = pkgs.stdenv.mkDerivation { name = "cardano-transaction-lib"; - version = "5f9c7523d18c49f8895dfcd67fb36f70b19860ea"; + version = "83476e9bce41efdf3307a6c036b5fd78895ee0d8"; src = pkgs.fetchgit { url = "https://github.com/Plutonomicon/cardano-transaction-lib.git"; - rev = "5f9c7523d18c49f8895dfcd67fb36f70b19860ea"; - sha256 = "0frdq5ad0zvivwmfjj6a9ksrdngkfynkjz1v5fpn06sqshwzh6ax"; + rev = "83476e9bce41efdf3307a6c036b5fd78895ee0d8"; + sha256 = "1za82vmqd6a8v5c13b519395848mhg13894csgdj8iihiy9arkvq"; }; phases = "installPhase"; installPhase = "ln -s $src $out"; From 67c31f7c756f386b96b412caef2dd7c7db33862d Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Fri, 17 Feb 2023 21:21:27 +0400 Subject: [PATCH 370/373] Add docs for NPM scripts to template --- doc/e2e-testing.md | 1 + templates/ctl-scaffold/README.md | 31 +++++++++++++++++++++++++++++-- 2 files changed, 30 insertions(+), 2 deletions(-) diff --git a/doc/e2e-testing.md b/doc/e2e-testing.md index 22818d0560..158c42e43c 100644 --- a/doc/e2e-testing.md +++ b/doc/e2e-testing.md @@ -45,6 +45,7 @@ For a working example see `test/E2E.purs`. It can be run conveniently using `npm - Use `npm run e2e-serve` to [serve](#serving-the-contract-to-be-tested) the examples for testing. - Use `npm run e2e-test` to run the test suite in headless mode or `npm run e2e-test-debug` to enable the browser UI. - Use `npm run e2e-browser` to open the browser window with extensions pre-loaded. If you modify any setting (e.g. set a collateral), it's important to run `npm run e2e-pack-settings` **without running anything in between**. The test suite resets the settings by loading them from the settings archive before each test run. +- To [pack and unpack](#how-wallets-are-used) extension settings to or from the archive file `npm run e2e-pack-settings` and `npm run e2e-unpack-settings` scripts should be used, respectively. ## How to Run the Included Examples diff --git a/templates/ctl-scaffold/README.md b/templates/ctl-scaffold/README.md index e9963c7668..2f065a4865 100644 --- a/templates/ctl-scaffold/README.md +++ b/templates/ctl-scaffold/README.md @@ -2,16 +2,43 @@ Welcome to your new CTL project! -To enter the Nix environment and start working on it, run `nix develop`. Please make sure to use Nix v2.8 or later. +## Development + +To start working on this project, enter the Nix environment by running `nix develop`. Please make sure to use Nix v2.8 or later. Please also see our - [Documentation](https://github.com/Plutonomicon/cardano-transaction-lib/tree/develop/doc) -- [Generated docs](https://plutonomicon.github.io/cardano-transaction-lib/) +- [PureScript API documentation for CTL](https://plutonomicon.github.io/cardano-transaction-lib/) - [Discord server](https://discord.gg/JhbexnV9Pc) If you encounter problems and/or want to report a bug, you can open an issue [here](https://github.com/Plutonomicon/cardano-transaction-lib/issues). Please search for existing issues beforehand! + +## Testing + +Here are a few tips on how to get started with testing your code. + +### Testing with Plutip + +[Plutip](https://github.com/Plutonomicon/cardano-transaction-lib/blob/develop/doc/plutip-testing.md) is a tool that manages local disposable cardano-node clusters that we use to test contracts locally. + +- run `npm run test` from Nix shell + +### Testing with Blockfrost + +[Blockfrost.io](https://blockfrost.io) is an alternative CTL backend that can be used as a subscription service. + +- populate the variables in [`test/blockfrost.env`](./test/blockfrost.env) following [this guide](https://github.com/Plutonomicon/cardano-transaction-lib/blob/develop/doc/blockfrost.md) +- run `npm run blockfrost-test` (no Nix shell required, but the correct versions of [Spago](https://github.com/purescript/spago/) and [PureScript compiler](https://github.com/purescript/purescript/releases/tag/v0.14.9) must be used) + +### Testing with a headless browser + +[Headless browser test suite](https://github.com/Plutonomicon/cardano-transaction-lib/blob/develop/doc/e2e-testing.md) allows to run user contracts with real wallet browser extensions automatically. + +- Start the CTL runtime: `nix run -L .#ctl-scaffold-runtime` +- run `npm run e2e-serve` from Nix shell +- run `npm run e2e-test` from Nix shell From 688ac44d269c2860b73b8aa8476445fad120997a Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Fri, 17 Feb 2023 22:25:38 +0400 Subject: [PATCH 371/373] Improve docs for E2E testing (screenshot) --- doc/development.md | 9 +++++---- doc/e2e-testing.md | 4 ++++ doc/images/e2e.png | Bin 0 -> 113042 bytes scripts/whitespace-check.sh | 2 +- 4 files changed, 10 insertions(+), 5 deletions(-) create mode 100644 doc/images/e2e.png diff --git a/doc/development.md b/doc/development.md index 89ff6c7419..c5269d1785 100644 --- a/doc/development.md +++ b/doc/development.md @@ -64,11 +64,12 @@ To develop locally, you can use one the CTL flake to launch all required service - `npm run plutip-test` for Plutip integration tests (does not require ctl-runtime) - `nix build .#checks..ctl-unit-test` will build and run the unit tests (useful for CI) - To run or build/bundle the project for the browser: - - `make run-dev` _or_ `npm run dev` will start a Webpack development server at `localhost:4008` - - `make run-build` _or_ `npm run build` will output a Webpack-bundled example module to `dist` - - `nix build -L .#ctl-example-bundle-web` will build an example module using Nix and Webpack + - `npm run e2e-serve` will start a Webpack development server at `localhost:4008` + - `npm run build` will output a Webpack-bundled example module to `dist` (or `nix build -L .#ctl-example-bundle-web` to build an example module using Nix into `./result/`) -By default, Webpack will build a [small Purescript example](../examples/Pkh2Pkh.purs). Make sure to follow the [instructions for setting up Nami](./runtime.md#other-requirements) before running the examples. You can point Webpack to another Purescript entrypoint by changing the `ps-bundle` variable in the Makefile or in the `main` argument in the flake's `packages.ctl-examples-bundle-web`. +By default, Webpack will build a [Purescript module](../examples/ByUrl.purs) that serves multiple example `Contract`s depending on URL (see [here](./e2e-testing.md#serving-the-contract-to-be-tested)). You can point Webpack to another Purescript entrypoint by changing the `ps-bundle` variable in the Makefile or in the `main` argument in the flake's `packages.ctl-examples-bundle-web`. + +You will also need a light wallet extension pre-configured. **Note**: The `BROWSER_RUNTIME` environment variable must be set to `1` in order to build/bundle the project properly for the browser (e.g. `BROWSER_RUNTIME=1 webpack ...`). For Node environments, leave this variable unset or set it to `0`. diff --git a/doc/e2e-testing.md b/doc/e2e-testing.md index 158c42e43c..c9303b8dc2 100644 --- a/doc/e2e-testing.md +++ b/doc/e2e-testing.md @@ -215,6 +215,10 @@ Note that the test closes successfully after the first successful `Contract` exe CTL offers a function to serve the `Contract`s to be tested with a router, that dispatches contracts and configuration parameters based on query part of the URL. +It also builds a page with a table consisting of links to all possible examples with all possible environments, that looks like this: + +![Headless browser test suite - served examples](./images/e2e.png) + See [this file](../templates/ctl-scaffold/test/E2E.purs) for a quick example: ```purescript diff --git a/doc/images/e2e.png b/doc/images/e2e.png new file mode 100644 index 0000000000000000000000000000000000000000..7af557e9d33eaf6ad222910d39c40564763850d7 GIT binary patch literal 113042 zcmdSARbU)T)21m|XrXN}Tb9Ml%oZ~1{pY#2Du`~0}?%Zu( zbXQeZW>rOIWkx>nMu@be5IhVf3NeGGd6WqUa*LwhG3TLTayODhWlN;^GU0|QGtV=Ma$unw-zlPLe5#BXb$ zV{c+*`BUD+!T?0j*5oHG^G`to-Jf(cbo4)IY1n94*yxylN=y7Cr(vLMjFJZd`3WNO zhgaS?{dCRA9$5jab8BNXUpf{Uz3l7DVmHh3mGCl|I3e<$e$9?rX(8!l60X7vBY z2aW&v#bI}R!v*qp>vPvxK^TPSKmVls`9kxb!-Kzncz^wO`wvl-m{nIK4mrRT$0N{8J}1ey^BR^G}%nD&n$>RVjbA;^f{R^mz>w2ypPp+yON2S^D}` z@eZlurq;uQ7=>1GgPz2sx7UoMq$?*6jEN%`Hx#d#QLY0x2yKuWqmOquM1JTiGFR); zqFH*AHt~+AyQbE`|E8ePkuS;r=2>Du#Q$@{bRpo{{~823M&vgL(!blm;=e$X|6?fq zA74BFQ{At)|Gk<152|i;mbJ7o9&&cA^$aRD2#uQa0d49iN(l=q`4Jl2;izJ3E&JE?Yg906l6_;g`7D9vLAcNYK>gNM@xh1xZFMd~v# zg&?Cg>X-!1o1DM>h(n^vY=F+bPau|2+IHU1c+h&;nM|7{sw6k|+!bMof)bZd%@Ox% zE}VYVaN;xs98VZhesu-nQl+Q+Frzy^;9ClBSCcmD>m9`46T`9pz~H%D>hKa`3^~&0 z6H)#9L_Dz}k4}gU@ckb(T@i0&=~$&3rvGxo+(#lVN^zYXmi_)p7T zeVGc53L8N7%GRF{xrgHtQRFnE)mEg08LgZL5Jh}Bq0r`1Ba-GS+g*d%gP50pLt||>4&~g`ymNfq!!9?T0w!?fp7-Z$ zFX_FkNTwcrJ>!Yw7*9A#>!HdjnV&C4dB1ANb{ zHg90}F1^iYsr`M^So6kOO0K>YQ*uXq)-vC7-Ww*s!`jJipl07WGC9;}x^8V0b3TR0 zNe@NI$vmu-DB#df4E@Cg)>QE}H>-hp9pbG}xdwt)56zBd zS@F#-YKDAZs!2z|9rkfEr322&gCVdE4VM{&F+^;|kgigLzc`-4w?T;u=1E}(fY6hS zg-N+1UXyPBqp7r`{~d$VSiKJsPYMqvzL@t!hnyvjQN)zE76>>N$xZj-RWro5yO-|_zGf+03!0X%-CbacV;Rbo`i8~&w~>8tkag3 z`aIfp&q3zDw@tBGMVYeZT2PwUJD|W8R%xNwiq#yJA5H|2v~~tL-<}NIH6L);ps4j< z_W0~G>U<*Xd`TP~uzSZ8%+(%u`s)*Rp%FDgQ`w3dzNjLBfszXbD!y*oZ@NXI7>wcUTh7S^4dAU=5CE3#xaR zARSY?WjxqgrgfLt+ac;y;dGym{iNOC$Qw$vU)k9Z%F_8J`r!}X7Ytk)?!d!EIJy%U4RkW`B10VyD6=|rj{sG!<0ul73vO0VZVxk}**}r-7e5Nm z#PRN5t8}5@FgIrFB8f3P`|R63 z<}sW>2~sMdS2MWtBj%zPWp2CHSqLSHuc z!futHMS9=5uEzi{jqh)el?z0$j4Xgzew(22ra@tcys41Yr;LVoIBQIPWiuR|2 zs_v4Odq8Zn)DCNZ{Hx*OVCG|)72_!ikJ$cf_tU>qvk56n$CP)2dbm%5#@05nq(^az zZOjhw1y=_@5=LBO7@?OYgVS6!wN@OnESUKLbD z{6*J~DY4zgPW(>>^PU-f6!P02-zW05_U-6~l*y0_s^v*Cp1%zubl3t1^FfS%15$+s z`<**GfeKW zJ#GZ5ojh3_LAbys0+(c(cr`eXK~SP}1+1AA*aDN|V*U9)$9Q3}zPX;YSkd*Vsc8q9 znMS7vE=(#WtV_h1U{%KO^9~$>Gj{j@bq7dV&O+bS;7rh-gk0|hU>tufH>Sfn-H4Z~9wi2#DF z&c(OHtltdp`Wd3I6q67%aG7n3zGZ$v-)3>%1b^Te6nHeYIe@nOa!JAdMeBVL>c#>bCzzKJT)wzA6H zcRjYRR|P_D>upbtqOpWTv<=H-B}G)^t8c9maxOx5$|rH`x)yrLz*JQwo&rej7gtp9 zVmR*=)98BpznOth-ZQj(ERFhc{y1|VK_cgzqzl4NWVcD|kQXqrIu%VEUSBV!wfK22 zNdXDhJFr$aiz3QYt>P3@-!QOGfgZ@BTY8^hYltZkCSG$T5V0F}&}0fiOiG{CJTv0oIwpax0wIE)0laNY@_=XkgFN+W@zZ`y>f zC^TYIBS?&jSpG)@Z*rn|_4;#gtZ+5k?>RzdDmvlcX3`piXF1&tdfItMaU%8Y_Cq3y zB69NTwk=sX+q>yV5Ig997&xDiOA=&d&AHuW0M?GOo6T2V4o|8yTL)2BHB-?_)lbqq z!-KG5RDe&{2Qf+{;@x>jeS-0#LbkTuu!E$X^G1ZHig|?}FtTcSPL(W4~hAfJ(#9;f*Y_;CC z#$o4}5({1%qM&+@)O2o9K|M^a&efqf?L#3q-0YW(3@Hl>_Yl3g+puDhF(x@UdQM2Q z0qd8udrC{J(YLwFa`li`vPA{#(Q+)rL_pf=B4_XXNW(|im{(`tLj9FX7Z1(kOHJ*4Rp@v;wr{dM?R*K^3Eu}`8T z0gkqzNw4I+j$ATeI`Jw*RoC%asfx;Lu1FL3?S4w8w~%!xTVE2x#Y8{bE$h?q4o2H} zgH9Aj7y8G`B(6Rkgr#wRqb-`kql_6eu_*k$n0A3?iBDJbg;(xff8-o6daMk+(uT`m zS%yAQs6gC=o%3v-KkkvbJDmk+PRdW=F9r*Tg9GfF37ii)?F4X8$M6)gXRk3T`3^YsqAj9?FWw zYzAl$GgOu7-S72@hf*lmC7J*D$a84NLw-n~?ccXB8z3zfygOMm+hN8zfGCjKe^1Kt zSO=8TAm$;|+Cgp2U^5)CPVs}PNGosXKYMeV31_Ue&bD01cP>DUV|QEp9&_)RSZPP6 z!F4{?illFiT}3CchI6E9InYmbD+M*25H03QqY-QZ4!_fOW*R*Tte-Md!kHnokv=VXrvjlp#LW5~ zbGRriF)bg}E97!=<`1!e9UDWs*j3_u_4__4AHUSM1ozAmAwE`Ts{ZN2`EzTgQxKu@ zRsI%_z{*KIb$X+^8R1sP_(?rx;qaEht;w0ys?(Upn;@2NHX-2f(yLb$>Wj0PS_E5@ zhD^B2134)pETMQPGbi~(8CB-3>&(drgxE45l#XCvn9K(?8JRQHQ`X(-wo8^EN1-z& z)57alRYJT3o^R02;VR?hgK^lfYn|a4XXsT8Ab3&l;n$9NT0{?cKTl5q47?e!B?tuk zke7y>^9%A4^57c^(hX$)O-myJNh{RIaVj-g==~=s^qJ$r@&IWF;P9G(w zT)-mrs!9dE_);E%b3T^r?`RQTGa#uMhe+A}8Nt6Wtl=JGqiNwuH?zFoNjeaoBI}@{ ze$=~u=`jTGMfvjk1ct*u#exX!5Y4{g(HRQEugdd?=^pf+hbOnhCfs!F-CQ_klP10i z30NB3wBM`>bOFy7UMGRr<78RfeWT|d&`b8wNW=tBPDAL+P-8^x`#%F)Pl!Mlkz5oX zc%0=iLL1XN+suT%vf~;Y6&J6?(S9y&uX04#DghovM-gXYa&sG`{3lHen8S#?SK`mi zKC*Zbd2&Qd*BOwMu7qHi4|--fdo{a*NA||H8742O*G_R0Dtemv-y1whA{s2Ux8G&{ zKtNnuG%9$F=BeoO9DXKQsHAvy46=bzIrx?(I_FFo78%0L#m^_LIfIg)KlovE#Z`H2kQx}`~(hkJpq`XOCpo*t-`8u?)un-34b1&{} z%lKDUwDDgaPdsJu;p%B8X{MOdfE^(2TW=pgvZzJ|t1G-z+Mk?^X5Pb!F`XK|3f-X_ zTK{f{qP}ATpQbvL!+c^B>0y&QVr2kQju~p!>-Wv-DzmdhkDc^?uRldghBLZN$2d%F|Oyn>cznNe)JDLc(oZJSpNMF~mmfk&uRLP;%FuF6#z2Id_ zC-AgGpF>#$R?>d|8REfhpEXwBWxg?qr3JvM6DrfcN$a@WvGS^7G>709taL6esP`0^{4ra{uTuBHrlNtM$W@s`z>}-qBeGWH6 zF`Ry5j4yl)7cz~mcL2TTRkuwoXlBc4oFq#?h0ASBQS*hHAZ%K}7 zZF4y&sM+6;^wRy|z!AQ3`EHF*`*9ZD_kmAnO5Jg5B@t2GcX>Z5B=f=J`q~^7!C#z5 z31%5^R6RVcp%fOPuVT%d+NKb*{p4{uuH}2ps5-58?K-|*W3J_8%~0XOp{_ap=gjcf z2){ zaxMfoh4`xQTcFZTE8K=7a=RDnVvb%SkqnpcXxY*b{zN>EnM|6Z{ug*)L4YIou6B^)XqA6nOYb8bm!W(+D5?MvLUbB`!Mr#`X zl9DW*#J?d3%B2l<{e!4_nAi9 z0xY<}rz)$dpITw1b42A_-!TQl?~`{nZeIh*|KhqqU4|ScgnXGZM|XNRqyf7+?cwDy z3M|=x$2BqZg(6TN{swC?u*t25BWgsrW5>-q(2-A4KzXw8Dq0YmFSMdc;Wp5ar5MI5 zuI2H~G)iYL5hdJ9XdpX5?r^CQbnT@t=LgC7>ZuD}n_}UTb`KL3sx%i5{#jEn%;95bj%`OOwF7xHF$fjE5(#a3U`P^ zmI`yUBLMr7Hp8t?@Lg$VP^KERY`tu7?THh;v7e4e#Gyp;#k0+L+pN|0`DWy?^_<-v zL38kaB;b(43=Hc4T;}wcY2R}u(Up?;yX!(@d29=E9T=8enYSOIn%cCC=W`)W96`0* z@CF)l32Qmr0y9me3?&yjcK0zqnS&s;&PXCKygb*|*a6y)yHKE~VxBuLTwnDRGtiSQ z7Gi~f#p9e};J(aIwBcNwy9kPqy-!U-e_QAYNP8=c>Eswu;1c0AXp4JX+sso~xBvG`41B z5{(;1@goURFOO!lt*Ed9kqCEsmN=-BB`+BE(g2A+#qY|+wKvm{YecP)JIsDtxW0?n zUDUbUC@wnRz0Y-IO1@#VVbQ%kDQ~2(j z{*mz!Oia}D3<2xCl{ZP@quO%ni=xG&kKuVSD@aKq@g0cl|AOeeQmb6Wrz4Xnv07{+ z5HbspL45nRDMh<*TWk+;;JbH8t>&Fx|BIm@wDx=LjXQrE)&OIjOyEMMmN!D1?`?=;rxk))=$*!A+hF(oyFY zPi={=jy0fK*pH%Q`rKUGIO*$YYl?6F;*D$6lzp)b=7y*Q23sR*2AT1LR88Z=!K-;H z{GzoDuAiXAPCjU7XG=jaJ5RU#V@F_J1v|)0d=7pXivk>Z*2;Zq+ptlsFU82I?YHoC?+L`#okWDPV(~ zS^l088s8~B0tI^Te52i5v{H;JkEl9m^C|3rq&pS-c2ZAa z(4}RDzOl#gYJBDzB8(2Fx=kiOq+OcO9)>+HsAh;fRt0RtIPH z62l1mLQff6j<&V7JO;~GobGD!eAwJ)>2h^VyPc_Qd6!r5p`W!a*{^hF+#=|WwWg#k zvPcmBQnLQk8J}4A6S>j-xRe5EsW5SUp*=_ki8Ut$j!={?R>l+0Q4vXHV9y+iiO^v4 zQ0;9s0=s-G3>w2&L_v(bG4Tu1^h%QGIa}G+TUpS6RnPW3OHl$SM%4}>Pn;~4os*=E z+f6Bcul?UfHHTxO|1@R}F&%~P?rf*%kWcP8?$@uM$Z3^7iL)*&U9fu{fIV#dVDTo> z-Murmh83UAI=LoBWBE{yFfiMsTC0!n(UPRB<^#}`dLrAS#2AZDf1LM>I)1_}6;x2? zT&1+~#KxgqgJ6tsbGj&?mn1inS>v=}&P)Z1+(%kybXvH_7TtcLQ)eBfy*Vw1iNwWK zvc%+<0h7sXo4~nDPgW< zgJIKGitk}Yt;;!B(^YOh^f%*3tyt)e*3KQvW;LmUq=NYTFdzHMBz(I6=KJ2S~ z-EwWKOh-u;z_?<`0*|{mc50J0QB{=^E6i>6)m%JzdP`oAC?Ye?KYWj*nf{v>F{+=- z3L-OIpLv>&l{Ue(HM3?Qva z4BYx&!H6FYuviEl8`fVYs2tRFOyw7jyw$L z3RQIIUJ~&+$#2^=>+;X!?w{x%;~(1R2TeQU7I=mWrjQsr@{LoNPR`5AV*u^Yv^qIU z;FB~W)&mm+v(8f8V1+BuGy6iHz;Pr&QAWmu%T~y;=g7-wrAENYiUBXaAwe{B9F05| zusVJ%lvsCYJ+!A^6j!Godp8dxBOPOu*Rb8mDQ00k_|tV;uQih^Ri#Qy*ys4rRUj)B zMloRR(-((oOCMq1-9lA2i11r;(2<|j3XYdWk_w(H%o z;s@E5KxgOne`x^>8bxL`*lpRA=iT*543*MhfRsC0wY{gi6|$UXjwQ(5Tx_A}jKr*( z;ZVjZfv@U_H7SBFe-`O+*bAQHbL4Twn8tfg78)(?3{U#!)R-{aVI&Pk)MCd#Ld|T7 z^Pkd61Thx=edvZs;W23I#&JrtqeR>LDV;eP`RLU5H@i;q9T+Sx zHqs17vjb*lFmlL6TTIAjB!yxVNSlV@MqTE$bg7;Cx$k5_2Q+RL}P zuG}uM`oxbN-1x`W@xM4>amg#rcp%Q^V8U%aP{In}mmVgv+g~LesV-Ja(c%@Mm#vfD zZXx{O&L{OJCfz*_DLXs8*~A3J+dyD%j+Ta~8;5a%HZOfw5j9t<{|GEmBfUnip8&K|dl%yir?x zKqJy_R3;`&mW)|+B%92&U^Q&mBru2Ax$a4fdn@pGlW0elP+Vg5vayn=-fiCgM>H+JDf$TnWe5PNg}A|8iMXslOJV7f>MYZdE!K$Y%}uv=5Byw%U3Bq^WQ4GaJXU&DvK)tMi*F1?<$$a#9CC6fvy#q)cJ2R@lE5|7t3l(b2y2n(H zfR?M92FjrlkkEhGSbBwtRs)BNRjIb{3FK_)Ospoiko0e3Dy)4^zOQZ|oI&}uK$(GW zBmUW{aAr_YvK=~zsOpuw!;;Iif&CG#RgbpEMx^TMlYaSaNw!;)49ko-V~Td2iQn+&dD>64o{S_5izn$A;W^`+1Y8&=9xrn!L{_pO&@=e}=8g zS58buo!dyaqYSCsck26AT;Ew3CBQnX^o0yRZkXfT7S>3 zRm=N3sn`J5(^;Sw5EuJhyLqPT&EcADDSdiuGli`g@P4Y&E%z^QZ%|}R=iQ5hX)27x zkyjV;`pvh;m4OjLHJo30@RjDcDAu0QHXOX7Oj!|W-g8}N&8LG5oZO2RbVzELD-MG8 z14@6u{>wSv%DBf$Q1PW!E%Wa$Mwnr(rdb;C=Emmue!O@d@}z-|G{$!$&40R1c}`O9 zQBt0)-A68K#>-w1Mf8K8Si6)e!i3d^T4Yf!`=R1>wTz1JW}gSGCQ3^%Qf~{mfX-A% zwLg_V^j+KxPq-zMpfPFPqwZrPU6tNHpVy8xu6fYfkNbrw_h5U*9P^zj^VN3M{exju zv#0a3NmSiVK9?tH6WM8jzqh{e>GP5`jW8K?&hEnvZelKp*6XfLD~7wxCVehq%@+Mc z;N3V3&F)(<+=B}@2QC(>ME-@Oo+PH?%_CpxHGv;HPCD7-5+6ckavw061r4P`xf4cD zbCE|>FPpl^^mq>HrkbYr0FklwsOQ*0=qRPkcbX8nv*l-ovc72=Bq(n>3kq zORIu0d+R4m<#t62RT>aVL`$ni$x&RWnmvBjF9|WauyIf(`@iYx&|#vTbg76JUn+;X zo-J8r^hn~zjPL;Ql5JzJcs8LSAqH^{#!SHT@x<%%A4mH&c zZ!^@@q1)!sEgC1%HRLBQ{*!1xPuunX396OZK&oO7C`slhmAHaGqI9jy1iki=T?)pH z!==@wmDKO2h=uHLcGJ4wYf22GQ3p3T;fuzX2u29vP1)H)lXsVM-$EYh44vYhN@at`undhg!pDi5V^pCzQ z#-V6E;VYbboGvS+h~luexk_Z{K>5{$)6@yQ?=+%daK`pWNrRRCJBZiz!|PC#$2!pP#^$tD zuTF8>#?V7O2{O}bVB11SgkmNoGqJ+pY}&+KK}%-@5$uS=7()qng{VH)ykN>6b}&M2 zDJrE|m-0kODlcGRrisw3$_)MaNEp>TYV)?K279F;m2|C{{w)tT{uJ4YF(w3W&&vc0 zMAq<6APH4`=~8lF0taQ$B>X|jN)zV>&ivNS8TinZI;>WY6JEo?N&xrdy`T2IS%xz^ zuk0!cLd9!F)QZPIHpA2y=P$$hgEL6paIH#!nE*RdwI%rpADhhWvLkBbM>?ccgPvgH zow8O$+6Np#r6Lw&Q0ZRh-fAnoIaA3(h4%SlBr^94RBp3Ze_mS@URmC*NoUsg3t5sh zw7bB!uI4*4nBV#=35)3xEg7vFy8+o=@??!ANmjKprcFM;f9)W zn<70o$+~&+uITVg5^V<-O__jaD%C+z2BfhQPa6!n%8@+p-u&ZYy1|LP z*yMwTwvf<4(+hwp;rHknCEC|X75=VAu9nYKFe%0X!aE#3_>GZULTFT9v;ZdYisgBx zx8n(RMUhf_Xj$t>z85{!B;>pJaaFP{eM6<=)UWyR58qfv5X=xE)Jp9RLYn3d=Hzky z1v^#|uohW&x@xq$kr&x^Ppd$O&$xa>-U!xXvmK3_ga}dXVFDaXs-SW>Xl1VQ0p8JZvE;cLT!k-Wa#fWh5oX39Dj9y zdugXE^M@VOmJ^QDzYqEDnLSno(2|$_Bfr)BN!D~yOEf74fo%Ko6uUe=Kgb&~e-Wbv zMKb>QyvNMBG(VZiDq`Ai7yCf}vLJn)in-tjB$Fm$%&a*USgOX&zmsij=J4;RFpI8@ zVy)>GVJOqnYDZ;UElXn(P-s~w6AR6 zXqoZpYw9#xCyNZgBP14C3h?}UkBwNWz%W0;XomWRHANrO;z&LbrcbVi{Zl59KsQ#D zA7gKdi;uMf3bye64oHy6U&t!PvYIE0axgC=UyZ&mGm~DvlUZ2rJOgZ8^QLJHvTDF@VZEn&zFAEgKU06+Y8T)})!~F}RXOADdRYzr@iyaTK z-mj)(E^{gO%M6~H!w0xs3q!#|=0TI!6Ul%T_Xeq>7S89009j%g3VOvuh!O{y5i zVJ+3>*?g+s;7Z^?-Ni7F@%|gCTX*axugGP!GBU;9WtB!M#2|QQ(+BBr3JC*~H`ayA zjQaY8BN|^wDIT#SQ$!kgtEqw2*mQ@bTK|;c;dE}je@JMzgffv58`tV0VKpx^n7GDr zkn?X(Aqh2|Q&m7NDQAQcO%yT+y%dvl07*4Sr)y{5ZzQd0T zVlJDV{wi5KMe_{d+*Y!zm`W>-wf>8P^A8u?UpIfJzMSUh6Z7k>p~quxa_>4vXa?4wYJ#TT98az4$7=nd(c*tq&!RFnPdgWS z7%MU8I1;T*ZF-xEw-z@u#(h;^6h@YE_e*#Lq(<08l&EYtC06=7fpr`7k0(w3YYlZu zI2m(ha#iwXM3Tn5T!1gCzrJ%j812?8yT}6i{#s5~$=6%7X*9yD=PYftx_SS3r6HL1 zL25L>%bVJ9QKsIO6Bzt&$E0U#RTeT&VFY$7_Gv$?sDDCqzIL75=JG1=BJjm5I8(!1d; zbxZBH_yAZHeDp!MEeJ8M;*3n`9e*?3l?4TB_;?CD=f+E5?X3R!k2GChW%-QWKLB?p z^$FfbaJw$|QyQ|ZIV;lrtHPGM4yXA4xrDO%ddtje^D{n<`OZ7?2cUqaD1v$kMYyRt z`8z>k&4)4ghd9>gtjAE+;o!@>l7DzHKNUo02A!7p-b$x$KNZ(i8phL-apD>6IaXCa6kH5mDIlyqjAV6T!G3|#${f0NF?(coC(2|_ z@uf;a1Zu(RkA|+-7DeC046OaO1^Fng=?Ydr5XMh4i6onDP4c zX?WpbjD7IGTAI1Xwoffh!((t-SpL>z1H{a@TJskoykzmThumcPjkxa;9S4m~W?FPx zGs`o^4&TThBJ)x`m_)s=c!?IERBR~0rda(H0 zpL`1ch~h22QgLJ@BaGj_gP?q4FeL(nzKU%MY)?W|gddx1@;j>G&(cP?fesb9k9Zl91&y z?ZB9OdA*A-AhcjGgV_)9J4*Wcbw`i~{1_}y#x>$9if*1B} z8-?g@G`EeSV`9V>S7m7AJ+1xp;GwlOyyIlVS#n~fPj8Mva59q#;2kLd88nAL85PN?sh_MuYlg91FudtTa-4z(#vm)`<$JYPlvCvyW8)> zhW|4Q3ST5UDHDkB^${~R^O}n3LEeVhVq*tB!1_&Y-N*SzP-HOR>K z>=>yBbH}TBbTHybQ}^8~^LlDcPYg-^zw&Ah3lTTueSiKcTu4FBHU2Qj<4Qe=Z z7g+U?9(q%)ulSnUtT*0%H#Ke}+L=h|XI(OydchxY|M)W*SUr@D2Hv_{Qj^NnU>(B~ z*M*;T1{(?KI(-^2g<5fozzQW(3i*c*&YOfD*{Xu8m531zn7D;8#>&>3%vQUJ%px=j z;>^K05T(AqGu8)2L9EajP1@y#KY$UfwB7)dShhCJ=0okJun}n45Wp9ID>PbNZlUzp znk{OBhjP(P=D$@p=L{@akP3e|WqulvU_!$|3j(JjN$QQzd&Me)6mdCT) z>=gkcmO@8=6J$FnygcFq8)z_*cgu3q%{Ii8D==la2ZgJ=7E5p;y?nBc;F8$9b`6l! zK$Zk1E7C+DEpd-GelQEB-g`~+>|S7=*F$E898kH&b+_P=ygI1mItBaOk;C1V!4RyF zoi@TcwqttXF;{Mh$)Vwal^z49^&9!NG9d2(wASxgKHsg#MxVujDm1^7>jC+2CY8k% z!xIf#GZl=G_1>q72HT??0ne1kj&5e7OM08zDquIwUF}mackE=?QlqaMg8Jd8xis4v z2@{6=0Bx`sG>dfPYBWu^#nBz2JjKJ^i2QXwwQX2P2!G<6GQ6mX6mvYFa za1htLaY<-MkuC{3h2$kdc0~bu(5M*+z%)qXjYHAun|#YDO`iF7ZEhphDoBA&HQ4x{*#OItxd-=(Wq831GG zuEa}bQ zY3)0W3O>UZ22Sz90=g%k{>nsiY+}drJU$rJR1gV=d6F%Q7nW{BUrnDJLR`x~M=<=~ z*`c|iwrHi-vuG^n)T>h~B`HDLnnjrx4tTwOAPo4FvmjSpIjPrzA2Q4^T0VKjvuNPFXN&^Qcp-?e@c7Y6IG)8}6MIa5=NWBO3UQxqr!x~L5Kok}C+yp~OxBF6+#m3*|E4B3# z+1iGQDgS)Eu8ITV#}80}o<0nFOU$%#F|C?XJ{wRY2+P%g7AC5ZHE_Ml-SiQ3>o+Zf z@vq46xA)Rno4ErCZ1r=E%ZkGTBfIya0i;k}Wp(|xo|uw~Bdd1G?`mJn|4#M#F6#yi ztMb9D5X^8UNfx~pL1izf19u%a-3a2u++oC9rLe^4Kf*KBOepEOmjMX5wGCRCwsx zCe#V2J3K!O+SAJca>BDey}m|3X~h;OqXd6odmj-DTqO!=a-4{7`;XbDLsGqB2Pc)V zmzV!d*fo4VOQKk2R@ZgSin@ALU$b$z>#Vqe!F5Xw6nkCIp|RY*b9ZLmh3W6Gi6~6q zERv=0w)D~(xJ;Jdl+^8&B?6by-|F%o@KOmz8$D8h>DobY6y&@hsIm}YA9?+gaTjkd zhsGVFzevlUy~a)k3@dbQR=eLiE}q_xs*M;fOn^}cEwX<}E0E445rIa&Rs>&G z%o@ScP`Nl7R`v{NUZMquY^4(4s-49m766;Oq5+pss#7suykC5G2;|H!nCzQkr2{j>8W|TxLs5zlr04eXl zr~NxGJR%m-H@8Ita1gS%w*e4}lpe7}8}*79?DlX2A#>oX%+SY`du00J&>^$d^mhL9!*&Y47B>e2XZdp2#1W)CY@0(EIf_bQ;KD4N^FJ(*Sa8R-2QMjB!r! z9nD8sB1oxSuTy}NGfLlr_eKhXu<)0!lsv!i;iJg}fTBXjh|s?NWTEykInbfdUu41m zq;?m`0{t~1WMuM4goT>Dg=2m-9a$W_=uzjbY4d#*Nq=y0_6DpiEv?xZ?T@BcpGxoY z&jY9QxyLQOi>Llt^tcge=w&L~M^9%hH$Hm3I532U*ocY-k3#-4ui*X^(KQukh)}|* zXMuS7k&dF?4n{0#WLdX?IwiEV6XI(Sgj-&2469sPGWnHOyNW0M%XZffNSXN|340dh zUlM(^RMWR7A|S#v6Je211mmq-{UFGHR7>-<=U@EQ0C_vPoj+oBZ_kxcMOS*3w7?hi zwstWW-M_cC;ca&@L_rZd-w*_3`bIUw?3)MZ4QP*G^LF5bnnKKI$`;n?nnM4vM7>2P zXR!g>&fT&u%vv$#?b`}P=o_`O7>Xw3IHL-@l@U+LB5_xoG^*U}R0t09^%Dd4F!VLj z>#NORB?k8h!G$E2#0oFDb3RU54>cf$bBq{g0}>Encb9quekZO}{yG1gTk#Z`;{~yJ zouR$W)QAM@H2yXJ_J?_>k0w1b{Awx6n$W&01-O+`C(RoYLFrorMbV?PZ_XiOm-hlV z`*=!zXwt*i^+Wu|d12aX0l@Wk6%sLv1F9t;fE&-c<%+jI!FMdH4RKYS;E zMwq-JRlOPew5In9R}nO9P3rKOL^O#!T%+4WF#xx_Ul(M02p)0b3(E@hLJE5{OOxy7 z(Uzd5n}|+D_u!)6XxbaW(K&Nbn)#zWMxrl771(L|+STQ4=iJdbaTP)3$HHsn8M|Vu z4AFr7E@lJ~W#m)m3>Y@vTrd`?a_yJG;$*h}i?_FmimPk7MuFh&?(XhR2=4CCxQ7OU z1#i4@cM0z9-e{0OfCP69!QJ8Tyw4}+ALESw@?7=ku`kxzRkdrcS#wrx;|nKBTz0$t z2IftR6$8=wJ_yDNs&03p3Vk>}q)IA@`-3vVwOA2t2@D-dt>m?=R6cM@v=O`0C|l{_$33v_1Dw`ZdE%BNzppU# zlfjxWp&u3*-k{~}#D4(hzJ!gcN>wQ)VZSEn?MuBJ!Ye(|GQqW4eQ)dDG$KhB=))Yo zRhNl90)3uV>VBckJ&{uY#VZ44R)w7zj;uuotDy z^{9>SjWIVFhc)pZ-ZzW<>+(>jVTRuy7%ZHykqcU83Mj+a?g!!_$&wuCB9M3ea)fCC>c#>2Bt@T(F$63 zE4Ab6$py@L@f|(y&Mz|$h5XRRlqs;2MR4;)ti06EP8C|kRjMuJp>iy0Umo!^*u)R% z7mgzLaSwBNAmJ&{ zGJpMWEWx?kfu(eQ-YxkAsI4qfk`a)v70S{~R$(W?ZMiXBIti_!%2-rYuKuv0rj&mD6#5j;qS_0_LcyicB)Hb;ws|>_{U62cRRW}Xrm5{RtbtrP0w^M(DLUhAy3tPW__=-F1?5%Uud7zl+su^NU+zn`uV5? zcMg7|JG*r28NbKlkiF2vD_<}8@PVFvt1NnkKVLcR?@-Wu7-nKuhS-?^Nn9Gf=cJ*$ zRYY%dqd9l5YvK|Ieampwli_5U{N`rH0i%f`bsYM-^>Z*)a>#ioDY%y@-neOg z&1#t2sbBKvueKi9AysI!bUm~I)AI1o6#C?&-IGB}9E!+k1jpcz#T$^tyyq`Mm%%NO zB|fi}qu(aLHoce?D#Z395ncVu84bbvu!1F?Bn#6dWHi{h0L6VCdz?-hPN#Bifh{?=3|&RkfIVN(vNfHl46W2Oa=0HH!+sQQuQ&_qSZzc9I2UL{ zhnB9Jc0D*L+ypi{Keq60k*iZRC=YrwWvz zvpzx`ao*~6k3t7B_$f-JetBN^T%oUwbW2M4 zQhIXaqmzzu+{p6SY7ykIe4ftb5y^a;qBOPl46Rrpz}}|8f)hF4Yp^w#ufiG(WF9zT z;peV44B)A1VU@kBi`TrG_}u*1N<`B42b5n1>F^P=yL$C7^lOalshQABFd{V-35J#q zuV>&+5VNdIv{^9SEz{^b745O%9!;OLkbdJpWKU`S=KOrY$J2%|>nn#xDzN;OZ~fXh zAm%n5f2L(iKk0e(#Jlnb!X&!rR3`>QBi$A}Nd(%i)9d~<*;)>X1c${fSk3#U6+uMc zW_SY~SUud{)5inUadGIq;n5ilm`*1{p@!P}qX-S%fKc|c_l5M>chdaFGdyfN18^_B zj_CK9*ds-2(d9h!y){ZU-H*Vqj6o1O1Qb2ZWaF$SYDQZ7Mo&1WhS`l~PZPyiv|}#%!odzE(m=)b-0VC;IGn1{ZxiWF&!+e1k2+& z7#0Tl7AVyv1?CSNcoqV=u0f7$Wkw5wiY!)5hx>IvSuRMGaeViUH1n^p$W{YGm$xSo zXmEuM3Z#=q%tRMBzy4I|&&zJ%)9dr-Tt2e7bFb{;yx$Pyx3GE@CnVzyNjzRxImZ^$ z7-^dW2|orG)t*YQ@h3o28q-H>>{UZ59!~v&ZaCtE>Pr@YV(hOIO@@!m#jR5ao=1=b zTs{WQwIj1&GiObOo@`_X)nX?iy;zBN4>>N>)Ele!o3oUa%8)P=GXStQX`jM{=fdDNUfGL}GXPLhE*}`NIUj_ogjSw3v_r2e89A zw)70{Ey5EBz@Idw^1k6eUM-${UkeOVZAU&FgO?JqR==iGV8rhEJb1#Z=f`HYk;j>AgEJf<}Za5K4Tjq||m%h5e1 zraNrdhU7oEj?aFmTm)wuNk6nW$QcqO2Ni!hQvKznv$~8we!D_sw34Ly8Mks3G!o$X z>1<>0O!aiPC7}6xe%qy1ir6hu*<$Mp$fIQO&^`=RNGR+ z7Al{JSAnvWUQW!FlYVb{d4KD*vtHasRqQS8NJX-dD|3XpCr@~EwYvf{8n62U5*rS| zOebsMEV2AIiuCNek{-0VAzx?LtNx}SCFVWVO^se82qc#2h+Vy{cL(@WJ57aH{w{$W zHT!|iMdCPSdg)ns8AJO9gAfqxm_!x*vFaAw86ZjR)CX(Eu6cb@>Fr#+-6T$V zhNyccpC#CV3xz>&wQO^v^@v$qzu0@k;xuXf zN}<`b$q@wDclGutExh7MkOMg?$n+V2=N~q!ykPr=V9=SY-`Z+08K(fQ`&f43rd-A1?aLumbr$EwGSS`V50a3!v@aAiCeO=E>-H!T0hARQ%d0;= z-=_6*={H!%7FJHs_@)x~x6=|{#%-QS4(Bj|6~iFwNX(wvlVpejeORcEeZ^#B*Sjv) zddTrbi!nF}<_~kC8k#ZjZLkp`sA(#iUobRKv+d7sn=swg>kmJUAFXz8re1&(#y4px z)u`?_2t!`2&4;ac92gTy1BI?>t_`aRZ^4C6fML+qCLt1zuhc^(*wr7;#8l6ZPkIZj z+ANjzTgwOBbEr0_W9%CMa)xVa>^FvrCpRt88k$reWVqY(-En!AmoevsykoeeLY*+I6>>iC9m%?{YVpcAgoRLdO zU&G2MUh{w+Z_w-;O?sHSF1Q~ZIqn@#wsAj5K5x|-c$Q#M{Sd9eiTZ?%CNKCVMuHwe z=UXcJi?Ah%FNC>x?WNNz`(yLz29jBqV4NRU#98$nS8a{?zJr?Sp;1Hx8AFPR^|BZ1 zpx8swaJgZLAom6K0f&v~lt-bt%fJOZ4ol33r@)_ONsj8kvbdVj;FHN|uiO}h0YSNW!LQT&$fXX5Hs zJHVt_FNljuF#JYbqCF`iHT>of;wn?`ZM3g~wU(!gnpM8oxU#wH6XK|cruyP=KI{uF zqxd;vnk;Vn5w44dvOcWPsS-2X+K~Aj;s?usERn1_p6&BU$I+L)XqTRGDs`bV5f3=% zMKmO{GvRmsmQ?nm!zg|nI0JI#hGl$=Eiip8ek1Ug)fhmxcrI{OpS=)Go#YZYhFP7I zvON931Q;ptsD5lh%Kb|>eRiz)l5V7BEPJst9&0>yu2f& zJ8c84!Xk3)e75U@j_{XnNmtITJufh+f4yvnCi#v#Fypp%6_7aYu2Yp`_ql*437dx0 z`twNRDJdz+uMG0_^DwfZo2xCT+V~vzCxqp&8MBN!CUkUY^qC?s1XGc`$l+gfV7*_S z*!-Tg!5fi4cmV|U2F&E-=c|(f?Xi@IVv=^n$XK8IpEp^olv2Q5FZEkYeP-tduZm`z z&Cn(w?doLUt)^t)UFl1q5%BcdXUJH1wE*ub@ z2Qb zVPQA3S|@@TmepyGQLInGPOn)~xn8Ck6fOS}+nn-WCU-=TqzQal`;iek_UTI?zE&FhT{k`mMYI2Ly^Q_6D58pTa zHH!TT1H1E)w@RQ40b~Ggqw!=>p0w|Q{0W|i(b5GWmKaBHi_^F5bk`Fn zq$Yx8c2_IjibEtV-$re(Y{kcp(~|tmi!ntTKafbzcO`##s!oiGuaxu4f@T`Uk-}Yw z(&FJluvfn7i(<}s#X-Fe#fi%=O)lP8C^q!Kp&!sttOg5sx(?2BZR*|0XVFzOMhi{_>rwzp?*cV_V} z74AjwjTM8YX$bQ|N!pR`MUV@flxqvAe<<`+b)DpRWI2JL1gczYQ)-|VqUMX6KW^wm-&}*%n{iK(Fvq#0pt5r(SRcy2} zt#jw?ROw~&Lx=`453+wj*6u@2jOH8crb|jlh;v};v0LlFIvuf3<9N;rQ$p9^D|S}2R(u&e6S)Jj z&sGmMY|ioec(9rUwq@ukDX{wXnJ@Igkv5FI94m)4TB{S{aC(Qn-eo&t006ypaU zb~prm7*6I6QKnWh+VdqoM8S;f1yJ&ks^DvW!(L<&^b)S= zu-m3MmlIul`sm};82fDBh_S$qXn~i4s9wB|tMVMbLSd^39c^v)M^<~VG)1Xw;Y<0i z6xrcpdBLXe)IMv`5bfS&m5Nl3#0`Rg@3SHv_RldMXEVK|u_X9%hMt^TMfr@si>Zc_ z+6>#b_EItIS2uqht}xMSAO#*DY}QcGU)=h_+QUmPSQ`ni20r(#1c)7HUOZSn?k zh%Y5`Z=?e+80tgG24?UUMBhqPkVH*M`};?x)%mv?J5WC^v^Rl z&#;mEto+sUL@9BH^rb0fobY&^=ofPl**ck#VMNl(erVk+IOu!pYjpZe@tS*U3hoUr z=L1gEVEu`aZ6pA-smIE8>BZe_GQ>zz*0#RNNIyV$54e6f%!~uB4m69XwP5xW z$r0qVIz^pYz|$L&=kUi8)O+dmL7ABnvG0tKtQsZ)fnO?+tb9p)tuOW|PXS)(`{TGB z^J%YF#YWe_djuAT-4GrUI5{mDYSG^H7=T_&6Zb*rlFX|cVuy;ZlSX~UfNB3;GU)p* z9M}0#!`tnE?Fe4|y&da9Ta%L|HJ{@HHkq@f-lt(4yd$-m<-G4hO4Uz~2%q(-Bjcim zu<=#Dz(`Whq;axpTrin-1M8IL4sy9(dsQuR>9zZ8y>=z{=+PLd2RZ^)B4p8ewD^QM zIIjOF+K<}xzSRrt2$1f-55&t^Y0CIkH@%wyO*?``WJATxu49FnE*#p-5)~6$2B^X$ z?pPs2jv)!{y~9VjH5tHm!K4VtG)s@!Yx3Wun2mj8_cDuzQ__cRh)Te;rkcc-I$m25 z(k*zKb#}_0iz++i7pDpbDiLmR*?1)r;wb26z+JTv56KuJqQrCQ!=ugD7%d@5- zTA*I}%NeqM8X=Yxow@s~H6#~i9u?WMkSUbLre^;HJN0^rvS3Lg*s=evXq=2_YdhR> zy?tA^`Bgb+9IMQZF=aWhoh+#HS61G`8K+?EBPpOCRmRyX;~@+1`WZ1kr2Yz& z*+YwxYVn-Sq=FN|%$S3{)o&UZ7k*=gqACQ@@>Ku7(mP*c1nc$dUwbKMEgmI{P0OQ^ z5TZS-C8+2RNonT0#nCCT1_mja*SpO!;I{DqlI_C|omWspGFbu6HXBfBoRb04QYmn( zGcaL3YSD1pzx-fhn%FZ8s}0N5Q)9HQfjDjo{uwq*vCX1K8{4jv7p73dLIzr zyUiZ~DJ-iS26>t%^H%GQeG%|09$>;36t%Lc%DO7VkTI)N&jkPVhdS^5UFbKVIBYRg z)f|38y(5J-+8sjId2z_{jEqszBlKZW2Dg;PeRaV!01{kfvjGG~6-+CiJ5^`Q^Dwo` zc3v*%oM(4+>||nEpJ3E1SjoP+;RwA4eQdl};L{8~VjKKMWIT*gXoWI?6a0z)=0361 z1`!A+eQTTvvKo*Cmp%!Xk%3sRe)>(`FI`45 z;)OBwD}`wS-V4TOM7m4)1*a_X<~a(gWS&ZFoe*s#e-eW|)+~1BI5uSQ#|Op} zqwsYSnvQ1~1eh12^TP_*n4@SUB-Fy2)hpVO&);0sDbeW3=}l!CPj9&If4?Sl&4+kG z*PYLlr{S)NgetB}H5>ksydx^I+dq{*F*iGRt%FjXI+iH{_j>!Jmt7R_Mb1++1?&Ns zZFWSFvsR*J;{LO!wdFErxAUsgFe@6Vq`idQcC~e@s0>= zbBb}^&?I!{X0w-4LyX|Q$H6}7p~)^lQ}t7&!bLL{5VlMK0w{)~ z;^}@XDJbfu`uV}E8@X^6cHVpN$~BbXhG3BLH6Zl5q5iXv3TYCD-F zup;pkr}oJv-AY3)B|@gVvL13CuWmS{$jCL%KIuZz3{*chxbIurB z8Q*md)wKcwyC0kxYIRZVk>yH}Ov{-oHpo=9HM-xZF%c{sl|WySsLyy>YyUD`xKIn` zLH%>TFq597FM>-Mj$}q%Y!QpOAX~)}(v?%wd=tzzmyPC*5ABW%pB;WzLQ5{xt{JqS zS5-Ud;eTsyEvMnbpSN0>4_3(R;v-f`JKy+YOP;fO9dIhH6z3PG4{>}2-IU;UwK0=R z;U`AyOIhuF_f{CR|LK?viCFT}%r3GvgMa{I*I!d z$@R@4&{pL?NF2On0rvy~dbN^-t;H~-4h%Z(p;AAVnp;|`6wO$1k&|Pjk%*VMJ$de< zQa3(5js3dPhozDNvCXdyFDIk!!y|_GG2EY`?xJXSUj|#8qhR{$pP$M@!b1SKAbb~M zcv)y&m*9+{KAY2`hiiBCj5 z_zs&^-hRyF!uP>~fR8|bx?Hv32&V*zqEu=~BaKVd+ zNPp8````zQlc_XF1iQL&|2IAm^dPKb z;C63UktZEqw64^&9^9}jNsJ?G+|-gKcG`~B)`s`5#-y=cy0&q}+T>)^{}=58<3z~b zVJy$}=YwFI#`%&SC>>9kjWWYeX2!XA;4&JpuPHSxfA1Qrh-D(SA6XzR0!h?7+!g%s zW0Byt?AM0b%+`|7u74$e-SpRZ_$Bk7zwCIk-muZ%OWE5*NYV#L=r4#Uf$F?tF8Bgp z@U%(LaeN^Kd|)Z-$(@t@@PlQ<`8sSreZ4i55jV#Wz&SSKstH#WK|7S7bo3osEm>N( zm;(0=T!@Cwv3v%Oxe@!Tvc(7vc(p^OvIQMfP{|F|a# zI|W|f**uB`^{T)wxJdbtBbFC>J9cchbYdg~(r06;t8Ec5>R*cIEU^LC0GyST2J;QV zInI=e+#e}N2>oV;SIyOHHqR;mpiNwqhf6kOVK-Km_JAWex56Q%{}a@(f>% zpMWI5&o?IiTfU=?7Aa2e3MR8Av$k=9b7h9%>txWp@9D;Eh89Tb1$KCZc+w%i*P_mc zS5(np%xR<0n(l5>!xYOHe#(z|(a-SQS16?ArDlVckUAgFuR)o!FxTSBDXa`im}&Jb z1$BjH(NAHft+=HTHiJvOo`sm+uhz{;;<Kx(x@2pd)AM~R1i5_l~9?A39 z$<0}vkg7n!XTr)qMgn)r`^V3CC(Lv&8{&w}9a0wEg+5iZSL|D*<@m5sfdgSy^d|pX zgk{zmr1!k$tencrBToKiNWnqg@q;38eox zKqN>E{Z9!|)?uW~ka_*H{fgYqyA`@#LD^F07E1_$rauPF4?e6j!NMEoNZ|*Udlq;xUM?M9-=ALR*fz*jY+=4mi zq-@?`P?f`k267O#()#YDKB#R0d_l~l@1I2Kt>C^wVWO-vayH z(05bImqW!Zz|zPfIgRGdi|Uf=>T=Jt*%^!t3ob4u;_g$7{({r(P<%zAVVxHrHK6*5 zoFQ8@W9KFevw8`wh)I;&sxKo|46}t?3lp0C&;|}KpHy}u#S7`vWxY3^p_Dkjm#p8N zE&7V6l1A14<97~?jLZ_FS~GnH9FV`>r_Dqb!a`Aj z{S+5~GnBnG1u8RJ=kI!}29RzaP;v#s>MdCIU66?MsG_Is0ZMg2;a~Gs#whW*{;!?I z7pCHxdSZH_eo ziWw@wq!5(PnPuMYoB~%T*6M>QrxTYQ8LRCUMRj>1#*`B-X{?HYr(e&eHnsLiHKVPX z;)5Yaq_WOJJP&M9n%hPsQk*s3T)0$Tl}&9I$yY}j+k~ZFnF%mG8EGZ6X}~h-NW&{g zxBox(3XOaRtiNGdsYb3R6ri^M8&x4TNmfJ4vg)&9BD{lExWek0aZy9YQcqB}8Oq}n zzx&(JYUoW7EzWI!(;zCmoyomi`ee(AdhBD(NSaU>RxJD;nH0G$;m2u90rr zZbc6@IJOO)U!GxSBZ$4vWUPtH49Bk66lmtUL{yMx_J%0HP%zzO3KljMH)`Sbr29K? zUhW*ma}EX`#g+Zv)RPLq`lsUy8_{t72gvMU(#C?%f<~NQ(7uqBAU1y3{?WSFS>_Tc zl@A7bqylz{+bx3y#X165|2H24hB6y*ETNF8*>taVKh2dLo!;Z%K;s{^MYl?}dqnVv zk6$Ax!`4Rx=QBEV^vl&D)dc+$Z2L%<{|NImZGwn;eWn?s%zPki4fT~}Lw!-3-Y~0% z^oYm_eqWK}0$49Fu&Wy+pQWVyB^28B=E+!*ew2|oIeM( zX%(djy;b`T5jLCH&(}nf+{CfpI+N%cz&<2+&OMV?x7{2UDA?8UiayirA3%>Bh@RoW z7x9}lSxG@QpyaPC#|;g&=|gql02k7s&-f{~$uVM31P2N*AK>1_kpn_fRZt4wH6z#P z%J(^Zju0qyIjb9sSF`7VTR~=#7QW?$BOX$12XyNJNmK3x%ksmwaAQfF(n)?Qy0o>p zzgXBVm}rP@(XI_0IBW9`H?X>XJ1s=!Yp(I=a<*4mjZ>*dVLnzCYbOB4ZmI*K-_Xb_ z{yU?!KZnu&+#n5%IRYg}DjaoS`s%Aso6XvW5QPUgIV&tdgBBU3&L|Z^qV@~dD)X@W zmO(GNGHh!9L6!oF(Ql^IHnH!y#p(ko-kcg!=?b%v!_S%d3vT$p_;$5i?7YK5{Z%?k zrQrd*;_vgC$$Qt1AT68edmWF!@vpO=MWjE1_r z@!(M=r4IK@$@e_@&ja}W(@6DihWO7P-YnLSEP#J6{Bu27#_Bsl^*drZUT%4EZIdaQ zd5)NQnS2>zJ7Z`QmGh)->ziAB^-}|{-oH=0^m6oLS`^ofO@%Pv>J^}H$N=R1R0hZ)53N>6-k?V60d)_Rk{|K8xHu`jN+k8da z%Ei_cibiyoJC{5Szy;CCBd)3 zu1q0?r>P{x{3M?e}s`cbQkC;yoXfpQ_x$P+>kS` zl6ff@1qnUhe2pJ8ILm8x50gs$L`}4Q23BsyXFQpejfq=*HEwV_A%N@(z@b$sJuAtB zQ&WDu>%BU7#waxYeWJ#`uHxpC2?#z$4Ip`cZiXE4z}x<#xX+y8!~V)HAb3->y`;S# zrPiV`nO9?Hipu$qcq{4C9}z>YcDm;lm2(FU$kL}HxOelsBu_pqkUI9f5ryoSF(EIz ziO-3;em=o$4p68+r5Mh>LTh#AB-A7u@x(s{!#qh2KWf3RL>Q>}p)T^u&$=}i?2^Fu ze4M{#6u+B zIQ3^S0>~KbR!xA+{6`zH^p@rCI=K0y1%i(uQShU0yn+|8g|6)dW?Exi8)e!9v)@+@ zLjt5YyD@Tsb0YrjM!-e5gW3F?ySBPaN!X1$-sf^|PEs{pfWu4n`Ftv1 z?57&-)iN`42*3MpxsSEpocc;Y+jT{`gB+Ai&^>F0rMdLA0Q1=;2J#@56qOA3 zLd^1V@{hriyVN~@_7-_0z$U1-Ab5ppwM;joL@B49$GcDm1KssqIyea zA+QpUtWOxcjqT}-xjJt%B?Lx|XMtIs%E!1SRo7KVEwC*C4!;k_6X+qmGX#58<#hC^bnX5xECm&$h z8I<%Hdd$^bocAAT;4M3(S{G6ZTl;DDL-yO7xkRY`Aol2|LvxnxwpF`&xbRvA@ z6_5!l2Lpw^TCoFa)4=FrKl-Z|Ygb~XtBg$lqX9@}15x!AF446Bm-bT#HmDw0g2(yK zyLXqHl+pv%*FM*zDyCMLq~5mz@cA-Tg+ZnRVh4AOgk{c!<8t7k%da9srgbJuh>4Fb z*l%=%y6nAJt0!ERN?^nd8}u$d=n#3YHjyp{H{oE?)rYdgcnO!(rl8-41ORIP&7&wf-LdJ|Um?+RjNn!#ao+6=QxUCWA8|JUZJeWUC z6qi`w9pG4>5@%fLi0NC>l*Qpy!kP93w7mCt_8dlmV?WO(uUcUK@f5L&11VrtD#TT- zlPt^ko#|&N(a_l6736EUs6dwodO)*Mnm|Smuy{WPWmgGhg29a%d5DP(LF(-tpxiQx zQ4eRwG!x9vo6MVMjFF8O28Glrdt<-XwA;z$_b-Fh6E>mN#qaJ|JpNXif%^m7}^}3!1b0@nLoSOT3BE;3+*((_;&|~wj?vH2P?|Y7C3z- zGf0%D*bR*+re1r6c8>cm*3VBe#Ia~o&e+O1tc(6T|MaeXGfBF{!Lz5GMKj4^+BRP} z0I{pkTKm( zvd<>&m423e1Kc(Q_Gl*$3yN3SX<=_;AkOC~8QhK9nLBiV{9REREJ3qatY7 zo%Rb~88+^PoLBG#woBU|PJmhbr-SJPAn%jp-_KwEFh<-t zThC;~r98T`B}eppY*RxA?A$%()0!O#kxICS5^)H>JdF|m@E2^8;j{+>?tU<=VXri2 zSpxUl3rnv0^0TRM{UknOi)vyT=w0jyz{{y+302?5w20Nex$6QS&~pTHJAMZkeWD19 zXFyIP``X@F$OdSr{m3vBGz{a49EqSr_{l(I;t#O?Qx@3LxcG1(87cvgM?i)lo8#jj z1I-xOtgiy8zC&uO^&gfCrlTG^Tx(!WX^m*=L#!Pg7~`vdp!W8a7z(i`$51`rmqV6- zdoNH=E+LP`LDGak0V24+kxP4u)g6a_VMea9{^8OEZo?1B4Q{DRwatLQgLq`%%!B15 zDkbk_6V(5cRK+BKLr6z_oP?bo0o#kYt0F%B4;y>&i=zi`LY45CIM+i_PFXP2;0cvR z^}P?W`bN&|icIDWxqeR!GUN_!Xk4O=p(0{^nE3Zn#yZ+h;8#IV3+ zOZif?cgX(q3f~;EZg*4UY|FQT&|P(neiE&Q!SBldd83iSu1DAvI#-P>W~J4Up!(U{ z8^3=^wtdQ2dO$;*q9urjoh`HZi>S#_>R_846*%SmAd_A!v)k>x70NDp8dq?CaBwcf zufu?ym$;vc!uxB`P7$%|KLtxD9XzcFmOQl30k|Kcx^Tu$BGCx90{7W5(pU5ez_I#1aPDep=!0d8d zv|M5hV4qK0(w~OS;f*ezbR6~y;tn*vosw>CQXnmgnFL>++LuWT z^zfe;rETkVIdR>*zsiINX;9yZDn=L?9^r%)Y4z06cr?5yyo{@#ho2~-MN3tVYMnB0w;n$fxtvXh%LXL zslX%inqM+%bXtCw&l<9k*;FiMS2F9cIaDoX8>aT0J-oQ~W!;om&>#BrnflOm+^zaf z_uRQp3r!0h_@GN`p8YBDp1VA-T-@ApdJABASZ@9X3M5&+U$Qhd7;Q9}AAm8SNp;C^ z{A_%sYdI;U^cMV>y&0Fc>+8dM$DasHx%hqgmMrd)%0(&<^~)K(E@!GBF1EsOgaG3X z&C!^5Or9c+GVFq7^G1H^oU0rwn`V~ zPwOFqi2s~;{1Q>}`}M~f=+uKw<}%w*zLoV@maw2#pN7*}KG?v-_sb{mj%r5mdk1e4VAb*SedR424((ye!HAuhI9zJxN%oRl+qzn+_aV{}-nF>t zdeJv8A&?4lw*CGl%>DGpqP*-Es-&mZyCSv6=(1*QvDWM$1XqoU^Q?qgHVPt(4+dg%*6(SEJHpqWa$W;zLBK z#5>g6Jid0|Pk^=uq?9Zdsh@wD&V)%O--jXz|r3gxI-)EtIQ!dYVNN*G}Lcy|KNOIZ{ z#S_0j%EWqyrPXpistW1kA>*NtQ9@OV#h6V99S+2`qP4aOXf?8rJ<%z#J`P=m(GiU7Iv#iT%$_FlA$m#V22_iD@I6OjEfr z!7h3AzEnVbmj%QHK7ERa^)H(5DDqz~{7~Bb!c4=!Y*hT%@OGgjj5d_2v*&L&cL}0r zcUd|&iG=~YfHldn!cTwrKF-uJ881B*>Vf~Dgk0L3 zc)gNwyjIF=W`T~fo(EeZ%p!}SjoZ$8-(Ivkkq>uv^I=pLj5UatO2<;Uyq`ieHqvzGx-c%AM>EjQxveu^U+cZGyx=*{BjBtBGnK8~^ z-zChRGriX@-xWM3Pk&>fp3x@YvW1&eY&T~=89mTWhi-~gA34CDqa)dFx*NW%Hl}!IdtK5QMa{=2$e`9p ztto!;9(+_y$mbkes%z@%f5P#|+8b{AwiIW7f#ZyU^JFw+Ctybx28$!e;l$v6N;t)o z^4T(~aX0JT%`l6ZTe?sR`yaVqc(4zLmM&8y^1_{XcjI>~eP)p2mbITOTXD4wLmi{c z-TW==><;;jH6LICZu2&Dg@*|h0r!GgpT6#go6 znBOPS-E6p3z5Qzo)-BGDTsX?$+XX`c+3W;H&45rO8FZQMv&u(@o48P)* z3BdJ&AjoXuoq+zWe#Ur($O+6z1Llu@(9sPyQ~^yAGu6dglZ7$texPn;zv0=`#ieg^}Jf8!5S{TnimJ+Ps1d%aT8my2^I$!tpi>WobmJY06 zM2jk-n;GF=le4sM7H9D4tMjoh3Q1(P#w?u;)J}rLOld#Muc-!8_iDG3fj{PiM9t^# zb|e)Ab+ZcWI5b!l6}f-0*zgF$WRjkM20vagCb+vs)otTS{^^&LXcal{Q%7(~4?m;N zRF@9r`7;jAFMN_3>aUBLdcnOy2o0oB-p2@<16cYq3SFxOJY^PfG}!olg|9uKNM~-h zGE1+JZTi_xHC^5PT18BCESKig{czp`Xr;ANn}&7uM$Eol$)3gk z=8_$>ImEVF;h5h)!)n;!$Y~ZgZn)%D$%I}_Eq7@>_Lw z_kKFJjJZXU z+j@oU%-(f2vxYYeiAt_}gQ_ffT%T0Xnbf+aP!WQ<@_#2RRbuy@3HJ))Mdb!_XO&!T z;rbrV6$fKMr=1*p=(^Vvnc_7mjZ}&$vAU|4w6-0pWj$IXg{>g2$?r=v*_#MP*2q88PY+ zUuo`aiDQ8i{XIRX1IRH?4={eo1QQq4{Xo%A=}H+lR(qo|cIz zCp6Y}PK^8m!e9tG7(y!1VFBzk%ybd4R2(<|NM$=3LxoR^@^@pZ@~zabUwlj&PJzqg z9em+<@X4?2v(l~>tpk)A4IBh$azk&2r92Zd&O>i7{q0P8?X)k&W^C+?kIHI}D^9?z z8t{z+0;NBC@2lFyEVav=*THMkE3lJNGY)R%&0EhCPrO+AF;Q>#Iuc}7M&ox@HpC;RC~dGPl92N2;%F^p>P zNar-IGhgE_J^ig#S!+*B0}Eq&>tmYf$Nmk2u_(2i%GEkS_^`g+J?o?P z!8=%Yv9~PVt_1f39k@nhgqZgh)MzPlt0}JpOV!vvI~h>RoGdn%iFq)-$5LdO;?>dg zJ}AF-ux48{?`wrE!M1W17K&GY$Ab z$B&8zvUrY@t%08yJt!Mu?w`iJfX?8PBOX6oh!fA*VZvEf+KCS!{{R!6BkmdhzFW;U z{=&9-V7QCGr1Bf^x8H{TB7#cUN=~hfKPaYlFZQfU)B4VcsO_12GK;rNr2}Ti_d;Rl za^C8F9XT!@D~h6{;!|OU0d7u5UH_G-3PfyfGeE?qk*dK=l^_-HHH88@waAqs7cjK) zCfY}4!XzUXHww+>RbW9$$32qe=2*ssRy7oGBa080BHXjB{(FoGF^gQ4tn6OGKo%q_h2*s1 zYBDMH8uWo%DDQ_uHFmqSrLc(VD0G({aBsC3dFb6jibEX9zOZ*dngh;2YkBNexs!vT zlyFxa`~-`7mvH(PgsVKxux`ag7a9fJ;(jTZ;P-s0{+Myhroz)tY{>%D0i>vWT^hZaaT&m zDSu>Z+^p0ZPqo* zB|}(3%%=tb#1`4TU^QY|3mclb>eMq1&bJB7;i>#PUDfi4 zU$zuq1l=q#2W7&s%|k{{<>Pr2P8!-Yo>0<>;+EPIzjBN1RhMS#Up%N2h^@#rShd*p!ufPkps zi+vuo&Y_&WuQ$^JJt_LTY$ZC<2n1MwJ2B%*t}?)pn1=A&vg&%Qp-=U}0y4p|)88iN zU1|_4%cg2teazlxTH%A!)a6ec_wK_E9vS{28vuG=2Z@U)Ll?*ii0;tA_4Y)*=;pz2 zo84wG0D0qeJ7x#}8`1#?Tg9GD_vTW*+*fynI^B7nLf>qhZNf{J1)FREJlEhHtf%?ssD! z9F2Lx=hL0;?R|A)-6rlSZCu z5Xux9&O$ zs*g>N@9yl80u3+fBO+}GYNEzMm?abu$x|ld%|eTYvZbd`{#yt5Ga**VkX+Fgm;|K8 zBS8%vc}EbB1G!{u$l~gJ5BLc|o+MiQdk&d##^dim3-TCzpnD5!VlK&2@*gfkzOTp; z*nreo^Y!+r)T2uJCdJEi*4VDk;MFGE*(p!$w)?;X61i=ie!$KdzVF~@2N0}NRSsfPQVKIsm$f!UPjU|Yo}pRea;L`1uZpIwiLQXSLk>l$wZ04ph32o9LI<-}mEQ0EDOV~#&^tDN0 zLv2Nw%2Do`kl7Lxz{hOO+elAFD;EDSy!q%WSp$+9!mUJ75C-{?|r0` z<@1Oz<8lETeA1pl`^M>MIFB=q+oej3tkytBAW3^*pG|6i3;2j}=yjJ+iNy_MJ z14|c>ne0^|E;b;T=9ho$+ITlRAFx=>zS|KxGoOx>I4Qf!(Xf;A*RnW*u1>(%v$P7JvQYPmtPa|$B%4fpuGiBe;k+;L)R4YI#z|bHuPKr+E6<6L zwysY9vvkZ>P^LS|x2pk4;lDh$Z1bZL_H_+&#=|FvS}QA%Fiq|6r24!KW!bz0#zOUi z0R`}`8FUh|}bLljA_*T83v;Yx`>Rcf-X@_)AMF?Ga9;&T8_$9rHFOQ(lFh zOBG@}`?G_9FwR0-d6rZbL#3P|mpLCN=M+#9`vvJ?&KEz*e zd%5inv$B!u4L5L(j2<~4(qv2@tzESSMthf|m-^j`#`#}S>yUQICLhc5+LRmJaiH@Z6iJ|MSqoI~^ z_nyD3I&aq^KSv!{Rrz-7-H+@lu8R!i>Y zS4{`$0(BNphBS&iw~jlpioWTJ<)_2Z(`D7G5qFgB_OZytK0=!6cpY|TreRlD@)K;g zon@Um4=oZEKT>BL9!Vea#SD-^?}vSO!32d&Hq5SXoB$GP7y+yr7NHG<=boZOBS zO$SLSYYA4KO1IFjXwpxmg9AJd>jW4PcaeM}#9%THS;U(b&O z#-5Zm3~&e6LeaP3U-%`?E>KLBLbGL`3g=sloEo-HW*aV~!Qrexe!SB>Y~@onJ#yGp zam}Bu3jRhmBp#zCLjRN||Pi`$gZ9zC#}rW{8+1-ZdB4ii2MrY?gp# zi3NKe!0P(@W#b@{{6M7Ad`ILc+<#gO3+dd?G;-VDF-JumJQ)vyXh(sIeH=Xmx_rE{ky|r zT+g~v=g%>SI4n1gmz}IsFR^~&AIO%WV)cHJuH)oBoGx4Mwy?&#OyAhgx2t=H9c&pU z#mBmseHl<=~Rc{iIIb1}?XwjXaJETRcHy+57CWcc##2lmRT&35yXJHTvn-q8L-C z7!`9<`G={IRVV*ZW-cgVi3!7EDG3vq#V^{$kEg^fBCDCOB^mT0H^~c1L}c zF)p_zY@I4~dWGsg3%(!1F1AaOlQ_n_W<7~;X#<3>b**#t=yzI+o#6^kjMP3~uRBDFx=EE{FO-vidAsw3{;o1#WTMZb z{G$9wU%UmqPFSo+Utbl)7x9PZ6zfM-eH5!H2xmq|}*;IeHfbl8wzy5~(z=)a-o z*6vFrdycBhHhRQvg?&HQ=8sl2SI8^_PH0e3COV)K%s`2orF zOx!rt;luevHThM*RZ2S@9gR`LSx=0gc^@0vZU4gGdRnoyq-p8?dnK$L>Wk}l&tEJG z)xi|O3enyZymCRLY!_ck9^9)2f9p1Ip=~7~9r`K>u|{aG(&qJoc-66jCDeW^%?8|3 z!?kgkITs98SDC3o%HXkZ?^3#3rXcipUQWZlLZ9$Opuc-}miSJb4xBV{8w=sS_Md5b zbK$*l%)v)V7PWBrIGdLXF!>fq`nD5}i@2HrB1Vb92?dVk3QZ3`9=K(Sa}v(KatplG zWTxszemvfogh$}^XK-f6hMP}sCPis=A&9GhmI^VhB4nXTx48cp)*%WQ5l_@&Vq)B4 zf7lTSXdgC{r&W?-US>bEHy)=d_nl%F8c>y{DK$w+`N*)CrOD}@44FEs?{bYQA(Y{8 zrEfgK9p?7n5Ur{{_9a)M#>`AmNzlx`*cYC$6@j_xm3II7Ye_?T$qP$`fL5bt-T=R^ zi{8hVU&+m6Q08yk_g{-Udgq3{C%)R3(mvlyAF;Wlzu(@TKsxo-0hidQtVsy%>O-8j-FXG-~TR&@r+vMysXXagX_@g2b6j= zHC>SyK8%FqpD(zb_51|MVB(fcgC~?-c*Vz49cA%4pH;!*%C4bT1P81 zd#BzYoSw-%11K5~LwgR!jZJc}CZz_)K5s?Sdv*4Qfx+nWIWM&bfTxl*3#(`f1pF@P zaUJttnMT>fe8J|hE-<@r{^S`Z+k-ZI6M}!*Ujt5BGTcmK)xywHCMrB{#nHG~W&`io zgIJ$7bXeMb84p{+pj{YH$}qxm6-_yp3M9;BIt+evelAL@PmPFVrO5+yKYkTt0w!pX z6FlF8uUtM^)3AzsiefX(i`1FbZ?%%CwZh94`E)(sfhY^+UxtE};pIpa2ma}TbGPWrofw=I~{TpNbABD@mP%J)f^?#*kE0?v#J6* zf%FT!-OJ|~WzyoPiZFZB9(v+NOPhy_>T2+<+UdbGzv3OLFFx&)2TrAJ`4v9=Pc1+U zI`$7&qHa-BY(2QI!t3-GO*GhSFO&qgV%;3d>b(?$CQ&!}ie)6BHr%+pZdOvP3Ke&~ z11B^AkA)jj0&zk3TBJkgkqu6D8&Bp*6*)1A%y50_I%p)wBVq9FeYhTzm5Y1~f1X6T zY}U>GU&A= zBgV%sw#6_JQ3T@s|PPcO?Q2IpDc%##?d` z7E?Bw90gpHrhp;rcB zo3FdQt*ILxq~Kvn7|!n-M;NXz9c(aTdqXbknalF9c;0Tnz6r?K*9WW&9Lr|1 zM^D7JS@hqMe=7Qos@9Qr5fyIC~SAw$`kn@HYa!$ zY4oxqgd6U?#^$88uQCp_<3*0RtcJAy^h*GM2@C*{y{&-&!hXN&LS@4VxKke7-v@$* zM*8bOMfRH$zp?)nth2l~pH9)_dXE9b{W1xANn2m}FYU`SxPnRv_?zNpFg$0=x?QO= z`JyzC`wdbuj-vujL~39}%Cpbm-xw;3!OSwan`v(_`f=z4W;OL`*(qMH-@RzK2pM36 zgN+xI*bT#XFIhP~MpBgY`1)f~4nqnQQZzKHa`KfCCa?7i5R$8gxd6e+NiOLvq&q1L zjd}xoYp!=?$?-kxY40f|XKMILyqM=i0?Cw^4_FMFb-uFA62`QbuIy&OhNJuVLAJeP zrJv2CpXq*5u;EA5t%kc&!uOADCPPD#mk!_7#GKkMd7SXA>mcw~piEzNkZ0EoiF;qR zUGb6iYxZyQv_UM%1kMdZqJcJ41h(&bN8g{z8=BT60A6NyE@xVqM-cei1%M^_n?7Zb z)Dw8Cs(->^Cs^11qDFLFj~a=Fua_WP>suvKr!%YGYFBGzeq0kLk8(94c7qXHm((}# zi9;zfS(@?(!aw-SB@APf14a8OPNmE6AN)m|f(eg(FqDzj@*@(wjR{(3+zqU(xPozn zjCb(3P*@G$&7|xfT5^QIU;U+gJAJdi`96ip`k$x;uj8IDvV<&Iwj2d8M#gjmy_D9) z%E@2_+ohtGq7L#Yw!7~n=4@`S-P|RAtKKIq&C40i5Fzk4??czq6yg1Es5UOOMFhv5 z|Ky+Cb%-GF7pd0>!&|c@$Wf#)$h9GG22J~Az!*FVy=(C+YeMGWt6BBNgaY@Vha1i` zxWlL62CgrsXoa2H-b_(pMfA$i$C-cfn* zVQr;frsd|5BuM{>@(H$#-nYAsKppe+m4Togs~J75;~YZ^f{Znf;N&bcPla1$v67Hp zPXMKkkUhl<8r9l+eBcJ34~cMCfC3eU%3&#g^Sak|W&7DtyMOt6{>ZqK|Hb(xTw$&? zg7yD-S0eNl1C$e7@c$eB^89P3goGZZ2OFmciJAqVU?BqcJ5KFHOSHxJBjAy+WPRrD zvN&g(*(7l6-n8&iA}k1yRA>C3fYkYu*{n`GF`~Mzxn%Iz3er&2SqSVG0!tHalhV#I zP}w(J=&AE<1~7lHlwQd#vVYc~oOFc@HBH7DEg$yZFrAlIit2r&lvYkAod|9btF+OK zIhHfwMG9HW*fzjd71a+?AlHZBs{VgPtrThgkDZNbKO9;&ECdE4zD;w(!|F(lY@(PF zQ>;zIwmA495MHyuE~KGG)`fSOW0eyxs7BCNre3G98Zhfa#=!hk`CHJ9)}*Ye!V}ne z`b+$80PE}h@3lAM61W0k-a$KVuG+^O#-CqgOA-I0nZ6i<$OsQgirtoxF0Y>LgX5~_ z(kv`zbQjJP0%=ff=}3_27Gjv8)cNw=f$+@VC|*MfTGLDBG{%wA!iP1{=RfFF`~fWw z(dPZ3wZvrfo8;CLqgaxv3>mE?=w053#W>$KQ((l5_Wm$dq&Jk~8IyKu(`hQ6Eq23Vd&P9>lBAC<}V$$8cQP*xB`eggi-cYnb@E@&N&GS9Oq%29iw{ zNd-e#T}o;*hL^9Z|3V0b%HA}H{MG$p;m}ZYXbMtcS3>buSe^#ONCOP_Xbr;&ldgFc z65Ey4s@n&P!>u-K_Inr299if3sJ)Ui>nVjbjk$GxOq+5&P*l7}3X<0NsoSt$Z~KD# zMl7OUThin>V=yLU^lGrR?KCewYzm?vSGZcj@|RZ|H=K2^g~(rzkdhr?i2MZ`_9h9v zn^5Wcvr1zE4GP4QW;G-nnq`f-i-~<(lbZO8NyeZSnad&>$_#$DEf&vRVDoFg-`hM!`6F=*H;wu;@bg(Mjb3ZfTdJ43{{hGvAllcE^`N%(L zpX2&!FZcbHMWFoYvGTw;@8W-_5ja@e}&aE5KSM1Xs^dQ8IbbB4EgLjZYrHJHL?;#UqEU_S^vDsRY_n1-l z^a0W2>&ZKLlImqCT(b)T}xIpG&}y;zRDNkOsHW z^>X<1vw@3bGf&EK53E2qu}lg*xATkX(iuB0sN0xEf3(+U74;vx2S!w8Ip8sIfTVB! z)B~@6eiVju{oh?bnM`-e4+c?h+|+^h7c_MgRc_}KE_{D)ltTeo(N!x0|89vhzN3Hb z;ovjZq9CZ6RAAp6ZIZg^zgKGhIAP!jR6Wdr9m^8PC89hN;)5Z(Dvxa0YvJET=Z+%NM(Qx*z{E5V}e?m7oKzKzM)qUH|!g z%q?GiUvd86$(pYrvh(4?C&IKNVfY@CR3H2=?f8j542t5KEQwU-b!|NODPD)6iEA4Al`q9@iIIX#5BB8+~ z@x!}pLvf`kfGA5&GU8i|D@d1FQRH9!F?uIb8flXlKrmvro96R6fCMSiR(=7IVn>_09( zO@=>&KY|votSJDcElZFiVhubj0WW^M6O@%|D@C9bXJ#tT%Daa|MiZGa!|+hB^XMro zis2^IxGz})sjMLWPE-|o1B{0I=;LfVlfGrU@f%e_k|&+S-&t3gyB+TS*#!>{pkKkv zk5jyhU*`*gX$e+M8kkWW192Us&{{E?l`lBW0?8HTut8L3gvX)|z|8`1#UaR7l!lc~ zqU6sCBTtE0VDQ*+U*T`y(1y+z(M-B2Hk_X>w2Rwydgs~TQg?({zi(@epvPQz%Esx} zB|9<<029G4qghL_pP6RB<0SCKWX$6xXbqkATWdMbz^t8fs-%l4!OwS7GzNXcnKGcq zdgLixjT%8K;6n~LDF_&lRq%QQ!g4CHMVU3OhhkV1k>s$(^mrKfx$u9~aoQa!sY*gR zIuT8}gU0}lITL*+ZXwmb`|ePL+CvQ48kAaAAq%Z~Fe-s;i$D$F=z^J3Fc8YF9N0@i z*s0p^+Px*penl{1v~g(n>U4zU>^vV9WXFZncz%EgnuC#LQM+cdalXCMyhoAzj2R00 z!i~Sv-0b`>ph62GCycW!@)DF(g79^+|pugxWnr#C|p|Oy3F_DgG z2=L)w5K*1)8Sp;nq_lb@eSH8GV3>!e9tXOqT~ z9y0i`eG$bTn2jwA<8>Xl)F#JK*f(Np;H~ahxB_VHCN=2p-%ZMZf!JHm1AM&!hVz1B&8eiw;mu)qP4!#G{9*V8|n^ zu|*@dA0Y-18ZN#m0U4Y1uc;8;|5aIoc@&(8bX1NM^dP*%M~p;L#E}1@@JB0|td8{E z3f~4i`)G32lU`?N6!)=8FQ>`*h`JgwM@OEOLDld->N}N>1EIbIc987N#HycIJV`hl zv`lQN)BC0WUD0DN&EY^~q|$1Z%YqiTHalmOkBD5p0TfvD2`f)MYq#TUP*3wFxkt)^ z#USVLY;kB9y!xgkjQ)v7A}1m?`pfngv**hcQYdHWnBMxsnZ`I-ze4~3+Q9}1&k--D z9p-;g-yguz|2~s*9{;1h_QuswC!Ty}cNXB|9noxz7>$=72#fAiR1-!%!u}Z6o>dir zhcig9Qs1D3eS%vgQFV{@QUzxZhq5A})UfcJRZ}ZGE9E}}Tv+8ynYMgC}1FK^{f3->`L5pV{wEX9u`QhWS*)eoj z@Q%Ke^%>Bab2sub_&Q)WQ8$3^}C@j4N5O5d@ z5%WjEfxl1XmSdQ$73{CC@jV_Zw!aC59)FTI_y9-B!0q7n(oLZwS!faSGi)b%4DMnP zL2sZj8g6G&x>rb3(4Lp196Yr2Ve~AESa)Hiy|c~wVqO2&vTit;G5EgC07q>(O6uV% zxvzkqUAsg~Lz z7Efb(_79P=X5WCqu(~S^h65%>+no$(QYd7PMARxLFzVmeiW zube>x8FJ~nHz))qO`50wuB*Dj@8R0{DazOsMTqB1%5}=lc&-P!uC7AYnFb$|OWixI z>!fQFOO;Ar5{m>BI#nzd(fbVg?@$6(h>R3$%K;|C0Lkf2P^R45joKvlaPQY58SGE% z?0UX*e|p`k;rwgkWd9R;8fJMpwJ|fBy;91!_FY4u@c)V^HCl=iYO%v}>nMs2NgLj!oJPgCMST9s>ezH^MBI9ieU zOJ0EcS~`Dut=S%!n&i>x9ja_g>3*rUGSOnH%G_-^C)R7V0B`c)z1Z^;-8^6Kqsz(nlzdXUy8Y zziY;f0G&wFgi6CF@&eW!`2^esjJ_Q%%*-?2_Nk(>tw(Ir&n^6R`MghkJ_ZL)3QO>= zgDk2xT|?lpgdV{lBL&%j6y*Jq$Ui_JmBMIbZ^eo!3ooCqmN!Py83J3P5J?!+>j zT*APxK4|SXF2KE9lt$HkD23wF3dKH`0q~g)B99BrB+IcuTw%CQC>i#(_6#f{Ck&C- zYRY8wqy7dzn)1!wcp>vjVPoM$%fk!5Tg`XNW1g@Y4j!!KC*S`>$*VxdB#c`DvVZ1FjPYJ<0r=T0oA1~Z8r1;~}WCa~; zSA`ASW*M*1*lCxtc+N{=Ou6iK!xDFbxD`A6I9hW^7KRY~` z1yjuKSNj(Xw)W0HR8gtGT>Z#!>Hxt2vT~AaF4qeIp?RhV+gFht=A91@2&);*j&vue z2ZZ^I4c-I4CIRJgKO=gQnSB*|h8?uOO0Jmmy^+LddNCWvw=TKHKSxZ;z1Xdmq4^r+ zHqeK*`v6_|Gua=1mS$9o&dwtze01S*A13x0CbQYyU~gP5FPJHL=T8rGhkv5i-j+qd z3&6Z*E<@AMx()5_nDnf16EyI~yZaj>up+GYrArb;nuGWQXld6tNq+>BvN0Y~XL>D+NdqQHw@n3GYD4qBDC=?ux&bQki0GoS^GPr6x7nWVw4sK|@!I9Zv|F=nP* zn=-8aaq^cFOJ+M_B%7AjG&C|LXm~AY`CU?+XFbKxJRl}AvOv{1TFzV{*Bid*v&D9L z%s{8${k5x>@+;Wvh)?F-o}BOyB8U^fb0f!WNgR@GdjHyz8?8)TNX2c8UmRDLE8MYz0_Qi!}f zEX{S1goF^43xG!t(OFl7BkRJ3zhm_pqo+Siwo}knH zq?vM`@<%eXvGooX=JvKZ%{5Lh!f_dy$1{XOPLFpJ`MIprSpJxi|KPh5yNfI6871Si z@-`-y$UpzG{e`gWL^R-Xby^NFEuu_?^>IK)?Cgq&J@tBUb@g4}B{UBT(O^pIll*~A zTB2p~l#9id;fKmCT{M1v%Z{ye0E;xIF&qOdG2?n5UU1VUS`Jd8xi zemP5>|LKZ1m}{hPj?MfKCq5Pfz^|C!{WUmTbzSgs4M3~4FKv_9p|Dkf9(-567c0hH zG=)mnOIx``@9LiHlbYI0NU`WieUWi54N6CmUuNZ#QykV-z2>fX(NAj8MiV%%g^UVK z+KQlsOgygQ!HY9i;Ho7fp=C4^6gOoA$E)cHYMmF=)AUsjmWJ%inZiptM=#im;lHl1 z`V`ldWMmIkgLZQ3!5=x#D+oBQ019Hk;8VR%`qaR-o#JHyW{h=(sg8WpHa5^xe&8`* z=yc$EBTSNN!T{I>?lZIe$|{ZZA&S^~>Yy!)&W{CEjqU`&k1fT0gEv8)wHi+lEM4;Y zQU4@;Nqw{7nOahUG1^cv+Eg1H;<7nNk~pzIZ@*e3W&Xe*85Wa7<(yR1o8(6dj~b+U z`6{jH@K!GhBD}1a<##@gut@IJYp~~#bP@-} zhN5@^*r*)#nVDTJ+sq^!qWj7RCyh0PB!0M*ZDaw~v#cJOX&ALNIlQPvM$zewAC>5* zAA4+c152vNr77;EB?08ohUyBR7vPE6%f-%iT|m(%TS=W&#u$DVJ$VWK|rCHer;eA1G;xiJTlahWO)TcfTI0+Y_}3fCJR zpAgf|u8RW;@cH<}nw?GI5j|r+kGKAhmG-!T`o4%vLL4ysD$d8zzYej|z1bfiGogk1 zAXd5#YB8wqb8dpY`jbpk6-s0|Z=s#AvR(y2m2w$Mti>KvuqS$a7Vx^ZLR=T(K z`D~GFc){!aBHmtY>WJXAKB>F5!+}crS^QV`!B`PpOWdx6sqGsO!rrb&=}hrsPi$D_x26>-j{@dx3+)PCzNB@1}nMVN+^jVML(iB=CDV z!EIZ;VEnpD*$Fp(pcR4>v4_=iCRaean>c=b-fr7QLM3reUZYE^?L_=yl<@62+A`nq z@W3aU*InNKsRbBTUh~VT)>ZxL;LLC2^_i|g(gjpcS9uvHuD{;K`9bcuc+o$0(fgGt z9i!Gp>$Bm+(NYH9_8qOe7*AbYf$kie@-p;I&u z7Pph>ne7h@x^?;1Z{O8_e%2d0C$n74De+{!oGMU`XYC#bkSu#Xum0{M@P6!fxSA>bW%!kVor>4C25qMJtuIoTaHwN`1fHtakU0Yvc zKG37@HuEfKAGCq5!-U+2H=e}OD!mYD&Y10mq|}Z@!vgov*+{tvw52)f%S(oQUS|%k zSaG>+nM^zpacjsaGGF*T$m{MK06VxLVMTWyL-;NrQY`oPKiqMBTD9ZI>KO8&ViA=h zU(Vsk;=)gr&{a;fv|13Oba6*m?z$RHiH>4Q1n3!C*%`#LOZN@ujz4z^m~xyW+Rf^6 zUOLH4X@VM!;l`Z}R2p>SRvj9GK?BegV#^!Ne;!BrCKm_3dY=*L-=A6#GwVq<#GQPoj$hOo~wvT@8C_RbKuo)856frk9q zj5EWn><45x>;k5;cr_#pa5a@#w3E~??P#<<0Zj4Smh zVka~YAImp-UN;u?I4#%Af5*@pcX?qt1n zysm61zqq|~D19`AKI&j(@e(<=&Io{f0Td`KiN_!=^X_jMqGTZb1v9-jz zdUnVA3sTf`ii2=Gr_*W@|E^Q_!R;7@iCd_!zwJy{kf2Eg-so@3-LGD604j|@B^X3{ ze4`vv%_qx6!6bgx{El`@Wsw_+2k(Hv|Z=7X4?=5I^YWU#jA#m=WuB7Cm`b8E!o z>|UYD88fj&WbuoOI|Ds#^ko5SnFIW~+>R@FO7*>4Q_JSprUCG8&`pGMTkuAtG`GHi zc04|G?3V)6^67dLz<>cp;pX5y;3dTnoh0Wr>4A8cYRC@%yIc_*KkEh4= zT*u-=oC7PgCy))zV>KJoeO(mAO%!j8aw_J^IN_~ebamKmRkgmREVc#knxh+No^@O| zW1u_Nm`<+g(Zf7?C|Q#@ zM`7!HCs9y@=e)oD0_2c42mrsjCsCkEHqFNvKk zFVSX?u75GMH2f$fxH6+?8cpVE<@_WHv~B^_wX^&d_zsR$JuXmgrm);XQ9QyOLld!U z1i6enRCk0C;U_e`A@EY`I=|K~>0Pg%?z!}%pF{HIFU1RUrA0vvjoNU*tkwI#(7*zV zZ6+Dok&#;l-Vj%Pjtyx@!N*XILW~=H|2*{fR?UeZd}kND>lY!{_gt(mpYL@x-Ega2 zVPOfa5Cu>Lj?y2(6*$?hngC3pIY3^w${QFt8ZR@Ez3KK}=&0fYhI@|CXp(}EAmzzmbCX+llm7yd&b^e@w@#l!~INz zr{pa0T?+0eQ>fE~`n=Ouf+=(HuL0kjwCbP?_&t^Agb?5Gc$gEH*{43K_N&d1==E{x zUlSd?3Ynf|DK_B-c|rK&Y|SUguq0x=R#AnOg^E=c!}NaUT8E@OKmFC!;qv^m!QOce zI*;=osDDIZw{B7K$Pvr4AQ}o%d-2=wFNR{!6E_9^Mj+x<#tx8@l3;E49O{{^p=z(e z_oI&c`CU6ll*O!A7<6e8`Q9=X5lwV&T9e5AZ>hndpAfn2^|4vghsIZ)mYF#xWPDFk zocsgbKe-Kr{tN?9c*=QCCS&&91&Ttd0Vt@ZccHkn(-q#d^~dcCP`%+){&2j52ZR^# z?#;BOd~3%sLOT3Ex&MVjdj1I+u^|U&NTV{Am81*x1`&3K$9P@G6-(e{H+Yg5q5PIG z;3{z|BFdwAp=2`C44el%cPe5?wSeof(v(3q6ljnDvgDOR;C9nrxb5{9ZWn6Ed_e}j zY9ztJH)l9=w0gzBIrf(m48B1l&h391GbR5ho__x(1;CYYq*#W)ZODVY`V<6ivkjcE zK;X6(1a4n`)G@LjjcQ58C=^gH4|GRC4E{Ft=cs+Hm-ryN$2vCnn;&l81MhGCGx{N$t?=(&%4@2}#z=f%fyfdGWF=ttK&^&flYaMz(L_jJQoS|99hZuNOz4h5hOGHC<0 z?Q?+-S{wuHX4`2S5uGgqiWLG(%lNCac#HLmKiuznmPMy_)-zpGt`B$1wI+J=H+l;i z^0-({{hm7RZHlQy9f#*KJik@wC-;4Z6_7k@8xU= z=jMXm*6o!ZQ)Y-6g?uVdo$z#fHUh2)=xoG7{bD3jYa^8>!>9nBSKMQQg9DCE?Zha@+7PZwnY({@W<|b223`-OGHSNjwR2}dv?2m zsPDpdOOBAx9Ka(&sa>WSfcqKh;2U&m@)^^9Syd!nf~aMw{SJDbj*LyrV@MnTQkEgY zegmQ2SFYEXgQyVdU4`ug3@u|J?naW8EU22F|DM0ULXivkq9nUaToKE`&oV%$H{ZY1 z`|_RCAmA_c#x5my`R#yvqcsMh-l4@I#H4EM6@RI>)*^&@7k$d?ThV4(4nD*c4^m7z z({Ph|3%oZC1HV`hJm9Ks+=m7ZAuKSkr^BzdxYDzRphWRB3VR#(T(HQ*Ba{$ctcvhB z^-3-+;fXp6sFb9=m;b>*>g~sRVoK8QtRE**T#BPtLGODEH%MX@FrUY)%P74Aif=es zRkztE^kOywMcj6uqpkM?Zoa`G=&CgRsxS0O2Rr(|5S30Djoz&uaCl9$#(L1pMfCN= z5`hs?jpypV92=b@+eN5~F+Ie#4TQQN%s4IksZ2k{(ztvt(yfnrYp5O`67uD5o@3`>ANANs0Vo^PsJ>ZcPPo}sej z918p%ruEJM?m*&DZjyZ|w*SpfQ>U5!p$Bu$^glFwuGJ6O&%*%hRb@{$xk+S>BBfH50{+aEo*7ezDL(!~Klzi| zzJMLdsJ#=g5q;MkiW0ui9K~JK7(&A-{-xoEbR_UNS&FozVUc0D9z;xQ?%9mXJbIkx zBe)}UAd$Gsp`Ri*AMdJ`EhgHa@m~>{dJ=ZxXgYswrOrWUxTOq{z&ByJ^YQtv_jOVa zi`j1F62(7QCrxi*4dc;=g08$Ak5r1kRHHArgq+but#sNWdK0~K6fjDQG^Iu_#T=-~ zOkVNiMf5D2+S+LWkZby^JQl8b;v}{Szm5;oKwqu4>qa^M zOEuZ|-aprDn8MYm?B2bA@^H5~K!=v=Ieqk;UFjIK7eJ<)paVU0ets@@!6cKL7Dvyx z!`I_p!cWI%yt`cz`QD9(wa#8FPUc>#gK zQ@6u8VYEy#va^FEf_=u&`+IIBj6<2LH#crPDvcjsyeCaRMk|Q3$n&t5yzD2C^t!V4 zD-DQjpmGOTa&J7hedYx!O58cy+&za-xs7DZH!^7kDO24R`n=I45X9skOXZSh_1Gnk zQX@=E93#1n%QouFbmy%6qSo%-wnDfj7|eQOr0bczk@n4eHZPm-tPsZ@1Wxw^e-i6uxL`AQMpvBm%|+vvHBumEqQ6I1bE|xc&7C)*RYoQAM&71t#RQU z$)BionvlwR@wrc#=UU}js*3{bF_B%LQc|C{014Uhk~8anCOjJ$Zz=p{x8<3{*J|63-q6l<0DOMt7m#fkR%}>`IM%1ao~R@9TY%d=R(G zduKf!S`F|h(`55VbcJRe46UZS7fiOlE*leC>!OcVR~wW~bXVi1Sm%+rr4B>TL+eGT zmHh4?b;zxt-02=ye&#Isl&Q`9D*PO`v<4klo+ub9x}RWv(QUw8Zf1|PnpP^_-9I|x z6mWUS3goSd@}Dz`5o&ASlX(~H_WOF>Dz5w<^^xC)t{Q^ROSX=NMM?P(eC~n;!RI(C{7E_g;`0`-vAX<~9?^GOMyc;!K4GYK;P3d_ z%J+lkb5tpZ+cXVVyf~T#P8gfZo>6ZHN%STjn8vEVhF?v9+g_=?);P+DZFcn@8EbL0 z#`Eqine@H5hx}uHjC8T_x>m})oo7?PFOn~l+1(*sO>^KeoKg68@p`gO{zY`^7x47pi+VoECxBbehK)%rzcsj;`5raUH-x6ik}9HeaYGO zLzXuV&VM$+rXV}!?WZ6tY&;2-3LERRaR}Wj0=iC;Pgc3Si8n|V5tiqNdw`VXxPxRk z%z{}Kwz!jz8m^Vm3j4+BRES9MvuQ6O=gI)TICy{T0(m-V5wq2~g(EFvL*y$ACWU+3 zDF(D@l&BoYAZ?k<$VxZmnaVt~eaV{Uq)g<~j5cRQ&;!6D(^sT4d^i-ihQfo0dP+0f ziGl}bh|Cj~Tx7}gnFCP5q;afUcjEv$C8SS(6FeI1s`b$kol~RkgXZNobWg*&4+L`F z(jyNmXPuowhO~wbP8S=~0%6{S>tG8Gyjns-J01cY!P{|Lu-8&|#}C9bIcgAko(hU&*2j3XI(zJG zx<|(Gt3ZnilK%`axyx@oLG2Rsq<`;zYQ2_CcJ+L*Dm5Z~wKS_8uyDooO(!t_j)*@y z)j%e``RX9oUJ}_A68hwQWcQx7?zgZ+=I;$V6!zmXZMHS){hD@Y26&p1<>DWWiAI22MO)wp)O=;5sr>2hUmP5c<_${>aegeg zhu=FGJv>VP;AV0(-epYLpoNoF?A`X%WQ-5yY2f z0XV_pM!3Xp@IR7L&z zsKxYP?00};30(tA2K_xFb8Eaf}Ad(E->H0sJqz&QAtv8j~hAAv5qGZ+=O^w zlM5|;1R`+t$=iL=XBd`|unRv-upLB_kf0d8bo-GGz;1E9`D0M3^(?e@qTr~uP-J`64xa?%yd}(rzs3C zCB;6glWD#{-KBiyaOP1;;KVJI-n=!OwZ_O#e$}eY!*Lx1O1ixo9}NOf z!{BPB{7FR5hGQR^SbByk*{yV$2OVwId|jS8n5kCW&HE#Mpfl}|Uuit15+tK*3urlu zIT3uSR)u|stNM($UoMofrzk>McaQh7)QF|cv{-afZj4LHo^=~ReQ{tjH(3Vf)YG1| zy|t=YsO`~3++{~{ja{+5yOLV6G+A+7>z56G_P$Kxf)e*4F!R*o44a)Y<9#uVYln;C zimvVMKKkV27ow80D%&|hrwYRgG&Zd&$!rL2AEt^P`-9ux3~4GsaQh+zx1(HcuQhpT z)vAT@SiaHp9i-3NCBVFbeIEDOS_-70xI1fgBujJ7oE8+3y>HT{5sL9qZyrFaS;*-7 z0l$8(qA_5zyKH3rSod*)Ql#83yS8(wztxUooQLF_D!gC4;{e<{YV<3%b)TE7o2vXd z{B#ns`KlZ`=`Pq`JO@0UrB&8$wMk>d+}4RYlLl9!2n*a0+zyL=)LbxK<Mu@w8oH5N=JwOew=alt= zg^^)Z>s%9hr~#c(f7v?(;Dnps66KMvkaw4&bg#%^58$M#SMa&<2)oh5Wfg>*8kYz9 zD0WPR3TUF?-zj{g?RkhBTr#{IVqky4g##-HJ;RGq8`^2Hw$B4TfkMi4JQGhMt%wJCE8P0){;$I10(xyl+kHlkR)aPrc|Ba{4U> zUx(bci=DZ(U&hrMIUn2#e5XoU=S1j!CXKv_>5Go4h@%NIhV#ZT107-K>i`syU2lj& zYZI&%`MHRAM1ZPMOeiOKDNKy^JY*e8n%rJN(doHkVB4vxDo!m+L>E@}j1^5c+fU?m zpH-JMq?9pXjx{FDuzc|bbcrTUO871^zbLrL*DEAVtMth_pharc6Wd8Y4hdH~ z=<{XU2dy9ny`yA!?)vhP3Z!E@G^vbW`N6h#mJRCAtY*sAlVnVz ze2-->q$KX&h{4e4{x=j7)MS*d>JvL)FVqNJq~*=U|zaYK_9qJM)*F~;WqGWe&P4KUb*<3pOeICYLKxF0qJ^&zJTK?@S}o*x+6 z>utWiS?_#HWIc5}O(%JW!-#Z=!;`MMt=kF6N#xa8M-h8Cpx8cipVBBN2k_37QR z5TbMp6O2hjODK?&VX<9)y!#A}<}pLK8A|R~&$yX|*aH~|heCqA4Sm75s679p`8M3W zyD@$GFT_z#5Fq%ylC2W<;u?x4i^6U81OPp?PllPTD^M69-` zy;tLK3-4c5ko!*537=ew(sCTN%CY&oqaGZQ*<9#pDD5Q5 zgoHOj2w~&-yHh1IW+|Zf zH=jijT9gvIR`u%w>p*kRPdEtr5lAx4m`c4hKEaWoIfG4C3?9|Qt~)Hpp2B-;tsgOP zf~{JPNKq=9TPI*(pT*~ShPbeNT4dKfZ&2OcR=YV6C4yp~w(8Z06HL#YU09yUg!(~V z;`t7*rflmf0WQ7Y?7FkyH)A9(z{vxCB2u0*7f)LUC5Wk*kQ-YC4s}0>=GT7JG7lg4 zQK%Q9-+Reb4Tk`xcqO@8_l)BC&;W!^^S#$3rCKhtK-018iGr6u`W?_2B3TJ{hK3!` z8}pBT*JRd%Uf;lMOJFB7Bs=!7j+fC(oA2+vXlqUaHPCc^pjkbnCK1|@;Fu@SNx*W9 zjcN{~(Y<1Nh!6KTf-?~33K@JdNPBh68a$Op3v zpd}+(6JiFN0jw@35C)jCM$Sm-GJ@c;0!j$=mbMd8FtXyf+wLo^UV5!wF9pOC*fw)Z zfTV0fr%_i(yBb~Z@p}yEeyyvWACN>(K#Snvov~?m=^s%n=8sX|FX%uNA$}m5?JZKy z;ybijt5XME_-~7Nj>MFh#b`Z;cJb`xHm;RPW+#lG`cU9ynoh!hH^hqMft+cxH4P`Y zjcmxjRWPrg4eD!JGr#3F172d31E-GdX9?7{Jcm+}0sFl|d}p&|aDk6VYqCU>cDXI) zwZ1|^D%Dm^e^j7I8)WxUu|Jayjz|Udh2H7>c{R-&8wpDreuEhc&Aw!rU2}^uWC`z^ zE_GNCmSbDhFXPE1Js~B3-8w-O5wL>wiu--xnEH`rkdR+IQEQDy(1wOc`BoAONhqXo zjg~2~S7afG_2M;xksi1#)Bt+yftN?EHKSV|2S2q3(* zxhkd3IHWa@q>M-7xYY+^USs>!Y&`(vWG-zg2KEB-W=rI8!{Izf6*vfrpB5s_dxkw! zT*(=X*+JlQl9M_QFs(YND>(-UWD5aCq#Ni#bUrd3BS2Xwr!&PTXe|h|yN61MDF`iv#Rn3sZHXb+O?ACP zGLjFu=W^vHc0>uYWjsLl>8aQbD_soaX066-@-uW@#V}#GIlrs)<#rS*u;T=USh9YG z-vS$rwF>eBG%!=CKVHpBVzL#qss64o<{9dn$KPh_pT#6safLKs6CFJ?u#^yjYx)gl z*2{4KHPvvUgG^c9LsOisv*@O&>}kTRV-^)|r3J(}mUdT(JwofCRTFksJq}u`l(W7} zw!6u>azW=Yy{XaoOZUd$mdj>;)U~RT)Cg&>N@qHBk>kc!EaGs)wHy6uz%Ipp#p9nk zIi%T2DL5cJXM#0fg%88GuJN>f(OlMdDL@gddu;XoI(ZX;`*|J+9slQHaSAziZ18v8 ztU+XvL)vII*jrwB$w<_yKMmOGq}ohx>HkoD4lf-U>IiV7YWqM@<(FD^p#_coT@9qa zmNBa;K18S;ng;T?vfEHvA{=H5P6bAa^vV7~Xc&=>HM?oM=zTw-AC%O!+(Y)rkQQHW!krba?#Imj5PkU= zi9K9r9!&Q)FP#79sL9f(%GMr;sATLJ?9qO zDS4da|5~lHY1>UUE%;3y_JW5~Yy2!Zv}$d(jtLs9c4fn-tQ`PAC$(<@6MjM?l2iQX zvdK|!Q-)WLVt~on98m|nK0_B`K{~MIu?gTQ@Z&IDdeSrC*exiy2N#f#F|lA0>-Ra# zDKM?yZbN=**(ajQAc_13DfP{&0^MLxC=n(RG9m%8pEBYS0&u#M4#A?mw$>08zS|a+ zHA>u(@HmHounk23UH5(k%FV{4%6Oh@v_MzCtzLrtBiAhQ7P6G#d&vBEwekk#w~xF4TXU?LypJak)FF@3 zETL8wKG+DbIyRR+^F?4npw*|x!~6!^szmQOMiLF8XE>p_sG-rvEzW3EnVp*wI!#ZY zF$n^^PaLa#>o2BuU=50gq}%bkOpUka^;|VDB7`|~?mqiy;~d9DWS|4EO_F92H|K~y z)z+H*^o$mzv)iXaHbCR(gir0JIeUd0L_$bSPdT+kCV1oXcbwKU!>^~LFXic92AIo* zAmg-5lB6>z)J<{lkSE}q73G8!6cC&uNn_B57kQoqEqF4)?;4nf-dn;wGs)AEz@$Qf zT;za{$oS9Tru^;Tu#vB+|D38TQI#8V0o_v%Blnt^yG-^XM3AD45B`dN)$a#p65f1H z@sq{GVepwy)$s0Gv2QKv9Apx!+ps9#qp#HKkiIZMzSuB~*8gLqGok#4QZ#`Ki?=L1 zcD7Fb@?nOOq@PQ}QAqGm1xsry_4vdm3V~^o^CCUNK4HDXhO5PV1qTSi+Asu!a0aXD zLz^~a4uZIJuQVw+h9MU2VgehM0@r&pT5iwrH_wf%j5Z}_3R$wd^$!1Dj{A04!m?fT zSBsauCmuSpy>~$G#-RS$WZb^(%*R{ zR|~Uo$jUM^ezRW)AVz*?TmA!s|NoHiwEt7Wr~FR|Pcyd%t5cyt<8}7)>dRFTM4u1* za^DA8r5_|4pHgupuIJl(_4e9Idj-_2T;%1we;u-Y;6BxdtheB zMdg1kl8_Q?&41c#{~S*Ug=a{tVTjHZ@bv9p`KQO4QTyv)=UET>FZbbhD~I5<-t?*< zvdoC%FX#?dcaQ!$RwD;lBxi^ESEd1_s*ic|-EWqkz#AeU$3IG+lHow_$eorS@`3D8t?i> zky(-vJ*sWwuZ(Z}Vp`C#Y4>E=6GFRM{I5M1v@nxk8uPz`e{o@2JmuhX`>{FsHtemk zm>&P$StFqG4)QQgEx`v|UVOgd14@!i$V-DrK)7Y5;nVl`JA%^Y*>oPCLfjC_Ue)06 zd^iss8blBO%!>N=o8oIj=)F|~ZF2hdkBc`QqWh1FC;r#P&(mpP?$WxQ(MCgi^}1YC zjM5$6X}&vv4Wq!-*VVY_&LGUSk7{{~<=fP+<}`A|Gge?P)95(2w{ z@}rlT!9;KSw(E<6C1^PnGi_J6Y)*~7ikQ)7c4<3ZPweuresIU-7$41!<>D@-tzA(8 z5$RzH*C-}1OI7lUy_{W-U*%lE`cqW)m-5;#=DMKEoy9Ury7`>+-S6J;h?1lMaS)sz zXsBR9Z}WR6;y0j`4wY3(^j=7LpJLz!7?ItJOnZy7P)T{gO6kT%Tk%tZJy5ntwCLY+ z@p`QI{;~};TY-YOIfR8!Hcgnr@5J8X_wE3){9f2xP?7$QJCBp^QkcQ7dGS@ytgk~n zNg8>^KfEYdv#mw?Tm}QQ0ylw-4{5>1nLN@Zb83Hqv|w*ALPF<|7Hp4GM;vY!D!u2{ zq79=k76)_$tI(E?GA%#ly`m^LpGi8ZZ%eT8SdW=(nE;Az-2zLMv zc@O>0|jR~Ytn@mLskK4!CRe|VGAAq*R1ckzrK%n#!)wq}Y#xp1% zRG^pL;FK7YI~XlV9nbrH+RxEk?!#tPeF^9lpb79P?i_-n_~ z`Swot9$9=UA*6pZhaiWgI$O{I{+S@`bp(>*)C)i$DVQ}2!?;sKP)VJ%x1U+!ZH^3L z`B3M^w+n+5euN0`g&jKqfF?t61~cL-YoydeT)b0RMxeZ!H=y8b3F6|L6D(}3?jWPp zsLp@u0--&bH@eD-ULE;Nl+V9+0@8zZ7N!S!?Nl^81V6L+J`7uf`Y_`OCx^1B>@3NK*@^MN5flaA*=ujTG)gIRW z=wMp^LdOD6K}8y5@_&P6bB&Xk`|8op+I7Dvm$fyTt`&Nw8zYL`6)KHD4`9G5&rG>F zily9tLU!bPVv!A@Ub!s81Y&Q7z62t`DuDi9K{o1^{|4EVqG+cBq>%6tAnQ1v>Y&Rv z1c|B_22g}c@TjdB#kg-5iCua0>gZq?-|OJY%@*%yYpUz@pEd(J{jxmLDA#X*A^7u< zUv`zm5cGT8uzS%>v+{pkJddORgU}V-M%n@YXOyCOh>M3hqC*XO5ghx+#g~7+a)Y>d zEN5bZHI7Yww$c0|h>HhA;T+3%aHyO=a;ROfSM*qY076_m7o-9^4~x1W>8;(Ltd)&0 z8KeTcD`Z=wf=K?yif%Hq9$k#YM(Z{AlCAjDTRv#3n^7mFc_%Vo^{y%%nH>-Cuv(B0HjqwVLPi@w~b$1Z3;T^d&O zF}Ml(HWmrvJ;Bd!nTq49^1&F}VuP5wb9CM%7;$WlsJMMcp?rm)>gOAN?&L#zoe;RETY z_i#tU@db@50R9a&w2=A?%eQ2cl0^-ZiOs|--ho8krtcX0g)gbsW` zqeePsbBR~8((?!j=D%8-AJI61h1I!EZOVcYP_wz+-Io@R1yG6rQ^IzU<>4+y5%iue zkl}DgRY4t^e7Q1w-^#?F3hTSH$jMk)!LDvMrFZ)y1Up=fYsE6f_21fW02es${x5!u z5aH}PGI;X|Ws$%>lJy&=Tiqj*_()`uMqUyCj9t66O=TVVr!nJ!@er$yqT{4sBJ*_>pxr6f!6aY+^YPC?Gj$kJ zY~LCe0G;9@7_8ZYs;oc1MsSz5eIO-sV{fh>tWDgU(L{U9pEfpU+WaklF^x?C^=Hfe zQ0JsHd?SFDU~kIc$CcW^~F&Dj7apDu7a0$KRYUPS3YZ3<>6dx)=v$} zTb&l5TeRny*qn5eo;P|8a_oTYjzm+tmXjByZ3kzg$LDb`)je1@-2k8ey{S5ky}31{ z`b{6eV^X&}Q(S_FhfdU{D&gWhQ=r1!xGvb6TIWgh+92=9_<{`2V^t zwavx6mhO0$!w0#;7*3Wq#n)!$H?Q*_oaYiK8XzBpNb!0AWD~m{BE?0ux{MKcf~X05 z;ZKM9x;+5$!f;2$g(KY3>q2Sa5Gh`BRalPmM~ZL#k>Z*Gx1Wk;ltF?nC@r~MWsD}z z+UF*^ps5F7VeKy(wmiOifTr!%H~qHD&jWE7nzg$QXw|}-w~XRv_5d8+tp^6su}G3{ z`qUjM$xAtc-eeG9NlK&WBedhTY9r-6rj7t?-Wwi%H!ruX_M8M?9c!BoS;&nuP5m@_ z4XfE}+lMtI5WrfDW@r}#{Mw^Np5Gp?Z6bU0ZM(;X=&5PQY{ftGi#Z{q&w#4NCCNPW zbNW`&c2AP;62*tyzG=-lhw8T#r^!FC^GgAZZtT2j+uF)?y!aM8ND4j*KMfFddlT>d z6npsKhw}mCrjW5|pE0R^ozPVXl5XQxoibdYU>>*P?*3o)rNO!FpNRmzYbSq6+0=HC&%O9G+yNO%ccdUqB{|cYH&|T$<+KxKR;T`g zNm~5`>UtL?XoDvZS&uFiMkyB>t3CR0cL!;@Pz)sOk_I_`cHd-xT_7stE0~f z3!@V7)4dm_ZGZl+&Fm7JUTDz(HTrJ6c9whXfTERgLSNh%=P$E=g!L>$SZ_dtbu~m- zgZ~KY*Ah>NuugrX_qv{qKi7|tc#qfkq14B83&5~trb+JkM_6P0M_4nlpzDvYh;i_X z9nsF4*JijYaO^=xA<^0KYt6dbJ^U5cs`Ruao+_S0Uw+%4EeZL$`-*{sMVXc7SaC>= zYWaK^BPTV{H}AFP+FW6hZLObk6aSmoJc0T%dS6gw+VG3M;I}` z=sTb2`P}OE1e7tP1_Cu^s`*};1-ZOVe6a_9$zrb6*ZFoSil8j!4}&CQzy;QxPrwe% z@?WS6c3iP%@lnqc*Xew>Z>q&!9+$kvq9Cy;C4S3z$&r_Zd~ERP8B_EtqG%c6y26>T z#Bs~rd3(N2XjXvVwac67BiVTck+!{wgqRq?sRI+!nw`$)}!L8l`Id*R8%bIh$!+cOUE>Nr&@hiX5`C1OC_t|(g45@WKvt+;+j(+yBx!>XOu1j=0C+Sx zHcBKodj%{hXz4HV>S9?Ta>=yk69c3%eX_`;dLhb8#{++$>6bAwR>g_$^+l3(Mj61`mGZ#gM z$MjZI;}1l*V-8~y8eomBx`33Kf(CI4|I8Z!6jPE8kNNK#WvC~%rD!>hs|cba5<>eFt+bg>d++JBl?mHPo%bS>X~BwA7>}Jc zI$${t5y<8vbbs;?`X!i1XjMipn8&(DQ52P|n`$9wu0T&b>`5B!D-T|&BMmrbRsPl8 zt#YO(D>PUnEa`hhLQiYZBi3VhUK|<>Dj}Q}yN|;gDe6NljaVn|U-SN=y=Nq6Ar-+r zJC$Sr`)3n!R@RxKo8;Kl&fFWt7WS^itNR!KGI3BmDnGH`r=ePrk%HWj%-IW)OWxyw z@Dh-Z@pCFXRTRh8_hI7PuC!@Gf?;^JcdDXdap!T@U!Q1?SObO(jT_XTPZF8m?aSU5 z;sppodl(kE&fEX_NjcKy07QzD+tujjyxZupWgF&$?Dj0>X>_$6VLJ{>W@iZv0k(~ZcyACw8Zu47FK2g$Jo!@N!J`)5OONrdXfzK`@y7n<% zcAvD;4nBuL;nh|`1!z-+-+ZcTX$6_^N|%9v=Vajty3nLRXU&4GX^C2W%uZ9EKx8fF z3c@_3N*g59M zI`2?+U%{L_rfV=x)}0o&Fk)jFDwUvEPd;w-CCn)>Q4mi!4O#mUIW;mn;O98!5|;O9 z;v1X^ho#e7ddxV@Z8IIguuxHnRA->HGG32)Kkx#f*0hJ0KE4CUv>AUzX1`^4E7&sl5%Aju!xt}#DWkoB)UHsyd zJDKKth)4fqkHp_G!J`BDF8KcTrY5 zmM~R^4z84)MXPEt^is9du%#IAC>xsNhQF`7|#r75u-c{TDu zo9uEwz< z;td-t=JNHPGqC`A9t7v#m1y8I1!s;-Y_70|pGHx%Mq%(jx$Aiyek!~7yHF_t_{~@Q zzIE?}+AWosP>;R$MGXYu1XBGc3vhZ2`+@syI$Xw6OWlAnNATBe{YPq!VC$hl}!^%ayAQhKLIpv=$S2FJd65hN!jG$+~((eVxL?L;uC4xZL>GCb-rI6a*!9WmdkX zq1P!vXegVwN7_q@VLF-#>o7Ysb-CVVOfq&!4H`v_Go**?+ta=x5l#1}MF1skMH)CI z)-U=mm4Rta)#7tZi1)twhczaPkBi@S-$tRvL?jw+)$;(`CGl3^#niXlkoY&wj-@1y691B`R>d45EKQs)J2M{`^u{mtkRDvJLA6bD`vIe1R9K0 z8D!1dfh#V&ZigS%)MB#^2*h70CyyzF?vjgC=29oQF_(=v$gz9CeP$}UZKUWcC=%b* zh92^Ob0*$knD=As(9=9xoe|AtcrJ)PCl9hQOae7$ZzEaEoPFFf#wth< zEJd(8mb6n`q1Te`*!+V-+BcYfTemiRzr|v_i{daYI6#q}PFlRdFWEXQ?f-4vAN_j~ zK<)f_03(2_ZgOpfw9Gg0y<&n|w`ZXH4_TA3^$;F(cgmKjfaVwX-}~@25xzb8C04dO zM7~598lG$m-(A4JJC7JH-vu?>nXIynk+WG7g|vXt z%>i!4G?gyjff!efj8{B0vDt!vOX{&wpBfnIJp9FDRsCGkKs$rY{S9doUE<8b^Jv_C zHu!nP3ya)clnzL;g%D;R-u$KYkXQPerTQ1YOnp%2SfVCvI%^j3^U!YN9bU=V%&bYW zz(_jEDiwKoV*l)N`7SCDyXO2zXv+)+!{~(@17i<{#b70s4GNY~7+QuhM<97uCbU#j zNoLWNz7HNq5E{N=o`7DqTLb&PVdF{AMOs>%AR0N`2EZ8_dyQ1T+sZWdze2&2;&Hw9sc2X|{Fp>=)}5 zv?gnB(Fck80Hxe$*y+iKZY|R!BF2vH$ytZ&fAqWyn(ZXi?8VkLyxH1e3*NjJMQ*d6 zP!;b*tNQ7{?cG<>-CrVASBW4r{=kjO|jTZDRnX3U)YMCXHS#Q>K;^W9{v zZvs~9y7>M6&roCwN;(~8%e&0tCUlb&A^9O3Cq`^97VEvkHy_!4EA@H|u?(ffZ60Rg ziDQ|^$nno~c9gB{VX1aCz%WLhpYu5r7)!YG?(Rjl-`k9F?!V3?j5jx)KNdw0qxxnK zGsI(cuJUy3Y#qBz$~j`uqF@N+=HC6@|B~CL)-+(mgZC0UHoxEKK0z!K^ax)pL|SZN zrz#UTlQ|yr14=I07YViTN$WC#QRhbcn;=7|qwl<0hW$`%Kl(#8r~U7PC!T?Md5rC} zmW=n`f{s`b621&?C-%$CX0acx*UG}dV_}8RI|O{}TUXw)WB(8tIt7=G4fMUjg{~N+ zAN{@Cy7Mt-Kp=q1DAWpGm2N;&NA-xIe*o@={zdJDiJs|A7EFUcBArp+JZv~?P($L`6t>sWH%lt5Xbtj{{F)%Z*&ch@BBJgr+5TdREanG%;#Yjn#L z>jO_^LNC^I;obyGwwWyU^u-AO$jt)13bC+kkyWA9$~Hq&|Dfo!>o;}S7}23wP2^}p z(Muy2?j_`mf z1F`zc)?KwA-&=c6o6~j$&Dty1o;9KTZ_?bdZt) z{IG_fW-rLHHD!}Ht%g1og?0A<0;I)+DOaI`qFX7+pB^iAKGUn+UI>aHD_w=q>p~mh zxTLWUX~4&P~=Jfz5% zEPbq0%NGC}%klL9YJ)r)@{?U7n3q-2d0XB(z)+D05Lul*fHuQZq#OP7T@5uKEtq3OXET;qP! z?g2NPx75wa+QIc+hZs@<-(Ya!IeK*oXiwxw&lJ0WSXwjiZg(KM7!%0_E7G-mttJ+D zWW)#>L}Kh>^KWJS8}N9c@#J%FQ3`sYqq2juV_oVG+U9zUJNTNDBrf4T<5xsvnv{wVz3KPy#!-O#YF_*VLb z6pJ&vijPV+D5A0tOeJA87fyJ;w;Ale#dU(B7r@=p%hO<|OsSoZPA>3c%)AIvv$|{{ zM3jU>b-`TO^OQHyf@G0QsUDZ13)#RtN)K)F04LtIpQtpkLd)($oZEOX`{>P{tzsu3*L}HJxWJ&sllueN|EtM7NH;JL&F7f zS3Fu*8iVrEKbp`~oJD+ionjMc`ten)a$uA!s2sx~zg?ccoQwdbmLC%?t@t^TmrO`T zzLFsFH`#KTUY|?`Flr2D&e@vS96mm0G#)Xx_$1$-Up+OL@#UWaESy#~HOV?F$CTPY zhRJvoD`w*k{l_Pmq=@Ea;S9!T`;0^7-bvZC29epYTv+b^1EEHqU}> zoyJGG^PJtEK5s|J4jR!0GYu7dIA5YHd`9d~cr@F<=tm@p2p%s*lZH}rD%hSvsk2NG z@0E7tK(VL=bznsNJSupM0-8OVWlG!*6^~p?UI~{Y`Ys zjM%EW>ALHaNXZHVxx3`RnV{5mCad&7WxVsbFB}j00Xxt?b z+-V>*1OfyJ)>v?d;6WM*1osf!A-Fr--r4Ut_l)n3JI4L>{jaX7eyY}5HRm(un!Ak%!?#mBSt8PSg0h=1th&0c-=#^O?Fj|#O;9)x)P#xt#?B~1Q}p{)KY{)_7HsluhB z7UaGvrj|AzLqf`AbYw0n=Uyk)7qF5wi4DPybTsLbkj- zRbq(u9!BGsN7Ys8pdLaCpxhPqlEw+-6SoTXXjAcKJ-p;)pok4Dz^dA3*fbjaoHhs+o8+-*QymtMyM(PK@D%%?7y zI}*^z1xs3`&QL-ys^1}F|K6O(yGEIHxX8M6z~%rO25A`lxCW1rnAUo;o`Y#mo+WRj zfxXOVEE8t?%H@Fg%NH3<-bjsvh`V%H)DcZyCBup02Ix5zOQn;s4?zrt9O?JTU2uU+ zoh2{|djl8kJ(#S~0*k$!6bT8lqL3yeQImfnZzx_&cnJzx$VUm+1Lb()wX3t>Tb>TQ zIxsxZmqF3MsYfXs4XzX=dC3XLMS9@x?0_3V%9xp;X^HgU#NYYG%d%oBoPxG1MHm4l zS8ayK?`WIy2Gr7>sOLv?$!xYx0P72YO=7pd$g;_K8PL2eYZ#hvqCs%O!3<88t^stx7phm{RWfz1rcs22{?Mm^Zu{j}YFzN3-w0x(o zb=N>@(sMB_FFjA6cqT)9k&a9+k=vF5fAmU50!Dv6H~5jKKwbOYfv+J43OCnfd!@#H z_#?5z=$Vf!F|$&boH}a+Hb3T@)XG%x&e3g_&toIVftJtankgGhC)*_tAvEF!LwRDaeQmbYRKpYeG zqTALuOVPsP@AiIiuBMhNiR8l9aokNlxfwPPt$L*MjSu}D!gN*NB2B`7cZf9$o)jk^ z8w2sgo~gVaA~q6gZ$1cNN57^?mpch-i59biuYW6*wXBHz)X$`Usi~Q(VuGA0 zeWgXs>=+!Y2q4V)`rY}wxk3GpZOWoIr(KPUoKB(jzokzOg*+8@3(%Zck6m;KOP_6onFLLn40Sf_o`%~+ z5{;rbiVO`FeO($(xs8F*@6973~p;{e0+FHG^O&T>@aDjw*TrERoPfJ#))cDS$JuA8aL|Bp!pCu{8Haw&F|r#tM11B z+2LG&w;UsdKde;m!9KOrwS;S=Y`>aJX1lGGlwy*!!s|QE6B$6r$*)9TW3}MZABB&y znbwP(_fDsO4+z$#I$iz&t>p%7u4^`CTJ0%Au>Ga>nlf^pSZ*1}WMUD$RCjtLA4zo-#rdR0e6zD^{Yfu_r?QM^JECA! zH>H2JXHztYe{${UW<4toOxc_LpbBr}Tx>`Jf5g<2HchYjceX2q#xjQH}@r4+`jdDes1RfVxm;LFpjJc54-m>8bt%IFIA zrwm6yhFR}J;9}A-8tgG@>~viIKpq2gjcEk-8E>0(M;5=bq+sJz;kDfm|8a}lhA{Ki z@B>{nBInbjb8uBVLy^xh56x&hW(^GQ=v`Lx&{S=~8`|=`?quG7IJT&r`08<50wsgC zF{xyXS}1Rf^`{n^ZS;+Xyx%3G{O>jd`sw@7$ct8hgj86HGf1Ng&zPMQB6qtNQSd|) zbz~3xDVwju@K`I$h)D=&uy9x~{beDLN?LM5oN@taULOh*;qL z+Sf&lvw1&X?``C4VX`EaCfY+-D!irG>ECX6?-SFPF555hMJi8FV@>f(F@45D>t637 zkdLa+yr#$0up<|p(rMzR##w${ZDozwk;jSgyG7aOpJFgIa;7SXT-UX_)Il0z1YM!F zJiY-3EL3g%mXzIo<|)R!G|k^Lnrd4q5D;J1HTRNIE=Q6J?G`qk-B#!?lLI zhW;@+!}PcP>9Jwt+4vW%5NKQIA`9?mh=YL6WJ%gGH7kk0bNALIS7d9m|6_wQhzrtf z5(h9-Sv^SiBJpEeAw{>S#&4S?d~U-yGs?Rq1c$@{YV^7yZ~4hU8?TANWuOtX9zpGE z7vF}~RP>E2nAhbwfltyh(O-hD!QXoGUiGe~f@%!VP#;*Rn#Ti18e~u4p{p`r^LY-e4&6JR81phGxe0y%@qtm4YM zKyrm9FO*s+G4?a?-yKocz%}4fy~7RJ%--63I9-n0Pb>MR+R@4 zF^5p@pKZ)Gw6$a8@uex%BrvtPz?aOW_jzxwvqE>PN?G>kvN8X|2g2E!0XH36tgI*- z3oMUJ*D+3=tQG1bf!Gc+hG);X(DaKaUx=okJjO*Q!t~q8zB3kY5{D@{e6>H|pI>Zc z_fRMNfhaniaHh0ddJ2OTWQ#BBZl0{g4(97StJOW4JtR0kSaRKiraRsS0a7EQQUlk# z#b4CR6S)CRiqe|&3aqF)y~*4xD)A&CIm{G?1uQ2B&N~`yyI5;s|7RWe=UuV7l}^eYs`2-a zXpxrA-1Y#AwoxnfS- z_;UqZHHJD>LqdkS$_DkRqIe66^nwdRN)4g<7W*-X$2rZT&l7r7UaCW~B$4+ZufT|V z`^OA;wEZx{GWwl42UZ_|n$uQQ-rz0*ka@kn?7xd5;8Ze*>|#m_Vpih^Ua8QoU>kq? z2Fcv}>h~3yGznV%5vO9L?$jt0cwh7Big-sk>NiXDT=+p&ROf}vfn_3bzbrtnWBvBk zy0puAqg+K)VXWr9tpb@r^6DTd0!|H)7}zw=@a!TD2}cZT z7iwiQGw|GcsVoQ{U$G7}hqGH?EEgNqg<4g2|LH-YJ`O9n&%6xSuv^wcWm(}sbw8%W7K=xQqUAX!u@1y@UEKgT$+QIjm}V&=y~(E=N6&ZWUZ0P{BS8)% zMl&ms9%}=m=eSYzy_4&F&gJ&bqRoc6Lp*MQnG^QNjpUVRKJXh=_MZCo(k3a@+v^*A zzzK{Nw_fo3^48t|Juh1h7}XP6BVf?E`dno>|b~?9O8hu{pj|E1O2c491SO}3(vsyz3@eg{XciFYCu|`5cA$r(gA)&Pp2 zU)>hU<RO?ZFlrKEhu>p%C`Z-I3HLQk)qMskHE%h=ivTTwiPZ~T#4Gh z;^gPJ7Ir2oJyq|trir4|h66^mXDYuqKJ3z4u+=lWqX`=^wS%D2q>JXC8!54Yt#eX) zR;i8ke?ZYif}EU36yxJ=*YN&N zf5baMH8vM;R2T;Dn0rduD*xw2S=$@>CsfscvIqbhg@OG~pTCZ@s^BM%GYbL=}7#+CH29$_1}~KW6gS`w|sT*Us{0l38oMK zy0`wBKmWNHx>dUmfwN{CXr=-H&u@5d0h7_#fXGDoFotX83=6WAOR^&Y=I;-rf}YOaEu(!v$Qt z;vi)cD7V5h?56QmN0gF!==yiP-B(y=H!a{%ck-?JbVy0L2hBQ_LEg~if1NzhkaTfr?Wk3DK?q>sE+i5(vUTg3 zQua|g+vaW;R=5vY1w5!Yo8uG%jFi zsTXLQsfbI#$E#eCStPfu;V~-%6HBzlf8!2E<$60%=2g)~APGas>_}3cQV^K&4ED4h zV&;}%n+d$RSgS*Ky&&5P)%$?lbk*>nyT#|X`=EQC!Bf?vwwe$`2_g-g$_1kMAI^KF z5;XlEayDfnAE~5*<*NJUYraAM!lfOkt!rWiu=TQV0;c<`dqlYdlg>DC2L)>H>HH~n z5f{OFem~5+KF;wER?4+mnJFl{8E%KIE%TD<^0uspKa*c$}UA6BhPl-B>I! zUAh4^1-of1LL&KSp<>e@sZFY_#fc?!Hj1=Ff>*kNET6}_r3UlN71t}|#?+EhhD`H% zE+jw_z~<^rD6Z_d9m>}@!*i{+^3xr^^~4O5-Dw+&DT(S|t(Og_lVY+*%-CRnz@SB6 zo|6vn=UmqFhyRo=@`u6MK5YtO3K3QJw47Q3rI1L-h>gvx?m6j%W8KgsHIar$1~ai+ zd4{0cSx`tf=yfnQF@tP#KG>YQ8?uU#(~ibWa71<(Lf8Jo_{xCNt>&d=D4(0CHCqJY zNF{0@gsx^zp#N0pXWul`Y>{;tLJ-}>;Sz^1Pt*UWkcs@^w_4C&6Wp-&OtzGK@xBIdx1#R4&v$~GG?p_Q8#&|b2?!;ES7na5~? zGK7qE=7@&kWAN$8n-oD^7($NiIq=G#BTbRpRmBM{EG6giu5mwIN!wB}#Q0+3I3+=P z?;Dj8J9Z%4DqZ@J>~XK$|0kGf_l3u31`|hv;7=2Nf)nFY63y}^Mp%UV0NSRn><|0z4VA-fE_e^Ns^6x`zx+8_&omzBrvFF9eOYVc*V&0;TpqSbxT z^b3u(nj8)wVJP%sh84_R((g)5Ve!Wi$-CaTURCuY9@2}XiSN}@tLFcV%P*LJ1stf# z|1IFS;DM-m3H2Qj=x3uetAOpoho%uS+1SLKwlU_$0M#whPXRbTKf%+^_Pi#ZbAkKu z5o;Tv>i1$QcNhoQvn%703;DnFA_bp&)m?^2h!{=R=l!8F!2u^<7h3-@peL;kF<+ScESkXMja(-mgUnW_JY+dUn{^PHU)E}2|WxkL$%=M$3Asx5(2FuB7t5-Epf=ju5c|0 z0TP&4LnQVcD*}AA$C>~ITI9Q8o?wD(4T9RS)0kX$2mbjO8K~zkY8Pk2QCuY^@v4pYZ}k<=F~ArJAMmD=%YJ!69$wO^f@8A;x@({ftHB*yT8O7g!d zyBCclQgw8+e19yX5kjHxLVL|Wi^?Du@36-|pKqwb0#+?Cn|&1PMN<$-PA}mKkW5;j z@iDdyAPHqU_;!i>yn_^q!Ir}79|hF z7un`(_A5Ul&of(2>MyaOb7(p@vSa#SjR%&Fl%nnPj=LA*p1Hq^b;|mXfpOAwSS{gc z^B3{a4vbwWC0`306*posT1Vf)EyL!A^eIq2!V7U$LZ|sqck2$e%>GUeJ41T z|29slyC|9wy;>^#yRSb|35L{An!ok_awjkCb|g!N5cS<-WSLogSr?!ujKgx7fDBpZ!|GtpAb^*{T|yTp%;@eBqQo(wW`Jnmlm zPeuB_amcu_Tb&8%|IR68=ErL82><4Dt(Dxlq_!Ep{v+C(kbd@SMA0cuFKG|Ve*P5? zw~w`>GBR;eOsWa9KE-wE|0!||RD_hj+; z+G7}QFm{qJeJJ^ZYZYk}MFruo9-J5_1`iAetUVX@_P0Q4x% z>~ZZn1k?N2oBqPwgnfhn$X)Y(%oLI8Lz*&9y?Yx#eB z*{i_O>@dQa>*9{TBd-1dy-I<$a6x~Q?(rFE4bPiTaN1OFnx5Xks}4)?LRVHv6^N)q zO9um${SICOre(KbNTw1!lm`^PeAQb{Xq*^5sQ}sL zA?W&r$9gGGVS7(@!<=toYzrZ>s+s-4nx^>|pX7IP`t>1BxaO7G$#i#A^cG1|x{gyh zL(X$Nd}zziKlngkUE=dKz|v=_A9*|o;3yHm zK^d2sZ6cZT)jqlUA~QSZhD%PcU;F8)?6Sg$l-pP1v7)Q@68N4slvMp>T>YysSRb~4 z9~1k!5ALHL-#GPsB--JGXJZ|Jb#?$q{_l)DE8qEv_!8p=Om987tEF}1$S_3<=6lu3 z3^jA0UQ$NFurS$3E8L_rXbmp1+QNi+HrTK??-mmp>z6_4glDMmiww2y07L+f;$9hk z0U<*I@ZWB+WQ3x-Mq*|D?-nU6_;mIFC7c%O*8Xny|7;283sMh%+N!KF{BAfY+|E;7 zD3db)qaLDhOXRfRJrU=Nq~H*9A(r(%1yJ{jiIxbN9xIfZv4~7UHDaIdWkkX$`C;`? zUv(z;{|gB~p-`*%Q=AOY+Y9d5-QQBW3e z$|*O;K|fYNI^wtS`sT=$f+~b}T zBl7X!9|TW^%#T&w7a@+~KP~#HUG|jl=BjQgrpBtLUzf>74M375s)1?jJ~iqH9{MVj zZDtUZYb*hWklN1PX4yI!5)r^|ar-24GofV{{-ki~U%yle#i3Wt5*Yg$RUmFeuv^y?eyaoMHR zv7`Wq$AM=*y)>^!f>oZitWdx6^@~~w0`b7Wg2lOF0l7xA!<#yjEg#O=?A+yzq@X!t z=cVFi*5!Bb25Q~kh@J%9i$lo_2(A+tijI*InBbCg^euuE_v(`3Gn=F2NUTpeG!uRw z-SZYbcx`DEkdpcT)Z$M}0b3_{?CH|INdW6|`FQ0Boh5R*NT!B4w=$Qm9o0%68s(~d zH8pBG2o$7L%R4W$YN?vEu`19&*BQXDa1HkoJRL#Qn9=W;Rm8VS98ak=Kr3U{e}RuL zcjEb(+x1A3auTrU8>o8wzMAJ46FBer!3X(e3e1!PkjOMHv4TG&v(t1h_y%^|(&Jbx zYY}}z`jF~z&c@It-BklXH7A-|H0YNb$Q(k!qQ74QAt+i#vWUptIa3 z1)lS*_vxK-7C6l4O|qJo-c{qFuH|QV>YgPp&!{X|?#lz`*w#;xog-d7elB{&5s!XBtG>V@J zj^Gp)O+G{ZvArcin>8@W)Fidz6UB(q6)~;TF?OwJc;tB<8VkaE9ShS#h}6y`rKpAsg(xC^+>=kQZE|ubl_rEr|0!H_6UslTCjSA3$mO&@Uwb9U-<{R=Ch7CaeQ4Pza{Z zJi9DrgtJk9G(Gs_p3K__Tf!jAo82vS{SVAfVEq5P)69D>!9SUyHBCQAobs9rkI6k| z+AB&jRQ4hlT)b;}?G3a+9fY}8^vt`>c;A&2{NT%XlFFa*NEtUVB6ReOq1eyRvTqzx zD5k}+`^HatORu|MY&fI4PR>+G>VA5!H_TkT!jQr`9yyM^&8|v%UBJU{%xjmX?1211 zihYEP;nI!a5aP_&B&ej1x*$d4osGC{p&jo4|CSj|Xb$BchT@+d{>HK+)7x_RUC@`{ zsN<`s?_N5Y0bipshN02^JWaJ5SFb)H3SXu0Y?;y4cUbKW&)Jy$zZ=aS;){)*r*1p$ z7gwp1KPIBr7T5H|9)jKE0O_Fw#hmz}7LirXfS2P?mRq}cp63XwrINX3Jp;>L`ABol zs6t4VYUeuc?nKxBvv%Qqh4GCO7?Q}^ge{o7PqDup@>9Ewi09%r^&`Gr1k9e|7e&C!KlF~L{qu- z{@a8z?Pp3WzJf9{){FlywemmP)raRoMpC5W@UrVrs-98GazO)KfxK}J;J97J)AtSJ z2Y9&A$ozM2fkzlX7s~A=)d#NA)2M8b!-{CPw3C6OKT2uL=x@v&mSmG$OL*=SfB6wN zap)4kqES=v|0Iy4xobDNIAbT9i`+^D?vj}+Od_w{jHrbR(9BH8(ZD0gvl4^pw2_dL z@>oW}2*gG7kPj?u3PeS$g3_8q@}eI~VaxSOT$s0G>;Cp}kkqx+Z)}D}qMhJe>G}qK zvGzb8yRi`wdo-V{kifge@kQa3UCM+Jz?-V@DO^Xpgb5-5oZ2!uO?h2ysxG9@t1{Ru zqY)6mJ?;H{Qc}OPzIfc`*DuXmzf!yfd9M`rfQ1)lWYt^!3ri6(4ePwC028XYPA1jg zNUp2XmtDP_^!b?~)0PKS(7 zZ<>*M8G)2U_qYIckh5Ll^o(bXkJ+jb|54aPQ2fLV;%M@U&tib&-NB;aDN&v%^SS+? z1mATcIXwsQ4XQ;L>g#Y+qTXk`wBvbklC(^279^@*MzFC{ zxftBZ<74qDN?K$z?&S7(X# zvzIT0UPA6i|8Mg7SneoHvskYAEK$m1M)4z-o(c>~`h(3Q(LMu<$1UJ0lKUU=3lXWx zha`6r)wQH4XR@U>GF**S`H@f^&P>oPlE7N3TuWVSQ`9mP^b;(ZNtuM|eMMu8I!{qB*f8c&Y+oWFI67Qxwbd!fifB z)>Ps@_KkafJq(YxZvHA;V=}` z_<-*~>F;*xOfQo;7{3Z9U3of0A}um%HeaHVOqaQM5aHZaYooI>jNBZJv#tG7{a9r8 zL*S!3>@e}#$JaMaN;P?J(MP|lb&JvkoxdL|bU-mH*%vcz2+HYC2qylKV0`$vywOYY zdfqI0%{=<@FqgS9F8s9p^=tl&S92|jI?I^P*^DmA>*d1`+M5ZSy_tooAb6Hi3*66` z*OW?L1=2Cf#D$r*EZy+4Y;r$+3{NhDJ|=VK8BNY~4KJ0lo`ivTTDa-1{PNp;Amrbu z)prUdg%sH>H+B=d;6#&dkw$GHH$>cQx@=i8?7BoX#;KOy(sUM^-VM%X*J4@JYG|_l zL`f}h>F4<)&=#wm<7PjBiK`>-g1vcyh6Iw0!lac}N#4bVCa37Y<$C}v__LgOw&;Ec zqWv)aRIgcDM|UxwL5i4`UVD=fJ%LG-#_{+K*&8F?IX~l5zHpAqV#CQQXUoJs3M!kX z4(As1s*1FDx{4!~8p%IW9Rzw5$l45JOP!|Hmcc8f;a#7Sn#ou=Blkcw%c^5gCB|m6o=5 zt27~8AtlO)J&H1hRuH|hX|;-&md$vvsgJA_uY7ta`!>8wIv=blT9pUeiIRKo_HlN1 zM+si1zXH!#_pG<9kV14PLM44sa~xFzQx{fzNcRva^BAUtsUqX?$y|K;Jcr%$h&!pL zB5DL)gbL9Q0|8zwb?w0xlBfYPz(+=NB5tFR4C+@{txCF|k4gv#%8Z0H1Ko;{z@LZS z0MowP6Rq$#6_s$$6Ds=|=S_Lm^*MbC%X3ixu!y7E+={3dj+eJ4Pj{Oh15O8us6-qN7BFwrE)(@treVtR;P zu${7ucB8UWPRuN zMIHMQo8eE%&g>V|p#+Sj#j+#`@@h_kP4%;0Xe!0{o=3@e?R~|GaA9z%e_)}mm{!ei z@8CYnBfs-k3ml^QIrV6HMBKdBAP)b(dHE^XkCd7)yR6 zr?&S}xChT}TuL+?NlOzgQVTKb!e z9u6^hS%S3iA*=6PHG<4R?K*Hm*iZ2b!4(Zh+t-cz7dV)qD`Vl-%))K%^s6Hj>LvOb zbrT0vE02D7SK~&PUm5U@;+X`M5s71Y)w6kH_YK+^!UAZ!rkm#((w>`AIYWa+XQW#6 zD*j6gP(r=)ag|e+I^ZMx$K|M48tIvGl6^iuL8+JEXn6xZUd1{7m#=P@Pmf6OLgK>* z8uCS+x4OE=ywT}yH^5Q$?_^J-tHOi@3olQ80pA-jUUhY6B^r!U#5OOyMo$S~vvV4C9xoA6i!Uuad*1`;k`5B*xYzx)kC{rLS^wQGh~$GA zllVEf_Q*mhA?D)+h>9L`5aU3_;+$^H7(R`TPMk+O=lCFPlU@4u14>DtofISO6$Sg` z7zAl8Vvps++ol?lZIDg-9sTcp!R1!8WGmOMCZaGR4_J?*-fUHvS$GrqW3XBYVe+N_ zc?->eqnJV@FifvE0erOIf)c`soTxOR# z=Jw)U-i4nh8oDgn@|JtL%`-e0Djy5>EKl@{=`6zQY4IPwS1Xf{tqFlb6pxyKPcHfM z3@j_!7jxESJ+JFOcO6456b=F7pM`w`_r_8P@7R^LgpAH+q;emwH*@fg%#)N85bfiu zRMQ<0bJ(Cm$g(G~&?Y$#n-ZR?M5_UrKm;aQlhX$Qzl(p zJ@IdSI0wrjrjs5S%Vfb~-JLs2ghso{p7V7FF16a0vg8VVy--JzkpLyFszQ%$nRJp!zFRDE8A3FTW#MoZ!adp~1i-FfVVgJTXvH=+wKO;=_n*%8_ea)fdc<)DOJn8)3;ITO`BlC`@U zui;4Ly56x{{`&?uK~SpY^L;@DcMgHcp6e;#S|%v<&~-cI)7Roq=UvWNcnb9afXV8fpZN}bh(sc{6GAG-_-zAuwh$)9Rp2t#lcL{SZ#IIBPt&L{o z@?@w-GbQKi;gweu5Z0azUf*Dqv@dW!Dc0mar4EAhx8n)r)PeS39m$BcZ7znMhZf)oT#%$ zK+EAe{nkG~O2GsC6 zpAprWWY2ii;!uIzo0;#(dM)ig)qrF*n<93i?I!l&)f&)n$+6o#j|h+3`pp5tid8+t zt2kp%;fChPQ5Q)^*V`(CDmaU25iIO?3hHBu>JLj-^nj|BrcoL_veC!)ne;Vm1HtHu zVJMUW?(s7-mr?F3L~lYk4ilo;)LzpMI2nH)HnoGoHn{R^eOZoV&n+z_9UCwSQ?R;p zREMB5$Da+B`xjv59ogX|V&^tln0@QswZB0EbP{bi zax@+a{Pg}aPkkiM{s+4Wo4D5I@Dn4$yQYm+65zJh=s11D3Pa0aaHcKqL@9>X1YNNg_CM|V2raS2Som0 z8CZ4W?Z^#&{yh&;&RRRZ5kSmre@ar3ZcpdDeksrJ5C21LN_QEAn){_<-+y^KL^wSR zvQwsYx=)br%f5cgs>Fpf`^OPwbXMGRv0pTFS8_Jf5eki3;O;qoFS}+Hw|;fhIED?> z@B-dpM#MMX)@FT&<}LQb-a|K#p=t1$PiL`L{h*)N$DLxRdDXL1Qfu9*Yk_WK@upAD_A5xE;<*?S7^cce&RI`^{|ZtrAO( zOkZ|Ztzqp@=)I;qD1JTyz`u{|POWrY)*h5=#44Fg)8ajsvi`f@ zO{7MwwGJ^moe7RB%0RX62hz+voRmvHNx~w?55nn@uc?$qA&)UU_UwN1(@Q$EFX}Kx z4ka=lPK#FHyK?lu97xgeF4`LQb7$Tr?Rs|N`})&);t6xjZz?~)FefR z(WAU;EU5WkvW4=dBr;g@Q2HaMmi@__~P~Z ztN0z8{7m@X2`IebVy=^Ko@gZ(wR8h}g(RTl_lkuQVw42SnsE0x$wUNyCgx9rGzQEX zDYl{+c!)I=vo}hdDx=EsU0Ho{WK;j33jDxgFSzKJlq4D9(!11az<}_wYXamA4@L&; z?IS%GLy&#+V1G3N2aCT4tcXnOg?UiN^yt!V!I!y~s zFD!0QFJ=zyWHhFM?2S}{rh^e>2irn^d0Z~QoXXN&-*wPprVP{k)%9_`oN7t`mC$1j zmU+HrJKFx1b0X@U%5QpA2-o4D@Y?lMqXW8R=ftk7TCl~fRc-C%D!aE%^solbA~8LC zbR~<90pUhi>G#tbTOyuFSXH)sk&ch6S>Y>^y0b4@yM+uqWE0Lp@>I0c5AA>8 z%_M=qTXd&dTJRg$w-iSQK9@KWpsgklN&dzeGu$NfVN_0tVQG&4WYv`}PhzON7GH0R zMAG+0#xyxt-J7VdJ-ub)9~gJ03wXV0KL7bQ{pBC#M}MN^4a@%t1;Y);hUQ~6Kr7Rr z$jMJc*ix$aC>&wOy|3|cXcnsDN}Qv8>h|7CP~>o9nZViSe6m5AHvkQ@vi~g$5k)0~ zi4OsXv|Q!1YwlrvaNF3G6guykcUQX~vwXXOaLT3&M4BXwL|jZ}`WN+zpX`5zo+*to zskVjICYe~!#dt3O_$|tv0QhVTF0TSrv3mUBr!B~Yfu-6zHHBF;U^rp&Jf<&*HDKg@ zjU}tYLsNgU=PL<|mcll=%QyX{A2V0@Id*WB8noDG6a;!nj5`*wJ1NUc^|Z9E1p5!= zM=u#OA7l?NLPC`BiD@~&Z$n3mq@u*!Nap0j-@hT9fx)7WwY?lsX1v7Lx}asY$7H0~ zVbC8S*x(t2I1N}|hsM)?syA>jP@A;HVWJT#(#+y@UaLV18 z+muZ-Ap$^&%t~Y=4{_NQm=r>m5TI!&61nX52`Hnb@N@W}P^fqE;>2Vx8O2?xbU7eOb5>#Tbm6mN* z*>YBYbm0F>JFYxy^@G`vT-GOwLq_TI!XH@8B~oM6p%-xz6B}AoN@yt*M5uH`Q&L>*vb<|1yqm+< zl%p}K8PkPFbMm9B@tBDNW{L6S^{nqS(2)U|)%;g+g#@F=48k2PBr@adw6G%6kMuUV z{(trs=x=;-T@EY`#Z2CJp_=ft?7;`dro9eLjo+(H|DO4}t|Nw!Z}<_d#MR+3fbOjg zxuK6;Y4ot!2W!xuNf;~~s?zzd53pZkGWz=;|GuD6&U6^1%=huGOt0lgZmt)$y>}#Xw z+u5L*1X}*b?KQuCPNsG{emVhE1a}!W5*8bDh>nZia~m#_C=ulCI3MYs-TQ0;(7%87 z$jMqWuv5X!v=MJDT;A69F3`NssA5f0c9RJT&^7jS0bbn8| ze=g8O`@8FDG=C^|AK*b&8kitMjBLfJahXpNkQ%-a34J5BysuPMKB6y$C+ zB}*I@@`TTQf?243cs2BHwulRx3e?E(yAakN!uxzpj9$aEk0KOZa@aG2Isb(Hqs@P^ z6E2C(#5wCGf8h2UHJ)=*Nc^Z-;4Rt3uw=CR=Os35Tz>t?G_r_kG_KuxrhKQ!*xB!# zaZ~qhpmaN-zOQ#a^?BB^9tVWWJ9Vy}F#cP$dx4w3C4vm_#R82wde( z+_Oo~REK>V3fmR|RbHbbSQiYv>yA0e)QLj!gGmREmK-?&>GyQf-Mo+@b{fG^ud&yX ziZ@P4ur!J#_8)N@k*vi#RC>%8$9Y8*C8&(0MKe+!zF`jhd)A^@-Mv}4(BU~y3n`E( z7{~--))sl?{bQzv(Md2FL$%gNLyOAw$%gz^eAg>;qj{*_TX*ig$CuU)b_y#n!ltAmB4^vqdUbvz(a5H)r-?~a!A@7+!_lX|p8hm}`p;s%~Cx@x{|$@rQr zTqUx4Ab0&o6QPjb#ByAh@Q;ruqj8KW^=5Dw37BdlZsNyyDZba8&`NN>7rK}35vHA3 zj9B0Noc%@E{ap)dy>A&KbntfM+kTohYi);tmdCsEhkHT;_WIp5T>U+!vPgtVhtZsL z!cydB1#cFuMNP+X)a)~7!j9t_{;DoxQxl`U*f8u|npr(JL6WJe+79DI5|7V~=9V(R zw0HDZqlDUS1iomKBX=_!nH{X=*8yuXXslF(ZuI((7A6Cff^x(Q`lp-nmZFQs`(lJk z8rItHFnqL`pRV=3(6Pjh_?S&Hzz1Ihwy}-R%?s&RdUjNGWSdXE3zziM@t(!0SHRU4 zeSN?!_obb>{}J6kI6fDA+R;gSym(f3>>eJ#13tw8-mx}p4gWn~X*5w$k!AcJTN|bMJ7tn1YIz(vBJz^r|;2)XT-$`p1Ml_D|ozjTvmaOmPECksjk+sxUZw zg6ZR$U9yZ%!M^2&KfL*G;G`fimw^rN|5c*BS^uvR4Mu73jH#!#h3{$$hOv$i=%A}Hg!jH05tPgqR>h+&f0kUyE(xJ5RSS0pw5%*&5oNY{cWOQx z^G1U2z5v1ll;gXUd&pEF*lmJ)peWwv-{Ap3N%WLuWc{yIrbwo`12CuhayQJWPB0a5 zzmnspFfXE{MT7u#x3MPQAn;+{SR!^u#2Bo!9k5l|)F6F_M#Pxi)PSZX z15#?Q*JN~Jaqi6Ugfwdvt-Vua>W)yqAvzmUKY?Tz#Fp#e>rB!EH632~j_>_f7 z_P*6hyfXYtT`_W0fQ==ByQ&oHAA7Ej33Yc}&{NQVs$rb!MvszFOJ~W|jRXN@%up`_ zNAHcC34Z_qY zbX2i(^^!aK0`#&^^t2>5_pp=sBk_YUs)~`AmpY4}+{A8pY!gsN^vHX3qi#uLPO>#C zj!4Qr zraffu${UE|mo7OTWZr%g0Y-+`p!Ac-%8xm`70(h|M+Be(nDv9@P!W+9gNhsZarW3k z6%eKH2~eXpQfB%i%RlLh2U07qOOf|@dayeFs6Qjn>d|OqliP-W%bn*T2@c!2X1+Wu z5m=lVkP+V)d1-Wp3|#$me)K}&ZA$G+-{KB3q@_P68f3`~hD|{QMdjfmE3hLy^jTHF4Mu7|BH^`;3pEJr(l@q=%$VJ~ z8n!djFSMu;i)d(F+uP0cz>5CoA1SFdgH1`A`DI>rFJ6P}$_aQR0r?;D^lACEPS*?f zP~xB2@JK<7cP!Nk)@ zZ5^+%waXdIJ+4{xEFLaNxfwn8biPRSuBYLZ;ZlR0Z5NG>os35KjaCMiE52GRD%8!l zsXIrnfyYM)N!z`|@dV^U+Z4_x<-$jW4n)d)eS4kzea)jCc3D0z#n&wOD)rb0^T}Xj z+BVi!Z=|ogj7t>0_Mb+RC4G-;CROPl;$e$fYDVPF&si zShU1P^0G|Uixk9O9qZLEEYF}U_UF*vdOgBiQiJ3(b)->?C6?K!#xHU*65LWvOPI{E z4uUk3kCS|)C7#XLEPg7)k34A#pc*f*qX;-3ZNfRH!1G&6*7?9PEmyV#wc*0kSI(oW zcj~jPx6K73oX}(j(2SR@YOiDm`nbp|a+_=tx5S0Bjj-6)2g?YBSDj)+O-wGFk8)pm zCyHOC=~7>006z;M%DACV-vQ0ZYuCIa0tlG((>Caa@w9Vk z%3H9u+w5mK?gvZAb#CA(TI9#Lg-l_SevVWWPFa}Pn@uyCjCtgayr_~yOv+i6KaR=h z*hGC~t)|A~W}0x#&-V1z+0)c;mw+-_`KL#p+uLW)#vHju<37AlgI7`@rZ24Zv@>n1 z@+yavMoMp5sftls)Nkm}UM8Z=NCK2t10<=KAf-&J3uv>B*&iBn9=RRp(A#KX(owQH z7_7tuNkR2%j2DvO871rHG4sXytpR^Vw(zf50Oi_LG#sU$wVc}~p5HgztqDhGYMGfL zyrd>`(l^p=Pwv!;UQw^E$6p~RPh7Ev=iA!^&Y>RuW*X8|7lwridMp_$R;uN9#$tkJ z3ENLOqR{qpKJh3y?>lDqvxcD?g;l6#cX5oCkfflljd-3h4b80vjgL#dzZ`akLq!kH z@zt~<75QT}zfcT)CcH|4Vz90rVy|^%6{*Xrl-5<1gqjbbhij(h zYeu~pT28kGnD_=5Wm=Nniw`Mg+p70cjzqjvqba z1hQs$M;pt|xThj);#`}dL%%ff>>5w3K7Dshb$Igatq1p)-v%;}*k5`&BW_7DsqRNHB;A}B zj}-7awtTwzom*Q*B!2tt3^ei+vEJ65nw>WvR%zK{TmmVkyPtZE-{ zeNE&mobp9+2pO92F>K8FApZLtY5pAvw-?vwDih(u?T?f7!!V{T0-AUNtR>Xk_FBo8 znI@0#r5W9yUh;r>{?TDMrjF7MjJ;$X=z0<#E2p1)_}eu+TAOm5LSG%c>*b>A1X#hd zBsnGKNZA_MzI@I0a;SOVao>iLynT98Ky&R|2-sOC;dMD-N%}bjbH0ZOSJ|_&rE_l1 z=g=HQXJ|Rq^i2dEnh!03`rSP2&AVd^%VcgaF{esBkC`=K?ReaDb;0yL&6&t6c$HWC zYJ)!exxdP`Iq&@Pb~%|o8o!;Gv9_!bNCoqlS2Wh7a_m=fAFm~Ux_Z`QxM)>XX^LRQ zu-f_{)16p}=FX$6=90MZ8xI;@PGsNQ>{BxFt8IjgL1+$Q|JA|7S)pnZ=XOYm{J+c1 z`5=1*!CU6sq6IbLI`Xld;8@n%Vfv;=eT))s)8ACNhO5fiMm*B*k)(fxfVNP$c7(1{ zIj%gRW5Ho1TL3d=W>QyN`tkr5HW$jp#9SK?r2+sTLBL~&-{))Zch5-%Zg*#fStKO( znKF{$IIT$I<$acEkE9C#a702GQZ5~@^GtubRfu}m)=^j-XKIwoy## zLMr^-tHHY~52s+FrUj=4C4IXNhsQSaOH4~tCA3@CfU`P8`ZjZQr~Ug8*lM5u{JysE zI+Ks{chIrNZXa%IT8kD>Hq|($XPC)W1807`;}33PwqQ^s1R(|zkjfLQX=TTV(*OMO z-4))ej^M#zo|vt!(t7h=>`}fT0udtdHEF`O(gib*+ZKhxKce`w=hg0MLT?@~E-}iQ zqPp;X-pLAEI9Rfi>OXvy?p;$)VOXmv{lPXlez>c;s5jPMlmdA>&>jmUH|U{*syJv?XO7A^JLGO70*u88g`dnquOFDpl8{W8tTH|$_xk&Yp|N8T8duIm>{^erkli+W zAEdI@9y1_{WF=pg7HHtjH^1GTHn40WY<~bo4w@03UC$u)hJ!_zR~HgGKF`jz-ZM)! zKXD?#tQ`l8C3_+g=f_HrxN&g5Qg=#zO3BW_GEW&fYlK)1$#un}-KDJ7X?@Nb0%RXdPZX}q_c+zP3&vf z_ovm)m)J%Zp->Y4=SP*=eRPxgh+{n$>o)C*HWFXgU+5tKlo*8(D)*D#s zstI>`eQ(_MwHG^{>CZFMK1AapdHgb9Niu|0Q(PGCAnpw(QaXpbQ|6uz@01`BlLgx= zb94oO->@DRzqz!UE5?@g^^E^2c4T&WT6k;J7X$*nT~k>2h2>#<>hh(1CH+(QJEw55 zw-$CWE8JvlVYh1;`P~S;xNkGHdo7q1RZ8yhFD#X3+Y^oPY9H4uc`J`XLu6kBb$z4w zXt?1F8DC9NqPHP!LHTM%X1VH%;oG8lvt~2lR82nsCml#rg-fm67 z`aoFe=D=*$KJg{AcS4K+fgV_}W--Y}9%y6p%BJ(k9c0!5GGNwXp~Cik5#wOmwtk2Z zDQIn{#$ni8^`ztR>@_NK^x_2tZB`coWC{tAM3^Fxczb$-EPiS{ZyVKc*y5ONlQ$fT ztd6|sIz@0RopeK6CWyK=I;rO3o`Hp{9YxfxTke?^z9M@^6lCZpv@*QryV{p5eC%La z!C{RR=lh<^8B|d8!t(d(3zbN4dEVXY43oosNM8AbS8~CA^%@&s!L8 z!yJ6ttUW%V#eJTQL4M}h&{wl{K#->Uig1rzm?C0{K}7gmp$97tI!!F;F|)bnS?bZW z7k_5XLyXQl=!fcDFJY)^nPTLiQ6#!dfXdJj?249gUMSf;l?;(ZskMuzxq*e(HUwzC zV)+!akSF{9qjVAlyr7Ed3yShj?PJFMqTwbotZq+sr_k_}eYUB|)o(m4J81jH)DLzF zqnPhRc#bAv!Kh*uXgVJofBzZOS_DB?H)ewu=)dO>wgP=nrqX~DM&Emj%t_E4-qsC$ ztEQM0I(OB?d+022QG9*D zAIS{o7-#)>lLs^XhVNEn1jsT2KiIf93Cn8ZZOLzxATqhe(bs-l^fc)b>%ibd0N&T(lrKzGekq1}hMbOy zb~_0838&6fD3%8^%ZM98@G)uI|?>f73(W^K`X5i}jF@~V1-({1gBHV}N@zriN2ellzBAv-e3oVg6 zRy{F6`K_pKVxCqKJUWbDZ=J36sgAz5irkfm2vd2#slD5Hn(Oc9Ym<#k`|v?kKt07R zRQ|6rN#7Cv`R&x@SX>#Um_51Tin5!x#2wVf(@Ts8^x+~FeV=w3H&!h@po zU3@t_?~P8*4Kuap$19{=;IcpH9?2?oa8QEwEi+|qqW_Sbd$ z#uvkxYx(dQM5TkCXW4kbfj;a|ICDFQs~kF`;ON)pU49`pNMc^QJc-Dhdue# zM+Z&}8CN5NGjt8C3S09l%wY1DxTZ_*`adaGY|#03qr*SKF%-Qm(mFl+IcYc$i;9T+ zLXn17^t_0kk_J%NK#fI^rxQ`*;xYsPn87jPZ zz|}f0+n8kYa2sQ}Wgz?@7p&PrX`f!nufFINvRS3bn*J0Le=_`LiKi?66waB#a7@U+ zQU3np&ZLahCZ%}O)55rTVjmu*qCGT>>SX3wnODopu}t_uD=5lgWFo(*gOBv zIVD8WdYa6el9XF#%!U=eyty9m^q*)FUNy9Lf<$4_-lgBF<21fi+oQBh+o5LX-tJ#h zP+nJ^vg)GJecQb1sKy@8pG(K#H2Z+QF5O!t=g|~Z?WN@M`-NQQc1wImj0cj8+H6d3 z>&*aABSX;-Z*2mV$ukHY^Hrz(Aql2H-~Tz61ajLvO`x0b^XobH5!>k3li`0FCrs$Lecer%E}bhI z<^B?oev@E?e+|Wu>4y_Vb-@4Se;EC6;KBS^7wSe3)y&vFY<)(oLuZ z(Q^LZO*bKz`#+_d?9u!`NH;n0yBZT#Ec_k)>-adGq?;p%#Pn+fC)ZUvdhF{D^^o~j zAM#k@59HD4Y;wwqeQ9zy78*id9=eg-C$O4kaNY}FKRh+!n0vnCA~r8L_if7{avm4i z$?!Vf$#8DBxTVy|tD_u`06=V)S?-&H_}2ti46bnaBxK~nChxC;}|@-0`_APboV&zL6z=csyY`5q6vq36ZGhV>wbX( zY_gB}rL#Z z5QV;3p9uk3A@j6cc?SZQ$$FhFe-#N%&$OHgmF(*m(Cc%Jg({ou2`|AL?vLIRzY?4y z)h_3xZ)hudHj;6-fH)M6Q@I@nQX11?HFu|d4OF&4s3GT(H^3^rhKN0Qg=|~2MslW$ zTV;L^!Z9#f%{}RekgaQHk1mQ%Er74CnMafqQW>Q8X{^TXr;O}xU6~b90M2Xv-wQpi zOP3e+ztdy#hNY@Pe5APi#NhACXx=eaupY{0RZ`_Y46C;33*GtE0(9~-LZM6GwaewDu4F6E?F)j&#X^c+@0QTSrChDIy&L@7d*wElyas~k>iZ^K1=sS ze-?*kB7e;Hpl01^nLO-{;U2Zgx4mf}C>vj0XEYIcB%8_6$o2JRTuFYgMp~u|Fsado z8Z^WGx_bSs%Ki=32b3vKDBTE1Qr?F2tzkoDBWX)~mpVcb;EdKWN;s}UBqh`MdBg8; zXnk#4RdL}k?SY@z?|CQ5btLM;V3a(pJQThL*Q-WeI2@w>N(~wMka)9Bh`RTDwQ~Lb z!nEZP5oJ8!120psD0=1<2P)7`xd~iV_idxJj_K=?yMM?cW1l<7O#xGD0~%{7v9RvqdT-OoPqkR-HhWfj(fefaw^l*Xkj_@13p&S1InX<` zF@S^tv(!lWN}YyqUSO(o+;J>Z6-y2UJ)1Xlje(oRcES}6CY(C?l(k5ZPFp~Q511M0 zJ}6_X@;9&NJ1gr?RLOfP07EyVt<{T8`zth^SsJ10B(@}`dd`FSKYzXEKb!ZYNkZc& zFBUiCgO*Sb3fr%*z2i3vsmVlxdqS>>`n2G1su@95419=H&TkYSzMVLfl%8&NKdI&t z;JX?bicv>*;q$Nx7#v9iXcA&{MPdqq{B4wCRh0Zu8|hN78Eyfznn~VMI*unkLE8D4 zaId^{a+Pp4Tk2L66h-9x6|0FTtVVs8B8W_Jl-w!5nVrvR1OOyOm`c5 z(P)<1guMd`WVrmY(b%s5WKGvNgeWLlhhmt*2S6P=x*n`l^O41bC*e;_mCq@OmiXrH zi#vjmZBYUa1!ALHfS86Wr5Xzaza7Lf%pc9Ts#7%5W}?T(kiE(#7$&m15KChndxw#I z#Ub{mvn}aWx|~&L2aj((s)M^!SJn+(dzZ#vIG!ke6E|e1IpcNRuck!KC&NH_xjtk} zGqE<*-+qlh(-hTQxBoJ9gQVXbQXD~er#d3Y_w@)C0Q&)n?KaDUQCgYH zlB%pI?sH~pkM8|P;L_ahVx&%g%53`Bz^NzHH=y@MT0)jpT9X{7eLZgTcN9gCutH{2 zHr9MuKKhZ*<|o_ZvzbS%0Ha*PAw#1{?9j`A0w4KRFOoAo@TYDpbNj&IiWAE!<0+uD z6$6|4xIGcQ53lK#`Z!%}|U@ z_`H#a$sq_`QlTEx=LGA=NFI18X8Vkew)Xp2HJy+(UFq(oTVBK13Qu3wshSOGo{H9w z&mkMjEy%Hn-2z$W%)K|9VNORUhxd@AaWE~O@^7@>BH6Iu-j4+&&JsyHw_SeMu)4y| zu@{6<&pg#L=Y#pXTofr!uP~D^IK9BWYn>)51ecXvfh3R{Hi-;&f{w^wh%G^`c4vwJ zBu5-s;6sXhNg_}Lf40@=Wa_0Qcb}<_1&|nntdO*IR{h2{bh!TMNY60SNWywaYrJ&W6>^We;=j@)_XizI5^|a5{VJ!M1q9T_uOV zT~$+KM*cx$IEsR-dL=$g62>50ot1!T$u9+UCKmPhzz={sZbdE$FgC@XfB1SblZve3 z38+iJ=urEJNr{D$h@R=q(we0C!&7VO+S5DxF4U%)A}vw4-LqW8KmX%r-B8GrUn`Up+vS_7)cv7pFaw> z-_j<8GAJ7#t3cT5O?9&?4Ac(V^UA*Mhn4Ij-;Y6mJ3L9x;K!Tv%)TJjroDTK*V-&K zS^CiC%kLf#vJnr9X|c{$GJ$RYLdVgbW&n~2K>dYa*iJy zAl1+c(RQc}sImi5o5+iLb&(n=vqC>&8L1al`F+bN$(=FDAVkI{VnYHFDr%@XMYyRS zWhME@S#qfCJ{KFiQZc79mxAEJS$syl7qZ#27SF?qLqHbptD?u8MiS5M5|i%o=Cukd zRddT^NBJ64I`x+2rc|xWOo79Ym}pR42w03c$$NVIR56g|Oa)rg3kl^7tK$NQ!V6ap zc=Z{cC>kAFNoRhK>Up`|JqJ3RHt=m3HQ))Qs4Sh3FmEXLu4%g|w%?c3MfDW^ht0L2akqm;8bxuD!Y3{O} z9N2`_^QiKvDYD`R%1Dk&Cy(5~JAku@09=Ww56x?v7oM@_4D#&;CA+HZ_uSjMa?Fcr zO_vQe)M}^jUadKwhIOV}dOoOd;T~A5o8~a;$t0i)RY<;dmTodt#Tu?xj&lUB5ux7W zzd$P8!AR`=+U{RMLBL-3qEZbJ|GaRbE$ACVk7=`=@|ydR9P=KlPOU~Y>yY$hvqFyh z_YW#yG@Tiym(>)pWe z$O9W&V(i#(!+K%y0-p^9!nJku;LGD4@&OH)A;s}+2_Yh69WOesU&J}+BQAyW{z?1F zH)`b}v8|tMiQm`v(a{);4ES-`4;FETdYjsHhZ)~>6aaU7%1tiBv%ScmONi3Lg?660 zGs|Lsn#uB~ne4#~aTl^*SQ=15F>Vsxe-T!q>|f3MI+S+a0>*F~&_wsfwEYWjN92MqubMs0)K@ zuKh2n3f~{9%F|&wlZ_t@(x#KK|1WsTBmbA5@g7RsKho(FU*~*NMsw1|eHTHHcAq|L z3Un`xcZp-wW?mrXW1#(R{OI%=$6=T0l)2T;IZl8QU7YMM-o)Tb~MVY{PbNnk7 zKr1y(Y!~z2fRz$;L|OmtepO@x5#;Bjbybou7+}S!XcO(KV;vOxZf3z2(m%YeT|FBe z&d$w*P!X+FQF5+_{|={`w{+H&l}Q~=6R96thphnLL=28$qicqUX`AkAdz9d$=CX>> zkuFsE47s5+$B1?SitSU#WZl?3Ckf{9vzSn@IuiM7D7lMO8pCozF+fy79SZ-9St;#A zYk1C!Dn_-?_vGe~A$yPq-|oa9l!von16*$?h0e@Nw{I2&9uG#V@eR>!NX}5(@a!!L zcCZcSxWSm<)tb$5smgJqxhhKWO9=%x=GfvwiBGxZ zfb`L-1cFQ#l++Ktlp8sQa}wFtE+6j;r}4SNuNbMwVjmlxnb62r3i+P z2^u{;`s>!vi0JBB#6>t=Xq{D9bCc1-ha9ZGDMBwcKt?>6L+#d0_Ny>eP?>XL%fhm6 zq}=?&ff}xYg%JJ`OB6lG=a?)Gn?S-Ax8sAy(0JDV%YM`ZxY2@?vWzn2VNl@^@r?!- zaf{5PMaE#Y_*Y&zq}P?ko9M9u?41cvWPluTT!lpyhX$v6U5+c>ervit*$ompbMAM2 zSb-^MF$35ZYWPHpS!}YtrpBKa0(lbwXv2K4#t`cjKhVyO$m|m8=q_$ThJ%B&I)8JJ zx7@Rzu)^!HBeG85C9Vd9!cOr#MJK`Cdi?8ivOlbfbFQSb_kSVxK4J=v2d2=3DV)Ew zgiHYZn>xWl4Ps>LSaUdlmcRviy?b$9}nYYFsd^FV0) z+aP58GQ}1%5zL1`&>DHL_SjGu9T}i95w8ue=CAklg#dwSH-Tz8nDx!x`hmx%*blUJ zu?285`pVv?5{u1Yz4+Q8K<$t`U*8opdOsxx!kinuaai4IM0O4|H$vs%O$h@FxG>4* z4Y`W<-;CvyN!LtBFSb@C9FM}zPd+gKYNp)iM)jP=>tH8SX&X8(pxSZ z5_GuaZt9{BgLC*1>y0gE9GrPq5Br$XSKo7u9$jB&4MdIe2(3;BZFk(rANPw4&y~w0|ds;&@N|+`zlw`aa{5KHpXVAm0DXTM^CvX96mZ zlvX*!O|;er7;pv!iXyMBMy*LAPe(I|JRi?UD2N5MGs6HYHvLC1wSt>)&^`>}CRNy` zR@|lXD8(%1e7SLaN>|@%r`#Fin=J@w2YGqJDb&mSy_|d>A6yZ_`jZwt3VHU_&tb!>gkJqp=uQq*J`~#nx2BGK7aDCA7aT5xA{3qANq7( z?TW;9!)#K3p`;6*g-q_2?72T9yRDCZT~lR9b<<{kHg+z{oG&bp){nMpQO$$e$}Emt zR|$JeLV9=K0cf&gE~Z^m*Amw9B}ec!_T)c{Hu1K4qjjLcqziX~E=|>!ciVsSRU#yp zj{b~u)AKw?Q5rL>9oPfE6v98NM!?}=V#DMppL9D?UPmF_jK&$2rDuYPE)YcoWcZ8` zlHU#1enOTGBm3#2ujMYNq8;V>D*sM4 z52}FlnLx6f8fsN+Fqd@`Od!XZ7!;Y@K=qNV0b1m`6m*kBNvWLcGzl1Ah4Pg!;ks6$ z)_~!|lg>`&8XM+k8|BHltoJHG=;9DEE^x=j(a!WAz6yLo2ZONcbe0re&;}fGWDAA? zm4hfi;Oq7SW=b3V0eZ(H&zKMUg}tqEdtQF@nJdUw6@<^(5M4MZoY$i7=l~@$nj(Wt z*I~+ueO9i`6HnKGT-Y|u(pvv(y0Z7CA<*9!FfIr5ze^?;HFnyp8k`p_?%~Ype;HeK z42Y&r&A55b+&hvSW-bkfuYtp>Wf>xxOMsx=X+Q?fXanWC$sqO%#;nn6&sCmB{koHp z$M&uOu75sF-VSg!t2y~BWYjAb#wW_T&^Tmj$m&s8Qze3~i$K8KEzgVPCV$Flq~I4s zm<#$|nfmZ$dGn`TET=2jlbx(K3M|u9?ik0Ia|(c$aR3+)(mN7`C3i=n+IsIy$I{;+}V@o5=p#MHHdo^nlA`G zCsE7aqBW2IxNv>YjP2S2F&<(em(^V47gGOGb=v{o`pI<9w4UA1U)X2*9Rpmh;WHoB z6Al{PrKKG{@t?(1T~$>vOqkBRbwJrIIuSO*Jxi_H&f9PmV^%zRSWjQN>#(sqIdwdO z;ZsVAfu?RpdHQfCOz`YisxBqJ`IT`q z$V{BP3%fwF5^L||I=ud@aHi~W7`2D%MX%v7i&Q8ug~-J&shta&$ToZlC6oenu%vA| z@{HPH(de-{FuckL5nIdK*uKFC8ic^#0X8gU`Z$9qZ{jdqc7JoUzi?urf3|*8MNa;S z>7WrCZWOTfJ+ddkHXHa0y@MV1%4TjeIr=>`Jl}9zLwJtEDkPjhS(pfMTL2m!ISZ6- z=0PFXV>$>0ktzVd-!FG>M6!YAomc7*b&*kl4>8+cq_bvRU^{y(-8%de9Su}z-fS9% z;(|3|(405}eJxNn+H(s*Qe0kp&S2hXlmOcA_maXnU>z^ay6H$=k!KJ300#|2yM4$q ztUfa7Mv?P?MD?Kj`XjdF{0FhH3g~PwOFeAT=Lcy6DdKzHatQ;Tq|pVd>=w-Bzwnb*a`wS}O&-vOxBijTJKeiK|Dj7-VAb)2 z!V-JFWoc^W3X0rrPlv%xGleLCU3j?uLx#A4#R|n=>Dxx6#l^0cIjzWLSTi=W1u6zF zYRFUI0KYQ&%N+5qxRlwoaDNeGJ_nP%zBaVy*Pdf4ZyTdO(0ViC}hTh<7PTq?e(#@}*)~EB zs@K}F`Fnv&*=+2Z*P}O~auMa`8~kO)BbN(vv^hE%|B9vH=;Y!vMCitsi)%zl#yvT! zB~^t1Eg^@vBp9KPVSHV0f>ie3P3Fl+r|?PvA5?I+HtVFMwfkZ%^oQ4*X-Bur23v zEZaT8>_GqO6QZW{3_7(NKkoMHu6@W7E0zQ=zq?2VX?%%)X`o36ep9o%;lD+ff=o`z zec->OTO&Tg-3?w9hFY0*q;j5)^V?n~jpgop)!%>MDtwk)c(u7B2ZP{PiL$_uN5CM; z;Ne%q7&e5Fr=5G@TV=S`w&^owxzcfV0rsCcN@s^xw&^wkk=`RqgpMmkYW9ZPP_AYy=v6OjR!@AT!$}mZiy#L z+fX)4SPhgzH>{HTO!cvoXyxw!U1n8o-5VMt5$qXra+8(#W$$=d{p!1|gkk>~2 zYdC@oW1sFI<&R$}t%1eOY>GsuRgWf6a3AuPHx?z6!#?TiDl$cf{9@6ASDo_oc-FC; zjoj!8Zi_*Zu(($BJsbWIV&e|HBsJUO7kwDC@VF41eE-Z-vMn0>OGUc$JMMD}?iUuT z`LFgMgY<}Z+{Zb<7oYXNJJ~mMBy>NBguMYw?>tujTTmvJ0elSeam_F3|1U+kxqh?)TGwMevbsCt>T5o(Fx393$DiANVS zi*_Xi0e*>zavZ@z17j(c#PT!*{K-JP>#SJbab{U)!$?~-sFNOYbU$y&uB--Sa=7}o zyu1PLPkiJ0%sQGs{K6S+cQ{O}oBu>b)hX;-LUC=9{IA&di9N%A^ zEG5v%|NexuRImqX{Tb!n?tDhK(&-xpFnE?Pt9Jg<`_b)pEJ)%d!NsTB^g`GBf0pU0) zpQ&7*BchT}QQhN6%+m~O#LIr=R&wc1R=zCr`jAwGSJ4ZpGl6XCLsE!$FSBz35^1xS zEGzE4fk$Xbvv)oFQD=R?Vh_KxoD(GIOd@EszYJD2+>cQIm`&HR2-WkQy=M%x2hB(Z zI;6ty9MT=>{;`t465aMg=azEzcnGAc#(_;fX=ToE)oQ=3UsvgvKq@h9^YW@|Y4{HG zx{%@4$NNO~bXdlY;Yt(o!_&oHB+j+s@W%UBV#LuIxB4UHc6JD5fy+$cp70q4FUx_r zzYclgxL!SzF|`b(eQR6Wz!sA~bJO{De}8{Sh+JHOQ=7&G$urLqpL|x#lKsf;Y6_eU zJKY|XM~U5ZJ#F{S+8Gf94#SqNZG1Zr>N)4TIo&QGo9265OC#=XSlb5MAIBc3=w zh~-fQtS*5P)G;a9Y)>|HJ*-Oxb5WCFP#_2jM@o^>H;Dfxgi}vBrj3jENkd+h~&C2dwKYrG(urx-0%;W{C zEN6Au1lDSn-D|1nvcDMeaAKzSv#GYK$!Xe2r*mYu4BOO{*Qy|%N4)Z-7XH+|UTo)3 z)x2?N;m_~EFfc&PK>p703(G<;#?h_)*ZGHV_K;}v^O?ZfOu_HL;Iv|;lL|gi_Bczf zl3+-uv!+MPLQS-C$E9vN`3-L*RjRDB{r>OM`)5P@G;wGcz++(0%vr-)A+^N7QFx{> zrnB8_&7tXbiG@W3{LcQl@2-*$f3=9t)0HR~rv1i~pbi3rn>4_**|22*e5r+H{ZvSz zG4xiA)U=#nM@Ik$L(5{S-zszvteHlk`M_QW%kKGkP&z-W$qpK4BJh>q-2ZBNyx+`m zDcDFLx5q|~P~!G+N`m?5kN%9t&;9P`h+;i|?CWaVQfTbo-U;p&8Qm;)pOQqI}mOf(c4C_l{QZQiH z_oHqywfuuNzZ=p48;5DU@tQM4P^QvjLMk?T7?s8z#zsL*d^J&9IXF+$wXaWv^N$BM zszVc9nu0>X3_005GpAOGq`xhHqh}{9?d`I8wzro}CYi3$fO%|R2Rh9(cx5O1t$_5k zO4wWw`83@I=m`M6jjD57LMFb!bjZ^&_~BlhV@P_uuq3qa24~RrrJ;294WTPVf+DV{ zEmduAYRSzDk>pf}tU=(l>vWxmycA*?c`V8s+4rxv6^pn4i1{>_?y^8+TWMdJ zR#8xHC`tFui4)dbUVYdZCusaD1Jz*T=Lj>)d?RFFvlXttwHFn`?xUB*Ilsl0i{4&* zd|rWt0{P4bE%wC@=-c~ttUF|qoNzYLRmLa&1Fl#rpm!cAZ2djEsn1BbHiA7vKF$r^VQXTV^-;ociD{mIt{#ov5l$O zA#B96p%l6Hrh|gMY6;aw+U_}gu!S?BU#qOBY`G~Nr!wLB+n6H9Y7U~!5)UyE(P(_r zCs6?mwdeZ)N{h1)<2whPmg9+zgl2V@wMuvNJ08$kZ*p+U--U4+V{f8oZOn7*7TtjC z%vQ4cvj`rKKQ-iHMQ<8u#^9gz?`-z8=XULT$Y$Nm$wv<^FUgyJuKd<_QP_c()h0g`(Qkf( zJpqE+3&uU{?xVTQIeY&CK0aePH0gJIiU8CD<$7?6!UiL7PtHRBjYFDBft(uH?Uc*` zFPbpCmaj$HKbYc^nFks>HlGZ^-||mkc)}uPr zPfBM?y!m4U`M<>&Uk=R$iWtzhH54q;7hjPrh6|@J_nG(NYqrN*y0HQETL?t^Hg?$N zGSh!gtCk2Mk5m5EZ{ddjxNh0?g|#wv>(V|qaC5yUUocq^TesSrrfp5K56qkJr`B;U z^=al{f0AmM6#DUh>+`mmepe{2^0z+ViRLKqw}7GYkM?xCE*4Kn>9>)aJNF4R!q0`L z*P3*7b(T7|m9;;wJWt>;i;q{(#_Y%14O=;2hbyhlzL=(616A4!*JR4D&gIQ0e`xa; z5i`C_o2OzP$o;AJS`9;ki;f{;j#m3d5&3meVttHD`-y~o zk4P{v*5p7d4+Ki?EwZ+L>PG*A2X}Y+^Febt3$G1_*7=_#o zPL%@>$)_-U@BzPHv!WJMi+1k49lxAGr{QF0vaZtZ82(yowd?%K+{IjuW=4d&N?7gk zM*be)LV@KRGpImW7o&#l^~PLgFQpR=lj=JJ|2bAs{rb2a_VRr(IH=Q8FdYIH_*w%a)Q=kt2CB5lw zqZUql7;Yi%?p3(sWWtR_8F7`tyqT8djj5!R8qvr!vblW*>fHL~hC8sbz)g~EX*ySC)Pg&o>=Ix1 zlFO0G#h9Afk)g_jvBP-$PeL#5`L|Gg#<>yGbi5GTty-srM~*C)=Q-}WTz49w$wV#Y zux#p9-iA7_(bVYIK_C$Qy^X#KTn7v9g1K(7 z=WWDYcFN)RDj_h4xv_#U&jFu2v5%F=^x-dM@?!ZiEbRn`&G;w7=e8(Q0{J3 z4&D+);nz=5nd@L%meKkR2r#2P(%9%c)VSEt<{TFYL_vAiuebgx+Mm16sqA-4E zh{U;JMnv=+W-7Qh&%8kJXRrOr8|DCtFs1#CZ-l-knp+Rj-3!kP8#XK(`&G#j`BSpE zOs8?EnoJ6(RQpUhk*yhB28Bm!()$?c&g<=a1!DBb2=vw@t3K4cien0q8VNeW(%Yx@ z*ebK;%v8s~&EA@5ibXH6Z#FfbyejFVs zoha;AV8|C>kTy$b^mpY&1a)DoZ>H}jHV_cVHI&{<>%8fTAy~Ro0exHyv+Kg^k3$ql z4o}6=QC|fyy{?_|V8QJi^rlBuz6*^G@o%T26W$r9V!Qym2)&KG8cS++H&G6$VLKAT ze1PWH?LE!r?RH!Eu=-&$O6;cMdmfTe{m$=?4C)}CwEr4LhJcI0&9 z1wB-}%_PPj;7F)PQKI_OD(&p8IcZoq_N(7ZRz3IOkz`z?HOA#2spU&>vcf)O8UDcqV$9 z1@9PA8<> zA5#D+aSSb{hL-Q_!y}TP>{q6mY-8J#lTC2yiuyKlE#nGi&8G^@3{g<$Ymf^Dj(blB zVI_)^7Be{LS(u#GB-o_Pejmz(+(quZvh8Wu_b3Um-jb>3*zcT!zYr2~mQ~&6Kk94F zN!noz?7Y`#35pOSU|66h*=~j0Pm4=s&%}pst(N!ZdGM?H&6!UH*ohmQDSePj6i>qv z#OEV#U|7718c0;WOM0U)WPf7l_Uh69RSOTZ(TUPf+f#2Rav+$iiSO!zX~U1m`v-oq zn!T=4AHt5QWZ4UL<7R3`=@s9Gfa5IA&DksB$2K-JNSpPU(sde6%@+@Hq3lt|w)&$P zX()Yu#itjtixJi|YRAEBns7}C-=1Fa@q*my^oBjkv}e&2hsLYi-B+W(Xyd;N2#F4b zSuzl*xwR1EoQ~iwbe)C~F+2-|%O`sh!bOk^VFUXq)tN0VDWfDk#OLI$ETmuF;V}G_ zwk_~6%$4JklTJzgt*cWsTXr*Y=r=B^#wgu2JngU|FDHW8EGAeC0Dfo6kPplp>3LTP zq-gIh4YeGjmCJo^fhw*Yd!0ucx}vZk(&WI(CzR9LN>`^M#q`lRord%C#v#YN_Q?h4 zDfVoXx>#@7@G)b|c|P*E{`T^_aFHhV*GAvl-O)vjfWEH1b?Xm4tooieznS8LTXq?5 z)Wn9yqFmD43!K?9Z&QD~kFtU!3D`|{i2uCitGc~cD471P3&-}b-I+)S`}V6*Y7FsFeeWW85v+9m+NaL8M!g|n1yTlJFH zqaGZ%fQz6zve#{Cyy`11GVLYMr22ya`TwGDT9U&b&fb`ll^I-hULiUDO;FZ_%e8BJ z5;_JN^MZ)aHvV7(E|Tmo;Z;2oVU}K2p9Ql-Kh2rkG*NNNWH+>haKn++`}yklQD)U; zx09)=3G1}jS3M<=oa&Tlt9b>Ni@PX4eu_sdf$7OBD$k9;%fA;QOeTH@x6gK&Uzv{W zwcNxEn>MSa%lT{3o6fgTlT8E;HIIJ_99ys(2ZaByi7zFH1!5P!5-O?68tiK{s~4a@ z_Jvcu<;jI<1s_Bd7r6WyxeU$uN3!0Sd^Lc5FWX7uV~PwR?|-J7pU2h^0(dRt`;y5a znqLsXPOS9i%!VzVspT?2hVEEBp->63e~j5_Fo$P`%K)SF))(o$qqX`=RAd*I!y8Rm zn1M}hyuH-4xg0erWg6Bz(Shk=Sh0Hc=tj9uJ}!AJG|74p3UGp3NT{)Or@++bjQ>v@ z>n>|bDierMShfiaUp#3SlUV)%mgQQL3zK^h-+#SIRU8Uvyy!}tg?26!S)l7-S$LIA z8ftZ?jub-JWxS?Ad{`v9Em+wSZ{IWGMFyMQyflkRPTK}$xV>M3*2)<@Bk7vFZ8~*@ zet2|x-&gEc#o4#a^X-l#cgwL&z%RF%%*p1a7SiHzfD_>r(9^IsYA11qv2z~?ZSazF zvEh_l3g>tft@T1(h>8OfQU}Bi?`gQX_ABp(H87Q(X$t zI1){qR{ONU!uj|lv=@J})6OM7S$m=IcyLE9yY^R#2bsu{zU6${GA*ZCNfYQ(dLtvl zuLX1<)|moa49Sz$NXq)WR|Qei!&kNX%El}{K-$;hUIoe|R)zbqCmwtH8^wq|=w?k( zRDcJZ1YO00yr4`@g3ndxMyROWfP zZ2#a`lP+n6ui@}yAq0c$6HJr2N&>YndVNvC+Qw*%SLBP-Bz?5%ca|k-!gCZ86Lt?O zjz=*1wI5f^U(Ux5ldV0`O!Cb4y1_Xo6gY-Bdxf;utW{J@I40Qs{VYgShho}x?^asV z4srA^D^U*Dh!~y19BW;V)45x}gBj7j`j^=ysFPh921m4Ky%u-kZTcHJrnJPf_1Ze5 z@JDphDl2*n5omCW1Q>_)3mpTJ*E|$%iVa+w?k-K-45e<)b}XuZa6)N(s|m-$m=%2Y zBa^A0teO6^1wg3t$&T{9aJEaYLhx~$wJO>FKf|p=X51BBcs)I!U1_{kNcSkZkh&v& zDDR(AH0C)|t#u|9Qkbh|(rg+rvi+9F6fIri=uPI`1L1-#E|0R?XL}7K|EE*6Gq#>+ zm7W}WT?GwZ(rR8QzC}F?l(P`gnS%{F~obSPpf|=-D$Z;DLdrLl6A{ z{#Lv6Bc`s@iK>vUJ`mc{7dMWvS)8-(&=X-I=)aM5Bv`OyRDjD_H2Ug1vI8aiRH9eK zBZm+s)-4rGzUG$67rKQjSobBxg7V{`r4l$uAW9u)Iwy{zTZd}p z&1PyLRKX9I@wqx(TuW;N0mtq-crddZ>*TY{Fe@7VcR?RFPH}-*E3Fgb z=&11k8v@OxjY4j2F033R96vU!bw+3N-Zw&4- zfTgayF`D7L$rqL@Vazyjua6iuNUDww1Pf{{4iTv1l()@<>WgqXOeP4@UG+&%(Bu)Y zrND~y@>Yk%dE$$t$Aji1{|Qyck?L5iMEw`5)cjZfJB=>#*=9_ACB>j6GT_g6N|GDC zeQ|7uaAv_#l?F_{q8T&U(5BF?>+HdPQxY`rU)@S4EYB7ijr!+03PUxvu|NH`wxJSw z`^0u|Mq_rcWz!lNLJMp5Ib2o$A5&yn@OJ{=tTst10V!h}lWGy@g4x*F*gZ<@m;JDus6<3%r9uY(<6jUL)e!KBFjs_+z^B zIrLHoid(j%!~>Z=o@PA*!BgYs9i#sP;o%CjZdb(|I89xfC8-gkT^jzAEdQ|F0qXoc z5p?tV_=UQ(Ux-mcdpJUBv=j8%|7Dn1k(Vn8ed$-F-Hr3qP5q4oH!kyI!iDfSuD-a? zqu|M<*OGS{zJ?uD0etsN%1}~i)qktV!@&Icgh${hcoV8JHm#Wa3?I@q<5_UKemAq8 z)m~%SE8Z8mjp$Fp#UPgAa91}_6k5M!t;SibxG*%GIGkau^7W|_PBHNNe6yXXn^7H_ ztvtvgNL}B^;yDE7*`A z6Jo*p6MI`pGRzW6gAHVX$G|}8B5ZMOCBhZs$z~Roxr+)6j3>o(O4ir6*l>6EnKtN$ z&4i?Z7R#cfP*m%6v1U`v><8>1L4N1JFBKIj%`)gID2Zg{ubvFgJqN7hijo5Ci|`--$c zQ|fc6aIQ)*HWz`0Tnl>TI9^ z!ZV#H?l&kcGnBBK;bndmc{@0@sp2)GtT#D$tmu-{?ieGzRX)eBSO~UU#OrJI#%1J+ zaF-g@1D$;$*;#=t-vD{?uodWk%n*aLl1Xr*i&gn{!?+#KLtp;FNq}9(1CG}(j#ia> z$tsh!qWn*CH`z9R)8j1RBix4C_$xKt z;pJ#G5LC)BHm^7(|KyF1YJg*n?05SKmrnYYx7+8cJKGOYRAY~H9U>^_zsk$>a4fmH zGVyUrjzZJ;NHlz`q&X-iTqB`-+h!~>(tuG`G062#RYv!LwjucNvB z6DQsfb>i!$s9H7uJ_0N?6JDn&TgQL+7rW#o5h|OO*BT9yb_cGm_dHgEe&1DXlu7_I zd(36H_Gv2i&E`bcn#9HDlnq){eVTLI4q|rxN%LfwXViEK$+po>gLYlAOcp+IdlYo1 zFsaGwHIJ=7=W_dV@xK`Glm&m1&_=WqS=!znN4t1ocqrA!{v{cr|DE}3Dr6pikMmTs zgO{|^gyYhl-J}EQOr#sqW;sCAr*g$R^5ho2Wo8B=qhf z9Li(x{@$)9t0F|3CE}bV&;w#UptDqn8cFQhTWq+(w1X^RR&osecKSPbpvBTKG-BX$ z9;@C>?Nsae3%q@~rQ%QAR^GZl7d9p)i9>1=iVPCwfK8BS0R=XmM+Hg=femwH+$MBQ zkb!feMDCBKe8mhZiKqwt+kGj}d#fc&`(pKjm=g2gy6>YzX=U5i-wvOy;vejqz9;Zo zD2eA~jAVI_`QNN$UF57wK)#LLJ*@%0U{U#32k=&L(SB;H`vc~-*SMJfD?$J0ntOU> zEm))Wd8t;Y0spu>b#95YFm+5eo=*8%O86QC-YRpo1CNSb^!O*?>Uv`xt`m`JXn9rX zG0mTP6fYY_uSh`S_=Z+GVacel9UwG90PI)oWgzARpWqm--pjFNu6na{(rnGV?h!16 z%2+y^){hrK=gj;L)ms1K0Bgrhi6&Z1R@n>XDS~--Sd_8{g5YNyE{ZB5K_@h^j~O%E zByHG?96BX&4og}hrf;pdfc;o5ynEPPxEb-Rm4UVwlZaV-#e&65pS@hPcGs4D(cFLP zSPz{po&4n|&&9|OI`8UT+A&Qki%|}pFcj9cRhqBmfUd)r5Q?>CXmL1leTs)riW31I z3L@~>1LIn$wS7SH>l zXx>dP&37wTzrYu$=F-10Tv1`Y2TSYdlB8JpGBX$qmEQgSg#UU~)Zd?M->dMx#oI)+ zOx~Dl)2LvMj7O|SJV}+9Lxj)tt3{E9%l`zkSSe6-4R&1cnfqtOsplL{UFj zv1r)JtrfbpDW>z9F{^~0;N8ER%ufiKC{48In$t?+RT<}Nm^___`Dg-PxqLo*_9r0O zpNE`Haq62XddZ%W9C4u|LD!If{2aLdg0G#%spA|)Fju>427U7(>?U-mx3-Z`A9p@p z(7rgesn4$X!jeI1J@;yOb4$u3AzKI1;W+Q=JS8ev>XGLviL&}2tuZY8?=0sQ%t&X; z212S;VH4lN+GtUcj|2>oO=lwT6Ya%p)5>qmo9bh6Vab03O@;(DPBd+*xiCT)WABcwE>@=v7_67*aFxS<&-$;CcK?0nwkl#|@# zPz?Cz;E0I<7V_HJko|Cgh3V`uR9RzTx0fZv?O*4?#3Z5O5muR|?sSV$WxjF_cpnof zY2VKQSEtz~fw+3xN&9@B^~N*e9R~nwtYKb_{3j(+6y_Ltd7G$=KXbOZUP>>@pTl8F z*saadpx;;t?Yhk*hH$gtz_PRokt4Y?sgb>Lj2@0!VuDZKZe;TIqr6$dzt)A%^vZ+e zNJL?UFU}@UcbK=(@Z6ps&DbmD-28|#FTu%#Xu5d;v{f7-!?^PAep->|;r*3VFZ=WN zJFqx9+iEsEu5SXip(pG%gUMt1eL_i?0>PUX=RjVamJ34(sXKGeCTj{*h;Lq zA2?3Vp^3MR?e#L}(amg)m;w81%nGCDQ>EuvG|sg$R%kzqXMQ1o=ZQ!=-AWAa14FF`ZgPOG5E8;9l22Se*; z&4o?_9}6avYuPK2h0{;b>pHCOOc8jb1`Zo2CeS{!T0OlVR1Gp6$An0rv4fA%HChV^Wi)m1W&`%pL0`%+HQZ)>e$b0=*)y=PeP=Th;~W_zR95ab z!~KRGCQ>6aem101?|@uuGCAKD3tgE9@&Pt#f>tYma>lTHafVS;lx)YS8JlyQERmic z4T=VJ0M2h+E@<=fVb?SN`RLf|z7|_LTMCj%W$F+Y**-dGJAXXW3t?LE7N9P}7VKc2hs;Qi}Baz+S%Wh9a!lL^DJZnh1Ja0u6Kq$k;BK#olN?6jaCH?zw8S2x z)U5c*F7W}~r(k0Dj%Vx{Z~Y|a(CBdnsR@F&uzsjv|2`3K1D&JWYZ zsekT)Dc@U6fCnl7zpDj7EItF=Zj_)0PuR-TE9O>h&!yz>BG$ zc4>0TC8ur+TG3P`9Zw27=m(ZWJd|)x2n>y&x=OU53Z$cN$H$?4CzTZ)oh4F=O2L;J z%V&IDVL)VlPGo(aR1y!d1&$U25*<>A>IL`Pl74kFifQ*XJB^J;>*T-gRAz4dm@yQc z!Ew}2y3fX_B64H6eJ@a&BEaD|I3d4e%2wULA Date: Sat, 18 Feb 2023 16:33:22 +0400 Subject: [PATCH 372/373] Update the template revision --- templates/ctl-scaffold/flake.lock | 8 ++++---- templates/ctl-scaffold/flake.nix | 2 +- templates/ctl-scaffold/packages.dhall | 2 +- templates/ctl-scaffold/spago-packages.nix | 6 +++--- 4 files changed, 9 insertions(+), 9 deletions(-) diff --git a/templates/ctl-scaffold/flake.lock b/templates/ctl-scaffold/flake.lock index 04d3dc8521..ef566500c7 100644 --- a/templates/ctl-scaffold/flake.lock +++ b/templates/ctl-scaffold/flake.lock @@ -1490,17 +1490,17 @@ "plutip": "plutip" }, "locked": { - "lastModified": 1676560148, - "narHash": "sha256-eM+sko8wRiTb04wkNMKDFRFU0kihrBFY2UiZhusWSP0=", + "lastModified": 1676722762, + "narHash": "sha256-E6fvOkRzE9h9SIqBMoMtN+yFKNOgh330zHvJCf0Pm7M=", "owner": "Plutonomicon", "repo": "cardano-transaction-lib", - "rev": "83476e9bce41efdf3307a6c036b5fd78895ee0d8", + "rev": "ee5233d556bce8aee7fd1c2934641b72eecae196", "type": "github" }, "original": { "owner": "Plutonomicon", "repo": "cardano-transaction-lib", - "rev": "83476e9bce41efdf3307a6c036b5fd78895ee0d8", + "rev": "ee5233d556bce8aee7fd1c2934641b72eecae196", "type": "github" } }, diff --git a/templates/ctl-scaffold/flake.nix b/templates/ctl-scaffold/flake.nix index d9299bf646..6dbc8dc06a 100644 --- a/templates/ctl-scaffold/flake.nix +++ b/templates/ctl-scaffold/flake.nix @@ -10,7 +10,7 @@ type = "github"; owner = "Plutonomicon"; repo = "cardano-transaction-lib"; - rev = "83476e9bce41efdf3307a6c036b5fd78895ee0d8"; + rev = "ee5233d556bce8aee7fd1c2934641b72eecae196"; }; # To use the same version of `nixpkgs` as we do nixpkgs.follows = "ctl/nixpkgs"; diff --git a/templates/ctl-scaffold/packages.dhall b/templates/ctl-scaffold/packages.dhall index 17962152d3..01290d1ca6 100644 --- a/templates/ctl-scaffold/packages.dhall +++ b/templates/ctl-scaffold/packages.dhall @@ -353,7 +353,7 @@ let additions = , "web-html" ] , repo = "https://github.com/Plutonomicon/cardano-transaction-lib.git" - , version = "83476e9bce41efdf3307a6c036b5fd78895ee0d8" + , version = "ee5233d556bce8aee7fd1c2934641b72eecae196" } , noble-secp256k1 = { dependencies = diff --git a/templates/ctl-scaffold/spago-packages.nix b/templates/ctl-scaffold/spago-packages.nix index 8a15943a9e..afb4c04443 100644 --- a/templates/ctl-scaffold/spago-packages.nix +++ b/templates/ctl-scaffold/spago-packages.nix @@ -211,11 +211,11 @@ let "cardano-transaction-lib" = pkgs.stdenv.mkDerivation { name = "cardano-transaction-lib"; - version = "83476e9bce41efdf3307a6c036b5fd78895ee0d8"; + version = "ee5233d556bce8aee7fd1c2934641b72eecae196"; src = pkgs.fetchgit { url = "https://github.com/Plutonomicon/cardano-transaction-lib.git"; - rev = "83476e9bce41efdf3307a6c036b5fd78895ee0d8"; - sha256 = "1za82vmqd6a8v5c13b519395848mhg13894csgdj8iihiy9arkvq"; + rev = "ee5233d556bce8aee7fd1c2934641b72eecae196"; + sha256 = "1cwv1zyhkjbvrks7v1x0scl8bv1p5n1k50ca91yxh4vk8hxfz9qk"; }; phases = "installPhase"; installPhase = "ln -s $src $out"; From 3c58c4bb29d19a5b7562938a8be8f9884d12b084 Mon Sep 17 00:00:00 2001 From: Vladimir Kalnitsky Date: Sat, 18 Feb 2023 16:45:55 +0400 Subject: [PATCH 373/373] Make the tests pass in template --- templates/ctl-scaffold/test/Main.purs | 23 +++++++++++++---------- 1 file changed, 13 insertions(+), 10 deletions(-) diff --git a/templates/ctl-scaffold/test/Main.purs b/templates/ctl-scaffold/test/Main.purs index 36812c88a0..cda7a7fbbd 100644 --- a/templates/ctl-scaffold/test/Main.purs +++ b/templates/ctl-scaffold/test/Main.purs @@ -11,6 +11,7 @@ import Contract.Test.Plutip , PlutipConfig , PlutipTest , testPlutipContracts + , withKeyWallet , withWallets ) import Contract.Test.Utils (exitCode, interruptOnSignal) @@ -24,7 +25,7 @@ import Effect.Aff , effectCanceler , launchAff ) -import Mote (test) +import Mote (group, test) import Scaffold (contract) import Test.Spec.Runner (defaultConfig) @@ -38,15 +39,17 @@ main = interruptOnSignal SIGINT =<< launchAff do suite :: TestPlanM PlutipTest Unit suite = do - test "Print PubKey" do - let - distribution :: InitialUTxOs - distribution = - [ BigInt.fromInt 5_000_000 - , BigInt.fromInt 2_000_000_000 - ] - withWallets distribution \_ -> do - contract + group "Project tests" do + test "Print PubKey" do + let + distribution :: InitialUTxOs + distribution = + [ BigInt.fromInt 5_000_000 + , BigInt.fromInt 2_000_000_000 + ] + withWallets distribution \wallet -> do + withKeyWallet wallet do + contract config :: PlutipConfig config =