Control.Concurrent.Actors
Contents
- data Action i a
- newtype Behavior i = Receive {
- headAction :: Action i (Behavior i)
- (<.|>) :: Behavior i -> Behavior i -> Behavior i
- data Mailbox a
- send :: (MonadIO m, SplitChan c x) => c a -> a -> m ()
- received :: Action i i
- guardReceived :: (i -> Bool) -> Action i i
- spawn :: MonadIO m => Behavior i -> m (Mailbox i)
- spawn_ :: MonadIO m => Behavior () -> m ()
- spawnReading :: (MonadIO m, SplitChan x c) => c i -> Behavior i -> m ()
- yield :: Action i a
- receive :: Action i (Behavior i) -> Action i (Behavior i)
- runBehavior_ :: Behavior () -> IO ()
- runBehavior :: Behavior a -> [a] -> IO ()
- printB :: (Show s, Num n) => n -> Behavior s
- putStrB :: Num n => n -> Behavior String
- signalB :: SplitChan c x => c () -> Behavior i
- constB :: Behavior i -> Behavior i
Documentation
Here we demonstrate a binary tree of actors that supports insert and query operations:
import Control.Concurrent.Actors
import Control.Applicative
import Control.Concurrent.MVar
-- the actor equivalent of a Nil leaf node:
nil :: Behavior Operation
nil = Receive $ do
(Query _ var) <- received
send var False -- signal Int is not present in tree
return nil -- await next message
<|> do -- else, Insert received
l <- spawn nil -- spawn child nodes
r <- spawn nil
branch l r . val <$> received -- create branch from inserted val
-- a branch node with a value 'v' and two children
branch :: Node -> Node -> Int -> Behavior Operation
branch l r v = loop where
loop = Receive $ do
m <- received
case compare (val m) v of
LT -> send l m
GT -> send r m
EQ -> case m of -- signal Int present in tree:
(Query _ var) -> send var True
_ -> return ()
return loop
type Node = Mailbox Operation
-- operations supported by the network:
data Operation = Insert { val :: Int }
| Query { val :: Int
, sigVar :: MVar Bool }
insert :: Node -> Int -> IO ()
insert t = send t . Insert
-- MVar is in the 'SplitChan' class so actors can 'send' to it:
query :: Node -> Int -> IO Bool
query t a = do
v <- newEmptyMVar
send t (Query a v)
takeMVar v
You can use the tree defined above in GHCi:
>>>:l TreeExample.hsOk>>>t <- spawn nil>>>query t 7False>>>insert t 7>>>query t 7True
Actor Behaviors
In the Actor Model, at each step an actor...
- processes a single
receivedmessage - may
spawnnew actors - may
sendmessages to other actors -
returns theBehaviorfor processing the next message
These actions take place within the Action i monad, where i is the type
of the input message the actor receives.
N.B.: the MonadIO instance here is an abstraction leak. An example of a
good use of liftIO might be to give an Action access to a source of
randomness.
An actor is created by spawning a Behavior. Behaviors consist of
a composed Action that is executed when a message is received and
returns the Behavior for processing the next input.
Constructors
| Receive | |
Fields
| |
Instances
| Contravariant Behavior | |
| Monoid (Behavior i) |
|
Composing Behaviors
Available actions
Message passing
One can send a messages to a Mailbox where it will be processed
according to an actor's defined Behavior
Instances
| Contravariant Mailbox | |
| SplitChan Mailbox Messages | |
| NewSplitChan Mailbox Messages |
guardReceived :: (i -> Bool) -> Action i iSource
Spawning actors
spawnReading :: (MonadIO m, SplitChan x c) => c i -> Behavior i -> m ()Source
Like spawn but allows one to specify explicitly the channel from which
an actor should take its input. Useful for extending the library to work
over other channels.
Building an actor computation
An actor computation can be halted immediately by calling yield,
a synonym for mzero. When an Action calling yield is composed with
another using | the second takes over processing the same input
which the former yield-ed on.
Here is an example of a computation using guard which returns mzero if
the test is false:
foo c n = Receive $
do i <- received
guard (n<10)
send c i
return (foo c $ n+1)
<|> do i <- received -- same as the 'i' above
send c $ "TENTH INPUT: "++i
return (foo c 0)
The Monoid instance for Behavior works on the same principle.
Immediately give up processing an input, perhaps relinquishing the input
to an Alternative computation or exiting the actor.
yield = mzero
receive :: Action i (Behavior i) -> Action i (Behavior i)Source
Useful to make defining a continuing Behavior more readable as a "receive block", e.g.
pairUp out = Receive $ do
a <- received
receive $ do
b <- received
send out (b,a)
return (pairUp out)
Defined: receive = return . Receive
Utility functions
runBehavior_ :: Behavior () -> IO ()Source
Run a Behavior () in the main thread, returning when the computation
exits.
runBehavior :: Behavior a -> [a] -> IO ()Source
run a Behavior in the IO monad, taking its "messages" from the list.
Useful for debugging Behaviors.
Useful predefined Behaviors
printB :: (Show s, Num n) => n -> Behavior sSource
Prints all messages to STDOUT in the order they are received,
yield-ing immediately after n inputs are printed.