| Copyright | (c) 2014 Forkk | 
|---|---|
| License | MIT | 
| Maintainer | forkk@forkk.net | 
| Stability | experimental | 
| Portability | GHC only (requires throwTo) | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Control.Concurrent.Actor.Internal
Description
Module exposing more of hactor's internals. Use with caution.
- data ActorMessage msg => ActorHandle msg = ActorHandle {- ahContext :: ActorContext msg
- ahThread :: ThreadId
 
- class ActorMessage msg
- class (ActorMessage msg, MonadActorSuper m) => MonadActor msg m
- data ActorM msg a
- send :: (MonadIO m, ActorMessage msg) => ActorHandle msg -> msg -> m ()
- receive :: (ActorMessage msg, MonadActor msg m) => m msg
- receiveMaybe :: (ActorMessage msg, MonadActor msg m) => m (Maybe msg)
- receiveSTM :: (ActorMessage msg, MonadActor msg m) => m (STM msg)
- runActorM :: ActorMessage msg => ActorM msg a -> ActorContext msg -> IO a
- wrapActor :: ActorMessage msg => ActorM msg () -> IO (IO (), ActorContext msg)
- spawnActor :: ActorMessage msg => ActorM msg () -> IO (ActorHandle msg)
- runActor :: ActorMessage msg => ActorM msg () -> IO ()
- self :: (ActorMessage msg, MonadActor msg m) => m (ActorHandle msg)
- actorThread :: ActorMessage msg => ActorHandle msg -> ThreadId
- data ActorMessage msg => ActorContext msg = ActorContext {}
- type MailBox msg = TChan msg
- getContext :: (ActorMessage msg, MonadActor msg m) => m (ActorContext msg)
- getMailBox :: (ActorMessage msg, MonadActor msg m) => m (MailBox msg)
Types
data ActorMessage msg => ActorHandle msg Source
An ActorHandle acts as a reference to a specific actor.
Constructors
| ActorHandle | |
| Fields 
 | |
class ActorMessage msg Source
The ActorMessage class must be implemented by any type that will be sent
 as a message to actors.
 Any given type of actor will have one ActorMessage type that is sent to
 that actor. This ensures type safety.
 Currently this is simply a dummy class with nothing in it, but things may be
 added in the future.
Instances
| ActorMessage () | 
class (ActorMessage msg, MonadActorSuper m) => MonadActor msg m Source
The MonadActor typeclass. This provides the actorCtx function, which
 all of the actor monad's functionality is based on.
Minimal complete definition
actorCtx
Instances
| (ActorMessage msg, MonadActor msg m, MonadTrans t, MonadActorSuper (t m)) => MonadActor msg (t m) | |
| ActorMessage msg => MonadActor msg (ActorM msg) | 
The base actor monad.
Instances
| ActorMessage msg => MonadBase IO (ActorM msg) | |
| ActorMessage msg => MonadBaseControl IO (ActorM msg) | |
| ActorMessage msg => MonadActor msg (ActorM msg) | |
| Monad (ActorM msg) | |
| Functor (ActorM msg) | |
| Applicative (ActorM msg) | |
| MonadThrow (ActorM msg) | |
| MonadIO (ActorM msg) | |
| data StM (ActorM msg) = StMA { 
 | 
Sending Messages
send :: (MonadIO m, ActorMessage msg) => ActorHandle msg -> msg -> m () Source
Sends a message to the given actor handle.
Receiving Messages
receive :: (ActorMessage msg, MonadActor msg m) => m msg Source
Reads a message from the actor's mail box.
 If there are no messages, blocks until one is received. If you don't want
 this, use receiveMaybe instead.
receiveMaybe :: (ActorMessage msg, MonadActor msg m) => m (Maybe msg) Source
Reads a message from the actor's mail box.
 If there are no messages, returns Nothing.
receiveSTM :: (ActorMessage msg, MonadActor msg m) => m (STM msg) Source
An ActorM action which returns an STM action to receive a message.
Spawning Actors
runActorM :: ActorMessage msg => ActorM msg a -> ActorContext msg -> IO a Source
Runs the given ActorM in the IO monad with the given context.
wrapActor :: ActorMessage msg => ActorM msg () -> IO (IO (), ActorContext msg) Source
Internal function for starting actors.
 This takes an ActorM action, makes a channel for it, wraps it in exception
 handling stuff, and turns it into an IO monad. The function returns a tuple
 containing the actor's context and the IO action to execute the actor.
spawnActor :: ActorMessage msg => ActorM msg () -> IO (ActorHandle msg) Source
Spawns the given actor on another thread and returns a handle to it.
runActor :: ActorMessage msg => ActorM msg () -> IO () Source
Runs the given actor on the current thread. This function effectively turns the current thread into the actor's thread. Obviously, this means that this function will block until the actor exits. You probably want to use this for your "main" actor.
Getting Information
self :: (ActorMessage msg, MonadActor msg m) => m (ActorHandle msg) Source
Gets a handle to the current actor.
actorThread :: ActorMessage msg => ActorHandle msg -> ThreadId Source
Gets the thread ID for the given actor handle.
Internals
data ActorMessage msg => ActorContext msg Source
The ActorContext holds shared information about a given actor.
 This is information such as the actor's mail box, the list of actors it's
 linked to, etc.
Constructors
| ActorContext | |
getContext :: (ActorMessage msg, MonadActor msg m) => m (ActorContext msg) Source
Gets the internal context object for the current actor. This is an internal function and may be dangerous. Use with caution.
getMailBox :: (ActorMessage msg, MonadActor msg m) => m (MailBox msg) Source
Retrieves the mail box for the current actor. This is an internal function and may be dangerous. Use with caution.