Safe Haskell | None |
---|
A time and space-efficient implementation of vectors using
packed arrays, suitable for high performance use, both in terms
of large data quantities, or high speed requirements. Vectors
are encoded as strict arrays, held in a ForeignPtr
,
and can be passed between C and Haskell with little effort.
This module is intended to be imported qualified
, to avoid name
clashes with Prelude functions. eg.
import qualified Data.StorableVector as V
Original GHC implementation by Bryan O'Sullivan. Rewritten to use UArray by Simon Marlow. Rewritten to support slices and use ForeignPtr by David Roundy. Polished and extended by Don Stewart. Generalized to any Storable value by Spencer Janssen. Chunky lazy stream, also with chunk pattern control, mutable access in ST monad, Builder monoid by Henning Thieleman.
- data Vector a
- empty :: Storable a => Vector a
- singleton :: Storable a => a -> Vector a
- pack :: Storable a => [a] -> Vector a
- unpack :: Storable a => Vector a -> [a]
- packN :: Storable a => Int -> [a] -> (Vector a, [a])
- packWith :: Storable b => (a -> b) -> [a] -> Vector b
- unpackWith :: Storable a => (a -> b) -> Vector a -> [b]
- cons :: Storable a => a -> Vector a -> Vector a
- snoc :: Storable a => Vector a -> a -> Vector a
- append :: Storable a => Vector a -> Vector a -> Vector a
- head :: Storable a => Vector a -> a
- last :: Storable a => Vector a -> a
- tail :: Storable a => Vector a -> Vector a
- init :: Vector a -> Vector a
- null :: Vector a -> Bool
- length :: Vector a -> Int
- viewL :: Storable a => Vector a -> Maybe (a, Vector a)
- viewR :: Storable a => Vector a -> Maybe (Vector a, a)
- switchL :: Storable a => b -> (a -> Vector a -> b) -> Vector a -> b
- switchR :: Storable a => b -> (Vector a -> a -> b) -> Vector a -> b
- map :: (Storable a, Storable b) => (a -> b) -> Vector a -> Vector b
- reverse :: Storable a => Vector a -> Vector a
- intersperse :: Storable a => a -> Vector a -> Vector a
- transpose :: Storable a => [Vector a] -> [Vector a]
- foldl :: Storable a => (b -> a -> b) -> b -> Vector a -> b
- foldl' :: Storable a => (b -> a -> b) -> b -> Vector a -> b
- foldl1 :: Storable a => (a -> a -> a) -> Vector a -> a
- foldl1' :: Storable a => (a -> a -> a) -> Vector a -> a
- foldr :: Storable a => (a -> b -> b) -> b -> Vector a -> b
- foldr1 :: Storable a => (a -> a -> a) -> Vector a -> a
- concat :: Storable a => [Vector a] -> Vector a
- concatMap :: (Storable a, Storable b) => (a -> Vector b) -> Vector a -> Vector b
- monoidConcatMap :: (Storable a, Monoid m) => (a -> m) -> Vector a -> m
- any :: Storable a => (a -> Bool) -> Vector a -> Bool
- all :: Storable a => (a -> Bool) -> Vector a -> Bool
- maximum :: (Storable a, Ord a) => Vector a -> a
- minimum :: (Storable a, Ord a) => Vector a -> a
- scanl :: (Storable a, Storable b) => (a -> b -> a) -> a -> Vector b -> Vector a
- scanl1 :: Storable a => (a -> a -> a) -> Vector a -> Vector a
- scanr :: (Storable a, Storable b) => (a -> b -> b) -> b -> Vector a -> Vector b
- scanr1 :: Storable a => (a -> a -> a) -> Vector a -> Vector a
- mapAccumL :: (Storable a, Storable b) => (acc -> a -> (acc, b)) -> acc -> Vector a -> (acc, Vector b)
- mapAccumR :: (Storable a, Storable b) => (acc -> a -> (acc, b)) -> acc -> Vector a -> (acc, Vector b)
- mapIndexed :: (Storable a, Storable b) => (Int -> a -> b) -> Vector a -> Vector b
- replicate :: Storable a => Int -> a -> Vector a
- iterateN :: Storable a => Int -> (a -> a) -> a -> Vector a
- unfoldr :: Storable b => (a -> Maybe (b, a)) -> a -> Vector b
- unfoldrN :: Storable b => Int -> (a -> Maybe (b, a)) -> a -> (Vector b, Maybe a)
- unfoldrResultN :: Storable b => Int -> (a -> c) -> (a -> Either c (b, a)) -> a -> (Vector b, c)
- sample :: Storable a => Int -> (Int -> a) -> Vector a
- take :: Storable a => Int -> Vector a -> Vector a
- drop :: Storable a => Int -> Vector a -> Vector a
- splitAt :: Storable a => Int -> Vector a -> (Vector a, Vector a)
- takeWhile :: Storable a => (a -> Bool) -> Vector a -> Vector a
- dropWhile :: Storable a => (a -> Bool) -> Vector a -> Vector a
- span :: Storable a => (a -> Bool) -> Vector a -> (Vector a, Vector a)
- spanEnd :: Storable a => (a -> Bool) -> Vector a -> (Vector a, Vector a)
- break :: Storable a => (a -> Bool) -> Vector a -> (Vector a, Vector a)
- breakEnd :: Storable a => (a -> Bool) -> Vector a -> (Vector a, Vector a)
- group :: (Storable a, Eq a) => Vector a -> [Vector a]
- groupBy :: Storable a => (a -> a -> Bool) -> Vector a -> [Vector a]
- inits :: Storable a => Vector a -> [Vector a]
- tails :: Storable a => Vector a -> [Vector a]
- split :: (Storable a, Eq a) => a -> Vector a -> [Vector a]
- splitWith :: Storable a => (a -> Bool) -> Vector a -> [Vector a]
- tokens :: Storable a => (a -> Bool) -> Vector a -> [Vector a]
- join :: Storable a => Vector a -> [Vector a] -> Vector a
- isPrefixOf :: (Storable a, Eq a) => Vector a -> Vector a -> Bool
- isSuffixOf :: (Storable a, Eq a) => Vector a -> Vector a -> Bool
- elem :: (Storable a, Eq a) => a -> Vector a -> Bool
- notElem :: (Storable a, Eq a) => a -> Vector a -> Bool
- find :: Storable a => (a -> Bool) -> Vector a -> Maybe a
- filter :: Storable a => (a -> Bool) -> Vector a -> Vector a
- index :: Storable a => Vector a -> Int -> a
- elemIndex :: (Storable a, Eq a) => a -> Vector a -> Maybe Int
- elemIndices :: (Storable a, Eq a) => a -> Vector a -> [Int]
- elemIndexEnd :: (Storable a, Eq a) => a -> Vector a -> Maybe Int
- findIndex :: Storable a => (a -> Bool) -> Vector a -> Maybe Int
- findIndices :: Storable a => (a -> Bool) -> Vector a -> [Int]
- count :: (Storable a, Eq a) => a -> Vector a -> Int
- findIndexOrEnd :: Storable a => (a -> Bool) -> Vector a -> Int
- zip :: (Storable a, Storable b) => Vector a -> Vector b -> [(a, b)]
- zipWith :: (Storable a, Storable b, Storable c) => (a -> b -> c) -> Vector a -> Vector b -> Vector c
- zipWith3 :: (Storable a, Storable b, Storable c, Storable d) => (a -> b -> c -> d) -> Vector a -> Vector b -> Vector c -> Vector d
- zipWith4 :: (Storable a, Storable b, Storable c, Storable d, Storable e) => (a -> b -> c -> d -> e) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e
- unzip :: (Storable a, Storable b) => [(a, b)] -> (Vector a, Vector b)
- copy :: Storable a => Vector a -> Vector a
- sieve :: Storable a => Int -> Vector a -> Vector a
- deinterleave :: Storable a => Int -> Vector a -> [Vector a]
- interleave :: Storable a => [Vector a] -> Vector a
- hGet :: Storable a => Handle -> Int -> IO (Vector a)
- hPut :: Storable a => Handle -> Vector a -> IO ()
- readFile :: Storable a => FilePath -> IO (Vector a)
- writeFile :: Storable a => FilePath -> Vector a -> IO ()
- appendFile :: Storable a => FilePath -> Vector a -> IO ()
The Vector
type
A space-efficient representation of a vector, supporting many efficient operations.
Instances of Eq, Ord, Read, Show, Data, Typeable
Introducing and eliminating Vector
s
packN :: Storable a => Int -> [a] -> (Vector a, [a])Source
O(n) Convert first n
elements of a '[a]' into a 'Vector a'.
packWith :: Storable b => (a -> b) -> [a] -> Vector bSource
O(n) Convert a list into a Vector
using a conversion function
unpackWith :: Storable a => (a -> b) -> Vector a -> [b]Source
O(n) Convert a Vector
into a list using a conversion function
Basic interface
cons :: Storable a => a -> Vector a -> Vector aSource
O(n) cons
is analogous to (:) for lists, but of different
complexity, as it requires a memcpy.
Transforming Vector
s
reverse :: Storable a => Vector a -> Vector aSource
O(n) reverse
xs
efficiently returns the elements of xs
in reverse order.
intersperse :: Storable a => a -> Vector a -> Vector aSource
O(n) The intersperse
function takes a element and a
Vector
and `intersperses' that element between the elements of
the Vector
. It is analogous to the intersperse function on
Lists.
Reducing Vector
s (folds)
foldl' :: Storable a => (b -> a -> b) -> b -> Vector a -> bSource
'foldl\'' is like foldl
, but strict in the accumulator.
foldr :: Storable a => (a -> b -> b) -> b -> Vector a -> bSource
foldr
, applied to a binary operator, a starting value
(typically the right-identity of the operator), and a Vector
,
reduces the Vector
using the binary operator, from right to left.
However, it is not the same as foldl
applied to the reversed vector.
Actually foldr
starts processing with the first element,
and thus can be used for efficiently building a singly linked list
by foldr (:) [] vec
.
Unfortunately foldr
is quite slow for low-level loops,
since GHC (up to 6.12.1) cannot detect the loop.
Special folds
concatMap :: (Storable a, Storable b) => (a -> Vector b) -> Vector a -> Vector bSource
Map a function over a Vector
and concatenate the results
monoidConcatMap :: (Storable a, Monoid m) => (a -> m) -> Vector a -> mSource
This is like mconcat . map f
,
but in many cases the result of f
will not be storable.
Building Vector
s
Scans
scanr :: (Storable a, Storable b) => (a -> b -> b) -> b -> Vector a -> Vector bSource
scanr is the right-to-left dual of scanl.
Accumulating maps
mapAccumL :: (Storable a, Storable b) => (acc -> a -> (acc, b)) -> acc -> Vector a -> (acc, Vector b)Source
mapAccumR :: (Storable a, Storable b) => (acc -> a -> (acc, b)) -> acc -> Vector a -> (acc, Vector b)Source
mapIndexed :: (Storable a, Storable b) => (Int -> a -> b) -> Vector a -> Vector bSource
O(n) map functions, provided with the index at each position
Unfolding Vector
s
unfoldr :: Storable b => (a -> Maybe (b, a)) -> a -> Vector bSource
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 element in the Vector
,
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 :: Storable b => Int -> (a -> Maybe (b, a)) -> a -> (Vector 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)
unfoldrResultN :: Storable b => Int -> (a -> c) -> (a -> Either c (b, a)) -> a -> (Vector b, c)Source
O(n) Like unfoldrN
this function builds a Vector
from a seed value with limited size.
Additionally it returns a value, that depends on the state,
but is not necessarily the state itself.
If end of vector and end of the generator coincide,
then the result is as if only the end of vector is reached.
Example:
unfoldrResultN 30 Char.ord (\c -> if c>'z' then Left 1000 else Right (c, succ c)) 'a'
The following equation relates unfoldrN
and unfoldrResultN
:
unfoldrN n f s == unfoldrResultN n Just (maybe (Left Nothing) Right . f) s
It is not possible to express unfoldrResultN
in terms of unfoldrN
.
sample :: Storable a => Int -> (Int -> a) -> Vector aSource
O(n), where n is the length of the result.
This function constructs a vector by evaluating a function
that depends on the element index.
It is a special case of unfoldrN
and can in principle be parallelized.
Examples:
sample 26 (\x -> chr(ord 'a'+x)) == pack "abcdefghijklmnopqrstuvwxyz"
Substrings
Breaking strings
group :: (Storable a, Eq a) => Vector a -> [Vector a]Source
The group
function takes a Vector
and returns a list of
Vector
s such that the concatenation of the result is equal to the
argument. Moreover, each sublist in the result contains only equal
elements. For example,
group "Mississippi" = ["M","i","ss","i","ss","i","pp","i"]
It is a special case of groupBy
, which allows the programmer to
supply their own equality test. It is about 40% faster than
groupBy (==)
inits :: Storable a => Vector a -> [Vector a]Source
O(n) Return all initial segments of the given Vector
, shortest first.
tails :: Storable a => Vector a -> [Vector a]Source
O(n) Return all final segments of the given Vector
, longest first.
Breaking into many substrings
split :: (Storable a, Eq a) => a -> Vector a -> [Vector a]Source
O(n) Break a Vector
into pieces separated by the
argument, 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
join [c] . split c == id split == splitWith . (==)
As for all splitting functions in this library, this function does
not copy the substrings, it just constructs new Vector
s that
are slices of the original.
splitWith :: Storable a => (a -> Bool) -> Vector a -> [Vector 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') [] == []
tokens :: Storable a => (a -> Bool) -> Vector a -> [Vector a]Source
Like splitWith
, except that sequences of adjacent separators are
treated as a single separator. eg.
tokens (=='a') "aabbaca" == ["bb","c"]
Joining strings
Predicates
isPrefixOf :: (Storable a, Eq a) => Vector a -> Vector a -> BoolSource
O(n) The isPrefixOf
function takes two Vector
and returns True
iff the first is a prefix of the second.
isSuffixOf :: (Storable a, Eq a) => Vector a -> Vector a -> BoolSource
O(n) The isSuffixOf
function takes two Vector
s and returns True
iff the first is a suffix of the second.
The following holds:
isSuffixOf x y == reverse x `isPrefixOf` reverse y
Searching Vector
s
Searching by equality
Searching with a predicate
Indexing Vector
s
index :: Storable a => Vector a -> Int -> aSource
O(1) Vector
index (subscript) operator, starting from 0.
elemIndices :: (Storable a, Eq a) => a -> Vector 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.
elemIndexEnd :: (Storable a, Eq a) => a -> Vector a -> Maybe IntSource
O(n) The elemIndexEnd
function returns the last index of the
element in the given Vector
which is equal to the query
element, or Nothing
if there is no such element. The following
holds:
elemIndexEnd c xs == (-) (length xs - 1) `fmap` elemIndex c (reverse xs)
findIndices :: Storable a => (a -> Bool) -> Vector a -> [Int]Source
The findIndices
function extends findIndex
, by returning the
indices of all elements satisfying the predicate, in ascending order.
count :: (Storable a, Eq a) => a -> Vector a -> IntSource
count returns the number of times its argument appears in the Vector
count = length . elemIndices
But more efficiently than using length on the intermediate list.
findIndexOrEnd :: Storable a => (a -> Bool) -> Vector a -> IntSource
findIndexOrEnd
is a variant of findIndex, that returns the length
of the string if no element is found, rather than Nothing.
Zipping and unzipping Vector
s
zipWith :: (Storable a, Storable b, Storable c) => (a -> b -> c) -> Vector a -> Vector b -> Vector cSource
zipWith3 :: (Storable a, Storable b, Storable c, Storable d) => (a -> b -> c -> d) -> Vector a -> Vector b -> Vector c -> Vector dSource
Like zipWith
but for three input vectors
zipWith4 :: (Storable a, Storable b, Storable c, Storable d, Storable e) => (a -> b -> c -> d -> e) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector eSource
Like zipWith
but for four input vectors
If you need even more input vectors,
you might write a function yourselve using unfoldrN and viewL.
Interleaved Vector
s
deinterleave :: Storable a => Int -> Vector a -> [Vector a]Source
O(n)
Returns n sieved vectors with successive starting elements.
deinterleave 3 (pack ['a'..'k']) = [pack adgj, pack behk, pack cfi]
This is the same as sliceHorizontal
.
interleave :: Storable a => [Vector a] -> Vector aSource