bounded-queue-1.0.0: A strict, immutable, thread-safe, single-ended, bounded queue.

Copyright(c) Kadena LLC 2019
LicenseBSD3
MaintainerColin Woodbury <colin@kadena.io>
Safe HaskellSafe
LanguageHaskell2010

Data.Queue.Bounded

Contents

Description

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

Type

data BQueue a Source #

A single-ended, bounded queue which keeps track of its size.

Instances
Functor BQueue Source # 
Instance details

Defined in Data.Queue.Bounded

Methods

fmap :: (a -> b) -> BQueue a -> BQueue b #

(<$) :: a -> BQueue b -> BQueue a #

Foldable BQueue Source #

\(\mathcal{O}(1)\) length implementation.

Instance details

Defined in Data.Queue.Bounded

Methods

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 #

toList :: BQueue a -> [a] #

null :: BQueue a -> Bool #

length :: BQueue a -> Int #

elem :: Eq a => a -> BQueue a -> Bool #

maximum :: Ord a => BQueue a -> a #

minimum :: Ord a => BQueue a -> a #

sum :: Num a => BQueue a -> a #

product :: Num a => BQueue a -> a #

Traversable BQueue Source # 
Instance details

Defined in Data.Queue.Bounded

Methods

traverse :: Applicative f => (a -> f b) -> BQueue a -> f (BQueue b) #

sequenceA :: Applicative f => BQueue (f a) -> f (BQueue a) #

mapM :: Monad m => (a -> m b) -> BQueue a -> m (BQueue b) #

sequence :: Monad m => BQueue (m a) -> m (BQueue a) #

Eq a => Eq (BQueue a) Source # 
Instance details

Defined in Data.Queue.Bounded

Methods

(==) :: BQueue a -> BQueue a -> Bool #

(/=) :: BQueue a -> BQueue a -> Bool #

Show a => Show (BQueue a) Source # 
Instance details

Defined in Data.Queue.Bounded

Methods

showsPrec :: Int -> BQueue a -> ShowS #

show :: BQueue a -> String #

showList :: [BQueue a] -> ShowS #

Generic (BQueue a) Source # 
Instance details

Defined in Data.Queue.Bounded

Associated Types

type Rep (BQueue a) :: Type -> Type #

Methods

from :: BQueue a -> Rep (BQueue a) x #

to :: Rep (BQueue a) x -> BQueue a #

Semigroup (BQueue a) Source # 
Instance details

Defined in Data.Queue.Bounded

Methods

(<>) :: BQueue a -> BQueue a -> BQueue a #

sconcat :: NonEmpty (BQueue a) -> BQueue a #

stimes :: Integral b => b -> BQueue a -> BQueue a #

NFData a => NFData (BQueue a) Source # 
Instance details

Defined in Data.Queue.Bounded

Methods

rnf :: BQueue a -> () #

type Rep (BQueue a) Source # 
Instance details

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

empty :: Int -> BQueue a Source #

Given a limit value, yield an empty BQueue.

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.

Insertion / Removal

cons :: a -> BQueue a -> BQueue a Source #

\(\mathcal{O}(1)\).

uncons :: BQueue a -> Maybe (a, BQueue a) Source #

\(\mathcal{O}(1)\).

Extra

average :: Integral a => BQueue a -> a Source #

\(\mathcal{O}(n)\).

reverse :: BQueue a -> BQueue a Source #

\(\mathcal{O}(n)\).

take :: Int -> BQueue a -> BQueue a Source #

\(\mathcal{O}(\log(\min(i,n-i)))\).

drop :: Int -> BQueue a -> BQueue a Source #

\(\mathcal{O}(\log(\min(i,n-i)))\).