{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE UndecidableInstances #-}

{-# OPTIONS_GHC -Wno-orphans #-}
{-# OPTIONS_GHC -Wno-unticked-promoted-constructors #-}

module Cardano.Api.Orphans () where

import           Prelude

import           Data.Aeson (FromJSON (..), ToJSON (..), object, (.=))
import qualified Data.Aeson as Aeson
import           Data.Aeson.Types (ToJSONKey (..), toJSONKeyText)
import           Data.BiMap (BiMap (..), Bimap)
import qualified Data.ByteString.Base16 as B16
import qualified Data.ByteString.Short as Short
import qualified Data.Map.Strict as Map
import           Data.Text (Text)
import qualified Data.Text as Text
import qualified Data.Text.Encoding as Text
import           Data.UMap (Trip (Triple), UMap (UnifiedMap))
import           Data.VMap (VB, VMap, VP)
import qualified Data.VMap as VMap

import qualified Cardano.Ledger.Babbage as Babbage
import           Cardano.Ledger.BaseTypes (StrictMaybe (..))
import qualified Cardano.Ledger.BaseTypes as Ledger
import           Cardano.Ledger.Compactible (Compactible (fromCompact))
import qualified Cardano.Ledger.Era as Ledger
import qualified Cardano.Ledger.Shelley.PoolRank as Shelley
import           Cardano.Ledger.UnifiedMap (UnifiedMap)
import           Cardano.Slotting.Slot (SlotNo (..))
import           Cardano.Slotting.Time (SystemStart (..))
import           Control.State.Transition (STS (State))

import qualified Cardano.Binary as CBOR
import qualified Cardano.Crypto.Hash.Class as Crypto
import qualified Cardano.Ledger.Alonzo.Data as Alonzo
import qualified Cardano.Ledger.Alonzo.Scripts as Alonzo
import qualified Cardano.Ledger.Babbage.PParams as Babbage
import qualified Cardano.Ledger.Babbage.TxBody as Babbage
import qualified Cardano.Ledger.Coin as Shelley
import qualified Cardano.Ledger.Core as Core
import qualified Cardano.Ledger.Crypto as Crypto
import qualified Cardano.Ledger.Mary.Value as Mary
import qualified Cardano.Ledger.PoolDistr as Ledger
import qualified Cardano.Ledger.SafeHash as SafeHash
import qualified Cardano.Ledger.Shelley.API as Shelley
import qualified Cardano.Ledger.Shelley.Constraints as Shelley
import qualified Cardano.Ledger.Shelley.EpochBoundary as ShelleyEpoch
import qualified Cardano.Ledger.Shelley.LedgerState as ShelleyLedger
import           Cardano.Ledger.Shelley.PParams (PParamsUpdate)
import qualified Cardano.Ledger.Shelley.Rewards as Shelley
import qualified Cardano.Ledger.Shelley.RewardUpdate as Shelley
import qualified Ouroboros.Consensus.Shelley.Eras as Consensus

import           Cardano.Api.Script

-- Orphan instances involved in the JSON output of the API queries.
-- We will remove/replace these as we provide more API wrapper types

instance ToJSON (Mary.Value era) where
  toJSON :: Value era -> Value
toJSON = [Pair] -> Value
object ([Pair] -> Value) -> (Value era -> [Pair]) -> Value era -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value era -> [Pair]
forall a crypto. KeyValue a => Value crypto -> [a]
toMaryValuePairs
  toEncoding :: Value era -> Encoding
toEncoding = Series -> Encoding
Aeson.pairs (Series -> Encoding)
-> (Value era -> Series) -> Value era -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Series] -> Series
forall a. Monoid a => [a] -> a
mconcat ([Series] -> Series)
-> (Value era -> [Series]) -> Value era -> Series
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value era -> [Series]
forall a crypto. KeyValue a => Value crypto -> [a]
toMaryValuePairs

toMaryValuePairs :: Aeson.KeyValue a => Mary.Value crypto -> [a]
toMaryValuePairs :: Value crypto -> [a]
toMaryValuePairs (Mary.Value !Integer
l !Map (PolicyID crypto) (Map AssetName Integer)
ps) =
  [ Key
"lovelace" Key -> Integer -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Integer
l
  , Key
"policies" Key -> Map (PolicyID crypto) (Map AssetName Integer) -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Map (PolicyID crypto) (Map AssetName Integer)
ps
  ]

instance ToJSONKey Mary.AssetName where
  toJSONKey :: ToJSONKeyFunction AssetName
toJSONKey = (AssetName -> Text) -> ToJSONKeyFunction AssetName
forall a. (a -> Text) -> ToJSONKeyFunction a
toJSONKeyText AssetName -> Text
render
    where
      render :: AssetName -> Text
render = ByteString -> Text
Text.decodeLatin1 (ByteString -> Text)
-> (AssetName -> ByteString) -> AssetName -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
B16.encode (ByteString -> ByteString)
-> (AssetName -> ByteString) -> AssetName -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> ByteString
Short.fromShort (ShortByteString -> ByteString)
-> (AssetName -> ShortByteString) -> AssetName -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AssetName -> ShortByteString
Mary.assetName

instance ToJSON (Mary.PolicyID era) where
  toJSON :: PolicyID era -> Value
toJSON (Mary.PolicyID (Shelley.ScriptHash Hash (ADDRHASH era) EraIndependentScript
h)) = Text -> Value
Aeson.String (Hash (ADDRHASH era) EraIndependentScript -> Text
forall crypto a. Hash crypto a -> Text
hashToText Hash (ADDRHASH era) EraIndependentScript
h)

instance ToJSONKey (Mary.PolicyID era) where
  toJSONKey :: ToJSONKeyFunction (PolicyID era)
toJSONKey = (PolicyID era -> Text) -> ToJSONKeyFunction (PolicyID era)
forall a. (a -> Text) -> ToJSONKeyFunction a
toJSONKeyText PolicyID era -> Text
forall crypto. PolicyID crypto -> Text
render
    where
      render :: PolicyID crypto -> Text
render (Mary.PolicyID (Shelley.ScriptHash Hash (ADDRHASH crypto) EraIndependentScript
h)) = Hash (ADDRHASH crypto) EraIndependentScript -> Text
forall crypto a. Hash crypto a -> Text
hashToText Hash (ADDRHASH crypto) EraIndependentScript
h

instance ToJSON Mary.AssetName where
  toJSON :: AssetName -> Value
toJSON = Text -> Value
Aeson.String (Text -> Value) -> (AssetName -> Text) -> AssetName -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
Text.decodeLatin1 (ByteString -> Text)
-> (AssetName -> ByteString) -> AssetName -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
B16.encode (ByteString -> ByteString)
-> (AssetName -> ByteString) -> AssetName -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> ByteString
Short.fromShort (ShortByteString -> ByteString)
-> (AssetName -> ShortByteString) -> AssetName -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AssetName -> ShortByteString
Mary.assetName

instance ToJSON Shelley.AccountState where
  toJSON :: AccountState -> Value
toJSON = [Pair] -> Value
object ([Pair] -> Value)
-> (AccountState -> [Pair]) -> AccountState -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AccountState -> [Pair]
forall a. KeyValue a => AccountState -> [a]
toAccountStatePairs
  toEncoding :: AccountState -> Encoding
toEncoding = Series -> Encoding
Aeson.pairs (Series -> Encoding)
-> (AccountState -> Series) -> AccountState -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Series] -> Series
forall a. Monoid a => [a] -> a
mconcat ([Series] -> Series)
-> (AccountState -> [Series]) -> AccountState -> Series
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AccountState -> [Series]
forall a. KeyValue a => AccountState -> [a]
toAccountStatePairs

toAccountStatePairs :: Aeson.KeyValue a => ShelleyLedger.AccountState -> [a]
toAccountStatePairs :: AccountState -> [a]
toAccountStatePairs (Shelley.AccountState !Coin
tr !Coin
rs) =
  [ Key
"treasury" Key -> Coin -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Coin
tr
  , Key
"reserves" Key -> Coin -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Coin
rs
  ]

instance forall era.
         ( Consensus.ShelleyBasedEra era
         , ToJSON (Core.TxOut era)
         , ToJSON (Core.PParams era)
         , ToJSON (Core.PParamsDelta era)
         ) => ToJSON (Shelley.EpochState era) where
  toJSON :: EpochState era -> Value
toJSON = [Pair] -> Value
object ([Pair] -> Value)
-> (EpochState era -> [Pair]) -> EpochState era -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EpochState era -> [Pair]
forall era a.
(ShelleyBasedEra era, ToJSON (TxOut era),
 ToJSON (PParamsDelta era), ToJSON (PParams era), KeyValue a) =>
EpochState era -> [a]
toEpochStatePairs
  toEncoding :: EpochState era -> Encoding
toEncoding = Series -> Encoding
Aeson.pairs (Series -> Encoding)
-> (EpochState era -> Series) -> EpochState era -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Series] -> Series
forall a. Monoid a => [a] -> a
mconcat ([Series] -> Series)
-> (EpochState era -> [Series]) -> EpochState era -> Series
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EpochState era -> [Series]
forall era a.
(ShelleyBasedEra era, ToJSON (TxOut era),
 ToJSON (PParamsDelta era), ToJSON (PParams era), KeyValue a) =>
EpochState era -> [a]
toEpochStatePairs

toEpochStatePairs ::
  ( Consensus.ShelleyBasedEra era
  , ToJSON (Core.TxOut era)
  , ToJSON (Core.PParamsDelta era)
  , ToJSON (Core.PParams era)
  , Aeson.KeyValue a
  )
  => ShelleyLedger.EpochState era
  -> [a]
toEpochStatePairs :: EpochState era -> [a]
toEpochStatePairs EpochState era
eState =
  let !esAccountState :: AccountState
esAccountState = EpochState era -> AccountState
forall era. EpochState era -> AccountState
Shelley.esAccountState EpochState era
eState
      !esSnapshots :: SnapShots (Crypto era)
esSnapshots = EpochState era -> SnapShots (Crypto era)
forall era. EpochState era -> SnapShots (Crypto era)
Shelley.esSnapshots EpochState era
eState
      !esLState :: LedgerState era
esLState = EpochState era -> LedgerState era
forall era. EpochState era -> LedgerState era
Shelley.esLState EpochState era
eState
      !esPrevPp :: PParams era
esPrevPp = EpochState era -> PParams era
forall era. EpochState era -> PParams era
Shelley.esPrevPp EpochState era
eState
      !esPp :: PParams era
esPp = EpochState era -> PParams era
forall era. EpochState era -> PParams era
Shelley.esPp EpochState era
eState
      !esNonMyopic :: NonMyopic (Crypto era)
esNonMyopic = EpochState era -> NonMyopic (Crypto era)
forall era. EpochState era -> NonMyopic (Crypto era)
Shelley.esNonMyopic EpochState era
eState
  in  [ Key
"esAccountState" Key -> AccountState -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= AccountState
esAccountState
      , Key
"esSnapshots" Key -> SnapShots (Crypto era) -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= SnapShots (Crypto era)
esSnapshots
      , Key
"esLState" Key -> LedgerState era -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= LedgerState era
esLState
      , Key
"esPrevPp" Key -> PParams era -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= PParams era
esPrevPp
      , Key
"esPp" Key -> PParams era -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= PParams era
esPp
      , Key
"esNonMyopic" Key -> NonMyopic (Crypto era) -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= NonMyopic (Crypto era)
esNonMyopic
      ]


instance ( Consensus.ShelleyBasedEra era
         , ToJSON (Core.TxOut era)
         , ToJSON (Core.PParamsDelta era)
         ) => ToJSON (Shelley.LedgerState era) where
  toJSON :: LedgerState era -> Value
toJSON = [Pair] -> Value
object ([Pair] -> Value)
-> (LedgerState era -> [Pair]) -> LedgerState era -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LedgerState era -> [Pair]
forall era a.
(ShelleyBasedEra era, ToJSON (TxOut era),
 ToJSON (PParamsDelta era), KeyValue a) =>
LedgerState era -> [a]
toLedgerStatePairs
  toEncoding :: LedgerState era -> Encoding
toEncoding = Series -> Encoding
Aeson.pairs (Series -> Encoding)
-> (LedgerState era -> Series) -> LedgerState era -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Series] -> Series
forall a. Monoid a => [a] -> a
mconcat ([Series] -> Series)
-> (LedgerState era -> [Series]) -> LedgerState era -> Series
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LedgerState era -> [Series]
forall era a.
(ShelleyBasedEra era, ToJSON (TxOut era),
 ToJSON (PParamsDelta era), KeyValue a) =>
LedgerState era -> [a]
toLedgerStatePairs

toLedgerStatePairs ::
  ( Consensus.ShelleyBasedEra era
  , ToJSON (Core.TxOut era)
  , ToJSON (Core.PParamsDelta era)
  , Aeson.KeyValue a
  ) => ShelleyLedger.LedgerState era -> [a]
toLedgerStatePairs :: LedgerState era -> [a]
toLedgerStatePairs LedgerState era
lState =
  let !lsUTxOState :: UTxOState era
lsUTxOState = LedgerState era -> UTxOState era
forall era. LedgerState era -> UTxOState era
Shelley.lsUTxOState LedgerState era
lState
      !lsDPState :: DPState (Crypto era)
lsDPState = LedgerState era -> DPState (Crypto era)
forall era. LedgerState era -> DPState (Crypto era)
Shelley.lsDPState LedgerState era
lState
  in  [ Key
"utxoState" Key -> UTxOState era -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= UTxOState era
lsUTxOState
      , Key
"delegationState" Key -> DPState (Crypto era) -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= DPState (Crypto era)
lsDPState
      ]

instance Crypto.Crypto crypto => ToJSON (ShelleyLedger.IncrementalStake crypto) where
  toJSON :: IncrementalStake crypto -> Value
toJSON = [Pair] -> Value
object ([Pair] -> Value)
-> (IncrementalStake crypto -> [Pair])
-> IncrementalStake crypto
-> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IncrementalStake crypto -> [Pair]
forall a crypto.
(KeyValue a, Crypto crypto) =>
IncrementalStake crypto -> [a]
toIncrementalStakePairs
  toEncoding :: IncrementalStake crypto -> Encoding
toEncoding = Series -> Encoding
Aeson.pairs (Series -> Encoding)
-> (IncrementalStake crypto -> Series)
-> IncrementalStake crypto
-> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Series] -> Series
forall a. Monoid a => [a] -> a
mconcat ([Series] -> Series)
-> (IncrementalStake crypto -> [Series])
-> IncrementalStake crypto
-> Series
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IncrementalStake crypto -> [Series]
forall a crypto.
(KeyValue a, Crypto crypto) =>
IncrementalStake crypto -> [a]
toIncrementalStakePairs

toIncrementalStakePairs ::
  ( Aeson.KeyValue a
  , Crypto.Crypto crypto
  ) => ShelleyLedger.IncrementalStake crypto -> [a]
toIncrementalStakePairs :: IncrementalStake crypto -> [a]
toIncrementalStakePairs IncrementalStake crypto
iStake =
  let !credentials :: [(Credential 'Staking crypto, Coin)]
credentials = Map (Credential 'Staking crypto) Coin
-> [(Credential 'Staking crypto, Coin)]
forall k a. Map k a -> [(k, a)]
Map.toList (IncrementalStake crypto -> Map (Credential 'Staking crypto) Coin
forall crypto.
IncrementalStake crypto -> Map (Credential 'Staking crypto) Coin
ShelleyLedger.credMap IncrementalStake crypto
iStake)
      !pointers :: [(Ptr, Coin)]
pointers = Map Ptr Coin -> [(Ptr, Coin)]
forall k a. Map k a -> [(k, a)]
Map.toList (IncrementalStake crypto -> Map Ptr Coin
forall crypto. IncrementalStake crypto -> Map Ptr Coin
ShelleyLedger.ptrMap IncrementalStake crypto
iStake)
  in  [ Key
"credentials" Key -> [(Credential 'Staking crypto, Coin)] -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [(Credential 'Staking crypto, Coin)]
credentials
      , Key
"pointers" Key -> [(Ptr, Coin)] -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [(Ptr, Coin)]
pointers
      ]

instance ( Consensus.ShelleyBasedEra era
         , ToJSON (Core.TxOut era)
         , ToJSON (Core.PParamsDelta era)
         ) => ToJSON (Shelley.UTxOState era) where
  toJSON :: UTxOState era -> Value
toJSON = [Pair] -> Value
object ([Pair] -> Value)
-> (UTxOState era -> [Pair]) -> UTxOState era -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTxOState era -> [Pair]
forall a era.
(KeyValue a, ShelleyBasedEra era, ToJSON (TxOut era),
 ToJSON (State (EraRule "PPUP" era))) =>
UTxOState era -> [a]
toUtxoStatePairs
  toEncoding :: UTxOState era -> Encoding
toEncoding = Series -> Encoding
Aeson.pairs (Series -> Encoding)
-> (UTxOState era -> Series) -> UTxOState era -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Series] -> Series
forall a. Monoid a => [a] -> a
mconcat ([Series] -> Series)
-> (UTxOState era -> [Series]) -> UTxOState era -> Series
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UTxOState era -> [Series]
forall a era.
(KeyValue a, ShelleyBasedEra era, ToJSON (TxOut era),
 ToJSON (State (EraRule "PPUP" era))) =>
UTxOState era -> [a]
toUtxoStatePairs

toUtxoStatePairs ::
  ( Aeson.KeyValue a
  , Consensus.ShelleyBasedEra era
  , ToJSON (Core.TxOut era)
  , ToJSON (State (Core.EraRule "PPUP" era))
  ) => ShelleyLedger.UTxOState era -> [a]
toUtxoStatePairs :: UTxOState era -> [a]
toUtxoStatePairs UTxOState era
utxoState =
  let !utxo :: UTxO era
utxo = UTxOState era -> UTxO era
forall era. UTxOState era -> UTxO era
Shelley._utxo UTxOState era
utxoState
      !deposited :: Coin
deposited = UTxOState era -> Coin
forall era. UTxOState era -> Coin
Shelley._deposited UTxOState era
utxoState
      !fees :: Coin
fees = UTxOState era -> Coin
forall era. UTxOState era -> Coin
Shelley._fees UTxOState era
utxoState
      !ppups :: State (EraRule "PPUP" era)
ppups = UTxOState era -> State (EraRule "PPUP" era)
forall era. UTxOState era -> State (EraRule "PPUP" era)
Shelley._ppups UTxOState era
utxoState
      !stakeDistro :: IncrementalStake (Crypto era)
stakeDistro = UTxOState era -> IncrementalStake (Crypto era)
forall era. UTxOState era -> IncrementalStake (Crypto era)
Shelley._stakeDistro UTxOState era
utxoState
  in  [ Key
"utxo" Key -> UTxO era -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= UTxO era
utxo
      , Key
"deposited" Key -> Coin -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Coin
deposited
      , Key
"fees" Key -> Coin -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Coin
fees
      , Key
"ppups" Key -> PPUPState era -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= PPUPState era
State (EraRule "PPUP" era)
ppups
      , Key
"stake" Key -> IncrementalStake (Crypto era) -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= IncrementalStake (Crypto era)
stakeDistro
      ]

instance ( ToJSON (Core.PParamsDelta era)
         , Shelley.UsesPParams era
         ) => ToJSON (Shelley.PPUPState era) where
  toJSON :: PPUPState era -> Value
toJSON = [Pair] -> Value
object ([Pair] -> Value)
-> (PPUPState era -> [Pair]) -> PPUPState era -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PPUPState era -> [Pair]
forall a era.
(KeyValue a, ToJSON (PParamsDelta era), UsesPParams era) =>
PPUPState era -> [a]
toPpupStatePairs
  toEncoding :: PPUPState era -> Encoding
toEncoding = Series -> Encoding
Aeson.pairs (Series -> Encoding)
-> (PPUPState era -> Series) -> PPUPState era -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Series] -> Series
forall a. Monoid a => [a] -> a
mconcat ([Series] -> Series)
-> (PPUPState era -> [Series]) -> PPUPState era -> Series
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PPUPState era -> [Series]
forall a era.
(KeyValue a, ToJSON (PParamsDelta era), UsesPParams era) =>
PPUPState era -> [a]
toPpupStatePairs

toPpupStatePairs ::
  ( Aeson.KeyValue a
  , ToJSON (Core.PParamsDelta era)
  , Shelley.UsesPParams era
  ) => ShelleyLedger.PPUPState era -> [a]
toPpupStatePairs :: PPUPState era -> [a]
toPpupStatePairs PPUPState era
ppUpState =
  let !proposals :: ProposedPPUpdates era
proposals = PPUPState era -> ProposedPPUpdates era
forall era. PPUPState era -> ProposedPPUpdates era
Shelley.proposals PPUPState era
ppUpState
      !futureProposals :: ProposedPPUpdates era
futureProposals = PPUPState era -> ProposedPPUpdates era
forall era. PPUPState era -> ProposedPPUpdates era
Shelley.futureProposals PPUPState era
ppUpState
  in  [ Key
"proposals" Key -> ProposedPPUpdates era -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ProposedPPUpdates era
proposals
      , Key
"futureProposals" Key -> ProposedPPUpdates era -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ProposedPPUpdates era
futureProposals
      ]

instance ( ToJSON (Core.PParamsDelta era)
         , Shelley.UsesPParams era
         ) => ToJSON (Shelley.ProposedPPUpdates era) where
  toJSON :: ProposedPPUpdates era -> Value
toJSON (Shelley.ProposedPPUpdates Map (KeyHash 'Genesis (Crypto era)) (PParamsDelta era)
ppUpdates) = [(KeyHash 'Genesis (Crypto era), PParamsDelta era)] -> Value
forall a. ToJSON a => a -> Value
toJSON ([(KeyHash 'Genesis (Crypto era), PParamsDelta era)] -> Value)
-> [(KeyHash 'Genesis (Crypto era), PParamsDelta era)] -> Value
forall a b. (a -> b) -> a -> b
$ Map (KeyHash 'Genesis (Crypto era)) (PParamsDelta era)
-> [(KeyHash 'Genesis (Crypto era), PParamsDelta era)]
forall k a. Map k a -> [(k, a)]
Map.toList Map (KeyHash 'Genesis (Crypto era)) (PParamsDelta era)
ppUpdates
  toEncoding :: ProposedPPUpdates era -> Encoding
toEncoding (Shelley.ProposedPPUpdates Map (KeyHash 'Genesis (Crypto era)) (PParamsDelta era)
ppUpdates) = [(KeyHash 'Genesis (Crypto era), PParamsDelta era)] -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding ([(KeyHash 'Genesis (Crypto era), PParamsDelta era)] -> Encoding)
-> [(KeyHash 'Genesis (Crypto era), PParamsDelta era)] -> Encoding
forall a b. (a -> b) -> a -> b
$ Map (KeyHash 'Genesis (Crypto era)) (PParamsDelta era)
-> [(KeyHash 'Genesis (Crypto era), PParamsDelta era)]
forall k a. Map k a -> [(k, a)]
Map.toList Map (KeyHash 'Genesis (Crypto era)) (PParamsDelta era)
ppUpdates

instance ToJSON (PParamsUpdate era) where
  toJSON :: PParamsUpdate era -> Value
toJSON PParamsUpdate era
pp =
    [Pair] -> Value
Aeson.object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$
        [ Key
"minFeeA"               Key -> Natural -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Natural
x | Natural
x <- StrictMaybe Natural -> [Natural]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe Natural
forall (f :: * -> *) era. PParams' f era -> HKD f Natural
Shelley._minfeeA PParamsUpdate era
pp) ]
     [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [ Key
"minFeeB"               Key -> Natural -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Natural
x | Natural
x <- StrictMaybe Natural -> [Natural]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe Natural
forall (f :: * -> *) era. PParams' f era -> HKD f Natural
Shelley._minfeeB PParamsUpdate era
pp) ]
     [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [ Key
"maxBlockBodySize"      Key -> Natural -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Natural
x | Natural
x <- StrictMaybe Natural -> [Natural]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe Natural
forall (f :: * -> *) era. PParams' f era -> HKD f Natural
Shelley._maxBBSize PParamsUpdate era
pp) ]
     [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [ Key
"maxTxSize"             Key -> Natural -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Natural
x | Natural
x <- StrictMaybe Natural -> [Natural]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe Natural
forall (f :: * -> *) era. PParams' f era -> HKD f Natural
Shelley._maxTxSize PParamsUpdate era
pp) ]
     [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [ Key
"maxBlockHeaderSize"    Key -> Natural -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Natural
x | Natural
x <- StrictMaybe Natural -> [Natural]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe Natural
forall (f :: * -> *) era. PParams' f era -> HKD f Natural
Shelley._maxBHSize PParamsUpdate era
pp) ]
     [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [ Key
"keyDeposit"            Key -> Coin -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Coin
x | Coin
x <- StrictMaybe Coin -> [Coin]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe Coin
forall (f :: * -> *) era. PParams' f era -> HKD f Coin
Shelley._keyDeposit PParamsUpdate era
pp) ]
     [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [ Key
"poolDeposit"           Key -> Coin -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Coin
x | Coin
x <- StrictMaybe Coin -> [Coin]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe Coin
forall (f :: * -> *) era. PParams' f era -> HKD f Coin
Shelley._poolDeposit PParamsUpdate era
pp) ]
     [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [ Key
"eMax"                  Key -> EpochNo -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= EpochNo
x | EpochNo
x <- StrictMaybe EpochNo -> [EpochNo]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe EpochNo
forall (f :: * -> *) era. PParams' f era -> HKD f EpochNo
Shelley._eMax PParamsUpdate era
pp) ]
     [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [ Key
"nOpt"                  Key -> Natural -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Natural
x | Natural
x <- StrictMaybe Natural -> [Natural]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe Natural
forall (f :: * -> *) era. PParams' f era -> HKD f Natural
Shelley._nOpt PParamsUpdate era
pp) ]
     [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [ Key
"a0"                    Key -> NonNegativeInterval -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= NonNegativeInterval
x | NonNegativeInterval
x <- StrictMaybe NonNegativeInterval -> [NonNegativeInterval]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe NonNegativeInterval
forall (f :: * -> *) era.
PParams' f era -> HKD f NonNegativeInterval
Shelley._a0 PParamsUpdate era
pp) ]
     [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [ Key
"rho"                   Key -> UnitInterval -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= UnitInterval
x | UnitInterval
x <- StrictMaybe UnitInterval -> [UnitInterval]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe UnitInterval
forall (f :: * -> *) era. PParams' f era -> HKD f UnitInterval
Shelley._rho PParamsUpdate era
pp) ]
     [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [ Key
"tau"                   Key -> UnitInterval -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= UnitInterval
x | UnitInterval
x <- StrictMaybe UnitInterval -> [UnitInterval]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe UnitInterval
forall (f :: * -> *) era. PParams' f era -> HKD f UnitInterval
Shelley._tau PParamsUpdate era
pp) ]
     [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [ Key
"decentralisationParam" Key -> UnitInterval -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= UnitInterval
x | UnitInterval
x <- StrictMaybe UnitInterval -> [UnitInterval]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe UnitInterval
forall (f :: * -> *) era. PParams' f era -> HKD f UnitInterval
Shelley._d PParamsUpdate era
pp) ]
     [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [ Key
"extraEntropy"          Key -> Nonce -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Nonce
x | Nonce
x <- StrictMaybe Nonce -> [Nonce]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe Nonce
forall (f :: * -> *) era. PParams' f era -> HKD f Nonce
Shelley._extraEntropy PParamsUpdate era
pp) ]
     [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [ Key
"protocolVersion"       Key -> ProtVer -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ProtVer
x | ProtVer
x <- StrictMaybe ProtVer -> [ProtVer]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe ProtVer
forall (f :: * -> *) era. PParams' f era -> HKD f ProtVer
Shelley._protocolVersion PParamsUpdate era
pp) ]
     [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [ Key
"minUTxOValue"          Key -> Coin -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Coin
x | Coin
x <- StrictMaybe Coin -> [Coin]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe Coin
forall (f :: * -> *) era. PParams' f era -> HKD f Coin
Shelley._minUTxOValue PParamsUpdate era
pp) ]
     [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [ Key
"minPoolCost"           Key -> Coin -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Coin
x | Coin
x <- StrictMaybe Coin -> [Coin]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe Coin
forall (f :: * -> *) era. PParams' f era -> HKD f Coin
Shelley._minPoolCost PParamsUpdate era
pp) ]

instance ToJSON (Babbage.PParamsUpdate era) where
  toJSON :: PParamsUpdate era -> Value
toJSON PParamsUpdate era
pp =
    [Pair] -> Value
Aeson.object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$
        [ Key
"minFeeA"               Key -> Natural -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Natural
x | Natural
x <- StrictMaybe Natural -> [Natural]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe Natural
forall (f :: * -> *) era. PParams' f era -> HKD f Natural
Babbage._minfeeA PParamsUpdate era
pp) ]
     [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [ Key
"minFeeB"               Key -> Natural -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Natural
x | Natural
x <- StrictMaybe Natural -> [Natural]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe Natural
forall (f :: * -> *) era. PParams' f era -> HKD f Natural
Babbage._minfeeB PParamsUpdate era
pp) ]
     [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [ Key
"maxBlockBodySize"      Key -> Natural -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Natural
x | Natural
x <- StrictMaybe Natural -> [Natural]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe Natural
forall (f :: * -> *) era. PParams' f era -> HKD f Natural
Babbage._maxBBSize PParamsUpdate era
pp) ]
     [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [ Key
"maxTxSize"             Key -> Natural -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Natural
x | Natural
x <- StrictMaybe Natural -> [Natural]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe Natural
forall (f :: * -> *) era. PParams' f era -> HKD f Natural
Babbage._maxTxSize PParamsUpdate era
pp) ]
     [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [ Key
"maxBlockHeaderSize"    Key -> Natural -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Natural
x | Natural
x <- StrictMaybe Natural -> [Natural]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe Natural
forall (f :: * -> *) era. PParams' f era -> HKD f Natural
Babbage._maxBHSize PParamsUpdate era
pp) ]
     [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [ Key
"keyDeposit"            Key -> Coin -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Coin
x | Coin
x <- StrictMaybe Coin -> [Coin]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe Coin
forall (f :: * -> *) era. PParams' f era -> HKD f Coin
Babbage._keyDeposit PParamsUpdate era
pp) ]
     [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [ Key
"poolDeposit"           Key -> Coin -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Coin
x | Coin
x <- StrictMaybe Coin -> [Coin]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe Coin
forall (f :: * -> *) era. PParams' f era -> HKD f Coin
Babbage._poolDeposit PParamsUpdate era
pp) ]
     [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [ Key
"eMax"                  Key -> EpochNo -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= EpochNo
x | EpochNo
x <- StrictMaybe EpochNo -> [EpochNo]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe EpochNo
forall (f :: * -> *) era. PParams' f era -> HKD f EpochNo
Babbage._eMax PParamsUpdate era
pp) ]
     [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [ Key
"nOpt"                  Key -> Natural -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Natural
x | Natural
x <- StrictMaybe Natural -> [Natural]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe Natural
forall (f :: * -> *) era. PParams' f era -> HKD f Natural
Babbage._nOpt PParamsUpdate era
pp) ]
     [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [ Key
"a0"                    Key -> NonNegativeInterval -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= NonNegativeInterval
x | NonNegativeInterval
x <- StrictMaybe NonNegativeInterval -> [NonNegativeInterval]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe NonNegativeInterval
forall (f :: * -> *) era.
PParams' f era -> HKD f NonNegativeInterval
Babbage._a0 PParamsUpdate era
pp) ]
     [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [ Key
"rho"                   Key -> UnitInterval -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= UnitInterval
x | UnitInterval
x <- StrictMaybe UnitInterval -> [UnitInterval]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe UnitInterval
forall (f :: * -> *) era. PParams' f era -> HKD f UnitInterval
Babbage._rho PParamsUpdate era
pp) ]
     [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [ Key
"tau"                   Key -> UnitInterval -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= UnitInterval
x | UnitInterval
x <- StrictMaybe UnitInterval -> [UnitInterval]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe UnitInterval
forall (f :: * -> *) era. PParams' f era -> HKD f UnitInterval
Babbage._tau PParamsUpdate era
pp) ]
     [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [ Key
"protocolVersion"       Key -> ProtVer -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ProtVer
x | ProtVer
x <- StrictMaybe ProtVer -> [ProtVer]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe ProtVer
forall (f :: * -> *) era. PParams' f era -> HKD f ProtVer
Babbage._protocolVersion PParamsUpdate era
pp) ]
     [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [ Key
"minPoolCost"           Key -> Coin -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Coin
x | Coin
x <- StrictMaybe Coin -> [Coin]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe Coin
forall (f :: * -> *) era. PParams' f era -> HKD f Coin
Babbage._minPoolCost PParamsUpdate era
pp) ]
     [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [ Key
"coinsPerUTxOByte"      Key -> Coin -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Coin
x | Coin
x <- StrictMaybe Coin -> [Coin]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe Coin
forall (f :: * -> *) era. PParams' f era -> HKD f Coin
Babbage._coinsPerUTxOByte PParamsUpdate era
pp) ]
     [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [ Key
"costmdls"              Key -> CostModels -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= CostModels
x | CostModels
x <- StrictMaybe CostModels -> [CostModels]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe CostModels
forall (f :: * -> *) era. PParams' f era -> HKD f CostModels
Babbage._costmdls PParamsUpdate era
pp) ]
     [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [ Key
"prices"                Key -> Prices -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Prices
x | Prices
x <- StrictMaybe Prices -> [Prices]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe Prices
forall (f :: * -> *) era. PParams' f era -> HKD f Prices
Babbage._prices PParamsUpdate era
pp) ]
     [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [ Key
"maxTxExUnits"          Key -> ExUnits -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ExUnits
x | ExUnits
x <- StrictMaybe ExUnits -> [ExUnits]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe ExUnits
forall (f :: * -> *) era. PParams' f era -> HKD f ExUnits
Babbage._maxTxExUnits PParamsUpdate era
pp) ]
     [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [ Key
"maxBlockExUnits"       Key -> ExUnits -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ExUnits
x | ExUnits
x <- StrictMaybe ExUnits -> [ExUnits]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe ExUnits
forall (f :: * -> *) era. PParams' f era -> HKD f ExUnits
Babbage._maxBlockExUnits PParamsUpdate era
pp) ]
     [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [ Key
"maxValSize"            Key -> Natural -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Natural
x | Natural
x <- StrictMaybe Natural -> [Natural]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe Natural
forall (f :: * -> *) era. PParams' f era -> HKD f Natural
Babbage._maxValSize PParamsUpdate era
pp) ]
     [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [ Key
"collateralPercentage"  Key -> Natural -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Natural
x | Natural
x <- StrictMaybe Natural -> [Natural]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe Natural
forall (f :: * -> *) era. PParams' f era -> HKD f Natural
Babbage._collateralPercentage PParamsUpdate era
pp) ]
     [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [ Key
"maxCollateralInputs"   Key -> Natural -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Natural
x | Natural
x <- StrictMaybe Natural -> [Natural]
forall a. StrictMaybe a -> [a]
mbfield (PParamsUpdate era -> HKD StrictMaybe Natural
forall (f :: * -> *) era. PParams' f era -> HKD f Natural
Babbage._maxCollateralInputs PParamsUpdate era
pp) ]

instance ToJSON (Babbage.PParams (Babbage.BabbageEra Consensus.StandardCrypto)) where
  toJSON :: PParams (BabbageEra StandardCrypto) -> Value
toJSON PParams (BabbageEra StandardCrypto)
pp =
    [Pair] -> Value
Aeson.object
      [ Key
"minFeeA" Key -> Natural -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= PParams (BabbageEra StandardCrypto) -> HKD Identity Natural
forall (f :: * -> *) era. PParams' f era -> HKD f Natural
Babbage._minfeeA PParams (BabbageEra StandardCrypto)
pp
      , Key
"minFeeB" Key -> Natural -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= PParams (BabbageEra StandardCrypto) -> HKD Identity Natural
forall (f :: * -> *) era. PParams' f era -> HKD f Natural
Babbage._minfeeB PParams (BabbageEra StandardCrypto)
pp
      , Key
"maxBlockBodySize" Key -> Natural -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= PParams (BabbageEra StandardCrypto) -> HKD Identity Natural
forall (f :: * -> *) era. PParams' f era -> HKD f Natural
Babbage._maxBBSize PParams (BabbageEra StandardCrypto)
pp
      , Key
"maxTxSize" Key -> Natural -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= PParams (BabbageEra StandardCrypto) -> HKD Identity Natural
forall (f :: * -> *) era. PParams' f era -> HKD f Natural
Babbage._maxTxSize PParams (BabbageEra StandardCrypto)
pp
      , Key
"maxBlockHeaderSize" Key -> Natural -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= PParams (BabbageEra StandardCrypto) -> HKD Identity Natural
forall (f :: * -> *) era. PParams' f era -> HKD f Natural
Babbage._maxBHSize PParams (BabbageEra StandardCrypto)
pp
      , Key
"keyDeposit" Key -> Coin -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= PParams (BabbageEra StandardCrypto) -> HKD Identity Coin
forall (f :: * -> *) era. PParams' f era -> HKD f Coin
Babbage._keyDeposit PParams (BabbageEra StandardCrypto)
pp
      , Key
"poolDeposit" Key -> Coin -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= PParams (BabbageEra StandardCrypto) -> HKD Identity Coin
forall (f :: * -> *) era. PParams' f era -> HKD f Coin
Babbage._poolDeposit PParams (BabbageEra StandardCrypto)
pp
      , Key
"eMax" Key -> EpochNo -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= PParams (BabbageEra StandardCrypto) -> HKD Identity EpochNo
forall (f :: * -> *) era. PParams' f era -> HKD f EpochNo
Babbage._eMax PParams (BabbageEra StandardCrypto)
pp
      , Key
"nOpt" Key -> Natural -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= PParams (BabbageEra StandardCrypto) -> HKD Identity Natural
forall (f :: * -> *) era. PParams' f era -> HKD f Natural
Babbage._nOpt PParams (BabbageEra StandardCrypto)
pp
      , Key
"a0" Key -> NonNegativeInterval -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= PParams (BabbageEra StandardCrypto)
-> HKD Identity NonNegativeInterval
forall (f :: * -> *) era.
PParams' f era -> HKD f NonNegativeInterval
Babbage._a0 PParams (BabbageEra StandardCrypto)
pp
      , Key
"rho" Key -> UnitInterval -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= PParams (BabbageEra StandardCrypto) -> HKD Identity UnitInterval
forall (f :: * -> *) era. PParams' f era -> HKD f UnitInterval
Babbage._rho PParams (BabbageEra StandardCrypto)
pp
      , Key
"tau" Key -> UnitInterval -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= PParams (BabbageEra StandardCrypto) -> HKD Identity UnitInterval
forall (f :: * -> *) era. PParams' f era -> HKD f UnitInterval
Babbage._tau PParams (BabbageEra StandardCrypto)
pp
      , Key
"protocolVersion" Key -> ProtVer -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= PParams (BabbageEra StandardCrypto) -> HKD Identity ProtVer
forall (f :: * -> *) era. PParams' f era -> HKD f ProtVer
Babbage._protocolVersion PParams (BabbageEra StandardCrypto)
pp
      , Key
"minPoolCost" Key -> Coin -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= PParams (BabbageEra StandardCrypto) -> HKD Identity Coin
forall (f :: * -> *) era. PParams' f era -> HKD f Coin
Babbage._minPoolCost PParams (BabbageEra StandardCrypto)
pp
      , Key
"coinsPerUTxOByte" Key -> Coin -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= PParams (BabbageEra StandardCrypto) -> HKD Identity Coin
forall (f :: * -> *) era. PParams' f era -> HKD f Coin
Babbage._coinsPerUTxOByte PParams (BabbageEra StandardCrypto)
pp
      , Key
"costmdls" Key -> CostModels -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= PParams (BabbageEra StandardCrypto) -> HKD Identity CostModels
forall (f :: * -> *) era. PParams' f era -> HKD f CostModels
Babbage._costmdls PParams (BabbageEra StandardCrypto)
pp
      , Key
"prices" Key -> Prices -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= PParams (BabbageEra StandardCrypto) -> HKD Identity Prices
forall (f :: * -> *) era. PParams' f era -> HKD f Prices
Babbage._prices PParams (BabbageEra StandardCrypto)
pp
      , Key
"maxTxExUnits" Key -> ExUnits -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= PParams (BabbageEra StandardCrypto) -> HKD Identity ExUnits
forall (f :: * -> *) era. PParams' f era -> HKD f ExUnits
Babbage._maxTxExUnits PParams (BabbageEra StandardCrypto)
pp
      , Key
"maxBlockExUnits" Key -> ExUnits -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= PParams (BabbageEra StandardCrypto) -> HKD Identity ExUnits
forall (f :: * -> *) era. PParams' f era -> HKD f ExUnits
Babbage._maxBlockExUnits PParams (BabbageEra StandardCrypto)
pp
      , Key
"maxValSize" Key -> Natural -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= PParams (BabbageEra StandardCrypto) -> HKD Identity Natural
forall (f :: * -> *) era. PParams' f era -> HKD f Natural
Babbage._maxValSize PParams (BabbageEra StandardCrypto)
pp
      , Key
"collateralPercentage" Key -> Natural -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= PParams (BabbageEra StandardCrypto) -> HKD Identity Natural
forall (f :: * -> *) era. PParams' f era -> HKD f Natural
Babbage._collateralPercentage PParams (BabbageEra StandardCrypto)
pp
      , Key
"maxCollateralInputs" Key -> Natural -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= PParams (BabbageEra StandardCrypto) -> HKD Identity Natural
forall (f :: * -> *) era. PParams' f era -> HKD f Natural
Babbage._maxCollateralInputs PParams (BabbageEra StandardCrypto)
pp
      ]

mbfield :: StrictMaybe a -> [a]
mbfield :: StrictMaybe a -> [a]
mbfield StrictMaybe a
SNothing  = []
mbfield (SJust a
x) = [a
x]

instance ( Ledger.Era era
         , ToJSON (Core.Value era)
         , ToJSON (Babbage.Datum era)
         , ToJSON (Core.Script era)
         , Ledger.Crypto era ~ Consensus.StandardCrypto
         ) => ToJSON (Babbage.TxOut era) where
  toJSON :: TxOut era -> Value
toJSON = [Pair] -> Value
object ([Pair] -> Value) -> (TxOut era -> [Pair]) -> TxOut era -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxOut era -> [Pair]
forall a era.
(KeyValue a, Era era, ToJSON (Value era), ToJSON (Script era),
 Crypto era ~ StandardCrypto) =>
TxOut era -> [a]
toBabbageTxOutPairs
  toEncoding :: TxOut era -> Encoding
toEncoding = Series -> Encoding
Aeson.pairs (Series -> Encoding)
-> (TxOut era -> Series) -> TxOut era -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Series] -> Series
forall a. Monoid a => [a] -> a
mconcat ([Series] -> Series)
-> (TxOut era -> [Series]) -> TxOut era -> Series
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxOut era -> [Series]
forall a era.
(KeyValue a, Era era, ToJSON (Value era), ToJSON (Script era),
 Crypto era ~ StandardCrypto) =>
TxOut era -> [a]
toBabbageTxOutPairs

toBabbageTxOutPairs ::
  ( Aeson.KeyValue a
  , Ledger.Era era
  , ToJSON (Core.Value era)
  , ToJSON (Core.Script era)
  , Ledger.Crypto era ~ Consensus.StandardCrypto
  ) => Babbage.TxOut era -> [a]
toBabbageTxOutPairs :: TxOut era -> [a]
toBabbageTxOutPairs (Babbage.TxOut !Addr (Crypto era)
addr !Value era
val !Datum era
dat !StrictMaybe (Script era)
mRefScript) =
  [ Key
"address" Key -> Addr StandardCrypto -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Addr StandardCrypto
Addr (Crypto era)
addr
  , Key
"value" Key -> Value era -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Value era
val
  , Key
"datum" Key -> Datum era -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Datum era
dat
  , Key
"referenceScript" Key -> StrictMaybe (Script era) -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= StrictMaybe (Script era)
mRefScript
  ]

instance ( Ledger.Era era
         , Ledger.Crypto era ~ Consensus.StandardCrypto
         ) => ToJSON (Babbage.Datum era) where
  toJSON :: Datum era -> Value
toJSON Datum era
d =
    case Datum era -> StrictMaybe (DataHash (Crypto era))
forall era.
Era era =>
Datum era -> StrictMaybe (DataHash (Crypto era))
Alonzo.datumDataHash Datum era
d of
      StrictMaybe (DataHash (Crypto era))
SNothing -> Value
Aeson.Null
      SJust DataHash (Crypto era)
dH -> Hash ScriptData -> Value
forall a. ToJSON a => a -> Value
toJSON (Hash ScriptData -> Value) -> Hash ScriptData -> Value
forall a b. (a -> b) -> a -> b
$ DataHash StandardCrypto -> Hash ScriptData
ScriptDataHash DataHash StandardCrypto
DataHash (Crypto era)
dH
  toEncoding :: Datum era -> Encoding
toEncoding Datum era
d =
    case Datum era -> StrictMaybe (DataHash (Crypto era))
forall era.
Era era =>
Datum era -> StrictMaybe (DataHash (Crypto era))
Alonzo.datumDataHash Datum era
d of
      StrictMaybe (DataHash (Crypto era))
SNothing -> Value -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding Value
Aeson.Null
      SJust DataHash (Crypto era)
dH -> Hash ScriptData -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding (Hash ScriptData -> Encoding) -> Hash ScriptData -> Encoding
forall a b. (a -> b) -> a -> b
$ DataHash StandardCrypto -> Hash ScriptData
ScriptDataHash DataHash StandardCrypto
DataHash (Crypto era)
dH



instance ToJSON (Alonzo.Script (Babbage.BabbageEra Consensus.StandardCrypto)) where
  toJSON :: Script (BabbageEra StandardCrypto) -> Value
toJSON = Text -> Value
Aeson.String (Text -> Value)
-> (Script (BabbageEra StandardCrypto) -> Text)
-> Script (BabbageEra StandardCrypto)
-> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
Text.decodeUtf8 (ByteString -> Text)
-> (Script (BabbageEra StandardCrypto) -> ByteString)
-> Script (BabbageEra StandardCrypto)
-> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
B16.encode (ByteString -> ByteString)
-> (Script (BabbageEra StandardCrypto) -> ByteString)
-> Script (BabbageEra StandardCrypto)
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Script (BabbageEra StandardCrypto) -> ByteString
forall a. ToCBOR a => a -> ByteString
CBOR.serialize'

instance Crypto.Crypto crypto => ToJSON (Shelley.DPState crypto) where
  toJSON :: DPState crypto -> Value
toJSON = [Pair] -> Value
object ([Pair] -> Value)
-> (DPState crypto -> [Pair]) -> DPState crypto -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DPState crypto -> [Pair]
forall a crypto.
(KeyValue a, Crypto crypto) =>
DPState crypto -> [a]
toDpStatePairs
  toEncoding :: DPState crypto -> Encoding
toEncoding = Series -> Encoding
Aeson.pairs (Series -> Encoding)
-> (DPState crypto -> Series) -> DPState crypto -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Series] -> Series
forall a. Monoid a => [a] -> a
mconcat ([Series] -> Series)
-> (DPState crypto -> [Series]) -> DPState crypto -> Series
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DPState crypto -> [Series]
forall a crypto.
(KeyValue a, Crypto crypto) =>
DPState crypto -> [a]
toDpStatePairs

toDpStatePairs ::
  ( Aeson.KeyValue a
  , Crypto.Crypto crypto
  ) => ShelleyLedger.DPState crypto -> [a]
toDpStatePairs :: DPState crypto -> [a]
toDpStatePairs DPState crypto
dpState =
  let !dstate :: DState crypto
dstate = DPState crypto -> DState crypto
forall crypto. DPState crypto -> DState crypto
Shelley.dpsDState DPState crypto
dpState
      !pstate :: PState crypto
pstate = DPState crypto -> PState crypto
forall crypto. DPState crypto -> PState crypto
Shelley.dpsPState DPState crypto
dpState
  in  [ Key
"dstate" Key -> DState crypto -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= DState crypto
dstate
      , Key
"pstate" Key -> PState crypto -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= PState crypto
pstate
      ]

instance (ToJSON coin, ToJSON ptr, ToJSON pool) => ToJSON (Trip coin ptr pool) where
  toJSON :: Trip coin ptr pool -> Value
toJSON = [Pair] -> Value
object ([Pair] -> Value)
-> (Trip coin ptr pool -> [Pair]) -> Trip coin ptr pool -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Trip coin ptr pool -> [Pair]
forall a coin ptr pool.
(KeyValue a, ToJSON coin, ToJSON ptr, ToJSON pool) =>
Trip coin ptr pool -> [a]
toTripPair
  toEncoding :: Trip coin ptr pool -> Encoding
toEncoding = Series -> Encoding
Aeson.pairs (Series -> Encoding)
-> (Trip coin ptr pool -> Series) -> Trip coin ptr pool -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Series] -> Series
forall a. Monoid a => [a] -> a
mconcat ([Series] -> Series)
-> (Trip coin ptr pool -> [Series]) -> Trip coin ptr pool -> Series
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Trip coin ptr pool -> [Series]
forall a coin ptr pool.
(KeyValue a, ToJSON coin, ToJSON ptr, ToJSON pool) =>
Trip coin ptr pool -> [a]
toTripPair

toTripPair ::
  ( Aeson.KeyValue a
  , ToJSON coin
  , ToJSON ptr
  , ToJSON pool
  ) => Trip coin ptr pool -> [a]
toTripPair :: Trip coin ptr pool -> [a]
toTripPair (Triple !StrictMaybe coin
coin !Set ptr
ptr !StrictMaybe pool
pool) =
  [ Key
"coin" Key -> StrictMaybe coin -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= StrictMaybe coin
coin
  , Key
"ptr" Key -> Set ptr -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Set ptr
ptr
  , Key
"pool" Key -> StrictMaybe pool -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= StrictMaybe pool
pool
  ]

instance Crypto.Crypto crypto => ToJSON (UnifiedMap crypto) where
  toJSON :: UnifiedMap crypto -> Value
toJSON = [Pair] -> Value
object ([Pair] -> Value)
-> (UnifiedMap crypto -> [Pair]) -> UnifiedMap crypto -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnifiedMap crypto -> [Pair]
forall a coin ptr pool cred.
(KeyValue a, ToJSON coin, ToJSON ptr, ToJSON pool, ToJSON cred,
 ToJSONKey cred, ToJSONKey ptr) =>
UMap coin cred pool ptr -> [a]
toUnifiedMapPair
  toEncoding :: UnifiedMap crypto -> Encoding
toEncoding = Series -> Encoding
Aeson.pairs (Series -> Encoding)
-> (UnifiedMap crypto -> Series) -> UnifiedMap crypto -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Series] -> Series
forall a. Monoid a => [a] -> a
mconcat ([Series] -> Series)
-> (UnifiedMap crypto -> [Series]) -> UnifiedMap crypto -> Series
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnifiedMap crypto -> [Series]
forall a coin ptr pool cred.
(KeyValue a, ToJSON coin, ToJSON ptr, ToJSON pool, ToJSON cred,
 ToJSONKey cred, ToJSONKey ptr) =>
UMap coin cred pool ptr -> [a]
toUnifiedMapPair

toUnifiedMapPair ::
  ( Aeson.KeyValue a
  , ToJSON coin
  , ToJSON ptr
  , ToJSON pool
  , ToJSON cred
  , ToJSONKey cred
  , ToJSONKey ptr
  ) => UMap coin cred pool ptr -> [a]
toUnifiedMapPair :: UMap coin cred pool ptr -> [a]
toUnifiedMapPair (UnifiedMap !Map cred (Trip coin ptr pool)
m1 !Map ptr cred
m2) =
  [ Key
"credentials" Key -> Map cred (Trip coin ptr pool) -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Map cred (Trip coin ptr pool)
m1
  , Key
"pointers" Key -> Map ptr cred -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Map ptr cred
m2
  ]

instance Crypto.Crypto crypto => ToJSON (Shelley.DState crypto) where
  toJSON :: DState crypto -> Value
toJSON = [Pair] -> Value
object ([Pair] -> Value)
-> (DState crypto -> [Pair]) -> DState crypto -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DState crypto -> [Pair]
forall a crypto.
(KeyValue a, Crypto crypto) =>
DState crypto -> [a]
toDStatePair
  toEncoding :: DState crypto -> Encoding
toEncoding = Series -> Encoding
Aeson.pairs (Series -> Encoding)
-> (DState crypto -> Series) -> DState crypto -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Series] -> Series
forall a. Monoid a => [a] -> a
mconcat ([Series] -> Series)
-> (DState crypto -> [Series]) -> DState crypto -> Series
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DState crypto -> [Series]
forall a crypto.
(KeyValue a, Crypto crypto) =>
DState crypto -> [a]
toDStatePair

toDStatePair ::
  ( Aeson.KeyValue a
  , Crypto.Crypto crypto
  ) => ShelleyLedger.DState crypto -> [a]
toDStatePair :: DState crypto -> [a]
toDStatePair DState crypto
dState =
  let !unifiedRewards :: UnifiedMap crypto
unifiedRewards = DState crypto -> UnifiedMap crypto
forall crypto. DState crypto -> UnifiedMap crypto
Shelley._unified DState crypto
dState
      !fGenDelegs :: [(FutureGenDeleg crypto, GenDelegPair crypto)]
fGenDelegs = Map (FutureGenDeleg crypto) (GenDelegPair crypto)
-> [(FutureGenDeleg crypto, GenDelegPair crypto)]
forall k a. Map k a -> [(k, a)]
Map.toList (DState crypto -> Map (FutureGenDeleg crypto) (GenDelegPair crypto)
forall crypto.
DState crypto -> Map (FutureGenDeleg crypto) (GenDelegPair crypto)
Shelley._fGenDelegs DState crypto
dState)
      !genDelegs :: GenDelegs crypto
genDelegs = DState crypto -> GenDelegs crypto
forall crypto. DState crypto -> GenDelegs crypto
Shelley._genDelegs DState crypto
dState
      !irwd :: InstantaneousRewards crypto
irwd = DState crypto -> InstantaneousRewards crypto
forall crypto. DState crypto -> InstantaneousRewards crypto
Shelley._irwd DState crypto
dState
  in  [ Key
"unifiedRewards" Key -> UnifiedMap crypto -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= UnifiedMap crypto
unifiedRewards
      , Key
"fGenDelegs" Key -> [(FutureGenDeleg crypto, GenDelegPair crypto)] -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [(FutureGenDeleg crypto, GenDelegPair crypto)]
fGenDelegs
      , Key
"genDelegs" Key -> GenDelegs crypto -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= GenDelegs crypto
genDelegs
      , Key
"irwd" Key -> InstantaneousRewards crypto -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= InstantaneousRewards crypto
irwd
      ]

instance Crypto.Crypto crypto => ToJSON (ShelleyLedger.FutureGenDeleg crypto) where
  toJSON :: FutureGenDeleg crypto -> Value
toJSON FutureGenDeleg crypto
fGenDeleg =
    [Pair] -> Value
object [ Key
"fGenDelegSlot" Key -> SlotNo -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FutureGenDeleg crypto -> SlotNo
forall crypto. FutureGenDeleg crypto -> SlotNo
ShelleyLedger.fGenDelegSlot FutureGenDeleg crypto
fGenDeleg
           , Key
"fGenDelegGenKeyHash" Key -> KeyHash 'Genesis crypto -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= FutureGenDeleg crypto -> KeyHash 'Genesis crypto
forall crypto. FutureGenDeleg crypto -> KeyHash 'Genesis crypto
ShelleyLedger.fGenDelegGenKeyHash FutureGenDeleg crypto
fGenDeleg
           ]

instance Crypto.Crypto crypto => ToJSON (Shelley.GenDelegs crypto) where
  toJSON :: GenDelegs crypto -> Value
toJSON (Shelley.GenDelegs Map (KeyHash 'Genesis crypto) (GenDelegPair crypto)
delegs) = Map (KeyHash 'Genesis crypto) (GenDelegPair crypto) -> Value
forall a. ToJSON a => a -> Value
toJSON Map (KeyHash 'Genesis crypto) (GenDelegPair crypto)
delegs
  toEncoding :: GenDelegs crypto -> Encoding
toEncoding (Shelley.GenDelegs Map (KeyHash 'Genesis crypto) (GenDelegPair crypto)
delegs) = Map (KeyHash 'Genesis crypto) (GenDelegPair crypto) -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding Map (KeyHash 'Genesis crypto) (GenDelegPair crypto)
delegs

instance Crypto.Crypto crypto => ToJSON (Shelley.InstantaneousRewards crypto) where
  toJSON :: InstantaneousRewards crypto -> Value
toJSON = [Pair] -> Value
object ([Pair] -> Value)
-> (InstantaneousRewards crypto -> [Pair])
-> InstantaneousRewards crypto
-> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InstantaneousRewards crypto -> [Pair]
forall a crypto.
(KeyValue a, Crypto crypto) =>
InstantaneousRewards crypto -> [a]
toInstantaneousRewardsPair
  toEncoding :: InstantaneousRewards crypto -> Encoding
toEncoding = Series -> Encoding
Aeson.pairs (Series -> Encoding)
-> (InstantaneousRewards crypto -> Series)
-> InstantaneousRewards crypto
-> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Series] -> Series
forall a. Monoid a => [a] -> a
mconcat ([Series] -> Series)
-> (InstantaneousRewards crypto -> [Series])
-> InstantaneousRewards crypto
-> Series
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InstantaneousRewards crypto -> [Series]
forall a crypto.
(KeyValue a, Crypto crypto) =>
InstantaneousRewards crypto -> [a]
toInstantaneousRewardsPair

toInstantaneousRewardsPair ::
  ( Aeson.KeyValue a
  , Crypto.Crypto crypto
  ) => ShelleyLedger.InstantaneousRewards crypto -> [a]
toInstantaneousRewardsPair :: InstantaneousRewards crypto -> [a]
toInstantaneousRewardsPair InstantaneousRewards crypto
iRwds =
  let !iRReserves :: Map (Credential 'Staking crypto) Coin
iRReserves = InstantaneousRewards crypto
-> Map (Credential 'Staking crypto) Coin
forall crypto.
InstantaneousRewards crypto
-> Map (Credential 'Staking crypto) Coin
Shelley.iRReserves InstantaneousRewards crypto
iRwds
      !iRTreasury :: Map (Credential 'Staking crypto) Coin
iRTreasury = InstantaneousRewards crypto
-> Map (Credential 'Staking crypto) Coin
forall crypto.
InstantaneousRewards crypto
-> Map (Credential 'Staking crypto) Coin
Shelley.iRTreasury InstantaneousRewards crypto
iRwds
  in  [ Key
"iRReserves" Key -> Map (Credential 'Staking crypto) Coin -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Map (Credential 'Staking crypto) Coin
iRReserves
      , Key
"iRTreasury" Key -> Map (Credential 'Staking crypto) Coin -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Map (Credential 'Staking crypto) Coin
iRTreasury
      ]

instance
  Crypto.Crypto crypto =>
  ToJSON (Bimap Shelley.Ptr (Shelley.Credential Shelley.Staking crypto))
  where
  toJSON :: Bimap Ptr (Credential 'Staking crypto) -> Value
toJSON = [Pair] -> Value
object ([Pair] -> Value)
-> (Bimap Ptr (Credential 'Staking crypto) -> [Pair])
-> Bimap Ptr (Credential 'Staking crypto)
-> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bimap Ptr (Credential 'Staking crypto) -> [Pair]
forall a crypto.
(KeyValue a, Crypto crypto) =>
Bimap Ptr (Credential 'Staking crypto) -> [a]
toPtrCredentialStakingPair
  toEncoding :: Bimap Ptr (Credential 'Staking crypto) -> Encoding
toEncoding = Series -> Encoding
Aeson.pairs (Series -> Encoding)
-> (Bimap Ptr (Credential 'Staking crypto) -> Series)
-> Bimap Ptr (Credential 'Staking crypto)
-> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Series] -> Series
forall a. Monoid a => [a] -> a
mconcat ([Series] -> Series)
-> (Bimap Ptr (Credential 'Staking crypto) -> [Series])
-> Bimap Ptr (Credential 'Staking crypto)
-> Series
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bimap Ptr (Credential 'Staking crypto) -> [Series]
forall a crypto.
(KeyValue a, Crypto crypto) =>
Bimap Ptr (Credential 'Staking crypto) -> [a]
toPtrCredentialStakingPair

toPtrCredentialStakingPair ::
  ( Aeson.KeyValue a
  , Crypto.Crypto crypto
  ) => Bimap Shelley.Ptr (Shelley.Credential Shelley.Staking crypto) -> [a]
toPtrCredentialStakingPair :: Bimap Ptr (Credential 'Staking crypto) -> [a]
toPtrCredentialStakingPair (MkBiMap Map Ptr (Credential 'Staking crypto)
ptsStakeM Map (Credential 'Staking crypto) (Set Ptr)
stakePtrSetM) =
  let !stakedCreds :: [(Ptr, Credential 'Staking crypto)]
stakedCreds = Map Ptr (Credential 'Staking crypto)
-> [(Ptr, Credential 'Staking crypto)]
forall k a. Map k a -> [(k, a)]
Map.toList Map Ptr (Credential 'Staking crypto)
ptsStakeM
      !credPtrR :: Map (Credential 'Staking crypto) (Set Ptr)
credPtrR = Map (Credential 'Staking crypto) (Set Ptr)
stakePtrSetM
  in  [ Key
"stakedCreds" Key -> [(Ptr, Credential 'Staking crypto)] -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= [(Ptr, Credential 'Staking crypto)]
stakedCreds
      , Key
"credPtrR" Key -> Map (Credential 'Staking crypto) (Set Ptr) -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Map (Credential 'Staking crypto) (Set Ptr)
credPtrR
      ]

deriving newtype instance ToJSON Shelley.CertIx
deriving newtype instance ToJSON Shelley.TxIx

instance ToJSON Shelley.Ptr where
  toJSON :: Ptr -> Value
toJSON = [Pair] -> Value
object ([Pair] -> Value) -> (Ptr -> [Pair]) -> Ptr -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr -> [Pair]
forall a. KeyValue a => Ptr -> [a]
toPtrPair
  toEncoding :: Ptr -> Encoding
toEncoding = Series -> Encoding
Aeson.pairs (Series -> Encoding) -> (Ptr -> Series) -> Ptr -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Series] -> Series
forall a. Monoid a => [a] -> a
mconcat ([Series] -> Series) -> (Ptr -> [Series]) -> Ptr -> Series
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr -> [Series]
forall a. KeyValue a => Ptr -> [a]
toPtrPair

instance ToJSONKey Shelley.Ptr

toPtrPair :: Aeson.KeyValue a => Shelley.Ptr -> [a]
toPtrPair :: Ptr -> [a]
toPtrPair (Shelley.Ptr !SlotNo
slotNo !TxIx
txIndex !CertIx
certIndex) =
  [ Key
"slot" Key -> Word64 -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= SlotNo -> Word64
unSlotNo SlotNo
slotNo
  , Key
"txIndex" Key -> TxIx -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= TxIx
txIndex
  , Key
"certIndex" Key -> CertIx -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= CertIx
certIndex
  ]


instance Crypto.Crypto crypto => ToJSON (Shelley.PState crypto) where
  toJSON :: PState crypto -> Value
toJSON = [Pair] -> Value
object ([Pair] -> Value)
-> (PState crypto -> [Pair]) -> PState crypto -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PState crypto -> [Pair]
forall a crypto.
(KeyValue a, Crypto crypto) =>
PState crypto -> [a]
toPStatePair
  toEncoding :: PState crypto -> Encoding
toEncoding = Series -> Encoding
Aeson.pairs (Series -> Encoding)
-> (PState crypto -> Series) -> PState crypto -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Series] -> Series
forall a. Monoid a => [a] -> a
mconcat ([Series] -> Series)
-> (PState crypto -> [Series]) -> PState crypto -> Series
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PState crypto -> [Series]
forall a crypto.
(KeyValue a, Crypto crypto) =>
PState crypto -> [a]
toPStatePair

toPStatePair ::
  ( Aeson.KeyValue a
  , Crypto.Crypto crypto
  ) => ShelleyLedger.PState crypto -> [a]
toPStatePair :: PState crypto -> [a]
toPStatePair PState crypto
pState =
  let !pParams :: Map (KeyHash 'StakePool crypto) (PoolParams crypto)
pParams = PState crypto
-> Map (KeyHash 'StakePool crypto) (PoolParams crypto)
forall crypto.
PState crypto
-> Map (KeyHash 'StakePool crypto) (PoolParams crypto)
Shelley._pParams PState crypto
pState
      !fPParams :: Map (KeyHash 'StakePool crypto) (PoolParams crypto)
fPParams = PState crypto
-> Map (KeyHash 'StakePool crypto) (PoolParams crypto)
forall crypto.
PState crypto
-> Map (KeyHash 'StakePool crypto) (PoolParams crypto)
Shelley._fPParams PState crypto
pState
      !retiring :: Map (KeyHash 'StakePool crypto) EpochNo
retiring = PState crypto -> Map (KeyHash 'StakePool crypto) EpochNo
forall crypto.
PState crypto -> Map (KeyHash 'StakePool crypto) EpochNo
Shelley._retiring PState crypto
pState
  in  [ Key
"pParams pState" Key -> Map (KeyHash 'StakePool crypto) (PoolParams crypto) -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Map (KeyHash 'StakePool crypto) (PoolParams crypto)
pParams
      , Key
"fPParams pState" Key -> Map (KeyHash 'StakePool crypto) (PoolParams crypto) -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Map (KeyHash 'StakePool crypto) (PoolParams crypto)
fPParams
      , Key
"retiring pState" Key -> Map (KeyHash 'StakePool crypto) EpochNo -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Map (KeyHash 'StakePool crypto) EpochNo
retiring
      ]

instance ( Consensus.ShelleyBasedEra era
         , ToJSON (Core.TxOut era)
         ) => ToJSON (Shelley.UTxO era) where
  toJSON :: UTxO era -> Value
toJSON (Shelley.UTxO Map (TxIn (Crypto era)) (TxOut era)
utxo) = Map (TxIn (Crypto era)) (TxOut era) -> Value
forall a. ToJSON a => a -> Value
toJSON Map (TxIn (Crypto era)) (TxOut era)
utxo
  toEncoding :: UTxO era -> Encoding
toEncoding (Shelley.UTxO Map (TxIn (Crypto era)) (TxOut era)
utxo) = Map (TxIn (Crypto era)) (TxOut era) -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding Map (TxIn (Crypto era)) (TxOut era)
utxo

instance ( Consensus.ShelleyBasedEra era
         , ToJSON (Core.Value era)
         ) => ToJSON (Shelley.TxOut era) where
  toJSON :: TxOut era -> Value
toJSON = [Pair] -> Value
object ([Pair] -> Value) -> (TxOut era -> [Pair]) -> TxOut era -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxOut era -> [Pair]
forall era a.
(Era era, KeyValue a, ToJSON (Value era), Show (Value era)) =>
TxOut era -> [a]
toTxOutPair
  toEncoding :: TxOut era -> Encoding
toEncoding = Series -> Encoding
Aeson.pairs (Series -> Encoding)
-> (TxOut era -> Series) -> TxOut era -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Series] -> Series
forall a. Monoid a => [a] -> a
mconcat ([Series] -> Series)
-> (TxOut era -> [Series]) -> TxOut era -> Series
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxOut era -> [Series]
forall era a.
(Era era, KeyValue a, ToJSON (Value era), Show (Value era)) =>
TxOut era -> [a]
toTxOutPair

toTxOutPair ::
  ( Ledger.Era era
  , Aeson.KeyValue a
  , ToJSON (Core.Value era)
  , Show (Core.Value era))
  => Shelley.TxOut era -> [a]
toTxOutPair :: TxOut era -> [a]
toTxOutPair (Shelley.TxOut !Addr (Crypto era)
addr !Value era
amount) =
  [ Key
"address" Key -> Addr (Crypto era) -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Addr (Crypto era)
addr
  , Key
"amount" Key -> Value era -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Value era
amount
  ]

instance Crypto.Crypto crypto => ToJSON (Shelley.TxIn crypto) where
  toJSON :: TxIn crypto -> Value
toJSON = Text -> Value
forall a. ToJSON a => a -> Value
toJSON (Text -> Value) -> (TxIn crypto -> Text) -> TxIn crypto -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxIn crypto -> Text
forall crypto. TxIn crypto -> Text
txInToText
  toEncoding :: TxIn crypto -> Encoding
toEncoding = Text -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding (Text -> Encoding)
-> (TxIn crypto -> Text) -> TxIn crypto -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxIn crypto -> Text
forall crypto. TxIn crypto -> Text
txInToText

instance Crypto.Crypto crypto => ToJSONKey (Shelley.TxIn crypto) where
  toJSONKey :: ToJSONKeyFunction (TxIn crypto)
toJSONKey = (TxIn crypto -> Text) -> ToJSONKeyFunction (TxIn crypto)
forall a. (a -> Text) -> ToJSONKeyFunction a
toJSONKeyText TxIn crypto -> Text
forall crypto. TxIn crypto -> Text
txInToText

txInToText :: Shelley.TxIn crypto -> Text
txInToText :: TxIn crypto -> Text
txInToText (Shelley.TxIn (Shelley.TxId SafeHash crypto EraIndependentTxBody
txidHash) TxIx
ix) =
  Hash (HASH crypto) EraIndependentTxBody -> Text
forall crypto a. Hash crypto a -> Text
hashToText (SafeHash crypto EraIndependentTxBody
-> Hash (HASH crypto) EraIndependentTxBody
forall crypto i. SafeHash crypto i -> Hash (HASH crypto) i
SafeHash.extractHash SafeHash crypto EraIndependentTxBody
txidHash)
    Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
Text.pack String
"#"
    Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
Text.pack (TxIx -> String
forall a. Show a => a -> String
show TxIx
ix)

hashToText :: Crypto.Hash crypto a -> Text
hashToText :: Hash crypto a -> Text
hashToText = ByteString -> Text
Text.decodeLatin1 (ByteString -> Text)
-> (Hash crypto a -> ByteString) -> Hash crypto a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash crypto a -> ByteString
forall h a. Hash h a -> ByteString
Crypto.hashToBytesAsHex

instance Crypto.Crypto crypto => ToJSON (Shelley.NonMyopic crypto) where
  toJSON :: NonMyopic crypto -> Value
toJSON = [Pair] -> Value
object ([Pair] -> Value)
-> (NonMyopic crypto -> [Pair]) -> NonMyopic crypto -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonMyopic crypto -> [Pair]
forall a crypto.
(KeyValue a, Crypto crypto) =>
NonMyopic crypto -> [a]
toNonMyopicPair
  toEncoding :: NonMyopic crypto -> Encoding
toEncoding = Series -> Encoding
Aeson.pairs (Series -> Encoding)
-> (NonMyopic crypto -> Series) -> NonMyopic crypto -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Series] -> Series
forall a. Monoid a => [a] -> a
mconcat ([Series] -> Series)
-> (NonMyopic crypto -> [Series]) -> NonMyopic crypto -> Series
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonMyopic crypto -> [Series]
forall a crypto.
(KeyValue a, Crypto crypto) =>
NonMyopic crypto -> [a]
toNonMyopicPair

toNonMyopicPair ::
  ( Aeson.KeyValue a
  , Crypto.Crypto crypto
  ) => Shelley.NonMyopic crypto -> [a]
toNonMyopicPair :: NonMyopic crypto -> [a]
toNonMyopicPair NonMyopic crypto
nonMy =
  let !likelihoodsNM :: Map (KeyHash 'StakePool crypto) Likelihood
likelihoodsNM = NonMyopic crypto -> Map (KeyHash 'StakePool crypto) Likelihood
forall crypto.
NonMyopic crypto -> Map (KeyHash 'StakePool crypto) Likelihood
Shelley.likelihoodsNM NonMyopic crypto
nonMy
      !rewardPotNM :: Coin
rewardPotNM = NonMyopic crypto -> Coin
forall crypto. NonMyopic crypto -> Coin
Shelley.rewardPotNM NonMyopic crypto
nonMy
  in  [ Key
"likelihoodsNM" Key -> Map (KeyHash 'StakePool crypto) Likelihood -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Map (KeyHash 'StakePool crypto) Likelihood
likelihoodsNM
      , Key
"rewardPotNM" Key -> Coin -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Coin
rewardPotNM
      ]

instance ToJSON Shelley.Likelihood where
  toJSON :: Likelihood -> Value
toJSON (Shelley.Likelihood StrictSeq LogWeight
llhd) =
    StrictSeq Double -> Value
forall a. ToJSON a => a -> Value
toJSON (StrictSeq Double -> Value) -> StrictSeq Double -> Value
forall a b. (a -> b) -> a -> b
$ (LogWeight -> Double) -> StrictSeq LogWeight -> StrictSeq Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(Shelley.LogWeight Float
f) -> Double -> Double
forall a. Floating a => a -> a
exp (Double -> Double) -> Double -> Double
forall a b. (a -> b) -> a -> b
$ Float -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
f :: Double) StrictSeq LogWeight
llhd
  toEncoding :: Likelihood -> Encoding
toEncoding (Shelley.Likelihood StrictSeq LogWeight
llhd) =
    StrictSeq Double -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding (StrictSeq Double -> Encoding) -> StrictSeq Double -> Encoding
forall a b. (a -> b) -> a -> b
$ (LogWeight -> Double) -> StrictSeq LogWeight -> StrictSeq Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(Shelley.LogWeight Float
f) -> Double -> Double
forall a. Floating a => a -> a
exp (Double -> Double) -> Double -> Double
forall a b. (a -> b) -> a -> b
$ Float -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
f :: Double) StrictSeq LogWeight
llhd

instance Crypto.Crypto crypto => ToJSON (Shelley.SnapShots crypto) where
  toJSON :: SnapShots crypto -> Value
toJSON = [Pair] -> Value
object ([Pair] -> Value)
-> (SnapShots crypto -> [Pair]) -> SnapShots crypto -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SnapShots crypto -> [Pair]
forall a crypto.
(KeyValue a, Crypto crypto) =>
SnapShots crypto -> [a]
toSnapShotsPair
  toEncoding :: SnapShots crypto -> Encoding
toEncoding = Series -> Encoding
Aeson.pairs (Series -> Encoding)
-> (SnapShots crypto -> Series) -> SnapShots crypto -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Series] -> Series
forall a. Monoid a => [a] -> a
mconcat ([Series] -> Series)
-> (SnapShots crypto -> [Series]) -> SnapShots crypto -> Series
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SnapShots crypto -> [Series]
forall a crypto.
(KeyValue a, Crypto crypto) =>
SnapShots crypto -> [a]
toSnapShotsPair

toSnapShotsPair ::
  ( Aeson.KeyValue a
  , Crypto.Crypto crypto
  ) => ShelleyEpoch.SnapShots crypto -> [a]
toSnapShotsPair :: SnapShots crypto -> [a]
toSnapShotsPair SnapShots crypto
ss =
  let !pstakeMark :: SnapShot crypto
pstakeMark = SnapShots crypto -> SnapShot crypto
forall crypto. SnapShots crypto -> SnapShot crypto
Shelley._pstakeMark SnapShots crypto
ss
      !pstakeSet :: SnapShot crypto
pstakeSet = SnapShots crypto -> SnapShot crypto
forall crypto. SnapShots crypto -> SnapShot crypto
Shelley._pstakeSet SnapShots crypto
ss
      !pstakeGo :: SnapShot crypto
pstakeGo = SnapShots crypto -> SnapShot crypto
forall crypto. SnapShots crypto -> SnapShot crypto
Shelley._pstakeGo SnapShots crypto
ss
      !feeSS :: Coin
feeSS = SnapShots crypto -> Coin
forall crypto. SnapShots crypto -> Coin
Shelley._feeSS SnapShots crypto
ss
  in  [ Key
"pstakeMark" Key -> SnapShot crypto -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= SnapShot crypto
pstakeMark
      , Key
"pstakeSet" Key -> SnapShot crypto -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= SnapShot crypto
pstakeSet
      , Key
"pstakeGo" Key -> SnapShot crypto -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= SnapShot crypto
pstakeGo
      , Key
"feeSS" Key -> Coin -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Coin
feeSS
      ]

instance Crypto.Crypto crypto => ToJSON (Shelley.SnapShot crypto) where
  toJSON :: SnapShot crypto -> Value
toJSON = [Pair] -> Value
object ([Pair] -> Value)
-> (SnapShot crypto -> [Pair]) -> SnapShot crypto -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SnapShot crypto -> [Pair]
forall a crypto.
(KeyValue a, Crypto crypto) =>
SnapShot crypto -> [a]
toSnapShotPair
  toEncoding :: SnapShot crypto -> Encoding
toEncoding = Series -> Encoding
Aeson.pairs (Series -> Encoding)
-> (SnapShot crypto -> Series) -> SnapShot crypto -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Series] -> Series
forall a. Monoid a => [a] -> a
mconcat ([Series] -> Series)
-> (SnapShot crypto -> [Series]) -> SnapShot crypto -> Series
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SnapShot crypto -> [Series]
forall a crypto.
(KeyValue a, Crypto crypto) =>
SnapShot crypto -> [a]
toSnapShotPair

toSnapShotPair ::
  ( Aeson.KeyValue a
  , Crypto.Crypto crypto
  ) => ShelleyEpoch.SnapShot crypto -> [a]
toSnapShotPair :: SnapShot crypto -> [a]
toSnapShotPair SnapShot crypto
ss =
  let !stake :: Stake crypto
stake = SnapShot crypto -> Stake crypto
forall crypto. SnapShot crypto -> Stake crypto
Shelley._stake SnapShot crypto
ss
      !delegations :: VMap VB VB (Credential 'Staking crypto) (KeyHash 'StakePool crypto)
delegations = SnapShot crypto
-> VMap
     VB VB (Credential 'Staking crypto) (KeyHash 'StakePool crypto)
forall crypto.
SnapShot crypto
-> VMap
     VB VB (Credential 'Staking crypto) (KeyHash 'StakePool crypto)
ShelleyEpoch._delegations SnapShot crypto
ss
      !poolParams :: VMap VB VB (KeyHash 'StakePool crypto) (PoolParams crypto)
poolParams = SnapShot crypto
-> VMap VB VB (KeyHash 'StakePool crypto) (PoolParams crypto)
forall crypto.
SnapShot crypto
-> VMap VB VB (KeyHash 'StakePool crypto) (PoolParams crypto)
Shelley._poolParams SnapShot crypto
ss
  in  [ Key
"stake" Key -> Stake crypto -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Stake crypto
stake
      , Key
"delegations" Key
-> VMap
     VB VB (Credential 'Staking crypto) (KeyHash 'StakePool crypto)
-> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= VMap VB VB (Credential 'Staking crypto) (KeyHash 'StakePool crypto)
delegations
      , Key
"poolParams" Key
-> VMap VB VB (KeyHash 'StakePool crypto) (PoolParams crypto) -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= VMap VB VB (KeyHash 'StakePool crypto) (PoolParams crypto)
poolParams
      ]

instance Crypto.Crypto crypto => ToJSON (Shelley.Stake crypto) where
  toJSON :: Stake crypto -> Value
toJSON (Shelley.Stake VMap VB VP (Credential 'Staking crypto) (CompactForm Coin)
s) = VMap VB VP (Credential 'Staking crypto) (CompactForm Coin) -> Value
forall a. ToJSON a => a -> Value
toJSON VMap VB VP (Credential 'Staking crypto) (CompactForm Coin)
s
  toEncoding :: Stake crypto -> Encoding
toEncoding (Shelley.Stake VMap VB VP (Credential 'Staking crypto) (CompactForm Coin)
s) = VMap VB VP (Credential 'Staking crypto) (CompactForm Coin)
-> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding VMap VB VP (Credential 'Staking crypto) (CompactForm Coin)
s

instance Crypto.Crypto crypto => ToJSON (Shelley.RewardUpdate crypto) where
  toJSON :: RewardUpdate crypto -> Value
toJSON = [Pair] -> Value
object ([Pair] -> Value)
-> (RewardUpdate crypto -> [Pair]) -> RewardUpdate crypto -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RewardUpdate crypto -> [Pair]
forall a crypto.
(KeyValue a, Crypto crypto) =>
RewardUpdate crypto -> [a]
toRewardUpdatePair
  toEncoding :: RewardUpdate crypto -> Encoding
toEncoding = Series -> Encoding
Aeson.pairs (Series -> Encoding)
-> (RewardUpdate crypto -> Series)
-> RewardUpdate crypto
-> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Series] -> Series
forall a. Monoid a => [a] -> a
mconcat ([Series] -> Series)
-> (RewardUpdate crypto -> [Series])
-> RewardUpdate crypto
-> Series
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RewardUpdate crypto -> [Series]
forall a crypto.
(KeyValue a, Crypto crypto) =>
RewardUpdate crypto -> [a]
toRewardUpdatePair

toRewardUpdatePair ::
  ( Aeson.KeyValue a
  , Crypto.Crypto crypto
  ) => Shelley.RewardUpdate crypto -> [a]
toRewardUpdatePair :: RewardUpdate crypto -> [a]
toRewardUpdatePair RewardUpdate crypto
rUpdate =
  let !deltaT :: DeltaCoin
deltaT = RewardUpdate crypto -> DeltaCoin
forall crypto. RewardUpdate crypto -> DeltaCoin
Shelley.deltaT RewardUpdate crypto
rUpdate
      !deltaR :: DeltaCoin
deltaR = RewardUpdate crypto -> DeltaCoin
forall crypto. RewardUpdate crypto -> DeltaCoin
Shelley.deltaR RewardUpdate crypto
rUpdate
      !rs :: Map (Credential 'Staking crypto) (Set (Reward crypto))
rs = RewardUpdate crypto
-> Map (Credential 'Staking crypto) (Set (Reward crypto))
forall crypto.
RewardUpdate crypto
-> Map (Credential 'Staking crypto) (Set (Reward crypto))
Shelley.rs RewardUpdate crypto
rUpdate
      !deltaF :: DeltaCoin
deltaF = RewardUpdate crypto -> DeltaCoin
forall crypto. RewardUpdate crypto -> DeltaCoin
Shelley.deltaF RewardUpdate crypto
rUpdate
      !nonMyopic :: NonMyopic crypto
nonMyopic = RewardUpdate crypto -> NonMyopic crypto
forall crypto. RewardUpdate crypto -> NonMyopic crypto
Shelley.nonMyopic RewardUpdate crypto
rUpdate
  in  [ Key
"deltaT" Key -> DeltaCoin -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= DeltaCoin
deltaT
      , Key
"deltaR" Key -> DeltaCoin -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= DeltaCoin
deltaR
      , Key
"rs" Key -> Map (Credential 'Staking crypto) (Set (Reward crypto)) -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Map (Credential 'Staking crypto) (Set (Reward crypto))
rs
      , Key
"deltaF" Key -> DeltaCoin -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= DeltaCoin
deltaF
      , Key
"nonMyopic" Key -> NonMyopic crypto -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= NonMyopic crypto
nonMyopic
      ]

instance Crypto.Crypto crypto => ToJSON (Shelley.PulsingRewUpdate crypto) where
  toJSON :: PulsingRewUpdate crypto -> Value
toJSON  = \case
    Shelley.Pulsing RewardSnapShot crypto
_ Pulser crypto
_ -> Value
Aeson.Null
    Shelley.Complete RewardUpdate crypto
ru -> RewardUpdate crypto -> Value
forall a. ToJSON a => a -> Value
toJSON RewardUpdate crypto
ru
  toEncoding :: PulsingRewUpdate crypto -> Encoding
toEncoding  = \case
    Shelley.Pulsing RewardSnapShot crypto
_ Pulser crypto
_ -> Value -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding Value
Aeson.Null
    Shelley.Complete RewardUpdate crypto
ru -> RewardUpdate crypto -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding RewardUpdate crypto
ru

instance ToJSON Shelley.DeltaCoin where
  toJSON :: DeltaCoin -> Value
toJSON (Shelley.DeltaCoin Integer
i) = Integer -> Value
forall a. ToJSON a => a -> Value
toJSON Integer
i
  toEncoding :: DeltaCoin -> Encoding
toEncoding (Shelley.DeltaCoin Integer
i) = Integer -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding Integer
i

instance Crypto.Crypto crypto => ToJSON (Ledger.PoolDistr crypto) where
  toJSON :: PoolDistr crypto -> Value
toJSON (Ledger.PoolDistr Map (KeyHash 'StakePool crypto) (IndividualPoolStake crypto)
m) = Map (KeyHash 'StakePool crypto) (IndividualPoolStake crypto)
-> Value
forall a. ToJSON a => a -> Value
toJSON Map (KeyHash 'StakePool crypto) (IndividualPoolStake crypto)
m
  toEncoding :: PoolDistr crypto -> Encoding
toEncoding (Ledger.PoolDistr Map (KeyHash 'StakePool crypto) (IndividualPoolStake crypto)
m) = Map (KeyHash 'StakePool crypto) (IndividualPoolStake crypto)
-> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding Map (KeyHash 'StakePool crypto) (IndividualPoolStake crypto)
m

instance Crypto.Crypto crypto => ToJSON (Ledger.IndividualPoolStake crypto) where
  toJSON :: IndividualPoolStake crypto -> Value
toJSON = [Pair] -> Value
object ([Pair] -> Value)
-> (IndividualPoolStake crypto -> [Pair])
-> IndividualPoolStake crypto
-> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IndividualPoolStake crypto -> [Pair]
forall a crypto.
(KeyValue a, HashAlgorithm (HASH crypto)) =>
IndividualPoolStake crypto -> [a]
toIndividualPoolStakePair
  toEncoding :: IndividualPoolStake crypto -> Encoding
toEncoding = Series -> Encoding
Aeson.pairs (Series -> Encoding)
-> (IndividualPoolStake crypto -> Series)
-> IndividualPoolStake crypto
-> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Series] -> Series
forall a. Monoid a => [a] -> a
mconcat ([Series] -> Series)
-> (IndividualPoolStake crypto -> [Series])
-> IndividualPoolStake crypto
-> Series
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IndividualPoolStake crypto -> [Series]
forall a crypto.
(KeyValue a, HashAlgorithm (HASH crypto)) =>
IndividualPoolStake crypto -> [a]
toIndividualPoolStakePair

toIndividualPoolStakePair ::
  ( Aeson.KeyValue a
  , Crypto.HashAlgorithm (Crypto.HASH crypto)
  ) => Ledger.IndividualPoolStake crypto -> [a]
toIndividualPoolStakePair :: IndividualPoolStake crypto -> [a]
toIndividualPoolStakePair IndividualPoolStake crypto
indivPoolStake =
  let !individualPoolStake :: Rational
individualPoolStake = IndividualPoolStake crypto -> Rational
forall crypto. IndividualPoolStake crypto -> Rational
Ledger.individualPoolStake IndividualPoolStake crypto
indivPoolStake
      !individualPoolStakeVrf :: Hash crypto (VerKeyVRF crypto)
individualPoolStakeVrf = IndividualPoolStake crypto -> Hash crypto (VerKeyVRF crypto)
forall crypto.
IndividualPoolStake crypto -> Hash crypto (VerKeyVRF crypto)
Ledger.individualPoolStakeVrf IndividualPoolStake crypto
indivPoolStake
  in  [ Key
"individualPoolStake" Key -> Rational -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Rational
individualPoolStake
      , Key
"individualPoolStakeVrf" Key -> Hash crypto (VerKeyVRF crypto) -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Hash crypto (VerKeyVRF crypto)
individualPoolStakeVrf
      ]

instance Crypto.Crypto crypto => ToJSON (Shelley.Reward crypto) where
  toJSON :: Reward crypto -> Value
toJSON = [Pair] -> Value
object ([Pair] -> Value)
-> (Reward crypto -> [Pair]) -> Reward crypto -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Reward crypto -> [Pair]
forall a crypto.
(KeyValue a, Crypto crypto) =>
Reward crypto -> [a]
toRewardPair
  toEncoding :: Reward crypto -> Encoding
toEncoding = Series -> Encoding
Aeson.pairs (Series -> Encoding)
-> (Reward crypto -> Series) -> Reward crypto -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Series] -> Series
forall a. Monoid a => [a] -> a
mconcat ([Series] -> Series)
-> (Reward crypto -> [Series]) -> Reward crypto -> Series
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Reward crypto -> [Series]
forall a crypto.
(KeyValue a, Crypto crypto) =>
Reward crypto -> [a]
toRewardPair

toRewardPair ::
  ( Aeson.KeyValue a
  , Crypto.Crypto crypto
  ) => Shelley.Reward crypto -> [a]
toRewardPair :: Reward crypto -> [a]
toRewardPair Reward crypto
reward =
  let !rewardType :: RewardType
rewardType = Reward crypto -> RewardType
forall crypto. Reward crypto -> RewardType
Shelley.rewardType Reward crypto
reward
      !rewardPool :: KeyHash 'StakePool crypto
rewardPool = Reward crypto -> KeyHash 'StakePool crypto
forall crypto. Reward crypto -> KeyHash 'StakePool crypto
Shelley.rewardPool Reward crypto
reward
      !rewardAmount :: Coin
rewardAmount = Reward crypto -> Coin
forall crypto. Reward crypto -> Coin
Shelley.rewardAmount Reward crypto
reward
  in  [ Key
"rewardType" Key -> RewardType -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= RewardType
rewardType
      , Key
"rewardPool" Key -> KeyHash 'StakePool crypto -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= KeyHash 'StakePool crypto
rewardPool
      , Key
"rewardAmount" Key -> Coin -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Coin
rewardAmount
      ]

instance ToJSON Shelley.RewardType where
  toJSON :: RewardType -> Value
toJSON RewardType
Shelley.MemberReward = Value
"MemberReward"
  toJSON RewardType
Shelley.LeaderReward = Value
"LeaderReward"

instance Crypto.Crypto c => ToJSON (SafeHash.SafeHash c a) where
  toJSON :: SafeHash c a -> Value
toJSON = Hash (HASH c) a -> Value
forall a. ToJSON a => a -> Value
toJSON (Hash (HASH c) a -> Value)
-> (SafeHash c a -> Hash (HASH c) a) -> SafeHash c a -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SafeHash c a -> Hash (HASH c) a
forall crypto i. SafeHash crypto i -> Hash (HASH crypto) i
SafeHash.extractHash
  toEncoding :: SafeHash c a -> Encoding
toEncoding = Hash (HASH c) a -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding (Hash (HASH c) a -> Encoding)
-> (SafeHash c a -> Hash (HASH c) a) -> SafeHash c a -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SafeHash c a -> Hash (HASH c) a
forall crypto i. SafeHash crypto i -> Hash (HASH crypto) i
SafeHash.extractHash

-----

deriving newtype instance ToJSON SystemStart
deriving newtype instance FromJSON SystemStart


instance Crypto.Crypto crypto => ToJSON (VMap VB VB (Shelley.Credential 'Shelley.Staking crypto) (Shelley.KeyHash 'Shelley.StakePool crypto)) where
  toJSON :: VMap VB VB (Credential 'Staking crypto) (KeyHash 'StakePool crypto)
-> Value
toJSON = Map (Credential 'Staking crypto) (KeyHash 'StakePool crypto)
-> Value
forall a. ToJSON a => a -> Value
toJSON (Map (Credential 'Staking crypto) (KeyHash 'StakePool crypto)
 -> Value)
-> (VMap
      VB VB (Credential 'Staking crypto) (KeyHash 'StakePool crypto)
    -> Map (Credential 'Staking crypto) (KeyHash 'StakePool crypto))
-> VMap
     VB VB (Credential 'Staking crypto) (KeyHash 'StakePool crypto)
-> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VMap VB VB (Credential 'Staking crypto) (KeyHash 'StakePool crypto)
-> Map (Credential 'Staking crypto) (KeyHash 'StakePool crypto)
forall (kv :: * -> *) k (vv :: * -> *) v.
(Vector kv k, Vector vv v) =>
VMap kv vv k v -> Map k v
VMap.toMap
  toEncoding :: VMap VB VB (Credential 'Staking crypto) (KeyHash 'StakePool crypto)
-> Encoding
toEncoding = Map (Credential 'Staking crypto) (KeyHash 'StakePool crypto)
-> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding (Map (Credential 'Staking crypto) (KeyHash 'StakePool crypto)
 -> Encoding)
-> (VMap
      VB VB (Credential 'Staking crypto) (KeyHash 'StakePool crypto)
    -> Map (Credential 'Staking crypto) (KeyHash 'StakePool crypto))
-> VMap
     VB VB (Credential 'Staking crypto) (KeyHash 'StakePool crypto)
-> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VMap VB VB (Credential 'Staking crypto) (KeyHash 'StakePool crypto)
-> Map (Credential 'Staking crypto) (KeyHash 'StakePool crypto)
forall (kv :: * -> *) k (vv :: * -> *) v.
(Vector kv k, Vector vv v) =>
VMap kv vv k v -> Map k v
VMap.toMap

instance Crypto.Crypto crypto => ToJSON (VMap VB VB (Shelley.KeyHash    'Shelley.StakePool crypto) (Shelley.PoolParams crypto)) where
  toJSON :: VMap VB VB (KeyHash 'StakePool crypto) (PoolParams crypto) -> Value
toJSON = Map (KeyHash 'StakePool crypto) (PoolParams crypto) -> Value
forall a. ToJSON a => a -> Value
toJSON (Map (KeyHash 'StakePool crypto) (PoolParams crypto) -> Value)
-> (VMap VB VB (KeyHash 'StakePool crypto) (PoolParams crypto)
    -> Map (KeyHash 'StakePool crypto) (PoolParams crypto))
-> VMap VB VB (KeyHash 'StakePool crypto) (PoolParams crypto)
-> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VMap VB VB (KeyHash 'StakePool crypto) (PoolParams crypto)
-> Map (KeyHash 'StakePool crypto) (PoolParams crypto)
forall (kv :: * -> *) k (vv :: * -> *) v.
(Vector kv k, Vector vv v) =>
VMap kv vv k v -> Map k v
VMap.toMap
  toEncoding :: VMap VB VB (KeyHash 'StakePool crypto) (PoolParams crypto)
-> Encoding
toEncoding = Map (KeyHash 'StakePool crypto) (PoolParams crypto) -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding (Map (KeyHash 'StakePool crypto) (PoolParams crypto) -> Encoding)
-> (VMap VB VB (KeyHash 'StakePool crypto) (PoolParams crypto)
    -> Map (KeyHash 'StakePool crypto) (PoolParams crypto))
-> VMap VB VB (KeyHash 'StakePool crypto) (PoolParams crypto)
-> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VMap VB VB (KeyHash 'StakePool crypto) (PoolParams crypto)
-> Map (KeyHash 'StakePool crypto) (PoolParams crypto)
forall (kv :: * -> *) k (vv :: * -> *) v.
(Vector kv k, Vector vv v) =>
VMap kv vv k v -> Map k v
VMap.toMap

instance Crypto.Crypto crypto => ToJSON (VMap VB VP (Shelley.Credential 'Shelley.Staking   crypto) (Shelley.CompactForm Shelley.Coin)) where
  toJSON :: VMap VB VP (Credential 'Staking crypto) (CompactForm Coin) -> Value
toJSON = Map (Credential 'Staking crypto) Coin -> Value
forall a. ToJSON a => a -> Value
toJSON (Map (Credential 'Staking crypto) Coin -> Value)
-> (VMap VB VP (Credential 'Staking crypto) (CompactForm Coin)
    -> Map (Credential 'Staking crypto) Coin)
-> VMap VB VP (Credential 'Staking crypto) (CompactForm Coin)
-> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CompactForm Coin -> Coin)
-> Map (Credential 'Staking crypto) (CompactForm Coin)
-> Map (Credential 'Staking crypto) Coin
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CompactForm Coin -> Coin
forall a. Compactible a => CompactForm a -> a
fromCompact (Map (Credential 'Staking crypto) (CompactForm Coin)
 -> Map (Credential 'Staking crypto) Coin)
-> (VMap VB VP (Credential 'Staking crypto) (CompactForm Coin)
    -> Map (Credential 'Staking crypto) (CompactForm Coin))
-> VMap VB VP (Credential 'Staking crypto) (CompactForm Coin)
-> Map (Credential 'Staking crypto) Coin
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VMap VB VP (Credential 'Staking crypto) (CompactForm Coin)
-> Map (Credential 'Staking crypto) (CompactForm Coin)
forall (kv :: * -> *) k (vv :: * -> *) v.
(Vector kv k, Vector vv v) =>
VMap kv vv k v -> Map k v
VMap.toMap
  toEncoding :: VMap VB VP (Credential 'Staking crypto) (CompactForm Coin)
-> Encoding
toEncoding = Map (Credential 'Staking crypto) Coin -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding (Map (Credential 'Staking crypto) Coin -> Encoding)
-> (VMap VB VP (Credential 'Staking crypto) (CompactForm Coin)
    -> Map (Credential 'Staking crypto) Coin)
-> VMap VB VP (Credential 'Staking crypto) (CompactForm Coin)
-> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CompactForm Coin -> Coin)
-> Map (Credential 'Staking crypto) (CompactForm Coin)
-> Map (Credential 'Staking crypto) Coin
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CompactForm Coin -> Coin
forall a. Compactible a => CompactForm a -> a
fromCompact (Map (Credential 'Staking crypto) (CompactForm Coin)
 -> Map (Credential 'Staking crypto) Coin)
-> (VMap VB VP (Credential 'Staking crypto) (CompactForm Coin)
    -> Map (Credential 'Staking crypto) (CompactForm Coin))
-> VMap VB VP (Credential 'Staking crypto) (CompactForm Coin)
-> Map (Credential 'Staking crypto) Coin
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VMap VB VP (Credential 'Staking crypto) (CompactForm Coin)
-> Map (Credential 'Staking crypto) (CompactForm Coin)
forall (kv :: * -> *) k (vv :: * -> *) v.
(Vector kv k, Vector vv v) =>
VMap kv vv k v -> Map k v
VMap.toMap