{-# LANGUAGE CPP, DeriveDataTypeable, MultiParamTypeClasses, FlexibleInstances, TypeFamilies, Rank2Types, ScopedTypeVariables #-}
module Data.Vector.Storable (
Vector, MVector(..), Storable,
length, null,
(!), (!?), head, last,
unsafeIndex, unsafeHead, unsafeLast,
indexM, headM, lastM,
unsafeIndexM, unsafeHeadM, unsafeLastM,
slice, init, tail, take, drop, splitAt,
unsafeSlice, unsafeInit, unsafeTail, unsafeTake, unsafeDrop,
empty, singleton, replicate, generate, iterateN,
replicateM, generateM, iterateNM, create, createT,
unfoldr, unfoldrN,
unfoldrM, unfoldrNM,
constructN, constructrN,
enumFromN, enumFromStepN, enumFromTo, enumFromThenTo,
cons, snoc, (++), concat,
force,
(//), update_,
unsafeUpd, unsafeUpdate_,
accum, accumulate_,
unsafeAccum, unsafeAccumulate_,
reverse, backpermute, unsafeBackpermute,
modify,
map, imap, concatMap,
mapM, mapM_, forM, forM_,
zipWith, zipWith3, zipWith4, zipWith5, zipWith6,
izipWith, izipWith3, izipWith4, izipWith5, izipWith6,
zipWithM, zipWithM_,
filter, ifilter, uniq,
mapMaybe, imapMaybe,
filterM,
takeWhile, dropWhile,
partition, unstablePartition, partitionWith, span, break,
elem, notElem, find, findIndex, findIndices, elemIndex, elemIndices,
foldl, foldl1, foldl', foldl1', foldr, foldr1, foldr', foldr1',
ifoldl, ifoldl', ifoldr, ifoldr',
all, any, and, or,
sum, product,
maximum, maximumBy, minimum, minimumBy,
minIndex, minIndexBy, maxIndex, maxIndexBy,
foldM, foldM', fold1M, fold1M',
foldM_, foldM'_, fold1M_, fold1M'_,
prescanl, prescanl',
postscanl, postscanl',
scanl, scanl', scanl1, scanl1',
prescanr, prescanr',
postscanr, postscanr',
scanr, scanr', scanr1, scanr1',
toList, fromList, fromListN,
G.convert, unsafeCast,
freeze, thaw, copy, unsafeFreeze, unsafeThaw, unsafeCopy,
unsafeFromForeignPtr, unsafeFromForeignPtr0,
unsafeToForeignPtr, unsafeToForeignPtr0,
unsafeWith
) where
import qualified Data.Vector.Generic as G
import Data.Vector.Storable.Mutable ( MVector(..) )
import Data.Vector.Storable.Internal
import qualified Data.Vector.Fusion.Bundle as Bundle
import Foreign.Storable
import Foreign.ForeignPtr
import Foreign.Ptr
import Foreign.Marshal.Array ( advancePtr, copyArray )
import Control.DeepSeq ( NFData(rnf)
#if MIN_VERSION_deepseq(1,4,3)
, NFData1(liftRnf)
#endif
)
import Control.Monad.ST ( ST )
import Control.Monad.Primitive
import Prelude hiding ( length, null,
replicate, (++), concat,
head, last,
init, tail, take, drop, splitAt, reverse,
map, concatMap,
zipWith, zipWith3, zip, zip3, unzip, unzip3,
filter, takeWhile, dropWhile, span, break,
elem, notElem,
foldl, foldl1, foldr, foldr1,
all, any, and, or, sum, product, minimum, maximum,
scanl, scanl1, scanr, scanr1,
enumFromTo, enumFromThenTo,
mapM, mapM_ )
import Data.Typeable ( Typeable )
import Data.Data ( Data(..) )
import Text.Read ( Read(..), readListPrecDefault )
import Data.Semigroup ( Semigroup(..) )
#if !MIN_VERSION_base(4,8,0)
import Data.Monoid ( Monoid(..) )
import Data.Traversable ( Traversable )
#endif
#if __GLASGOW_HASKELL__ >= 708
import qualified GHC.Exts as Exts
#endif
#define NOT_VECTOR_MODULE
#include "vector.h"
data Vector a = Vector {-# UNPACK #-} !Int
{-# UNPACK #-} !(ForeignPtr a)
deriving ( Typeable )
instance NFData (Vector a) where
rnf (Vector _ _) = ()
#if MIN_VERSION_deepseq(1,4,3)
instance NFData1 Vector where
liftRnf _ (Vector _ _) = ()
#endif
instance (Show a, Storable a) => Show (Vector a) where
showsPrec = G.showsPrec
instance (Read a, Storable a) => Read (Vector a) where
readPrec = G.readPrec
readListPrec = readListPrecDefault
instance (Data a, Storable a) => Data (Vector a) where
gfoldl = G.gfoldl
toConstr _ = G.mkVecConstr "Data.Vector.Storable.Vector"
gunfold = G.gunfold
dataTypeOf _ = G.mkVecType "Data.Vector.Storable.Vector"
dataCast1 = G.dataCast
type instance G.Mutable Vector = MVector
instance Storable a => G.Vector Vector a where
{-# INLINE basicUnsafeFreeze #-}
basicUnsafeFreeze (MVector n fp) = return $ Vector n fp
{-# INLINE basicUnsafeThaw #-}
basicUnsafeThaw (Vector n fp) = return $ MVector n fp
{-# INLINE basicLength #-}
basicLength (Vector n _) = n
{-# INLINE basicUnsafeSlice #-}
basicUnsafeSlice i n (Vector _ fp) = Vector n (updPtr (`advancePtr` i) fp)
{-# INLINE basicUnsafeIndexM #-}
basicUnsafeIndexM (Vector _ fp) i = return
. unsafeInlineIO
$ withForeignPtr fp $ \p ->
peekElemOff p i
{-# INLINE basicUnsafeCopy #-}
basicUnsafeCopy (MVector n fp) (Vector _ fq)
= unsafePrimToPrim
$ withForeignPtr fp $ \p ->
withForeignPtr fq $ \q ->
copyArray p q n
{-# INLINE elemseq #-}
elemseq _ = seq
instance (Storable a, Eq a) => Eq (Vector a) where
{-# INLINE (==) #-}
xs == ys = Bundle.eq (G.stream xs) (G.stream ys)
{-# INLINE (/=) #-}
xs /= ys = not (Bundle.eq (G.stream xs) (G.stream ys))
instance (Storable a, Ord a) => Ord (Vector a) where
{-# INLINE compare #-}
compare xs ys = Bundle.cmp (G.stream xs) (G.stream ys)
{-# INLINE (<) #-}
xs < ys = Bundle.cmp (G.stream xs) (G.stream ys) == LT
{-# INLINE (<=) #-}
xs <= ys = Bundle.cmp (G.stream xs) (G.stream ys) /= GT
{-# INLINE (>) #-}
xs > ys = Bundle.cmp (G.stream xs) (G.stream ys) == GT
{-# INLINE (>=) #-}
xs >= ys = Bundle.cmp (G.stream xs) (G.stream ys) /= LT
instance Storable a => Semigroup (Vector a) where
{-# INLINE (<>) #-}
(<>) = (++)
{-# INLINE sconcat #-}
sconcat = G.concatNE
instance Storable a => Monoid (Vector a) where
{-# INLINE mempty #-}
mempty = empty
{-# INLINE mappend #-}
mappend = (++)
{-# INLINE mconcat #-}
mconcat = concat
#if __GLASGOW_HASKELL__ >= 708
instance Storable a => Exts.IsList (Vector a) where
type Item (Vector a) = a
fromList = fromList
fromListN = fromListN
toList = toList
#endif
length :: Storable a => Vector a -> Int
{-# INLINE length #-}
length = G.length
null :: Storable a => Vector a -> Bool
{-# INLINE null #-}
null = G.null
(!) :: Storable a => Vector a -> Int -> a
{-# INLINE (!) #-}
(!) = (G.!)
(!?) :: Storable a => Vector a -> Int -> Maybe a
{-# INLINE (!?) #-}
(!?) = (G.!?)
head :: Storable a => Vector a -> a
{-# INLINE head #-}
head = G.head
last :: Storable a => Vector a -> a
{-# INLINE last #-}
last = G.last
unsafeIndex :: Storable a => Vector a -> Int -> a
{-# INLINE unsafeIndex #-}
unsafeIndex = G.unsafeIndex
unsafeHead :: Storable a => Vector a -> a
{-# INLINE unsafeHead #-}
unsafeHead = G.unsafeHead
unsafeLast :: Storable a => Vector a -> a
{-# INLINE unsafeLast #-}
unsafeLast = G.unsafeLast
indexM :: (Storable a, Monad m) => Vector a -> Int -> m a
{-# INLINE indexM #-}
indexM = G.indexM
headM :: (Storable a, Monad m) => Vector a -> m a
{-# INLINE headM #-}
headM = G.headM
lastM :: (Storable a, Monad m) => Vector a -> m a
{-# INLINE lastM #-}
lastM = G.lastM
unsafeIndexM :: (Storable a, Monad m) => Vector a -> Int -> m a
{-# INLINE unsafeIndexM #-}
unsafeIndexM = G.unsafeIndexM
unsafeHeadM :: (Storable a, Monad m) => Vector a -> m a
{-# INLINE unsafeHeadM #-}
unsafeHeadM = G.unsafeHeadM
unsafeLastM :: (Storable a, Monad m) => Vector a -> m a
{-# INLINE unsafeLastM #-}
unsafeLastM = G.unsafeLastM
slice :: Storable a
=> Int
-> Int
-> Vector a
-> Vector a
{-# INLINE slice #-}
slice = G.slice
init :: Storable a => Vector a -> Vector a
{-# INLINE init #-}
init = G.init
tail :: Storable a => Vector a -> Vector a
{-# INLINE tail #-}
tail = G.tail
take :: Storable a => Int -> Vector a -> Vector a
{-# INLINE take #-}
take = G.take
drop :: Storable a => Int -> Vector a -> Vector a
{-# INLINE drop #-}
drop = G.drop
{-# INLINE splitAt #-}
splitAt :: Storable a => Int -> Vector a -> (Vector a, Vector a)
splitAt = G.splitAt
unsafeSlice :: Storable a => Int
-> Int
-> Vector a
-> Vector a
{-# INLINE unsafeSlice #-}
unsafeSlice = G.unsafeSlice
unsafeInit :: Storable a => Vector a -> Vector a
{-# INLINE unsafeInit #-}
unsafeInit = G.unsafeInit
unsafeTail :: Storable a => Vector a -> Vector a
{-# INLINE unsafeTail #-}
unsafeTail = G.unsafeTail
unsafeTake :: Storable a => Int -> Vector a -> Vector a
{-# INLINE unsafeTake #-}
unsafeTake = G.unsafeTake
unsafeDrop :: Storable a => Int -> Vector a -> Vector a
{-# INLINE unsafeDrop #-}
unsafeDrop = G.unsafeDrop
empty :: Storable a => Vector a
{-# INLINE empty #-}
empty = G.empty
singleton :: Storable a => a -> Vector a
{-# INLINE singleton #-}
singleton = G.singleton
replicate :: Storable a => Int -> a -> Vector a
{-# INLINE replicate #-}
replicate = G.replicate
generate :: Storable a => Int -> (Int -> a) -> Vector a
{-# INLINE generate #-}
generate = G.generate
iterateN :: Storable a => Int -> (a -> a) -> a -> Vector a
{-# INLINE iterateN #-}
iterateN = G.iterateN
unfoldr :: Storable a => (b -> Maybe (a, b)) -> b -> Vector a
{-# INLINE unfoldr #-}
unfoldr = G.unfoldr
unfoldrN :: Storable a => Int -> (b -> Maybe (a, b)) -> b -> Vector a
{-# INLINE unfoldrN #-}
unfoldrN = G.unfoldrN
unfoldrM :: (Monad m, Storable a) => (b -> m (Maybe (a, b))) -> b -> m (Vector a)
{-# INLINE unfoldrM #-}
unfoldrM = G.unfoldrM
unfoldrNM :: (Monad m, Storable a) => Int -> (b -> m (Maybe (a, b))) -> b -> m (Vector a)
{-# INLINE unfoldrNM #-}
unfoldrNM = G.unfoldrNM
constructN :: Storable a => Int -> (Vector a -> a) -> Vector a
{-# INLINE constructN #-}
constructN = G.constructN
constructrN :: Storable a => Int -> (Vector a -> a) -> Vector a
{-# INLINE constructrN #-}
constructrN = G.constructrN
enumFromN :: (Storable a, Num a) => a -> Int -> Vector a
{-# INLINE enumFromN #-}
enumFromN = G.enumFromN
enumFromStepN :: (Storable a, Num a) => a -> a -> Int -> Vector a
{-# INLINE enumFromStepN #-}
enumFromStepN = G.enumFromStepN
enumFromTo :: (Storable a, Enum a) => a -> a -> Vector a
{-# INLINE enumFromTo #-}
enumFromTo = G.enumFromTo
enumFromThenTo :: (Storable a, Enum a) => a -> a -> a -> Vector a
{-# INLINE enumFromThenTo #-}
enumFromThenTo = G.enumFromThenTo
cons :: Storable a => a -> Vector a -> Vector a
{-# INLINE cons #-}
cons = G.cons
snoc :: Storable a => Vector a -> a -> Vector a
{-# INLINE snoc #-}
snoc = G.snoc
infixr 5 ++
(++) :: Storable a => Vector a -> Vector a -> Vector a
{-# INLINE (++) #-}
(++) = (G.++)
concat :: Storable a => [Vector a] -> Vector a
{-# INLINE concat #-}
concat = G.concat
replicateM :: (Monad m, Storable a) => Int -> m a -> m (Vector a)
{-# INLINE replicateM #-}
replicateM = G.replicateM
generateM :: (Monad m, Storable a) => Int -> (Int -> m a) -> m (Vector a)
{-# INLINE generateM #-}
generateM = G.generateM
iterateNM :: (Monad m, Storable a) => Int -> (a -> m a) -> a -> m (Vector a)
{-# INLINE iterateNM #-}
iterateNM = G.iterateNM
create :: Storable a => (forall s. ST s (MVector s a)) -> Vector a
{-# INLINE create #-}
create p = G.create p
createT :: (Traversable f, Storable a) => (forall s. ST s (f (MVector s a))) -> f (Vector a)
{-# INLINE createT #-}
createT p = G.createT p
force :: Storable a => Vector a -> Vector a
{-# INLINE force #-}
force = G.force
(//) :: Storable a => Vector a
-> [(Int, a)]
-> Vector a
{-# INLINE (//) #-}
(//) = (G.//)
update_ :: Storable a
=> Vector a
-> Vector Int
-> Vector a
-> Vector a
{-# INLINE update_ #-}
update_ = G.update_
unsafeUpd :: Storable a => Vector a -> [(Int, a)] -> Vector a
{-# INLINE unsafeUpd #-}
unsafeUpd = G.unsafeUpd
unsafeUpdate_ :: Storable a => Vector a -> Vector Int -> Vector a -> Vector a
{-# INLINE unsafeUpdate_ #-}
unsafeUpdate_ = G.unsafeUpdate_
accum :: Storable a
=> (a -> b -> a)
-> Vector a
-> [(Int,b)]
-> Vector a
{-# INLINE accum #-}
accum = G.accum
accumulate_ :: (Storable a, Storable b)
=> (a -> b -> a)
-> Vector a
-> Vector Int
-> Vector b
-> Vector a
{-# INLINE accumulate_ #-}
accumulate_ = G.accumulate_
unsafeAccum :: Storable a => (a -> b -> a) -> Vector a -> [(Int,b)] -> Vector a
{-# INLINE unsafeAccum #-}
unsafeAccum = G.unsafeAccum
unsafeAccumulate_ :: (Storable a, Storable b) =>
(a -> b -> a) -> Vector a -> Vector Int -> Vector b -> Vector a
{-# INLINE unsafeAccumulate_ #-}
unsafeAccumulate_ = G.unsafeAccumulate_
reverse :: Storable a => Vector a -> Vector a
{-# INLINE reverse #-}
reverse = G.reverse
backpermute :: Storable a => Vector a -> Vector Int -> Vector a
{-# INLINE backpermute #-}
backpermute = G.backpermute
unsafeBackpermute :: Storable a => Vector a -> Vector Int -> Vector a
{-# INLINE unsafeBackpermute #-}
unsafeBackpermute = G.unsafeBackpermute
modify :: Storable a => (forall s. MVector s a -> ST s ()) -> Vector a -> Vector a
{-# INLINE modify #-}
modify p = G.modify p
map :: (Storable a, Storable b) => (a -> b) -> Vector a -> Vector b
{-# INLINE map #-}
map = G.map
imap :: (Storable a, Storable b) => (Int -> a -> b) -> Vector a -> Vector b
{-# INLINE imap #-}
imap = G.imap
concatMap :: (Storable a, Storable b) => (a -> Vector b) -> Vector a -> Vector b
{-# INLINE concatMap #-}
concatMap = G.concatMap
mapM :: (Monad m, Storable a, Storable b) => (a -> m b) -> Vector a -> m (Vector b)
{-# INLINE mapM #-}
mapM = G.mapM
mapM_ :: (Monad m, Storable a) => (a -> m b) -> Vector a -> m ()
{-# INLINE mapM_ #-}
mapM_ = G.mapM_
forM :: (Monad m, Storable a, Storable b) => Vector a -> (a -> m b) -> m (Vector b)
{-# INLINE forM #-}
forM = G.forM
forM_ :: (Monad m, Storable a) => Vector a -> (a -> m b) -> m ()
{-# INLINE forM_ #-}
forM_ = G.forM_
zipWith :: (Storable a, Storable b, Storable c)
=> (a -> b -> c) -> Vector a -> Vector b -> Vector c
{-# INLINE zipWith #-}
zipWith = G.zipWith
zipWith3 :: (Storable a, Storable b, Storable c, Storable d)
=> (a -> b -> c -> d) -> Vector a -> Vector b -> Vector c -> Vector d
{-# INLINE zipWith3 #-}
zipWith3 = G.zipWith3
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
{-# INLINE zipWith4 #-}
zipWith4 = G.zipWith4
zipWith5 :: (Storable a, Storable b, Storable c, Storable d, Storable e,
Storable f)
=> (a -> b -> c -> d -> e -> f)
-> Vector a -> Vector b -> Vector c -> Vector d -> Vector e
-> Vector f
{-# INLINE zipWith5 #-}
zipWith5 = G.zipWith5
zipWith6 :: (Storable a, Storable b, Storable c, Storable d, Storable e,
Storable f, Storable g)
=> (a -> b -> c -> d -> e -> f -> g)
-> Vector a -> Vector b -> Vector c -> Vector d -> Vector e
-> Vector f -> Vector g
{-# INLINE zipWith6 #-}
zipWith6 = G.zipWith6
izipWith :: (Storable a, Storable b, Storable c)
=> (Int -> a -> b -> c) -> Vector a -> Vector b -> Vector c
{-# INLINE izipWith #-}
izipWith = G.izipWith
izipWith3 :: (Storable a, Storable b, Storable c, Storable d)
=> (Int -> a -> b -> c -> d)
-> Vector a -> Vector b -> Vector c -> Vector d
{-# INLINE izipWith3 #-}
izipWith3 = G.izipWith3
izipWith4 :: (Storable a, Storable b, Storable c, Storable d, Storable e)
=> (Int -> a -> b -> c -> d -> e)
-> Vector a -> Vector b -> Vector c -> Vector d -> Vector e
{-# INLINE izipWith4 #-}
izipWith4 = G.izipWith4
izipWith5 :: (Storable a, Storable b, Storable c, Storable d, Storable e,
Storable f)
=> (Int -> a -> b -> c -> d -> e -> f)
-> Vector a -> Vector b -> Vector c -> Vector d -> Vector e
-> Vector f
{-# INLINE izipWith5 #-}
izipWith5 = G.izipWith5
izipWith6 :: (Storable a, Storable b, Storable c, Storable d, Storable e,
Storable f, Storable g)
=> (Int -> a -> b -> c -> d -> e -> f -> g)
-> Vector a -> Vector b -> Vector c -> Vector d -> Vector e
-> Vector f -> Vector g
{-# INLINE izipWith6 #-}
izipWith6 = G.izipWith6
zipWithM :: (Monad m, Storable a, Storable b, Storable c)
=> (a -> b -> m c) -> Vector a -> Vector b -> m (Vector c)
{-# INLINE zipWithM #-}
zipWithM = G.zipWithM
zipWithM_ :: (Monad m, Storable a, Storable b)
=> (a -> b -> m c) -> Vector a -> Vector b -> m ()
{-# INLINE zipWithM_ #-}
zipWithM_ = G.zipWithM_
filter :: Storable a => (a -> Bool) -> Vector a -> Vector a
{-# INLINE filter #-}
filter = G.filter
ifilter :: Storable a => (Int -> a -> Bool) -> Vector a -> Vector a
{-# INLINE ifilter #-}
ifilter = G.ifilter
uniq :: (Storable a, Eq a) => Vector a -> Vector a
{-# INLINE uniq #-}
uniq = G.uniq
mapMaybe :: (Storable a, Storable b) => (a -> Maybe b) -> Vector a -> Vector b
{-# INLINE mapMaybe #-}
mapMaybe = G.mapMaybe
imapMaybe :: (Storable a, Storable b) => (Int -> a -> Maybe b) -> Vector a -> Vector b
{-# INLINE imapMaybe #-}
imapMaybe = G.imapMaybe
filterM :: (Monad m, Storable a) => (a -> m Bool) -> Vector a -> m (Vector a)
{-# INLINE filterM #-}
filterM = G.filterM
takeWhile :: Storable a => (a -> Bool) -> Vector a -> Vector a
{-# INLINE takeWhile #-}
takeWhile = G.takeWhile
dropWhile :: Storable a => (a -> Bool) -> Vector a -> Vector a
{-# INLINE dropWhile #-}
dropWhile = G.dropWhile
partition :: Storable a => (a -> Bool) -> Vector a -> (Vector a, Vector a)
{-# INLINE partition #-}
partition = G.partition
unstablePartition :: Storable a => (a -> Bool) -> Vector a -> (Vector a, Vector a)
{-# INLINE unstablePartition #-}
unstablePartition = G.unstablePartition
partitionWith :: (Storable a, Storable b, Storable c) => (a -> Either b c) -> Vector a -> (Vector b, Vector c)
{-# INLINE partitionWith #-}
partitionWith = G.partitionWith
span :: Storable a => (a -> Bool) -> Vector a -> (Vector a, Vector a)
{-# INLINE span #-}
span = G.span
break :: Storable a => (a -> Bool) -> Vector a -> (Vector a, Vector a)
{-# INLINE break #-}
break = G.break
infix 4 `elem`
elem :: (Storable a, Eq a) => a -> Vector a -> Bool
{-# INLINE elem #-}
elem = G.elem
infix 4 `notElem`
notElem :: (Storable a, Eq a) => a -> Vector a -> Bool
{-# INLINE notElem #-}
notElem = G.notElem
find :: Storable a => (a -> Bool) -> Vector a -> Maybe a
{-# INLINE find #-}
find = G.find
findIndex :: Storable a => (a -> Bool) -> Vector a -> Maybe Int
{-# INLINE findIndex #-}
findIndex = G.findIndex
findIndices :: Storable a => (a -> Bool) -> Vector a -> Vector Int
{-# INLINE findIndices #-}
findIndices = G.findIndices
elemIndex :: (Storable a, Eq a) => a -> Vector a -> Maybe Int
{-# INLINE elemIndex #-}
elemIndex = G.elemIndex
elemIndices :: (Storable a, Eq a) => a -> Vector a -> Vector Int
{-# INLINE elemIndices #-}
elemIndices = G.elemIndices
foldl :: Storable b => (a -> b -> a) -> a -> Vector b -> a
{-# INLINE foldl #-}
foldl = G.foldl
foldl1 :: Storable a => (a -> a -> a) -> Vector a -> a
{-# INLINE foldl1 #-}
foldl1 = G.foldl1
foldl' :: Storable b => (a -> b -> a) -> a -> Vector b -> a
{-# INLINE foldl' #-}
foldl' = G.foldl'
foldl1' :: Storable a => (a -> a -> a) -> Vector a -> a
{-# INLINE foldl1' #-}
foldl1' = G.foldl1'
foldr :: Storable a => (a -> b -> b) -> b -> Vector a -> b
{-# INLINE foldr #-}
foldr = G.foldr
foldr1 :: Storable a => (a -> a -> a) -> Vector a -> a
{-# INLINE foldr1 #-}
foldr1 = G.foldr1
foldr' :: Storable a => (a -> b -> b) -> b -> Vector a -> b
{-# INLINE foldr' #-}
foldr' = G.foldr'
foldr1' :: Storable a => (a -> a -> a) -> Vector a -> a
{-# INLINE foldr1' #-}
foldr1' = G.foldr1'
ifoldl :: Storable b => (a -> Int -> b -> a) -> a -> Vector b -> a
{-# INLINE ifoldl #-}
ifoldl = G.ifoldl
ifoldl' :: Storable b => (a -> Int -> b -> a) -> a -> Vector b -> a
{-# INLINE ifoldl' #-}
ifoldl' = G.ifoldl'
ifoldr :: Storable a => (Int -> a -> b -> b) -> b -> Vector a -> b
{-# INLINE ifoldr #-}
ifoldr = G.ifoldr
ifoldr' :: Storable a => (Int -> a -> b -> b) -> b -> Vector a -> b
{-# INLINE ifoldr' #-}
ifoldr' = G.ifoldr'
all :: Storable a => (a -> Bool) -> Vector a -> Bool
{-# INLINE all #-}
all = G.all
any :: Storable a => (a -> Bool) -> Vector a -> Bool
{-# INLINE any #-}
any = G.any
and :: Vector Bool -> Bool
{-# INLINE and #-}
and = G.and
or :: Vector Bool -> Bool
{-# INLINE or #-}
or = G.or
sum :: (Storable a, Num a) => Vector a -> a
{-# INLINE sum #-}
sum = G.sum
product :: (Storable a, Num a) => Vector a -> a
{-# INLINE product #-}
product = G.product
maximum :: (Storable a, Ord a) => Vector a -> a
{-# INLINE maximum #-}
maximum = G.maximum
maximumBy :: Storable a => (a -> a -> Ordering) -> Vector a -> a
{-# INLINE maximumBy #-}
maximumBy = G.maximumBy
minimum :: (Storable a, Ord a) => Vector a -> a
{-# INLINE minimum #-}
minimum = G.minimum
minimumBy :: Storable a => (a -> a -> Ordering) -> Vector a -> a
{-# INLINE minimumBy #-}
minimumBy = G.minimumBy
maxIndex :: (Storable a, Ord a) => Vector a -> Int
{-# INLINE maxIndex #-}
maxIndex = G.maxIndex
maxIndexBy :: Storable a => (a -> a -> Ordering) -> Vector a -> Int
{-# INLINE maxIndexBy #-}
maxIndexBy = G.maxIndexBy
minIndex :: (Storable a, Ord a) => Vector a -> Int
{-# INLINE minIndex #-}
minIndex = G.minIndex
minIndexBy :: Storable a => (a -> a -> Ordering) -> Vector a -> Int
{-# INLINE minIndexBy #-}
minIndexBy = G.minIndexBy
foldM :: (Monad m, Storable b) => (a -> b -> m a) -> a -> Vector b -> m a
{-# INLINE foldM #-}
foldM = G.foldM
fold1M :: (Monad m, Storable a) => (a -> a -> m a) -> Vector a -> m a
{-# INLINE fold1M #-}
fold1M = G.fold1M
foldM' :: (Monad m, Storable b) => (a -> b -> m a) -> a -> Vector b -> m a
{-# INLINE foldM' #-}
foldM' = G.foldM'
fold1M' :: (Monad m, Storable a) => (a -> a -> m a) -> Vector a -> m a
{-# INLINE fold1M' #-}
fold1M' = G.fold1M'
foldM_ :: (Monad m, Storable b) => (a -> b -> m a) -> a -> Vector b -> m ()
{-# INLINE foldM_ #-}
foldM_ = G.foldM_
fold1M_ :: (Monad m, Storable a) => (a -> a -> m a) -> Vector a -> m ()
{-# INLINE fold1M_ #-}
fold1M_ = G.fold1M_
foldM'_ :: (Monad m, Storable b) => (a -> b -> m a) -> a -> Vector b -> m ()
{-# INLINE foldM'_ #-}
foldM'_ = G.foldM'_
fold1M'_ :: (Monad m, Storable a) => (a -> a -> m a) -> Vector a -> m ()
{-# INLINE fold1M'_ #-}
fold1M'_ = G.fold1M'_
prescanl :: (Storable a, Storable b) => (a -> b -> a) -> a -> Vector b -> Vector a
{-# INLINE prescanl #-}
prescanl = G.prescanl
prescanl' :: (Storable a, Storable b) => (a -> b -> a) -> a -> Vector b -> Vector a
{-# INLINE prescanl' #-}
prescanl' = G.prescanl'
postscanl :: (Storable a, Storable b) => (a -> b -> a) -> a -> Vector b -> Vector a
{-# INLINE postscanl #-}
postscanl = G.postscanl
postscanl' :: (Storable a, Storable b) => (a -> b -> a) -> a -> Vector b -> Vector a
{-# INLINE postscanl' #-}
postscanl' = G.postscanl'
scanl :: (Storable a, Storable b) => (a -> b -> a) -> a -> Vector b -> Vector a
{-# INLINE scanl #-}
scanl = G.scanl
scanl' :: (Storable a, Storable b) => (a -> b -> a) -> a -> Vector b -> Vector a
{-# INLINE scanl' #-}
scanl' = G.scanl'
scanl1 :: Storable a => (a -> a -> a) -> Vector a -> Vector a
{-# INLINE scanl1 #-}
scanl1 = G.scanl1
scanl1' :: Storable a => (a -> a -> a) -> Vector a -> Vector a
{-# INLINE scanl1' #-}
scanl1' = G.scanl1'
prescanr :: (Storable a, Storable b) => (a -> b -> b) -> b -> Vector a -> Vector b
{-# INLINE prescanr #-}
prescanr = G.prescanr
prescanr' :: (Storable a, Storable b) => (a -> b -> b) -> b -> Vector a -> Vector b
{-# INLINE prescanr' #-}
prescanr' = G.prescanr'
postscanr :: (Storable a, Storable b) => (a -> b -> b) -> b -> Vector a -> Vector b
{-# INLINE postscanr #-}
postscanr = G.postscanr
postscanr' :: (Storable a, Storable b) => (a -> b -> b) -> b -> Vector a -> Vector b
{-# INLINE postscanr' #-}
postscanr' = G.postscanr'
scanr :: (Storable a, Storable b) => (a -> b -> b) -> b -> Vector a -> Vector b
{-# INLINE scanr #-}
scanr = G.scanr
scanr' :: (Storable a, Storable b) => (a -> b -> b) -> b -> Vector a -> Vector b
{-# INLINE scanr' #-}
scanr' = G.scanr'
scanr1 :: Storable a => (a -> a -> a) -> Vector a -> Vector a
{-# INLINE scanr1 #-}
scanr1 = G.scanr1
scanr1' :: Storable a => (a -> a -> a) -> Vector a -> Vector a
{-# INLINE scanr1' #-}
scanr1' = G.scanr1'
toList :: Storable a => Vector a -> [a]
{-# INLINE toList #-}
toList = G.toList
fromList :: Storable a => [a] -> Vector a
{-# INLINE fromList #-}
fromList = G.fromList
fromListN :: Storable a => Int -> [a] -> Vector a
{-# INLINE fromListN #-}
fromListN = G.fromListN
unsafeCast :: forall a b. (Storable a, Storable b) => Vector a -> Vector b
{-# INLINE unsafeCast #-}
unsafeCast (Vector n fp)
= Vector ((n * sizeOf (undefined :: a)) `div` sizeOf (undefined :: b))
(castForeignPtr fp)
unsafeFreeze
:: (Storable a, PrimMonad m) => MVector (PrimState m) a -> m (Vector a)
{-# INLINE unsafeFreeze #-}
unsafeFreeze = G.unsafeFreeze
unsafeThaw
:: (Storable a, PrimMonad m) => Vector a -> m (MVector (PrimState m) a)
{-# INLINE unsafeThaw #-}
unsafeThaw = G.unsafeThaw
thaw :: (Storable a, PrimMonad m) => Vector a -> m (MVector (PrimState m) a)
{-# INLINE thaw #-}
thaw = G.thaw
freeze :: (Storable a, PrimMonad m) => MVector (PrimState m) a -> m (Vector a)
{-# INLINE freeze #-}
freeze = G.freeze
unsafeCopy
:: (Storable a, PrimMonad m) => MVector (PrimState m) a -> Vector a -> m ()
{-# INLINE unsafeCopy #-}
unsafeCopy = G.unsafeCopy
copy :: (Storable a, PrimMonad m) => MVector (PrimState m) a -> Vector a -> m ()
{-# INLINE copy #-}
copy = G.copy
unsafeFromForeignPtr :: Storable a
=> ForeignPtr a
-> Int
-> Int
-> Vector a
{-# INLINE_FUSED unsafeFromForeignPtr #-}
unsafeFromForeignPtr fp i n = unsafeFromForeignPtr0 fp' n
where
fp' = updPtr (`advancePtr` i) fp
{-# RULES
"unsafeFromForeignPtr fp 0 n -> unsafeFromForeignPtr0 fp n " forall fp n.
unsafeFromForeignPtr fp 0 n = unsafeFromForeignPtr0 fp n #-}
unsafeFromForeignPtr0 :: Storable a
=> ForeignPtr a
-> Int
-> Vector a
{-# INLINE unsafeFromForeignPtr0 #-}
unsafeFromForeignPtr0 fp n = Vector n fp
unsafeToForeignPtr :: Storable a => Vector a -> (ForeignPtr a, Int, Int)
{-# INLINE unsafeToForeignPtr #-}
unsafeToForeignPtr (Vector n fp) = (fp, 0, n)
unsafeToForeignPtr0 :: Storable a => Vector a -> (ForeignPtr a, Int)
{-# INLINE unsafeToForeignPtr0 #-}
unsafeToForeignPtr0 (Vector n fp) = (fp, n)
unsafeWith :: Storable a => Vector a -> (Ptr a -> IO b) -> IO b
{-# INLINE unsafeWith #-}
unsafeWith (Vector _ fp) = withForeignPtr fp