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.
You can try it with a $ cabal install simple-actors and view the documentation here: http://hackage.haskell.org/package/simple-actors or check out the repo here: https://github.com/jberryman/simple-actors Here is an example of a system of actors working as a binary tree, supporting insert and query operations: ---- EXAMPLE ---- module Main where import Control.Concurrent.Actors import Control.Applicative import Control.Concurrent.MVar type Node = Mailbox Operation -- operations supported by the network: data Operation = Insert { val :: Int } | Query { val :: Int , sigVar :: MVar Bool } -- the actor equivalent of a Nil leaf node: nil :: Behavior Operation nil = Receive $ do (Query _ var) <- received send var False -- signal that 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 an Int 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 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 main = do t <- spawn nil mapM_ (insert t) [5,3,7,2,4,6,8] mapM (query t) [1,5,0,7] >>= print ---- END EXAMPLE ---- I need to do some work on the documentation and performance testing. If anyone has anyone questions or comments, I would love to hear them. Thanks, Brandon http://coder.bsimmons.name _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe