Copyright | (c) Dong Han 2017-2018 |
---|---|
License | BSD |
Maintainer | winterland1989@gmail.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
This module provide 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
forPrim
types, it stores content in packed memory, and it's strict on its elements (following strictness consideration are mainly for liftedVector
type), many functions DO NOT NEED the result vectors's type to be same with the source one, e.g.map :: (Vec v a, Vec u b) => (a -> b) -> v a -> u b
. - There're some specialized function which only works on
Bytes
, which is enabled with rewrite rules, if you want to use specialized versions directly, import Std.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 forVector
are lazy in order to abidFunctor
law. namelyfmap id vectorConatinBottom == vectorContainBottom
, if you need strict mapping for liftedVector
, usemap'
(PrimVector
will never contain bottom thus it's not a problem). THIS MAY COME AS A SURPRISE SO MAKE SURE YOU USE THE CORRECTmap
s. - The
Foldable
instance forVector
is fine, usePrelude
functions such asnull
,length
, etc. should not incur performance overhead, though there're partial functions you should avoid, i.e. foldl1, foldr1, maximum, minimum. Usefoldl1Maybe'
,foldr1Maybe'
,maximumMaybe
,minmumMaybe
instead. - The
Traversable
instance have specialized implementations forST
andIO
, if you don't want to write thunks into result vector, usereturn $!
idiom. - When use stateful generating functions like
mapAccumL
,mapAccumR
,etc. force both the accumulator and value withacc
idiom to avoid thunks inside result vector.seq
vseq
(acc, v) The
unpack
,unpackR
andpack
,packN
,packR
,packRN
are designed to work withbuild/foldr
streaming fusion in base, thus it's OK to expect idioms likepack . 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
- class Arr (MArray v) (IArray v) a => Vec v a
- data Vector a
- data PrimVector a
- type Bytes = PrimVector Word8
- packASCII :: String -> Bytes
- empty :: Vec v a => v a
- singleton :: Vec v a => a -> v a
- copy :: Vec v a => v a -> v a
- pack :: Vec v a => [a] -> v a
- packN :: forall v a. Vec v a => Int -> [a] -> v a
- packR :: Vec v a => [a] -> v a
- packRN :: forall v a. Vec v a => Int -> [a] -> v a
- unpack :: Vec v a => v a -> [a]
- unpackR :: Vec v a => v a -> [a]
- null :: Vec v a => v a -> Bool
- length :: Vec v a => v a -> Int
- append :: Vec v a => v a -> v a -> v a
- map :: forall u v a b. (Vec u a, Vec v b) => (a -> b) -> u a -> v b
- map' :: forall u v a b. (Vec u a, Vec v b) => (a -> b) -> u a -> v b
- imap' :: forall u v a b. (Vec u a, Vec v b) => (Int -> a -> b) -> u a -> v b
- foldl' :: Vec v a => (b -> a -> b) -> b -> v a -> b
- ifoldl' :: Vec v a => (b -> Int -> a -> b) -> b -> v a -> b
- foldl1' :: forall v a. (Vec v a, HasCallStack) => (a -> a -> a) -> v a -> a
- foldl1Maybe' :: forall v a. Vec v a => (a -> a -> a) -> v a -> Maybe a
- foldr' :: Vec v a => (a -> b -> b) -> b -> v a -> b
- ifoldr' :: Vec v a => (Int -> a -> b -> b) -> b -> v a -> b
- foldr1' :: forall v a. (Vec v a, HasCallStack) => (a -> a -> a) -> v a -> a
- foldr1Maybe' :: forall v a. Vec v a => (a -> a -> a) -> v a -> Maybe a
- concat :: forall v a. Vec v a => [v a] -> v a
- concatMap :: Vec v a => (a -> v a) -> v a -> v a
- maximumMaybe :: (Vec v a, Ord a, HasCallStack) => v a -> Maybe a
- minimumMaybe :: (Vec v a, Ord a, HasCallStack) => v a -> Maybe a
- sum :: (Vec v a, Num a) => v a -> a
- count :: (Vec v a, Eq a) => a -> v a -> Int
- product :: (Vec v a, Num a) => v a -> a
- product' :: (Vec v a, Num a, Eq a) => v a -> a
- all :: Vec v a => (a -> Bool) -> v a -> Bool
- any :: Vec v a => (a -> Bool) -> v a -> Bool
- mapAccumL :: forall u v a b c. (Vec u b, Vec v c) => (a -> b -> (a, c)) -> a -> u b -> (a, v c)
- mapAccumR :: forall u v a b c. (Vec u b, Vec v c) => (a -> b -> (a, c)) -> a -> u b -> (a, v c)
- replicate :: Vec v a => Int -> a -> v a
- cycleN :: forall v a. Vec v a => Int -> v a -> v a
- unfoldr :: Vec u b => (a -> Maybe (b, a)) -> a -> u b
- unfoldrN :: forall v a b. Vec v b => Int -> (a -> Maybe (b, a)) -> a -> (v b, Maybe a)
- elem :: (Vec v a, Eq a) => a -> v a -> Bool
- notElem :: (Vec v a, Eq a) => a -> v a -> Bool
- elemIndex :: (Vec v a, Eq a) => a -> v a -> Maybe Int
- cons :: Vec v a => a -> v a -> v a
- snoc :: Vec v a => v a -> a -> v a
- uncons :: Vec v a => v a -> Maybe (a, v a)
- unsnoc :: Vec v a => v a -> Maybe (v a, a)
- headMaybe :: Vec v a => v a -> Maybe a
- tailMayEmpty :: Vec v a => v a -> v a
- lastMaybe :: Vec v a => v a -> Maybe a
- initMayEmpty :: Vec v a => v a -> v a
- inits :: Vec v a => v a -> [v a]
- tails :: Vec v a => v a -> [v a]
- take :: Vec v a => Int -> v a -> v a
- drop :: Vec v a => Int -> v a -> v a
- takeR :: Vec v a => Int -> v a -> v a
- dropR :: Vec v a => Int -> v a -> v a
- slice :: Vec v a => Int -> Int -> v a -> v a
- splitAt :: Vec v a => Int -> v a -> (v a, v a)
- takeWhile :: Vec v a => (a -> Bool) -> v a -> v a
- takeWhileR :: Vec v a => (a -> Bool) -> v a -> v a
- dropWhile :: Vec v a => (a -> Bool) -> v a -> v a
- dropWhileR :: Vec v a => (a -> Bool) -> v a -> v a
- dropAround :: Vec v a => (a -> Bool) -> v a -> v a
- break :: Vec v a => (a -> Bool) -> v a -> (v a, v a)
- span :: Vec v a => (a -> Bool) -> v a -> (v a, v a)
- breakR :: Vec v a => (a -> Bool) -> v a -> (v a, v a)
- spanR :: Vec v a => (a -> Bool) -> v a -> (v a, v a)
- breakOn :: (Vec v a, Eq a) => v a -> v a -> (v a, v a)
- group :: (Vec v a, Eq a) => v a -> [v a]
- groupBy :: Vec v a => (a -> a -> Bool) -> v a -> [v a]
- stripPrefix :: (Vec v a, Eq (v a)) => v a -> v a -> Maybe (v a)
- stripSuffix :: (Vec v a, Eq (v a)) => v a -> v a -> Maybe (v a)
- split :: (Vec v a, Eq a) => a -> v a -> [v a]
- splitWith :: Vec v a => (a -> Bool) -> v a -> [v a]
- splitOn :: (Vec v a, Eq a) => v a -> v a -> [v a]
- isPrefixOf :: (Vec v a, Eq (v a)) => v a -> v a -> Bool
- isSuffixOf :: (Vec v a, Eq (v a)) => v a -> v a -> Bool
- isInfixOf :: (Vec v a, Eq a) => v a -> v a -> Bool
- commonPrefix :: (Vec v a, Eq a) => v a -> v a -> (v a, v a, v a)
- words :: Bytes -> [Bytes]
- lines :: Bytes -> [Bytes]
- unwords :: [Bytes] -> Bytes
- unlines :: [Bytes] -> Bytes
- padLeft :: Vec v a => Int -> a -> v a -> v a
- padRight :: Vec v a => Int -> a -> v a -> v a
- reverse :: forall v a. Vec v a => v a -> v a
- intersperse :: forall v a. Vec v a => a -> v a -> v a
- intercalate :: Vec v a => v a -> [v a] -> v a
- intercalateElem :: Vec v a => a -> [v a] -> v a
- transpose :: Vec v a => [v a] -> [v a]
- zipWith' :: (Vec v a, Vec u b, Vec w c) => (a -> b -> c) -> v a -> u b -> w c
- unzipWith' :: (Vec v a, Vec u b, Vec w c) => (a -> (b, c)) -> v a -> (u b, w c)
- scanl' :: forall v u a b. (Vec v a, Vec u b) => (b -> a -> b) -> b -> v a -> u b
- scanl1' :: forall v a. Vec v a => (a -> a -> a) -> v a -> v a
- scanr' :: forall v u a b. (Vec v a, Vec u b) => (a -> b -> b) -> b -> v a -> u b
- scanr1' :: forall v a. Vec v a => (a -> a -> a) -> v a -> v a
- find :: Vec v a => (a -> Bool) -> v a -> (Int, Maybe a)
- findR :: Vec v a => (a -> Bool) -> v a -> (Int, Maybe a)
- findIndices :: Vec v a => (a -> Bool) -> v a -> [Int]
- elemIndices :: (Vec v a, Eq a) => a -> v a -> [Int]
- filter :: forall v a. Vec v a => (a -> Bool) -> v a -> v a
- partition :: forall v a. Vec v a => (a -> Bool) -> v a -> (v a, v a)
- indicesOverlapping :: (Vec v a, Eq a) => v a -> v a -> Bool -> [Int]
- indices :: (Vec v a, Eq a) => v a -> v a -> Bool -> [Int]
- mergeSort :: forall v a. (Vec v a, Ord a) => v a -> v a
- mergeSortBy :: forall v a. Vec v a => (a -> a -> Ordering) -> v a -> v a
- mergeTileSize :: Int
- insertSort :: (Vec v a, Ord a) => v a -> v a
- insertSortBy :: Vec v a => (a -> a -> Ordering) -> v a -> v a
- newtype Down a = Down a
- radixSort :: forall v a. (Vec v a, Radix a) => v a -> v a
- class Radix a where
- newtype RadixDown a = RadixDown a
- ascii :: QuasiQuoter
- vecW8 :: QuasiQuoter
- vecW16 :: QuasiQuoter
- vecW32 :: QuasiQuoter
- vecW64 :: QuasiQuoter
- vecWord :: QuasiQuoter
- vecI8 :: QuasiQuoter
- vecI16 :: QuasiQuoter
- vecI32 :: QuasiQuoter
- vecI64 :: QuasiQuoter
- vecInt :: QuasiQuoter
- data IPair a = IPair !Int a
- data VectorException
- castVector :: (Vec v a, Cast a b) => v a -> v b
The Vec typeclass
class Arr (MArray v) (IArray v) a => Vec v a Source #
Typeclass for box and unboxed vectors, which are created by slicing arrays.
Instances
Prim a => Vec PrimVector a Source # | |
Defined in Std.Data.Vector.Base toArr :: PrimVector a -> (IArray PrimVector a, Int, Int) Source # fromArr :: IArray PrimVector a -> Int -> Int -> PrimVector a Source # | |
Vec Vector a Source # | |
Boxed and unboxed vector type
Boxed vector
Instances
Functor Vector Source # | |
Foldable Vector Source # | |
Defined in Std.Data.Vector.Base fold :: Monoid m => Vector m -> 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 # elem :: Eq a => a -> Vector a -> Bool # maximum :: Ord a => Vector a -> a # minimum :: Ord a => Vector a -> a # | |
Traversable Vector Source # | |
Hashable1 Vector Source # | |
Defined in Std.Data.Vector.Base | |
Vec Vector a Source # | |
Eq a => Eq (Vector a) Source # | |
Data a => Data (Vector a) Source # | |
Defined in Std.Data.Vector.Base gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Vector a -> c (Vector a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Vector a) # toConstr :: Vector a -> Constr # dataTypeOf :: Vector a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Vector a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Vector a)) # gmapT :: (forall b. Data b => b -> b) -> Vector a -> Vector a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Vector a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Vector a -> r # gmapQ :: (forall d. Data d => d -> u) -> Vector a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Vector a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Vector a -> m (Vector a) # | |
Ord a => Ord (Vector a) Source # | |
Defined in Std.Data.Vector.Base | |
Read a => Read (Vector a) Source # | |
Show a => Show (Vector a) Source # | |
Semigroup (Vector a) Source # | |
Monoid (Vector a) Source # | |
NFData a => NFData (Vector a) Source # | |
Defined in Std.Data.Vector.Base | |
Hashable a => Hashable (Vector a) Source # | |
Defined in Std.Data.Vector.Base | |
type MArray Vector Source # | |
Defined in Std.Data.Vector.Base | |
type IArray Vector Source # | |
Defined in Std.Data.Vector.Base |
data PrimVector a Source #
Primitive vector
Instances
Word8 vector
Basic creating
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.
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
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 PrimVector
s never
store thunks.
imap' :: forall u v a b. (Vec u a, Vec v b) => (Int -> a -> b) -> u a -> v b Source #
Strict mapping with index.
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.
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
maximumMaybe :: (Vec v a, Ord a, HasCallStack) => v a -> Maybe a Source #
minimumMaybe :: (Vec v a, Ord a, HasCallStack) => v a -> Maybe a Source #
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
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.
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.
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.
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.
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.
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.
O(1) Extract a sub-range vector with give start index and length.
This function is a total function just like 'take/drop', index/length 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
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.
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.
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")
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)
The isPrefix
function returns True
if the first argument is a prefix of the second.
isSuffixOf :: (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
.
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 :: 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
unzipWith' :: (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'.
Search
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
:: (Vec v a, Eq a) | |
=> v a | vector to search for ( |
-> v a | vector to search in ( |
-> 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:
- Knuth, Donald; Morris, James H.; Pratt, Vaughan: "Fast pattern matching in strings" (1977)
- http://www-igm.univ-mlv.fr/~lecroq/string/node8.html#SECTION0080
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 = 16
.
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 #
The Down
type allows you to reverse sort order conveniently. A value of type
contains a value of type Down
aa
(represented as
).
If Down
aa
has an
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: Ord
then sortWith by
Down
x
Since: base-4.6.0.0
Down a |
Instances
Monad Down | Since: base-4.11.0.0 |
Functor Down | Since: base-4.11.0.0 |
Applicative Down | Since: base-4.11.0.0 |
Foldable Down | Since: base-4.12.0.0 |
Defined in Data.Foldable fold :: Monoid m => Down m -> 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 # elem :: Eq a => a -> Down a -> Bool # maximum :: Ord a => Down a -> a # | |
Traversable Down | Since: base-4.12.0.0 |
Eq1 Down | Since: base-4.12.0.0 |
Ord1 Down | Since: base-4.12.0.0 |
Defined in Data.Functor.Classes | |
Read1 Down | Since: base-4.12.0.0 |
Defined in Data.Functor.Classes | |
Show1 Down | Since: base-4.12.0.0 |
NFData1 Down | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Eq a => Eq (Down a) | Since: base-4.6.0.0 |
Data a => Data (Down a) | Since: base-4.12.0.0 |
Defined in Data.Data 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 :: (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 |
Ord a => Ord (Down a) | Since: base-4.6.0.0 |
Read a => Read (Down a) | Since: base-4.7.0.0 |
Show a => Show (Down a) | Since: base-4.7.0.0 |
Generic (Down a) | |
Semigroup a => Semigroup (Down a) | Since: base-4.11.0.0 |
Monoid a => Monoid (Down a) | Since: base-4.11.0.0 |
NFData a => NFData (Down a) | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
Generic1 Down | |
type Rep (Down a) | Since: base-4.12.0.0 |
Defined in GHC.Generics | |
type Rep1 Down | Since: base-4.12.0.0 |
Defined in GHC.Generics |
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)).
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.
bucketSize :: a -> Int Source #
The size of an auxiliary array, i.e. the counting bucket
The number of passes necessary to sort an array of es, it equals to the key's byte number.
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).
The radix function used in the last pass, works on the most significant bit.
Similar to Down
newtype for Ord
, this newtype can inverse the order of a Radix
instance when used in radixSort
.
Instances
Eq a => Eq (RadixDown a) Source # | |
Show a => Show (RadixDown a) Source # | |
Prim a => Prim (RadixDown a) Source # | |
Defined in Std.Data.Vector.Sort sizeOf# :: RadixDown a -> Int# # alignment# :: RadixDown a -> Int# # indexByteArray# :: ByteArray# -> Int# -> RadixDown a # readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, RadixDown a#) # writeByteArray# :: MutableByteArray# s -> Int# -> RadixDown a -> State# s -> State# s # setByteArray# :: MutableByteArray# s -> Int# -> Int# -> RadixDown a -> State# s -> State# s # indexOffAddr# :: Addr# -> Int# -> RadixDown a # readOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, RadixDown a#) # writeOffAddr# :: Addr# -> Int# -> RadixDown a -> State# s -> State# s # setOffAddr# :: Addr# -> Int# -> Int# -> RadixDown a -> State# s -> State# s # | |
Radix a => Radix (RadixDown a) Source # | |
QuasiQuoters
ascii :: QuasiQuoter Source #
vecW8 :: QuasiQuoter Source #
vecW16 :: QuasiQuoter Source #
vecW32 :: QuasiQuoter Source #
vecW64 :: QuasiQuoter Source #
vecI8 :: QuasiQuoter Source #
vecI16 :: QuasiQuoter Source #
vecI32 :: QuasiQuoter Source #
vecI64 :: QuasiQuoter Source #
vecInt :: QuasiQuoter Source #
Misc
Index pair type to help GHC unpack in some loops, useful when write fast folds.
data VectorException Source #
Instances
Show VectorException Source # | |
Defined in Std.Data.Vector.Base showsPrec :: Int -> VectorException -> ShowS # show :: VectorException -> String # showList :: [VectorException] -> ShowS # | |
Exception VectorException Source # | |
Defined in Std.Data.Vector.Base |
castVector :: (Vec v a, Cast a b) => v a -> v b Source #
Cast between vectors