| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
DMQ.Protocol.LocalMsgNotification.Type
Description
Defines types for the local message notification protocol
Synopsis
- data LocalMsgNotification msg where
- StIdle :: forall msg. LocalMsgNotification msg
- StBusy :: forall msg. StBlockingStyle -> LocalMsgNotification msg
- StDone :: forall msg. LocalMsgNotification msg
- data SingMsgNotification (k :: LocalMsgNotification msg) where
- SingIdle :: forall {msg}. SingMsgNotification ('StIdle :: LocalMsgNotification msg)
- SingBusy :: forall {msg} (blocking :: StBlockingStyle). SingBlockingStyle blocking -> SingMsgNotification ('StBusy blocking :: LocalMsgNotification msg)
- SingDone :: forall {msg}. SingMsgNotification ('StDone :: LocalMsgNotification msg)
- data StDone :: LocalMsgNotification msg
- MsgClientDone :: Message (LocalMsgNotification msg) ('StIdle :: LocalMsgNotification msg) ('StDone :: LocalMsgNotification msg)
- MsgRequest :: forall (blocking :: StBlockingStyle) msg. SingI blocking => SingBlockingStyle blocking %1 -> Message (LocalMsgNotification msg) ('StIdle :: LocalMsgNotification msg) ('StBusy blocking :: LocalMsgNotification msg)
- MsgReply :: forall (blocking :: StBlockingStyle) msg. BlockingReplyList blocking msg %1 -> HasMore %1 -> Message (LocalMsgNotification msg) ('StBusy blocking :: LocalMsgNotification msg) ('StIdle :: LocalMsgNotification msg)
- data StBusy (x0 :: StBlockingStyle) :: LocalMsgNotification msg
- data StIdle :: LocalMsgNotification msg
- data HasMore
- module Network.TypedProtocol.Core
- data StBlockingStyle where
- data BlockingReplyList (blocking :: StBlockingStyle) a where
- BlockingReply :: forall a. NonEmpty a -> BlockingReplyList 'StBlocking a
- NonBlockingReply :: forall a. [a] -> BlockingReplyList 'StNonBlocking a
- data SingBlockingStyle (k :: StBlockingStyle) where
Documentation
data LocalMsgNotification msg where Source #
The kind of the local message notification protocol, and the types of the states in the protocol state machine.
It is parameterised over the type of messages
Constructors
| StIdle :: forall msg. LocalMsgNotification msg | |
| StBusy :: forall msg. StBlockingStyle -> LocalMsgNotification msg | |
| StDone :: forall msg. LocalMsgNotification msg |
Instances
data SingMsgNotification (k :: LocalMsgNotification msg) where Source #
a singleton witness for protocol state
Constructors
| SingIdle :: forall {msg}. SingMsgNotification ('StIdle :: LocalMsgNotification msg) | |
| SingBusy :: forall {msg} (blocking :: StBlockingStyle). SingBlockingStyle blocking -> SingMsgNotification ('StBusy blocking :: LocalMsgNotification msg) | |
| SingDone :: forall {msg}. SingMsgNotification ('StDone :: LocalMsgNotification msg) |
Instances
| Show (SingMsgNotification k) Source # | |
Defined in DMQ.Protocol.LocalMsgNotification.Type Methods showsPrec :: Int -> SingMsgNotification k -> ShowS # show :: SingMsgNotification k -> String # showList :: [SingMsgNotification k] -> ShowS # | |
data StDone :: LocalMsgNotification msg Source #
Instances
| StateTokenI ('StDone :: LocalMsgNotification msg) Source # | |
Defined in DMQ.Protocol.LocalMsgNotification.Type Methods stateToken :: StateToken ('StDone :: LocalMsgNotification msg) # | |
| type StateAgency ('StDone :: LocalMsgNotification msg) Source # | |
Defined in DMQ.Protocol.LocalMsgNotification.Type | |
MsgClientDone :: Message (LocalMsgNotification msg) ('StIdle :: LocalMsgNotification msg) ('StDone :: LocalMsgNotification msg) Source #
MsgRequest :: forall (blocking :: StBlockingStyle) msg. SingI blocking => SingBlockingStyle blocking %1 -> Message (LocalMsgNotification msg) ('StIdle :: LocalMsgNotification msg) ('StBusy blocking :: LocalMsgNotification msg) Source #
MsgReply :: forall (blocking :: StBlockingStyle) msg. BlockingReplyList blocking msg %1 -> HasMore %1 -> Message (LocalMsgNotification msg) ('StBusy blocking :: LocalMsgNotification msg) ('StIdle :: LocalMsgNotification msg) Source #
data StBusy (x0 :: StBlockingStyle) :: LocalMsgNotification msg Source #
Instances
| SingI blocking => StateTokenI ('StBusy blocking :: LocalMsgNotification msg) Source # | |
Defined in DMQ.Protocol.LocalMsgNotification.Type Methods stateToken :: StateToken ('StBusy blocking :: LocalMsgNotification msg) # | |
| type StateAgency ('StBusy blocking :: LocalMsgNotification msg) Source # | |
Defined in DMQ.Protocol.LocalMsgNotification.Type | |
data StIdle :: LocalMsgNotification msg Source #
Instances
| StateTokenI ('StIdle :: LocalMsgNotification msg) Source # | |
Defined in DMQ.Protocol.LocalMsgNotification.Type Methods stateToken :: StateToken ('StIdle :: LocalMsgNotification msg) # | |
| type StateAgency ('StIdle :: LocalMsgNotification msg) Source # | |
Defined in DMQ.Protocol.LocalMsgNotification.Type | |
A boolean-like to indicate whether the server has more messages that it can provide.
Constructors
| HasMore | |
| DoesNotHaveMore |
module Network.TypedProtocol.Core
data StBlockingStyle where #
Constructors
| StBlocking :: StBlockingStyle | |
| StNonBlocking :: StBlockingStyle |
Instances
| SingI 'StBlocking | |
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type Methods sing :: Sing 'StBlocking # | |
| SingI 'StNonBlocking | |
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type Methods sing :: Sing 'StNonBlocking # | |
| type Sing | |
data BlockingReplyList (blocking :: StBlockingStyle) a where #
Constructors
| BlockingReply :: forall a. NonEmpty a -> BlockingReplyList 'StBlocking a | |
| NonBlockingReply :: forall a. [a] -> BlockingReplyList 'StNonBlocking a |
Instances
| Foldable (BlockingReplyList blocking) | |
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type Methods fold :: Monoid m => BlockingReplyList blocking m -> m # foldMap :: Monoid m => (a -> m) -> BlockingReplyList blocking a -> m # foldMap' :: Monoid m => (a -> m) -> BlockingReplyList blocking a -> m # foldr :: (a -> b -> b) -> b -> BlockingReplyList blocking a -> b # foldr' :: (a -> b -> b) -> b -> BlockingReplyList blocking a -> b # foldl :: (b -> a -> b) -> b -> BlockingReplyList blocking a -> b # foldl' :: (b -> a -> b) -> b -> BlockingReplyList blocking a -> b # foldr1 :: (a -> a -> a) -> BlockingReplyList blocking a -> a # foldl1 :: (a -> a -> a) -> BlockingReplyList blocking a -> a # toList :: BlockingReplyList blocking a -> [a] # null :: BlockingReplyList blocking a -> Bool # length :: BlockingReplyList blocking a -> Int # elem :: Eq a => a -> BlockingReplyList blocking a -> Bool # maximum :: Ord a => BlockingReplyList blocking a -> a # minimum :: Ord a => BlockingReplyList blocking a -> a # sum :: Num a => BlockingReplyList blocking a -> a # product :: Num a => BlockingReplyList blocking a -> a # | |
| NFData a => NFData (BlockingReplyList blocking a) | |
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type Methods rnf :: BlockingReplyList blocking a -> () # | |
| Show a => Show (BlockingReplyList blocking a) | |
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type Methods showsPrec :: Int -> BlockingReplyList blocking a -> ShowS # show :: BlockingReplyList blocking a -> String # showList :: [BlockingReplyList blocking a] -> ShowS # | |
| Eq a => Eq (BlockingReplyList blocking a) | |
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type Methods (==) :: BlockingReplyList blocking a -> BlockingReplyList blocking a -> Bool # (/=) :: BlockingReplyList blocking a -> BlockingReplyList blocking a -> Bool # | |
data SingBlockingStyle (k :: StBlockingStyle) where #
Constructors
| SingBlocking :: SingBlockingStyle 'StBlocking | |
| SingNonBlocking :: SingBlockingStyle 'StNonBlocking |
Instances
| NFData (SingBlockingStyle b) | |
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type Methods rnf :: SingBlockingStyle b -> () # | |
| Show (SingBlockingStyle b) | |
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type Methods showsPrec :: Int -> SingBlockingStyle b -> ShowS # show :: SingBlockingStyle b -> String # showList :: [SingBlockingStyle b] -> ShowS # | |
| Eq (SingBlockingStyle b) | |
Defined in Ouroboros.Network.Protocol.TxSubmission2.Type Methods (==) :: SingBlockingStyle b -> SingBlockingStyle b -> Bool # (/=) :: SingBlockingStyle b -> SingBlockingStyle b -> Bool # | |