simple-actors-0.2.0: A library for more structured concurrent programming, based on the Actor Model

Safe HaskellNone

Control.Concurrent.Actors

Contents

Synopsis

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.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...

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.

newtype Behavior i Source

Constructors

Receive 

Fields

headAction :: Action i (Behavior i)
 

Instances

Contravariant Behavior 
Monoid (Behavior i)

b1 mplus b2 has the headAction of b2 begin where the yield occured in b1, i.e. b2's first input will be the final input handed to b1.

Composing Behaviors

(<.|>) :: Behavior i -> Behavior i -> Behavior iSource

Sequence two Behaviors. After the first yields the second takes over, discarding the message the former was processing. See also the Monoid instance for Behavior.

 b <.|> b' = b `mappend` constB b'

Available actions

Message passing

data Mailbox a Source

One can send a messages to a Mailbox where it will be processed according to an actor's defined Behavior

send :: (MonadIO m, SplitChan c x) => c a -> a -> m ()Source

Send a message asynchronously. This can be used to send messages to other Actors via a Mailbox, or used as a means of output from the Actor system to IO since the function is polymorphic.

 send b = liftIO . writeChan b

received :: Action i iSource

Return the message received to start this Action block. N.B the value returned here does not change between calls in the same Action.

 received = ask

guardReceived :: (i -> Bool) -> Action i iSource

Return received message matching predicate, otherwise yield.

 guardReceived p = ask >>= \i-> guard (p i) >> return i

Spawning actors

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" 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 "first" b2
     yield

spawn :: MonadIO m => Behavior i -> m (Mailbox i)Source

Fork an actor performing the specified Behavior. N.B. an actor begins execution of its headBehavior only after a mesage has been received. See also spawn_.

spawn_ :: MonadIO m => Behavior () -> m ()Source

Fork a looping computation which starts immediately. Equivalent to launching a Behavior () and another Behavior that sends an infinite stream of ()s to the former's Mailbox.

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.

yield :: Action i aSource

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 as:

 receive = return . Receive

Utility functions

These are useful for debugging Behaviors

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 Behaviors

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.

putStrB :: (Eq n, Num n) => n -> Behavior StringSource

Like printB but using putStr.

signalB :: SplitChan c x => c () -> Behavior iSource

Sends a () to the passed chan. This is useful with mappend for signalling the end of some other Behavior.

 signalB c = Receive (send c () >> yield)

constB :: Behavior i -> Behavior iSource

A Behavior that discard its first input, returning the passed Behavior for processing subsequent inputs. Useful with Alternative or Monoid compositions when one wants to ignore the leftover yielded message.

 constB = Receive . return