Safe Haskell | None |
---|---|
Language | Haskell2010 |
Cardano.Api
Description
This module provides a library interface for interacting with Cardano as a user of the system.
It is intended to be the complete API covering everything but without exposing constructors that reveal any lower level types.
In the interest of simplicity it glosses over some details of the system. Most simple tools should be able to work just using this interface, however you can go deeper and expose the types from the underlying libraries.
Synopsis
- module Cardano.Api.Address
- module Cardano.Api.Certificate
- module Cardano.Api.Genesis
- module Cardano.Api.Governance
- module Cardano.Api.Era
- module Cardano.Api.Network
- module Cardano.Api.Network.IPC
- newtype PoolDistribution era = PoolDistribution {}
- data CommitteeMembersState = CommitteeMembersState {}
- data MemberStatus
- queryAccountState :: ConwayEraOnwards era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch AccountState))
- queryCommitteeMembersState :: ConwayEraOnwards era -> Set (Credential 'ColdCommitteeRole) -> Set (Credential 'HotCommitteeRole) -> Set MemberStatus -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch CommitteeMembersState))
- queryConstitution :: ConwayEraOnwards era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Constitution (ShelleyLedgerEra era))))
- queryConstitutionHash :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (SafeHash AnchorData)))
- queryDRepState :: ConwayEraOnwards era -> Set (Credential 'DRepRole) -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map (Credential 'DRepRole) DRepState)))
- queryFuturePParams :: ConwayEraOnwards era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Maybe (PParams (ShelleyLedgerEra era)))))
- queryGovState :: ConwayEraOnwards era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (GovState (ShelleyLedgerEra era))))
- queryProposals :: ConwayEraOnwards era -> Set GovActionId -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Seq (GovActionState (ShelleyLedgerEra era)))))
- queryRatifyState :: ConwayEraOnwards era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (RatifyState (ShelleyLedgerEra era))))
- queryStakePoolDefaultVote :: ConwayEraOnwards era -> KeyHash 'StakePool -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch DefaultVote))
- newtype SystemStart = SystemStart {}
- slotToEpoch :: SlotNo -> EraHistory -> Either PastHorizonException (EpochNo, SlotsInEpoch, SlotsToEpochEnd)
- data QueryInShelleyBasedEra era result where
- QueryEpoch :: forall era. QueryInShelleyBasedEra era EpochNo
- QueryGenesisParameters :: forall era. QueryInShelleyBasedEra era (GenesisParameters ShelleyEra)
- QueryProtocolParameters :: forall era. QueryInShelleyBasedEra era (PParams (ShelleyLedgerEra era))
- QueryStakeDistribution :: forall era. QueryInShelleyBasedEra era (Map (Hash StakePoolKey) Rational)
- QueryUTxO :: forall era. QueryUTxOFilter -> QueryInShelleyBasedEra era (UTxO era)
- QueryStakeAddresses :: forall era. Set StakeCredential -> NetworkId -> QueryInShelleyBasedEra era (Map StakeAddress Coin, Map StakeAddress PoolId)
- QueryStakePools :: forall era. QueryInShelleyBasedEra era (Set PoolId)
- QueryStakePoolParameters :: forall era. Set PoolId -> QueryInShelleyBasedEra era (Map PoolId StakePoolParameters)
- QueryDebugLedgerState :: forall era. QueryInShelleyBasedEra era (SerialisedDebugLedgerState era)
- QueryProtocolState :: forall era. QueryInShelleyBasedEra era (ProtocolState era)
- QueryCurrentEpochState :: forall era. QueryInShelleyBasedEra era (SerialisedCurrentEpochState era)
- QueryPoolState :: forall era. Maybe (Set PoolId) -> QueryInShelleyBasedEra era (SerialisedPoolState era)
- QueryPoolDistribution :: forall era. Maybe (Set PoolId) -> QueryInShelleyBasedEra era (SerialisedPoolDistribution era)
- QueryStakeSnapshot :: forall era. Maybe (Set PoolId) -> QueryInShelleyBasedEra era (SerialisedStakeSnapshots era)
- QueryStakeDelegDeposits :: forall era. Set StakeCredential -> QueryInShelleyBasedEra era (Map StakeCredential Coin)
- QueryAccountState :: forall era. QueryInShelleyBasedEra era AccountState
- QueryConstitution :: forall era. QueryInShelleyBasedEra era (Constitution (ShelleyLedgerEra era))
- QueryGovState :: forall era. QueryInShelleyBasedEra era (GovState (ShelleyLedgerEra era))
- QueryRatifyState :: forall era. QueryInShelleyBasedEra era (RatifyState (ShelleyLedgerEra era))
- QueryFuturePParams :: forall era. QueryInShelleyBasedEra era (Maybe (PParams (ShelleyLedgerEra era)))
- QueryDRepState :: forall era. Set (Credential 'DRepRole) -> QueryInShelleyBasedEra era (Map (Credential 'DRepRole) DRepState)
- QueryDRepStakeDistr :: forall era. Set DRep -> QueryInShelleyBasedEra era (Map DRep Coin)
- QuerySPOStakeDistr :: forall era. Set (KeyHash 'StakePool) -> QueryInShelleyBasedEra era (Map (KeyHash 'StakePool) Coin)
- QueryCommitteeMembersState :: forall era. Set (Credential 'ColdCommitteeRole) -> Set (Credential 'HotCommitteeRole) -> Set MemberStatus -> QueryInShelleyBasedEra era CommitteeMembersState
- QueryStakeVoteDelegatees :: forall era. Set StakeCredential -> QueryInShelleyBasedEra era (Map StakeCredential DRep)
- QueryProposals :: forall era. Set GovActionId -> QueryInShelleyBasedEra era (Seq (GovActionState (ShelleyLedgerEra era)))
- QueryLedgerPeerSnapshot :: forall era. QueryInShelleyBasedEra era (Serialised LedgerPeerSnapshot)
- QueryStakePoolDefaultVote :: forall era. KeyHash 'StakePool -> QueryInShelleyBasedEra era DefaultVote
- newtype StakeSnapshot era = StakeSnapshot StakeSnapshots
- data QueryInMode result where
- QueryCurrentEra :: QueryInMode AnyCardanoEra
- QueryInEra :: forall era result1. QueryInEra era result1 -> QueryInMode (Either EraMismatch result1)
- QueryEraHistory :: QueryInMode EraHistory
- QuerySystemStart :: QueryInMode SystemStart
- QueryChainBlockNo :: QueryInMode (WithOrigin BlockNo)
- QueryChainPoint :: QueryInMode ChainPoint
- QueryLedgerConfig :: QueryInMode (HardForkLedgerConfig (CardanoEras StandardCrypto))
- newtype CurrentEpochState era = CurrentEpochState (EpochState (ShelleyLedgerEra era))
- newtype ProtocolState era = ProtocolState (Serialised (ChainDepState (ConsensusProtocol era)))
- newtype SerialisedCurrentEpochState era = SerialisedCurrentEpochState (Serialised (EpochState (ShelleyLedgerEra era)))
- newtype SerialisedPoolDistribution era = SerialisedPoolDistribution (Serialised (PoolDistr StandardCrypto))
- decodeCurrentEpochState :: ShelleyBasedEra era -> SerialisedCurrentEpochState era -> Either DecoderError (CurrentEpochState era)
- decodePoolDistribution :: ShelleyBasedEra era -> SerialisedPoolDistribution era -> Either DecoderError (PoolDistribution era)
- decodeProtocolState :: FromCBOR (ChainDepState (ConsensusProtocol era)) => ProtocolState era -> Either (ByteString, DecoderError) (ChainDepState (ConsensusProtocol era))
- data QueryInEra era result where
- QueryByronUpdateState :: QueryInEra ByronEra ByronUpdateState
- QueryInShelleyBasedEra :: forall era result. ShelleyBasedEra era -> QueryInShelleyBasedEra era result -> QueryInEra era result
- data EraHistory where
- EraHistory :: forall (xs :: [Type]). CardanoBlock StandardCrypto ~ HardForkBlock xs => Interpreter xs -> EraHistory
- getProgress :: SlotNo -> EraHistory -> Either PastHorizonException (RelativeTime, SlotLength)
- data QueryUTxOFilter
- data UTxOInAnyEra where
- UTxOInAnyEra :: forall era. CardanoEra era -> UTxO era -> UTxOInAnyEra
- toConsensusQuery :: CardanoBlock StandardCrypto ~ block => QueryInMode result -> Some (Query block)
- fromConsensusQueryResult :: (HasCallStack, CardanoBlock StandardCrypto ~ block) => QueryInMode result -> Query block result' -> result' -> result
- newtype SerialisedDebugLedgerState era = SerialisedDebugLedgerState (Serialised (NewEpochState (ShelleyLedgerEra era)))
- newtype DebugLedgerState era = DebugLedgerState {}
- decodeDebugLedgerState :: FromCBOR (DebugLedgerState era) => SerialisedDebugLedgerState era -> Either (ByteString, DecoderError) (DebugLedgerState era)
- newtype SerialisedPoolState era = SerialisedPoolState (Serialised (PState (ShelleyLedgerEra era)))
- newtype PoolState era = PoolState (PState (ShelleyLedgerEra era))
- decodePoolState :: (Era (ShelleyLedgerEra era), DecCBOR (PState (ShelleyLedgerEra era))) => SerialisedPoolState era -> Either DecoderError (PoolState era)
- newtype SerialisedStakeSnapshots era = SerialisedStakeSnapshots (Serialised StakeSnapshots)
- decodeStakeSnapshot :: SerialisedStakeSnapshots era -> Either DecoderError (StakeSnapshot era)
- newtype LedgerEpochInfo = LedgerEpochInfo {}
- toLedgerEpochInfo :: EraHistory -> LedgerEpochInfo
- newtype SlotsInEpoch = SlotsInEpoch Word64
- newtype SlotsToEpochEnd = SlotsToEpochEnd Word64
- getSlotForRelativeTime :: RelativeTime -> EraHistory -> Either PastHorizonException SlotNo
- decodeBigLedgerPeerSnapshot :: Serialised LedgerPeerSnapshot -> Either (ByteString, DecoderError) LedgerPeerSnapshot
- data QueryConvenienceError
- newtype TxCurrentTreasuryValue = TxCurrentTreasuryValue {}
- determineEra :: LocalNodeConnectInfo -> ExceptT AcquiringFailure IO AnyCardanoEra
- executeQueryCardanoMode :: SocketPath -> NetworkId -> QueryInMode (Either EraMismatch result) -> ExceptT QueryConvenienceError IO result
- executeQueryAnyMode :: LocalNodeConnectInfo -> QueryInMode (Either EraMismatch result) -> ExceptT QueryConvenienceError IO result
- queryStateForBalancedTx :: CardanoEra era -> [TxIn] -> [Certificate era] -> LocalStateQueryExpr block point QueryInMode r IO (Either QueryConvenienceError (UTxO era, LedgerProtocolParameters era, EraHistory, SystemStart, Set PoolId, Map StakeCredential Coin, Map (Credential 'DRepRole) Coin, Maybe (Featured ConwayEraOnwards era TxCurrentTreasuryValue)))
- renderQueryConvenienceError :: QueryConvenienceError -> Text
- queryChainBlockNo :: LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (WithOrigin BlockNo))
- queryChainPoint :: LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError ChainPoint)
- queryCurrentEpochState :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (SerialisedCurrentEpochState era)))
- queryCurrentEra :: LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError AnyCardanoEra)
- queryDebugLedgerState :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (SerialisedDebugLedgerState era)))
- queryEpoch :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch EpochNo))
- queryEraHistory :: LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError EraHistory)
- queryGenesisParameters :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (GenesisParameters ShelleyEra)))
- queryPoolDistribution :: BabbageEraOnwards era -> Maybe (Set PoolId) -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (SerialisedPoolDistribution era)))
- queryPoolState :: BabbageEraOnwards era -> Maybe (Set PoolId) -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (SerialisedPoolState era)))
- queryProtocolParameters :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (PParams (ShelleyLedgerEra era))))
- queryProtocolState :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (ProtocolState era)))
- queryStakeAddresses :: ShelleyBasedEra era -> Set StakeCredential -> NetworkId -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map StakeAddress Coin, Map StakeAddress PoolId)))
- queryStakeDelegDeposits :: BabbageEraOnwards era -> Set StakeCredential -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map StakeCredential Coin)))
- queryStakeDistribution :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map (Hash StakePoolKey) Rational)))
- queryStakePoolParameters :: ShelleyBasedEra era -> Set PoolId -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map PoolId StakePoolParameters)))
- queryStakePools :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Set PoolId)))
- queryStakeSnapshot :: BabbageEraOnwards era -> Maybe (Set PoolId) -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (SerialisedStakeSnapshots era)))
- querySystemStart :: LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError SystemStart)
- queryUtxo :: ShelleyBasedEra era -> QueryUTxOFilter -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (UTxO era)))
- queryLedgerPeerSnapshot :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Serialised LedgerPeerSnapshot)))
- queryDRepStakeDistribution :: ConwayEraOnwards era -> Set DRep -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map DRep Coin)))
- querySPOStakeDistribution :: ConwayEraOnwards era -> Set (KeyHash 'StakePool) -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map (KeyHash 'StakePool) Coin)))
- queryStakeVoteDelegatees :: ConwayEraOnwards era -> Set StakeCredential -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map StakeCredential DRep)))
- queryLedgerConfig :: LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (CardanoLedgerConfig StandardCrypto))
- newtype DelegationsAndRewards = DelegationsAndRewards (Map StakeAddress Coin, Map StakeAddress PoolId)
- mergeDelegsAndRewards :: DelegationsAndRewards -> [(StakeAddress, Maybe Coin, Maybe PoolId)]
- toDebugLedgerStatePair :: KeyValue e a => ShelleyBasedEra era -> DebugLedgerState era -> [a]
- toLedgerUTxO :: ShelleyBasedEra era -> UTxO era -> UTxO (ShelleyLedgerEra era)
- fromLedgerUTxO :: ShelleyBasedEra era -> UTxO (ShelleyLedgerEra era) -> UTxO era
- module Cardano.Api.Consensus
- module Cardano.Api.Block
- module Cardano.Api.LedgerState
- module Cardano.Api.ProtocolParameters
- module Cardano.Api.Key
- module Cardano.Api.Hash
- module Cardano.Api.Tx
- module Cardano.Api.Plutus
- module Cardano.Api.Value
- module Cardano.Api.Serialise.Bech32
- module Cardano.Api.Serialise.Cip129
- module Cardano.Api.Serialise.Cbor
- module Cardano.Api.Serialise.Cbor.Canonical
- module Cardano.Api.Serialise.DeserialiseAnyOf
- module Cardano.Api.Serialise.Json
- module Cardano.Api.Serialise.Raw
- module Cardano.Api.Serialise.SerialiseUsing
- module Cardano.Api.Serialise.TextEnvelope
- module Cardano.Api.Error
- module Cardano.Api.Monad.Error
- module Cardano.Api.Pretty
- module Cardano.Api.IO
Address
module Cardano.Api.Address
Certificate
module Cardano.Api.Certificate
Genesis
module Cardano.Api.Genesis
Governance
module Cardano.Api.Governance
Eras
module Cardano.Api.Era
Network
module Cardano.Api.Network
Node queries
module Cardano.Api.Network.IPC
Query types
newtype PoolDistribution era Source #
Constructors
PoolDistribution | |
Fields |
data CommitteeMembersState Source #
Constructors
CommitteeMembersState | |
Fields
|
Instances
data MemberStatus Source #
Constructors
Active | |
Expired | |
Unrecognized | This can happen when a hot credential for an unknown cold credential exists. Such Committee member will be either removed from the state at the next epoch boundary or enacted as a new member. |
Instances
ToJSON MemberStatus | |||||
Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState Methods toJSON :: MemberStatus -> Value # toEncoding :: MemberStatus -> Encoding # toJSONList :: [MemberStatus] -> Value # toEncodingList :: [MemberStatus] -> Encoding # omitField :: MemberStatus -> Bool # | |||||
Bounded MemberStatus | |||||
Enum MemberStatus | |||||
Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState Methods succ :: MemberStatus -> MemberStatus Source # pred :: MemberStatus -> MemberStatus Source # toEnum :: Int -> MemberStatus Source # fromEnum :: MemberStatus -> Int Source # enumFrom :: MemberStatus -> [MemberStatus] Source # enumFromThen :: MemberStatus -> MemberStatus -> [MemberStatus] Source # enumFromTo :: MemberStatus -> MemberStatus -> [MemberStatus] Source # enumFromThenTo :: MemberStatus -> MemberStatus -> MemberStatus -> [MemberStatus] Source # | |||||
Generic MemberStatus | |||||
Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState Associated Types
Methods from :: MemberStatus -> Rep MemberStatus x Source # to :: Rep MemberStatus x -> MemberStatus Source # | |||||
Show MemberStatus | |||||
DecCBOR MemberStatus | |||||
EncCBOR MemberStatus | |||||
Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState Methods encCBOR :: MemberStatus -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy MemberStatus -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [MemberStatus] -> Size Source # | |||||
Eq MemberStatus | |||||
Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState Methods (==) :: MemberStatus -> MemberStatus -> Bool Source # (/=) :: MemberStatus -> MemberStatus -> Bool Source # | |||||
Ord MemberStatus | |||||
Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState Methods compare :: MemberStatus -> MemberStatus -> Ordering Source # (<) :: MemberStatus -> MemberStatus -> Bool Source # (<=) :: MemberStatus -> MemberStatus -> Bool Source # (>) :: MemberStatus -> MemberStatus -> Bool Source # (>=) :: MemberStatus -> MemberStatus -> Bool Source # max :: MemberStatus -> MemberStatus -> MemberStatus Source # min :: MemberStatus -> MemberStatus -> MemberStatus Source # | |||||
type Rep MemberStatus | |||||
Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState type Rep MemberStatus = D1 ('MetaData "MemberStatus" "Cardano.Ledger.Api.State.Query.CommitteeMembersState" "cardano-ledger-api-1.11.0.0-9852118f7dfe14ab1340be707d67c9317fb07912c1725cb4a7204d287e446e2f" 'False) (C1 ('MetaCons "Active" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Expired" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Unrecognized" 'PrefixI 'False) (U1 :: Type -> Type))) |
queryAccountState :: ConwayEraOnwards era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch AccountState)) Source #
queryCommitteeMembersState :: ConwayEraOnwards era -> Set (Credential 'ColdCommitteeRole) -> Set (Credential 'HotCommitteeRole) -> Set MemberStatus -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch CommitteeMembersState)) Source #
Returns info about committee members filtered by: cold credentials, hot credentials and statuses. If empty sets are passed as filters, then no filtering is done.
queryConstitution :: ConwayEraOnwards era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Constitution (ShelleyLedgerEra era)))) Source #
queryConstitutionHash :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (SafeHash AnchorData))) Source #
Arguments
:: ConwayEraOnwards era | |
-> Set (Credential 'DRepRole) | An empty credentials set means that states for all DReps will be returned |
-> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map (Credential 'DRepRole) DRepState))) |
queryFuturePParams :: ConwayEraOnwards era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Maybe (PParams (ShelleyLedgerEra era))))) Source #
queryGovState :: ConwayEraOnwards era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (GovState (ShelleyLedgerEra era)))) Source #
queryProposals :: ConwayEraOnwards era -> Set GovActionId -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Seq (GovActionState (ShelleyLedgerEra era))))) Source #
queryRatifyState :: ConwayEraOnwards era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (RatifyState (ShelleyLedgerEra era)))) Source #
queryStakePoolDefaultVote :: ConwayEraOnwards era -> KeyHash 'StakePool -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch DefaultVote)) Source #
newtype SystemStart Source #
System start
Slots are counted from the system start.
Constructors
SystemStart | |
Fields |
Instances
FromJSON SystemStart | |||||
Defined in Cardano.Slotting.Time | |||||
ToJSON SystemStart | |||||
Defined in Cardano.Slotting.Time Methods toJSON :: SystemStart -> Value # toEncoding :: SystemStart -> Encoding # toJSONList :: [SystemStart] -> Value # toEncodingList :: [SystemStart] -> Encoding # omitField :: SystemStart -> Bool # | |||||
Generic SystemStart | |||||
Defined in Cardano.Slotting.Time Associated Types
Methods from :: SystemStart -> Rep SystemStart x Source # to :: Rep SystemStart x -> SystemStart Source # | |||||
Show SystemStart | |||||
Defined in Cardano.Slotting.Time | |||||
FromCBOR SystemStart | |||||
Defined in Cardano.Slotting.Time | |||||
ToCBOR SystemStart | |||||
Defined in Cardano.Slotting.Time Methods toCBOR :: SystemStart -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy SystemStart -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SystemStart] -> Size Source # | |||||
DecCBOR SystemStart | |||||
Defined in Cardano.Ledger.Binary.Decoding.DecCBOR | |||||
EncCBOR SystemStart | |||||
Defined in Cardano.Ledger.Binary.Encoding.EncCBOR Methods encCBOR :: SystemStart -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy SystemStart -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [SystemStart] -> Size Source # | |||||
Eq SystemStart | |||||
Defined in Cardano.Slotting.Time Methods (==) :: SystemStart -> SystemStart -> Bool Source # (/=) :: SystemStart -> SystemStart -> Bool Source # | |||||
NoThunks SystemStart | |||||
Defined in Cardano.Slotting.Time Methods noThunks :: Context -> SystemStart -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> SystemStart -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy SystemStart -> String # | |||||
Serialise SystemStart | |||||
Defined in Cardano.Slotting.Time Methods encode :: SystemStart -> Encoding decode :: Decoder s SystemStart encodeList :: [SystemStart] -> Encoding decodeList :: Decoder s [SystemStart] | |||||
type Rep SystemStart | |||||
Defined in Cardano.Slotting.Time type Rep SystemStart = D1 ('MetaData "SystemStart" "Cardano.Slotting.Time" "cardano-slotting-0.2.0.0-1062762da5e24b3256026b7bf7ed7ea570deea61ae8ec963e4334bb658f0121b" 'True) (C1 ('MetaCons "SystemStart" 'PrefixI 'True) (S1 ('MetaSel ('Just "getSystemStart") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UTCTime))) |
slotToEpoch :: SlotNo -> EraHistory -> Either PastHorizonException (EpochNo, SlotsInEpoch, SlotsToEpochEnd) Source #
data QueryInShelleyBasedEra era result where Source #
Constructors
QueryEpoch :: forall era. QueryInShelleyBasedEra era EpochNo | |
QueryGenesisParameters :: forall era. QueryInShelleyBasedEra era (GenesisParameters ShelleyEra) | |
QueryProtocolParameters :: forall era. QueryInShelleyBasedEra era (PParams (ShelleyLedgerEra era)) | |
QueryStakeDistribution :: forall era. QueryInShelleyBasedEra era (Map (Hash StakePoolKey) Rational) | |
QueryUTxO :: forall era. QueryUTxOFilter -> QueryInShelleyBasedEra era (UTxO era) | |
QueryStakeAddresses :: forall era. Set StakeCredential -> NetworkId -> QueryInShelleyBasedEra era (Map StakeAddress Coin, Map StakeAddress PoolId) | |
QueryStakePools :: forall era. QueryInShelleyBasedEra era (Set PoolId) | |
QueryStakePoolParameters :: forall era. Set PoolId -> QueryInShelleyBasedEra era (Map PoolId StakePoolParameters) | |
QueryDebugLedgerState :: forall era. QueryInShelleyBasedEra era (SerialisedDebugLedgerState era) | |
QueryProtocolState :: forall era. QueryInShelleyBasedEra era (ProtocolState era) | |
QueryCurrentEpochState :: forall era. QueryInShelleyBasedEra era (SerialisedCurrentEpochState era) | |
QueryPoolState :: forall era. Maybe (Set PoolId) -> QueryInShelleyBasedEra era (SerialisedPoolState era) | |
QueryPoolDistribution :: forall era. Maybe (Set PoolId) -> QueryInShelleyBasedEra era (SerialisedPoolDistribution era) | |
QueryStakeSnapshot :: forall era. Maybe (Set PoolId) -> QueryInShelleyBasedEra era (SerialisedStakeSnapshots era) | |
QueryStakeDelegDeposits :: forall era. Set StakeCredential -> QueryInShelleyBasedEra era (Map StakeCredential Coin) | |
QueryAccountState :: forall era. QueryInShelleyBasedEra era AccountState | |
QueryConstitution :: forall era. QueryInShelleyBasedEra era (Constitution (ShelleyLedgerEra era)) | |
QueryGovState :: forall era. QueryInShelleyBasedEra era (GovState (ShelleyLedgerEra era)) | |
QueryRatifyState :: forall era. QueryInShelleyBasedEra era (RatifyState (ShelleyLedgerEra era)) | |
QueryFuturePParams :: forall era. QueryInShelleyBasedEra era (Maybe (PParams (ShelleyLedgerEra era))) | |
QueryDRepState :: forall era. Set (Credential 'DRepRole) -> QueryInShelleyBasedEra era (Map (Credential 'DRepRole) DRepState) | |
QueryDRepStakeDistr :: forall era. Set DRep -> QueryInShelleyBasedEra era (Map DRep Coin) | |
QuerySPOStakeDistr :: forall era. Set (KeyHash 'StakePool) -> QueryInShelleyBasedEra era (Map (KeyHash 'StakePool) Coin) | |
QueryCommitteeMembersState :: forall era. Set (Credential 'ColdCommitteeRole) -> Set (Credential 'HotCommitteeRole) -> Set MemberStatus -> QueryInShelleyBasedEra era CommitteeMembersState | |
QueryStakeVoteDelegatees :: forall era. Set StakeCredential -> QueryInShelleyBasedEra era (Map StakeCredential DRep) | |
QueryProposals :: forall era. Set GovActionId -> QueryInShelleyBasedEra era (Seq (GovActionState (ShelleyLedgerEra era))) | |
QueryLedgerPeerSnapshot :: forall era. QueryInShelleyBasedEra era (Serialised LedgerPeerSnapshot) | |
QueryStakePoolDefaultVote :: forall era. KeyHash 'StakePool -> QueryInShelleyBasedEra era DefaultVote |
Instances
Show (QueryInShelleyBasedEra era result) Source # | |
Defined in Cardano.Api.Query.Internal.Type.QueryInMode |
newtype StakeSnapshot era Source #
Constructors
StakeSnapshot StakeSnapshots |
data QueryInMode result where Source #
Constructors
QueryCurrentEra :: QueryInMode AnyCardanoEra | |
QueryInEra :: forall era result1. QueryInEra era result1 -> QueryInMode (Either EraMismatch result1) | |
QueryEraHistory :: QueryInMode EraHistory | |
QuerySystemStart :: QueryInMode SystemStart | |
QueryChainBlockNo :: QueryInMode (WithOrigin BlockNo) | |
QueryChainPoint :: QueryInMode ChainPoint | |
QueryLedgerConfig :: QueryInMode (HardForkLedgerConfig (CardanoEras StandardCrypto)) |
Instances
Show (QueryInMode result) Source # | |
Defined in Cardano.Api.Query.Internal.Type.QueryInMode |
newtype CurrentEpochState era Source #
Constructors
CurrentEpochState (EpochState (ShelleyLedgerEra era)) |
newtype ProtocolState era Source #
Constructors
ProtocolState (Serialised (ChainDepState (ConsensusProtocol era))) |
newtype SerialisedCurrentEpochState era Source #
Constructors
SerialisedCurrentEpochState (Serialised (EpochState (ShelleyLedgerEra era))) |
newtype SerialisedPoolDistribution era Source #
Constructors
SerialisedPoolDistribution (Serialised (PoolDistr StandardCrypto)) |
decodeCurrentEpochState :: ShelleyBasedEra era -> SerialisedCurrentEpochState era -> Either DecoderError (CurrentEpochState era) Source #
decodePoolDistribution :: ShelleyBasedEra era -> SerialisedPoolDistribution era -> Either DecoderError (PoolDistribution era) Source #
decodeProtocolState :: FromCBOR (ChainDepState (ConsensusProtocol era)) => ProtocolState era -> Either (ByteString, DecoderError) (ChainDepState (ConsensusProtocol era)) Source #
data QueryInEra era result where Source #
Constructors
QueryByronUpdateState :: QueryInEra ByronEra ByronUpdateState | |
QueryInShelleyBasedEra :: forall era result. ShelleyBasedEra era -> QueryInShelleyBasedEra era result -> QueryInEra era result |
Instances
Show (QueryInEra era result) Source # | |
Defined in Cardano.Api.Query.Internal.Type.QueryInMode |
data EraHistory where Source #
Constructors
EraHistory :: forall (xs :: [Type]). CardanoBlock StandardCrypto ~ HardForkBlock xs => Interpreter xs -> EraHistory |
Instances
HasTypeProxy EraHistory Source # | |||||
Defined in Cardano.Api.Query.Internal.Type.QueryInMode Associated Types
Methods proxyToAsType :: Proxy EraHistory -> AsType EraHistory Source # | |||||
SerialiseAsCBOR EraHistory Source # | |||||
Defined in Cardano.Api.Query.Internal.Type.QueryInMode Methods serialiseToCBOR :: EraHistory -> ByteString Source # deserialiseFromCBOR :: AsType EraHistory -> ByteString -> Either DecoderError EraHistory Source # | |||||
HasTextEnvelope EraHistory Source # | The | ||||
Defined in Cardano.Api.Query.Internal.Type.QueryInMode | |||||
data AsType EraHistory Source # | |||||
Defined in Cardano.Api.Query.Internal.Type.QueryInMode |
getProgress :: SlotNo -> EraHistory -> Either PastHorizonException (RelativeTime, SlotLength) Source #
data QueryUTxOFilter Source #
Getting the whole UTxO is obviously not efficient since the result can be huge. Filtering by address is also not efficient because it requires a linear search.
The QueryUTxOFilterByTxIn
is efficient since it fits with the structure of
the UTxO (which is indexed by TxIn
).
Constructors
QueryUTxOWhole | O(n) time and space for utxo size n |
QueryUTxOByAddress (Set AddressAny) | O(n) time, O(m) space for utxo size n, and address set size m |
QueryUTxOByTxIn (Set TxIn) | O(m log n) time, O(m) space for utxo size n, and address set size m |
Instances
Show QueryUTxOFilter Source # | |
Defined in Cardano.Api.Query.Internal.Type.QueryInMode | |
Eq QueryUTxOFilter Source # | |
Defined in Cardano.Api.Query.Internal.Type.QueryInMode Methods (==) :: QueryUTxOFilter -> QueryUTxOFilter -> Bool Source # (/=) :: QueryUTxOFilter -> QueryUTxOFilter -> Bool Source # |
data UTxOInAnyEra where Source #
Constructors
UTxOInAnyEra :: forall era. CardanoEra era -> UTxO era -> UTxOInAnyEra |
Instances
toConsensusQuery :: CardanoBlock StandardCrypto ~ block => QueryInMode result -> Some (Query block) Source #
fromConsensusQueryResult :: (HasCallStack, CardanoBlock StandardCrypto ~ block) => QueryInMode result -> Query block result' -> result' -> result Source #
newtype SerialisedDebugLedgerState era Source #
Constructors
SerialisedDebugLedgerState (Serialised (NewEpochState (ShelleyLedgerEra era))) |
newtype DebugLedgerState era Source #
Constructors
DebugLedgerState | |
Fields |
Instances
IsShelleyBasedEra era => ToJSON (DebugLedgerState era) Source # | |
Defined in Cardano.Api.Query.Internal.Type.DebugLedgerState Methods toJSON :: DebugLedgerState era -> Value # toEncoding :: DebugLedgerState era -> Encoding # toJSONList :: [DebugLedgerState era] -> Value # toEncodingList :: [DebugLedgerState era] -> Encoding # omitField :: DebugLedgerState era -> Bool # | |
IsShelleyBasedEra era => FromCBOR (DebugLedgerState era) Source # | |
decodeDebugLedgerState :: FromCBOR (DebugLedgerState era) => SerialisedDebugLedgerState era -> Either (ByteString, DecoderError) (DebugLedgerState era) Source #
newtype SerialisedPoolState era Source #
Constructors
SerialisedPoolState (Serialised (PState (ShelleyLedgerEra era))) |
decodePoolState :: (Era (ShelleyLedgerEra era), DecCBOR (PState (ShelleyLedgerEra era))) => SerialisedPoolState era -> Either DecoderError (PoolState era) Source #
newtype SerialisedStakeSnapshots era Source #
Constructors
SerialisedStakeSnapshots (Serialised StakeSnapshots) |
decodeStakeSnapshot :: SerialisedStakeSnapshots era -> Either DecoderError (StakeSnapshot era) Source #
newtype LedgerEpochInfo Source #
Constructors
LedgerEpochInfo | |
Fields |
newtype SlotsInEpoch Source #
Constructors
SlotsInEpoch Word64 |
newtype SlotsToEpochEnd Source #
Constructors
SlotsToEpochEnd Word64 |
getSlotForRelativeTime :: RelativeTime -> EraHistory -> Either PastHorizonException SlotNo Source #
Returns the slot number for provided relative time from SystemStart
decodeBigLedgerPeerSnapshot :: Serialised LedgerPeerSnapshot -> Either (ByteString, DecoderError) LedgerPeerSnapshot Source #
data QueryConvenienceError Source #
Constructors
AcqFailure AcquiringFailure | |
QueryEraMismatch EraMismatch | |
ByronEraNotSupported | |
QceUnsupportedNtcVersion !UnsupportedNtcVersionError | |
QceUnexpectedException !SomeException |
Instances
newtype TxCurrentTreasuryValue Source #
Constructors
TxCurrentTreasuryValue | |
Fields |
Instances
determineEra :: LocalNodeConnectInfo -> ExceptT AcquiringFailure IO AnyCardanoEra Source #
Query the node to determine which era it is in.
executeQueryCardanoMode :: SocketPath -> NetworkId -> QueryInMode (Either EraMismatch result) -> ExceptT QueryConvenienceError IO result Source #
Execute a query against the local node. The local node must be in CardanoMode.
executeQueryAnyMode :: LocalNodeConnectInfo -> QueryInMode (Either EraMismatch result) -> ExceptT QueryConvenienceError IO result Source #
Execute a query against the local node in any mode.
queryStateForBalancedTx :: CardanoEra era -> [TxIn] -> [Certificate era] -> LocalStateQueryExpr block point QueryInMode r IO (Either QueryConvenienceError (UTxO era, LedgerProtocolParameters era, EraHistory, SystemStart, Set PoolId, Map StakeCredential Coin, Map (Credential 'DRepRole) Coin, Maybe (Featured ConwayEraOnwards era TxCurrentTreasuryValue))) Source #
A convenience function to query the relevant information, from the local node, for Cardano.Api.Tx.Internal.Convenience.constructBalancedTx
queryChainBlockNo :: LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (WithOrigin BlockNo)) Source #
queryChainPoint :: LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError ChainPoint) Source #
queryCurrentEpochState :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (SerialisedCurrentEpochState era))) Source #
queryCurrentEra :: LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError AnyCardanoEra) Source #
queryDebugLedgerState :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (SerialisedDebugLedgerState era))) Source #
queryEpoch :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch EpochNo)) Source #
queryEraHistory :: LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError EraHistory) Source #
queryGenesisParameters :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (GenesisParameters ShelleyEra))) Source #
queryPoolDistribution :: BabbageEraOnwards era -> Maybe (Set PoolId) -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (SerialisedPoolDistribution era))) Source #
queryPoolState :: BabbageEraOnwards era -> Maybe (Set PoolId) -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (SerialisedPoolState era))) Source #
queryProtocolParameters :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (PParams (ShelleyLedgerEra era)))) Source #
queryProtocolState :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (ProtocolState era))) Source #
queryStakeAddresses :: ShelleyBasedEra era -> Set StakeCredential -> NetworkId -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map StakeAddress Coin, Map StakeAddress PoolId))) Source #
queryStakeDelegDeposits :: BabbageEraOnwards era -> Set StakeCredential -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map StakeCredential Coin))) Source #
queryStakeDistribution :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map (Hash StakePoolKey) Rational))) Source #
queryStakePoolParameters :: ShelleyBasedEra era -> Set PoolId -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map PoolId StakePoolParameters))) Source #
queryStakePools :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Set PoolId))) Source #
queryStakeSnapshot :: BabbageEraOnwards era -> Maybe (Set PoolId) -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (SerialisedStakeSnapshots era))) Source #
querySystemStart :: LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError SystemStart) Source #
queryUtxo :: ShelleyBasedEra era -> QueryUTxOFilter -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (UTxO era))) Source #
queryLedgerPeerSnapshot :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Serialised LedgerPeerSnapshot))) Source #
queryDRepStakeDistribution Source #
Arguments
:: ConwayEraOnwards era | |
-> Set DRep | An empty DRep set means that distributions for all DReps will be returned |
-> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map DRep Coin))) |
querySPOStakeDistribution Source #
Arguments
:: ConwayEraOnwards era | |
-> Set (KeyHash 'StakePool) | An empty SPO key hash set means that distributions for all SPOs will be returned |
-> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map (KeyHash 'StakePool) Coin))) |
queryStakeVoteDelegatees :: ConwayEraOnwards era -> Set StakeCredential -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map StakeCredential DRep))) Source #
queryLedgerConfig :: LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (CardanoLedgerConfig StandardCrypto)) Source #
newtype DelegationsAndRewards Source #
A mapping of Shelley reward accounts to both the stake pool that they delegate to and their reward account balance. TODO: Move to cardano-api
Constructors
DelegationsAndRewards (Map StakeAddress Coin, Map StakeAddress PoolId) |
Instances
FromJSON DelegationsAndRewards Source # | |
Defined in Cardano.Api.Query.Internal.Type.DelegationsAndRewards Methods parseJSON :: Value -> Parser DelegationsAndRewards # parseJSONList :: Value -> Parser [DelegationsAndRewards] # | |
ToJSON DelegationsAndRewards Source # | |
Defined in Cardano.Api.Query.Internal.Type.DelegationsAndRewards Methods toJSON :: DelegationsAndRewards -> Value # toEncoding :: DelegationsAndRewards -> Encoding # toJSONList :: [DelegationsAndRewards] -> Value # toEncodingList :: [DelegationsAndRewards] -> Encoding # omitField :: DelegationsAndRewards -> Bool # | |
Show DelegationsAndRewards Source # | |
Eq DelegationsAndRewards Source # | |
Defined in Cardano.Api.Query.Internal.Type.DelegationsAndRewards Methods (==) :: DelegationsAndRewards -> DelegationsAndRewards -> Bool Source # (/=) :: DelegationsAndRewards -> DelegationsAndRewards -> Bool Source # |
mergeDelegsAndRewards :: DelegationsAndRewards -> [(StakeAddress, Maybe Coin, Maybe PoolId)] Source #
toDebugLedgerStatePair :: KeyValue e a => ShelleyBasedEra era -> DebugLedgerState era -> [a] Source #
toLedgerUTxO :: ShelleyBasedEra era -> UTxO era -> UTxO (ShelleyLedgerEra era) Source #
fromLedgerUTxO :: ShelleyBasedEra era -> UTxO (ShelleyLedgerEra era) -> UTxO era Source #
Consensus
module Cardano.Api.Consensus
Block
module Cardano.Api.Block
Ledger state
module Cardano.Api.LedgerState
Protocol parameters
Cryptographic key interface
module Cardano.Api.Key
module Cardano.Api.Hash
Transaction building
module Cardano.Api.Tx
Plutus
module Cardano.Api.Plutus
Value
module Cardano.Api.Value
Serialisation
module Cardano.Api.Serialise.Bech32
module Cardano.Api.Serialise.Cip129
module Cardano.Api.Serialise.Cbor
module Cardano.Api.Serialise.Json
module Cardano.Api.Serialise.Raw
Supporting modules
module Cardano.Api.Error
module Cardano.Api.Monad.Error
module Cardano.Api.Pretty
module Cardano.Api.IO