[Haskell-cafe] Non-STM bounded queue

Joel Reymont joelr1 at gmail.com
Fri Dec 16 06:11:57 EST 2005


Folks,

I need to move away from STM (unfortunately) until I profile my  
program to my satisfaction. Profiling is somewhat crippled with STM  
in 6.4.1. I cannot do void and drag profiling, for examplel. I  
decided to abstract my mailboxes in a Queue module so that I could  
switch between STM and non-STM as needed. Please let me know what you  
think of this bounded queue implementation.

---
module Queue where

import Control.Monad
import Control.Concurrent

data Queue a = Queue !QSem !(Chan a)

newQ :: Int -> IO (Queue a)
newQ size =
     do sem <- newQSem size
        q <- newChan
        return $! Queue sem q

writeQ :: Queue a -> a -> IO ()
writeQ (Queue sem q) x =
     do waitQSem sem
        writeChan q x

readQ :: Queue a -> IO a
readQ (Queue sem q) =
     do x <- readChan q
        signalQSem sem
        return x

	Thank, Joel

--
http://wagerlabs.com/







More information about the Haskell-Cafe mailing list