Safe Haskell | None |
---|---|
Language | Haskell2010 |
The type of the transaction submission protocol.
This is used to relay transactions between nodes.
Synopsis
- data TxSubmission2 (txid :: k) (tx :: k1) where
- StInit :: forall {k} {k1} (txid :: k) (tx :: k1). TxSubmission2 txid tx
- StIdle :: forall {k} {k1} (txid :: k) (tx :: k1). TxSubmission2 txid tx
- StTxIds :: forall {k} {k1} (txid :: k) (tx :: k1). StBlockingStyle -> TxSubmission2 txid tx
- StTxs :: forall {k} {k1} (txid :: k) (tx :: k1). TxSubmission2 txid tx
- StDone :: forall {k} {k1} (txid :: k) (tx :: k1). TxSubmission2 txid tx
- data family Message ps (st :: ps) (st' :: ps)
- data SingTxSubmission (k2 :: TxSubmission2 txid tx) where
- SingInit :: forall {k} {k1} {txid :: k} {tx :: k1}. SingTxSubmission ('StInit :: TxSubmission2 txid tx)
- SingIdle :: forall {k} {k1} {txid :: k} {tx :: k1}. SingTxSubmission ('StIdle :: TxSubmission2 txid tx)
- SingTxIds :: forall {k} {k1} {txid :: k} {tx :: k1} (stBlocking :: StBlockingStyle). SingBlockingStyle stBlocking -> SingTxSubmission ('StTxIds stBlocking :: TxSubmission2 txid tx)
- SingTxs :: forall {k} {k1} {txid :: k} {tx :: k1}. SingTxSubmission ('StTxs :: TxSubmission2 txid tx)
- SingDone :: forall {k} {k1} {txid :: k} {tx :: k1}. SingTxSubmission ('StDone :: TxSubmission2 txid tx)
- data SingBlockingStyle (k :: StBlockingStyle) where
- data StBlockingStyle where
- data BlockingReplyList (blocking :: StBlockingStyle) a where
- BlockingReply :: forall a. NonEmpty a -> BlockingReplyList 'StBlocking a
- NonBlockingReply :: forall a. [a] -> BlockingReplyList 'StNonBlocking a
- newtype NumTxIdsToAck = NumTxIdsToAck {}
- newtype NumTxIdsToReq = NumTxIdsToReq {}
- newtype SizeInBytes = SizeInBytes {}
Documentation
data TxSubmission2 (txid :: k) (tx :: k1) where Source #
The kind of the transaction-submission protocol, and the types of the states in the protocol state machine.
We describe this protocol using the label "client" for the peer that is submitting transactions, and "server" for the one receiving them. The protocol is however pull based, so it is typically the server that has agency in this protocol. This is the opposite of the chain sync and block fetch protocols, but that makes sense because the information flow is also reversed: submitting transactions rather than receiving headers and blocks.
Because these client/server labels are somewhat confusing in this case, we sometimes clarify by using the terms inbound and outbound. This refers to whether transactions are flowing towards a peer or away, and thus indicates what role the peer is playing.
StInit :: forall {k} {k1} (txid :: k) (tx :: k1). TxSubmission2 txid tx | Initial protocol message. |
StIdle :: forall {k} {k1} (txid :: k) (tx :: k1). TxSubmission2 txid tx | The server (inbound side) has agency; it can either terminate, ask for transaction identifiers or ask for transactions. There is no timeout in this state. |
StTxIds :: forall {k} {k1} (txid :: k) (tx :: k1). StBlockingStyle -> TxSubmission2 txid tx | The client (outbound side) has agency; it must reply with a list of transaction identifiers that it wishes to submit. There are two sub-states for this, for blocking and non-blocking cases. |
StTxs :: forall {k} {k1} (txid :: k) (tx :: k1). TxSubmission2 txid tx | The client (outbound side) has agency; it must reply with the list of transactions. |
StDone :: forall {k} {k1} (txid :: k) (tx :: k1). TxSubmission2 txid tx | Nobody has agency; termination state. |
Instances
data family Message ps (st :: ps) (st' :: ps) #
The messages for this protocol. It is expected to be a GADT that is
indexed by the from
and to
protocol states. That is the protocol state
the message transitions from, and the protocol state it transitions into.
These are the edges of the protocol state transition system.
Instances
(NFData block, NFData point) => NFData (Message (BlockFetch block point) from to) Source # | |
Defined in Ouroboros.Network.Protocol.BlockFetch.Type rnf :: Message (BlockFetch block point) from to -> () # | |
(NFData header, NFData point, NFData tip) => NFData (Message (ChainSync header point tip) from to) Source # | |
Defined in Ouroboros.Network.Protocol.ChainSync.Type | |
NFData (Message KeepAlive from to) Source # | |
Defined in Ouroboros.Network.Protocol.KeepAlive.Type | |
(forall result. NFData (query result), NFData point) => NFData (Message (LocalStateQuery block point query) from to) Source # | |
Defined in Ouroboros.Network.Protocol.LocalStateQuery.Type rnf :: Message (LocalStateQuery block point query) from to -> () # | |
(NFData txid, NFData tx, NFData slot) => NFData (Message (LocalTxMonitor txid tx slot) from to) Source # | |
Defined in Ouroboros.Network.Protocol.LocalTxMonitor.Type rnf :: Message (LocalTxMonitor txid tx slot) from to -> () # | |
(NFData tx, NFData reject) => NFData (Message (LocalTxSubmission tx reject) from to) Source # | |
Defined in Ouroboros.Network.Protocol.LocalTxSubmission.Type rnf :: Message (LocalTxSubmission tx reject) from to -> () # | |
NFData peerAddress => NFData (Message (PeerSharing peerAddress) from to) Source # | |
Defined in Ouroboros.Network.Protocol.PeerSharing.Type rnf :: Message (PeerSharing peerAddress) from to -> () # | |
(NFData txid, NFData tx) => NFData (Message (TxSubmission2 txid tx) from to) Source # | |
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type rnf :: Message (TxSubmission2 txid tx) from to -> () # | |
(Show block, Show point) => Show (Message (BlockFetch block point) from to) Source # | |
Defined in Ouroboros.Network.Protocol.BlockFetch.Type | |
(Show header, Show point, Show tip) => Show (Message (ChainSync header point tip) from to) Source # | |
Show (Message KeepAlive from to) Source # | |
(Show txid, Show tx, Show slot) => Show (Message (LocalTxMonitor txid tx slot) from to) Source # | |
(Show tx, Show reject) => Show (Message (LocalTxSubmission tx reject) from to) Source # | |
Show peer => Show (Message (PeerSharing peer) from to) Source # | |
Defined in Ouroboros.Network.Protocol.PeerSharing.Type | |
(Show txid, Show tx) => Show (Message (TxSubmission2 txid tx) from to) Source # | |
(Eq tx, Eq reject) => Eq (Message (LocalTxSubmission tx reject) from to) Source # | |
Defined in Ouroboros.Network.Protocol.LocalTxSubmission.Type (==) :: Message (LocalTxSubmission tx reject) from to -> Message (LocalTxSubmission tx reject) from to -> Bool # (/=) :: Message (LocalTxSubmission tx reject) from to -> Message (LocalTxSubmission tx reject) from to -> Bool # | |
(Eq txid, Eq tx) => Eq (Message (TxSubmission2 txid tx) from to) Source # | |
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type (==) :: Message (TxSubmission2 txid tx) from to -> Message (TxSubmission2 txid tx) from to -> Bool # (/=) :: Message (TxSubmission2 txid tx) from to -> Message (TxSubmission2 txid tx) from to -> Bool # | |
data Message KeepAlive (from :: KeepAlive) (to :: KeepAlive) Source # | |
data Message (PeerSharing peerAddress) (from :: PeerSharing peerAddress) (to :: PeerSharing peerAddress) Source # | |
Defined in Ouroboros.Network.Protocol.PeerSharing.Type data Message (PeerSharing peerAddress) (from :: PeerSharing peerAddress) (to :: PeerSharing peerAddress) where
| |
data Message (LocalStateQuery block point query) (from :: LocalStateQuery block point query) (to :: LocalStateQuery block point query) Source # | |
Defined in Ouroboros.Network.Protocol.LocalStateQuery.Type data Message (LocalStateQuery block point query) (from :: LocalStateQuery block point query) (to :: LocalStateQuery block point query) where
| |
data Message (BlockFetch block point) (from :: BlockFetch block point) (to :: BlockFetch block point) Source # | |
Defined in Ouroboros.Network.Protocol.BlockFetch.Type data Message (BlockFetch block point) (from :: BlockFetch block point) (to :: BlockFetch block point) where
| |
data Message (LocalTxSubmission tx reject) (from :: LocalTxSubmission tx reject) (to :: LocalTxSubmission tx reject) Source # | |
Defined in Ouroboros.Network.Protocol.LocalTxSubmission.Type data Message (LocalTxSubmission tx reject) (from :: LocalTxSubmission tx reject) (to :: LocalTxSubmission tx reject) where
| |
data Message (TxSubmission2 txid tx) (from :: TxSubmission2 txid tx) (to :: TxSubmission2 txid tx) Source # | |
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type data Message (TxSubmission2 txid tx) (from :: TxSubmission2 txid tx) (to :: TxSubmission2 txid tx) where
| |
data Message (ChainSync header point tip) (from :: ChainSync header point tip) (to :: ChainSync header point tip) Source # | |
Defined in Ouroboros.Network.Protocol.ChainSync.Type data Message (ChainSync header point tip) (from :: ChainSync header point tip) (to :: ChainSync header point tip) where
| |
data Message (LocalTxMonitor txid tx slot) (from :: LocalTxMonitor txid tx slot) (to :: LocalTxMonitor txid tx slot) Source # | |
Defined in Ouroboros.Network.Protocol.LocalTxMonitor.Type data Message (LocalTxMonitor txid tx slot) (from :: LocalTxMonitor txid tx slot) (to :: LocalTxMonitor txid tx slot) where
|
data SingTxSubmission (k2 :: TxSubmission2 txid tx) where Source #
SingInit :: forall {k} {k1} {txid :: k} {tx :: k1}. SingTxSubmission ('StInit :: TxSubmission2 txid tx) | |
SingIdle :: forall {k} {k1} {txid :: k} {tx :: k1}. SingTxSubmission ('StIdle :: TxSubmission2 txid tx) | |
SingTxIds :: forall {k} {k1} {txid :: k} {tx :: k1} (stBlocking :: StBlockingStyle). SingBlockingStyle stBlocking -> SingTxSubmission ('StTxIds stBlocking :: TxSubmission2 txid tx) | |
SingTxs :: forall {k} {k1} {txid :: k} {tx :: k1}. SingTxSubmission ('StTxs :: TxSubmission2 txid tx) | |
SingDone :: forall {k} {k1} {txid :: k} {tx :: k1}. SingTxSubmission ('StDone :: TxSubmission2 txid tx) |
Instances
Show (SingTxSubmission k3) Source # | |
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type showsPrec :: Int -> SingTxSubmission k3 -> ShowS # show :: SingTxSubmission k3 -> String # showList :: [SingTxSubmission k3] -> ShowS # |
data SingBlockingStyle (k :: StBlockingStyle) where Source #
The value level equivalent of BlockingStyle
.
This is also used in MsgRequestTxIds
where it is interpreted (and can be
encoded) as a Bool
with True
for blocking, and False
for non-blocking.
Instances
NFData (SingBlockingStyle b) Source # | |
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type rnf :: SingBlockingStyle b -> () # | |
Show (SingBlockingStyle b) Source # | |
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type showsPrec :: Int -> SingBlockingStyle b -> ShowS # show :: SingBlockingStyle b -> String # showList :: [SingBlockingStyle b] -> ShowS # | |
Eq (SingBlockingStyle b) Source # | |
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type (==) :: SingBlockingStyle b -> SingBlockingStyle b -> Bool # (/=) :: SingBlockingStyle b -> SingBlockingStyle b -> Bool # |
data StBlockingStyle where Source #
StBlocking :: StBlockingStyle | In this sub-state the reply need not be prompt. There is no timeout. |
StNonBlocking :: StBlockingStyle | In this state the peer must reply. There is a timeout. |
Instances
SingI 'StBlocking Source # | |
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type sing :: Sing 'StBlocking # | |
SingI 'StNonBlocking Source # | |
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type sing :: Sing 'StNonBlocking # | |
type Sing Source # | |
data BlockingReplyList (blocking :: StBlockingStyle) a where Source #
We have requests for lists of things. In the blocking case the corresponding reply must be non-empty, whereas in the non-blocking case and empty reply is fine.
BlockingReply :: forall a. NonEmpty a -> BlockingReplyList 'StBlocking a | |
NonBlockingReply :: forall a. [a] -> BlockingReplyList 'StNonBlocking a |
Instances
NFData a => NFData (BlockingReplyList blocking a) Source # | |
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type rnf :: BlockingReplyList blocking a -> () # | |
Show a => Show (BlockingReplyList blocking a) Source # | |
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type showsPrec :: Int -> BlockingReplyList blocking a -> ShowS # show :: BlockingReplyList blocking a -> String # showList :: [BlockingReplyList blocking a] -> ShowS # | |
Eq a => Eq (BlockingReplyList blocking a) Source # | |
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type (==) :: BlockingReplyList blocking a -> BlockingReplyList blocking a -> Bool # (/=) :: BlockingReplyList blocking a -> BlockingReplyList blocking a -> Bool # |
newtype NumTxIdsToAck Source #
Instances
NFData NumTxIdsToAck Source # | |||||
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type rnf :: NumTxIdsToAck -> () # | |||||
Monoid NumTxIdsToAck Source # | |||||
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type mempty :: NumTxIdsToAck # mappend :: NumTxIdsToAck -> NumTxIdsToAck -> NumTxIdsToAck # mconcat :: [NumTxIdsToAck] -> NumTxIdsToAck # | |||||
Semigroup NumTxIdsToAck Source # | |||||
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type (<>) :: NumTxIdsToAck -> NumTxIdsToAck -> NumTxIdsToAck # sconcat :: NonEmpty NumTxIdsToAck -> NumTxIdsToAck # stimes :: Integral b => b -> NumTxIdsToAck -> NumTxIdsToAck # | |||||
Bounded NumTxIdsToAck Source # | |||||
Enum NumTxIdsToAck Source # | |||||
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type succ :: NumTxIdsToAck -> NumTxIdsToAck # pred :: NumTxIdsToAck -> NumTxIdsToAck # toEnum :: Int -> NumTxIdsToAck # fromEnum :: NumTxIdsToAck -> Int # enumFrom :: NumTxIdsToAck -> [NumTxIdsToAck] # enumFromThen :: NumTxIdsToAck -> NumTxIdsToAck -> [NumTxIdsToAck] # enumFromTo :: NumTxIdsToAck -> NumTxIdsToAck -> [NumTxIdsToAck] # enumFromThenTo :: NumTxIdsToAck -> NumTxIdsToAck -> NumTxIdsToAck -> [NumTxIdsToAck] # | |||||
Generic NumTxIdsToAck Source # | |||||
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type
from :: NumTxIdsToAck -> Rep NumTxIdsToAck x # to :: Rep NumTxIdsToAck x -> NumTxIdsToAck # | |||||
Num NumTxIdsToAck Source # | |||||
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type (+) :: NumTxIdsToAck -> NumTxIdsToAck -> NumTxIdsToAck # (-) :: NumTxIdsToAck -> NumTxIdsToAck -> NumTxIdsToAck # (*) :: NumTxIdsToAck -> NumTxIdsToAck -> NumTxIdsToAck # negate :: NumTxIdsToAck -> NumTxIdsToAck # abs :: NumTxIdsToAck -> NumTxIdsToAck # signum :: NumTxIdsToAck -> NumTxIdsToAck # fromInteger :: Integer -> NumTxIdsToAck # | |||||
Integral NumTxIdsToAck Source # | |||||
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type quot :: NumTxIdsToAck -> NumTxIdsToAck -> NumTxIdsToAck # rem :: NumTxIdsToAck -> NumTxIdsToAck -> NumTxIdsToAck # div :: NumTxIdsToAck -> NumTxIdsToAck -> NumTxIdsToAck # mod :: NumTxIdsToAck -> NumTxIdsToAck -> NumTxIdsToAck # quotRem :: NumTxIdsToAck -> NumTxIdsToAck -> (NumTxIdsToAck, NumTxIdsToAck) # divMod :: NumTxIdsToAck -> NumTxIdsToAck -> (NumTxIdsToAck, NumTxIdsToAck) # toInteger :: NumTxIdsToAck -> Integer # | |||||
Real NumTxIdsToAck Source # | |||||
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type toRational :: NumTxIdsToAck -> Rational # | |||||
Show NumTxIdsToAck Source # | |||||
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type showsPrec :: Int -> NumTxIdsToAck -> ShowS # show :: NumTxIdsToAck -> String # showList :: [NumTxIdsToAck] -> ShowS # | |||||
Eq NumTxIdsToAck Source # | |||||
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type (==) :: NumTxIdsToAck -> NumTxIdsToAck -> Bool # (/=) :: NumTxIdsToAck -> NumTxIdsToAck -> Bool # | |||||
Ord NumTxIdsToAck Source # | |||||
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type compare :: NumTxIdsToAck -> NumTxIdsToAck -> Ordering # (<) :: NumTxIdsToAck -> NumTxIdsToAck -> Bool # (<=) :: NumTxIdsToAck -> NumTxIdsToAck -> Bool # (>) :: NumTxIdsToAck -> NumTxIdsToAck -> Bool # (>=) :: NumTxIdsToAck -> NumTxIdsToAck -> Bool # max :: NumTxIdsToAck -> NumTxIdsToAck -> NumTxIdsToAck # min :: NumTxIdsToAck -> NumTxIdsToAck -> NumTxIdsToAck # | |||||
NoThunks NumTxIdsToAck Source # | |||||
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type noThunks :: Context -> NumTxIdsToAck -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> NumTxIdsToAck -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy NumTxIdsToAck -> String # | |||||
type Rep NumTxIdsToAck Source # | |||||
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type type Rep NumTxIdsToAck = D1 ('MetaData "NumTxIdsToAck" "Ouroboros.Network.Protocol.TxSubmission2.Type" "ouroboros-network-protocols-0.12.0.0-inplace" 'True) (C1 ('MetaCons "NumTxIdsToAck" 'PrefixI 'True) (S1 ('MetaSel ('Just "getNumTxIdsToAck") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word16))) |
newtype NumTxIdsToReq Source #
Instances
NFData NumTxIdsToReq Source # | |||||
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type rnf :: NumTxIdsToReq -> () # | |||||
Monoid NumTxIdsToReq Source # | |||||
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type mempty :: NumTxIdsToReq # mappend :: NumTxIdsToReq -> NumTxIdsToReq -> NumTxIdsToReq # mconcat :: [NumTxIdsToReq] -> NumTxIdsToReq # | |||||
Semigroup NumTxIdsToReq Source # | |||||
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type (<>) :: NumTxIdsToReq -> NumTxIdsToReq -> NumTxIdsToReq # sconcat :: NonEmpty NumTxIdsToReq -> NumTxIdsToReq # stimes :: Integral b => b -> NumTxIdsToReq -> NumTxIdsToReq # | |||||
Bounded NumTxIdsToReq Source # | |||||
Enum NumTxIdsToReq Source # | |||||
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type succ :: NumTxIdsToReq -> NumTxIdsToReq # pred :: NumTxIdsToReq -> NumTxIdsToReq # toEnum :: Int -> NumTxIdsToReq # fromEnum :: NumTxIdsToReq -> Int # enumFrom :: NumTxIdsToReq -> [NumTxIdsToReq] # enumFromThen :: NumTxIdsToReq -> NumTxIdsToReq -> [NumTxIdsToReq] # enumFromTo :: NumTxIdsToReq -> NumTxIdsToReq -> [NumTxIdsToReq] # enumFromThenTo :: NumTxIdsToReq -> NumTxIdsToReq -> NumTxIdsToReq -> [NumTxIdsToReq] # | |||||
Generic NumTxIdsToReq Source # | |||||
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type
from :: NumTxIdsToReq -> Rep NumTxIdsToReq x # to :: Rep NumTxIdsToReq x -> NumTxIdsToReq # | |||||
Num NumTxIdsToReq Source # | |||||
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type (+) :: NumTxIdsToReq -> NumTxIdsToReq -> NumTxIdsToReq # (-) :: NumTxIdsToReq -> NumTxIdsToReq -> NumTxIdsToReq # (*) :: NumTxIdsToReq -> NumTxIdsToReq -> NumTxIdsToReq # negate :: NumTxIdsToReq -> NumTxIdsToReq # abs :: NumTxIdsToReq -> NumTxIdsToReq # signum :: NumTxIdsToReq -> NumTxIdsToReq # fromInteger :: Integer -> NumTxIdsToReq # | |||||
Integral NumTxIdsToReq Source # | |||||
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type quot :: NumTxIdsToReq -> NumTxIdsToReq -> NumTxIdsToReq # rem :: NumTxIdsToReq -> NumTxIdsToReq -> NumTxIdsToReq # div :: NumTxIdsToReq -> NumTxIdsToReq -> NumTxIdsToReq # mod :: NumTxIdsToReq -> NumTxIdsToReq -> NumTxIdsToReq # quotRem :: NumTxIdsToReq -> NumTxIdsToReq -> (NumTxIdsToReq, NumTxIdsToReq) # divMod :: NumTxIdsToReq -> NumTxIdsToReq -> (NumTxIdsToReq, NumTxIdsToReq) # toInteger :: NumTxIdsToReq -> Integer # | |||||
Real NumTxIdsToReq Source # | |||||
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type toRational :: NumTxIdsToReq -> Rational # | |||||
Show NumTxIdsToReq Source # | |||||
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type showsPrec :: Int -> NumTxIdsToReq -> ShowS # show :: NumTxIdsToReq -> String # showList :: [NumTxIdsToReq] -> ShowS # | |||||
Eq NumTxIdsToReq Source # | |||||
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type (==) :: NumTxIdsToReq -> NumTxIdsToReq -> Bool # (/=) :: NumTxIdsToReq -> NumTxIdsToReq -> Bool # | |||||
Ord NumTxIdsToReq Source # | |||||
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type compare :: NumTxIdsToReq -> NumTxIdsToReq -> Ordering # (<) :: NumTxIdsToReq -> NumTxIdsToReq -> Bool # (<=) :: NumTxIdsToReq -> NumTxIdsToReq -> Bool # (>) :: NumTxIdsToReq -> NumTxIdsToReq -> Bool # (>=) :: NumTxIdsToReq -> NumTxIdsToReq -> Bool # max :: NumTxIdsToReq -> NumTxIdsToReq -> NumTxIdsToReq # min :: NumTxIdsToReq -> NumTxIdsToReq -> NumTxIdsToReq # | |||||
NoThunks NumTxIdsToReq Source # | |||||
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type noThunks :: Context -> NumTxIdsToReq -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> NumTxIdsToReq -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy NumTxIdsToReq -> String # | |||||
type Rep NumTxIdsToReq Source # | |||||
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type type Rep NumTxIdsToReq = D1 ('MetaData "NumTxIdsToReq" "Ouroboros.Network.Protocol.TxSubmission2.Type" "ouroboros-network-protocols-0.12.0.0-inplace" 'True) (C1 ('MetaCons "NumTxIdsToReq" 'PrefixI 'True) (S1 ('MetaSel ('Just "getNumTxIdsToReq") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word16))) |
newtype SizeInBytes #
Instances
NFData SizeInBytes | |||||
Defined in Ouroboros.Network.SizeInBytes rnf :: SizeInBytes -> () # | |||||
Monoid SizeInBytes | |||||
Defined in Ouroboros.Network.SizeInBytes mempty :: SizeInBytes # mappend :: SizeInBytes -> SizeInBytes -> SizeInBytes # mconcat :: [SizeInBytes] -> SizeInBytes # | |||||
Semigroup SizeInBytes | |||||
Defined in Ouroboros.Network.SizeInBytes (<>) :: SizeInBytes -> SizeInBytes -> SizeInBytes # sconcat :: NonEmpty SizeInBytes -> SizeInBytes # stimes :: Integral b => b -> SizeInBytes -> SizeInBytes # | |||||
Enum SizeInBytes | |||||
Defined in Ouroboros.Network.SizeInBytes succ :: SizeInBytes -> SizeInBytes # pred :: SizeInBytes -> SizeInBytes # toEnum :: Int -> SizeInBytes # fromEnum :: SizeInBytes -> Int # enumFrom :: SizeInBytes -> [SizeInBytes] # enumFromThen :: SizeInBytes -> SizeInBytes -> [SizeInBytes] # enumFromTo :: SizeInBytes -> SizeInBytes -> [SizeInBytes] # enumFromThenTo :: SizeInBytes -> SizeInBytes -> SizeInBytes -> [SizeInBytes] # | |||||
Generic SizeInBytes | |||||
Defined in Ouroboros.Network.SizeInBytes
from :: SizeInBytes -> Rep SizeInBytes x # to :: Rep SizeInBytes x -> SizeInBytes # | |||||
Num SizeInBytes | |||||
Defined in Ouroboros.Network.SizeInBytes (+) :: SizeInBytes -> SizeInBytes -> SizeInBytes # (-) :: SizeInBytes -> SizeInBytes -> SizeInBytes # (*) :: SizeInBytes -> SizeInBytes -> SizeInBytes # negate :: SizeInBytes -> SizeInBytes # abs :: SizeInBytes -> SizeInBytes # signum :: SizeInBytes -> SizeInBytes # fromInteger :: Integer -> SizeInBytes # | |||||
Integral SizeInBytes | |||||
Defined in Ouroboros.Network.SizeInBytes quot :: SizeInBytes -> SizeInBytes -> SizeInBytes # rem :: SizeInBytes -> SizeInBytes -> SizeInBytes # div :: SizeInBytes -> SizeInBytes -> SizeInBytes # mod :: SizeInBytes -> SizeInBytes -> SizeInBytes # quotRem :: SizeInBytes -> SizeInBytes -> (SizeInBytes, SizeInBytes) # divMod :: SizeInBytes -> SizeInBytes -> (SizeInBytes, SizeInBytes) # toInteger :: SizeInBytes -> Integer # | |||||
Real SizeInBytes | |||||
Defined in Ouroboros.Network.SizeInBytes toRational :: SizeInBytes -> Rational # | |||||
Show SizeInBytes | |||||
Defined in Ouroboros.Network.SizeInBytes showsPrec :: Int -> SizeInBytes -> ShowS # show :: SizeInBytes -> String # showList :: [SizeInBytes] -> ShowS # | |||||
Eq SizeInBytes | |||||
Defined in Ouroboros.Network.SizeInBytes (==) :: SizeInBytes -> SizeInBytes -> Bool # (/=) :: SizeInBytes -> SizeInBytes -> Bool # | |||||
Ord SizeInBytes | |||||
Defined in Ouroboros.Network.SizeInBytes compare :: SizeInBytes -> SizeInBytes -> Ordering # (<) :: SizeInBytes -> SizeInBytes -> Bool # (<=) :: SizeInBytes -> SizeInBytes -> Bool # (>) :: SizeInBytes -> SizeInBytes -> Bool # (>=) :: SizeInBytes -> SizeInBytes -> Bool # max :: SizeInBytes -> SizeInBytes -> SizeInBytes # min :: SizeInBytes -> SizeInBytes -> SizeInBytes # | |||||
BoundedMeasure SizeInBytes | |||||
Defined in Ouroboros.Network.SizeInBytes maxBound :: SizeInBytes # | |||||
Measure SizeInBytes | |||||
Defined in Ouroboros.Network.SizeInBytes zero :: SizeInBytes # plus :: SizeInBytes -> SizeInBytes -> SizeInBytes # min :: SizeInBytes -> SizeInBytes -> SizeInBytes # max :: SizeInBytes -> SizeInBytes -> SizeInBytes # | |||||
NoThunks SizeInBytes | |||||
Defined in Ouroboros.Network.SizeInBytes noThunks :: Context -> SizeInBytes -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> SizeInBytes -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy SizeInBytes -> String # | |||||
type Rep SizeInBytes | |||||
Defined in Ouroboros.Network.SizeInBytes type Rep SizeInBytes = D1 ('MetaData "SizeInBytes" "Ouroboros.Network.SizeInBytes" "ouroboros-network-api-0.11.0.0-inplace" 'True) (C1 ('MetaCons "SizeInBytes" 'PrefixI 'True) (S1 ('MetaSel ('Just "getSizeInBytes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32))) |