nonempty-vector-0.2.0.2: Non-empty vectors

Copyright(c) 2019 Emily Pillmore
LicenseBSD-style
MaintainerEmily Pillmore <emilypi@cohomolo.gy>
StabilityExperimental
PortabilityDataTypeable, CPP
Safe HaskellNone
LanguageHaskell2010

Data.Vector.NonEmpty

Contents

Description

A library for non-empty boxed vectors (that is, polymorphic arrays capable of holding any Haskell value). Non-empty vectors come in two flavors:

  • mutable
  • immutable

This library attempts to provide support for all standard Vector operations in the API, with some slight variation in types and implementation. For example, since head and foldr are always gauranteed to be over a non-empty Vector, it is safe to make use of the 'unsafe-*' Vector operations and semigroupal folds available in the API in lieu of the standard implementations.

In contrast, some operations such as filter may "break out" of a NonEmptyVector due to the fact that there are no guarantees that may be made on the types of Bool-valued functions passed in, hence one could write the following:

filter (const false) v

which always produces an empty vector. Thus, some operations must return either a Maybe containing a NonEmptyVector or a Vector whenever appropriate. Generally The former is used in initialization and generation operations, and the latter is used in iterative operations where the intent is not to create an instance of NonEmptyVector.

Credit to Roman Leshchinskiy for the original Vector library upon which this is based.

Synopsis

Boxed non-empty vectors

data NonEmptyVector a Source #

NonEmptyVector is a thin wrapper around Vector that witnesses an API requiring non-empty construction, initialization, and generation of non-empty vectors by design.

A newtype wrapper was chosen so that no new pointer indirection is introduced when working with Vectors, and all performance characteristics inherited from the Vector API still apply.

Instances
Monad NonEmptyVector Source # 
Instance details

Defined in Data.Vector.NonEmpty

Functor NonEmptyVector Source # 
Instance details

Defined in Data.Vector.NonEmpty

Methods

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

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

Applicative NonEmptyVector Source # 
Instance details

Defined in Data.Vector.NonEmpty

Foldable NonEmptyVector Source # 
Instance details

Defined in Data.Vector.NonEmpty

Methods

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

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

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

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

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

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

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

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

toList :: NonEmptyVector a -> [a] #

null :: NonEmptyVector a -> Bool #

length :: NonEmptyVector a -> Int #

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

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

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

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

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

Traversable NonEmptyVector Source # 
Instance details

Defined in Data.Vector.NonEmpty

Methods

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

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

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

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

Eq1 NonEmptyVector Source # 
Instance details

Defined in Data.Vector.NonEmpty

Methods

liftEq :: (a -> b -> Bool) -> NonEmptyVector a -> NonEmptyVector b -> Bool #

Ord1 NonEmptyVector Source # 
Instance details

Defined in Data.Vector.NonEmpty

Methods

liftCompare :: (a -> b -> Ordering) -> NonEmptyVector a -> NonEmptyVector b -> Ordering #

Read1 NonEmptyVector Source # 
Instance details

Defined in Data.Vector.NonEmpty

Show1 NonEmptyVector Source # 
Instance details

Defined in Data.Vector.NonEmpty

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> NonEmptyVector a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [NonEmptyVector a] -> ShowS #

MonadZip NonEmptyVector Source # 
Instance details

Defined in Data.Vector.NonEmpty

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

Defined in Data.Vector.NonEmpty

Data a => Data (NonEmptyVector a) Source # 
Instance details

Defined in Data.Vector.NonEmpty

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NonEmptyVector a -> c (NonEmptyVector a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (NonEmptyVector a) #

toConstr :: NonEmptyVector a -> Constr #

dataTypeOf :: NonEmptyVector a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (NonEmptyVector a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NonEmptyVector a)) #

gmapT :: (forall b. Data b => b -> b) -> NonEmptyVector a -> NonEmptyVector a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NonEmptyVector a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NonEmptyVector a -> r #

gmapQ :: (forall d. Data d => d -> u) -> NonEmptyVector a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NonEmptyVector a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NonEmptyVector a -> m (NonEmptyVector a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NonEmptyVector a -> m (NonEmptyVector a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NonEmptyVector a -> m (NonEmptyVector a) #

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

Defined in Data.Vector.NonEmpty

Read a => Read (NonEmptyVector a) Source # 
Instance details

Defined in Data.Vector.NonEmpty

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

Defined in Data.Vector.NonEmpty

Semigroup (NonEmptyVector a) Source # 
Instance details

Defined in Data.Vector.NonEmpty

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

Defined in Data.Vector.NonEmpty

Methods

rnf :: NonEmptyVector a -> () #

Accessors

Length information

length :: NonEmptyVector a -> Int Source #

O(1) Length.

>>> length $ unsafeFromList [1..10]
10

Indexing

head :: NonEmptyVector a -> a Source #

O(1) First element. Since head is gauranteed, bounds checks are bypassed by deferring to unsafeHead.

>>> head $ unsafeFromList [1..10]
1

last :: NonEmptyVector a -> a Source #

O(1) Last element. Since a last element is gauranteed, bounds checks are bypassed by deferring to unsafeLast.

>>> last $ unsafeFromList [1..10]
10

(!) :: NonEmptyVector a -> Int -> a Source #

O(1) Indexing.

>>> (unsafeFromList [1..10]) ! 0
1

(!?) :: NonEmptyVector a -> Int -> Maybe a Source #

O(1) Safe indexing.

>>> (unsafeFromList [1..10]) !? 0
Just 1
>>> (unsafeFromList [1..10]) !? 11
Nothing

unsafeIndex :: NonEmptyVector a -> Int -> a Source #

O(1) Unsafe indexing without bounds checking

Monadic Indexing

headM :: Monad m => NonEmptyVector a -> m a Source #

O(1) First element of a non-empty vector in a monad.

See indexM for an explanation of why this is useful.

Note that this function defers to unsafeHeadM since head is gauranteed to be safe by construction.

>>> headM @[] (unsafeFromList [1..10])
[1]

lastM :: Monad m => NonEmptyVector a -> m a Source #

O(1) Last element of a non-empty vector in a monad. See indexM for an explanation of why this is useful.

Note that this function defers to unsafeHeadM since a last element is gauranteed.

>>> lastM @[] (unsafeFromList [1..10])
[10]

indexM :: Monad m => NonEmptyVector a -> Int -> m a Source #

O(1) Indexing in a monad.

The monad allows operations to be strict in the non-empty vector when necessary.

See indexM for more details

>>> indexM @[] (unsafeFromList [1..10]) 3
[4]

unsafeIndexM :: Monad m => NonEmptyVector a -> Int -> m a Source #

O(1) Indexing in a monad without bounds checks. See indexM for an explanation of why this is useful.

Extracting subvectors (slicing)

tail :: NonEmptyVector a -> Vector a Source #

O(1) Yield all but the first element without copying. Since the vector returned may be empty (i.e. input was a singleton), this function returns a normal Vector

>>> tail (unsafeFromList [1..10])
[2,3,4,5,6,7,8,9,10]

slice :: Int -> Int -> NonEmptyVector a -> Vector a Source #

O(1) Yield a slice of the non-empty vector without copying it. The vector must contain at least i+n elements. Because this is not guaranteed, this function returns a Vector which could be empty

>>> slice 0 3 (unsafeFromList [1..10])
[1,2,3]

init :: NonEmptyVector a -> Vector a Source #

O(1) Yield all but the last element without copying. Since the vector returned may be empty (i.e. input was a singleton), this function returns a normal Vector

>>> init (unsafeFromList [1..3])
[1,2]

take :: Int -> NonEmptyVector a -> Vector a Source #

O(1) Yield at the first n elements without copying. The non-empty vector may contain less than n elements in which case it is returned as a vector unchanged.

>>> take 2 (unsafeFromList [1..3])
[1,2]

drop :: Int -> NonEmptyVector a -> Vector a Source #

O(1) Yield all but the first n elements without copying. The non-empty vector may contain less than n elements in which case an empty vector is returned.

>>> drop 2 (unsafeFromList [1..3])
[3]

uncons :: NonEmptyVector a -> (a, Vector a) Source #

O(1) Yield a slice of a non-empty vector without copying at the 0th and 1st indices.

>>> uncons (unsafeFromList [1..10])
(1,[2,3,4,5,6,7,8,9,10])

unsnoc :: NonEmptyVector a -> (Vector a, a) Source #

O(1) Yield a slice of a non-empty vector without copying at the n-1th and nth indices

>>> unsnoc (unsafeFromList [1..10])
([1,2,3,4,5,6,7,8,9],10)

splitAt :: Int -> NonEmptyVector a -> (Vector a, Vector a) Source #

O(1) Yield the first n elements paired with the remainder without copying.

This function returns a pair of vectors, as one may slice a (0, n+1).

>>> splitAt 2 (unsafeFromList [1..3])
([1,2],[3])

unsafeSlice :: Int -> Int -> NonEmptyVector a -> Vector a Source #

O(1) Yield a slice of the vector without copying. The vector must contain at least i+n elements but this is not checked.

unsafeTake :: Int -> NonEmptyVector a -> Vector a Source #

O(1) Yield the first n elements without copying. The vector must contain at least n elements but this is not checked.

unsafeDrop :: Int -> NonEmptyVector a -> Vector a Source #

O(1) Yield all but the first n elements without copying. The vector must contain at least n elements but this is not checked.

Construction

Initialization

singleton :: a -> NonEmptyVector a Source #

O(1) Non-empty vector with exactly one element

>>> singleton "a"
["a"]

replicate :: Int -> a -> Maybe (NonEmptyVector a) Source #

O(n) Non-empty 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 3 "a"
Just ["a","a","a"]
>>> replicate 0 "a"
Nothing

replicate1 :: Int -> a -> NonEmptyVector a Source #

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

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

>>> replicate1 3 "a"
["a","a","a"]
>>> replicate1 0 "a"
["a"]
>>> replicate1 (-1) "a"
["a"]

generate :: Int -> (Int -> a) -> Maybe (NonEmptyVector a) Source #

O(n) Construct a 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 1 f
Just ["a"]
>>> generate 0 f
Nothing
>>> generate 2 f
Just ["a","k"]

generate1 :: Int -> (Int -> a) -> NonEmptyVector a Source #

O(n) Construct a 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
>>> generate1 2 f
["a","k"]
>>> generate1 0 f
["a"]
>>> generate1 (-1) f
["a"]

iterateN :: Int -> (a -> a) -> a -> Maybe (NonEmptyVector 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 3 (+1) 0
Just [0,1,2]
>>> iterateN 0 (+1) 0
Nothing
>>> iterateN (-1) (+1) 0
Nothing

iterateN1 :: Int -> (a -> a) -> a -> NonEmptyVector 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 3 (+1) 0
[0,1,2]
>>> iterateN1 0 (+1) 0
[0]
>>> iterateN1 (-1) (+1) 0
[0]

Monad Initialization

replicateM :: Monad m => Int -> m a -> m (Maybe (NonEmptyVector a)) Source #

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

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

>>> replicateM @Maybe 3 (Just "a")
Just (Just ["a","a","a"])
>>> replicateM @Maybe 3 Nothing
Nothing
>>> replicateM @Maybe 0 (Just "a")
Just Nothing
>>> replicateM @Maybe (-1) (Just "a")
Just Nothing

replicate1M :: Monad m => Int -> m a -> m (NonEmptyVector a) Source #

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

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

>>> replicate1M @Maybe 3 (Just "a")
Just ["a","a","a"]
>>> replicate1M @Maybe 3 Nothing
Nothing
>>> replicate1M @Maybe 0 (Just "a")
Just ["a"]
>>> replicate1M @Maybe (-1) (Just "a")
Just ["a"]

generateM :: Monad m => Int -> (Int -> m a) -> m (Maybe (NonEmptyVector a)) Source #

O(n) Construct a 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 3 (\i -> if i P.< 1 then ["a"] else ["b"])
[Just ["a","b","b"]]
>>> generateM @[] @Int 3 (const [])
[]
>>> generateM @[] @Int 0 (const [1])
[Nothing]
>>> generateM @Maybe @Int (-1) (const Nothing)
Just Nothing

generate1M :: Monad m => Int -> (Int -> m a) -> m (NonEmptyVector a) Source #

O(n) Construct a 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 3 (\i -> if i P.< 1 then Just "a" else Just "b")
Just ["a","b","b"]
>>> generate1M 3 (const [])
[]
>>> generate1M 0 (const $ Just 1)
Just [1]
>>> generate1M (-1) (const Nothing)
Nothing

iterateNM :: Monad m => Int -> (a -> m a) -> a -> m (Maybe (NonEmptyVector 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 3 return "a"
Just (Just ["a","a","a"])
>>> iterateNM @Maybe 3 (const Nothing) "a"
Nothing
>>> iterateNM @Maybe 0 return "a"
Just Nothing

iterateN1M :: Monad m => Int -> (a -> m a) -> a -> m (NonEmptyVector 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 3 return "a"
Just ["a","a","a"]
>>> iterateN1M @Maybe 3 (const Nothing) "a"
Nothing
>>> iterateN1M @Maybe 0 return "a"
Just ["a"]
>>> iterateN1M @Maybe (-1) return "a"
Just ["a"]

create :: (forall s. ST s (MVector s a)) -> Maybe (NonEmptyVector a) Source #

Execute the monadic action and freeze the resulting non-empty vector.

unsafeCreate :: (forall s. ST s (MVector s a)) -> NonEmptyVector a Source #

Execute the monadic action and freeze the resulting non-empty vector, bypassing emptiness checks.

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

createT :: Traversable t => (forall s. ST s (t (MVector s a))) -> t (Maybe (NonEmptyVector a)) Source #

Execute the monadic action and freeze the resulting non-empty vector.

unsafeCreateT :: Traversable t => (forall s. ST s (t (MVector s a))) -> t (NonEmptyVector a) Source #

Execute the monadic action and freeze the resulting non-empty vector.

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

Unfolding

unfoldr :: (b -> Maybe (a, b)) -> b -> Maybe (NonEmptyVector a) Source #

O(n) Construct a non-empty 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 non-empty vector is returned.

>>> unfoldr (\b -> case b of "a" -> Just ("a", "b"); _ ->  Nothing) "a"
Just ["a"]
>>> unfoldr (const Nothing) "a"
Nothing

unfoldr1 :: (b -> Maybe (a, b)) -> a -> b -> NonEmptyVector a Source #

O(n) Construct a non-empty 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 (\b -> case b of "a" -> Just ("a", "b"); _ ->  Nothing) "first" "a"
["first","a"]
>>> unfoldr1 (const Nothing) "first" "a"
["first"]

unfoldrN :: Int -> (b -> Maybe (a, b)) -> b -> Maybe (NonEmptyVector a) Source #

O(n) Construct a 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 non-empty vector is returned.

>>> unfoldrN 3 (\b -> Just (b+1, b+1)) 0
Just [1,2,3]
>>> unfoldrN 3 (const Nothing) 0
Nothing
>>> unfoldrN 0 (\b -> Just (b+1, b+1)) 0
Nothing

unfoldr1N :: Int -> (b -> Maybe (a, b)) -> a -> b -> NonEmptyVector a Source #

O(n) Construct a 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 3 (\b -> Just (b+1, b+1)) 0 0
[0,1,2,3]
>>> unfoldr1N 3 (const Nothing) 0 0
[0]
>>> unfoldr1N 0 (\b -> Just (b+1, b+1)) 0 0
[0]

unfoldrM :: Monad m => (b -> m (Maybe (a, b))) -> b -> m (Maybe (NonEmptyVector a)) Source #

O(n) Construct a non-empty 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 non-empty vector is returned.

unfoldr1M :: Monad m => (b -> m (Maybe (a, b))) -> a -> b -> m (NonEmptyVector a) Source #

O(n) Construct a non-empty 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.

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

O(n) Construct a non-empty 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 non-empty vector is returned.

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

O(n) Construct a non-empty 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.

constructN :: Int -> (Vector a -> a) -> Maybe (NonEmptyVector a) Source #

O(n) Construct a non-empty 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 non-empty vector is returned.

constructrN :: Int -> (Vector a -> a) -> Maybe (NonEmptyVector a) Source #

O(n) Construct a 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 non-empty vector is returned.

Enumeration

enumFromN :: Num a => a -> Int -> Maybe (NonEmptyVector a) Source #

O(n) Yield a non-emptyvector 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 non-empty vector.

enumFromN1 :: Num a => a -> Int -> NonEmptyVector a Source #

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

enumFromStepN :: Num a => a -> a -> Int -> Maybe (NonEmptyVector a) Source #

O(n) Yield a non-empty 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 non-empty vector.

enumFromStepN1 :: Num a => a -> a -> Int -> NonEmptyVector a Source #

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

enumFromTo :: Enum a => a -> a -> Maybe (NonEmptyVector 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 non-empty vector.

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

enumFromThenTo :: Enum a => a -> a -> a -> Maybe (NonEmptyVector 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 non-empty vector.

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

Concatenation

cons :: a -> NonEmptyVector a -> NonEmptyVector a Source #

O(n) Prepend an element

>>> cons 1 (unsafeFromList [2,3])
[1,2,3]

snoc :: NonEmptyVector a -> a -> NonEmptyVector a Source #

O(n) Append an element

>>> snoc (unsafeFromList [1,2]) 3
[1,2,3]

(++) :: NonEmptyVector a -> NonEmptyVector a -> NonEmptyVector a Source #

O(m+n) Concatenate two non-empty vectors

>>> (unsafeFromList [1..3]) ++ (unsafeFromList [4..6])
[1,2,3,4,5,6]

concat :: [NonEmptyVector a] -> Maybe (NonEmptyVector a) Source #

O(n) Concatenate all non-empty vectors in the list

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

>>> concat [(unsafeFromList [1..3]), (unsafeFromList [4..6])]
Just [1,2,3,4,5,6]

concat1 :: NonEmpty (NonEmptyVector a) -> NonEmptyVector a Source #

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

>>> concat1 ((unsafeFromList [1..3]) :| [(unsafeFromList [4..6])])
[1,2,3,4,5,6]

Restricting memory usage

force :: NonEmptyVector a -> NonEmptyVector a Source #

O(n) Yield the argument but force it not to retain any extra memory, possibly by copying it.

Conversion

To/from non-empty lists

toNonEmpty :: NonEmptyVector a -> NonEmpty a Source #

O(n) Convert a non-empty vector to a non-empty list.

>>> toNonEmpty (unsafeFromList [1..3])
1 :| [2,3]

fromNonEmpty :: NonEmpty a -> NonEmptyVector a Source #

O(n) Convert from a non-empty list to a non-empty vector.

>>> fromNonEmpty (1 :| [2,3])
[1,2,3]

fromNonEmptyN :: Int -> NonEmpty a -> Maybe (NonEmptyVector a) Source #

O(n) Convert from the first n-elements of a non-empty list to a non-empty vector.

Returns Nothing if indices are <= 0, otherwise Just containing the non-empty vector.

>>> fromNonEmptyN 3 (1 :| [2..5])
Just [1,2,3]
>>> fromNonEmptyN 0 (1 :| [2..5])
Nothing

fromNonEmptyN1 :: Int -> NonEmpty a -> NonEmptyVector a Source #

O(n) Convert from the first n-elements of a non-empty list to a non-empty vector. This is a safe version of fromNonEmptyN which takes max n 1 of the first n-elements of the non-empty list.

>>> fromNonEmptyN1 3 (1 :| [2..5])
[1,2,3]
>>> fromNonEmptyN1 0 (1 :| [2..5])
[1]

unsafeFromList :: [a] -> NonEmptyVector a Source #

O(n) Convert from a list to a non-empty vector.

Warning: the onus is on the user to ensure that their vector is not empty, otherwise all bets are off!

>>> unsafeFromList [1..3]
[1,2,3]

To/from vector

toVector :: NonEmptyVector a -> Vector a Source #

O(1) Convert from a non-empty vector to a vector.

>>> let nev :: NonEmptyVector Int = unsafeFromList [1..3] in toVector nev
[1,2,3]

fromVector :: Vector a -> Maybe (NonEmptyVector a) Source #

O(1) Convert from a vector to a non-empty vector.

If the vector is empty, then Nothing is returned, otherwise Just containing the non-empty vector.

>>> fromVector $ V.fromList [1..3]
Just [1,2,3]
>>> fromVector $ V.fromList []
Nothing

unsafeFromVector :: Vector a -> NonEmptyVector a Source #

O(1) Convert from a vector to a non-empty vector without checking bounds.

Warning: the onus is on the user to ensure that their vector is not empty, otherwise all bets are off!

>>> unsafeFromVector $ V.fromList [1..3]
[1,2,3]

To/from list

toList :: NonEmptyVector a -> [a] Source #

O(n) Convert from a non-empty vector to a list.

>>> let nev :: NonEmptyVector Int = unsafeFromList [1..3] in toList nev
[1,2,3]

fromList :: [a] -> Maybe (NonEmptyVector a) Source #

O(n) Convert from a list to a non-empty vector.

>>> fromList [1..3]
Just [1,2,3]
>>> fromList []
Nothing

fromListN :: Int -> [a] -> Maybe (NonEmptyVector a) Source #

O(n) Convert the first n elements of a list to a non-empty vector.

If the list is empty or <= 0 elements are chosen, Nothing is returned, otherwise Just containing the non-empty vector

>>> fromListN 3 [1..5]
Just [1,2,3]
>>> fromListN 3 []
Nothing
>>> fromListN 0 [1..5]
Nothing

Modifying non-empty vectors

Bulk Updates

(//) :: NonEmptyVector a -> [(Int, a)] -> NonEmptyVector a Source #

O(m+n) For each pair (i,a) from the list, replace the non-empty vector element at position i by a.

>>> unsafeFromList [1..3] // [(2,4)]
[1,2,4]
>>> unsafeFromList [1..3] // []
[1,2,3]

update :: NonEmptyVector a -> Vector (Int, a) -> NonEmptyVector a Source #

O(m+n) For each pair (i,a) from the vector of index/value pairs, replace the vector element at position i by a.

>>> unsafeFromList [1..3] `update` V.fromList [(2,4)]
[1,2,4]
>>> unsafeFromList [1..3] `update` V.empty
[1,2,3]

update_ :: NonEmptyVector a -> Vector Int -> Vector a -> NonEmptyVector a Source #

O(m+min(n1,n2)) For each index i from the index vector and the corresponding value a from the value vector, replace the element of the initial vector at position i by a.

>>> update_ (unsafeFromList [1..3]) (V.fromList [2]) (V.fromList [4])
[1,2,4]
>>> update_ (unsafeFromList [1..3]) V.empty V.empty
[1,2,3]

unsafeUpd :: NonEmptyVector a -> [(Int, a)] -> NonEmptyVector a Source #

Same as '(//)' but without bounds checking.

unsafeUpdate :: NonEmptyVector a -> Vector (Int, a) -> NonEmptyVector a Source #

Same as update but without bounds checking.

unsafeUpdate_ :: NonEmptyVector a -> Vector Int -> Vector a -> NonEmptyVector a Source #

Same as update_ but without bounds checking.

Accumulations

accum Source #

Arguments

:: (a -> b -> a)

accumulating function f

-> NonEmptyVector a

initial non-empty vector (of length m)

-> [(Int, b)]

list of index/value pairs (of length n)

-> NonEmptyVector a 

O(m+n) For each pair (i,b) from the non-empty list, replace the non-empty vector element a at position i by f a b.

>>> accum (+) (unsafeFromList [1..3]) [(2,10)]
[1,2,13]
>>> accum (+) (unsafeFromList [1..3]) []
[1,2,3]

accumulate Source #

Arguments

:: (a -> b -> a)

accumulating function f

-> NonEmptyVector a

initial non-empty vector (of length m)

-> Vector (Int, b)

vector of index/value pairs (of length n)

-> NonEmptyVector a 

O(m+n) For each pair (i,b) from the vector of pairs, replace the non-empty vector element a at position i by f a b.

>>> accumulate (+) (unsafeFromList [1..3]) (V.fromList [(2,10)])
[1,2,13]
>>> accumulate (+) (unsafeFromList [1..3]) V.empty
[1,2,3]

accumulate_ Source #

Arguments

:: (a -> b -> a)

accumulating function f

-> NonEmptyVector a

initial non-empty vector (of length m)

-> Vector Int

vector of indices (of length n1)

-> Vector b

vector of values (of length n2)

-> NonEmptyVector a 

O(m+min(n1,n2)) For each index i from the index vector and the corresponding value b from the the value vector, replace the element of the initial non-empty vector at position i by f a b.

>>> accumulate_ (+) (unsafeFromList [1..3]) (V.fromList [2]) (V.fromList [10])
[1,2,13]
>>> accumulate_ (+) (unsafeFromList [1..3]) V.empty V.empty
[1,2,3]

unsafeAccum Source #

Arguments

:: (a -> b -> a)

accumulating function f

-> NonEmptyVector a

initial non-empty vector (of length m)

-> [(Int, b)]

list of index/value pairs (of length n)

-> NonEmptyVector a 

Same as accum but without bounds checking.

unsafeAccumulate Source #

Arguments

:: (a -> b -> a)

accumulating function f

-> NonEmptyVector a

initial non-empty vector (of length m)

-> Vector (Int, b)

vector of index/value pairs (of length n)

-> NonEmptyVector a 

Same as accumulate but without bounds checking.

unsafeAccumulate_ Source #

Arguments

:: (a -> b -> a)

accumulating function f

-> NonEmptyVector a

initial non-empty vector (of length m)

-> Vector Int

vector of indices of length n1

-> Vector b

vector of values (of length n2)

-> NonEmptyVector a 

Same as accumulate_ but without bounds checking.

Permutations

reverse :: NonEmptyVector a -> NonEmptyVector a Source #

O(n) Reverse a non-empty vector

>>> reverse $ unsafeFromList [1..3]
[3,2,1]

backpermute :: NonEmptyVector a -> NonEmptyVector Int -> NonEmptyVector a Source #

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

>>> backpermute (unsafeFromList [1..3]) (unsafeFromList [2,0])
[3,1]

unsafeBackpermute :: NonEmptyVector a -> NonEmptyVector Int -> NonEmptyVector a Source #

Same as backpermute but without bounds checking.

Safe destructive updates

modify :: (forall s. MVector s a -> ST s ()) -> NonEmptyVector a -> NonEmptyVector a Source #

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

Elementwise operations

Indexing

indexed :: NonEmptyVector a -> NonEmptyVector (Int, a) Source #

O(n) Pair each element in a vector with its index.

>>> indexed $ unsafeFromList ["a","b","c"]
[(0,"a"),(1,"b"),(2,"c")]

Mapping

map :: (a -> b) -> NonEmptyVector a -> NonEmptyVector b Source #

O(n) Map a function over a non-empty vector.

>>> map (+1) $ unsafeFromList [1..3]
[2,3,4]

imap :: (Int -> a -> b) -> NonEmptyVector a -> NonEmptyVector b Source #

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

>>> imap (\i a -> if i == 2 then a+1 else a+0) $ unsafeFromList [1..3]
[1,2,4]

concatMap :: (a -> NonEmptyVector b) -> NonEmptyVector a -> NonEmptyVector b Source #

Map a function over a vector and concatenate the results.

>>> concatMap (\a -> unsafeFromList [a,a]) (unsafeFromList [1,2,3])
[1,1,2,2,3,3]

Monadic mapping

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

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

>>> mapM Just (unsafeFromList [1..3])
Just [1,2,3]
>>> mapM (const Nothing) (unsafeFromList [1..3])
Nothing

imapM :: Monad m => (Int -> a -> m b) -> NonEmptyVector a -> m (NonEmptyVector b) Source #

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

>>> imapM (\i a -> if i == 1 then Just a else Just 0) (unsafeFromList [1..3])
Just [0,2,0]
>>> imapM (\_ _ -> Nothing) (unsafeFromList [1..3])
Nothing

mapM_ :: Monad m => (a -> m b) -> NonEmptyVector a -> m () Source #

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

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

imapM_ :: Monad m => (Int -> a -> m b) -> NonEmptyVector a -> m () Source #

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

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

forM :: Monad m => NonEmptyVector a -> (a -> m b) -> m (NonEmptyVector b) Source #

O(n) Apply the monadic action to all elements of the non-empty vector, yielding a non0empty vector of results.

Equivalent to flip mapM.

forM_ :: Monad m => NonEmptyVector a -> (a -> m b) -> m () Source #

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

Equivalent to flip mapM_.

Zipping

zipWith :: (a -> b -> c) -> NonEmptyVector a -> NonEmptyVector b -> NonEmptyVector c Source #

O(min(m,n)) Zip two non-empty vectors with the given function.

>>> zipWith (+) (unsafeFromList [1..3]) (unsafeFromList [1..3])
[2,4,6]

zipWith3 :: (a -> b -> c -> d) -> NonEmptyVector a -> NonEmptyVector b -> NonEmptyVector c -> NonEmptyVector d Source #

Zip three non-empty vectors with the given function.

zipWith4 :: (a -> b -> c -> d -> e) -> NonEmptyVector a -> NonEmptyVector b -> NonEmptyVector c -> NonEmptyVector d -> NonEmptyVector e Source #

Zip four non-empty vectors with the given function.

zipWith5 :: (a -> b -> c -> d -> e -> f) -> NonEmptyVector a -> NonEmptyVector b -> NonEmptyVector c -> NonEmptyVector d -> NonEmptyVector e -> NonEmptyVector f Source #

Zip five non-empty vectors with the given function.

zipWith6 :: (a -> b -> c -> d -> e -> f -> g) -> NonEmptyVector a -> NonEmptyVector b -> NonEmptyVector c -> NonEmptyVector d -> NonEmptyVector e -> NonEmptyVector f -> NonEmptyVector g Source #

Zip six non-empty vectors with the given function.

izipWith :: (Int -> a -> b -> c) -> NonEmptyVector a -> NonEmptyVector b -> NonEmptyVector c Source #

O(min(m,n)) Zip two non-empty vectors with a function that also takes the elements' indices.

izipWith3 :: (Int -> a -> b -> c -> d) -> NonEmptyVector a -> NonEmptyVector b -> NonEmptyVector c -> NonEmptyVector d Source #

Zip three non-empty vectors and their indices with the given function.

izipWith4 :: (Int -> a -> b -> c -> d -> e) -> NonEmptyVector a -> NonEmptyVector b -> NonEmptyVector c -> NonEmptyVector d -> NonEmptyVector e Source #

Zip four non-empty vectors and their indices with the given function.

izipWith5 :: (Int -> a -> b -> c -> d -> e -> f) -> NonEmptyVector a -> NonEmptyVector b -> NonEmptyVector c -> NonEmptyVector d -> NonEmptyVector e -> NonEmptyVector f Source #

Zip five non-empty vectors and their indices with the given function.

izipWith6 :: (Int -> a -> b -> c -> d -> e -> f -> g) -> NonEmptyVector a -> NonEmptyVector b -> NonEmptyVector c -> NonEmptyVector d -> NonEmptyVector e -> NonEmptyVector f -> NonEmptyVector g Source #

Zip six non-empty vectors and their indices with the given function.

zip :: NonEmptyVector a -> NonEmptyVector b -> NonEmptyVector (a, b) Source #

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

zip3 :: NonEmptyVector a -> NonEmptyVector b -> NonEmptyVector c -> NonEmptyVector (a, b, c) Source #

Zip together three non-empty vectors.

zip4 :: NonEmptyVector a -> NonEmptyVector b -> NonEmptyVector c -> NonEmptyVector d -> NonEmptyVector (a, b, c, d) Source #

Zip together four non-empty vectors.

zip5 :: NonEmptyVector a -> NonEmptyVector b -> NonEmptyVector c -> NonEmptyVector d -> NonEmptyVector e -> NonEmptyVector (a, b, c, d, e) Source #

Zip together five non-empty vectors.

zip6 :: NonEmptyVector a -> NonEmptyVector b -> NonEmptyVector c -> NonEmptyVector d -> NonEmptyVector e -> NonEmptyVector f -> NonEmptyVector (a, b, c, d, e, f) Source #

Zip together six non-empty vectors.

Monadic Zipping

zipWithM :: Monad m => (a -> b -> m c) -> NonEmptyVector a -> NonEmptyVector b -> m (NonEmptyVector c) Source #

O(min(m,n)) Zip the two non-empty vectors with the monadic action and yield a non-empty vector of results.

zipWithM_ :: Monad m => (a -> b -> m c) -> NonEmptyVector a -> NonEmptyVector b -> m () Source #

O(min(m,n)) Zip the two non-empty vectors with the monadic action and ignore the results.

izipWithM :: Monad m => (Int -> a -> b -> m c) -> NonEmptyVector a -> NonEmptyVector b -> m (NonEmptyVector c) Source #

O(min(m,n)) Zip the two non-empty vectors with a monadic action that also takes the element index and yield a vector of results.

izipWithM_ :: Monad m => (Int -> a -> b -> m c) -> NonEmptyVector a -> NonEmptyVector b -> m () Source #

O(min(m,n)) Zip the two non-empty vectors with a monadic action that also takes the element index and ignore the results.

Unzipping

unzip :: NonEmptyVector (a, b) -> (NonEmptyVector a, NonEmptyVector b) Source #

O(min(m,n)) Unzip a non-empty vector of pairs.

unzip3 :: NonEmptyVector (a, b, c) -> (NonEmptyVector a, NonEmptyVector b, NonEmptyVector c) Source #

Unzip a non-empty vector of triples.

unzip4 :: NonEmptyVector (a, b, c, d) -> (NonEmptyVector a, NonEmptyVector b, NonEmptyVector c, NonEmptyVector d) Source #

Unzip a non-empty vector of quadruples.

unzip5 :: NonEmptyVector (a, b, c, d, e) -> (NonEmptyVector a, NonEmptyVector b, NonEmptyVector c, NonEmptyVector d, NonEmptyVector e) Source #

Unzip a non-empty vector of quintuples.

unzip6 :: NonEmptyVector (a, b, c, d, e, f) -> (NonEmptyVector a, NonEmptyVector b, NonEmptyVector c, NonEmptyVector d, NonEmptyVector e, NonEmptyVector f) Source #

Unzip a non-empty vector of sextuples.

Working with predicates

Filtering

uniq :: Eq a => NonEmptyVector a -> NonEmptyVector a Source #

O(n) Drop repeated adjacent elements.

>>> uniq $ unsafeFromList [1,1,2,2,3,3,1]
[1,2,3,1]

mapMaybe :: (a -> Maybe b) -> NonEmptyVector a -> Vector 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 [1..3])
[1,3]

imapMaybe :: (Int -> a -> Maybe b) -> NonEmptyVector a -> Vector 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 [1..3])
[1]

filter :: (a -> Bool) -> NonEmptyVector a -> Vector 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 [1..3])
[1,3]
>>> filter (const False) (unsafeFromList [1..3])
[]

ifilter :: (Int -> a -> Bool) -> NonEmptyVector a -> Vector 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 [1..3])
[3]
>>> ifilter (\_ _ -> False) (unsafeFromList [1..3])
[]

filterM :: Monad m => (a -> m Bool) -> NonEmptyVector a -> m (Vector 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 [1..3])
Just [1,3]
>>> filterM (\a -> if a == 2 then Nothing else Just True) (unsafeFromList [1..3])
Nothing
>>> filterM (const $ Just False) (unsafeFromList [1..3])
Just []

ifilterM :: Monad m => (Int -> a -> m Bool) -> NonEmptyVector a -> m (Vector a) Source #

O(n) Drop elements that do not satisfy the monadic predicate that is a function of index and value.

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

TODO: this should be a more efficient function in vector.

>>> ifilterM (\i a -> if a == 2 || i == 0 then Just False else Just True) (unsafeFromList [1..3])
Just [3]
>>> ifilterM (\i a -> if a == 2 || i == 0 then Nothing else Just True) (unsafeFromList [1..3])
Nothing
>>> ifilterM (\_ _ -> Just False) (unsafeFromList [1..3])
Just []

takeWhile :: (a -> Bool) -> NonEmptyVector a -> Vector 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 [1..3])
[1,2]

dropWhile :: (a -> Bool) -> NonEmptyVector a -> Vector 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 [1..3])
[3]

Partitioning

partition :: (a -> Bool) -> NonEmptyVector a -> (Vector a, Vector a) Source #

O(n) Split the non-empty 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 [1..5])
([1,2],[3,4,5])

unstablePartition :: (a -> Bool) -> NonEmptyVector a -> (Vector a, Vector a) Source #

O(n) Split the non-empty 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.

span :: (a -> Bool) -> NonEmptyVector a -> (Vector a, Vector a) Source #

O(n) Split the non-empty 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 [1,1,2,3,1])
([1,1],[2,3,1])

break :: (a -> Bool) -> NonEmptyVector a -> (Vector a, Vector a) Source #

O(n) Split the 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 [1,1,2,3,1])
([1,1],[2,3,1])

Searching

elem :: Eq a => a -> NonEmptyVector a -> Bool Source #

O(n) Check if the non-empty vector contains an element

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

notElem :: Eq a => a -> NonEmptyVector a -> Bool Source #

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

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

find :: (a -> Bool) -> NonEmptyVector a -> Maybe a Source #

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

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

findIndex :: (a -> Bool) -> NonEmptyVector 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 [1..3]
Just 0
>>> findIndex (< 0) $ unsafeFromList [1..3]
Nothing

findIndices :: (a -> Bool) -> NonEmptyVector a -> Vector Int Source #

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

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

elemIndex :: Eq a => a -> NonEmptyVector a -> Maybe Int Source #

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

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

elemIndices :: Eq a => a -> NonEmptyVector a -> Vector 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 [1,2,3,1]
[0,3]
>>> elemIndices 0 $ unsafeFromList [1..3]
[]

Folding

foldl :: (a -> b -> a) -> a -> NonEmptyVector b -> a Source #

O(n) Left monoidal fold

foldl1 :: (a -> a -> a) -> NonEmptyVector a -> a Source #

O(n) Left semigroupal fold

foldl' :: (a -> b -> a) -> a -> NonEmptyVector b -> a Source #

O(n) Strict Left monoidal fold

foldl1' :: (a -> a -> a) -> NonEmptyVector a -> a Source #

O(n) Strict Left semigroupal fold

foldr :: (a -> b -> b) -> b -> NonEmptyVector a -> b Source #

O(n) Right monoidal fold

foldr1 :: (a -> a -> a) -> NonEmptyVector a -> a Source #

O(n) Right semigroupal fold

foldr' :: (a -> b -> b) -> b -> NonEmptyVector a -> b Source #

O(n) Strict right monoidal fold

foldr1' :: (a -> a -> a) -> NonEmptyVector a -> a Source #

O(n) Strict right semigroupal fold

ifoldl :: (a -> Int -> b -> a) -> a -> NonEmptyVector b -> a Source #

O(n) Left monoidal fold with function applied to each element and its index

ifoldl' :: (a -> Int -> b -> a) -> a -> NonEmptyVector b -> a Source #

O(n) Strict left monoidal fold with function applied to each element and its index

ifoldr :: (Int -> a -> b -> b) -> b -> NonEmptyVector a -> b Source #

O(n) Right monoidal fold with function applied to each element and its index

ifoldr' :: (Int -> a -> b -> b) -> b -> NonEmptyVector a -> b Source #

O(n) strict right monoidal fold with function applied to each element and its index

Specialized folds

all :: (a -> Bool) -> NonEmptyVector a -> Bool Source #

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

any :: (a -> Bool) -> NonEmptyVector a -> Bool Source #

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

and :: NonEmptyVector Bool -> Bool Source #

O(n) Check if all elements are True.

or :: NonEmptyVector Bool -> Bool Source #

O(n) Check if any element is True

sum :: Num a => NonEmptyVector a -> a Source #

O(n) Compute the sum of the elements

product :: Num a => NonEmptyVector a -> a Source #

O(n) Compute the produce of the elements

maximum :: Ord a => NonEmptyVector a -> a Source #

O(n) Yield the maximum element of the non-empty vector.

maximumBy :: (a -> a -> Ordering) -> NonEmptyVector a -> a Source #

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

minimum :: Ord a => NonEmptyVector a -> a Source #

O(n) Yield the minimum element of the non-empty vector.

minimumBy :: (a -> a -> Ordering) -> NonEmptyVector a -> a Source #

O(n) Yield the minimum element of the non-empty vector according to the given comparison function.

maxIndex :: Ord a => NonEmptyVector a -> Int Source #

O(n) Yield the index of the maximum element of the non-empty vector.

maxIndexBy :: (a -> a -> Ordering) -> NonEmptyVector a -> Int Source #

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

minIndex :: Ord a => NonEmptyVector a -> Int Source #

O(n) Yield the index of the minimum element of the non-empty vector.

minIndexBy :: (a -> a -> Ordering) -> NonEmptyVector a -> Int Source #

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

Monadic Folds

foldM :: Monad m => (a -> b -> m a) -> a -> NonEmptyVector b -> m a Source #

O(n) Monadic fold

foldM' :: Monad m => (a -> b -> m a) -> a -> NonEmptyVector b -> m a Source #

O(n) Strict monadic fold

fold1M :: Monad m => (a -> a -> m a) -> NonEmptyVector a -> m a Source #

O(n) Monadic semigroupal fold

fold1M' :: Monad m => (a -> a -> m a) -> NonEmptyVector a -> m a Source #

O(n) Strict monadic semigroupal fold

foldM_ :: Monad m => (a -> b -> m a) -> a -> NonEmptyVector b -> m () Source #

O(n) Monadic fold that discards the result

foldM'_ :: Monad m => (a -> b -> m a) -> a -> NonEmptyVector b -> m () Source #

O(n) Strict monadic fold that discards the result

fold1M_ :: Monad m => (a -> a -> m a) -> NonEmptyVector a -> m () Source #

O(n) Monadic semigroupal fold that discards the result

fold1M'_ :: Monad m => (a -> a -> m a) -> NonEmptyVector a -> m () Source #

O(n) Strict monadic semigroupal fold that discards the result

ifoldM :: Monad m => (a -> Int -> b -> m a) -> a -> NonEmptyVector b -> m a Source #

O(n) Monadic fold (action applied to each element and its index)

ifoldM' :: Monad m => (a -> Int -> b -> m a) -> a -> NonEmptyVector b -> m a Source #

O(n) Strict monadic fold (action applied to each element and its index)

ifoldM_ :: Monad m => (a -> Int -> b -> m a) -> a -> NonEmptyVector b -> m () Source #

O(n) Monadic fold that discards the result (action applied to each element and its index)

ifoldM'_ :: Monad m => (a -> Int -> b -> m a) -> a -> NonEmptyVector b -> m () Source #

O(n) Strict monadic fold that discards the result (action applied to each element and its index)

Monadic Sequencing

sequence :: Monad m => NonEmptyVector (m a) -> m (NonEmptyVector a) Source #

Evaluate each action and collect the results

sequence_ :: Monad m => NonEmptyVector (m a) -> m () Source #

Evaluate each action and discard the results

Prefix sums (scans)

prescanl :: (a -> b -> a) -> a -> NonEmptyVector b -> NonEmptyVector a Source #

O(n) Prescan

prescanl' :: (a -> b -> a) -> a -> NonEmptyVector b -> NonEmptyVector a Source #

O(n) Prescan with strict accumulator

postscanl :: (a -> b -> a) -> a -> NonEmptyVector b -> NonEmptyVector a Source #

O(n) Scan

postscanl' :: (a -> b -> a) -> a -> NonEmptyVector b -> NonEmptyVector a Source #

O(n) Scan with a strict accumulator

scanl :: (a -> b -> a) -> a -> NonEmptyVector b -> NonEmptyVector a Source #

O(n) Haskell-style scan

scanl' :: (a -> b -> a) -> a -> NonEmptyVector b -> NonEmptyVector a Source #

O(n) Haskell-style scan with strict accumulator

scanl1 :: (a -> a -> a) -> NonEmptyVector a -> NonEmptyVector a Source #

O(n) Semigroupal left scan

scanl1' :: (a -> a -> a) -> NonEmptyVector a -> NonEmptyVector a Source #

O(n) Strict semigroupal scan

iscanl :: (Int -> a -> b -> a) -> a -> NonEmptyVector b -> NonEmptyVector a Source #

O(n) Scan over a vector with its index

iscanl' :: (Int -> a -> b -> a) -> a -> NonEmptyVector b -> NonEmptyVector a Source #

O(n) Scan over a vector with its index with strict accumulator

prescanr :: (a -> b -> b) -> b -> NonEmptyVector a -> NonEmptyVector b Source #

O(n) Right-to-left prescan

prescanr' :: (a -> b -> b) -> b -> NonEmptyVector a -> NonEmptyVector b Source #

O(n) Right-to-left prescan with strict accumulator

postscanr :: (a -> b -> b) -> b -> NonEmptyVector a -> NonEmptyVector b Source #

O(n) Right-to-left scan

postscanr' :: (a -> b -> b) -> b -> NonEmptyVector a -> NonEmptyVector b Source #

O(n) Right-to-left scan with strict accumulator

scanr :: (a -> b -> b) -> b -> NonEmptyVector a -> NonEmptyVector b Source #

O(n) Right-to-left Haskell-style scan

scanr' :: (a -> b -> b) -> b -> NonEmptyVector a -> NonEmptyVector b Source #

O(n) Right-to-left Haskell-style scan with strict accumulator

scanr1 :: (a -> a -> a) -> NonEmptyVector a -> NonEmptyVector a Source #

O(n) Right-to-left Haskell-style semigroupal scan

scanr1' :: (a -> a -> a) -> NonEmptyVector a -> NonEmptyVector a Source #

O(n) Right-to-left Haskell-style semigroupal scan with strict accumulator

iscanr :: (Int -> a -> b -> b) -> b -> NonEmptyVector a -> NonEmptyVector b Source #

O(n) Right-to-left scan over a vector with its index

iscanr' :: (Int -> a -> b -> b) -> b -> NonEmptyVector a -> NonEmptyVector b Source #

O(n) Right-to-left scan over a vector with its index and a strict accumulator