vector-circular-0.1.4: circular vectors
Safe HaskellNone
LanguageHaskell2010

Data.Vector.Circular.Generic

Synopsis

Types

data CircularVector v a Source #

A circular, immutable vector. This type is equivalent to cycle xs for some finite, nonempty xs, but with O(1) access and O(1) rotations. Indexing into this type is always total.

Constructors

CircularVector 

Fields

Instances

Instances details
Lift a => Lift (CircularVector v a :: Type) Source #

since 0.1.2 instance Foldable (CircularVector v) where foldMap :: Monoid m => (a -> m) -> CircularVector v a -> m foldMap = Data.Vector.Circular.Generic.foldMap {--}

since 0.1.2 instance Foldable1 CircularVector where foldMap1 :: Semigroup m => (a -> m) -> CircularVector a -> m foldMap1 = Data.Vector.Circular.Generic.foldMap1 {--}

since 0.1.2

Instance details

Defined in Data.Vector.Circular.Generic

Methods

lift :: CircularVector v a -> Q Exp #

liftTyped :: CircularVector v a -> Q (TExp (CircularVector v a)) #

Functor v => Functor (CircularVector v) Source #

since 0.1.2

Instance details

Defined in Data.Vector.Circular.Generic

Methods

fmap :: (a -> b) -> CircularVector v a -> CircularVector v b #

(<$) :: a -> CircularVector v b -> CircularVector v a #

(Vector v a, Eq a) => Eq (CircularVector v a) Source #

instance Traversable (CircularVector v) where traverse :: (Applicative f) => (a -> f b) -> CircularVector a -> f (CircularVector b) traverse f (CircularVector v rot) = CircularVector $ traverse f v * pure rot

since 0.1.2

Since: 0.1.2

Instance details

Defined in Data.Vector.Circular.Generic

(Vector v a, Ord (v a), Eq a) => Ord (CircularVector v a) Source #

since 0.1.2

Instance details

Defined in Data.Vector.Circular.Generic

Read (v a) => Read (CircularVector v a) Source #

since 0.1.2

Instance details

Defined in Data.Vector.Circular.Generic

Show (v a) => Show (CircularVector v a) Source #

since 0.1.2

Instance details

Defined in Data.Vector.Circular.Generic

Generic (CircularVector v a) Source #

Since: 0.1.2

Instance details

Defined in Data.Vector.Circular.Generic

Associated Types

type Rep (CircularVector v a) :: Type -> Type #

Methods

from :: CircularVector v a -> Rep (CircularVector v a) x #

to :: Rep (CircularVector v a) x -> CircularVector v a #

Vector v a => Semigroup (CircularVector v a) Source #

instance Eq2 CircularVector where liftEq2 :: (a -> b -> Bool) -> CircularVector v a -> CircularVector v b -> Bool liftEq2 eq c0(CircularVector x rx) c1(CircularVector y ry) | G.length x /= G.length y = False | rx == ry = liftEq eq x y | otherwise = getAll $ flip Prelude.foldMap [0..NonEmpty.length x-1] $ i -> All (index c0 i eq index c1 i)

instance Ord1 CircularVector where liftCompare :: (a -> b -> Ordering) -> CircularVector a -> CircularVector b -> Ordering liftCompare cmp (CircularVector x rx) (CircularVector y ry) = liftCompare cmp x y <> compare rx ry

instance Show1 CircularVector where liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> CircularVector a -> ShowS liftShowsPrec sp sl d (CircularVector x rx) = showsBinaryWith (liftShowsPrec sp sl) showsPrec CircularVector d x rx

instance Read1 CircularVector where liftReadPrec rp rl = readData $ readBinaryWith (liftReadPrec rp rl) readPrec CircularVector CircularVector liftReadListPrec = liftReadListPrecDefault

The Semigroup (<>) operation behaves by un-rolling the two vectors so that their rotation is 0, concatenating them, returning a new vector with a 0-rotation.

since 0.1.2

Since: 0.1.2

Instance details

Defined in Data.Vector.Circular.Generic

NFData (v a) => NFData (CircularVector v a) Source #

Since: 0.1.2

Instance details

Defined in Data.Vector.Circular.Generic

Methods

rnf :: CircularVector v a -> () #

type Rep (CircularVector v a) Source # 
Instance details

Defined in Data.Vector.Circular.Generic

type Rep (CircularVector v a) = D1 ('MetaData "CircularVector" "Data.Vector.Circular.Generic" "vector-circular-0.1.4-9qfDy39LzyqKPukzOgd4Gw" 'False) (C1 ('MetaCons "CircularVector" 'PrefixI 'True) (S1 ('MetaSel ('Just "vector") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (v a)) :*: S1 ('MetaSel ('Just "rotation") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int)))

Construction

Initialization

singleton :: Vector v a => a -> CircularVector v a Source #

O(1) Construct a singleton 'CircularVector.

since 0.1.2

replicate :: Vector v a => Int -> a -> Maybe (CircularVector v a) Source #

O(n) Circular vector of the given length with the same value in each position.

When given a index n <= 0, then Nothing is returned, otherwise Just.

>>> replicate @Vector 3 "a"
Just (CircularVector {vector = ["a","a","a"], rotation = 0})
>>> replicate @Vector 0 "a"
Nothing

Since: 0.1.2

replicate1 :: Vector v a => Int -> a -> CircularVector v a Source #

O(n) Circular vector of the given length with the same value in each position.

This variant takes max n 1 for the supplied length parameter.

>>> toList $ replicate1 @Vector 3 "a"
["a","a","a"]
>>> toList $ replicate1 @Vector 0 "a"
["a"]
>>> toList $ replicate1 @Vector (-1) "a"
["a"]

Since: 0.1.2

generate :: Vector v a => Int -> (Int -> a) -> Maybe (CircularVector v a) Source #

O(n) Construct a circular vector of the given length by applying the function to each index.

When given a index n <= 0, then Nothing is returned, otherwise Just.

>>> let f 0 = "a"; f _ = "k"; f :: Int -> String
>>> generate @Vector 1 f
Just (CircularVector {vector = ["a"], rotation = 0})
>>> generate @Vector 0 f
Nothing
>>> generate @Vector 2 f
Just (CircularVector {vector = ["a","k"], rotation = 0})

Since: 0.1.2

generate1 :: Vector v a => Int -> (Int -> a) -> CircularVector v a Source #

O(n) Construct a circular vector of the given length by applying the function to each index.

This variant takes max n 1 for the supplied length parameter.

>>> let f 0 = "a"; f _ = "k"; f :: Int -> String
>>> toList $ generate1 @Vector 2 f
["a","k"]
>>> toList $ generate1 @Vector 0 f
["a"]
>>> toList $ generate1 @Vector (-1) f
["a"]

Since: 0.1.2

iterateN :: Vector v a => Int -> (a -> a) -> a -> Maybe (CircularVector v a) Source #

O(n) Apply function n times to value. Zeroth element is original value.

When given a index n <= 0, then Nothing is returned, otherwise Just.

>>> iterateN @Vector 3 (+1) 0
Just (CircularVector {vector = [0,1,2], rotation = 0})
>>> iterateN @Vector 0 (+1) 0
Nothing
>>> iterateN @Vector (-1) (+1) 0
Nothing

Since: 0.1.2

iterateN1 :: Vector v a => Int -> (a -> a) -> a -> CircularVector v a Source #

O(n) Apply function n times to value. Zeroth element is original value.

This variant takes max n 1 for the supplied length parameter.

>>> iterateN1 @Vector 3 (+1) 0
CircularVector {vector = [0,1,2], rotation = 0}
>>> iterateN1 @Vector 0 (+1) 0
CircularVector {vector = [0], rotation = 0}
>>> iterateN1 @Vector (-1) (+1) 0
CircularVector {vector = [0], rotation = 0}

Since: 0.1.2

Monad Initialization

replicateM :: (Monad m, Vector v a) => Int -> m a -> m (Maybe (CircularVector v a)) Source #

O(n) Execute the monadic action the given number of times and store the results in a circular vector.

When given a index n <= 0, then Nothing is returned, otherwise Just.

>>> replicateM @Maybe @Vector 3 (Just "a")
Just (Just (CircularVector {vector = ["a","a","a"], rotation = 0}))
>>> replicateM @Maybe @Vector 3 Nothing
Nothing
>>> replicateM @Maybe @Vector 0 (Just "a")
Just Nothing
>>> replicateM @Maybe @Vector (-1) (Just "a")
Just Nothing

Since: 0.1.2

replicate1M :: (Monad m, Vector v a) => Int -> m a -> m (CircularVector v a) Source #

O(n) Execute the monadic action the given number of times and store the results in a circular vector.

This variant takes max n 1 for the supplied length parameter.

>>> replicate1M @Maybe @Vector 3 (Just "a")
Just (CircularVector {vector = ["a","a","a"], rotation = 0})
>>> replicate1M @Maybe @Vector 3 Nothing
Nothing
>>> replicate1M @Maybe @Vector 0 (Just "a")
Just (CircularVector {vector = ["a"], rotation = 0})
>>> replicate1M @Maybe @Vector (-1) (Just "a")
Just (CircularVector {vector = ["a"], rotation = 0})

Since: 0.1.2

generateM :: (Monad m, Vector v a) => Int -> (Int -> m a) -> m (Maybe (CircularVector v a)) Source #

O(n) Construct a circular vector of the given length by applying the monadic action to each index

When given a index n <= 0, then Nothing is returned, otherwise Just.

>>> generateM @[] @Vector 3 (\i -> if i < 1 then ["a"] else ["b"])
[Just (CircularVector {vector = ["a","b","b"], rotation = 0})]
>>> generateM @[] @Vector @Int 3 (const [])
[]
>>> generateM @[] @Vector @Int 0 (const [1])
[Nothing]
>>> generateM @Maybe @Vector @Int (-1) (const Nothing)
Just Nothing

Since: 0.1.2

generate1M :: (Monad m, Vector v a) => Int -> (Int -> m a) -> m (CircularVector v a) Source #

O(n) Construct a circular vector of the given length by applying the monadic action to each index

This variant takes max n 1 for the supplied length parameter.

>>> generate1M @Maybe @Vector 3 (\i -> if i < 1 then Just "a" else Just "b")
Just (CircularVector {vector = ["a","b","b"], rotation = 0})
>>> generate1M @[] @Vector 3 (const [])
[]
>>> generate1M @Maybe @Vector 0 (const $ Just 1)
Just (CircularVector {vector = [1], rotation = 0})
>>> generate1M @Maybe @Vector (-1) (const Nothing)
Nothing

Since: 0.1.2

iterateNM :: (Monad m, Vector v a) => Int -> (a -> m a) -> a -> m (Maybe (CircularVector v a)) Source #

O(n) Apply monadic function n times to value. Zeroth element is original value.

When given a index n <= 0, then Nothing is returned, otherwise Just.

>>> iterateNM @Maybe @Vector 3 return "a"
Just (Just (CircularVector {vector = ["a","a","a"], rotation = 0}))
>>> iterateNM @Maybe @Vector 3 (const Nothing) "a"
Nothing
>>> iterateNM @Maybe @Vector 0 return "a"
Just Nothing

Since: 0.1.2

iterateN1M :: (Monad m, Vector v a) => Int -> (a -> m a) -> a -> m (CircularVector v a) Source #

O(n) Apply monadic function n times to value. Zeroth element is original value.

This variant takes max n 1 for the supplied length parameter.

>>> iterateN1M @Maybe @Vector 3 return "a"
Just (CircularVector {vector = ["a","a","a"], rotation = 0})
>>> iterateN1M @Maybe @Vector 3 (const Nothing) "a"
Nothing
>>> iterateN1M @Maybe @Vector 0 return "a"
Just (CircularVector {vector = ["a"], rotation = 0})
>>> iterateN1M @Maybe @Vector (-1) return "a"
Just (CircularVector {vector = ["a"], rotation = 0})

Since: 0.1.2

create :: Vector v a => (forall s. ST s (Mutable v s a)) -> Maybe (CircularVector v a) Source #

Execute the monadic action and freeze the resulting circular vector.

Since: 0.1.2

unsafeCreate :: Vector v a => (forall s. ST s (Mutable v s a)) -> CircularVector v a Source #

Execute the monadic action and freeze the resulting circular vector, bypassing emptiness checks.

The onus is on the caller to guarantee the created vector is non-empty.

Since: 0.1.2

createT :: (Traversable t, Vector v a) => (forall s. ST s (t (Mutable v s a))) -> t (Maybe (CircularVector v a)) Source #

Execute the monadic action and freeze the resulting circular vector.

Since: 0.1.2

unsafeCreateT :: (Traversable t, Vector v a) => (forall s. ST s (t (Mutable v s a))) -> t (CircularVector v a) Source #

Execute the monadic action and freeze the resulting circular vector.

The onus is on the caller to guarantee the created vector is non-empty.

Since: 0.1.2

Unfolding

unfoldr :: Vector v a => (b -> Maybe (a, b)) -> b -> Maybe (CircularVector v a) Source #

O(n) Construct a circular vector by repeatedly applying the generator function to a seed. The generator function yields Just the next element and the new seed or Nothing if there are no more elements.

If an unfold does not create meaningful values, Nothing is returned. Otherwise, Just containing a circular vector is returned.

>>> unfoldr @Vector (\b -> case b of "a" -> Just ("a", "b"); _ ->  Nothing) "a"
Just (CircularVector {vector = ["a"], rotation = 0})
>>> unfoldr @Vector (const Nothing) "a"
Nothing

Since: 0.1.2

unfoldr1 :: Vector v a => (b -> Maybe (a, b)) -> a -> b -> CircularVector v a Source #

O(n) Construct a circular vector by repeatedly applying the generator function to a seed and a first element.

This variant of unfoldr guarantees the resulting vector is non- empty by supplying an initial element a.

>>> unfoldr1 @Vector (\b -> case b of "a" -> Just ("a", "b"); _ ->  Nothing) "first" "a"
CircularVector {vector = ["first","a"], rotation = 0}
>>> unfoldr1 @Vector (const Nothing) "first" "a"
CircularVector {vector = ["first"], rotation = 0}

Since: 0.1.2

unfoldrN :: Vector v a => Int -> (b -> Maybe (a, b)) -> b -> Maybe (CircularVector v a) Source #

O(n) Construct a circular vector with at most n elements by repeatedly applying the generator function to a seed. The generator function yields Just the next element and the new seed or Nothing if there are no more elements.

If an unfold does not create meaningful values, Nothing is returned. Otherwise, Just containing a circular vector is returned.

>>> unfoldrN @Vector 3 (\b -> Just (b+1, b+1)) 0
Just (CircularVector {vector = [1,2,3], rotation = 0})
>>> unfoldrN @Vector 3 (const Nothing) 0
Nothing
>>> unfoldrN @Vector 0 (\b -> Just (b+1, b+1)) 0
Nothing

Since: 0.1.2

unfoldr1N :: Vector v a => Int -> (b -> Maybe (a, b)) -> a -> b -> CircularVector v a Source #

O(n) Construct a circular vector with at most n elements by repeatedly applying the generator function to a seed. The generator function yields Just the next element and the new seed or Nothing if there are no more elements.

This variant of unfoldrN guarantees the resulting vector is non- empty by supplying an initial element a.

>>> unfoldr1N @Vector 3 (\b -> Just (b+1, b+1)) 0 0
CircularVector {vector = [0,1,2,3], rotation = 0}
>>> unfoldr1N @Vector 3 (const Nothing) 0 0
CircularVector {vector = [0], rotation = 0}
>>> unfoldr1N @Vector 0 (\b -> Just (b+1, b+1)) 0 0
CircularVector {vector = [0], rotation = 0}

Since: 0.1.2

unfoldrM :: (Monad m, Vector v a) => (b -> m (Maybe (a, b))) -> b -> m (Maybe (CircularVector v a)) Source #

O(n) Construct a circular vector by repeatedly applying the monadic generator function to a seed. The generator function yields Just the next element and the new seed or Nothing if there are no more elements.

If an unfold does not create meaningful values, Nothing is returned. Otherwise, Just containing a circular vector is returned.

Since: 0.1.2

unfoldr1M :: (Monad m, Vector v a) => (b -> m (Maybe (a, b))) -> a -> b -> m (CircularVector v a) Source #

O(n) Construct a circular vector by repeatedly applying the monadic generator function to a seed. The generator function yields Just the next element and the new seed or Nothing if there are no more elements.

This variant of unfoldrM guarantees the resulting vector is non- empty by supplying an initial element a.

Since: 0.1.2

unfoldrNM :: (Monad m, Vector v a) => Int -> (b -> m (Maybe (a, b))) -> b -> m (Maybe (CircularVector v a)) Source #

O(n) Construct a circular vector by repeatedly applying the monadic generator function to a seed. The generator function yields Just the next element and the new seed or Nothing if there are no more elements.

If an unfold does not create meaningful values, Nothing is returned. Otherwise, Just containing a circular vector is returned.

Since: 0.1.2

unfoldr1NM :: (Monad m, Vector v a) => Int -> (b -> m (Maybe (a, b))) -> a -> b -> m (CircularVector v a) Source #

O(n) Construct a circular vector by repeatedly applying the monadic generator function to a seed. The generator function yields Just the next element and the new seed or Nothing if there are no more elements.

This variant of unfoldrNM guarantees the resulting vector is non- empty by supplying an initial element a.

Since: 0.1.2

constructN :: Vector v a => Int -> (v a -> a) -> Maybe (CircularVector v a) Source #

O(n) Construct a circular vector with n elements by repeatedly applying the generator function to the already constructed part of the vector.

If constructN does not create meaningful values, Nothing is returned. Otherwise, Just containing a circular vector is returned.

Since: 0.1.2

constructrN :: Vector v a => Int -> (v a -> a) -> Maybe (CircularVector v a) Source #

O(n) Construct a circular vector with n elements from right to left by repeatedly applying the generator function to the already constructed part of the vector.

If constructrN does not create meaningful values, Nothing is returned. Otherwise, Just containing a circular vector is returned.

Since: 0.1.2

Enumeration

enumFromN :: (Vector v a, Num a) => a -> Int -> Maybe (CircularVector v a) Source #

O(n) Yield a circular vector of the given length containing the values x, x+1 etc. This operation is usually more efficient than enumFromTo.

If an enumeration does not use meaningful indices, Nothing is returned, otherwise, Just containing a circular vector.

Since: 0.1.2

enumFromN1 :: (Vector v a, Num a) => a -> Int -> CircularVector v a Source #

O(n) Yield a circular vector of length max n 1 containing the values x, x+1 etc. This operation is usually more efficient than enumFromTo.

Since: 0.1.2

enumFromStepN :: (Vector v a, Num a) => a -> a -> Int -> Maybe (CircularVector v a) Source #

O(n) Yield a circular vector of the given length containing the values x, x+y, x+y+y etc. This operations is usually more efficient than enumFromThenTo.

If an enumeration does not use meaningful indices, Nothing is returned, otherwise, Just containing a circular vector.

Since: 0.1.2

enumFromStepN1 :: (Vector v a, Num a) => a -> a -> Int -> CircularVector v a Source #

O(n) Yield a circular vector of length max n 1 containing the values x, x+y, x+y+y etc. This operations is usually more efficient than enumFromThenTo.

Since: 0.1.2

enumFromTo :: (Vector v a, Enum a) => a -> a -> Maybe (CircularVector v a) Source #

O(n) Enumerate values from x to y.

If an enumeration does not use meaningful indices, Nothing is returned, otherwise, Just containing a circular vector.

WARNING: This operation can be very inefficient. If at all possible, use enumFromN instead.

Since: 0.1.2

enumFromThenTo :: (Vector v a, Enum a) => a -> a -> a -> Maybe (CircularVector v a) Source #

O(n) Enumerate values from x to y with a specific step z.

If an enumeration does not use meaningful indices, Nothing is returned, otherwise, Just containing a circular vector.

WARNING: This operation can be very inefficient. If at all possible, use enumFromStepN instead.

Since: 0.1.2

Concatenation

cons :: Vector v a => a -> CircularVector v a -> CircularVector v a Source #

O(n) Prepend an element

>>> cons 1 (unsafeFromList @Vector [2,3])
CircularVector {vector = [1,2,3], rotation = 0}

Since: 0.1.2

consV :: Vector v a => a -> v a -> CircularVector v a Source #

O(n) Prepend an element to a Vector

>>> consV 1 (Data.Vector.fromList [2,3])
CircularVector {vector = [1,2,3], rotation = 0}

Since: 0.1.2

snoc :: Vector v a => CircularVector v a -> a -> CircularVector v a Source #

O(n) Append an element

>>> snoc (unsafeFromList @Vector [1,2]) 3
CircularVector {vector = [1,2,3], rotation = 0}

Since: 0.1.2

snocV :: Vector v a => v a -> a -> CircularVector v a Source #

O(n) Append an element to a Vector

>>> snocV (Data.Vector.fromList [1,2]) 3
CircularVector {vector = [1,2,3], rotation = 0}

Since: 0.1.2

(++) :: Vector v a => CircularVector v a -> CircularVector v a -> CircularVector v a Source #

O(m+n) Concatenate two circular vectors

>>> (unsafeFromList @Vector [1..3]) ++ (unsafeFromList [4..6])
CircularVector {vector = [1,2,3,4,5,6], rotation = 0}

Since: 0.1.2

concat :: Vector v a => [CircularVector v a] -> Maybe (CircularVector v a) Source #

O(n) Concatenate all circular vectors in the list

If list is empty, Nothing is returned, otherwise Just containing the concatenated circular vectors

>>> concat [(unsafeFromList @Vector [1..3]), (unsafeFromList [4..6])]
Just (CircularVector {vector = [1,2,3,4,5,6], rotation = 0})

Since: 0.1.2

concat1 :: Vector v a => NonEmpty (CircularVector v a) -> CircularVector v a Source #

O(n) Concatenate all circular vectors in a non-empty list.

>>> concat1 ((unsafeFromList @Vector [1..3]) :| [(unsafeFromList [4..6])])
CircularVector {vector = [1,2,3,4,5,6], rotation = 0}

Since: 0.1.2

Restricting memory usage

force :: NFData a => a -> a #

a variant of deepseq that is useful in some circumstances:

force x = x `deepseq` x

force x fully evaluates x, and then returns it. Note that force x only performs evaluation when the value of force x itself is demanded, so essentially it turns shallow evaluation into deep evaluation.

force can be conveniently used in combination with ViewPatterns:

{-# LANGUAGE BangPatterns, ViewPatterns #-}
import Control.DeepSeq

someFun :: ComplexData -> SomeResult
someFun (force -> !arg) = {- 'arg' will be fully evaluated -}

Another useful application is to combine force with evaluate in order to force deep evaluation relative to other IO operations:

import Control.Exception (evaluate)
import Control.DeepSeq

main = do
  result <- evaluate $ force $ pureComputation
  {- 'result' will be fully evaluated at this point -}
  return ()

Finally, here's an exception safe variant of the readFile' example:

readFile' :: FilePath -> IO String
readFile' fn = bracket (openFile fn ReadMode) hClose $ \h ->
                       evaluate . force =<< hGetContents h

Since: deepseq-1.2.0.0

Template Haskell

Conversion

toVector :: Vector v a => CircularVector v a -> v a Source #

O(n) Construct a Vector from a CircularVector.

since 0.1.2

fromVector :: Vector v a => v a -> Maybe (CircularVector v a) Source #

O(1) Construct a CircularVector from a vector.

since 0.1.2

unsafeFromVector :: Vector v a => v a -> CircularVector v a Source #

O(1) Construct a CircularVector from a Vector.

Calls error if the input vector is empty.

since 0.1.2

toNonEmptyVector :: Vector v a => CircularVector v a -> NonEmptyVector a Source #

O(n) Construct a NonEmptyVector from a CircularVector.

Since: 0.1.2

toList :: Vector v a => CircularVector v a -> [a] Source #

O(n) Convert from a circular vector to a list.

>>> let nev = unsafeFromList @Vector [1..3] in toList nev
[1,2,3]

Since: 0.1.2

fromList :: Vector v a => [a] -> Maybe (CircularVector v a) Source #

O(n) Construct a CircularVector from a list.

since 0.1.2

fromListN :: Vector v a => Int -> [a] -> Maybe (CircularVector v a) Source #

Construct a CircularVector from a list with a size hint.

since 0.1.2

unsafeFromList :: Vector v a => [a] -> CircularVector v a Source #

O(n) Construct a CircularVector from a list.

Calls error if the input list is empty.

since 0.1.2

unsafeFromListN :: Vector v a => Int -> [a] -> CircularVector v a Source #

O(n) Construct a CircularVector from a list with a size hint.

Calls error if the input list is empty, or if the size hint is <= 0.

since 0.1.2

Rotation

rotateLeft :: Vector v a => Int -> CircularVector v a -> CircularVector v a Source #

O(1) Rotate the vector to the left by n number of elements.

Note: Left rotations start to break down due to arithmetic underflow when the size of the input vector is > maxBound Int@

since 0.1.2

rotateRight :: Vector v a => Int -> CircularVector v a -> CircularVector v a Source #

O(1) Rotate the vector to left by n number of elements.

Note: Right rotations start to break down due to arithmetic overflow when the size of the input vector is > maxBound Int@

since 0.1.2

Comparisons

equivalent :: (Vector v a, Eq (v a), Ord a) => CircularVector v a -> CircularVector v a -> Bool Source #

since 0.1.2

canonise :: (Vector v a, Ord a) => CircularVector v a -> CircularVector v a Source #

since 0.1.2

leastRotation :: forall a. Ord a => NonEmptyVector a -> Int Source #

since 0.1.2

Folds

foldMap :: (Monoid m, Vector v a) => (a -> m) -> CircularVector v a -> m Source #

Lazily-accumulating monoidal fold over a CircularVector. since 0.1.2

foldMap' :: (Monoid m, Vector v a) => (a -> m) -> CircularVector v a -> m Source #

Strictly-accumulating monoidal fold over a CircularVector.

since 0.1.2

foldr :: Vector v a => (a -> b -> b) -> b -> CircularVector v a -> b Source #

since 0.1.2

foldl :: Vector v a => (b -> a -> b) -> b -> CircularVector v a -> b Source #

foldr' :: Vector v a => (a -> b -> b) -> b -> CircularVector v a -> b Source #

foldl' :: Vector v a => (b -> a -> b) -> b -> CircularVector v a -> b Source #

foldr1 :: Vector v a => (a -> a -> a) -> CircularVector v a -> a Source #

foldl1 :: Vector v a => (a -> a -> a) -> CircularVector v a -> a Source #

foldMap1 :: (Vector v a, Semigroup m) => (a -> m) -> CircularVector v a -> m Source #

Lazily-accumulating semigroupoidal fold over a CircularVector.

since 0.1.2

foldMap1' :: (Vector v a, Semigroup m) => (a -> m) -> CircularVector v a -> m Source #

Strictly-accumulating semigroupoidal fold over a CircularVector.

since 0.1.2

toNonEmpty :: Vector v a => CircularVector v a -> NonEmpty a Source #

since 0.1.2

Specialized folds

all :: Vector v a => (a -> Bool) -> CircularVector v a -> Bool Source #

O(n) Check if all elements satisfy the predicate.

Since: 0.1.2

any :: Vector v a => (a -> Bool) -> CircularVector v a -> Bool Source #

O(n) Check if any element satisfies the predicate.

Since: 0.1.2

and :: Vector v Bool => CircularVector v Bool -> Bool Source #

O(n) Check if all elements are True.

Since: 0.1.2

or :: Vector v Bool => CircularVector v Bool -> Bool Source #

O(n) Check if any element is True.

Since: 0.1.2

sum :: (Vector v a, Num a) => CircularVector v a -> a Source #

O(n) Compute the sum of the elements.

Since: 0.1.2

product :: (Vector v a, Num a) => CircularVector v a -> a Source #

O(n) Compute the product of the elements.

Since: 0.1.2

maximum :: (Vector v a, Ord a) => CircularVector v a -> a Source #

O(n) Yield the maximum element of the circular vector.

Since: 0.1.2

maximumBy :: Vector v a => (a -> a -> Ordering) -> CircularVector v a -> a Source #

O(n) Yield the maximum element of a circular vector according to the given comparison function.

Since: 0.1.2

minimum :: (Vector v a, Ord a) => CircularVector v a -> a Source #

O(n) Yield the minimum element of the circular vector.

Since: 0.1.2

minimumBy :: Vector v a => (a -> a -> Ordering) -> CircularVector v a -> a Source #

O(n) Yield the minimum element of a circular vector according to the given comparison function.

Since: 0.1.2

rotateToMinimumBy :: Vector v a => (a -> a -> Ordering) -> CircularVector v a -> CircularVector v a Source #

O(n) Rotate to the minimum element of the circular vector according to the given comparison function.

Since: 0.1.2

rotateToMaximumBy :: Vector v a => (a -> a -> Ordering) -> CircularVector v a -> CircularVector v a Source #

O(n) Rotate to the maximum element of the circular vector according to the given comparison function.

Since: 0.1.2

Elementwise operations

Indexing

index :: Vector v a => CircularVector v a -> Int -> a Source #

O(1) Index into a CircularVector. This is always total.

since 0.1.2

head :: Vector v a => CircularVector v a -> a Source #

O(1) Get the first element of a CircularVector. This is always total.

since 0.1.2

last :: Vector v a => CircularVector v a -> a Source #

O(1) Get the last element of a CircularVector. This is always total.

since 0.1.2

Mapping

map :: (Vector v a, Vector v b) => (a -> b) -> CircularVector v a -> CircularVector v b Source #

O(n) Map a function over a circular vector.

>>> map (+1) $ unsafeFromList @Vector [1..3]
CircularVector {vector = [2,3,4], rotation = 0}

Since: 0.1.2

imap :: (Vector v a, Vector v b) => (Int -> a -> b) -> CircularVector v a -> CircularVector v b Source #

O(n) Apply a function to every element of a circular vector and its index.

>>> imap (\i a -> if i == 2 then a+1 else a+0) $ unsafeFromList @Vector [1..3]
CircularVector {vector = [1,2,4], rotation = 0}

Since: 0.1.2

concatMap :: (Vector v a, Vector v b) => (a -> CircularVector v b) -> CircularVector v a -> CircularVector v b Source #

Map a function over a circular vector and concatenate the results.

>>> concatMap (\a -> unsafeFromList @Vector [a,a]) (unsafeFromList [1,2,3])
CircularVector {vector = [1,1,2,2,3,3], rotation = 0}

Since: 0.1.2

Monadic mapping

mapM :: (Monad m, Vector v a, Vector v b) => (a -> m b) -> CircularVector v a -> m (CircularVector v b) Source #

O(n) Apply the monadic action to all elements of the circular vector, yielding circular vector of results.

>>> mapM Just (unsafeFromList @Vector [1..3])
Just (CircularVector {vector = [1,2,3], rotation = 0})
>>> mapM (const Nothing) (unsafeFromList @Vector [1..3])
Nothing

Since: 0.1.2

imapM :: (Monad m, Vector v a, Vector v b) => (Int -> a -> m b) -> CircularVector v a -> m (CircularVector v b) Source #

O(n) Apply the monadic action to every element of a circular vector and its index, yielding a circular vector of results.

>>> imapM (\i a -> if i == 1 then Just a else Just 0) (unsafeFromList @Vector [1..3])
Just (CircularVector {vector = [0,2,0], rotation = 0})
>>> imapM (\_ _ -> Nothing) (unsafeFromList @Vector [1..3])
Nothing

Since: 0.1.2

mapM_ :: (Monad m, Vector v a, Vector v b) => (a -> m b) -> CircularVector v a -> m () Source #

O(n) Apply the monadic action to all elements of a circular vector and ignore the results.

>>> mapM_ (const $ Just ()) (unsafeFromList @Vector [1..3])
Just ()
>>> mapM_ (const Nothing) (unsafeFromList @Vector [1..3])
Nothing

Since: 0.1.2

imapM_ :: (Monad m, Vector v a) => (Int -> a -> m b) -> CircularVector v a -> m () Source #

O(n) Apply the monadic action to every element of a circular vector and its index, ignoring the results

>>> imapM_ (\i a -> if i == 1 then print a else putStrLn "0") (unsafeFromList @Vector [1..3])
0
2
0
>>> imapM_ (\_ _ -> Nothing) (unsafeFromList @Vector [1..3])
Nothing

Since: 0.1.2

forM :: (Monad m, Vector v a, Vector v b) => CircularVector v a -> (a -> m b) -> m (CircularVector v b) Source #

O(n) Apply the monadic action to all elements of the circular vector, yielding a circular vector of results.

Equivalent to flip mapM.

Since: 0.1.2

forM_ :: (Monad m, Vector v a) => CircularVector v a -> (a -> m b) -> m () Source #

O(n) Apply the monadic action to all elements of a circular vector and ignore the results.

Equivalent to flip mapM_.

Since: 0.1.2

Zipping

zipWith :: (Vector v a, Vector v b, Vector v c) => (a -> b -> c) -> CircularVector v a -> CircularVector v b -> CircularVector v c Source #

O(min(m,n)) Zip two circular vectors with the given function.

Since: 0.1.2

zipWith3 :: (Vector v a, Vector v b, Vector v c, Vector v d) => (a -> b -> c -> d) -> CircularVector v a -> CircularVector v b -> CircularVector v c -> CircularVector v d Source #

Zip three circular vectors with the given function.

Since: 0.1.2

zip :: (Vector v a, Vector v b, Vector v (a, b)) => CircularVector v a -> CircularVector v b -> CircularVector v (a, b) Source #

O(min(n,m)) Elementwise pairing of circular vector elements. This is a special case of zipWith where the function argument is (,)

Since: 0.1.2

zip3 :: (Vector v a, Vector v b, Vector v c, Vector v (a, b, c)) => CircularVector v a -> CircularVector v b -> CircularVector v c -> CircularVector v (a, b, c) Source #

Zip together three circular vectors.

Since: 0.1.2

Unzipping

unzip :: [(a, b)] -> ([a], [b]) #

unzip transforms a list of pairs into a list of first components and a list of second components.

unzip3 :: [(a, b, c)] -> ([a], [b], [c]) #

The unzip3 function takes a list of triples and returns three lists, analogous to unzip.

Filtering

uniq :: (Vector v a, Eq a) => CircularVector v a -> CircularVector v a Source #

O(n) Drop repeated adjacent elements.

>>> toList $ uniq $ unsafeFromList @Vector [1,1,2,2,3,3,1]
[1,2,3]
>>> toList $ uniq $ unsafeFromList @Vector [1,2,3,1]
[1,2,3]

mapMaybe :: (Vector v a, Vector v b) => (a -> Maybe b) -> CircularVector v a -> v b Source #

O(n) Drop elements when predicate returns Nothing

If no elements satisfy the predicate, the resulting vector may be empty.

>>> mapMaybe (\a -> if a == 2 then Nothing else Just a) (unsafeFromList @Vector [1..3])
[1,3]

Since: 0.1.2

imapMaybe :: (Vector v a, Vector v b) => (Int -> a -> Maybe b) -> CircularVector v a -> v b Source #

O(n) Drop elements when predicate, applied to index and value, returns Nothing

If no elements satisfy the predicate, the resulting vector may be empty.

>>> imapMaybe (\i a -> if a == 2 || i == 2 then Nothing else Just a) (unsafeFromList @Vector [1..3])
[1]

Since: 0.1.2

filter :: Vector v a => (a -> Bool) -> CircularVector v a -> v a Source #

O(n) Drop elements that do not satisfy the predicate.

If no elements satisfy the predicate, the resulting vector may be empty.

>>> filter (\a -> if a == 2 then False else True) (unsafeFromList @Vector [1..3])
[1,3]
>>> filter (const False) (unsafeFromList @Vector [1..3])
[]

ifilter :: Vector v a => (Int -> a -> Bool) -> CircularVector v a -> v a Source #

O(n) Drop elements that do not satisfy the predicate which is applied to values and their indices.

If no elements satisfy the predicate, the resulting vector may be empty.

>>> ifilter (\i a -> if a == 2 || i == 0 then False else True) (unsafeFromList @Vector [1..3])
[3]
>>> ifilter (\_ _ -> False) (unsafeFromList @Vector [1..3])
[]

Since: 0.1.2

filterM :: (Monad m, Vector v a) => (a -> m Bool) -> CircularVector v a -> m (v a) Source #

O(n) Drop elements that do not satisfy the monadic predicate.

If no elements satisfy the predicate, the resulting vector may be empty.

>>> filterM (\a -> if a == 2 then Just False else Just True) (unsafeFromList @Vector [1..3])
Just [1,3]
>>> filterM (\a -> if a == 2 then Nothing else Just True) (unsafeFromList @Vector [1..3])
Nothing
>>> filterM (const $ Just False) (unsafeFromList @Vector [1..3])
Just []

Since: 0.1.2

takeWhile :: Vector v a => (a -> Bool) -> CircularVector v a -> v a Source #

O(n) Yield the longest prefix of elements satisfying the predicate without copying.

If no elements satisfy the predicate, the resulting vector may be empty.

>>> takeWhile (/= 3) (unsafeFromList @Vector [1..3])
[1,2]

Since: 0.1.2

dropWhile :: Vector v a => (a -> Bool) -> CircularVector v a -> v a Source #

O(n) Drop the longest prefix of elements that satisfy the predicate without copying.

If all elements satisfy the predicate, the resulting vector may be empty.

>>> dropWhile (/= 3) (unsafeFromList @Vector [1..3])
[3]

Since: 0.1.2

Partitioning

partition :: Vector v a => (a -> Bool) -> CircularVector v a -> (v a, v a) Source #

O(n) Split the circular vector in two parts, the first one containing those elements that satisfy the predicate and the second one those that don't. The relative order of the elements is preserved at the cost of a sometimes reduced performance compared to unstablePartition.

If all or no elements satisfy the predicate, one of the resulting vectors may be empty.

>>> partition (< 3) (unsafeFromList @Vector [1..5])
([1,2],[3,4,5])

Since: 0.1.2

unstablePartition :: Vector v a => (a -> Bool) -> CircularVector v a -> (v a, v a) Source #

O(n) Split the circular vector in two parts, the first one containing those elements that satisfy the predicate and the second one those that don't. The order of the elements is not preserved but the operation is often faster than partition.

If all or no elements satisfy the predicate, one of the resulting vectors may be empty.

Since: 0.1.2

span :: Vector v a => (a -> Bool) -> CircularVector v a -> (v a, v a) Source #

O(n) Split the circular vector into the longest prefix of elements that satisfy the predicate and the rest without copying.

If all or no elements satisfy the predicate, one of the resulting vectors may be empty.

>>> span (== 1) (unsafeFromList @Vector [1,1,2,3,1])
([1,1],[2,3,1])

Since: 0.1.2

break :: Vector v a => (a -> Bool) -> CircularVector v a -> (v a, v a) Source #

O(n) Split the circular vector into the longest prefix of elements that do not satisfy the predicate and the rest without copying.

If all or no elements satisfy the predicate, one of the resulting vectors may be empty.

>>> break (== 2) (unsafeFromList @Vector [1,1,2,3,1])
([1,1],[2,3,1])

Since: 0.1.2

Searching

elem :: (Vector v a, Eq a) => a -> CircularVector v a -> Bool Source #

O(n) Check if the circular vector contains an element

>>> elem 1 $ unsafeFromList @Vector [1..3]
True
>>> elem 4 $ unsafeFromList @Vector [1..3]
False

Since: 0.1.2

notElem :: (Vector v a, Eq a) => a -> CircularVector v a -> Bool Source #

O(n) Check if the circular vector does not contain an element (inverse of elem)

>>> notElem 1 $ unsafeFromList @Vector [1..3]
False
>>> notElem 4 $ unsafeFromList @Vector [1..3]
True

Since: 0.1.2

find :: Vector v a => (a -> Bool) -> CircularVector v a -> Maybe a Source #

O(n) Yield Just the first element matching the predicate or Nothing if no such element exists.

>>> find (< 2) $ unsafeFromList @Vector [1..3]
Just 1
>>> find (< 0) $ unsafeFromList @Vector [1..3]
Nothing

Since: 0.1.2

findIndex :: Vector v a => (a -> Bool) -> CircularVector v a -> Maybe Int Source #

O(n) Yield Just the index of the first element matching the predicate or Nothing if no such element exists.

>>> findIndex (< 2) $ unsafeFromList @Vector [1..3]
Just 0
>>> findIndex (< 0) $ unsafeFromList @Vector [1..3]
Nothing
>>> findIndex (==1) $ rotateRight 1 (unsafeFromList @Vector [1..3])
Just 2

Since: 0.1.2

findIndices :: (Vector v a, Vector v Int) => (a -> Bool) -> CircularVector v a -> v Int Source #

O(n) Yield the indices of elements satisfying the predicate in ascending order.

>>> findIndices (< 3) $ unsafeFromList @Vector [1..3]
[0,1]
>>> findIndices (< 0) $ unsafeFromList @Vector [1..3]
[]

Since: 0.1.2

elemIndex :: (Vector v a, Eq a) => a -> CircularVector v a -> Maybe Int Source #

O(n) Yield Just the index of the first occurence of the given element or Nothing if the circular vector does not contain the element. This is a specialised version of findIndex.

>>> elemIndex 1 $ unsafeFromList @Vector [1..3]
Just 0
>>> elemIndex 0 $ unsafeFromList @Vector [1..3]
Nothing

Since: 0.1.2

elemIndices :: (Vector v a, Vector v Int, Eq a) => a -> CircularVector v a -> v Int Source #

O(n) Yield the indices of all occurences of the given element in ascending order. This is a specialised version of findIndices.

>>> elemIndices 1 $ unsafeFromList @Vector [1,2,3,1]
[0,3]
>>> elemIndices 0 $ unsafeFromList @Vector [1..3]
[]

Since: 0.1.2

Permutations

reverse :: Vector v a => CircularVector v a -> CircularVector v a Source #

O(n) Reverse a circular vector.

Since: 0.1.2

backpermute :: (Vector v a, Vector v Int) => CircularVector v a -> CircularVector v Int -> CircularVector v a Source #

O(n) Yield the circular vector obtained by replacing each element i of the circular index vector by xs!i. This is equivalent to map (xs!) is but is often much more efficient.

>>> toList $ backpermute @Vector (unsafeFromList @Vector [1..3]) (unsafeFromList @Vector [2,0])
[3,1]

Since: 0.1.2

unsafeBackpermute :: (Vector v a, Vector v Int) => CircularVector v a -> CircularVector v Int -> CircularVector v a Source #

Same as backpermute but without bounds checking.

Since: 0.1.2

Safe destructive updates

modify :: Vector v a => (forall s. Mutable v s a -> ST s ()) -> CircularVector v a -> CircularVector v a Source #

Apply a destructive operation to a circular vector. The operation will be performed in place if it is safe to do so and will modify a copy of the circular vector otherwise.

Since: 0.1.2

Monadic Sequencing

sequence :: (Traversable t, Monad m) => t (m a) -> m (t a) #

Evaluate each monadic action in the structure from left to right, and collect the results. For a version that ignores the results see sequence_.

sequence_ :: (Foldable t, Monad m) => t (m a) -> m () #

Evaluate each monadic action in the structure from left to right, and ignore the results. For a version that doesn't ignore the results see sequence.

As of base 4.8.0.0, sequence_ is just sequenceA_, specialized to Monad.