schedule-0.2.0.0: Pure deterministic scheduled computations

Safe HaskellNone
LanguageHaskell2010

Control.Schedule.Future

Description

Pure serialisable futures.

This API is experimental at the moment, and parts of it may change.

Documentation

type OSet a = Set a Source #

type OMap k v = Map k v Source #

data TimedResult tk r Source #

Constructors

TimedOut !tk 
GotResult !r 
Instances
(Eq tk, Eq r) => Eq (TimedResult tk r) Source # 
Instance details

Defined in Control.Schedule.Future

Methods

(==) :: TimedResult tk r -> TimedResult tk r -> Bool #

(/=) :: TimedResult tk r -> TimedResult tk r -> Bool #

(Ord tk, Ord r) => Ord (TimedResult tk r) Source # 
Instance details

Defined in Control.Schedule.Future

Methods

compare :: TimedResult tk r -> TimedResult tk r -> Ordering #

(<) :: TimedResult tk r -> TimedResult tk r -> Bool #

(<=) :: TimedResult tk r -> TimedResult tk r -> Bool #

(>) :: TimedResult tk r -> TimedResult tk r -> Bool #

(>=) :: TimedResult tk r -> TimedResult tk r -> Bool #

max :: TimedResult tk r -> TimedResult tk r -> TimedResult tk r #

min :: TimedResult tk r -> TimedResult tk r -> TimedResult tk r #

(Read tk, Read r) => Read (TimedResult tk r) Source # 
Instance details

Defined in Control.Schedule.Future

(Show tk, Show r) => Show (TimedResult tk r) Source # 
Instance details

Defined in Control.Schedule.Future

Methods

showsPrec :: Int -> TimedResult tk r -> ShowS #

show :: TimedResult tk r -> String #

showList :: [TimedResult tk r] -> ShowS #

Generic (TimedResult tk r) Source # 
Instance details

Defined in Control.Schedule.Future

Associated Types

type Rep (TimedResult tk r) :: Type -> Type #

Methods

from :: TimedResult tk r -> Rep (TimedResult tk r) x #

to :: Rep (TimedResult tk r) x -> TimedResult tk r #

type Rep (TimedResult tk r) Source # 
Instance details

Defined in Control.Schedule.Future

type Rep (TimedResult tk r) = D1 (MetaData "TimedResult" "Control.Schedule.Future" "schedule-0.2.0.0-K49JMtE71hY4NI1zeQoVl3" False) (C1 (MetaCons "TimedOut" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 tk)) :+: C1 (MetaCons "GotResult" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 r)))

data SFuture wo ro Source #

Constructors

SFWaiting !(OSet wo)

SExpects waiting on us

SFResult !ro

Result of the Future

Instances
(Eq wo, Eq ro) => Eq (SFuture wo ro) Source # 
Instance details

Defined in Control.Schedule.Future

Methods

(==) :: SFuture wo ro -> SFuture wo ro -> Bool #

(/=) :: SFuture wo ro -> SFuture wo ro -> Bool #

(Ord wo, Ord ro) => Ord (SFuture wo ro) Source # 
Instance details

Defined in Control.Schedule.Future

Methods

compare :: SFuture wo ro -> SFuture wo ro -> Ordering #

(<) :: SFuture wo ro -> SFuture wo ro -> Bool #

(<=) :: SFuture wo ro -> SFuture wo ro -> Bool #

(>) :: SFuture wo ro -> SFuture wo ro -> Bool #

(>=) :: SFuture wo ro -> SFuture wo ro -> Bool #

max :: SFuture wo ro -> SFuture wo ro -> SFuture wo ro #

min :: SFuture wo ro -> SFuture wo ro -> SFuture wo ro #

(Ord wo, Read wo, Read ro) => Read (SFuture wo ro) Source # 
Instance details

Defined in Control.Schedule.Future

Methods

readsPrec :: Int -> ReadS (SFuture wo ro) #

readList :: ReadS [SFuture wo ro] #

readPrec :: ReadPrec (SFuture wo ro) #

readListPrec :: ReadPrec [SFuture wo ro] #

(Show wo, Show ro) => Show (SFuture wo ro) Source # 
Instance details

Defined in Control.Schedule.Future

Methods

showsPrec :: Int -> SFuture wo ro -> ShowS #

show :: SFuture wo ro -> String #

showList :: [SFuture wo ro] -> ShowS #

Generic (SFuture wo ro) Source # 
Instance details

Defined in Control.Schedule.Future

Associated Types

type Rep (SFuture wo ro) :: Type -> Type #

Methods

from :: SFuture wo ro -> Rep (SFuture wo ro) x #

to :: Rep (SFuture wo ro) x -> SFuture wo ro #

type Rep (SFuture wo ro) Source # 
Instance details

Defined in Control.Schedule.Future

type Rep (SFuture wo ro) = D1 (MetaData "SFuture" "Control.Schedule.Future" "schedule-0.2.0.0-K49JMtE71hY4NI1zeQoVl3" False) (C1 (MetaCons "SFWaiting" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (OSet wo))) :+: C1 (MetaCons "SFResult" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ro)))

_SFResult :: forall wo ro ro. Prism (SFuture wo ro) (SFuture wo ro) ro ro Source #

_SFWaiting :: forall wo ro wo. Prism (SFuture wo ro) (SFuture wo ro) (OSet wo) (OSet wo) Source #

data SExpect wi ri tk Source #

Constructors

SExpect 

Fields

  • seExpects :: !(OMap wi (Task tk))

    SFutures we're waiting for, with our own timeout.

    Note that the SFuture might have its own separate timeout which is different; this t timeout is when *we* stop waiting on it.

    For example if (i ~ TimedResult a) and our timeout is longer than their timeout then seResults will get a GotResult (TimedOut t).

  • seResults :: !(OMap wi (TimedResult tk ri))

    SFutures that have completed, with the result. This is meant to be a holding place and the caller of this should move items from here into some other place to indicate that the results have been processed, so that if it is called twice it does not process these results twice.

Instances
(Eq wi, Eq tk, Eq ri) => Eq (SExpect wi ri tk) Source # 
Instance details

Defined in Control.Schedule.Future

Methods

(==) :: SExpect wi ri tk -> SExpect wi ri tk -> Bool #

(/=) :: SExpect wi ri tk -> SExpect wi ri tk -> Bool #

(Ord wi, Ord tk, Ord ri) => Ord (SExpect wi ri tk) Source # 
Instance details

Defined in Control.Schedule.Future

Methods

compare :: SExpect wi ri tk -> SExpect wi ri tk -> Ordering #

(<) :: SExpect wi ri tk -> SExpect wi ri tk -> Bool #

(<=) :: SExpect wi ri tk -> SExpect wi ri tk -> Bool #

(>) :: SExpect wi ri tk -> SExpect wi ri tk -> Bool #

(>=) :: SExpect wi ri tk -> SExpect wi ri tk -> Bool #

max :: SExpect wi ri tk -> SExpect wi ri tk -> SExpect wi ri tk #

min :: SExpect wi ri tk -> SExpect wi ri tk -> SExpect wi ri tk #

(Ord wi, Read wi, Read tk, Read ri) => Read (SExpect wi ri tk) Source # 
Instance details

Defined in Control.Schedule.Future

Methods

readsPrec :: Int -> ReadS (SExpect wi ri tk) #

readList :: ReadS [SExpect wi ri tk] #

readPrec :: ReadPrec (SExpect wi ri tk) #

readListPrec :: ReadPrec [SExpect wi ri tk] #

(Show wi, Show tk, Show ri) => Show (SExpect wi ri tk) Source # 
Instance details

Defined in Control.Schedule.Future

Methods

showsPrec :: Int -> SExpect wi ri tk -> ShowS #

show :: SExpect wi ri tk -> String #

showList :: [SExpect wi ri tk] -> ShowS #

Generic (SExpect wi ri tk) Source # 
Instance details

Defined in Control.Schedule.Future

Associated Types

type Rep (SExpect wi ri tk) :: Type -> Type #

Methods

from :: SExpect wi ri tk -> Rep (SExpect wi ri tk) x #

to :: Rep (SExpect wi ri tk) x -> SExpect wi ri tk #

Ord wi => Semigroup (SExpect wi ri tk) Source # 
Instance details

Defined in Control.Schedule.Future

Methods

(<>) :: SExpect wi ri tk -> SExpect wi ri tk -> SExpect wi ri tk #

sconcat :: NonEmpty (SExpect wi ri tk) -> SExpect wi ri tk #

stimes :: Integral b => b -> SExpect wi ri tk -> SExpect wi ri tk #

Ord wi => Monoid (SExpect wi ri tk) Source # 
Instance details

Defined in Control.Schedule.Future

Methods

mempty :: SExpect wi ri tk #

mappend :: SExpect wi ri tk -> SExpect wi ri tk -> SExpect wi ri tk #

mconcat :: [SExpect wi ri tk] -> SExpect wi ri tk #

type Rep (SExpect wi ri tk) Source # 
Instance details

Defined in Control.Schedule.Future

type Rep (SExpect wi ri tk) = D1 (MetaData "SExpect" "Control.Schedule.Future" "schedule-0.2.0.0-K49JMtE71hY4NI1zeQoVl3" False) (C1 (MetaCons "SExpect" PrefixI True) (S1 (MetaSel (Just "seExpects") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (OMap wi (Task tk))) :*: S1 (MetaSel (Just "seResults") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (OMap wi (TimedResult tk ri)))))

_seResults :: forall wi ri tk ri. Lens (SExpect wi ri tk) (SExpect wi ri tk) (OMap wi (TimedResult tk ri)) (OMap wi (TimedResult tk ri)) Source #

_seExpects :: forall wi ri tk. Lens' (SExpect wi ri tk) (OMap wi (Task tk)) Source #

data SFStatus e Source #

Constructors

Expecting e 
NotExpecting 
Instances
Eq e => Eq (SFStatus e) Source # 
Instance details

Defined in Control.Schedule.Future

Methods

(==) :: SFStatus e -> SFStatus e -> Bool #

(/=) :: SFStatus e -> SFStatus e -> Bool #

Ord e => Ord (SFStatus e) Source # 
Instance details

Defined in Control.Schedule.Future

Methods

compare :: SFStatus e -> SFStatus e -> Ordering #

(<) :: SFStatus e -> SFStatus e -> Bool #

(<=) :: SFStatus e -> SFStatus e -> Bool #

(>) :: SFStatus e -> SFStatus e -> Bool #

(>=) :: SFStatus e -> SFStatus e -> Bool #

max :: SFStatus e -> SFStatus e -> SFStatus e #

min :: SFStatus e -> SFStatus e -> SFStatus e #

Read e => Read (SFStatus e) Source # 
Instance details

Defined in Control.Schedule.Future

Show e => Show (SFStatus e) Source # 
Instance details

Defined in Control.Schedule.Future

Methods

showsPrec :: Int -> SFStatus e -> ShowS #

show :: SFStatus e -> String #

showList :: [SFStatus e] -> ShowS #

Generic (SFStatus e) Source # 
Instance details

Defined in Control.Schedule.Future

Associated Types

type Rep (SFStatus e) :: Type -> Type #

Methods

from :: SFStatus e -> Rep (SFStatus e) x #

to :: Rep (SFStatus e) x -> SFStatus e #

type Rep (SFStatus e) Source # 
Instance details

Defined in Control.Schedule.Future

type Rep (SFStatus e) = D1 (MetaData "SFStatus" "Control.Schedule.Future" "schedule-0.2.0.0-K49JMtE71hY4NI1zeQoVl3" False) (C1 (MetaCons "Expecting" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 e)) :+: C1 (MetaCons "NotExpecting" PrefixI False) (U1 :: Type -> Type))

type SFStatusFull wo tk = SFStatus (OSet wo, Task tk) Source #

data SFError Source #

Instances
Eq SFError Source # 
Instance details

Defined in Control.Schedule.Future

Methods

(==) :: SFError -> SFError -> Bool #

(/=) :: SFError -> SFError -> Bool #

Ord SFError Source # 
Instance details

Defined in Control.Schedule.Future

Read SFError Source # 
Instance details

Defined in Control.Schedule.Future

Show SFError Source # 
Instance details

Defined in Control.Schedule.Future

Generic SFError Source # 
Instance details

Defined in Control.Schedule.Future

Associated Types

type Rep SFError :: Type -> Type #

Methods

from :: SFError -> Rep SFError x #

to :: Rep SFError x -> SFError #

type Rep SFError Source # 
Instance details

Defined in Control.Schedule.Future

type Rep SFError = D1 (MetaData "SFError" "Control.Schedule.Future" "schedule-0.2.0.0-K49JMtE71hY4NI1zeQoVl3" False) (C1 (MetaCons "SFEAlreadyFinished" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SFEInvalidPrecondition" PrefixI True) (S1 (MetaSel (Just "sfePreExpect") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (SFStatus ())) :*: S1 (MetaSel (Just "sfePreActual") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (SFStatus ()))))

sCheckStatus :: (HasCallStack, Ord wi, Ord wo) => wi -> wo -> Lens' s (SFuture wo r) -> Lens' s (SExpect wi r tk) -> s -> SFStatusFull wo tk Source #

sExpectFuture :: (Ord wi, Ord wo) => TickDelta -> tk -> wi -> wo -> Lens' s (SFuture wo r) -> Lens' s (SExpect wi r tk) -> Lens' s (Schedule tk) -> s -> Either SFError s Source #

sExpectCancel :: (Ord wi, Ord wo) => wi -> wo -> Lens' s (SFuture wo r) -> Lens' s (SExpect wi r tk) -> Lens' s (Schedule tk) -> s -> Either SFError s Source #

sExpectTimeout :: (HasCallStack, Ord wi, Ord wo) => tk -> wi -> wo -> Lens' s (SFuture wo r) -> Lens' s (SExpect wi r tk) -> Lens' s (Schedule tk) -> s -> Either SFError s Source #

sFutureResult :: (Ord wi, Ord wo) => r -> wi -> Lens' s (SFuture wo r) -> IndexedTraversal' wo s (SExpect wi r tk) -> Lens' s (Schedule tk) -> s -> Either SFError s Source #