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

Z.Data.Vector.Base

Description

This module provides unified vector interface. Conceptually a vector is simply a slice of an array, for example this is the definition of boxed vector:

data Vector a = Vector !(SmallArray a)   !Int    !Int
                     -- payload           offset  length

The Vec class unified different type of vectors, and this module provide operation over Vec instances, with all the internal structures. Be careful on modifying internal slices, otherwise segmentation fault await.

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.

Associated Types

type IArray v :: * -> * 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).

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

Create a vector by slicing an array(with 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 #

pattern Vec :: Vec v a => IArray v a -> Int -> Int -> v a Source #

A pattern synonyms for matching the underline array, offset and length.

This is a bidirectional pattern synonyms, but very unsafe if not use properly. Make sure your slice is within array's bounds!

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

O(1) Index array element.

Return Nothing if index is out of bounds.

Boxed and unboxed vector type

data Vector a Source #

Boxed vector

Constructors

Vector 

Fields

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 #

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 #

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

Defined in Z.Data.Text.ShowT

Methods

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

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

Defined in Z.Data.JSON.Base

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

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: Vector a -> Builder () Source #

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

Defined in Z.Data.JSON.Base

Methods

toValue :: Vector a -> Value Source #

type IArray Vector Source # 
Instance details

Defined in Z.Data.Vector.Base

data PrimVector a Source #

Primitive vector

Constructors

PrimVector 

Fields

  • !(PrimArray a)

    payload

  • !Int

    offset in elements of type a rather than in bytes

  • !Int

    length in elements of type a rather than in bytes

Instances

Instances details
FoldCase Bytes Source # 
Instance details

Defined in Z.Data.Vector.Base

Methods

foldCase :: Bytes -> Bytes #

foldCaseList :: [Bytes] -> [Bytes]

Prim a => Vec PrimVector a Source # 
Instance details

Defined in Z.Data.Vector.Base

Associated Types

type IArray PrimVector :: Type -> Type Source #

(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, ShowT a) => ShowT (PrimVector a) Source # 
Instance details

Defined in Z.Data.Text.ShowT

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

Defined in Z.Data.JSON.Base

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

Defined in Z.Data.JSON.Base

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

Defined in Z.Data.JSON.Base

type IArray PrimVector Source # 
Instance details

Defined in Z.Data.Vector.Base

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!

w2c :: Word8 -> Char Source #

Conversion between Word8 and Char. Should compile to a no-op.

c2w :: Char -> Word8 Source #

Unsafe conversion between Char and Word8. This is a no-op and silently truncates to 8 bits Chars > \255. It is provided as convenience for PrimVector construction.

Creating utilities

create Source #

Arguments

:: Vec v a 
=> Int

length in elements of type a

-> (forall s. MArr (IArray v) s a -> ST s ())

initialization function

-> v a 

Create a vector with size N.

create' Source #

Arguments

:: Vec v a 
=> Int

length in elements of type a

-> (forall s. MArr (IArray v) s a -> ST s (IPair (MArr (IArray v) s a)))

initialization function return a result size and array, the result must start from index 0

-> v a 

Create a vector with a initial size N array (which may not be the final array).

creating Source #

Arguments

:: Vec v a 
=> Int 
-> (forall s. MArr (IArray v) s a -> ST s b)

initialization function

-> (b, v a) 

Create a vector with a initial size N array, return both the vector and the monadic result during creating.

The result is not demanded strictly while the returned vector will be in normal form. It this is not desired, use return $! idiom in your initialization function.

creating' Source #

Arguments

:: Vec v a 
=> Int 
-> (forall s. MArr (IArray v) s a -> ST s (b, IPair (MArr (IArray v) s a)))

initialization function

-> (b, v a) 

Create a vector with a initial size N array (which may not be the final array), return both the vector and the monadic result during creating.

The result is not demanded strictly while the returned vector will be in normal form. It this is not desired, use return $! idiom in your initialization function.

createN Source #

Arguments

:: (Vec v a, HasCallStack) 
=> Int

length's upper bound

-> (forall s. MArr (IArray v) s a -> ST s Int)

initialization function which return the actual length

-> v a 

Create a vector up to a specific length.

If the initialization function return a length larger than initial size, an IndexOutOfVectorRange will be raised.

createN2 :: (Vec v a, Vec u b, HasCallStack) => Int -> Int -> (forall s. MArr (IArray v) s a -> MArr (IArray u) s b -> ST s (Int, Int)) -> (v a, u b) Source #

Create two vector up to a specific length.

If the initialization function return lengths larger than initial sizes, an IndexOutOfVectorRange will be raised.

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.

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.

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 #

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

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

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

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)

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.

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.

fromIPair :: IPair a -> (Int, a) Source #

toIPair :: (Int, a) -> IPair a Source #

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

C FFI