Safe Haskell | None |
---|
- data Action i a
- newtype Behavior i = Receive {
- headAction :: Action i (Behavior i)
- (<.|>) :: Behavior i -> Behavior i -> Behavior i
- data Mailbox a
- out :: SplitChan i x => i a -> Mailbox a
- send :: MonadIO m => Mailbox a -> a -> m ()
- send' :: MonadIO m => Mailbox a -> a -> m ()
- (<->) :: MonadIO m => a -> m (Mailbox a) -> m (Mailbox a)
- received :: Action i i
- guardReceived :: (i -> Bool) -> Action i i
- class Sources s where
- type Joined s
- spawn :: (MonadIO m, Sources s) => Behavior (Joined s) -> m s
- yield :: Action i a
- receive :: Action i (Behavior i) -> Action i (Behavior i)
- coproductMb :: Mailbox a -> Mailbox b -> Mailbox (Either a b)
- contraProduct :: Contravariant f => f (Either a b) -> (f a, f b)
- zipMb :: Mailbox a -> Mailbox b -> Mailbox (a, b)
- contraFanin :: Contravariant f => (b -> a) -> (c -> a) -> f a -> f (Either b c)
- contraFanout :: Contravariant f => (a -> b) -> (a -> c) -> f (b, c) -> f a
- runBehavior_ :: Behavior () -> IO ()
- runBehavior :: Behavior a -> [a] -> IO ()
- printB :: (Show s, Eq n, Num n) => n -> Behavior s
- putStrB :: (Eq n, Num n) => n -> Behavior String
- signalB :: Mailbox () -> Behavior i
- constB :: Behavior i -> Behavior i
Documentation
Here we demonstrate a binary tree of actors that supports concurrent 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 :: Mailbox Bool } insert :: Node -> Int -> IO () insert t = send t . Insert query :: Node -> Int -> IO Bool query t a = do -- turn an MVar into a Mailbox actors can send to with 'out' v <- newEmptyMVar send t (Query a $ out v) takeMVar v
You can use the tree defined above in GHCi:
>>>
:l TreeExample.hs
Ok>>>
t <- spawn nil
>>>
query t 7
False>>>
insert t 7
>>>
query t 7
True
Actor Behaviors
In the Actor Model, at each step an actor...
- processes a single
received
message - may
spawn
new actors - may
send
messages to other actors -
return
s theBehavior
for 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 spawn
ing 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.
Receive | |
|
Contravariant Behavior | |
Monoid (Behavior i) |
|
Composing and Transforming 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
type Joined (Mailbox a) = a
Contravariant Mailbox | |
SplitChan Mailbox Messages | |
NewSplitChan Mailbox Messages | |
Sources (Mailbox a) |
out :: SplitChan i x => i a -> Mailbox aSource
Convert the input side of a SplitChan
to a Mailbox
. Useful for
sending data out from an actor system via a channel created in IO.
(<->) :: MonadIO m => a -> m (Mailbox a) -> m (Mailbox a)Source
Like send
but supports chaining sends by returning the Mailbox.
Convenient for initializing an Actor with its first input after spawning,
e.g.
do mb <- 0 <-> spawn foo
guardReceived :: (i -> Bool) -> Action i iSource
Spawning actors
We extend the actor model to support joining (or synchronizing) multiple
Mailbox
es to a single Behavior
input type, using a new class with an
associated type. Functionality is best explained by example:
Spawn an actor returning it's Mailbox
, and send it its first message:
sumTuple :: Behavior (Int, Int) do b <- spawn sumTuple send b (4, 1) ...
But now we would like our sumTuple
actor to receive each number from a different
concurrent actor:
do (b1, b2) <- spawn sumTuple b3 <- spawn (multipliesBy2AndSendsTo b1) send b3 2 send b2 1 ...
Lastly spawn an actor that starts immediately on an infinite supply of ()
s,
and supplies an endless stream of Int
s to sumTuple
do (b1, b2) <- spawn sumTuple () <- spawn (sendsIntsTo b2) send b1 4 ...
Sources () | type Joined () = () Represents an endless supply of do () <- spawn startsImmediately -- :: Behavior () |
Sources (Mailbox a) | |
(Sources a, Sources b) => Sources (a, b) | |
(Sources a, Sources b, Sources c) => Sources (a, b, c) | |
(Sources a, Sources b, Sources c, Sources d) => Sources (a, b, c, d) | |
(Sources a, Sources b, Sources c, Sources d, Sources e) => Sources (a, b, c, d, e) | |
(Sources a, Sources b, Sources c, Sources d, Sources e, Sources f) => Sources (a, b, c, d, e, f) | |
(Sources a, Sources b, Sources c, Sources d, Sources e, Sources f, Sources g) => Sources (a, b, c, d, e, f, g) |
Mailboxes and scoping
Straightforward use of the spawn
function will be sufficient for
forking actors in most cases, but launching mutually-communicating actors
presents a problem.
In cases where a Behavior
needs access to its own Mailbox
or that of
an actor that must be forked later, the MonadFix
instance should be
used. GHC's "Recursive Do" notation make this especially easy:
beh = Receive $ do i <- received -- similar to the scoping in a "let" block: rec b1 <- spawn (senderTo b2) b2 <- spawn (senderTo b1) b3 <- spawn (senderTo b3) -- send initial messages to actors spawned above: send b3 i send b2 "first" yield
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.
pairUpAndSendTo mb = Receive $ do a <- received receive $ do b <- received send mb (b,a) return (pairUpAndSendTo mb)
Defined as:
receive = return . Receive
Composing and Transforming Mailboxes
We offer some operations to split and combine Mailbox
es of sum and
product types.
contraProduct :: Contravariant f => f (Either a b) -> (f a, f b)Source
contraProduct = contramap Left &&& contramap Right
contraFanin :: Contravariant f => (b -> a) -> (c -> a) -> f a -> f (Either b c)Source
contraFanin f g = contramap (f ||| g)
contraFanout :: Contravariant f => (a -> b) -> (a -> c) -> f (b, c) -> f aSource
contraFanout f g = contramap (f &&& g)
Utility functions
These are useful for debugging Behavior
s
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 predefined Behavior
s
printB :: (Show s, Eq n, Num n) => n -> Behavior sSource
Prints all messages to STDOUT in the order they are received,
yield
-ing immediately after n
inputs are printed.