{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralisedNewtypeDeriving #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RankNTypes #-}
module Cardano.CLI.Type.Common
( AllOrOnly (..)
, AddressKeyType (..)
, AnchorScheme (..)
, AnyPlutusScriptVersion (..)
, BalanceTxExecUnits (..)
, BlockId (..)
, ByronKeyFormat (..)
, ByronKeyType (..)
, CardanoAddressKeyType (..)
, CBORObject (..)
, CertificateFile (..)
, ConstitutionHashSource (..)
, ConstitutionText (..)
, ConstitutionUrl (..)
, CredentialGenerationMode (..)
, CurrentKesPeriod (..)
, DRepCredentials (..)
, EpochLeadershipSchedule (..)
, File (..)
, FileDirection (..)
, FormatBech32 (..)
, FormatCborBin (..)
, FormatCborHex (..)
, FormatCip129 (..)
, FormatHex (..)
, FormatJson (..)
, FormatText (..)
, FormatTextEnvelope (..)
, FormatYaml (..)
, GenesisDir (..)
, GenesisFile (..)
, GenesisKeyFile (..)
, IncludeStake (..)
, InputTxBodyOrTxFile (..)
, MetadataFile (..)
, MustCheckHash (..)
, OpCertCounter
, OpCertCounterFile
, OpCertEndingKesPeriod (..)
, OpCertIntervalInformation (..)
, OpCertNodeAndOnDiskCounterInformation (..)
, OpCertNodeStateCounter (..)
, OpCertOnDiskCounter (..)
, OpCertStartingKesPeriod (..)
, PoolParams (..)
, mkPoolStates
, ParserFileDirection (..)
, PrivKeyFile (..)
, ProposalBinary
, ProposalFile
, ProposalText
, ProposalUrl (..)
, ProtocolParamsFile (..)
, ReferenceScriptAnyEra (..)
, ReferenceScriptSize (..)
, RequiredSigner (..)
, ScriptDataOrFile (..)
, ScriptFile
, ScriptRedeemerOrFile
, SigningKeyFile
, SlotsTillKesKeyExpiry (..)
, SomeKeyFile (..)
, StakeDelegators (..)
, StakePoolMetadataFile
, SupportedSchemes
, TransferDirection (..)
, TxBodyFile
, TxBuildOutputOptions (..)
, TxByronWitnessCount (..)
, TxFile
, TxSubmissionResult (..)
, TxTreasuryDonation (..)
, TxInCount (..)
, TxMempoolQuery (..)
, TxOutAnyEra (..)
, TxOutShelleyBasedEra (..)
, TxOutChangeAddress (..)
, TxOutCount (..)
, TxOutDatumAnyEra (..)
, TxShelleyWitnessCount (..)
, UpdateProposalFile (..)
, VerificationKeyBase64 (..)
, VerificationKeyFile
, VoteUrl (..)
, VoteText (..)
, VoteHashSource (..)
, WitnessFile (..)
, WitnessSigningData (..)
, DRepMetadataFile
, DRepMetadataUrl
, ResignationMetadataUrl
, PotentiallyCheckedAnchor (..)
)
where
import Cardano.Api hiding (Script)
import Cardano.Api.Ledger qualified as L
import Cardano.Ledger.Api.State.Query qualified as L
import Cardano.Ledger.State qualified as L
import Data.Aeson (object, pairs, (.=))
import Data.Aeson qualified as Aeson
import Data.Map.Strict (Map)
import Data.Map.Strict qualified as Map
import Data.String (IsString)
import Data.Text (Text)
import Data.Text qualified as Text
import Data.Word (Word64)
import GHC.Generics (Generic)
data TransferDirection
= TransferToReserves
| TransferToTreasury
deriving Int -> TransferDirection -> ShowS
[TransferDirection] -> ShowS
TransferDirection -> String
(Int -> TransferDirection -> ShowS)
-> (TransferDirection -> String)
-> ([TransferDirection] -> ShowS)
-> Show TransferDirection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TransferDirection -> ShowS
showsPrec :: Int -> TransferDirection -> ShowS
$cshow :: TransferDirection -> String
show :: TransferDirection -> String
$cshowList :: [TransferDirection] -> ShowS
showList :: [TransferDirection] -> ShowS
Show
data OpCertCounter
newtype ConstitutionUrl = ConstitutionUrl
{ ConstitutionUrl -> Url
unConstitutionUrl :: L.Url
}
deriving (ConstitutionUrl -> ConstitutionUrl -> Bool
(ConstitutionUrl -> ConstitutionUrl -> Bool)
-> (ConstitutionUrl -> ConstitutionUrl -> Bool)
-> Eq ConstitutionUrl
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ConstitutionUrl -> ConstitutionUrl -> Bool
== :: ConstitutionUrl -> ConstitutionUrl -> Bool
$c/= :: ConstitutionUrl -> ConstitutionUrl -> Bool
/= :: ConstitutionUrl -> ConstitutionUrl -> Bool
Eq, Int -> ConstitutionUrl -> ShowS
[ConstitutionUrl] -> ShowS
ConstitutionUrl -> String
(Int -> ConstitutionUrl -> ShowS)
-> (ConstitutionUrl -> String)
-> ([ConstitutionUrl] -> ShowS)
-> Show ConstitutionUrl
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ConstitutionUrl -> ShowS
showsPrec :: Int -> ConstitutionUrl -> ShowS
$cshow :: ConstitutionUrl -> String
show :: ConstitutionUrl -> String
$cshowList :: [ConstitutionUrl] -> ShowS
showList :: [ConstitutionUrl] -> ShowS
Show)
newtype ConstitutionText = ConstitutionText
{ ConstitutionText -> Text
unConstitutionText :: Text
}
deriving (ConstitutionText -> ConstitutionText -> Bool
(ConstitutionText -> ConstitutionText -> Bool)
-> (ConstitutionText -> ConstitutionText -> Bool)
-> Eq ConstitutionText
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ConstitutionText -> ConstitutionText -> Bool
== :: ConstitutionText -> ConstitutionText -> Bool
$c/= :: ConstitutionText -> ConstitutionText -> Bool
/= :: ConstitutionText -> ConstitutionText -> Bool
Eq, Int -> ConstitutionText -> ShowS
[ConstitutionText] -> ShowS
ConstitutionText -> String
(Int -> ConstitutionText -> ShowS)
-> (ConstitutionText -> String)
-> ([ConstitutionText] -> ShowS)
-> Show ConstitutionText
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ConstitutionText -> ShowS
showsPrec :: Int -> ConstitutionText -> ShowS
$cshow :: ConstitutionText -> String
show :: ConstitutionText -> String
$cshowList :: [ConstitutionText] -> ShowS
showList :: [ConstitutionText] -> ShowS
Show)
data ConstitutionHashSource
= ConstitutionHashSourceFile (File ConstitutionText In)
| ConstitutionHashSourceText Text
| ConstitutionHashSourceHash (L.SafeHash L.AnchorData)
deriving Int -> ConstitutionHashSource -> ShowS
[ConstitutionHashSource] -> ShowS
ConstitutionHashSource -> String
(Int -> ConstitutionHashSource -> ShowS)
-> (ConstitutionHashSource -> String)
-> ([ConstitutionHashSource] -> ShowS)
-> Show ConstitutionHashSource
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ConstitutionHashSource -> ShowS
showsPrec :: Int -> ConstitutionHashSource -> ShowS
$cshow :: ConstitutionHashSource -> String
show :: ConstitutionHashSource -> String
$cshowList :: [ConstitutionHashSource] -> ShowS
showList :: [ConstitutionHashSource] -> ShowS
Show
newtype ProposalUrl = ProposalUrl
{ ProposalUrl -> Url
unProposalUrl :: L.Url
}
deriving (ProposalUrl -> ProposalUrl -> Bool
(ProposalUrl -> ProposalUrl -> Bool)
-> (ProposalUrl -> ProposalUrl -> Bool) -> Eq ProposalUrl
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ProposalUrl -> ProposalUrl -> Bool
== :: ProposalUrl -> ProposalUrl -> Bool
$c/= :: ProposalUrl -> ProposalUrl -> Bool
/= :: ProposalUrl -> ProposalUrl -> Bool
Eq, Int -> ProposalUrl -> ShowS
[ProposalUrl] -> ShowS
ProposalUrl -> String
(Int -> ProposalUrl -> ShowS)
-> (ProposalUrl -> String)
-> ([ProposalUrl] -> ShowS)
-> Show ProposalUrl
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ProposalUrl -> ShowS
showsPrec :: Int -> ProposalUrl -> ShowS
$cshow :: ProposalUrl -> String
show :: ProposalUrl -> String
$cshowList :: [ProposalUrl] -> ShowS
showList :: [ProposalUrl] -> ShowS
Show)
type SupportedSchemes = [AnchorScheme]
data AnchorScheme = FileScheme | HttpScheme | HttpsScheme | IpfsScheme
deriving (Int -> AnchorScheme -> ShowS
[AnchorScheme] -> ShowS
AnchorScheme -> String
(Int -> AnchorScheme -> ShowS)
-> (AnchorScheme -> String)
-> ([AnchorScheme] -> ShowS)
-> Show AnchorScheme
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AnchorScheme -> ShowS
showsPrec :: Int -> AnchorScheme -> ShowS
$cshow :: AnchorScheme -> String
show :: AnchorScheme -> String
$cshowList :: [AnchorScheme] -> ShowS
showList :: [AnchorScheme] -> ShowS
Show, AnchorScheme -> AnchorScheme -> Bool
(AnchorScheme -> AnchorScheme -> Bool)
-> (AnchorScheme -> AnchorScheme -> Bool) -> Eq AnchorScheme
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AnchorScheme -> AnchorScheme -> Bool
== :: AnchorScheme -> AnchorScheme -> Bool
$c/= :: AnchorScheme -> AnchorScheme -> Bool
/= :: AnchorScheme -> AnchorScheme -> Bool
Eq)
data ProposalBinary
data ProposalText
data DRepMetadataUrl
data ResignationMetadataUrl
newtype VoteUrl = VoteUrl
{ VoteUrl -> Url
unVoteUrl :: L.Url
}
deriving (VoteUrl -> VoteUrl -> Bool
(VoteUrl -> VoteUrl -> Bool)
-> (VoteUrl -> VoteUrl -> Bool) -> Eq VoteUrl
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VoteUrl -> VoteUrl -> Bool
== :: VoteUrl -> VoteUrl -> Bool
$c/= :: VoteUrl -> VoteUrl -> Bool
/= :: VoteUrl -> VoteUrl -> Bool
Eq, Int -> VoteUrl -> ShowS
[VoteUrl] -> ShowS
VoteUrl -> String
(Int -> VoteUrl -> ShowS)
-> (VoteUrl -> String) -> ([VoteUrl] -> ShowS) -> Show VoteUrl
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VoteUrl -> ShowS
showsPrec :: Int -> VoteUrl -> ShowS
$cshow :: VoteUrl -> String
show :: VoteUrl -> String
$cshowList :: [VoteUrl] -> ShowS
showList :: [VoteUrl] -> ShowS
Show)
newtype VoteText = VoteText
{ VoteText -> Text
unVoteText :: Text
}
deriving (VoteText -> VoteText -> Bool
(VoteText -> VoteText -> Bool)
-> (VoteText -> VoteText -> Bool) -> Eq VoteText
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VoteText -> VoteText -> Bool
== :: VoteText -> VoteText -> Bool
$c/= :: VoteText -> VoteText -> Bool
/= :: VoteText -> VoteText -> Bool
Eq, Int -> VoteText -> ShowS
[VoteText] -> ShowS
VoteText -> String
(Int -> VoteText -> ShowS)
-> (VoteText -> String) -> ([VoteText] -> ShowS) -> Show VoteText
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VoteText -> ShowS
showsPrec :: Int -> VoteText -> ShowS
$cshow :: VoteText -> String
show :: VoteText -> String
$cshowList :: [VoteText] -> ShowS
showList :: [VoteText] -> ShowS
Show)
data VoteHashSource
= VoteHashSourceFile (File VoteText In)
| VoteHashSourceText Text
| VoteHashSourceHash (L.SafeHash L.AnchorData)
deriving Int -> VoteHashSource -> ShowS
[VoteHashSource] -> ShowS
VoteHashSource -> String
(Int -> VoteHashSource -> ShowS)
-> (VoteHashSource -> String)
-> ([VoteHashSource] -> ShowS)
-> Show VoteHashSource
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VoteHashSource -> ShowS
showsPrec :: Int -> VoteHashSource -> ShowS
$cshow :: VoteHashSource -> String
show :: VoteHashSource -> String
$cshowList :: [VoteHashSource] -> ShowS
showList :: [VoteHashSource] -> ShowS
Show
data StakeDelegators = StakeDelegators
{ StakeDelegators -> CredentialGenerationMode
stakeDelegatorsGenerationMode :: !CredentialGenerationMode
, StakeDelegators -> Word
numOfStakeDelegators :: !Word
}
deriving Int -> StakeDelegators -> ShowS
[StakeDelegators] -> ShowS
StakeDelegators -> String
(Int -> StakeDelegators -> ShowS)
-> (StakeDelegators -> String)
-> ([StakeDelegators] -> ShowS)
-> Show StakeDelegators
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StakeDelegators -> ShowS
showsPrec :: Int -> StakeDelegators -> ShowS
$cshow :: StakeDelegators -> String
show :: StakeDelegators -> String
$cshowList :: [StakeDelegators] -> ShowS
showList :: [StakeDelegators] -> ShowS
Show
data IncludeStake = WithStake | NoStake deriving Int -> IncludeStake -> ShowS
[IncludeStake] -> ShowS
IncludeStake -> String
(Int -> IncludeStake -> ShowS)
-> (IncludeStake -> String)
-> ([IncludeStake] -> ShowS)
-> Show IncludeStake
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IncludeStake -> ShowS
showsPrec :: Int -> IncludeStake -> ShowS
$cshow :: IncludeStake -> String
show :: IncludeStake -> String
$cshowList :: [IncludeStake] -> ShowS
showList :: [IncludeStake] -> ShowS
Show
data DRepCredentials = DRepCredentials
{ DRepCredentials -> CredentialGenerationMode
dRepCredentialGenerationMode :: !CredentialGenerationMode
, DRepCredentials -> Word
numOfDRepCredentials :: !Word
}
deriving Int -> DRepCredentials -> ShowS
[DRepCredentials] -> ShowS
DRepCredentials -> String
(Int -> DRepCredentials -> ShowS)
-> (DRepCredentials -> String)
-> ([DRepCredentials] -> ShowS)
-> Show DRepCredentials
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DRepCredentials -> ShowS
showsPrec :: Int -> DRepCredentials -> ShowS
$cshow :: DRepCredentials -> String
show :: DRepCredentials -> String
$cshowList :: [DRepCredentials] -> ShowS
showList :: [DRepCredentials] -> ShowS
Show
data CredentialGenerationMode
=
OnDisk
|
Transient
deriving (Int -> CredentialGenerationMode -> ShowS
[CredentialGenerationMode] -> ShowS
CredentialGenerationMode -> String
(Int -> CredentialGenerationMode -> ShowS)
-> (CredentialGenerationMode -> String)
-> ([CredentialGenerationMode] -> ShowS)
-> Show CredentialGenerationMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CredentialGenerationMode -> ShowS
showsPrec :: Int -> CredentialGenerationMode -> ShowS
$cshow :: CredentialGenerationMode -> String
show :: CredentialGenerationMode -> String
$cshowList :: [CredentialGenerationMode] -> ShowS
showList :: [CredentialGenerationMode] -> ShowS
Show, CredentialGenerationMode -> CredentialGenerationMode -> Bool
(CredentialGenerationMode -> CredentialGenerationMode -> Bool)
-> (CredentialGenerationMode -> CredentialGenerationMode -> Bool)
-> Eq CredentialGenerationMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CredentialGenerationMode -> CredentialGenerationMode -> Bool
== :: CredentialGenerationMode -> CredentialGenerationMode -> Bool
$c/= :: CredentialGenerationMode -> CredentialGenerationMode -> Bool
/= :: CredentialGenerationMode -> CredentialGenerationMode -> Bool
Eq)
data TxBuildOutputOptions
= OutputScriptCostOnly (File () Out)
| OutputTxBodyOnly (TxBodyFile Out)
deriving Int -> TxBuildOutputOptions -> ShowS
[TxBuildOutputOptions] -> ShowS
TxBuildOutputOptions -> String
(Int -> TxBuildOutputOptions -> ShowS)
-> (TxBuildOutputOptions -> String)
-> ([TxBuildOutputOptions] -> ShowS)
-> Show TxBuildOutputOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TxBuildOutputOptions -> ShowS
showsPrec :: Int -> TxBuildOutputOptions -> ShowS
$cshow :: TxBuildOutputOptions -> String
show :: TxBuildOutputOptions -> String
$cshowList :: [TxBuildOutputOptions] -> ShowS
showList :: [TxBuildOutputOptions] -> ShowS
Show
data CBORObject
= CBORBlockByron EpochSlots
| CBORDelegationCertificateByron
| CBORTxByron
| CBORUpdateProposalByron
| CBORVoteByron
deriving Int -> CBORObject -> ShowS
[CBORObject] -> ShowS
CBORObject -> String
(Int -> CBORObject -> ShowS)
-> (CBORObject -> String)
-> ([CBORObject] -> ShowS)
-> Show CBORObject
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CBORObject -> ShowS
showsPrec :: Int -> CBORObject -> ShowS
$cshow :: CBORObject -> String
show :: CBORObject -> String
$cshowList :: [CBORObject] -> ShowS
showList :: [CBORObject] -> ShowS
Show
newtype CertificateFile = CertificateFile {CertificateFile -> String
unCertificateFile :: FilePath}
deriving newtype (CertificateFile -> CertificateFile -> Bool
(CertificateFile -> CertificateFile -> Bool)
-> (CertificateFile -> CertificateFile -> Bool)
-> Eq CertificateFile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CertificateFile -> CertificateFile -> Bool
== :: CertificateFile -> CertificateFile -> Bool
$c/= :: CertificateFile -> CertificateFile -> Bool
/= :: CertificateFile -> CertificateFile -> Bool
Eq, Int -> CertificateFile -> ShowS
[CertificateFile] -> ShowS
CertificateFile -> String
(Int -> CertificateFile -> ShowS)
-> (CertificateFile -> String)
-> ([CertificateFile] -> ShowS)
-> Show CertificateFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CertificateFile -> ShowS
showsPrec :: Int -> CertificateFile -> ShowS
$cshow :: CertificateFile -> String
show :: CertificateFile -> String
$cshowList :: [CertificateFile] -> ShowS
showList :: [CertificateFile] -> ShowS
Show)
newtype CurrentKesPeriod = CurrentKesPeriod {CurrentKesPeriod -> Word64
unCurrentKesPeriod :: Word64} deriving (CurrentKesPeriod -> CurrentKesPeriod -> Bool
(CurrentKesPeriod -> CurrentKesPeriod -> Bool)
-> (CurrentKesPeriod -> CurrentKesPeriod -> Bool)
-> Eq CurrentKesPeriod
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CurrentKesPeriod -> CurrentKesPeriod -> Bool
== :: CurrentKesPeriod -> CurrentKesPeriod -> Bool
$c/= :: CurrentKesPeriod -> CurrentKesPeriod -> Bool
/= :: CurrentKesPeriod -> CurrentKesPeriod -> Bool
Eq, Int -> CurrentKesPeriod -> ShowS
[CurrentKesPeriod] -> ShowS
CurrentKesPeriod -> String
(Int -> CurrentKesPeriod -> ShowS)
-> (CurrentKesPeriod -> String)
-> ([CurrentKesPeriod] -> ShowS)
-> Show CurrentKesPeriod
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CurrentKesPeriod -> ShowS
showsPrec :: Int -> CurrentKesPeriod -> ShowS
$cshow :: CurrentKesPeriod -> String
show :: CurrentKesPeriod -> String
$cshowList :: [CurrentKesPeriod] -> ShowS
showList :: [CurrentKesPeriod] -> ShowS
Show)
instance ToJSON CurrentKesPeriod where
toJSON :: CurrentKesPeriod -> Value
toJSON (CurrentKesPeriod Word64
k) = Word64 -> Value
forall a. ToJSON a => a -> Value
toJSON Word64
k
instance FromJSON CurrentKesPeriod where
parseJSON :: Value -> Parser CurrentKesPeriod
parseJSON Value
v = Word64 -> CurrentKesPeriod
CurrentKesPeriod (Word64 -> CurrentKesPeriod)
-> Parser Word64 -> Parser CurrentKesPeriod
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Word64
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
newtype GenesisFile = GenesisFile
{GenesisFile -> String
unGenesisFile :: FilePath}
deriving stock (GenesisFile -> GenesisFile -> Bool
(GenesisFile -> GenesisFile -> Bool)
-> (GenesisFile -> GenesisFile -> Bool) -> Eq GenesisFile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GenesisFile -> GenesisFile -> Bool
== :: GenesisFile -> GenesisFile -> Bool
$c/= :: GenesisFile -> GenesisFile -> Bool
/= :: GenesisFile -> GenesisFile -> Bool
Eq, Eq GenesisFile
Eq GenesisFile =>
(GenesisFile -> GenesisFile -> Ordering)
-> (GenesisFile -> GenesisFile -> Bool)
-> (GenesisFile -> GenesisFile -> Bool)
-> (GenesisFile -> GenesisFile -> Bool)
-> (GenesisFile -> GenesisFile -> Bool)
-> (GenesisFile -> GenesisFile -> GenesisFile)
-> (GenesisFile -> GenesisFile -> GenesisFile)
-> Ord GenesisFile
GenesisFile -> GenesisFile -> Bool
GenesisFile -> GenesisFile -> Ordering
GenesisFile -> GenesisFile -> GenesisFile
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
$ccompare :: GenesisFile -> GenesisFile -> Ordering
compare :: GenesisFile -> GenesisFile -> Ordering
$c< :: GenesisFile -> GenesisFile -> Bool
< :: GenesisFile -> GenesisFile -> Bool
$c<= :: GenesisFile -> GenesisFile -> Bool
<= :: GenesisFile -> GenesisFile -> Bool
$c> :: GenesisFile -> GenesisFile -> Bool
> :: GenesisFile -> GenesisFile -> Bool
$c>= :: GenesisFile -> GenesisFile -> Bool
>= :: GenesisFile -> GenesisFile -> Bool
$cmax :: GenesisFile -> GenesisFile -> GenesisFile
max :: GenesisFile -> GenesisFile -> GenesisFile
$cmin :: GenesisFile -> GenesisFile -> GenesisFile
min :: GenesisFile -> GenesisFile -> GenesisFile
Ord)
deriving newtype (String -> GenesisFile
(String -> GenesisFile) -> IsString GenesisFile
forall a. (String -> a) -> IsString a
$cfromString :: String -> GenesisFile
fromString :: String -> GenesisFile
IsString, Int -> GenesisFile -> ShowS
[GenesisFile] -> ShowS
GenesisFile -> String
(Int -> GenesisFile -> ShowS)
-> (GenesisFile -> String)
-> ([GenesisFile] -> ShowS)
-> Show GenesisFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GenesisFile -> ShowS
showsPrec :: Int -> GenesisFile -> ShowS
$cshow :: GenesisFile -> String
show :: GenesisFile -> String
$cshowList :: [GenesisFile] -> ShowS
showList :: [GenesisFile] -> ShowS
Show)
data OpCertNodeAndOnDiskCounterInformation
=
OpCertOnDiskCounterEqualToNodeState
OpCertOnDiskCounter
OpCertNodeStateCounter
|
OpCertOnDiskCounterAheadOfNodeState
OpCertOnDiskCounter
OpCertNodeStateCounter
|
OpCertOnDiskCounterTooFarAheadOfNodeState
OpCertOnDiskCounter
OpCertNodeStateCounter
|
OpCertOnDiskCounterBehindNodeState
OpCertOnDiskCounter
OpCertNodeStateCounter
|
OpCertNoBlocksMintedYet
OpCertOnDiskCounter
deriving (OpCertNodeAndOnDiskCounterInformation
-> OpCertNodeAndOnDiskCounterInformation -> Bool
(OpCertNodeAndOnDiskCounterInformation
-> OpCertNodeAndOnDiskCounterInformation -> Bool)
-> (OpCertNodeAndOnDiskCounterInformation
-> OpCertNodeAndOnDiskCounterInformation -> Bool)
-> Eq OpCertNodeAndOnDiskCounterInformation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OpCertNodeAndOnDiskCounterInformation
-> OpCertNodeAndOnDiskCounterInformation -> Bool
== :: OpCertNodeAndOnDiskCounterInformation
-> OpCertNodeAndOnDiskCounterInformation -> Bool
$c/= :: OpCertNodeAndOnDiskCounterInformation
-> OpCertNodeAndOnDiskCounterInformation -> Bool
/= :: OpCertNodeAndOnDiskCounterInformation
-> OpCertNodeAndOnDiskCounterInformation -> Bool
Eq, Int -> OpCertNodeAndOnDiskCounterInformation -> ShowS
[OpCertNodeAndOnDiskCounterInformation] -> ShowS
OpCertNodeAndOnDiskCounterInformation -> String
(Int -> OpCertNodeAndOnDiskCounterInformation -> ShowS)
-> (OpCertNodeAndOnDiskCounterInformation -> String)
-> ([OpCertNodeAndOnDiskCounterInformation] -> ShowS)
-> Show OpCertNodeAndOnDiskCounterInformation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OpCertNodeAndOnDiskCounterInformation -> ShowS
showsPrec :: Int -> OpCertNodeAndOnDiskCounterInformation -> ShowS
$cshow :: OpCertNodeAndOnDiskCounterInformation -> String
show :: OpCertNodeAndOnDiskCounterInformation -> String
$cshowList :: [OpCertNodeAndOnDiskCounterInformation] -> ShowS
showList :: [OpCertNodeAndOnDiskCounterInformation] -> ShowS
Show)
newtype OpCertOnDiskCounter = OpCertOnDiskCounter {OpCertOnDiskCounter -> Word64
unOpCertOnDiskCounter :: Word64}
deriving (OpCertOnDiskCounter -> OpCertOnDiskCounter -> Bool
(OpCertOnDiskCounter -> OpCertOnDiskCounter -> Bool)
-> (OpCertOnDiskCounter -> OpCertOnDiskCounter -> Bool)
-> Eq OpCertOnDiskCounter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OpCertOnDiskCounter -> OpCertOnDiskCounter -> Bool
== :: OpCertOnDiskCounter -> OpCertOnDiskCounter -> Bool
$c/= :: OpCertOnDiskCounter -> OpCertOnDiskCounter -> Bool
/= :: OpCertOnDiskCounter -> OpCertOnDiskCounter -> Bool
Eq, Int -> OpCertOnDiskCounter -> ShowS
[OpCertOnDiskCounter] -> ShowS
OpCertOnDiskCounter -> String
(Int -> OpCertOnDiskCounter -> ShowS)
-> (OpCertOnDiskCounter -> String)
-> ([OpCertOnDiskCounter] -> ShowS)
-> Show OpCertOnDiskCounter
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OpCertOnDiskCounter -> ShowS
showsPrec :: Int -> OpCertOnDiskCounter -> ShowS
$cshow :: OpCertOnDiskCounter -> String
show :: OpCertOnDiskCounter -> String
$cshowList :: [OpCertOnDiskCounter] -> ShowS
showList :: [OpCertOnDiskCounter] -> ShowS
Show)
instance ToJSON OpCertOnDiskCounter where
toJSON :: OpCertOnDiskCounter -> Value
toJSON (OpCertOnDiskCounter Word64
k) = Word64 -> Value
forall a. ToJSON a => a -> Value
toJSON Word64
k
instance FromJSON OpCertOnDiskCounter where
parseJSON :: Value -> Parser OpCertOnDiskCounter
parseJSON Value
v = Word64 -> OpCertOnDiskCounter
OpCertOnDiskCounter (Word64 -> OpCertOnDiskCounter)
-> Parser Word64 -> Parser OpCertOnDiskCounter
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Word64
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
newtype OpCertNodeStateCounter = OpCertNodeStateCounter {OpCertNodeStateCounter -> Word64
unOpCertNodeStateCounter :: Word64}
deriving (OpCertNodeStateCounter -> OpCertNodeStateCounter -> Bool
(OpCertNodeStateCounter -> OpCertNodeStateCounter -> Bool)
-> (OpCertNodeStateCounter -> OpCertNodeStateCounter -> Bool)
-> Eq OpCertNodeStateCounter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OpCertNodeStateCounter -> OpCertNodeStateCounter -> Bool
== :: OpCertNodeStateCounter -> OpCertNodeStateCounter -> Bool
$c/= :: OpCertNodeStateCounter -> OpCertNodeStateCounter -> Bool
/= :: OpCertNodeStateCounter -> OpCertNodeStateCounter -> Bool
Eq, Int -> OpCertNodeStateCounter -> ShowS
[OpCertNodeStateCounter] -> ShowS
OpCertNodeStateCounter -> String
(Int -> OpCertNodeStateCounter -> ShowS)
-> (OpCertNodeStateCounter -> String)
-> ([OpCertNodeStateCounter] -> ShowS)
-> Show OpCertNodeStateCounter
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OpCertNodeStateCounter -> ShowS
showsPrec :: Int -> OpCertNodeStateCounter -> ShowS
$cshow :: OpCertNodeStateCounter -> String
show :: OpCertNodeStateCounter -> String
$cshowList :: [OpCertNodeStateCounter] -> ShowS
showList :: [OpCertNodeStateCounter] -> ShowS
Show)
instance ToJSON OpCertNodeStateCounter where
toJSON :: OpCertNodeStateCounter -> Value
toJSON (OpCertNodeStateCounter Word64
k) = Word64 -> Value
forall a. ToJSON a => a -> Value
toJSON Word64
k
instance FromJSON OpCertNodeStateCounter where
parseJSON :: Value -> Parser OpCertNodeStateCounter
parseJSON Value
v = Word64 -> OpCertNodeStateCounter
OpCertNodeStateCounter (Word64 -> OpCertNodeStateCounter)
-> Parser Word64 -> Parser OpCertNodeStateCounter
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Word64
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
newtype OpCertStartingKesPeriod = OpCertStartingKesPeriod {OpCertStartingKesPeriod -> Word64
unOpCertStartingKesPeriod :: Word64}
deriving (OpCertStartingKesPeriod -> OpCertStartingKesPeriod -> Bool
(OpCertStartingKesPeriod -> OpCertStartingKesPeriod -> Bool)
-> (OpCertStartingKesPeriod -> OpCertStartingKesPeriod -> Bool)
-> Eq OpCertStartingKesPeriod
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OpCertStartingKesPeriod -> OpCertStartingKesPeriod -> Bool
== :: OpCertStartingKesPeriod -> OpCertStartingKesPeriod -> Bool
$c/= :: OpCertStartingKesPeriod -> OpCertStartingKesPeriod -> Bool
/= :: OpCertStartingKesPeriod -> OpCertStartingKesPeriod -> Bool
Eq, Int -> OpCertStartingKesPeriod -> ShowS
[OpCertStartingKesPeriod] -> ShowS
OpCertStartingKesPeriod -> String
(Int -> OpCertStartingKesPeriod -> ShowS)
-> (OpCertStartingKesPeriod -> String)
-> ([OpCertStartingKesPeriod] -> ShowS)
-> Show OpCertStartingKesPeriod
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OpCertStartingKesPeriod -> ShowS
showsPrec :: Int -> OpCertStartingKesPeriod -> ShowS
$cshow :: OpCertStartingKesPeriod -> String
show :: OpCertStartingKesPeriod -> String
$cshowList :: [OpCertStartingKesPeriod] -> ShowS
showList :: [OpCertStartingKesPeriod] -> ShowS
Show)
instance ToJSON OpCertStartingKesPeriod where
toJSON :: OpCertStartingKesPeriod -> Value
toJSON (OpCertStartingKesPeriod Word64
k) = Word64 -> Value
forall a. ToJSON a => a -> Value
toJSON Word64
k
instance FromJSON OpCertStartingKesPeriod where
parseJSON :: Value -> Parser OpCertStartingKesPeriod
parseJSON Value
v = Word64 -> OpCertStartingKesPeriod
OpCertStartingKesPeriod (Word64 -> OpCertStartingKesPeriod)
-> Parser Word64 -> Parser OpCertStartingKesPeriod
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Word64
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
newtype OpCertEndingKesPeriod = OpCertEndingKesPeriod {OpCertEndingKesPeriod -> Word64
unOpCertEndingKesPeriod :: Word64}
deriving (OpCertEndingKesPeriod -> OpCertEndingKesPeriod -> Bool
(OpCertEndingKesPeriod -> OpCertEndingKesPeriod -> Bool)
-> (OpCertEndingKesPeriod -> OpCertEndingKesPeriod -> Bool)
-> Eq OpCertEndingKesPeriod
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OpCertEndingKesPeriod -> OpCertEndingKesPeriod -> Bool
== :: OpCertEndingKesPeriod -> OpCertEndingKesPeriod -> Bool
$c/= :: OpCertEndingKesPeriod -> OpCertEndingKesPeriod -> Bool
/= :: OpCertEndingKesPeriod -> OpCertEndingKesPeriod -> Bool
Eq, Int -> OpCertEndingKesPeriod -> ShowS
[OpCertEndingKesPeriod] -> ShowS
OpCertEndingKesPeriod -> String
(Int -> OpCertEndingKesPeriod -> ShowS)
-> (OpCertEndingKesPeriod -> String)
-> ([OpCertEndingKesPeriod] -> ShowS)
-> Show OpCertEndingKesPeriod
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OpCertEndingKesPeriod -> ShowS
showsPrec :: Int -> OpCertEndingKesPeriod -> ShowS
$cshow :: OpCertEndingKesPeriod -> String
show :: OpCertEndingKesPeriod -> String
$cshowList :: [OpCertEndingKesPeriod] -> ShowS
showList :: [OpCertEndingKesPeriod] -> ShowS
Show)
instance ToJSON OpCertEndingKesPeriod where
toJSON :: OpCertEndingKesPeriod -> Value
toJSON (OpCertEndingKesPeriod Word64
k) = Word64 -> Value
forall a. ToJSON a => a -> Value
toJSON Word64
k
instance FromJSON OpCertEndingKesPeriod where
parseJSON :: Value -> Parser OpCertEndingKesPeriod
parseJSON Value
v = Word64 -> OpCertEndingKesPeriod
OpCertEndingKesPeriod (Word64 -> OpCertEndingKesPeriod)
-> Parser Word64 -> Parser OpCertEndingKesPeriod
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Word64
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
data OpCertIntervalInformation
= OpCertWithinInterval
OpCertStartingKesPeriod
OpCertEndingKesPeriod
CurrentKesPeriod
SlotsTillKesKeyExpiry
| OpCertStartingKesPeriodIsInTheFuture
OpCertStartingKesPeriod
OpCertEndingKesPeriod
CurrentKesPeriod
| OpCertExpired
OpCertStartingKesPeriod
OpCertEndingKesPeriod
CurrentKesPeriod
|
OpCertSomeOtherError
OpCertStartingKesPeriod
OpCertEndingKesPeriod
CurrentKesPeriod
deriving (OpCertIntervalInformation -> OpCertIntervalInformation -> Bool
(OpCertIntervalInformation -> OpCertIntervalInformation -> Bool)
-> (OpCertIntervalInformation -> OpCertIntervalInformation -> Bool)
-> Eq OpCertIntervalInformation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OpCertIntervalInformation -> OpCertIntervalInformation -> Bool
== :: OpCertIntervalInformation -> OpCertIntervalInformation -> Bool
$c/= :: OpCertIntervalInformation -> OpCertIntervalInformation -> Bool
/= :: OpCertIntervalInformation -> OpCertIntervalInformation -> Bool
Eq, Int -> OpCertIntervalInformation -> ShowS
[OpCertIntervalInformation] -> ShowS
OpCertIntervalInformation -> String
(Int -> OpCertIntervalInformation -> ShowS)
-> (OpCertIntervalInformation -> String)
-> ([OpCertIntervalInformation] -> ShowS)
-> Show OpCertIntervalInformation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OpCertIntervalInformation -> ShowS
showsPrec :: Int -> OpCertIntervalInformation -> ShowS
$cshow :: OpCertIntervalInformation -> String
show :: OpCertIntervalInformation -> String
$cshowList :: [OpCertIntervalInformation] -> ShowS
showList :: [OpCertIntervalInformation] -> ShowS
Show)
instance FromJSON GenesisFile where
parseJSON :: Value -> Parser GenesisFile
parseJSON (Aeson.String Text
genFp) = GenesisFile -> Parser GenesisFile
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (GenesisFile -> Parser GenesisFile)
-> (String -> GenesisFile) -> String -> Parser GenesisFile
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> GenesisFile
GenesisFile (String -> Parser GenesisFile) -> String -> Parser GenesisFile
forall a b. (a -> b) -> a -> b
$ Text -> String
Text.unpack Text
genFp
parseJSON Value
invalid =
String -> Parser GenesisFile
forall a. HasCallStack => String -> a
error (String -> Parser GenesisFile) -> String -> Parser GenesisFile
forall a b. (a -> b) -> a -> b
$
String
"Parsing of GenesisFile failed due to type mismatch. "
String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"Encountered: "
String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Value -> String
forall a. Show a => a -> String
show Value
invalid
data AllOrOnly a = All | Only [a] deriving (AllOrOnly a -> AllOrOnly a -> Bool
(AllOrOnly a -> AllOrOnly a -> Bool)
-> (AllOrOnly a -> AllOrOnly a -> Bool) -> Eq (AllOrOnly a)
forall a. Eq a => AllOrOnly a -> AllOrOnly a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => AllOrOnly a -> AllOrOnly a -> Bool
== :: AllOrOnly a -> AllOrOnly a -> Bool
$c/= :: forall a. Eq a => AllOrOnly a -> AllOrOnly a -> Bool
/= :: AllOrOnly a -> AllOrOnly a -> Bool
Eq, Int -> AllOrOnly a -> ShowS
[AllOrOnly a] -> ShowS
AllOrOnly a -> String
(Int -> AllOrOnly a -> ShowS)
-> (AllOrOnly a -> String)
-> ([AllOrOnly a] -> ShowS)
-> Show (AllOrOnly a)
forall a. Show a => Int -> AllOrOnly a -> ShowS
forall a. Show a => [AllOrOnly a] -> ShowS
forall a. Show a => AllOrOnly a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> AllOrOnly a -> ShowS
showsPrec :: Int -> AllOrOnly a -> ShowS
$cshow :: forall a. Show a => AllOrOnly a -> String
show :: AllOrOnly a -> String
$cshowList :: forall a. Show a => [AllOrOnly a] -> ShowS
showList :: [AllOrOnly a] -> ShowS
Show)
data PoolParams = PoolParams
{ PoolParams -> Maybe StakePoolState
poolParameters :: Maybe L.StakePoolState
, PoolParams -> Maybe StakePoolState
futurePoolParameters :: Maybe L.StakePoolState
, PoolParams -> Maybe EpochNo
retiringEpoch :: Maybe EpochNo
}
deriving Int -> PoolParams -> ShowS
[PoolParams] -> ShowS
PoolParams -> String
(Int -> PoolParams -> ShowS)
-> (PoolParams -> String)
-> ([PoolParams] -> ShowS)
-> Show PoolParams
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PoolParams -> ShowS
showsPrec :: Int -> PoolParams -> ShowS
$cshow :: PoolParams -> String
show :: PoolParams -> String
$cshowList :: [PoolParams] -> ShowS
showList :: [PoolParams] -> ShowS
Show
mkPoolStates :: PoolState era -> Map (L.KeyHash L.StakePool) PoolParams
mkPoolStates :: forall era. PoolState era -> Map (KeyHash 'StakePool) PoolParams
mkPoolStates
( PoolState
( L.QueryPoolStateResult
{ Map (KeyHash 'StakePool) PoolParams
qpsrStakePoolParams :: Map (KeyHash 'StakePool) PoolParams
qpsrStakePoolParams :: QueryPoolStateResult -> Map (KeyHash 'StakePool) PoolParams
L.qpsrStakePoolParams
, Map (KeyHash 'StakePool) PoolParams
qpsrFutureStakePoolParams :: Map (KeyHash 'StakePool) PoolParams
qpsrFutureStakePoolParams :: QueryPoolStateResult -> Map (KeyHash 'StakePool) PoolParams
L.qpsrFutureStakePoolParams
, Map (KeyHash 'StakePool) EpochNo
qpsrRetiring :: Map (KeyHash 'StakePool) EpochNo
qpsrRetiring :: QueryPoolStateResult -> Map (KeyHash 'StakePool) EpochNo
L.qpsrRetiring
, Map (KeyHash 'StakePool) Coin
qpsrDeposits :: Map (KeyHash 'StakePool) Coin
qpsrDeposits :: QueryPoolStateResult -> Map (KeyHash 'StakePool) Coin
L.qpsrDeposits
}
)
) = ((KeyHash 'StakePool -> PoolParams -> PoolParams)
-> Map (KeyHash 'StakePool) PoolParams
-> Map (KeyHash 'StakePool) PoolParams
forall k a b. (k -> a -> b) -> Map k a -> Map k b
`Map.mapWithKey` Map (KeyHash 'StakePool) PoolParams
qpsrStakePoolParams) ((KeyHash 'StakePool -> PoolParams -> PoolParams)
-> Map (KeyHash 'StakePool) PoolParams)
-> (KeyHash 'StakePool -> PoolParams -> PoolParams)
-> Map (KeyHash 'StakePool) PoolParams
forall a b. (a -> b) -> a -> b
$ \KeyHash 'StakePool
kh PoolParams
pp -> do
let mDeposit :: Maybe (CompactForm Coin)
mDeposit = Coin -> Maybe (CompactForm Coin)
forall a. Compactible a => a -> Maybe (CompactForm a)
L.toCompact (Coin -> Maybe (CompactForm Coin))
-> Maybe Coin -> Maybe (CompactForm Coin)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< KeyHash 'StakePool -> Map (KeyHash 'StakePool) Coin -> Maybe Coin
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup KeyHash 'StakePool
kh Map (KeyHash 'StakePool) Coin
qpsrDeposits
PoolParams
{ poolParameters :: Maybe StakePoolState
poolParameters = (CompactForm Coin -> PoolParams -> StakePoolState
`L.mkStakePoolState` PoolParams
pp) (CompactForm Coin -> StakePoolState)
-> Maybe (CompactForm Coin) -> Maybe StakePoolState
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (CompactForm Coin)
mDeposit
, futurePoolParameters :: Maybe StakePoolState
futurePoolParameters = do
PoolParams
futurePp <- KeyHash 'StakePool
-> Map (KeyHash 'StakePool) PoolParams -> Maybe PoolParams
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup KeyHash 'StakePool
kh Map (KeyHash 'StakePool) PoolParams
qpsrFutureStakePoolParams
(CompactForm Coin -> PoolParams -> StakePoolState
`L.mkStakePoolState` PoolParams
futurePp) (CompactForm Coin -> StakePoolState)
-> Maybe (CompactForm Coin) -> Maybe StakePoolState
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (CompactForm Coin)
mDeposit
, retiringEpoch :: Maybe EpochNo
retiringEpoch = KeyHash 'StakePool
-> Map (KeyHash 'StakePool) EpochNo -> Maybe EpochNo
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup KeyHash 'StakePool
kh Map (KeyHash 'StakePool) EpochNo
qpsrRetiring
}
instance ToJSON PoolParams where
toJSON :: PoolParams -> Value
toJSON (PoolParams Maybe StakePoolState
p Maybe StakePoolState
fp Maybe EpochNo
r) =
[Pair] -> Value
object
[ Key
"poolParams" Key -> Maybe StakePoolState -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe StakePoolState
p
, Key
"futurePoolParams" Key -> Maybe StakePoolState -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe StakePoolState
fp
, Key
"retiring" Key -> Maybe EpochNo -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe EpochNo
r
]
toEncoding :: PoolParams -> Encoding
toEncoding (PoolParams Maybe StakePoolState
p Maybe StakePoolState
fp Maybe EpochNo
r) =
Series -> Encoding
pairs (Series -> Encoding) -> Series -> Encoding
forall a b. (a -> b) -> a -> b
$
[Series] -> Series
forall a. Monoid a => [a] -> a
mconcat
[ Key
"poolParams" Key -> Maybe StakePoolState -> Series
forall v. ToJSON v => Key -> v -> Series
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe StakePoolState
p
, Key
"futurePoolParams" Key -> Maybe StakePoolState -> Series
forall v. ToJSON v => Key -> v -> Series
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe StakePoolState
fp
, Key
"retiring" Key -> Maybe EpochNo -> Series
forall v. ToJSON v => Key -> v -> Series
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Maybe EpochNo
r
]
type SigningKeyFile = File (SigningKey ())
type ProposalFile = File ()
newtype UpdateProposalFile = UpdateProposalFile {UpdateProposalFile -> String
unUpdateProposalFile :: FilePath}
deriving newtype (UpdateProposalFile -> UpdateProposalFile -> Bool
(UpdateProposalFile -> UpdateProposalFile -> Bool)
-> (UpdateProposalFile -> UpdateProposalFile -> Bool)
-> Eq UpdateProposalFile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UpdateProposalFile -> UpdateProposalFile -> Bool
== :: UpdateProposalFile -> UpdateProposalFile -> Bool
$c/= :: UpdateProposalFile -> UpdateProposalFile -> Bool
/= :: UpdateProposalFile -> UpdateProposalFile -> Bool
Eq, Int -> UpdateProposalFile -> ShowS
[UpdateProposalFile] -> ShowS
UpdateProposalFile -> String
(Int -> UpdateProposalFile -> ShowS)
-> (UpdateProposalFile -> String)
-> ([UpdateProposalFile] -> ShowS)
-> Show UpdateProposalFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UpdateProposalFile -> ShowS
showsPrec :: Int -> UpdateProposalFile -> ShowS
$cshow :: UpdateProposalFile -> String
show :: UpdateProposalFile -> String
$cshowList :: [UpdateProposalFile] -> ShowS
showList :: [UpdateProposalFile] -> ShowS
Show)
type VerificationKeyFile = File (VerificationKey ())
type ScriptFile = File ScriptInAnyLang In
data ScriptDataOrFile
=
ScriptDataCborFile FilePath
|
ScriptDataJsonFile FilePath
|
ScriptDataValue HashableScriptData
deriving (ScriptDataOrFile -> ScriptDataOrFile -> Bool
(ScriptDataOrFile -> ScriptDataOrFile -> Bool)
-> (ScriptDataOrFile -> ScriptDataOrFile -> Bool)
-> Eq ScriptDataOrFile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ScriptDataOrFile -> ScriptDataOrFile -> Bool
== :: ScriptDataOrFile -> ScriptDataOrFile -> Bool
$c/= :: ScriptDataOrFile -> ScriptDataOrFile -> Bool
/= :: ScriptDataOrFile -> ScriptDataOrFile -> Bool
Eq, Int -> ScriptDataOrFile -> ShowS
[ScriptDataOrFile] -> ShowS
ScriptDataOrFile -> String
(Int -> ScriptDataOrFile -> ShowS)
-> (ScriptDataOrFile -> String)
-> ([ScriptDataOrFile] -> ShowS)
-> Show ScriptDataOrFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ScriptDataOrFile -> ShowS
showsPrec :: Int -> ScriptDataOrFile -> ShowS
$cshow :: ScriptDataOrFile -> String
show :: ScriptDataOrFile -> String
$cshowList :: [ScriptDataOrFile] -> ShowS
showList :: [ScriptDataOrFile] -> ShowS
Show)
type ScriptRedeemerOrFile = ScriptDataOrFile
newtype SlotsTillKesKeyExpiry = SlotsTillKesKeyExpiry {SlotsTillKesKeyExpiry -> SlotNo
unSlotsTillKesKeyExpiry :: SlotNo}
deriving (SlotsTillKesKeyExpiry -> SlotsTillKesKeyExpiry -> Bool
(SlotsTillKesKeyExpiry -> SlotsTillKesKeyExpiry -> Bool)
-> (SlotsTillKesKeyExpiry -> SlotsTillKesKeyExpiry -> Bool)
-> Eq SlotsTillKesKeyExpiry
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SlotsTillKesKeyExpiry -> SlotsTillKesKeyExpiry -> Bool
== :: SlotsTillKesKeyExpiry -> SlotsTillKesKeyExpiry -> Bool
$c/= :: SlotsTillKesKeyExpiry -> SlotsTillKesKeyExpiry -> Bool
/= :: SlotsTillKesKeyExpiry -> SlotsTillKesKeyExpiry -> Bool
Eq, Int -> SlotsTillKesKeyExpiry -> ShowS
[SlotsTillKesKeyExpiry] -> ShowS
SlotsTillKesKeyExpiry -> String
(Int -> SlotsTillKesKeyExpiry -> ShowS)
-> (SlotsTillKesKeyExpiry -> String)
-> ([SlotsTillKesKeyExpiry] -> ShowS)
-> Show SlotsTillKesKeyExpiry
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SlotsTillKesKeyExpiry -> ShowS
showsPrec :: Int -> SlotsTillKesKeyExpiry -> ShowS
$cshow :: SlotsTillKesKeyExpiry -> String
show :: SlotsTillKesKeyExpiry -> String
$cshowList :: [SlotsTillKesKeyExpiry] -> ShowS
showList :: [SlotsTillKesKeyExpiry] -> ShowS
Show)
instance ToJSON SlotsTillKesKeyExpiry where
toJSON :: SlotsTillKesKeyExpiry -> Value
toJSON (SlotsTillKesKeyExpiry SlotNo
k) = SlotNo -> Value
forall a. ToJSON a => a -> Value
toJSON SlotNo
k
instance FromJSON SlotsTillKesKeyExpiry where
parseJSON :: Value -> Parser SlotsTillKesKeyExpiry
parseJSON Value
v = SlotNo -> SlotsTillKesKeyExpiry
SlotsTillKesKeyExpiry (SlotNo -> SlotsTillKesKeyExpiry)
-> Parser SlotNo -> Parser SlotsTillKesKeyExpiry
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser SlotNo
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
data TxOutShelleyBasedEra
= TxOutShelleyBasedEra
!(Address ShelleyAddr)
Value
TxOutDatumAnyEra
ReferenceScriptAnyEra
deriving Int -> TxOutShelleyBasedEra -> ShowS
[TxOutShelleyBasedEra] -> ShowS
TxOutShelleyBasedEra -> String
(Int -> TxOutShelleyBasedEra -> ShowS)
-> (TxOutShelleyBasedEra -> String)
-> ([TxOutShelleyBasedEra] -> ShowS)
-> Show TxOutShelleyBasedEra
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TxOutShelleyBasedEra -> ShowS
showsPrec :: Int -> TxOutShelleyBasedEra -> ShowS
$cshow :: TxOutShelleyBasedEra -> String
show :: TxOutShelleyBasedEra -> String
$cshowList :: [TxOutShelleyBasedEra] -> ShowS
showList :: [TxOutShelleyBasedEra] -> ShowS
Show
data TxOutAnyEra
= TxOutAnyEra
AddressAny
Value
TxOutDatumAnyEra
ReferenceScriptAnyEra
deriving (TxOutAnyEra -> TxOutAnyEra -> Bool
(TxOutAnyEra -> TxOutAnyEra -> Bool)
-> (TxOutAnyEra -> TxOutAnyEra -> Bool) -> Eq TxOutAnyEra
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TxOutAnyEra -> TxOutAnyEra -> Bool
== :: TxOutAnyEra -> TxOutAnyEra -> Bool
$c/= :: TxOutAnyEra -> TxOutAnyEra -> Bool
/= :: TxOutAnyEra -> TxOutAnyEra -> Bool
Eq, Int -> TxOutAnyEra -> ShowS
[TxOutAnyEra] -> ShowS
TxOutAnyEra -> String
(Int -> TxOutAnyEra -> ShowS)
-> (TxOutAnyEra -> String)
-> ([TxOutAnyEra] -> ShowS)
-> Show TxOutAnyEra
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TxOutAnyEra -> ShowS
showsPrec :: Int -> TxOutAnyEra -> ShowS
$cshow :: TxOutAnyEra -> String
show :: TxOutAnyEra -> String
$cshowList :: [TxOutAnyEra] -> ShowS
showList :: [TxOutAnyEra] -> ShowS
Show)
data TxOutDatumAnyEra
= TxOutDatumByHashOnly (Hash ScriptData)
| TxOutDatumByHashOf ScriptDataOrFile
| TxOutDatumByValue ScriptDataOrFile
| TxOutInlineDatumByValue ScriptDataOrFile
| TxOutDatumByNone
deriving (TxOutDatumAnyEra -> TxOutDatumAnyEra -> Bool
(TxOutDatumAnyEra -> TxOutDatumAnyEra -> Bool)
-> (TxOutDatumAnyEra -> TxOutDatumAnyEra -> Bool)
-> Eq TxOutDatumAnyEra
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TxOutDatumAnyEra -> TxOutDatumAnyEra -> Bool
== :: TxOutDatumAnyEra -> TxOutDatumAnyEra -> Bool
$c/= :: TxOutDatumAnyEra -> TxOutDatumAnyEra -> Bool
/= :: TxOutDatumAnyEra -> TxOutDatumAnyEra -> Bool
Eq, Int -> TxOutDatumAnyEra -> ShowS
[TxOutDatumAnyEra] -> ShowS
TxOutDatumAnyEra -> String
(Int -> TxOutDatumAnyEra -> ShowS)
-> (TxOutDatumAnyEra -> String)
-> ([TxOutDatumAnyEra] -> ShowS)
-> Show TxOutDatumAnyEra
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TxOutDatumAnyEra -> ShowS
showsPrec :: Int -> TxOutDatumAnyEra -> ShowS
$cshow :: TxOutDatumAnyEra -> String
show :: TxOutDatumAnyEra -> String
$cshowList :: [TxOutDatumAnyEra] -> ShowS
showList :: [TxOutDatumAnyEra] -> ShowS
Show)
data ReferenceScriptAnyEra
= ReferenceScriptAnyEraNone
| ReferenceScriptAnyEra FilePath
deriving (ReferenceScriptAnyEra -> ReferenceScriptAnyEra -> Bool
(ReferenceScriptAnyEra -> ReferenceScriptAnyEra -> Bool)
-> (ReferenceScriptAnyEra -> ReferenceScriptAnyEra -> Bool)
-> Eq ReferenceScriptAnyEra
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ReferenceScriptAnyEra -> ReferenceScriptAnyEra -> Bool
== :: ReferenceScriptAnyEra -> ReferenceScriptAnyEra -> Bool
$c/= :: ReferenceScriptAnyEra -> ReferenceScriptAnyEra -> Bool
/= :: ReferenceScriptAnyEra -> ReferenceScriptAnyEra -> Bool
Eq, Int -> ReferenceScriptAnyEra -> ShowS
[ReferenceScriptAnyEra] -> ShowS
ReferenceScriptAnyEra -> String
(Int -> ReferenceScriptAnyEra -> ShowS)
-> (ReferenceScriptAnyEra -> String)
-> ([ReferenceScriptAnyEra] -> ShowS)
-> Show ReferenceScriptAnyEra
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ReferenceScriptAnyEra -> ShowS
showsPrec :: Int -> ReferenceScriptAnyEra -> ShowS
$cshow :: ReferenceScriptAnyEra -> String
show :: ReferenceScriptAnyEra -> String
$cshowList :: [ReferenceScriptAnyEra] -> ShowS
showList :: [ReferenceScriptAnyEra] -> ShowS
Show)
newtype TxOutChangeAddress = TxOutChangeAddress AddressAny
deriving (TxOutChangeAddress -> TxOutChangeAddress -> Bool
(TxOutChangeAddress -> TxOutChangeAddress -> Bool)
-> (TxOutChangeAddress -> TxOutChangeAddress -> Bool)
-> Eq TxOutChangeAddress
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TxOutChangeAddress -> TxOutChangeAddress -> Bool
== :: TxOutChangeAddress -> TxOutChangeAddress -> Bool
$c/= :: TxOutChangeAddress -> TxOutChangeAddress -> Bool
/= :: TxOutChangeAddress -> TxOutChangeAddress -> Bool
Eq, Int -> TxOutChangeAddress -> ShowS
[TxOutChangeAddress] -> ShowS
TxOutChangeAddress -> String
(Int -> TxOutChangeAddress -> ShowS)
-> (TxOutChangeAddress -> String)
-> ([TxOutChangeAddress] -> ShowS)
-> Show TxOutChangeAddress
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TxOutChangeAddress -> ShowS
showsPrec :: Int -> TxOutChangeAddress -> ShowS
$cshow :: TxOutChangeAddress -> String
show :: TxOutChangeAddress -> String
$cshowList :: [TxOutChangeAddress] -> ShowS
showList :: [TxOutChangeAddress] -> ShowS
Show)
data BalanceTxExecUnits = AutoBalance | ManualBalance
data RequiredSigner
= RequiredSignerSkeyFile (SigningKeyFile In)
| RequiredSignerHash (Hash PaymentKey)
deriving Int -> RequiredSigner -> ShowS
[RequiredSigner] -> ShowS
RequiredSigner -> String
(Int -> RequiredSigner -> ShowS)
-> (RequiredSigner -> String)
-> ([RequiredSigner] -> ShowS)
-> Show RequiredSigner
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RequiredSigner -> ShowS
showsPrec :: Int -> RequiredSigner -> ShowS
$cshow :: RequiredSigner -> String
show :: RequiredSigner -> String
$cshowList :: [RequiredSigner] -> ShowS
showList :: [RequiredSigner] -> ShowS
Show
data EpochLeadershipSchedule
= CurrentEpoch
| NextEpoch
deriving Int -> EpochLeadershipSchedule -> ShowS
[EpochLeadershipSchedule] -> ShowS
EpochLeadershipSchedule -> String
(Int -> EpochLeadershipSchedule -> ShowS)
-> (EpochLeadershipSchedule -> String)
-> ([EpochLeadershipSchedule] -> ShowS)
-> Show EpochLeadershipSchedule
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EpochLeadershipSchedule -> ShowS
showsPrec :: Int -> EpochLeadershipSchedule -> ShowS
$cshow :: EpochLeadershipSchedule -> String
show :: EpochLeadershipSchedule -> String
$cshowList :: [EpochLeadershipSchedule] -> ShowS
showList :: [EpochLeadershipSchedule] -> ShowS
Show
type TxBodyFile = File (TxBody ())
type TxFile = File (Tx ())
newtype TxTreasuryDonation = TxTreasuryDonation {TxTreasuryDonation -> Coin
unTxTreasuryDonation :: Lovelace}
deriving Int -> TxTreasuryDonation -> ShowS
[TxTreasuryDonation] -> ShowS
TxTreasuryDonation -> String
(Int -> TxTreasuryDonation -> ShowS)
-> (TxTreasuryDonation -> String)
-> ([TxTreasuryDonation] -> ShowS)
-> Show TxTreasuryDonation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TxTreasuryDonation -> ShowS
showsPrec :: Int -> TxTreasuryDonation -> ShowS
$cshow :: TxTreasuryDonation -> String
show :: TxTreasuryDonation -> String
$cshowList :: [TxTreasuryDonation] -> ShowS
showList :: [TxTreasuryDonation] -> ShowS
Show
data TxMempoolQuery
= TxMempoolQueryTxExists TxId
| TxMempoolQueryNextTx
| TxMempoolQueryInfo
deriving Int -> TxMempoolQuery -> ShowS
[TxMempoolQuery] -> ShowS
TxMempoolQuery -> String
(Int -> TxMempoolQuery -> ShowS)
-> (TxMempoolQuery -> String)
-> ([TxMempoolQuery] -> ShowS)
-> Show TxMempoolQuery
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TxMempoolQuery -> ShowS
showsPrec :: Int -> TxMempoolQuery -> ShowS
$cshow :: TxMempoolQuery -> String
show :: TxMempoolQuery -> String
$cshowList :: [TxMempoolQuery] -> ShowS
showList :: [TxMempoolQuery] -> ShowS
Show
data FormatBech32 = FormatBech32
deriving (Int -> FormatBech32
FormatBech32 -> Int
FormatBech32 -> [FormatBech32]
FormatBech32 -> FormatBech32
FormatBech32 -> FormatBech32 -> [FormatBech32]
FormatBech32 -> FormatBech32 -> FormatBech32 -> [FormatBech32]
(FormatBech32 -> FormatBech32)
-> (FormatBech32 -> FormatBech32)
-> (Int -> FormatBech32)
-> (FormatBech32 -> Int)
-> (FormatBech32 -> [FormatBech32])
-> (FormatBech32 -> FormatBech32 -> [FormatBech32])
-> (FormatBech32 -> FormatBech32 -> [FormatBech32])
-> (FormatBech32 -> FormatBech32 -> FormatBech32 -> [FormatBech32])
-> Enum FormatBech32
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: FormatBech32 -> FormatBech32
succ :: FormatBech32 -> FormatBech32
$cpred :: FormatBech32 -> FormatBech32
pred :: FormatBech32 -> FormatBech32
$ctoEnum :: Int -> FormatBech32
toEnum :: Int -> FormatBech32
$cfromEnum :: FormatBech32 -> Int
fromEnum :: FormatBech32 -> Int
$cenumFrom :: FormatBech32 -> [FormatBech32]
enumFrom :: FormatBech32 -> [FormatBech32]
$cenumFromThen :: FormatBech32 -> FormatBech32 -> [FormatBech32]
enumFromThen :: FormatBech32 -> FormatBech32 -> [FormatBech32]
$cenumFromTo :: FormatBech32 -> FormatBech32 -> [FormatBech32]
enumFromTo :: FormatBech32 -> FormatBech32 -> [FormatBech32]
$cenumFromThenTo :: FormatBech32 -> FormatBech32 -> FormatBech32 -> [FormatBech32]
enumFromThenTo :: FormatBech32 -> FormatBech32 -> FormatBech32 -> [FormatBech32]
Enum, FormatBech32 -> FormatBech32 -> Bool
(FormatBech32 -> FormatBech32 -> Bool)
-> (FormatBech32 -> FormatBech32 -> Bool) -> Eq FormatBech32
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FormatBech32 -> FormatBech32 -> Bool
== :: FormatBech32 -> FormatBech32 -> Bool
$c/= :: FormatBech32 -> FormatBech32 -> Bool
/= :: FormatBech32 -> FormatBech32 -> Bool
Eq, Eq FormatBech32
Eq FormatBech32 =>
(FormatBech32 -> FormatBech32 -> Ordering)
-> (FormatBech32 -> FormatBech32 -> Bool)
-> (FormatBech32 -> FormatBech32 -> Bool)
-> (FormatBech32 -> FormatBech32 -> Bool)
-> (FormatBech32 -> FormatBech32 -> Bool)
-> (FormatBech32 -> FormatBech32 -> FormatBech32)
-> (FormatBech32 -> FormatBech32 -> FormatBech32)
-> Ord FormatBech32
FormatBech32 -> FormatBech32 -> Bool
FormatBech32 -> FormatBech32 -> Ordering
FormatBech32 -> FormatBech32 -> FormatBech32
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
$ccompare :: FormatBech32 -> FormatBech32 -> Ordering
compare :: FormatBech32 -> FormatBech32 -> Ordering
$c< :: FormatBech32 -> FormatBech32 -> Bool
< :: FormatBech32 -> FormatBech32 -> Bool
$c<= :: FormatBech32 -> FormatBech32 -> Bool
<= :: FormatBech32 -> FormatBech32 -> Bool
$c> :: FormatBech32 -> FormatBech32 -> Bool
> :: FormatBech32 -> FormatBech32 -> Bool
$c>= :: FormatBech32 -> FormatBech32 -> Bool
>= :: FormatBech32 -> FormatBech32 -> Bool
$cmax :: FormatBech32 -> FormatBech32 -> FormatBech32
max :: FormatBech32 -> FormatBech32 -> FormatBech32
$cmin :: FormatBech32 -> FormatBech32 -> FormatBech32
min :: FormatBech32 -> FormatBech32 -> FormatBech32
Ord, Int -> FormatBech32 -> ShowS
[FormatBech32] -> ShowS
FormatBech32 -> String
(Int -> FormatBech32 -> ShowS)
-> (FormatBech32 -> String)
-> ([FormatBech32] -> ShowS)
-> Show FormatBech32
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FormatBech32 -> ShowS
showsPrec :: Int -> FormatBech32 -> ShowS
$cshow :: FormatBech32 -> String
show :: FormatBech32 -> String
$cshowList :: [FormatBech32] -> ShowS
showList :: [FormatBech32] -> ShowS
Show)
data FormatHex = FormatHex
deriving (Int -> FormatHex
FormatHex -> Int
FormatHex -> [FormatHex]
FormatHex -> FormatHex
FormatHex -> FormatHex -> [FormatHex]
FormatHex -> FormatHex -> FormatHex -> [FormatHex]
(FormatHex -> FormatHex)
-> (FormatHex -> FormatHex)
-> (Int -> FormatHex)
-> (FormatHex -> Int)
-> (FormatHex -> [FormatHex])
-> (FormatHex -> FormatHex -> [FormatHex])
-> (FormatHex -> FormatHex -> [FormatHex])
-> (FormatHex -> FormatHex -> FormatHex -> [FormatHex])
-> Enum FormatHex
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: FormatHex -> FormatHex
succ :: FormatHex -> FormatHex
$cpred :: FormatHex -> FormatHex
pred :: FormatHex -> FormatHex
$ctoEnum :: Int -> FormatHex
toEnum :: Int -> FormatHex
$cfromEnum :: FormatHex -> Int
fromEnum :: FormatHex -> Int
$cenumFrom :: FormatHex -> [FormatHex]
enumFrom :: FormatHex -> [FormatHex]
$cenumFromThen :: FormatHex -> FormatHex -> [FormatHex]
enumFromThen :: FormatHex -> FormatHex -> [FormatHex]
$cenumFromTo :: FormatHex -> FormatHex -> [FormatHex]
enumFromTo :: FormatHex -> FormatHex -> [FormatHex]
$cenumFromThenTo :: FormatHex -> FormatHex -> FormatHex -> [FormatHex]
enumFromThenTo :: FormatHex -> FormatHex -> FormatHex -> [FormatHex]
Enum, FormatHex -> FormatHex -> Bool
(FormatHex -> FormatHex -> Bool)
-> (FormatHex -> FormatHex -> Bool) -> Eq FormatHex
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FormatHex -> FormatHex -> Bool
== :: FormatHex -> FormatHex -> Bool
$c/= :: FormatHex -> FormatHex -> Bool
/= :: FormatHex -> FormatHex -> Bool
Eq, Eq FormatHex
Eq FormatHex =>
(FormatHex -> FormatHex -> Ordering)
-> (FormatHex -> FormatHex -> Bool)
-> (FormatHex -> FormatHex -> Bool)
-> (FormatHex -> FormatHex -> Bool)
-> (FormatHex -> FormatHex -> Bool)
-> (FormatHex -> FormatHex -> FormatHex)
-> (FormatHex -> FormatHex -> FormatHex)
-> Ord FormatHex
FormatHex -> FormatHex -> Bool
FormatHex -> FormatHex -> Ordering
FormatHex -> FormatHex -> FormatHex
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
$ccompare :: FormatHex -> FormatHex -> Ordering
compare :: FormatHex -> FormatHex -> Ordering
$c< :: FormatHex -> FormatHex -> Bool
< :: FormatHex -> FormatHex -> Bool
$c<= :: FormatHex -> FormatHex -> Bool
<= :: FormatHex -> FormatHex -> Bool
$c> :: FormatHex -> FormatHex -> Bool
> :: FormatHex -> FormatHex -> Bool
$c>= :: FormatHex -> FormatHex -> Bool
>= :: FormatHex -> FormatHex -> Bool
$cmax :: FormatHex -> FormatHex -> FormatHex
max :: FormatHex -> FormatHex -> FormatHex
$cmin :: FormatHex -> FormatHex -> FormatHex
min :: FormatHex -> FormatHex -> FormatHex
Ord, Int -> FormatHex -> ShowS
[FormatHex] -> ShowS
FormatHex -> String
(Int -> FormatHex -> ShowS)
-> (FormatHex -> String)
-> ([FormatHex] -> ShowS)
-> Show FormatHex
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FormatHex -> ShowS
showsPrec :: Int -> FormatHex -> ShowS
$cshow :: FormatHex -> String
show :: FormatHex -> String
$cshowList :: [FormatHex] -> ShowS
showList :: [FormatHex] -> ShowS
Show)
data FormatCborBin = FormatCborBin
deriving (Int -> FormatCborBin
FormatCborBin -> Int
FormatCborBin -> [FormatCborBin]
FormatCborBin -> FormatCborBin
FormatCborBin -> FormatCborBin -> [FormatCborBin]
FormatCborBin -> FormatCborBin -> FormatCborBin -> [FormatCborBin]
(FormatCborBin -> FormatCborBin)
-> (FormatCborBin -> FormatCborBin)
-> (Int -> FormatCborBin)
-> (FormatCborBin -> Int)
-> (FormatCborBin -> [FormatCborBin])
-> (FormatCborBin -> FormatCborBin -> [FormatCborBin])
-> (FormatCborBin -> FormatCborBin -> [FormatCborBin])
-> (FormatCborBin
-> FormatCborBin -> FormatCborBin -> [FormatCborBin])
-> Enum FormatCborBin
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: FormatCborBin -> FormatCborBin
succ :: FormatCborBin -> FormatCborBin
$cpred :: FormatCborBin -> FormatCborBin
pred :: FormatCborBin -> FormatCborBin
$ctoEnum :: Int -> FormatCborBin
toEnum :: Int -> FormatCborBin
$cfromEnum :: FormatCborBin -> Int
fromEnum :: FormatCborBin -> Int
$cenumFrom :: FormatCborBin -> [FormatCborBin]
enumFrom :: FormatCborBin -> [FormatCborBin]
$cenumFromThen :: FormatCborBin -> FormatCborBin -> [FormatCborBin]
enumFromThen :: FormatCborBin -> FormatCborBin -> [FormatCborBin]
$cenumFromTo :: FormatCborBin -> FormatCborBin -> [FormatCborBin]
enumFromTo :: FormatCborBin -> FormatCborBin -> [FormatCborBin]
$cenumFromThenTo :: FormatCborBin -> FormatCborBin -> FormatCborBin -> [FormatCborBin]
enumFromThenTo :: FormatCborBin -> FormatCborBin -> FormatCborBin -> [FormatCborBin]
Enum, FormatCborBin -> FormatCborBin -> Bool
(FormatCborBin -> FormatCborBin -> Bool)
-> (FormatCborBin -> FormatCborBin -> Bool) -> Eq FormatCborBin
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FormatCborBin -> FormatCborBin -> Bool
== :: FormatCborBin -> FormatCborBin -> Bool
$c/= :: FormatCborBin -> FormatCborBin -> Bool
/= :: FormatCborBin -> FormatCborBin -> Bool
Eq, Eq FormatCborBin
Eq FormatCborBin =>
(FormatCborBin -> FormatCborBin -> Ordering)
-> (FormatCborBin -> FormatCborBin -> Bool)
-> (FormatCborBin -> FormatCborBin -> Bool)
-> (FormatCborBin -> FormatCborBin -> Bool)
-> (FormatCborBin -> FormatCborBin -> Bool)
-> (FormatCborBin -> FormatCborBin -> FormatCborBin)
-> (FormatCborBin -> FormatCborBin -> FormatCborBin)
-> Ord FormatCborBin
FormatCborBin -> FormatCborBin -> Bool
FormatCborBin -> FormatCborBin -> Ordering
FormatCborBin -> FormatCborBin -> FormatCborBin
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
$ccompare :: FormatCborBin -> FormatCborBin -> Ordering
compare :: FormatCborBin -> FormatCborBin -> Ordering
$c< :: FormatCborBin -> FormatCborBin -> Bool
< :: FormatCborBin -> FormatCborBin -> Bool
$c<= :: FormatCborBin -> FormatCborBin -> Bool
<= :: FormatCborBin -> FormatCborBin -> Bool
$c> :: FormatCborBin -> FormatCborBin -> Bool
> :: FormatCborBin -> FormatCborBin -> Bool
$c>= :: FormatCborBin -> FormatCborBin -> Bool
>= :: FormatCborBin -> FormatCborBin -> Bool
$cmax :: FormatCborBin -> FormatCborBin -> FormatCborBin
max :: FormatCborBin -> FormatCborBin -> FormatCborBin
$cmin :: FormatCborBin -> FormatCborBin -> FormatCborBin
min :: FormatCborBin -> FormatCborBin -> FormatCborBin
Ord, Int -> FormatCborBin -> ShowS
[FormatCborBin] -> ShowS
FormatCborBin -> String
(Int -> FormatCborBin -> ShowS)
-> (FormatCborBin -> String)
-> ([FormatCborBin] -> ShowS)
-> Show FormatCborBin
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FormatCborBin -> ShowS
showsPrec :: Int -> FormatCborBin -> ShowS
$cshow :: FormatCborBin -> String
show :: FormatCborBin -> String
$cshowList :: [FormatCborBin] -> ShowS
showList :: [FormatCborBin] -> ShowS
Show)
data FormatCborHex = FormatCborHex
deriving (Int -> FormatCborHex
FormatCborHex -> Int
FormatCborHex -> [FormatCborHex]
FormatCborHex -> FormatCborHex
FormatCborHex -> FormatCborHex -> [FormatCborHex]
FormatCborHex -> FormatCborHex -> FormatCborHex -> [FormatCborHex]
(FormatCborHex -> FormatCborHex)
-> (FormatCborHex -> FormatCborHex)
-> (Int -> FormatCborHex)
-> (FormatCborHex -> Int)
-> (FormatCborHex -> [FormatCborHex])
-> (FormatCborHex -> FormatCborHex -> [FormatCborHex])
-> (FormatCborHex -> FormatCborHex -> [FormatCborHex])
-> (FormatCborHex
-> FormatCborHex -> FormatCborHex -> [FormatCborHex])
-> Enum FormatCborHex
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: FormatCborHex -> FormatCborHex
succ :: FormatCborHex -> FormatCborHex
$cpred :: FormatCborHex -> FormatCborHex
pred :: FormatCborHex -> FormatCborHex
$ctoEnum :: Int -> FormatCborHex
toEnum :: Int -> FormatCborHex
$cfromEnum :: FormatCborHex -> Int
fromEnum :: FormatCborHex -> Int
$cenumFrom :: FormatCborHex -> [FormatCborHex]
enumFrom :: FormatCborHex -> [FormatCborHex]
$cenumFromThen :: FormatCborHex -> FormatCborHex -> [FormatCborHex]
enumFromThen :: FormatCborHex -> FormatCborHex -> [FormatCborHex]
$cenumFromTo :: FormatCborHex -> FormatCborHex -> [FormatCborHex]
enumFromTo :: FormatCborHex -> FormatCborHex -> [FormatCborHex]
$cenumFromThenTo :: FormatCborHex -> FormatCborHex -> FormatCborHex -> [FormatCborHex]
enumFromThenTo :: FormatCborHex -> FormatCborHex -> FormatCborHex -> [FormatCborHex]
Enum, FormatCborHex -> FormatCborHex -> Bool
(FormatCborHex -> FormatCborHex -> Bool)
-> (FormatCborHex -> FormatCborHex -> Bool) -> Eq FormatCborHex
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FormatCborHex -> FormatCborHex -> Bool
== :: FormatCborHex -> FormatCborHex -> Bool
$c/= :: FormatCborHex -> FormatCborHex -> Bool
/= :: FormatCborHex -> FormatCborHex -> Bool
Eq, Eq FormatCborHex
Eq FormatCborHex =>
(FormatCborHex -> FormatCborHex -> Ordering)
-> (FormatCborHex -> FormatCborHex -> Bool)
-> (FormatCborHex -> FormatCborHex -> Bool)
-> (FormatCborHex -> FormatCborHex -> Bool)
-> (FormatCborHex -> FormatCborHex -> Bool)
-> (FormatCborHex -> FormatCborHex -> FormatCborHex)
-> (FormatCborHex -> FormatCborHex -> FormatCborHex)
-> Ord FormatCborHex
FormatCborHex -> FormatCborHex -> Bool
FormatCborHex -> FormatCborHex -> Ordering
FormatCborHex -> FormatCborHex -> FormatCborHex
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
$ccompare :: FormatCborHex -> FormatCborHex -> Ordering
compare :: FormatCborHex -> FormatCborHex -> Ordering
$c< :: FormatCborHex -> FormatCborHex -> Bool
< :: FormatCborHex -> FormatCborHex -> Bool
$c<= :: FormatCborHex -> FormatCborHex -> Bool
<= :: FormatCborHex -> FormatCborHex -> Bool
$c> :: FormatCborHex -> FormatCborHex -> Bool
> :: FormatCborHex -> FormatCborHex -> Bool
$c>= :: FormatCborHex -> FormatCborHex -> Bool
>= :: FormatCborHex -> FormatCborHex -> Bool
$cmax :: FormatCborHex -> FormatCborHex -> FormatCborHex
max :: FormatCborHex -> FormatCborHex -> FormatCborHex
$cmin :: FormatCborHex -> FormatCborHex -> FormatCborHex
min :: FormatCborHex -> FormatCborHex -> FormatCborHex
Ord, Int -> FormatCborHex -> ShowS
[FormatCborHex] -> ShowS
FormatCborHex -> String
(Int -> FormatCborHex -> ShowS)
-> (FormatCborHex -> String)
-> ([FormatCborHex] -> ShowS)
-> Show FormatCborHex
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FormatCborHex -> ShowS
showsPrec :: Int -> FormatCborHex -> ShowS
$cshow :: FormatCborHex -> String
show :: FormatCborHex -> String
$cshowList :: [FormatCborHex] -> ShowS
showList :: [FormatCborHex] -> ShowS
Show)
data FormatCip129 = FormatCip129
deriving (Int -> FormatCip129
FormatCip129 -> Int
FormatCip129 -> [FormatCip129]
FormatCip129 -> FormatCip129
FormatCip129 -> FormatCip129 -> [FormatCip129]
FormatCip129 -> FormatCip129 -> FormatCip129 -> [FormatCip129]
(FormatCip129 -> FormatCip129)
-> (FormatCip129 -> FormatCip129)
-> (Int -> FormatCip129)
-> (FormatCip129 -> Int)
-> (FormatCip129 -> [FormatCip129])
-> (FormatCip129 -> FormatCip129 -> [FormatCip129])
-> (FormatCip129 -> FormatCip129 -> [FormatCip129])
-> (FormatCip129 -> FormatCip129 -> FormatCip129 -> [FormatCip129])
-> Enum FormatCip129
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: FormatCip129 -> FormatCip129
succ :: FormatCip129 -> FormatCip129
$cpred :: FormatCip129 -> FormatCip129
pred :: FormatCip129 -> FormatCip129
$ctoEnum :: Int -> FormatCip129
toEnum :: Int -> FormatCip129
$cfromEnum :: FormatCip129 -> Int
fromEnum :: FormatCip129 -> Int
$cenumFrom :: FormatCip129 -> [FormatCip129]
enumFrom :: FormatCip129 -> [FormatCip129]
$cenumFromThen :: FormatCip129 -> FormatCip129 -> [FormatCip129]
enumFromThen :: FormatCip129 -> FormatCip129 -> [FormatCip129]
$cenumFromTo :: FormatCip129 -> FormatCip129 -> [FormatCip129]
enumFromTo :: FormatCip129 -> FormatCip129 -> [FormatCip129]
$cenumFromThenTo :: FormatCip129 -> FormatCip129 -> FormatCip129 -> [FormatCip129]
enumFromThenTo :: FormatCip129 -> FormatCip129 -> FormatCip129 -> [FormatCip129]
Enum, FormatCip129 -> FormatCip129 -> Bool
(FormatCip129 -> FormatCip129 -> Bool)
-> (FormatCip129 -> FormatCip129 -> Bool) -> Eq FormatCip129
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FormatCip129 -> FormatCip129 -> Bool
== :: FormatCip129 -> FormatCip129 -> Bool
$c/= :: FormatCip129 -> FormatCip129 -> Bool
/= :: FormatCip129 -> FormatCip129 -> Bool
Eq, Eq FormatCip129
Eq FormatCip129 =>
(FormatCip129 -> FormatCip129 -> Ordering)
-> (FormatCip129 -> FormatCip129 -> Bool)
-> (FormatCip129 -> FormatCip129 -> Bool)
-> (FormatCip129 -> FormatCip129 -> Bool)
-> (FormatCip129 -> FormatCip129 -> Bool)
-> (FormatCip129 -> FormatCip129 -> FormatCip129)
-> (FormatCip129 -> FormatCip129 -> FormatCip129)
-> Ord FormatCip129
FormatCip129 -> FormatCip129 -> Bool
FormatCip129 -> FormatCip129 -> Ordering
FormatCip129 -> FormatCip129 -> FormatCip129
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
$ccompare :: FormatCip129 -> FormatCip129 -> Ordering
compare :: FormatCip129 -> FormatCip129 -> Ordering
$c< :: FormatCip129 -> FormatCip129 -> Bool
< :: FormatCip129 -> FormatCip129 -> Bool
$c<= :: FormatCip129 -> FormatCip129 -> Bool
<= :: FormatCip129 -> FormatCip129 -> Bool
$c> :: FormatCip129 -> FormatCip129 -> Bool
> :: FormatCip129 -> FormatCip129 -> Bool
$c>= :: FormatCip129 -> FormatCip129 -> Bool
>= :: FormatCip129 -> FormatCip129 -> Bool
$cmax :: FormatCip129 -> FormatCip129 -> FormatCip129
max :: FormatCip129 -> FormatCip129 -> FormatCip129
$cmin :: FormatCip129 -> FormatCip129 -> FormatCip129
min :: FormatCip129 -> FormatCip129 -> FormatCip129
Ord, Int -> FormatCip129 -> ShowS
[FormatCip129] -> ShowS
FormatCip129 -> String
(Int -> FormatCip129 -> ShowS)
-> (FormatCip129 -> String)
-> ([FormatCip129] -> ShowS)
-> Show FormatCip129
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FormatCip129 -> ShowS
showsPrec :: Int -> FormatCip129 -> ShowS
$cshow :: FormatCip129 -> String
show :: FormatCip129 -> String
$cshowList :: [FormatCip129] -> ShowS
showList :: [FormatCip129] -> ShowS
Show)
data FormatJson = FormatJson
deriving (Int -> FormatJson
FormatJson -> Int
FormatJson -> [FormatJson]
FormatJson -> FormatJson
FormatJson -> FormatJson -> [FormatJson]
FormatJson -> FormatJson -> FormatJson -> [FormatJson]
(FormatJson -> FormatJson)
-> (FormatJson -> FormatJson)
-> (Int -> FormatJson)
-> (FormatJson -> Int)
-> (FormatJson -> [FormatJson])
-> (FormatJson -> FormatJson -> [FormatJson])
-> (FormatJson -> FormatJson -> [FormatJson])
-> (FormatJson -> FormatJson -> FormatJson -> [FormatJson])
-> Enum FormatJson
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: FormatJson -> FormatJson
succ :: FormatJson -> FormatJson
$cpred :: FormatJson -> FormatJson
pred :: FormatJson -> FormatJson
$ctoEnum :: Int -> FormatJson
toEnum :: Int -> FormatJson
$cfromEnum :: FormatJson -> Int
fromEnum :: FormatJson -> Int
$cenumFrom :: FormatJson -> [FormatJson]
enumFrom :: FormatJson -> [FormatJson]
$cenumFromThen :: FormatJson -> FormatJson -> [FormatJson]
enumFromThen :: FormatJson -> FormatJson -> [FormatJson]
$cenumFromTo :: FormatJson -> FormatJson -> [FormatJson]
enumFromTo :: FormatJson -> FormatJson -> [FormatJson]
$cenumFromThenTo :: FormatJson -> FormatJson -> FormatJson -> [FormatJson]
enumFromThenTo :: FormatJson -> FormatJson -> FormatJson -> [FormatJson]
Enum, FormatJson -> FormatJson -> Bool
(FormatJson -> FormatJson -> Bool)
-> (FormatJson -> FormatJson -> Bool) -> Eq FormatJson
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FormatJson -> FormatJson -> Bool
== :: FormatJson -> FormatJson -> Bool
$c/= :: FormatJson -> FormatJson -> Bool
/= :: FormatJson -> FormatJson -> Bool
Eq, Eq FormatJson
Eq FormatJson =>
(FormatJson -> FormatJson -> Ordering)
-> (FormatJson -> FormatJson -> Bool)
-> (FormatJson -> FormatJson -> Bool)
-> (FormatJson -> FormatJson -> Bool)
-> (FormatJson -> FormatJson -> Bool)
-> (FormatJson -> FormatJson -> FormatJson)
-> (FormatJson -> FormatJson -> FormatJson)
-> Ord FormatJson
FormatJson -> FormatJson -> Bool
FormatJson -> FormatJson -> Ordering
FormatJson -> FormatJson -> FormatJson
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
$ccompare :: FormatJson -> FormatJson -> Ordering
compare :: FormatJson -> FormatJson -> Ordering
$c< :: FormatJson -> FormatJson -> Bool
< :: FormatJson -> FormatJson -> Bool
$c<= :: FormatJson -> FormatJson -> Bool
<= :: FormatJson -> FormatJson -> Bool
$c> :: FormatJson -> FormatJson -> Bool
> :: FormatJson -> FormatJson -> Bool
$c>= :: FormatJson -> FormatJson -> Bool
>= :: FormatJson -> FormatJson -> Bool
$cmax :: FormatJson -> FormatJson -> FormatJson
max :: FormatJson -> FormatJson -> FormatJson
$cmin :: FormatJson -> FormatJson -> FormatJson
min :: FormatJson -> FormatJson -> FormatJson
Ord, Int -> FormatJson -> ShowS
[FormatJson] -> ShowS
FormatJson -> String
(Int -> FormatJson -> ShowS)
-> (FormatJson -> String)
-> ([FormatJson] -> ShowS)
-> Show FormatJson
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FormatJson -> ShowS
showsPrec :: Int -> FormatJson -> ShowS
$cshow :: FormatJson -> String
show :: FormatJson -> String
$cshowList :: [FormatJson] -> ShowS
showList :: [FormatJson] -> ShowS
Show)
data FormatText = FormatText
deriving (Int -> FormatText
FormatText -> Int
FormatText -> [FormatText]
FormatText -> FormatText
FormatText -> FormatText -> [FormatText]
FormatText -> FormatText -> FormatText -> [FormatText]
(FormatText -> FormatText)
-> (FormatText -> FormatText)
-> (Int -> FormatText)
-> (FormatText -> Int)
-> (FormatText -> [FormatText])
-> (FormatText -> FormatText -> [FormatText])
-> (FormatText -> FormatText -> [FormatText])
-> (FormatText -> FormatText -> FormatText -> [FormatText])
-> Enum FormatText
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: FormatText -> FormatText
succ :: FormatText -> FormatText
$cpred :: FormatText -> FormatText
pred :: FormatText -> FormatText
$ctoEnum :: Int -> FormatText
toEnum :: Int -> FormatText
$cfromEnum :: FormatText -> Int
fromEnum :: FormatText -> Int
$cenumFrom :: FormatText -> [FormatText]
enumFrom :: FormatText -> [FormatText]
$cenumFromThen :: FormatText -> FormatText -> [FormatText]
enumFromThen :: FormatText -> FormatText -> [FormatText]
$cenumFromTo :: FormatText -> FormatText -> [FormatText]
enumFromTo :: FormatText -> FormatText -> [FormatText]
$cenumFromThenTo :: FormatText -> FormatText -> FormatText -> [FormatText]
enumFromThenTo :: FormatText -> FormatText -> FormatText -> [FormatText]
Enum, FormatText -> FormatText -> Bool
(FormatText -> FormatText -> Bool)
-> (FormatText -> FormatText -> Bool) -> Eq FormatText
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FormatText -> FormatText -> Bool
== :: FormatText -> FormatText -> Bool
$c/= :: FormatText -> FormatText -> Bool
/= :: FormatText -> FormatText -> Bool
Eq, Eq FormatText
Eq FormatText =>
(FormatText -> FormatText -> Ordering)
-> (FormatText -> FormatText -> Bool)
-> (FormatText -> FormatText -> Bool)
-> (FormatText -> FormatText -> Bool)
-> (FormatText -> FormatText -> Bool)
-> (FormatText -> FormatText -> FormatText)
-> (FormatText -> FormatText -> FormatText)
-> Ord FormatText
FormatText -> FormatText -> Bool
FormatText -> FormatText -> Ordering
FormatText -> FormatText -> FormatText
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
$ccompare :: FormatText -> FormatText -> Ordering
compare :: FormatText -> FormatText -> Ordering
$c< :: FormatText -> FormatText -> Bool
< :: FormatText -> FormatText -> Bool
$c<= :: FormatText -> FormatText -> Bool
<= :: FormatText -> FormatText -> Bool
$c> :: FormatText -> FormatText -> Bool
> :: FormatText -> FormatText -> Bool
$c>= :: FormatText -> FormatText -> Bool
>= :: FormatText -> FormatText -> Bool
$cmax :: FormatText -> FormatText -> FormatText
max :: FormatText -> FormatText -> FormatText
$cmin :: FormatText -> FormatText -> FormatText
min :: FormatText -> FormatText -> FormatText
Ord, Int -> FormatText -> ShowS
[FormatText] -> ShowS
FormatText -> String
(Int -> FormatText -> ShowS)
-> (FormatText -> String)
-> ([FormatText] -> ShowS)
-> Show FormatText
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FormatText -> ShowS
showsPrec :: Int -> FormatText -> ShowS
$cshow :: FormatText -> String
show :: FormatText -> String
$cshowList :: [FormatText] -> ShowS
showList :: [FormatText] -> ShowS
Show)
data FormatTextEnvelope = FormatTextEnvelope
deriving (Int -> FormatTextEnvelope
FormatTextEnvelope -> Int
FormatTextEnvelope -> [FormatTextEnvelope]
FormatTextEnvelope -> FormatTextEnvelope
FormatTextEnvelope -> FormatTextEnvelope -> [FormatTextEnvelope]
FormatTextEnvelope
-> FormatTextEnvelope -> FormatTextEnvelope -> [FormatTextEnvelope]
(FormatTextEnvelope -> FormatTextEnvelope)
-> (FormatTextEnvelope -> FormatTextEnvelope)
-> (Int -> FormatTextEnvelope)
-> (FormatTextEnvelope -> Int)
-> (FormatTextEnvelope -> [FormatTextEnvelope])
-> (FormatTextEnvelope
-> FormatTextEnvelope -> [FormatTextEnvelope])
-> (FormatTextEnvelope
-> FormatTextEnvelope -> [FormatTextEnvelope])
-> (FormatTextEnvelope
-> FormatTextEnvelope
-> FormatTextEnvelope
-> [FormatTextEnvelope])
-> Enum FormatTextEnvelope
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: FormatTextEnvelope -> FormatTextEnvelope
succ :: FormatTextEnvelope -> FormatTextEnvelope
$cpred :: FormatTextEnvelope -> FormatTextEnvelope
pred :: FormatTextEnvelope -> FormatTextEnvelope
$ctoEnum :: Int -> FormatTextEnvelope
toEnum :: Int -> FormatTextEnvelope
$cfromEnum :: FormatTextEnvelope -> Int
fromEnum :: FormatTextEnvelope -> Int
$cenumFrom :: FormatTextEnvelope -> [FormatTextEnvelope]
enumFrom :: FormatTextEnvelope -> [FormatTextEnvelope]
$cenumFromThen :: FormatTextEnvelope -> FormatTextEnvelope -> [FormatTextEnvelope]
enumFromThen :: FormatTextEnvelope -> FormatTextEnvelope -> [FormatTextEnvelope]
$cenumFromTo :: FormatTextEnvelope -> FormatTextEnvelope -> [FormatTextEnvelope]
enumFromTo :: FormatTextEnvelope -> FormatTextEnvelope -> [FormatTextEnvelope]
$cenumFromThenTo :: FormatTextEnvelope
-> FormatTextEnvelope -> FormatTextEnvelope -> [FormatTextEnvelope]
enumFromThenTo :: FormatTextEnvelope
-> FormatTextEnvelope -> FormatTextEnvelope -> [FormatTextEnvelope]
Enum, FormatTextEnvelope -> FormatTextEnvelope -> Bool
(FormatTextEnvelope -> FormatTextEnvelope -> Bool)
-> (FormatTextEnvelope -> FormatTextEnvelope -> Bool)
-> Eq FormatTextEnvelope
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FormatTextEnvelope -> FormatTextEnvelope -> Bool
== :: FormatTextEnvelope -> FormatTextEnvelope -> Bool
$c/= :: FormatTextEnvelope -> FormatTextEnvelope -> Bool
/= :: FormatTextEnvelope -> FormatTextEnvelope -> Bool
Eq, Eq FormatTextEnvelope
Eq FormatTextEnvelope =>
(FormatTextEnvelope -> FormatTextEnvelope -> Ordering)
-> (FormatTextEnvelope -> FormatTextEnvelope -> Bool)
-> (FormatTextEnvelope -> FormatTextEnvelope -> Bool)
-> (FormatTextEnvelope -> FormatTextEnvelope -> Bool)
-> (FormatTextEnvelope -> FormatTextEnvelope -> Bool)
-> (FormatTextEnvelope -> FormatTextEnvelope -> FormatTextEnvelope)
-> (FormatTextEnvelope -> FormatTextEnvelope -> FormatTextEnvelope)
-> Ord FormatTextEnvelope
FormatTextEnvelope -> FormatTextEnvelope -> Bool
FormatTextEnvelope -> FormatTextEnvelope -> Ordering
FormatTextEnvelope -> FormatTextEnvelope -> FormatTextEnvelope
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
$ccompare :: FormatTextEnvelope -> FormatTextEnvelope -> Ordering
compare :: FormatTextEnvelope -> FormatTextEnvelope -> Ordering
$c< :: FormatTextEnvelope -> FormatTextEnvelope -> Bool
< :: FormatTextEnvelope -> FormatTextEnvelope -> Bool
$c<= :: FormatTextEnvelope -> FormatTextEnvelope -> Bool
<= :: FormatTextEnvelope -> FormatTextEnvelope -> Bool
$c> :: FormatTextEnvelope -> FormatTextEnvelope -> Bool
> :: FormatTextEnvelope -> FormatTextEnvelope -> Bool
$c>= :: FormatTextEnvelope -> FormatTextEnvelope -> Bool
>= :: FormatTextEnvelope -> FormatTextEnvelope -> Bool
$cmax :: FormatTextEnvelope -> FormatTextEnvelope -> FormatTextEnvelope
max :: FormatTextEnvelope -> FormatTextEnvelope -> FormatTextEnvelope
$cmin :: FormatTextEnvelope -> FormatTextEnvelope -> FormatTextEnvelope
min :: FormatTextEnvelope -> FormatTextEnvelope -> FormatTextEnvelope
Ord, Int -> FormatTextEnvelope -> ShowS
[FormatTextEnvelope] -> ShowS
FormatTextEnvelope -> String
(Int -> FormatTextEnvelope -> ShowS)
-> (FormatTextEnvelope -> String)
-> ([FormatTextEnvelope] -> ShowS)
-> Show FormatTextEnvelope
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FormatTextEnvelope -> ShowS
showsPrec :: Int -> FormatTextEnvelope -> ShowS
$cshow :: FormatTextEnvelope -> String
show :: FormatTextEnvelope -> String
$cshowList :: [FormatTextEnvelope] -> ShowS
showList :: [FormatTextEnvelope] -> ShowS
Show)
data FormatYaml = FormatYaml
deriving (Int -> FormatYaml
FormatYaml -> Int
FormatYaml -> [FormatYaml]
FormatYaml -> FormatYaml
FormatYaml -> FormatYaml -> [FormatYaml]
FormatYaml -> FormatYaml -> FormatYaml -> [FormatYaml]
(FormatYaml -> FormatYaml)
-> (FormatYaml -> FormatYaml)
-> (Int -> FormatYaml)
-> (FormatYaml -> Int)
-> (FormatYaml -> [FormatYaml])
-> (FormatYaml -> FormatYaml -> [FormatYaml])
-> (FormatYaml -> FormatYaml -> [FormatYaml])
-> (FormatYaml -> FormatYaml -> FormatYaml -> [FormatYaml])
-> Enum FormatYaml
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: FormatYaml -> FormatYaml
succ :: FormatYaml -> FormatYaml
$cpred :: FormatYaml -> FormatYaml
pred :: FormatYaml -> FormatYaml
$ctoEnum :: Int -> FormatYaml
toEnum :: Int -> FormatYaml
$cfromEnum :: FormatYaml -> Int
fromEnum :: FormatYaml -> Int
$cenumFrom :: FormatYaml -> [FormatYaml]
enumFrom :: FormatYaml -> [FormatYaml]
$cenumFromThen :: FormatYaml -> FormatYaml -> [FormatYaml]
enumFromThen :: FormatYaml -> FormatYaml -> [FormatYaml]
$cenumFromTo :: FormatYaml -> FormatYaml -> [FormatYaml]
enumFromTo :: FormatYaml -> FormatYaml -> [FormatYaml]
$cenumFromThenTo :: FormatYaml -> FormatYaml -> FormatYaml -> [FormatYaml]
enumFromThenTo :: FormatYaml -> FormatYaml -> FormatYaml -> [FormatYaml]
Enum, FormatYaml -> FormatYaml -> Bool
(FormatYaml -> FormatYaml -> Bool)
-> (FormatYaml -> FormatYaml -> Bool) -> Eq FormatYaml
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FormatYaml -> FormatYaml -> Bool
== :: FormatYaml -> FormatYaml -> Bool
$c/= :: FormatYaml -> FormatYaml -> Bool
/= :: FormatYaml -> FormatYaml -> Bool
Eq, Eq FormatYaml
Eq FormatYaml =>
(FormatYaml -> FormatYaml -> Ordering)
-> (FormatYaml -> FormatYaml -> Bool)
-> (FormatYaml -> FormatYaml -> Bool)
-> (FormatYaml -> FormatYaml -> Bool)
-> (FormatYaml -> FormatYaml -> Bool)
-> (FormatYaml -> FormatYaml -> FormatYaml)
-> (FormatYaml -> FormatYaml -> FormatYaml)
-> Ord FormatYaml
FormatYaml -> FormatYaml -> Bool
FormatYaml -> FormatYaml -> Ordering
FormatYaml -> FormatYaml -> FormatYaml
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
$ccompare :: FormatYaml -> FormatYaml -> Ordering
compare :: FormatYaml -> FormatYaml -> Ordering
$c< :: FormatYaml -> FormatYaml -> Bool
< :: FormatYaml -> FormatYaml -> Bool
$c<= :: FormatYaml -> FormatYaml -> Bool
<= :: FormatYaml -> FormatYaml -> Bool
$c> :: FormatYaml -> FormatYaml -> Bool
> :: FormatYaml -> FormatYaml -> Bool
$c>= :: FormatYaml -> FormatYaml -> Bool
>= :: FormatYaml -> FormatYaml -> Bool
$cmax :: FormatYaml -> FormatYaml -> FormatYaml
max :: FormatYaml -> FormatYaml -> FormatYaml
$cmin :: FormatYaml -> FormatYaml -> FormatYaml
min :: FormatYaml -> FormatYaml -> FormatYaml
Ord, Int -> FormatYaml -> ShowS
[FormatYaml] -> ShowS
FormatYaml -> String
(Int -> FormatYaml -> ShowS)
-> (FormatYaml -> String)
-> ([FormatYaml] -> ShowS)
-> Show FormatYaml
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FormatYaml -> ShowS
showsPrec :: Int -> FormatYaml -> ShowS
$cshow :: FormatYaml -> String
show :: FormatYaml -> String
$cshowList :: [FormatYaml] -> ShowS
showList :: [FormatYaml] -> ShowS
Show)
newtype ProtocolParamsFile
= ProtocolParamsFile FilePath
deriving (Int -> ProtocolParamsFile -> ShowS
[ProtocolParamsFile] -> ShowS
ProtocolParamsFile -> String
(Int -> ProtocolParamsFile -> ShowS)
-> (ProtocolParamsFile -> String)
-> ([ProtocolParamsFile] -> ShowS)
-> Show ProtocolParamsFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ProtocolParamsFile -> ShowS
showsPrec :: Int -> ProtocolParamsFile -> ShowS
$cshow :: ProtocolParamsFile -> String
show :: ProtocolParamsFile -> String
$cshowList :: [ProtocolParamsFile] -> ShowS
showList :: [ProtocolParamsFile] -> ShowS
Show, ProtocolParamsFile -> ProtocolParamsFile -> Bool
(ProtocolParamsFile -> ProtocolParamsFile -> Bool)
-> (ProtocolParamsFile -> ProtocolParamsFile -> Bool)
-> Eq ProtocolParamsFile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ProtocolParamsFile -> ProtocolParamsFile -> Bool
== :: ProtocolParamsFile -> ProtocolParamsFile -> Bool
$c/= :: ProtocolParamsFile -> ProtocolParamsFile -> Bool
/= :: ProtocolParamsFile -> ProtocolParamsFile -> Bool
Eq)
newtype TxInCount
= TxInCount Int
deriving Int -> TxInCount -> ShowS
[TxInCount] -> ShowS
TxInCount -> String
(Int -> TxInCount -> ShowS)
-> (TxInCount -> String)
-> ([TxInCount] -> ShowS)
-> Show TxInCount
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TxInCount -> ShowS
showsPrec :: Int -> TxInCount -> ShowS
$cshow :: TxInCount -> String
show :: TxInCount -> String
$cshowList :: [TxInCount] -> ShowS
showList :: [TxInCount] -> ShowS
Show
newtype TxOutCount
= TxOutCount Int
deriving Int -> TxOutCount -> ShowS
[TxOutCount] -> ShowS
TxOutCount -> String
(Int -> TxOutCount -> ShowS)
-> (TxOutCount -> String)
-> ([TxOutCount] -> ShowS)
-> Show TxOutCount
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TxOutCount -> ShowS
showsPrec :: Int -> TxOutCount -> ShowS
$cshow :: TxOutCount -> String
show :: TxOutCount -> String
$cshowList :: [TxOutCount] -> ShowS
showList :: [TxOutCount] -> ShowS
Show
newtype TxShelleyWitnessCount
= TxShelleyWitnessCount Int
deriving Int -> TxShelleyWitnessCount -> ShowS
[TxShelleyWitnessCount] -> ShowS
TxShelleyWitnessCount -> String
(Int -> TxShelleyWitnessCount -> ShowS)
-> (TxShelleyWitnessCount -> String)
-> ([TxShelleyWitnessCount] -> ShowS)
-> Show TxShelleyWitnessCount
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TxShelleyWitnessCount -> ShowS
showsPrec :: Int -> TxShelleyWitnessCount -> ShowS
$cshow :: TxShelleyWitnessCount -> String
show :: TxShelleyWitnessCount -> String
$cshowList :: [TxShelleyWitnessCount] -> ShowS
showList :: [TxShelleyWitnessCount] -> ShowS
Show
newtype TxByronWitnessCount
= TxByronWitnessCount Int
deriving Int -> TxByronWitnessCount -> ShowS
[TxByronWitnessCount] -> ShowS
TxByronWitnessCount -> String
(Int -> TxByronWitnessCount -> ShowS)
-> (TxByronWitnessCount -> String)
-> ([TxByronWitnessCount] -> ShowS)
-> Show TxByronWitnessCount
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TxByronWitnessCount -> ShowS
showsPrec :: Int -> TxByronWitnessCount -> ShowS
$cshow :: TxByronWitnessCount -> String
show :: TxByronWitnessCount -> String
$cshowList :: [TxByronWitnessCount] -> ShowS
showList :: [TxByronWitnessCount] -> ShowS
Show
newtype ReferenceScriptSize
= ReferenceScriptSize {ReferenceScriptSize -> Int
unReferenceScriptSize :: Int}
deriving Int -> ReferenceScriptSize -> ShowS
[ReferenceScriptSize] -> ShowS
ReferenceScriptSize -> String
(Int -> ReferenceScriptSize -> ShowS)
-> (ReferenceScriptSize -> String)
-> ([ReferenceScriptSize] -> ShowS)
-> Show ReferenceScriptSize
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ReferenceScriptSize -> ShowS
showsPrec :: Int -> ReferenceScriptSize -> ShowS
$cshow :: ReferenceScriptSize -> String
show :: ReferenceScriptSize -> String
$cshowList :: [ReferenceScriptSize] -> ShowS
showList :: [ReferenceScriptSize] -> ShowS
Show
newtype BlockId
= BlockId String
deriving Int -> BlockId -> ShowS
[BlockId] -> ShowS
BlockId -> String
(Int -> BlockId -> ShowS)
-> (BlockId -> String) -> ([BlockId] -> ShowS) -> Show BlockId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BlockId -> ShowS
showsPrec :: Int -> BlockId -> ShowS
$cshow :: BlockId -> String
show :: BlockId -> String
$cshowList :: [BlockId] -> ShowS
showList :: [BlockId] -> ShowS
Show
newtype GenesisKeyFile
= GenesisKeyFile FilePath
deriving Int -> GenesisKeyFile -> ShowS
[GenesisKeyFile] -> ShowS
GenesisKeyFile -> String
(Int -> GenesisKeyFile -> ShowS)
-> (GenesisKeyFile -> String)
-> ([GenesisKeyFile] -> ShowS)
-> Show GenesisKeyFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GenesisKeyFile -> ShowS
showsPrec :: Int -> GenesisKeyFile -> ShowS
$cshow :: GenesisKeyFile -> String
show :: GenesisKeyFile -> String
$cshowList :: [GenesisKeyFile] -> ShowS
showList :: [GenesisKeyFile] -> ShowS
Show
data MetadataFile
= MetadataFileJSON (File () In)
| MetadataFileCBOR (File () In)
deriving Int -> MetadataFile -> ShowS
[MetadataFile] -> ShowS
MetadataFile -> String
(Int -> MetadataFile -> ShowS)
-> (MetadataFile -> String)
-> ([MetadataFile] -> ShowS)
-> Show MetadataFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MetadataFile -> ShowS
showsPrec :: Int -> MetadataFile -> ShowS
$cshow :: MetadataFile -> String
show :: MetadataFile -> String
$cshowList :: [MetadataFile] -> ShowS
showList :: [MetadataFile] -> ShowS
Show
type StakePoolMetadataFile = File StakePoolMetadata
type DRepMetadataFile = File DRepMetadata
newtype GenesisDir
= GenesisDir FilePath
deriving Int -> GenesisDir -> ShowS
[GenesisDir] -> ShowS
GenesisDir -> String
(Int -> GenesisDir -> ShowS)
-> (GenesisDir -> String)
-> ([GenesisDir] -> ShowS)
-> Show GenesisDir
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GenesisDir -> ShowS
showsPrec :: Int -> GenesisDir -> ShowS
$cshow :: GenesisDir -> String
show :: GenesisDir -> String
$cshowList :: [GenesisDir] -> ShowS
showList :: [GenesisDir] -> ShowS
Show
data SomeKeyFile direction
= AVerificationKeyFile (VerificationKeyFile direction)
| ASigningKeyFile (SigningKeyFile direction)
deriving Int -> SomeKeyFile direction -> ShowS
[SomeKeyFile direction] -> ShowS
SomeKeyFile direction -> String
(Int -> SomeKeyFile direction -> ShowS)
-> (SomeKeyFile direction -> String)
-> ([SomeKeyFile direction] -> ShowS)
-> Show (SomeKeyFile direction)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (direction :: FileDirection).
Int -> SomeKeyFile direction -> ShowS
forall (direction :: FileDirection).
[SomeKeyFile direction] -> ShowS
forall (direction :: FileDirection).
SomeKeyFile direction -> String
$cshowsPrec :: forall (direction :: FileDirection).
Int -> SomeKeyFile direction -> ShowS
showsPrec :: Int -> SomeKeyFile direction -> ShowS
$cshow :: forall (direction :: FileDirection).
SomeKeyFile direction -> String
show :: SomeKeyFile direction -> String
$cshowList :: forall (direction :: FileDirection).
[SomeKeyFile direction] -> ShowS
showList :: [SomeKeyFile direction] -> ShowS
Show
data AddressKeyType
= AddressKeyShelley
| AddressKeyShelleyExtended
| AddressKeyByron
deriving Int -> AddressKeyType -> ShowS
[AddressKeyType] -> ShowS
AddressKeyType -> String
(Int -> AddressKeyType -> ShowS)
-> (AddressKeyType -> String)
-> ([AddressKeyType] -> ShowS)
-> Show AddressKeyType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AddressKeyType -> ShowS
showsPrec :: Int -> AddressKeyType -> ShowS
$cshow :: AddressKeyType -> String
show :: AddressKeyType -> String
$cshowList :: [AddressKeyType] -> ShowS
showList :: [AddressKeyType] -> ShowS
Show
data ByronKeyType
= ByronPaymentKey ByronKeyFormat
| ByronGenesisKey ByronKeyFormat
| ByronDelegateKey ByronKeyFormat
deriving Int -> ByronKeyType -> ShowS
[ByronKeyType] -> ShowS
ByronKeyType -> String
(Int -> ByronKeyType -> ShowS)
-> (ByronKeyType -> String)
-> ([ByronKeyType] -> ShowS)
-> Show ByronKeyType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ByronKeyType -> ShowS
showsPrec :: Int -> ByronKeyType -> ShowS
$cshow :: ByronKeyType -> String
show :: ByronKeyType -> String
$cshowList :: [ByronKeyType] -> ShowS
showList :: [ByronKeyType] -> ShowS
Show
data ByronKeyFormat
= NonLegacyByronKeyFormat
| LegacyByronKeyFormat
deriving Int -> ByronKeyFormat -> ShowS
[ByronKeyFormat] -> ShowS
ByronKeyFormat -> String
(Int -> ByronKeyFormat -> ShowS)
-> (ByronKeyFormat -> String)
-> ([ByronKeyFormat] -> ShowS)
-> Show ByronKeyFormat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ByronKeyFormat -> ShowS
showsPrec :: Int -> ByronKeyFormat -> ShowS
$cshow :: ByronKeyFormat -> String
show :: ByronKeyFormat -> String
$cshowList :: [ByronKeyFormat] -> ShowS
showList :: [ByronKeyFormat] -> ShowS
Show
data CardanoAddressKeyType
= CardanoAddressShelleyPaymentKey
| CardanoAddressShelleyStakeKey
| CardanoAddressIcarusPaymentKey
| CardanoAddressByronPaymentKey
| CardanoAddressCommitteeColdKey
| CardanoAddressCommitteeHotKey
| CardanoAddressDRepKey
deriving Int -> CardanoAddressKeyType -> ShowS
[CardanoAddressKeyType] -> ShowS
CardanoAddressKeyType -> String
(Int -> CardanoAddressKeyType -> ShowS)
-> (CardanoAddressKeyType -> String)
-> ([CardanoAddressKeyType] -> ShowS)
-> Show CardanoAddressKeyType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CardanoAddressKeyType -> ShowS
showsPrec :: Int -> CardanoAddressKeyType -> ShowS
$cshow :: CardanoAddressKeyType -> String
show :: CardanoAddressKeyType -> String
$cshowList :: [CardanoAddressKeyType] -> ShowS
showList :: [CardanoAddressKeyType] -> ShowS
Show
type OpCertCounterFile = File OpCertCounter
newtype PrivKeyFile
= PrivKeyFile FilePath
deriving Int -> PrivKeyFile -> ShowS
[PrivKeyFile] -> ShowS
PrivKeyFile -> String
(Int -> PrivKeyFile -> ShowS)
-> (PrivKeyFile -> String)
-> ([PrivKeyFile] -> ShowS)
-> Show PrivKeyFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PrivKeyFile -> ShowS
showsPrec :: Int -> PrivKeyFile -> ShowS
$cshow :: PrivKeyFile -> String
show :: PrivKeyFile -> String
$cshowList :: [PrivKeyFile] -> ShowS
showList :: [PrivKeyFile] -> ShowS
Show
newtype WitnessFile
= WitnessFile FilePath
deriving Int -> WitnessFile -> ShowS
[WitnessFile] -> ShowS
WitnessFile -> String
(Int -> WitnessFile -> ShowS)
-> (WitnessFile -> String)
-> ([WitnessFile] -> ShowS)
-> Show WitnessFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> WitnessFile -> ShowS
showsPrec :: Int -> WitnessFile -> ShowS
$cshow :: WitnessFile -> String
show :: WitnessFile -> String
$cshowList :: [WitnessFile] -> ShowS
showList :: [WitnessFile] -> ShowS
Show
newtype VerificationKeyBase64
= VerificationKeyBase64 String
deriving Int -> VerificationKeyBase64 -> ShowS
[VerificationKeyBase64] -> ShowS
VerificationKeyBase64 -> String
(Int -> VerificationKeyBase64 -> ShowS)
-> (VerificationKeyBase64 -> String)
-> ([VerificationKeyBase64] -> ShowS)
-> Show VerificationKeyBase64
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VerificationKeyBase64 -> ShowS
showsPrec :: Int -> VerificationKeyBase64 -> ShowS
$cshow :: VerificationKeyBase64 -> String
show :: VerificationKeyBase64 -> String
$cshowList :: [VerificationKeyBase64] -> ShowS
showList :: [VerificationKeyBase64] -> ShowS
Show
data WitnessSigningData
= KeyWitnessSigningData
!(SigningKeyFile In)
!(Maybe (Address ByronAddr))
deriving Int -> WitnessSigningData -> ShowS
[WitnessSigningData] -> ShowS
WitnessSigningData -> String
(Int -> WitnessSigningData -> ShowS)
-> (WitnessSigningData -> String)
-> ([WitnessSigningData] -> ShowS)
-> Show WitnessSigningData
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> WitnessSigningData -> ShowS
showsPrec :: Int -> WitnessSigningData -> ShowS
$cshow :: WitnessSigningData -> String
show :: WitnessSigningData -> String
$cshowList :: [WitnessSigningData] -> ShowS
showList :: [WitnessSigningData] -> ShowS
Show
data InputTxBodyOrTxFile = InputTxBodyFile (TxBodyFile In) | InputTxFile (TxFile In)
deriving Int -> InputTxBodyOrTxFile -> ShowS
[InputTxBodyOrTxFile] -> ShowS
InputTxBodyOrTxFile -> String
(Int -> InputTxBodyOrTxFile -> ShowS)
-> (InputTxBodyOrTxFile -> String)
-> ([InputTxBodyOrTxFile] -> ShowS)
-> Show InputTxBodyOrTxFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InputTxBodyOrTxFile -> ShowS
showsPrec :: Int -> InputTxBodyOrTxFile -> ShowS
$cshow :: InputTxBodyOrTxFile -> String
show :: InputTxBodyOrTxFile -> String
$cshowList :: [InputTxBodyOrTxFile] -> ShowS
showList :: [InputTxBodyOrTxFile] -> ShowS
Show
data ParserFileDirection
= Input
| Output
deriving (ParserFileDirection -> ParserFileDirection -> Bool
(ParserFileDirection -> ParserFileDirection -> Bool)
-> (ParserFileDirection -> ParserFileDirection -> Bool)
-> Eq ParserFileDirection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ParserFileDirection -> ParserFileDirection -> Bool
== :: ParserFileDirection -> ParserFileDirection -> Bool
$c/= :: ParserFileDirection -> ParserFileDirection -> Bool
/= :: ParserFileDirection -> ParserFileDirection -> Bool
Eq, Int -> ParserFileDirection -> ShowS
[ParserFileDirection] -> ShowS
ParserFileDirection -> String
(Int -> ParserFileDirection -> ShowS)
-> (ParserFileDirection -> String)
-> ([ParserFileDirection] -> ShowS)
-> Show ParserFileDirection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ParserFileDirection -> ShowS
showsPrec :: Int -> ParserFileDirection -> ShowS
$cshow :: ParserFileDirection -> String
show :: ParserFileDirection -> String
$cshowList :: [ParserFileDirection] -> ShowS
showList :: [ParserFileDirection] -> ShowS
Show)
data MustCheckHash a
= CheckHash
| TrustHash
deriving (MustCheckHash a -> MustCheckHash a -> Bool
(MustCheckHash a -> MustCheckHash a -> Bool)
-> (MustCheckHash a -> MustCheckHash a -> Bool)
-> Eq (MustCheckHash a)
forall a. MustCheckHash a -> MustCheckHash a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. MustCheckHash a -> MustCheckHash a -> Bool
== :: MustCheckHash a -> MustCheckHash a -> Bool
$c/= :: forall a. MustCheckHash a -> MustCheckHash a -> Bool
/= :: MustCheckHash a -> MustCheckHash a -> Bool
Eq, Int -> MustCheckHash a -> ShowS
[MustCheckHash a] -> ShowS
MustCheckHash a -> String
(Int -> MustCheckHash a -> ShowS)
-> (MustCheckHash a -> String)
-> ([MustCheckHash a] -> ShowS)
-> Show (MustCheckHash a)
forall a. Int -> MustCheckHash a -> ShowS
forall a. [MustCheckHash a] -> ShowS
forall a. MustCheckHash a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Int -> MustCheckHash a -> ShowS
showsPrec :: Int -> MustCheckHash a -> ShowS
$cshow :: forall a. MustCheckHash a -> String
show :: MustCheckHash a -> String
$cshowList :: forall a. [MustCheckHash a] -> ShowS
showList :: [MustCheckHash a] -> ShowS
Show)
data PotentiallyCheckedAnchor anchorType anchor
= PotentiallyCheckedAnchor
{ forall anchorType anchor.
PotentiallyCheckedAnchor anchorType anchor -> anchor
pcaAnchor :: anchor
, forall anchorType anchor.
PotentiallyCheckedAnchor anchorType anchor
-> MustCheckHash anchorType
pcaMustCheck :: MustCheckHash anchorType
}
deriving (PotentiallyCheckedAnchor anchorType anchor
-> PotentiallyCheckedAnchor anchorType anchor -> Bool
(PotentiallyCheckedAnchor anchorType anchor
-> PotentiallyCheckedAnchor anchorType anchor -> Bool)
-> (PotentiallyCheckedAnchor anchorType anchor
-> PotentiallyCheckedAnchor anchorType anchor -> Bool)
-> Eq (PotentiallyCheckedAnchor anchorType anchor)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall anchorType anchor.
Eq anchor =>
PotentiallyCheckedAnchor anchorType anchor
-> PotentiallyCheckedAnchor anchorType anchor -> Bool
$c== :: forall anchorType anchor.
Eq anchor =>
PotentiallyCheckedAnchor anchorType anchor
-> PotentiallyCheckedAnchor anchorType anchor -> Bool
== :: PotentiallyCheckedAnchor anchorType anchor
-> PotentiallyCheckedAnchor anchorType anchor -> Bool
$c/= :: forall anchorType anchor.
Eq anchor =>
PotentiallyCheckedAnchor anchorType anchor
-> PotentiallyCheckedAnchor anchorType anchor -> Bool
/= :: PotentiallyCheckedAnchor anchorType anchor
-> PotentiallyCheckedAnchor anchorType anchor -> Bool
Eq, Int -> PotentiallyCheckedAnchor anchorType anchor -> ShowS
[PotentiallyCheckedAnchor anchorType anchor] -> ShowS
PotentiallyCheckedAnchor anchorType anchor -> String
(Int -> PotentiallyCheckedAnchor anchorType anchor -> ShowS)
-> (PotentiallyCheckedAnchor anchorType anchor -> String)
-> ([PotentiallyCheckedAnchor anchorType anchor] -> ShowS)
-> Show (PotentiallyCheckedAnchor anchorType anchor)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall anchorType anchor.
Show anchor =>
Int -> PotentiallyCheckedAnchor anchorType anchor -> ShowS
forall anchorType anchor.
Show anchor =>
[PotentiallyCheckedAnchor anchorType anchor] -> ShowS
forall anchorType anchor.
Show anchor =>
PotentiallyCheckedAnchor anchorType anchor -> String
$cshowsPrec :: forall anchorType anchor.
Show anchor =>
Int -> PotentiallyCheckedAnchor anchorType anchor -> ShowS
showsPrec :: Int -> PotentiallyCheckedAnchor anchorType anchor -> ShowS
$cshow :: forall anchorType anchor.
Show anchor =>
PotentiallyCheckedAnchor anchorType anchor -> String
show :: PotentiallyCheckedAnchor anchorType anchor -> String
$cshowList :: forall anchorType anchor.
Show anchor =>
[PotentiallyCheckedAnchor anchorType anchor] -> ShowS
showList :: [PotentiallyCheckedAnchor anchorType anchor] -> ShowS
Show)
newtype TxSubmissionResult = TxSubmissionResult {TxSubmissionResult -> TxId
txhash :: TxId}
deriving (Int -> TxSubmissionResult -> ShowS
[TxSubmissionResult] -> ShowS
TxSubmissionResult -> String
(Int -> TxSubmissionResult -> ShowS)
-> (TxSubmissionResult -> String)
-> ([TxSubmissionResult] -> ShowS)
-> Show TxSubmissionResult
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TxSubmissionResult -> ShowS
showsPrec :: Int -> TxSubmissionResult -> ShowS
$cshow :: TxSubmissionResult -> String
show :: TxSubmissionResult -> String
$cshowList :: [TxSubmissionResult] -> ShowS
showList :: [TxSubmissionResult] -> ShowS
Show, (forall x. TxSubmissionResult -> Rep TxSubmissionResult x)
-> (forall x. Rep TxSubmissionResult x -> TxSubmissionResult)
-> Generic TxSubmissionResult
forall x. Rep TxSubmissionResult x -> TxSubmissionResult
forall x. TxSubmissionResult -> Rep TxSubmissionResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TxSubmissionResult -> Rep TxSubmissionResult x
from :: forall x. TxSubmissionResult -> Rep TxSubmissionResult x
$cto :: forall x. Rep TxSubmissionResult x -> TxSubmissionResult
to :: forall x. Rep TxSubmissionResult x -> TxSubmissionResult
Generic)
instance FromJSON TxSubmissionResult
instance ToJSON TxSubmissionResult