module Control.Concurrent.Futures.Example06 where import Control.Concurrent.Futures.Buffer import Control.Concurrent import IO import Data.List -- | a binary tree data structure data BTree a = BLeaf a | BNode a (BTree a) (BTree a) -- | sum of all nodevalues of a binary tree concSumB :: (Num a) => BTree a -> IO a concSumB t = do putStrLn $ "Sum of nodes and leafs of a binary tree example using buffers" result <- newBuf case t of BLeaf a -> putBuf result a; -- own value BNode a t1 t2 -> sumB result t -- calculate recursivly out <- getBuf result return out sumB :: (Num a) => Buffer a -> BTree a -> IO () sumB mvar tree = do case tree of BLeaf a -> putBuf mvar a -- own value BNode a t1 t2 -> do sem <- newBuf forkIO (sumB sem t1) -- compute left section beam forkIO (sumB sem t2) -- compute right section beam erg1 <-getBuf sem -- get result of left computation erg2 <-getBuf sem -- get result of right computation putBuf mvar (erg1 + erg2 + a) --return left + right + own value --test data treeb = BNode 1 (BNode 24 (BLeaf 2) (BNode 6 (BLeaf 24) (BLeaf 3)))(BNode 33 (BLeaf 7) (BLeaf 8)) --test function test_concSumB :: IO Integer test_concSumB = concSumB treeb