{-# LANGUAGE TypeFamilies #-}
module Control.Concurrent.EQueue.Simple (
JustOneEventually(..)
, ChanEQueue(..)
, TChanEQueue(..)
, TQueueEQueue(..)
, IOEQueue(..)
) where
import Control.Concurrent.Chan
import Control.Concurrent.EQueue.Class
import Control.Concurrent.STM
import Control.Monad.Trans
data JustOneEventually = JustOneEventually
newtype ChanEQueue a = CEQ (Chan a)
instance EQueue ChanEQueue where
registerSemi (CEQ c) f = return (writeChan c . f, return ())
registerQueued (CEQ c) = return (writeChan c, return ())
instance EQueueW ChanEQueue where
type WaitPolicy ChanEQueue = JustOneEventually
waitEQ (CEQ c) JustOneEventually = fmap pure . liftIO . readChan $ c
newtype TChanEQueue a = TCEQ (TChan a)
instance EQueue TChanEQueue where
registerSemi (TCEQ c) f = return (atomically . writeTChan c . f, return ())
registerQueued (TCEQ c) = return (atomically . writeTChan c, return ())
instance EQueueW TChanEQueue where
type WaitPolicy TChanEQueue = JustOneEventually
waitEQ (TCEQ c) JustOneEventually = fmap pure . liftIO . atomically . readTChan $ c
newtype TQueueEQueue a = TQEQ (TQueue a)
instance EQueue TQueueEQueue where
registerSemi (TQEQ c) f = return (atomically . writeTQueue c . f, return ())
registerQueued (TQEQ c) = return (atomically . writeTQueue c, return ())
instance EQueueW TQueueEQueue where
type WaitPolicy TQueueEQueue = JustOneEventually
waitEQ (TQEQ c) JustOneEventually = fmap pure . liftIO . atomically . readTQueue $ c
newtype IOEQueue a = IOEQ (a -> IO ())
instance EQueue IOEQueue where
registerSemi (IOEQ act) f = return (act . f, return ())
registerQueued (IOEQ act) = return (act, return ())