rio-0.1.9.2: A standard library for Haskell

Safe HaskellNone
LanguageHaskell2010

RIO.Deque

Contents

Synopsis

Types

data Deque v s a Source #

A double-ended queue supporting any underlying vector type and any monad.

This implements a circular double-ended queue with exponential growth.

Since: 0.1.9.0

type UDeque = Deque MVector Source #

A Deque specialized to unboxed vectors.

Since: 0.1.9.0

type SDeque = Deque MVector Source #

A Deque specialized to storable vectors.

Since: 0.1.9.0

type BDeque = Deque MVector Source #

A Deque specialized to boxed vectors.

Since: 0.1.9.0

Operations

newDeque :: (MVector v a, PrimMonad m) => m (Deque v (PrimState m) a) Source #

Create a new, empty Deque

Since: 0.1.9.0

getDequeSize :: PrimMonad m => Deque v (PrimState m) a -> m Int Source #

O(1) - Get the number of elements that is currently in the Deque

Since: 0.1.9.0

popFrontDeque :: (MVector v a, PrimMonad m) => Deque v (PrimState m) a -> m (Maybe a) Source #

Pop the first value from the beginning of the Deque

Since: 0.1.9.0

popBackDeque :: (MVector v a, PrimMonad m) => Deque v (PrimState m) a -> m (Maybe a) Source #

Pop the first value from the end of the Deque

Since: 0.1.9.0

pushFrontDeque :: (MVector v a, PrimMonad m) => Deque v (PrimState m) a -> a -> m () Source #

Push a new value to the beginning of the Deque

Since: 0.1.9.0

pushBackDeque :: (MVector v a, PrimMonad m) => Deque v (PrimState m) a -> a -> m () Source #

Push a new value to the end of the Deque

Since: 0.1.9.0

foldlDeque :: (MVector v a, PrimMonad m) => (acc -> a -> m acc) -> acc -> Deque v (PrimState m) a -> m acc Source #

Fold over a Deque, starting at the beginning. Does not modify the Deque.

Since: 0.1.9.0

foldrDeque :: (MVector v a, PrimMonad m) => (a -> acc -> m acc) -> acc -> Deque v (PrimState m) a -> m acc Source #

Fold over a Deque, starting at the end. Does not modify the Deque.

Since: 0.1.9.0

dequeToList :: (MVector v a, PrimMonad m) => Deque v (PrimState m) a -> m [a] Source #

Convert a Deque into a list. Does not modify the Deque.

Since: 0.1.9.0

dequeToVector :: (Vector v' a, MVector v a, PrimMonad m) => Deque v (PrimState m) a -> m (v' a) Source #

Convert to an immutable vector of any type. If resulting pure vector corresponds to the mutable one used by the Deque, it will be more efficient to use freezeDeque instead.

Example

Expand
>>> :set -XTypeApplications
>>> import qualified RIO.Vector.Unboxed as U
>>> import qualified RIO.Vector.Storable as S
>>> d <- newDeque @U.MVector @Int
>>> mapM_ (pushFrontDeque d) [0..10]
>>> dequeToVector @S.Vector d
[10,9,8,7,6,5,4,3,2,1,0]

Since: 0.1.9.0

freezeDeque :: (Vector v a, PrimMonad m) => Deque (Mutable v) (PrimState m) a -> m (v a) Source #

Yield an immutable copy of the underlying mutable vector. The difference from dequeToVector is that the the copy will be performed with a more efficient memcpy, rather than element by element. The downside is that the resulting vector type must be the one that corresponds to the mutable one that is used in the Deque.

Example

Expand
>>> :set -XTypeApplications
>>> import qualified RIO.Vector.Unboxed as U
>>> d <- newDeque @U.MVector @Int
>>> mapM_ (pushFrontDeque d) [0..10]
>>> freezeDeque @U.Vector d
[10,9,8,7,6,5,4,3,2,1,0]

Since: 0.1.9.0

Inference helpers

asUDeque :: UDeque s a -> UDeque s a Source #

Helper function to assist with type inference, forcing usage of an unboxed vector.

Since: 0.1.9.0

asSDeque :: SDeque s a -> SDeque s a Source #

Helper function to assist with type inference, forcing usage of a storable vector.

Since: 0.1.9.0

asBDeque :: BDeque s a -> BDeque s a Source #

Helper function to assist with type inference, forcing usage of a boxed vector.

Since: 0.1.9.0