Z-Data-0.8.3.0: Array, vector and text
Copyright(c) Dong Han 2017-2018
LicenseBSD
Maintainerwinterland1989@gmail.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Z.Data.Vector

Description

This module provides fast boxed and unboxed vector with unified interface. The API is similar to bytestring and vector. If you find missing functions, please report!

Performance consideration:

  • Use PrimVector for Prim types, it stores content in packed memory, and it's strict on its elements
  • Many functions DO NOT NEED result vectors's type to be the same with source one, e.g. map :: (Vec v a, Vec u b) => (a -> b) -> v a -> u b.
  • There're some specialized functions only works on Bytes, which is enabled by rewrite rules, if you want to use specialized versions directly, import Z.Data.Vector.Base and Std.Data.Vector.Extra module. Doing so will also enable vector internals, which is useful for working on the underlying arrays.
  • The Functor instance for Vector are lazy in order to abid Functor law. namely fmap id vectorConatinBottom == vectorContainBottom, if you need strict mapping for lifted Vector, use map' (PrimVector will never contain bottom thus it's not a problem). THIS MAY COME AS A SURPRISE SO MAKE SURE YOU USE THE CORRECT map.
  • The Foldable instance for Vector is fine, you can use Prelude functions such as null, length, etc. without incurring performance overhead, though there're partial functions you should avoid, i.e. foldl1, foldr1, maximum, minimum. Use foldl1Maybe', foldr1Maybe', maximumMaybe, minmumMaybe instead.
  • The Traversable instance have specialized implementations for ST and IO, if you don't want to write thunks into result vector, use return $! idiom.
  • When use stateful generating functions like mapAccumL, mapAccumR ,etc. force both the accumulator and value with acc seq v seq (acc, v) idiom to avoid thunks inside result vector.
  • The unpack, unpackR and pack, packN, packR, packRN are designed to work with build/foldr streaming fusion in base, thus it's OK to expect idioms like

    pack . List filter f . List.map . unpack

    to work in contant space. While

    Vector.filter . Vector.map

    will create intermediate vectors on the fly, which have different time/space characteristic.

Since all functions works on more general types, inlining and specialization are the keys to achieve high performance, e.g. the performance gap between running in GHCi and compiled binary may be huge due to dictionary passing. If there're cases that GHC fail to specialized these functions, it should be regarded as a bug either in this library or GHC.

Synopsis

The Vec typeclass

class Arr (IArray v) a => Vec v a where Source #

Typeclass for box and unboxed vectors, which are created by slicing arrays.

Instead of providing a generalized vector with polymorphric array field, we use this typeclass so that instances use concrete array type can unpack their array payload.

Vector types, e.g. Vector,PrimVector... are obivious instances, with O(1) toArr and fromArr, which convert slices to (array, offset, length) tuple back and forth.

Array types can also be instances of this class, e.g. Array, PrimArray..., in this case toArr will always return offset 0 and whole array length, and fromArr is O(n) copyArr.

Minimal complete definition

toArr, fromArr

Associated Types

type IArray v :: Type -> Type Source #

Vector's immutable array type

Methods

toArr :: v a -> (IArray v a, Int, Int) Source #

Get underline array and slice range(offset and length).

Instances

Instances details
Prim a => Vec PrimArray a Source # 
Instance details

Defined in Z.Data.Vector.Base

Associated Types

type IArray PrimArray :: Type -> Type Source #

Vec SmallArray a Source # 
Instance details

Defined in Z.Data.Vector.Base

Associated Types

type IArray SmallArray :: Type -> Type Source #

Vec Array a Source # 
Instance details

Defined in Z.Data.Vector.Base

Associated Types

type IArray Array :: Type -> Type Source #

Methods

toArr :: Array a -> (IArray Array a, Int, Int) Source #

fromArr :: IArray Array a -> Int -> Int -> Array a Source #

Prim a => Vec PrimVector a Source # 
Instance details

Defined in Z.Data.Vector.Base

Associated Types

type IArray PrimVector :: Type -> Type Source #

Vec Vector a Source # 
Instance details

Defined in Z.Data.Vector.Base

Associated Types

type IArray Vector :: Type -> Type Source #

Methods

toArr :: Vector a -> (IArray Vector a, Int, Int) Source #

fromArr :: IArray Vector a -> Int -> Int -> Vector a Source #

PrimUnlifted a => Vec (UnliftedArray :: Type -> Type) a Source # 
Instance details

Defined in Z.Data.Vector.Base

Associated Types

type IArray UnliftedArray :: Type -> Type Source #

arrVec :: Vec v a => IArray v a -> v a Source #

Construct a Vec by slicing a whole array.

indexMaybe :: Vec v a => v a -> Int -> Maybe a Source #

O(1) Index vector's element.

Return Nothing if index is out of bounds.

index :: (Vec v a, HasCallStack) => v a -> Int -> a Source #

O(1) Index array element.

Throw IndexOutOfVectorRange if index outside of the vector.

indexM :: (Vec v a, Monad m, HasCallStack) => v a -> Int -> m a Source #

O(1) Index array element.

Throw IndexOutOfVectorRange if index outside of the vector.

modifyIndex :: (Vec v a, HasCallStack) => v a -> Int -> (a -> a) -> v a Source #

O(n) Modify vector's element under given index.

Throw IndexOutOfVectorRange if index outside of the vector.

modifyIndexMaybe :: (Vec v a, HasCallStack) => v a -> Int -> (a -> a) -> v a Source #

O(n) Modify vector's element under given index.

Return original vector if index outside of the vector.

insertIndex :: (Vec v a, HasCallStack) => v a -> Int -> a -> v a Source #

O(n) insert element to vector under given index.

Throw IndexOutOfVectorRange if index outside of the vector.

insertIndexMaybe :: (Vec v a, HasCallStack) => v a -> Int -> a -> v a Source #

O(n) insert element to vector under given index.

Return original vector if index outside of the vector.

deleteIndex :: (Vec v a, HasCallStack) => v a -> Int -> v a Source #

O(n) Delete vector's element under given index.

Throw IndexOutOfVectorRange if index outside of the vector.

deleteIndexMaybe :: (Vec v a, HasCallStack) => v a -> Int -> v a Source #

O(n) Delete vector's element under given index.

Return original vector if index outside of the vector.

Boxed and unboxed vector type

data Vector a Source #

Boxed vector

Instances

Instances details
Functor Vector Source # 
Instance details

Defined in Z.Data.Vector.Base

Methods

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

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

Foldable Vector Source # 
Instance details

Defined in Z.Data.Vector.Base

Methods

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

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

foldMap' :: Monoid m => (a -> m) -> Vector a -> m #

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

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

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

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

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

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

toList :: Vector a -> [a] #

null :: Vector a -> Bool #

length :: Vector a -> Int #

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

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

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

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

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

Traversable Vector Source # 
Instance details

Defined in Z.Data.Vector.Base

Methods

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

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

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

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

Hashable1 Vector Source # 
Instance details

Defined in Z.Data.Vector.Base

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Vector a -> Int #

Vec Vector a Source # 
Instance details

Defined in Z.Data.Vector.Base

Associated Types

type IArray Vector :: Type -> Type Source #

Methods

toArr :: Vector a -> (IArray Vector a, Int, Int) Source #

fromArr :: IArray Vector a -> Int -> Int -> Vector a Source #

IsList (Vector a) Source # 
Instance details

Defined in Z.Data.Vector.Base

Associated Types

type Item (Vector a) #

Methods

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

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

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

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

Defined in Z.Data.Vector.Base

Methods

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

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

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

Defined in Z.Data.Vector.Base

Methods

compare :: Vector a -> Vector a -> Ordering #

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

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

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

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

max :: Vector a -> Vector a -> Vector a #

min :: Vector a -> Vector a -> Vector a #

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

Defined in Z.Data.Vector.Base

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

Defined in Z.Data.Vector.Base

Methods

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

show :: Vector a -> String #

showList :: [Vector a] -> ShowS #

Semigroup (Vector a) Source # 
Instance details

Defined in Z.Data.Vector.Base

Methods

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

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

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

Monoid (Vector a) Source # 
Instance details

Defined in Z.Data.Vector.Base

Methods

mempty :: Vector a #

mappend :: Vector a -> Vector a -> Vector a #

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

Arbitrary a => Arbitrary (Vector a) Source # 
Instance details

Defined in Z.Data.Vector.Base

Methods

arbitrary :: Gen (Vector a) #

shrink :: Vector a -> [Vector a] #

CoArbitrary a => CoArbitrary (Vector a) Source # 
Instance details

Defined in Z.Data.Vector.Base

Methods

coarbitrary :: Vector a -> Gen b -> Gen b #

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

Defined in Z.Data.Vector.Base

Methods

rnf :: Vector a -> () #

Hashable a => Hashable (Vector a) Source # 
Instance details

Defined in Z.Data.Vector.Base

Methods

hashWithSalt :: Int -> Vector a -> Int #

hash :: Vector a -> Int #

Print a => Print (Vector a) Source # 
Instance details

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> Vector a -> Builder () Source #

JSON a => JSON (Vector a) Source # 
Instance details

Defined in Z.Data.JSON.Base

type IArray Vector Source # 
Instance details

Defined in Z.Data.Vector.Base

type Item (Vector a) Source # 
Instance details

Defined in Z.Data.Vector.Base

type Item (Vector a) = a

data PrimVector a Source #

Primitive vector

Instances

Instances details
Ord Bytes Source #

This is an INCOHERENT instance, compare binary data using SIMD.

Instance details

Defined in Z.Data.Vector.Base

Methods

compare :: Bytes -> Bytes -> Ordering #

(<) :: Bytes -> Bytes -> Bool #

(<=) :: Bytes -> Bytes -> Bool #

(>) :: Bytes -> Bytes -> Bool #

(>=) :: Bytes -> Bytes -> Bool #

max :: Bytes -> Bytes -> Bytes #

min :: Bytes -> Bytes -> Bytes #

FoldCase Bytes Source #

This instance assume ASCII encoded bytes

Instance details

Defined in Z.Data.Vector.Base

Methods

foldCase :: Bytes -> Bytes #

foldCaseList :: [Bytes] -> [Bytes]

Hashable Bytes Source #

This is an INCOHERENT instance, hash binary data using FNV-1a

Note this is different from Vector Word8 or [Word8] which use FNV-1.

Instance details

Defined in Z.Data.Vector.Base

Methods

hashWithSalt :: Int -> Bytes -> Int #

hash :: Bytes -> Int #

JSON Bytes Source #

This is an INCOHERENT instance, encode binary data with base64 encoding.

Instance details

Defined in Z.Data.JSON.Base

Prim a => Vec PrimVector a Source # 
Instance details

Defined in Z.Data.Vector.Base

Associated Types

type IArray PrimVector :: Type -> Type Source #

Prim a => IsList (PrimVector a) Source # 
Instance details

Defined in Z.Data.Vector.Base

Associated Types

type Item (PrimVector a) #

(Prim a, Eq a) => Eq (PrimVector a) Source # 
Instance details

Defined in Z.Data.Vector.Base

Methods

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

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

(Prim a, Ord a) => Ord (PrimVector a) Source # 
Instance details

Defined in Z.Data.Vector.Base

(Prim a, Read a) => Read (PrimVector a) Source # 
Instance details

Defined in Z.Data.Vector.Base

(Prim a, Show a) => Show (PrimVector a) Source # 
Instance details

Defined in Z.Data.Vector.Base

a ~ Word8 => IsString (PrimVector a) Source #

This instance use packASCII, which may silently chop bytes, use it with ASCII literals only.

Instance details

Defined in Z.Data.Vector.Base

Methods

fromString :: String -> PrimVector a #

Prim a => Semigroup (PrimVector a) Source # 
Instance details

Defined in Z.Data.Vector.Base

Prim a => Monoid (PrimVector a) Source # 
Instance details

Defined in Z.Data.Vector.Base

(Prim a, Arbitrary a) => Arbitrary (PrimVector a) Source # 
Instance details

Defined in Z.Data.Vector.Base

(Prim a, CoArbitrary a) => CoArbitrary (PrimVector a) Source # 
Instance details

Defined in Z.Data.Vector.Base

Methods

coarbitrary :: PrimVector a -> Gen b -> Gen b #

NFData (PrimVector a) Source # 
Instance details

Defined in Z.Data.Vector.Base

Methods

rnf :: PrimVector a -> () #

(Hashable a, Prim a) => Hashable (PrimVector a) Source # 
Instance details

Defined in Z.Data.Vector.Base

Methods

hashWithSalt :: Int -> PrimVector a -> Int #

hash :: PrimVector a -> Int #

(Prim a, Print a) => Print (PrimVector a) Source # 
Instance details

Defined in Z.Data.Text.Print

(Prim a, JSON a) => JSON (PrimVector a) Source # 
Instance details

Defined in Z.Data.JSON.Base

type IArray PrimVector Source # 
Instance details

Defined in Z.Data.Vector.Base

type Item (PrimVector a) Source # 
Instance details

Defined in Z.Data.Vector.Base

type Item (PrimVector a) = a

Word8 vector

type Bytes = PrimVector Word8 Source #

Bytes is just primitive word8 vectors.

packASCII :: String -> Bytes Source #

O(n), pack an ASCII String, multi-bytes char WILL BE CHOPPED!

Basic creating

empty :: Vec v a => v a Source #

O(1). The empty vector.

singleton :: Vec v a => a -> v a Source #

O(1). Single element vector.

copy :: Vec v a => v a -> v a Source #

O(n). Copy a vector from slice.

Conversion between list

pack :: Vec v a => [a] -> v a Source #

O(n) Convert a list into a vector

Alias for packN defaultInitSize.

packN :: forall v a. Vec v a => Int -> [a] -> v a Source #

O(n) Convert a list into a vector with an approximate size.

If the list's length is large than the size given, we simply double the buffer size and continue building.

This function is a good consumer in the sense of build/foldr fusion.

packN' :: forall v a. Vec v a => Int -> [a] -> v a Source #

O(n) Convert a list into a vector with given size.

If the list's length is large than the size given, we drop the rest elements.

This function is a good consumer in the sense of build/foldr fusion.

packR :: Vec v a => [a] -> v a Source #

O(n) Alias for packRN defaultInitSize.

packRN :: forall v a. Vec v a => Int -> [a] -> v a Source #

O(n) packN in reverse order.

This function is a good consumer in the sense of build/foldr fusion.

packRN' :: forall v a. Vec v a => Int -> [a] -> v a Source #

O(n) packN' in reverse order.

>>> packRN' 3 [1,2,3,4,5]
>>> [3,2,1]

This function is a good consumer in the sense of build/foldr fusion.

unpack :: Vec v a => v a -> [a] Source #

O(n) Convert vector to a list.

Unpacking is done lazily. i.e. we will retain reference to the array until all element are consumed.

This function is a good producer in the sense of build/foldr fusion.

unpackR :: Vec v a => v a -> [a] Source #

O(n) Convert vector to a list in reverse order.

This function is a good producer in the sense of build/foldr fusion.

Basic interface

null :: Vec v a => v a -> Bool Source #

O(1) Test whether a vector is empty.

length :: Vec v a => v a -> Int Source #

O(1) The length of a vector.

append :: Vec v a => v a -> v a -> v a Source #

O(m+n)

There's no need to guard empty vector because we guard them for you, so appending empty vectors are no-ops.

map :: forall u v a b. (Vec u a, Vec v b) => (a -> b) -> u a -> v b Source #

Mapping between vectors (possiblely with two different vector types).

NOTE, the result vector contain thunks in lifted Vector case, use map' if that's not desired.

For PrimVector, map and map' are same, since PrimVectors never store thunks.

map' :: forall u v a b. (Vec u a, Vec v b) => (a -> b) -> u a -> v b Source #

Mapping between vectors (possiblely with two different vector types).

This is the strict version map. Note that the Functor instance of lifted Vector is defined with map to statisfy laws, which this strict version breaks (map' id arrayContainsBottom /= arrayContainsBottom ).

imap' :: forall u v a b. (Vec u a, Vec v b) => (Int -> a -> b) -> u a -> v b Source #

Strict mapping with index.

traverseVec :: (Vec v a, Vec u b, Applicative f) => (a -> f b) -> v a -> f (u b) Source #

Traverse vector and gather result in another vector,

traverseWithIndex :: (Vec v a, Vec u b, Applicative f) => (Int -> a -> f b) -> v a -> f (u b) Source #

Traverse vector and gather result in another vector,

traverseVec_ :: (Vec v a, Applicative f) => (a -> f b) -> v a -> f () Source #

Traverse vector without gathering result.

traverseWithIndex_ :: (Vec v a, Applicative f) => (Int -> a -> f b) -> v a -> f () Source #

Traverse vector with index.

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

Strict left to right fold.

ifoldl' :: Vec v a => (b -> Int -> a -> b) -> b -> v a -> b Source #

Strict left to right fold with index.

foldl1' :: forall v a. (Vec v a, HasCallStack) => (a -> a -> a) -> v a -> a Source #

Strict left to right fold using first element as the initial value.

Throw EmptyVector if vector is empty.

foldl1Maybe' :: forall v a. Vec v a => (a -> a -> a) -> v a -> Maybe a Source #

Strict left to right fold using first element as the initial value. return Nothing when vector is empty.

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

Strict right to left fold

ifoldr' :: Vec v a => (Int -> a -> b -> b) -> b -> v a -> b Source #

Strict right to left fold with index

NOTE: the index is counting from 0, not backwards

foldr1' :: forall v a. (Vec v a, HasCallStack) => (a -> a -> a) -> v a -> a Source #

Strict right to left fold using last element as the initial value.

Throw EmptyVector if vector is empty.

foldr1Maybe' :: forall v a. Vec v a => (a -> a -> a) -> v a -> Maybe a Source #

Strict right to left fold using last element as the initial value, return Nothing when vector is empty.

Special folds

concat :: forall v a. Vec v a => [v a] -> v a Source #

O(n) Concatenate a list of vector.

Note: concat have to force the entire list to filter out empty vector and calculate the length for allocation.

concatMap :: Vec v a => (a -> v a) -> v a -> v a Source #

Map a function over a vector and concatenate the results

maximum :: (Vec v a, Ord a, HasCallStack) => v a -> a Source #

O(n) maximum returns the maximum value from a vector

It's defined with foldl1', an EmptyVector exception will be thrown in the case of an empty vector.

minimum :: (Vec v a, Ord a, HasCallStack) => v a -> a Source #

O(n) minimum returns the minimum value from a vector

An EmptyVector exception will be thrown in the case of an empty vector.

maximumMaybe :: (Vec v a, Ord a) => v a -> Maybe a Source #

O(n) maximum returns the maximum value from a vector, return Nothing in the case of an empty vector.

minimumMaybe :: (Vec v a, Ord a) => v a -> Maybe a Source #

O(n) minimum returns the minimum value from a vector, return Nothing in the case of an empty vector.

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

O(n) sum returns the sum value from a vector

count :: (Vec v a, Eq a) => a -> v a -> Int Source #

O(n) count returns count of an element from a vector

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

O(n) product returns the product value from a vector

product' :: (Vec v a, Num a, Eq a) => v a -> a Source #

O(n) product returns the product value from a vector

This function will shortcut on zero. Note this behavior change the semantics for lifted vector: product [1,0,undefined] /= product' [1,0,undefined].

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

O(n) Applied to a predicate and a vector, all determines if all elements of the vector satisfy the predicate.

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

O(n) Applied to a predicate and a vector, any determines if any elements of the vector satisfy the predicate.

Building vector

Accumulating maps

mapAccumL :: forall u v a b c. (Vec u b, Vec v c) => (a -> b -> (a, c)) -> a -> u b -> (a, v c) Source #

The mapAccumL function behaves like a combination of map and foldl; it applies a function to each element of a vector, passing an accumulating parameter from left to right, and returning a final value of this accumulator together with the new list.

Note, this function will only force the result tuple, not the elements inside, to prevent creating thunks during mapAccumL, seq your accumulator and result with the result tuple.

mapAccumR :: forall u v a b c. (Vec u b, Vec v c) => (a -> b -> (a, c)) -> a -> u b -> (a, v c) Source #

The mapAccumR function behaves like a combination of map and foldr; it applies a function to each element of a vector, passing an accumulating parameter from right to left, and returning a final value of this accumulator together with the new vector.

The same strictness property with mapAccumL applys to mapAccumR too.

Generating and unfolding vector

replicate :: Vec v a => Int -> a -> v a Source #

O(n) replicate n x is a vector of length n with x the value of every element.

Note: replicate will not force the element in boxed vector case.

cycleN :: forall v a. Vec v a => Int -> v a -> v a Source #

O(n*m) cycleN a vector n times.

unfoldr :: Vec u b => (a -> Maybe (b, a)) -> a -> u b Source #

O(n), where n is the length of the result. The unfoldr function is analogous to the List 'unfoldr'. unfoldr builds a vector from a seed value. The function takes the element and returns Nothing if it is done producing the vector or returns Just (a,b), in which case, a is the next byte in the string, and b is the seed value for further production.

Examples:

   unfoldr (\x -> if x <= 5 then Just (x, x + 1) else Nothing) 0
== pack [0, 1, 2, 3, 4, 5]

unfoldrN :: forall v a b. Vec v b => Int -> (a -> Maybe (b, a)) -> a -> (v b, Maybe a) Source #

O(n) Like unfoldr, unfoldrN builds a vector from a seed value. However, the length of the result is limited by the first argument to unfoldrN. This function is more efficient than unfoldr when the maximum length of the result is known.

The following equation relates unfoldrN and unfoldr:

fst (unfoldrN n f s) == take n (unfoldr f s)

Slice manipulation

cons :: Vec v a => a -> v a -> v a Source #

O(n) cons is analogous to (:) for lists, but of different complexity, as it requires making a copy.

snoc :: Vec v a => v a -> a -> v a Source #

O(n) Append a byte to the end of a vector

uncons :: Vec v a => v a -> Maybe (a, v a) Source #

O(1) Extract the head and tail of a vector, return Nothing if it is empty.

unsnoc :: Vec v a => v a -> Maybe (v a, a) Source #

O(1) Extract the init and last of a vector, return Nothing if vector is empty.

headMaybe :: Vec v a => v a -> Maybe a Source #

O(1) Extract the first element of a vector.

tailMayEmpty :: Vec v a => v a -> v a Source #

O(1) Extract the elements after the head of a vector.

NOTE: tailMayEmpty return empty vector in the case of an empty vector.

lastMaybe :: Vec v a => v a -> Maybe a Source #

O(1) Extract the last element of a vector.

initMayEmpty :: Vec v a => v a -> v a Source #

O(1) Extract the elements before of the last one.

NOTE: initMayEmpty return empty vector in the case of an empty vector.

head :: (Vec v a, HasCallStack) => v a -> a Source #

O(1) Extract the first element of a vector.

Throw EmptyVector if vector is empty.

tail :: (Vec v a, HasCallStack) => v a -> v a Source #

O(1) Extract the elements after the head of a vector.

Throw EmptyVector if vector is empty.

last :: (Vec v a, HasCallStack) => v a -> a Source #

O(1) Extract the last element of a vector.

Throw EmptyVector if vector is empty.

init :: (Vec v a, HasCallStack) => v a -> v a Source #

O(1) Extract the elements before of the last one.

Throw EmptyVector if vector is empty.

inits :: Vec v a => v a -> [v a] Source #

O(n) Return all initial segments of the given vector, empty first.

tails :: Vec v a => v a -> [v a] Source #

O(n) Return all final segments of the given vector, whole vector first.

take :: Vec v a => Int -> v a -> v a Source #

O(1) take n, applied to a vector xs, returns the prefix of xs of length n, or xs itself if n > length xs.

drop :: Vec v a => Int -> v a -> v a Source #

O(1) drop n xs returns the suffix of xs after the first n elements, or [] if n > length xs.

takeR :: Vec v a => Int -> v a -> v a Source #

O(1) takeR n, applied to a vector xs, returns the suffix of xs of length n, or xs itself if n > length xs.

dropR :: Vec v a => Int -> v a -> v a Source #

O(1) dropR n xs returns the prefix of xs before the last n elements, or [] if n > length xs.

slice Source #

Arguments

:: Vec v a 
=> Int

slice beginning index

-> Int

slice length

-> v a 
-> v a 

O(1) Extract a sub-range vector with give start index and length.

This function is a total function just like 'takedrop', indexlength exceeds range will be ingored, e.g.

slice 1 3 "hello"   == "ell"
slice -1 -1 "hello" == ""
slice -2 2 "hello"  == ""
slice 2 10 "hello"  == "llo"

This holds for all x y: slice x y vs == drop x . take (x+y) vs

splitAt :: Vec v a => Int -> v a -> (v a, v a) Source #

O(1) splitAt n xs is equivalent to (take n xs, drop n xs).

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

O(n) Applied to a predicate p and a vector vs, returns the longest prefix (possibly empty) of vs of elements that satisfy p.

takeWhileR :: Vec v a => (a -> Bool) -> v a -> v a Source #

O(n) Applied to a predicate p and a vector vs, returns the longest suffix (possibly empty) of vs of elements that satisfy p.

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

O(n) Applied to a predicate p and a vector vs, returns the suffix (possibly empty) remaining after takeWhile p vs.

dropWhileR :: Vec v a => (a -> Bool) -> v a -> v a Source #

O(n) Applied to a predicate p and a vector vs, returns the prefix (possibly empty) remaining before takeWhileR p vs.

dropAround :: Vec v a => (a -> Bool) -> v a -> v a Source #

O(n) dropAround f = dropWhile f . dropWhileR f

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

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

break (==x) will be rewritten using a memchr.

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

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

span (/=x) will be rewritten using a memchr.

breakR :: Vec v a => (a -> Bool) -> v a -> (v a, v a) Source #

breakR behaves like break but from the end of the vector.

breakR p == spanR (not.p)

spanR :: Vec v a => (a -> Bool) -> v a -> (v a, v a) Source #

spanR behaves like span but from the end of the vector.

breakOn :: (Vec v a, Eq a) => v a -> v a -> (v a, v a) Source #

Break a vector on a subvector, returning a pair of the part of the vector prior to the match, and the rest of the vector, e.g.

break "wor" "hello, world" = ("hello, ", "world")

group :: (Vec v a, Eq a) => v a -> [v a] Source #

groupBy :: forall v a. Vec v a => (a -> a -> Bool) -> v a -> [v a] Source #

stripPrefix Source #

Arguments

:: (Vec v a, Eq (v a)) 
=> v a

the prefix to be tested

-> v a 
-> Maybe (v a) 

O(n) The stripPrefix function takes two vectors and returns Just the remainder of the second iff the first is its prefix, and otherwise Nothing.

stripSuffix :: (Vec v a, Eq (v a)) => v a -> v a -> Maybe (v a) Source #

O(n) The stripSuffix function takes two vectors and returns Just the remainder of the second iff the first is its suffix, and otherwise Nothing.

split :: (Vec v a, Eq a) => a -> v a -> [v a] Source #

O(n) Break a vector into pieces separated by the delimiter element consuming the delimiter. I.e.

split '\n' "a\nb\nd\ne" == ["a","b","d","e"]
split 'a'  "aXaXaXa"    == ["","X","X","X",""]
split 'x'  "x"          == ["",""]

and

intercalate [c] . split c == id
split == splitWith . (==)

NOTE, this function behavior different with bytestring's. see #56.

splitWith :: Vec v a => (a -> Bool) -> v a -> [v a] Source #

O(n) Splits a vector into components delimited by separators, where the predicate returns True for a separator element. The resulting components do not contain the separators. Two adjacent separators result in an empty component in the output. eg.

splitWith (=='a') "aabbaca" == ["","","bb","c",""]
splitWith (=='a') []        == [""]

NOTE, this function behavior different with bytestring's. see #56.

splitOn :: (Vec v a, Eq a) => v a -> v a -> [v a] Source #

O(m+n) Break haystack into pieces separated by needle.

Note: An empty needle will essentially split haystack element by element.

Examples:

>>> splitOn "\r\n" "a\r\nb\r\nd\r\ne"
["a","b","d","e"]
>>> splitOn "aaa"  "aaaXaaaXaaaXaaa"
["","X","X","X",""]
>>> splitOn "x"  "x"
["",""]

and

intercalate s . splitOn s         == id
splitOn (singleton c)             == split (==c)

isPrefixOf Source #

Arguments

:: forall v a. (Vec v a, Eq (v a)) 
=> v a

the prefix to be tested

-> v a 
-> Bool 

The isPrefix function returns True if the first argument is a prefix of the second.

isSuffixOf :: forall v a. (Vec v a, Eq (v a)) => v a -> v a -> Bool Source #

O(n) The isSuffixOf function takes two vectors and returns True if the first is a suffix of the second.

isInfixOf :: (Vec v a, Eq a) => v a -> v a -> Bool Source #

Check whether one vector is a subvector of another.

needle isInfixOf haystack === null haystack || indices needle haystake /= [].

commonPrefix :: (Vec v a, Eq a) => v a -> v a -> (v a, v a, v a) Source #

O(n) Find the longest non-empty common prefix of two strings and return it, along with the suffixes of each string at which they no longer match. e.g.

>>> commonPrefix "foobar" "fooquux"
("foo","bar","quux")
>>> commonPrefix "veeble" "fetzer"
("","veeble","fetzer")

words :: Bytes -> [Bytes] Source #

O(n) Breaks a Bytes up into a list of words, delimited by ascii space.

lines :: Bytes -> [Bytes] Source #

O(n) Breaks a Bytes up into a list of lines, delimited by ascii n, The resulting strings do not contain newlines.

Note that it does not regard CR ('\r') as a newline character.

unwords :: [Bytes] -> Bytes Source #

O(n) Joins words with ascii space.

unlines :: [Bytes] -> Bytes Source #

O(n) Joins lines with ascii n.

NOTE: This functions is different from unlines, it DOES NOT add a trailing n.

padLeft :: Vec v a => Int -> a -> v a -> v a Source #

Add padding to the left so that the whole vector's length is at least n.

padRight :: Vec v a => Int -> a -> v a -> v a Source #

Add padding to the right so that the whole vector's length is at least n.

Transform

reverse :: forall v a. Vec v a => v a -> v a Source #

O(n) reverse vs efficiently returns the elements of xs in reverse order.

intersperse :: forall v a. Vec v a => a -> v a -> v a Source #

O(n) The intersperse function takes an element and a vector and `intersperses' that element between the elements of the vector. It is analogous to the intersperse function on Lists.

intercalate :: Vec v a => v a -> [v a] -> v a Source #

O(n) The intercalate function takes a vector and a list of vectors and concatenates the list after interspersing the first argument between each element of the list.

Note: intercalate will force the entire vector list.

intercalateElem :: forall v a. Vec v a => a -> [v a] -> v a Source #

O(n) An efficient way to join vector with an element.

transpose :: Vec v a => [v a] -> [v a] Source #

The transpose function transposes the rows and columns of its vector argument.

Zipping

zipWith' :: forall v a u b w c. (Vec v a, Vec u b, Vec w c) => (a -> b -> c) -> v a -> u b -> w c Source #

zipWith' zip two vector with a zipping function.

For example, zipWith (+) is applied to two vector to produce a vector of corresponding sums, the result will be evaluated strictly.

unzipWith' :: forall v a u b w c. (Vec v a, Vec u b, Vec w c) => (a -> (b, c)) -> v a -> (u b, w c) Source #

unzipWith' disassemble a vector with a disassembling function,

The results inside tuple will be evaluated strictly.

Scans

scanl' :: forall v u a b. (Vec v a, Vec u b) => (b -> a -> b) -> b -> v a -> u b Source #

scanl' is similar to foldl, but returns a list of successive reduced values from the left.

scanl' f z [x1, x2, ...] == [z, z `f` x1, (z `f` x1) `f` x2, ...]

Note that

lastM (scanl' f z xs) == Just (foldl f z xs).

scanl1' :: forall v a. Vec v a => (a -> a -> a) -> v a -> v a Source #

'scanl1'' is a variant of scanl that has no starting value argument.

scanl1' f [x1, x2, ...] == [x1, x1 `f` x2, ...]
scanl1' f [] == []

scanr' :: forall v u a b. (Vec v a, Vec u b) => (a -> b -> b) -> b -> v a -> u b Source #

scanr' is the right-to-left dual of scanl'.

scanr1' :: forall v a. Vec v a => (a -> a -> a) -> v a -> v a Source #

scanr1' is a variant of scanr that has no starting value argument.

Search

searching by equality

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

O(n) elem test if given element is in given vector.

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

O(n) 'not . elem'

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

O(n) The elemIndex function returns the index of the first element in the given vector which is equal to the query element, or Nothing if there is no such element.

element-wise search

find :: Vec v a => (a -> Bool) -> v a -> (Int, Maybe a) Source #

O(n) find the first index and element matching the predicate in a vector from left to right, if there isn't one, return (length of the vector, Nothing).

findR :: Vec v a => (a -> Bool) -> v a -> (Int, Maybe a) Source #

O(n) Find the first index and element matching the predicate in a vector from right to left, if there isn't one, return '(-1, Nothing)'.

findIndices :: Vec v a => (a -> Bool) -> v a -> [Int] Source #

The findIndex function takes a predicate and a vector and returns the index of the first element in the vector satisfying the predicate.

elemIndices :: (Vec v a, Eq a) => a -> v a -> [Int] Source #

O(n) The elemIndices function extends elemIndex, by returning the indices of all elements equal to the query element, in ascending order.

filter :: forall v a. Vec v a => (a -> Bool) -> v a -> v a Source #

O(n) filter, applied to a predicate and a vector, returns a vector containing those elements that satisfy the predicate.

partition :: forall v a. Vec v a => (a -> Bool) -> v a -> (v a, v a) Source #

O(n) The partition function takes a predicate, a vector, returns a pair of vector with elements which do and do not satisfy the predicate, respectively; i.e.,

partition p vs == (filter p vs, filter (not . p) vs)

sub-vector search

indicesOverlapping Source #

Arguments

:: (Vec v a, Eq a) 
=> v a

vector to search for (needle)

-> v a

vector to search in (haystack)

-> Bool

report partial match at the end of haystack

-> [Int] 

O(n+m) Find the offsets of all indices (possibly overlapping) of needle within haystack using KMP algorithm.

The KMP algorithm need pre-calculate a shift table in O(m) time and space, the worst case time complexity is O(n+m). Partial apply this function to reuse pre-calculated table between same needles.

Chunked input are support via partial match argument, if set we will return an extra negative index in case of partial match at the end of input chunk, e.g.

indicesOverlapping [ascii|ada|]  [ascii|adadad|] True == [0,2,-2]

Where -2 is the length of the partial match part ad 's negation.

If an empty pattern is supplied, we will return every possible index of haystack, e.g.

indicesOverlapping "" "abc" = [0,1,2]

References:

indices :: (Vec v a, Eq a) => v a -> v a -> Bool -> [Int] Source #

O(n+m) Find the offsets of all non-overlapping indices of needle within haystack using KMP algorithm.

If an empty pattern is supplied, we will return every possible index of haystack, e.g.

indicesOverlapping "" "abc" = [0,1,2]

Sort

comparison search

mergeSort :: forall v a. (Vec v a, Ord a) => v a -> v a Source #

O(n*log(n)) Sort vector based on element's Ord instance with classic mergesort algorithm.

This is a stable sort, During sorting two O(n) worker arrays are needed, one of them will be freezed into the result vector. The merge sort only begin at tile size larger than mergeTileSize, each tile will be sorted with insertSort, then iteratively merged into larger array, until all elements are sorted.

mergeSortBy :: forall v a. Vec v a => (a -> a -> Ordering) -> v a -> v a Source #

mergeTileSize :: Int Source #

The mergesort tile size, mergeTileSize = 8.

insertSort :: (Vec v a, Ord a) => v a -> v a Source #

O(n^2) Sort vector based on element's Ord instance with simple insertion-sort algorithm.

This is a stable sort. O(n) extra space are needed, which will be freezed into result vector.

insertSortBy :: Vec v a => (a -> a -> Ordering) -> v a -> v a Source #

newtype Down a #

The Down type allows you to reverse sort order conveniently. A value of type Down a contains a value of type a (represented as Down a). If a has an Ord instance associated with it then comparing two values thus wrapped will give you the opposite of their normal sort order. This is particularly useful when sorting in generalised list comprehensions, as in: then sortWith by Down x

Since: base-4.6.0.0

Constructors

Down 

Fields

Instances

Instances details
Monad Down

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Methods

(>>=) :: Down a -> (a -> Down b) -> Down b #

(>>) :: Down a -> Down b -> Down b #

return :: a -> Down a #

Functor Down

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Methods

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

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

Applicative Down

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Methods

pure :: a -> Down a #

(<*>) :: Down (a -> b) -> Down a -> Down b #

liftA2 :: (a -> b -> c) -> Down a -> Down b -> Down c #

(*>) :: Down a -> Down b -> Down b #

(<*) :: Down a -> Down b -> Down a #

Foldable Down

Since: base-4.12.0.0

Instance details

Defined in Data.Foldable

Methods

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

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

foldMap' :: Monoid m => (a -> m) -> Down a -> m #

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

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

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

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

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

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

toList :: Down a -> [a] #

null :: Down a -> Bool #

length :: Down a -> Int #

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

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

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

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

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

Traversable Down

Since: base-4.12.0.0

Instance details

Defined in Data.Traversable

Methods

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

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

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

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

Eq1 Down

Since: base-4.12.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Ord1 Down

Since: base-4.12.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Read1 Down

Since: base-4.12.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Down a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Down a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Down a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Down a] #

Show1 Down

Since: base-4.12.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

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

NFData1 Down

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> Down a -> () #

Bounded a => Bounded (Down a)

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

Methods

minBound :: Down a #

maxBound :: Down a #

Enum a => Enum (Down a)

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

Methods

succ :: Down a -> Down a #

pred :: Down a -> Down a #

toEnum :: Int -> Down a #

fromEnum :: Down a -> Int #

enumFrom :: Down a -> [Down a] #

enumFromThen :: Down a -> Down a -> [Down a] #

enumFromTo :: Down a -> Down a -> [Down a] #

enumFromThenTo :: Down a -> Down a -> Down a -> [Down a] #

Eq a => Eq (Down a)

Since: base-4.6.0.0

Instance details

Defined in Data.Ord

Methods

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

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

Floating a => Floating (Down a)

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

Methods

pi :: Down a #

exp :: Down a -> Down a #

log :: Down a -> Down a #

sqrt :: Down a -> Down a #

(**) :: Down a -> Down a -> Down a #

logBase :: Down a -> Down a -> Down a #

sin :: Down a -> Down a #

cos :: Down a -> Down a #

tan :: Down a -> Down a #

asin :: Down a -> Down a #

acos :: Down a -> Down a #

atan :: Down a -> Down a #

sinh :: Down a -> Down a #

cosh :: Down a -> Down a #

tanh :: Down a -> Down a #

asinh :: Down a -> Down a #

acosh :: Down a -> Down a #

atanh :: Down a -> Down a #

log1p :: Down a -> Down a #

expm1 :: Down a -> Down a #

log1pexp :: Down a -> Down a #

log1mexp :: Down a -> Down a #

Fractional a => Fractional (Down a)

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

Methods

(/) :: Down a -> Down a -> Down a #

recip :: Down a -> Down a #

fromRational :: Rational -> Down a #

Integral a => Integral (Down a)

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

Methods

quot :: Down a -> Down a -> Down a #

rem :: Down a -> Down a -> Down a #

div :: Down a -> Down a -> Down a #

mod :: Down a -> Down a -> Down a #

quotRem :: Down a -> Down a -> (Down a, Down a) #

divMod :: Down a -> Down a -> (Down a, Down a) #

toInteger :: Down a -> Integer #

Data a => Data (Down a)

Since: base-4.12.0.0

Instance details

Defined in Data.Data

Methods

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

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

toConstr :: Down a -> Constr #

dataTypeOf :: Down a -> DataType #

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

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

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

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

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

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

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

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

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

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

Num a => Num (Down a)

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Methods

(+) :: Down a -> Down a -> Down a #

(-) :: Down a -> Down a -> Down a #

(*) :: Down a -> Down a -> Down a #

negate :: Down a -> Down a #

abs :: Down a -> Down a #

signum :: Down a -> Down a #

fromInteger :: Integer -> Down a #

Ord a => Ord (Down a)

Since: base-4.6.0.0

Instance details

Defined in Data.Ord

Methods

compare :: Down a -> Down a -> Ordering #

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

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

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

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

max :: Down a -> Down a -> Down a #

min :: Down a -> Down a -> Down a #

Read a => Read (Down a)

This instance would be equivalent to the derived instances of the Down newtype if the getDown field were removed

Since: base-4.7.0.0

Instance details

Defined in Data.Ord

Real a => Real (Down a)

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

Methods

toRational :: Down a -> Rational #

RealFloat a => RealFloat (Down a)

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

RealFrac a => RealFrac (Down a)

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

Methods

properFraction :: Integral b => Down a -> (b, Down a) #

truncate :: Integral b => Down a -> b #

round :: Integral b => Down a -> b #

ceiling :: Integral b => Down a -> b #

floor :: Integral b => Down a -> b #

Show a => Show (Down a)

This instance would be equivalent to the derived instances of the Down newtype if the getDown field were removed

Since: base-4.7.0.0

Instance details

Defined in Data.Ord

Methods

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

show :: Down a -> String #

showList :: [Down a] -> ShowS #

Ix a => Ix (Down a)

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

Methods

range :: (Down a, Down a) -> [Down a] #

index :: (Down a, Down a) -> Down a -> Int #

unsafeIndex :: (Down a, Down a) -> Down a -> Int #

inRange :: (Down a, Down a) -> Down a -> Bool #

rangeSize :: (Down a, Down a) -> Int #

unsafeRangeSize :: (Down a, Down a) -> Int #

Generic (Down a)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Semigroup a => Semigroup (Down a)

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Methods

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

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

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

Monoid a => Monoid (Down a)

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Methods

mempty :: Down a #

mappend :: Down a -> Down a -> Down a #

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

Storable a => Storable (Down a)

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

Methods

sizeOf :: Down a -> Int #

alignment :: Down a -> Int #

peekElemOff :: Ptr (Down a) -> Int -> IO (Down a) #

pokeElemOff :: Ptr (Down a) -> Int -> Down a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Down a) #

pokeByteOff :: Ptr b -> Int -> Down a -> IO () #

peek :: Ptr (Down a) -> IO (Down a) #

poke :: Ptr (Down a) -> Down a -> IO () #

Bits a => Bits (Down a)

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

Methods

(.&.) :: Down a -> Down a -> Down a #

(.|.) :: Down a -> Down a -> Down a #

xor :: Down a -> Down a -> Down a #

complement :: Down a -> Down a #

shift :: Down a -> Int -> Down a #

rotate :: Down a -> Int -> Down a #

zeroBits :: Down a #

bit :: Int -> Down a #

setBit :: Down a -> Int -> Down a #

clearBit :: Down a -> Int -> Down a #

complementBit :: Down a -> Int -> Down a #

testBit :: Down a -> Int -> Bool #

bitSizeMaybe :: Down a -> Maybe Int #

bitSize :: Down a -> Int #

isSigned :: Down a -> Bool #

shiftL :: Down a -> Int -> Down a #

unsafeShiftL :: Down a -> Int -> Down a #

shiftR :: Down a -> Int -> Down a #

unsafeShiftR :: Down a -> Int -> Down a #

rotateL :: Down a -> Int -> Down a #

rotateR :: Down a -> Int -> Down a #

popCount :: Down a -> Int #

FiniteBits a => FiniteBits (Down a)

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

NFData a => NFData (Down a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Down a -> () #

Prim a => Prim (Down a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Generic1 Down

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Down :: k -> Type #

Methods

from1 :: forall (a :: k). Down a -> Rep1 Down a #

to1 :: forall (a :: k). Rep1 Down a -> Down a #

type Rep (Down a) 
Instance details

Defined in GHC.Generics

type Rep (Down a) = D1 ('MetaData "Down" "Data.Ord" "base" 'True) (C1 ('MetaCons "Down" 'PrefixI 'True) (S1 ('MetaSel ('Just "getDown") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))
type Rep1 Down 
Instance details

Defined in GHC.Generics

type Rep1 Down = D1 ('MetaData "Down" "Data.Ord" "base" 'True) (C1 ('MetaCons "Down" 'PrefixI 'True) (S1 ('MetaSel ('Just "getDown") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))

radix search

radixSort :: forall v a. (Vec v a, Radix a) => v a -> v a Source #

O(n) Sort vector based on element's Radix instance with radix-sort, (Least significant digit radix sorts variation).

This is a stable sort, one or two extra O(n) worker array are need depend on how many passes shall be performed, and a bucketSize counting bucket are also needed. This sort algorithms performed extremly well on small byte size types such as Int8 or Word8, while on larger type, constant passes may render this algorithm not suitable for small vectors (turning point around 2^(2*passes)).

class Radix a where Source #

Types contain radixs, which can be inspected with radix during different passes.

The default instances share a same bucketSize 256, which seems to be a good default.

Methods

bucketSize :: a -> Int Source #

The size of an auxiliary array, i.e. the counting bucket

passes :: a -> Int Source #

The number of passes necessary to sort an array of es, it equals to the key's byte number.

radixLSB :: a -> Int Source #

The radix function used in the first pass, works on the least significant bit.

radix :: Int -> a -> Int Source #

The radix function parameterized by the current pass (0 < pass < passes e-1).

radixMSB :: a -> Int Source #

The radix function used in the last pass, works on the most significant bit.

Instances

Instances details
Radix Int Source # 
Instance details

Defined in Z.Data.Vector.Sort

Radix Int8 Source # 
Instance details

Defined in Z.Data.Vector.Sort

Radix Int16 Source # 
Instance details

Defined in Z.Data.Vector.Sort

Radix Int32 Source # 
Instance details

Defined in Z.Data.Vector.Sort

Radix Int64 Source # 
Instance details

Defined in Z.Data.Vector.Sort

Radix Word Source # 
Instance details

Defined in Z.Data.Vector.Sort

Radix Word8 Source # 
Instance details

Defined in Z.Data.Vector.Sort

Radix Word16 Source # 
Instance details

Defined in Z.Data.Vector.Sort

Radix Word32 Source # 
Instance details

Defined in Z.Data.Vector.Sort

Radix Word64 Source # 
Instance details

Defined in Z.Data.Vector.Sort

Radix a => Radix (RadixDown a) Source # 
Instance details

Defined in Z.Data.Vector.Sort

newtype RadixDown a Source #

Similar to Down newtype for Ord, this newtype can inverse the order of a Radix instance when used in radixSort.

Constructors

RadixDown a 

Instances

Instances details
Eq a => Eq (RadixDown a) Source # 
Instance details

Defined in Z.Data.Vector.Sort

Methods

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

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

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

Defined in Z.Data.Vector.Sort

Prim a => Prim (RadixDown a) Source # 
Instance details

Defined in Z.Data.Vector.Sort

Unaligned a => Unaligned (RadixDown a) Source # 
Instance details

Defined in Z.Data.Vector.Sort

Radix a => Radix (RadixDown a) Source # 
Instance details

Defined in Z.Data.Vector.Sort

QuasiQuoters

Misc

data IPair a Source #

Pair type to help GHC unpack in some loops, useful when write fast folds.

Constructors

IPair 

Fields

Instances

Instances details
Functor IPair Source # 
Instance details

Defined in Z.Data.Vector.Base

Methods

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

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

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

Defined in Z.Data.Vector.Base

Methods

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

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

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

Defined in Z.Data.Vector.Base

Methods

compare :: IPair a -> IPair a -> Ordering #

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

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

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

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

max :: IPair a -> IPair a -> IPair a #

min :: IPair a -> IPair a -> IPair a #

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

Defined in Z.Data.Vector.Base

Methods

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

show :: IPair a -> String #

showList :: [IPair a] -> ShowS #

Arbitrary v => Arbitrary (IPair v) Source # 
Instance details

Defined in Z.Data.Vector.Base

Methods

arbitrary :: Gen (IPair v) #

shrink :: IPair v -> [IPair v] #

CoArbitrary v => CoArbitrary (IPair v) Source # 
Instance details

Defined in Z.Data.Vector.Base

Methods

coarbitrary :: IPair v -> Gen b -> Gen b #

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

Defined in Z.Data.Vector.Base

Methods

rnf :: IPair a -> () #

mapIPair' :: (a -> b) -> IPair a -> IPair b Source #

Unlike Functor instance, this mapping evaluate value inside IPair strictly.

defaultInitSize :: Int Source #

defaultInitSize = 30, used as initialize size when packing list of unknown size.

chunkOverhead :: Int Source #

The memory management overhead. Currently this is tuned for GHC only.

defaultChunkSize :: Int Source #

The chunk size used for I/O. Currently set to 16k - chunkOverhead

smallChunkSize :: Int Source #

The recommended chunk size. Currently set to 4k - chunkOverhead.

castVector :: (Vec v a, Cast a b) => v a -> v b Source #

Cast between vectors