Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module contains peer state management and error policies.
Synopsis
- data SuspendDecision t
- = SuspendPeer !t !t
- | SuspendConsumer !t
- | Throw
- suspend :: forall (m :: Type -> Type). Ord (Async m ()) => Maybe (PeerState m) -> SuspendDecision Time -> (Set (Async m ()), Maybe (PeerState m))
- data PeerState (m :: Type -> Type)
- threadsToCancel :: forall (m :: Type -> Type) diffTime. Ord (Async m ()) => PeerState m -> SuspendDecision diffTime -> Set (Async m ())
- data PeerStates (m :: Type -> Type) addr where
- PeerStates :: forall addr (m :: Type -> Type). !(Map addr (PeerState m)) -> PeerStates m addr
- ThrowException :: forall e (m :: Type -> Type) addr. Exception e => e -> PeerStates m addr
- newPeerStatesVar :: MonadSTM m => m (StrictTVar m (PeerStates m addr))
- newPeerStatesVarSTM :: forall (m :: Type -> Type) addr. MonadSTM m => STM m (StrictTVar m (PeerStates m addr))
- cleanPeerStates :: (MonadDelay m, MonadTimer m) => DiffTime -> StrictTVar m (PeerStates m addr) -> m ()
- runSuspendDecision :: forall (m :: Type -> Type) addr e. (Ord addr, Ord (Async m ()), Exception e) => Time -> addr -> e -> SuspendDecision DiffTime -> PeerStates m addr -> (PeerStates m addr, Set (Async m ()))
- registerConsumer :: forall (m :: Type -> Type) addr. (Ord addr, Ord (Async m ())) => addr -> Async m () -> PeerStates m addr -> PeerStates m addr
- unregisterConsumer :: forall (m :: Type -> Type) addr. (Ord addr, Ord (Async m ())) => addr -> Async m () -> PeerStates m addr -> PeerStates m addr
- registerProducer :: forall (m :: Type -> Type) addr. (Ord addr, Ord (Async m ())) => addr -> Async m () -> PeerStates m addr -> PeerStates m addr
- unregisterProducer :: forall (m :: Type -> Type) addr. (Ord addr, Ord (Async m ())) => addr -> Async m () -> PeerStates m addr -> PeerStates m addr
- type BeforeConnect (m :: Type -> Type) s addr = Time -> addr -> s -> STM m (ConnectDecision s)
- data ConnectDecision s
- = AllowConnection !s
- | DisallowConnection !s
- | OnlyAccept !s
- runBeforeConnect :: (MonadMonotonicTime m, MonadSTM m) => StrictTVar m s -> BeforeConnect m s addr -> addr -> m Bool
- beforeConnectTx :: forall (m :: Type -> Type) addr. (MonadSTM m, Ord addr) => BeforeConnect m (PeerStates m addr) addr
- data DiffTime
- alterAndLookup :: forall k s a. Ord k => (Maybe a -> (s, Maybe a)) -> k -> Map k a -> (Map k a, Maybe s)
Documentation
data SuspendDecision t Source #
Semigroup of commands which acts on PeerState
. The t
variable might
be initiated to DiffTime
or Time m
.
This semigroup allows to either suspend both consumer and producer or just the consumer part.
SuspendPeer !t !t | peer is suspend; The first |
SuspendConsumer !t | suspend local consumer / initiator side until |
Throw | throw an error from the main thread. |
Instances
suspend :: forall (m :: Type -> Type). Ord (Async m ()) => Maybe (PeerState m) -> SuspendDecision Time -> (Set (Async m ()), Maybe (PeerState m)) Source #
Action of SuspendDecision
on Maybe
. Action laws are only
satisfied for the submonoid form by PeerState
SuspendPeer
and SuspendConsumer
.
PeerStates and its operations
data PeerState (m :: Type -> Type) Source #
HotPeer !(Set (Async m ())) !(Set (Async m ())) | active peer with its producers and consumer threads |
SuspendedConsumer !(Set (Async m ())) !Time | suspended consumer: with producer threads and time until the consumer is suspended |
SuspendedPeer !Time !Time | suspended peer: producer & consumer suspend time |
ColdPeer | peer with no opened connections in either direction |
Instances
MonadAsync m => Show (PeerState m) Source # | |
Eq (Async m ()) => Eq (PeerState m) Source # | |
Ord (Async m ()) => Ord (PeerState m) Source # | |
Defined in Ouroboros.Network.Subscription.PeerState | |
SAct (SuspendDecision Time) (Maybe (PeerState m)) Source # | Action of Note: |
Defined in Ouroboros.Network.Subscription.PeerState |
threadsToCancel :: forall (m :: Type -> Type) diffTime. Ord (Async m ()) => PeerState m -> SuspendDecision diffTime -> Set (Async m ()) Source #
Threads which needs to be cancelled when updating the PeerState
with
SuspendDecision
.
data PeerStates (m :: Type -> Type) addr where Source #
Map from addresses to PeerState
s; it will be be shared in a StrictTVar
.
Abstracting t
is useful for tests, the IO
version will use Time IO
.
PeerStates :: forall addr (m :: Type -> Type). !(Map addr (PeerState m)) -> PeerStates m addr | Map of peer states |
ThrowException :: forall e (m :: Type -> Type) addr. Exception e => e -> PeerStates m addr | Or an exception to throw |
Instances
Show addr => Show (PeerStates IO addr) Source # | |
Defined in Ouroboros.Network.Subscription.PeerState | |
Eq addr => Eq (PeerStates IO addr) Source # | |
Defined in Ouroboros.Network.Subscription.PeerState (==) :: PeerStates IO addr -> PeerStates IO addr -> Bool # (/=) :: PeerStates IO addr -> PeerStates IO addr -> Bool # |
newPeerStatesVar :: MonadSTM m => m (StrictTVar m (PeerStates m addr)) Source #
newPeerStatesVarSTM :: forall (m :: Type -> Type) addr. MonadSTM m => STM m (StrictTVar m (PeerStates m addr)) Source #
cleanPeerStates :: (MonadDelay m, MonadTimer m) => DiffTime -> StrictTVar m (PeerStates m addr) -> m () Source #
Periodically clean PeerState
. It will stop when PeerState
becomes
ThrowException
.
runSuspendDecision :: forall (m :: Type -> Type) addr e. (Ord addr, Ord (Async m ()), Exception e) => Time -> addr -> e -> SuspendDecision DiffTime -> PeerStates m addr -> (PeerStates m addr, Set (Async m ())) Source #
Update PeerStates
for a given addr
, using suspend
, and return
threads which must be cancelled.
This is more efficient that using the action of SuspendDecision
on
PeerStates
, since it only uses a single dictionary lookup to update the
state and return the set of threads to be cancelled.
registerConsumer :: forall (m :: Type -> Type) addr. (Ord addr, Ord (Async m ())) => addr -> Async m () -> PeerStates m addr -> PeerStates m addr Source #
unregisterConsumer :: forall (m :: Type -> Type) addr. (Ord addr, Ord (Async m ())) => addr -> Async m () -> PeerStates m addr -> PeerStates m addr Source #
Unregister consumer from a PeerState
.
registerProducer :: forall (m :: Type -> Type) addr. (Ord addr, Ord (Async m ())) => addr -> Async m () -> PeerStates m addr -> PeerStates m addr Source #
Register producer in PeerStates. This is a partial function which assumes
that the PeerState
is either HotPeer
or SuspendedConsumer
.
unregisterProducer :: forall (m :: Type -> Type) addr. (Ord addr, Ord (Async m ())) => addr -> Async m () -> PeerStates m addr -> PeerStates m addr Source #
type BeforeConnect (m :: Type -> Type) s addr = Time -> addr -> s -> STM m (ConnectDecision s) Source #
Check state before connecting to a remote peer. We will connect only if
it retuns True
.
data ConnectDecision s Source #
Before connectin with a peer we make a decision to either connect to it or not.
AllowConnection !s | |
DisallowConnection !s | |
OnlyAccept !s |
Instances
Functor ConnectDecision Source # | |
Defined in Ouroboros.Network.Subscription.PeerState fmap :: (a -> b) -> ConnectDecision a -> ConnectDecision b # (<$) :: a -> ConnectDecision b -> ConnectDecision a # |
runBeforeConnect :: (MonadMonotonicTime m, MonadSTM m) => StrictTVar m s -> BeforeConnect m s addr -> addr -> m Bool Source #
Run BeforeConnect
callback in a MonadTime
monad.
beforeConnectTx :: forall (m :: Type -> Type) addr. (MonadSTM m, Ord addr) => BeforeConnect m (PeerStates m addr) addr Source #
BeforeConnect
callback: it updates peer state and return boolean value
wheather to connect to it or not. If a peer hasn't been recorded in
PeerStates
, we add it and try to connect to it.
Re-exports
This is a length of time, as measured by a clock.
Conversion functions such as fromInteger
and realToFrac
will treat it as seconds.
For example, (0.010 :: DiffTime)
corresponds to 10 milliseconds.
It has a precision of one picosecond (= 10^-12 s). Enumeration functions will treat it as picoseconds.
Instances
NFData DiffTime | |
Defined in Data.Time.Clock.Internal.DiffTime | |
Data DiffTime | |
Defined in Data.Time.Clock.Internal.DiffTime gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DiffTime -> c DiffTime # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DiffTime # toConstr :: DiffTime -> Constr # dataTypeOf :: DiffTime -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DiffTime) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DiffTime) # gmapT :: (forall b. Data b => b -> b) -> DiffTime -> DiffTime # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DiffTime -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DiffTime -> r # gmapQ :: (forall d. Data d => d -> u) -> DiffTime -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DiffTime -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DiffTime -> m DiffTime # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DiffTime -> m DiffTime # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DiffTime -> m DiffTime # | |
Enum DiffTime | |
Defined in Data.Time.Clock.Internal.DiffTime | |
Num DiffTime | |
Read DiffTime | |
Fractional DiffTime | |
Real DiffTime | |
Defined in Data.Time.Clock.Internal.DiffTime toRational :: DiffTime -> Rational # | |
RealFrac DiffTime | |
Show DiffTime | |
Eq DiffTime | |
Ord DiffTime | |
Defined in Data.Time.Clock.Internal.DiffTime | |
NoThunks DiffTime | |