{-# LANGUAGE Trustworthy, DeriveDataTypeable #-}
module Control.CUtils.FChan (Chan, listToChan, chanContents, DoneReadingException(..), takeChan, tryTakeChan, newChan, makeConsumer, dupChan) where
import Control.Concurrent.MVar
import Control.Concurrent (forkIO)
import Control.Monad
import Control.Exception
import System.Mem.Weak
import Data.Typeable
import Data.IORef
import System.IO.Unsafe
newtype Chan t = Chan {-# NOUNPACK #-} (MVar (t, Chan t))
{-# NOINLINE listToChan #-}
listToChan :: [t] -> Chan t
listToChan (x:xs) = Chan (unsafePerformIO (newMVar (x, listToChan xs)))
listToChan [] = Chan (unsafePerformIO newEmptyMVar)
data DoneReadingException = DoneReadingException deriving (Typeable, Show)
instance Exception DoneReadingException
addChan :: MVar (Chan t) -> t -> IO ()
addChan vr x = modifyMVar_ vr (\chn -> do
may <- return (Just chn)
case may of
Just (Chan vr2) -> do
vr' <- newEmptyMVar
let chn' = Chan vr'
putMVar vr2 (x, chn')
return chn'
Nothing -> throwIO DoneReadingException)
takeChan (Chan vr) = readMVar vr
tryTakeChan (Chan vr) = tryReadMVar vr
newChan = do
vr <- newEmptyMVar
vr2 <- newEmptyMVar
let chn = Chan vr
putMVar vr2 chn
return (addChan vr2, chn)
makeConsumer chn = do
vr2 <- newMVar chn
return (modifyMVar vr2 (\chn -> do
(x, chn2) <- takeChan chn
return (chn2, x)),
readMVar vr2)
chanContents :: Chan t -> IO [t]
chanContents chn = tryTakeChan chn >>= maybe
(return [])
(\(x, xs) -> liftM (x:) (chanContents xs))
dupChan chn = tryTakeChan chn >>= maybe
(return chn)
(dupChan . snd)