{- |
Module      :  <File name or $Header$ to be replaced automatically>
Description :  This module implements a bounded channel concurrency primitive using channels and quantity semaphores
Maintainer  :  willig@ki.informatik.uni-frankfurt.de
Stability   :  experimental
Portability :  non-portable (requires Futures)

This modules combines a quantity semaphore from the module Control.Concurrent.Fututes.QSem and a channel from 
module  Control.Concurrent.Fututes.Chan to a new synchronisation primitive. Bounded channels have a limited 
capacity of storage cells.
Warning: All operations on bounded channels should only be used within the 
global wrapper function 'Futures.withFuturesDo'!
-}
module Control.Concurrent.Futures.BChan (
          BChan,
          newBChan,
          readBChan,
          writeBChan

) where
import Control.Concurrent.Futures.Chan
import Control.Concurrent.Futures.QSem

--data BChan a = BChan a (Chan a, QSem )
--type BChanType a = (ChanType a, QSem)

type BChan a = (Chan a, QSem)

-- | Creates a new bounded channel
newBChan :: Int -> IO (BChan a)
newBChan n = do
 chan <- newChan
 qsem <- newQSem n
 return (chan , qsem)

-- | Performs an up-operation on the QSem of the bounded channel and then reads
-- a value from the channel. The read operation may block.
readBChan :: BChan a -> IO a
readBChan (chan, sem) = do
  up sem
  readChan chan

-- | Performs a down-operations on the QSem of the bounded channel and writes a
-- new value to it. The down-operation may block.
writeBChan :: BChan a -> a -> IO ()     
writeBChan (chan, sem) val = do
  down sem
  writeChan chan val