| Portability | GHC only (requires throwTo) |
|---|---|
| Stability | alpha |
| Maintainer | alexander.the.average@gmail.com |
Control.Concurrent.Actor
Contents
Description
This module implements Erlang-style actors (what Erlang calls processes). It does not implement network distribution (yet?). Here is an example:
act1 :: Actor
act1 = do
me <- self
liftIO $ print act1 started
forever $ receive
[ Case $ ((n, a) :: (Int, Address)) ->
if n > 10000
then do
liftIO . throwIO $ NonTermination
else do
liftIO . putStrLn $ act1 got ++ (show n) ++ from ++ (show a)
send a (n+1, me)
, Case $ (e :: RemoteException) ->
liftIO . print $ act1 received a remote exception
, Default $ liftIO . print $ act1: received a malformed message
]
act2 :: Address -> Actor
act2 addr = do
monitor addr
-- setFlag TrapRemoteExceptions
me <- self
send addr (0 :: Int, me)
forever $ receive
[ Case $ ((n, a) :: (Int, Address)) -> do
liftIO . putStrLn $ act2 got ++ (show n) ++ from ++ (show a)
send a (n+1, me)
, Case $ (e :: RemoteException) ->
liftIO . print $ act2 received a remote exception: ++ (show e)
]
act3 :: Address -> Actor
act3 addr = do
monitor addr
setFlag TrapRemoteExceptions
forever $ receive
[ Case $ (e :: RemoteException) ->
liftIO . print $ act3 received a remote exception: ++ (show e)
]
main = do
addr1 <- spawn act1
addr2 <- spawn (act2 addr1)
spawn (act3 addr2)
threadDelay 20000000
- data Address
- data Handler
- type ActorM = ReaderT Context IO
- type Actor = ActorM ()
- data RemoteException
- data ActorExitNormal
- data Flag = TrapRemoteExceptions
- send :: Typeable m => Address -> m -> ActorM ()
- (◁) :: Typeable m => Address -> m -> ActorM ()
- (▷) :: Typeable m => m -> Address -> ActorM ()
- self :: ActorM Address
- receive :: [Handler] -> ActorM ()
- receiveWithTimeout :: Int -> [Handler] -> ActorM () -> ActorM ()
- spawn :: Actor -> IO Address
- monitor :: Address -> ActorM ()
- link :: Address -> ActorM ()
- setFlag :: Flag -> ActorM ()
- clearFlag :: Flag -> ActorM ()
- toggleFlag :: Flag -> ActorM ()
- testFlag :: Flag -> ActorM Bool
Types
The address of an actor, used to send messages
The type of an actor. It is just a monadic action
in the ActorM monad, returning ()
data RemoteException Source
data ActorExitNormal Source
Exception raised by an actor on exit
Actor actions
receive :: [Handler] -> ActorM ()Source
Try to handle a message using a list of handlers. The first handler matching the type of the message is used.
receiveWithTimeout :: Int -> [Handler] -> ActorM () -> ActorM ()Source
Same as receive, but times out after a specified amount of time and runs a default action
monitor :: Address -> ActorM ()Source
Monitors the actor at the specified address.
If an exception is raised in the monitored actor's
thread, it is wrapped in an ActorException and
forwarded to the monitoring actor. If the monitored
actor terminates, an ActorException is raised in
the monitoring Actor
toggleFlag :: Flag -> ActorM ()Source
Toggles the specified flag in the actor's environment