cardano-api:internal
Safe HaskellNone
LanguageHaskell2010

Cardano.Api.IPC

Description

Node IPC protocols

Synopsis

Node interaction

Operations that involve talking to a local Cardano node.

connectToLocalNode :: MonadIO m => LocalNodeConnectInfo -> LocalNodeClientProtocolsInMode -> m () Source #

Establish a connection to a local node and execute the given set of protocol handlers.

connectToLocalNodeWithVersion :: MonadIO m => LocalNodeConnectInfo -> (NodeToClientVersion -> LocalNodeClientProtocolsInMode) -> m () Source #

Establish a connection to a local node and execute the given set of protocol handlers parameterized on the negotiated node-to-client protocol version.

data LocalNodeClientParams where Source #

This type defines the boundary between the mode-parametrised style used in this API and the block-parametrised style used by the underlying network and consensus libraries.

This interface itself is in the block-parametrised style, with the block type itself being an hidden/existential type.

It bundles together all the necessary class instances, the consensus protocol client identifier, and the set of client side mini-protocol handlers for the node-to-client protocol.

mkLocalNodeClientParams :: ConsensusModeParams -> (NodeToClientVersion -> LocalNodeClientProtocolsInMode) -> LocalNodeClientParams Source #

Convert from the mode-parametrised style to the block-parametrised style.

data LocalNodeClientProtocols block point tip slot tx txid txerr (query :: Type -> Type) (m :: Type -> Type) Source #

The protocols we can use with a local node. Use in conjunction with connectToLocalNode.

These protocols use the types from the rest of this API. The conversion to/from the types used by the underlying wire formats is handled by connectToLocalNode.

data LocalChainSyncClient block point tip (m :: Type -> Type) Source #

Modes

TODO move to Cardano.Api

data ConsensusModeParams where Source #

The consensus-mode-specific parameters needed to connect to a local node that is using each consensus mode.

It is in fact only the Byron era that requires extra parameters, but this is of course inherited by the CardanoMode that uses the Byron era. The reason this parameter is needed stems from unfortunate design decisions from the legacy Byron era. The slots per epoch are needed to be able to decode epoch boundary blocks from the Byron era.

It is possible in future that we may be able to eliminate this parameter by discovering it from the node during the initial handshake.

newtype EpochSlots Source #

The number of slots per epoch.

Constructors

EpochSlots 

Fields

Instances

Instances details
Data EpochSlots 
Instance details

Defined in Cardano.Chain.Slotting.EpochSlots

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EpochSlots -> c EpochSlots Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EpochSlots Source #

toConstr :: EpochSlots -> Constr Source #

dataTypeOf :: EpochSlots -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EpochSlots) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EpochSlots) Source #

gmapT :: (forall b. Data b => b -> b) -> EpochSlots -> EpochSlots Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EpochSlots -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EpochSlots -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> EpochSlots -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EpochSlots -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EpochSlots -> m EpochSlots Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EpochSlots -> m EpochSlots Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EpochSlots -> m EpochSlots Source #

Generic EpochSlots 
Instance details

Defined in Cardano.Chain.Slotting.EpochSlots

Associated Types

type Rep EpochSlots 
Instance details

Defined in Cardano.Chain.Slotting.EpochSlots

type Rep EpochSlots = D1 ('MetaData "EpochSlots" "Cardano.Chain.Slotting.EpochSlots" "cardano-ledger-byron-1.0.1.0-ee1397b2c0d43b85f835fc34d15006ff5cedf035a94d0c96915a880ab6ff4d0e" 'True) (C1 ('MetaCons "EpochSlots" 'PrefixI 'True) (S1 ('MetaSel ('Just "unEpochSlots") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))
Read EpochSlots 
Instance details

Defined in Cardano.Chain.Slotting.EpochSlots

Show EpochSlots 
Instance details

Defined in Cardano.Chain.Slotting.EpochSlots

FromCBOR EpochSlots 
Instance details

Defined in Cardano.Chain.Slotting.EpochSlots

ToCBOR EpochSlots 
Instance details

Defined in Cardano.Chain.Slotting.EpochSlots

DecCBOR EpochSlots 
Instance details

Defined in Cardano.Chain.Slotting.EpochSlots

EncCBOR EpochSlots 
Instance details

Defined in Cardano.Chain.Slotting.EpochSlots

Buildable EpochSlots 
Instance details

Defined in Cardano.Chain.Slotting.EpochSlots

Methods

build :: EpochSlots -> Builder

Eq EpochSlots 
Instance details

Defined in Cardano.Chain.Slotting.EpochSlots

Ord EpochSlots 
Instance details

Defined in Cardano.Chain.Slotting.EpochSlots

NoThunks EpochSlots 
Instance details

Defined in Cardano.Chain.Slotting.EpochSlots

Methods

noThunks :: Context -> EpochSlots -> IO (Maybe ThunkInfo) #

wNoThunks :: Context -> EpochSlots -> IO (Maybe ThunkInfo) #

showTypeOf :: Proxy EpochSlots -> String #

type Rep EpochSlots 
Instance details

Defined in Cardano.Chain.Slotting.EpochSlots

type Rep EpochSlots = D1 ('MetaData "EpochSlots" "Cardano.Chain.Slotting.EpochSlots" "cardano-ledger-byron-1.0.1.0-ee1397b2c0d43b85f835fc34d15006ff5cedf035a94d0c96915a880ab6ff4d0e" 'True) (C1 ('MetaCons "EpochSlots" 'PrefixI 'True) (S1 ('MetaSel ('Just "unEpochSlots") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))

Chain sync protocol

newtype ChainSyncClient header point tip (m :: Type -> Type) a Source #

A chain sync protocol client, on top of some effect m. The first choice of request is within that m.

Constructors

ChainSyncClient 

Fields

newtype ChainSyncClientPipelined header point tip (m :: Type -> Type) a Source #

Pipelined chain sync client. It can only pipeline MsgRequestNext messages, while the MsgFindIntersect are non pipelined. This has a penalty cost of an RTT, but they are sent relatively seldom and their response might impact how many messages one would like to pipeline. It also simplifies the receiver callback.

Constructors

ChainSyncClientPipelined 

Fields

data BlockInMode where Source #

A Block in one of the eras. TODO Rename this to BlockInEra

Constructors

BlockInMode :: forall era. CardanoEra era -> Block era -> BlockInMode 

Instances

Instances details
Show BlockInMode Source # 
Instance details

Defined in Cardano.Api.Block

Local tx submission

newtype LocalTxSubmissionClient tx reject (m :: Type -> Type) a Source #

data TxInMode where Source #

A Tx in one of the eras supported by a given protocol mode.

For multi-era modes such as the CardanoMode this type is a sum of the different transaction types for all the eras. It is used in the LocalTxSubmission protocol.

Constructors

TxInMode :: forall era. ShelleyBasedEra era -> Tx era -> TxInMode

Shelley based transactions.

TxInByronSpecial :: GenTx ByronBlock -> TxInMode

Legacy Byron transactions and things we can post to the chain which are not actually transactions. This covers: update proposals, votes and delegation certs.

Instances

Instances details
Show TxInMode Source # 
Instance details

Defined in Cardano.Api.InMode

data TxValidationError era Source #

The transaction validations errors that can occur from trying to submit a transaction to a local node. The errors are specific to an era.

Instances

Instances details
ToJSON (TxValidationError era) Source # 
Instance details

Defined in Cardano.Api.InMode

Methods

toJSON :: TxValidationError era -> Value #

toEncoding :: TxValidationError era -> Encoding #

toJSONList :: [TxValidationError era] -> Value #

toEncodingList :: [TxValidationError era] -> Encoding #

omitField :: TxValidationError era -> Bool #

Generic (TxValidationError era) Source # 
Instance details

Defined in Cardano.Api.InMode

Associated Types

type Rep (TxValidationError era) 
Instance details

Defined in Cardano.Api.InMode

type Rep (TxValidationError era) = D1 ('MetaData "TxValidationError" "Cardano.Api.InMode" "cardano-api-9.3.0.0-inplace-internal" 'False) (C1 ('MetaCons "ByronTxValidationError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ApplyTxErr ByronBlock))) :+: C1 ('MetaCons "ShelleyTxValidationError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ShelleyBasedEra era)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ApplyTxErr (ShelleyBlock (ConsensusProtocol era) (ShelleyLedgerEra era))))))
Show (TxValidationError era) Source # 
Instance details

Defined in Cardano.Api.InMode

type Rep (TxValidationError era) Source # 
Instance details

Defined in Cardano.Api.InMode

type Rep (TxValidationError era) = D1 ('MetaData "TxValidationError" "Cardano.Api.InMode" "cardano-api-9.3.0.0-inplace-internal" 'False) (C1 ('MetaCons "ByronTxValidationError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ApplyTxErr ByronBlock))) :+: C1 ('MetaCons "ShelleyTxValidationError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ShelleyBasedEra era)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ApplyTxErr (ShelleyBlock (ConsensusProtocol era) (ShelleyLedgerEra era))))))

data SubmitResult reason Source #

Isomorphic with Maybe but with a name that better describes its purpose and usage.

Constructors

SubmitSuccess 
SubmitFail reason 

Instances

Instances details
Functor SubmitResult 
Instance details

Defined in Ouroboros.Network.Protocol.LocalTxSubmission.Type

Methods

fmap :: (a -> b) -> SubmitResult a -> SubmitResult b Source #

(<$) :: a -> SubmitResult b -> SubmitResult a Source #

Eq reason => Eq (SubmitResult reason) 
Instance details

Defined in Ouroboros.Network.Protocol.LocalTxSubmission.Type

Methods

(==) :: SubmitResult reason -> SubmitResult reason -> Bool Source #

(/=) :: SubmitResult reason -> SubmitResult reason -> Bool Source #

Local state query

newtype LocalStateQueryClient block point (query :: Type -> Type) (m :: Type -> Type) a Source #

Constructors

LocalStateQueryClient 

Fields

data AcquiringFailure Source #

Establish a connection to a node and execute a single query using the local state query protocol.

data QueryInEra era result where Source #

Constructors

QueryByronUpdateState :: QueryInEra ByronEra ByronUpdateState 
QueryInShelleyBasedEra :: forall era result. ShelleyBasedEra era -> QueryInShelleyBasedEra era result -> QueryInEra era result 

Instances

Instances details
Show (QueryInEra era result) Source # 
Instance details

Defined in Cardano.Api.Query

Methods

showsPrec :: Int -> QueryInEra era result -> ShowS Source #

show :: QueryInEra era result -> String Source #

showList :: [QueryInEra era result] -> ShowS Source #

NodeToClientVersionOf (QueryInEra era result) Source # 
Instance details

Defined in Cardano.Api.Query

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)) 
QueryProtocolParametersUpdate :: forall era. QueryInShelleyBasedEra era (Map (Hash GenesisKey) ProtocolParametersUpdate) 
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)) 
QueryDRepState :: forall era. Set (Credential 'DRepRole StandardCrypto) -> QueryInShelleyBasedEra era (Map (Credential 'DRepRole StandardCrypto) (DRepState StandardCrypto)) 
QueryDRepStakeDistr :: forall era. Set (DRep StandardCrypto) -> QueryInShelleyBasedEra era (Map (DRep StandardCrypto) Coin) 
QuerySPOStakeDistr :: forall era. Set (KeyHash 'StakePool StandardCrypto) -> QueryInShelleyBasedEra era (Map (KeyHash 'StakePool StandardCrypto) Coin) 
QueryCommitteeMembersState :: forall era. Set (Credential 'ColdCommitteeRole StandardCrypto) -> Set (Credential 'HotCommitteeRole StandardCrypto) -> Set MemberStatus -> QueryInShelleyBasedEra era (CommitteeMembersState StandardCrypto) 
QueryStakeVoteDelegatees :: forall era. Set StakeCredential -> QueryInShelleyBasedEra era (Map StakeCredential (DRep StandardCrypto)) 

Instances

Instances details
Show (QueryInShelleyBasedEra era result) Source # 
Instance details

Defined in Cardano.Api.Query

NodeToClientVersionOf (QueryInShelleyBasedEra era result) Source #

Mapping for queries in Shelley-based eras returning minimal node-to-client protocol versions. More information about queries versioning can be found: * https://ouroboros-network.cardano.intersectmbo.org/ouroboros-network/Ouroboros-Network-NodeToClient.html#t:NodeToClientVersion * https://ouroboros-consensus.cardano.intersectmbo.org/docs/for-developers/QueryVersioning/#implementation

Instance details

Defined in Cardano.Api.Query

Local tx monitoring

newtype LocalTxMonitorClient txid tx slot (m :: Type -> Type) a Source #

A tx monitor client, on top of some effect m.

Constructors

LocalTxMonitorClient 

Fields

data LocalTxMonitoringQuery Source #

Constructors

LocalTxMonitoringQueryTx TxIdInMode

Query if a particular tx exists in the mempool. Note that, the absence of a transaction does not imply anything about how the transaction was processed: it may have been dropped, or inserted in a block.

LocalTxMonitoringSendNextTx

The mempool is modeled as an ordered list of transactions and thus, can be traversed linearly. LocalTxMonitoringSendNextTx requests the next transaction from the current list. This must be a transaction that was not previously sent to the client for this particular snapshot.

LocalTxMonitoringMempoolInformation

Ask the server about the current mempool's capacity and sizes. This is fixed in a given snapshot.

data LocalTxMonitoringResult Source #

Constructors

LocalTxMonitoringTxExists TxId SlotNo

Slot number at which the mempool snapshot was taken

LocalTxMonitoringTxDoesNotExist TxId SlotNo

Slot number at which the mempool snapshot was taken

LocalTxMonitoringNextTx (Maybe TxInMode) SlotNo

Slot number at which the mempool snapshot was taken

LocalTxMonitoringMempoolSizeAndCapacity MempoolSizeAndCapacity SlotNo

Slot number at which the mempool snapshot was taken

data MempoolSizeAndCapacity Source #

Describes the MemPool sizes and capacity for a given snapshot.

Constructors

MempoolSizeAndCapacity 

Fields

  • capacityInBytes :: !Word32

    The maximum capacity of the mempool. Note that this may dynamically change when the ledger state is updated.

  • sizeInBytes :: !Word32

    The summed byte size of all the transactions in the mempool.

  • numberOfTxs :: !Word32

    The number of transactions in the mempool

Instances

Instances details
Generic MempoolSizeAndCapacity 
Instance details

Defined in Ouroboros.Network.Protocol.LocalTxMonitor.Type

Associated Types

type Rep MempoolSizeAndCapacity 
Instance details

Defined in Ouroboros.Network.Protocol.LocalTxMonitor.Type

type Rep MempoolSizeAndCapacity = D1 ('MetaData "MempoolSizeAndCapacity" "Ouroboros.Network.Protocol.LocalTxMonitor.Type" "ouroboros-network-protocols-0.10.0.2-9769ea296feec0abc192c54a9ae1893d82ab7fe37c8542f06de6a6cb48509d25" 'False) (C1 ('MetaCons "MempoolSizeAndCapacity" 'PrefixI 'True) (S1 ('MetaSel ('Just "capacityInBytes") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word32) :*: (S1 ('MetaSel ('Just "sizeInBytes") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word32) :*: S1 ('MetaSel ('Just "numberOfTxs") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word32))))
Show MempoolSizeAndCapacity 
Instance details

Defined in Ouroboros.Network.Protocol.LocalTxMonitor.Type

NFData MempoolSizeAndCapacity 
Instance details

Defined in Ouroboros.Network.Protocol.LocalTxMonitor.Type

Eq MempoolSizeAndCapacity 
Instance details

Defined in Ouroboros.Network.Protocol.LocalTxMonitor.Type

type Rep MempoolSizeAndCapacity 
Instance details

Defined in Ouroboros.Network.Protocol.LocalTxMonitor.Type

type Rep MempoolSizeAndCapacity = D1 ('MetaData "MempoolSizeAndCapacity" "Ouroboros.Network.Protocol.LocalTxMonitor.Type" "ouroboros-network-protocols-0.10.0.2-9769ea296feec0abc192c54a9ae1893d82ab7fe37c8542f06de6a6cb48509d25" 'False) (C1 ('MetaCons "MempoolSizeAndCapacity" 'PrefixI 'True) (S1 ('MetaSel ('Just "capacityInBytes") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word32) :*: (S1 ('MetaSel ('Just "sizeInBytes") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word32) :*: S1 ('MetaSel ('Just "numberOfTxs") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word32))))

data EraHistory where Source #

Constructors

EraHistory :: forall (xs :: [Type]). CardanoBlock StandardCrypto ~ HardForkBlock xs => Interpreter xs -> EraHistory 

Common queries

Helpers

data NodeToClientVersion Source #

Enumeration of node to client protocol versions.

Constructors

NodeToClientV_9

enabled CardanoNodeToClientVersion7, i.e., Alonzo

NodeToClientV_10

added GetChainBlockNo and GetChainPoint queries

NodeToClientV_11

added GetRewardInfoPools Block query

NodeToClientV_12

added LocalTxMonitor mini-protocol

NodeToClientV_13

enabled CardanoNodeToClientVersion9, i.e., Babbage

NodeToClientV_14

added GetPoolDistr, GetPoolState, GetSnapshots

NodeToClientV_15

added query to NodeToClientVersionData

NodeToClientV_16

add ImmutableTip to LocalStateQuery, enabled CardanoNodeToClientVersion11, i.e., Conway and GetStakeDelegDeposits.

NodeToClientV_17

add GetProposals and GetRatifyState queries

Instances

Instances details
Bounded NodeToClientVersion 
Instance details

Defined in Ouroboros.Network.NodeToClient.Version

Enum NodeToClientVersion 
Instance details

Defined in Ouroboros.Network.NodeToClient.Version

Generic NodeToClientVersion 
Instance details

Defined in Ouroboros.Network.NodeToClient.Version

Associated Types

type Rep NodeToClientVersion 
Instance details

Defined in Ouroboros.Network.NodeToClient.Version

type Rep NodeToClientVersion = D1 ('MetaData "NodeToClientVersion" "Ouroboros.Network.NodeToClient.Version" "ouroboros-network-api-0.9.0.1-d476b713cf1261d3b9f399401dd5ff15dc41c995d5afec7cfd32ed3c7184b91c" 'False) (((C1 ('MetaCons "NodeToClientV_9" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NodeToClientV_10" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NodeToClientV_11" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NodeToClientV_12" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "NodeToClientV_13" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NodeToClientV_14" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NodeToClientV_15" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NodeToClientV_16" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NodeToClientV_17" 'PrefixI 'False) (U1 :: Type -> Type)))))
Show NodeToClientVersion 
Instance details

Defined in Ouroboros.Network.NodeToClient.Version

NFData NodeToClientVersion 
Instance details

Defined in Ouroboros.Network.NodeToClient.Version

Eq NodeToClientVersion 
Instance details

Defined in Ouroboros.Network.NodeToClient.Version

Ord NodeToClientVersion 
Instance details

Defined in Ouroboros.Network.NodeToClient.Version

MonadReader NodeToClientVersion (LocalStateQueryExpr block point query r m) Source # 
Instance details

Defined in Cardano.Api.IPC.Monad

Methods

ask :: LocalStateQueryExpr block point query r m NodeToClientVersion Source #

local :: (NodeToClientVersion -> NodeToClientVersion) -> LocalStateQueryExpr block point query r m a -> LocalStateQueryExpr block point query r m a Source #

reader :: (NodeToClientVersion -> a) -> LocalStateQueryExpr block point query r m a Source #

type Rep NodeToClientVersion 
Instance details

Defined in Ouroboros.Network.NodeToClient.Version

type Rep NodeToClientVersion = D1 ('MetaData "NodeToClientVersion" "Ouroboros.Network.NodeToClient.Version" "ouroboros-network-api-0.9.0.1-d476b713cf1261d3b9f399401dd5ff15dc41c995d5afec7cfd32ed3c7184b91c" 'False) (((C1 ('MetaCons "NodeToClientV_9" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NodeToClientV_10" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NodeToClientV_11" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NodeToClientV_12" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "NodeToClientV_13" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NodeToClientV_14" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NodeToClientV_15" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NodeToClientV_16" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NodeToClientV_17" 'PrefixI 'False) (U1 :: Type -> Type)))))