{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE NumericUnderscores #-}
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Cardano.Wallet.Primitive.Types
(
Block(..)
, BlockHeader(..)
, isGenesisBlockHeader
, ChainPoint (..)
, compareSlot
, chainPointFromBlockHeader
, Slot
, WithOrigin (..)
, toSlot
, CertificatePublicationTime (..)
, DelegationCertificate (..)
, dlgCertAccount
, dlgCertPoolId
, PoolLifeCycleStatus (..)
, PoolRegistrationCertificate (..)
, PoolRetirementCertificate (..)
, PoolCertificate (..)
, getPoolCertificatePoolId
, setPoolCertificatePoolId
, getPoolRegistrationCertificate
, getPoolRetirementCertificate
, NonWalletCertificate (..)
, Certificate (..)
, NetworkParameters (..)
, GenesisParameters (..)
, SlottingParameters (..)
, ProtocolParameters (..)
, TxParameters (..)
, TokenBundleMaxSize (..)
, EraInfo (..)
, emptyEraInfo
, ActiveSlotCoefficient (..)
, DecentralizationLevel
, getDecentralizationLevel
, getFederationPercentage
, fromDecentralizationLevel
, fromFederationPercentage
, EpochLength (..)
, EpochNo (..)
, unsafeEpochNo
, isValidEpochNo
, FeePolicy (..)
, LinearFunction (..)
, SlotId (..)
, SlotNo (..)
, SlotLength (..)
, SlotInEpoch (..)
, StartTime (..)
, stabilityWindowByron
, stabilityWindowShelley
, ExecutionUnits (..)
, ExecutionUnitPrices (..)
, WalletMetadata(..)
, WalletId(..)
, WalletName(..)
, walletNameMinLength
, walletNameMaxLength
, WalletDelegation (..)
, WalletDelegationStatus (..)
, WalletDelegationNext (..)
, IsDelegatingTo (..)
, StakePoolsSummary (..)
, PoolId(..)
, PoolOwner(..)
, poolIdBytesLength
, decodePoolIdBech32
, encodePoolIdBech32
, StakePoolMetadata (..)
, StakePoolMetadataHash (..)
, StakePoolMetadataUrl (..)
, StakePoolTicker (..)
, StakeKeyCertificate (..)
, PoolMetadataGCStatus (..)
, SortOrder (..)
, Range (..)
, RangeBound (..)
, wholeRange
, isAfterRange
, isBeforeRange
, isSubrangeOf
, isWithinRange
, mapRangeLowerBound
, mapRangeUpperBound
, rangeIsFinite
, rangeIsSingleton
, rangeIsValid
, rangeHasLowerBound
, rangeHasUpperBound
, rangeLowerBound
, rangeUpperBound
, Signature (..)
, Settings(..)
, SmashServer
, unSmashServer
, PoolMetadataSource( .. )
, defaultSettings
, unsafeToPMS
, TokenMetadataServer (..)
, InternalState (..)
, defaultInternalState
) where
import Prelude
import Cardano.Slotting.Slot
( SlotNo (..), WithOrigin (..) )
import Cardano.Wallet.Orphans
()
import Cardano.Wallet.Primitive.Passphrase.Types
( WalletPassphraseInfo (..) )
import Cardano.Wallet.Primitive.Types.Coin
( Coin (..) )
import Cardano.Wallet.Primitive.Types.Hash
( Hash (..), hashFromText )
import Cardano.Wallet.Primitive.Types.MinimumUTxO
( MinimumUTxO )
import Cardano.Wallet.Primitive.Types.RewardAccount
( RewardAccount (..) )
import Cardano.Wallet.Primitive.Types.Tx
( Tx (..), TxSize (..) )
import Cardano.Wallet.Util
( ShowFmt (..), parseURI, uriToText )
import Control.Arrow
( left, right )
import Control.DeepSeq
( NFData (..) )
import Control.Monad
( when, (<=<), (>=>) )
import Crypto.Hash
( Blake2b_160, Digest, digestFromByteString )
import Data.Aeson
( FromJSON (..)
, ToJSON (..)
, Value
, object
, withObject
, (.:)
, (.:?)
, (.=)
)
import Data.ByteArray
( ByteArrayAccess )
import Data.ByteArray.Encoding
( Base (Base16), convertFromBase, convertToBase )
import Data.ByteString
( ByteString )
import Data.Generics.Internal.VL.Lens
( set, view, (^.) )
import Data.Generics.Labels
()
import Data.Kind
( Type )
import Data.List
( intercalate )
import Data.Map.Strict
( Map )
import Data.Maybe
( isJust, isNothing )
import Data.Quantity
( Percentage (..), Quantity (..), complementPercentage )
import Data.Scientific
( fromRationalRepetendLimited )
import Data.String
( fromString )
import Data.Text
( Text )
import Data.Text.Class
( CaseStyle (..)
, FromText (..)
, TextDecodingError (..)
, ToText (..)
, fromTextToBoundedEnum
, toTextFromBoundedEnum
)
import Data.Time.Clock
( NominalDiffTime, UTCTime )
import Data.Time.Clock.POSIX
( POSIXTime )
import Data.Time.Format
( defaultTimeLocale, formatTime )
import Data.Word
( Word16, Word32, Word64 )
import Data.Word.Odd
( Word31 )
import Fmt
( Buildable (..)
, blockListF
, blockListF'
, indentF
, listF'
, mapF
, prefixF
, pretty
, suffixF
)
import GHC.Generics
( Generic )
import GHC.Stack
( HasCallStack )
import Network.URI
( URI (..), uriToString )
import NoThunks.Class
( NoThunks )
import Numeric.Natural
( Natural )
import Test.QuickCheck
( Arbitrary (..), oneof )
import qualified Cardano.Api.Shelley as Node
import qualified Codec.Binary.Bech32 as Bech32
import qualified Codec.Binary.Bech32.TH as Bech32
import qualified Data.ByteString as BS
import qualified Data.Map.Strict as Map
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
data WalletMetadata = WalletMetadata
{ WalletMetadata -> WalletName
name
:: !WalletName
, WalletMetadata -> UTCTime
creationTime
:: !UTCTime
, WalletMetadata -> Maybe WalletPassphraseInfo
passphraseInfo
:: !(Maybe WalletPassphraseInfo)
, WalletMetadata -> WalletDelegation
delegation
:: !WalletDelegation
} deriving (WalletMetadata -> WalletMetadata -> Bool
(WalletMetadata -> WalletMetadata -> Bool)
-> (WalletMetadata -> WalletMetadata -> Bool) -> Eq WalletMetadata
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WalletMetadata -> WalletMetadata -> Bool
$c/= :: WalletMetadata -> WalletMetadata -> Bool
== :: WalletMetadata -> WalletMetadata -> Bool
$c== :: WalletMetadata -> WalletMetadata -> Bool
Eq, Int -> WalletMetadata -> ShowS
[WalletMetadata] -> ShowS
WalletMetadata -> String
(Int -> WalletMetadata -> ShowS)
-> (WalletMetadata -> String)
-> ([WalletMetadata] -> ShowS)
-> Show WalletMetadata
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WalletMetadata] -> ShowS
$cshowList :: [WalletMetadata] -> ShowS
show :: WalletMetadata -> String
$cshow :: WalletMetadata -> String
showsPrec :: Int -> WalletMetadata -> ShowS
$cshowsPrec :: Int -> WalletMetadata -> ShowS
Show, (forall x. WalletMetadata -> Rep WalletMetadata x)
-> (forall x. Rep WalletMetadata x -> WalletMetadata)
-> Generic WalletMetadata
forall x. Rep WalletMetadata x -> WalletMetadata
forall x. WalletMetadata -> Rep WalletMetadata x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WalletMetadata x -> WalletMetadata
$cfrom :: forall x. WalletMetadata -> Rep WalletMetadata x
Generic)
instance NFData WalletMetadata
formatUTCTime :: UTCTime -> Text
formatUTCTime :: UTCTime -> Text
formatUTCTime =
String -> Text
T.pack (String -> Text) -> (UTCTime -> String) -> UTCTime -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TimeLocale -> String -> UTCTime -> String
forall t. FormatTime t => TimeLocale -> String -> t -> String
formatTime TimeLocale
defaultTimeLocale String
"%Y-%m-%d %H:%M:%S %Z"
instance Buildable WalletMetadata where
build :: WalletMetadata -> Builder
build (WalletMetadata WalletName
wName UTCTime
wTime Maybe WalletPassphraseInfo
_ WalletDelegation
wDelegation) = Builder
forall a. Monoid a => a
mempty
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> WalletName -> Builder
forall p. Buildable p => p -> Builder
build WalletName
wName Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
", "
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
"created at " Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Text -> Builder
forall p. Buildable p => p -> Builder
build (UTCTime -> Text
formatUTCTime UTCTime
wTime) Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
", "
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> WalletDelegation -> Builder
forall p. Buildable p => p -> Builder
build WalletDelegation
wDelegation
newtype WalletName = WalletName { WalletName -> Text
getWalletName :: Text }
deriving ((forall x. WalletName -> Rep WalletName x)
-> (forall x. Rep WalletName x -> WalletName) -> Generic WalletName
forall x. Rep WalletName x -> WalletName
forall x. WalletName -> Rep WalletName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WalletName x -> WalletName
$cfrom :: forall x. WalletName -> Rep WalletName x
Generic, WalletName -> WalletName -> Bool
(WalletName -> WalletName -> Bool)
-> (WalletName -> WalletName -> Bool) -> Eq WalletName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WalletName -> WalletName -> Bool
$c/= :: WalletName -> WalletName -> Bool
== :: WalletName -> WalletName -> Bool
$c== :: WalletName -> WalletName -> Bool
Eq, Int -> WalletName -> ShowS
[WalletName] -> ShowS
WalletName -> String
(Int -> WalletName -> ShowS)
-> (WalletName -> String)
-> ([WalletName] -> ShowS)
-> Show WalletName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WalletName] -> ShowS
$cshowList :: [WalletName] -> ShowS
show :: WalletName -> String
$cshow :: WalletName -> String
showsPrec :: Int -> WalletName -> ShowS
$cshowsPrec :: Int -> WalletName -> ShowS
Show)
instance NFData WalletName
instance FromText WalletName where
fromText :: Text -> Either TextDecodingError WalletName
fromText Text
t
| Text -> Int
T.length Text
t Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
walletNameMinLength =
TextDecodingError -> Either TextDecodingError WalletName
forall a b. a -> Either a b
Left (TextDecodingError -> Either TextDecodingError WalletName)
-> TextDecodingError -> Either TextDecodingError WalletName
forall a b. (a -> b) -> a -> b
$ String -> TextDecodingError
TextDecodingError (String -> TextDecodingError) -> String -> TextDecodingError
forall a b. (a -> b) -> a -> b
$
String
"name is too short: expected at least "
String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Int -> String
forall a. Show a => a -> String
show Int
walletNameMinLength String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" character"
| Text -> Int
T.length Text
t Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
walletNameMaxLength =
TextDecodingError -> Either TextDecodingError WalletName
forall a b. a -> Either a b
Left (TextDecodingError -> Either TextDecodingError WalletName)
-> TextDecodingError -> Either TextDecodingError WalletName
forall a b. (a -> b) -> a -> b
$ String -> TextDecodingError
TextDecodingError (String -> TextDecodingError) -> String -> TextDecodingError
forall a b. (a -> b) -> a -> b
$
String
"name is too long: expected at most "
String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Int -> String
forall a. Show a => a -> String
show Int
walletNameMaxLength String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" characters"
| Bool
otherwise =
WalletName -> Either TextDecodingError WalletName
forall (m :: * -> *) a. Monad m => a -> m a
return (WalletName -> Either TextDecodingError WalletName)
-> WalletName -> Either TextDecodingError WalletName
forall a b. (a -> b) -> a -> b
$ Text -> WalletName
WalletName Text
t
instance ToText WalletName where
toText :: WalletName -> Text
toText = WalletName -> Text
getWalletName
instance Buildable WalletName where
build :: WalletName -> Builder
build = Text -> Builder
forall p. Buildable p => p -> Builder
build (Text -> Builder) -> (WalletName -> Text) -> WalletName -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WalletName -> Text
forall a. ToText a => a -> Text
toText
walletNameMinLength :: Int
walletNameMinLength :: Int
walletNameMinLength = Int
1
walletNameMaxLength :: Int
walletNameMaxLength :: Int
walletNameMaxLength = Int
255
newtype WalletId = WalletId { WalletId -> Digest Blake2b_160
getWalletId :: Digest Blake2b_160 }
deriving ((forall x. WalletId -> Rep WalletId x)
-> (forall x. Rep WalletId x -> WalletId) -> Generic WalletId
forall x. Rep WalletId x -> WalletId
forall x. WalletId -> Rep WalletId x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WalletId x -> WalletId
$cfrom :: forall x. WalletId -> Rep WalletId x
Generic, WalletId -> WalletId -> Bool
(WalletId -> WalletId -> Bool)
-> (WalletId -> WalletId -> Bool) -> Eq WalletId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WalletId -> WalletId -> Bool
$c/= :: WalletId -> WalletId -> Bool
== :: WalletId -> WalletId -> Bool
$c== :: WalletId -> WalletId -> Bool
Eq, Eq WalletId
Eq WalletId
-> (WalletId -> WalletId -> Ordering)
-> (WalletId -> WalletId -> Bool)
-> (WalletId -> WalletId -> Bool)
-> (WalletId -> WalletId -> Bool)
-> (WalletId -> WalletId -> Bool)
-> (WalletId -> WalletId -> WalletId)
-> (WalletId -> WalletId -> WalletId)
-> Ord WalletId
WalletId -> WalletId -> Bool
WalletId -> WalletId -> Ordering
WalletId -> WalletId -> WalletId
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WalletId -> WalletId -> WalletId
$cmin :: WalletId -> WalletId -> WalletId
max :: WalletId -> WalletId -> WalletId
$cmax :: WalletId -> WalletId -> WalletId
>= :: WalletId -> WalletId -> Bool
$c>= :: WalletId -> WalletId -> Bool
> :: WalletId -> WalletId -> Bool
$c> :: WalletId -> WalletId -> Bool
<= :: WalletId -> WalletId -> Bool
$c<= :: WalletId -> WalletId -> Bool
< :: WalletId -> WalletId -> Bool
$c< :: WalletId -> WalletId -> Bool
compare :: WalletId -> WalletId -> Ordering
$ccompare :: WalletId -> WalletId -> Ordering
$cp1Ord :: Eq WalletId
Ord, Int -> WalletId -> ShowS
[WalletId] -> ShowS
WalletId -> String
(Int -> WalletId -> ShowS)
-> (WalletId -> String) -> ([WalletId] -> ShowS) -> Show WalletId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WalletId] -> ShowS
$cshowList :: [WalletId] -> ShowS
show :: WalletId -> String
$cshow :: WalletId -> String
showsPrec :: Int -> WalletId -> ShowS
$cshowsPrec :: Int -> WalletId -> ShowS
Show)
instance NFData WalletId
instance FromText WalletId where
fromText :: Text -> Either TextDecodingError WalletId
fromText Text
txt = Either TextDecodingError WalletId
-> (Digest Blake2b_160 -> Either TextDecodingError WalletId)
-> Maybe (Digest Blake2b_160)
-> Either TextDecodingError WalletId
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
(TextDecodingError -> Either TextDecodingError WalletId
forall a b. a -> Either a b
Left (TextDecodingError -> Either TextDecodingError WalletId)
-> TextDecodingError -> Either TextDecodingError WalletId
forall a b. (a -> b) -> a -> b
$ String -> TextDecodingError
TextDecodingError String
msg)
(WalletId -> Either TextDecodingError WalletId
forall a b. b -> Either a b
Right (WalletId -> Either TextDecodingError WalletId)
-> (Digest Blake2b_160 -> WalletId)
-> Digest Blake2b_160
-> Either TextDecodingError WalletId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Digest Blake2b_160 -> WalletId
WalletId)
(Text -> Maybe ByteString
decodeHex Text
txt Maybe ByteString
-> (ByteString -> Maybe (Digest Blake2b_160))
-> Maybe (Digest Blake2b_160)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (HashAlgorithm Blake2b_160, ByteArrayAccess ByteString) =>
ByteString -> Maybe (Digest Blake2b_160)
forall a ba.
(HashAlgorithm a, ByteArrayAccess ba) =>
ba -> Maybe (Digest a)
digestFromByteString @_ @ByteString)
where
msg :: String
msg = String
"wallet id should be a hex-encoded string of 40 characters"
decodeHex :: Text -> Maybe ByteString
decodeHex =
(String -> Maybe ByteString)
-> (ByteString -> Maybe ByteString)
-> Either String ByteString
-> Maybe ByteString
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe ByteString -> String -> Maybe ByteString
forall a b. a -> b -> a
const Maybe ByteString
forall a. Maybe a
Nothing) ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (Either String ByteString -> Maybe ByteString)
-> (Text -> Either String ByteString) -> Text -> Maybe ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Base -> ByteString -> Either String ByteString
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
Base -> bin -> Either String bout
convertFromBase Base
Base16 (ByteString -> Either String ByteString)
-> (Text -> ByteString) -> Text -> Either String ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
T.encodeUtf8
instance ToText WalletId where
toText :: WalletId -> Text
toText = ByteString -> Text
T.decodeUtf8 (ByteString -> Text)
-> (WalletId -> ByteString) -> WalletId -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Base -> Digest Blake2b_160 -> ByteString
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
Base -> bin -> bout
convertToBase Base
Base16 (Digest Blake2b_160 -> ByteString)
-> (WalletId -> Digest Blake2b_160) -> WalletId -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WalletId -> Digest Blake2b_160
getWalletId
instance Buildable WalletId where
build :: WalletId -> Builder
build WalletId
wid = Int -> Text -> Builder
forall a. Buildable a => Int -> a -> Builder
prefixF Int
8 Text
widF Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
"..." Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Int -> Text -> Builder
forall a. Buildable a => Int -> a -> Builder
suffixF Int
8 Text
widF
where
widF :: Text
widF = WalletId -> Text
forall a. ToText a => a -> Text
toText WalletId
wid
data WalletDelegationStatus
= NotDelegating
| Delegating !PoolId
deriving ((forall x. WalletDelegationStatus -> Rep WalletDelegationStatus x)
-> (forall x.
Rep WalletDelegationStatus x -> WalletDelegationStatus)
-> Generic WalletDelegationStatus
forall x. Rep WalletDelegationStatus x -> WalletDelegationStatus
forall x. WalletDelegationStatus -> Rep WalletDelegationStatus x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WalletDelegationStatus x -> WalletDelegationStatus
$cfrom :: forall x. WalletDelegationStatus -> Rep WalletDelegationStatus x
Generic, WalletDelegationStatus -> WalletDelegationStatus -> Bool
(WalletDelegationStatus -> WalletDelegationStatus -> Bool)
-> (WalletDelegationStatus -> WalletDelegationStatus -> Bool)
-> Eq WalletDelegationStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WalletDelegationStatus -> WalletDelegationStatus -> Bool
$c/= :: WalletDelegationStatus -> WalletDelegationStatus -> Bool
== :: WalletDelegationStatus -> WalletDelegationStatus -> Bool
$c== :: WalletDelegationStatus -> WalletDelegationStatus -> Bool
Eq, Int -> WalletDelegationStatus -> ShowS
[WalletDelegationStatus] -> ShowS
WalletDelegationStatus -> String
(Int -> WalletDelegationStatus -> ShowS)
-> (WalletDelegationStatus -> String)
-> ([WalletDelegationStatus] -> ShowS)
-> Show WalletDelegationStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WalletDelegationStatus] -> ShowS
$cshowList :: [WalletDelegationStatus] -> ShowS
show :: WalletDelegationStatus -> String
$cshow :: WalletDelegationStatus -> String
showsPrec :: Int -> WalletDelegationStatus -> ShowS
$cshowsPrec :: Int -> WalletDelegationStatus -> ShowS
Show)
instance NFData WalletDelegationStatus
instance Buildable WalletDelegationStatus where
build :: WalletDelegationStatus -> Builder
build = \case
WalletDelegationStatus
NotDelegating -> Builder
"∅"
Delegating PoolId
poolId -> PoolId -> Builder
forall p. Buildable p => p -> Builder
build PoolId
poolId
data WalletDelegationNext = WalletDelegationNext
{ WalletDelegationNext -> EpochNo
changesAt :: !EpochNo
, WalletDelegationNext -> WalletDelegationStatus
status :: !WalletDelegationStatus
} deriving (WalletDelegationNext -> WalletDelegationNext -> Bool
(WalletDelegationNext -> WalletDelegationNext -> Bool)
-> (WalletDelegationNext -> WalletDelegationNext -> Bool)
-> Eq WalletDelegationNext
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WalletDelegationNext -> WalletDelegationNext -> Bool
$c/= :: WalletDelegationNext -> WalletDelegationNext -> Bool
== :: WalletDelegationNext -> WalletDelegationNext -> Bool
$c== :: WalletDelegationNext -> WalletDelegationNext -> Bool
Eq, (forall x. WalletDelegationNext -> Rep WalletDelegationNext x)
-> (forall x. Rep WalletDelegationNext x -> WalletDelegationNext)
-> Generic WalletDelegationNext
forall x. Rep WalletDelegationNext x -> WalletDelegationNext
forall x. WalletDelegationNext -> Rep WalletDelegationNext x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WalletDelegationNext x -> WalletDelegationNext
$cfrom :: forall x. WalletDelegationNext -> Rep WalletDelegationNext x
Generic, Int -> WalletDelegationNext -> ShowS
[WalletDelegationNext] -> ShowS
WalletDelegationNext -> String
(Int -> WalletDelegationNext -> ShowS)
-> (WalletDelegationNext -> String)
-> ([WalletDelegationNext] -> ShowS)
-> Show WalletDelegationNext
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WalletDelegationNext] -> ShowS
$cshowList :: [WalletDelegationNext] -> ShowS
show :: WalletDelegationNext -> String
$cshow :: WalletDelegationNext -> String
showsPrec :: Int -> WalletDelegationNext -> ShowS
$cshowsPrec :: Int -> WalletDelegationNext -> ShowS
Show)
instance NFData WalletDelegationNext
instance Buildable WalletDelegationNext where
build :: WalletDelegationNext -> Builder
build (WalletDelegationNext EpochNo
e WalletDelegationStatus
st) =
WalletDelegationStatus -> Builder
forall p. Buildable p => p -> Builder
build WalletDelegationStatus
st Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
" (in epoch: " Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> EpochNo -> Builder
forall p. Buildable p => p -> Builder
build EpochNo
e Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
")"
data WalletDelegation = WalletDelegation
{ WalletDelegation -> WalletDelegationStatus
active :: !WalletDelegationStatus
, WalletDelegation -> [WalletDelegationNext]
next :: ![WalletDelegationNext]
} deriving (WalletDelegation -> WalletDelegation -> Bool
(WalletDelegation -> WalletDelegation -> Bool)
-> (WalletDelegation -> WalletDelegation -> Bool)
-> Eq WalletDelegation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WalletDelegation -> WalletDelegation -> Bool
$c/= :: WalletDelegation -> WalletDelegation -> Bool
== :: WalletDelegation -> WalletDelegation -> Bool
$c== :: WalletDelegation -> WalletDelegation -> Bool
Eq, (forall x. WalletDelegation -> Rep WalletDelegation x)
-> (forall x. Rep WalletDelegation x -> WalletDelegation)
-> Generic WalletDelegation
forall x. Rep WalletDelegation x -> WalletDelegation
forall x. WalletDelegation -> Rep WalletDelegation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WalletDelegation x -> WalletDelegation
$cfrom :: forall x. WalletDelegation -> Rep WalletDelegation x
Generic, Int -> WalletDelegation -> ShowS
[WalletDelegation] -> ShowS
WalletDelegation -> String
(Int -> WalletDelegation -> ShowS)
-> (WalletDelegation -> String)
-> ([WalletDelegation] -> ShowS)
-> Show WalletDelegation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WalletDelegation] -> ShowS
$cshowList :: [WalletDelegation] -> ShowS
show :: WalletDelegation -> String
$cshow :: WalletDelegation -> String
showsPrec :: Int -> WalletDelegation -> ShowS
$cshowsPrec :: Int -> WalletDelegation -> ShowS
Show)
instance NFData WalletDelegation
instance Buildable WalletDelegation where
build :: WalletDelegation -> Builder
build (WalletDelegation WalletDelegationStatus
act []) =
Builder
"delegating to " Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> WalletDelegationStatus -> Builder
forall p. Buildable p => p -> Builder
build WalletDelegationStatus
act
build (WalletDelegation WalletDelegationStatus
act [WalletDelegationNext]
xs) =
WalletDelegation -> Builder
forall p. Buildable p => p -> Builder
build (WalletDelegationStatus
-> [WalletDelegationNext] -> WalletDelegation
WalletDelegation WalletDelegationStatus
act []) Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
" → "
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Text -> Builder
forall p. Buildable p => p -> Builder
build (Text -> [Text] -> Text
T.intercalate Text
" → " ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ WalletDelegationNext -> Text
forall a b. (Buildable a, FromBuilder b) => a -> b
pretty (WalletDelegationNext -> Text) -> [WalletDelegationNext] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [WalletDelegationNext]
xs)
class IsDelegatingTo a where
isDelegatingTo :: (PoolId -> Bool) -> a -> Bool
instance IsDelegatingTo WalletDelegationStatus where
isDelegatingTo :: (PoolId -> Bool) -> WalletDelegationStatus -> Bool
isDelegatingTo PoolId -> Bool
predicate = \case
Delegating PoolId
pid -> PoolId -> Bool
predicate PoolId
pid
WalletDelegationStatus
NotDelegating -> Bool
False
instance IsDelegatingTo WalletDelegationNext where
isDelegatingTo :: (PoolId -> Bool) -> WalletDelegationNext -> Bool
isDelegatingTo PoolId -> Bool
predicate WalletDelegationNext{WalletDelegationStatus
status :: WalletDelegationStatus
$sel:status:WalletDelegationNext :: WalletDelegationNext -> WalletDelegationStatus
status} =
(PoolId -> Bool) -> WalletDelegationStatus -> Bool
forall a. IsDelegatingTo a => (PoolId -> Bool) -> a -> Bool
isDelegatingTo PoolId -> Bool
predicate WalletDelegationStatus
status
instance IsDelegatingTo WalletDelegation where
isDelegatingTo :: (PoolId -> Bool) -> WalletDelegation -> Bool
isDelegatingTo PoolId -> Bool
predicate WalletDelegation{WalletDelegationStatus
active :: WalletDelegationStatus
$sel:active:WalletDelegation :: WalletDelegation -> WalletDelegationStatus
active,[WalletDelegationNext]
next :: [WalletDelegationNext]
$sel:next:WalletDelegation :: WalletDelegation -> [WalletDelegationNext]
next} =
(PoolId -> Bool) -> WalletDelegationStatus -> Bool
forall a. IsDelegatingTo a => (PoolId -> Bool) -> a -> Bool
isDelegatingTo PoolId -> Bool
predicate WalletDelegationStatus
active Bool -> Bool -> Bool
|| (WalletDelegationNext -> Bool) -> [WalletDelegationNext] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ((PoolId -> Bool) -> WalletDelegationNext -> Bool
forall a. IsDelegatingTo a => (PoolId -> Bool) -> a -> Bool
isDelegatingTo PoolId -> Bool
predicate) [WalletDelegationNext]
next
data SortOrder
= Ascending
| Descending
deriving (SortOrder
SortOrder -> SortOrder -> Bounded SortOrder
forall a. a -> a -> Bounded a
maxBound :: SortOrder
$cmaxBound :: SortOrder
minBound :: SortOrder
$cminBound :: SortOrder
Bounded, Int -> SortOrder
SortOrder -> Int
SortOrder -> [SortOrder]
SortOrder -> SortOrder
SortOrder -> SortOrder -> [SortOrder]
SortOrder -> SortOrder -> SortOrder -> [SortOrder]
(SortOrder -> SortOrder)
-> (SortOrder -> SortOrder)
-> (Int -> SortOrder)
-> (SortOrder -> Int)
-> (SortOrder -> [SortOrder])
-> (SortOrder -> SortOrder -> [SortOrder])
-> (SortOrder -> SortOrder -> [SortOrder])
-> (SortOrder -> SortOrder -> SortOrder -> [SortOrder])
-> Enum SortOrder
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: SortOrder -> SortOrder -> SortOrder -> [SortOrder]
$cenumFromThenTo :: SortOrder -> SortOrder -> SortOrder -> [SortOrder]
enumFromTo :: SortOrder -> SortOrder -> [SortOrder]
$cenumFromTo :: SortOrder -> SortOrder -> [SortOrder]
enumFromThen :: SortOrder -> SortOrder -> [SortOrder]
$cenumFromThen :: SortOrder -> SortOrder -> [SortOrder]
enumFrom :: SortOrder -> [SortOrder]
$cenumFrom :: SortOrder -> [SortOrder]
fromEnum :: SortOrder -> Int
$cfromEnum :: SortOrder -> Int
toEnum :: Int -> SortOrder
$ctoEnum :: Int -> SortOrder
pred :: SortOrder -> SortOrder
$cpred :: SortOrder -> SortOrder
succ :: SortOrder -> SortOrder
$csucc :: SortOrder -> SortOrder
Enum, SortOrder -> SortOrder -> Bool
(SortOrder -> SortOrder -> Bool)
-> (SortOrder -> SortOrder -> Bool) -> Eq SortOrder
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SortOrder -> SortOrder -> Bool
$c/= :: SortOrder -> SortOrder -> Bool
== :: SortOrder -> SortOrder -> Bool
$c== :: SortOrder -> SortOrder -> Bool
Eq, (forall x. SortOrder -> Rep SortOrder x)
-> (forall x. Rep SortOrder x -> SortOrder) -> Generic SortOrder
forall x. Rep SortOrder x -> SortOrder
forall x. SortOrder -> Rep SortOrder x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SortOrder x -> SortOrder
$cfrom :: forall x. SortOrder -> Rep SortOrder x
Generic, Int -> SortOrder -> ShowS
[SortOrder] -> ShowS
SortOrder -> String
(Int -> SortOrder -> ShowS)
-> (SortOrder -> String)
-> ([SortOrder] -> ShowS)
-> Show SortOrder
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SortOrder] -> ShowS
$cshowList :: [SortOrder] -> ShowS
show :: SortOrder -> String
$cshow :: SortOrder -> String
showsPrec :: Int -> SortOrder -> ShowS
$cshowsPrec :: Int -> SortOrder -> ShowS
Show)
instance ToText SortOrder where
toText :: SortOrder -> Text
toText = CaseStyle -> SortOrder -> Text
forall a. (Bounded a, Enum a, Show a) => CaseStyle -> a -> Text
toTextFromBoundedEnum CaseStyle
SnakeLowerCase
instance FromText SortOrder where
fromText :: Text -> Either TextDecodingError SortOrder
fromText = CaseStyle -> Text -> Either TextDecodingError SortOrder
forall a.
(Bounded a, Enum a, Show a) =>
CaseStyle -> Text -> Either TextDecodingError a
fromTextToBoundedEnum CaseStyle
SnakeLowerCase
data Range a = Range
{ Range a -> Maybe a
inclusiveLowerBound :: Maybe a
, Range a -> Maybe a
inclusiveUpperBound :: Maybe a
} deriving (Range a -> Range a -> Bool
(Range a -> Range a -> Bool)
-> (Range a -> Range a -> Bool) -> Eq (Range a)
forall a. Eq a => Range a -> Range a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Range a -> Range a -> Bool
$c/= :: forall a. Eq a => Range a -> Range a -> Bool
== :: Range a -> Range a -> Bool
$c== :: forall a. Eq a => Range a -> Range a -> Bool
Eq, a -> Range b -> Range a
(a -> b) -> Range a -> Range b
(forall a b. (a -> b) -> Range a -> Range b)
-> (forall a b. a -> Range b -> Range a) -> Functor Range
forall a b. a -> Range b -> Range a
forall a b. (a -> b) -> Range a -> Range b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Range b -> Range a
$c<$ :: forall a b. a -> Range b -> Range a
fmap :: (a -> b) -> Range a -> Range b
$cfmap :: forall a b. (a -> b) -> Range a -> Range b
Functor, Int -> Range a -> ShowS
[Range a] -> ShowS
Range a -> String
(Int -> Range a -> ShowS)
-> (Range a -> String) -> ([Range a] -> ShowS) -> Show (Range a)
forall a. Show a => Int -> Range a -> ShowS
forall a. Show a => [Range a] -> ShowS
forall a. Show a => Range a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Range a] -> ShowS
$cshowList :: forall a. Show a => [Range a] -> ShowS
show :: Range a -> String
$cshow :: forall a. Show a => Range a -> String
showsPrec :: Int -> Range a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Range a -> ShowS
Show)
mapRangeLowerBound :: (a -> a) -> Range a -> Range a
mapRangeLowerBound :: (a -> a) -> Range a -> Range a
mapRangeLowerBound a -> a
f (Range Maybe a
x Maybe a
y) = Maybe a -> Maybe a -> Range a
forall a. Maybe a -> Maybe a -> Range a
Range (a -> a
f (a -> a) -> Maybe a -> Maybe a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe a
x) Maybe a
y
mapRangeUpperBound :: (a -> a) -> Range a -> Range a
mapRangeUpperBound :: (a -> a) -> Range a -> Range a
mapRangeUpperBound a -> a
f (Range Maybe a
x Maybe a
y) = Maybe a -> Maybe a -> Range a
forall a. Maybe a -> Maybe a -> Range a
Range Maybe a
x (a -> a
f (a -> a) -> Maybe a -> Maybe a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe a
y)
data RangeBound a
= NegativeInfinity
| InclusiveBound a
| PositiveInfinity
deriving (RangeBound a -> RangeBound a -> Bool
(RangeBound a -> RangeBound a -> Bool)
-> (RangeBound a -> RangeBound a -> Bool) -> Eq (RangeBound a)
forall a. Eq a => RangeBound a -> RangeBound a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RangeBound a -> RangeBound a -> Bool
$c/= :: forall a. Eq a => RangeBound a -> RangeBound a -> Bool
== :: RangeBound a -> RangeBound a -> Bool
$c== :: forall a. Eq a => RangeBound a -> RangeBound a -> Bool
Eq, Eq (RangeBound a)
Eq (RangeBound a)
-> (RangeBound a -> RangeBound a -> Ordering)
-> (RangeBound a -> RangeBound a -> Bool)
-> (RangeBound a -> RangeBound a -> Bool)
-> (RangeBound a -> RangeBound a -> Bool)
-> (RangeBound a -> RangeBound a -> Bool)
-> (RangeBound a -> RangeBound a -> RangeBound a)
-> (RangeBound a -> RangeBound a -> RangeBound a)
-> Ord (RangeBound a)
RangeBound a -> RangeBound a -> Bool
RangeBound a -> RangeBound a -> Ordering
RangeBound a -> RangeBound a -> RangeBound a
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall a. Ord a => Eq (RangeBound a)
forall a. Ord a => RangeBound a -> RangeBound a -> Bool
forall a. Ord a => RangeBound a -> RangeBound a -> Ordering
forall a. Ord a => RangeBound a -> RangeBound a -> RangeBound a
min :: RangeBound a -> RangeBound a -> RangeBound a
$cmin :: forall a. Ord a => RangeBound a -> RangeBound a -> RangeBound a
max :: RangeBound a -> RangeBound a -> RangeBound a
$cmax :: forall a. Ord a => RangeBound a -> RangeBound a -> RangeBound a
>= :: RangeBound a -> RangeBound a -> Bool
$c>= :: forall a. Ord a => RangeBound a -> RangeBound a -> Bool
> :: RangeBound a -> RangeBound a -> Bool
$c> :: forall a. Ord a => RangeBound a -> RangeBound a -> Bool
<= :: RangeBound a -> RangeBound a -> Bool
$c<= :: forall a. Ord a => RangeBound a -> RangeBound a -> Bool
< :: RangeBound a -> RangeBound a -> Bool
$c< :: forall a. Ord a => RangeBound a -> RangeBound a -> Bool
compare :: RangeBound a -> RangeBound a -> Ordering
$ccompare :: forall a. Ord a => RangeBound a -> RangeBound a -> Ordering
$cp1Ord :: forall a. Ord a => Eq (RangeBound a)
Ord)
wholeRange :: Range a
wholeRange :: Range a
wholeRange = Maybe a -> Maybe a -> Range a
forall a. Maybe a -> Maybe a -> Range a
Range Maybe a
forall a. Maybe a
Nothing Maybe a
forall a. Maybe a
Nothing
isAfterRange :: Ord a => a -> Range a -> Bool
isAfterRange :: a -> Range a -> Bool
isAfterRange a
x (Range Maybe a
_ Maybe a
high) =
Bool -> (a -> Bool) -> Maybe a -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False (a
x a -> a -> Bool
forall a. Ord a => a -> a -> Bool
>) Maybe a
high
isBeforeRange :: Ord a => a -> Range a -> Bool
isBeforeRange :: a -> Range a -> Bool
isBeforeRange a
x (Range Maybe a
low Maybe a
_) =
Bool -> (a -> Bool) -> Maybe a -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False (a
x a -> a -> Bool
forall a. Ord a => a -> a -> Bool
<) Maybe a
low
isWithinRange :: Ord a => a -> Range a -> Bool
isWithinRange :: a -> Range a -> Bool
isWithinRange a
x (Range Maybe a
low Maybe a
high) =
(Bool -> (a -> Bool) -> Maybe a -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
True (a
x a -> a -> Bool
forall a. Ord a => a -> a -> Bool
>=) Maybe a
low) Bool -> Bool -> Bool
&&
(Bool -> (a -> Bool) -> Maybe a -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
True (a
x a -> a -> Bool
forall a. Ord a => a -> a -> Bool
<=) Maybe a
high)
rangeHasLowerBound :: Range a -> Bool
rangeHasLowerBound :: Range a -> Bool
rangeHasLowerBound = Maybe a -> Bool
forall a. Maybe a -> Bool
isJust (Maybe a -> Bool) -> (Range a -> Maybe a) -> Range a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Range a -> Maybe a
forall a. Range a -> Maybe a
inclusiveLowerBound
rangeHasUpperBound :: Range a -> Bool
rangeHasUpperBound :: Range a -> Bool
rangeHasUpperBound = Maybe a -> Bool
forall a. Maybe a -> Bool
isJust (Maybe a -> Bool) -> (Range a -> Maybe a) -> Range a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Range a -> Maybe a
forall a. Range a -> Maybe a
inclusiveUpperBound
rangeIsFinite :: Range a -> Bool
rangeIsFinite :: Range a -> Bool
rangeIsFinite Range a
r = Range a -> Bool
forall a. Range a -> Bool
rangeHasLowerBound Range a
r Bool -> Bool -> Bool
&& Range a -> Bool
forall a. Range a -> Bool
rangeHasUpperBound Range a
r
rangeIsSingleton :: Eq a => Range a -> Bool
rangeIsSingleton :: Range a -> Bool
rangeIsSingleton (Range Maybe a
a Maybe a
b) = (a -> a -> Bool
forall a. Eq a => a -> a -> Bool
(==) (a -> a -> Bool) -> Maybe a -> Maybe (a -> Bool)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe a
a Maybe (a -> Bool) -> Maybe a -> Maybe Bool
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe a
b) Maybe Bool -> Maybe Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True
rangeIsValid :: Ord a => Range a -> Bool
rangeIsValid :: Range a -> Bool
rangeIsValid (Range Maybe a
a Maybe a
b) = (a -> a -> Bool
forall a. Ord a => a -> a -> Bool
(<=) (a -> a -> Bool) -> Maybe a -> Maybe (a -> Bool)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe a
a Maybe (a -> Bool) -> Maybe a -> Maybe Bool
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe a
b) Maybe Bool -> Maybe Bool -> Bool
forall a. Eq a => a -> a -> Bool
/= Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
False
rangeLowerBound :: Range a -> RangeBound a
rangeLowerBound :: Range a -> RangeBound a
rangeLowerBound = RangeBound a -> (a -> RangeBound a) -> Maybe a -> RangeBound a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe RangeBound a
forall a. RangeBound a
NegativeInfinity a -> RangeBound a
forall a. a -> RangeBound a
InclusiveBound (Maybe a -> RangeBound a)
-> (Range a -> Maybe a) -> Range a -> RangeBound a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Range a -> Maybe a
forall a. Range a -> Maybe a
inclusiveLowerBound
rangeUpperBound :: Range a -> RangeBound a
rangeUpperBound :: Range a -> RangeBound a
rangeUpperBound = RangeBound a -> (a -> RangeBound a) -> Maybe a -> RangeBound a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe RangeBound a
forall a. RangeBound a
PositiveInfinity a -> RangeBound a
forall a. a -> RangeBound a
InclusiveBound (Maybe a -> RangeBound a)
-> (Range a -> Maybe a) -> Range a -> RangeBound a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Range a -> Maybe a
forall a. Range a -> Maybe a
inclusiveUpperBound
isSubrangeOf :: Ord a => Range a -> Range a -> Bool
isSubrangeOf :: Range a -> Range a -> Bool
isSubrangeOf Range a
r1 Range a
r2 =
Range a -> RangeBound a
forall a. Range a -> RangeBound a
rangeLowerBound Range a
r1 RangeBound a -> RangeBound a -> Bool
forall a. Ord a => a -> a -> Bool
>= Range a -> RangeBound a
forall a. Range a -> RangeBound a
rangeLowerBound Range a
r2 Bool -> Bool -> Bool
&&
Range a -> RangeBound a
forall a. Range a -> RangeBound a
rangeUpperBound Range a
r1 RangeBound a -> RangeBound a -> Bool
forall a. Ord a => a -> a -> Bool
<= Range a -> RangeBound a
forall a. Range a -> RangeBound a
rangeUpperBound Range a
r2
data PoolMetadataGCStatus
= NotApplicable
| NotStarted
| Restarting POSIXTime
| HasRun POSIXTime
deriving (PoolMetadataGCStatus -> PoolMetadataGCStatus -> Bool
(PoolMetadataGCStatus -> PoolMetadataGCStatus -> Bool)
-> (PoolMetadataGCStatus -> PoolMetadataGCStatus -> Bool)
-> Eq PoolMetadataGCStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PoolMetadataGCStatus -> PoolMetadataGCStatus -> Bool
$c/= :: PoolMetadataGCStatus -> PoolMetadataGCStatus -> Bool
== :: PoolMetadataGCStatus -> PoolMetadataGCStatus -> Bool
$c== :: PoolMetadataGCStatus -> PoolMetadataGCStatus -> Bool
Eq, Int -> PoolMetadataGCStatus -> ShowS
[PoolMetadataGCStatus] -> ShowS
PoolMetadataGCStatus -> String
(Int -> PoolMetadataGCStatus -> ShowS)
-> (PoolMetadataGCStatus -> String)
-> ([PoolMetadataGCStatus] -> ShowS)
-> Show PoolMetadataGCStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PoolMetadataGCStatus] -> ShowS
$cshowList :: [PoolMetadataGCStatus] -> ShowS
show :: PoolMetadataGCStatus -> String
$cshow :: PoolMetadataGCStatus -> String
showsPrec :: Int -> PoolMetadataGCStatus -> ShowS
$cshowsPrec :: Int -> PoolMetadataGCStatus -> ShowS
Show, (forall x. PoolMetadataGCStatus -> Rep PoolMetadataGCStatus x)
-> (forall x. Rep PoolMetadataGCStatus x -> PoolMetadataGCStatus)
-> Generic PoolMetadataGCStatus
forall x. Rep PoolMetadataGCStatus x -> PoolMetadataGCStatus
forall x. PoolMetadataGCStatus -> Rep PoolMetadataGCStatus x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PoolMetadataGCStatus x -> PoolMetadataGCStatus
$cfrom :: forall x. PoolMetadataGCStatus -> Rep PoolMetadataGCStatus x
Generic)
newtype StakePoolMetadataHash = StakePoolMetadataHash ByteString
deriving (StakePoolMetadataHash -> StakePoolMetadataHash -> Bool
(StakePoolMetadataHash -> StakePoolMetadataHash -> Bool)
-> (StakePoolMetadataHash -> StakePoolMetadataHash -> Bool)
-> Eq StakePoolMetadataHash
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StakePoolMetadataHash -> StakePoolMetadataHash -> Bool
$c/= :: StakePoolMetadataHash -> StakePoolMetadataHash -> Bool
== :: StakePoolMetadataHash -> StakePoolMetadataHash -> Bool
$c== :: StakePoolMetadataHash -> StakePoolMetadataHash -> Bool
Eq, Eq StakePoolMetadataHash
Eq StakePoolMetadataHash
-> (StakePoolMetadataHash -> StakePoolMetadataHash -> Ordering)
-> (StakePoolMetadataHash -> StakePoolMetadataHash -> Bool)
-> (StakePoolMetadataHash -> StakePoolMetadataHash -> Bool)
-> (StakePoolMetadataHash -> StakePoolMetadataHash -> Bool)
-> (StakePoolMetadataHash -> StakePoolMetadataHash -> Bool)
-> (StakePoolMetadataHash
-> StakePoolMetadataHash -> StakePoolMetadataHash)
-> (StakePoolMetadataHash
-> StakePoolMetadataHash -> StakePoolMetadataHash)
-> Ord StakePoolMetadataHash
StakePoolMetadataHash -> StakePoolMetadataHash -> Bool
StakePoolMetadataHash -> StakePoolMetadataHash -> Ordering
StakePoolMetadataHash
-> StakePoolMetadataHash -> StakePoolMetadataHash
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: StakePoolMetadataHash
-> StakePoolMetadataHash -> StakePoolMetadataHash
$cmin :: StakePoolMetadataHash
-> StakePoolMetadataHash -> StakePoolMetadataHash
max :: StakePoolMetadataHash
-> StakePoolMetadataHash -> StakePoolMetadataHash
$cmax :: StakePoolMetadataHash
-> StakePoolMetadataHash -> StakePoolMetadataHash
>= :: StakePoolMetadataHash -> StakePoolMetadataHash -> Bool
$c>= :: StakePoolMetadataHash -> StakePoolMetadataHash -> Bool
> :: StakePoolMetadataHash -> StakePoolMetadataHash -> Bool
$c> :: StakePoolMetadataHash -> StakePoolMetadataHash -> Bool
<= :: StakePoolMetadataHash -> StakePoolMetadataHash -> Bool
$c<= :: StakePoolMetadataHash -> StakePoolMetadataHash -> Bool
< :: StakePoolMetadataHash -> StakePoolMetadataHash -> Bool
$c< :: StakePoolMetadataHash -> StakePoolMetadataHash -> Bool
compare :: StakePoolMetadataHash -> StakePoolMetadataHash -> Ordering
$ccompare :: StakePoolMetadataHash -> StakePoolMetadataHash -> Ordering
$cp1Ord :: Eq StakePoolMetadataHash
Ord, Int -> StakePoolMetadataHash -> ShowS
[StakePoolMetadataHash] -> ShowS
StakePoolMetadataHash -> String
(Int -> StakePoolMetadataHash -> ShowS)
-> (StakePoolMetadataHash -> String)
-> ([StakePoolMetadataHash] -> ShowS)
-> Show StakePoolMetadataHash
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StakePoolMetadataHash] -> ShowS
$cshowList :: [StakePoolMetadataHash] -> ShowS
show :: StakePoolMetadataHash -> String
$cshow :: StakePoolMetadataHash -> String
showsPrec :: Int -> StakePoolMetadataHash -> ShowS
$cshowsPrec :: Int -> StakePoolMetadataHash -> ShowS
Show, (forall x. StakePoolMetadataHash -> Rep StakePoolMetadataHash x)
-> (forall x. Rep StakePoolMetadataHash x -> StakePoolMetadataHash)
-> Generic StakePoolMetadataHash
forall x. Rep StakePoolMetadataHash x -> StakePoolMetadataHash
forall x. StakePoolMetadataHash -> Rep StakePoolMetadataHash x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StakePoolMetadataHash x -> StakePoolMetadataHash
$cfrom :: forall x. StakePoolMetadataHash -> Rep StakePoolMetadataHash x
Generic)
instance NFData StakePoolMetadataHash
instance ToText StakePoolMetadataHash where
toText :: StakePoolMetadataHash -> Text
toText (StakePoolMetadataHash ByteString
bytes) =
Hash Any -> Text
forall a. ToText a => a -> Text
toText (ByteString -> Hash Any
forall (tag :: Symbol). ByteString -> Hash tag
Hash ByteString
bytes)
instance FromText StakePoolMetadataHash where
fromText :: Text -> Either TextDecodingError StakePoolMetadataHash
fromText = (Hash "_" -> StakePoolMetadataHash)
-> Either TextDecodingError (Hash "_")
-> Either TextDecodingError StakePoolMetadataHash
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (ByteString -> StakePoolMetadataHash
StakePoolMetadataHash (ByteString -> StakePoolMetadataHash)
-> (Hash "_" -> ByteString) -> Hash "_" -> StakePoolMetadataHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash "_" -> ByteString
forall (tag :: Symbol). Hash tag -> ByteString
getHash @"_") (Either TextDecodingError (Hash "_")
-> Either TextDecodingError StakePoolMetadataHash)
-> (Text -> Either TextDecodingError (Hash "_"))
-> Text
-> Either TextDecodingError StakePoolMetadataHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Text -> Either TextDecodingError (Hash "_")
forall (t :: Symbol).
KnownSymbol t =>
Int -> Text -> Either TextDecodingError (Hash t)
hashFromText Int
32
instance Buildable StakePoolMetadataHash where
build :: StakePoolMetadataHash -> Builder
build (StakePoolMetadataHash ByteString
hash) = Hash Any -> Builder
forall p. Buildable p => p -> Builder
build (ByteString -> Hash Any
forall (tag :: Symbol). ByteString -> Hash tag
Hash ByteString
hash)
newtype StakePoolMetadataUrl = StakePoolMetadataUrl Text
deriving (StakePoolMetadataUrl -> StakePoolMetadataUrl -> Bool
(StakePoolMetadataUrl -> StakePoolMetadataUrl -> Bool)
-> (StakePoolMetadataUrl -> StakePoolMetadataUrl -> Bool)
-> Eq StakePoolMetadataUrl
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StakePoolMetadataUrl -> StakePoolMetadataUrl -> Bool
$c/= :: StakePoolMetadataUrl -> StakePoolMetadataUrl -> Bool
== :: StakePoolMetadataUrl -> StakePoolMetadataUrl -> Bool
$c== :: StakePoolMetadataUrl -> StakePoolMetadataUrl -> Bool
Eq, Eq StakePoolMetadataUrl
Eq StakePoolMetadataUrl
-> (StakePoolMetadataUrl -> StakePoolMetadataUrl -> Ordering)
-> (StakePoolMetadataUrl -> StakePoolMetadataUrl -> Bool)
-> (StakePoolMetadataUrl -> StakePoolMetadataUrl -> Bool)
-> (StakePoolMetadataUrl -> StakePoolMetadataUrl -> Bool)
-> (StakePoolMetadataUrl -> StakePoolMetadataUrl -> Bool)
-> (StakePoolMetadataUrl
-> StakePoolMetadataUrl -> StakePoolMetadataUrl)
-> (StakePoolMetadataUrl
-> StakePoolMetadataUrl -> StakePoolMetadataUrl)
-> Ord StakePoolMetadataUrl
StakePoolMetadataUrl -> StakePoolMetadataUrl -> Bool
StakePoolMetadataUrl -> StakePoolMetadataUrl -> Ordering
StakePoolMetadataUrl
-> StakePoolMetadataUrl -> StakePoolMetadataUrl
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: StakePoolMetadataUrl
-> StakePoolMetadataUrl -> StakePoolMetadataUrl
$cmin :: StakePoolMetadataUrl
-> StakePoolMetadataUrl -> StakePoolMetadataUrl
max :: StakePoolMetadataUrl
-> StakePoolMetadataUrl -> StakePoolMetadataUrl
$cmax :: StakePoolMetadataUrl
-> StakePoolMetadataUrl -> StakePoolMetadataUrl
>= :: StakePoolMetadataUrl -> StakePoolMetadataUrl -> Bool
$c>= :: StakePoolMetadataUrl -> StakePoolMetadataUrl -> Bool
> :: StakePoolMetadataUrl -> StakePoolMetadataUrl -> Bool
$c> :: StakePoolMetadataUrl -> StakePoolMetadataUrl -> Bool
<= :: StakePoolMetadataUrl -> StakePoolMetadataUrl -> Bool
$c<= :: StakePoolMetadataUrl -> StakePoolMetadataUrl -> Bool
< :: StakePoolMetadataUrl -> StakePoolMetadataUrl -> Bool
$c< :: StakePoolMetadataUrl -> StakePoolMetadataUrl -> Bool
compare :: StakePoolMetadataUrl -> StakePoolMetadataUrl -> Ordering
$ccompare :: StakePoolMetadataUrl -> StakePoolMetadataUrl -> Ordering
$cp1Ord :: Eq StakePoolMetadataUrl
Ord, Int -> StakePoolMetadataUrl -> ShowS
[StakePoolMetadataUrl] -> ShowS
StakePoolMetadataUrl -> String
(Int -> StakePoolMetadataUrl -> ShowS)
-> (StakePoolMetadataUrl -> String)
-> ([StakePoolMetadataUrl] -> ShowS)
-> Show StakePoolMetadataUrl
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StakePoolMetadataUrl] -> ShowS
$cshowList :: [StakePoolMetadataUrl] -> ShowS
show :: StakePoolMetadataUrl -> String
$cshow :: StakePoolMetadataUrl -> String
showsPrec :: Int -> StakePoolMetadataUrl -> ShowS
$cshowsPrec :: Int -> StakePoolMetadataUrl -> ShowS
Show, (forall x. StakePoolMetadataUrl -> Rep StakePoolMetadataUrl x)
-> (forall x. Rep StakePoolMetadataUrl x -> StakePoolMetadataUrl)
-> Generic StakePoolMetadataUrl
forall x. Rep StakePoolMetadataUrl x -> StakePoolMetadataUrl
forall x. StakePoolMetadataUrl -> Rep StakePoolMetadataUrl x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StakePoolMetadataUrl x -> StakePoolMetadataUrl
$cfrom :: forall x. StakePoolMetadataUrl -> Rep StakePoolMetadataUrl x
Generic)
instance NFData StakePoolMetadataUrl
instance ToText StakePoolMetadataUrl where
toText :: StakePoolMetadataUrl -> Text
toText (StakePoolMetadataUrl Text
url) = Text
url
instance FromText StakePoolMetadataUrl where
fromText :: Text -> Either TextDecodingError StakePoolMetadataUrl
fromText = StakePoolMetadataUrl
-> Either TextDecodingError StakePoolMetadataUrl
forall (f :: * -> *) a. Applicative f => a -> f a
pure (StakePoolMetadataUrl
-> Either TextDecodingError StakePoolMetadataUrl)
-> (Text -> StakePoolMetadataUrl)
-> Text
-> Either TextDecodingError StakePoolMetadataUrl
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> StakePoolMetadataUrl
StakePoolMetadataUrl
data StakePoolMetadata = StakePoolMetadata
{ StakePoolMetadata -> StakePoolTicker
ticker :: StakePoolTicker
, StakePoolMetadata -> Text
name :: Text
, StakePoolMetadata -> Maybe Text
description :: Maybe Text
, StakePoolMetadata -> Text
homepage :: Text
} deriving (StakePoolMetadata -> StakePoolMetadata -> Bool
(StakePoolMetadata -> StakePoolMetadata -> Bool)
-> (StakePoolMetadata -> StakePoolMetadata -> Bool)
-> Eq StakePoolMetadata
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StakePoolMetadata -> StakePoolMetadata -> Bool
$c/= :: StakePoolMetadata -> StakePoolMetadata -> Bool
== :: StakePoolMetadata -> StakePoolMetadata -> Bool
$c== :: StakePoolMetadata -> StakePoolMetadata -> Bool
Eq, Eq StakePoolMetadata
Eq StakePoolMetadata
-> (StakePoolMetadata -> StakePoolMetadata -> Ordering)
-> (StakePoolMetadata -> StakePoolMetadata -> Bool)
-> (StakePoolMetadata -> StakePoolMetadata -> Bool)
-> (StakePoolMetadata -> StakePoolMetadata -> Bool)
-> (StakePoolMetadata -> StakePoolMetadata -> Bool)
-> (StakePoolMetadata -> StakePoolMetadata -> StakePoolMetadata)
-> (StakePoolMetadata -> StakePoolMetadata -> StakePoolMetadata)
-> Ord StakePoolMetadata
StakePoolMetadata -> StakePoolMetadata -> Bool
StakePoolMetadata -> StakePoolMetadata -> Ordering
StakePoolMetadata -> StakePoolMetadata -> StakePoolMetadata
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: StakePoolMetadata -> StakePoolMetadata -> StakePoolMetadata
$cmin :: StakePoolMetadata -> StakePoolMetadata -> StakePoolMetadata
max :: StakePoolMetadata -> StakePoolMetadata -> StakePoolMetadata
$cmax :: StakePoolMetadata -> StakePoolMetadata -> StakePoolMetadata
>= :: StakePoolMetadata -> StakePoolMetadata -> Bool
$c>= :: StakePoolMetadata -> StakePoolMetadata -> Bool
> :: StakePoolMetadata -> StakePoolMetadata -> Bool
$c> :: StakePoolMetadata -> StakePoolMetadata -> Bool
<= :: StakePoolMetadata -> StakePoolMetadata -> Bool
$c<= :: StakePoolMetadata -> StakePoolMetadata -> Bool
< :: StakePoolMetadata -> StakePoolMetadata -> Bool
$c< :: StakePoolMetadata -> StakePoolMetadata -> Bool
compare :: StakePoolMetadata -> StakePoolMetadata -> Ordering
$ccompare :: StakePoolMetadata -> StakePoolMetadata -> Ordering
$cp1Ord :: Eq StakePoolMetadata
Ord, Int -> StakePoolMetadata -> ShowS
[StakePoolMetadata] -> ShowS
StakePoolMetadata -> String
(Int -> StakePoolMetadata -> ShowS)
-> (StakePoolMetadata -> String)
-> ([StakePoolMetadata] -> ShowS)
-> Show StakePoolMetadata
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StakePoolMetadata] -> ShowS
$cshowList :: [StakePoolMetadata] -> ShowS
show :: StakePoolMetadata -> String
$cshow :: StakePoolMetadata -> String
showsPrec :: Int -> StakePoolMetadata -> ShowS
$cshowsPrec :: Int -> StakePoolMetadata -> ShowS
Show, (forall x. StakePoolMetadata -> Rep StakePoolMetadata x)
-> (forall x. Rep StakePoolMetadata x -> StakePoolMetadata)
-> Generic StakePoolMetadata
forall x. Rep StakePoolMetadata x -> StakePoolMetadata
forall x. StakePoolMetadata -> Rep StakePoolMetadata x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StakePoolMetadata x -> StakePoolMetadata
$cfrom :: forall x. StakePoolMetadata -> Rep StakePoolMetadata x
Generic)
instance FromJSON StakePoolMetadata where
parseJSON :: Value -> Parser StakePoolMetadata
parseJSON = String
-> (Object -> Parser StakePoolMetadata)
-> Value
-> Parser StakePoolMetadata
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"StakePoolMetadta" ((Object -> Parser StakePoolMetadata)
-> Value -> Parser StakePoolMetadata)
-> (Object -> Parser StakePoolMetadata)
-> Value
-> Parser StakePoolMetadata
forall a b. (a -> b) -> a -> b
$ \Object
obj -> do
StakePoolTicker
ticker <- Object
obj Object -> Key -> Parser StakePoolTicker
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"ticker"
let tickerLen :: Int
tickerLen = Text -> Int
T.length (Text -> Int)
-> (StakePoolTicker -> Text) -> StakePoolTicker -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StakePoolTicker -> Text
unStakePoolTicker (StakePoolTicker -> Int) -> StakePoolTicker -> Int
forall a b. (a -> b) -> a -> b
$ StakePoolTicker
ticker
Bool -> Parser () -> Parser ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
tickerLen Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
5 Bool -> Bool -> Bool
|| Int
tickerLen Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
3)
(Parser () -> Parser ()) -> Parser () -> Parser ()
forall a b. (a -> b) -> a -> b
$ String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"ticker length must be between 3 and 5 characters"
Text
name <- Object
obj Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
Bool -> Parser () -> Parser ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Text -> Int
T.length Text
name Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
50)
(Parser () -> Parser ()) -> Parser () -> Parser ()
forall a b. (a -> b) -> a -> b
$ String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"name exceeds max length of 50 chars"
Maybe Text
description <- Object
obj Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"description"
Bool -> Parser () -> Parser ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ((Text -> Int
T.length (Text -> Int) -> Maybe Text -> Maybe Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
description) Maybe Int -> Maybe Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int -> Maybe Int
forall a. a -> Maybe a
Just Int
255)
(Parser () -> Parser ()) -> Parser () -> Parser ()
forall a b. (a -> b) -> a -> b
$ String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"description exceeds max length of 255 characters"
Text
homepage <- Object
obj Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"homepage"
StakePoolMetadata -> Parser StakePoolMetadata
forall (f :: * -> *) a. Applicative f => a -> f a
pure (StakePoolMetadata -> Parser StakePoolMetadata)
-> StakePoolMetadata -> Parser StakePoolMetadata
forall a b. (a -> b) -> a -> b
$ StakePoolMetadata :: StakePoolTicker -> Text -> Maybe Text -> Text -> StakePoolMetadata
StakePoolMetadata{StakePoolTicker
ticker :: StakePoolTicker
$sel:ticker:StakePoolMetadata :: StakePoolTicker
ticker,Text
name :: Text
$sel:name:StakePoolMetadata :: Text
name,Maybe Text
description :: Maybe Text
$sel:description:StakePoolMetadata :: Maybe Text
description,Text
homepage :: Text
$sel:homepage:StakePoolMetadata :: Text
homepage}
newtype StakePoolTicker = StakePoolTicker { StakePoolTicker -> Text
unStakePoolTicker :: Text }
deriving stock ((forall x. StakePoolTicker -> Rep StakePoolTicker x)
-> (forall x. Rep StakePoolTicker x -> StakePoolTicker)
-> Generic StakePoolTicker
forall x. Rep StakePoolTicker x -> StakePoolTicker
forall x. StakePoolTicker -> Rep StakePoolTicker x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StakePoolTicker x -> StakePoolTicker
$cfrom :: forall x. StakePoolTicker -> Rep StakePoolTicker x
Generic, Int -> StakePoolTicker -> ShowS
[StakePoolTicker] -> ShowS
StakePoolTicker -> String
(Int -> StakePoolTicker -> ShowS)
-> (StakePoolTicker -> String)
-> ([StakePoolTicker] -> ShowS)
-> Show StakePoolTicker
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StakePoolTicker] -> ShowS
$cshowList :: [StakePoolTicker] -> ShowS
show :: StakePoolTicker -> String
$cshow :: StakePoolTicker -> String
showsPrec :: Int -> StakePoolTicker -> ShowS
$cshowsPrec :: Int -> StakePoolTicker -> ShowS
Show, StakePoolTicker -> StakePoolTicker -> Bool
(StakePoolTicker -> StakePoolTicker -> Bool)
-> (StakePoolTicker -> StakePoolTicker -> Bool)
-> Eq StakePoolTicker
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StakePoolTicker -> StakePoolTicker -> Bool
$c/= :: StakePoolTicker -> StakePoolTicker -> Bool
== :: StakePoolTicker -> StakePoolTicker -> Bool
$c== :: StakePoolTicker -> StakePoolTicker -> Bool
Eq, Eq StakePoolTicker
Eq StakePoolTicker
-> (StakePoolTicker -> StakePoolTicker -> Ordering)
-> (StakePoolTicker -> StakePoolTicker -> Bool)
-> (StakePoolTicker -> StakePoolTicker -> Bool)
-> (StakePoolTicker -> StakePoolTicker -> Bool)
-> (StakePoolTicker -> StakePoolTicker -> Bool)
-> (StakePoolTicker -> StakePoolTicker -> StakePoolTicker)
-> (StakePoolTicker -> StakePoolTicker -> StakePoolTicker)
-> Ord StakePoolTicker
StakePoolTicker -> StakePoolTicker -> Bool
StakePoolTicker -> StakePoolTicker -> Ordering
StakePoolTicker -> StakePoolTicker -> StakePoolTicker
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: StakePoolTicker -> StakePoolTicker -> StakePoolTicker
$cmin :: StakePoolTicker -> StakePoolTicker -> StakePoolTicker
max :: StakePoolTicker -> StakePoolTicker -> StakePoolTicker
$cmax :: StakePoolTicker -> StakePoolTicker -> StakePoolTicker
>= :: StakePoolTicker -> StakePoolTicker -> Bool
$c>= :: StakePoolTicker -> StakePoolTicker -> Bool
> :: StakePoolTicker -> StakePoolTicker -> Bool
$c> :: StakePoolTicker -> StakePoolTicker -> Bool
<= :: StakePoolTicker -> StakePoolTicker -> Bool
$c<= :: StakePoolTicker -> StakePoolTicker -> Bool
< :: StakePoolTicker -> StakePoolTicker -> Bool
$c< :: StakePoolTicker -> StakePoolTicker -> Bool
compare :: StakePoolTicker -> StakePoolTicker -> Ordering
$ccompare :: StakePoolTicker -> StakePoolTicker -> Ordering
$cp1Ord :: Eq StakePoolTicker
Ord)
deriving newtype (StakePoolTicker -> Text
(StakePoolTicker -> Text) -> ToText StakePoolTicker
forall a. (a -> Text) -> ToText a
toText :: StakePoolTicker -> Text
$ctoText :: StakePoolTicker -> Text
ToText)
instance FromText StakePoolTicker where
fromText :: Text -> Either TextDecodingError StakePoolTicker
fromText Text
t
| Text -> Int
T.length Text
t Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
3 Bool -> Bool -> Bool
&& Text -> Int
T.length Text
t Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
5
= StakePoolTicker -> Either TextDecodingError StakePoolTicker
forall a b. b -> Either a b
Right (StakePoolTicker -> Either TextDecodingError StakePoolTicker)
-> StakePoolTicker -> Either TextDecodingError StakePoolTicker
forall a b. (a -> b) -> a -> b
$ Text -> StakePoolTicker
StakePoolTicker Text
t
| Bool
otherwise
= TextDecodingError -> Either TextDecodingError StakePoolTicker
forall a b. a -> Either a b
Left (TextDecodingError -> Either TextDecodingError StakePoolTicker)
-> (String -> TextDecodingError)
-> String
-> Either TextDecodingError StakePoolTicker
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> TextDecodingError
TextDecodingError (String -> Either TextDecodingError StakePoolTicker)
-> String -> Either TextDecodingError StakePoolTicker
forall a b. (a -> b) -> a -> b
$
String
"stake pool ticker length must be 3-5 characters"
instance FromJSON StakePoolTicker where
parseJSON :: Value -> Parser StakePoolTicker
parseJSON = Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
parseJSON (Value -> Parser Text)
-> (Text -> Parser StakePoolTicker)
-> Value
-> Parser StakePoolTicker
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (TextDecodingError -> Parser StakePoolTicker)
-> (StakePoolTicker -> Parser StakePoolTicker)
-> Either TextDecodingError StakePoolTicker
-> Parser StakePoolTicker
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (String -> Parser StakePoolTicker
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser StakePoolTicker)
-> (TextDecodingError -> String)
-> TextDecodingError
-> Parser StakePoolTicker
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowFmt TextDecodingError -> String
forall a. Show a => a -> String
show (ShowFmt TextDecodingError -> String)
-> (TextDecodingError -> ShowFmt TextDecodingError)
-> TextDecodingError
-> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextDecodingError -> ShowFmt TextDecodingError
forall a. a -> ShowFmt a
ShowFmt) StakePoolTicker -> Parser StakePoolTicker
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either TextDecodingError StakePoolTicker
-> Parser StakePoolTicker)
-> (Text -> Either TextDecodingError StakePoolTicker)
-> Text
-> Parser StakePoolTicker
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either TextDecodingError StakePoolTicker
forall a. FromText a => Text -> Either TextDecodingError a
fromText
instance ToJSON StakePoolTicker where
toJSON :: StakePoolTicker -> Value
toJSON = Text -> Value
forall a. ToJSON a => a -> Value
toJSON (Text -> Value)
-> (StakePoolTicker -> Text) -> StakePoolTicker -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StakePoolTicker -> Text
forall a. ToText a => a -> Text
toText
newtype PoolId = PoolId { PoolId -> ByteString
getPoolId :: ByteString }
deriving ((forall x. PoolId -> Rep PoolId x)
-> (forall x. Rep PoolId x -> PoolId) -> Generic PoolId
forall x. Rep PoolId x -> PoolId
forall x. PoolId -> Rep PoolId x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PoolId x -> PoolId
$cfrom :: forall x. PoolId -> Rep PoolId x
Generic, PoolId -> PoolId -> Bool
(PoolId -> PoolId -> Bool)
-> (PoolId -> PoolId -> Bool) -> Eq PoolId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PoolId -> PoolId -> Bool
$c/= :: PoolId -> PoolId -> Bool
== :: PoolId -> PoolId -> Bool
$c== :: PoolId -> PoolId -> Bool
Eq, Int -> PoolId -> ShowS
[PoolId] -> ShowS
PoolId -> String
(Int -> PoolId -> ShowS)
-> (PoolId -> String) -> ([PoolId] -> ShowS) -> Show PoolId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PoolId] -> ShowS
$cshowList :: [PoolId] -> ShowS
show :: PoolId -> String
$cshow :: PoolId -> String
showsPrec :: Int -> PoolId -> ShowS
$cshowsPrec :: Int -> PoolId -> ShowS
Show, Eq PoolId
Eq PoolId
-> (PoolId -> PoolId -> Ordering)
-> (PoolId -> PoolId -> Bool)
-> (PoolId -> PoolId -> Bool)
-> (PoolId -> PoolId -> Bool)
-> (PoolId -> PoolId -> Bool)
-> (PoolId -> PoolId -> PoolId)
-> (PoolId -> PoolId -> PoolId)
-> Ord PoolId
PoolId -> PoolId -> Bool
PoolId -> PoolId -> Ordering
PoolId -> PoolId -> PoolId
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PoolId -> PoolId -> PoolId
$cmin :: PoolId -> PoolId -> PoolId
max :: PoolId -> PoolId -> PoolId
$cmax :: PoolId -> PoolId -> PoolId
>= :: PoolId -> PoolId -> Bool
$c>= :: PoolId -> PoolId -> Bool
> :: PoolId -> PoolId -> Bool
$c> :: PoolId -> PoolId -> Bool
<= :: PoolId -> PoolId -> Bool
$c<= :: PoolId -> PoolId -> Bool
< :: PoolId -> PoolId -> Bool
$c< :: PoolId -> PoolId -> Bool
compare :: PoolId -> PoolId -> Ordering
$ccompare :: PoolId -> PoolId -> Ordering
$cp1Ord :: Eq PoolId
Ord)
poolIdBytesLength :: [Int]
poolIdBytesLength :: [Int]
poolIdBytesLength = [Int
28, Int
32]
instance NFData PoolId
instance Buildable PoolId where
build :: PoolId -> Builder
build PoolId
poolId = Builder
forall a. Monoid a => a
mempty
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Int -> Builder -> Builder
forall a. Buildable a => Int -> a -> Builder
prefixF Int
8 Builder
poolIdF
where
poolIdF :: Builder
poolIdF = Text -> Builder
forall p. Buildable p => p -> Builder
build (PoolId -> Text
forall a. ToText a => a -> Text
toText PoolId
poolId)
instance ToText PoolId where
toText :: PoolId -> Text
toText = ByteString -> Text
T.decodeUtf8
(ByteString -> Text) -> (PoolId -> ByteString) -> PoolId -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Base -> ByteString -> ByteString
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
Base -> bin -> bout
convertToBase Base
Base16
(ByteString -> ByteString)
-> (PoolId -> ByteString) -> PoolId -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PoolId -> ByteString
getPoolId
instance FromText PoolId where
fromText :: Text -> Either TextDecodingError PoolId
fromText Text
t = case Base -> ByteString -> Either String ByteString
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
Base -> bin -> Either String bout
convertFromBase Base
Base16 (ByteString -> Either String ByteString)
-> ByteString -> Either String ByteString
forall a b. (a -> b) -> a -> b
$ Text -> ByteString
T.encodeUtf8 Text
t of
Left String
_ ->
Either TextDecodingError PoolId
forall b. Either TextDecodingError b
textDecodingError
Right ByteString
bytes | ByteString -> Int
BS.length ByteString
bytes Int -> [Int] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Int]
poolIdBytesLength ->
PoolId -> Either TextDecodingError PoolId
forall a b. b -> Either a b
Right (PoolId -> Either TextDecodingError PoolId)
-> PoolId -> Either TextDecodingError PoolId
forall a b. (a -> b) -> a -> b
$ ByteString -> PoolId
PoolId ByteString
bytes
Right ByteString
_ ->
Either TextDecodingError PoolId
forall b. Either TextDecodingError b
textDecodingError
where
textDecodingError :: Either TextDecodingError b
textDecodingError = TextDecodingError -> Either TextDecodingError b
forall a b. a -> Either a b
Left (TextDecodingError -> Either TextDecodingError b)
-> TextDecodingError -> Either TextDecodingError b
forall a b. (a -> b) -> a -> b
$ String -> TextDecodingError
TextDecodingError (String -> TextDecodingError) -> String -> TextDecodingError
forall a b. (a -> b) -> a -> b
$ [String] -> String
unwords
[ String
"Invalid stake pool id: expecting a hex-encoded value that is"
, String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
" or " (Int -> String
forall a. Show a => a -> String
show (Int -> String) -> [Int] -> [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Int]
poolIdBytesLength)
, String
"bytes in length."
]
encodePoolIdBech32 :: PoolId -> T.Text
encodePoolIdBech32 :: PoolId -> Text
encodePoolIdBech32 =
HumanReadablePart -> DataPart -> Text
Bech32.encodeLenient HumanReadablePart
hrp
(DataPart -> Text) -> (PoolId -> DataPart) -> PoolId -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> DataPart
Bech32.dataPartFromBytes
(ByteString -> DataPart)
-> (PoolId -> ByteString) -> PoolId -> DataPart
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PoolId -> ByteString
getPoolId
where
hrp :: HumanReadablePart
hrp = [Bech32.humanReadablePart|pool|]
decodePoolIdBech32 :: T.Text -> Either TextDecodingError PoolId
decodePoolIdBech32 :: Text -> Either TextDecodingError PoolId
decodePoolIdBech32 Text
t =
case (DataPart -> Maybe ByteString)
-> (HumanReadablePart, DataPart)
-> (HumanReadablePart, Maybe ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap DataPart -> Maybe ByteString
Bech32.dataPartToBytes ((HumanReadablePart, DataPart)
-> (HumanReadablePart, Maybe ByteString))
-> Either DecodingError (HumanReadablePart, DataPart)
-> Either DecodingError (HumanReadablePart, Maybe ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Either DecodingError (HumanReadablePart, DataPart)
Bech32.decodeLenient Text
t of
Left DecodingError
_ -> TextDecodingError -> Either TextDecodingError PoolId
forall a b. a -> Either a b
Left TextDecodingError
textDecodingError
Right (HumanReadablePart
_, Just ByteString
bytes) ->
PoolId -> Either TextDecodingError PoolId
forall a b. b -> Either a b
Right (PoolId -> Either TextDecodingError PoolId)
-> PoolId -> Either TextDecodingError PoolId
forall a b. (a -> b) -> a -> b
$ ByteString -> PoolId
PoolId ByteString
bytes
Right (HumanReadablePart, Maybe ByteString)
_ -> TextDecodingError -> Either TextDecodingError PoolId
forall a b. a -> Either a b
Left TextDecodingError
textDecodingError
where
textDecodingError :: TextDecodingError
textDecodingError = String -> TextDecodingError
TextDecodingError (String -> TextDecodingError) -> String -> TextDecodingError
forall a b. (a -> b) -> a -> b
$ [String] -> String
unwords
[ String
"Invalid stake pool id: expecting a Bech32 encoded value with human readable part of 'pool'."
]
newtype PoolOwner = PoolOwner { PoolOwner -> ByteString
getPoolOwner :: ByteString }
deriving ((forall x. PoolOwner -> Rep PoolOwner x)
-> (forall x. Rep PoolOwner x -> PoolOwner) -> Generic PoolOwner
forall x. Rep PoolOwner x -> PoolOwner
forall x. PoolOwner -> Rep PoolOwner x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PoolOwner x -> PoolOwner
$cfrom :: forall x. PoolOwner -> Rep PoolOwner x
Generic, PoolOwner -> PoolOwner -> Bool
(PoolOwner -> PoolOwner -> Bool)
-> (PoolOwner -> PoolOwner -> Bool) -> Eq PoolOwner
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PoolOwner -> PoolOwner -> Bool
$c/= :: PoolOwner -> PoolOwner -> Bool
== :: PoolOwner -> PoolOwner -> Bool
$c== :: PoolOwner -> PoolOwner -> Bool
Eq, Int -> PoolOwner -> ShowS
[PoolOwner] -> ShowS
PoolOwner -> String
(Int -> PoolOwner -> ShowS)
-> (PoolOwner -> String)
-> ([PoolOwner] -> ShowS)
-> Show PoolOwner
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PoolOwner] -> ShowS
$cshowList :: [PoolOwner] -> ShowS
show :: PoolOwner -> String
$cshow :: PoolOwner -> String
showsPrec :: Int -> PoolOwner -> ShowS
$cshowsPrec :: Int -> PoolOwner -> ShowS
Show, Eq PoolOwner
Eq PoolOwner
-> (PoolOwner -> PoolOwner -> Ordering)
-> (PoolOwner -> PoolOwner -> Bool)
-> (PoolOwner -> PoolOwner -> Bool)
-> (PoolOwner -> PoolOwner -> Bool)
-> (PoolOwner -> PoolOwner -> Bool)
-> (PoolOwner -> PoolOwner -> PoolOwner)
-> (PoolOwner -> PoolOwner -> PoolOwner)
-> Ord PoolOwner
PoolOwner -> PoolOwner -> Bool
PoolOwner -> PoolOwner -> Ordering
PoolOwner -> PoolOwner -> PoolOwner
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PoolOwner -> PoolOwner -> PoolOwner
$cmin :: PoolOwner -> PoolOwner -> PoolOwner
max :: PoolOwner -> PoolOwner -> PoolOwner
$cmax :: PoolOwner -> PoolOwner -> PoolOwner
>= :: PoolOwner -> PoolOwner -> Bool
$c>= :: PoolOwner -> PoolOwner -> Bool
> :: PoolOwner -> PoolOwner -> Bool
$c> :: PoolOwner -> PoolOwner -> Bool
<= :: PoolOwner -> PoolOwner -> Bool
$c<= :: PoolOwner -> PoolOwner -> Bool
< :: PoolOwner -> PoolOwner -> Bool
$c< :: PoolOwner -> PoolOwner -> Bool
compare :: PoolOwner -> PoolOwner -> Ordering
$ccompare :: PoolOwner -> PoolOwner -> Ordering
$cp1Ord :: Eq PoolOwner
Ord)
poolOwnerPrefix :: Bech32.HumanReadablePart
poolOwnerPrefix :: HumanReadablePart
poolOwnerPrefix = [Bech32.humanReadablePart|ed25519_pk|]
instance NFData PoolOwner
instance Buildable PoolOwner where
build :: PoolOwner -> Builder
build PoolOwner
poolId = Text -> Builder
forall p. Buildable p => p -> Builder
build (PoolOwner -> Text
forall a. ToText a => a -> Text
toText PoolOwner
poolId)
instance ToText PoolOwner where
toText :: PoolOwner -> Text
toText = HumanReadablePart -> DataPart -> Text
Bech32.encodeLenient HumanReadablePart
poolOwnerPrefix
(DataPart -> Text) -> (PoolOwner -> DataPart) -> PoolOwner -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> DataPart
Bech32.dataPartFromBytes
(ByteString -> DataPart)
-> (PoolOwner -> ByteString) -> PoolOwner -> DataPart
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PoolOwner -> ByteString
getPoolOwner
instance FromText PoolOwner where
fromText :: Text -> Either TextDecodingError PoolOwner
fromText Text
t = case (DataPart -> Maybe ByteString)
-> (HumanReadablePart, DataPart)
-> (HumanReadablePart, Maybe ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap DataPart -> Maybe ByteString
Bech32.dataPartToBytes ((HumanReadablePart, DataPart)
-> (HumanReadablePart, Maybe ByteString))
-> Either DecodingError (HumanReadablePart, DataPart)
-> Either DecodingError (HumanReadablePart, Maybe ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Either DecodingError (HumanReadablePart, DataPart)
Bech32.decode Text
t of
Left DecodingError
err ->
TextDecodingError -> Either TextDecodingError PoolOwner
forall a b. a -> Either a b
Left (TextDecodingError -> Either TextDecodingError PoolOwner)
-> TextDecodingError -> Either TextDecodingError PoolOwner
forall a b. (a -> b) -> a -> b
$ String -> TextDecodingError
TextDecodingError (String -> TextDecodingError) -> String -> TextDecodingError
forall a b. (a -> b) -> a -> b
$
String
"Stake pool owner is not a valid bech32 string: "
String -> ShowS
forall a. Semigroup a => a -> a -> a
<> DecodingError -> String
forall a. Show a => a -> String
show DecodingError
err
Right (HumanReadablePart
hrp, Just ByteString
bytes)
| HumanReadablePart
hrp HumanReadablePart -> HumanReadablePart -> Bool
forall a. Eq a => a -> a -> Bool
== HumanReadablePart
poolOwnerPrefix ->
PoolOwner -> Either TextDecodingError PoolOwner
forall a b. b -> Either a b
Right (PoolOwner -> Either TextDecodingError PoolOwner)
-> PoolOwner -> Either TextDecodingError PoolOwner
forall a b. (a -> b) -> a -> b
$ ByteString -> PoolOwner
PoolOwner ByteString
bytes
| Bool
otherwise ->
TextDecodingError -> Either TextDecodingError PoolOwner
forall a b. a -> Either a b
Left (TextDecodingError -> Either TextDecodingError PoolOwner)
-> TextDecodingError -> Either TextDecodingError PoolOwner
forall a b. (a -> b) -> a -> b
$ String -> TextDecodingError
TextDecodingError (String -> TextDecodingError) -> String -> TextDecodingError
forall a b. (a -> b) -> a -> b
$
String
"Stake pool owner has wrong prefix:"
String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" expected "
String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> String
T.unpack (HumanReadablePart -> Text
Bech32.humanReadablePartToText HumanReadablePart
poolOwnerPrefix)
String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" but got "
String -> ShowS
forall a. Semigroup a => a -> a -> a
<> HumanReadablePart -> String
forall a. Show a => a -> String
show HumanReadablePart
hrp
Right (HumanReadablePart
_, Maybe ByteString
Nothing) ->
TextDecodingError -> Either TextDecodingError PoolOwner
forall a b. a -> Either a b
Left (TextDecodingError -> Either TextDecodingError PoolOwner)
-> TextDecodingError -> Either TextDecodingError PoolOwner
forall a b. (a -> b) -> a -> b
$ String -> TextDecodingError
TextDecodingError String
"Stake pool owner is invalid"
instance FromJSON PoolOwner where
parseJSON :: Value -> Parser PoolOwner
parseJSON = Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
parseJSON (Value -> Parser Text)
-> (Text -> Parser PoolOwner) -> Value -> Parser PoolOwner
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (TextDecodingError -> Parser PoolOwner)
-> (PoolOwner -> Parser PoolOwner)
-> Either TextDecodingError PoolOwner
-> Parser PoolOwner
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (String -> Parser PoolOwner
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser PoolOwner)
-> (TextDecodingError -> String)
-> TextDecodingError
-> Parser PoolOwner
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowFmt TextDecodingError -> String
forall a. Show a => a -> String
show (ShowFmt TextDecodingError -> String)
-> (TextDecodingError -> ShowFmt TextDecodingError)
-> TextDecodingError
-> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextDecodingError -> ShowFmt TextDecodingError
forall a. a -> ShowFmt a
ShowFmt) PoolOwner -> Parser PoolOwner
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either TextDecodingError PoolOwner -> Parser PoolOwner)
-> (Text -> Either TextDecodingError PoolOwner)
-> Text
-> Parser PoolOwner
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either TextDecodingError PoolOwner
forall a. FromText a => Text -> Either TextDecodingError a
fromText
instance ToJSON PoolOwner where
toJSON :: PoolOwner -> Value
toJSON = Text -> Value
forall a. ToJSON a => a -> Value
toJSON (Text -> Value) -> (PoolOwner -> Text) -> PoolOwner -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PoolOwner -> Text
forall a. ToText a => a -> Text
toText
data StakePoolsSummary = StakePoolsSummary
{ StakePoolsSummary -> Int
nOpt :: Int
, StakePoolsSummary -> Map PoolId Coin
rewards :: Map PoolId Coin
, StakePoolsSummary -> Map PoolId Percentage
stake :: Map PoolId Percentage
} deriving (Int -> StakePoolsSummary -> ShowS
[StakePoolsSummary] -> ShowS
StakePoolsSummary -> String
(Int -> StakePoolsSummary -> ShowS)
-> (StakePoolsSummary -> String)
-> ([StakePoolsSummary] -> ShowS)
-> Show StakePoolsSummary
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StakePoolsSummary] -> ShowS
$cshowList :: [StakePoolsSummary] -> ShowS
show :: StakePoolsSummary -> String
$cshow :: StakePoolsSummary -> String
showsPrec :: Int -> StakePoolsSummary -> ShowS
$cshowsPrec :: Int -> StakePoolsSummary -> ShowS
Show, StakePoolsSummary -> StakePoolsSummary -> Bool
(StakePoolsSummary -> StakePoolsSummary -> Bool)
-> (StakePoolsSummary -> StakePoolsSummary -> Bool)
-> Eq StakePoolsSummary
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StakePoolsSummary -> StakePoolsSummary -> Bool
$c/= :: StakePoolsSummary -> StakePoolsSummary -> Bool
== :: StakePoolsSummary -> StakePoolsSummary -> Bool
$c== :: StakePoolsSummary -> StakePoolsSummary -> Bool
Eq)
instance Buildable StakePoolsSummary where
build :: StakePoolsSummary -> Builder
build StakePoolsSummary{Int
nOpt :: Int
$sel:nOpt:StakePoolsSummary :: StakePoolsSummary -> Int
nOpt,Map PoolId Coin
rewards :: Map PoolId Coin
$sel:rewards:StakePoolsSummary :: StakePoolsSummary -> Map PoolId Coin
rewards,Map PoolId Percentage
stake :: Map PoolId Percentage
$sel:stake:StakePoolsSummary :: StakePoolsSummary -> Map PoolId Percentage
stake} = (Builder -> Builder) -> [Builder] -> Builder
forall (f :: * -> *) a.
Foldable f =>
(a -> Builder) -> f a -> Builder
listF' Builder -> Builder
forall a. a -> a
id
[ Builder
"Stake: " Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> [(PoolId, Percentage)] -> Builder
forall t k v.
(IsList t, Item t ~ (k, v), Buildable k, Buildable v) =>
t -> Builder
mapF (Map PoolId Percentage -> [(PoolId, Percentage)]
forall k a. Map k a -> [(k, a)]
Map.toList Map PoolId Percentage
stake)
, Builder
"Non-myopic member rewards: " Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> [(PoolId, Coin)] -> Builder
forall t k v.
(IsList t, Item t ~ (k, v), Buildable k, Buildable v) =>
t -> Builder
mapF (Map PoolId Coin -> [(PoolId, Coin)]
forall k a. Map k a -> [(k, a)]
Map.toList Map PoolId Coin
rewards)
, Builder
"Optimum number of pools: " Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Int -> Builder
forall a b. (Buildable a, FromBuilder b) => a -> b
pretty Int
nOpt
]
data Block = Block
{
:: !BlockHeader
, Block -> [Tx]
transactions
:: ![Tx]
, Block -> [DelegationCertificate]
delegations
:: ![DelegationCertificate]
} deriving (Int -> Block -> ShowS
[Block] -> ShowS
Block -> String
(Int -> Block -> ShowS)
-> (Block -> String) -> ([Block] -> ShowS) -> Show Block
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Block] -> ShowS
$cshowList :: [Block] -> ShowS
show :: Block -> String
$cshow :: Block -> String
showsPrec :: Int -> Block -> ShowS
$cshowsPrec :: Int -> Block -> ShowS
Show, Block -> Block -> Bool
(Block -> Block -> Bool) -> (Block -> Block -> Bool) -> Eq Block
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Block -> Block -> Bool
$c/= :: Block -> Block -> Bool
== :: Block -> Block -> Bool
$c== :: Block -> Block -> Bool
Eq, Eq Block
Eq Block
-> (Block -> Block -> Ordering)
-> (Block -> Block -> Bool)
-> (Block -> Block -> Bool)
-> (Block -> Block -> Bool)
-> (Block -> Block -> Bool)
-> (Block -> Block -> Block)
-> (Block -> Block -> Block)
-> Ord Block
Block -> Block -> Bool
Block -> Block -> Ordering
Block -> Block -> Block
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Block -> Block -> Block
$cmin :: Block -> Block -> Block
max :: Block -> Block -> Block
$cmax :: Block -> Block -> Block
>= :: Block -> Block -> Bool
$c>= :: Block -> Block -> Bool
> :: Block -> Block -> Bool
$c> :: Block -> Block -> Bool
<= :: Block -> Block -> Bool
$c<= :: Block -> Block -> Bool
< :: Block -> Block -> Bool
$c< :: Block -> Block -> Bool
compare :: Block -> Block -> Ordering
$ccompare :: Block -> Block -> Ordering
$cp1Ord :: Eq Block
Ord, (forall x. Block -> Rep Block x)
-> (forall x. Rep Block x -> Block) -> Generic Block
forall x. Rep Block x -> Block
forall x. Block -> Rep Block x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Block x -> Block
$cfrom :: forall x. Block -> Rep Block x
Generic)
instance NFData Block
instance Buildable (Block) where
build :: Block -> Builder
build (Block BlockHeader
h [Tx]
txs [DelegationCertificate]
_) = Builder
forall a. Monoid a => a
mempty
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> BlockHeader -> Builder
forall p. Buildable p => p -> Builder
build BlockHeader
h
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> if [Tx] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Tx]
txs then Builder
" ∅" else Builder
"\n" Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Int -> Builder -> Builder
indentF Int
4 ([Tx] -> Builder
forall (f :: * -> *) a. (Foldable f, Buildable a) => f a -> Builder
blockListF [Tx]
txs)
data =
{
:: SlotNo
,
:: Quantity "block" Word32
,
:: !(Hash "BlockHeader")
,
:: !(Maybe (Hash "BlockHeader"))
} deriving (Int -> BlockHeader -> ShowS
[BlockHeader] -> ShowS
BlockHeader -> String
(Int -> BlockHeader -> ShowS)
-> (BlockHeader -> String)
-> ([BlockHeader] -> ShowS)
-> Show BlockHeader
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BlockHeader] -> ShowS
$cshowList :: [BlockHeader] -> ShowS
show :: BlockHeader -> String
$cshow :: BlockHeader -> String
showsPrec :: Int -> BlockHeader -> ShowS
$cshowsPrec :: Int -> BlockHeader -> ShowS
Show, BlockHeader -> BlockHeader -> Bool
(BlockHeader -> BlockHeader -> Bool)
-> (BlockHeader -> BlockHeader -> Bool) -> Eq BlockHeader
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BlockHeader -> BlockHeader -> Bool
$c/= :: BlockHeader -> BlockHeader -> Bool
== :: BlockHeader -> BlockHeader -> Bool
$c== :: BlockHeader -> BlockHeader -> Bool
Eq, Eq BlockHeader
Eq BlockHeader
-> (BlockHeader -> BlockHeader -> Ordering)
-> (BlockHeader -> BlockHeader -> Bool)
-> (BlockHeader -> BlockHeader -> Bool)
-> (BlockHeader -> BlockHeader -> Bool)
-> (BlockHeader -> BlockHeader -> Bool)
-> (BlockHeader -> BlockHeader -> BlockHeader)
-> (BlockHeader -> BlockHeader -> BlockHeader)
-> Ord BlockHeader
BlockHeader -> BlockHeader -> Bool
BlockHeader -> BlockHeader -> Ordering
BlockHeader -> BlockHeader -> BlockHeader
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: BlockHeader -> BlockHeader -> BlockHeader
$cmin :: BlockHeader -> BlockHeader -> BlockHeader
max :: BlockHeader -> BlockHeader -> BlockHeader
$cmax :: BlockHeader -> BlockHeader -> BlockHeader
>= :: BlockHeader -> BlockHeader -> Bool
$c>= :: BlockHeader -> BlockHeader -> Bool
> :: BlockHeader -> BlockHeader -> Bool
$c> :: BlockHeader -> BlockHeader -> Bool
<= :: BlockHeader -> BlockHeader -> Bool
$c<= :: BlockHeader -> BlockHeader -> Bool
< :: BlockHeader -> BlockHeader -> Bool
$c< :: BlockHeader -> BlockHeader -> Bool
compare :: BlockHeader -> BlockHeader -> Ordering
$ccompare :: BlockHeader -> BlockHeader -> Ordering
$cp1Ord :: Eq BlockHeader
Ord, (forall x. BlockHeader -> Rep BlockHeader x)
-> (forall x. Rep BlockHeader x -> BlockHeader)
-> Generic BlockHeader
forall x. Rep BlockHeader x -> BlockHeader
forall x. BlockHeader -> Rep BlockHeader x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BlockHeader x -> BlockHeader
$cfrom :: forall x. BlockHeader -> Rep BlockHeader x
Generic)
isGenesisBlockHeader :: BlockHeader -> Bool
= Maybe (Hash "BlockHeader") -> Bool
forall a. Maybe a -> Bool
isNothing (Maybe (Hash "BlockHeader") -> Bool)
-> (BlockHeader -> Maybe (Hash "BlockHeader"))
-> BlockHeader
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Maybe (Hash "BlockHeader")
-> Const (Maybe (Hash "BlockHeader")) (Maybe (Hash "BlockHeader")))
-> BlockHeader -> Const (Maybe (Hash "BlockHeader")) BlockHeader)
-> BlockHeader -> Maybe (Hash "BlockHeader")
forall a s. ((a -> Const a a) -> s -> Const a s) -> s -> a
view IsLabel
"parentHeaderHash"
((Maybe (Hash "BlockHeader")
-> Const (Maybe (Hash "BlockHeader")) (Maybe (Hash "BlockHeader")))
-> BlockHeader -> Const (Maybe (Hash "BlockHeader")) BlockHeader)
(Maybe (Hash "BlockHeader")
-> Const (Maybe (Hash "BlockHeader")) (Maybe (Hash "BlockHeader")))
-> BlockHeader -> Const (Maybe (Hash "BlockHeader")) BlockHeader
#parentHeaderHash
instance NFData BlockHeader
instance Buildable BlockHeader where
build :: BlockHeader -> Builder
build BlockHeader{Maybe (Hash "BlockHeader")
SlotNo
Hash "BlockHeader"
Quantity "block" Word32
parentHeaderHash :: Maybe (Hash "BlockHeader")
headerHash :: Hash "BlockHeader"
blockHeight :: Quantity "block" Word32
slotNo :: SlotNo
$sel:parentHeaderHash:BlockHeader :: BlockHeader -> Maybe (Hash "BlockHeader")
$sel:headerHash:BlockHeader :: BlockHeader -> Hash "BlockHeader"
$sel:blockHeight:BlockHeader :: BlockHeader -> Quantity "block" Word32
$sel:slotNo:BlockHeader :: BlockHeader -> SlotNo
..} =
Builder
previous
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
"["
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
current
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
"-"
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> SlotNo -> Builder
forall p. Buildable p => p -> Builder
build SlotNo
slotNo
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
"#" Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> (String -> Builder
forall p. Buildable p => p -> Builder
build (String -> Builder)
-> (Quantity "block" Word32 -> String)
-> Quantity "block" Word32
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> String
forall a. Show a => a -> String
show (Word32 -> String)
-> (Quantity "block" Word32 -> Word32)
-> Quantity "block" Word32
-> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Quantity "block" Word32 -> Word32
forall (unit :: Symbol) a. Quantity unit a -> a
getQuantity) Quantity "block" Word32
blockHeight
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
"]"
where
toHex :: ByteString -> Text
toHex = ByteString -> Text
T.decodeUtf8 (ByteString -> Text)
-> (ByteString -> ByteString) -> ByteString -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Base -> ByteString -> ByteString
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
Base -> bin -> bout
convertToBase Base
Base16
current :: Builder
current = Int -> Builder -> Builder
forall a. Buildable a => Int -> a -> Builder
prefixF Int
8 (Builder -> Builder) -> Builder -> Builder
forall a b. (a -> b) -> a -> b
$ Text -> Builder
forall p. Buildable p => p -> Builder
build (Text -> Builder) -> Text -> Builder
forall a b. (a -> b) -> a -> b
$ ByteString -> Text
toHex (ByteString -> Text) -> ByteString -> Text
forall a b. (a -> b) -> a -> b
$ Hash "BlockHeader" -> ByteString
forall (tag :: Symbol). Hash tag -> ByteString
getHash Hash "BlockHeader"
headerHash
previous :: Builder
previous = case Maybe (Hash "BlockHeader")
parentHeaderHash of
Maybe (Hash "BlockHeader")
Nothing -> Builder
""
Just Hash "BlockHeader"
h -> Int -> Builder -> Builder
forall a. Buildable a => Int -> a -> Builder
prefixF Int
8 (Text -> Builder
forall p. Buildable p => p -> Builder
build (Text -> Builder) -> Text -> Builder
forall a b. (a -> b) -> a -> b
$ ByteString -> Text
toHex (ByteString -> Text) -> ByteString -> Text
forall a b. (a -> b) -> a -> b
$ Hash "BlockHeader" -> ByteString
forall (tag :: Symbol). Hash tag -> ByteString
getHash Hash "BlockHeader"
h) Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
"<-"
data ChainPoint
= ChainPointAtGenesis
| ChainPoint !SlotNo !(Hash "BlockHeader")
deriving (ChainPoint -> ChainPoint -> Bool
(ChainPoint -> ChainPoint -> Bool)
-> (ChainPoint -> ChainPoint -> Bool) -> Eq ChainPoint
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChainPoint -> ChainPoint -> Bool
$c/= :: ChainPoint -> ChainPoint -> Bool
== :: ChainPoint -> ChainPoint -> Bool
$c== :: ChainPoint -> ChainPoint -> Bool
Eq, Eq ChainPoint
Eq ChainPoint
-> (ChainPoint -> ChainPoint -> Ordering)
-> (ChainPoint -> ChainPoint -> Bool)
-> (ChainPoint -> ChainPoint -> Bool)
-> (ChainPoint -> ChainPoint -> Bool)
-> (ChainPoint -> ChainPoint -> Bool)
-> (ChainPoint -> ChainPoint -> ChainPoint)
-> (ChainPoint -> ChainPoint -> ChainPoint)
-> Ord ChainPoint
ChainPoint -> ChainPoint -> Bool
ChainPoint -> ChainPoint -> Ordering
ChainPoint -> ChainPoint -> ChainPoint
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ChainPoint -> ChainPoint -> ChainPoint
$cmin :: ChainPoint -> ChainPoint -> ChainPoint
max :: ChainPoint -> ChainPoint -> ChainPoint
$cmax :: ChainPoint -> ChainPoint -> ChainPoint
>= :: ChainPoint -> ChainPoint -> Bool
$c>= :: ChainPoint -> ChainPoint -> Bool
> :: ChainPoint -> ChainPoint -> Bool
$c> :: ChainPoint -> ChainPoint -> Bool
<= :: ChainPoint -> ChainPoint -> Bool
$c<= :: ChainPoint -> ChainPoint -> Bool
< :: ChainPoint -> ChainPoint -> Bool
$c< :: ChainPoint -> ChainPoint -> Bool
compare :: ChainPoint -> ChainPoint -> Ordering
$ccompare :: ChainPoint -> ChainPoint -> Ordering
$cp1Ord :: Eq ChainPoint
Ord, Int -> ChainPoint -> ShowS
[ChainPoint] -> ShowS
ChainPoint -> String
(Int -> ChainPoint -> ShowS)
-> (ChainPoint -> String)
-> ([ChainPoint] -> ShowS)
-> Show ChainPoint
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChainPoint] -> ShowS
$cshowList :: [ChainPoint] -> ShowS
show :: ChainPoint -> String
$cshow :: ChainPoint -> String
showsPrec :: Int -> ChainPoint -> ShowS
$cshowsPrec :: Int -> ChainPoint -> ShowS
Show, (forall x. ChainPoint -> Rep ChainPoint x)
-> (forall x. Rep ChainPoint x -> ChainPoint) -> Generic ChainPoint
forall x. Rep ChainPoint x -> ChainPoint
forall x. ChainPoint -> Rep ChainPoint x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChainPoint x -> ChainPoint
$cfrom :: forall x. ChainPoint -> Rep ChainPoint x
Generic)
compareSlot :: ChainPoint -> ChainPoint -> Ordering
compareSlot :: ChainPoint -> ChainPoint -> Ordering
compareSlot ChainPoint
pt1 ChainPoint
pt2 = Slot -> Slot -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (ChainPoint -> Slot
toSlot ChainPoint
pt1) (ChainPoint -> Slot
toSlot ChainPoint
pt2)
chainPointFromBlockHeader :: BlockHeader -> ChainPoint
header :: BlockHeader
header@(BlockHeader SlotNo
sl Quantity "block" Word32
_ Hash "BlockHeader"
hash Maybe (Hash "BlockHeader")
_)
| BlockHeader -> Bool
isGenesisBlockHeader BlockHeader
header = ChainPoint
ChainPointAtGenesis
| Bool
otherwise = SlotNo -> Hash "BlockHeader" -> ChainPoint
ChainPoint SlotNo
sl Hash "BlockHeader"
hash
instance NFData ChainPoint
instance NoThunks ChainPoint
instance Buildable ChainPoint where
build :: ChainPoint -> Builder
build ChainPoint
ChainPointAtGenesis = Builder
"[point genesis]"
build (ChainPoint SlotNo
slot Hash "BlockHeader"
hash) =
Builder
"[point " Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
hashF Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
" at slot " Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> SlotNo -> Builder
forall a b. (Buildable a, FromBuilder b) => a -> b
pretty SlotNo
slot Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
"]"
where
hashF :: Builder
hashF = Int -> Text -> Builder
forall a. Buildable a => Int -> a -> Builder
prefixF Int
8 (Text -> Builder) -> Text -> Builder
forall a b. (a -> b) -> a -> b
$ ByteString -> Text
T.decodeUtf8 (ByteString -> Text) -> ByteString -> Text
forall a b. (a -> b) -> a -> b
$ Base -> ByteString -> ByteString
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
Base -> bin -> bout
convertToBase Base
Base16 (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ Hash "BlockHeader" -> ByteString
forall (tag :: Symbol). Hash tag -> ByteString
getHash Hash "BlockHeader"
hash
type Slot = WithOrigin SlotNo
toSlot :: ChainPoint -> Slot
toSlot :: ChainPoint -> Slot
toSlot ChainPoint
ChainPointAtGenesis = Slot
forall t. WithOrigin t
Origin
toSlot (ChainPoint SlotNo
slot Hash "BlockHeader"
_) = SlotNo -> Slot
forall t. t -> WithOrigin t
At SlotNo
slot
instance Buildable Slot where
build :: Slot -> Builder
build Slot
Origin = Builder
"[genesis]"
build (At SlotNo
slot) = Builder
"[at slot " Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> SlotNo -> Builder
forall a b. (Buildable a, FromBuilder b) => a -> b
pretty SlotNo
slot Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
"]"
data LinearFunction a = LinearFunction { LinearFunction a -> a
intercept :: a, LinearFunction a -> a
slope :: a }
deriving (LinearFunction a -> LinearFunction a -> Bool
(LinearFunction a -> LinearFunction a -> Bool)
-> (LinearFunction a -> LinearFunction a -> Bool)
-> Eq (LinearFunction a)
forall a. Eq a => LinearFunction a -> LinearFunction a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LinearFunction a -> LinearFunction a -> Bool
$c/= :: forall a. Eq a => LinearFunction a -> LinearFunction a -> Bool
== :: LinearFunction a -> LinearFunction a -> Bool
$c== :: forall a. Eq a => LinearFunction a -> LinearFunction a -> Bool
Eq, Int -> LinearFunction a -> ShowS
[LinearFunction a] -> ShowS
LinearFunction a -> String
(Int -> LinearFunction a -> ShowS)
-> (LinearFunction a -> String)
-> ([LinearFunction a] -> ShowS)
-> Show (LinearFunction a)
forall a. Show a => Int -> LinearFunction a -> ShowS
forall a. Show a => [LinearFunction a] -> ShowS
forall a. Show a => LinearFunction a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LinearFunction a] -> ShowS
$cshowList :: forall a. Show a => [LinearFunction a] -> ShowS
show :: LinearFunction a -> String
$cshow :: forall a. Show a => LinearFunction a -> String
showsPrec :: Int -> LinearFunction a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> LinearFunction a -> ShowS
Show, (forall x. LinearFunction a -> Rep (LinearFunction a) x)
-> (forall x. Rep (LinearFunction a) x -> LinearFunction a)
-> Generic (LinearFunction a)
forall x. Rep (LinearFunction a) x -> LinearFunction a
forall x. LinearFunction a -> Rep (LinearFunction a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (LinearFunction a) x -> LinearFunction a
forall a x. LinearFunction a -> Rep (LinearFunction a) x
$cto :: forall a x. Rep (LinearFunction a) x -> LinearFunction a
$cfrom :: forall a x. LinearFunction a -> Rep (LinearFunction a) x
Generic)
instance NFData a => NFData (LinearFunction a)
newtype FeePolicy = LinearFee (LinearFunction Double)
deriving (FeePolicy -> FeePolicy -> Bool
(FeePolicy -> FeePolicy -> Bool)
-> (FeePolicy -> FeePolicy -> Bool) -> Eq FeePolicy
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FeePolicy -> FeePolicy -> Bool
$c/= :: FeePolicy -> FeePolicy -> Bool
== :: FeePolicy -> FeePolicy -> Bool
$c== :: FeePolicy -> FeePolicy -> Bool
Eq, Int -> FeePolicy -> ShowS
[FeePolicy] -> ShowS
FeePolicy -> String
(Int -> FeePolicy -> ShowS)
-> (FeePolicy -> String)
-> ([FeePolicy] -> ShowS)
-> Show FeePolicy
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FeePolicy] -> ShowS
$cshowList :: [FeePolicy] -> ShowS
show :: FeePolicy -> String
$cshow :: FeePolicy -> String
showsPrec :: Int -> FeePolicy -> ShowS
$cshowsPrec :: Int -> FeePolicy -> ShowS
Show, (forall x. FeePolicy -> Rep FeePolicy x)
-> (forall x. Rep FeePolicy x -> FeePolicy) -> Generic FeePolicy
forall x. Rep FeePolicy x -> FeePolicy
forall x. FeePolicy -> Rep FeePolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FeePolicy x -> FeePolicy
$cfrom :: forall x. FeePolicy -> Rep FeePolicy x
Generic)
instance NFData FeePolicy
instance ToText FeePolicy where
toText :: FeePolicy -> Text
toText (LinearFee LinearFunction {Double
slope :: Double
intercept :: Double
$sel:slope:LinearFunction :: forall a. LinearFunction a -> a
$sel:intercept:LinearFunction :: forall a. LinearFunction a -> a
..}) =
Double -> Text
forall a. ToText a => a -> Text
toText Double
intercept Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" + " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
Double -> Text
forall a. ToText a => a -> Text
toText Double
slope Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"x"
instance FromText FeePolicy where
fromText :: Text -> Either TextDecodingError FeePolicy
fromText Text
txt = case Text -> Text -> [Text]
T.splitOn Text
" + " Text
txt of
[Text
a, Text
b] | Int -> Text -> Text
T.takeEnd Int
1 Text
b Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"x" ->
(TextDecodingError -> TextDecodingError)
-> Either TextDecodingError FeePolicy
-> Either TextDecodingError FeePolicy
forall (a :: * -> * -> *) b c d.
ArrowChoice a =>
a b c -> a (Either b d) (Either c d)
left (TextDecodingError -> TextDecodingError -> TextDecodingError
forall a b. a -> b -> a
const TextDecodingError
err) (Either TextDecodingError FeePolicy
-> Either TextDecodingError FeePolicy)
-> Either TextDecodingError FeePolicy
-> Either TextDecodingError FeePolicy
forall a b. (a -> b) -> a -> b
$
(LinearFunction Double -> FeePolicy
LinearFee (LinearFunction Double -> FeePolicy)
-> (Double -> LinearFunction Double) -> Double -> FeePolicy
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Double -> LinearFunction Double) -> Double -> FeePolicy)
-> (Double -> Double -> LinearFunction Double)
-> Double
-> Double
-> FeePolicy
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> Double -> LinearFunction Double
forall a. a -> a -> LinearFunction a
LinearFunction
(Double -> Double -> FeePolicy)
-> Either TextDecodingError Double
-> Either TextDecodingError (Double -> FeePolicy)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Either TextDecodingError Double
forall a. FromText a => Text -> Either TextDecodingError a
fromText Text
a
Either TextDecodingError (Double -> FeePolicy)
-> Either TextDecodingError Double
-> Either TextDecodingError FeePolicy
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Either TextDecodingError Double
forall a. FromText a => Text -> Either TextDecodingError a
fromText (Int -> Text -> Text
T.dropEnd Int
1 Text
b)
[Text]
_ -> TextDecodingError -> Either TextDecodingError FeePolicy
forall a b. a -> Either a b
Left TextDecodingError
err
where
err :: TextDecodingError
err = String -> TextDecodingError
TextDecodingError
String
"Unable to decode FeePolicy: \
\Linear equation not in expected format: a + bx \
\where 'a' and 'b' are numbers"
newtype DerivationIndex
= DerivationIndex Word32
deriving (Int -> DerivationIndex -> ShowS
[DerivationIndex] -> ShowS
DerivationIndex -> String
(Int -> DerivationIndex -> ShowS)
-> (DerivationIndex -> String)
-> ([DerivationIndex] -> ShowS)
-> Show DerivationIndex
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DerivationIndex] -> ShowS
$cshowList :: [DerivationIndex] -> ShowS
show :: DerivationIndex -> String
$cshow :: DerivationIndex -> String
showsPrec :: Int -> DerivationIndex -> ShowS
$cshowsPrec :: Int -> DerivationIndex -> ShowS
Show, DerivationIndex -> DerivationIndex -> Bool
(DerivationIndex -> DerivationIndex -> Bool)
-> (DerivationIndex -> DerivationIndex -> Bool)
-> Eq DerivationIndex
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DerivationIndex -> DerivationIndex -> Bool
$c/= :: DerivationIndex -> DerivationIndex -> Bool
== :: DerivationIndex -> DerivationIndex -> Bool
$c== :: DerivationIndex -> DerivationIndex -> Bool
Eq, Eq DerivationIndex
Eq DerivationIndex
-> (DerivationIndex -> DerivationIndex -> Ordering)
-> (DerivationIndex -> DerivationIndex -> Bool)
-> (DerivationIndex -> DerivationIndex -> Bool)
-> (DerivationIndex -> DerivationIndex -> Bool)
-> (DerivationIndex -> DerivationIndex -> Bool)
-> (DerivationIndex -> DerivationIndex -> DerivationIndex)
-> (DerivationIndex -> DerivationIndex -> DerivationIndex)
-> Ord DerivationIndex
DerivationIndex -> DerivationIndex -> Bool
DerivationIndex -> DerivationIndex -> Ordering
DerivationIndex -> DerivationIndex -> DerivationIndex
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DerivationIndex -> DerivationIndex -> DerivationIndex
$cmin :: DerivationIndex -> DerivationIndex -> DerivationIndex
max :: DerivationIndex -> DerivationIndex -> DerivationIndex
$cmax :: DerivationIndex -> DerivationIndex -> DerivationIndex
>= :: DerivationIndex -> DerivationIndex -> Bool
$c>= :: DerivationIndex -> DerivationIndex -> Bool
> :: DerivationIndex -> DerivationIndex -> Bool
$c> :: DerivationIndex -> DerivationIndex -> Bool
<= :: DerivationIndex -> DerivationIndex -> Bool
$c<= :: DerivationIndex -> DerivationIndex -> Bool
< :: DerivationIndex -> DerivationIndex -> Bool
$c< :: DerivationIndex -> DerivationIndex -> Bool
compare :: DerivationIndex -> DerivationIndex -> Ordering
$ccompare :: DerivationIndex -> DerivationIndex -> Ordering
$cp1Ord :: Eq DerivationIndex
Ord, (forall x. DerivationIndex -> Rep DerivationIndex x)
-> (forall x. Rep DerivationIndex x -> DerivationIndex)
-> Generic DerivationIndex
forall x. Rep DerivationIndex x -> DerivationIndex
forall x. DerivationIndex -> Rep DerivationIndex x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DerivationIndex x -> DerivationIndex
$cfrom :: forall x. DerivationIndex -> Rep DerivationIndex x
Generic)
instance NFData DerivationIndex
instance FromText DerivationIndex where
fromText :: Text -> Either TextDecodingError DerivationIndex
fromText = (Word32 -> DerivationIndex)
-> Either TextDecodingError Word32
-> Either TextDecodingError DerivationIndex
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Word32 -> DerivationIndex
DerivationIndex (Either TextDecodingError Word32
-> Either TextDecodingError DerivationIndex)
-> (Text -> Either TextDecodingError Word32)
-> Text
-> Either TextDecodingError DerivationIndex
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either TextDecodingError Word32
forall a. FromText a => Text -> Either TextDecodingError a
fromText
instance ToText DerivationIndex where
toText :: DerivationIndex -> Text
toText (DerivationIndex Word32
index) = Word32 -> Text
forall a. ToText a => a -> Text
toText Word32
index
data NetworkParameters = NetworkParameters
{ NetworkParameters -> GenesisParameters
genesisParameters :: GenesisParameters
, NetworkParameters -> SlottingParameters
slottingParameters :: SlottingParameters
, NetworkParameters -> ProtocolParameters
protocolParameters :: ProtocolParameters
} deriving ((forall x. NetworkParameters -> Rep NetworkParameters x)
-> (forall x. Rep NetworkParameters x -> NetworkParameters)
-> Generic NetworkParameters
forall x. Rep NetworkParameters x -> NetworkParameters
forall x. NetworkParameters -> Rep NetworkParameters x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NetworkParameters x -> NetworkParameters
$cfrom :: forall x. NetworkParameters -> Rep NetworkParameters x
Generic, Int -> NetworkParameters -> ShowS
[NetworkParameters] -> ShowS
NetworkParameters -> String
(Int -> NetworkParameters -> ShowS)
-> (NetworkParameters -> String)
-> ([NetworkParameters] -> ShowS)
-> Show NetworkParameters
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NetworkParameters] -> ShowS
$cshowList :: [NetworkParameters] -> ShowS
show :: NetworkParameters -> String
$cshow :: NetworkParameters -> String
showsPrec :: Int -> NetworkParameters -> ShowS
$cshowsPrec :: Int -> NetworkParameters -> ShowS
Show, NetworkParameters -> NetworkParameters -> Bool
(NetworkParameters -> NetworkParameters -> Bool)
-> (NetworkParameters -> NetworkParameters -> Bool)
-> Eq NetworkParameters
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NetworkParameters -> NetworkParameters -> Bool
$c/= :: NetworkParameters -> NetworkParameters -> Bool
== :: NetworkParameters -> NetworkParameters -> Bool
$c== :: NetworkParameters -> NetworkParameters -> Bool
Eq)
instance NFData NetworkParameters
instance Buildable NetworkParameters where
build :: NetworkParameters -> Builder
build (NetworkParameters GenesisParameters
gp SlottingParameters
sp ProtocolParameters
pp) = GenesisParameters -> Builder
forall p. Buildable p => p -> Builder
build GenesisParameters
gp Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> SlottingParameters -> Builder
forall p. Buildable p => p -> Builder
build SlottingParameters
sp Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> ProtocolParameters -> Builder
forall p. Buildable p => p -> Builder
build ProtocolParameters
pp
data GenesisParameters = GenesisParameters
{ GenesisParameters -> Hash "Genesis"
getGenesisBlockHash :: Hash "Genesis"
, GenesisParameters -> StartTime
getGenesisBlockDate :: StartTime
} deriving ((forall x. GenesisParameters -> Rep GenesisParameters x)
-> (forall x. Rep GenesisParameters x -> GenesisParameters)
-> Generic GenesisParameters
forall x. Rep GenesisParameters x -> GenesisParameters
forall x. GenesisParameters -> Rep GenesisParameters x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GenesisParameters x -> GenesisParameters
$cfrom :: forall x. GenesisParameters -> Rep GenesisParameters x
Generic, Int -> GenesisParameters -> ShowS
[GenesisParameters] -> ShowS
GenesisParameters -> String
(Int -> GenesisParameters -> ShowS)
-> (GenesisParameters -> String)
-> ([GenesisParameters] -> ShowS)
-> Show GenesisParameters
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GenesisParameters] -> ShowS
$cshowList :: [GenesisParameters] -> ShowS
show :: GenesisParameters -> String
$cshow :: GenesisParameters -> String
showsPrec :: Int -> GenesisParameters -> ShowS
$cshowsPrec :: Int -> GenesisParameters -> ShowS
Show, GenesisParameters -> GenesisParameters -> Bool
(GenesisParameters -> GenesisParameters -> Bool)
-> (GenesisParameters -> GenesisParameters -> Bool)
-> Eq GenesisParameters
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GenesisParameters -> GenesisParameters -> Bool
$c/= :: GenesisParameters -> GenesisParameters -> Bool
== :: GenesisParameters -> GenesisParameters -> Bool
$c== :: GenesisParameters -> GenesisParameters -> Bool
Eq)
instance NFData GenesisParameters
instance Buildable GenesisParameters where
build :: GenesisParameters -> Builder
build GenesisParameters
gp = Text -> (Builder -> Builder) -> [Builder] -> Builder
forall (f :: * -> *) a.
Foldable f =>
Text -> (a -> Builder) -> f a -> Builder
blockListF' Text
"" Builder -> Builder
forall a. a -> a
id
[ Builder
"Genesis block hash: " Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Hash "Genesis" -> Builder
forall (tag :: Symbol). Hash tag -> Builder
genesisF (GenesisParameters -> Hash "Genesis"
getGenesisBlockHash GenesisParameters
gp)
, Builder
"Genesis block date: " Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> StartTime -> Builder
startTimeF (GenesisParameters -> StartTime
getGenesisBlockDate
(GenesisParameters
gp :: GenesisParameters))
]
where
genesisF :: Hash tag -> Builder
genesisF = Text -> Builder
forall p. Buildable p => p -> Builder
build (Text -> Builder) -> (Hash tag -> Text) -> Hash tag -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
T.decodeUtf8 (ByteString -> Text)
-> (Hash tag -> ByteString) -> Hash tag -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Base -> ByteString -> ByteString
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
Base -> bin -> bout
convertToBase Base
Base16 (ByteString -> ByteString)
-> (Hash tag -> ByteString) -> Hash tag -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash tag -> ByteString
forall (tag :: Symbol). Hash tag -> ByteString
getHash
startTimeF :: StartTime -> Builder
startTimeF (StartTime UTCTime
s) = UTCTime -> Builder
forall p. Buildable p => p -> Builder
build UTCTime
s
data SlottingParameters = SlottingParameters
{ SlottingParameters -> SlotLength
getSlotLength :: SlotLength
, SlottingParameters -> EpochLength
getEpochLength :: EpochLength
, SlottingParameters -> ActiveSlotCoefficient
getActiveSlotCoefficient :: ActiveSlotCoefficient
, SlottingParameters -> Quantity "block" Word32
getSecurityParameter :: Quantity "block" Word32
} deriving ((forall x. SlottingParameters -> Rep SlottingParameters x)
-> (forall x. Rep SlottingParameters x -> SlottingParameters)
-> Generic SlottingParameters
forall x. Rep SlottingParameters x -> SlottingParameters
forall x. SlottingParameters -> Rep SlottingParameters x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SlottingParameters x -> SlottingParameters
$cfrom :: forall x. SlottingParameters -> Rep SlottingParameters x
Generic, Int -> SlottingParameters -> ShowS
[SlottingParameters] -> ShowS
SlottingParameters -> String
(Int -> SlottingParameters -> ShowS)
-> (SlottingParameters -> String)
-> ([SlottingParameters] -> ShowS)
-> Show SlottingParameters
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SlottingParameters] -> ShowS
$cshowList :: [SlottingParameters] -> ShowS
show :: SlottingParameters -> String
$cshow :: SlottingParameters -> String
showsPrec :: Int -> SlottingParameters -> ShowS
$cshowsPrec :: Int -> SlottingParameters -> ShowS
Show, SlottingParameters -> SlottingParameters -> Bool
(SlottingParameters -> SlottingParameters -> Bool)
-> (SlottingParameters -> SlottingParameters -> Bool)
-> Eq SlottingParameters
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SlottingParameters -> SlottingParameters -> Bool
$c/= :: SlottingParameters -> SlottingParameters -> Bool
== :: SlottingParameters -> SlottingParameters -> Bool
$c== :: SlottingParameters -> SlottingParameters -> Bool
Eq)
instance NFData SlottingParameters
stabilityWindowByron :: SlottingParameters -> Quantity "block" Word64
stabilityWindowByron :: SlottingParameters -> Quantity "block" Word64
stabilityWindowByron SlottingParameters
sp = Word64 -> Quantity "block" Word64
forall (unit :: Symbol) a. a -> Quantity unit a
Quantity (Word64
2 Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
* Word64
k)
where
k :: Word64
k = Word32 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Word64) -> Word32 -> Word64
forall a b. (a -> b) -> a -> b
$ Quantity "block" Word32 -> Word32
forall (unit :: Symbol) a. Quantity unit a -> a
getQuantity (Quantity "block" Word32 -> Word32)
-> Quantity "block" Word32 -> Word32
forall a b. (a -> b) -> a -> b
$ SlottingParameters -> Quantity "block" Word32
getSecurityParameter SlottingParameters
sp
stabilityWindowShelley :: SlottingParameters -> Quantity "block" Word64
stabilityWindowShelley :: SlottingParameters -> Quantity "block" Word64
stabilityWindowShelley SlottingParameters
sp = Word64 -> Quantity "block" Word64
forall (unit :: Symbol) a. a -> Quantity unit a
Quantity Word64
len
where
len :: Word64
len = Double -> Word64
forall a b. (RealFrac a, Integral b) => a -> b
ceiling (Double
3 Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
k Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
f)
k :: Double
k = Word32 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Double) -> Word32 -> Double
forall a b. (a -> b) -> a -> b
$ Quantity "block" Word32 -> Word32
forall (unit :: Symbol) a. Quantity unit a -> a
getQuantity (Quantity "block" Word32 -> Word32)
-> Quantity "block" Word32 -> Word32
forall a b. (a -> b) -> a -> b
$ SlottingParameters -> Quantity "block" Word32
getSecurityParameter SlottingParameters
sp
f :: Double
f = ActiveSlotCoefficient -> Double
unActiveSlotCoefficient (ActiveSlotCoefficient -> Double)
-> ActiveSlotCoefficient -> Double
forall a b. (a -> b) -> a -> b
$ SlottingParameters -> ActiveSlotCoefficient
getActiveSlotCoefficient SlottingParameters
sp
instance Buildable SlottingParameters where
build :: SlottingParameters -> Builder
build SlottingParameters
sp = Text -> (Builder -> Builder) -> [Builder] -> Builder
forall (f :: * -> *) a.
Foldable f =>
Text -> (a -> Builder) -> f a -> Builder
blockListF' Text
"" Builder -> Builder
forall a. a -> a
id
[ Builder
"Slot length: " Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> SlotLength -> Builder
slotLengthF (SlottingParameters -> SlotLength
getSlotLength SlottingParameters
sp)
, Builder
"Epoch length: " Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> EpochLength -> Builder
epochLengthF (SlottingParameters -> EpochLength
getEpochLength SlottingParameters
sp)
, Builder
"Active slot coeff: " Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> ActiveSlotCoefficient -> Builder
forall p. Buildable p => p -> Builder
build (SlottingParameters
sp SlottingParameters
-> ((ActiveSlotCoefficient
-> Const ActiveSlotCoefficient ActiveSlotCoefficient)
-> SlottingParameters
-> Const ActiveSlotCoefficient SlottingParameters)
-> ActiveSlotCoefficient
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. IsLabel
"getActiveSlotCoefficient"
((ActiveSlotCoefficient
-> Const ActiveSlotCoefficient ActiveSlotCoefficient)
-> SlottingParameters
-> Const ActiveSlotCoefficient SlottingParameters)
(ActiveSlotCoefficient
-> Const ActiveSlotCoefficient ActiveSlotCoefficient)
-> SlottingParameters
-> Const ActiveSlotCoefficient SlottingParameters
#getActiveSlotCoefficient)
, Builder
"Security parameter: " Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Quantity "block" Word32 -> Builder
forall p. Buildable p => p -> Builder
build (SlottingParameters
sp SlottingParameters
-> ((Quantity "block" Word32
-> Const (Quantity "block" Word32) (Quantity "block" Word32))
-> SlottingParameters
-> Const (Quantity "block" Word32) SlottingParameters)
-> Quantity "block" Word32
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. IsLabel
"getSecurityParameter"
((Quantity "block" Word32
-> Const (Quantity "block" Word32) (Quantity "block" Word32))
-> SlottingParameters
-> Const (Quantity "block" Word32) SlottingParameters)
(Quantity "block" Word32
-> Const (Quantity "block" Word32) (Quantity "block" Word32))
-> SlottingParameters
-> Const (Quantity "block" Word32) SlottingParameters
#getSecurityParameter)
]
where
slotLengthF :: SlotLength -> Builder
slotLengthF (SlotLength NominalDiffTime
s) = NominalDiffTime -> Builder
forall p. Buildable p => p -> Builder
build NominalDiffTime
s
epochLengthF :: EpochLength -> Builder
epochLengthF (EpochLength Word32
s) = Word32 -> Builder
forall p. Buildable p => p -> Builder
build Word32
s
newtype ActiveSlotCoefficient
= ActiveSlotCoefficient { ActiveSlotCoefficient -> Double
unActiveSlotCoefficient :: Double }
deriving stock ((forall x. ActiveSlotCoefficient -> Rep ActiveSlotCoefficient x)
-> (forall x. Rep ActiveSlotCoefficient x -> ActiveSlotCoefficient)
-> Generic ActiveSlotCoefficient
forall x. Rep ActiveSlotCoefficient x -> ActiveSlotCoefficient
forall x. ActiveSlotCoefficient -> Rep ActiveSlotCoefficient x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ActiveSlotCoefficient x -> ActiveSlotCoefficient
$cfrom :: forall x. ActiveSlotCoefficient -> Rep ActiveSlotCoefficient x
Generic, ActiveSlotCoefficient -> ActiveSlotCoefficient -> Bool
(ActiveSlotCoefficient -> ActiveSlotCoefficient -> Bool)
-> (ActiveSlotCoefficient -> ActiveSlotCoefficient -> Bool)
-> Eq ActiveSlotCoefficient
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ActiveSlotCoefficient -> ActiveSlotCoefficient -> Bool
$c/= :: ActiveSlotCoefficient -> ActiveSlotCoefficient -> Bool
== :: ActiveSlotCoefficient -> ActiveSlotCoefficient -> Bool
$c== :: ActiveSlotCoefficient -> ActiveSlotCoefficient -> Bool
Eq, Int -> ActiveSlotCoefficient -> ShowS
[ActiveSlotCoefficient] -> ShowS
ActiveSlotCoefficient -> String
(Int -> ActiveSlotCoefficient -> ShowS)
-> (ActiveSlotCoefficient -> String)
-> ([ActiveSlotCoefficient] -> ShowS)
-> Show ActiveSlotCoefficient
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ActiveSlotCoefficient] -> ShowS
$cshowList :: [ActiveSlotCoefficient] -> ShowS
show :: ActiveSlotCoefficient -> String
$cshow :: ActiveSlotCoefficient -> String
showsPrec :: Int -> ActiveSlotCoefficient -> ShowS
$cshowsPrec :: Int -> ActiveSlotCoefficient -> ShowS
Show)
deriving newtype (ActiveSlotCoefficient -> Builder
(ActiveSlotCoefficient -> Builder)
-> Buildable ActiveSlotCoefficient
forall p. (p -> Builder) -> Buildable p
build :: ActiveSlotCoefficient -> Builder
$cbuild :: ActiveSlotCoefficient -> Builder
Buildable, Integer -> ActiveSlotCoefficient
ActiveSlotCoefficient -> ActiveSlotCoefficient
ActiveSlotCoefficient
-> ActiveSlotCoefficient -> ActiveSlotCoefficient
(ActiveSlotCoefficient
-> ActiveSlotCoefficient -> ActiveSlotCoefficient)
-> (ActiveSlotCoefficient
-> ActiveSlotCoefficient -> ActiveSlotCoefficient)
-> (ActiveSlotCoefficient
-> ActiveSlotCoefficient -> ActiveSlotCoefficient)
-> (ActiveSlotCoefficient -> ActiveSlotCoefficient)
-> (ActiveSlotCoefficient -> ActiveSlotCoefficient)
-> (ActiveSlotCoefficient -> ActiveSlotCoefficient)
-> (Integer -> ActiveSlotCoefficient)
-> Num ActiveSlotCoefficient
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> ActiveSlotCoefficient
$cfromInteger :: Integer -> ActiveSlotCoefficient
signum :: ActiveSlotCoefficient -> ActiveSlotCoefficient
$csignum :: ActiveSlotCoefficient -> ActiveSlotCoefficient
abs :: ActiveSlotCoefficient -> ActiveSlotCoefficient
$cabs :: ActiveSlotCoefficient -> ActiveSlotCoefficient
negate :: ActiveSlotCoefficient -> ActiveSlotCoefficient
$cnegate :: ActiveSlotCoefficient -> ActiveSlotCoefficient
* :: ActiveSlotCoefficient
-> ActiveSlotCoefficient -> ActiveSlotCoefficient
$c* :: ActiveSlotCoefficient
-> ActiveSlotCoefficient -> ActiveSlotCoefficient
- :: ActiveSlotCoefficient
-> ActiveSlotCoefficient -> ActiveSlotCoefficient
$c- :: ActiveSlotCoefficient
-> ActiveSlotCoefficient -> ActiveSlotCoefficient
+ :: ActiveSlotCoefficient
-> ActiveSlotCoefficient -> ActiveSlotCoefficient
$c+ :: ActiveSlotCoefficient
-> ActiveSlotCoefficient -> ActiveSlotCoefficient
Num, Num ActiveSlotCoefficient
Num ActiveSlotCoefficient
-> (ActiveSlotCoefficient
-> ActiveSlotCoefficient -> ActiveSlotCoefficient)
-> (ActiveSlotCoefficient -> ActiveSlotCoefficient)
-> (Rational -> ActiveSlotCoefficient)
-> Fractional ActiveSlotCoefficient
Rational -> ActiveSlotCoefficient
ActiveSlotCoefficient -> ActiveSlotCoefficient
ActiveSlotCoefficient
-> ActiveSlotCoefficient -> ActiveSlotCoefficient
forall a.
Num a
-> (a -> a -> a) -> (a -> a) -> (Rational -> a) -> Fractional a
fromRational :: Rational -> ActiveSlotCoefficient
$cfromRational :: Rational -> ActiveSlotCoefficient
recip :: ActiveSlotCoefficient -> ActiveSlotCoefficient
$crecip :: ActiveSlotCoefficient -> ActiveSlotCoefficient
/ :: ActiveSlotCoefficient
-> ActiveSlotCoefficient -> ActiveSlotCoefficient
$c/ :: ActiveSlotCoefficient
-> ActiveSlotCoefficient -> ActiveSlotCoefficient
$cp1Fractional :: Num ActiveSlotCoefficient
Fractional)
instance NFData ActiveSlotCoefficient
data EraInfo info = EraInfo
{ EraInfo info -> Maybe info
byron :: Maybe info
, EraInfo info -> Maybe info
shelley :: Maybe info
, EraInfo info -> Maybe info
allegra :: Maybe info
, EraInfo info -> Maybe info
mary :: Maybe info
, EraInfo info -> Maybe info
alonzo :: Maybe info
, EraInfo info -> Maybe info
babbage :: Maybe info
} deriving (EraInfo info -> EraInfo info -> Bool
(EraInfo info -> EraInfo info -> Bool)
-> (EraInfo info -> EraInfo info -> Bool) -> Eq (EraInfo info)
forall info. Eq info => EraInfo info -> EraInfo info -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EraInfo info -> EraInfo info -> Bool
$c/= :: forall info. Eq info => EraInfo info -> EraInfo info -> Bool
== :: EraInfo info -> EraInfo info -> Bool
$c== :: forall info. Eq info => EraInfo info -> EraInfo info -> Bool
Eq, (forall x. EraInfo info -> Rep (EraInfo info) x)
-> (forall x. Rep (EraInfo info) x -> EraInfo info)
-> Generic (EraInfo info)
forall x. Rep (EraInfo info) x -> EraInfo info
forall x. EraInfo info -> Rep (EraInfo info) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall info x. Rep (EraInfo info) x -> EraInfo info
forall info x. EraInfo info -> Rep (EraInfo info) x
$cto :: forall info x. Rep (EraInfo info) x -> EraInfo info
$cfrom :: forall info x. EraInfo info -> Rep (EraInfo info) x
Generic, Int -> EraInfo info -> ShowS
[EraInfo info] -> ShowS
EraInfo info -> String
(Int -> EraInfo info -> ShowS)
-> (EraInfo info -> String)
-> ([EraInfo info] -> ShowS)
-> Show (EraInfo info)
forall info. Show info => Int -> EraInfo info -> ShowS
forall info. Show info => [EraInfo info] -> ShowS
forall info. Show info => EraInfo info -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EraInfo info] -> ShowS
$cshowList :: forall info. Show info => [EraInfo info] -> ShowS
show :: EraInfo info -> String
$cshow :: forall info. Show info => EraInfo info -> String
showsPrec :: Int -> EraInfo info -> ShowS
$cshowsPrec :: forall info. Show info => Int -> EraInfo info -> ShowS
Show, a -> EraInfo b -> EraInfo a
(a -> b) -> EraInfo a -> EraInfo b
(forall a b. (a -> b) -> EraInfo a -> EraInfo b)
-> (forall a b. a -> EraInfo b -> EraInfo a) -> Functor EraInfo
forall a b. a -> EraInfo b -> EraInfo a
forall a b. (a -> b) -> EraInfo a -> EraInfo b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> EraInfo b -> EraInfo a
$c<$ :: forall a b. a -> EraInfo b -> EraInfo a
fmap :: (a -> b) -> EraInfo a -> EraInfo b
$cfmap :: forall a b. (a -> b) -> EraInfo a -> EraInfo b
Functor)
emptyEraInfo :: EraInfo info
emptyEraInfo :: EraInfo info
emptyEraInfo = Maybe info
-> Maybe info
-> Maybe info
-> Maybe info
-> Maybe info
-> Maybe info
-> EraInfo info
forall info.
Maybe info
-> Maybe info
-> Maybe info
-> Maybe info
-> Maybe info
-> Maybe info
-> EraInfo info
EraInfo Maybe info
forall a. Maybe a
Nothing Maybe info
forall a. Maybe a
Nothing Maybe info
forall a. Maybe a
Nothing Maybe info
forall a. Maybe a
Nothing Maybe info
forall a. Maybe a
Nothing Maybe info
forall a. Maybe a
Nothing
instance NFData info => NFData (EraInfo info)
instance Buildable (EraInfo EpochNo) where
build :: EraInfo EpochNo -> Builder
build (EraInfo Maybe EpochNo
byron Maybe EpochNo
shelley Maybe EpochNo
allegra Maybe EpochNo
mary Maybe EpochNo
alonzo Maybe EpochNo
babbage) =
Text -> (Builder -> Builder) -> [Builder] -> Builder
forall (f :: * -> *) a.
Foldable f =>
Text -> (a -> Builder) -> f a -> Builder
blockListF' Text
"-" Builder -> Builder
forall a. a -> a
id
[ Builder
"byron" Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Maybe EpochNo -> Builder
forall p. Buildable p => Maybe p -> Builder
boundF Maybe EpochNo
byron
, Builder
"shelley" Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Maybe EpochNo -> Builder
forall p. Buildable p => Maybe p -> Builder
boundF Maybe EpochNo
shelley
, Builder
"allegra" Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Maybe EpochNo -> Builder
forall p. Buildable p => Maybe p -> Builder
boundF Maybe EpochNo
allegra
, Builder
"mary" Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Maybe EpochNo -> Builder
forall p. Buildable p => Maybe p -> Builder
boundF Maybe EpochNo
mary
, Builder
"alonzo" Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Maybe EpochNo -> Builder
forall p. Buildable p => Maybe p -> Builder
boundF Maybe EpochNo
alonzo
, Builder
"babbage" Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Maybe EpochNo -> Builder
forall p. Buildable p => Maybe p -> Builder
boundF Maybe EpochNo
babbage
]
where
boundF :: Maybe p -> Builder
boundF (Just p
e) = Builder
" from " Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> p -> Builder
forall p. Buildable p => p -> Builder
build p
e
boundF Maybe p
Nothing = Builder
" <not started>"
data ProtocolParameters = ProtocolParameters
{ ProtocolParameters -> DecentralizationLevel
decentralizationLevel
:: DecentralizationLevel
, ProtocolParameters -> TxParameters
txParameters
:: TxParameters
, ProtocolParameters -> Word16
desiredNumberOfStakePools
:: Word16
, ProtocolParameters -> MinimumUTxO
minimumUTxO
:: MinimumUTxO
, ProtocolParameters -> Coin
stakeKeyDeposit
:: Coin
, ProtocolParameters -> EraInfo EpochNo
eras
:: EraInfo EpochNo
, ProtocolParameters -> Word16
maximumCollateralInputCount
:: Word16
, ProtocolParameters -> Natural
minimumCollateralPercentage
:: Natural
, ProtocolParameters -> Maybe ExecutionUnitPrices
executionUnitPrices
:: Maybe ExecutionUnitPrices
, ProtocolParameters -> Maybe ProtocolParameters
currentNodeProtocolParameters
:: Maybe Node.ProtocolParameters
} deriving (ProtocolParameters -> ProtocolParameters -> Bool
(ProtocolParameters -> ProtocolParameters -> Bool)
-> (ProtocolParameters -> ProtocolParameters -> Bool)
-> Eq ProtocolParameters
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ProtocolParameters -> ProtocolParameters -> Bool
$c/= :: ProtocolParameters -> ProtocolParameters -> Bool
== :: ProtocolParameters -> ProtocolParameters -> Bool
$c== :: ProtocolParameters -> ProtocolParameters -> Bool
Eq, (forall x. ProtocolParameters -> Rep ProtocolParameters x)
-> (forall x. Rep ProtocolParameters x -> ProtocolParameters)
-> Generic ProtocolParameters
forall x. Rep ProtocolParameters x -> ProtocolParameters
forall x. ProtocolParameters -> Rep ProtocolParameters x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ProtocolParameters x -> ProtocolParameters
$cfrom :: forall x. ProtocolParameters -> Rep ProtocolParameters x
Generic, Int -> ProtocolParameters -> ShowS
[ProtocolParameters] -> ShowS
ProtocolParameters -> String
(Int -> ProtocolParameters -> ShowS)
-> (ProtocolParameters -> String)
-> ([ProtocolParameters] -> ShowS)
-> Show ProtocolParameters
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ProtocolParameters] -> ShowS
$cshowList :: [ProtocolParameters] -> ShowS
show :: ProtocolParameters -> String
$cshow :: ProtocolParameters -> String
showsPrec :: Int -> ProtocolParameters -> ShowS
$cshowsPrec :: Int -> ProtocolParameters -> ShowS
Show)
instance NFData ProtocolParameters where
rnf :: ProtocolParameters -> ()
rnf ProtocolParameters {Natural
Maybe ProtocolParameters
Maybe ExecutionUnitPrices
Word16
Coin
MinimumUTxO
TxParameters
DecentralizationLevel
EraInfo EpochNo
currentNodeProtocolParameters :: Maybe ProtocolParameters
executionUnitPrices :: Maybe ExecutionUnitPrices
minimumCollateralPercentage :: Natural
maximumCollateralInputCount :: Word16
eras :: EraInfo EpochNo
stakeKeyDeposit :: Coin
minimumUTxO :: MinimumUTxO
desiredNumberOfStakePools :: Word16
txParameters :: TxParameters
decentralizationLevel :: DecentralizationLevel
$sel:currentNodeProtocolParameters:ProtocolParameters :: ProtocolParameters -> Maybe ProtocolParameters
$sel:executionUnitPrices:ProtocolParameters :: ProtocolParameters -> Maybe ExecutionUnitPrices
$sel:minimumCollateralPercentage:ProtocolParameters :: ProtocolParameters -> Natural
$sel:maximumCollateralInputCount:ProtocolParameters :: ProtocolParameters -> Word16
$sel:eras:ProtocolParameters :: ProtocolParameters -> EraInfo EpochNo
$sel:stakeKeyDeposit:ProtocolParameters :: ProtocolParameters -> Coin
$sel:minimumUTxO:ProtocolParameters :: ProtocolParameters -> MinimumUTxO
$sel:desiredNumberOfStakePools:ProtocolParameters :: ProtocolParameters -> Word16
$sel:txParameters:ProtocolParameters :: ProtocolParameters -> TxParameters
$sel:decentralizationLevel:ProtocolParameters :: ProtocolParameters -> DecentralizationLevel
..} = [()] -> ()
forall a. Monoid a => [a] -> a
mconcat
[ DecentralizationLevel -> ()
forall a. NFData a => a -> ()
rnf DecentralizationLevel
decentralizationLevel
, TxParameters -> ()
forall a. NFData a => a -> ()
rnf TxParameters
txParameters
, Word16 -> ()
forall a. NFData a => a -> ()
rnf Word16
desiredNumberOfStakePools
, MinimumUTxO -> ()
forall a. NFData a => a -> ()
rnf MinimumUTxO
minimumUTxO
, Coin -> ()
forall a. NFData a => a -> ()
rnf Coin
stakeKeyDeposit
, EraInfo EpochNo -> ()
forall a. NFData a => a -> ()
rnf EraInfo EpochNo
eras
, Word16 -> ()
forall a. NFData a => a -> ()
rnf Word16
maximumCollateralInputCount
, Natural -> ()
forall a. NFData a => a -> ()
rnf Natural
minimumCollateralPercentage
, Maybe ExecutionUnitPrices -> ()
forall a. NFData a => a -> ()
rnf Maybe ExecutionUnitPrices
executionUnitPrices
]
instance Buildable ProtocolParameters where
build :: ProtocolParameters -> Builder
build ProtocolParameters
pp = Text -> (Builder -> Builder) -> [Builder] -> Builder
forall (f :: * -> *) a.
Foldable f =>
Text -> (a -> Builder) -> f a -> Builder
blockListF' Text
"" Builder -> Builder
forall a. a -> a
id
[ Builder
"Decentralization level: "
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> DecentralizationLevel -> Builder
forall p. Buildable p => p -> Builder
build (ProtocolParameters
pp ProtocolParameters
-> ((DecentralizationLevel
-> Const DecentralizationLevel DecentralizationLevel)
-> ProtocolParameters
-> Const DecentralizationLevel ProtocolParameters)
-> DecentralizationLevel
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. IsLabel
"decentralizationLevel"
((DecentralizationLevel
-> Const DecentralizationLevel DecentralizationLevel)
-> ProtocolParameters
-> Const DecentralizationLevel ProtocolParameters)
(DecentralizationLevel
-> Const DecentralizationLevel DecentralizationLevel)
-> ProtocolParameters
-> Const DecentralizationLevel ProtocolParameters
#decentralizationLevel)
, Builder
"Transaction parameters: "
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> TxParameters -> Builder
forall p. Buildable p => p -> Builder
build (ProtocolParameters
pp ProtocolParameters
-> ((TxParameters -> Const TxParameters TxParameters)
-> ProtocolParameters -> Const TxParameters ProtocolParameters)
-> TxParameters
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. IsLabel
"txParameters"
((TxParameters -> Const TxParameters TxParameters)
-> ProtocolParameters -> Const TxParameters ProtocolParameters)
(TxParameters -> Const TxParameters TxParameters)
-> ProtocolParameters -> Const TxParameters ProtocolParameters
#txParameters)
, Builder
"Desired number of pools: "
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Word16 -> Builder
forall p. Buildable p => p -> Builder
build (ProtocolParameters
pp ProtocolParameters
-> ((Word16 -> Const Word16 Word16)
-> ProtocolParameters -> Const Word16 ProtocolParameters)
-> Word16
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. IsLabel
"desiredNumberOfStakePools"
((Word16 -> Const Word16 Word16)
-> ProtocolParameters -> Const Word16 ProtocolParameters)
(Word16 -> Const Word16 Word16)
-> ProtocolParameters -> Const Word16 ProtocolParameters
#desiredNumberOfStakePools)
, Builder
"Minimum UTxO: "
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> MinimumUTxO -> Builder
forall p. Buildable p => p -> Builder
build (ProtocolParameters
pp ProtocolParameters
-> ((MinimumUTxO -> Const MinimumUTxO MinimumUTxO)
-> ProtocolParameters -> Const MinimumUTxO ProtocolParameters)
-> MinimumUTxO
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. IsLabel
"minimumUTxO"
((MinimumUTxO -> Const MinimumUTxO MinimumUTxO)
-> ProtocolParameters -> Const MinimumUTxO ProtocolParameters)
(MinimumUTxO -> Const MinimumUTxO MinimumUTxO)
-> ProtocolParameters -> Const MinimumUTxO ProtocolParameters
#minimumUTxO)
, Builder
"Eras:\n"
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Int -> Builder -> Builder
indentF Int
2 (EraInfo EpochNo -> Builder
forall p. Buildable p => p -> Builder
build (ProtocolParameters
pp ProtocolParameters
-> ((EraInfo EpochNo -> Const (EraInfo EpochNo) (EraInfo EpochNo))
-> ProtocolParameters
-> Const (EraInfo EpochNo) ProtocolParameters)
-> EraInfo EpochNo
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. IsLabel
"eras"
((EraInfo EpochNo -> Const (EraInfo EpochNo) (EraInfo EpochNo))
-> ProtocolParameters
-> Const (EraInfo EpochNo) ProtocolParameters)
(EraInfo EpochNo -> Const (EraInfo EpochNo) (EraInfo EpochNo))
-> ProtocolParameters -> Const (EraInfo EpochNo) ProtocolParameters
#eras))
, Builder
"Execution unit prices: "
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
-> (ExecutionUnitPrices -> Builder)
-> Maybe ExecutionUnitPrices
-> Builder
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Builder
"not specified" ExecutionUnitPrices -> Builder
forall p. Buildable p => p -> Builder
build (ProtocolParameters
pp ProtocolParameters
-> ((Maybe ExecutionUnitPrices
-> Const (Maybe ExecutionUnitPrices) (Maybe ExecutionUnitPrices))
-> ProtocolParameters
-> Const (Maybe ExecutionUnitPrices) ProtocolParameters)
-> Maybe ExecutionUnitPrices
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. IsLabel
"executionUnitPrices"
((Maybe ExecutionUnitPrices
-> Const (Maybe ExecutionUnitPrices) (Maybe ExecutionUnitPrices))
-> ProtocolParameters
-> Const (Maybe ExecutionUnitPrices) ProtocolParameters)
(Maybe ExecutionUnitPrices
-> Const (Maybe ExecutionUnitPrices) (Maybe ExecutionUnitPrices))
-> ProtocolParameters
-> Const (Maybe ExecutionUnitPrices) ProtocolParameters
#executionUnitPrices)
]
data ExecutionUnits = ExecutionUnits
{ ExecutionUnits -> Natural
executionSteps
:: Natural
, ExecutionUnits -> Natural
executionMemory
:: Natural
} deriving (ExecutionUnits -> ExecutionUnits -> Bool
(ExecutionUnits -> ExecutionUnits -> Bool)
-> (ExecutionUnits -> ExecutionUnits -> Bool) -> Eq ExecutionUnits
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExecutionUnits -> ExecutionUnits -> Bool
$c/= :: ExecutionUnits -> ExecutionUnits -> Bool
== :: ExecutionUnits -> ExecutionUnits -> Bool
$c== :: ExecutionUnits -> ExecutionUnits -> Bool
Eq, (forall x. ExecutionUnits -> Rep ExecutionUnits x)
-> (forall x. Rep ExecutionUnits x -> ExecutionUnits)
-> Generic ExecutionUnits
forall x. Rep ExecutionUnits x -> ExecutionUnits
forall x. ExecutionUnits -> Rep ExecutionUnits x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ExecutionUnits x -> ExecutionUnits
$cfrom :: forall x. ExecutionUnits -> Rep ExecutionUnits x
Generic, Int -> ExecutionUnits -> ShowS
[ExecutionUnits] -> ShowS
ExecutionUnits -> String
(Int -> ExecutionUnits -> ShowS)
-> (ExecutionUnits -> String)
-> ([ExecutionUnits] -> ShowS)
-> Show ExecutionUnits
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExecutionUnits] -> ShowS
$cshowList :: [ExecutionUnits] -> ShowS
show :: ExecutionUnits -> String
$cshow :: ExecutionUnits -> String
showsPrec :: Int -> ExecutionUnits -> ShowS
$cshowsPrec :: Int -> ExecutionUnits -> ShowS
Show)
instance NFData ExecutionUnits
instance Buildable ExecutionUnits where
build :: ExecutionUnits -> Builder
build (ExecutionUnits Natural
steps Natural
mem) =
String -> Builder
forall p. Buildable p => p -> Builder
build (String -> Builder) -> String -> Builder
forall a b. (a -> b) -> a -> b
$ String
"max steps: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Natural -> String
forall a. Show a => a -> String
show Natural
steps String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
", max memory: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Natural -> String
forall a. Show a => a -> String
show Natural
mem
data ExecutionUnitPrices = ExecutionUnitPrices
{ ExecutionUnitPrices -> Rational
pricePerStep :: Rational
, ExecutionUnitPrices -> Rational
pricePerMemoryUnit :: Rational
} deriving (ExecutionUnitPrices -> ExecutionUnitPrices -> Bool
(ExecutionUnitPrices -> ExecutionUnitPrices -> Bool)
-> (ExecutionUnitPrices -> ExecutionUnitPrices -> Bool)
-> Eq ExecutionUnitPrices
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExecutionUnitPrices -> ExecutionUnitPrices -> Bool
$c/= :: ExecutionUnitPrices -> ExecutionUnitPrices -> Bool
== :: ExecutionUnitPrices -> ExecutionUnitPrices -> Bool
$c== :: ExecutionUnitPrices -> ExecutionUnitPrices -> Bool
Eq, (forall x. ExecutionUnitPrices -> Rep ExecutionUnitPrices x)
-> (forall x. Rep ExecutionUnitPrices x -> ExecutionUnitPrices)
-> Generic ExecutionUnitPrices
forall x. Rep ExecutionUnitPrices x -> ExecutionUnitPrices
forall x. ExecutionUnitPrices -> Rep ExecutionUnitPrices x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ExecutionUnitPrices x -> ExecutionUnitPrices
$cfrom :: forall x. ExecutionUnitPrices -> Rep ExecutionUnitPrices x
Generic, Int -> ExecutionUnitPrices -> ShowS
[ExecutionUnitPrices] -> ShowS
ExecutionUnitPrices -> String
(Int -> ExecutionUnitPrices -> ShowS)
-> (ExecutionUnitPrices -> String)
-> ([ExecutionUnitPrices] -> ShowS)
-> Show ExecutionUnitPrices
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExecutionUnitPrices] -> ShowS
$cshowList :: [ExecutionUnitPrices] -> ShowS
show :: ExecutionUnitPrices -> String
$cshow :: ExecutionUnitPrices -> String
showsPrec :: Int -> ExecutionUnitPrices -> ShowS
$cshowsPrec :: Int -> ExecutionUnitPrices -> ShowS
Show)
instance NFData ExecutionUnitPrices
instance Buildable ExecutionUnitPrices where
build :: ExecutionUnitPrices -> Builder
build ExecutionUnitPrices {Rational
pricePerStep :: Rational
$sel:pricePerStep:ExecutionUnitPrices :: ExecutionUnitPrices -> Rational
pricePerStep, Rational
pricePerMemoryUnit :: Rational
$sel:pricePerMemoryUnit:ExecutionUnitPrices :: ExecutionUnitPrices -> Rational
pricePerMemoryUnit} =
String -> Builder
forall p. Buildable p => p -> Builder
build (String -> Builder) -> String -> Builder
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall a. Monoid a => [a] -> a
mconcat
[ Rational -> String
forall a. Show a => a -> String
show Rational
pricePerStep
, String
" per step, "
, Rational -> String
forall a. Show a => a -> String
show Rational
pricePerMemoryUnit
, String
" per memory unit"
]
instance ToJSON ExecutionUnitPrices where
toJSON :: ExecutionUnitPrices -> Value
toJSON ExecutionUnitPrices {Rational
pricePerStep :: Rational
$sel:pricePerStep:ExecutionUnitPrices :: ExecutionUnitPrices -> Rational
pricePerStep, Rational
pricePerMemoryUnit :: Rational
$sel:pricePerMemoryUnit:ExecutionUnitPrices :: ExecutionUnitPrices -> Rational
pricePerMemoryUnit} =
[Pair] -> Value
object
[ Key
"step_price"
Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Rational -> Value
toRationalJSON Rational
pricePerStep
, Key
"memory_unit_price"
Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Rational -> Value
toRationalJSON Rational
pricePerMemoryUnit
]
where
toRationalJSON :: Rational -> Value
toRationalJSON :: Rational -> Value
toRationalJSON Rational
r = case Int
-> Rational
-> Either (Scientific, Rational) (Scientific, Maybe Int)
fromRationalRepetendLimited Int
20 Rational
r of
Right (Scientific
s, Maybe Int
Nothing) -> Scientific -> Value
forall a. ToJSON a => a -> Value
toJSON Scientific
s
Either (Scientific, Rational) (Scientific, Maybe Int)
_ -> Rational -> Value
forall a. ToJSON a => a -> Value
toJSON Rational
r
instance FromJSON ExecutionUnitPrices where
parseJSON :: Value -> Parser ExecutionUnitPrices
parseJSON = String
-> (Object -> Parser ExecutionUnitPrices)
-> Value
-> Parser ExecutionUnitPrices
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ExecutionUnitPrices" ((Object -> Parser ExecutionUnitPrices)
-> Value -> Parser ExecutionUnitPrices)
-> (Object -> Parser ExecutionUnitPrices)
-> Value
-> Parser ExecutionUnitPrices
forall a b. (a -> b) -> a -> b
$ \Object
o ->
Rational -> Rational -> ExecutionUnitPrices
ExecutionUnitPrices (Rational -> Rational -> ExecutionUnitPrices)
-> Parser Rational -> Parser (Rational -> ExecutionUnitPrices)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser Rational
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"step_price" Parser (Rational -> ExecutionUnitPrices)
-> Parser Rational -> Parser ExecutionUnitPrices
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Rational
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"memory_unit_price"
newtype DecentralizationLevel = DecentralizationLevel
{ DecentralizationLevel -> Percentage
getDecentralizationLevel :: Percentage }
deriving (DecentralizationLevel
DecentralizationLevel
-> DecentralizationLevel -> Bounded DecentralizationLevel
forall a. a -> a -> Bounded a
maxBound :: DecentralizationLevel
$cmaxBound :: DecentralizationLevel
minBound :: DecentralizationLevel
$cminBound :: DecentralizationLevel
Bounded, DecentralizationLevel -> DecentralizationLevel -> Bool
(DecentralizationLevel -> DecentralizationLevel -> Bool)
-> (DecentralizationLevel -> DecentralizationLevel -> Bool)
-> Eq DecentralizationLevel
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DecentralizationLevel -> DecentralizationLevel -> Bool
$c/= :: DecentralizationLevel -> DecentralizationLevel -> Bool
== :: DecentralizationLevel -> DecentralizationLevel -> Bool
$c== :: DecentralizationLevel -> DecentralizationLevel -> Bool
Eq, (forall x. DecentralizationLevel -> Rep DecentralizationLevel x)
-> (forall x. Rep DecentralizationLevel x -> DecentralizationLevel)
-> Generic DecentralizationLevel
forall x. Rep DecentralizationLevel x -> DecentralizationLevel
forall x. DecentralizationLevel -> Rep DecentralizationLevel x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DecentralizationLevel x -> DecentralizationLevel
$cfrom :: forall x. DecentralizationLevel -> Rep DecentralizationLevel x
Generic, Int -> DecentralizationLevel -> ShowS
[DecentralizationLevel] -> ShowS
DecentralizationLevel -> String
(Int -> DecentralizationLevel -> ShowS)
-> (DecentralizationLevel -> String)
-> ([DecentralizationLevel] -> ShowS)
-> Show DecentralizationLevel
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DecentralizationLevel] -> ShowS
$cshowList :: [DecentralizationLevel] -> ShowS
show :: DecentralizationLevel -> String
$cshow :: DecentralizationLevel -> String
showsPrec :: Int -> DecentralizationLevel -> ShowS
$cshowsPrec :: Int -> DecentralizationLevel -> ShowS
Show)
fromDecentralizationLevel :: Percentage -> DecentralizationLevel
fromDecentralizationLevel :: Percentage -> DecentralizationLevel
fromDecentralizationLevel = Percentage -> DecentralizationLevel
DecentralizationLevel
fromFederationPercentage :: Percentage -> DecentralizationLevel
fromFederationPercentage :: Percentage -> DecentralizationLevel
fromFederationPercentage = Percentage -> DecentralizationLevel
fromDecentralizationLevel (Percentage -> DecentralizationLevel)
-> (Percentage -> Percentage)
-> Percentage
-> DecentralizationLevel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Percentage -> Percentage
complementPercentage
getFederationPercentage :: DecentralizationLevel -> Percentage
getFederationPercentage :: DecentralizationLevel -> Percentage
getFederationPercentage = Percentage -> Percentage
complementPercentage (Percentage -> Percentage)
-> (DecentralizationLevel -> Percentage)
-> DecentralizationLevel
-> Percentage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DecentralizationLevel -> Percentage
getDecentralizationLevel
instance NFData DecentralizationLevel
instance Buildable DecentralizationLevel where
build :: DecentralizationLevel -> Builder
build = Percentage -> Builder
forall p. Buildable p => p -> Builder
build (Percentage -> Builder)
-> (DecentralizationLevel -> Percentage)
-> DecentralizationLevel
-> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DecentralizationLevel -> Percentage
getDecentralizationLevel
newtype TokenBundleMaxSize = TokenBundleMaxSize
{ TokenBundleMaxSize -> TxSize
unTokenBundleMaxSize :: TxSize }
deriving (TokenBundleMaxSize -> TokenBundleMaxSize -> Bool
(TokenBundleMaxSize -> TokenBundleMaxSize -> Bool)
-> (TokenBundleMaxSize -> TokenBundleMaxSize -> Bool)
-> Eq TokenBundleMaxSize
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TokenBundleMaxSize -> TokenBundleMaxSize -> Bool
$c/= :: TokenBundleMaxSize -> TokenBundleMaxSize -> Bool
== :: TokenBundleMaxSize -> TokenBundleMaxSize -> Bool
$c== :: TokenBundleMaxSize -> TokenBundleMaxSize -> Bool
Eq, (forall x. TokenBundleMaxSize -> Rep TokenBundleMaxSize x)
-> (forall x. Rep TokenBundleMaxSize x -> TokenBundleMaxSize)
-> Generic TokenBundleMaxSize
forall x. Rep TokenBundleMaxSize x -> TokenBundleMaxSize
forall x. TokenBundleMaxSize -> Rep TokenBundleMaxSize x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TokenBundleMaxSize x -> TokenBundleMaxSize
$cfrom :: forall x. TokenBundleMaxSize -> Rep TokenBundleMaxSize x
Generic, Int -> TokenBundleMaxSize -> ShowS
[TokenBundleMaxSize] -> ShowS
TokenBundleMaxSize -> String
(Int -> TokenBundleMaxSize -> ShowS)
-> (TokenBundleMaxSize -> String)
-> ([TokenBundleMaxSize] -> ShowS)
-> Show TokenBundleMaxSize
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TokenBundleMaxSize] -> ShowS
$cshowList :: [TokenBundleMaxSize] -> ShowS
show :: TokenBundleMaxSize -> String
$cshow :: TokenBundleMaxSize -> String
showsPrec :: Int -> TokenBundleMaxSize -> ShowS
$cshowsPrec :: Int -> TokenBundleMaxSize -> ShowS
Show)
instance NFData TokenBundleMaxSize
instance Arbitrary TokenBundleMaxSize where
arbitrary :: Gen TokenBundleMaxSize
arbitrary = TxSize -> TokenBundleMaxSize
TokenBundleMaxSize (TxSize -> TokenBundleMaxSize)
-> (Natural -> TxSize) -> Natural -> TokenBundleMaxSize
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Natural -> TxSize
TxSize (Natural -> TokenBundleMaxSize)
-> Gen Natural -> Gen TokenBundleMaxSize
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
[Gen Natural] -> Gen Natural
forall a. [Gen a] -> Gen a
oneof
[ Int -> Natural
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Natural) -> (Int -> Int) -> Int -> Natural
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
0 (Int -> Int) -> (Int -> Int) -> Int -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int
4000 Int -> Int -> Int
forall a. Num a => a -> a -> a
+) (Int -> Natural) -> Gen Int -> Gen Natural
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Arbitrary Int => Gen Int
forall a. Arbitrary a => Gen a
arbitrary @Int
, Word64 -> Natural
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64 -> Natural) -> Gen Word64 -> Gen Natural
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Arbitrary Word64 => Gen Word64
forall a. Arbitrary a => Gen a
arbitrary @Word64
]
shrink :: TokenBundleMaxSize -> [TokenBundleMaxSize]
shrink (TokenBundleMaxSize (TxSize Natural
s)) =
(Word64 -> TokenBundleMaxSize) -> [Word64] -> [TokenBundleMaxSize]
forall a b. (a -> b) -> [a] -> [b]
map (TxSize -> TokenBundleMaxSize
TokenBundleMaxSize (TxSize -> TokenBundleMaxSize)
-> (Word64 -> TxSize) -> Word64 -> TokenBundleMaxSize
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Natural -> TxSize
TxSize (Natural -> TxSize) -> (Word64 -> Natural) -> Word64 -> TxSize
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> Natural
forall a b. (Integral a, Num b) => a -> b
fromIntegral)
([Word64] -> [TokenBundleMaxSize])
-> (Word64 -> [Word64]) -> Word64 -> [TokenBundleMaxSize]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Arbitrary Word64 => Word64 -> [Word64]
forall a. Arbitrary a => a -> [a]
shrink @Word64
(Word64 -> [TokenBundleMaxSize]) -> Word64 -> [TokenBundleMaxSize]
forall a b. (a -> b) -> a -> b
$ Natural -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Natural
s
data TxParameters = TxParameters
{ TxParameters -> FeePolicy
getFeePolicy :: FeePolicy
, TxParameters -> Quantity "byte" Word16
getTxMaxSize :: Quantity "byte" Word16
, TxParameters -> TokenBundleMaxSize
getTokenBundleMaxSize :: TokenBundleMaxSize
, TxParameters -> ExecutionUnits
getMaxExecutionUnits :: ExecutionUnits
} deriving ((forall x. TxParameters -> Rep TxParameters x)
-> (forall x. Rep TxParameters x -> TxParameters)
-> Generic TxParameters
forall x. Rep TxParameters x -> TxParameters
forall x. TxParameters -> Rep TxParameters x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TxParameters x -> TxParameters
$cfrom :: forall x. TxParameters -> Rep TxParameters x
Generic, Int -> TxParameters -> ShowS
[TxParameters] -> ShowS
TxParameters -> String
(Int -> TxParameters -> ShowS)
-> (TxParameters -> String)
-> ([TxParameters] -> ShowS)
-> Show TxParameters
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TxParameters] -> ShowS
$cshowList :: [TxParameters] -> ShowS
show :: TxParameters -> String
$cshow :: TxParameters -> String
showsPrec :: Int -> TxParameters -> ShowS
$cshowsPrec :: Int -> TxParameters -> ShowS
Show, TxParameters -> TxParameters -> Bool
(TxParameters -> TxParameters -> Bool)
-> (TxParameters -> TxParameters -> Bool) -> Eq TxParameters
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TxParameters -> TxParameters -> Bool
$c/= :: TxParameters -> TxParameters -> Bool
== :: TxParameters -> TxParameters -> Bool
$c== :: TxParameters -> TxParameters -> Bool
Eq)
instance NFData TxParameters
instance Buildable TxParameters where
build :: TxParameters -> Builder
build TxParameters
txp = (Builder -> Builder) -> [Builder] -> Builder
forall (f :: * -> *) a.
Foldable f =>
(a -> Builder) -> f a -> Builder
listF' Builder -> Builder
forall a. a -> a
id
[ Builder
"Fee policy: " Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> FeePolicy -> Builder
feePolicyF (TxParameters
txp TxParameters
-> ((FeePolicy -> Const FeePolicy FeePolicy)
-> TxParameters -> Const FeePolicy TxParameters)
-> FeePolicy
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. IsLabel
"getFeePolicy"
((FeePolicy -> Const FeePolicy FeePolicy)
-> TxParameters -> Const FeePolicy TxParameters)
(FeePolicy -> Const FeePolicy FeePolicy)
-> TxParameters -> Const FeePolicy TxParameters
#getFeePolicy)
, Builder
"Tx max size: " Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Quantity "byte" Word16 -> Builder
forall p (unit :: Symbol).
Buildable p =>
Quantity unit p -> Builder
txMaxSizeF (TxParameters
txp TxParameters
-> ((Quantity "byte" Word16
-> Const (Quantity "byte" Word16) (Quantity "byte" Word16))
-> TxParameters -> Const (Quantity "byte" Word16) TxParameters)
-> Quantity "byte" Word16
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. IsLabel
"getTxMaxSize"
((Quantity "byte" Word16
-> Const (Quantity "byte" Word16) (Quantity "byte" Word16))
-> TxParameters -> Const (Quantity "byte" Word16) TxParameters)
(Quantity "byte" Word16
-> Const (Quantity "byte" Word16) (Quantity "byte" Word16))
-> TxParameters -> Const (Quantity "byte" Word16) TxParameters
#getTxMaxSize)
, Builder
"max exec units: " Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> ExecutionUnits -> Builder
maxExUnitsF (TxParameters
txp TxParameters
-> ((ExecutionUnits -> Const ExecutionUnits ExecutionUnits)
-> TxParameters -> Const ExecutionUnits TxParameters)
-> ExecutionUnits
forall s a. s -> ((a -> Const a a) -> s -> Const a s) -> a
^. IsLabel
"getMaxExecutionUnits"
((ExecutionUnits -> Const ExecutionUnits ExecutionUnits)
-> TxParameters -> Const ExecutionUnits TxParameters)
(ExecutionUnits -> Const ExecutionUnits ExecutionUnits)
-> TxParameters -> Const ExecutionUnits TxParameters
#getMaxExecutionUnits)
]
where
feePolicyF :: FeePolicy -> Builder
feePolicyF = Text -> Builder
forall p. Buildable p => p -> Builder
build (Text -> Builder) -> (FeePolicy -> Text) -> FeePolicy -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FeePolicy -> Text
forall a. ToText a => a -> Text
toText
txMaxSizeF :: Quantity unit p -> Builder
txMaxSizeF (Quantity p
s) = p -> Builder
forall p. Buildable p => p -> Builder
build p
s
maxExUnitsF :: ExecutionUnits -> Builder
maxExUnitsF = ExecutionUnits -> Builder
forall p. Buildable p => p -> Builder
build
data SlotId = SlotId
{ SlotId -> EpochNo
epochNumber :: !EpochNo
, SlotId -> SlotInEpoch
slotNumber :: !SlotInEpoch
} deriving stock (Int -> SlotId -> ShowS
[SlotId] -> ShowS
SlotId -> String
(Int -> SlotId -> ShowS)
-> (SlotId -> String) -> ([SlotId] -> ShowS) -> Show SlotId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SlotId] -> ShowS
$cshowList :: [SlotId] -> ShowS
show :: SlotId -> String
$cshow :: SlotId -> String
showsPrec :: Int -> SlotId -> ShowS
$cshowsPrec :: Int -> SlotId -> ShowS
Show, ReadPrec [SlotId]
ReadPrec SlotId
Int -> ReadS SlotId
ReadS [SlotId]
(Int -> ReadS SlotId)
-> ReadS [SlotId]
-> ReadPrec SlotId
-> ReadPrec [SlotId]
-> Read SlotId
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SlotId]
$creadListPrec :: ReadPrec [SlotId]
readPrec :: ReadPrec SlotId
$creadPrec :: ReadPrec SlotId
readList :: ReadS [SlotId]
$creadList :: ReadS [SlotId]
readsPrec :: Int -> ReadS SlotId
$creadsPrec :: Int -> ReadS SlotId
Read, SlotId -> SlotId -> Bool
(SlotId -> SlotId -> Bool)
-> (SlotId -> SlotId -> Bool) -> Eq SlotId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SlotId -> SlotId -> Bool
$c/= :: SlotId -> SlotId -> Bool
== :: SlotId -> SlotId -> Bool
$c== :: SlotId -> SlotId -> Bool
Eq, Eq SlotId
Eq SlotId
-> (SlotId -> SlotId -> Ordering)
-> (SlotId -> SlotId -> Bool)
-> (SlotId -> SlotId -> Bool)
-> (SlotId -> SlotId -> Bool)
-> (SlotId -> SlotId -> Bool)
-> (SlotId -> SlotId -> SlotId)
-> (SlotId -> SlotId -> SlotId)
-> Ord SlotId
SlotId -> SlotId -> Bool
SlotId -> SlotId -> Ordering
SlotId -> SlotId -> SlotId
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SlotId -> SlotId -> SlotId
$cmin :: SlotId -> SlotId -> SlotId
max :: SlotId -> SlotId -> SlotId
$cmax :: SlotId -> SlotId -> SlotId
>= :: SlotId -> SlotId -> Bool
$c>= :: SlotId -> SlotId -> Bool
> :: SlotId -> SlotId -> Bool
$c> :: SlotId -> SlotId -> Bool
<= :: SlotId -> SlotId -> Bool
$c<= :: SlotId -> SlotId -> Bool
< :: SlotId -> SlotId -> Bool
$c< :: SlotId -> SlotId -> Bool
compare :: SlotId -> SlotId -> Ordering
$ccompare :: SlotId -> SlotId -> Ordering
$cp1Ord :: Eq SlotId
Ord, (forall x. SlotId -> Rep SlotId x)
-> (forall x. Rep SlotId x -> SlotId) -> Generic SlotId
forall x. Rep SlotId x -> SlotId
forall x. SlotId -> Rep SlotId x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SlotId x -> SlotId
$cfrom :: forall x. SlotId -> Rep SlotId x
Generic)
newtype SlotInEpoch = SlotInEpoch { SlotInEpoch -> Word32
unSlotInEpoch :: Word32 }
deriving stock (Int -> SlotInEpoch -> ShowS
[SlotInEpoch] -> ShowS
SlotInEpoch -> String
(Int -> SlotInEpoch -> ShowS)
-> (SlotInEpoch -> String)
-> ([SlotInEpoch] -> ShowS)
-> Show SlotInEpoch
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SlotInEpoch] -> ShowS
$cshowList :: [SlotInEpoch] -> ShowS
show :: SlotInEpoch -> String
$cshow :: SlotInEpoch -> String
showsPrec :: Int -> SlotInEpoch -> ShowS
$cshowsPrec :: Int -> SlotInEpoch -> ShowS
Show, ReadPrec [SlotInEpoch]
ReadPrec SlotInEpoch
Int -> ReadS SlotInEpoch
ReadS [SlotInEpoch]
(Int -> ReadS SlotInEpoch)
-> ReadS [SlotInEpoch]
-> ReadPrec SlotInEpoch
-> ReadPrec [SlotInEpoch]
-> Read SlotInEpoch
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SlotInEpoch]
$creadListPrec :: ReadPrec [SlotInEpoch]
readPrec :: ReadPrec SlotInEpoch
$creadPrec :: ReadPrec SlotInEpoch
readList :: ReadS [SlotInEpoch]
$creadList :: ReadS [SlotInEpoch]
readsPrec :: Int -> ReadS SlotInEpoch
$creadsPrec :: Int -> ReadS SlotInEpoch
Read, SlotInEpoch -> SlotInEpoch -> Bool
(SlotInEpoch -> SlotInEpoch -> Bool)
-> (SlotInEpoch -> SlotInEpoch -> Bool) -> Eq SlotInEpoch
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SlotInEpoch -> SlotInEpoch -> Bool
$c/= :: SlotInEpoch -> SlotInEpoch -> Bool
== :: SlotInEpoch -> SlotInEpoch -> Bool
$c== :: SlotInEpoch -> SlotInEpoch -> Bool
Eq, Eq SlotInEpoch
Eq SlotInEpoch
-> (SlotInEpoch -> SlotInEpoch -> Ordering)
-> (SlotInEpoch -> SlotInEpoch -> Bool)
-> (SlotInEpoch -> SlotInEpoch -> Bool)
-> (SlotInEpoch -> SlotInEpoch -> Bool)
-> (SlotInEpoch -> SlotInEpoch -> Bool)
-> (SlotInEpoch -> SlotInEpoch -> SlotInEpoch)
-> (SlotInEpoch -> SlotInEpoch -> SlotInEpoch)
-> Ord SlotInEpoch
SlotInEpoch -> SlotInEpoch -> Bool
SlotInEpoch -> SlotInEpoch -> Ordering
SlotInEpoch -> SlotInEpoch -> SlotInEpoch
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SlotInEpoch -> SlotInEpoch -> SlotInEpoch
$cmin :: SlotInEpoch -> SlotInEpoch -> SlotInEpoch
max :: SlotInEpoch -> SlotInEpoch -> SlotInEpoch
$cmax :: SlotInEpoch -> SlotInEpoch -> SlotInEpoch
>= :: SlotInEpoch -> SlotInEpoch -> Bool
$c>= :: SlotInEpoch -> SlotInEpoch -> Bool
> :: SlotInEpoch -> SlotInEpoch -> Bool
$c> :: SlotInEpoch -> SlotInEpoch -> Bool
<= :: SlotInEpoch -> SlotInEpoch -> Bool
$c<= :: SlotInEpoch -> SlotInEpoch -> Bool
< :: SlotInEpoch -> SlotInEpoch -> Bool
$c< :: SlotInEpoch -> SlotInEpoch -> Bool
compare :: SlotInEpoch -> SlotInEpoch -> Ordering
$ccompare :: SlotInEpoch -> SlotInEpoch -> Ordering
$cp1Ord :: Eq SlotInEpoch
Ord, (forall x. SlotInEpoch -> Rep SlotInEpoch x)
-> (forall x. Rep SlotInEpoch x -> SlotInEpoch)
-> Generic SlotInEpoch
forall x. Rep SlotInEpoch x -> SlotInEpoch
forall x. SlotInEpoch -> Rep SlotInEpoch x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SlotInEpoch x -> SlotInEpoch
$cfrom :: forall x. SlotInEpoch -> Rep SlotInEpoch x
Generic)
deriving newtype (Integer -> SlotInEpoch
SlotInEpoch -> SlotInEpoch
SlotInEpoch -> SlotInEpoch -> SlotInEpoch
(SlotInEpoch -> SlotInEpoch -> SlotInEpoch)
-> (SlotInEpoch -> SlotInEpoch -> SlotInEpoch)
-> (SlotInEpoch -> SlotInEpoch -> SlotInEpoch)
-> (SlotInEpoch -> SlotInEpoch)
-> (SlotInEpoch -> SlotInEpoch)
-> (SlotInEpoch -> SlotInEpoch)
-> (Integer -> SlotInEpoch)
-> Num SlotInEpoch
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> SlotInEpoch
$cfromInteger :: Integer -> SlotInEpoch
signum :: SlotInEpoch -> SlotInEpoch
$csignum :: SlotInEpoch -> SlotInEpoch
abs :: SlotInEpoch -> SlotInEpoch
$cabs :: SlotInEpoch -> SlotInEpoch
negate :: SlotInEpoch -> SlotInEpoch
$cnegate :: SlotInEpoch -> SlotInEpoch
* :: SlotInEpoch -> SlotInEpoch -> SlotInEpoch
$c* :: SlotInEpoch -> SlotInEpoch -> SlotInEpoch
- :: SlotInEpoch -> SlotInEpoch -> SlotInEpoch
$c- :: SlotInEpoch -> SlotInEpoch -> SlotInEpoch
+ :: SlotInEpoch -> SlotInEpoch -> SlotInEpoch
$c+ :: SlotInEpoch -> SlotInEpoch -> SlotInEpoch
Num, SlotInEpoch -> Builder
(SlotInEpoch -> Builder) -> Buildable SlotInEpoch
forall p. (p -> Builder) -> Buildable p
build :: SlotInEpoch -> Builder
$cbuild :: SlotInEpoch -> Builder
Buildable, SlotInEpoch -> ()
(SlotInEpoch -> ()) -> NFData SlotInEpoch
forall a. (a -> ()) -> NFData a
rnf :: SlotInEpoch -> ()
$crnf :: SlotInEpoch -> ()
NFData, Int -> SlotInEpoch
SlotInEpoch -> Int
SlotInEpoch -> [SlotInEpoch]
SlotInEpoch -> SlotInEpoch
SlotInEpoch -> SlotInEpoch -> [SlotInEpoch]
SlotInEpoch -> SlotInEpoch -> SlotInEpoch -> [SlotInEpoch]
(SlotInEpoch -> SlotInEpoch)
-> (SlotInEpoch -> SlotInEpoch)
-> (Int -> SlotInEpoch)
-> (SlotInEpoch -> Int)
-> (SlotInEpoch -> [SlotInEpoch])
-> (SlotInEpoch -> SlotInEpoch -> [SlotInEpoch])
-> (SlotInEpoch -> SlotInEpoch -> [SlotInEpoch])
-> (SlotInEpoch -> SlotInEpoch -> SlotInEpoch -> [SlotInEpoch])
-> Enum SlotInEpoch
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: SlotInEpoch -> SlotInEpoch -> SlotInEpoch -> [SlotInEpoch]
$cenumFromThenTo :: SlotInEpoch -> SlotInEpoch -> SlotInEpoch -> [SlotInEpoch]
enumFromTo :: SlotInEpoch -> SlotInEpoch -> [SlotInEpoch]
$cenumFromTo :: SlotInEpoch -> SlotInEpoch -> [SlotInEpoch]
enumFromThen :: SlotInEpoch -> SlotInEpoch -> [SlotInEpoch]
$cenumFromThen :: SlotInEpoch -> SlotInEpoch -> [SlotInEpoch]
enumFrom :: SlotInEpoch -> [SlotInEpoch]
$cenumFrom :: SlotInEpoch -> [SlotInEpoch]
fromEnum :: SlotInEpoch -> Int
$cfromEnum :: SlotInEpoch -> Int
toEnum :: Int -> SlotInEpoch
$ctoEnum :: Int -> SlotInEpoch
pred :: SlotInEpoch -> SlotInEpoch
$cpred :: SlotInEpoch -> SlotInEpoch
succ :: SlotInEpoch -> SlotInEpoch
$csucc :: SlotInEpoch -> SlotInEpoch
Enum)
newtype EpochNo = EpochNo { EpochNo -> Word31
unEpochNo :: Word31 }
deriving stock (Int -> EpochNo -> ShowS
[EpochNo] -> ShowS
EpochNo -> String
(Int -> EpochNo -> ShowS)
-> (EpochNo -> String) -> ([EpochNo] -> ShowS) -> Show EpochNo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EpochNo] -> ShowS
$cshowList :: [EpochNo] -> ShowS
show :: EpochNo -> String
$cshow :: EpochNo -> String
showsPrec :: Int -> EpochNo -> ShowS
$cshowsPrec :: Int -> EpochNo -> ShowS
Show, ReadPrec [EpochNo]
ReadPrec EpochNo
Int -> ReadS EpochNo
ReadS [EpochNo]
(Int -> ReadS EpochNo)
-> ReadS [EpochNo]
-> ReadPrec EpochNo
-> ReadPrec [EpochNo]
-> Read EpochNo
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EpochNo]
$creadListPrec :: ReadPrec [EpochNo]
readPrec :: ReadPrec EpochNo
$creadPrec :: ReadPrec EpochNo
readList :: ReadS [EpochNo]
$creadList :: ReadS [EpochNo]
readsPrec :: Int -> ReadS EpochNo
$creadsPrec :: Int -> ReadS EpochNo
Read, EpochNo -> EpochNo -> Bool
(EpochNo -> EpochNo -> Bool)
-> (EpochNo -> EpochNo -> Bool) -> Eq EpochNo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EpochNo -> EpochNo -> Bool
$c/= :: EpochNo -> EpochNo -> Bool
== :: EpochNo -> EpochNo -> Bool
$c== :: EpochNo -> EpochNo -> Bool
Eq, Eq EpochNo
Eq EpochNo
-> (EpochNo -> EpochNo -> Ordering)
-> (EpochNo -> EpochNo -> Bool)
-> (EpochNo -> EpochNo -> Bool)
-> (EpochNo -> EpochNo -> Bool)
-> (EpochNo -> EpochNo -> Bool)
-> (EpochNo -> EpochNo -> EpochNo)
-> (EpochNo -> EpochNo -> EpochNo)
-> Ord EpochNo
EpochNo -> EpochNo -> Bool
EpochNo -> EpochNo -> Ordering
EpochNo -> EpochNo -> EpochNo
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: EpochNo -> EpochNo -> EpochNo
$cmin :: EpochNo -> EpochNo -> EpochNo
max :: EpochNo -> EpochNo -> EpochNo
$cmax :: EpochNo -> EpochNo -> EpochNo
>= :: EpochNo -> EpochNo -> Bool
$c>= :: EpochNo -> EpochNo -> Bool
> :: EpochNo -> EpochNo -> Bool
$c> :: EpochNo -> EpochNo -> Bool
<= :: EpochNo -> EpochNo -> Bool
$c<= :: EpochNo -> EpochNo -> Bool
< :: EpochNo -> EpochNo -> Bool
$c< :: EpochNo -> EpochNo -> Bool
compare :: EpochNo -> EpochNo -> Ordering
$ccompare :: EpochNo -> EpochNo -> Ordering
$cp1Ord :: Eq EpochNo
Ord, (forall x. EpochNo -> Rep EpochNo x)
-> (forall x. Rep EpochNo x -> EpochNo) -> Generic EpochNo
forall x. Rep EpochNo x -> EpochNo
forall x. EpochNo -> Rep EpochNo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EpochNo x -> EpochNo
$cfrom :: forall x. EpochNo -> Rep EpochNo x
Generic)
deriving newtype (Integer -> EpochNo
EpochNo -> EpochNo
EpochNo -> EpochNo -> EpochNo
(EpochNo -> EpochNo -> EpochNo)
-> (EpochNo -> EpochNo -> EpochNo)
-> (EpochNo -> EpochNo -> EpochNo)
-> (EpochNo -> EpochNo)
-> (EpochNo -> EpochNo)
-> (EpochNo -> EpochNo)
-> (Integer -> EpochNo)
-> Num EpochNo
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> EpochNo
$cfromInteger :: Integer -> EpochNo
signum :: EpochNo -> EpochNo
$csignum :: EpochNo -> EpochNo
abs :: EpochNo -> EpochNo
$cabs :: EpochNo -> EpochNo
negate :: EpochNo -> EpochNo
$cnegate :: EpochNo -> EpochNo
* :: EpochNo -> EpochNo -> EpochNo
$c* :: EpochNo -> EpochNo -> EpochNo
- :: EpochNo -> EpochNo -> EpochNo
$c- :: EpochNo -> EpochNo -> EpochNo
+ :: EpochNo -> EpochNo -> EpochNo
$c+ :: EpochNo -> EpochNo -> EpochNo
Num, EpochNo
EpochNo -> EpochNo -> Bounded EpochNo
forall a. a -> a -> Bounded a
maxBound :: EpochNo
$cmaxBound :: EpochNo
minBound :: EpochNo
$cminBound :: EpochNo
Bounded, Int -> EpochNo
EpochNo -> Int
EpochNo -> [EpochNo]
EpochNo -> EpochNo
EpochNo -> EpochNo -> [EpochNo]
EpochNo -> EpochNo -> EpochNo -> [EpochNo]
(EpochNo -> EpochNo)
-> (EpochNo -> EpochNo)
-> (Int -> EpochNo)
-> (EpochNo -> Int)
-> (EpochNo -> [EpochNo])
-> (EpochNo -> EpochNo -> [EpochNo])
-> (EpochNo -> EpochNo -> [EpochNo])
-> (EpochNo -> EpochNo -> EpochNo -> [EpochNo])
-> Enum EpochNo
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: EpochNo -> EpochNo -> EpochNo -> [EpochNo]
$cenumFromThenTo :: EpochNo -> EpochNo -> EpochNo -> [EpochNo]
enumFromTo :: EpochNo -> EpochNo -> [EpochNo]
$cenumFromTo :: EpochNo -> EpochNo -> [EpochNo]
enumFromThen :: EpochNo -> EpochNo -> [EpochNo]
$cenumFromThen :: EpochNo -> EpochNo -> [EpochNo]
enumFrom :: EpochNo -> [EpochNo]
$cenumFrom :: EpochNo -> [EpochNo]
fromEnum :: EpochNo -> Int
$cfromEnum :: EpochNo -> Int
toEnum :: Int -> EpochNo
$ctoEnum :: Int -> EpochNo
pred :: EpochNo -> EpochNo
$cpred :: EpochNo -> EpochNo
succ :: EpochNo -> EpochNo
$csucc :: EpochNo -> EpochNo
Enum)
instance ToText EpochNo where
toText :: EpochNo -> Text
toText = String -> Text
T.pack (String -> Text) -> (EpochNo -> String) -> EpochNo -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word31 -> String
forall a. Show a => a -> String
show (Word31 -> String) -> (EpochNo -> Word31) -> EpochNo -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EpochNo -> Word31
unEpochNo
instance FromText EpochNo where
fromText :: Text -> Either TextDecodingError EpochNo
fromText = EpochNo -> Either TextDecodingError EpochNo
validate (EpochNo -> Either TextDecodingError EpochNo)
-> (Text -> Either TextDecodingError EpochNo)
-> Text
-> Either TextDecodingError EpochNo
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< ((Natural -> EpochNo)
-> Either TextDecodingError Natural
-> Either TextDecodingError EpochNo
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Word31 -> EpochNo
EpochNo (Word31 -> EpochNo) -> (Natural -> Word31) -> Natural -> EpochNo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Natural -> Word31
forall a b. (Integral a, Num b) => a -> b
fromIntegral) (Either TextDecodingError Natural
-> Either TextDecodingError EpochNo)
-> (Text -> Either TextDecodingError Natural)
-> Text
-> Either TextDecodingError EpochNo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FromText Natural => Text -> Either TextDecodingError Natural
forall a. FromText a => Text -> Either TextDecodingError a
fromText @Natural)
where
validate :: EpochNo -> Either TextDecodingError EpochNo
validate EpochNo
x
| EpochNo -> Bool
isValidEpochNo EpochNo
x =
EpochNo -> Either TextDecodingError EpochNo
forall (m :: * -> *) a. Monad m => a -> m a
return EpochNo
x
| Bool
otherwise =
TextDecodingError -> Either TextDecodingError EpochNo
forall a b. a -> Either a b
Left (TextDecodingError -> Either TextDecodingError EpochNo)
-> TextDecodingError -> Either TextDecodingError EpochNo
forall a b. (a -> b) -> a -> b
$ String -> TextDecodingError
TextDecodingError String
"EpochNo value is out of bounds"
isValidEpochNo :: EpochNo -> Bool
isValidEpochNo :: EpochNo -> Bool
isValidEpochNo EpochNo
c = EpochNo
c EpochNo -> EpochNo -> Bool
forall a. Ord a => a -> a -> Bool
>= EpochNo
forall a. Bounded a => a
minBound Bool -> Bool -> Bool
&& EpochNo
c EpochNo -> EpochNo -> Bool
forall a. Ord a => a -> a -> Bool
<= EpochNo
forall a. Bounded a => a
maxBound
instance Buildable EpochNo where
build :: EpochNo -> Builder
build (EpochNo Word31
e) = Word32 -> Builder
forall p. Buildable p => p -> Builder
build (Word32 -> Builder) -> Word32 -> Builder
forall a b. (a -> b) -> a -> b
$ Word31 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral @Word31 @Word32 Word31
e
instance NFData EpochNo where
rnf :: EpochNo -> ()
rnf (EpochNo !Word31
_) = ()
unsafeEpochNo :: HasCallStack => Word32 -> EpochNo
unsafeEpochNo :: Word32 -> EpochNo
unsafeEpochNo Word32
epochNo
| Word32
epochNo Word32 -> Word32 -> Bool
forall a. Ord a => a -> a -> Bool
> Word32
maxEpochNo =
String -> EpochNo
forall a. HasCallStack => String -> a
error (String -> EpochNo) -> String -> EpochNo
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall a. Monoid a => [a] -> a
mconcat
[ String
"unsafeEpochNo: epoch number ("
, Word32 -> String
forall a. Show a => a -> String
show Word32
epochNo
, String
") out of bounds ("
, Word31 -> String
forall a. Show a => a -> String
show (Bounded Word31 => Word31
forall a. Bounded a => a
minBound @Word31)
, String
", "
, Word31 -> String
forall a. Show a => a -> String
show (Bounded Word31 => Word31
forall a. Bounded a => a
maxBound @Word31)
, String
")."
]
| Bool
otherwise =
Word31 -> EpochNo
EpochNo (Word31 -> EpochNo) -> Word31 -> EpochNo
forall a b. (a -> b) -> a -> b
$ Word32 -> Word31
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
epochNo
where
maxEpochNo :: Word32
maxEpochNo :: Word32
maxEpochNo = forall b. (Integral Word31, Num b) => Word31 -> b
forall a b. (Integral a, Num b) => a -> b
fromIntegral @Word31 (Word31 -> Word32) -> Word31 -> Word32
forall a b. (a -> b) -> a -> b
$ EpochNo -> Word31
unEpochNo EpochNo
forall a. Bounded a => a
maxBound
instance NFData SlotId
instance Buildable SlotId where
build :: SlotId -> Builder
build (SlotId (EpochNo Word31
e) (SlotInEpoch Word32
s)) =
String -> Builder
forall a. IsString a => String -> a
fromString (Word31 -> String
forall a. Show a => a -> String
show Word31
e) Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
"." Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> String -> Builder
forall a. IsString a => String -> a
fromString (Word32 -> String
forall a. Show a => a -> String
show Word32
s)
newtype SlotLength = SlotLength { SlotLength -> NominalDiffTime
unSlotLength :: NominalDiffTime }
deriving (Int -> SlotLength -> ShowS
[SlotLength] -> ShowS
SlotLength -> String
(Int -> SlotLength -> ShowS)
-> (SlotLength -> String)
-> ([SlotLength] -> ShowS)
-> Show SlotLength
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SlotLength] -> ShowS
$cshowList :: [SlotLength] -> ShowS
show :: SlotLength -> String
$cshow :: SlotLength -> String
showsPrec :: Int -> SlotLength -> ShowS
$cshowsPrec :: Int -> SlotLength -> ShowS
Show, SlotLength -> SlotLength -> Bool
(SlotLength -> SlotLength -> Bool)
-> (SlotLength -> SlotLength -> Bool) -> Eq SlotLength
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SlotLength -> SlotLength -> Bool
$c/= :: SlotLength -> SlotLength -> Bool
== :: SlotLength -> SlotLength -> Bool
$c== :: SlotLength -> SlotLength -> Bool
Eq, (forall x. SlotLength -> Rep SlotLength x)
-> (forall x. Rep SlotLength x -> SlotLength) -> Generic SlotLength
forall x. Rep SlotLength x -> SlotLength
forall x. SlotLength -> Rep SlotLength x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SlotLength x -> SlotLength
$cfrom :: forall x. SlotLength -> Rep SlotLength x
Generic)
instance NFData SlotLength
newtype EpochLength = EpochLength { EpochLength -> Word32
unEpochLength :: Word32 }
deriving (Int -> EpochLength -> ShowS
[EpochLength] -> ShowS
EpochLength -> String
(Int -> EpochLength -> ShowS)
-> (EpochLength -> String)
-> ([EpochLength] -> ShowS)
-> Show EpochLength
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EpochLength] -> ShowS
$cshowList :: [EpochLength] -> ShowS
show :: EpochLength -> String
$cshow :: EpochLength -> String
showsPrec :: Int -> EpochLength -> ShowS
$cshowsPrec :: Int -> EpochLength -> ShowS
Show, EpochLength -> EpochLength -> Bool
(EpochLength -> EpochLength -> Bool)
-> (EpochLength -> EpochLength -> Bool) -> Eq EpochLength
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EpochLength -> EpochLength -> Bool
$c/= :: EpochLength -> EpochLength -> Bool
== :: EpochLength -> EpochLength -> Bool
$c== :: EpochLength -> EpochLength -> Bool
Eq, (forall x. EpochLength -> Rep EpochLength x)
-> (forall x. Rep EpochLength x -> EpochLength)
-> Generic EpochLength
forall x. Rep EpochLength x -> EpochLength
forall x. EpochLength -> Rep EpochLength x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EpochLength x -> EpochLength
$cfrom :: forall x. EpochLength -> Rep EpochLength x
Generic)
instance NFData EpochLength
newtype StartTime = StartTime UTCTime
deriving (Int -> StartTime -> ShowS
[StartTime] -> ShowS
StartTime -> String
(Int -> StartTime -> ShowS)
-> (StartTime -> String)
-> ([StartTime] -> ShowS)
-> Show StartTime
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartTime] -> ShowS
$cshowList :: [StartTime] -> ShowS
show :: StartTime -> String
$cshow :: StartTime -> String
showsPrec :: Int -> StartTime -> ShowS
$cshowsPrec :: Int -> StartTime -> ShowS
Show, StartTime -> StartTime -> Bool
(StartTime -> StartTime -> Bool)
-> (StartTime -> StartTime -> Bool) -> Eq StartTime
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartTime -> StartTime -> Bool
$c/= :: StartTime -> StartTime -> Bool
== :: StartTime -> StartTime -> Bool
$c== :: StartTime -> StartTime -> Bool
Eq, Eq StartTime
Eq StartTime
-> (StartTime -> StartTime -> Ordering)
-> (StartTime -> StartTime -> Bool)
-> (StartTime -> StartTime -> Bool)
-> (StartTime -> StartTime -> Bool)
-> (StartTime -> StartTime -> Bool)
-> (StartTime -> StartTime -> StartTime)
-> (StartTime -> StartTime -> StartTime)
-> Ord StartTime
StartTime -> StartTime -> Bool
StartTime -> StartTime -> Ordering
StartTime -> StartTime -> StartTime
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: StartTime -> StartTime -> StartTime
$cmin :: StartTime -> StartTime -> StartTime
max :: StartTime -> StartTime -> StartTime
$cmax :: StartTime -> StartTime -> StartTime
>= :: StartTime -> StartTime -> Bool
$c>= :: StartTime -> StartTime -> Bool
> :: StartTime -> StartTime -> Bool
$c> :: StartTime -> StartTime -> Bool
<= :: StartTime -> StartTime -> Bool
$c<= :: StartTime -> StartTime -> Bool
< :: StartTime -> StartTime -> Bool
$c< :: StartTime -> StartTime -> Bool
compare :: StartTime -> StartTime -> Ordering
$ccompare :: StartTime -> StartTime -> Ordering
$cp1Ord :: Eq StartTime
Ord, (forall x. StartTime -> Rep StartTime x)
-> (forall x. Rep StartTime x -> StartTime) -> Generic StartTime
forall x. Rep StartTime x -> StartTime
forall x. StartTime -> Rep StartTime x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartTime x -> StartTime
$cfrom :: forall x. StartTime -> Rep StartTime x
Generic)
instance NFData StartTime
data DelegationCertificate
= CertDelegateNone RewardAccount
| CertDelegateFull RewardAccount PoolId
| CertRegisterKey RewardAccount
deriving ((forall x. DelegationCertificate -> Rep DelegationCertificate x)
-> (forall x. Rep DelegationCertificate x -> DelegationCertificate)
-> Generic DelegationCertificate
forall x. Rep DelegationCertificate x -> DelegationCertificate
forall x. DelegationCertificate -> Rep DelegationCertificate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DelegationCertificate x -> DelegationCertificate
$cfrom :: forall x. DelegationCertificate -> Rep DelegationCertificate x
Generic, Int -> DelegationCertificate -> ShowS
[DelegationCertificate] -> ShowS
DelegationCertificate -> String
(Int -> DelegationCertificate -> ShowS)
-> (DelegationCertificate -> String)
-> ([DelegationCertificate] -> ShowS)
-> Show DelegationCertificate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DelegationCertificate] -> ShowS
$cshowList :: [DelegationCertificate] -> ShowS
show :: DelegationCertificate -> String
$cshow :: DelegationCertificate -> String
showsPrec :: Int -> DelegationCertificate -> ShowS
$cshowsPrec :: Int -> DelegationCertificate -> ShowS
Show, DelegationCertificate -> DelegationCertificate -> Bool
(DelegationCertificate -> DelegationCertificate -> Bool)
-> (DelegationCertificate -> DelegationCertificate -> Bool)
-> Eq DelegationCertificate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DelegationCertificate -> DelegationCertificate -> Bool
$c/= :: DelegationCertificate -> DelegationCertificate -> Bool
== :: DelegationCertificate -> DelegationCertificate -> Bool
$c== :: DelegationCertificate -> DelegationCertificate -> Bool
Eq, Eq DelegationCertificate
Eq DelegationCertificate
-> (DelegationCertificate -> DelegationCertificate -> Ordering)
-> (DelegationCertificate -> DelegationCertificate -> Bool)
-> (DelegationCertificate -> DelegationCertificate -> Bool)
-> (DelegationCertificate -> DelegationCertificate -> Bool)
-> (DelegationCertificate -> DelegationCertificate -> Bool)
-> (DelegationCertificate
-> DelegationCertificate -> DelegationCertificate)
-> (DelegationCertificate
-> DelegationCertificate -> DelegationCertificate)
-> Ord DelegationCertificate
DelegationCertificate -> DelegationCertificate -> Bool
DelegationCertificate -> DelegationCertificate -> Ordering
DelegationCertificate
-> DelegationCertificate -> DelegationCertificate
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DelegationCertificate
-> DelegationCertificate -> DelegationCertificate
$cmin :: DelegationCertificate
-> DelegationCertificate -> DelegationCertificate
max :: DelegationCertificate
-> DelegationCertificate -> DelegationCertificate
$cmax :: DelegationCertificate
-> DelegationCertificate -> DelegationCertificate
>= :: DelegationCertificate -> DelegationCertificate -> Bool
$c>= :: DelegationCertificate -> DelegationCertificate -> Bool
> :: DelegationCertificate -> DelegationCertificate -> Bool
$c> :: DelegationCertificate -> DelegationCertificate -> Bool
<= :: DelegationCertificate -> DelegationCertificate -> Bool
$c<= :: DelegationCertificate -> DelegationCertificate -> Bool
< :: DelegationCertificate -> DelegationCertificate -> Bool
$c< :: DelegationCertificate -> DelegationCertificate -> Bool
compare :: DelegationCertificate -> DelegationCertificate -> Ordering
$ccompare :: DelegationCertificate -> DelegationCertificate -> Ordering
$cp1Ord :: Eq DelegationCertificate
Ord)
instance NFData DelegationCertificate
data StakeKeyCertificate
= StakeKeyRegistration
| StakeKeyDeregistration
deriving ((forall x. StakeKeyCertificate -> Rep StakeKeyCertificate x)
-> (forall x. Rep StakeKeyCertificate x -> StakeKeyCertificate)
-> Generic StakeKeyCertificate
forall x. Rep StakeKeyCertificate x -> StakeKeyCertificate
forall x. StakeKeyCertificate -> Rep StakeKeyCertificate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StakeKeyCertificate x -> StakeKeyCertificate
$cfrom :: forall x. StakeKeyCertificate -> Rep StakeKeyCertificate x
Generic, Int -> StakeKeyCertificate -> ShowS
[StakeKeyCertificate] -> ShowS
StakeKeyCertificate -> String
(Int -> StakeKeyCertificate -> ShowS)
-> (StakeKeyCertificate -> String)
-> ([StakeKeyCertificate] -> ShowS)
-> Show StakeKeyCertificate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StakeKeyCertificate] -> ShowS
$cshowList :: [StakeKeyCertificate] -> ShowS
show :: StakeKeyCertificate -> String
$cshow :: StakeKeyCertificate -> String
showsPrec :: Int -> StakeKeyCertificate -> ShowS
$cshowsPrec :: Int -> StakeKeyCertificate -> ShowS
Show, ReadPrec [StakeKeyCertificate]
ReadPrec StakeKeyCertificate
Int -> ReadS StakeKeyCertificate
ReadS [StakeKeyCertificate]
(Int -> ReadS StakeKeyCertificate)
-> ReadS [StakeKeyCertificate]
-> ReadPrec StakeKeyCertificate
-> ReadPrec [StakeKeyCertificate]
-> Read StakeKeyCertificate
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StakeKeyCertificate]
$creadListPrec :: ReadPrec [StakeKeyCertificate]
readPrec :: ReadPrec StakeKeyCertificate
$creadPrec :: ReadPrec StakeKeyCertificate
readList :: ReadS [StakeKeyCertificate]
$creadList :: ReadS [StakeKeyCertificate]
readsPrec :: Int -> ReadS StakeKeyCertificate
$creadsPrec :: Int -> ReadS StakeKeyCertificate
Read, StakeKeyCertificate -> StakeKeyCertificate -> Bool
(StakeKeyCertificate -> StakeKeyCertificate -> Bool)
-> (StakeKeyCertificate -> StakeKeyCertificate -> Bool)
-> Eq StakeKeyCertificate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StakeKeyCertificate -> StakeKeyCertificate -> Bool
$c/= :: StakeKeyCertificate -> StakeKeyCertificate -> Bool
== :: StakeKeyCertificate -> StakeKeyCertificate -> Bool
$c== :: StakeKeyCertificate -> StakeKeyCertificate -> Bool
Eq)
instance NFData StakeKeyCertificate
dlgCertAccount :: DelegationCertificate -> RewardAccount
dlgCertAccount :: DelegationCertificate -> RewardAccount
dlgCertAccount = \case
CertDelegateNone RewardAccount
acc -> RewardAccount
acc
CertDelegateFull RewardAccount
acc PoolId
_ -> RewardAccount
acc
CertRegisterKey RewardAccount
acc -> RewardAccount
acc
dlgCertPoolId :: DelegationCertificate -> Maybe PoolId
dlgCertPoolId :: DelegationCertificate -> Maybe PoolId
dlgCertPoolId = \case
CertDelegateNone{} -> Maybe PoolId
forall a. Maybe a
Nothing
CertDelegateFull RewardAccount
_ PoolId
poolId -> PoolId -> Maybe PoolId
forall a. a -> Maybe a
Just PoolId
poolId
CertRegisterKey RewardAccount
_ -> Maybe PoolId
forall a. Maybe a
Nothing
data PoolCertificate
= Registration PoolRegistrationCertificate
| Retirement PoolRetirementCertificate
deriving ((forall x. PoolCertificate -> Rep PoolCertificate x)
-> (forall x. Rep PoolCertificate x -> PoolCertificate)
-> Generic PoolCertificate
forall x. Rep PoolCertificate x -> PoolCertificate
forall x. PoolCertificate -> Rep PoolCertificate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PoolCertificate x -> PoolCertificate
$cfrom :: forall x. PoolCertificate -> Rep PoolCertificate x
Generic, Int -> PoolCertificate -> ShowS
[PoolCertificate] -> ShowS
PoolCertificate -> String
(Int -> PoolCertificate -> ShowS)
-> (PoolCertificate -> String)
-> ([PoolCertificate] -> ShowS)
-> Show PoolCertificate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PoolCertificate] -> ShowS
$cshowList :: [PoolCertificate] -> ShowS
show :: PoolCertificate -> String
$cshow :: PoolCertificate -> String
showsPrec :: Int -> PoolCertificate -> ShowS
$cshowsPrec :: Int -> PoolCertificate -> ShowS
Show, PoolCertificate -> PoolCertificate -> Bool
(PoolCertificate -> PoolCertificate -> Bool)
-> (PoolCertificate -> PoolCertificate -> Bool)
-> Eq PoolCertificate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PoolCertificate -> PoolCertificate -> Bool
$c/= :: PoolCertificate -> PoolCertificate -> Bool
== :: PoolCertificate -> PoolCertificate -> Bool
$c== :: PoolCertificate -> PoolCertificate -> Bool
Eq, Eq PoolCertificate
Eq PoolCertificate
-> (PoolCertificate -> PoolCertificate -> Ordering)
-> (PoolCertificate -> PoolCertificate -> Bool)
-> (PoolCertificate -> PoolCertificate -> Bool)
-> (PoolCertificate -> PoolCertificate -> Bool)
-> (PoolCertificate -> PoolCertificate -> Bool)
-> (PoolCertificate -> PoolCertificate -> PoolCertificate)
-> (PoolCertificate -> PoolCertificate -> PoolCertificate)
-> Ord PoolCertificate
PoolCertificate -> PoolCertificate -> Bool
PoolCertificate -> PoolCertificate -> Ordering
PoolCertificate -> PoolCertificate -> PoolCertificate
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PoolCertificate -> PoolCertificate -> PoolCertificate
$cmin :: PoolCertificate -> PoolCertificate -> PoolCertificate
max :: PoolCertificate -> PoolCertificate -> PoolCertificate
$cmax :: PoolCertificate -> PoolCertificate -> PoolCertificate
>= :: PoolCertificate -> PoolCertificate -> Bool
$c>= :: PoolCertificate -> PoolCertificate -> Bool
> :: PoolCertificate -> PoolCertificate -> Bool
$c> :: PoolCertificate -> PoolCertificate -> Bool
<= :: PoolCertificate -> PoolCertificate -> Bool
$c<= :: PoolCertificate -> PoolCertificate -> Bool
< :: PoolCertificate -> PoolCertificate -> Bool
$c< :: PoolCertificate -> PoolCertificate -> Bool
compare :: PoolCertificate -> PoolCertificate -> Ordering
$ccompare :: PoolCertificate -> PoolCertificate -> Ordering
$cp1Ord :: Eq PoolCertificate
Ord)
instance NFData PoolCertificate
getPoolCertificatePoolId :: PoolCertificate -> PoolId
getPoolCertificatePoolId :: PoolCertificate -> PoolId
getPoolCertificatePoolId = \case
Registration PoolRegistrationCertificate
cert ->
((PoolId -> Const PoolId PoolId)
-> PoolRegistrationCertificate
-> Const PoolId PoolRegistrationCertificate)
-> PoolRegistrationCertificate -> PoolId
forall a s. ((a -> Const a a) -> s -> Const a s) -> s -> a
view IsLabel
"poolId"
((PoolId -> Const PoolId PoolId)
-> PoolRegistrationCertificate
-> Const PoolId PoolRegistrationCertificate)
(PoolId -> Const PoolId PoolId)
-> PoolRegistrationCertificate
-> Const PoolId PoolRegistrationCertificate
#poolId PoolRegistrationCertificate
cert
Retirement PoolRetirementCertificate
cert ->
((PoolId -> Const PoolId PoolId)
-> PoolRetirementCertificate
-> Const PoolId PoolRetirementCertificate)
-> PoolRetirementCertificate -> PoolId
forall a s. ((a -> Const a a) -> s -> Const a s) -> s -> a
view IsLabel
"poolId"
((PoolId -> Const PoolId PoolId)
-> PoolRetirementCertificate
-> Const PoolId PoolRetirementCertificate)
(PoolId -> Const PoolId PoolId)
-> PoolRetirementCertificate
-> Const PoolId PoolRetirementCertificate
#poolId PoolRetirementCertificate
cert
setPoolCertificatePoolId :: PoolId -> PoolCertificate -> PoolCertificate
setPoolCertificatePoolId :: PoolId -> PoolCertificate -> PoolCertificate
setPoolCertificatePoolId PoolId
newPoolId = \case
Registration PoolRegistrationCertificate
cert -> PoolRegistrationCertificate -> PoolCertificate
Registration
(PoolRegistrationCertificate -> PoolCertificate)
-> PoolRegistrationCertificate -> PoolCertificate
forall a b. (a -> b) -> a -> b
$ Lens
PoolRegistrationCertificate
PoolRegistrationCertificate
PoolId
PoolId
-> PoolId
-> PoolRegistrationCertificate
-> PoolRegistrationCertificate
forall s t a b. Lens s t a b -> b -> s -> t
set IsLabel
"poolId"
((PoolId -> f PoolId)
-> PoolRegistrationCertificate -> f PoolRegistrationCertificate)
Lens
PoolRegistrationCertificate
PoolRegistrationCertificate
PoolId
PoolId
#poolId PoolId
newPoolId PoolRegistrationCertificate
cert
Retirement PoolRetirementCertificate
cert -> PoolRetirementCertificate -> PoolCertificate
Retirement
(PoolRetirementCertificate -> PoolCertificate)
-> PoolRetirementCertificate -> PoolCertificate
forall a b. (a -> b) -> a -> b
$ Lens
PoolRetirementCertificate PoolRetirementCertificate PoolId PoolId
-> PoolId -> PoolRetirementCertificate -> PoolRetirementCertificate
forall s t a b. Lens s t a b -> b -> s -> t
set IsLabel
"poolId"
((PoolId -> f PoolId)
-> PoolRetirementCertificate -> f PoolRetirementCertificate)
Lens
PoolRetirementCertificate PoolRetirementCertificate PoolId PoolId
#poolId PoolId
newPoolId PoolRetirementCertificate
cert
data PoolRegistrationCertificate = PoolRegistrationCertificate
{ PoolRegistrationCertificate -> PoolId
poolId :: !PoolId
, PoolRegistrationCertificate -> [PoolOwner]
poolOwners :: ![PoolOwner]
, PoolRegistrationCertificate -> Percentage
poolMargin :: Percentage
, PoolRegistrationCertificate -> Coin
poolCost :: Coin
, PoolRegistrationCertificate -> Coin
poolPledge :: Coin
, PoolRegistrationCertificate
-> Maybe (StakePoolMetadataUrl, StakePoolMetadataHash)
poolMetadata :: Maybe (StakePoolMetadataUrl, StakePoolMetadataHash)
} deriving ((forall x.
PoolRegistrationCertificate -> Rep PoolRegistrationCertificate x)
-> (forall x.
Rep PoolRegistrationCertificate x -> PoolRegistrationCertificate)
-> Generic PoolRegistrationCertificate
forall x.
Rep PoolRegistrationCertificate x -> PoolRegistrationCertificate
forall x.
PoolRegistrationCertificate -> Rep PoolRegistrationCertificate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep PoolRegistrationCertificate x -> PoolRegistrationCertificate
$cfrom :: forall x.
PoolRegistrationCertificate -> Rep PoolRegistrationCertificate x
Generic, Int -> PoolRegistrationCertificate -> ShowS
[PoolRegistrationCertificate] -> ShowS
PoolRegistrationCertificate -> String
(Int -> PoolRegistrationCertificate -> ShowS)
-> (PoolRegistrationCertificate -> String)
-> ([PoolRegistrationCertificate] -> ShowS)
-> Show PoolRegistrationCertificate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PoolRegistrationCertificate] -> ShowS
$cshowList :: [PoolRegistrationCertificate] -> ShowS
show :: PoolRegistrationCertificate -> String
$cshow :: PoolRegistrationCertificate -> String
showsPrec :: Int -> PoolRegistrationCertificate -> ShowS
$cshowsPrec :: Int -> PoolRegistrationCertificate -> ShowS
Show, PoolRegistrationCertificate -> PoolRegistrationCertificate -> Bool
(PoolRegistrationCertificate
-> PoolRegistrationCertificate -> Bool)
-> (PoolRegistrationCertificate
-> PoolRegistrationCertificate -> Bool)
-> Eq PoolRegistrationCertificate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PoolRegistrationCertificate -> PoolRegistrationCertificate -> Bool
$c/= :: PoolRegistrationCertificate -> PoolRegistrationCertificate -> Bool
== :: PoolRegistrationCertificate -> PoolRegistrationCertificate -> Bool
$c== :: PoolRegistrationCertificate -> PoolRegistrationCertificate -> Bool
Eq, Eq PoolRegistrationCertificate
Eq PoolRegistrationCertificate
-> (PoolRegistrationCertificate
-> PoolRegistrationCertificate -> Ordering)
-> (PoolRegistrationCertificate
-> PoolRegistrationCertificate -> Bool)
-> (PoolRegistrationCertificate
-> PoolRegistrationCertificate -> Bool)
-> (PoolRegistrationCertificate
-> PoolRegistrationCertificate -> Bool)
-> (PoolRegistrationCertificate
-> PoolRegistrationCertificate -> Bool)
-> (PoolRegistrationCertificate
-> PoolRegistrationCertificate -> PoolRegistrationCertificate)
-> (PoolRegistrationCertificate
-> PoolRegistrationCertificate -> PoolRegistrationCertificate)
-> Ord PoolRegistrationCertificate
PoolRegistrationCertificate -> PoolRegistrationCertificate -> Bool
PoolRegistrationCertificate
-> PoolRegistrationCertificate -> Ordering
PoolRegistrationCertificate
-> PoolRegistrationCertificate -> PoolRegistrationCertificate
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PoolRegistrationCertificate
-> PoolRegistrationCertificate -> PoolRegistrationCertificate
$cmin :: PoolRegistrationCertificate
-> PoolRegistrationCertificate -> PoolRegistrationCertificate
max :: PoolRegistrationCertificate
-> PoolRegistrationCertificate -> PoolRegistrationCertificate
$cmax :: PoolRegistrationCertificate
-> PoolRegistrationCertificate -> PoolRegistrationCertificate
>= :: PoolRegistrationCertificate -> PoolRegistrationCertificate -> Bool
$c>= :: PoolRegistrationCertificate -> PoolRegistrationCertificate -> Bool
> :: PoolRegistrationCertificate -> PoolRegistrationCertificate -> Bool
$c> :: PoolRegistrationCertificate -> PoolRegistrationCertificate -> Bool
<= :: PoolRegistrationCertificate -> PoolRegistrationCertificate -> Bool
$c<= :: PoolRegistrationCertificate -> PoolRegistrationCertificate -> Bool
< :: PoolRegistrationCertificate -> PoolRegistrationCertificate -> Bool
$c< :: PoolRegistrationCertificate -> PoolRegistrationCertificate -> Bool
compare :: PoolRegistrationCertificate
-> PoolRegistrationCertificate -> Ordering
$ccompare :: PoolRegistrationCertificate
-> PoolRegistrationCertificate -> Ordering
$cp1Ord :: Eq PoolRegistrationCertificate
Ord)
instance NFData PoolRegistrationCertificate
instance Buildable PoolRegistrationCertificate where
build :: PoolRegistrationCertificate -> Builder
build (PoolRegistrationCertificate {PoolId
poolId :: PoolId
$sel:poolId:PoolRegistrationCertificate :: PoolRegistrationCertificate -> PoolId
poolId, [PoolOwner]
poolOwners :: [PoolOwner]
$sel:poolOwners:PoolRegistrationCertificate :: PoolRegistrationCertificate -> [PoolOwner]
poolOwners}) = Builder
forall a. Monoid a => a
mempty
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
"Registration of "
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> PoolId -> Builder
forall p. Buildable p => p -> Builder
build PoolId
poolId
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
" owned by "
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> [PoolOwner] -> Builder
forall p. Buildable p => p -> Builder
build [PoolOwner]
poolOwners
data PoolRetirementCertificate = PoolRetirementCertificate
{ PoolRetirementCertificate -> PoolId
poolId :: !PoolId
, PoolRetirementCertificate -> EpochNo
retirementEpoch :: !EpochNo
} deriving ((forall x.
PoolRetirementCertificate -> Rep PoolRetirementCertificate x)
-> (forall x.
Rep PoolRetirementCertificate x -> PoolRetirementCertificate)
-> Generic PoolRetirementCertificate
forall x.
Rep PoolRetirementCertificate x -> PoolRetirementCertificate
forall x.
PoolRetirementCertificate -> Rep PoolRetirementCertificate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep PoolRetirementCertificate x -> PoolRetirementCertificate
$cfrom :: forall x.
PoolRetirementCertificate -> Rep PoolRetirementCertificate x
Generic, Int -> PoolRetirementCertificate -> ShowS
[PoolRetirementCertificate] -> ShowS
PoolRetirementCertificate -> String
(Int -> PoolRetirementCertificate -> ShowS)
-> (PoolRetirementCertificate -> String)
-> ([PoolRetirementCertificate] -> ShowS)
-> Show PoolRetirementCertificate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PoolRetirementCertificate] -> ShowS
$cshowList :: [PoolRetirementCertificate] -> ShowS
show :: PoolRetirementCertificate -> String
$cshow :: PoolRetirementCertificate -> String
showsPrec :: Int -> PoolRetirementCertificate -> ShowS
$cshowsPrec :: Int -> PoolRetirementCertificate -> ShowS
Show, PoolRetirementCertificate -> PoolRetirementCertificate -> Bool
(PoolRetirementCertificate -> PoolRetirementCertificate -> Bool)
-> (PoolRetirementCertificate -> PoolRetirementCertificate -> Bool)
-> Eq PoolRetirementCertificate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PoolRetirementCertificate -> PoolRetirementCertificate -> Bool
$c/= :: PoolRetirementCertificate -> PoolRetirementCertificate -> Bool
== :: PoolRetirementCertificate -> PoolRetirementCertificate -> Bool
$c== :: PoolRetirementCertificate -> PoolRetirementCertificate -> Bool
Eq, Eq PoolRetirementCertificate
Eq PoolRetirementCertificate
-> (PoolRetirementCertificate
-> PoolRetirementCertificate -> Ordering)
-> (PoolRetirementCertificate -> PoolRetirementCertificate -> Bool)
-> (PoolRetirementCertificate -> PoolRetirementCertificate -> Bool)
-> (PoolRetirementCertificate -> PoolRetirementCertificate -> Bool)
-> (PoolRetirementCertificate -> PoolRetirementCertificate -> Bool)
-> (PoolRetirementCertificate
-> PoolRetirementCertificate -> PoolRetirementCertificate)
-> (PoolRetirementCertificate
-> PoolRetirementCertificate -> PoolRetirementCertificate)
-> Ord PoolRetirementCertificate
PoolRetirementCertificate -> PoolRetirementCertificate -> Bool
PoolRetirementCertificate -> PoolRetirementCertificate -> Ordering
PoolRetirementCertificate
-> PoolRetirementCertificate -> PoolRetirementCertificate
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PoolRetirementCertificate
-> PoolRetirementCertificate -> PoolRetirementCertificate
$cmin :: PoolRetirementCertificate
-> PoolRetirementCertificate -> PoolRetirementCertificate
max :: PoolRetirementCertificate
-> PoolRetirementCertificate -> PoolRetirementCertificate
$cmax :: PoolRetirementCertificate
-> PoolRetirementCertificate -> PoolRetirementCertificate
>= :: PoolRetirementCertificate -> PoolRetirementCertificate -> Bool
$c>= :: PoolRetirementCertificate -> PoolRetirementCertificate -> Bool
> :: PoolRetirementCertificate -> PoolRetirementCertificate -> Bool
$c> :: PoolRetirementCertificate -> PoolRetirementCertificate -> Bool
<= :: PoolRetirementCertificate -> PoolRetirementCertificate -> Bool
$c<= :: PoolRetirementCertificate -> PoolRetirementCertificate -> Bool
< :: PoolRetirementCertificate -> PoolRetirementCertificate -> Bool
$c< :: PoolRetirementCertificate -> PoolRetirementCertificate -> Bool
compare :: PoolRetirementCertificate -> PoolRetirementCertificate -> Ordering
$ccompare :: PoolRetirementCertificate -> PoolRetirementCertificate -> Ordering
$cp1Ord :: Eq PoolRetirementCertificate
Ord)
instance NFData PoolRetirementCertificate
instance Buildable PoolRetirementCertificate where
build :: PoolRetirementCertificate -> Builder
build (PoolRetirementCertificate PoolId
p EpochNo
e) = Builder
forall a. Monoid a => a
mempty
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
"Pool "
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> PoolId -> Builder
forall p. Buildable p => p -> Builder
build PoolId
p
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
" with retirement epoch "
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> EpochNo -> Builder
forall p. Buildable p => p -> Builder
build EpochNo
e
data NonWalletCertificate
= GenesisCertificate
| MIRCertificate
deriving ((forall x. NonWalletCertificate -> Rep NonWalletCertificate x)
-> (forall x. Rep NonWalletCertificate x -> NonWalletCertificate)
-> Generic NonWalletCertificate
forall x. Rep NonWalletCertificate x -> NonWalletCertificate
forall x. NonWalletCertificate -> Rep NonWalletCertificate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NonWalletCertificate x -> NonWalletCertificate
$cfrom :: forall x. NonWalletCertificate -> Rep NonWalletCertificate x
Generic, Int -> NonWalletCertificate -> ShowS
[NonWalletCertificate] -> ShowS
NonWalletCertificate -> String
(Int -> NonWalletCertificate -> ShowS)
-> (NonWalletCertificate -> String)
-> ([NonWalletCertificate] -> ShowS)
-> Show NonWalletCertificate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NonWalletCertificate] -> ShowS
$cshowList :: [NonWalletCertificate] -> ShowS
show :: NonWalletCertificate -> String
$cshow :: NonWalletCertificate -> String
showsPrec :: Int -> NonWalletCertificate -> ShowS
$cshowsPrec :: Int -> NonWalletCertificate -> ShowS
Show, ReadPrec [NonWalletCertificate]
ReadPrec NonWalletCertificate
Int -> ReadS NonWalletCertificate
ReadS [NonWalletCertificate]
(Int -> ReadS NonWalletCertificate)
-> ReadS [NonWalletCertificate]
-> ReadPrec NonWalletCertificate
-> ReadPrec [NonWalletCertificate]
-> Read NonWalletCertificate
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [NonWalletCertificate]
$creadListPrec :: ReadPrec [NonWalletCertificate]
readPrec :: ReadPrec NonWalletCertificate
$creadPrec :: ReadPrec NonWalletCertificate
readList :: ReadS [NonWalletCertificate]
$creadList :: ReadS [NonWalletCertificate]
readsPrec :: Int -> ReadS NonWalletCertificate
$creadsPrec :: Int -> ReadS NonWalletCertificate
Read, NonWalletCertificate -> NonWalletCertificate -> Bool
(NonWalletCertificate -> NonWalletCertificate -> Bool)
-> (NonWalletCertificate -> NonWalletCertificate -> Bool)
-> Eq NonWalletCertificate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NonWalletCertificate -> NonWalletCertificate -> Bool
$c/= :: NonWalletCertificate -> NonWalletCertificate -> Bool
== :: NonWalletCertificate -> NonWalletCertificate -> Bool
$c== :: NonWalletCertificate -> NonWalletCertificate -> Bool
Eq)
instance ToText NonWalletCertificate where
toText :: NonWalletCertificate -> Text
toText NonWalletCertificate
GenesisCertificate = Text
"genesis"
toText NonWalletCertificate
MIRCertificate = Text
"mir"
instance FromText NonWalletCertificate where
fromText :: Text -> Either TextDecodingError NonWalletCertificate
fromText Text
"genesis" = NonWalletCertificate
-> Either TextDecodingError NonWalletCertificate
forall a b. b -> Either a b
Right NonWalletCertificate
GenesisCertificate
fromText Text
"mir" = NonWalletCertificate
-> Either TextDecodingError NonWalletCertificate
forall a b. b -> Either a b
Right NonWalletCertificate
MIRCertificate
fromText Text
_ = TextDecodingError -> Either TextDecodingError NonWalletCertificate
forall a b. a -> Either a b
Left (TextDecodingError
-> Either TextDecodingError NonWalletCertificate)
-> TextDecodingError
-> Either TextDecodingError NonWalletCertificate
forall a b. (a -> b) -> a -> b
$ String -> TextDecodingError
TextDecodingError
String
"expecting either 'genesis' or 'mir' for NonWalletCertificate text value"
instance NFData NonWalletCertificate
data Certificate =
CertificateOfDelegation DelegationCertificate
| CertificateOfPool PoolCertificate
| CertificateOther NonWalletCertificate
deriving ((forall x. Certificate -> Rep Certificate x)
-> (forall x. Rep Certificate x -> Certificate)
-> Generic Certificate
forall x. Rep Certificate x -> Certificate
forall x. Certificate -> Rep Certificate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Certificate x -> Certificate
$cfrom :: forall x. Certificate -> Rep Certificate x
Generic, Int -> Certificate -> ShowS
[Certificate] -> ShowS
Certificate -> String
(Int -> Certificate -> ShowS)
-> (Certificate -> String)
-> ([Certificate] -> ShowS)
-> Show Certificate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Certificate] -> ShowS
$cshowList :: [Certificate] -> ShowS
show :: Certificate -> String
$cshow :: Certificate -> String
showsPrec :: Int -> Certificate -> ShowS
$cshowsPrec :: Int -> Certificate -> ShowS
Show, Certificate -> Certificate -> Bool
(Certificate -> Certificate -> Bool)
-> (Certificate -> Certificate -> Bool) -> Eq Certificate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Certificate -> Certificate -> Bool
$c/= :: Certificate -> Certificate -> Bool
== :: Certificate -> Certificate -> Bool
$c== :: Certificate -> Certificate -> Bool
Eq)
instance NFData Certificate
data CertificatePublicationTime = CertificatePublicationTime
{ CertificatePublicationTime -> SlotNo
slotNo
:: SlotNo
, CertificatePublicationTime -> Word64
slotInternalIndex
:: Word64
}
deriving (CertificatePublicationTime -> CertificatePublicationTime -> Bool
(CertificatePublicationTime -> CertificatePublicationTime -> Bool)
-> (CertificatePublicationTime
-> CertificatePublicationTime -> Bool)
-> Eq CertificatePublicationTime
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CertificatePublicationTime -> CertificatePublicationTime -> Bool
$c/= :: CertificatePublicationTime -> CertificatePublicationTime -> Bool
== :: CertificatePublicationTime -> CertificatePublicationTime -> Bool
$c== :: CertificatePublicationTime -> CertificatePublicationTime -> Bool
Eq, (forall x.
CertificatePublicationTime -> Rep CertificatePublicationTime x)
-> (forall x.
Rep CertificatePublicationTime x -> CertificatePublicationTime)
-> Generic CertificatePublicationTime
forall x.
Rep CertificatePublicationTime x -> CertificatePublicationTime
forall x.
CertificatePublicationTime -> Rep CertificatePublicationTime x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CertificatePublicationTime x -> CertificatePublicationTime
$cfrom :: forall x.
CertificatePublicationTime -> Rep CertificatePublicationTime x
Generic, Eq CertificatePublicationTime
Eq CertificatePublicationTime
-> (CertificatePublicationTime
-> CertificatePublicationTime -> Ordering)
-> (CertificatePublicationTime
-> CertificatePublicationTime -> Bool)
-> (CertificatePublicationTime
-> CertificatePublicationTime -> Bool)
-> (CertificatePublicationTime
-> CertificatePublicationTime -> Bool)
-> (CertificatePublicationTime
-> CertificatePublicationTime -> Bool)
-> (CertificatePublicationTime
-> CertificatePublicationTime -> CertificatePublicationTime)
-> (CertificatePublicationTime
-> CertificatePublicationTime -> CertificatePublicationTime)
-> Ord CertificatePublicationTime
CertificatePublicationTime -> CertificatePublicationTime -> Bool
CertificatePublicationTime
-> CertificatePublicationTime -> Ordering
CertificatePublicationTime
-> CertificatePublicationTime -> CertificatePublicationTime
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CertificatePublicationTime
-> CertificatePublicationTime -> CertificatePublicationTime
$cmin :: CertificatePublicationTime
-> CertificatePublicationTime -> CertificatePublicationTime
max :: CertificatePublicationTime
-> CertificatePublicationTime -> CertificatePublicationTime
$cmax :: CertificatePublicationTime
-> CertificatePublicationTime -> CertificatePublicationTime
>= :: CertificatePublicationTime -> CertificatePublicationTime -> Bool
$c>= :: CertificatePublicationTime -> CertificatePublicationTime -> Bool
> :: CertificatePublicationTime -> CertificatePublicationTime -> Bool
$c> :: CertificatePublicationTime -> CertificatePublicationTime -> Bool
<= :: CertificatePublicationTime -> CertificatePublicationTime -> Bool
$c<= :: CertificatePublicationTime -> CertificatePublicationTime -> Bool
< :: CertificatePublicationTime -> CertificatePublicationTime -> Bool
$c< :: CertificatePublicationTime -> CertificatePublicationTime -> Bool
compare :: CertificatePublicationTime
-> CertificatePublicationTime -> Ordering
$ccompare :: CertificatePublicationTime
-> CertificatePublicationTime -> Ordering
$cp1Ord :: Eq CertificatePublicationTime
Ord, Int -> CertificatePublicationTime -> ShowS
[CertificatePublicationTime] -> ShowS
CertificatePublicationTime -> String
(Int -> CertificatePublicationTime -> ShowS)
-> (CertificatePublicationTime -> String)
-> ([CertificatePublicationTime] -> ShowS)
-> Show CertificatePublicationTime
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CertificatePublicationTime] -> ShowS
$cshowList :: [CertificatePublicationTime] -> ShowS
show :: CertificatePublicationTime -> String
$cshow :: CertificatePublicationTime -> String
showsPrec :: Int -> CertificatePublicationTime -> ShowS
$cshowsPrec :: Int -> CertificatePublicationTime -> ShowS
Show)
data PoolLifeCycleStatus
= PoolNotRegistered
| PoolRegistered
PoolRegistrationCertificate
| PoolRegisteredAndRetired
PoolRegistrationCertificate
PoolRetirementCertificate
deriving (PoolLifeCycleStatus -> PoolLifeCycleStatus -> Bool
(PoolLifeCycleStatus -> PoolLifeCycleStatus -> Bool)
-> (PoolLifeCycleStatus -> PoolLifeCycleStatus -> Bool)
-> Eq PoolLifeCycleStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PoolLifeCycleStatus -> PoolLifeCycleStatus -> Bool
$c/= :: PoolLifeCycleStatus -> PoolLifeCycleStatus -> Bool
== :: PoolLifeCycleStatus -> PoolLifeCycleStatus -> Bool
$c== :: PoolLifeCycleStatus -> PoolLifeCycleStatus -> Bool
Eq, Eq PoolLifeCycleStatus
Eq PoolLifeCycleStatus
-> (PoolLifeCycleStatus -> PoolLifeCycleStatus -> Ordering)
-> (PoolLifeCycleStatus -> PoolLifeCycleStatus -> Bool)
-> (PoolLifeCycleStatus -> PoolLifeCycleStatus -> Bool)
-> (PoolLifeCycleStatus -> PoolLifeCycleStatus -> Bool)
-> (PoolLifeCycleStatus -> PoolLifeCycleStatus -> Bool)
-> (PoolLifeCycleStatus
-> PoolLifeCycleStatus -> PoolLifeCycleStatus)
-> (PoolLifeCycleStatus
-> PoolLifeCycleStatus -> PoolLifeCycleStatus)
-> Ord PoolLifeCycleStatus
PoolLifeCycleStatus -> PoolLifeCycleStatus -> Bool
PoolLifeCycleStatus -> PoolLifeCycleStatus -> Ordering
PoolLifeCycleStatus -> PoolLifeCycleStatus -> PoolLifeCycleStatus
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PoolLifeCycleStatus -> PoolLifeCycleStatus -> PoolLifeCycleStatus
$cmin :: PoolLifeCycleStatus -> PoolLifeCycleStatus -> PoolLifeCycleStatus
max :: PoolLifeCycleStatus -> PoolLifeCycleStatus -> PoolLifeCycleStatus
$cmax :: PoolLifeCycleStatus -> PoolLifeCycleStatus -> PoolLifeCycleStatus
>= :: PoolLifeCycleStatus -> PoolLifeCycleStatus -> Bool
$c>= :: PoolLifeCycleStatus -> PoolLifeCycleStatus -> Bool
> :: PoolLifeCycleStatus -> PoolLifeCycleStatus -> Bool
$c> :: PoolLifeCycleStatus -> PoolLifeCycleStatus -> Bool
<= :: PoolLifeCycleStatus -> PoolLifeCycleStatus -> Bool
$c<= :: PoolLifeCycleStatus -> PoolLifeCycleStatus -> Bool
< :: PoolLifeCycleStatus -> PoolLifeCycleStatus -> Bool
$c< :: PoolLifeCycleStatus -> PoolLifeCycleStatus -> Bool
compare :: PoolLifeCycleStatus -> PoolLifeCycleStatus -> Ordering
$ccompare :: PoolLifeCycleStatus -> PoolLifeCycleStatus -> Ordering
$cp1Ord :: Eq PoolLifeCycleStatus
Ord, Int -> PoolLifeCycleStatus -> ShowS
[PoolLifeCycleStatus] -> ShowS
PoolLifeCycleStatus -> String
(Int -> PoolLifeCycleStatus -> ShowS)
-> (PoolLifeCycleStatus -> String)
-> ([PoolLifeCycleStatus] -> ShowS)
-> Show PoolLifeCycleStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PoolLifeCycleStatus] -> ShowS
$cshowList :: [PoolLifeCycleStatus] -> ShowS
show :: PoolLifeCycleStatus -> String
$cshow :: PoolLifeCycleStatus -> String
showsPrec :: Int -> PoolLifeCycleStatus -> ShowS
$cshowsPrec :: Int -> PoolLifeCycleStatus -> ShowS
Show)
getPoolRegistrationCertificate
:: PoolLifeCycleStatus -> Maybe PoolRegistrationCertificate
getPoolRegistrationCertificate :: PoolLifeCycleStatus -> Maybe PoolRegistrationCertificate
getPoolRegistrationCertificate = \case
PoolLifeCycleStatus
PoolNotRegistered -> Maybe PoolRegistrationCertificate
forall a. Maybe a
Nothing
PoolRegistered PoolRegistrationCertificate
c -> PoolRegistrationCertificate -> Maybe PoolRegistrationCertificate
forall a. a -> Maybe a
Just PoolRegistrationCertificate
c
PoolRegisteredAndRetired PoolRegistrationCertificate
c PoolRetirementCertificate
_ -> PoolRegistrationCertificate -> Maybe PoolRegistrationCertificate
forall a. a -> Maybe a
Just PoolRegistrationCertificate
c
getPoolRetirementCertificate
:: PoolLifeCycleStatus -> Maybe PoolRetirementCertificate
getPoolRetirementCertificate :: PoolLifeCycleStatus -> Maybe PoolRetirementCertificate
getPoolRetirementCertificate = \case
PoolLifeCycleStatus
PoolNotRegistered -> Maybe PoolRetirementCertificate
forall a. Maybe a
Nothing
PoolRegistered PoolRegistrationCertificate
_ -> Maybe PoolRetirementCertificate
forall a. Maybe a
Nothing
PoolRegisteredAndRetired PoolRegistrationCertificate
_ PoolRetirementCertificate
c -> PoolRetirementCertificate -> Maybe PoolRetirementCertificate
forall a. a -> Maybe a
Just PoolRetirementCertificate
c
newtype Signature (what :: Type) = Signature { Signature what -> ByteString
getSignature :: ByteString }
deriving stock (Int -> Signature what -> ShowS
[Signature what] -> ShowS
Signature what -> String
(Int -> Signature what -> ShowS)
-> (Signature what -> String)
-> ([Signature what] -> ShowS)
-> Show (Signature what)
forall what. Int -> Signature what -> ShowS
forall what. [Signature what] -> ShowS
forall what. Signature what -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Signature what] -> ShowS
$cshowList :: forall what. [Signature what] -> ShowS
show :: Signature what -> String
$cshow :: forall what. Signature what -> String
showsPrec :: Int -> Signature what -> ShowS
$cshowsPrec :: forall what. Int -> Signature what -> ShowS
Show, Signature what -> Signature what -> Bool
(Signature what -> Signature what -> Bool)
-> (Signature what -> Signature what -> Bool)
-> Eq (Signature what)
forall what. Signature what -> Signature what -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Signature what -> Signature what -> Bool
$c/= :: forall what. Signature what -> Signature what -> Bool
== :: Signature what -> Signature what -> Bool
$c== :: forall what. Signature what -> Signature what -> Bool
Eq, (forall x. Signature what -> Rep (Signature what) x)
-> (forall x. Rep (Signature what) x -> Signature what)
-> Generic (Signature what)
forall x. Rep (Signature what) x -> Signature what
forall x. Signature what -> Rep (Signature what) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall what x. Rep (Signature what) x -> Signature what
forall what x. Signature what -> Rep (Signature what) x
$cto :: forall what x. Rep (Signature what) x -> Signature what
$cfrom :: forall what x. Signature what -> Rep (Signature what) x
Generic)
deriving newtype (Signature what -> Int
Signature what -> Ptr p -> IO ()
Signature what -> (Ptr p -> IO a) -> IO a
(Signature what -> Int)
-> (forall p a. Signature what -> (Ptr p -> IO a) -> IO a)
-> (forall p. Signature what -> Ptr p -> IO ())
-> ByteArrayAccess (Signature what)
forall what. Signature what -> Int
forall p. Signature what -> Ptr p -> IO ()
forall ba.
(ba -> Int)
-> (forall p a. ba -> (Ptr p -> IO a) -> IO a)
-> (forall p. ba -> Ptr p -> IO ())
-> ByteArrayAccess ba
forall what p. Signature what -> Ptr p -> IO ()
forall p a. Signature what -> (Ptr p -> IO a) -> IO a
forall what p a. Signature what -> (Ptr p -> IO a) -> IO a
copyByteArrayToPtr :: Signature what -> Ptr p -> IO ()
$ccopyByteArrayToPtr :: forall what p. Signature what -> Ptr p -> IO ()
withByteArray :: Signature what -> (Ptr p -> IO a) -> IO a
$cwithByteArray :: forall what p a. Signature what -> (Ptr p -> IO a) -> IO a
length :: Signature what -> Int
$clength :: forall what. Signature what -> Int
ByteArrayAccess)
newtype TokenMetadataServer = TokenMetadataServer
{ TokenMetadataServer -> URI
unTokenMetadataServer :: URI }
deriving (Int -> TokenMetadataServer -> ShowS
[TokenMetadataServer] -> ShowS
TokenMetadataServer -> String
(Int -> TokenMetadataServer -> ShowS)
-> (TokenMetadataServer -> String)
-> ([TokenMetadataServer] -> ShowS)
-> Show TokenMetadataServer
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TokenMetadataServer] -> ShowS
$cshowList :: [TokenMetadataServer] -> ShowS
show :: TokenMetadataServer -> String
$cshow :: TokenMetadataServer -> String
showsPrec :: Int -> TokenMetadataServer -> ShowS
$cshowsPrec :: Int -> TokenMetadataServer -> ShowS
Show, (forall x. TokenMetadataServer -> Rep TokenMetadataServer x)
-> (forall x. Rep TokenMetadataServer x -> TokenMetadataServer)
-> Generic TokenMetadataServer
forall x. Rep TokenMetadataServer x -> TokenMetadataServer
forall x. TokenMetadataServer -> Rep TokenMetadataServer x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TokenMetadataServer x -> TokenMetadataServer
$cfrom :: forall x. TokenMetadataServer -> Rep TokenMetadataServer x
Generic, TokenMetadataServer -> TokenMetadataServer -> Bool
(TokenMetadataServer -> TokenMetadataServer -> Bool)
-> (TokenMetadataServer -> TokenMetadataServer -> Bool)
-> Eq TokenMetadataServer
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TokenMetadataServer -> TokenMetadataServer -> Bool
$c/= :: TokenMetadataServer -> TokenMetadataServer -> Bool
== :: TokenMetadataServer -> TokenMetadataServer -> Bool
$c== :: TokenMetadataServer -> TokenMetadataServer -> Bool
Eq)
instance ToText TokenMetadataServer where
toText :: TokenMetadataServer -> Text
toText = URI -> Text
uriToText (URI -> Text)
-> (TokenMetadataServer -> URI) -> TokenMetadataServer -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TokenMetadataServer -> URI
unTokenMetadataServer
instance FromText TokenMetadataServer where
fromText :: Text -> Either TextDecodingError TokenMetadataServer
fromText = (URI -> TokenMetadataServer)
-> Either TextDecodingError URI
-> Either TextDecodingError TokenMetadataServer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap URI -> TokenMetadataServer
TokenMetadataServer (Either TextDecodingError URI
-> Either TextDecodingError TokenMetadataServer)
-> (Text -> Either TextDecodingError URI)
-> Text
-> Either TextDecodingError TokenMetadataServer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either TextDecodingError URI
parseURI
newtype SmashServer = SmashServer { SmashServer -> URI
unSmashServer :: URI }
deriving (Int -> SmashServer -> ShowS
[SmashServer] -> ShowS
SmashServer -> String
(Int -> SmashServer -> ShowS)
-> (SmashServer -> String)
-> ([SmashServer] -> ShowS)
-> Show SmashServer
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SmashServer] -> ShowS
$cshowList :: [SmashServer] -> ShowS
show :: SmashServer -> String
$cshow :: SmashServer -> String
showsPrec :: Int -> SmashServer -> ShowS
$cshowsPrec :: Int -> SmashServer -> ShowS
Show, (forall x. SmashServer -> Rep SmashServer x)
-> (forall x. Rep SmashServer x -> SmashServer)
-> Generic SmashServer
forall x. Rep SmashServer x -> SmashServer
forall x. SmashServer -> Rep SmashServer x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SmashServer x -> SmashServer
$cfrom :: forall x. SmashServer -> Rep SmashServer x
Generic, SmashServer -> SmashServer -> Bool
(SmashServer -> SmashServer -> Bool)
-> (SmashServer -> SmashServer -> Bool) -> Eq SmashServer
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SmashServer -> SmashServer -> Bool
$c/= :: SmashServer -> SmashServer -> Bool
== :: SmashServer -> SmashServer -> Bool
$c== :: SmashServer -> SmashServer -> Bool
Eq)
instance ToText SmashServer where
toText :: SmashServer -> Text
toText = URI -> Text
uriToText (URI -> Text) -> (SmashServer -> URI) -> SmashServer -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SmashServer -> URI
unSmashServer
instance FromText SmashServer where
fromText :: Text -> Either TextDecodingError SmashServer
fromText = (URI -> SmashServer)
-> Either TextDecodingError URI
-> Either TextDecodingError SmashServer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap URI -> SmashServer
SmashServer (Either TextDecodingError URI
-> Either TextDecodingError SmashServer)
-> (Text -> Either TextDecodingError URI)
-> Text
-> Either TextDecodingError SmashServer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either TextDecodingError URI
parseURI
data PoolMetadataSource
= FetchNone
| FetchDirect
| FetchSMASH SmashServer
deriving (Int -> PoolMetadataSource -> ShowS
[PoolMetadataSource] -> ShowS
PoolMetadataSource -> String
(Int -> PoolMetadataSource -> ShowS)
-> (PoolMetadataSource -> String)
-> ([PoolMetadataSource] -> ShowS)
-> Show PoolMetadataSource
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PoolMetadataSource] -> ShowS
$cshowList :: [PoolMetadataSource] -> ShowS
show :: PoolMetadataSource -> String
$cshow :: PoolMetadataSource -> String
showsPrec :: Int -> PoolMetadataSource -> ShowS
$cshowsPrec :: Int -> PoolMetadataSource -> ShowS
Show, (forall x. PoolMetadataSource -> Rep PoolMetadataSource x)
-> (forall x. Rep PoolMetadataSource x -> PoolMetadataSource)
-> Generic PoolMetadataSource
forall x. Rep PoolMetadataSource x -> PoolMetadataSource
forall x. PoolMetadataSource -> Rep PoolMetadataSource x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PoolMetadataSource x -> PoolMetadataSource
$cfrom :: forall x. PoolMetadataSource -> Rep PoolMetadataSource x
Generic, PoolMetadataSource -> PoolMetadataSource -> Bool
(PoolMetadataSource -> PoolMetadataSource -> Bool)
-> (PoolMetadataSource -> PoolMetadataSource -> Bool)
-> Eq PoolMetadataSource
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PoolMetadataSource -> PoolMetadataSource -> Bool
$c/= :: PoolMetadataSource -> PoolMetadataSource -> Bool
== :: PoolMetadataSource -> PoolMetadataSource -> Bool
$c== :: PoolMetadataSource -> PoolMetadataSource -> Bool
Eq)
instance ToText PoolMetadataSource where
toText :: PoolMetadataSource -> Text
toText PoolMetadataSource
FetchNone = (String -> Text
T.pack String
"none")
toText PoolMetadataSource
FetchDirect = (String -> Text
T.pack String
"direct")
toText (FetchSMASH (SmashServer URI
uri)) = String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ ShowS -> URI -> ShowS
uriToString ShowS
forall a. a -> a
id URI
uri String
""
instance FromText PoolMetadataSource where
fromText :: Text -> Either TextDecodingError PoolMetadataSource
fromText Text
"none" = PoolMetadataSource -> Either TextDecodingError PoolMetadataSource
forall a b. b -> Either a b
Right PoolMetadataSource
FetchNone
fromText Text
"direct" = PoolMetadataSource -> Either TextDecodingError PoolMetadataSource
forall a b. b -> Either a b
Right PoolMetadataSource
FetchDirect
fromText Text
uri = (SmashServer -> PoolMetadataSource)
-> Either TextDecodingError SmashServer
-> Either TextDecodingError PoolMetadataSource
forall (a :: * -> * -> *) b c d.
ArrowChoice a =>
a b c -> a (Either d b) (Either d c)
right SmashServer -> PoolMetadataSource
FetchSMASH (Either TextDecodingError SmashServer
-> Either TextDecodingError PoolMetadataSource)
-> (Text -> Either TextDecodingError SmashServer)
-> Text
-> Either TextDecodingError PoolMetadataSource
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FromText SmashServer =>
Text -> Either TextDecodingError SmashServer
forall a. FromText a => Text -> Either TextDecodingError a
fromText @SmashServer (Text -> Either TextDecodingError PoolMetadataSource)
-> Text -> Either TextDecodingError PoolMetadataSource
forall a b. (a -> b) -> a -> b
$ Text
uri
unsafeToPMS :: URI -> PoolMetadataSource
unsafeToPMS :: URI -> PoolMetadataSource
unsafeToPMS = SmashServer -> PoolMetadataSource
FetchSMASH (SmashServer -> PoolMetadataSource)
-> (URI -> SmashServer) -> URI -> PoolMetadataSource
forall b c a. (b -> c) -> (a -> b) -> a -> c
. URI -> SmashServer
SmashServer
data Settings = Settings {
Settings -> PoolMetadataSource
poolMetadataSource :: PoolMetadataSource
} deriving (Int -> Settings -> ShowS
[Settings] -> ShowS
Settings -> String
(Int -> Settings -> ShowS)
-> (Settings -> String) -> ([Settings] -> ShowS) -> Show Settings
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Settings] -> ShowS
$cshowList :: [Settings] -> ShowS
show :: Settings -> String
$cshow :: Settings -> String
showsPrec :: Int -> Settings -> ShowS
$cshowsPrec :: Int -> Settings -> ShowS
Show, (forall x. Settings -> Rep Settings x)
-> (forall x. Rep Settings x -> Settings) -> Generic Settings
forall x. Rep Settings x -> Settings
forall x. Settings -> Rep Settings x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Settings x -> Settings
$cfrom :: forall x. Settings -> Rep Settings x
Generic, Settings -> Settings -> Bool
(Settings -> Settings -> Bool)
-> (Settings -> Settings -> Bool) -> Eq Settings
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Settings -> Settings -> Bool
$c/= :: Settings -> Settings -> Bool
== :: Settings -> Settings -> Bool
$c== :: Settings -> Settings -> Bool
Eq)
defaultSettings :: Settings
defaultSettings :: Settings
defaultSettings = Settings :: PoolMetadataSource -> Settings
Settings {
$sel:poolMetadataSource:Settings :: PoolMetadataSource
poolMetadataSource = PoolMetadataSource
FetchNone
}
data InternalState = InternalState
{ InternalState -> Maybe NominalDiffTime
lastMetadataGC :: Maybe POSIXTime
} deriving ((forall x. InternalState -> Rep InternalState x)
-> (forall x. Rep InternalState x -> InternalState)
-> Generic InternalState
forall x. Rep InternalState x -> InternalState
forall x. InternalState -> Rep InternalState x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InternalState x -> InternalState
$cfrom :: forall x. InternalState -> Rep InternalState x
Generic, Int -> InternalState -> ShowS
[InternalState] -> ShowS
InternalState -> String
(Int -> InternalState -> ShowS)
-> (InternalState -> String)
-> ([InternalState] -> ShowS)
-> Show InternalState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InternalState] -> ShowS
$cshowList :: [InternalState] -> ShowS
show :: InternalState -> String
$cshow :: InternalState -> String
showsPrec :: Int -> InternalState -> ShowS
$cshowsPrec :: Int -> InternalState -> ShowS
Show, InternalState -> InternalState -> Bool
(InternalState -> InternalState -> Bool)
-> (InternalState -> InternalState -> Bool) -> Eq InternalState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InternalState -> InternalState -> Bool
$c/= :: InternalState -> InternalState -> Bool
== :: InternalState -> InternalState -> Bool
$c== :: InternalState -> InternalState -> Bool
Eq)
defaultInternalState :: InternalState
defaultInternalState :: InternalState
defaultInternalState = InternalState :: Maybe NominalDiffTime -> InternalState
InternalState
{ $sel:lastMetadataGC:InternalState :: Maybe NominalDiffTime
lastMetadataGC = Maybe NominalDiffTime
forall a. Maybe a
Nothing }
instance FromJSON PoolMetadataSource where
parseJSON :: Value -> Parser PoolMetadataSource
parseJSON = Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
parseJSON (Value -> Parser Text)
-> (Text -> Parser PoolMetadataSource)
-> Value
-> Parser PoolMetadataSource
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (TextDecodingError -> Parser PoolMetadataSource)
-> (PoolMetadataSource -> Parser PoolMetadataSource)
-> Either TextDecodingError PoolMetadataSource
-> Parser PoolMetadataSource
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (String -> Parser PoolMetadataSource
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser PoolMetadataSource)
-> (TextDecodingError -> String)
-> TextDecodingError
-> Parser PoolMetadataSource
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowFmt TextDecodingError -> String
forall a. Show a => a -> String
show (ShowFmt TextDecodingError -> String)
-> (TextDecodingError -> ShowFmt TextDecodingError)
-> TextDecodingError
-> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextDecodingError -> ShowFmt TextDecodingError
forall a. a -> ShowFmt a
ShowFmt) PoolMetadataSource -> Parser PoolMetadataSource
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either TextDecodingError PoolMetadataSource
-> Parser PoolMetadataSource)
-> (Text -> Either TextDecodingError PoolMetadataSource)
-> Text
-> Parser PoolMetadataSource
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either TextDecodingError PoolMetadataSource
forall a. FromText a => Text -> Either TextDecodingError a
fromText
instance ToJSON PoolMetadataSource where
toJSON :: PoolMetadataSource -> Value
toJSON = Text -> Value
forall a. ToJSON a => a -> Value
toJSON (Text -> Value)
-> (PoolMetadataSource -> Text) -> PoolMetadataSource -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PoolMetadataSource -> Text
forall a. ToText a => a -> Text
toText