| Copyright | (c) James King 2020 2021 |
|---|---|
| License | BSD3 |
| Maintainer | [email protected] |
| Stability | experimental |
| Portability | POSIX |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Database.PostgreSQL.Replicant.Queue
Description
Shared FIFO queues
Synopsis
- data BoundedFifoQueueMeta a = BoundedFifoQueueMeta {}
- newtype BoundedFifoQueue a = BoundedFifoQueue (MVar (BoundedFifoQueueMeta a))
- newtype BoundedQueueException a = BoundedQueueOverflow a
- emptyBounded :: Int -> IO (BoundedFifoQueue a)
- enqueueBounded :: BoundedFifoQueue a -> a -> IO (Either (BoundedQueueException a) ())
- newtype FifoQueue a = FifoQueue (MVar (Seq a))
- empty :: IO (FifoQueue a)
- null :: FifoQueue a -> IO Bool
- dequeue :: FifoQueue a -> IO (Maybe a)
- enqueue :: FifoQueue a -> a -> IO ()
- enqueueRight :: FifoQueue a -> a -> IO ()
Documentation
data BoundedFifoQueueMeta a Source #
Constructors
| BoundedFifoQueueMeta | |
Fields
| |
Instances
| Eq a => Eq (BoundedFifoQueueMeta a) Source # | |
Defined in Database.PostgreSQL.Replicant.Queue Methods (==) :: BoundedFifoQueueMeta a -> BoundedFifoQueueMeta a -> Bool # (/=) :: BoundedFifoQueueMeta a -> BoundedFifoQueueMeta a -> Bool # | |
| Show a => Show (BoundedFifoQueueMeta a) Source # | |
Defined in Database.PostgreSQL.Replicant.Queue Methods showsPrec :: Int -> BoundedFifoQueueMeta a -> ShowS # show :: BoundedFifoQueueMeta a -> String # showList :: [BoundedFifoQueueMeta a] -> ShowS # | |
newtype BoundedFifoQueue a Source #
Constructors
| BoundedFifoQueue (MVar (BoundedFifoQueueMeta a)) |
newtype BoundedQueueException a Source #
Constructors
| BoundedQueueOverflow a |
Instances
| Eq a => Eq (BoundedQueueException a) Source # | |
Defined in Database.PostgreSQL.Replicant.Queue Methods (==) :: BoundedQueueException a -> BoundedQueueException a -> Bool # (/=) :: BoundedQueueException a -> BoundedQueueException a -> Bool # | |
| Show a => Show (BoundedQueueException a) Source # | |
Defined in Database.PostgreSQL.Replicant.Queue Methods showsPrec :: Int -> BoundedQueueException a -> ShowS # show :: BoundedQueueException a -> String # showList :: [BoundedQueueException a] -> ShowS # | |
emptyBounded :: Int -> IO (BoundedFifoQueue a) Source #
enqueueBounded :: BoundedFifoQueue a -> a -> IO (Either (BoundedQueueException a) ()) Source #
enqueueRight :: FifoQueue a -> a -> IO () Source #
Put an item on the end of the queue so that it will be dequeued first.