diff --git a/lib/core-integration/src/Test/Integration/Scenario/API/Shelley/StakePools.hs b/lib/core-integration/src/Test/Integration/Scenario/API/Shelley/StakePools.hs index ca53557ffb3..14df6e8aa60 100644 --- a/lib/core-integration/src/Test/Integration/Scenario/API/Shelley/StakePools.hs +++ b/lib/core-integration/src/Test/Integration/Scenario/API/Shelley/StakePools.hs @@ -142,7 +142,7 @@ spec :: forall n t. ) => SpecWith (Context t) spec = describe "SHELLEY_STAKE_POOLS" $ do let listPools ctx stake = request @[ApiStakePool] ctx - (Link.listStakePools stake) Default Empty + (Link.listStakePools stake) Default Empty it "STAKE_POOLS_JOIN_01 - Cannot join non-existent wallet" $ \ctx -> runResourceT $ do w <- emptyWallet ctx @@ -165,7 +165,8 @@ spec = describe "SHELLEY_STAKE_POOLS" $ do \Cannot join existent stakepool with wrong password" $ \ctx -> runResourceT $ do w <- fixtureWallet ctx pool:_ <- map (view #id) . snd <$> unsafeRequest - @[ApiStakePool] ctx (Link.listStakePools arbitraryStake) Empty + @[ApiStakePool] + ctx (Link.listStakePools arbitraryStake) Empty joinStakePool @n ctx pool (w, "Wrong Passphrase") >>= flip verify [ expectResponseCode HTTP.status403 , expectErrorMessage errMsg403WrongPass @@ -178,7 +179,8 @@ spec = describe "SHELLEY_STAKE_POOLS" $ do dest <- emptyWallet ctx -- Join Pool - pool:_ <- map (view #id) . snd <$> unsafeRequest @[ApiStakePool] ctx + pool:_ <- map (view #id) . snd <$> + unsafeRequest @[ApiStakePool] ctx (Link.listStakePools arbitraryStake) Empty joinStakePool @n ctx pool (src, fixturePassphrase) >>= flip verify [ expectResponseCode HTTP.status202 @@ -355,8 +357,9 @@ spec = describe "SHELLEY_STAKE_POOLS" $ do it "STAKE_POOLS_JOIN_02 - \ \Cannot join already joined stake pool" $ \ctx -> runResourceT $ do w <- fixtureWallet ctx - pool:_ <- map (view #id) . snd <$> unsafeRequest @[ApiStakePool] - ctx (Link.listStakePools arbitraryStake) Empty + pool:_ <- map (view #id) . snd + <$> unsafeRequest @[ApiStakePool] + ctx (Link.listStakePools arbitraryStake) Empty joinStakePool @n ctx pool (w, fixturePassphrase) >>= flip verify [ expectResponseCode HTTP.status202 , expectField (#status . #getApiT) (`shouldBe` Pending) @@ -404,8 +407,9 @@ spec = describe "SHELLEY_STAKE_POOLS" $ do it "STAKE_POOLS_QUIT_02 - Passphrase must be correct to quit" $ \ctx -> runResourceT $ do w <- fixtureWallet ctx - pool:_ <- map (view #id) . snd <$> unsafeRequest @[ApiStakePool] - ctx (Link.listStakePools arbitraryStake) Empty + pool:_ <- map (view #id) . snd + <$> unsafeRequest @[ApiStakePool] + ctx (Link.listStakePools arbitraryStake) Empty joinStakePool @n ctx pool (w, fixturePassphrase) >>= flip verify [ expectResponseCode HTTP.status202 , expectField (#status . #getApiT) (`shouldBe` Pending) @@ -444,8 +448,8 @@ spec = describe "SHELLEY_STAKE_POOLS" $ do waitForNextEpoch ctx pool1:pool2:_ <- map (view #id) . snd - <$> unsafeRequest @[ApiStakePool] ctx - (Link.listStakePools arbitraryStake) Empty + <$> unsafeRequest @[ApiStakePool] + ctx (Link.listStakePools arbitraryStake) Empty joinStakePool @n ctx pool1 (w, fixturePassphrase) >>= flip verify [ expectResponseCode HTTP.status202 @@ -509,8 +513,9 @@ spec = describe "SHELLEY_STAKE_POOLS" $ do it "STAKE_POOLS_JOIN_04 - Rewards accumulate" $ \ctx -> runResourceT $ do w <- fixtureWallet ctx - pool:_ <- map (view #id) . snd <$> unsafeRequest @[ApiStakePool] - ctx (Link.listStakePools arbitraryStake) Empty + pool:_ <- map (view #id) . snd + <$> unsafeRequest @[ApiStakePool] + ctx (Link.listStakePools arbitraryStake) Empty -- Join a pool joinStakePool @n ctx pool (w, fixturePassphrase) >>= flip verify [ expectResponseCode HTTP.status202 @@ -557,8 +562,9 @@ spec = describe "SHELLEY_STAKE_POOLS" $ do } |] w <- unsafeResponse <$> postWallet ctx payload - pool:_ <- map (view #id) . snd <$> unsafeRequest @[ApiStakePool] - ctx (Link.listStakePools arbitraryStake) Empty + pool:_ <- map (view #id) . snd <$> + unsafeRequest @[ApiStakePool] + ctx (Link.listStakePools arbitraryStake) Empty eventually "wallet join a pool" $ do joinStakePool @n ctx pool (w, fixturePassphrase) >>= flip verify @@ -685,8 +691,8 @@ spec = describe "SHELLEY_STAKE_POOLS" $ do $ it "Join/quit when already joined a pool" $ \ctx -> runResourceT $ do w <- fixtureWallet ctx - pool1:pool2:_ <- - map (view #id) . snd <$> unsafeRequest @[ApiStakePool] + pool1:pool2:_ <- map (view #id) . snd <$> + unsafeRequest @[ApiStakePool] ctx (Link.listStakePools arbitraryStake) Empty liftIO $ joinStakePool @n ctx pool1 (w, fixturePassphrase) >>= flip verify @@ -755,8 +761,9 @@ spec = describe "SHELLEY_STAKE_POOLS" $ do it "STAKE_POOLS_JOIN_01x - \ \I can join if I have just the right amount" $ \ctx -> runResourceT $ do w <- fixtureWalletWith @n ctx [costOfJoining ctx + depositAmt ctx] - pool:_ <- map (view #id) . snd <$> unsafeRequest @[ApiStakePool] - ctx (Link.listStakePools arbitraryStake) Empty + pool:_ <- map (view #id) . snd <$> + unsafeRequest @[ApiStakePool] + ctx (Link.listStakePools arbitraryStake) Empty joinStakePool @n ctx pool (w, fixturePassphrase)>>= flip verify [ expectResponseCode HTTP.status202 , expectField (#status . #getApiT) (`shouldBe` Pending) @@ -766,8 +773,9 @@ spec = describe "SHELLEY_STAKE_POOLS" $ do it "STAKE_POOLS_JOIN_01x - \ \I cannot join if I have not enough fee to cover" $ \ctx -> runResourceT $ do w <- fixtureWalletWith @n ctx [costOfJoining ctx + depositAmt ctx - 1] - pool:_ <- map (view #id) . snd <$> unsafeRequest @[ApiStakePool] - ctx (Link.listStakePools arbitraryStake) Empty + pool:_ <- map (view #id) . snd <$> + unsafeRequest @[ApiStakePool] + ctx (Link.listStakePools arbitraryStake) Empty joinStakePool @n ctx pool (w, fixturePassphrase) >>= flip verify [ expectResponseCode HTTP.status403 , expectErrorMessage (errMsg403DelegationFee 1) @@ -788,8 +796,9 @@ spec = describe "SHELLEY_STAKE_POOLS" $ do ] w <- fixtureWalletWith @n ctx initBalance - pool:_ <- map (view #id) . snd <$> unsafeRequest @[ApiStakePool] - ctx (Link.listStakePools arbitraryStake) Empty + pool:_ <- map (view #id) . snd + <$> unsafeRequest @[ApiStakePool] + ctx (Link.listStakePools arbitraryStake) Empty joinStakePool @n ctx pool (w, fixturePassphrase) >>= flip verify [ expectResponseCode HTTP.status202 @@ -824,8 +833,9 @@ spec = describe "SHELLEY_STAKE_POOLS" $ do let initBalance = [ costOfJoining ctx + depositAmt ctx ] w <- fixtureWalletWith @n ctx initBalance - pool:_ <- map (view #id) . snd <$> unsafeRequest @[ApiStakePool] - ctx (Link.listStakePools arbitraryStake) Empty + pool:_ <- map (view #id) . snd + <$> unsafeRequest @[ApiStakePool] + ctx (Link.listStakePools arbitraryStake) Empty joinStakePool @n ctx pool (w, fixturePassphrase) >>= flip verify [ expectResponseCode HTTP.status202 @@ -898,18 +908,18 @@ spec = describe "SHELLEY_STAKE_POOLS" $ do r <- listPools ctx arbitraryStake expectResponseCode HTTP.status200 r let oneMillionAda = 1_000_000_000_000 - let pools = either (error . show) Prelude.id $ snd r + let pools' = either (error . show) Prelude.id $ snd r -- To ignore the ordering of the pools, we use Set. - setOf pools (view #cost) + setOf pools' (view #cost) `shouldBe` Set.singleton (Quantity 0) - setOf pools (view #margin) + setOf pools' (view #margin) `shouldBe` Set.singleton (Quantity $ unsafeMkPercentage 0.1) - setOf pools (view #pledge) + setOf pools' (view #pledge) `shouldBe` Set.fromList [ Quantity oneMillionAda @@ -960,9 +970,9 @@ spec = describe "SHELLEY_STAKE_POOLS" $ do verify r [ expectListSize 3 - , expectField Prelude.id $ \pools -> do + , expectField Prelude.id $ \pools' -> do let metadataActual = Set.fromList $ - mapMaybe (fmap getApiT . view #metadata) pools + mapMaybe (fmap getApiT . view #metadata) pools' metadataActual `shouldSatisfy` (`Set.isSubsetOf` metadataPossible) metadataActual @@ -971,11 +981,12 @@ spec = describe "SHELLEY_STAKE_POOLS" $ do it "contains and is sorted by non-myopic-rewards" $ \ctx -> runResourceT $ do eventually "eventually shows non-zero rewards" $ do - Right pools@[pool1,_pool2,pool3] <- + Right pools'@[pool1,_pool2,pool3] <- snd <$> listPools ctx arbitraryStake let rewards = view (#metrics . #nonMyopicMemberRewards) - (rewards <$> pools) `shouldBe` - (rewards <$> sortOn (Down . rewards) pools) + + (rewards <$> pools') `shouldBe` + (rewards <$> sortOn (Down . rewards) pools') -- Make sure the rewards are not all equal: rewards pool1 .> rewards pool3 @@ -1001,7 +1012,8 @@ spec = describe "SHELLEY_STAKE_POOLS" $ do \NonMyopicMemberRewards are 0 when stake is 0" $ \ctx -> runResourceT $ do liftIO $ pendingWith "This assumption seems false, for some reasons..." let stake = Just $ Coin 0 - r <- request @[ApiStakePool] ctx (Link.listStakePools stake) + r <- request @[ApiStakePool] + ctx (Link.listStakePools stake) Default Empty expectResponseCode HTTP.status200 r verify r diff --git a/lib/core/cardano-wallet-core.cabal b/lib/core/cardano-wallet-core.cabal index 3787b4fbf5d..eeb6ec264b2 100644 --- a/lib/core/cardano-wallet-core.cabal +++ b/lib/core/cardano-wallet-core.cabal @@ -94,7 +94,7 @@ library , statistics , stm , streaming-commons - , string-qq + , string-interpolate , template-haskell , text , text-class diff --git a/lib/core/src/Cardano/Pool/DB.hs b/lib/core/src/Cardano/Pool/DB.hs index d6c965aa6bf..e3a50f2a48a 100644 --- a/lib/core/src/Cardano/Pool/DB.hs +++ b/lib/core/src/Cardano/Pool/DB.hs @@ -49,6 +49,8 @@ import Data.Map.Strict ( Map ) import Data.Quantity ( Quantity (..) ) +import Data.Time.Clock.POSIX + ( POSIXTime ) import Data.Word ( Word64 ) import System.Random @@ -211,6 +213,16 @@ data DBLayer m = forall stm. (MonadFail stm, MonadIO stm) => DBLayer -> stm () -- ^ Remove all entries of slot ids newer than the argument + , putDelistedPools + :: [PoolId] + -> stm () + -- ^ Overwrite the set of delisted pools with a completely new set. + -- Pools may be delisted for reasons such as non-compliance. + + , readDelistedPools + :: stm [PoolId] + -- ^ Fetch the set of delisted pools. + , removePools :: [PoolId] -> stm () @@ -249,6 +261,15 @@ data DBLayer m = forall stm. (MonadFail stm, MonadIO stm) => DBLayer -> stm () -- ^ Modify the settings. + , readLastMetadataGC + :: stm (Maybe POSIXTime) + -- ^ Get the last metadata GC time. + + , putLastMetadataGC + :: POSIXTime + -> stm () + -- ^ Set the last metadata GC time. + -- , cleanDB :: stm () -- ^ Clean a database diff --git a/lib/core/src/Cardano/Pool/DB/MVar.hs b/lib/core/src/Cardano/Pool/DB/MVar.hs index a5784911a56..44d9ac4a07f 100644 --- a/lib/core/src/Cardano/Pool/DB/MVar.hs +++ b/lib/core/src/Cardano/Pool/DB/MVar.hs @@ -30,8 +30,10 @@ import Cardano.Pool.DB.Model , mListPoolLifeCycleData , mListRegisteredPools , mListRetiredPools + , mPutDelistedPools , mPutFetchAttempt , mPutHeader + , mPutLastMetadataGC , mPutPoolMetadata , mPutPoolProduction , mPutPoolRegistration @@ -39,6 +41,8 @@ import Cardano.Pool.DB.Model , mPutSettings , mPutStakeDistribution , mReadCursor + , mReadDelistedPools + , mReadLastMetadataGC , mReadPoolLifeCycleStatus , mReadPoolMetadata , mReadPoolProduction @@ -146,6 +150,12 @@ newDBLayer timeInterpreter = do rollbackTo = void . alterPoolDB (const Nothing) db . mRollbackTo timeInterpreter + putDelistedPools = + void . alterPoolDB (const Nothing) db . mPutDelistedPools + + readDelistedPools = + readPoolDB db mReadDelistedPools + removePools = void . alterPoolDB (const Nothing) db . mRemovePools @@ -165,6 +175,11 @@ newDBLayer timeInterpreter = do putSettings = void . alterPoolDB (const Nothing) db . mPutSettings + readLastMetadataGC = readPoolDB db mReadLastMetadataGC + + putLastMetadataGC = + void . alterPoolDB (const Nothing) db . mPutLastMetadataGC + cleanDB = void $ alterPoolDB (const Nothing) db mCleanDatabase diff --git a/lib/core/src/Cardano/Pool/DB/Model.hs b/lib/core/src/Cardano/Pool/DB/Model.hs index cdd60403b9a..658ea3f5449 100644 --- a/lib/core/src/Cardano/Pool/DB/Model.hs +++ b/lib/core/src/Cardano/Pool/DB/Model.hs @@ -16,6 +16,7 @@ {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE UndecidableInstances #-} + -- | -- Copyright: © 2018-2020 IOHK -- License: Apache-2.0 @@ -50,6 +51,7 @@ module Cardano.Pool.DB.Model , mPutPoolRetirement , mReadPoolRetirement , mUnfetchedPoolMetadataRefs + , mPutDelistedPools , mPutFetchAttempt , mPutPoolMetadata , mListPoolLifeCycleData @@ -60,9 +62,12 @@ module Cardano.Pool.DB.Model , mRollbackTo , mReadCursor , mRemovePools + , mReadDelistedPools , mRemoveRetiredPools , mReadSettings , mPutSettings + , mPutLastMetadataGC + , mReadLastMetadataGC ) where import Prelude @@ -75,6 +80,7 @@ import Cardano.Wallet.Primitive.Types ( BlockHeader (..) , CertificatePublicationTime , EpochNo (..) + , InternalState (..) , PoolId , PoolLifeCycleStatus (..) , PoolOwner (..) @@ -82,9 +88,10 @@ import Cardano.Wallet.Primitive.Types , PoolRetirementCertificate (..) , Settings , SlotNo (..) - , StakePoolMetadata + , StakePoolMetadata (..) , StakePoolMetadataHash , StakePoolMetadataUrl + , defaultInternalState , defaultSettings ) import Control.Monad.Trans.Class @@ -109,6 +116,10 @@ import Data.Ord ( Down (..) ) import Data.Quantity ( Quantity (..) ) +import Data.Set + ( Set ) +import Data.Time.Clock.POSIX + ( POSIXTime ) import Data.Word ( Word64 ) import GHC.Generics @@ -143,6 +154,8 @@ data PoolDatabase = PoolDatabase !(Map (CertificatePublicationTime, PoolId) PoolRetirementCertificate) -- ^ On-chain retirements associated with pools + , delisted :: !(Set PoolId) + , metadata :: !(Map StakePoolMetadataHash StakePoolMetadata) -- ^ Off-chain metadata cached in database @@ -156,6 +169,10 @@ data PoolDatabase = PoolDatabase -- ^ Store headers during syncing , settings :: Settings + + , internalState :: InternalState + -- ^ Various internal states that need to persist across + -- wallet restarts. } deriving (Generic, Show, Eq) data SystemSeed @@ -171,9 +188,9 @@ instance Eq SystemSeed where -- | Produces an empty model pool production database. emptyPoolDatabase :: PoolDatabase -emptyPoolDatabase = - PoolDatabase mempty mempty mempty mempty mempty mempty mempty NotSeededYet - mempty defaultSettings +emptyPoolDatabase = PoolDatabase + mempty mempty mempty mempty mempty mempty mempty mempty NotSeededYet + mempty defaultSettings defaultInternalState {------------------------------------------------------------------------------- Model Operation Types @@ -414,6 +431,12 @@ mRollbackTo ti point = do | point' <= getPoint point = Just v | otherwise = Nothing +mPutDelistedPools :: [PoolId] -> ModelOp () +mPutDelistedPools = modify #delisted . const . Set.fromList + +mReadDelistedPools :: ModelOp [PoolId] +mReadDelistedPools = Set.toList <$> get #delisted + mRemovePools :: [PoolId] -> ModelOp () mRemovePools poolsToRemove = do modify #distributions @@ -453,6 +476,15 @@ mPutSettings -> ModelOp () mPutSettings s = modify #settings (\_ -> s) +mReadLastMetadataGC + :: ModelOp (Maybe POSIXTime) +mReadLastMetadataGC = get (#internalState . #lastMetadataGC) + +mPutLastMetadataGC + :: POSIXTime + -> ModelOp () +mPutLastMetadataGC t = modify (#internalState . #lastMetadataGC) (\_ -> Just t) + -------------------------------------------------------------------------------- -- Utilities -------------------------------------------------------------------------------- diff --git a/lib/core/src/Cardano/Pool/DB/Sqlite.hs b/lib/core/src/Cardano/Pool/DB/Sqlite.hs index dcfb548703c..17d778d5ca9 100644 --- a/lib/core/src/Cardano/Pool/DB/Sqlite.hs +++ b/lib/core/src/Cardano/Pool/DB/Sqlite.hs @@ -50,6 +50,8 @@ import Cardano.Pool.DB ( DBLayer (..), ErrPointAlreadyExists (..), determinePoolLifeCycleStatus ) import Cardano.Pool.DB.Log ( ParseFailure (..), PoolDbLog (..) ) +import Cardano.Pool.DB.Sqlite.TH hiding + ( BlockHeader, blockHeight ) import Cardano.Wallet.DB.Sqlite.Types ( BlockId (..) ) import Cardano.Wallet.Logging @@ -60,7 +62,7 @@ import Cardano.Wallet.Primitive.Types ( BlockHeader (..) , CertificatePublicationTime (..) , EpochNo (..) - , PoolId + , PoolId (..) , PoolLifeCycleStatus (..) , PoolRegistrationCertificate (..) , PoolRetirementCertificate (..) @@ -96,8 +98,8 @@ import Data.Quantity ( Percentage (..), Quantity (..) ) import Data.Ratio ( denominator, numerator, (%) ) -import Data.String.QQ - ( s ) +import Data.String.Interpolate + ( i ) import Data.Text ( Text ) import Data.Time.Clock @@ -120,7 +122,9 @@ import Database.Persist.Sql , selectFirst , selectList , toPersistValue + , update , (<.) + , (=.) , (==.) , (>.) , (>=.) @@ -134,9 +138,6 @@ import System.FilePath import System.Random ( newStdGen ) -import Cardano.Pool.DB.Sqlite.TH hiding - ( BlockHeader, blockHeight ) - import qualified Cardano.Pool.DB.Sqlite.TH as TH import qualified Cardano.Wallet.Primitive.Types as W import qualified Data.Map.Strict as Map @@ -393,7 +394,8 @@ newDBLayer trace fp timeInterpreter = do (PoolMetadataFetchAttempts hash url retryAfter $ retryCount + 1) putPoolMetadata hash metadata = do - let StakePoolMetadata{ticker,name,description,homepage} = metadata + let StakePoolMetadata + {ticker, name, description, homepage} = metadata repsert (PoolMetadataKey hash) (PoolMetadata hash name ticker description homepage) @@ -489,6 +491,13 @@ newDBLayer trace fp timeInterpreter = do deleteWhere [ BlockSlot >. point ] -- TODO: remove dangling metadata no longer attached to a pool + putDelistedPools pools = do + deleteWhere ([] :: [Filter PoolDelistment]) + insertMany_ $ fmap PoolDelistment pools + + readDelistedPools = + fmap (delistedPoolId . entityVal) <$> selectList [] [] + removePools = mapM_ $ \pool -> do liftIO $ traceWith trace $ MsgRemovingPool pool deleteWhere [ PoolProductionPoolId ==. pool ] @@ -541,16 +550,33 @@ newDBLayer trace fp timeInterpreter = do (SettingsKey 1) . toSettings + readLastMetadataGC = do + -- only ever read the first row + result <- selectFirst + [] + [Asc InternalStateId, LimitTo 1] + pure $ (W.lastMetadataGC . fromInternalState . entityVal) =<< result + + putLastMetadataGC utc = do + result <- selectFirst + [ InternalStateId ==. (InternalStateKey 1) ] + [ ] + case result of + Just _ -> update (InternalStateKey 1) [ LastGCMetadata =. Just utc ] + Nothing -> insert_ (InternalState $ Just utc) + cleanDB = do deleteWhere ([] :: [Filter PoolProduction]) deleteWhere ([] :: [Filter PoolOwner]) deleteWhere ([] :: [Filter PoolRegistration]) deleteWhere ([] :: [Filter PoolRetirement]) + deleteWhere ([] :: [Filter PoolDelistment]) deleteWhere ([] :: [Filter StakeDistribution]) deleteWhere ([] :: [Filter PoolMetadata]) deleteWhere ([] :: [Filter PoolMetadataFetchAttempts]) deleteWhere ([] :: [Filter TH.BlockHeader]) deleteWhere ([] :: [Filter Settings]) + deleteWhere ([] :: [Filter InternalState]) atomically :: forall a. (SqlPersistT IO a -> IO a) atomically = runQuery @@ -706,7 +732,7 @@ createView conn (DatabaseView name definition) = do -- This view does NOT exclude pools that have retired. -- activePoolLifeCycleData :: DatabaseView -activePoolLifeCycleData = DatabaseView "active_pool_lifecycle_data" [s| +activePoolLifeCycleData = DatabaseView "active_pool_lifecycle_data" [i| SELECT active_pool_registrations.pool_id as pool_id, active_pool_retirements.retirement_epoch as retirement_epoch, @@ -735,7 +761,7 @@ activePoolLifeCycleData = DatabaseView "active_pool_lifecycle_data" [s| -- This view does NOT exclude pools that have retired. -- activePoolOwners :: DatabaseView -activePoolOwners = DatabaseView "active_pool_owners" [s| +activePoolOwners = DatabaseView "active_pool_owners" [i| SELECT pool_id, pool_owners FROM ( SELECT row_number() OVER w AS r, * FROM ( @@ -763,7 +789,7 @@ activePoolOwners = DatabaseView "active_pool_owners" [s| -- This view does NOT exclude pools that have retired. -- activePoolRegistrations :: DatabaseView -activePoolRegistrations = DatabaseView "active_pool_registrations" [s| +activePoolRegistrations = DatabaseView "active_pool_registrations" [i| SELECT pool_id, cost, @@ -793,7 +819,7 @@ activePoolRegistrations = DatabaseView "active_pool_registrations" [s| -- certificates revoked by subsequent re-registration certificates. -- activePoolRetirements :: DatabaseView -activePoolRetirements = DatabaseView "active_pool_retirements" [s| +activePoolRetirements = DatabaseView "active_pool_retirements" [i| SELECT * FROM ( SELECT pool_id, @@ -973,3 +999,7 @@ toSettings -> Settings toSettings (W.Settings pms) = Settings pms +fromInternalState + :: InternalState + -> W.InternalState +fromInternalState (InternalState utc) = W.InternalState utc diff --git a/lib/core/src/Cardano/Pool/DB/Sqlite/TH.hs b/lib/core/src/Cardano/Pool/DB/Sqlite/TH.hs index a1e4a97a9b9..c4b5d2443c3 100644 --- a/lib/core/src/Cardano/Pool/DB/Sqlite/TH.hs +++ b/lib/core/src/Cardano/Pool/DB/Sqlite/TH.hs @@ -28,6 +28,8 @@ import Data.Text ( Text ) import Data.Time.Clock ( UTCTime ) +import Data.Time.Clock.POSIX + ( POSIXTime ) import Data.Word ( Word32, Word64, Word8 ) import Database.Persist.Class @@ -49,6 +51,11 @@ share ] [persistLowerCase| +InternalState sql=internal_state + lastGCMetadata POSIXTime Maybe sql=last_gc_metadata + + deriving Show Generic + Settings sql=settings settingsPoolMetadataSource W.PoolMetadataSource sql=metadata_source @@ -117,6 +124,11 @@ PoolRegistration sql=pool_registration Primary poolRegistrationPoolId poolRegistrationSlot poolRegistrationSlotInternalIndex deriving Show Generic +PoolDelistment sql=pool_delistment + delistedPoolId W.PoolId sql=pool_id + Primary delistedPoolId + deriving Show Generic + -- Mapping of retirement certificates to pools PoolRetirement sql=pool_retirement poolRetirementPoolId W.PoolId sql=pool_id diff --git a/lib/core/src/Cardano/Pool/Metadata.hs b/lib/core/src/Cardano/Pool/Metadata.hs index b960cba8d74..f2ae2b95e89 100644 --- a/lib/core/src/Cardano/Pool/Metadata.hs +++ b/lib/core/src/Cardano/Pool/Metadata.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE NumericUnderscores #-} {-# LANGUAGE Rank2Types #-} @@ -16,6 +17,7 @@ module Cardano.Pool.Metadata -- * Fetch fetchFromRemote , StakePoolMetadataFetchLog (..) + , fetchDelistedPools -- * Construct URLs , identityUrlBuilder @@ -43,7 +45,7 @@ import Cardano.Wallet.Primitive.Types import Control.Exception ( IOException, handle ) import Control.Monad - ( when ) + ( forM, when ) import Control.Monad.IO.Class ( MonadIO (..) ) import Control.Monad.Trans.Except @@ -53,7 +55,16 @@ import Control.Tracer import Crypto.Hash.Utils ( blake2b256 ) import Data.Aeson - ( eitherDecodeStrict ) + ( FromJSON (..) + , ToJSON (..) + , eitherDecodeStrict + , object + , withObject + , (.:) + , (.=) + ) +import Data.Bifunctor + ( first ) import Data.ByteArray.Encoding ( Base (..), convertToBase ) import Data.ByteString @@ -63,13 +74,14 @@ import Data.Coerce import Data.List ( intercalate ) import Data.Text.Class - ( ToText (..) ) + ( TextDecodingError (..), ToText (..), fromText ) import Fmt ( pretty ) import Network.HTTP.Client ( HttpException (..) , Manager , ManagerSettings + , brConsume , brReadSome , managerResponseTimeout , requestFromURI @@ -83,6 +95,7 @@ import Network.HTTP.Types.Status import Network.URI ( URI (..), parseURI ) +import qualified Data.ByteString as BS import qualified Data.ByteString.Char8 as B8 import qualified Data.ByteString.Lazy as BL import qualified Data.Text as T @@ -98,6 +111,24 @@ metadaFetchEp pid (StakePoolMetadataHash bytes) hashStr = T.unpack $ T.decodeUtf8 $ convertToBase Base16 bytes pidStr = T.unpack $ toText pid +-- | TODO: import SMASH types +newtype SMASHPoolId = SMASHPoolId T.Text + deriving stock (Eq, Show, Ord) + +instance ToJSON SMASHPoolId where + toJSON (SMASHPoolId poolId) = + object + [ "poolId" .= poolId + ] + +instance FromJSON SMASHPoolId where + parseJSON = withObject "SMASHPoolId" $ \o -> do + poolId <- o .: "poolId" + return $ SMASHPoolId poolId + +toPoolId :: SMASHPoolId -> Either TextDecodingError PoolId +toPoolId (SMASHPoolId pid) = fromText pid + -- | Some default settings, overriding some of the library's default with -- stricter values. defaultManagerSettings :: ManagerSettings @@ -134,6 +165,49 @@ registryUrlBuilder baseUrl pid _ hash = { uriPath = "/" <> metadaFetchEp pid hash } +fetchDelistedPools + :: Tracer IO StakePoolMetadataFetchLog + -> URI + -> Manager + -> IO (Maybe [PoolId]) +fetchDelistedPools tr uri manager = runExceptTLog $ do + pl <- getPoolsPayload + smashPids <- except $ eitherDecodeStrict @[SMASHPoolId] pl + forM smashPids $ except . first getTextDecodingError . toPoolId + where + getPoolsPayload :: ExceptT String IO ByteString + getPoolsPayload = do + req <- withExceptT show $ except $ requestFromURI uri + liftIO $ traceWith tr $ MsgFetchDelistedPools uri + ExceptT + $ handle fromIOException + $ handle fromHttpException + $ withResponse req manager handleResponseStatus + + handleResponseStatus response = case responseStatus response of + s | s == status200 -> do + let body = responseBody response + Right . BS.concat <$> brConsume body + s -> + pure $ Left $ mconcat + [ "The server replied with something unexpected: " + , show s + ] + + runExceptTLog + :: ExceptT String IO [PoolId] + -> IO (Maybe [PoolId]) + runExceptTLog action = runExceptT action >>= \case + Left msg -> + Nothing <$ traceWith tr (MsgFetchDelistedPoolsFailure msg) + + Right meta -> + Just meta <$ traceWith tr (MsgFetchDelistedPoolsSuccess meta) + + fromHttpException :: Monad m => HttpException -> m (Either String a) + fromHttpException = return . Left . ("HTTP exception: " <>) . show + +-- TODO: refactor/simplify this fetchFromRemote :: Tracer IO StakePoolMetadataFetchLog -> [ PoolId @@ -209,19 +283,24 @@ fetchFromRemote tr builders manager pid url hash = runExceptTLog $ do pure $ Left "There's no known metadata for this pool." s -> do - pure $ Left $ "The server replied something unexpected: " <> show s - - fromIOException :: Monad m => IOException -> m (Either String a) - fromIOException = return . Left . ("IO exception: " <>) . show + pure $ Left $ mconcat + [ "The server replied with something unexpected: " + , show s + ] fromHttpException :: Monad m => HttpException -> m (Either String (Maybe a)) fromHttpException = const (return $ Right Nothing) +fromIOException :: Monad m => IOException -> m (Either String a) +fromIOException = return . Left . ("IO exception: " <>) . show data StakePoolMetadataFetchLog = MsgFetchPoolMetadata StakePoolMetadataHash URI | MsgFetchPoolMetadataSuccess StakePoolMetadataHash StakePoolMetadata | MsgFetchPoolMetadataFailure StakePoolMetadataHash String | MsgFetchPoolMetadataFallback URI Bool + | MsgFetchDelistedPools URI + | MsgFetchDelistedPoolsFailure String + | MsgFetchDelistedPoolsSuccess [PoolId] deriving (Show, Eq) instance HasPrivacyAnnotation StakePoolMetadataFetchLog @@ -231,6 +310,9 @@ instance HasSeverityAnnotation StakePoolMetadataFetchLog where MsgFetchPoolMetadataSuccess{} -> Info MsgFetchPoolMetadataFailure{} -> Warning MsgFetchPoolMetadataFallback{} -> Warning + MsgFetchDelistedPools{} -> Info + MsgFetchDelistedPoolsFailure{} -> Warning + MsgFetchDelistedPoolsSuccess{} -> Info instance ToText StakePoolMetadataFetchLog where toText = \case @@ -251,3 +333,14 @@ instance ToText StakePoolMetadataFetchLog where then "" else " Falling back using a different strategy." ] + MsgFetchDelistedPools uri -> mconcat + [ "Fetching delisted pools from ", T.pack (show uri) + ] + MsgFetchDelistedPoolsSuccess poolIds -> mconcat + [ "Successfully fetched delisted " + , T.pack (show . length $ poolIds) + , " pools." + ] + MsgFetchDelistedPoolsFailure err -> mconcat + [ "Failed to fetch delisted pools: ", T.pack err + ] diff --git a/lib/core/src/Cardano/Wallet/Api.hs b/lib/core/src/Cardano/Wallet/Api.hs index e00a1a5fb73..369b398a53f 100644 --- a/lib/core/src/Cardano/Wallet/Api.hs +++ b/lib/core/src/Cardano/Wallet/Api.hs @@ -53,6 +53,8 @@ module Cardano.Wallet.Api , JoinStakePool , QuitStakePool , DelegationFee + , PostPoolMaintenance + , GetPoolMaintenance , ShelleyMigrations , MigrateShelleyWallet @@ -60,8 +62,8 @@ module Cardano.Wallet.Api -- * Settings , Settings - , PutSettings - , GetSettings + , PutSettings + , GetSettings -- * Byron , ByronWallets @@ -124,6 +126,8 @@ import Cardano.Wallet.Api.Types , ApiByronWallet , ApiCoinSelectionT , ApiFee + , ApiMaintenanceAction + , ApiMaintenanceActionPostData , ApiNetworkClock , ApiNetworkInformation , ApiNetworkParameters @@ -443,6 +447,8 @@ type StakePools n apiPool = :<|> JoinStakePool n :<|> QuitStakePool n :<|> DelegationFee + :<|> PostPoolMaintenance + :<|> GetPoolMaintenance -- | https://input-output-hk.github.io/cardano-wallet/api/edge/#operation/listStakePools type ListStakePools apiPool = "stake-pools" @@ -471,6 +477,17 @@ type DelegationFee = "wallets" :> "delegation-fees" :> Get '[JSON] ApiFee +-- | https://input-output-hk.github.io/cardano-wallet/api/#operation/postPoolMaintenance +type PostPoolMaintenance = "stake-pools" + :> "maintenance-actions" + :> ReqBody '[JSON] ApiMaintenanceActionPostData + :> Post '[JSON] ApiMaintenanceAction + +-- | https://input-output-hk.github.io/cardano-wallet/api/#operation/getPoolMaintenance +type GetPoolMaintenance = "stake-pools" + :> "maintenance-actions" + :> Get '[JSON] ApiMaintenanceAction + {------------------------------------------------------------------------------- Settings -------------------------------------------------------------------------------} diff --git a/lib/core/src/Cardano/Wallet/Api/Client.hs b/lib/core/src/Cardano/Wallet/Api/Client.hs index ec87a0dad31..c750d678a38 100644 --- a/lib/core/src/Cardano/Wallet/Api/Client.hs +++ b/lib/core/src/Cardano/Wallet/Api/Client.hs @@ -366,6 +366,8 @@ stakePoolClient = :<|> _joinStakePool :<|> _quitStakePool :<|> _delegationFee + :<|> _postPoolMaintenance + :<|> _getPoolMaintenance = client (Proxy @("v2" :> StakePools Aeson.Value apiPool)) in StakePoolClient diff --git a/lib/core/src/Cardano/Wallet/Api/Types.hs b/lib/core/src/Cardano/Wallet/Api/Types.hs index da00c6c6704..2f028d48870 100644 --- a/lib/core/src/Cardano/Wallet/Api/Types.hs +++ b/lib/core/src/Cardano/Wallet/Api/Types.hs @@ -61,6 +61,7 @@ module Cardano.Wallet.Api.Types , ApiCoinSelectionOutput (..) , ApiStakePool (..) , ApiStakePoolMetrics (..) + , ApiStakePoolFlag (..) , ApiWallet (..) , ApiWalletPassphrase (..) , ApiWalletPassphraseInfo (..) @@ -76,6 +77,9 @@ module Cardano.Wallet.Api.Types , PostExternalTransactionData (..) , ApiTransaction (..) , ApiWithdrawalPostData (..) + , ApiMaintenanceAction (..) + , ApiMaintenanceActionPostData (..) + , MaintenanceAction (..) , ApiFee (..) , ApiTxId (..) , ApiTxInput (..) @@ -196,6 +200,7 @@ import Cardano.Wallet.Primitive.Types , HistogramBar (..) , NetworkParameters (..) , PoolId (..) + , PoolMetadataGCStatus (..) , ShowFmt (..) , SlotInEpoch (..) , SlotLength (..) @@ -294,6 +299,8 @@ import Data.Text.Class ) import Data.Time.Clock ( NominalDiffTime, UTCTime ) +import Data.Time.Clock.POSIX + ( posixSecondsToUTCTime, utcTimeToPOSIXSeconds ) import Data.Time.Text ( iso8601, iso8601ExtendedUtc, utcTimeFromText, utcTimeToText ) import Data.Typeable @@ -402,6 +409,17 @@ fmtAllowedWords = API Types -------------------------------------------------------------------------------} +data MaintenanceAction = GcStakePools + deriving (Eq, Generic, Show) + +newtype ApiMaintenanceActionPostData = ApiMaintenanceActionPostData + { maintenanceAction :: MaintenanceAction + } deriving (Eq, Generic, Show) + +newtype ApiMaintenanceAction = ApiMaintenanceAction + { gcStakePools :: ApiT PoolMetadataGCStatus + } deriving (Eq, Generic, Show) + data ApiAddress (n :: NetworkDiscriminant) = ApiAddress { id :: !(ApiT Address, Proxy n) , state :: !(ApiT AddressState) @@ -543,8 +561,14 @@ data ApiStakePool = ApiStakePool , margin :: !(Quantity "percent" Percentage) , pledge :: !(Quantity "lovelace" Natural) , retirement :: !(Maybe ApiEpochInfo) + , flags :: ![ApiStakePoolFlag] } deriving (Eq, Generic, Show) +data ApiStakePoolFlag + = Delisted + deriving stock (Eq, Generic, Show) + deriving anyclass NFData + data ApiStakePoolMetrics = ApiStakePoolMetrics { nonMyopicMemberRewards :: !(Quantity "lovelace" Natural) , relativeStake :: !(Quantity "percent" Percentage) @@ -819,7 +843,6 @@ data ApiPostRandomAddressData = ApiPostRandomAddressData } deriving (Eq, Generic, Show) deriving anyclass NFData - data ApiWalletMigrationPostData (n :: NetworkDiscriminant) (s :: Symbol) = ApiWalletMigrationPostData { passphrase :: !(ApiT (Passphrase s)) @@ -922,6 +945,12 @@ instance FromText Iso8601Time where <> "'. Expecting ISO 8601 date-and-time format (basic or extended)" <> ", e.g. 2012-09-25T10:15:00Z." +instance FromJSON (ApiT Iso8601Time) where + parseJSON = + parseJSON >=> eitherToParser . bimap ShowFmt ApiT . fromText +instance ToJSON (ApiT Iso8601Time) where + toJSON = toJSON . toText . getApiT + instance FromHttpApiData Iso8601Time where parseUrlPiece = first (T.pack . getTextDecodingError) . fromText @@ -1376,11 +1405,57 @@ instance FromJSON WalletPutPassphraseData where instance ToJSON WalletPutPassphraseData where toJSON = genericToJSON defaultRecordTypeOptions +instance FromJSON (ApiT PoolMetadataGCStatus) where + parseJSON = withObject "PoolMetadataGCStatus" $ \o -> do + (status' :: String) <- o .: "status" + last_run <- o .:? "last_run" + case (status', last_run) of + ("restarting", Just (ApiT (Iso8601Time gctime))) + -> pure $ ApiT (Restarting $ utcTimeToPOSIXSeconds gctime) + ("has_run", Just (ApiT (Iso8601Time gctime))) + -> pure $ ApiT (HasRun $ utcTimeToPOSIXSeconds gctime) + ("restarting", Nothing) + -> fail "missing field last_run" + ("has_run", Nothing) + -> fail "missing field last_run" + ("not_applicable", _) + -> pure $ ApiT NotApplicable + ("not_started", _) + -> pure $ ApiT NotStarted + _ -> fail ("Unknown status: " <> status') + +instance ToJSON (ApiT PoolMetadataGCStatus) where + toJSON (ApiT (NotApplicable)) = + object [ "status" .= String "not_applicable" ] + toJSON (ApiT (NotStarted)) = + object [ "status" .= String "not_started" ] + toJSON (ApiT (Restarting gctime)) = + object [ "status" .= String "restarting" + , "last_run" .= ApiT (Iso8601Time (posixSecondsToUTCTime gctime)) ] + toJSON (ApiT (HasRun gctime)) = + object [ "status" .= String "has_run" + , "last_run" .= ApiT (Iso8601Time (posixSecondsToUTCTime gctime)) ] + instance FromJSON ByronWalletPutPassphraseData where parseJSON = genericParseJSON defaultRecordTypeOptions instance ToJSON ByronWalletPutPassphraseData where toJSON = genericToJSON defaultRecordTypeOptions +instance FromJSON ApiMaintenanceActionPostData where + parseJSON = genericParseJSON defaultRecordTypeOptions +instance ToJSON ApiMaintenanceActionPostData where + toJSON = genericToJSON defaultRecordTypeOptions + +instance FromJSON ApiMaintenanceAction where + parseJSON = genericParseJSON defaultRecordTypeOptions +instance ToJSON ApiMaintenanceAction where + toJSON = genericToJSON defaultRecordTypeOptions + +instance FromJSON MaintenanceAction where + parseJSON = genericParseJSON defaultSumTypeOptions +instance ToJSON MaintenanceAction where + toJSON = genericToJSON defaultSumTypeOptions + instance FromJSON ApiTxId where parseJSON = genericParseJSON defaultRecordTypeOptions instance ToJSON ApiTxId where @@ -1541,6 +1616,11 @@ instance FromJSON ApiStakePoolMetrics where instance ToJSON ApiStakePoolMetrics where toJSON = genericToJSON defaultRecordTypeOptions +instance FromJSON ApiStakePoolFlag where + parseJSON = genericParseJSON defaultSumTypeOptions +instance ToJSON ApiStakePoolFlag where + toJSON = genericToJSON defaultSumTypeOptions + instance FromJSON (ApiT WalletName) where parseJSON = parseJSON >=> eitherToParser . bimap ShowFmt ApiT . fromText instance ToJSON (ApiT WalletName) where diff --git a/lib/core/src/Cardano/Wallet/DB/Sqlite/Types.hs b/lib/core/src/Cardano/Wallet/DB/Sqlite/Types.hs index de81434c6eb..922f5119edb 100644 --- a/lib/core/src/Cardano/Wallet/DB/Sqlite/Types.hs +++ b/lib/core/src/Cardano/Wallet/DB/Sqlite/Types.hs @@ -89,12 +89,16 @@ import Data.Text.Class ) import Data.Text.Encoding ( decodeUtf8, encodeUtf8 ) +import Data.Time.Clock.POSIX + ( POSIXTime, posixSecondsToUTCTime, utcTimeToPOSIXSeconds ) +import Data.Time.Format + ( defaultTimeLocale, formatTime, iso8601DateFormat, parseTimeM ) import Data.Word ( Word32, Word64 ) import Data.Word.Odd ( Word31 ) import Database.Persist.Sqlite - ( PersistField (..), PersistFieldSql (..), PersistValue ) + ( PersistField (..), PersistFieldSql (..), PersistValue (..) ) import Database.Persist.TH ( MkPersistSettings (..), sqlSettings ) import GHC.Generics @@ -670,3 +674,21 @@ instance PersistField DerivationPrefix where instance PersistFieldSql DerivationPrefix where sqlType _ = sqlType (Proxy @Text) + +---------------------------------------------------------------------------- +-- Other + +instance PersistField POSIXTime where + toPersistValue = PersistText + . T.pack + . formatTime defaultTimeLocale (iso8601DateFormat (Just "%H:%M:%S")) + . posixSecondsToUTCTime + fromPersistValue (PersistText time) = + utcTimeToPOSIXSeconds <$> + parseTimeM True defaultTimeLocale + (iso8601DateFormat (Just "%H:%M:%S")) (T.unpack time) + fromPersistValue _ = Left + "Could not parse POSIX time value" + +instance PersistFieldSql POSIXTime where + sqlType _ = sqlType (Proxy @Text) diff --git a/lib/core/src/Cardano/Wallet/Primitive/Types.hs b/lib/core/src/Cardano/Wallet/Primitive/Types.hs index 9842fda7a2b..f665a2ec2e2 100644 --- a/lib/core/src/Cardano/Wallet/Primitive/Types.hs +++ b/lib/core/src/Cardano/Wallet/Primitive/Types.hs @@ -145,6 +145,7 @@ module Cardano.Wallet.Primitive.Types , StakePoolMetadataUrl (..) , StakePoolTicker (..) , StakeKeyCertificate (..) + , PoolMetadataGCStatus (..) -- * Querying , SortOrder (..) @@ -185,6 +186,11 @@ module Cardano.Wallet.Primitive.Types , PoolMetadataSource( .. ) , defaultSettings , unsafeToPMS + + -- * InternalState + , InternalState (..) + , defaultInternalState + ) where import Prelude @@ -257,6 +263,8 @@ import Data.Text.Class ) import Data.Time.Clock ( NominalDiffTime, UTCTime ) +import Data.Time.Clock.POSIX + ( POSIXTime ) import Data.Time.Format ( defaultTimeLocale, formatTime ) import Data.Word @@ -606,6 +614,15 @@ data StakePool = StakePool , saturation :: Double } deriving (Show, Generic) +-- Status encoding of the metadata GC thread, which queries +-- the SMASH server for delisted pools. +data PoolMetadataGCStatus + = NotApplicable + | NotStarted + | Restarting POSIXTime -- shows last GC before restart occured + | HasRun POSIXTime -- shows last GC + deriving (Eq, Show, Generic) + -- | A newtype to wrap metadata hash. -- -- NOTE: not using the 'Hash' type as this newtype is primarily for database @@ -1808,11 +1825,11 @@ data PoolRegistrationCertificate = PoolRegistrationCertificate instance NFData PoolRegistrationCertificate instance Buildable PoolRegistrationCertificate where - build (PoolRegistrationCertificate p o _ _ _ _) = mempty + build (PoolRegistrationCertificate {poolId, poolOwners}) = mempty <> "Registration of " - <> build p + <> build poolId <> " owned by " - <> build o + <> build poolOwners data PoolRetirementCertificate = PoolRetirementCertificate { poolId :: !PoolId @@ -1997,6 +2014,18 @@ defaultSettings = Settings { poolMetadataSource = FetchNone } +-- | Various internal states of the pool DB +-- that need to survive wallet restarts. These aren't +-- exposed settings. +{-# HLINT ignore InternalState "Use newtype instead of data" #-} +data InternalState = InternalState + { lastMetadataGC :: Maybe POSIXTime + } deriving (Generic, Show, Eq) + +defaultInternalState :: InternalState +defaultInternalState = InternalState + { lastMetadataGC = Nothing } + instance FromJSON PoolMetadataSource where parseJSON = parseJSON >=> either (fail . show . ShowFmt) pure . fromText diff --git a/lib/core/test/data/Cardano/Wallet/Api/ApiListStakePoolsApiStakePool.json b/lib/core/test/data/Cardano/Wallet/Api/ApiListStakePoolsApiStakePool.json new file mode 100644 index 00000000000..40e453d7d78 --- /dev/null +++ b/lib/core/test/data/Cardano/Wallet/Api/ApiListStakePoolsApiStakePool.json @@ -0,0 +1,4272 @@ +{ + "seed": 2068412580338120591, + "samples": [ + { + "pools": [ + { + "metrics": { + "saturation": 0.10063791170130454, + "non_myopic_member_rewards": { + "quantity": 151141558091, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 771096, + "unit": "block" + }, + "relative_stake": { + "quantity": 41.89, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1871-07-20T21:35:00Z", + "epoch_number": 24007 + }, + "cost": { + "quantity": 175, + "unit": "lovelace" + }, + "margin": { + "quantity": 29.46, + "unit": "percent" + }, + "pledge": { + "quantity": 182, + "unit": "lovelace" + }, + "delisted": true, + "id": "pool1re0eggswxhempkjrfp0m5cs4g6mv5uhum0tvfn9fjqwezaqdddl" + }, + { + "metrics": { + "saturation": 1.4460900857225596, + "non_myopic_member_rewards": { + "quantity": 989217369004, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 8322240, + "unit": "block" + }, + "relative_stake": { + "quantity": 16, + "unit": "percent" + } + }, + "cost": { + "quantity": 183, + "unit": "lovelace" + }, + "margin": { + "quantity": 6.98, + "unit": "percent" + }, + "pledge": { + "quantity": 108, + "unit": "lovelace" + }, + "delisted": true, + "metadata": { + "homepage": "\u0003񙇢S\u001a󇂾fdv𒁇\u0004Z|j\u0007rz\u0006Qꮝ􍲕{[戼XSu\u0019f\u000c>b􊚷rpX/$Y𸤏𾁵􏰪%A󺃄h򪧧A{?\nf󄥌'~l\u0002L6\u0016yo$\u001ax𼖣&􅄴_O򴩇^nZ", + "name": "\u001c\u001a򫭰IW󍏇\u0016", + "ticker": "󠽤\n`d`", + "description": "O}򣺲򝚾񨝡\u0019\u0003\u0005\r򏉽\u0016X򳊁Wb6\n\u0011&\u0005璻PQ%𧸉^~M<[\u0015e(w`_WY\u001bVzy\u0000􊒠S\u0005\u0004\n𤴢%\u001a2&\u0013!񝢉_;5Zq\u0018𬭯򱪠^D𡅢񮅽򬌭,󜖉)򠘭b&K\u000b􏥐ag\u0004񩚰/!\u000e󝐴m12𡔭\u001aQE񊈴,a󅸯\u000f򯦏pV\"G\u0001󃝠Gh򸷖.񱪖(G&\u001b򠐫ೡ\u0004#𔾶hW\u0014a6\u0015`񌋓tB1|[Rk񨗂mM\\LH\r[}󜄻N\u0005+G󃆨󼫆𨇄򽢱򩨾󂨌" + }, + "id": "pool12zrsgh8m96j2dgc37hctuulrpsgwrnx3qwnnglw6vmjwwwvn6nd" + }, + { + "metrics": { + "saturation": 6.693835861161679e-2, + "non_myopic_member_rewards": { + "quantity": 797066414135, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 10102242, + "unit": "block" + }, + "relative_stake": { + "quantity": 76.85, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1889-12-09T03:32:50.95358664512Z", + "epoch_number": 19102 + }, + "cost": { + "quantity": 2, + "unit": "lovelace" + }, + "margin": { + "quantity": 19.71, + "unit": "percent" + }, + "pledge": { + "quantity": 141, + "unit": "lovelace" + }, + "delisted": false, + "metadata": { + "homepage": "򼏉hZk\u000e4OrW𸈅\u0016\u000ekf\u0001V-ctcaw3/\u0004\u0015?jR𘊄K8𽙍󈽆--𤁻򞕆x𱂯:d\u0011M󒴔\r@", + "name": "󳐓gb󩮀\u000c>L^X\u001ct\u0012r\u00136h>\u0017򮜱񧾳U7r󱻺^B\\󕽚򀚎\nyK!Lk<\u0017<󅦌+񖷭𥲋I\u00177\u0016k𽚥", + "ticker": "H>f\u000b\u001e", + "description": "𔱆J򜫊h񍃈 t[\u0017*n\\\u0001H򓑛𽮪:9c򣶵Z򜲃󶇣bR𩽴\u0007񇕵\u0003nAkIꄁt󜔧\u001c^ O𕘥\u001e\u000b']𛬗\u001b󪁻䀹}\u001e򊚔󤞭uuSkoK\u00100DG\u001d-\u0013\u001e\u0017wdc𺇑\u001c\u000e䳯^o𺝔pH󷲯𦱘䕭ENlM5~\u001d񖆢3H\u0019򾹙񞖮𜖒_𴥗m/3󆥶nT0Q􄀢wMrM\u00130Kj󺚄k\t\u0017򱂵\u0006𯐈\u0003\u001c]\u000c\u001dD\u000e󐓻񇞆\u0010񀈝h񭟆𱨸#l]I'uZ\u0001'u󭾭T\u0018=mf𠖚\u0005F%򬌔􎘅.\u0006󞨕" + }, + "id": "pool17ve3mx20ne22pxrkh4h38kkvzda3uxhaq59t67nh6l74yet9yjg" + }, + { + "metrics": { + "saturation": 0.5478744614415704, + "non_myopic_member_rewards": { + "quantity": 731711621990, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 12148341, + "unit": "block" + }, + "relative_stake": { + "quantity": 26.66, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1864-05-21T06:58:58.019169008053Z", + "epoch_number": 28412 + }, + "cost": { + "quantity": 152, + "unit": "lovelace" + }, + "margin": { + "quantity": 46.28, + "unit": "percent" + }, + "pledge": { + "quantity": 91, + "unit": "lovelace" + }, + "delisted": true, + "metadata": { + "homepage": ".􊼶3:O򣮜n񂙥Y\u0017񤟮󵓎:`𶕖b`!fo9<9\u0006𲄒/\u0017#\u000bqbz)k'\u0001.𤖀\u0010\tuO|Ps򌎔z$", + "name": "*b:D$헓$M.Ak\u0002\nw\u001cj_y+6\u000e:\u00074򭙭n\u0010\u00173\u0008򲭳Y񍪩", + "ticker": "}A$y=", + "description": "?\u001cm\u0015\u0002\u0016>h𚓋4\u0005ᨪ򳝜\u0018b_\u001aE-῍\u0018\u0005J\u00185􅍍D@𱯘򷿢]i$w&'\\Z\u0006zUzMt3d\u000fJ\u0017E)𔁃񏺇SV򰃵S" + }, + "id": "pool1dpe8vn2fsx7lwxp2ha78fmjrk448pg6jjkp6x3nznlkwjuxl6ns" + }, + { + "metrics": { + "saturation": 3.798173693540594, + "non_myopic_member_rewards": { + "quantity": 461786696091, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 11860863, + "unit": "block" + }, + "relative_stake": { + "quantity": 88.41, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1874-04-24T11:00:00Z", + "epoch_number": 22724 + }, + "cost": { + "quantity": 45, + "unit": "lovelace" + }, + "margin": { + "quantity": 36.6, + "unit": "percent" + }, + "pledge": { + "quantity": 117, + "unit": "lovelace" + }, + "delisted": false, + "metadata": { + "homepage": "񟐟z򗤔r\u0015P򵺩񞨇񫥗􎡿28/\u0004\u000b;VX<񬼽J~f^j\u0018C-򿯘\u0000󶍆|V\u0017l\u001b\u0018󟰏򠿭]Ō\u0013\u0000b\u000cꐣ5\u00198e󮒩b򎯌", + "name": "L򼒅\u0008Wg%󘙤S󎒞Q|P_ZX򗅌\u000c(.", + "ticker": "/4?K񚞇", + "description": "tQ\u0001PPn\n􁎰Wd6󓇝򕋧GVk&qi𳃉񀛽𝻳􊌀🬍\u0013m^\u0011i\u001b󑖼򏟆󠭎DMW\u0000:@Q񨋛\u000cSJf񐖺u֍񋓥Jnj&;🭩򾂳s3rX% c𫨡mFm>J\u0000n,9񳔳򌗢󹞙9򈂢\u0010􇘐󤍵.AUiHQ\u001e-s\u0002󍬶IV>8T𳫤Q|'񩵝z)򁋜𾏶\u0013򻎊|&򧁘񝃜]\\\u000eD󾥀Q\u0011c\u000c𮔢o񾓰񟤄|񴪊6P6fp򱬰q\u0017\u000f$M" + }, + "id": "pool1d7qvcc7ga6qsw7s0f80mdlvmhhj58t5zuwd8lhe2hy2nsqlufd6" + }, + { + "metrics": { + "saturation": 4.231916765266923, + "non_myopic_member_rewards": { + "quantity": 684079915532, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 6769538, + "unit": "block" + }, + "relative_stake": { + "quantity": 68.01, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1892-12-05T00:00:00Z", + "epoch_number": 17254 + }, + "cost": { + "quantity": 129, + "unit": "lovelace" + }, + "margin": { + "quantity": 70.8, + "unit": "percent" + }, + "pledge": { + "quantity": 62, + "unit": "lovelace" + }, + "delisted": true, + "metadata": { + "homepage": "F/jhC\u001a$b'~󤶓F)EH\u000b􏠏uH5n\u0015\u0011\u001d򶥓\u0007QN񜅡>򈌞𻐽$\"󋬩7u\u0002O󲓯N\u0007h(C񫪢󟪍𻽬EcS\u000e3\u0006\rm=󪄶\t󤜳a􂠪", + "name": "\u001dk񤐠\u0019O|{D\u0016\u0011\u0004{􄻟󙽣8𝶞", + "ticker": " 񆱗#", + "description": "𷦌~c\u0015\u0019򋗭nT\u0016j7򕐲~)饻mW\u0008DO|26V\u001f\n\u000c]vds\u0005\u000c󾙒n5\u0004fiM(\\&\u0008㈻Ur1򍔒)g񏹷𛷳+\u0003W򖋽S{D#HMn$򍦣𛡂U`q7e\u0010<\u0006" + }, + "id": "pool1xhc85e7ppe624yawfer5xskqnpq2x6ddyu5z77tc5rfqs6qrrjk" + }, + { + "metrics": { + "saturation": 2.0552369596455664, + "non_myopic_member_rewards": { + "quantity": 721200472327, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 15763097, + "unit": "block" + }, + "relative_stake": { + "quantity": 53.99, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1879-05-22T19:39:50Z", + "epoch_number": 7974 + }, + "cost": { + "quantity": 19, + "unit": "lovelace" + }, + "margin": { + "quantity": 35.99, + "unit": "percent" + }, + "pledge": { + "quantity": 49, + "unit": "lovelace" + }, + "delisted": true, + "id": "pool13s2cqhgcp3pv6av3904pety6ayhj4nretduq4eg54f3gwpxpd7s" + }, + { + "metrics": { + "saturation": 1.6581732967242424, + "non_myopic_member_rewards": { + "quantity": 768728279778, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 19770810, + "unit": "block" + }, + "relative_stake": { + "quantity": 73.92, + "unit": "percent" + } + }, + "cost": { + "quantity": 21, + "unit": "lovelace" + }, + "margin": { + "quantity": 23.78, + "unit": "percent" + }, + "pledge": { + "quantity": 24, + "unit": "lovelace" + }, + "delisted": true, + "id": "pool1a5l6van2npw528jneejy79efwgka9txwa9mv27lnfl8xx7rp4ar" + }, + { + "metrics": { + "saturation": 0.8490618200968297, + "non_myopic_member_rewards": { + "quantity": 797103977115, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 11953307, + "unit": "block" + }, + "relative_stake": { + "quantity": 13.49, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1887-04-02T08:00:00Z", + "epoch_number": 25151 + }, + "cost": { + "quantity": 87, + "unit": "lovelace" + }, + "margin": { + "quantity": 99.13, + "unit": "percent" + }, + "pledge": { + "quantity": 182, + "unit": "lovelace" + }, + "delisted": true, + "metadata": { + "homepage": "\u0010a1\u001fx91uk+n񟶱\u0002󇺢T񻱏~𾣆7\u001e9/\u00001&\u0007N󁚪𙺗\u0008b\u0005\u001cQ򘑈󥡫\u0003Stesbp󋁹P򽕇jC񓑏Y󊞢\"m䔶𤈺?󌙫\u0014b𳪣h\u0016񹷜6^p𽵓󼼱󯐲\u0005泄yrpO\u001e4Bt~T\u0003𭵤>L\u0011\u0016~whtxtl\u0011z򔊶Sa;", + "name": "s\u0003\u0001b󙠼𫇩i,𱻕yAx\u001aH򑌒=HZ]񖭼񡇀\u0006󂪾,%\\򿥩\u001b(\"%S.󿧲򡗝\rB󪟚R2~]G𕪆\u0015򥪃", + "ticker": "\u001b\t9L", + "description": "\u0013\u0010*J򞴗-9󰸍򢷨o񎍴\u0013򆳚pm򃚾/`\u0010dzs\u0001d\u00174t𞪏󂾛n󠺬H񗫰4b󯿫C򴌀򣞷%\nkpj\u000f%2O\u000c6,X-Sy\u0018Pn󷸕y+𳔈k\u0007𷽲x񊸼򓭰𱅎\u0003\u000ch񘁼g*𲆫M[b𸥮񎩏#4j\u0011H񗂃PDQ􂦍HFm7W\u001a񱚰}:󺇴9\u0006񯀌\u0010󵲃\u0019=A\u0015x\u00012g򭍾.!.A\u0005P\u0008%鱵+󶹵Vq\u0004y򑛋J_\u0012\u001a^2uM񤃤zjD󼭋1\n\t񬂋<\u0010򎖽3򸺊󏤨Z󼯽.n\u0012\u001d|􁍣e􌐀#𶛖򲜭\t츙N򼡐󞒷󢙕W󻧡u𤓇􀜻m\u000eHQ\\󴶼|+\u0004\u0008󛹺\u001d򜵶%\u0007$" + }, + "id": "pool1judwh8lw9xfk87vhs90733kzkel50wrsc6edvemqz92s57dcyu2" + }, + { + "metrics": { + "saturation": 4.900887254999616, + "non_myopic_member_rewards": { + "quantity": 298484035257, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 16898, + "unit": "block" + }, + "relative_stake": { + "quantity": 37.87, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1897-07-16T06:18:56Z", + "epoch_number": 24320 + }, + "cost": { + "quantity": 4, + "unit": "lovelace" + }, + "margin": { + "quantity": 91.23, + "unit": "percent" + }, + "pledge": { + "quantity": 112, + "unit": "lovelace" + }, + "delisted": true, + "id": "pool1zjd76hgn83qfqgxj8mfch4q8aulqjxm6yr0tuf37wczj6zdh8m0" + }, + { + "metrics": { + "saturation": 4.597363391757413, + "non_myopic_member_rewards": { + "quantity": 499621119513, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 15123365, + "unit": "block" + }, + "relative_stake": { + "quantity": 9.21, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1858-12-23T18:00:00Z", + "epoch_number": 9610 + }, + "cost": { + "quantity": 185, + "unit": "lovelace" + }, + "margin": { + "quantity": 74.03, + "unit": "percent" + }, + "pledge": { + "quantity": 61, + "unit": "lovelace" + }, + "delisted": true, + "metadata": { + "homepage": "򚟣󽔖𞼚\u000e`\u000cz򤈫I󬶘[#Q\u000e򢱆<\u001d<\u0001u񵕞&󶫤G#\u0014򢾙򽙚\u0008 񂀕q=`!\u0019", + "name": "埔\u0000󇁯|\u0010񽿊\u001b<\r0Gr_򯿁T񯡴\u0012]\u0018hydE+񂩌u\u000eO󃿣I7lU􀂥^Pp>웑2񯩂+", + "ticker": "l\u0004l(", + "description": "O\u00080xhx/\u001d_F\u0012\u000c@s]񥵤(nH6T󍥃p𺍳\t0JT㔮O!\u000e򜗭h&3i\"\u0018\u00030FV<񛎦\u0006G=\u001bZla\u0005\u000cM\u0016󱂓󹝸=\u001d#\u0016짻\u0003m8o򙞾򾶥!H#򆛣>>:.\u00157\u001c򛐔򅗩<\nbkq\u0000b(𶷌\u001b◿\u0004\u0006򵋖8hz{t\u0010!򅞃[z}>𤗌񹦞" + }, + "id": "pool1g6ujwflxqjjg2zed0nplcj4fm7jqw0p08fjty467zymp640y478" + }, + { + "metrics": { + "saturation": 4.560649805609918, + "non_myopic_member_rewards": { + "quantity": 933719623424, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 16013501, + "unit": "block" + }, + "relative_stake": { + "quantity": 22.59, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1892-05-17T12:49:09Z", + "epoch_number": 14261 + }, + "cost": { + "quantity": 128, + "unit": "lovelace" + }, + "margin": { + "quantity": 59.38, + "unit": "percent" + }, + "pledge": { + "quantity": 81, + "unit": "lovelace" + }, + "delisted": true, + "id": "pool1vycza6uesdlxvp0aresc9y3s0mlgsnnfmq6qflve5cq26t8uqle" + }, + { + "metrics": { + "saturation": 3.8012087711259785, + "non_myopic_member_rewards": { + "quantity": 71466564545, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 18877743, + "unit": "block" + }, + "relative_stake": { + "quantity": 97.48, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1896-12-13T02:52:29.899035567014Z", + "epoch_number": 3135 + }, + "cost": { + "quantity": 50, + "unit": "lovelace" + }, + "margin": { + "quantity": 65.84, + "unit": "percent" + }, + "pledge": { + "quantity": 180, + "unit": "lovelace" + }, + "delisted": false, + "metadata": { + "homepage": "񍷢Q\u0008e򚉗Q~", + "name": "\u0003\u0000\u0015􅩐H@_9*P󆅷", + "ticker": "Vn򩸜\u000e󹒼" + }, + "id": "pool12jwk5709e6cvdvq4vg7z3as57mcxvhrw4k65uzprxv042mekjml" + }, + { + "metrics": { + "saturation": 0.9756006870848394, + "non_myopic_member_rewards": { + "quantity": 7160737728, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 3115405, + "unit": "block" + }, + "relative_stake": { + "quantity": 45, + "unit": "percent" + } + }, + "cost": { + "quantity": 251, + "unit": "lovelace" + }, + "margin": { + "quantity": 5.46, + "unit": "percent" + }, + "pledge": { + "quantity": 33, + "unit": "lovelace" + }, + "delisted": true, + "metadata": { + "homepage": "\u000ek򅴱++5tR8J􁆩񾨮7\u0014\r𜧮򈼵\u0007&t\u0001\u00074\u0008򁇾~<\u000cVf򕟳\u0016<󛔷\u0005\r񾣎zR\u001f򰴀񞿮t'W<|q򦏆򄣍uy\u0014[􌃒\u000e+\u000f\u0000\u0004\u0010󡈄L\rq\u0005' OHM􅧫$f񶡜i񩕓\u000bY=HvQb򒱵r0c\u0015U9\u0005[n1L4xK", + "name": "󠽠}\u001dk.<򙶚\u000f4\u001b򵷉]񭖌", + "ticker": "\r\u0001Q", + "description": "8o.['b6@;9񄺗#yZ\u0016\u0007l9A{\u0018NQ񈫟D t򥷰[\u0012􄚜O,/1􇬁񥘡2~q񜘆$5\u0003c򶺂dVx񜶖𩦌C񸦢򷡞}\u0007񣹍l^cy\u0017" + }, + "id": "pool1wam7syqu9f05gceseuzx5azldpauykpgw7p3su3g7vexv8c5m3e" + }, + { + "metrics": { + "saturation": 4.826753495946856e-2, + "non_myopic_member_rewards": { + "quantity": 12194687205, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 12084764, + "unit": "block" + }, + "relative_stake": { + "quantity": 33.57, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1902-08-27T11:00:00Z", + "epoch_number": 11109 + }, + "cost": { + "quantity": 128, + "unit": "lovelace" + }, + "margin": { + "quantity": 98.56, + "unit": "percent" + }, + "pledge": { + "quantity": 33, + "unit": "lovelace" + }, + "delisted": false, + "metadata": { + "homepage": "󤐭󣗛\u0014 i򽙨\u0017B0󲮱", + "name": "|", + "ticker": "󓌑/-򶋝q񝄒5&?𵃕vzDX][􆠾\u0013񨼟𿔸񰢎k󝙡rR/\u0010򛝭^N8*񊵰Fb\u000f>\u0014󀳙\u000f\u0007𱂭󝬖m" + }, + "id": "pool14pzamk4w290ny80d09gcmqqgqxr65qzdn9chrthlh8z5qnse76l" + }, + { + "metrics": { + "saturation": 3.430891809613163, + "non_myopic_member_rewards": { + "quantity": 629506276593, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 6894338, + "unit": "block" + }, + "relative_stake": { + "quantity": 84.51, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1881-09-11T21:03:57Z", + "epoch_number": 28523 + }, + "cost": { + "quantity": 31, + "unit": "lovelace" + }, + "margin": { + "quantity": 3.1, + "unit": "percent" + }, + "pledge": { + "quantity": 144, + "unit": "lovelace" + }, + "delisted": false, + "metadata": { + "homepage": "r򚞣􅗖󋹛򮡈(\u0013", + "name": "𶻬P󒉋\u0017Q,z\u0014\u0008򋄫", + "ticker": "U\u0014NM", + "description": "`\u0003L\u001fm+9\u0007g\t񛾕&>tGJ\u001e𑉧\u000ceP\u001c񲻮D\u001a񀔌𬊫#:#񺊘\u000e~[-𷰠񓹢\u0016\u000en\u0012\u0000_-t9񊲙i3𬾭𦁏\u0002_mzfBC\u001aH\u0015%\u0010nksu\u0016%>9 \u0000ipFC𦖙\u0011󇅍U " + }, + "id": "pool1pxxlllhf6unam05a4sf76alvuncl6vx0ywp3j2y90zksydjtcgy" + }, + { + "metrics": { + "saturation": 4.259674776198254, + "non_myopic_member_rewards": { + "quantity": 417714392243, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 10027698, + "unit": "block" + }, + "relative_stake": { + "quantity": 12.04, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1899-01-28T20:55:39Z", + "epoch_number": 9861 + }, + "cost": { + "quantity": 195, + "unit": "lovelace" + }, + "margin": { + "quantity": 39.6, + "unit": "percent" + }, + "pledge": { + "quantity": 171, + "unit": "lovelace" + }, + "delisted": true, + "id": "pool1xsyzfxx4pf05akuxxttfdtk3sjyld62kht4gw3s6g6mrcc534qg" + }, + { + "metrics": { + "saturation": 3.888665033542913, + "non_myopic_member_rewards": { + "quantity": 299091110062, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 22445299, + "unit": "block" + }, + "relative_stake": { + "quantity": 66.87, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1892-07-03T06:00:00Z", + "epoch_number": 18833 + }, + "cost": { + "quantity": 79, + "unit": "lovelace" + }, + "margin": { + "quantity": 19.74, + "unit": "percent" + }, + "pledge": { + "quantity": 114, + "unit": "lovelace" + }, + "delisted": false, + "metadata": { + "homepage": "J񁕇\u0014u򬻅)X;򰁳򇙧󲃬񅦒򴠫\u001c󺍞󯾛R\u001d?}?!𽶦rN\u001b􎚨𕠄+B\u0010񶣳\u0010򉘌XqM(􆰻w\u001c\u0006@򧙂򫒗񎺔|񜂧򥂺y@;񟣒-`\u0015" + }, + "id": "pool18f3hszevx4kgx9je3qqh27323yn0kmn53jmd843qtxu66qd6p8c" + }, + { + "metrics": { + "saturation": 4.823609786214378e-2, + "non_myopic_member_rewards": { + "quantity": 933480702566, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 12901738, + "unit": "block" + }, + "relative_stake": { + "quantity": 67.03, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1902-02-08T02:17:55Z", + "epoch_number": 13097 + }, + "cost": { + "quantity": 117, + "unit": "lovelace" + }, + "margin": { + "quantity": 18.17, + "unit": "percent" + }, + "pledge": { + "quantity": 170, + "unit": "lovelace" + }, + "delisted": true, + "id": "pool13jt0rqq4jfjq8nsky5gv5n8eqt90w7kt98n8000lvyqmgttsg49" + }, + { + "metrics": { + "saturation": 2.5909355786284345, + "non_myopic_member_rewards": { + "quantity": 978277584918, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 9058469, + "unit": "block" + }, + "relative_stake": { + "quantity": 55.28, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1886-05-24T08:00:00Z", + "epoch_number": 10062 + }, + "cost": { + "quantity": 88, + "unit": "lovelace" + }, + "margin": { + "quantity": 81.31, + "unit": "percent" + }, + "pledge": { + "quantity": 31, + "unit": "lovelace" + }, + "delisted": true, + "metadata": { + "homepage": "E񜀁QUVBA񀂻𿦷򛾕c񵲮3\u0018%\u0015G񟽔\u0003}-lOU+\n!\r|򇮳񫡄^{񈧬Ih\u0007Ⱜ<𝄓", + "name": "?񝾦y}\u001b{󛵈򝣗y}cb\u001c\u001bJ󊇇3(𷌧􆛸)\u0011^#Ὴ", + "ticker": "c/E", + "description": "𮚨򀩻\u000f5%񺗲񳧛𒟆0je\u001aJ" + }, + "id": "pool1q4tla06rpe0cx3xsysfa5mr7ua3k3w75mstmcdftexjuzqxdmss" + }, + { + "metrics": { + "saturation": 0.9486761414657646, + "non_myopic_member_rewards": { + "quantity": 795684733152, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 7849237, + "unit": "block" + }, + "relative_stake": { + "quantity": 57.87, + "unit": "percent" + } + }, + "cost": { + "quantity": 216, + "unit": "lovelace" + }, + "margin": { + "quantity": 82.87, + "unit": "percent" + }, + "pledge": { + "quantity": 130, + "unit": "lovelace" + }, + "delisted": false, + "metadata": { + "homepage": "m\")F\"\u001e𱈌A\t]7", + "name": "\u001c\u000cm\u0003SO,񚤜U^H𪁉\u0016\u0004/S\t-gi'8-", + "ticker": "q=e\u0011", + "description": "Z\u0019\u0007\u001d󣳦򝕂󳖪򱔵L򨊟_6\u0015񼁦9.\nQ.Z򮱛񸍈𣖿K\u001b,\u001e\r񰀩;u\u001e#?Dc\"xi򤠻S񣙚򈥲򑫆v\u0003mO󞿩;MMP\u001c􁗌OGs񿔭O\u001a򳺲\u0006j@0|4\u0008𐣨]x𬁔}w𒈡;&q􎬅󝹬\u0002𝫚+9Mn񒡿\u0000U\u0001A\u0002\u000f\u0017c䋿򢽽AkK\rR-\u0006O񍁘h\u000e򏑴򒨚 򏑇yyN򖽌􎤀X&\u000e\u00176\u0014򐚆`a=D򻤰" + }, + "id": "pool13gr48jjtl2gn2ydnwgayxn5fpaquxvr5vf5efsxm62a86s7nyzz" + }, + { + "metrics": { + "saturation": 4.320457841388825, + "non_myopic_member_rewards": { + "quantity": 10248385195, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 11331278, + "unit": "block" + }, + "relative_stake": { + "quantity": 14.17, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1886-07-23T22:46:12.737672065491Z", + "epoch_number": 25505 + }, + "cost": { + "quantity": 64, + "unit": "lovelace" + }, + "margin": { + "quantity": 69.61, + "unit": "percent" + }, + "pledge": { + "quantity": 181, + "unit": "lovelace" + }, + "delisted": false, + "metadata": { + "homepage": "Ow򇾵:\u0007i󄦌y񗍜A^\u0016@𻲁\u0011򸁳x񯡵3񁙓򖴩񳮙\u001eJ􏙞񇩾񀗉񭃕J+,(+/GJ􂾈_$Q\u0003;M󵺆󫴍4񤒖aM#`\u001avIy@󸟏m\"j򺈫(𐡙>J;򃬎񱶝y9󼟠򁌰8𺇱W^.3#򌘬&\u000bO", + "name": "\u0001%2\u001e?V!pZv)>J|", + "ticker": "\u0008񶾧+\u0004" + }, + "id": "pool1pya76hf23a4wveqkcqkelmj35fgsnnel97futq74c2h8z0wcryp" + } + ] + }, + { + "pools": [ + { + "metrics": { + "saturation": 3.1674384602505326, + "non_myopic_member_rewards": { + "quantity": 672649754951, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 17737998, + "unit": "block" + }, + "relative_stake": { + "quantity": 1.97, + "unit": "percent" + } + }, + "cost": { + "quantity": 136, + "unit": "lovelace" + }, + "margin": { + "quantity": 90.76, + "unit": "percent" + }, + "pledge": { + "quantity": 28, + "unit": "lovelace" + }, + "delisted": false, + "metadata": { + "homepage": "\u0011򡦟󑞞OVFA@񕮶,Hpq\u0019󃊁񳩈E\u0003|󺰪AR?񦈍DG񆹓񹎋򽧙\\jNxv񪼙򌱤~\u0001l񕏂T\\=JQ", + "name": "񗝄f󢎣B]%\u00149󈰪g񚱶LAs _\u0015f򺄄*t9󟽄J&)𥛡F􌜨𑱓򌬑C\u001d'T", + "ticker": "Th\\", + "description": "s񓗽Y`򑗮񽛑s\u0003PF+🐾-M𾁖H|$a=\u000fx𲃢򪓨l\u0014򺏟󤽀uR@𰦿󒔺*򉀢񒗛Ugw񚡞񧛴\u0002@%E\u0008=+vxs#:eQ򈟉f_H&;򧀬KR;", + "ticker": "\u0017\u0018󷖎񧅶8", + "description": ",69\"\u001b藯=\t񧊞k\u00152㨋\u0011t\u0016\u0003.𤎂\u0013\n?񑉟\u001fP񩅅󢣐𘛛^Xdul-a\r_񭛳񤹄{\u00009@\u0003@\u0018򭉡1\\\u0019rH񴧢󀒫򊌜[𿗼\u001d#򛞩|S򄲕G򉂞󛒀󾴸S🼃w\u0015#򟦢sIg󥝃ise\u0011f𦖭\u00161G󎬯b\n\u0017^񇢄Wf𚩽\u0018򃇵𷻇 d@\n󀂽r,J󌫰fPwCW亭x\u0016/E" + }, + "id": "pool1vcetv548mumzmz26c840nqszyr9ahwkng2ega0s6836gzeux5y3" + }, + { + "metrics": { + "saturation": 4.028992890748087, + "non_myopic_member_rewards": { + "quantity": 198649245982, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 14796356, + "unit": "block" + }, + "relative_stake": { + "quantity": 97.35, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1891-06-19T23:07:38.49045315416Z", + "epoch_number": 27068 + }, + "cost": { + "quantity": 121, + "unit": "lovelace" + }, + "margin": { + "quantity": 9.64, + "unit": "percent" + }, + "pledge": { + "quantity": 113, + "unit": "lovelace" + }, + "delisted": false, + "metadata": { + "homepage": "\u0010𹚇#􉶶QC򣳯ಈ0u:񋜛;𜬉񋸻\u000b𢌱񄁉AS 퀀5", + "name": "TY(>'9=y<..򮕀\u000fc񬤒 񟿝I\u001e\u0010}", + "ticker": "T\u001d𫣑z", + "description": "\u0000󌷏7/-򛣙\u0013\nTJx򲂡mf񺰰+Z($􆍈\u0015𪒢\u0013L\u000b\u0015󔃹)\u000b}󃓡.QB_V\r&d𼅱򅋸!󭉗L\u0012.𨚥k2𛐤O𨙶𭒋󅷪򑻣" + }, + "id": "pool12ckr4mqplvf8r8s3nt34tcjr507rdtsylqqmxkyphxfzc7dvafx" + }, + { + "metrics": { + "saturation": 0.7331432072467392, + "non_myopic_member_rewards": { + "quantity": 813830880949, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 14737684, + "unit": "block" + }, + "relative_stake": { + "quantity": 57.94, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1892-10-13T14:00:00Z", + "epoch_number": 32337 + }, + "cost": { + "quantity": 134, + "unit": "lovelace" + }, + "margin": { + "quantity": 69.43, + "unit": "percent" + }, + "pledge": { + "quantity": 12, + "unit": "lovelace" + }, + "delisted": true, + "metadata": { + "homepage": "by\u001e\u001f񁗶f\u000b򲷿\u0011~!\u00121\u000c\u000f\u0005\u0012󚵆\\\u001al򞤳\u0019񩡉37T\u0007򴘎𥲸_󤓲󩡺񙜇)q핻񕯱&򿽪QNC+C{M񈲜=%xY\u000c𷜑l?q\u0016\\򭕬򐈓􁂉󣝱󷪙\u0019[Nv\u001d񃟱^F􉴙󄵵񗓵[/ᅛ󵥊!(Hf\\%\\\"񶤚񶗍\u001aEX񱉑", + "name": ")򂡷*2\u0014*;`v6#\\", + "ticker": "i\u0008񈵱\u0005򾑹", + "description": "B\u0004󣟒,\u000f\ro\"f5=X&\u0017K\u000ci򬦵ꝕE𡐊\u0003o䉉򦲲C$\u0018\u001fu򊇄\u0006*@\u0015򧨧}\u000f\nk$򊖬\u0012\u0019vBW\u0013񌗍T󖮇!V񸡘G񶑔\u0018𥅉sⶒ򬖋|C4\\Y\u0018X򑂲𤩤T\u0004󢄽\u0003+(e$\u0016󦓔񺙹<'\nj󶂆[|z\u0005>\u0011\u0002\u0005E\u0014𤭋򄉻򌾢\u000f,\u0006'\n\t\"񀢥\u0018둛J󃩸i\u000e(]𨥰𻋹^@HP𜜇9OWiT掍􊢅򩻠5򾼌􄭃򂽞\u0014𰷶+𑸙U􄕡򷳂򬜓UL𑯢l󎈤򱘺,򝎯UXc󍝭<@X\u0016Qgv\u0013_m\u0004l񞊾L\td󏊃򧿻\u0016Nu񩙆4fU+zf\n,is򍁋\u001c񾥅^񀔬\u001f񅷼q󓲗\u0008%=𣕜U\u001ez򰔇AD\u0015\\𷐼]6񕵕\u001c񑐄{\\a\u0008򫓙CxK`E𬅓񚃯B󮑟Dp\u0008S$𣳭N􇉲" + }, + "id": "pool1x94zuqpa0fanggvhkayc0lnq3l2dytpje9d80qk34xwfqfa3rwt" + }, + { + "metrics": { + "saturation": 2.97260677565158, + "non_myopic_member_rewards": { + "quantity": 815118397587, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 21127130, + "unit": "block" + }, + "relative_stake": { + "quantity": 25.25, + "unit": "percent" + } + }, + "cost": { + "quantity": 191, + "unit": "lovelace" + }, + "margin": { + "quantity": 9.1, + "unit": "percent" + }, + "pledge": { + "quantity": 210, + "unit": "lovelace" + }, + "delisted": false, + "metadata": { + "homepage": "񑕽t񟏪硴 ", + "name": "􇋻4.)򅛼\u0005\u000fsTy", + "ticker": "W򴬼򝂟DS", + "description": "\u001f􀨇3\u001e,𢙑j+K\u0003񘕚<~h󖔻O󵁇󑻔򤉟\u0000G)U󔏘Nqn򠇬H0IqX\u001b\u001b3信󄥘1GJ}󰈱𡧹򭉬o\u0000}zZ󬔈\tm)U3a񠢬JO󅬙ҕ" + }, + "id": "pool1mel844l5aja5zenfrh9hfwm09gv9f3rjkh0ame7xv3usqjm0nl4" + }, + { + "metrics": { + "saturation": 2.047650702289764, + "non_myopic_member_rewards": { + "quantity": 849472407436, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 5018817, + "unit": "block" + }, + "relative_stake": { + "quantity": 49.86, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1888-05-06T12:43:39.374472532636Z", + "epoch_number": 28977 + }, + "cost": { + "quantity": 229, + "unit": "lovelace" + }, + "margin": { + "quantity": 45.46, + "unit": "percent" + }, + "pledge": { + "quantity": 1, + "unit": "lovelace" + }, + "delisted": true, + "metadata": { + "homepage": "\t򓪚򲃏\rg-\u001d򎛺pF[Qt{\u0006\u001a<\u000c[󨴀\u000e𒚟񊱁\"𧳼%󗜳򳖬񎍌󑻆\u0014\u0008{\u0015", + "name": "\u0016\u0016񰂩|a\u00026g\u0007󌒺񓤀𥠘`Xy񺚁w񯳎􎰺.\u000c", + "ticker": "YWi􊿿", + "description": "(Jw9V򃉋󩦘o{4\u0008L\u0004EKOm󷽱\u0006\u0014\u0001f𤗅󂗉\u000e\u001d+\u001a\t@K𙁻5\u0003󊺀pM]um:8򉗃KH\u0013" + }, + "id": "pool1y3zp9cw97mnl6y4ak4ufg48navfwgn9dh83h2ta2mwc4geev4mu" + }, + { + "metrics": { + "saturation": 2.893620783457633, + "non_myopic_member_rewards": { + "quantity": 222615935140, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 16415905, + "unit": "block" + }, + "relative_stake": { + "quantity": 38.4, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1880-07-22T11:09:27.320389004833Z", + "epoch_number": 23567 + }, + "cost": { + "quantity": 183, + "unit": "lovelace" + }, + "margin": { + "quantity": 77.59, + "unit": "percent" + }, + "pledge": { + "quantity": 97, + "unit": "lovelace" + }, + "delisted": false, + "metadata": { + "homepage": "/T\u0016C򡧉\u0003)𫗉󮒞\u0010fH󊰑[񣿟\u000e􌯻񻐌q󦐑𡻐򜻖;ᄄT:񪆀DI%4(򦠸#9\u0019k\u000e\u0011k\u0017(i󧌔V󳯕𳜀򀖌PgV򉰙cfrY񜿅nb,򭦠𽳏⹬kl􁧘L񾽴", + "name": "L􈦇t9\u00140kKm嵉󮃏\u000fW\u001d\u0010 |\u0007𬱣~񟵹)〾\"𦡴8𐜇\\)|[+L1󙪖\u0004jd\u0001]YS9\u0019", + "ticker": "S[񤹆", + "description": "\u001fw\u0016J%,V󢃳렰h3\u001fI񺞃\u0001QVK񟧬9P-\u0013YiN`񅚌tSM𥺫𑇂]\u0012\u000b񍔘1=SE'/_]\u0019􆟐tF\u0003zl2\u000e􌣷\u0004񉦙\u001brKf\u001bg)" + }, + "id": "pool172hh8lt29er43mumn7y28drmwpxpjyn3vtfack20xy26j5w7h4y" + }, + { + "metrics": { + "saturation": 1.139355244532414, + "non_myopic_member_rewards": { + "quantity": 738847662176, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 5592457, + "unit": "block" + }, + "relative_stake": { + "quantity": 2.27, + "unit": "percent" + } + }, + "cost": { + "quantity": 151, + "unit": "lovelace" + }, + "margin": { + "quantity": 82.59, + "unit": "percent" + }, + "pledge": { + "quantity": 126, + "unit": "lovelace" + }, + "delisted": true, + "metadata": { + "homepage": "\u0016~\ro*\u0002򨨠V򔓱\u0007񛇛\u000fP잢񯇲.+𹅉)\u0000mz~\u001e\"48񆻻Y򴛘vXk\u0003򤺬\u0015񐁭q\u0007񗊛򴾇B,㆘t𼖫\"]]W2$򠄐O񉈏\n+\u0008𯴸oDvnz\n8\t>\u001b#4J\u0007l􏖩\u0010\u001f}Mh\u000c\u0005(=𗢳5ᰌ8\u001cL񽳤", + "name": "\th񅟇/\u0001lB|<", + "ticker": "\"񐗨hs􄧀", + "description": "r󆳡l\u0003\u0000\u0016M>Yx񹈈R򟻑𫙺\t򝽏M0򺶹󠆨𫝱q`o\u0002\r񵑩[\u001dZ\u0013񠐡\u001a`u򼃃󺅳F􂶅񱺹7;\u0018l\u001e\u001f񭢔A򵕎󄶹U𐄖yᮢL냔\u000cvg􁏅-v\u001cRN𐬫=\u0013M/񜣷\u0017\u0001?\t򝀇y}w\u0007򯮞vY>/핆񙌦U\u0016oC\u001e\u0004𩞜j\u00191+󔁑j\u0005\u0004􎜇}𩔽S򖡃󻟵=򤘱\u0012e񹦖U𴴺%eI\u0016🅳\u001f𾬆\u0000񬻁\u0018(J]e򟪛$󗧈򽨻󜊁8􋯹72ixP3/*1,\u0012𬣤?\u0006񝝺\u001e򏳴\\󌔪\u0018PjP43S\u0018" + }, + "id": "pool1aqmrq4c3rgrssxv949yzx9xevmwl0hggwte0ew8pwvdn5chhs9j" + }, + { + "metrics": { + "saturation": 4.484787358982117, + "non_myopic_member_rewards": { + "quantity": 341434316241, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 17473550, + "unit": "block" + }, + "relative_stake": { + "quantity": 36.7, + "unit": "percent" + } + }, + "cost": { + "quantity": 243, + "unit": "lovelace" + }, + "margin": { + "quantity": 36.93, + "unit": "percent" + }, + "pledge": { + "quantity": 50, + "unit": "lovelace" + }, + "delisted": false, + "metadata": { + "homepage": "򆚗k󃟧\u0007$p\u001a𹿧DS\u0019R򵇽򥲊򾟨m𣶐-V󜕟\u000f[󽶈cGY\u0017)", + "name": "H\u000f򻡠yD𦻒甦F!9\u0008\u0012dC󕱆񃦑-\r#Z|𹷕\u0007\u001b􄲦(2%p<\u001e]\r򯖬򛦓򒙧\u0014/񘵫\r󸆻\u0001:\u0003\u0008", + "ticker": "h񃕐󈒹\u0019\u0013", + "description": "\u0015\u0001\u001fe0\u0013񑨆\u0012<\r󃣨8[m\u0018\u001fc󟢈􂐛tB󜞳\u0015񈊦H𘣫0򹄼K,IDL\r?y񫺧𬞜\u0015$>\u0005󛖨\u001a󊒀\u0014i\u000b򧶇R\u001b\u0006{b񿌾\\OZ\u0008n5:^k񈝏񤰎\u000c:\u0017\u001c", + "name": "򙓹󧴷fFr<.󮫩o򪠋\u001bJ󼰈\\\u000b>\u0015\u0007򺄋\u000f\u001bCP񰸥wx#Q/䁇I", + "ticker": "\u0017򺷝񫐘Q", + "description": "󥕉q#n\"􁉃F\u0017`3A+`<,򷀟󞗊𴕘񈥐Fp'\u0007򔳜J-\u0003򷚇0~[𫽃]\u0016\u001b󲱱K'^򩌋!&)}񽳯\u000f\u000f&l򕄩񼚭o\u001f\u0018\u001e󩅑𣳵c!\u0010p򒆢8򳁞\u0006P򧯱;KGﲿ񀙃Z\u000b\rZ\nH_p 񪥻qG>0\u0006zQ򄉙?򒵳\u001d𕛒񳃮~񐤺P\u0017?t" + }, + "id": "pool1mptdfctf7xhclj8x6zx0x4kepd2kutg99vp0mzw9wfruzx6kkk3" + }, + { + "metrics": { + "saturation": 2.027664401757319, + "non_myopic_member_rewards": { + "quantity": 996298896377, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 2898160, + "unit": "block" + }, + "relative_stake": { + "quantity": 85.68, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1870-06-18T06:00:00Z", + "epoch_number": 23474 + }, + "cost": { + "quantity": 154, + "unit": "lovelace" + }, + "margin": { + "quantity": 88.45, + "unit": "percent" + }, + "pledge": { + "quantity": 111, + "unit": "lovelace" + }, + "delisted": false, + "metadata": { + "homepage": "}0X򓱂b\u0004;S\u0011=/񴣛d\r\u000f􆗿U󮫊󤥁`𒝍tPa){\u001a]a@`@\u001d\u000eWt󝛶\u001eW􃄪\u0018\u000f\u0006u𿞹X4\u0016aPdM+q99󖓽Jx􇵜񛞉L=󕱥vd򳙏+^{)1񷹽e򲘄w$򣬰\u0011\u0018\u000fq(𷮰􌗰1f𤻼R򱝵K\u001b{", + "name": "񑚆\u000bYu򀰴򷞇\u001b翣>񆙖;Xr*𔒰\rKX*[h_n𤓥󪣘.򩌾*uM\u001f{|\u0012\"fsdlf򄨼7z񳯬򆺡0[", + "ticker": "(a􋮻\\", + "description": "򐮸\u0011r㭲0𠄮mW[Y򌢖􏿺}󯃲}󘅃*\u000cp[󖉀𰴷,~?Y1R󡧖)򓈊􈍵>)\\WHjj\u0006񤠳\u0013\r񡩗l򛖉󡆮7d/Oavt{\u0002Pr&Q{`vZJi;񻊽\u0001]+򧬭On򮏶k򞵏L\u0012r򉿆3񓲽eb6" + }, + "id": "pool1yzrhljw3fhlgjyssznrlvwwaynad84f6l99trurxmhvm73wqlf5" + }, + { + "metrics": { + "saturation": 4.1751661223912215, + "non_myopic_member_rewards": { + "quantity": 252804970937, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 22233578, + "unit": "block" + }, + "relative_stake": { + "quantity": 58.94, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1874-07-07T17:03:39Z", + "epoch_number": 19325 + }, + "cost": { + "quantity": 40, + "unit": "lovelace" + }, + "margin": { + "quantity": 96.46, + "unit": "percent" + }, + "pledge": { + "quantity": 121, + "unit": "lovelace" + }, + "delisted": true, + "metadata": { + "homepage": "\u0006󡫲", + "name": "񪊭\u000c-O", + "ticker": "𡠙{\"" + }, + "id": "pool1e9uwm4xucwkns5hsujh75jtvj5e04dnfg7wglgwxk2vpqqehr4w" + }, + { + "metrics": { + "saturation": 2.191211709950399, + "non_myopic_member_rewards": { + "quantity": 705103116656, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 3921006, + "unit": "block" + }, + "relative_stake": { + "quantity": 52.5, + "unit": "percent" + } + }, + "cost": { + "quantity": 186, + "unit": "lovelace" + }, + "margin": { + "quantity": 43.38, + "unit": "percent" + }, + "pledge": { + "quantity": 233, + "unit": "lovelace" + }, + "delisted": false, + "id": "pool1ptp60cy8pss7yel5wamhnj3kds42cnd64tl75vmmck2w68fzkt7" + }, + { + "metrics": { + "saturation": 4.792535280765888, + "non_myopic_member_rewards": { + "quantity": 355409073571, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 20915880, + "unit": "block" + }, + "relative_stake": { + "quantity": 9.96, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1899-12-30T07:52:07.19614811522Z", + "epoch_number": 19645 + }, + "cost": { + "quantity": 138, + "unit": "lovelace" + }, + "margin": { + "quantity": 31.72, + "unit": "percent" + }, + "pledge": { + "quantity": 191, + "unit": "lovelace" + }, + "delisted": false, + "metadata": { + "homepage": "%6}􌟭P򑶒8󾲚\u0006Qa0@\\6;~\u001c\u0013r񧳚󿖛\u001a\u001b\u000b\u001b񟖔򈷓W\u0000=󐡽|*\u001do򛋠򰥶\u0003󊢡󣨴򑱣!\u001b", + "name": "􋱒񩙍\u001fꌮ򞮿񴧷񸘠T󈺿򎈬la\n\u0001򴺞\n", + "ticker": "c\u001f\u000fD", + "description": "\u000e𩈼L9Y\u0011$󊞄 /}\u001bT\u0008򽿡YD\u001aWgn󇒖F\u0018/𬥴>񋐌񫸺\u0019\u000b\u001f\u0003o\r>x\u000614􇃓􂼻dtC󵣇B[(t򱍿<>\u001a򛳿=~Y򇻥\u0015򷖷SIAB󂔫0z󯣜󤆍W8\u0012󖊚󅂯[v\u000fPh\u000c\u001b򍗇,IPlQ)'\u001cP\u0013򗝇\u001a" + }, + "id": "pool1yg6thknkwy9g2nz2r692673846k54ky6jljh9ftqm4vk6qq6y36" + }, + { + "metrics": { + "saturation": 0.6658801259460828, + "non_myopic_member_rewards": { + "quantity": 128527682280, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 21887153, + "unit": "block" + }, + "relative_stake": { + "quantity": 53.35, + "unit": "percent" + } + }, + "cost": { + "quantity": 18, + "unit": "lovelace" + }, + "margin": { + "quantity": 23.62, + "unit": "percent" + }, + "pledge": { + "quantity": 113, + "unit": "lovelace" + }, + "delisted": true, + "metadata": { + "homepage": "񄺆t􄁄i󙟋\u0011􂚿`<𱲕\u001an31A?\u0013X?.\n󹏒W\u0001\n򫁩A󛌡C􉮆\u0001&|=\td\\󰴾񷷦󰋤X[\u000b񩅹\u001f𔊒󫍞M򨧀LxvAuo󴈿#", + "name": "𧢊a\u001e?U@CF񿃤JgHḧz\u00071v󥗯Lli𻤃\u001f\u0003񱐤\u0005񨩝󴲖\u001es\rA񼜄`\u0003x򕹃򆭠򸮥JLR'cnWnWz", + "ticker": "\u0003򡺩1񄄲", + "description": "o\t\u0007\u00019C\u0019V)S-j􉹚򺩀9x򣻟򵻋𥓲~򡉤G\u0007񛻔񪏟h񥎿\t\u0013P\u0003\u000eQGe锇0𒀯!򈪱'f\u0000𝡦)򎝷񢅣\u0013\r򿍣?*y\u0014\u001a񌁮\u0011L}q󃄎a6\u0019C򚬥󐞯3󳨓inYPa󋸣񰀵\u0017S%\u0013\\󼡙hP\u0008T!𝑹W󁆥\u0017\u000c1󱨑򈄁򁂣j򀡄񒊄<{\u001e򁠺\u00183񣻁#\u0015\"l󹱣?zJ\tc𐛽Aa񶍞󕪍,󩭜K𜷈񵥹S\u0001󉧲\rE/FER󺖝񱷢򠇻e*\u001eV#Wv\u0004#\u0001IfB𹂬\u0002򴮩HD\u00012\u0018񘲷\u0004򠵢2%) |D񒖸𑜿[o\u0019\u000e9򀴭\u0010񲍱/\u001ddD W1򛮈m\u0001󢸈y_J󂖱y%-ndTK󦆁\u0003󄶐^" + }, + "id": "pool1ct2ly2my4h5dnuf0uqtq6aq5q6lxyella5g48q3wg23hz5425q0" + }, + { + "metrics": { + "saturation": 1.3303565969250024, + "non_myopic_member_rewards": { + "quantity": 414306773623, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 9737256, + "unit": "block" + }, + "relative_stake": { + "quantity": 95.74, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1880-11-22T19:00:00Z", + "epoch_number": 19987 + }, + "cost": { + "quantity": 234, + "unit": "lovelace" + }, + "margin": { + "quantity": 53.71, + "unit": "percent" + }, + "pledge": { + "quantity": 202, + "unit": "lovelace" + }, + "delisted": true, + "id": "pool1dfqcgfh75zxs0fltncazjzez4w6psyaagnq8zalha3r968pxg8u" + }, + { + "metrics": { + "saturation": 3.109595456147728, + "non_myopic_member_rewards": { + "quantity": 597330890423, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 22565413, + "unit": "block" + }, + "relative_stake": { + "quantity": 48.9, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1864-12-29T12:00:00Z", + "epoch_number": 22081 + }, + "cost": { + "quantity": 85, + "unit": "lovelace" + }, + "margin": { + "quantity": 15.21, + "unit": "percent" + }, + "pledge": { + "quantity": 211, + "unit": "lovelace" + }, + "delisted": false, + "metadata": { + "homepage": "o\\\u0003#򈉢u򻵼󅋟\r1\u0002񩰺R􅡩󚛆󘺒f^􉿽!4GE\tR b𹙗)W%윑:-D񭉩zT􎺗󟕘Mx'𺡝#\u0006CzhZ^󋼨qg#󴸮", + "name": "b\u0015un", + "ticker": "򡎈\u0010_", + "description": "\u0004񣄏\\y\u0006k􅨥m*:d-\u0004l\"7\u0014n]\u0007J􈔂񹹌!;񀤳\u0016got󬩎G\u0001\u0006񜩅\u0012'j\u000e#񁻫񮸞(GX񴬟-X7P&򼷿𛼂5񯟸.7v}\u0003s\u00199)𹸻},\u0005󥥇򻽞7+j]mH󑓎X{^\u0007󮍱A9\u0007\t\u0000@񗻷1m𜽐" + }, + "id": "pool14q5ts8kwwxahj3z5yl4dr3slee9hp6m0k8fnnjjhqz9pvmk80a4" + }, + { + "metrics": { + "saturation": 2.1539159330820867, + "non_myopic_member_rewards": { + "quantity": 861417427455, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 5531834, + "unit": "block" + }, + "relative_stake": { + "quantity": 27.05, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1869-06-18T14:50:33.809139934957Z", + "epoch_number": 1623 + }, + "cost": { + "quantity": 10, + "unit": "lovelace" + }, + "margin": { + "quantity": 7.67, + "unit": "percent" + }, + "pledge": { + "quantity": 1, + "unit": "lovelace" + }, + "delisted": false, + "metadata": { + "homepage": "󨞐\u0011\u001d\u001b򵐰Q򢌋G󎨯򜱈i򏪎g𲯙c\u00003񽽶f\u0011u񘧭􄹂2󡟬\u0006񴞞\u0015H\u0019𩏅XK\u0008񉭬JN\u0016쪟", + "name": "/^\u0015󧅟𮓟\"\u0011a\\J􏳓M򸛸\"򆺳hHg5򊱥1$2e:\u001e", + "ticker": "񣯄\u001fiQ", + "description": "&f\n𹁣\"󗓛Y4\u001d񜑨2?𤭛\u0015\u000e򿑦v󳫃p`r󑑙X}!񜜑򪿪/UMgE䓲}?\u001e\u0010\u000ew󸙵𘎑\u001e.𑢬u򫓗=򍨠򙒯󚎑\u0001\u000e\u0015>񖜁^3\u0008w\\󎸐3\u0008Wttit\r\u0006A\u0019򚎬R񍖥d򱁿-𥺡𠒶\u0004\u001b񯹙T񍻬Q%iI\u0010򴨷j\t(\u0008'e󣖳p2)\u001a\u000b񝵡\u001d9lo&'񉩟I7A\u001f~&\r\u0008l𤝳ZS򔝮Zu,󽊔󕍽񃶸T∡󴦕A\u0004򸪋\u001d*P\u0007|T\u0019\u0017􌜙\u0018󄪆ve\u0018\u0011 h𬷤\u000e򷑴񟯹=3񳀏MmuPk7ZܮlW􆪉:\u0018򫄘𭾘뎧LGX񲨻󱹔^:*}iA𰿄\u0004l\u000b󑀡\u0005DYlKT򄫖@񟪅\u001a򇪬\u0016oz\u001b\u0005m񀚎[gW4\u001f\u001d/\u0015\u0017𳰑\u0008H)񔠿Eo0f>S򹋯󆚁򓿾\r򂊥.\r򙿮^􃲴\tG2򈫒" + }, + "id": "pool10n4r2k66jfzmmsym6kr0n22nuqjc4hm46deajwqq2hcwk8numy9" + }, + { + "metrics": { + "saturation": 1.6980786943221193, + "non_myopic_member_rewards": { + "quantity": 248704373905, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 12995460, + "unit": "block" + }, + "relative_stake": { + "quantity": 11.47, + "unit": "percent" + } + }, + "cost": { + "quantity": 162, + "unit": "lovelace" + }, + "margin": { + "quantity": 44.78, + "unit": "percent" + }, + "pledge": { + "quantity": 231, + "unit": "lovelace" + }, + "delisted": false, + "id": "pool16efejatdg3yf7dk8e2pml6cjmcs69xqwrkna4462wdtsufc76yy" + }, + { + "metrics": { + "saturation": 3.220200756946721, + "non_myopic_member_rewards": { + "quantity": 744051606323, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 14827544, + "unit": "block" + }, + "relative_stake": { + "quantity": 0.87, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1904-09-18T22:00:00Z", + "epoch_number": 8693 + }, + "cost": { + "quantity": 193, + "unit": "lovelace" + }, + "margin": { + "quantity": 93.63, + "unit": "percent" + }, + "pledge": { + "quantity": 43, + "unit": "lovelace" + }, + "delisted": false, + "metadata": { + "homepage": "[󨗆󂖝󻺜񤨌𛵯LsL󈣵U5񝂭p)(n󉊬T#\u0019%Nz\nꅔ(n\u001c򢩨H(*6\u001f<򆿝\n􃉢\u0013xu1\\#󥶢𱾷5𗃂k;𔚤򰃏@)x򻵣A\u0001-[󖩀", + "name": "1󤄱*c\u000ce.󦨡\u001b򊒐9\r\u0007o", + "ticker": "e\"Yf񳶬", + "description": "𻤵y􄄊󋜢x/EHw{񊡃\u0011C񉯈hI6\u0019#aῖH&\u001b~𽪅\\򽹰\u000f\u0014K􂡂񙳷\u0011}K󇝑)^]#R/qR𣰅\u0008󷱬%\u000e\u0004,񌶠5\u0001\u001e󳎓\u0018]񽅽󿻕i𲗅S@\u001c󪰿\\=[R/\u0011$\u0014nZ󺉠R򈏮𞝥,>ゲ\u001b3Y𚜒7s񏿓닒_CFQfh\"LQ\u0007񚣍򞞩𒉓@G*\u0018\u0002򽊻au𑸁{F𩃱\u000e򱕒6@I>5\u0000m񘣱V!kD{\u0004񞨢T5 p`\u0013c𜠯O6񧡃Vn\u0017D1@\u001dC&E\u0010'򕜟1\u0018\\}Dm>F󂺰_\u0001򗊩=򫰥񋙁i=򛄅e\u0005𴟽;nn?\nE)曟G񴕹PKb?󟷊񶜋󠅬Y D㷥w?140\n7@", + "description": "XDF~D\u001evka{󕈡s𿜣-\u001bn\u0004^\r+$뀬󛙴%G\u0010_\u0000k񉤌򕛪a\u0001o\\z\u001d}\u001d𘄂&`\u0018\u000fGqQj$􂻼\u000f\u0014m&xZ&U\u001d񺐥qH^\u001d\u0008\u0007󚱚s\u0015t򖻎\u0005\u00127\u001dk=򵄤_;\u0008?;\u0006!𐶪\u0007Y#q^Co쭬\u0010\u000e\u0003-Fo񾅱o𛎍\u0015(=\u0016\u0006󂖧k7T\u0019V-y+\u001cS񰂱󯊤L񊜖\u0006`l!1_|\u0001_a.򫘻\u000c+\u000bat7\u0016~\u000c-|𞿎񏐯j\n\u001aHI󏦧ful\u0001\u000bR\u0007\u000ftH\u001dW}mM󵪐󷑿S񅎫Ba{J𼽁󖱛𧧩󢠩,!?򎵂􆪖xo򠯦񌍽\u0010\u000f񠓱\u0007𯚹򏯧\u0003\u0005񕃌g񚞒\u0005hnKV*f\u0001H>򯵿?򩢂􏩫B\u000e𡊥񿸒.q񨈠`󨙸񓜗Y\u001c\u0012􍃩񉍹S5|>򥇷Ni_-󫹊!k_򸛟6Wn^\u001c󵀚*󢡍EyT\u0013", + "name": "e`0i4@^'\"󝎙򈍬󮦓󊦚\u0008򑓳sj\u00194\u0003';H󶷕\u0006\u001a", + "ticker": "5𕘀=", + "description": "\u000e\u001b/𵿾J9b󯳥\u001dC/?y⭵C7\u0014M񃧮񉏏\u0017ggXv󤀣3󺔃򘚣RY񩕪\u00123󣥶t 󖟮a\u0012\u0018/EY=(xE\u001cVH$򬚧IG󿾷񐲵.\u0013\"\"<&n>P𼒉Aj󁴍" + }, + "id": "pool1c9jqtkjplzvyyr7d3at9t4xhqalw5u49knue58qr9jswgxumjqh" + }, + { + "metrics": { + "saturation": 2.8220190771005003, + "non_myopic_member_rewards": { + "quantity": 486272784210, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 16610990, + "unit": "block" + }, + "relative_stake": { + "quantity": 48.81, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1880-10-30T00:00:00Z", + "epoch_number": 1707 + }, + "cost": { + "quantity": 231, + "unit": "lovelace" + }, + "margin": { + "quantity": 7.85, + "unit": "percent" + }, + "pledge": { + "quantity": 207, + "unit": "lovelace" + }, + "delisted": true, + "metadata": { + "homepage": "\u0006\u001f񪠿i`eMr%'򼁀R]b4\u000eA\u0013\u0010z񾪏1ᥩASxGn󕊍zX󛞽UO񃶴&\\>jq{M#C򋀠\u0017񄜶4񮽋\u000b~k", + "name": "_<-\u0010O􉛊r󹻅\u0003򘕏mm\u0001?\u0004\u0011ﭩ;,E\u0001\u000c𓉔\u001c\u0017򲡯f;\u0018&y\u0018K+n𛾞\u0019cM󴀾2񼍤", + "ticker": "F(%􀟏\u000b", + "description": "󭐿&\u000b򞊸🞥󹼕x\n󁭹p[U\u0015𩿯A\u000fo򓸉\u0012_򁤆9Jk\u0008`3E󯫍D\u00068\u0016w󸭏Aw!:􅝃񓳣p􌷭\u001c\\>򵗲)3J(;b񨪋񅡻%" + }, + "id": "pool1jxgr3vkd24wmqsp4vh9ayfmhfq52wph4pnymcpa5cvqaye3qwaq" + }, + { + "metrics": { + "saturation": 3.1071825072904122, + "non_myopic_member_rewards": { + "quantity": 265870398862, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 19792023, + "unit": "block" + }, + "relative_stake": { + "quantity": 38.63, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1901-05-05T02:57:58.955473977949Z", + "epoch_number": 24201 + }, + "cost": { + "quantity": 254, + "unit": "lovelace" + }, + "margin": { + "quantity": 25.55, + "unit": "percent" + }, + "pledge": { + "quantity": 252, + "unit": "lovelace" + }, + "delisted": true, + "id": "pool1xaak7fwk7p3lqq3u4twuj2gpwlwjew2ajm84rggp2c9yge0j3ys" + }, + { + "metrics": { + "saturation": 0.7409671860250505, + "non_myopic_member_rewards": { + "quantity": 962524453742, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 1964670, + "unit": "block" + }, + "relative_stake": { + "quantity": 99.79, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1878-02-17T02:00:00Z", + "epoch_number": 18230 + }, + "cost": { + "quantity": 41, + "unit": "lovelace" + }, + "margin": { + "quantity": 16.56, + "unit": "percent" + }, + "pledge": { + "quantity": 232, + "unit": "lovelace" + }, + "delisted": true, + "id": "pool1qef44e8hv6kzpzqy8d72472xnmsu5g84csy26d8qw57r59pcm8j" + }, + { + "metrics": { + "saturation": 7.47359277157944e-2, + "non_myopic_member_rewards": { + "quantity": 832905742979, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 11702195, + "unit": "block" + }, + "relative_stake": { + "quantity": 52.72, + "unit": "percent" + } + }, + "cost": { + "quantity": 59, + "unit": "lovelace" + }, + "margin": { + "quantity": 66.69, + "unit": "percent" + }, + "pledge": { + "quantity": 68, + "unit": "lovelace" + }, + "delisted": true, + "metadata": { + "homepage": "㟞Djp񋭚󂸘񽭌𠳲5??$\u000b/񼛷O\u0014\u0003㓋馛.\u0005^W\u000c򾋘E\u0013􏡙󥮃𯄼", + "name": "1𝷄\u0013-F𗂿\u0014Rn\u0002*)6X򅐖񪍢󭘹󥎨񄶻D`~񿜑󽅆]\\K򇧈뼠󎗛抙񏻋񧯩|\r)\u0015򎀊\r,𷕞󻃉", + "ticker": "U\u000e}ᡠ򥾻", + "description": "M]/j3oE\u0000񷷅&=\rD\u0018NdW\u0000 ,Le\u001be]_.񑈦\u0007\u0002aJW\n򔟚󢩹𲙥\n3C򈧟" + }, + "id": "pool1le6ttplpxcpfw4jvuaqy6x40vzx874jkmxzz9dxpf49mzj8kqg7" + }, + { + "metrics": { + "saturation": 0.7930162147443875, + "non_myopic_member_rewards": { + "quantity": 626613423680, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 17804852, + "unit": "block" + }, + "relative_stake": { + "quantity": 12.19, + "unit": "percent" + } + }, + "cost": { + "quantity": 62, + "unit": "lovelace" + }, + "margin": { + "quantity": 37.02, + "unit": "percent" + }, + "pledge": { + "quantity": 23, + "unit": "lovelace" + }, + "delisted": false, + "metadata": { + "homepage": "\u000e\u0005x𠎖񹲈o{\u000e", + "name": "(\u0001\u0016Y𳿑񛎟\u0003񡯊\u0019\u0003\u000b\n.\u00155𼞆\u0004K{񃳕e\u000fJ\u0016", + "ticker": "lp1", + "description": "􇷽-󼸱s\u0010\u001e\\쉠\u0012(-􀧸򥖚󢼩󺾓h\u0015񍭷:bLRux𹇱l\u0014񻙸򁧠.𧘍m8\u0013kFf񶞿񞚪`񫿦u򴼽=Z񨿽Y\u001a4𩐋\u0019򓁏kXk񩯒=󬋦XF[=nb\t SF\u0010𢼊F\u000eJ4$㯲𑔅g\u000b򋣪AC\u0013򎋾2u񦜅\u0011\u000be>\u001dB\u00050򳻠(\u0007S\u0017Am_PG[򡊺[tWN$󨥳J6N򾋗\u0003'B]?X@iy)6s󄼡.򎎹=󤲚񻷅~;󉭰\u0000B򰎤򑦑\u0014;8z&獝󠣩𓴡󦻵0\u0012\u0013󨊶򱋘\u001eD󔨀\u000e\u0000M4􊱆\u0000\t2aj45S%T!!\u001dnPEyw񗖈\r򞀔(LI𻱣t*m󀐵󲅄瞿<^A\neM?lV'\u001c\u0007򘪪0V񊔱񉠸f񿈼a\u001d:}9M2󞌶\u001cpDX󧶻񯃲U1N󹴷o&󱆷𔘕󟕅𴢗獐\u00010鵜c򕆒 " + }, + "id": "pool1l8rnvtkfpy06mxn9sfya0j9t3hmm3ykhqgah84gjghpwwd3qve7" + }, + { + "metrics": { + "saturation": 1.7526075052673034, + "non_myopic_member_rewards": { + "quantity": 637982204233, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 18340465, + "unit": "block" + }, + "relative_stake": { + "quantity": 89.8, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1903-07-12T05:51:30Z", + "epoch_number": 10709 + }, + "cost": { + "quantity": 57, + "unit": "lovelace" + }, + "margin": { + "quantity": 2.77, + "unit": "percent" + }, + "pledge": { + "quantity": 245, + "unit": "lovelace" + }, + "delisted": false, + "metadata": { + "homepage": "򭥦S𔲥xN\u0010FK\u001d8N'&\u0019󺒺\u000e𭕊𣜩\u0013򸞂1񑫖'&\u0006ah\u0012򗻎󈫟\u0001Q9\u0015&?`\u001d3u\n󪳲򤘌\u0019@󕋯K\u001a󳔩+e[􁟡=Q򇾍=(4\u0015XR^: 񅪶{l\u001cc[󒛶*񨡌\u0013-\u001a񕔣'<\u001aC0\u0008􈔀v_f󬺐w𹩦󰫓\u001dr\\Q", + "name": "\tDQ򺣔b\u0004jJ\u000e\u0005񃫒MdI󏗼l򺟰 u󤯔\nBR󅩼d𽠇8򭮅񒱌", + "ticker": "\u0012y\u0015Y", + "description": "h񉰳[Xu!􏀤\"!n\u0004OR򑿧\u0017z膼^񑿚7\u0003{#1ɠ𭤽3􆺸򉊬6K" + }, + "id": "pool1xdutwd8kay0lnxkur98jmmna28gg3m47xtjke4hmag50gxzwkkg" + } + ], + "gc_status": { + "status": "has_run", + "last_run": "1883-11-22T10:58:53Z" + } + }, + { + "pools": [ + { + "metrics": { + "saturation": 4.084682659563115, + "non_myopic_member_rewards": { + "quantity": 820659256833, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 5004462, + "unit": "block" + }, + "relative_stake": { + "quantity": 15.12, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1889-11-02T00:17:00.873337537978Z", + "epoch_number": 11546 + }, + "cost": { + "quantity": 178, + "unit": "lovelace" + }, + "margin": { + "quantity": 76.77, + "unit": "percent" + }, + "pledge": { + "quantity": 89, + "unit": "lovelace" + }, + "delisted": false, + "metadata": { + "homepage": "񚫮V0󄃐kFoSz󻙵򈑆󘯞6yF1h}0D2d]𝈓𪗋LEX BL}󲄞Z\u0011񐹣c\u000b8༚j󉩢{𪀙񋧾񼭒:9h\u0014\u0001𤽾w", + "name": "*\u0003\u0004i𰼐pY񺹦񽊾F\u0005*🃇P6򅊳.,𳾟qMDfK<򟮢&\u0018d􈼚u\u00032n&񉰬\u001c5󍪯󁽐\u001arp񥰛=U~(r\u0012󜎧\u0001\u001f󠥐T#𮜊N/kkN򯄫X\u001aL\rxE񥽦J" + }, + "id": "pool17w070w7syu7gvm7mpkypl8c87jdj68mhm52ukxmuajrgg3rc2mk" + }, + { + "metrics": { + "saturation": 1.1425815537039425, + "non_myopic_member_rewards": { + "quantity": 176308315599, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 6272262, + "unit": "block" + }, + "relative_stake": { + "quantity": 99.21, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1864-12-18T12:02:27Z", + "epoch_number": 23289 + }, + "cost": { + "quantity": 215, + "unit": "lovelace" + }, + "margin": { + "quantity": 37.29, + "unit": "percent" + }, + "pledge": { + "quantity": 125, + "unit": "lovelace" + }, + "delisted": true, + "id": "pool147g559k35uc8ewc7sql4z5f8y450w48yxrlsc0p4u9apylw9y4y" + }, + { + "metrics": { + "saturation": 1.0082952772373233, + "non_myopic_member_rewards": { + "quantity": 12254426176, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 10080712, + "unit": "block" + }, + "relative_stake": { + "quantity": 62.82, + "unit": "percent" + } + }, + "cost": { + "quantity": 168, + "unit": "lovelace" + }, + "margin": { + "quantity": 62.2, + "unit": "percent" + }, + "pledge": { + "quantity": 162, + "unit": "lovelace" + }, + "delisted": true, + "metadata": { + "homepage": "?]񷊲񈒐JJrK񲬙rd?e񗯆o%򉕔\n\u0000L%t{}􀧗O󌗼}🺈\u0017󦹨󝃗򡈼S98趴tn\u0006񇂟e\u0005uI𕴄j\u0015񂳇\u0018򊅅;􃥑󜠾t򻻡@𗡁𼢀xg\u0007UA񍞠B\r\u001d򣾆7UF𘼢򎯢W\u000e򠿱cm\u0008cP梒#􋺷q\u0002`XS򕒘\u0005\u001e𚒉'", + "name": "1O\u0015\u001dFL\u0002\u0007q-BO+\u001a6;򺫥[yn }Kn󨼣򯲼󿽫\u000f\r󳟣13\u0000񼆢򝘟\u001ba\u0016(\u0001E\u001a)\u0016s", + "ticker": "C𝶊\u001e򢾎", + "description": "𹳤\"\u0017\u0000\u000c\n8 Krl{\u0014b󥊑=\u000e\u000frf\u0013_9z:#\u000e򺦦\u000f񸕽BIH|\u0019 \u0016򜆏1D&w{𐀭񰵸[L2\u0001{\u001dl񪱟32\t:𽏲񗽉CBCe𲿀~e򱃛f`𥤖W篊\u0006񳳒7􀘒\t>mR\u000fZ\u0004񜗎{7OY񦚦\u001e񔒂&Zz􊛏\u0013񸨲w\u0006\u000c􃉣󿋂􊢌󆥌pn󜏤ꜙmi򜉙)EM𱹱}񖄇\nsl+Cr񛰷\u0015𨐷𖡊񥈺|B񬾝,G󡭵𡩢(\u0012x\u0013\t \t\u0005񿔪Y󓏭~Z񫵱𐙢\u000b" + }, + "id": "pool10jr3gref8s0hzdzh8jvcvaykx9eyh4lgn3d424uzvk9m75arjs9" + } + ], + "gc_status": { + "status": "has_run", + "last_run": "1889-11-06T07:43:13.860207111408Z" + } + }, + { + "pools": [ + { + "metrics": { + "saturation": 4.172407150961861, + "non_myopic_member_rewards": { + "quantity": 342437008583, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 7391890, + "unit": "block" + }, + "relative_stake": { + "quantity": 17.8, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1903-09-16T00:49:23.362415198811Z", + "epoch_number": 9393 + }, + "cost": { + "quantity": 254, + "unit": "lovelace" + }, + "margin": { + "quantity": 97.61, + "unit": "percent" + }, + "pledge": { + "quantity": 146, + "unit": "lovelace" + }, + "delisted": true, + "metadata": { + "homepage": "(񭱳\u0000򤧩M2򛣫8󑆟\u0018l򄯘TqI\u0018񁅏\u0017񰛽jwt0-񢰏\u001a𹊶񂕽\u0001󟵮\u0008\u0004/􇅂\u0004p#񗪡w󡜆\u0006\u00195󽲮D\u000b󣓯B\u0010\u001d,(p򢁨𘛋Q\u0008\"򮓪]Pw{L\u001cr8(T-C\u0011f񃉣𽬳O]c", + "name": "񺦁g8=𷉐e򱡕Oꄽ,=\u0008\u001c$-@06\u000b&tl\n\u0015\u0019]𯊙&4QN\u000c\u0007&k\u001e6\r2'򹈠\u001c", + "ticker": "S󰝤󥳝" + }, + "id": "pool12030cgker8rywsrhqujan278v9refh4qsas6d5ldfv087xtplly" + }, + { + "metrics": { + "saturation": 1.0240958168171277, + "non_myopic_member_rewards": { + "quantity": 967720633630, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 15745213, + "unit": "block" + }, + "relative_stake": { + "quantity": 7.06, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1862-04-28T15:02:53Z", + "epoch_number": 15160 + }, + "cost": { + "quantity": 60, + "unit": "lovelace" + }, + "margin": { + "quantity": 69.55, + "unit": "percent" + }, + "pledge": { + "quantity": 85, + "unit": "lovelace" + }, + "delisted": false, + "metadata": { + "homepage": "MC)|񁼔7\r\\ae<\u0006d|]􊨡U; `Gh\u001d\u0004W=󿱓\u000e|\u0006yJ?y_\u0016z\u0010%󸿉w#&\u0000&a\u001br'򦕪(pg\u0005KdB񾳁6M", + "name": "n", + "ticker": "􉦭F\n", + "description": "\u001c쟄7򨊝󥴟M𩨷\rx7\u001c\nY𗥞\u0006|;x\u0018p=\u0019󠰟񂰔𝂒M􁔩𖍇o]C񞗶e\u0018𙔟HV󆜂򐸙󈉋3(\u001ef9𵏵\u0014󉍇h\t\u0013_A5\u001e񵠉򜯢<񧇑\u0005󏲲\u001cd\u001ch\r0hPPJ " + }, + "id": "pool1k4es6e4tnmwjc9sdlg8zzcequj8ud7vuej2cjukklkpz75ng9x3" + }, + { + "metrics": { + "saturation": 3.6696436264555237, + "non_myopic_member_rewards": { + "quantity": 420822746573, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 11853048, + "unit": "block" + }, + "relative_stake": { + "quantity": 35.73, + "unit": "percent" + } + }, + "cost": { + "quantity": 103, + "unit": "lovelace" + }, + "margin": { + "quantity": 25.65, + "unit": "percent" + }, + "pledge": { + "quantity": 181, + "unit": "lovelace" + }, + "delisted": false, + "metadata": { + "homepage": "w񸊏𢖬im4Xl@U6M^6󓱚l1\u0011Tl񕓪/\u0017r\"PG􏃒yJ^i>s󳆲^H1i𠫜)^\u001f񂩐􋝡UM𻡝\u0017WJ\u000eC􊶫W񮀊􍑀M\u0003\u0011\u0014 \u000b󖻷_\u0010\u0016\u000eow-2୧፪", + "ticker": "_(攔", + "description": "]k)cOU N\u001e\u001eU/0򮵐񘉚򠓘5\u0012>7򛳡,T\u0016\u000fX[\u000b4󧽸𩩄\u0012񅍂U\u0011#" + }, + "id": "pool1t4udw7q7p52050c26a0mzlcwlplc7693rvmmgvhavvwdjqsr90l" + }, + { + "metrics": { + "saturation": 3.770269836167919, + "non_myopic_member_rewards": { + "quantity": 352293096174, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 15555900, + "unit": "block" + }, + "relative_stake": { + "quantity": 54.54, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1880-09-21T10:00:00Z", + "epoch_number": 23349 + }, + "cost": { + "quantity": 97, + "unit": "lovelace" + }, + "margin": { + "quantity": 77.88, + "unit": "percent" + }, + "pledge": { + "quantity": 150, + "unit": "lovelace" + }, + "delisted": true, + "metadata": { + "homepage": "󇳄,\u001ac\u001c'#v,?\u0015U@5\u0015򄛂m8r~78 Kw𸀱\r \u001d􃐴\u001e󑑬򭩻󅇃\u0015\u0000𼴱R󿽞G\u0002t󩢕򤶌\u0012(\u000f\u0014𭤺l", + "name": "5󾴣𐛦x\t\\+_R񘚣{ey񑕸3GZ8񉺾o򹓕VNd", + "ticker": "򗤵<<\u0012", + "description": " \u000c\u000e]" + }, + "id": "pool19pdlw2wsdy9hg2dd5kvtg06xjs9nzp2g685xer6qgawp2y3daq4" + } + ], + "gc_status": { + "status": "not_started" + } + }, + { + "pools": [ + { + "metrics": { + "saturation": 4.781139316227327, + "non_myopic_member_rewards": { + "quantity": 930214461079, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 4539459, + "unit": "block" + }, + "relative_stake": { + "quantity": 26.27, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1883-12-24T06:41:03Z", + "epoch_number": 10528 + }, + "cost": { + "quantity": 161, + "unit": "lovelace" + }, + "margin": { + "quantity": 91.31, + "unit": "percent" + }, + "pledge": { + "quantity": 71, + "unit": "lovelace" + }, + "delisted": false, + "metadata": { + "homepage": "&𲽳HHMg,?𱆇󨙢7򺮶%󢕭񼠸\u0001\u000e𶎅xwQ+𠖾^\u001a6񁏆?<\u001cu\u0000?m򞛪gq>@񛒧\u0010\u0010;󀮲𶷋򇅶𩬜\u0010ョ򢁠\u0015𚧌+󸌽k'A<\"%", + "name": "V𰪿󦁸𹚘񇋴0󭰱u-󾄥l񰠤+𛆋)񥛌l𓃤tXy\u000f&\u001e8x\u0000\"𼘒7|kA\u0000[", + "ticker": "a./󈠛", + "description": "񼑚SS]Jk^𸷟u񊘌\u000c!񴔄M4󹾝#~I\u0010l\u0007#\u0015%𖁃9\u0015\u000bc\u0016􀉗󒊨\u0019{PJ\u001d!l:\n󐉄[Q𚶘󏿭!m\u001b@pF6󜇰[ꦄ񬻍󉧟A%Sa񬣕񬎂Pt#񑲥Z0󜥬bx)\u001dZ\u00008\u0017V򪹽\u0019򌨾Mb󐲇񆓤i\u0007\u0006H򦑎G8򤁫!J\u001e?󾻤\u0001󺏅=\u0015Q򺝻0򿚉nAk򼁑󚇲/0\u0004񆏕@S\n󏓷8_󀁷\u0008[+Bokn\u0017\r~3q򕣕f\u0016򖖖~󖣎;ir\u001e󂡀󡝨\u000e\u0005񙾼~\u000c񚥢-kw\u0011z{\u000c]0򀪛򕮇t8r𫖹jz(XB򆆶\u0006" + }, + "id": "pool1yevuejpzztrpmxsm4sm99lsrukf2we2g99tvkk65kpzekmncejw" + }, + { + "metrics": { + "saturation": 2.2123030423414742, + "non_myopic_member_rewards": { + "quantity": 996985257935, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 13081465, + "unit": "block" + }, + "relative_stake": { + "quantity": 54.01, + "unit": "percent" + } + }, + "cost": { + "quantity": 245, + "unit": "lovelace" + }, + "margin": { + "quantity": 20.39, + "unit": "percent" + }, + "pledge": { + "quantity": 165, + "unit": "lovelace" + }, + "delisted": false, + "id": "pool1uryep3vtvfn3tgsscnwz3shguxnp98ftza2d4g07lefqx2vcyjs" + }, + { + "metrics": { + "saturation": 2.0923852535513783, + "non_myopic_member_rewards": { + "quantity": 638275672841, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 4049163, + "unit": "block" + }, + "relative_stake": { + "quantity": 19.68, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1886-03-12T14:00:00Z", + "epoch_number": 18839 + }, + "cost": { + "quantity": 184, + "unit": "lovelace" + }, + "margin": { + "quantity": 28.07, + "unit": "percent" + }, + "pledge": { + "quantity": 172, + "unit": "lovelace" + }, + "delisted": true, + "metadata": { + "homepage": "hAAJ*\u0003򄭒\u0005vR\\>~d%mmD𧝔􁀢\u0005`៥\u000b򸊃k񧜛(\u0001{_򬻄\r\u001d|k{^\\\u000cV8𞨭\u0006򳝉)\u0016񕹵o\"+𼍣%V򋏧𫃤񦜺v񝾏\u0008\u0012Oh򕐠'9\u0011`%PG𻼁Qz\n-3rE򻃽g􈺪g𡷚𠇦ZWa񼺒_)񋗝\u000e\n\u0010K\u0013𯉗", + "name": "\"P+W\u0013򯄬Or{򂉥\u0010\u001de󨜶M\u001d𵤫)V倧v*󦤃𙛥𩙎f__󄣙񇦄s򜫋)51󠃵", + "ticker": "IOI,񔗎", + "description": "\u0000\r\u0010񫿱\u000e󯺨(\u000bi!7񇈆G4K%,b\u0010\u0006\u0003Ny4򞜻\u0018㠷\u0010NeGu\u0010\u000fUIm_\u0002bc\u000eZa񨃣^򕢩X񎉒:\u000e𵃒򇓆\u0011񳗄}1s\t/\u001f񗓫@񅃾sCuX𸝻'z𝡭𸿿\u0004🅶\u0011𲬄񍲓񮥉(o\u0018I𵒋6zfAAsx9\u0011픝\u000ey]񯶫3%󃏥^Fx\u0016\u001c\"𥜎1|6%\u0007q򏐵,򋵘𮈱J\r򃰇oX\u001f]𴫽\u001d>oP\u0014񩛂U\u000c󹕕" + }, + "id": "pool1nrpym6pd494t58f7upsdtg9eecu9n76dw38pn8cz63nwqhhvmtq" + }, + { + "metrics": { + "saturation": 3.737659378715624, + "non_myopic_member_rewards": { + "quantity": 498356412626, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 18083377, + "unit": "block" + }, + "relative_stake": { + "quantity": 74.89, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1866-05-14T07:32:48Z", + "epoch_number": 30415 + }, + "cost": { + "quantity": 97, + "unit": "lovelace" + }, + "margin": { + "quantity": 64.47, + "unit": "percent" + }, + "pledge": { + "quantity": 112, + "unit": "lovelace" + }, + "delisted": false, + "metadata": { + "homepage": "b\u000e򑆐󉾩񼙺\u0006;)\u0018a\"\u0019k/|6f\\p򶡧H\u001fz򸩆\u0007򶠕", + "name": "U\u0006W", + "ticker": "F5q򯟤", + "description": "{4SPydhaH-\t񵢷\u0017\u0007\u0008_\u0007O9[e\u00060p򝖠򚠵\u0001M\u0001\u0003􁑬\u000b\u0012Z\u0018^򗉼]򪱲󓟬T=󫂖\u0014[󋱞[5T1\u0004L򯚞PBC/?d򱅇򩒇O󞯐􄙈򩫯\u001fBሚuc-\u000c􆇭󞘷򑽴󛝜3h\u001e\u001e􄨁𩦆!򛴯1~I𐊲lS [{Kf:\u0011󐞀j:\u001cL쥗B a'3V񔪀BN.n􀭡Qd񫸎\u0010}7'񟃴.񔓡𘂫\u0012\u0017m-mO󈭜􍃗G\u0017X\u0005\u0018񚺡𦒰-\u0000b/䵰]񵴂\u000f\u000e\u0003v򌆫\u0016\u0006c\u0019-Vz\u0012qh񤒺񰲡򿄜𥣢B#:~\u0002󤤝CMP󝏙c\u0002m\u000f\r\t\u0003IC\u001e6\u0004nE􆽊S󉧠(\u000b'񕯚𘝝;p" + }, + "id": "pool167p9ggdt0knuwdn97304d3xk2qmkrpt5uk5z7al72va9647gglv" + }, + { + "metrics": { + "saturation": 1.1696632894808063, + "non_myopic_member_rewards": { + "quantity": 194313410853, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 2142158, + "unit": "block" + }, + "relative_stake": { + "quantity": 98.94, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1885-09-01T17:40:04Z", + "epoch_number": 22058 + }, + "cost": { + "quantity": 60, + "unit": "lovelace" + }, + "margin": { + "quantity": 66.66, + "unit": "percent" + }, + "pledge": { + "quantity": 13, + "unit": "lovelace" + }, + "delisted": false, + "id": "pool1prctaun8vmucn3g0luc57pms5hc40avpnfkn6zedxpka2t3gvwg" + }, + { + "metrics": { + "saturation": 3.7751844934474974, + "non_myopic_member_rewards": { + "quantity": 603536044423, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 13427707, + "unit": "block" + }, + "relative_stake": { + "quantity": 20.92, + "unit": "percent" + } + }, + "cost": { + "quantity": 115, + "unit": "lovelace" + }, + "margin": { + "quantity": 36.21, + "unit": "percent" + }, + "pledge": { + "quantity": 236, + "unit": "lovelace" + }, + "delisted": false, + "metadata": { + "homepage": "t?9?򙻢4vk-(\u0017l$^\u001b󺤻U\u0003\u0016\u0013\u0007UT򦮱𾊢\n񿹌``\u000b\u0006\u0008Yl/L𠘽񸰑^:\u0010#񝓌\u0001I", + "name": "򯾜𸺌", + "ticker": "l>yh񾔒", + "description": "#l\u0017T\u0005cz\u0014􆪊8F񿛞񋱱O=>d񬞸<򱲧\u0012\tI\u0011񶡈~e\u0008𤃛\u001b?\u0015󖈐\u0000T\neꀙ񬇯<򔰴U]󁥿蓪\u001c\u001b񎛵!񢘐\u000b23\u0008]􁻐}Ya񠶈_Xmb򄴥@P􃨛W\u0004!𵁟󃂸#Y50󭥲\u0008$񫂗\u001a|-󽄹\u0006񷰩g'\u0001cⱐ\u0004𔤰'\u000b=q\u0014񮬟\u0016𪊪L{\r%Ej\u0006N↝ꃐ򏟨" + }, + "id": "pool1qu9awhxu0g3wssuvyanp0muckqe2zsn47pf3gslcrpx9v7pj8ch" + }, + { + "metrics": { + "saturation": 2.508274278046802, + "non_myopic_member_rewards": { + "quantity": 242572720739, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 9146470, + "unit": "block" + }, + "relative_stake": { + "quantity": 65.03, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1890-05-13T08:00:00Z", + "epoch_number": 21664 + }, + "cost": { + "quantity": 8, + "unit": "lovelace" + }, + "margin": { + "quantity": 60.54, + "unit": "percent" + }, + "pledge": { + "quantity": 221, + "unit": "lovelace" + }, + "delisted": false, + "id": "pool1nn5uj7tvy2924afemz6zlfefrqap5xrmewt9gjv5hzkuvdy2h38" + }, + { + "metrics": { + "saturation": 0.15525194872872738, + "non_myopic_member_rewards": { + "quantity": 540056611675, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 6364470, + "unit": "block" + }, + "relative_stake": { + "quantity": 9.72, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1872-08-28T20:51:06Z", + "epoch_number": 13512 + }, + "cost": { + "quantity": 234, + "unit": "lovelace" + }, + "margin": { + "quantity": 84.39, + "unit": "percent" + }, + "pledge": { + "quantity": 208, + "unit": "lovelace" + }, + "delisted": true, + "metadata": { + "homepage": "=\u001c󹀱s򃋝\u001a\\p9f򂤿%(a'y򸆄LN4󛕺QP󀮨񷛿\u001bV-|9\u0017P󵑡Vv𝱪j򫼧p엖-񁲘􍂑\u0000󺗵ho\u000b9𚎌d$B򰛚bxt|7C06jc\u0014򌩩g7􁇼\u0006\u0007eF𹋟3rn󢄛*;i\u0012\u000b\u0002R򳆿\u001a,S", + "name": "p\u001f\r\u001d񳷀A'OD𥔯\u001d~~]񨉵\u0001%򷯹", + "ticker": "򿱋s񓝞", + "description": ",TFc^𹳚\u00066𚪫a&𪏽\u0002\u001dH\u0002_򱻼0Sp\u0006r<򪧫&\u0008󱦪\u0015&𩄿󓜞\"\u0016\u0007\rp9\u0001\u0015B*A\u00167񍏈\u0007񡙳򣞝<\u000cEU򂓇B\tD􆈠킙盼(󬂕#𮙆~񭚆Mi\u0006x𡢯򿞮\u0004\\\u0005򄊜򲆇񚋜/" + }, + "id": "pool1e8kk4ldsp0jdfqc0emupqa44ayc9gmpj8laks0pahn6hzh5fvw5" + }, + { + "metrics": { + "saturation": 2.4651988691416795, + "non_myopic_member_rewards": { + "quantity": 309371935744, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 16387507, + "unit": "block" + }, + "relative_stake": { + "quantity": 73.9, + "unit": "percent" + } + }, + "cost": { + "quantity": 125, + "unit": "lovelace" + }, + "margin": { + "quantity": 85.66, + "unit": "percent" + }, + "pledge": { + "quantity": 120, + "unit": "lovelace" + }, + "delisted": true, + "metadata": { + "homepage": "%cl%5@򢆵CW򲢓G\u0015.\u0004\r򔷛+/E*,𿘐񈗝\"\u001a)𣗴h򻍿GY󲅪p@9 򭮡5", + "name": "\u0019ba\u0019Wji񋅽s\u0018񋵒", + "ticker": "{򎤅^𷓧\u0003", + "description": "\u0003\\^\u001c-f%񛠌>򳱷QN񪭌..4d?\u001f≑\u0002" + }, + "id": "pool1u2nydg7n2dnnxus7wntluf4q8lcu8ys5ve28fpc5cc0dc623jqz" + }, + { + "metrics": { + "saturation": 4.730682759434615, + "non_myopic_member_rewards": { + "quantity": 272671478150, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 4603967, + "unit": "block" + }, + "relative_stake": { + "quantity": 33.81, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1906-03-22T17:40:35Z", + "epoch_number": 5721 + }, + "cost": { + "quantity": 17, + "unit": "lovelace" + }, + "margin": { + "quantity": 52.25, + "unit": "percent" + }, + "pledge": { + "quantity": 181, + "unit": "lovelace" + }, + "delisted": true, + "metadata": { + "homepage": "F]\u0001$y\t`񰒢M|󧶍]2\u001b-h\u0012J/m𕱎I󶜈\u0010𚞯>\u001e<+/]񳩅G7\u001e峼򯊙B\u0014Q󓼡9}A\t_򒴏6񬰡\u0018񟬫匰dn󯀊󆨵j5\u001b󄞔,\u0013'f&E$8i\u0006%b\"𒷋j,\u001c.r\u0017V.򺠒\neH񱹤\u0001J", + "name": "〧\u001eNx\u0005(\u0001\u000e\u0012z𖒴\u0016\u0011􍁡򹉓l􇊝\u000c$h򭟣>ep\r|󿷌sUH\\HV{A񴲼򍢜󜱔:F𥞛\n𴧍", + "ticker": "Z\u0016MH\u0004", + "description": "U#Tu1{󴕦zy􆞥񞈮>𸏑G=(d?-D򺷞\rnoD\u001b+򳿡\n\u0008Z\u001e\u0013󓈄񆘉p񏃥򁋐񺎄򱴛ꌿay\u000cv$k\\\u000f)kxc󏵁񡉣v񷲕Mbt+𙀬Qa򹀃\u001d򟸸F\u0011\u0019\u0002&l3xW|^񙘖\\h\"\u000bZg񠇔򞸐򣆴I󇚮" + }, + "id": "pool1kwnnusappafsqvl9uratzy4qugwpwcn0tjltc2mlrsaacn55ldk" + }, + { + "metrics": { + "saturation": 1.5271092031591276, + "non_myopic_member_rewards": { + "quantity": 587311714349, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 17857179, + "unit": "block" + }, + "relative_stake": { + "quantity": 27.65, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1883-04-11T03:00:00Z", + "epoch_number": 18446 + }, + "cost": { + "quantity": 133, + "unit": "lovelace" + }, + "margin": { + "quantity": 40.56, + "unit": "percent" + }, + "pledge": { + "quantity": 148, + "unit": "lovelace" + }, + "delisted": false, + "metadata": { + "homepage": "􁀎\u0014󒴣򀼼򗋹q񧐒󠂏\u000e'󡸄B{񡃬.rk*#I𦵌f\u0005\u001dYPKel~xS)N\r\u001a)vqX}1𵗤U󥯼𙽎\u0015\u0017򫕣񖽝񃔪\u0014Z,񳨑M\u0001󹘦us\u000b𤃗=*𤥯\nF", + "name": "1\u001a򉎴T\u0005'򶽃򱖈򂜺R\"4\u001e\\\u000c\u0012\u0005󜏿󲑓P󋯩Z򇰜N\u000f𱧪𩟊󋳋񪩑):񁽵񽜫񀼉(򣗌\u0011򩗱񨒔\u0004񏨦󌛮m[OKF񓹫\u001f", + "ticker": "x􀽒\u001c\u0006Z", + "description": "󈬵󯻈(\u0001򅟘M\u001aN\u001d\u0010 u󅥐򖕿'FJ𲕉V%\u001cE񇺠^D\u0008L1󳩵E򍿏:|󑓺O󴊘!񢴹\u0016\r!'UM󹲥\u0005S\u0012)1\rT񔷿SS->" + }, + "id": "pool1ty8hcvrhrgnduyngnynq0ufxayudvsl95twk6t79mzu0yl9vgrj" + }, + { + "metrics": { + "saturation": 2.6162039176534675, + "non_myopic_member_rewards": { + "quantity": 239489474594, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 12652208, + "unit": "block" + }, + "relative_stake": { + "quantity": 78.05, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1905-08-01T23:58:27.584842259343Z", + "epoch_number": 1172 + }, + "cost": { + "quantity": 120, + "unit": "lovelace" + }, + "margin": { + "quantity": 28.45, + "unit": "percent" + }, + "pledge": { + "quantity": 79, + "unit": "lovelace" + }, + "delisted": false, + "metadata": { + "homepage": "]\u0001\u0019m?h\u0012󭍏\n*fV.=-:(\u0005R񽮸4", + "name": "ua󺆳N$񭬯(𰞄򘔹o񬲫Otᐁj\u0005𡁁\r!", + "ticker": "EdK7K", + "description": "\u0018du񵆑&Nv\u0011oIb󆿭񽼯򛙙𲧮];G@G򷒛{\t񉪯'q񆝢rX񶶢@򆮽򏹠\u0019xCH\u0006N[𒚣\u0008+s𪻈u\u0012o5B򮉘ZF𕄰󯿢'W򊻇󋐨+򛍺dpF󼃄O\u0019\td5\u0014\u0013x0T56􉄴󅍭\u000b󆚙Ca+`𠧉𮍕V\nS5^u򮔬\u0018뺮􍱀𵠌'uE\u0005𹐊󽭝\u0010񧌿N\u001b}R\u0008\u0000\u0017Q)𭚅>D󕷌[簆󝤶d󌿼d\u0010𚍍񴒇\\\u0014?9H\u0019T-3\n򪻠\"4G\\\r\n)\u0012񞷁𗱵c\\z􀡄QNd􉳵{B\u001c4),!\u001f􎃑,񻘅\u0003H+7[qQ}*򲬣\u0012n\u0016\"\u0014l𔿚|\u001awj+|!}~R\u0016yl#v𮔎\u0017󯻣n𘒩򄾐Dd\u001e\u001cRv_/{񢜹\u001c񂂿mL.\u001a򵰨𚏠tLyb@C*,BMkC(\u001a\\I\u0016􉽠\u0010@\"w[H\r2gyhB򷼿\u0003\u0002\u001f򧊫6/[H\u001eZ}gr󉻝W71XzY򃻚S" + }, + "id": "pool1f4kfc2nmmtm833mnxawuqqxk2y6vpyg5k85nn8mltxqfyfmemhm" + }, + { + "metrics": { + "saturation": 1.5709247808311888, + "non_myopic_member_rewards": { + "quantity": 260216313299, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 9284735, + "unit": "block" + }, + "relative_stake": { + "quantity": 95.59, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1900-04-09T04:04:11Z", + "epoch_number": 24518 + }, + "cost": { + "quantity": 204, + "unit": "lovelace" + }, + "margin": { + "quantity": 55.09, + "unit": "percent" + }, + "pledge": { + "quantity": 113, + "unit": "lovelace" + }, + "delisted": true, + "id": "pool1e34vs6fe6sxusjh48cvzysg53s7e8028nrkkmaekjhnhs70rpk0" + } + ] + }, + { + "pools": [ + { + "metrics": { + "saturation": 0.691880963554069, + "non_myopic_member_rewards": { + "quantity": 588722329228, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 17292079, + "unit": "block" + }, + "relative_stake": { + "quantity": 44.11, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1875-11-06T23:10:30Z", + "epoch_number": 14844 + }, + "cost": { + "quantity": 235, + "unit": "lovelace" + }, + "margin": { + "quantity": 38.95, + "unit": "percent" + }, + "pledge": { + "quantity": 34, + "unit": "lovelace" + }, + "delisted": true, + "metadata": { + "homepage": ".󶳺񮓕X", + "name": "\u0015~*A񭄠󶉚n񎔨1}􉫒󧵿E񠌩+R򥮮\u001fy􉝨\u000c񌼵\u001c\u0005✟=8\u001f\u0018i򜙸󃚦󄪥𺠾𠩕 Oz􋂏", + "ticker": "c\\󯇜\u0005N" + }, + "id": "pool1vwgxj3cdzfhk5dvx4dyzqy6ez7hcgt8sd5saexjpzyjfcxfjgqz" + }, + { + "metrics": { + "saturation": 1.1992081705754325, + "non_myopic_member_rewards": { + "quantity": 602863086270, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 7847667, + "unit": "block" + }, + "relative_stake": { + "quantity": 36.26, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1886-10-05T08:32:09Z", + "epoch_number": 8033 + }, + "cost": { + "quantity": 193, + "unit": "lovelace" + }, + "margin": { + "quantity": 33.13, + "unit": "percent" + }, + "pledge": { + "quantity": 130, + "unit": "lovelace" + }, + "delisted": false, + "metadata": { + "homepage": "񑷍󝮫\u0000\u0015\u0013\u000elOW\u000eD\u0000_WG6)\u001azmb\u001b\u000b󓝾󖨗\u0011󞑘T6]\u0017LL=A\u0001gq{VU򟢎`y\u000b񙨙\u0013𥧞򃼌L򽽈;>N񋲮Ow򶊚񁤀x򏷰\u000f\u000e", + "name": ":h~C\u001d򙡊񞣼P\u0008", + "ticker": "+񌎲XG\u0019", + "description": "ZZ\u0017񛣂P򕁁<񡼏򸉝󃩩i\u0013,,2q𪦷~l𠾿\u0007𗦧" + }, + "id": "pool1yl99yx8zx5zzptd2pxd76fr2jjfum09sm6sw52revxs0ghfjw0u" + }, + { + "metrics": { + "saturation": 3.875154230234256, + "non_myopic_member_rewards": { + "quantity": 937957211197, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 12058181, + "unit": "block" + }, + "relative_stake": { + "quantity": 46.82, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1875-12-14T19:05:22Z", + "epoch_number": 26016 + }, + "cost": { + "quantity": 57, + "unit": "lovelace" + }, + "margin": { + "quantity": 14.68, + "unit": "percent" + }, + "pledge": { + "quantity": 60, + "unit": "lovelace" + }, + "delisted": false, + "id": "pool1vztp7etv5c683uvgqu2zqzrnvsr0yfnrmllnum0mhep85u5yw3z" + }, + { + "metrics": { + "saturation": 0.4255757590055803, + "non_myopic_member_rewards": { + "quantity": 118045909349, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 10713532, + "unit": "block" + }, + "relative_stake": { + "quantity": 49.84, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1883-01-21T02:56:17.246161142213Z", + "epoch_number": 17898 + }, + "cost": { + "quantity": 255, + "unit": "lovelace" + }, + "margin": { + "quantity": 89.15, + "unit": "percent" + }, + "pledge": { + "quantity": 16, + "unit": "lovelace" + }, + "delisted": true, + "metadata": { + "homepage": "|\u0003\u0018Fz\t6n󨢢\u0019'k򦰦\u0007𐁵\u0018M񄧢\u0014򈐙g񻝧󄰱${{𬢹6'4\u0000yZ'EcP\u0015򄞗\u0000򦿼7\u000f\u0010\"`񖿊{𾓍󪊕򌝡'\u0016\u00065j󖹗𕪏>MHPh|i\u0019񗈋*6[򐢼󶃍:>\nw\u0010&񇂯^wG\u0003\u0001\u0004\r\u0014𼲠F󣔴𪟒򘅯K", + "name": "󚻕\u0011\u0010\u001dk5T_󈍑񉮖󩾪򻫩|𜢪V+𓿖\u001dQ\n\n󋷔=z[򵖏W_򜀏eD𡽢򣟑n", + "ticker": "t\u0010񓌰Y\"", + "description": "?c Y\tk\u0015v񸬎6\u0008񔉟Ym򹜒\u000c\u0011WFi򡸡8@󰽸I\u000e%/,\u0016]KJaP\u000b􍛄zh\u00062󥞇n+)񉰧򦑒e]󮔾\u001bD󛃗RH&򧡜,6𐷎\u0007𓕙E򴮀|MJ񫺘<.qX\u0002򽑾#󲵦]򝴼+B@~" + }, + "id": "pool1mpzx077349ancav40gpxkv7p50jpgw9vgynslvskjduxvsq5p6p" + }, + { + "metrics": { + "saturation": 2.6497012792291645, + "non_myopic_member_rewards": { + "quantity": 213312136400, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 4079475, + "unit": "block" + }, + "relative_stake": { + "quantity": 71.07, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1897-01-03T04:00:00Z", + "epoch_number": 26995 + }, + "cost": { + "quantity": 223, + "unit": "lovelace" + }, + "margin": { + "quantity": 48.75, + "unit": "percent" + }, + "pledge": { + "quantity": 108, + "unit": "lovelace" + }, + "delisted": false, + "metadata": { + "homepage": "y񨗤򮁠󋋐񺫸𘶱f𠄗\u0013`򈡡:\u0011F@񅳛nZa?\u001ff𪯥񮳳B򇊛P\u0000FA\u000e󳋚\u0019\\^\u001eTHS\u0010eg$", + "name": "򚾳?R򏛠Odxv!l>", + "ticker": "򵕰H󚧊󊃊", + "description": "DP󨨌𹂂\u0001w􋪤\u0010񘧆𬎼`3h^<􋚛,\u001c籪\u0001􌥺?m(\u0006\u0006𑐕NL𳕄[4񜶣𺃣򡔔j6KBQ񂍋+DE) 󪌀󢁋08x񸎎\u000b\u0005<\u00135q%&򭿰cgR\t󺊞^<4B򰿬󓕌񏄤g𫗘r*`7p)񹘽ӕ\u000b3󊏮n+B%r#񳸰󍣡o=~T>󄑅)y𹕸\rBLB{Q󙐓8]\u000bW󑛓4?o8\u0014}85n\u0015tAp7\u0000\u0008#v\u0008\u0013\u0001ouh򝒅󩤝i6ks򅛚#h\u0003򙣹 \u000bGY\u0003m𨂐N𤃤4򧍓nS򔡑񣒡;f\u000bwsNAw%\u0012YuM\u00103𣢫q񭴻y \u0017v\u0018\u000f_\u0006𵄤*;O!v\u001f\u000f_'\u0007zw񰓚;򢽪S2\u0015>񃩌( f_𽱠\u001c򉽟􊯺0" + }, + "id": "pool1qsgy6gf24xuyy2fpvd7mr8csc7hhxh7sjnnm0n8t23q4vjj65e7" + }, + { + "metrics": { + "saturation": 0.7374172626109726, + "non_myopic_member_rewards": { + "quantity": 817199123613, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 20546335, + "unit": "block" + }, + "relative_stake": { + "quantity": 52.9, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1860-01-05T14:25:13.311793425408Z", + "epoch_number": 8093 + }, + "cost": { + "quantity": 110, + "unit": "lovelace" + }, + "margin": { + "quantity": 87.18, + "unit": "percent" + }, + "pledge": { + "quantity": 186, + "unit": "lovelace" + }, + "delisted": true, + "metadata": { + "homepage": "pG3\u0016i';\\񪻩񐜫e\u0017\u0015RZ \u00069\u0006!񌲿O񠲨\u0007񊪳񩉥=\"K- r򆑦8'\u001f󞂽%񭝩#@\u0000`Q􉤕󻘙GW򗶝&\\\u000crs𚑛\u000ca@􆵢\u0003\u0003\n-d\"󙪩;?\nGVQ#+3\u0019lq򎔙1BQ򝤟\u001b\u0015򀬧\n󆕪򚋇&\u001c[a6@8", + "name": "󫒽.9m𧔜/xS񷘯3\u0007w򺄚v\u001bꡨ񔓣f;20\u0007U&;D`9*!DF", + "ticker": "w',P\u001a", + "description": "\u0006XI񻍵\u001c𥼠󊰝7A򲢨$񱃲mJ縲9n𓴧\u00079$\neH򗁩󑗬q5ze\u0014X\"$Kbp򆰘\u0014{\u000c?\u0012HON󼕷mRP\u0018p&+f4n\u001d\u001c\u0007QE򴡨kHn󎟨gu\u0018𽕶\u001b6򶨓𼛏v?J.\u001203\u0006RK\u00181G򘁑񉙁7P F'󦎓E\u0017\u0001w\u0017񅜷C\u001a\u001a0y>;\u0006s\u000e2𼝹*\u001a\u0017d񋯲q𭇨m2+l\u0003+PTa\ng󽃏\u000fB4𹗻󟡄\u0000we󅢾\u0004񺚆h񱾍e󚦶󢴟\u001e\u0008L\u0011\r1t򿴚𺄯񹤸m󃐐\u000b蜥K5򌀤\r~󦕒d󛛹k񩔣bGn\u0001y󌧰\u000cpe]󷒼W񲧗@D򜓇P\u0000'WM\u0014\u000f%u,\u001a𐾛r,o\u0003^_\u0008,\u001a\u0010\u0010\u0010E\u0000A2N񪤕[t \u0014" + }, + "id": "pool1juugypdg6xperwrvuexvu9v0gghhf70dg5k66pnzwzxques8krz" + }, + { + "metrics": { + "saturation": 4.039542462022454, + "non_myopic_member_rewards": { + "quantity": 160541820718, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 11086323, + "unit": "block" + }, + "relative_stake": { + "quantity": 86.32, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1877-11-05T01:00:00Z", + "epoch_number": 31663 + }, + "cost": { + "quantity": 47, + "unit": "lovelace" + }, + "margin": { + "quantity": 20.66, + "unit": "percent" + }, + "pledge": { + "quantity": 211, + "unit": "lovelace" + }, + "delisted": false, + "id": "pool104hxhk3ywv22ffjkx7t77a8zccd3dzvyrdzfkt930lueg3rhwvk" + }, + { + "metrics": { + "saturation": 0.6933620619207898, + "non_myopic_member_rewards": { + "quantity": 46482595259, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 16804772, + "unit": "block" + }, + "relative_stake": { + "quantity": 26.55, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1886-03-05T00:42:36.100954952453Z", + "epoch_number": 19824 + }, + "cost": { + "quantity": 240, + "unit": "lovelace" + }, + "margin": { + "quantity": 33.78, + "unit": "percent" + }, + "pledge": { + "quantity": 157, + "unit": "lovelace" + }, + "delisted": false, + "metadata": { + "homepage": "(񳛩񄴻񓣣d񼮶Z򲬸}\u0004񁵤l<\u0015HC", + "name": "QSry󇜡5u𐫨O\n}MH񪉫L򇻓9򣊪xf󃭱򠦩󆊕\u0007󊇣H񡶵a/\u0014O`򮾦IP", + "ticker": "2\re", + "description": "\t\u001f򐔉UvM-`>񔁵\trU􍅳󙿫\u001fL2\nN#󖒶A?6\u0019\u0013*\u001f=<𣂩񻇼񆐤𻢈$𕌠PK񼠴`F󊸒򓏐Mnf 󱤝\t󻄀|򍽶I\u001f]no𭑥9\u001cd+F&o2 G𐭷u2\u001a򳬍\u0007\u0013󥡷\u00151\u001fm򐙳򚒒Q\u001e#񸟄򲽮^񴼓xG񝼎\\\u0001\u001f&W񉐔\u000ewBV󫐲񑾮AG\"t$򝢏󿀿\u000f'\u0007󐵐-\\.D򼯄𾎂\u001d򉙞X𰚖󋠘N򓳏fN񑬹C\u0012y󣑂M\u0003񝱗򸜼M񻋯]zjn𲼚}y󀟡m" + }, + "id": "pool1mz367408wz5wl8hzmp3k9ykn92dqc2rtugf5v6mh0pnw2dpymeh" + }, + { + "metrics": { + "saturation": 1.6856943013561154, + "non_myopic_member_rewards": { + "quantity": 153963422774, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 8170632, + "unit": "block" + }, + "relative_stake": { + "quantity": 56.18, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1886-11-29T16:00:23Z", + "epoch_number": 21825 + }, + "cost": { + "quantity": 213, + "unit": "lovelace" + }, + "margin": { + "quantity": 64.71, + "unit": "percent" + }, + "pledge": { + "quantity": 216, + "unit": "lovelace" + }, + "delisted": true, + "id": "pool1zkdtu6zmntarts7dkgfkt9czjdclv8r597asghadfh0qs53dqna" + }, + { + "metrics": { + "saturation": 4.286369284703593, + "non_myopic_member_rewards": { + "quantity": 645057503258, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 10451778, + "unit": "block" + }, + "relative_stake": { + "quantity": 10.84, + "unit": "percent" + } + }, + "cost": { + "quantity": 240, + "unit": "lovelace" + }, + "margin": { + "quantity": 15.19, + "unit": "percent" + }, + "pledge": { + "quantity": 109, + "unit": "lovelace" + }, + "delisted": false, + "metadata": { + "homepage": "F", + "name": "\u0017|\u0002&y\t<󆦌\u0006,d򶋒'", + "ticker": "򶍈{nr", + "description": "򳶒􊥻XiE񛊹NO𲊲[6𵱻Bv\t𜬠J󜁈p7@󝖖@𺆊\r񁻢A􂨾=\u000c󽞘𒋉|\u0014oQ\u0013RR𥧙Kd}\u0002񉬣󞼵󺀍\\cez\u0013=v cG)󡬎\u0015g./񍐂=/R\u0003m(\u0011YS\u0013󪀗I\u0005ﶉ򖈬S\u0015j򅎜}EW񑊸𳐑\u0018󘤑󙇵\u001d\u001d\\%{XJc𚽤MQKJd*)\u0010=?𧆡{ht1J񎽑㬬/濗\u001bo\u0007J򤭷!򸴑\u000e𰣟󦰤^R5g񰅤\\񥩝򖙐𑦆?=𖫴LM񊗏򴧶j);󫡀\u000eD򌅒󅕺\u0012>h\r\u0010񄠧&UAz6h񛝫🢀'W8\u0013laW󕜵񲃨z򮌠@O򫯊\\\u000f􇽊򊢔pYx?!;\"󞙉򲌟\u001b\u001d򨛼;" + }, + "id": "pool1ye7gpx9pqwp6tshrr7yrftd63qwf3pwvnsc6r3d64nc3g97f3aw" + }, + { + "metrics": { + "saturation": 4.0338193447253925, + "non_myopic_member_rewards": { + "quantity": 33891646032, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 16265144, + "unit": "block" + }, + "relative_stake": { + "quantity": 76.4, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1861-09-27T07:02:06.901318667399Z", + "epoch_number": 24607 + }, + "cost": { + "quantity": 118, + "unit": "lovelace" + }, + "margin": { + "quantity": 54.92, + "unit": "percent" + }, + "pledge": { + "quantity": 129, + "unit": "lovelace" + }, + "delisted": true, + "metadata": { + "homepage": "u􆾸B\u0018>g򼲭 [h\u0007vN@j񐋸j򾾞򳛨\t󏨏7*^Z3=\u000cn1\u001bM󍆈#ഏ", + "name": "񤀫QZ_\n򧻶򳆝BP5w@!!Scx񿐼󱦦2󁲊6T𡖟\u0016\u0004\u0014\u0000\u0000~M\u001d\u000f\rvZ\u001a񴋟\u0006񋚜p𽅎\u00183o\u000f\u001f򽍑?N2F󵟚.ss\u0011uZ\\q4񏥲\u0015񖷫Ur\u0016\u0010#\u0016V\u001c9xvE6\"F/񌒃C򑠘U\t\u0010rtv򗆍+p42󡆡0\u0005e򦶫\u000f-񙺥\u0012e$" + }, + "id": "pool1h8t5q89l36z6hyluym0qw7vc9p7zyjkcyrdxqqcuu8dx2xfajh6" + }, + { + "metrics": { + "saturation": 1.130831531646002, + "non_myopic_member_rewards": { + "quantity": 299607698651, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 3991299, + "unit": "block" + }, + "relative_stake": { + "quantity": 92.73, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1892-07-16T14:00:00Z", + "epoch_number": 30476 + }, + "cost": { + "quantity": 90, + "unit": "lovelace" + }, + "margin": { + "quantity": 25.2, + "unit": "percent" + }, + "pledge": { + "quantity": 11, + "unit": "lovelace" + }, + "delisted": true, + "metadata": { + "homepage": "򊗓[}'\u0004\n\u0008\u001a\u001c\u0015MV\u0007󓢋<-A~u󈘝񫞌-\u000b\u001bE\u0017~Z", + "name": "Q\u0008󾕉\\`l0񶇻\u000f\u0019X񨽴;\u000b6\u001c򪢶򊷈\u00007򯔽Q?p񃟐c򱷱\u00164Fn2H", + "ticker": "\u0015D&", + "description": "Y񣛎>gF򈇟C-\u00171\u0006\u001dy\t7\u0000v򾄊s􅊩\"򩅠\u001b\u0019P񅸥;񔄬\u0002򬦺v򴭔\u0007D\n\u0010Z*+\u0019񧭖񾓀/\u0016x򖬻􁬇Z୯򘢤񎖿\u0004N5򥿾'\u0019􋺏򓵹%򛫭\n{󢴷򹙋~;N󫣴q𳌪Slt]gt򿔄􏸰p_\u0002𚼍񬋥\u0002BqC(\u001bW~G+6𤼃\u0000G񒐁AV!\\?r𹭦􈙾򲞺\u0001\u0003sU򴧜\r𮜳򼟰\u001ak" + }, + "id": "pool1dds68f26efjjhpzz4v4y5j055cznf2g372anu9cjl6fc676y34d" + } + ], + "gc_status": { + "status": "has_run", + "last_run": "1905-11-04T08:00:00Z" + } + }, + { + "pools": [ + { + "metrics": { + "saturation": 0.672441549518279, + "non_myopic_member_rewards": { + "quantity": 343004378127, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 6772558, + "unit": "block" + }, + "relative_stake": { + "quantity": 21.39, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1862-09-10T20:00:00Z", + "epoch_number": 15058 + }, + "cost": { + "quantity": 234, + "unit": "lovelace" + }, + "margin": { + "quantity": 94.5, + "unit": "percent" + }, + "pledge": { + "quantity": 143, + "unit": "lovelace" + }, + "delisted": true, + "metadata": { + "homepage": "Y2 b\u0013\u0008<𑩣󧨿X\\N2򮳙FiCY?[[n+m!_\"1򂕗/w🜑", + "name": "𭎛\u0019򔢤A`'\u000f", + "ticker": "\u0014񜢴]", + "description": "\u0017\u0003\r򜭔Z\u0004PX\u0005򭇝;\u0001򰸮\u001fW򐢑󆭣u1󎒺\u0000G/2x񑇌k)g򬺫B򜷪\u000f񲟢N?YR\n/\n񴵲󪕫񩌯M\u000f\u0014bp_𛰠\u0004񘔿a𭢎\u000e\\𴩐u󬄢pF𙲧s\u0006\tB𫢯𭃍*6r󲑬K7\u0019񨠍VyB" + }, + "id": "pool1ppdt6kucpe7f0lcwjy4ps9r4aec7mjtfam4yqnyr3y0ry798qcw" + }, + { + "metrics": { + "saturation": 1.118889508765157, + "non_myopic_member_rewards": { + "quantity": 921795084094, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 19289061, + "unit": "block" + }, + "relative_stake": { + "quantity": 22.34, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1893-02-08T09:00:00Z", + "epoch_number": 22338 + }, + "cost": { + "quantity": 127, + "unit": "lovelace" + }, + "margin": { + "quantity": 49.52, + "unit": "percent" + }, + "pledge": { + "quantity": 1, + "unit": "lovelace" + }, + "delisted": false, + "metadata": { + "homepage": "5T v\u0012\u0000'|rW\u0016􈖒񿩪󛆵񔶬/\u001a򓵰qE,~f򟉗 &-7򻞑\r\u0007r\u0015`b흳󘦀S_+y𣦽E\u001b42", + "name": "V-{򲣔:M󛹩?H@s\u0016\t򅜰g-3sniQ𥟥}򣾗\u00143\u0016K{d5%[K󈅭\u001c디򒪒_\u0014񄇷\u000c󜙪󣀢-0", + "ticker": "񼘟\"\u001e򳍽;", + "description": ">6\n\u0012񎹌\u0010𖖋wt򁛲\t`P5\\GNO򙸭0=UFr񸷁V󰾾v𱤅\u0006#\u0019A򩽳\u001dE󒈈h\u0002\u0016񶻜\u0010\n\tz򂆛e𙯉)񣽗_𲐛@\u0006m.򙙰\u000c]\u0003\u0002𺬓&󨖍\t0L6PC\u000eYSh\u001a񿎭Rd\u0014𤪇E򐳶򃴹!}\tJ\u000e􌖮&8󃘢񑋭=񧷲o)RJ𤡺\\񑅱\u0000-X1ji)^\u0014Jj`c頯\u0002\t(N󮱜D-[񃾓򺎖y\u0010z~\u0019v􂻟򰻘󽚣񴌧y:%?\taB&\u000fI𺬝\u0012[󭹤Cb\u0019󍰝\u000e󀿐򋯽󂗸;R|ZYpX\u001c𮅻\"V򽘋e\u001d򧽷]𡟭][򧚩o|;00򲐎\u0002W&\u0014Z򃐨񬖝\u00000?\u001ca񶱍9\u0006IkV򉀀.\u001cd򾈳" + }, + "id": "pool1rglfv2cugyz4xayvf4352s4s4glntpdrxajh0hr89szu77zk0m2" + }, + { + "metrics": { + "saturation": 1.0048748412571578, + "non_myopic_member_rewards": { + "quantity": 299965296800, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 14676602, + "unit": "block" + }, + "relative_stake": { + "quantity": 57.25, + "unit": "percent" + } + }, + "cost": { + "quantity": 239, + "unit": "lovelace" + }, + "margin": { + "quantity": 2.26, + "unit": "percent" + }, + "pledge": { + "quantity": 91, + "unit": "lovelace" + }, + "delisted": true, + "metadata": { + "homepage": "OTb𪢾򴠇Ui!򜰋G𐍈v}\u0019&._\u0014(𗋆F򙋺v{;𦼏=bz\u0011EZw󅂜N򩈫𻥿򪖞88Y 󒷬%𓽾\u00045l;v𸴨q0\u0012񂕢񌽧'9\r\nt1\u000c𨖆\u000e[񵚦񆫹\u0013󊱟AN\u001c Wr\\󓽭Fᣵ񳹧1", + "name": ",\u0001+򶷔7\u0014s򠣦g򁭗I\u0002🌌?񋋝󑿍z~\u000c\\A񀑶wM-E|g3\u000b#", + "ticker": "󌇕(\u000bv=", + "description": "\u0000)]\u000e\u0012O\u0001q+%h\u001f<Თ\u0016\"VQ󿾳򑂤f󠋙F\u001dEM񴅲񱡿𙑙e𷶙b򕻖c)c󮮙,8𘘵,򇪁e8xZut*𰈌\",󸴺-\u0007@f\u0019')%󕟇򬷭󛨔\u001e瘔\u001f񖪝񽑪r)\u0007dy:o\u0012󎲖)\u0003|k󵻝3\u001c𞤐Eo)1񔏈󣨲kC򓄟2iR$\u0016+=M񕬃mpQ\u001biZ񉹶򛂑Ib񠻲򾜫" + }, + "id": "pool1jgcwmrtzh3elkf6rh3lkcjcawdfnavw20lw9pw7p5spfc3ce8lv" + }, + { + "metrics": { + "saturation": 1.6136279626551708, + "non_myopic_member_rewards": { + "quantity": 35368562973, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 13046696, + "unit": "block" + }, + "relative_stake": { + "quantity": 25.38, + "unit": "percent" + } + }, + "cost": { + "quantity": 244, + "unit": "lovelace" + }, + "margin": { + "quantity": 53.52, + "unit": "percent" + }, + "pledge": { + "quantity": 138, + "unit": "lovelace" + }, + "delisted": false, + "id": "pool1eudlkka0u0vjzdaynmj2fuqzadcj7mf57m39s847v4mlq7fk4t7" + }, + { + "metrics": { + "saturation": 2.755618733425398, + "non_myopic_member_rewards": { + "quantity": 350195306150, + "unit": "lovelace" + }, + "produced_blocks": { + "quantity": 18398880, + "unit": "block" + }, + "relative_stake": { + "quantity": 16.34, + "unit": "percent" + } + }, + "retirement": { + "epoch_start_time": "1883-11-11T23:15:40.649748813745Z", + "epoch_number": 13455 + }, + "cost": { + "quantity": 25, + "unit": "lovelace" + }, + "margin": { + "quantity": 41.18, + "unit": "percent" + }, + "pledge": { + "quantity": 3, + "unit": "lovelace" + }, + "delisted": false, + "metadata": { + "homepage": "\u0008\n\u0000I7\u001d?f\u0013񁮱Z񊬿\\j0\u0016g=𕾺Cp\u00152\u001eY\u0004\u0008\"V\n󎉨J+\u0011󫩧8$ 򟻃O\nv\u0011󭶗񗡆񷛬\u001b󛐚j\u0000rpMS\u000bm eYDv𙵆^4\u0001", + "name": "\u0002񗙝\u000b2\u0013𠔋", + "ticker": "򄰞)c", + "description": "l[󕦷򳖈gl􋉖Uv\u0018񤂆\u001b5`]\u000b򜅎-𓵺󑏊oY㴟S\u000c󉈑\u0014&\u0006&{0򄆽yc񶾖t皋󱱭k򄢃r#\u0002\u0003\u0002\u001a4/򺜙񘶶(\u0008𘳕6\u001c𗹟dE\u000f󹓴 %駓{󝍞i\u0011񐭅\u000eVA\u001er󥸄\u0013C𾖏ok𞝈>f\u000f`򘜬\u001bc\u0005\u001c󬊜\u000e󛃐U\u0005\u000c\u0007,򢌢v'4񨘗\u000c/\u0001F\u0004y_e/rA򠑃7\u0001\u0000󋀓\u0013𔼡8m櫒⑓𯊯򥦁&J󔡱\u0016\u0013]qqn>𾗩7\u0016𻝟\r?a%y A\u0002XO\n?󔊰򇽅\u000f+\u0016\tDA\th񓙓NrQ󦒽󭛟\u0006\u0001󜓙󴓀D3KV\u0004/񑩉\u0018x𳡶\u0019󬽍z񂨼" + }, + "id": "pool1ap3d4d0zekkg927gra5mjwpw47ymg7zvvr3hx28y66ldwatahpr" + } + ], + "gc_status": { + "status": "not_started" + } + } + ] +} \ No newline at end of file diff --git a/lib/core/test/data/Cardano/Wallet/Api/ApiMaintenanceAction.json b/lib/core/test/data/Cardano/Wallet/Api/ApiMaintenanceAction.json new file mode 100644 index 00000000000..9e1357fd7b9 --- /dev/null +++ b/lib/core/test/data/Cardano/Wallet/Api/ApiMaintenanceAction.json @@ -0,0 +1,61 @@ +{ + "seed": -9096659285789418454, + "samples": [ + { + "gc_stake_pools": { + "status": "has_run", + "last_run": "1887-02-07T15:59:58Z" + } + }, + { + "gc_stake_pools": { + "status": "restarting", + "last_run": "1895-01-25T13:15:15Z" + } + }, + { + "gc_stake_pools": { + "status": "restarting", + "last_run": "1873-08-31T03:33:04Z" + } + }, + { + "gc_stake_pools": { + "status": "not_started" + } + }, + { + "gc_stake_pools": { + "status": "not_started" + } + }, + { + "gc_stake_pools": { + "status": "restarting", + "last_run": "1864-06-09T06:48:03.138827934098Z" + } + }, + { + "gc_stake_pools": { + "status": "not_started" + } + }, + { + "gc_stake_pools": { + "status": "has_run", + "last_run": "1901-11-24T13:54:25Z" + } + }, + { + "gc_stake_pools": { + "status": "has_run", + "last_run": "1896-02-25T15:16:00Z" + } + }, + { + "gc_stake_pools": { + "status": "not_applicable" + } + } + ] +} \ No newline at end of file diff --git a/lib/core/test/data/Cardano/Wallet/Api/ApiMaintenanceActionPostData.json b/lib/core/test/data/Cardano/Wallet/Api/ApiMaintenanceActionPostData.json new file mode 100644 index 00000000000..219b6ade5e1 --- /dev/null +++ b/lib/core/test/data/Cardano/Wallet/Api/ApiMaintenanceActionPostData.json @@ -0,0 +1,35 @@ +{ + "seed": -940073206050741807, + "samples": [ + { + "maintenance_action": "gc_stake_pools" + }, + { + "maintenance_action": "gc_stake_pools" + }, + { + "maintenance_action": "gc_stake_pools" + }, + { + "maintenance_action": "gc_stake_pools" + }, + { + "maintenance_action": "gc_stake_pools" + }, + { + "maintenance_action": "gc_stake_pools" + }, + { + "maintenance_action": "gc_stake_pools" + }, + { + "maintenance_action": "gc_stake_pools" + }, + { + "maintenance_action": "gc_stake_pools" + }, + { + "maintenance_action": "gc_stake_pools" + } + ] +} \ No newline at end of file diff --git a/lib/core/test/data/Cardano/Wallet/Api/ApiStakePool.json b/lib/core/test/data/Cardano/Wallet/Api/ApiStakePool.json index 2af1b1984e4..e222cd73d83 100644 --- a/lib/core/test/data/Cardano/Wallet/Api/ApiStakePool.json +++ b/lib/core/test/data/Cardano/Wallet/Api/ApiStakePool.json @@ -1,405 +1,591 @@ { - "seed": 1648950576562293098, + "seed": -4132539117587378523, "samples": [ { + "flags": [ + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted" + ], "metrics": { - "saturation": 2.4871362368537793, + "saturation": 1.347474258087622e-2, "non_myopic_member_rewards": { - "quantity": 300829650366, + "quantity": 389762930128, "unit": "lovelace" }, "produced_blocks": { - "quantity": 12428833, + "quantity": 8342542, "unit": "block" }, "relative_stake": { - "quantity": 74.03, + "quantity": 73.62, "unit": "percent" } }, - "retirement": { - "epoch_start_time": "1878-09-25T02:48:29Z", - "epoch_number": 9909 - }, "cost": { - "quantity": 78, + "quantity": 143, "unit": "lovelace" }, "margin": { - "quantity": 8.0e-2, + "quantity": 74.1, "unit": "percent" }, "pledge": { - "quantity": 255, + "quantity": 123, "unit": "lovelace" }, "metadata": { - "homepage": "D\u0017\r9G𥙩\u000bn\u001dZ򨔘\u0011:1A\u001f|G\u001ee򶢹m?򼓘k74D񷖋\u0011N򐹯D􉘃󐿚񯛝\u0013A9=>", - "name": "\u0008𾦶\u0004&~-󫡲\u0014@󙖯i𯩁R,񾔶|#𸴟>C\u000f", - "ticker": "`\u0007\u001d", - "description": "^W'k񬈅F*k&P!C*\u0008=\u0016}𨿋Z 򛫻񲦚aY)\u0003D\u0000W𱐬󁎦񋟙t;\u000c" + "homepage": "򪏔fi@9Jq72􉿏y\u001a\u0007F", + "name": "Y𶸻p\n󑪊$󎙷\u001e2\u0019򼤺\u0000R>JF\u00024򣾜U7k=Vt7S𩬻𞼟򗀆!=3GjQpN\u0004", + "ticker": "z񜊑$z򫔄", + "description": "iF@,\u0000!񖅬󞉳\u0001󚩾IeT`򲌉M񟴙񘜮􈇒󫁮xK󁄢\u0017z8_?𰮧_l \u000e\u001e\t-*^'0u\r򱱺^k񢓱3\t\u000fAcD8uZ@\u0007I𯊓-򼫌񤮸&\u0003oC󠉄`𤬱OG(񿠝\r󇿣󲡳𐕕\u0007}毲񔪓k\u000e{KT\u0013\u0001\u000e\u001e\u0003c_󞒉񎖾`\u00001Xd~SH\u00199𱘎\u000b;w\u0003Vv񐉑𮇪bW!񟯆03𿰄\u0018nU𯝅\u0007t򫖺\u0008󊞛넇󨲹󵪌󿯵^" }, - "id": "pool1j4p8d27crkjde00p4l9v5f95hftm23x2yylllp9lzg72w6p4ecm" + "id": "pool16rqaujxmx4j0quwyzct9rdauvhm30ttrhncpcj4c9hzqxndf3ac" }, { + "flags": [ + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted" + ], "metrics": { - "saturation": 4.206923248389226, + "saturation": 3.8837672493828688, "non_myopic_member_rewards": { - "quantity": 939832251301, + "quantity": 801057920191, "unit": "lovelace" }, "produced_blocks": { - "quantity": 22311798, + "quantity": 21889826, "unit": "block" }, "relative_stake": { - "quantity": 86.03, + "quantity": 22.66, "unit": "percent" } }, "retirement": { - "epoch_start_time": "1885-01-28T19:23:12.506992765083Z", - "epoch_number": 19632 + "epoch_start_time": "1881-07-25T04:00:00Z", + "epoch_number": 2951 }, "cost": { - "quantity": 195, + "quantity": 67, "unit": "lovelace" }, "margin": { - "quantity": 25.17, + "quantity": 9.67, "unit": "percent" }, "pledge": { - "quantity": 144, + "quantity": 203, "unit": "lovelace" }, "metadata": { - "homepage": "𵍓\u0006\u001d򡗓񍹭", - "name": "\u0011&񐔒񕜳\u001a𻧩񣕣Q񙡺󞖋򝷙W񆫽:\u001c򥷪4#", - "ticker": "󵬘N;", - "description": "P&u~y򎛊\u0011qDg\u0003\u000e\u0006D^r򃚦\u000f򔇰h񷩙񍓧񓫢:>k񼝛򡜣!k\u000c\u0008x\rs3􃞧d\u0001xvA,W`󩰫󧀿\u001br򓚁񂥳g{\u001cW\u0005\u0002򄗭񄢩@\u001fLEX哠N0 #\u0011\u00082\r#D򘵻򪬏\u0008]򞳭z񞥃񰦑c󗎟򕗀'\u0013\u001b򔌏%8]򱐄6N\n\u0018n#j񜉅:kxX\u0010@yDq\u0011󂻎g򾾡c\u00004򗙧𾤢y󛷥K\\?Ik^Wf^𝽠_򝗆kpuaCz\u001a󖀃\u0016O񁕓9\u000c󮩹\u000bIQ\u0006P\r>f\u00179\u0015!/~u򁽟{)#\u001a\u0011W󧔾?\u00048d&f𚉐(򻙔l'Z\u0015򏼘i[R&𫟾" + "homepage": "K\u0004R9𡨭z<7Wu\u000b\\\"𴵻4񹭽󐴫l󿛛f`\u0018񉌹(\u0006\u0002/?a􆄓\tU\u0016G\u0005'?g넎kK\u000cM򃡆v񨛪󑌺EB򍔦򏊁S􀠪T\u000bl}s`񖈾\u0010\u0015j󁉿M񙅇,񙎌󚕆7Ikh󫹠\u0014O\u001f򳤥", + "name": "C\u0000򋛐v𲓻򓧨#2Q𝄺\u000bY𹼶m𲗡񳥥󉮳}Su򮐵{񂆢L\u0007", + "ticker": "9򗛽^􆋶򄈩" }, - "id": "pool1y4zccfz0vrvmt8e96gfn5u5pd0zln5fn2uup25fk8grfw4frwqh" + "id": "pool19vd9w4kgkzrpaxvykv2x5wa7pd6e07c64qrvkckk9fj5c7zzmuz" }, { + "flags": [ + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted" + ], "metrics": { - "saturation": 2.0262672273589573, + "saturation": 2.2678498772463547, "non_myopic_member_rewards": { - "quantity": 688229616774, + "quantity": 916311513140, "unit": "lovelace" }, "produced_blocks": { - "quantity": 11174627, + "quantity": 20949158, "unit": "block" }, "relative_stake": { - "quantity": 1.75, + "quantity": 47.99, "unit": "percent" } }, "retirement": { - "epoch_start_time": "1908-07-23T01:18:41.264047239015Z", - "epoch_number": 14875 + "epoch_start_time": "1894-11-16T03:37:27.329210709372Z", + "epoch_number": 26550 }, "cost": { - "quantity": 175, + "quantity": 20, "unit": "lovelace" }, "margin": { - "quantity": 6.67, + "quantity": 34.53, "unit": "percent" }, "pledge": { - "quantity": 230, + "quantity": 156, "unit": "lovelace" }, "metadata": { - "homepage": " 𹙢'Y𴛤-󉡙\u0000\u0016\u0002wm񅨚PG򣁢󡿡Z􇵂\u000e񙄟\u0010jB󞭖􁄽y'$\u001f5񲒖𮡧\u0007^򎴁\u00009sy􏂦W􉑤LNfiQ󉜴%\\Rb\u0001!+򿋳\u001d\u0015l񔺑񃨍D\"𼢴篸\u001b)s\u0012>?", - "name": "\u001bL𘜚H\r񳭨\"mC~?U\u0002dvh${rr&)\u0017򦤘񖙢\n򥺪i\u0008\u0006􄓄]1_𹍘\u000b񁾊IfK\"󖈷𳫴򾝢", - "ticker": "=us󬟶򷬣", - "description": "~`]\u0017򂃱^\u001bIr\u0000,\u0005\u0013m򂋲/󱞉P\u0005\u0005\u0018\u0007jL" + "homepage": "򫇂򨐵s'XH\nX\u0004G\t񨵄S\u0019I㝒BNL%򇮂U0󅐦9\u0007\u0011~So+\u0004`򑳍\u0000𑹙\r𵌨 󠼦Rw\u0006򭹺p񳎦q\"𭗎e8\u000bLX𙮴s|z&\u001dz=\"-\r\u001fx\"𰩵d<^%m󀏒!a\u0018\u0000:]𠊮\u0007G\u0010\u0018/\u001f񅩼𦡡\tF,\u001c񙠻\u001fM)G\u0007NKAR.Fp𽹃L󁷤.M\u0011 𲭳񌩼\u001f\u0005]񳘥N\u0019\u0012\u000c;􂣟\u0003\u0006\u000b%," }, - "id": "pool1ve8ysena2jsdqyxz6jevrzk3q9d7hagw7ayfmg46ldqcgxgj3sh" + "id": "pool198e0usn343jw6xza34hcg5qd9m6ah7kn79pyhe5wdz6m536h6lc" }, { + "flags": [ + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted" + ], "metrics": { - "saturation": 0.20777293359932947, + "saturation": 4.9370305129779055, "non_myopic_member_rewards": { - "quantity": 262774299112, + "quantity": 982002410599, "unit": "lovelace" }, "produced_blocks": { - "quantity": 11082948, + "quantity": 182860, "unit": "block" }, "relative_stake": { - "quantity": 88.97, + "quantity": 46.11, "unit": "percent" } }, "retirement": { - "epoch_start_time": "1876-09-13T20:06:19Z", - "epoch_number": 5035 + "epoch_start_time": "1867-06-14T08:14:50Z", + "epoch_number": 27512 }, "cost": { - "quantity": 251, + "quantity": 213, "unit": "lovelace" }, "margin": { - "quantity": 2.84, + "quantity": 49.06, "unit": "percent" }, "pledge": { - "quantity": 212, + "quantity": 154, "unit": "lovelace" }, "metadata": { - "homepage": "\u001e򢉉O4r󕵦򬃑Z+G=󝨌򂏞IFR?pN", - "name": "\u0015\\\u0001\u000f$DE󛡬񑠅_񍓎~c8)\u001a\u0010-F<", - "ticker": "(M񔏺", - "description": "`\u0007𜖆\u001a9`􁌴8.𸧏C\u0000򚕌\"I򛡧𴶉\u0008\u001fg\u0005!\u0001\u000fz>(🯨\u001385򱋖701\u0003jW򏹞r󙠎z" + "homepage": "u񯫽U\u0008\u0006a񆧦\u0006\u0015>3󬌥^𓃷򽽈𖮩mh+U\u000e\u0018NJB\u000c{/\u0005\n򯡕U𻂆{򝨓\u0002躳6\u000e'񤄂\u0013-:eE򑍌򁫢񅞿򍞪n򮨏*􆳭_oSDK\u001f񫴒", + "name": "!򣫨񲡷wn񆣮\u001a򾇢x)]+G<󜇻4(ZK]񋢕_Lssw򜢲aUtq", + "ticker": "~񪗜\u0004񘨎", + "description": "\u000f𐗷􋒍e𑺡bT𵲷c󀣷󌫄`$\u000b%&x򸩡&窝\u0007bq}󇇕𡛚񪵈,Y@R{sBV\u0010O𖳡6\u0001:xjApL󓡠ru򱙾!#񈾆򕠨*񇟳2\u0017\u001f񺿨G%󃦧$򮷧@𼾛򘮪\u000b\u0019'󈯙\u00059^A}񩒩𮚭[KR)\u001a񮃅\u000409\\-8𜀶\u0000+\t^򇕰񡜁\r𖦒i\u0016C1\t򣓥\riq𯋾1A\u0001񜾋\"󼭳\u001a񶪄ZxNA\u000f𖓡" }, - "id": "pool1wr3kzh64ruwv3h8zmegr6qyr3kxpz5urqfzja2mj90zucd03jgu" + "id": "pool16t92v0svq0f4anmf0y9yn4s0262fcut9cyydzrw3wl8awqac9er" }, { + "flags": [ + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted" + ], "metrics": { - "saturation": 4.875352324926411, + "saturation": 1.138016094198579, "non_myopic_member_rewards": { - "quantity": 960257825132, + "quantity": 404203198635, "unit": "lovelace" }, "produced_blocks": { - "quantity": 15032451, + "quantity": 15534840, "unit": "block" }, "relative_stake": { - "quantity": 79.66, + "quantity": 42.13, "unit": "percent" } }, "retirement": { - "epoch_start_time": "1866-10-03T08:00:00Z", - "epoch_number": 6360 + "epoch_start_time": "1903-02-27T02:29:54.859997028566Z", + "epoch_number": 18574 }, "cost": { - "quantity": 242, + "quantity": 135, "unit": "lovelace" }, "margin": { - "quantity": 72.05, + "quantity": 35.18, "unit": "percent" }, "pledge": { - "quantity": 187, + "quantity": 173, "unit": "lovelace" }, "metadata": { - "homepage": "]9}}E򰨣#񊛈+@𺦵#%mR𝽹\u0014󫱝􅄧p򿨶𲑲\tCC\u0018[_4򾝽H󦿫k\u00037𖥿\t&\u0010&*F𛪀<${򉁡󢨌-\u0017󽯶󌜷򦫊񑺤򩅓򣯺򏑀|\u0005򚹶", - "name": "󸘗\u0019\u001f@&\u00018Q򟵄{񬙪񫻣)RIF!􃠛", - "ticker": "\u0011*yG", - "description": "fB[󳜲񀫴zE\r\u000fs\u0002\u001eW\"Ag>65񀒚ys\u001bY|Qj1\n/&/򢏿e\u0017𥩡񠩷:}L\u001bA\u0013򇌺󬖧\u0011񋘏T󻺽󭃊8򼑠m/S\u0012{|y&rS򟭠8#゗I{\u0001p񣘑򘏪hM6Z\u001dn\n\u00140\u001b𧲨\u000b-\u0008q􉟰 򞊮󑾤C䖛k_T=w򸛕񆠹\u001b󖏙B񖭀}I\u0019\u000b􂮔\u0003^[z\n񼕦e{􅧂󐈘\u001a񜏢vQ󧉯pf\u0000\u0005P󁛞y򑰓\")h\u001b񶧻\u0007d􁗱T\u00104^$\u0010\u001b<", - "name": "󔖿𹡴02", - "ticker": "\u0016x񋎰", - "description": "*񾞜⮚4\u0012U򋽈\u0015哊\u0011􅇎\u0015R:g\u0006+scB򅽻򍫈-\u0000~\u000e$𼼌񝀜,R0?2VwDSvh\u001e󡂖qO8C+H!󟠪'\"󠔑0bc.U񛆣𙠇Jp򃞫/!򱼟UD0󋒵F]l\u001b+\u001aKQ\n\u0007%C 򆪭_%Jf\u0000\u0013F8)\u0019nhK!򖉫S𾿆J*ldA􍾼a󨘯'_\u0008𽠫f񋺧oE򬷨󀡢*6\u0015<)E\u000b\u001es]^y񤚺\u001cp\u0013𥸿-Iy/" + "homepage": "8𷗴'lP<{Q椪}:\u000c@򗸆񨯟e񢼮At󨁱l7\n򙎸򠥀o\u000f8(\u0013!a\u0014􄯜󯿨󃗭]\u001f򾹙s-򩶄󍍙󖦨󢹢5򭏀Id񱞊󴓅/\u0000񌚪?񒋼w\u000c@" }, - "id": "pool1fekspzgvpqfs3u6kklujpa7mjm0f5h62f4dqrt87g6xqqn57u8f" + "id": "pool1mjpjwlpz6nh05s6036c9us877r75t6uf0wupx8j2rcyvqkd25c3" }, { + "flags": [ + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted" + ], "metrics": { - "saturation": 1.2142612304199552, + "saturation": 0.17884223298848034, "non_myopic_member_rewards": { - "quantity": 508608277141, + "quantity": 946806669499, "unit": "lovelace" }, "produced_blocks": { - "quantity": 4990020, + "quantity": 11703246, "unit": "block" }, "relative_stake": { - "quantity": 20.09, + "quantity": 5.93, "unit": "percent" } }, "retirement": { - "epoch_start_time": "1891-12-19T02:56:44.132395228958Z", - "epoch_number": 29024 + "epoch_start_time": "1860-03-24T16:53:01.445638759844Z", + "epoch_number": 9997 }, "cost": { - "quantity": 238, + "quantity": 116, "unit": "lovelace" }, "margin": { - "quantity": 39.16, + "quantity": 82.73, "unit": "percent" }, "pledge": { - "quantity": 141, + "quantity": 100, "unit": "lovelace" }, - "metadata": { - "homepage": "KP󢘢q򬏠󞳇򆀓\u0013\u000b𦷣񡛴935> 'oZ\u001dLb򱾟N\u001b𼒔tN/r󔕗𛅯\u0004* ", - "name": "\u0011~茭v𥅸򴛻:Z,zfAY\u00157\u001dR1kd\u0007\u000brn󱕋򦤒󶫪lk", - "ticker": "}\u0019B𴅞", - "description": "/\u0015xm󕄖I𧧖hz\u000c\u0012U\u0004\u0015󕆾^&r0\u001a򈜰pC\u000ehP򒉯L\u0000𪺇\n𾚆𷺍\u0017񦉈K焇wp" - }, - "id": "pool13qrex33gtplf6e7zcfdtrqlg23qh5pvv2zeld6lff02t2ayhtk9" + "id": "pool1e09np6w4qrg09ru2v7l5zlkef4e49uwsu7ud8zs64mu8zy2gu2w" }, { + "flags": [ + "delisted", + "delisted", + "delisted", + "delisted", + "delisted" + ], "metrics": { - "saturation": 2.8405765784728616, + "saturation": 1.908211384172374, "non_myopic_member_rewards": { - "quantity": 594623145378, + "quantity": 808230372438, "unit": "lovelace" }, "produced_blocks": { - "quantity": 16619957, + "quantity": 1967385, "unit": "block" }, "relative_stake": { - "quantity": 32.81, + "quantity": 9.24, "unit": "percent" } }, - "retirement": { - "epoch_start_time": "1882-03-17T09:53:49.10233897594Z", - "epoch_number": 22451 - }, "cost": { - "quantity": 130, + "quantity": 217, "unit": "lovelace" }, "margin": { - "quantity": 77.85, + "quantity": 25.41, "unit": "percent" }, "pledge": { - "quantity": 200, + "quantity": 248, "unit": "lovelace" }, "metadata": { - "homepage": "򲰠\u001a\u0005qL3", - "name": "eKሙ񼿾~,", - "ticker": "򄘮f':X", - "description": "H𧿾W􃙱/𔖇.\\#mew\u001d􂰿p^򄩜z\u0011Up񍫴#WC7W8`Wh8J\u000cu@󚝽򓺏򰎦2\\N\u0017#\u0004\t\u0000!󮉑񑗭v񧿊򙆂\u001bs񡩐/uIk\u001co@MxU1\u0002|\r񙮊󌝟򝢐?5\u0014󣩶\u0004\u0012m\u0008\u0013#l򏠟h\u001bdw~}𵀃󼝫\u0018\u001a42xq\u0008\u000f&\u0003𒭁\u0006B)m\u0008񙛍󺖟l\u0002-SO󂄓󻆐\u0008\u0004>F>򻡾𕡾=\u001d\u0014x\u000e\u0011T񳈴\u0019(󁙁4򘤠_󨅳3{bQ\u001b񭷺G򟩌\u001f" + "homepage": "򷗒\u0001Q񰋥m+eY4t\"b\u0000^wK]0󣾎zH@L𡊕^\u0013lO\u0018񰤜B\u000b>\u0012MK?𥲓h\u0016\u0014h\u0004𭵁𰰝񥎔x𻧽|񀺝%𹼠񭂢Y㤁\u0016\u000e'o\u0004+<2P񸬑\u001au󅱦󲗍V", + "name": "k{]\"i", + "ticker": "򙭾󽸴k", + "description": "?pO%\u000e7Q0L5񅡳D\u001cT'񬟜J\u001cg󍯤j𞩎uBnp\u0005\u0008v4Aᘨ[=񜈏8񓩁\u0018A컆a'\n3fk_b\u0010RXH񵖫򔐭󈨤;XD:Qd9m𒋞󜇇𨣹>\u0011B򏤈\u0018ASWSv\u0005H󾉾Zf򬚑%*\\K󤎈񂿽\u00134`[%\u0017򧆇\u001f:{5 ^x5\u0008$\\󠒫񪳀l庰󓬛򼉀򕣙\u0001t𸳾mfo=񫛖򓘭񑙤t򋮰󡫛\u0018G񏞚}\u000fA\u0011t󊧀&󿿕U󩩰T`|G8z)@*(}[\u0008𷬟@\u000fT\u0004򩲃R]i񸛱s%ht\u0018I_M񃥺/f񪒫~u\u0013򣰝\u000f4Oa#D񉇜M\u0019\u001cCx+\u0003|g򼥺𫉣+^z𭂿;_JA(\u0005򆒛-\rs!wNfծ\u001bsn\t񉼫P6v\u0005\n񂀧󙢃񓃻򅨣𳋜?\u0000ਵlr󘅃#\u0002BR񛯛񬗛QTz" }, - "id": "pool18jfu63v0h8gx82w2pdggfskct4lejy7kfzk5kmesuptl25ga7jj" + "id": "pool1nclnu8l5qnsgrdc9full4kta4pckzwkh600dducxyrm35q22dwu" }, { + "flags": [ + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted", + "delisted" + ], "metrics": { - "saturation": 4.975393457145774, + "saturation": 1.0444737007095983, "non_myopic_member_rewards": { - "quantity": 122384106809, + "quantity": 958698119066, "unit": "lovelace" }, "produced_blocks": { - "quantity": 7489956, + "quantity": 3442578, "unit": "block" }, "relative_stake": { - "quantity": 74.56, + "quantity": 21.12, "unit": "percent" } }, "retirement": { - "epoch_start_time": "1908-01-27T00:55:45.460634418303Z", - "epoch_number": 19317 + "epoch_start_time": "1872-07-25T22:00:00Z", + "epoch_number": 23284 }, "cost": { - "quantity": 242, + "quantity": 69, "unit": "lovelace" }, "margin": { - "quantity": 45.69, + "quantity": 31.27, "unit": "percent" }, "pledge": { - "quantity": 239, + "quantity": 192, "unit": "lovelace" }, - "metadata": { - "homepage": "SW(𙵁\u0000~6񩶷l+0C\u0017󔁗z\u0010𷌺KN^\u0000w󥨐󿶯👿`\u0007;󨪅􉻡\u000eu\t\\H􄥒_3$􅿋S(r\u001dgvsu?8󌝔糛X]MS\u001a\u001c$_=s\u0007C\u0014&󞳜:-󂜍n\u001f򩲣8ak;\u000e", - "name": "\u0008򊹚񵡦\u001e\u0006o󼪖o񫳥\u001cx\u001a]𲀛OXW򣰗򘮉an\u000b󙵹#ZGh\u0004gRE𖅷J\u0016𒂟򡫮LF𗲤\u0000\u0003h", - "ticker": "N򓋠e", - "description": ";\u00136\"rI\u0013񜡃b\u0001󓃀󿣯򾜒\u001e󼪤򅋨󇜩\"3mQB\u0010\u000b_sY#񦲿񫚮[wg򼈦ph󬦇󺝺\"\u0014󠠟\u000bTw\u0006f\"!\u001f#jOj򃺀*'>\"󾩢n𵺒`3\u001e&rJxll򰐰?B+g󥨒\u0013=!󒥤RHS-Yt\u0003td񁭚򨫮z\u0007򛡆" - }, - "id": "pool1xeknyngmmezr042e6g8xyy9w05r6ecstjxlt8j7ts3p77slrate" + "id": "pool1mnx8q7lhtep4h0k3dpzg9npl2kcgjxatpckc2kc7mghqxudeqv6" } ] } \ No newline at end of file diff --git a/lib/core/test/data/Cardano/Wallet/Api/ApiTPoolMetadataGCStatus.json b/lib/core/test/data/Cardano/Wallet/Api/ApiTPoolMetadataGCStatus.json new file mode 100644 index 00000000000..18df57a14c8 --- /dev/null +++ b/lib/core/test/data/Cardano/Wallet/Api/ApiTPoolMetadataGCStatus.json @@ -0,0 +1,39 @@ +{ + "seed": 1418264416350966807, + "samples": [ + { + "status": "not_started" + }, + { + "status": "not_started" + }, + { + "status": "has_run", + "last_run": "1866-08-30T12:00:00Z" + }, + { + "status": "has_run", + "last_run": "1859-12-29T07:42:46Z" + }, + { + "status": "not_started" + }, + { + "status": "not_applicable" + }, + { + "status": "not_applicable" + }, + { + "status": "not_applicable" + }, + { + "status": "has_run", + "last_run": "1885-09-08T15:11:50Z" + }, + { + "status": "restarting", + "last_run": "1875-12-06T21:00:00Z" + } + ] +} \ No newline at end of file diff --git a/lib/core/test/data/Cardano/Wallet/Api/ApiTStakePoolMetadata.json b/lib/core/test/data/Cardano/Wallet/Api/ApiTStakePoolMetadata.json index 054a0aee3f9..108fcf45688 100644 --- a/lib/core/test/data/Cardano/Wallet/Api/ApiTStakePoolMetadata.json +++ b/lib/core/test/data/Cardano/Wallet/Api/ApiTStakePoolMetadata.json @@ -1,64 +1,63 @@ { - "seed": 5786763469590622506, + "seed": -9194523005649707982, "samples": [ { - "homepage": "J!n.q4\u0004(񾶹g򯋥\n򏚐񞪌e\r3񙢠r34s򛴩\u000c򾋃\u001e򯧎񬌏\u0017\t𘙉vl\u001c𓺺󶾛N|\u0006򱝝\u0012\u0013񂙢v_}pXp򡻹)ᩑ\u001e󋐑v\u0000j\u0018e;W\"KYu򩺮'", - "name": ")IRX𱁑󔈷isE󕷍}*#\u001dAힱ`", - "ticker": "|󟁈,\u001a󝔌", - "description": "B񭯣\u001c𘚁񶲡𛍂񵓏!񚗟񬅇𝘃\u0013qN=W}8\t+0F\u0012􌗰𘳿侕򦬳񨠌c񱱁\u0015_󒢷𔩢vPM񒤢G򉳝󬹶\u001b𔼡Hi񦇬e9\u001cL񲋜'\u001b0i88}|QeF󱘣%򑒪𙖇fb\u0004򅬭_4\u000f>;𫣂2-|󋇡\u000c^\u0004@r6}\u001a􂎂L\u0008k\u0019@3auH󕟊OW񎇖[􍰅!񚳺\u0004Qy9󦋈񟔚򦫷H4!K򲰫򙯊u3\u0019X_l􎆠w0􂂩轐󾗈\n񛆛􇔔^\u0003򨢵%<>6\u000b\u001dh󫩨#\u001fI\"r1&󷚾$O񸿢u:\u0000掚\u0002񽊥/Q~𮙁񛛩򀤲~񌿅\u0008K[\u0015\u0016" + "homepage": "(L𾊺𒦛kH\u0007Zu2}yE󠜤\u001f𺑏򢸵n0`p1\u001a󲔃򜔬򴬫i񙈆N", + "name": "Lp󹬗r𼑠;", + "ticker": "󵘞_Gf槓򒧢6&u8񽢺E\u00088h񐵚9Ck=QYMG鬠Z+񑛺󷨉oTUc󞁃?򇧐󭬓r12v'󫯖M􄀃K/H6z񟤿\\n\u0013ge򿏔", - "name": "k\u001cyT񡹭񚹰_򓢄2\u0017Ym񵸇5H`\\AuT", - "ticker": "󹚜񭐱\u0014\u0017\u0016", - "description": "l\u0018FJ\u000b񖌫\u001c򇸅)򰁭&e&\u0010\u0016iL퇌壱3+\",\u001a'񺈶#9𯔍NWsBe`\t\u0003󁄩r" + "homepage": "efJU>3D&୸\u000f.𣃢[񽦄P򶜅B񑨼;o\u0006cDSDT<^扦S9Z\u0005􂈛󻧳m򳋇z\u0007\rp'pKk* \u0017G򌙓⺾\u000b񟷉", + "name": "z\u0010Oe𭮡@S񬔌\u0014{X\u0018\u0018Z󟺹'v\u001f\u001d v\u0016q", + "ticker": "]𮁜uo" }, { - "homepage": "y\r\\:񶶣N\u000cyog\"񈺛+07zOd\u0008eN\u000b*e}8\u000eS򪈜N򣥌򅁂󮯐\u0013$\u0010\u000eXO\u0001򦿵Br_F\r𲝮\u0007#`󁞜\u001d\u0006󉹦\u0016򬧏z򣭮\u001b Cw\u0013Oꪜ\u000b`+񴘢f9f", - "name": "<\u0019?MD\u000bE", - "ticker": "󈬅4d", - "description": "!z^a񧁆\u0001R񥖿\u0000𾴽\u0011G\u0005􏺎\u0005-𱟿񶈚󓰓򭭚\u0018f2&򮰞?򯲂𜣹\u0014𓆇4bV.6򩹦SP;\u0004s𵟲, ?4󪆪򃦥i󚻺\r]󻿔g𠘒𷊰\u0010n􎜙𪏏i񄘷󽭦 \u000c\u001dd\u0001󼛴\u000frjW\u0018>\u0004𙢻\u001c(rjYyPYE~񸉊m𘙉H𼤔\u0014['28\u001c񞽵𿊵񤉰Ik&_𣊝\u000c𣵸\r\u000c񟏸𞡦񅜛񧭑IJ$񲽇U򽹀V򴳸򨘄L+𝦬3\u001a炇\u0017\\gH\u001dky?c2}5`I\u0008W񂕊bA𦕞i񀤸\u001bW0\u0012'8\u001a𺴜󼢶\u001bD򻎢I򀷒X񖝧񐠻*^;R\u001f򠊖\u00133Z\u0004V*l\u0003IVL𚨬󁁪?񁂙Ge];୷\u0000\"hd\u0008[񓊤􋢌4X]𕍨4YLf󜃳<#&\t\u00075򌇷\u0016\u00164H\u0017\u0005AxjwdH_𹠴𺝋\u0015򦍌P1h󏁽+W\rQ" + "homepage": "s\u000f\t񣔑g򧨆A򚃟\n򾡄_񡐶񲹒\u0017`=\u0011􇘺\u001aXyH\u0018[񕾐򸝜uf\u001a7\u0016l26񜌃;tOh9L􉕝6t\u0001񽾫8N\u001d\u0002/(Z豥;󍿠{\u001fT- \u0010RR\u0007+󳌹}\u0005q𳏱󔜅", + "name": "4/d\u0013\u0018r/h\u001fN\n𩟑\u0016\u0011Jn;\u0018LK0#`򩜿z\u0012RZ#`q/򾺋𘈲𔱢{\u0011\u0011󃢜􍏰󜷁V%󆴓􅉉G", + "ticker": "󻱩=", + "description": "T󍴗n𴙭\u0001)\u0005𻏪\"%2󢴻cmK񜛚i\u0016Y\u001c\u0012󥏒󲥡Jk񳧍Sy1񬛘\u0008񠆎@\u00199򶛒󗙙\u0007𡟖\u0011eFW\u000b\u000b󱂭O\u001c\u0014N\u0004]w$󪫶\u0012\u0019+s\u001c\u0000\u0019\"" }, { - "homepage": "\u001aঃTd\u0005󺟛󱜷񐅭򘁖򗢶󊴽PZ[", - "name": "󠐷Mh@𸏝{4\u001a%\u001bi\u001c񓁙", - "ticker": "𳀟񶗣􂈃" + "homepage": "\u0003\u0007GE򣖔S󤜃&\\c5_\u0002\u000f񛼙*tg񨗌a\u001bZ5\u001b*0)uU񟒲𱜅򰛿*E󗛺~􍾘 >\u0002u=񯚈?\u0011Zy\t\u0017", + "name": "t󷤐𽎏`gV`T]", + "ticker": "\n𯸷MwH", + "description": "\u001a?nSS\u0003U-󇩚󭔏TD򰎬i\u0003𚀂C`\u0002t\u0002rB~򰀗i񹎍򱄱B;<7\u0001\u0008\u000e󙻥9jv򔦫6g}󲋐򱇷9LR1$󣇤>a\u0006󩥮}(Ftr%񕹫\u001cq", - "name": "\u0012N*H+\u00166D󬭦o=\u0012_𠘏𫘼𝺋R򅳯󠐆V󤿝\u000b6k=^񲵠RO*<\r'񭵷3P5hkH򺌂c򆾓\u001b\u001d*l𫏜", - "ticker": "[oi", - "description": "9\r])a\t𠓏m\u0016 Z\u0002hY36jo*+\u001b\nY8I\u0015V\u0019𦔘V\u0014y>񕝤슚I|u\u001dU<󓕋\u001a񿙜񞨵~>$򓸃&\u0001\u001dke🡥E 񝄢񕸑xu𧱙`򤺞\u0013G\u000ey򽌞F\u0017_8>\u001e:x􇹤,\u000ch\tG󣆀򈪄yI󵡝񈙻\u000e^𑄩/򜌨\u000c%\u0019}\u000bN\u000b&\u0010_N򛙝\u00065C󢏬J&𨦓\u000bg{\"0k􇳒򈆛P{\u0000\u0017\u001b򙒧󭗿I\u0007@􁟅\u0018\r\u00028\u0008񘍜QiL>+/w𷜹𭩗n񋳡s􂂲OAo\u0018Q񱶒\u0017󱼷\u0002\\63|]񙨻w􂰗EDA,\u0008Ah;\u001f𪯲\u0007\u001c\u0015考&\u0000򇏞0+~𓂡򠔰E@\u0012_\r򡝺o.t:\n*􇯢kN#D\u0010򽬙闍\u0018򿢥򪴯𒓳0\tY\u001d\n\u000f?n𛿍\\t鋯񼐵6򍋤𥧥U󇜮\u0003v=" + "homepage": "\u001f񲆒0]6#򽫉\u001e򍷔:scZ-\u0003򗆊0E󳘷g\u0005𱾀_f\u0016񗐂\"#NoF\u000cA_\u0004y\u0006", + "name": "\u000c񸰸y", + "ticker": "1󡲧E\u0004/" }, { - "homepage": "v򅏒.)+񸵼7񻏞d:😹?0:", - "name": "TW(-\u0000G󗺂^\u000e.t8E𤨫-򆃳n&aF\u0011\u000b󫐎dT򟝩\u0016@󗊁񰼲f", - "ticker": "p\u0000T9V", - "description": "𨣹y𹣟󚾾񋇰񭴶tQJ񐝈񟫹%g'O򿭀򥰟3<\u0000R/񎕊󽔈󌿍𱐧'򋆩\u0016c9\u0013>g" }, { - "homepage": "n\u0000\u0000𝶬\u0011򦚉\u0017g", - "name": "񠲓\u0011S\u0001񧜁򛸬S9w\u000eV\u0018u", - "ticker": "󛭨򨣎D", - "description": "񞴘\u000b\u0008^:𼈞򙊏Fn򠴥z񧛵jiz򠠅7KU󅃄\u000eh\u0011~,\u0010\u0006VWf]񝃸`񣭛yHvQt\u0003󚒮+j\u001e򳟗5\u0000?􎅇o\u0004=S嵔.󻕨󭕸uA>񱱳|󧄏\u0013󼱉.<񎣰\u0014\u0005|?O򶰉qu򰗮?󣹭88𳭜!ah\u000c\u0004m𾯙\"𾟏>󢸜󳣉\u0006𞼫\u0004zJu򹔏񴉆n\u0014\u0019􎬗򱂭>\u0006򁸗x]aSO\u001a򻙌\u0001U~O\u001e\u0018,7*shb\u001e\u00018\r%-3󝢭X\u001cA\u001d|\u0017o򇇥𢺴<\u0019&fPB 󝢋m\u0011\u0000t g+/\u0010*w󹗔\u0008(7R\u0018򀰤򨉽:\u0016󨰺􈢁󰦷e\u001dd&\u0003񁅰P\u001agWP1𶯦rv蜧|A𑲑\nE]\tM\u0006AM!" + "homepage": "1 _u<𳻞󧇓񕒃謡|-􂼇\u0003ymj+ꭶ򙩔3񛾂򠎧\u0000&A4Z6zg", + "name": "7$󑉰\u001em", + "ticker": "Dv\u0007𚶛𘲯", + "description": "D\\\u001fJ:H2I𑈝󞔱m/\u0015Z\u0018!򿙷\u0008\u0018Ey򅭁=DJ󾫂\u0012򨻅=\u0013𥉏e\".{󃆗`\u0006\u0014🀾𿾜RszZTih򎉷(^󩊺d\u000bJ\u0005r-򲮅􏜌e𝁁󰟷񭆸𔉶`򈖓!_\u001f8B>}\u0019KW򡌚\u001ai(^\u0003Y\u001e\u001fo\u0001𸯟\u001c󜌆\u0001򆈂J񼛒\u0018\u000b\u0001\u0018Z} y\u0014\u0013񒒛Yh\\MF#Ami$􋞖?L\u000e&\u0008򚞞.d򥬱򝴕\u0015p09i\u001a󓢈,O񯯉,󡲔\u0018\u0003g|\u0016O񯜳}z*\u0018l򗺏{*\"\u001dBn.+_𯬵Y" }, { - "homepage": "󒆕Q +v򳺮T\u0018 \u000f{=9UUE򉐃p20\\\u000c", - "name": "򾦘\u00125\nbIU\u0017>3󤝏", - "ticker": "+P񜷟", - "description": "x2|j\u0002-\u000cf", - "name": "!\u0014=D󣯦JQ\u00176#8F\tSu$񤡉R\\^,s\u0007\n𯗝.`|򖴫{\u0000&򷚡@j2", - "ticker": "P\u0016g", - "description": "󿠗\u000f+򖱁HgJ𱜴򏸟)󫷺\u0017󰓔\u0016<𨓪i\\򹜑\u0013).󥻙t^t]\u001c+\u000e{A\u0003f]L𱨌\"{=\\&}vH\t\u001a\u0015-,򌴦\u0010򫪱7񐵾!-񃟶 n󋛖Xp\u001b򓛡\u0003#_B𗁟뼷򀆛񆫚\u0018V򱎗H]G\u0006HY\u0005\u001ar򣑫+a򳸌L󨞣\u0005\u0015\u001e\u0004􋼤1U 7u2󦟦n񴖝򚫕k\u0008s󞎌𫷟\\&K@\u001e\u00152Yt d򌿥=+a&%𐨪񕀑E؝󲎸򾢽E\n򸛭\u000e\u0019S\u001c}05j\u0001\u0019󇛉򒰖U󟲺\u0000sck\t󈾋v_򣕪af\u0019\u000e\u0001[p\u0011/\u0003󅡭|m|\u001e򍤦g$񡪼\rs􁘈󵨒XS򔩜:v\u0000j򸑹\u0007I,Zt\u0007G0h9\r\u0001\u001f,#󪱓0Oj\u0001󞉓s񇲼󣟏񿢓󏩷\"*񄆥^󈔠瀀򬂍򑮢kE}\u000b\u0016+1󓟼@\u000e񩺩ZGu\u000b3\u000b" + "homepage": "(􅛵;󔼛7a󃒗\r򄥛W\\󖉇\u0018򱒤:􍦂e\u000c a򛏴\u0013򘔜󘈚0🗣#5𯼦,\u0012񶦄󾗫𳲜9BFHy\n3\u0015񈲋🲜᱑~/􁖜ea*\nꧼBx\u0004򂓕𼒼e𺁓ܡr󧏙c\u0010񩒆s\u001bDkY󻿜󔳎򦽳H\u0015M\nY;\u000f}Y񼆘5W\u0012𡷽\u0011", + "name": "&Q\u0017O𪯐IF󱂄lQ6s\u0018\"Z򑃈\n'b񽇈\u00057&\u0002󥐏", + "ticker": "`\"\u001f", + "description": "𥞮AJDy5W򏾐𥝦!K󪃈5𤔨G\u001b񧂩􍏞i󩿀bG򂌘C-@]\u0004󩁸a{<\u0014{*%Y򉻣%R񆁜?񞩏񃸜\u0017L<7\u0018\u001dq\tk񋒥'򏙟\n=Wx&ic\"\u001aP]󢴾D\rE𼌀\u001c@\u00083䴥\u0011I􎡍(򔝟򚈌W\u0019|P\u0019\u0008?\u0011쯼򏴸񀱣\u001f9|)H?\u001b\u0010V.|𝟧𨛭C\u0004&+Z󓬇cNw􌎭󧸲h򴘃0\u001b9<6}񨺻\u0011c𡾠𽴛AO𒔞v;𮾊=󊌟:򬿉6{Z񹐪g_󮓌O򿖼\u0012^\u0010&\u0007ix<;􎥏\u001d󾏃h\r\"򍣌1@kQi󁇫򻵟C留9]\u0018=󈩏\"񭙤=󝉉 𫏔󆙶홰6,󚆳\u0019\u0002S\u000fHBX\u0015񔀇w񏃘\u0010v;𢊴\u0006\u001fT{\u0012\u0019𢄊L󰧳󖱇5񵁯\u0010GP\u0000ᤏx󑒄b+" }, { - "homepage": "󪤀\n\u001aC\t򒕒!򀻗񺣧\u001f򃾺P򌦂񠷾X񴄭", - "name": "򗣀󂴴𩞌m", - "ticker": "𕩌rC㋄", - "description": "K}>\u001b\u000f򩉒#\u0015Xq񣁚󞒒kp\u0001~hM󔃗\u001b0\u0013\u00169\u000e󸓠󱯟Y4\u0015\u0016\u001a\u000f\u0017" + "homepage": "LA/\u001c󞴂/\u0013𶰱QJT\t򂔅:(.(򗖕Y4𞜏\"H𡈈򟣼\u001byY\\p^񶸂#Zn򉴟󙣟VS𭴏C.e𣒿<}|򐨴|'񏐍x𱬨T󄽋\u001eJC[s[/󔲒H򳋽\u001e򭰹\u0018s\u0007\u0019񍦦dx7[󼰀\u000f\u0002&񜌑h򅵷\t񄕝j쌯", + "name": "_y񜁳𛷷󸆼JNjQ~􀖆;S\u001du*󯥹(?񒢂􁤸AE;Z󚡄\u0000Q\u0015\u0010󅒉", + "ticker": "\u0003𨌠\r󽟘", + "description": "񫚜\u000e\u0017J\u0016O󚊉\u000f󛷛\u0003\u001d\rfPNC!\u0011򧰍}a𼤵Ll󏨯񍲒\u0008\u0016(󗣡c࡭Hq.򱌌\u001eT𭥻\u000e\u0011񠺢!񞭀񌲙/򨋑𜯶𦅁\u001cX缱h:񦻙MyAL\u0010\u001e4?󌳗\u0001\u0004k󕸁>\u0018PD񃶖pA򢇮Q\u0002\u000b/񔥲󪱲HPyTK[5񘨓j:F\u0013𽐠s0(󎶦*2g\t|\u000bK;𰬊8e󖊋[𳺈H\u0008:󜐢mdGs=\u0003T󾹥𝱃L6_\\򅘦q񟔂t񳯆A𜽎`qlF-\u00103򌊌\t\u0007򍀕􆩣\u000be򙠛񦭢" } ] } \ No newline at end of file diff --git a/lib/core/test/data/Cardano/Wallet/Api/SMASHPoolId.json b/lib/core/test/data/Cardano/Wallet/Api/SMASHPoolId.json new file mode 100644 index 00000000000..ec0bd9b35b7 --- /dev/null +++ b/lib/core/test/data/Cardano/Wallet/Api/SMASHPoolId.json @@ -0,0 +1,35 @@ +{ + "seed": 1693755052676937632, + "samples": [ + { + "pool_id": "961d329fba1807eef89db767ba405aec0c5426501c6b1df20f5c0995" + }, + { + "pool_id": "3d9aab7ac059512c948fe8bb773aad076c5e8b3941fa4fbcdff34597" + }, + { + "pool_id": "ff5b4952dd7734f07e4905dea64fa230fb75f7b2d603d154d9ff1d43" + }, + { + "pool_id": "a6906f8ecfcc437375bd8763120ac5c96ae4796c8f78f549193e7b36" + }, + { + "pool_id": "74d3e2c4d640dd181def5a5b6b22308b5a835b98ccfb7143d52bd150" + }, + { + "pool_id": "81017236ed16380bb96bd02bbd452541f3e5694e14196f65e37ce502" + }, + { + "pool_id": "a6906f8ecfcc437375bd8763120ac5c96ae4796c8f78f549193e7b36" + }, + { + "pool_id": "3d9aab7ac059512c948fe8bb773aad076c5e8b3941fa4fbcdff34597" + }, + { + "pool_id": "5ee7591bf30eaa4f5dce70b4a676eb02d5be8012d188f04fe3beffb0" + }, + { + "pool_id": "eb7832cb137b6d20ee2c3f4892d4938a734326ca18122f0d21e5f587" + } + ] +} \ No newline at end of file diff --git a/lib/core/test/unit/Cardano/Pool/DB/Arbitrary.hs b/lib/core/test/unit/Cardano/Pool/DB/Arbitrary.hs index e6e7c5bb72e..bcf86450472 100644 --- a/lib/core/test/unit/Cardano/Pool/DB/Arbitrary.hs +++ b/lib/core/test/unit/Cardano/Pool/DB/Arbitrary.hs @@ -54,7 +54,7 @@ import Control.Monad import Data.Function ( (&) ) import Data.Generics.Internal.VL.Lens - ( (^.) ) + ( view, (^.) ) import Data.Maybe ( fromJust ) import Data.Ord @@ -166,10 +166,13 @@ instance Arbitrary PoolOwner where return $ PoolOwner $ B8.pack (replicate 32 byte) instance Arbitrary PoolRegistrationCertificate where - shrink (PoolRegistrationCertificate pid owners m c pl md) = - (\pid' owners' -> PoolRegistrationCertificate pid' owners' m c pl md) - <$> shrink pid - <*> shrinkOwners owners + shrink regCert = do + shrunkPoolId <- shrink $ view #poolId regCert + shrunkPoolOwners <- shrinkOwners $ view #poolOwners regCert + pure regCert + { poolId = shrunkPoolId + , poolOwners = shrunkPoolOwners + } where shrinkOwners os = -- A valid registration certificate must have at least one owner: @@ -398,4 +401,3 @@ instance Arbitrary PoolMetadataSource where instance Arbitrary Settings where shrink = genericShrink arbitrary = genericArbitrary - diff --git a/lib/core/test/unit/Cardano/Pool/DB/Properties.hs b/lib/core/test/unit/Cardano/Pool/DB/Properties.hs index a7a3cfa0da1..185f60bbd76 100644 --- a/lib/core/test/unit/Cardano/Pool/DB/Properties.hs +++ b/lib/core/test/unit/Cardano/Pool/DB/Properties.hs @@ -6,7 +6,9 @@ {-# LANGUAGE OverloadedLabels #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE TypeApplications #-} {-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeSynonymInstances #-} {-# OPTIONS_GHC -fno-warn-orphans #-} module Cardano.Pool.DB.Properties @@ -44,7 +46,7 @@ import Cardano.Wallet.Primitive.Types , PoolId , PoolLifeCycleStatus (..) , PoolRegistrationCertificate (..) - , PoolRetirementCertificate (..) + , PoolRetirementCertificate , Settings , SlotNo (..) , StakePoolMetadata (..) @@ -87,6 +89,8 @@ import Data.Quantity ( Quantity (..) ) import Data.Text.Class ( toText ) +import Data.Time.Clock.POSIX + ( POSIXTime ) import Data.Word ( Word64 ) import Fmt @@ -217,6 +221,10 @@ properties = do (property . prop_putHeaderListHeader) it "modSettings . readSettings == id" (property . prop_modSettingsReadSettings) + it "putLastMetadataGC . readLastMetadataGC == id" + (property . prop_putLastMetadataGCReadLastMetadataGC) + it "putDelistedPools >> readDelistedPools shows the pool as delisted" + (property . prop_putDelistedPools) {------------------------------------------------------------------------------- Properties @@ -1430,6 +1438,68 @@ prop_modSettingsReadSettings DBLayer{..} settings = do assertWith "Modifying settings and reading afterwards works" (modSettings' == settings) +-- | read . put == id +prop_putLastMetadataGCReadLastMetadataGC + :: DBLayer IO + -> POSIXTime + -> Property +prop_putLastMetadataGCReadLastMetadataGC DBLayer{..} posixTime = do + monadicIO (setup >> prop) + where + setup = run $ atomically cleanDB + prop = do + defGCTime <- run $ atomically readLastMetadataGC + assertWith + "Reading sync time from empty db returns Nothing" + (isNothing defGCTime) + run $ atomically $ putLastMetadataGC posixTime + time <- run $ atomically readLastMetadataGC + assertWith "Setting sync time and reading afterwards works" + (time == Just posixTime) + +-- Check that 'putDelistedPools' completely overwrites the existing set +-- of delisted pools every time: +-- +prop_putDelistedPools + :: DBLayer IO + -> [PoolId] + -> [PoolId] + -> Property +prop_putDelistedPools DBLayer {..} pools1 pools2 = + checkCoverage + $ cover 2 (Set.size poolSet1 == 0) + "number of pools in set #1 = 0" + $ cover 2 (Set.size poolSet1 == 1) + "number of pools in set #1 = 1" + $ cover 2 (Set.size poolSet1 > 1) + "number of pools in set #1 > 1" + $ cover 2 (Set.size poolSet2 == 0) + "number of pools in set #2 = 0" + $ cover 2 (Set.size poolSet2 == 1) + "number of pools in set #2 = 1" + $ cover 2 (Set.size poolSet2 > 1) + "number of pools in set #2 > 1" + $ monadicIO (setup >> prop) + where + poolSet1 = Set.fromList pools1 `Set.difference` Set.fromList pools2 + poolSet2 = Set.fromList pools2 `Set.difference` Set.fromList pools1 + + setup = run $ atomically cleanDB + + prop = forM_ [poolSet1, poolSet2] $ \poolsToMarkAsDelisted -> do + run $ atomically $ putDelistedPools $ + Set.toList poolsToMarkAsDelisted + poolsActuallyDelisted <- Set.fromList . L.sort <$> + run (atomically readDelistedPools) + monitor $ counterexample $ unlines + [ "Pools to mark as delisted: " + , pretty $ Set.toList poolsToMarkAsDelisted + , "Pools actually delisted: " + , pretty $ Set.toList poolsActuallyDelisted + ] + assertWith "poolsToMarkAsDelisted == poolsActuallyDelisted" + $ poolsToMarkAsDelisted == poolsActuallyDelisted + descSlotsPerPool :: Map PoolId [BlockHeader] -> Expectation descSlotsPerPool pools = do let checkIfDesc slots = @@ -1483,3 +1553,8 @@ testCertificatePublicationTimes = instance Arbitrary BlockHeader where arbitrary = genSlotNo >>= genBlockHeader + +instance Arbitrary POSIXTime where + arbitrary = do + NonNegative int <- arbitrary @(NonNegative Int) + pure (fromIntegral int) diff --git a/lib/core/test/unit/Cardano/Wallet/Api/Malformed.hs b/lib/core/test/unit/Cardano/Wallet/Api/Malformed.hs index f82715fe217..d0e2e02fbfa 100644 --- a/lib/core/test/unit/Cardano/Wallet/Api/Malformed.hs +++ b/lib/core/test/unit/Cardano/Wallet/Api/Malformed.hs @@ -52,6 +52,7 @@ import Prelude import Cardano.Wallet.Api.Types ( ApiAddressData , ApiAddressInspectData + , ApiMaintenanceActionPostData , ApiPoolId , ApiPostRandomAddressData , ApiPutAddressesData @@ -1139,6 +1140,15 @@ instance Malformed (BodyParam SettingsPutData) where ) ] +instance Malformed (BodyParam ApiMaintenanceActionPostData) where + malformed = first (BodyParam . Aeson.encode) <$> + [ ( [aesonQQ| + { "maintenance_action": "unknown_action" + }|] + , "Error in $['maintenance_action']: parsing Cardano.Wallet.Api.Types.MaintenanceAction failed, expected one of the tags ['gc_stake_pools'], but found tag 'unknown_action'" + ) + ] + -- -- Class instances (Header) -- diff --git a/lib/core/test/unit/Cardano/Wallet/Api/TypesSpec.hs b/lib/core/test/unit/Cardano/Wallet/Api/TypesSpec.hs index 88706b3fb48..27687630a75 100644 --- a/lib/core/test/unit/Cardano/Wallet/Api/TypesSpec.hs +++ b/lib/core/test/unit/Cardano/Wallet/Api/TypesSpec.hs @@ -63,6 +63,8 @@ import Cardano.Wallet.Api.Types , ApiEpochInfo (..) , ApiErrorCode (..) , ApiFee (..) + , ApiMaintenanceAction (..) + , ApiMaintenanceActionPostData (..) , ApiMnemonicT (..) , ApiNetworkClock (..) , ApiNetworkInformation (..) @@ -76,6 +78,7 @@ import Cardano.Wallet.Api.Types , ApiSlotId (..) , ApiSlotReference (..) , ApiStakePool (..) + , ApiStakePoolFlag (..) , ApiStakePoolMetrics (..) , ApiT (..) , ApiTransaction (..) @@ -155,6 +158,7 @@ import Cardano.Wallet.Primitive.Types , EpochNo (..) , HistogramBar (..) , PoolId (..) + , PoolMetadataGCStatus (..) , PoolMetadataSource , PoolOwner (..) , Settings @@ -249,6 +253,8 @@ import Data.Text.Class ( FromText (..), TextDecodingError (..), ToText (..) ) import Data.Time.Clock ( NominalDiffTime ) +import Data.Time.Clock.POSIX + ( utcTimeToPOSIXSeconds ) import Data.Word ( Word32, Word8 ) import Data.Word.Odd @@ -408,6 +414,8 @@ spec = do jsonRoundtripAndGolden $ Proxy @(ApiT StakePoolMetadata) jsonRoundtripAndGolden $ Proxy @ApiPostRandomAddressData jsonRoundtripAndGolden $ Proxy @ApiTxMetadata + jsonRoundtripAndGolden $ Proxy @ApiMaintenanceAction + jsonRoundtripAndGolden $ Proxy @ApiMaintenanceActionPostData describe "Textual encoding" $ do describe "Can perform roundtrip textual encoding & decoding" $ do @@ -1180,9 +1188,16 @@ instance Arbitrary ApiTxId where instance Arbitrary AddressPoolGap where arbitrary = arbitraryBoundedEnum +instance Arbitrary NominalDiffTime where + arbitrary = fmap utcTimeToPOSIXSeconds genUniformTime + instance Arbitrary Iso8601Time where arbitrary = Iso8601Time <$> genUniformTime +instance Arbitrary PoolMetadataGCStatus where + arbitrary = genericArbitrary + shrink = genericShrink + instance Arbitrary SortOrder where arbitrary = arbitraryBoundedEnum shrink = genericShrink @@ -1319,6 +1334,7 @@ instance Arbitrary ApiStakePool where <*> arbitrary <*> arbitrary <*> arbitrary + <*> arbitrary instance Arbitrary ApiStakePoolMetrics where arbitrary = ApiStakePoolMetrics @@ -1327,6 +1343,10 @@ instance Arbitrary ApiStakePoolMetrics where <*> (choose (0.0, 5.0)) <*> (Quantity . fromIntegral <$> choose (1::Integer, 22_600_000)) +instance Arbitrary ApiStakePoolFlag where + shrink = genericShrink + arbitrary = genericArbitrary + instance Arbitrary StakePoolMetadata where arbitrary = StakePoolMetadata <$> arbitrary @@ -1369,6 +1389,14 @@ instance Arbitrary WalletName where instance Arbitrary ApiWalletPassphraseInfo where arbitrary = ApiWalletPassphraseInfo <$> genUniformTime +instance Arbitrary ApiMaintenanceAction where + arbitrary = genericArbitrary + shrink = genericShrink + +instance Arbitrary ApiMaintenanceActionPostData where + arbitrary = genericArbitrary + shrink = genericShrink + instance Arbitrary SyncProgress where arbitrary = genericArbitrary shrink = genericShrink @@ -1512,6 +1540,16 @@ instance Arbitrary ApiVerificationKey where instance ToSchema ApiVerificationKey where declareNamedSchema _ = declareSchemaForDefinition "ApiVerificationKey" +instance Arbitrary Api.MaintenanceAction where + arbitrary = genericArbitrary + shrink = genericShrink + +instance ToSchema Api.ApiMaintenanceAction where + declareNamedSchema _ = declareSchemaForDefinition "ApiMaintenanceAction" + +instance ToSchema Api.ApiMaintenanceActionPostData where + declareNamedSchema _ = declareSchemaForDefinition "ApiMaintenanceActionPostData" + instance Arbitrary ApiNetworkParameters where arbitrary = genericArbitrary shrink = genericShrink diff --git a/lib/core/test/unit/Cardano/Wallet/DB/Sqlite/TypesSpec.hs b/lib/core/test/unit/Cardano/Wallet/DB/Sqlite/TypesSpec.hs index 2acf83c88c3..578e65f2e75 100644 --- a/lib/core/test/unit/Cardano/Wallet/DB/Sqlite/TypesSpec.hs +++ b/lib/core/test/unit/Cardano/Wallet/DB/Sqlite/TypesSpec.hs @@ -19,6 +19,8 @@ import Cardano.Wallet.Primitive.Types ( EpochNo (..), SlotInEpoch (..), SlotNo ) import Data.Proxy ( Proxy (..) ) +import Data.Time.Clock.POSIX + ( POSIXTime ) import Data.Typeable ( Typeable, typeRep ) import Data.Word.Odd @@ -29,6 +31,7 @@ import Test.Hspec ( Spec, describe, it ) import Test.QuickCheck ( Arbitrary (..) + , NonNegative (..) , arbitrarySizedBoundedIntegral , property , shrinkIntegral @@ -39,6 +42,7 @@ spec :: Spec spec = do describe "Values can be persisted and unpersisted successfully" $ do persistRoundtrip $ Proxy @SlotNo + persistRoundtrip $ Proxy @POSIXTime -- | Constructs a test to check that roundtrip persistence and unpersistence is -- possible for values of the given type. @@ -57,6 +61,11 @@ persistRoundtrip proxy = it Arbitrary Instances -------------------------------------------------------------------------------} +instance Arbitrary POSIXTime where + arbitrary = do + NonNegative int <- arbitrary @(NonNegative Int) + pure (fromIntegral int) + instance Arbitrary SlotNo where arbitrary = genSlotNo shrink = shrinkSlotNo diff --git a/lib/jormungandr/src/Cardano/Wallet/Jormungandr/Api/Server.hs b/lib/jormungandr/src/Cardano/Wallet/Jormungandr/Api/Server.hs index 6fe59996c4e..65ce9ab8b3b 100644 --- a/lib/jormungandr/src/Cardano/Wallet/Jormungandr/Api/Server.hs +++ b/lib/jormungandr/src/Cardano/Wallet/Jormungandr/Api/Server.hs @@ -216,6 +216,8 @@ server byron icarus jormungandr spl ntp = (getPoolLifeCycleStatus spl) :<|> quitStakePool jormungandr :<|> delegationFee jormungandr + :<|> (\_ -> throwError err501) + :<|> throwError err501 byronWallets :: Server ByronWallets byronWallets = diff --git a/lib/jormungandr/src/Cardano/Wallet/Jormungandr/Binary.hs b/lib/jormungandr/src/Cardano/Wallet/Jormungandr/Binary.hs index e2e6c122043..bb1ae74ad8b 100644 --- a/lib/jormungandr/src/Cardano/Wallet/Jormungandr/Binary.hs +++ b/lib/jormungandr/src/Cardano/Wallet/Jormungandr/Binary.hs @@ -1090,7 +1090,9 @@ poolRegistrationsFromBlock (Block _hdr fragments) = do let margin = fromRight maxBound $ mkPercentage $ toRational $ taxRatio taxes let cost = Quantity (taxFixed taxes) let dummyPledge = Quantity 0 - pure $ W.PoolRegistrationCertificate poolId owners margin cost dummyPledge Nothing + let metadata = Nothing + pure $ W.PoolRegistrationCertificate + poolId owners margin cost dummyPledge metadata -- | If all incentives parameters are present in the blocks, returns a function -- that computes reward based on a given epoch. diff --git a/lib/jormungandr/test/unit/Cardano/Wallet/Jormungandr/ApiSpec.hs b/lib/jormungandr/test/unit/Cardano/Wallet/Jormungandr/ApiSpec.hs index ecde489c2f6..435c9649b71 100644 --- a/lib/jormungandr/test/unit/Cardano/Wallet/Jormungandr/ApiSpec.hs +++ b/lib/jormungandr/test/unit/Cardano/Wallet/Jormungandr/ApiSpec.hs @@ -81,6 +81,8 @@ import Test.QuickCheck ( Arbitrary (..), Gen, applyArbitrary3, choose, frequency, vector ) import Test.Utils.Paths ( getTestData ) +import Test.Utils.Time + ( genUniformTime ) import qualified Cardano.Wallet.Api.Types as W import qualified Data.Aeson as Aeson @@ -329,6 +331,9 @@ instance Arbitrary StakePoolTicker where len <- choose (3, 5) replicateM len arbitrary +instance Arbitrary W.Iso8601Time where + arbitrary = W.Iso8601Time <$> genUniformTime + instance ToSchema ApiStakePool where declareNamedSchema _ = declareSchemaForDefinition "ApiJormungandrStakePool" diff --git a/lib/shelley/cardano-wallet.cabal b/lib/shelley/cardano-wallet.cabal index b8509e2db36..83b7a97926c 100644 --- a/lib/shelley/cardano-wallet.cabal +++ b/lib/shelley/cardano-wallet.cabal @@ -63,6 +63,7 @@ library , memory , network , network-mux + , network-uri , optparse-applicative , ouroboros-consensus , ouroboros-consensus-byron diff --git a/lib/shelley/src/Cardano/Wallet/Shelley.hs b/lib/shelley/src/Cardano/Wallet/Shelley.hs index 222c31b30f4..b2818a67638 100644 --- a/lib/shelley/src/Cardano/Wallet/Shelley.hs +++ b/lib/shelley/src/Cardano/Wallet/Shelley.hs @@ -104,6 +104,7 @@ import Cardano.Wallet.Primitive.Types , Block , ChimericAccount , NetworkParameters (..) + , PoolMetadataGCStatus (..) , ProtocolParameters (..) , Settings (..) , SlottingParameters (..) @@ -151,6 +152,8 @@ import Data.Text ( Text ) import Data.Text.Class ( ToText (..) ) +import GHC.Conc + ( newTVarIO ) import GHC.Generics ( Generic ) import Network.Ntp @@ -331,9 +334,11 @@ serveWallet (timeInterpreter nl) $ \db@DBLayer{..} -> do + gcStatus <- newTVarIO NotStarted forM_ settings $ atomically . putSettings void $ forkFinally (monitorStakePools tr gp nl db) onExit - spl <- newStakePoolLayer nl db $ forkFinally (monitorMetadata tr sp db) onExit + spl <- newStakePoolLayer gcStatus nl db + $ forkFinally (monitorMetadata gcStatus tr sp db) onExit action spl where tr = contramap (MsgFromWorker mempty) poolsEngineTracer diff --git a/lib/shelley/src/Cardano/Wallet/Shelley/Api/Server.hs b/lib/shelley/src/Cardano/Wallet/Shelley/Api/Server.hs index 2a29ce6a51e..4dd63997d52 100644 --- a/lib/shelley/src/Cardano/Wallet/Shelley/Api/Server.hs +++ b/lib/shelley/src/Cardano/Wallet/Shelley/Api/Server.hs @@ -106,10 +106,13 @@ import Cardano.Wallet.Api.Types , ApiAddressInspectData (..) , ApiCredential (..) , ApiErrorCode (..) + , ApiMaintenanceAction (..) + , ApiMaintenanceActionPostData (..) , ApiSelectCoinsAction (..) , ApiSelectCoinsData (..) , ApiStakePool , ApiT (..) + , MaintenanceAction (..) , SettingsPutData (..) , SomeByronWalletPostData (..) ) @@ -264,6 +267,8 @@ server byron icarus shelley spl ntp = :<|> joinStakePool shelley (knownPools spl) (getPoolLifeCycleStatus spl) :<|> quitStakePool shelley :<|> delegationFee shelley + :<|> postPoolMaintenance + :<|> getPoolMaintenance where listStakePools_ = \case Just (ApiT stake) -> do @@ -275,6 +280,15 @@ server byron icarus shelley spl ntp = , "parameter as it affects the rewards and ranking." ] + postPoolMaintenance action = do + case action of + ApiMaintenanceActionPostData GcStakePools -> + liftIO $ forceMetadataGC spl + getPoolMaintenance + + getPoolMaintenance = + liftIO (ApiMaintenanceAction . ApiT <$> getGCMetadataStatus spl) + byronWallets :: Server ByronWallets byronWallets = (\case diff --git a/lib/shelley/src/Cardano/Wallet/Shelley/Compatibility.hs b/lib/shelley/src/Cardano/Wallet/Shelley/Compatibility.hs index 73d6ee0c0bd..02d50b1aa11 100644 --- a/lib/shelley/src/Cardano/Wallet/Shelley/Compatibility.hs +++ b/lib/shelley/src/Cardano/Wallet/Shelley/Compatibility.hs @@ -1090,7 +1090,6 @@ inspectAddress = inspect = maybe (Left errMalformedAddress) Right . inspectShelleyAddress mRootPub . unsafeMkAddress - -- TODO: It's possible to inspect a byron address, given a root XPub. -- However, this is not yet exposed by the API. mRootPub = Nothing diff --git a/lib/shelley/src/Cardano/Wallet/Shelley/Launch.hs b/lib/shelley/src/Cardano/Wallet/Shelley/Launch.hs index bec3c4a2a85..e87788e571f 100644 --- a/lib/shelley/src/Cardano/Wallet/Shelley/Launch.hs +++ b/lib/shelley/src/Cardano/Wallet/Shelley/Launch.hs @@ -4,6 +4,7 @@ {-# LANGUAGE LambdaCase #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE NumericUnderscores #-} +{-# LANGUAGE PackageImports #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} diff --git a/lib/shelley/src/Cardano/Wallet/Shelley/Pools.hs b/lib/shelley/src/Cardano/Wallet/Shelley/Pools.hs index 59a82a4db4c..7e97d5ac2d4 100644 --- a/lib/shelley/src/Cardano/Wallet/Shelley/Pools.hs +++ b/lib/shelley/src/Cardano/Wallet/Shelley/Pools.hs @@ -5,6 +5,7 @@ {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE NumericUnderscores #-} {-# LANGUAGE OverloadedLabels #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE Rank2Types #-} @@ -42,6 +43,7 @@ import Cardano.Pool.DB import Cardano.Pool.Metadata ( StakePoolMetadataFetchLog , defaultManagerSettings + , fetchDelistedPools , fetchFromRemote , identityUrlBuilder , newManager @@ -80,6 +82,7 @@ import Cardano.Wallet.Primitive.Types , PoolCertificate (..) , PoolId , PoolLifeCycleStatus (..) + , PoolMetadataGCStatus (..) , PoolMetadataSource (..) , PoolRegistrationCertificate (..) , PoolRetirementCertificate (..) @@ -107,9 +110,16 @@ import Cardano.Wallet.Shelley.Network import Cardano.Wallet.Unsafe ( unsafeMkPercentage ) import Control.Concurrent - ( threadDelay ) + ( forkFinally, threadDelay ) import Control.Exception - ( SomeException (..), bracket, mask_, try ) + ( AsyncException (..) + , SomeException (..) + , asyncExceptionFromException + , bracket + , finally + , mask_ + , try + ) import Control.Monad ( forM, forM_, forever, void, when, (<=<) ) import Control.Monad.IO.Class @@ -135,15 +145,19 @@ import Data.Map import Data.Map.Merge.Strict ( dropMissing, traverseMissing, zipWithAMatched, zipWithMatched ) import Data.Maybe - ( catMaybes ) + ( catMaybes, fromMaybe ) import Data.Ord ( Down (..) ) import Data.Quantity ( Percentage (..), Quantity (..) ) import Data.Set ( Set ) +import Data.Text + ( Text ) import Data.Text.Class ( ToText (..) ) +import Data.Time.Clock.POSIX + ( getPOSIXTime, posixDayLength ) import Data.Tuple.Extra ( dupe ) import Data.Word @@ -154,6 +168,8 @@ import GHC.Conc ( TVar, ThreadId, killThread, newTVarIO, readTVarIO, writeTVar ) import GHC.Generics ( Generic ) +import Network.URI + ( URI (..) ) import Ouroboros.Consensus.Cardano.Block ( CardanoBlock, HardForkBlock (..) ) import System.Random @@ -192,26 +208,33 @@ data StakePoolLayer = StakePoolLayer -> Coin -> ExceptT ErrListPools IO [Api.ApiStakePool] + , forceMetadataGC :: IO () + , putSettings :: Settings -> IO () , getSettings :: IO Settings + + , getGCMetadataStatus :: IO PoolMetadataGCStatus } newStakePoolLayer :: forall sc. () - => NetworkLayer IO (IO Shelley) (CardanoBlock sc) + => TVar PoolMetadataGCStatus + -> NetworkLayer IO (IO Shelley) (CardanoBlock sc) -> DBLayer IO -> IO ThreadId -> IO StakePoolLayer -newStakePoolLayer nl db@DBLayer {..} worker = do +newStakePoolLayer gcStatus nl db@DBLayer {..} worker = do tid <- worker tvTid <- newTVarIO tid pure $ StakePoolLayer { getPoolLifeCycleStatus = _getPoolLifeCycleStatus , knownPools = _knownPools , listStakePools = _listPools + , forceMetadataGC = _forceMetadataGC tvTid , putSettings = _putSettings tvTid , getSettings = _getSettings + , getGCMetadataStatus = _getGCMetadataStatus } where _getPoolLifeCycleStatus @@ -227,17 +250,9 @@ newStakePoolLayer nl db@DBLayer {..} worker = do -- In order to apply the settings, we have to restart the -- metadata sync thread as well to avoid race conditions. _putSettings :: TVar ThreadId -> Settings -> IO () - _putSettings tvTid settings = do - bracket - killSyncThread - (\_ -> restartSyncThread) - (\_ -> atomically (gcMetadata >> writeSettings)) + _putSettings tvTid settings = + bracketSyncThread tvTid (atomically (gcMetadata >> writeSettings)) where - -- kill syncing thread, so we can apply the settings cleanly - killSyncThread = do - tid <- readTVarIO tvTid - killThread tid - -- clean up metadata table if the new sync settings suggests so gcMetadata = do oldSettings <- readSettings @@ -252,10 +267,7 @@ newStakePoolLayer nl db@DBLayer {..} worker = do writeSettings = putSettings settings - restartSyncThread = do - tid <- worker - STM.atomically $ writeTVar tvTid tid - + _getSettings :: IO Settings _getSettings = liftIO $ atomically readSettings _listPools @@ -321,6 +333,36 @@ newStakePoolLayer nl db@DBLayer {..} worker = do rewards = view (#metrics . #nonMyopicMemberRewards) . stakePool (randomWeight, stakePool) = (fst, snd) + _forceMetadataGC :: TVar ThreadId -> IO () + _forceMetadataGC tvTid = + -- We force a GC by resetting last sync time to 0 (start of POSIX + -- time) and have the metadata thread restart. + bracketSyncThread tvTid $ do + lastGC <- atomically readLastMetadataGC + case lastGC of + Nothing -> STM.atomically $ writeTVar gcStatus NotStarted + Just gc -> STM.atomically $ writeTVar gcStatus (Restarting gc) + atomically $ putLastMetadataGC $ fromIntegral @Int 0 + + _getGCMetadataStatus = + readTVarIO gcStatus + + -- Stop the sync thread, carry out an action, and restart the sync thread. + bracketSyncThread :: TVar ThreadId -> IO a -> IO () + bracketSyncThread tvTid action = + void $ bracket + killSyncThread + (\_ -> restartSyncThread) + (\_ -> action) + where + killSyncThread = do + tid <- readTVarIO tvTid + killThread tid + + restartSyncThread = do + tid <- worker + STM.atomically $ writeTVar tvTid tid + -- -- Data Combination functions -- @@ -339,6 +381,7 @@ data PoolDbData = PoolDbData , retirementCert :: Maybe PoolRetirementCertificate , nProducedBlocks :: Quantity "block" Word64 , metadata :: Maybe StakePoolMetadata + , delisted :: Bool } -- | Top level combine-function that merges DB and LSQ data. @@ -413,7 +456,10 @@ combineDbAndLsqData ti nOpt lsqData = fmap fromIntegral $ poolPledge $ registrationCert dbData , Api.margin = Quantity $ poolMargin $ registrationCert dbData - , Api.retirement = retirementEpochInfo + , Api.retirement = + retirementEpochInfo + , Api.flags = + [ Api.Delisted | delisted dbData ] } toApiEpochInfo ep = do @@ -465,8 +511,9 @@ combineChainData -> Map PoolId PoolRetirementCertificate -> Map PoolId (Quantity "block" Word64) -> Map StakePoolMetadataHash StakePoolMetadata + -> Set PoolId -> Map PoolId PoolDbData -combineChainData registrationMap retirementMap prodMap metaMap = +combineChainData registrationMap retirementMap prodMap metaMap delistedSet = Map.map mkPoolDbData $ Map.merge registeredNoProductions @@ -487,12 +534,13 @@ combineChainData registrationMap retirementMap prodMap metaMap = :: (PoolRegistrationCertificate, Quantity "block" Word64) -> PoolDbData mkPoolDbData (registrationCert, n) = - PoolDbData registrationCert mRetirementCert n meta + PoolDbData registrationCert mRetirementCert n meta delisted where metaHash = snd <$> poolMetadata registrationCert meta = flip Map.lookup metaMap =<< metaHash mRetirementCert = Map.lookup (view #poolId registrationCert) retirementMap + delisted = view #poolId registrationCert `Set.member` delistedSet readPoolDbData :: DBLayer IO -> EpochNo -> IO (Map PoolId PoolDbData) readPoolDbData DBLayer {..} currentEpoch = atomically $ do @@ -512,6 +560,7 @@ readPoolDbData DBLayer {..} currentEpoch = atomically $ do retirementCertificates <$> readTotalProduction <*> readPoolMetadata + <*> (Set.fromList <$> readDelistedPools) -- -- Monitoring stake pool @@ -682,24 +731,49 @@ monitorStakePools tr gp nl DBLayer{..} = -- | Worker thread that monitors pool metadata and syncs it to the database. monitorMetadata - :: Tracer IO StakePoolLog + :: TVar PoolMetadataGCStatus + -> Tracer IO StakePoolLog -> SlottingParameters -> DBLayer IO -> IO () -monitorMetadata tr sp DBLayer{..} = do +monitorMetadata gcStatus tr sp db@(DBLayer{..}) = do settings <- atomically readSettings manager <- newManager defaultManagerSettings + let fetcher fetchStrategies = fetchFromRemote trFetch fetchStrategies manager - forever $ do - (refs, successes) <- case poolMetadataSource settings of - FetchNone -> pure ([], []) - FetchDirect -> fetchThem $ fetcher [identityUrlBuilder] - FetchSMASH (unSmashServer -> uri) -> fetchThem $ fetcher [registryUrlBuilder uri] - - when (null refs || null successes) $ do - traceWith tr $ MsgFetchTakeBreak blockFrequency - threadDelay blockFrequency + loop getPoolMetadata = forever $ do + (refs, successes) <- getPoolMetadata + when (null refs || null successes) $ do + traceWith tr $ MsgFetchTakeBreak blockFrequency + threadDelay blockFrequency + + case poolMetadataSource settings of + FetchNone -> do + STM.atomically $ writeTVar gcStatus NotApplicable + loop (pure ([], [])) -- TODO: exit loop? + FetchDirect -> do + STM.atomically $ writeTVar gcStatus NotApplicable + loop (fetchThem $ fetcher [identityUrlBuilder]) + FetchSMASH (unSmashServer -> uri) -> do + STM.atomically $ writeTVar gcStatus NotStarted + let getDelistedPools = + fetchDelistedPools trFetch (toDelistedPoolsURI uri) manager + tid <- forkFinally + (gcDelistedPools gcStatus tr db getDelistedPools) + onExit + flip finally (killThread tid) $ + loop (fetchThem $ fetcher [registryUrlBuilder uri]) + where + -- Currently the SMASH url points to the full API path, e.g. + -- https://smash.cardano-testnet.iohkdev.io/api/v1/monitorMetadata + -- so we need to recover/infer the delisted pools url. + -- TODO: + -- - require the smash URL to only specify scheme and host + -- - use smash servant types to call the endpoints + toDelistedPoolsURI uri = + uri { uriPath = "/api/v1/delisted" , uriQuery = "", uriFragment = "" } + trFetch = contramap MsgFetchPoolMetadata tr -- We mask this entire section just in case, although the database -- operations runs masked anyway. Unfortunately we cannot run @@ -724,6 +798,48 @@ monitorMetadata tr sp DBLayer{..} = do slotLength = unSlotLength $ getSlotLength sp f = unActiveSlotCoefficient (getActiveSlotCoefficient sp) + onExit + :: Either SomeException a + -> IO () + onExit = traceWith tr . \case + Right _ -> MsgGCFinished + Left e -> case asyncExceptionFromException e of + Just ThreadKilled -> MsgGCThreadKilled + Just UserInterrupt -> MsgGCUserInterrupt + _ -> MsgGCUnhandledException $ pretty $ show e + +gcDelistedPools + :: TVar PoolMetadataGCStatus + -> Tracer IO StakePoolLog + -> DBLayer IO + -> IO (Maybe [PoolId]) -- ^ delisted pools fetcher + -> IO () +gcDelistedPools gcStatus tr DBLayer{..} fetchDelisted = forever $ do + lastGC <- atomically readLastMetadataGC + currentTime <- getPOSIXTime + + case lastGC of + Nothing -> pure () + Just gc -> STM.atomically $ writeTVar gcStatus (HasRun gc) + + let timeSinceLastGC = fmap (currentTime -) lastGC + sixHours = posixDayLength / 4 + when (maybe True (> sixHours) timeSinceLastGC) $ do + delistedPools <- fmap (fromMaybe []) fetchDelisted + STM.atomically $ writeTVar gcStatus (HasRun currentTime) + atomically $ do + putLastMetadataGC currentTime + putDelistedPools delistedPools + + -- Sleep for 60 seconds. This is useful in case + -- something else is modifying the last sync time + -- in the database. + let ms = (* 1_000_000) + let sleepTime = ms 60 + traceWith tr $ MsgGCTakeBreak sleepTime + threadDelay sleepTime + pure () + data StakePoolLog = MsgFollow FollowLog | MsgStartMonitoring [BlockHeader] @@ -736,6 +852,11 @@ data StakePoolLog | MsgErrProduction ErrPointAlreadyExists | MsgFetchPoolMetadata StakePoolMetadataFetchLog | MsgFetchTakeBreak Int + | MsgGCTakeBreak Int + | MsgGCFinished + | MsgGCThreadKilled + | MsgGCUserInterrupt + | MsgGCUnhandledException Text deriving (Show, Eq) data PoolGarbageCollectionInfo = PoolGarbageCollectionInfo @@ -763,6 +884,11 @@ instance HasSeverityAnnotation StakePoolLog where MsgErrProduction{} -> Error MsgFetchPoolMetadata e -> getSeverityAnnotation e MsgFetchTakeBreak{} -> Debug + MsgGCTakeBreak{} -> Debug + MsgGCFinished{} -> Debug + MsgGCThreadKilled{} -> Debug + MsgGCUserInterrupt{} -> Debug + MsgGCUnhandledException{} -> Debug instance ToText StakePoolLog where toText = \case @@ -805,3 +931,13 @@ instance ToText StakePoolLog where , "back to it in about " , pretty (fixedF 1 (toRational delay / 1000000)), "s" ] + MsgGCTakeBreak delay -> mconcat + [ "Taking a little break from GCing delisted metadata pools, " + , "back to it in about " + , pretty (fixedF 1 (toRational delay / 1_000_000)), "s" + ] + MsgGCFinished -> "GC thread has exited: main action is over." + MsgGCThreadKilled -> "GC thread has exited: killed by parent." + MsgGCUserInterrupt -> "GC thread has exited: killed by user." + MsgGCUnhandledException err -> + "GC thread has exited unexpectedly: " <> err diff --git a/nix/.stack.nix/cardano-wallet-core.nix b/nix/.stack.nix/cardano-wallet-core.nix index ed9cf203cac..b8d3aac8ee7 100644 --- a/nix/.stack.nix/cardano-wallet-core.nix +++ b/nix/.stack.nix/cardano-wallet-core.nix @@ -90,7 +90,7 @@ (hsPkgs."statistics" or (errorHandler.buildDepError "statistics")) (hsPkgs."stm" or (errorHandler.buildDepError "stm")) (hsPkgs."streaming-commons" or (errorHandler.buildDepError "streaming-commons")) - (hsPkgs."string-qq" or (errorHandler.buildDepError "string-qq")) + (hsPkgs."string-interpolate" or (errorHandler.buildDepError "string-interpolate")) (hsPkgs."template-haskell" or (errorHandler.buildDepError "template-haskell")) (hsPkgs."text" or (errorHandler.buildDepError "text")) (hsPkgs."text-class" or (errorHandler.buildDepError "text-class")) diff --git a/nix/.stack.nix/cardano-wallet.nix b/nix/.stack.nix/cardano-wallet.nix index 03a3b8cbf7e..fc987f4e09e 100644 --- a/nix/.stack.nix/cardano-wallet.nix +++ b/nix/.stack.nix/cardano-wallet.nix @@ -60,6 +60,7 @@ (hsPkgs."memory" or (errorHandler.buildDepError "memory")) (hsPkgs."network" or (errorHandler.buildDepError "network")) (hsPkgs."network-mux" or (errorHandler.buildDepError "network-mux")) + (hsPkgs."network-uri" or (errorHandler.buildDepError "network-uri")) (hsPkgs."optparse-applicative" or (errorHandler.buildDepError "optparse-applicative")) (hsPkgs."ouroboros-consensus" or (errorHandler.buildDepError "ouroboros-consensus")) (hsPkgs."ouroboros-consensus-byron" or (errorHandler.buildDepError "ouroboros-consensus-byron")) diff --git a/specifications/api/swagger.yaml b/specifications/api/swagger.yaml index 5fcecfef2b7..953c099bea2 100644 --- a/specifications/api/swagger.yaml +++ b/specifications/api/swagger.yaml @@ -1018,6 +1018,21 @@ x-stakePoolMetrics: &stakePoolMetrics <<: *numberOfBlocks description: Number of blocks produced by a given stake pool in its lifetime. +x-stakePoolFlag: &stakePoolFlag + type: string + enum: + - delisted + +x-stakePoolFlags: &stakePoolFlags + type: array + description: | + Various flags applicable to stake pools. Possible flags: + + | flag | description | + | --- | --- | + | delisted | The pool is marked as delisted on a configured SMASH server; metadata for this pool have therefore been dropped. | + items: *stakePoolFlag + x-jormungandrStakePoolMetrics: &jormungandrStakePoolMetrics type: object required: @@ -1105,6 +1120,8 @@ x-addressIndex: &addressIndex description: | An address derivation index. +x-gCStatus :: &gCStatus + ############################################################################# # # # DEFINITIONS # @@ -1264,6 +1281,51 @@ components: type: array items: *certificate + ApiGCStatus: &ApiGCStatus + type: object + description: | + Gives an indication if metadata GC checking for delisted pools + has run and if so, when. + + Possible values are: + - not_applicable -> we're currently not querying a SMASH server for metadata + - not_started -> the GC hasn't started yet, try again in a short while + - restarting -> the GC thread is currently restarting, try again in short while + - has_run -> the GC has run successfully + + When 'status' is 'restarting' or 'has_run' then the field 'last_run' + is set to the last GC time in UTC. + required: + - status + properties: + status: + type: string + enum: + - not_applicable + - not_started + - restarting + - has_run + last_run: *date + + ApiMaintenanceActionPostData: &ApiMaintenanceActionPostData + type: object + required: + - maintenance_action + description: | + The maintenance action to carry out, current values are + - gc_stake_pools -> trigger looking up delisted pools from the remote SMASH server + properties: + maintenance_action: + type: string + enum: ['gc_stake_pools'] + + ApiMaintenanceAction: &ApiMaintenanceAction + type: object + required: + - gc_stake_pools + properties: + gc_stake_pools: *ApiGCStatus + ApiStakePool: &ApiStakePool type: object required: @@ -1272,6 +1334,7 @@ components: - cost - margin - pledge + - flags properties: id: *stakePoolId metrics: *stakePoolMetrics @@ -1280,6 +1343,7 @@ components: pledge: *stakePoolPledge metadata: *stakePoolMetadata retirement: *stakePoolRetirement + flags: *stakePoolFlags ApiJormungandrStakePool: &ApiJormungandrStakePool type: object @@ -3000,10 +3064,21 @@ x-responsesListStakePools: &responsesListStakePools oneOf: - type: array items: *ApiStakePool - title: "cardano-node stake pools" - type: array items: *ApiJormungandrStakePool - title: "jormungandr stake pools" + +x-responsesPostMaintenanceAction: &responsesPostMaintenanceAction + <<: *responsesErr404 + 204: + description: No Content + +x-responsesGetMaintenanceAction: &responsesGetMaintenanceAction + 200: + description: Ok + content: + application/json: + schema: + <<: *ApiMaintenanceAction x-responsesJoinStakePool: &responsesJoinStakePool <<: *responsesErr400 @@ -3449,6 +3524,31 @@ paths: - *parametersIntendedStakeAmount responses: *responsesListStakePools + /stake-pools/maintenance-actions: + get: + operationId: getMaintenanceActions + tags: ["Stake Pools"] + summary: View maintenance actions + description: | + Returns the current status of the stake pools maintenance actions. + responses: *responsesGetMaintenanceAction + + post: + operationId: postMaintenanceAction + tags: ["Stake Pools"] + summary: Trigger Maintenance actions + description: | + Performs maintenance actions on stake pools, such + as triggering metadata garbage collection. + + Actions may not be instantaneous. + requestBody: + required: true + content: + application/json: + schema: *ApiMaintenanceActionPostData + responses: *responsesPostMaintenanceAction + /wallets/{walletId}/delegation-fees: get: operationId: getDelegationFee