[Haskell-cafe] ANNOUNCE: simple-actors 0.1.0 - an eDSL library for actor model concurrency

Felipe Almeida Lessa felipe.lessa at gmail.com
Wed Oct 12 04:57:42 CEST 2011


On Tue, Oct 11, 2011 at 2:37 PM, Brandon Simmons
<brandon.m.simmons at gmail.com> wrote:
> I'm happy to announce the release of my library 'simple-actors', a
> DSL-style library for more structured concurrent programs based on the
> Actor Model. It offers an alternative to ad-hoc use of Chans that
> allows for tight control of side-effects and message passing, and is
> especially suited to applications such as  simulations of
> communicating processes.

Pretty interesting!

> Here is an example of a system of actors working as a binary tree,
> supporting insert and query operations:
[snip]

I'm kind of spoiled after having used Haskell for a long time, so I
couldn't ignore the fact that your example is tied to Ints and don't
store a value =).  So I've changed the example, as seen below.  It's
somewhat more complex, but I like the fact that now 'branch' has to
deal with updating the value of its key =).

-----8<-----BEGIN-EXAMPLE-----8<----
module Main
   where

import Control.Concurrent.Actors
import Control.Applicative
import Control.Concurrent.MVar

type Node k v = Mailbox (Operation k v)

-- operations supported by the network:
data Operation k v = Insert { key :: k
                            , val :: v }
                   | Query  { key    :: k
                            , sigVar :: MVar (Maybe v) }

-- the actor equivalent of a Nil leaf node:
nil :: Ord k => Behavior (Operation k v)
nil = Receive $ do
   (Query _key var) <- received
   send var Nothing -- signal that key is not present in tree
   return nil       -- await next message

  <|> do          -- else, Insert received
   l <- spawn nil -- spawn child nodes
   r <- spawn nil
   (Insert key val) <- received
   return $ branch l r key val -- create branch from inserted val

-- a "branch" node with a key-value pair and two children
branch :: Ord k => Node k v -> Node k v -> k -> v -> Behavior (Operation k v)
branch l r k = go
  where
    go v = Receive $ do
             m <- received
             case compare (key m) k of
               LT -> send l m >> cont v
               GT -> send r m >> cont v
               EQ -> case m of
                       (Query _ var)  -> send var (Just v) >> cont v
                       (Insert _ val) -> cont val
    cont = return . go


insert :: Node k v -> (k, v) -> IO ()
insert t (k,v) = send t (Insert k v)

-- MVar is in the 'SplitChan' class so actors can 'send' to it:
query :: Node k v -> k -> IO (Maybe v)
query t k = do
   v <- newEmptyMVar
   send t (Query k v)
   takeMVar v

main :: IO ()
main = do
   t <- spawn nil
   mapM_ (insert t) [(5, "five"),  (3, "three"), (7, "seven"),
                     (2, "two"),   (4, "four"),  (6, "six"),
                     (8, "eight"), (5, "BOO!")]
   mapM (query t) [1,2,5,7] >>= print

-----8<-----END-EXAMPLE-----8<----

Cheers,

-- 
Felipe.



More information about the Haskell-Cafe mailing list