stm-actor-0.2.3.1: A simplistic actor model based on STM
Copyright(c) Samuel Schlesinger 2020
LicenseMIT
Maintainersgschlesinger@gmail.com
Stabilityexperimental
PortabilityPOSIX, Windows
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Concurrent.Actor

Description

 
Synopsis

Documentation

data ActionT message m a Source #

A type that contains the actions that Actors will do.

Instances

Instances details
(MonadWriter w m, MonadReader r m, MonadState s m) => MonadRWS r w s (ActionT message m) Source # 
Instance details

Defined in Control.Concurrent.Actor

MonadWriter w m => MonadWriter w (ActionT message m) Source # 
Instance details

Defined in Control.Concurrent.Actor

Methods

writer :: (a, w) -> ActionT message m a #

tell :: w -> ActionT message m () #

listen :: ActionT message m a -> ActionT message m (a, w) #

pass :: ActionT message m (a, w -> w) -> ActionT message m a #

MonadState s m => MonadState s (ActionT message m) Source # 
Instance details

Defined in Control.Concurrent.Actor

Methods

get :: ActionT message m s #

put :: s -> ActionT message m () #

state :: (s -> (a, s)) -> ActionT message m a #

MonadReader r m => MonadReader r (ActionT message m) Source # 
Instance details

Defined in Control.Concurrent.Actor

Methods

ask :: ActionT message m r #

local :: (r -> r) -> ActionT message m a -> ActionT message m a #

reader :: (r -> a) -> ActionT message m a #

MonadError e m => MonadError e (ActionT message m) Source # 
Instance details

Defined in Control.Concurrent.Actor

Methods

throwError :: e -> ActionT message m a #

catchError :: ActionT message m a -> (e -> ActionT message m a) -> ActionT message m a #

MonadTrans (ActionT message) Source # 
Instance details

Defined in Control.Concurrent.Actor

Methods

lift :: Monad m => m a -> ActionT message m a #

Monad m => Monad (ActionT message m) Source # 
Instance details

Defined in Control.Concurrent.Actor

Methods

(>>=) :: ActionT message m a -> (a -> ActionT message m b) -> ActionT message m b #

(>>) :: ActionT message m a -> ActionT message m b -> ActionT message m b #

return :: a -> ActionT message m a #

Functor m => Functor (ActionT message m) Source # 
Instance details

Defined in Control.Concurrent.Actor

Methods

fmap :: (a -> b) -> ActionT message m a -> ActionT message m b #

(<$) :: a -> ActionT message m b -> ActionT message m a #

Applicative m => Applicative (ActionT message m) Source # 
Instance details

Defined in Control.Concurrent.Actor

Methods

pure :: a -> ActionT message m a #

(<*>) :: ActionT message m (a -> b) -> ActionT message m a -> ActionT message m b #

liftA2 :: (a -> b -> c) -> ActionT message m a -> ActionT message m b -> ActionT message m c #

(*>) :: ActionT message m a -> ActionT message m b -> ActionT message m b #

(<*) :: ActionT message m a -> ActionT message m b -> ActionT message m a #

MonadIO m => MonadIO (ActionT message m) Source # 
Instance details

Defined in Control.Concurrent.Actor

Methods

liftIO :: IO a -> ActionT message m a #

MonadCont m => MonadCont (ActionT message m) Source # 
Instance details

Defined in Control.Concurrent.Actor

Methods

callCC :: ((a -> ActionT message m b) -> ActionT message m a) -> ActionT message m a #

MonadUnliftIO m => MonadUnliftIO (ActionT message m) Source # 
Instance details

Defined in Control.Concurrent.Actor

Methods

withRunInIO :: ((forall a. ActionT message m a -> IO a) -> IO b) -> ActionT message m b #

data Actor message Source #

A handle to do things to actors, like sending them messages, fiddling with their threads, or adding an effect that will occur after they've finished executing.

Instances

Instances details
Contravariant Actor Source # 
Instance details

Defined in Control.Concurrent.Actor

Methods

contramap :: (a -> b) -> Actor b -> Actor a #

(>$) :: b -> Actor b -> Actor a #

Eq (Actor message) Source # 
Instance details

Defined in Control.Concurrent.Actor

Methods

(==) :: Actor message -> Actor message -> Bool #

(/=) :: Actor message -> Actor message -> Bool #

Show (Actor message) Source # 
Instance details

Defined in Control.Concurrent.Actor

Methods

showsPrec :: Int -> Actor message -> ShowS #

show :: Actor message -> String #

showList :: [Actor message] -> ShowS #

send :: Actor message -> message -> STM () Source #

Send a message to this Actor.

addAfterEffect :: Actor message -> (Maybe SomeException -> IO ()) -> STM () Source #

Once the Actor dies, all of the effects that have been added via this function will run. This is how you can implement your own functions like link or linkSTM.

threadId :: Actor message -> ThreadId Source #

Retrieve the ThreadId associated with this Actor.

livenessCheck :: Actor message -> STM Liveness Source #

Checks the Liveness of a particular Actor

withLivenessCheck :: (Actor message -> x -> STM ()) -> Actor message -> x -> STM () Source #

Allows us to wrap addAfterEffect, send, and any other custom combinators in a liveness check. This causes contention on the underlying TVar that contains the status report of the Actor, and thus should be avoided where possible. That being said, it is also useful to avoid sending messages or add after effects to dead actors, which will certainly be lost forever. If the Actor is Completed or ThrewException, then we throw an ActorDead exception with Nothing or Just the exception, respectively.

data Liveness Source #

The liveness state of a particular Actor.

Instances

Instances details
Show Liveness Source # 
Instance details

Defined in Control.Concurrent.Actor

data ActorDead Source #

The exception thrown when we run an action wrapped in withLivenessCheck on an Actor which has died.

Constructors

ActorDead (Maybe SomeException) 

actFinally :: (Either SomeException a -> IO ()) -> ActionT message IO a -> IO (Actor message) Source #

Perform some ActionT in a thread, with some cleanup afterwards.

act :: ActionT message IO a -> IO (Actor message) Source #

Perform some ActionT in a thread.

receiveSTM :: MonadIO m => (message -> STM a) -> ActionT message m a Source #

Receive a message and, in the same transaction, produce some result.

receive :: MonadIO m => (message -> ActionT message m a) -> ActionT message m a Source #

Receive a message and do some ActionT with it.

hoistActionT :: (forall x. m x -> n x) -> ActionT message m a -> ActionT message n a Source #

Use a natural transformation to transform an ActionT on one base monad to another.

link :: MonadIO m => Actor message -> ActionT message' m () Source #

Link the lifetime of the given actor to this one. If the given actor dies, it will throw a LinkKill exception to us with its ThreadId attached to it.

linkSTM :: Actor message -> Actor message' -> STM () Source #

Links the lifetime of the first actor to the second. If the second actor's thread dies, it will throw a LinkKill exception to the first with its ThreadId attached to it.

data LinkKill Source #

The exception thrown when an actor we've linked with has died.

Constructors

LinkKill ThreadId 

self :: Applicative m => ActionT message m (Actor message) Source #

Returns the Actor handle of the actor executing this action.

murder :: MonadIO m => Actor message -> m () Source #

Throws a MurderKill exception to the given Actor.

data MurderKill Source #

The exception thrown when we murder an Actor.

Constructors

MurderKill ThreadId