compact-sequences-0.2.0.0: Stacks, queues, and deques with compact representations.

Safe HaskellSafe
LanguageHaskell2010

Data.CompactSequence.Queue.Simple

Description

Space-efficient queues with amortized \( O(\log n) \) operations. These directly use an underlying array-based implementation, without doing any special optimization for the first few and last few elements of the queue.

Synopsis

Documentation

data Queue a where Source #

A queue.

Bundled Patterns

pattern Empty :: Queue a

A bidirectional pattern synonym for the empty queue.

pattern (:<) :: a -> Queue a -> Queue a infixr 5

A unidirectional pattern synonym for viewing the front of a queue.

Instances
Functor Queue Source # 
Instance details

Defined in Data.CompactSequence.Queue.Simple.Internal

Methods

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

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

Foldable Queue Source # 
Instance details

Defined in Data.CompactSequence.Queue.Simple.Internal

Methods

fold :: Monoid m => Queue m -> m #

foldMap :: Monoid m => (a -> m) -> Queue a -> m #

foldr :: (a -> b -> b) -> b -> Queue a -> b #

foldr' :: (a -> b -> b) -> b -> Queue a -> b #

foldl :: (b -> a -> b) -> b -> Queue a -> b #

foldl' :: (b -> a -> b) -> b -> Queue a -> b #

foldr1 :: (a -> a -> a) -> Queue a -> a #

foldl1 :: (a -> a -> a) -> Queue a -> a #

toList :: Queue a -> [a] #

null :: Queue a -> Bool #

length :: Queue a -> Int #

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

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

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

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

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

Traversable Queue Source # 
Instance details

Defined in Data.CompactSequence.Queue.Simple.Internal

Methods

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

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

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

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

IsList (Queue a) Source # 
Instance details

Defined in Data.CompactSequence.Queue.Simple.Internal

Associated Types

type Item (Queue a) :: Type #

Methods

fromList :: [Item (Queue a)] -> Queue a #

fromListN :: Int -> [Item (Queue a)] -> Queue a #

toList :: Queue a -> [Item (Queue a)] #

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

Defined in Data.CompactSequence.Queue.Simple.Internal

Methods

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

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

Ord a => Ord (Queue a) Source # 
Instance details

Defined in Data.CompactSequence.Queue.Simple.Internal

Methods

compare :: Queue a -> Queue a -> Ordering #

(<) :: Queue a -> Queue a -> Bool #

(<=) :: Queue a -> Queue a -> Bool #

(>) :: Queue a -> Queue a -> Bool #

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

max :: Queue a -> Queue a -> Queue a #

min :: Queue a -> Queue a -> Queue a #

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

Defined in Data.CompactSequence.Queue.Simple.Internal

Methods

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

show :: Queue a -> String #

showList :: [Queue a] -> ShowS #

Semigroup (Queue a) Source # 
Instance details

Defined in Data.CompactSequence.Queue.Simple.Internal

Methods

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

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

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

Monoid (Queue a) Source # 
Instance details

Defined in Data.CompactSequence.Queue.Simple.Internal

Methods

mempty :: Queue a #

mappend :: Queue a -> Queue a -> Queue a #

mconcat :: [Queue a] -> Queue a #

type Item (Queue a) Source # 
Instance details

Defined in Data.CompactSequence.Queue.Simple.Internal

type Item (Queue a) = a

(|>) :: Queue a -> a -> Queue a infixl 4 Source #

An infix synonym for snoc.

empty :: Queue a Source #

The empty queue.

snoc :: Queue a -> a -> Queue a infixl 4 Source #

Enqueue an element at the rear of a queue.

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

Dequeue an element from the front of a queue.

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

Take up to the given number of elements from the front of a queue to form a new queue. \( O(\min (k, n)) \), where \( k \) is the integer argument and \( n \) is the size of the queue.

fromList :: [a] -> Queue a Source #

\( O(n \log n) \). Convert a list to a Queue, with the head of the list at the front of the queue.

fromListN :: Int -> [a] -> Queue a Source #

\( O(n) \). Convert a list of the given size to a Queue, with the head of the list at the front of the queue.

fromListNIncremental :: Int -> [a] -> Queue a Source #

\( O(n) \). Convert a list of the given size to a Queue, with the head of the list at the front of the queue. Unlike fromListN, the conversion is performed incrementally. This is generally beneficial if the list is represented compactly (e.g., an enumeration) or when it's otherwise not important to consume the entire list immediately.