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

Z.Data.Vector.Extra

Description

Various combinators works on Vec class instances.

Synopsis

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.

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.

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.

Misc

rangeCut :: Int -> Int -> Int -> Int Source #

x' = rangeCut x min max limit x' 's range to min ~ max.

Unsafe operations

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.

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.

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

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

Throw EmptyVector if vector is empty.

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.

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

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

Make sure vector is non-empty, otherwise segmentation fault await!

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

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

Make sure vector is non-empty, otherwise segmentation fault await!

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

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

Make sure vector is non-empty, otherwise segmentation fault await!

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

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

Make sure vector is non-empty, otherwise segmentation fault await!

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

O(1) Index array element.

Make sure index is in bound, otherwise segmentation fault await!

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

O(1) Index array element.

Make sure index is in bound, otherwise segmentation fault await!

unsafeTake :: 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.

Make sure n is smaller than vector's length, otherwise segmentation fault await!

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

O(1) drop n xs returns the suffix of xs after the first n elements.

Make sure n is smaller than vector's length, otherwise segmentation fault await!