| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Ouroboros.Network.Protocol.LocalStateQuery.Type
Description
The type of the local ledger state query protocol.
This is used by local clients (like wallets and CLI tools) to query the ledger state of a local node.
Synopsis
- data LocalStateQuery block point (query :: Type -> Type) where
- StIdle :: forall block point (query :: Type -> Type). LocalStateQuery block point query
- StAcquiring :: forall block point (query :: Type -> Type). LocalStateQuery block point query
- StAcquired :: forall block point (query :: Type -> Type). LocalStateQuery block point query
- StQuerying :: forall block point (query :: Type -> Type) result. result -> LocalStateQuery block point query
- StDone :: forall block point (query :: Type -> Type). LocalStateQuery block point query
- data SingLocalStateQuery (k :: LocalStateQuery block point query) where
- SingIdle :: forall {block} {point} {query :: Type -> Type}. SingLocalStateQuery ('StIdle :: LocalStateQuery block point query)
- SingAcquiring :: forall {block} {point} {query :: Type -> Type}. SingLocalStateQuery ('StAcquiring :: LocalStateQuery block point query)
- SingAcquired :: forall {block} {point} {query :: Type -> Type}. SingLocalStateQuery ('StAcquired :: LocalStateQuery block point query)
- SingQuerying :: forall block point (query :: Type -> Type) result. SingLocalStateQuery ('StQuerying result :: LocalStateQuery block point query)
- SingDone :: forall {block} {point} {query :: Type -> Type}. SingLocalStateQuery ('StDone :: LocalStateQuery block point query)
- data Target point
- = VolatileTip
- | SpecificPoint point
- | ImmutableTip
- data AcquireFailure
- class (forall result. Show (query result)) => ShowQuery (query :: Type -> Type) where
- showResult :: query result -> result -> String
- data State (st :: LocalStateQuery block point query) where
- StateIdle :: forall {block} {point} {query :: Type -> Type}. State ('StIdle :: LocalStateQuery block point query)
- StateAcquiring :: forall {block} {point} {query :: Type -> Type}. State ('StAcquiring :: LocalStateQuery block point query)
- StateAcquired :: forall {block} {point} {query :: Type -> Type}. State ('StAcquired :: LocalStateQuery block point query)
- StateQuerying :: forall (query :: Type -> Type) result block point. query result -> State ('StQuerying result :: LocalStateQuery block point query)
- StateDone :: forall {block} {point} {query :: Type -> Type}. State ('StDone :: LocalStateQuery block point query)
- data LocalStateQueryVersion
Documentation
data LocalStateQuery block point (query :: Type -> Type) where Source #
The kind of the local state query protocol, and the types of the states in the protocol state machine.
It is parameterised over the type of block (for points), the type of queries and query results.
Constructors
| StIdle :: forall block point (query :: Type -> Type). LocalStateQuery block point query | The client has agency. It can ask to acquire a state or terminate. There is no timeout in this state. |
| StAcquiring :: forall block point (query :: Type -> Type). LocalStateQuery block point query | The server has agency. It must acquire the state at the requested point or report a failure. There is a timeout in this state. |
| StAcquired :: forall block point (query :: Type -> Type). LocalStateQuery block point query | The client has agency. It can request queries against the current state, or it can release the state. |
| StQuerying :: forall block point (query :: Type -> Type) result. result -> LocalStateQuery block point query | The server has agency. It must respond with the query result. |
| StDone :: forall block point (query :: Type -> Type). LocalStateQuery block point query | Nobody has agency. The terminal state. |
Instances
| (ShowProxy block, ShowProxy query) => ShowProxy (LocalStateQuery block point query :: Type) Source # | |||||
Defined in Ouroboros.Network.Protocol.LocalStateQuery.Type Methods showProxy :: Proxy (LocalStateQuery block point query) -> String | |||||
| (ShowQuery query, Show point) => Show (AnyMessage (LocalStateQuery block point query) (State :: LocalStateQuery block point query -> Type)) Source # | |||||
Defined in Ouroboros.Network.Protocol.LocalStateQuery.Type Methods showsPrec :: Int -> AnyMessage (LocalStateQuery block point query) (State :: LocalStateQuery block point query -> Type) -> ShowS # show :: AnyMessage (LocalStateQuery block point query) (State :: LocalStateQuery block point query -> Type) -> String # showList :: [AnyMessage (LocalStateQuery block point query) (State :: LocalStateQuery block point query -> Type)] -> ShowS # | |||||
| (forall result. NFData (query result), NFData point) => NFData (Message (LocalStateQuery block point query) from to) Source # | |||||
Defined in Ouroboros.Network.Protocol.LocalStateQuery.Type Methods rnf :: Message (LocalStateQuery block point query) from to -> () # | |||||
| Protocol (LocalStateQuery block point query) Source # | |||||
Defined in Ouroboros.Network.Protocol.LocalStateQuery.Type Associated Types
| |||||
| StateTokenI ('StAcquired :: LocalStateQuery block point query) Source # | |||||
Defined in Ouroboros.Network.Protocol.LocalStateQuery.Type Methods stateToken :: StateToken ('StAcquired :: LocalStateQuery block point query) # | |||||
| StateTokenI ('StAcquiring :: LocalStateQuery block point query) Source # | |||||
Defined in Ouroboros.Network.Protocol.LocalStateQuery.Type Methods stateToken :: StateToken ('StAcquiring :: LocalStateQuery block point query) # | |||||
| StateTokenI ('StDone :: LocalStateQuery block point query) Source # | |||||
Defined in Ouroboros.Network.Protocol.LocalStateQuery.Type Methods stateToken :: StateToken ('StDone :: LocalStateQuery block point query) # | |||||
| StateTokenI ('StIdle :: LocalStateQuery block point query) Source # | |||||
Defined in Ouroboros.Network.Protocol.LocalStateQuery.Type Methods stateToken :: StateToken ('StIdle :: LocalStateQuery block point query) # | |||||
| StateTokenI ('StQuerying result :: LocalStateQuery block point query) Source # | |||||
Defined in Ouroboros.Network.Protocol.LocalStateQuery.Type Methods stateToken :: StateToken ('StQuerying result :: LocalStateQuery block point query) # | |||||
| 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
| |||||
| type StateToken Source # | |||||
| type StateAgency ('StAcquired :: LocalStateQuery block point query) Source # | |||||
| type StateAgency ('StAcquiring :: LocalStateQuery block point query) Source # | |||||
| type StateAgency ('StDone :: LocalStateQuery block point query) Source # | |||||
| type StateAgency ('StIdle :: LocalStateQuery block point query) Source # | |||||
| type StateAgency ('StQuerying result2 :: LocalStateQuery block point query) Source # | |||||
data SingLocalStateQuery (k :: LocalStateQuery block point query) where Source #
Singletons for LocalStateQuery state types.
Constructors
| SingIdle :: forall {block} {point} {query :: Type -> Type}. SingLocalStateQuery ('StIdle :: LocalStateQuery block point query) | |
| SingAcquiring :: forall {block} {point} {query :: Type -> Type}. SingLocalStateQuery ('StAcquiring :: LocalStateQuery block point query) | |
| SingAcquired :: forall {block} {point} {query :: Type -> Type}. SingLocalStateQuery ('StAcquired :: LocalStateQuery block point query) | |
| SingQuerying :: forall block point (query :: Type -> Type) result. SingLocalStateQuery ('StQuerying result :: LocalStateQuery block point query) | |
| SingDone :: forall {block} {point} {query :: Type -> Type}. SingLocalStateQuery ('StDone :: LocalStateQuery block point query) |
Instances
| (forall result. Show (query result)) => Show (SingLocalStateQuery k) Source # | |
Defined in Ouroboros.Network.Protocol.LocalStateQuery.Type Methods showsPrec :: Int -> SingLocalStateQuery k -> ShowS # show :: SingLocalStateQuery k -> String # showList :: [SingLocalStateQuery k] -> ShowS # | |
Constructors
| VolatileTip | The tip of the volatile chain Cannot fail to be acquired. |
| SpecificPoint point | A specified point Fails to be acquired if the point is not between
|
| ImmutableTip | The tip of the immutable chain Cannot fail to be acquired. Requires at least |
Instances
| Functor Target Source # | |||||
| Foldable Target Source # | |||||
Defined in Ouroboros.Network.Protocol.LocalStateQuery.Type Methods fold :: Monoid m => Target m -> m # foldMap :: Monoid m => (a -> m) -> Target a -> m # foldMap' :: Monoid m => (a -> m) -> Target a -> m # foldr :: (a -> b -> b) -> b -> Target a -> b # foldr' :: (a -> b -> b) -> b -> Target a -> b # foldl :: (b -> a -> b) -> b -> Target a -> b # foldl' :: (b -> a -> b) -> b -> Target a -> b # foldr1 :: (a -> a -> a) -> Target a -> a # foldl1 :: (a -> a -> a) -> Target a -> a # elem :: Eq a => a -> Target a -> Bool # maximum :: Ord a => Target a -> a # minimum :: Ord a => Target a -> a # | |||||
| Traversable Target Source # | |||||
| NFData point => NFData (Target point) Source # | |||||
| Generic (Target point) Source # | |||||
Defined in Ouroboros.Network.Protocol.LocalStateQuery.Type Associated Types
| |||||
| Show point => Show (Target point) Source # | |||||
| Eq point => Eq (Target point) Source # | |||||
| Ord point => Ord (Target point) Source # | |||||
| type Rep (Target point) Source # | |||||
Defined in Ouroboros.Network.Protocol.LocalStateQuery.Type type Rep (Target point) = D1 ('MetaData "Target" "Ouroboros.Network.Protocol.LocalStateQuery.Type" "ouroboros-network-0.23.0.0-inplace-protocols" 'False) (C1 ('MetaCons "VolatileTip" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SpecificPoint" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 point)) :+: C1 ('MetaCons "ImmutableTip" 'PrefixI 'False) (U1 :: Type -> Type))) | |||||
data AcquireFailure Source #
Instances
class (forall result. Show (query result)) => ShowQuery (query :: Type -> Type) where Source #
To implement Show for:
('Message' ('LocalStateQuery' block query) st st')we need a way to print the query GADT and its type index, result. This
class contain the method we need to provide this Show instance.
We use a type class for this, as this Show constraint propagates to a lot
of places.
Methods
showResult :: query result -> result -> String Source #
data State (st :: LocalStateQuery block point query) where Source #
Constructors
| StateIdle :: forall {block} {point} {query :: Type -> Type}. State ('StIdle :: LocalStateQuery block point query) | |
| StateAcquiring :: forall {block} {point} {query :: Type -> Type}. State ('StAcquiring :: LocalStateQuery block point query) | |
| StateAcquired :: forall {block} {point} {query :: Type -> Type}. State ('StAcquired :: LocalStateQuery block point query) | |
| StateQuerying :: forall (query :: Type -> Type) result block point. query result -> State ('StQuerying result :: LocalStateQuery block point query) | |
| StateDone :: forall {block} {point} {query :: Type -> Type}. State ('StDone :: LocalStateQuery block point query) |
Instances
| (ShowQuery query, Show point) => Show (AnyMessage (LocalStateQuery block point query) (State :: LocalStateQuery block point query -> Type)) Source # | |
Defined in Ouroboros.Network.Protocol.LocalStateQuery.Type Methods showsPrec :: Int -> AnyMessage (LocalStateQuery block point query) (State :: LocalStateQuery block point query -> Type) -> ShowS # show :: AnyMessage (LocalStateQuery block point query) (State :: LocalStateQuery block point query -> Type) -> String # showList :: [AnyMessage (LocalStateQuery block point query) (State :: LocalStateQuery block point query -> Type)] -> ShowS # | |
| Show (State st) Source # | |
data LocalStateQueryVersion Source #
Constructors
| LocalStateQuery_V1 | |
| LocalStateQuery_V2 |
Instances
| Bounded LocalStateQueryVersion Source # | |
| Enum LocalStateQueryVersion Source # | |
Defined in Ouroboros.Network.Protocol.LocalStateQuery.Type Methods succ :: LocalStateQueryVersion -> LocalStateQueryVersion # pred :: LocalStateQueryVersion -> LocalStateQueryVersion # toEnum :: Int -> LocalStateQueryVersion # fromEnum :: LocalStateQueryVersion -> Int # enumFrom :: LocalStateQueryVersion -> [LocalStateQueryVersion] # enumFromThen :: LocalStateQueryVersion -> LocalStateQueryVersion -> [LocalStateQueryVersion] # enumFromTo :: LocalStateQueryVersion -> LocalStateQueryVersion -> [LocalStateQueryVersion] # enumFromThenTo :: LocalStateQueryVersion -> LocalStateQueryVersion -> LocalStateQueryVersion -> [LocalStateQueryVersion] # | |
| Show LocalStateQueryVersion Source # | |
Defined in Ouroboros.Network.Protocol.LocalStateQuery.Type Methods showsPrec :: Int -> LocalStateQueryVersion -> ShowS # show :: LocalStateQueryVersion -> String # showList :: [LocalStateQueryVersion] -> ShowS # | |
| Eq LocalStateQueryVersion Source # | |
Defined in Ouroboros.Network.Protocol.LocalStateQuery.Type Methods (==) :: LocalStateQueryVersion -> LocalStateQueryVersion -> Bool # (/=) :: LocalStateQueryVersion -> LocalStateQueryVersion -> Bool # | |
| Ord LocalStateQueryVersion Source # | |
Defined in Ouroboros.Network.Protocol.LocalStateQuery.Type Methods compare :: LocalStateQueryVersion -> LocalStateQueryVersion -> Ordering # (<) :: LocalStateQueryVersion -> LocalStateQueryVersion -> Bool # (<=) :: LocalStateQueryVersion -> LocalStateQueryVersion -> Bool # (>) :: LocalStateQueryVersion -> LocalStateQueryVersion -> Bool # (>=) :: LocalStateQueryVersion -> LocalStateQueryVersion -> Bool # max :: LocalStateQueryVersion -> LocalStateQueryVersion -> LocalStateQueryVersion # min :: LocalStateQueryVersion -> LocalStateQueryVersion -> LocalStateQueryVersion # | |