{-# LANGUAGE TypeFamilies #-} -- | This module provides the core abstractions that represent managers for queueable events. module Control.Concurrent.EQueue.Class where import Control.Monad.Trans import Data.Semigroup -- | An EQueue is a way of managing edge and level triggered events. -- The choice of EQueue implementation allows late binding of the policy -- by which the application processes events. class EQueue eq where -- | Registers a level triggered event. -- These are the events that accumulate a combined change or resulting state. -- Returns a function to enqueue updates and unregister this event. registerSemi :: (MonadIO m, Semigroup b) => eq a -> (b -> a) -> m (b -> IO (), IO ()) -- | Registers an edge triggered event. -- Returns a function to enqueue updates and unregister this event. registerQueued :: MonadIO m => eq a -> m (a -> IO (), IO ()) -- | An EQueueW is the interface for waiting on events in a queue. class EQueueW eq where -- | The WaitPolicy allows control per-call of waitEQ as to which policy is followed. -- For example, if it should return immediately if there are no events to dequeue -- or if it should wait for at least one event to be available. type WaitPolicy eq :: * -- | The dequeue operation, collecting some set of available events, depending on the -- particular policy the given EQueue impliments. waitEQ :: MonadIO m => eq a -> WaitPolicy eq -> m [a]