| Portability | portable |
|---|---|
| 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?). An actor is parametrised by the type of messages it receives and the type of messages it sends.
Here is an example:
act1 :: Actor Int Int
act1 = forever $ do
(num, addr) <- receive
liftIO . putStrLn $ "act1: received " ++ (show num)
send addr (num + 1)
act2 :: Int -> Address Int Int -> Actor Int Int
act2 n0 addr = do
send addr n0
forever $ do
(num, addr1) <- receive
liftIO . putStrLn $ "act2: received " ++ (show num)
send addr1 (num + 1)
main = do
addr1 <- spawn act1
addr2 <- spawn $ act2 0 addr1
threadDelay 20000000
- data Address a b
- type ActorM a b = ReaderT (Mailbox a b) IO
- type Actor a b = ActorM a b ()
- send :: Address a b -> a -> ActorM b a ()
- (◁) :: Address a b -> a -> ActorM b a ()
- (▷) :: a -> Address a b -> ActorM b a ()
- receive :: ActorM a b (a, Address b a)
- receiveWithTimeout :: Int -> ActorM a b (Maybe (a, Address b a))
- spawn :: Actor a b -> IO (Address a b)
Types
The address of an actor that accepts messages of type a and sends messages of type b
type ActorM a b = ReaderT (Mailbox a b) IOSource
The actor monad, just a reader monad on top of IO.
It carries information about an actor's mailbox, which is
hidden from the library's users.
type Actor a b = ActorM a b ()Source
The type of an actor accepting messages of type a and
returning messages of type b. It is just a monadic action
in the ActorM monad, returning ()
Actor actions
receive :: ActorM a b (a, Address b a)Source
Receive a message inside the ActorM monad. Blocks until
a message arrives if the mailbox is empty