Safe Haskell | None |
---|---|
Language | GHC2021 |
Test.Credit.Queue.Base
Documentation
Instances
Arbitrary a => Arbitrary (QueueOp a) Source # | |
Show a => Show (QueueOp a) Source # | |
Eq a => Eq (QueueOp a) Source # | |
Ord a => Ord (QueueOp a) Source # | |
(Arbitrary a, BoundedQueue q, Show a) => DataStructure (Q q a) (QueueOp a) Source # | |
class Queue (q :: Type -> (Type -> Type) -> Type) where Source #
Methods
empty :: MonadInherit m => m (q a m) Source #
snoc :: MonadInherit m => q a m -> a -> m (q a m) Source #
uncons :: MonadInherit m => q a m -> m (Maybe (a, q a m)) Source #
Instances
Queue BQueue Source # | |
Defined in Test.Credit.Queue.Bankers | |
Queue Bootstrapped Source # | |
Defined in Test.Credit.Queue.Bootstrapped Methods empty :: MonadInherit m => m (Bootstrapped a m) Source # snoc :: MonadInherit m => Bootstrapped a m -> a -> m (Bootstrapped a m) Source # uncons :: MonadInherit m => Bootstrapped a m -> m (Maybe (a, Bootstrapped a m)) Source # | |
Queue Implicit Source # | |
Defined in Test.Credit.Queue.Implicit | |
Queue Physicists Source # | |
Defined in Test.Credit.Queue.Physicists Methods empty :: MonadInherit m => m (Physicists a m) Source # snoc :: MonadInherit m => Physicists a m -> a -> m (Physicists a m) Source # uncons :: MonadInherit m => Physicists a m -> m (Maybe (a, Physicists a m)) Source # | |
Queue RQueue Source # | |
Defined in Test.Credit.Queue.Realtime | |
Queue (Batched :: Type -> (Type -> Type) -> Type) Source # | |
Defined in Test.Credit.Queue.Batched |
class Queue q => BoundedQueue (q :: Type -> (Type -> Type) -> Type) where Source #
Instances
data Q (q :: Type -> k -> Type) a (m :: k) Source #
Constructors
E | |
Q Size (q (PrettyCell a) m) |
Instances
MemoryStructure (q (PrettyCell a)) => MemoryStructure (Q q a) Source # | |
Defined in Test.Credit.Queue.Base Methods prettyStructure :: MonadMemory m => Q q a m -> m Memory Source # | |
(Arbitrary a, BoundedQueue q, Show a) => DataStructure (Q q a) (QueueOp a) Source # | |
act :: (MonadInherit m, Queue q) => Size -> q (PrettyCell a) m -> QueueOp a -> m (Q q a m) Source #