{- - ``Data/Queue/Instances'' - (c) 2008 Cook, J. MR SSD, Inc. -} {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, CPP #-} module Data.Queue.Instances ( Chan , MVar #ifdef useSTM , module Data.Queue.Instances.STM #endif ) where import Data.Queue.Classes #ifdef useSTM import Data.Queue.Instances.STM #endif import Control.Concurrent -- Chan : write only, because there's no atomic nonblocking read (that I know of) instance NewFifo (Chan a) IO where newFifo = newChan instance Enqueue (Chan a) IO a where enqueue = writeChan -- MVar : one-item queue in IO monad instance NewFifo (MVar a) IO where newFifo = newEmptyMVar instance Enqueue (MVar a) IO a where enqueue = putMVar instance Dequeue (MVar a) IO a where dequeue = tryTakeMVar