Copyright | (c) Kadena LLC 2019 |
---|---|
License | BSD3 |
Maintainer | Colin Woodbury <colin@kadena.io> |
Safe Haskell | Safe |
Language | Haskell2010 |
This library provides a strict, immutable, thread-safe, single-ended, bounded
queue. When the insert limit is reached and a cons
is attempted, this
BQueue
automatically drops old entries off its end. Thus, writes always
succeed and never block.
This data structure is intended as a "sliding window" over some stream of data, where we wish old entries to be naturally forgotten. Since this is an immutable data structure and not a concurrent queue, we provide instances for the usual useful typeclasses with which one can perform analysis over the entire "window".
This module is intended to be imported qualified:
import qualified Data.Queue.Bounded as BQ
Synopsis
- data BQueue a
- empty :: Int -> BQueue a
- singleton :: Int -> a -> BQueue a
- fromList :: Int -> [a] -> BQueue a
- cons :: a -> BQueue a -> BQueue a
- uncons :: BQueue a -> Maybe (a, BQueue a)
- average :: Integral a => BQueue a -> a
- reverse :: BQueue a -> BQueue a
- take :: Int -> BQueue a -> BQueue a
- drop :: Int -> BQueue a -> BQueue a
Type
A single-ended, bounded queue which keeps track of its size.
Instances
Functor BQueue Source # | |
Foldable BQueue Source # | \(\mathcal{O}(1)\) |
Defined in Data.Queue.Bounded fold :: Monoid m => BQueue m -> m # foldMap :: Monoid m => (a -> m) -> BQueue a -> m # foldr :: (a -> b -> b) -> b -> BQueue a -> b # foldr' :: (a -> b -> b) -> b -> BQueue a -> b # foldl :: (b -> a -> b) -> b -> BQueue a -> b # foldl' :: (b -> a -> b) -> b -> BQueue a -> b # foldr1 :: (a -> a -> a) -> BQueue a -> a # foldl1 :: (a -> a -> a) -> BQueue a -> a # elem :: Eq a => a -> BQueue a -> Bool # maximum :: Ord a => BQueue a -> a # minimum :: Ord a => BQueue a -> a # | |
Traversable BQueue Source # | |
Eq a => Eq (BQueue a) Source # | |
Show a => Show (BQueue a) Source # | |
Generic (BQueue a) Source # | |
Semigroup (BQueue a) Source # | |
NFData a => NFData (BQueue a) Source # | |
Defined in Data.Queue.Bounded | |
type Rep (BQueue a) Source # | |
Defined in Data.Queue.Bounded type Rep (BQueue a) = D1 (MetaData "BQueue" "Data.Queue.Bounded" "bounded-queue-1.0.0-6fHlBSsUo6Y5MKgg2DOph0" False) (C1 (MetaCons "BQueue" PrefixI True) (S1 (MetaSel (Just "_bqs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq a)) :*: (S1 (MetaSel (Just "_bqsLimit") SourceUnpack SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "_bqsSize") SourceUnpack SourceStrict DecidedStrict) (Rec0 Int)))) |
Construction
singleton :: Int -> a -> BQueue a Source #
Given a limit value and an initial value, yield a singleton BQueue
.
fromList :: Int -> [a] -> BQueue a Source #
\(\mathcal{O}(c)\). Naively keeps the first \(c\) values of the input list
(as defined by the given limiting Int
value) and does not attempt any
elegant queue-like cycling.