{-# LANGUAGE CPP
           , DeriveDataTypeable
           , FlexibleInstances
           , MultiParamTypeClasses
           , TypeFamilies
           , Rank2Types
           , BangPatterns
  #-}

-- |
-- Module      : Data.Vector
-- Copyright   : (c) Roman Leshchinskiy 2008-2010
-- License     : BSD-style
--
-- Maintainer  : Roman Leshchinskiy <rl@cse.unsw.edu.au>
-- Stability   : experimental
-- Portability : non-portable
--
-- A library for boxed vectors (that is, polymorphic arrays capable of
-- holding any Haskell value). The vectors come in two flavours:
--
--  * mutable
--
--  * immutable
--
-- and support a rich interface of both list-like operations, and bulk
-- array operations.
--
-- For unboxed arrays, use "Data.Vector.Unboxed"
--

module Data.Vector (
  -- * Boxed vectors
  Vector, MVector,

  -- * Accessors

  -- ** Length information
  length, null,

  -- ** Indexing
  (!), (!?), head, last,
  unsafeIndex, unsafeHead, unsafeLast,

  -- ** Monadic indexing
  indexM, headM, lastM,
  unsafeIndexM, unsafeHeadM, unsafeLastM,

  -- ** Extracting subvectors (slicing)
  slice, init, tail, take, drop, splitAt, uncons, unsnoc,
  unsafeSlice, unsafeInit, unsafeTail, unsafeTake, unsafeDrop,

  -- * Construction

  -- ** Initialisation
  empty, singleton, replicate, generate, iterateN,

  -- ** Monadic initialisation
  replicateM, generateM, iterateNM, create, createT,

  -- ** Unfolding
  unfoldr, unfoldrN, unfoldrExactN,
  unfoldrM, unfoldrNM, unfoldrExactNM,
  constructN, constructrN,

  -- ** Enumeration
  enumFromN, enumFromStepN, enumFromTo, enumFromThenTo,

  -- ** Concatenation
  cons, snoc, (++), concat,

  -- ** Restricting memory usage
  force,

  -- * Modifying vectors

  -- ** Bulk updates
  (//), update, update_,
  unsafeUpd, unsafeUpdate, unsafeUpdate_,

  -- ** Accumulations
  accum, accumulate, accumulate_,
  unsafeAccum, unsafeAccumulate, unsafeAccumulate_,

  -- ** Permutations
  reverse, backpermute, unsafeBackpermute,

  -- ** Safe destructive updates
  modify,

  -- * Elementwise operations

  -- ** Indexing
  indexed,

  -- ** Mapping
  map, imap, concatMap,

  -- ** Monadic mapping
  mapM, imapM, mapM_, imapM_, forM, forM_,
  iforM, iforM_,

  -- ** Zipping
  zipWith, zipWith3, zipWith4, zipWith5, zipWith6,
  izipWith, izipWith3, izipWith4, izipWith5, izipWith6,
  zip, zip3, zip4, zip5, zip6,

  -- ** Monadic zipping
  zipWithM, izipWithM, zipWithM_, izipWithM_,

  -- ** Unzipping
  unzip, unzip3, unzip4, unzip5, unzip6,

  -- * Working with predicates

  -- ** Filtering
  filter, ifilter, filterM, uniq,
  mapMaybe, imapMaybe,
  mapMaybeM, imapMaybeM,
  catMaybes,
  takeWhile, dropWhile,

  -- ** Partitioning
  partition, unstablePartition, partitionWith, span, break,

  -- ** Searching
  elem, notElem, find, findIndex, findIndices, elemIndex, elemIndices,

  -- * Folding
  foldl, foldl1, foldl', foldl1', foldr, foldr1, foldr', foldr1',
  ifoldl, ifoldl', ifoldr, ifoldr',
  foldMap, foldMap',

  -- ** Specialised folds
  all, any, and, or,
  sum, product,
  maximum, maximumBy, minimum, minimumBy,
  minIndex, minIndexBy, maxIndex, maxIndexBy,

  -- ** Monadic folds
  foldM, ifoldM, foldM', ifoldM',
  fold1M, fold1M',foldM_, ifoldM_,
  foldM'_, ifoldM'_, fold1M_, fold1M'_,

  -- ** Monadic sequencing
  sequence, sequence_,

  -- * Prefix sums (scans)
  prescanl, prescanl',
  postscanl, postscanl',
  scanl, scanl', scanl1, scanl1',
  iscanl, iscanl',
  prescanr, prescanr',
  postscanr, postscanr',
  scanr, scanr', scanr1, scanr1',
  iscanr, iscanr',

  -- ** Comparisons
  eqBy, cmpBy,

  -- * Conversions

  -- ** Lists
  toList, Data.Vector.fromList, Data.Vector.fromListN,

  -- ** Arrays
  fromArray, toArray,

  -- ** Other vector types
  G.convert,

  -- ** Mutable vectors
  freeze, thaw, copy, unsafeFreeze, unsafeThaw, unsafeCopy
) where

import Data.Vector.Mutable  ( MVector(..) )
import Data.Primitive.Array
import qualified Data.Vector.Fusion.Bundle as Bundle
import qualified Data.Vector.Generic as G

import Control.DeepSeq ( NFData(rnf)
#if MIN_VERSION_deepseq(1,4,3)
                       , NFData1(liftRnf)
#endif
                       )

import Control.Monad ( MonadPlus(..), liftM, ap )
import Control.Monad.ST ( ST, runST )
import Control.Monad.Primitive
import qualified Control.Monad.Fail as Fail
import Control.Monad.Fix ( MonadFix (mfix) )
import Control.Monad.Zip
import Data.Function ( fix )

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,
#if __GLASGOW_HASKELL__ >= 706
                        foldMap,
#endif
                        all, any, and, or, sum, product, minimum, maximum,
                        scanl, scanl1, scanr, scanr1,
                        enumFromTo, enumFromThenTo,
                        mapM, mapM_, sequence, sequence_ )

#if MIN_VERSION_base(4,9,0)
import Data.Functor.Classes (Eq1 (..), Ord1 (..), Read1 (..), Show1 (..))
#endif

import Data.Typeable  ( Typeable )
import Data.Data      ( Data(..) )
import Text.Read      ( Read(..), readListPrecDefault )
import Data.Semigroup ( Semigroup(..) )

import qualified Control.Applicative as Applicative
import qualified Data.Foldable as Foldable
import qualified Data.Traversable as Traversable

#if !MIN_VERSION_base(4,8,0)
import Data.Monoid   ( Monoid(..) )
#endif

#if __GLASGOW_HASKELL__ >= 708
import qualified GHC.Exts as Exts (IsList(..))
#endif


-- | Boxed vectors, supporting efficient slicing.
data Vector a = Vector {-# UNPACK #-} !Int
                       {-# UNPACK #-} !Int
                       {-# UNPACK #-} !(Array a)
        deriving ( Typeable )

liftRnfV :: (a -> ()) -> Vector a -> ()
liftRnfV :: (a -> ()) -> Vector a -> ()
liftRnfV a -> ()
elemRnf = (() -> a -> ()) -> () -> Vector a -> ()
forall a b. (a -> b -> a) -> a -> Vector b -> a
foldl' (\()
_ -> a -> ()
elemRnf) ()

instance NFData a => NFData (Vector a) where
  rnf :: Vector a -> ()
rnf = (a -> ()) -> Vector a -> ()
forall a. (a -> ()) -> Vector a -> ()
liftRnfV a -> ()
forall a. NFData a => a -> ()
rnf
  {-# INLINEABLE rnf #-}

#if MIN_VERSION_deepseq(1,4,3)
-- | @since 0.12.1.0
instance NFData1 Vector where
  liftRnf :: (a -> ()) -> Vector a -> ()
liftRnf = (a -> ()) -> Vector a -> ()
forall a. (a -> ()) -> Vector a -> ()
liftRnfV
  {-# INLINEABLE liftRnf #-}
#endif

instance Show a => Show (Vector a) where
  showsPrec :: Int -> Vector a -> ShowS
showsPrec = Int -> Vector a -> ShowS
forall (v :: * -> *) a. (Vector v a, Show a) => Int -> v a -> ShowS
G.showsPrec

instance Read a => Read (Vector a) where
  readPrec :: ReadPrec (Vector a)
readPrec = ReadPrec (Vector a)
forall (v :: * -> *) a. (Vector v a, Read a) => ReadPrec (v a)
G.readPrec
  readListPrec :: ReadPrec [Vector a]
readListPrec = ReadPrec [Vector a]
forall a. Read a => ReadPrec [a]
readListPrecDefault

#if MIN_VERSION_base(4,9,0)
instance Show1 Vector where
    liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Vector a -> ShowS
liftShowsPrec = (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Vector a -> ShowS
forall (v :: * -> *) a.
Vector v a =>
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> v a -> ShowS
G.liftShowsPrec

instance Read1 Vector where
    liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Vector a)
liftReadsPrec = (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Vector a)
forall (v :: * -> *) a.
Vector v a =>
(Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (v a)
G.liftReadsPrec
#endif

#if __GLASGOW_HASKELL__ >= 708

instance Exts.IsList (Vector a) where
  type Item (Vector a) = a
  fromList :: [Item (Vector a)] -> Vector a
fromList = [Item (Vector a)] -> Vector a
forall a. [a] -> Vector a
Data.Vector.fromList
  fromListN :: Int -> [Item (Vector a)] -> Vector a
fromListN = Int -> [Item (Vector a)] -> Vector a
forall a. Int -> [a] -> Vector a
Data.Vector.fromListN
  toList :: Vector a -> [Item (Vector a)]
toList = Vector a -> [Item (Vector a)]
forall a. Vector a -> [a]
toList
#endif

instance Data a => Data (Vector a) where
  gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Vector a -> c (Vector a)
gfoldl       = (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Vector a -> c (Vector a)
forall (v :: * -> *) a (c :: * -> *).
(Vector v a, Data a) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> v a -> c (v a)
G.gfoldl
  toConstr :: Vector a -> Constr
toConstr Vector a
_   = String -> Constr
G.mkVecConstr String
"Data.Vector.Vector"
  gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Vector a)
gunfold      = (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Vector a)
forall (v :: * -> *) a (c :: * -> *).
(Vector v a, Data a) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (v a)
G.gunfold
  dataTypeOf :: Vector a -> DataType
dataTypeOf Vector a
_ = String -> DataType
G.mkVecType String
"Data.Vector.Vector"
  dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (Vector a))
dataCast1    = (forall d. Data d => c (t d)) -> Maybe (c (Vector a))
forall (v :: * -> *) a (t :: * -> *) (c :: * -> *).
(Vector v a, Data a, Typeable v, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (v a))
G.dataCast

type instance G.Mutable Vector = MVector

instance G.Vector Vector a where
  {-# INLINE basicUnsafeFreeze #-}
  basicUnsafeFreeze :: Mutable Vector (PrimState m) a -> m (Vector a)
basicUnsafeFreeze (MVector i n marr)
    = Int -> Int -> Array a -> Vector a
forall a. Int -> Int -> Array a -> Vector a
Vector Int
i Int
n (Array a -> Vector a) -> m (Array a) -> m (Vector a)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` MutableArray (PrimState m) a -> m (Array a)
forall (m :: * -> *) a.
PrimMonad m =>
MutableArray (PrimState m) a -> m (Array a)
unsafeFreezeArray MutableArray (PrimState m) a
marr

  {-# INLINE basicUnsafeThaw #-}
  basicUnsafeThaw :: Vector a -> m (Mutable Vector (PrimState m) a)
basicUnsafeThaw (Vector Int
i Int
n Array a
arr)
    = Int
-> Int -> MutableArray (PrimState m) a -> MVector (PrimState m) a
forall s a. Int -> Int -> MutableArray s a -> MVector s a
MVector Int
i Int
n (MutableArray (PrimState m) a -> MVector (PrimState m) a)
-> m (MutableArray (PrimState m) a) -> m (MVector (PrimState m) a)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` Array a -> m (MutableArray (PrimState m) a)
forall (m :: * -> *) a.
PrimMonad m =>
Array a -> m (MutableArray (PrimState m) a)
unsafeThawArray Array a
arr

  {-# INLINE basicLength #-}
  basicLength :: Vector a -> Int
basicLength (Vector Int
_ Int
n Array a
_) = Int
n

  {-# INLINE basicUnsafeSlice #-}
  basicUnsafeSlice :: Int -> Int -> Vector a -> Vector a
basicUnsafeSlice Int
j Int
n (Vector Int
i Int
_ Array a
arr) = Int -> Int -> Array a -> Vector a
forall a. Int -> Int -> Array a -> Vector a
Vector (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
j) Int
n Array a
arr

  {-# INLINE basicUnsafeIndexM #-}
  basicUnsafeIndexM :: Vector a -> Int -> m a
basicUnsafeIndexM (Vector Int
i Int
_ Array a
arr) Int
j = Array a -> Int -> m a
forall (m :: * -> *) a. Monad m => Array a -> Int -> m a
indexArrayM Array a
arr (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
j)

  {-# INLINE basicUnsafeCopy #-}
  basicUnsafeCopy :: Mutable Vector (PrimState m) a -> Vector a -> m ()
basicUnsafeCopy (MVector i n dst) (Vector Int
j Int
_ Array a
src)
    = MutableArray (PrimState m) a
-> Int -> Array a -> Int -> Int -> m ()
forall (m :: * -> *) a.
PrimMonad m =>
MutableArray (PrimState m) a
-> Int -> Array a -> Int -> Int -> m ()
copyArray MutableArray (PrimState m) a
dst Int
i Array a
src Int
j Int
n

-- See http://trac.haskell.org/vector/ticket/12
instance Eq a => Eq (Vector a) where
  {-# INLINE (==) #-}
  Vector a
xs == :: Vector a -> Vector a -> Bool
== Vector a
ys = Bundle Vector a -> Bundle Vector a -> Bool
forall a (v :: * -> *). Eq a => Bundle v a -> Bundle v a -> Bool
Bundle.eq (Vector a -> Bundle Vector a
forall (v :: * -> *) a. Vector v a => v a -> Bundle v a
G.stream Vector a
xs) (Vector a -> Bundle Vector a
forall (v :: * -> *) a. Vector v a => v a -> Bundle v a
G.stream Vector a
ys)

  {-# INLINE (/=) #-}
  Vector a
xs /= :: Vector a -> Vector a -> Bool
/= Vector a
ys = Bool -> Bool
not (Bundle Vector a -> Bundle Vector a -> Bool
forall a (v :: * -> *). Eq a => Bundle v a -> Bundle v a -> Bool
Bundle.eq (Vector a -> Bundle Vector a
forall (v :: * -> *) a. Vector v a => v a -> Bundle v a
G.stream Vector a
xs) (Vector a -> Bundle Vector a
forall (v :: * -> *) a. Vector v a => v a -> Bundle v a
G.stream Vector a
ys))

-- See http://trac.haskell.org/vector/ticket/12
instance Ord a => Ord (Vector a) where
  {-# INLINE compare #-}
  compare :: Vector a -> Vector a -> Ordering
compare Vector a
xs Vector a
ys = Bundle Vector a -> Bundle Vector a -> Ordering
forall a (v :: * -> *).
Ord a =>
Bundle v a -> Bundle v a -> Ordering
Bundle.cmp (Vector a -> Bundle Vector a
forall (v :: * -> *) a. Vector v a => v a -> Bundle v a
G.stream Vector a
xs) (Vector a -> Bundle Vector a
forall (v :: * -> *) a. Vector v a => v a -> Bundle v a
G.stream Vector a
ys)

  {-# INLINE (<) #-}
  Vector a
xs < :: Vector a -> Vector a -> Bool
< Vector a
ys = Bundle Vector a -> Bundle Vector a -> Ordering
forall a (v :: * -> *).
Ord a =>
Bundle v a -> Bundle v a -> Ordering
Bundle.cmp (Vector a -> Bundle Vector a
forall (v :: * -> *) a. Vector v a => v a -> Bundle v a
G.stream Vector a
xs) (Vector a -> Bundle Vector a
forall (v :: * -> *) a. Vector v a => v a -> Bundle v a
G.stream Vector a
ys) Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Ordering
LT

  {-# INLINE (<=) #-}
  Vector a
xs <= :: Vector a -> Vector a -> Bool
<= Vector a
ys = Bundle Vector a -> Bundle Vector a -> Ordering
forall a (v :: * -> *).
Ord a =>
Bundle v a -> Bundle v a -> Ordering
Bundle.cmp (Vector a -> Bundle Vector a
forall (v :: * -> *) a. Vector v a => v a -> Bundle v a
G.stream Vector a
xs) (Vector a -> Bundle Vector a
forall (v :: * -> *) a. Vector v a => v a -> Bundle v a
G.stream Vector a
ys) Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
/= Ordering
GT

  {-# INLINE (>) #-}
  Vector a
xs > :: Vector a -> Vector a -> Bool
> Vector a
ys = Bundle Vector a -> Bundle Vector a -> Ordering
forall a (v :: * -> *).
Ord a =>
Bundle v a -> Bundle v a -> Ordering
Bundle.cmp (Vector a -> Bundle Vector a
forall (v :: * -> *) a. Vector v a => v a -> Bundle v a
G.stream Vector a
xs) (Vector a -> Bundle Vector a
forall (v :: * -> *) a. Vector v a => v a -> Bundle v a
G.stream Vector a
ys) Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Ordering
GT

  {-# INLINE (>=) #-}
  Vector a
xs >= :: Vector a -> Vector a -> Bool
>= Vector a
ys = Bundle Vector a -> Bundle Vector a -> Ordering
forall a (v :: * -> *).
Ord a =>
Bundle v a -> Bundle v a -> Ordering
Bundle.cmp (Vector a -> Bundle Vector a
forall (v :: * -> *) a. Vector v a => v a -> Bundle v a
G.stream Vector a
xs) (Vector a -> Bundle Vector a
forall (v :: * -> *) a. Vector v a => v a -> Bundle v a
G.stream Vector a
ys) Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
/= Ordering
LT

#if MIN_VERSION_base(4,9,0)
instance Eq1 Vector where
  liftEq :: (a -> b -> Bool) -> Vector a -> Vector b -> Bool
liftEq a -> b -> Bool
eq Vector a
xs Vector b
ys = (a -> b -> Bool) -> Bundle Vector a -> Bundle Vector b -> Bool
forall a b (v :: * -> *).
(a -> b -> Bool) -> Bundle v a -> Bundle v b -> Bool
Bundle.eqBy a -> b -> Bool
eq (Vector a -> Bundle Vector a
forall (v :: * -> *) a. Vector v a => v a -> Bundle v a
G.stream Vector a
xs) (Vector b -> Bundle Vector b
forall (v :: * -> *) a. Vector v a => v a -> Bundle v a
G.stream Vector b
ys)

instance Ord1 Vector where
  liftCompare :: (a -> b -> Ordering) -> Vector a -> Vector b -> Ordering
liftCompare a -> b -> Ordering
cmp Vector a
xs Vector b
ys = (a -> b -> Ordering)
-> Bundle Vector a -> Bundle Vector b -> Ordering
forall a b (v :: * -> *).
(a -> b -> Ordering) -> Bundle v a -> Bundle v b -> Ordering
Bundle.cmpBy a -> b -> Ordering
cmp (Vector a -> Bundle Vector a
forall (v :: * -> *) a. Vector v a => v a -> Bundle v a
G.stream Vector a
xs) (Vector b -> Bundle Vector b
forall (v :: * -> *) a. Vector v a => v a -> Bundle v a
G.stream Vector b
ys)
#endif

instance Semigroup (Vector a) where
  {-# INLINE (<>) #-}
  <> :: Vector a -> Vector a -> Vector a
(<>) = Vector a -> Vector a -> Vector a
forall a. Vector a -> Vector a -> Vector a
(++)

  {-# INLINE sconcat #-}
  sconcat :: NonEmpty (Vector a) -> Vector a
sconcat = NonEmpty (Vector a) -> Vector a
forall (v :: * -> *) a. Vector v a => NonEmpty (v a) -> v a
G.concatNE

instance Monoid (Vector a) where
  {-# INLINE mempty #-}
  mempty :: Vector a
mempty = Vector a
forall a. Vector a
empty

  {-# INLINE mappend #-}
  mappend :: Vector a -> Vector a -> Vector a
mappend = Vector a -> Vector a -> Vector a
forall a. Vector a -> Vector a -> Vector a
(++)

  {-# INLINE mconcat #-}
  mconcat :: [Vector a] -> Vector a
mconcat = [Vector a] -> Vector a
forall a. [Vector a] -> Vector a
concat

instance Functor Vector where
  {-# INLINE fmap #-}
  fmap :: (a -> b) -> Vector a -> Vector b
fmap = (a -> b) -> Vector a -> Vector b
forall a b. (a -> b) -> Vector a -> Vector b
map

#if MIN_VERSION_base(4,8,0)
  {-# INLINE (<$) #-}
  <$ :: a -> Vector b -> Vector a
(<$) = (b -> a) -> Vector b -> Vector a
forall a b. (a -> b) -> Vector a -> Vector b
map ((b -> a) -> Vector b -> Vector a)
-> (a -> b -> a) -> a -> Vector b -> Vector a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> b -> a
forall a b. a -> b -> a
const
#endif

instance Monad Vector where
  {-# INLINE return #-}
  return :: a -> Vector a
return = a -> Vector a
forall (f :: * -> *) a. Applicative f => a -> f a
Applicative.pure

  {-# INLINE (>>=) #-}
  >>= :: Vector a -> (a -> Vector b) -> Vector b
(>>=) = ((a -> Vector b) -> Vector a -> Vector b)
-> Vector a -> (a -> Vector b) -> Vector b
forall a b c. (a -> b -> c) -> b -> a -> c
flip (a -> Vector b) -> Vector a -> Vector b
forall a b. (a -> Vector b) -> Vector a -> Vector b
concatMap

#if !(MIN_VERSION_base(4,13,0))
  {-# INLINE fail #-}
  fail = Fail.fail -- == \ _str -> empty
#endif

-- | @since 0.12.1.0
instance Fail.MonadFail Vector where
  {-# INLINE fail #-}
  fail :: String -> Vector a
fail String
_ = Vector a
forall a. Vector a
empty

instance MonadPlus Vector where
  {-# INLINE mzero #-}
  mzero :: Vector a
mzero = Vector a
forall a. Vector a
empty

  {-# INLINE mplus #-}
  mplus :: Vector a -> Vector a -> Vector a
mplus = Vector a -> Vector a -> Vector a
forall a. Vector a -> Vector a -> Vector a
(++)

instance MonadZip Vector where
  {-# INLINE mzip #-}
  mzip :: Vector a -> Vector b -> Vector (a, b)
mzip = Vector a -> Vector b -> Vector (a, b)
forall a b. Vector a -> Vector b -> Vector (a, b)
zip

  {-# INLINE mzipWith #-}
  mzipWith :: (a -> b -> c) -> Vector a -> Vector b -> Vector c
mzipWith = (a -> b -> c) -> Vector a -> Vector b -> Vector c
forall a b c. (a -> b -> c) -> Vector a -> Vector b -> Vector c
zipWith

  {-# INLINE munzip #-}
  munzip :: Vector (a, b) -> (Vector a, Vector b)
munzip = Vector (a, b) -> (Vector a, Vector b)
forall a b. Vector (a, b) -> (Vector a, Vector b)
unzip

-- | Instance has same semantics as one for lists
--
--  @since 0.12.2.0
instance MonadFix Vector where
  -- We take care to dispose of v0 as soon as possible (see headM docs).
  --
  -- It's perfectly safe to use non-monadic indexing within generate
  -- call since intermediate vector won't be created until result's
  -- value is demanded.
  {-# INLINE mfix #-}
  mfix :: (a -> Vector a) -> Vector a
mfix a -> Vector a
f
    | Vector a -> Bool
forall a. Vector a -> Bool
null Vector a
v0 = Vector a
forall a. Vector a
empty
    -- We take first element of resulting vector from v0 and create
    -- rest using generate. Note that cons should fuse with generate
    | Bool
otherwise = (forall s. ST s (Vector a)) -> Vector a
forall a. (forall s. ST s a) -> a
runST ((forall s. ST s (Vector a)) -> Vector a)
-> (forall s. ST s (Vector a)) -> Vector a
forall a b. (a -> b) -> a -> b
$ do
        a
h <- Vector a -> ST s a
forall (m :: * -> *) a. Monad m => Vector a -> m a
headM Vector a
v0
        Vector a -> ST s (Vector a)
forall (m :: * -> *) a. Monad m => a -> m a
return (Vector a -> ST s (Vector a)) -> Vector a -> ST s (Vector a)
forall a b. (a -> b) -> a -> b
$ a -> Vector a -> Vector a
forall a. a -> Vector a -> Vector a
cons a
h (Vector a -> Vector a) -> Vector a -> Vector a
forall a b. (a -> b) -> a -> b
$
          Int -> (Int -> a) -> Vector a
forall a. Int -> (Int -> a) -> Vector a
generate (Int
lv0 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) ((Int -> a) -> Vector a) -> (Int -> a) -> Vector a
forall a b. (a -> b) -> a -> b
$
            \Int
i -> (a -> a) -> a
forall a. (a -> a) -> a
fix (\a
a -> a -> Vector a
f a
a Vector a -> Int -> a
forall a. Vector a -> Int -> a
! (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1))
    where
      -- Used to calculate size of resulting vector
      v0 :: Vector a
v0 = (Vector a -> Vector a) -> Vector a
forall a. (a -> a) -> a
fix (a -> Vector a
f (a -> Vector a) -> (Vector a -> a) -> Vector a -> Vector a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector a -> a
forall a. Vector a -> a
head)
      !lv0 :: Int
lv0 = Vector a -> Int
forall a. Vector a -> Int
length Vector a
v0

instance Applicative.Applicative Vector where
  {-# INLINE pure #-}
  pure :: a -> Vector a
pure = a -> Vector a
forall a. a -> Vector a
singleton

  {-# INLINE (<*>) #-}
  <*> :: Vector (a -> b) -> Vector a -> Vector b
(<*>) = Vector (a -> b) -> Vector a -> Vector b
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
ap

instance Applicative.Alternative Vector where
  {-# INLINE empty #-}
  empty :: Vector a
empty = Vector a
forall a. Vector a
empty

  {-# INLINE (<|>) #-}
  <|> :: Vector a -> Vector a -> Vector a
(<|>) = Vector a -> Vector a -> Vector a
forall a. Vector a -> Vector a -> Vector a
(++)

instance Foldable.Foldable Vector where
  {-# INLINE foldr #-}
  foldr :: (a -> b -> b) -> b -> Vector a -> b
foldr = (a -> b -> b) -> b -> Vector a -> b
forall a b. (a -> b -> b) -> b -> Vector a -> b
foldr

  {-# INLINE foldl #-}
  foldl :: (b -> a -> b) -> b -> Vector a -> b
foldl = (b -> a -> b) -> b -> Vector a -> b
forall a b. (a -> b -> a) -> a -> Vector b -> a
foldl

  {-# INLINE foldr1 #-}
  foldr1 :: (a -> a -> a) -> Vector a -> a
foldr1 = (a -> a -> a) -> Vector a -> a
forall a. (a -> a -> a) -> Vector a -> a
foldr1

  {-# INLINE foldl1 #-}
  foldl1 :: (a -> a -> a) -> Vector a -> a
foldl1 = (a -> a -> a) -> Vector a -> a
forall a. (a -> a -> a) -> Vector a -> a
foldl1

#if MIN_VERSION_base(4,6,0)
  {-# INLINE foldr' #-}
  foldr' :: (a -> b -> b) -> b -> Vector a -> b
foldr' = (a -> b -> b) -> b -> Vector a -> b
forall a b. (a -> b -> b) -> b -> Vector a -> b
foldr'

  {-# INLINE foldl' #-}
  foldl' :: (b -> a -> b) -> b -> Vector a -> b
foldl' = (b -> a -> b) -> b -> Vector a -> b
forall a b. (a -> b -> a) -> a -> Vector b -> a
foldl'
#endif

#if MIN_VERSION_base(4,8,0)
  {-# INLINE toList #-}
  toList :: Vector a -> [a]
toList = Vector a -> [a]
forall a. Vector a -> [a]
toList

  {-# INLINE length #-}
  length :: Vector a -> Int
length = Vector a -> Int
forall a. Vector a -> Int
length

  {-# INLINE null #-}
  null :: Vector a -> Bool
null = Vector a -> Bool
forall a. Vector a -> Bool
null

  {-# INLINE elem #-}
  elem :: a -> Vector a -> Bool
elem = a -> Vector a -> Bool
forall a. Eq a => a -> Vector a -> Bool
elem

  {-# INLINE maximum #-}
  maximum :: Vector a -> a
maximum = Vector a -> a
forall a. Ord a => Vector a -> a
maximum

  {-# INLINE minimum #-}
  minimum :: Vector a -> a
minimum = Vector a -> a
forall a. Ord a => Vector a -> a
minimum

  {-# INLINE sum #-}
  sum :: Vector a -> a
sum = Vector a -> a
forall a. Num a => Vector a -> a
sum

  {-# INLINE product #-}
  product :: Vector a -> a
product = Vector a -> a
forall a. Num a => Vector a -> a
product
#endif

instance Traversable.Traversable Vector where
  {-# INLINE traverse #-}
  traverse :: (a -> f b) -> Vector a -> f (Vector b)
traverse a -> f b
f Vector a
xs =
      -- Get the length of the vector in /O(1)/ time
      let !n :: Int
n = Vector a -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
G.length Vector a
xs
      -- Use fromListN to be more efficient in construction of resulting vector
      -- Also behaves better with compact regions, preventing runtime exceptions
      in  Int -> [b] -> Vector b
forall a. Int -> [a] -> Vector a
Data.Vector.fromListN Int
n ([b] -> Vector b) -> f [b] -> f (Vector b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Applicative.<$> (a -> f b) -> [a] -> f [b]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
Traversable.traverse a -> f b
f (Vector a -> [a]
forall a. Vector a -> [a]
toList Vector a
xs)

  {-# INLINE mapM #-}
  mapM :: (a -> m b) -> Vector a -> m (Vector b)
mapM = (a -> m b) -> Vector a -> m (Vector b)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Vector a -> m (Vector b)
mapM

  {-# INLINE sequence #-}
  sequence :: Vector (m a) -> m (Vector a)
sequence = Vector (m a) -> m (Vector a)
forall (m :: * -> *) a. Monad m => Vector (m a) -> m (Vector a)
sequence

-- Length information
-- ------------------

-- | /O(1)/ Yield the length of the vector
length :: Vector a -> Int
{-# INLINE length #-}
length :: Vector a -> Int
length = Vector a -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
G.length

-- | /O(1)/ Test whether a vector is empty
null :: Vector a -> Bool
{-# INLINE null #-}
null :: Vector a -> Bool
null = Vector a -> Bool
forall (v :: * -> *) a. Vector v a => v a -> Bool
G.null

-- Indexing
-- --------

-- | O(1) Indexing
(!) :: Vector a -> Int -> a
{-# INLINE (!) #-}
(!) = Vector a -> Int -> a
forall (v :: * -> *) a. Vector v a => v a -> Int -> a
(G.!)

-- | O(1) Safe indexing
(!?) :: Vector a -> Int -> Maybe a
{-# INLINE (!?) #-}
!? :: Vector a -> Int -> Maybe a
(!?) = Vector a -> Int -> Maybe a
forall (v :: * -> *) a. Vector v a => v a -> Int -> Maybe a
(G.!?)

-- | /O(1)/ First element
head :: Vector a -> a
{-# INLINE head #-}
head :: Vector a -> a
head = Vector a -> a
forall (v :: * -> *) a. Vector v a => v a -> a
G.head

-- | /O(1)/ Last element
last :: Vector a -> a
{-# INLINE last #-}
last :: Vector a -> a
last = Vector a -> a
forall (v :: * -> *) a. Vector v a => v a -> a
G.last

-- | /O(1)/ Unsafe indexing without bounds checking
unsafeIndex :: Vector a -> Int -> a
{-# INLINE unsafeIndex #-}
unsafeIndex :: Vector a -> Int -> a
unsafeIndex = Vector a -> Int -> a
forall (v :: * -> *) a. Vector v a => v a -> Int -> a
G.unsafeIndex

-- | /O(1)/ First element without checking if the vector is empty
unsafeHead :: Vector a -> a
{-# INLINE unsafeHead #-}
unsafeHead :: Vector a -> a
unsafeHead = Vector a -> a
forall (v :: * -> *) a. Vector v a => v a -> a
G.unsafeHead

-- | /O(1)/ Last element without checking if the vector is empty
unsafeLast :: Vector a -> a
{-# INLINE unsafeLast #-}
unsafeLast :: Vector a -> a
unsafeLast = Vector a -> a
forall (v :: * -> *) a. Vector v a => v a -> a
G.unsafeLast

-- Monadic indexing
-- ----------------

-- | /O(1)/ Indexing in a monad.
--
-- The monad allows operations to be strict in the vector when necessary.
-- Suppose vector copying is implemented like this:
--
-- > copy mv v = ... write mv i (v ! i) ...
--
-- For lazy vectors, @v ! i@ would not be evaluated which means that @mv@
-- would unnecessarily retain a reference to @v@ in each element written.
--
-- With 'indexM', copying can be implemented like this instead:
--
-- > copy mv v = ... do
-- >                   x <- indexM v i
-- >                   write mv i x
--
-- Here, no references to @v@ are retained because indexing (but /not/ the
-- elements) is evaluated eagerly.
--
indexM :: Monad m => Vector a -> Int -> m a
{-# INLINE indexM #-}
indexM :: Vector a -> Int -> m a
indexM = Vector a -> Int -> m a
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, Monad m) =>
v a -> Int -> m a
G.indexM

-- | /O(1)/ First element of a vector in a monad. See 'indexM' for an
-- explanation of why this is useful.
headM :: Monad m => Vector a -> m a
{-# INLINE headM #-}
headM :: Vector a -> m a
headM = Vector a -> m a
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, Monad m) =>
v a -> m a
G.headM

-- | /O(1)/ Last element of a vector in a monad. See 'indexM' for an
-- explanation of why this is useful.
lastM :: Monad m => Vector a -> m a
{-# INLINE lastM #-}
lastM :: Vector a -> m a
lastM = Vector a -> m a
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, Monad m) =>
v a -> m a
G.lastM

-- | /O(1)/ Indexing in a monad without bounds checks. See 'indexM' for an
-- explanation of why this is useful.
unsafeIndexM :: Monad m => Vector a -> Int -> m a
{-# INLINE unsafeIndexM #-}
unsafeIndexM :: Vector a -> Int -> m a
unsafeIndexM = Vector a -> Int -> m a
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, Monad m) =>
v a -> Int -> m a
G.unsafeIndexM

-- | /O(1)/ First element in a monad without checking for empty vectors.
-- See 'indexM' for an explanation of why this is useful.
unsafeHeadM :: Monad m => Vector a -> m a
{-# INLINE unsafeHeadM #-}
unsafeHeadM :: Vector a -> m a
unsafeHeadM = Vector a -> m a
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, Monad m) =>
v a -> m a
G.unsafeHeadM

-- | /O(1)/ Last element in a monad without checking for empty vectors.
-- See 'indexM' for an explanation of why this is useful.
unsafeLastM :: Monad m => Vector a -> m a
{-# INLINE unsafeLastM #-}
unsafeLastM :: Vector a -> m a
unsafeLastM = Vector a -> m a
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, Monad m) =>
v a -> m a
G.unsafeLastM

-- Extracting subvectors (slicing)
-- -------------------------------

-- | /O(1)/ Yield a slice of the vector without copying it. The vector must
-- contain at least @i+n@ elements.
slice :: Int   -- ^ @i@ starting index
                 -> Int   -- ^ @n@ length
                 -> Vector a
                 -> Vector a
{-# INLINE slice #-}
slice :: Int -> Int -> Vector a -> Vector a
slice = Int -> Int -> Vector a -> Vector a
forall (v :: * -> *) a. Vector v a => Int -> Int -> v a -> v a
G.slice

-- | /O(1)/ Yield all but the last element without copying. The vector may not
-- be empty.
init :: Vector a -> Vector a
{-# INLINE init #-}
init :: Vector a -> Vector a
init = Vector a -> Vector a
forall (v :: * -> *) a. Vector v a => v a -> v a
G.init

-- | /O(1)/ Yield all but the first element without copying. The vector may not
-- be empty.
tail :: Vector a -> Vector a
{-# INLINE tail #-}
tail :: Vector a -> Vector a
tail = Vector a -> Vector a
forall (v :: * -> *) a. Vector v a => v a -> v a
G.tail

-- | /O(1)/ Yield at the first @n@ elements without copying. The vector may
-- contain less than @n@ elements in which case it is returned unchanged.
take :: Int -> Vector a -> Vector a
{-# INLINE take #-}
take :: Int -> Vector a -> Vector a
take = Int -> Vector a -> Vector a
forall (v :: * -> *) a. Vector v a => Int -> v a -> v a
G.take

-- | /O(1)/ Yield all but the first @n@ elements without copying. The vector may
-- contain less than @n@ elements in which case an empty vector is returned.
drop :: Int -> Vector a -> Vector a
{-# INLINE drop #-}
drop :: Int -> Vector a -> Vector a
drop = Int -> Vector a -> Vector a
forall (v :: * -> *) a. Vector v a => Int -> v a -> v a
G.drop

-- | /O(1)/ Yield the first @n@ elements paired with the remainder without copying.
--
-- Note that @'splitAt' n v@ is equivalent to @('take' n v, 'drop' n v)@
-- but slightly more efficient.
--
-- @since 0.7.1
splitAt :: Int -> Vector a -> (Vector a, Vector a)
{-# INLINE splitAt #-}
splitAt :: Int -> Vector a -> (Vector a, Vector a)
splitAt = Int -> Vector a -> (Vector a, Vector a)
forall (v :: * -> *) a. Vector v a => Int -> v a -> (v a, v a)
G.splitAt

-- | /O(1)/ Yield the 'head' and 'tail' of the vector, or 'Nothing' if empty.
--
-- @since 0.12.2.0
uncons :: Vector a -> Maybe (a, Vector a)
{-# INLINE uncons #-}
uncons :: Vector a -> Maybe (a, Vector a)
uncons = Vector a -> Maybe (a, Vector a)
forall (v :: * -> *) a. Vector v a => v a -> Maybe (a, v a)
G.uncons

-- | /O(1)/ Yield the 'last' and 'init' of the vector, or 'Nothing' if empty.
--
-- @since 0.12.2.0
unsnoc :: Vector a -> Maybe (Vector a, a)
{-# INLINE unsnoc #-}
unsnoc :: Vector a -> Maybe (Vector a, a)
unsnoc = Vector a -> Maybe (Vector a, a)
forall (v :: * -> *) a. Vector v a => v a -> Maybe (v a, a)
G.unsnoc

-- | /O(1)/ Yield a slice of the vector without copying. The vector must
-- contain at least @i+n@ elements but this is not checked.
unsafeSlice :: Int   -- ^ @i@ starting index
                       -> Int   -- ^ @n@ length
                       -> Vector a
                       -> Vector a
{-# INLINE unsafeSlice #-}
unsafeSlice :: Int -> Int -> Vector a -> Vector a
unsafeSlice = Int -> Int -> Vector a -> Vector a
forall (v :: * -> *) a. Vector v a => Int -> Int -> v a -> v a
G.unsafeSlice

-- | /O(1)/ Yield all but the last element without copying. The vector may not
-- be empty but this is not checked.
unsafeInit :: Vector a -> Vector a
{-# INLINE unsafeInit #-}
unsafeInit :: Vector a -> Vector a
unsafeInit = Vector a -> Vector a
forall (v :: * -> *) a. Vector v a => v a -> v a
G.unsafeInit

-- | /O(1)/ Yield all but the first element without copying. The vector may not
-- be empty but this is not checked.
unsafeTail :: Vector a -> Vector a
{-# INLINE unsafeTail #-}
unsafeTail :: Vector a -> Vector a
unsafeTail = Vector a -> Vector a
forall (v :: * -> *) a. Vector v a => v a -> v a
G.unsafeTail

-- | /O(1)/ Yield the first @n@ elements without copying. The vector must
-- contain at least @n@ elements but this is not checked.
unsafeTake :: Int -> Vector a -> Vector a
{-# INLINE unsafeTake #-}
unsafeTake :: Int -> Vector a -> Vector a
unsafeTake = Int -> Vector a -> Vector a
forall (v :: * -> *) a. Vector v a => Int -> v a -> v a
G.unsafeTake

-- | /O(1)/ Yield all but the first @n@ elements without copying. The vector
-- must contain at least @n@ elements but this is not checked.
unsafeDrop :: Int -> Vector a -> Vector a
{-# INLINE unsafeDrop #-}
unsafeDrop :: Int -> Vector a -> Vector a
unsafeDrop = Int -> Vector a -> Vector a
forall (v :: * -> *) a. Vector v a => Int -> v a -> v a
G.unsafeDrop

-- Initialisation
-- --------------

-- | /O(1)/ Empty vector
empty :: Vector a
{-# INLINE empty #-}
empty :: Vector a
empty = Vector a
forall (v :: * -> *) a. Vector v a => v a
G.empty

-- | /O(1)/ Vector with exactly one element
singleton :: a -> Vector a
{-# INLINE singleton #-}
singleton :: a -> Vector a
singleton = a -> Vector a
forall (v :: * -> *) a. Vector v a => a -> v a
G.singleton

-- | /O(n)/ Vector of the given length with the same value in each position
replicate :: Int -> a -> Vector a
{-# INLINE replicate #-}
replicate :: Int -> a -> Vector a
replicate = Int -> a -> Vector a
forall (v :: * -> *) a. Vector v a => Int -> a -> v a
G.replicate

-- | /O(n)/ Construct a vector of the given length by applying the function to
-- each index
generate :: Int -> (Int -> a) -> Vector a
{-# INLINE generate #-}
generate :: Int -> (Int -> a) -> Vector a
generate = Int -> (Int -> a) -> Vector a
forall (v :: * -> *) a. Vector v a => Int -> (Int -> a) -> v a
G.generate

-- | /O(n)/ Apply function \(\max(n - 1, 0)\) times to an initial value, producing a vector
-- of length \(\max(n, 0)\). Zeroth element will contain the initial value, that's why there
-- is one less function application than the number of elements in the produced vector.
--
-- \( \underbrace{x, f (x), f (f (x)), \ldots}_{\max(0,n)\rm{~elements}} \)
--
-- ===__Examples__
--
-- >>> import qualified Data.Vector as V
-- >>> V.iterateN 0 undefined undefined :: V.Vector String
-- []
-- >>> V.iterateN 4 (\x -> x <> x) "Hi"
-- ["Hi","HiHi","HiHiHiHi","HiHiHiHiHiHiHiHi"]
--
-- @since 0.7.1
iterateN :: Int -> (a -> a) -> a -> Vector a
{-# INLINE iterateN #-}
iterateN :: Int -> (a -> a) -> a -> Vector a
iterateN = Int -> (a -> a) -> a -> Vector a
forall (v :: * -> *) a. Vector v a => Int -> (a -> a) -> a -> v a
G.iterateN

-- Unfolding
-- ---------

-- | /O(n)/ Construct a vector by repeatedly applying the generator function
-- to a seed. The generator function yields 'Just' the next element and the
-- new seed or 'Nothing' if there are no more elements.
--
-- > unfoldr (\n -> if n == 0 then Nothing else Just (n,n-1)) 10
-- >  = <10,9,8,7,6,5,4,3,2,1>
unfoldr :: (b -> Maybe (a, b)) -> b -> Vector a
{-# INLINE unfoldr #-}
unfoldr :: (b -> Maybe (a, b)) -> b -> Vector a
unfoldr = (b -> Maybe (a, b)) -> b -> Vector a
forall (v :: * -> *) a b.
Vector v a =>
(b -> Maybe (a, b)) -> b -> v a
G.unfoldr

-- | /O(n)/ Construct a vector with at most @n@ elements by repeatedly applying
-- the generator function to a seed. The generator function yields 'Just' the
-- next element and the new seed or 'Nothing' if there are no more elements.
--
-- > unfoldrN 3 (\n -> Just (n,n-1)) 10 = <10,9,8>
unfoldrN :: Int -> (b -> Maybe (a, b)) -> b -> Vector a
{-# INLINE unfoldrN #-}
unfoldrN :: Int -> (b -> Maybe (a, b)) -> b -> Vector a
unfoldrN = Int -> (b -> Maybe (a, b)) -> b -> Vector a
forall (v :: * -> *) a b.
Vector v a =>
Int -> (b -> Maybe (a, b)) -> b -> v a
G.unfoldrN

-- | /O(n)/ Construct a vector with exactly @n@ elements by repeatedly applying
-- the generator function to a seed. The generator function yields the
-- next element and the new seed.
--
-- > unfoldrExactN 3 (\n -> (n,n-1)) 10 = <10,9,8>
--
-- @since 0.12.2.0
unfoldrExactN  :: Int -> (b -> (a, b)) -> b -> Vector a
{-# INLINE unfoldrExactN #-}
unfoldrExactN :: Int -> (b -> (a, b)) -> b -> Vector a
unfoldrExactN = Int -> (b -> (a, b)) -> b -> Vector a
forall (v :: * -> *) a b.
Vector v a =>
Int -> (b -> (a, b)) -> b -> v a
G.unfoldrExactN

-- | /O(n)/ Construct a vector by repeatedly applying the monadic
-- generator function to a seed. The generator function yields 'Just'
-- the next element and the new seed or 'Nothing' if there are no more
-- elements.
unfoldrM :: (Monad m) => (b -> m (Maybe (a, b))) -> b -> m (Vector a)
{-# INLINE unfoldrM #-}
unfoldrM :: (b -> m (Maybe (a, b))) -> b -> m (Vector a)
unfoldrM = (b -> m (Maybe (a, b))) -> b -> m (Vector a)
forall (m :: * -> *) (v :: * -> *) a b.
(Monad m, Vector v a) =>
(b -> m (Maybe (a, b))) -> b -> m (v a)
G.unfoldrM

-- | /O(n)/ Construct a vector by repeatedly applying the monadic
-- generator function to a seed. The generator function yields 'Just'
-- the next element and the new seed or 'Nothing' if there are no more
-- elements.
unfoldrNM :: (Monad m) => Int -> (b -> m (Maybe (a, b))) -> b -> m (Vector a)
{-# INLINE unfoldrNM #-}
unfoldrNM :: Int -> (b -> m (Maybe (a, b))) -> b -> m (Vector a)
unfoldrNM = Int -> (b -> m (Maybe (a, b))) -> b -> m (Vector a)
forall (m :: * -> *) (v :: * -> *) a b.
(Monad m, Vector v a) =>
Int -> (b -> m (Maybe (a, b))) -> b -> m (v a)
G.unfoldrNM

-- | /O(n)/ Construct a vector with exactly @n@ elements by repeatedly
-- applying the monadic generator function to a seed. The generator
-- function yields the next element and the new seed.
--
-- @since 0.12.2.0
unfoldrExactNM :: (Monad m) => Int -> (b -> m (a, b)) -> b -> m (Vector a)
{-# INLINE unfoldrExactNM #-}
unfoldrExactNM :: Int -> (b -> m (a, b)) -> b -> m (Vector a)
unfoldrExactNM = Int -> (b -> m (a, b)) -> b -> m (Vector a)
forall (m :: * -> *) (v :: * -> *) a b.
(Monad m, Vector v a) =>
Int -> (b -> m (a, b)) -> b -> m (v a)
G.unfoldrExactNM

-- | /O(n)/ Construct a vector with @n@ elements by repeatedly applying the
-- generator function to the already constructed part of the vector.
--
-- > constructN 3 f = let a = f <> ; b = f <a> ; c = f <a,b> in <a,b,c>
--
constructN :: Int -> (Vector a -> a) -> Vector a
{-# INLINE constructN #-}
constructN :: Int -> (Vector a -> a) -> Vector a
constructN = Int -> (Vector a -> a) -> Vector a
forall (v :: * -> *) a. Vector v a => Int -> (v a -> a) -> v a
G.constructN

-- | /O(n)/ Construct a vector with @n@ elements from right to left by
-- repeatedly applying the generator function to the already constructed part
-- of the vector.
--
-- > constructrN 3 f = let a = f <> ; b = f<a> ; c = f <b,a> in <c,b,a>
--
constructrN :: Int -> (Vector a -> a) -> Vector a
{-# INLINE constructrN #-}
constructrN :: Int -> (Vector a -> a) -> Vector a
constructrN = Int -> (Vector a -> a) -> Vector a
forall (v :: * -> *) a. Vector v a => Int -> (v a -> a) -> v a
G.constructrN

-- Enumeration
-- -----------

-- | /O(n)/ Yield a vector of the given length containing the values @x@, @x+1@
-- etc. This operation is usually more efficient than 'enumFromTo'.
--
-- > enumFromN 5 3 = <5,6,7>
enumFromN :: Num a => a -> Int -> Vector a
{-# INLINE enumFromN #-}
enumFromN :: a -> Int -> Vector a
enumFromN = a -> Int -> Vector a
forall (v :: * -> *) a. (Vector v a, Num a) => a -> Int -> v a
G.enumFromN

-- | /O(n)/ Yield a vector of the given length containing the values @x@, @x+y@,
-- @x+y+y@ etc. This operations is usually more efficient than 'enumFromThenTo'.
--
-- > enumFromStepN 1 0.1 5 = <1,1.1,1.2,1.3,1.4>
enumFromStepN :: Num a => a -> a -> Int -> Vector a
{-# INLINE enumFromStepN #-}
enumFromStepN :: a -> a -> Int -> Vector a
enumFromStepN = a -> a -> Int -> Vector a
forall (v :: * -> *) a. (Vector v a, Num a) => a -> a -> Int -> v a
G.enumFromStepN

-- | /O(n)/ Enumerate values from @x@ to @y@.
--
-- /WARNING:/ This operation can be very inefficient. If at all possible, use
-- 'enumFromN' instead.
enumFromTo :: Enum a => a -> a -> Vector a
{-# INLINE enumFromTo #-}
enumFromTo :: a -> a -> Vector a
enumFromTo = a -> a -> Vector a
forall (v :: * -> *) a. (Vector v a, Enum a) => a -> a -> v a
G.enumFromTo

-- | /O(n)/ Enumerate values from @x@ to @y@ with a specific step @z@.
--
-- /WARNING:/ This operation can be very inefficient. If at all possible, use
-- 'enumFromStepN' instead.
enumFromThenTo :: Enum a => a -> a -> a -> Vector a
{-# INLINE enumFromThenTo #-}
enumFromThenTo :: a -> a -> a -> Vector a
enumFromThenTo = a -> a -> a -> Vector a
forall (v :: * -> *) a. (Vector v a, Enum a) => a -> a -> a -> v a
G.enumFromThenTo

-- Concatenation
-- -------------

-- | /O(n)/ Prepend an element
cons :: a -> Vector a -> Vector a
{-# INLINE cons #-}
cons :: a -> Vector a -> Vector a
cons = a -> Vector a -> Vector a
forall (v :: * -> *) a. Vector v a => a -> v a -> v a
G.cons

-- | /O(n)/ Append an element
snoc :: Vector a -> a -> Vector a
{-# INLINE snoc #-}
snoc :: Vector a -> a -> Vector a
snoc = Vector a -> a -> Vector a
forall (v :: * -> *) a. Vector v a => v a -> a -> v a
G.snoc

infixr 5 ++
-- | /O(m+n)/ Concatenate two vectors
(++) :: Vector a -> Vector a -> Vector a
{-# INLINE (++) #-}
++ :: Vector a -> Vector a -> Vector a
(++) = Vector a -> Vector a -> Vector a
forall (v :: * -> *) a. Vector v a => v a -> v a -> v a
(G.++)

-- | /O(n)/ Concatenate all vectors in the list
concat :: [Vector a] -> Vector a
{-# INLINE concat #-}
concat :: [Vector a] -> Vector a
concat = [Vector a] -> Vector a
forall (v :: * -> *) a. Vector v a => [v a] -> v a
G.concat

-- Monadic initialisation
-- ----------------------

-- | /O(n)/ Execute the monadic action the given number of times and store the
-- results in a vector.
replicateM :: Monad m => Int -> m a -> m (Vector a)
{-# INLINE replicateM #-}
replicateM :: Int -> m a -> m (Vector a)
replicateM = Int -> m a -> m (Vector a)
forall (m :: * -> *) (v :: * -> *) a.
(Monad m, Vector v a) =>
Int -> m a -> m (v a)
G.replicateM

-- | /O(n)/ Construct a vector of the given length by applying the monadic
-- action to each index
generateM :: Monad m => Int -> (Int -> m a) -> m (Vector a)
{-# INLINE generateM #-}
generateM :: Int -> (Int -> m a) -> m (Vector a)
generateM = Int -> (Int -> m a) -> m (Vector a)
forall (m :: * -> *) (v :: * -> *) a.
(Monad m, Vector v a) =>
Int -> (Int -> m a) -> m (v a)
G.generateM

-- | /O(n)/ Apply monadic function \(\max(n - 1, 0)\) times to an initial value, producing a vector
-- of length \(\max(n, 0)\). Zeroth element will contain the initial value, that's why there
-- is one less function application than the number of elements in the produced vector.
--
-- For non-monadic version see `iterateN`
--
-- @since 0.12.0.0
iterateNM :: Monad m => Int -> (a -> m a) -> a -> m (Vector a)
{-# INLINE iterateNM #-}
iterateNM :: Int -> (a -> m a) -> a -> m (Vector a)
iterateNM = Int -> (a -> m a) -> a -> m (Vector a)
forall (m :: * -> *) (v :: * -> *) a.
(Monad m, Vector v a) =>
Int -> (a -> m a) -> a -> m (v a)
G.iterateNM

-- | Execute the monadic action and freeze the resulting vector.
--
-- @
-- create (do { v \<- new 2; write v 0 \'a\'; write v 1 \'b\'; return v }) = \<'a','b'\>
-- @
create :: (forall s. ST s (MVector s a)) -> Vector a
{-# INLINE create #-}
-- NOTE: eta-expanded due to http://hackage.haskell.org/trac/ghc/ticket/4120
create :: (forall s. ST s (MVector s a)) -> Vector a
create forall s. ST s (MVector s a)
p = (forall s. ST s (Mutable Vector s a)) -> Vector a
forall (v :: * -> *) a.
Vector v a =>
(forall s. ST s (Mutable v s a)) -> v a
G.create forall s. ST s (Mutable Vector s a)
forall s. ST s (MVector s a)
p

-- | Execute the monadic action and freeze the resulting vectors.
createT :: Traversable.Traversable f => (forall s. ST s (f (MVector s a))) -> f (Vector a)
{-# INLINE createT #-}
createT :: (forall s. ST s (f (MVector s a))) -> f (Vector a)
createT forall s. ST s (f (MVector s a))
p = (forall s. ST s (f (Mutable Vector s a))) -> f (Vector a)
forall (f :: * -> *) (v :: * -> *) a.
(Traversable f, Vector v a) =>
(forall s. ST s (f (Mutable v s a))) -> f (v a)
G.createT forall s. ST s (f (Mutable Vector s a))
forall s. ST s (f (MVector s a))
p



-- Restricting memory usage
-- ------------------------

-- | /O(n)/ Yield the argument but force it not to retain any extra memory,
-- possibly by copying it.
--
-- This is especially useful when dealing with slices. For example:
--
-- > force (slice 0 2 <huge vector>)
--
-- Here, the slice retains a reference to the huge vector. Forcing it creates
-- a copy of just the elements that belong to the slice and allows the huge
-- vector to be garbage collected.
force :: Vector a -> Vector a
{-# INLINE force #-}
force :: Vector a -> Vector a
force = Vector a -> Vector a
forall (v :: * -> *) a. Vector v a => v a -> v a
G.force

-- Bulk updates
-- ------------

-- | /O(m+n)/ For each pair @(i,a)@ from the list, replace the vector
-- element at position @i@ by @a@.
--
-- > <5,9,2,7> // [(2,1),(0,3),(2,8)] = <3,9,8,7>
--
(//) :: Vector a   -- ^ initial vector (of length @m@)
                -> [(Int, a)] -- ^ list of index/value pairs (of length @n@)
                -> Vector a
{-# INLINE (//) #-}
// :: Vector a -> [(Int, a)] -> Vector a
(//) = Vector a -> [(Int, a)] -> Vector a
forall (v :: * -> *) a. Vector v a => v a -> [(Int, a)] -> v a
(G.//)

-- | /O(m+n)/ For each pair @(i,a)@ from the vector of index/value pairs,
-- replace the vector element at position @i@ by @a@.
--
-- > update <5,9,2,7> <(2,1),(0,3),(2,8)> = <3,9,8,7>
--
update :: Vector a        -- ^ initial vector (of length @m@)
       -> Vector (Int, a) -- ^ vector of index/value pairs (of length @n@)
       -> Vector a
{-# INLINE update #-}
update :: Vector a -> Vector (Int, a) -> Vector a
update = Vector a -> Vector (Int, a) -> Vector a
forall (v :: * -> *) a.
(Vector v a, Vector v (Int, a)) =>
v a -> v (Int, a) -> v a
G.update

-- | /O(m+min(n1,n2))/ For each index @i@ from the index vector and the
-- corresponding value @a@ from the value vector, replace the element of the
-- initial vector at position @i@ by @a@.
--
-- > update_ <5,9,2,7>  <2,0,2> <1,3,8> = <3,9,8,7>
--
-- The function 'update' provides the same functionality and is usually more
-- convenient.
--
-- @
-- update_ xs is ys = 'update' xs ('zip' is ys)
-- @
update_ :: Vector a   -- ^ initial vector (of length @m@)
        -> Vector Int -- ^ index vector (of length @n1@)
        -> Vector a   -- ^ value vector (of length @n2@)
        -> Vector a
{-# INLINE update_ #-}
update_ :: Vector a -> Vector Int -> Vector a -> Vector a
update_ = Vector a -> Vector Int -> Vector a -> Vector a
forall (v :: * -> *) a.
(Vector v a, Vector v Int) =>
v a -> v Int -> v a -> v a
G.update_

-- | Same as ('//') but without bounds checking.
unsafeUpd :: Vector a -> [(Int, a)] -> Vector a
{-# INLINE unsafeUpd #-}
unsafeUpd :: Vector a -> [(Int, a)] -> Vector a
unsafeUpd = Vector a -> [(Int, a)] -> Vector a
forall (v :: * -> *) a. Vector v a => v a -> [(Int, a)] -> v a
G.unsafeUpd

-- | Same as 'update' but without bounds checking.
unsafeUpdate :: Vector a -> Vector (Int, a) -> Vector a
{-# INLINE unsafeUpdate #-}
unsafeUpdate :: Vector a -> Vector (Int, a) -> Vector a
unsafeUpdate = Vector a -> Vector (Int, a) -> Vector a
forall (v :: * -> *) a.
(Vector v a, Vector v (Int, a)) =>
v a -> v (Int, a) -> v a
G.unsafeUpdate

-- | Same as 'update_' but without bounds checking.
unsafeUpdate_ :: Vector a -> Vector Int -> Vector a -> Vector a
{-# INLINE unsafeUpdate_ #-}
unsafeUpdate_ :: Vector a -> Vector Int -> Vector a -> Vector a
unsafeUpdate_ = Vector a -> Vector Int -> Vector a -> Vector a
forall (v :: * -> *) a.
(Vector v a, Vector v Int) =>
v a -> v Int -> v a -> v a
G.unsafeUpdate_

-- Accumulations
-- -------------

-- | /O(m+n)/ For each pair @(i,b)@ from the list, replace the vector element
-- @a@ at position @i@ by @f a b@.
--
-- ==== __Examples__
--
-- >>> import qualified Data.Vector as V
-- >>> V.accum (+) (V.fromList [1000.0,2000.0,3000.0]) [(2,4),(1,6),(0,3),(1,10)]
-- [1003.0,2016.0,3004.0]
accum :: (a -> b -> a) -- ^ accumulating function @f@
      -> Vector a      -- ^ initial vector (of length @m@)
      -> [(Int,b)]     -- ^ list of index/value pairs (of length @n@)
      -> Vector a
{-# INLINE accum #-}
accum :: (a -> b -> a) -> Vector a -> [(Int, b)] -> Vector a
accum = (a -> b -> a) -> Vector a -> [(Int, b)] -> Vector a
forall (v :: * -> *) a b.
Vector v a =>
(a -> b -> a) -> v a -> [(Int, b)] -> v a
G.accum

-- | /O(m+n)/ For each pair @(i,b)@ from the vector of pairs, replace the vector
-- element @a@ at position @i@ by @f a b@.
--
-- ==== __Examples__
--
-- >>> import qualified Data.Vector as V
-- >>> V.accumulate (+) (V.fromList [1000.0,2000.0,3000.0]) (V.fromList [(2,4),(1,6),(0,3),(1,10)])
-- [1003.0,2016.0,3004.0]
accumulate :: (a -> b -> a)  -- ^ accumulating function @f@
            -> Vector a       -- ^ initial vector (of length @m@)
            -> Vector (Int,b) -- ^ vector of index/value pairs (of length @n@)
            -> Vector a
{-# INLINE accumulate #-}
accumulate :: (a -> b -> a) -> Vector a -> Vector (Int, b) -> Vector a
accumulate = (a -> b -> a) -> Vector a -> Vector (Int, b) -> Vector a
forall (v :: * -> *) a b.
(Vector v a, Vector v (Int, b)) =>
(a -> b -> a) -> v a -> v (Int, b) -> v a
G.accumulate

-- | /O(m+min(n1,n2))/ For each index @i@ from the index vector and the
-- corresponding value @b@ from the the value vector,
-- replace the element of the initial vector at
-- position @i@ by @f a b@.
--
-- > accumulate_ (+) <5,9,2> <2,1,0,1> <4,6,3,7> = <5+3, 9+6+7, 2+4>
--
-- The function 'accumulate' provides the same functionality and is usually more
-- convenient.
--
-- @
-- accumulate_ f as is bs = 'accumulate' f as ('zip' is bs)
-- @
accumulate_ :: (a -> b -> a) -- ^ accumulating function @f@
            -> Vector a      -- ^ initial vector (of length @m@)
            -> Vector Int    -- ^ index vector (of length @n1@)
            -> Vector b      -- ^ value vector (of length @n2@)
            -> Vector a
{-# INLINE accumulate_ #-}
accumulate_ :: (a -> b -> a) -> Vector a -> Vector Int -> Vector b -> Vector a
accumulate_ = (a -> b -> a) -> Vector a -> Vector Int -> Vector b -> Vector a
forall (v :: * -> *) a b.
(Vector v a, Vector v Int, Vector v b) =>
(a -> b -> a) -> v a -> v Int -> v b -> v a
G.accumulate_

-- | Same as 'accum' but without bounds checking.
unsafeAccum :: (a -> b -> a) -> Vector a -> [(Int,b)] -> Vector a
{-# INLINE unsafeAccum #-}
unsafeAccum :: (a -> b -> a) -> Vector a -> [(Int, b)] -> Vector a
unsafeAccum = (a -> b -> a) -> Vector a -> [(Int, b)] -> Vector a
forall (v :: * -> *) a b.
Vector v a =>
(a -> b -> a) -> v a -> [(Int, b)] -> v a
G.unsafeAccum

-- | Same as 'accumulate' but without bounds checking.
unsafeAccumulate :: (a -> b -> a) -> Vector a -> Vector (Int,b) -> Vector a
{-# INLINE unsafeAccumulate #-}
unsafeAccumulate :: (a -> b -> a) -> Vector a -> Vector (Int, b) -> Vector a
unsafeAccumulate = (a -> b -> a) -> Vector a -> Vector (Int, b) -> Vector a
forall (v :: * -> *) a b.
(Vector v a, Vector v (Int, b)) =>
(a -> b -> a) -> v a -> v (Int, b) -> v a
G.unsafeAccumulate

-- | Same as 'accumulate_' but without bounds checking.
unsafeAccumulate_
  :: (a -> b -> a) -> Vector a -> Vector Int -> Vector b -> Vector a
{-# INLINE unsafeAccumulate_ #-}
unsafeAccumulate_ :: (a -> b -> a) -> Vector a -> Vector Int -> Vector b -> Vector a
unsafeAccumulate_ = (a -> b -> a) -> Vector a -> Vector Int -> Vector b -> Vector a
forall (v :: * -> *) a b.
(Vector v a, Vector v Int, Vector v b) =>
(a -> b -> a) -> v a -> v Int -> v b -> v a
G.unsafeAccumulate_

-- Permutations
-- ------------

-- | /O(n)/ Reverse a vector
reverse :: Vector a -> Vector a
{-# INLINE reverse #-}
reverse :: Vector a -> Vector a
reverse = Vector a -> Vector a
forall (v :: * -> *) a. Vector v a => v a -> v a
G.reverse

-- | /O(n)/ Yield the vector obtained by replacing each element @i@ of the
-- index vector by @xs'!'i@. This is equivalent to @'map' (xs'!') is@ but is
-- often much more efficient.
--
-- > backpermute <a,b,c,d> <0,3,2,3,1,0> = <a,d,c,d,b,a>
backpermute :: Vector a -> Vector Int -> Vector a
{-# INLINE backpermute #-}
backpermute :: Vector a -> Vector Int -> Vector a
backpermute = Vector a -> Vector Int -> Vector a
forall (v :: * -> *) a.
(Vector v a, Vector v Int) =>
v a -> v Int -> v a
G.backpermute

-- | Same as 'backpermute' but without bounds checking.
unsafeBackpermute :: Vector a -> Vector Int -> Vector a
{-# INLINE unsafeBackpermute #-}
unsafeBackpermute :: Vector a -> Vector Int -> Vector a
unsafeBackpermute = Vector a -> Vector Int -> Vector a
forall (v :: * -> *) a.
(Vector v a, Vector v Int) =>
v a -> v Int -> v a
G.unsafeBackpermute

-- Safe destructive updates
-- ------------------------

-- | Apply a destructive operation to a vector. The operation will be
-- performed in place if it is safe to do so and will modify a copy of the
-- vector otherwise.
--
-- @
-- modify (\\v -> write v 0 \'x\') ('replicate' 3 \'a\') = \<\'x\',\'a\',\'a\'\>
-- @
modify :: (forall s. MVector s a -> ST s ()) -> Vector a -> Vector a
{-# INLINE modify #-}
modify :: (forall s. MVector s a -> ST s ()) -> Vector a -> Vector a
modify forall s. MVector s a -> ST s ()
p = (forall s. Mutable Vector s a -> ST s ()) -> Vector a -> Vector a
forall (v :: * -> *) a.
Vector v a =>
(forall s. Mutable v s a -> ST s ()) -> v a -> v a
G.modify forall s. Mutable Vector s a -> ST s ()
forall s. MVector s a -> ST s ()
p

-- Indexing
-- --------

-- | /O(n)/ Pair each element in a vector with its index
indexed :: Vector a -> Vector (Int,a)
{-# INLINE indexed #-}
indexed :: Vector a -> Vector (Int, a)
indexed = Vector a -> Vector (Int, a)
forall (v :: * -> *) a.
(Vector v a, Vector v (Int, a)) =>
v a -> v (Int, a)
G.indexed

-- Mapping
-- -------

-- | /O(n)/ Map a function over a vector
map :: (a -> b) -> Vector a -> Vector b
{-# INLINE map #-}
map :: (a -> b) -> Vector a -> Vector b
map = (a -> b) -> Vector a -> Vector b
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> b) -> v a -> v b
G.map

-- | /O(n)/ Apply a function to every element of a vector and its index
imap :: (Int -> a -> b) -> Vector a -> Vector b
{-# INLINE imap #-}
imap :: (Int -> a -> b) -> Vector a -> Vector b
imap = (Int -> a -> b) -> Vector a -> Vector b
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(Int -> a -> b) -> v a -> v b
G.imap

-- | Map a function over a vector and concatenate the results.
concatMap :: (a -> Vector b) -> Vector a -> Vector b
{-# INLINE concatMap #-}
concatMap :: (a -> Vector b) -> Vector a -> Vector b
concatMap = (a -> Vector b) -> Vector a -> Vector b
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> v b) -> v a -> v b
G.concatMap

-- Monadic mapping
-- ---------------

-- | /O(n)/ Apply the monadic action to all elements of the vector, yielding a
-- vector of results
mapM :: Monad m => (a -> m b) -> Vector a -> m (Vector b)
{-# INLINE mapM #-}
mapM :: (a -> m b) -> Vector a -> m (Vector b)
mapM = (a -> m b) -> Vector a -> m (Vector b)
forall (m :: * -> *) (v :: * -> *) a b.
(Monad m, Vector v a, Vector v b) =>
(a -> m b) -> v a -> m (v b)
G.mapM

-- | /O(n)/ Apply the monadic action to every element of a vector and its
-- index, yielding a vector of results
imapM :: Monad m => (Int -> a -> m b) -> Vector a -> m (Vector b)
{-# INLINE imapM #-}
imapM :: (Int -> a -> m b) -> Vector a -> m (Vector b)
imapM = (Int -> a -> m b) -> Vector a -> m (Vector b)
forall (m :: * -> *) (v :: * -> *) a b.
(Monad m, Vector v a, Vector v b) =>
(Int -> a -> m b) -> v a -> m (v b)
G.imapM

-- | /O(n)/ Apply the monadic action to all elements of a vector and ignore the
-- results
mapM_ :: Monad m => (a -> m b) -> Vector a -> m ()
{-# INLINE mapM_ #-}
mapM_ :: (a -> m b) -> Vector a -> m ()
mapM_ = (a -> m b) -> Vector a -> m ()
forall (m :: * -> *) (v :: * -> *) a b.
(Monad m, Vector v a) =>
(a -> m b) -> v a -> m ()
G.mapM_

-- | /O(n)/ Apply the monadic action to every element of a vector and its
-- index, ignoring the results
imapM_ :: Monad m => (Int -> a -> m b) -> Vector a -> m ()
{-# INLINE imapM_ #-}
imapM_ :: (Int -> a -> m b) -> Vector a -> m ()
imapM_ = (Int -> a -> m b) -> Vector a -> m ()
forall (m :: * -> *) (v :: * -> *) a b.
(Monad m, Vector v a) =>
(Int -> a -> m b) -> v a -> m ()
G.imapM_

-- | /O(n)/ Apply the monadic action to all elements of the vector, yielding a
-- vector of results. Equivalent to @flip 'mapM'@.
forM :: Monad m => Vector a -> (a -> m b) -> m (Vector b)
{-# INLINE forM #-}
forM :: Vector a -> (a -> m b) -> m (Vector b)
forM = Vector a -> (a -> m b) -> m (Vector b)
forall (m :: * -> *) (v :: * -> *) a b.
(Monad m, Vector v a, Vector v b) =>
v a -> (a -> m b) -> m (v b)
G.forM

-- | /O(n)/ Apply the monadic action to all elements of a vector and ignore the
-- results. Equivalent to @flip 'mapM_'@.
forM_ :: Monad m => Vector a -> (a -> m b) -> m ()
{-# INLINE forM_ #-}
forM_ :: Vector a -> (a -> m b) -> m ()
forM_ = Vector a -> (a -> m b) -> m ()
forall (m :: * -> *) (v :: * -> *) a b.
(Monad m, Vector v a) =>
v a -> (a -> m b) -> m ()
G.forM_

-- | /O(n)/ Apply the monadic action to all elements of the vector and their indices, yielding a
-- vector of results. Equivalent to 'flip' 'imapM'.
--
-- @since 0.12.2.0
iforM :: Monad m => Vector a -> (Int -> a -> m b) -> m (Vector b)
{-# INLINE iforM #-}
iforM :: Vector a -> (Int -> a -> m b) -> m (Vector b)
iforM = Vector a -> (Int -> a -> m b) -> m (Vector b)
forall (m :: * -> *) (v :: * -> *) a b.
(Monad m, Vector v a, Vector v b) =>
v a -> (Int -> a -> m b) -> m (v b)
G.iforM

-- | /O(n)/ Apply the monadic action to all elements of the vector and their indices and ignore the
-- results. Equivalent to 'flip' 'imapM_'.
--
-- @since 0.12.2.0
iforM_ :: Monad m => Vector a -> (Int -> a -> m b) -> m ()
{-# INLINE iforM_ #-}
iforM_ :: Vector a -> (Int -> a -> m b) -> m ()
iforM_ = Vector a -> (Int -> a -> m b) -> m ()
forall (m :: * -> *) (v :: * -> *) a b.
(Monad m, Vector v a) =>
v a -> (Int -> a -> m b) -> m ()
G.iforM_

-- Zipping
-- -------

-- | /O(min(m,n))/ Zip two vectors with the given function.
zipWith :: (a -> b -> c) -> Vector a -> Vector b -> Vector c
{-# INLINE zipWith #-}
zipWith :: (a -> b -> c) -> Vector a -> Vector b -> Vector c
zipWith = (a -> b -> c) -> Vector a -> Vector b -> Vector c
forall (v :: * -> *) a b c.
(Vector v a, Vector v b, Vector v c) =>
(a -> b -> c) -> v a -> v b -> v c
G.zipWith

-- | Zip three vectors with the given function.
zipWith3 :: (a -> b -> c -> d) -> Vector a -> Vector b -> Vector c -> Vector d
{-# INLINE zipWith3 #-}
zipWith3 :: (a -> b -> c -> d) -> Vector a -> Vector b -> Vector c -> Vector d
zipWith3 = (a -> b -> c -> d) -> Vector a -> Vector b -> Vector c -> Vector d
forall (v :: * -> *) a b c d.
(Vector v a, Vector v b, Vector v c, Vector v d) =>
(a -> b -> c -> d) -> v a -> v b -> v c -> v d
G.zipWith3

zipWith4 :: (a -> b -> c -> d -> e)
         -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e
{-# INLINE zipWith4 #-}
zipWith4 :: (a -> b -> c -> d -> e)
-> Vector a -> Vector b -> Vector c -> Vector d -> Vector e
zipWith4 = (a -> b -> c -> d -> e)
-> Vector a -> Vector b -> Vector c -> Vector d -> Vector e
forall (v :: * -> *) a b c d e.
(Vector v a, Vector v b, Vector v c, Vector v d, Vector v e) =>
(a -> b -> c -> d -> e) -> v a -> v b -> v c -> v d -> v e
G.zipWith4

zipWith5 :: (a -> b -> c -> d -> e -> f)
         -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e
         -> Vector f
{-# INLINE zipWith5 #-}
zipWith5 :: (a -> b -> c -> d -> e -> f)
-> Vector a
-> Vector b
-> Vector c
-> Vector d
-> Vector e
-> Vector f
zipWith5 = (a -> b -> c -> d -> e -> f)
-> Vector a
-> Vector b
-> Vector c
-> Vector d
-> Vector e
-> Vector f
forall (v :: * -> *) a b c d e f.
(Vector v a, Vector v b, Vector v c, Vector v d, Vector v e,
 Vector v f) =>
(a -> b -> c -> d -> e -> f)
-> v a -> v b -> v c -> v d -> v e -> v f
G.zipWith5

zipWith6 :: (a -> b -> c -> d -> e -> f -> g)
         -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e
         -> Vector f -> Vector g
{-# INLINE zipWith6 #-}
zipWith6 :: (a -> b -> c -> d -> e -> f -> g)
-> Vector a
-> Vector b
-> Vector c
-> Vector d
-> Vector e
-> Vector f
-> Vector g
zipWith6 = (a -> b -> c -> d -> e -> f -> g)
-> Vector a
-> Vector b
-> Vector c
-> Vector d
-> Vector e
-> Vector f
-> Vector g
forall (v :: * -> *) a b c d e f g.
(Vector v a, Vector v b, Vector v c, Vector v d, Vector v e,
 Vector v f, Vector v g) =>
(a -> b -> c -> d -> e -> f -> g)
-> v a -> v b -> v c -> v d -> v e -> v f -> v g
G.zipWith6

-- | /O(min(m,n))/ Zip two vectors with a function that also takes the
-- elements' indices.
izipWith :: (Int -> a -> b -> c) -> Vector a -> Vector b -> Vector c
{-# INLINE izipWith #-}
izipWith :: (Int -> a -> b -> c) -> Vector a -> Vector b -> Vector c
izipWith = (Int -> a -> b -> c) -> Vector a -> Vector b -> Vector c
forall (v :: * -> *) a b c.
(Vector v a, Vector v b, Vector v c) =>
(Int -> a -> b -> c) -> v a -> v b -> v c
G.izipWith

-- | Zip three vectors and their indices with the given function.
izipWith3 :: (Int -> a -> b -> c -> d)
          -> Vector a -> Vector b -> Vector c -> Vector d
{-# INLINE izipWith3 #-}
izipWith3 :: (Int -> a -> b -> c -> d)
-> Vector a -> Vector b -> Vector c -> Vector d
izipWith3 = (Int -> a -> b -> c -> d)
-> Vector a -> Vector b -> Vector c -> Vector d
forall (v :: * -> *) a b c d.
(Vector v a, Vector v b, Vector v c, Vector v d) =>
(Int -> a -> b -> c -> d) -> v a -> v b -> v c -> v d
G.izipWith3

izipWith4 :: (Int -> a -> b -> c -> d -> e)
          -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e
{-# INLINE izipWith4 #-}
izipWith4 :: (Int -> a -> b -> c -> d -> e)
-> Vector a -> Vector b -> Vector c -> Vector d -> Vector e
izipWith4 = (Int -> a -> b -> c -> d -> e)
-> Vector a -> Vector b -> Vector c -> Vector d -> Vector e
forall (v :: * -> *) a b c d e.
(Vector v a, Vector v b, Vector v c, Vector v d, Vector v e) =>
(Int -> a -> b -> c -> d -> e) -> v a -> v b -> v c -> v d -> v e
G.izipWith4

izipWith5 :: (Int -> a -> b -> c -> d -> e -> f)
          -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e
          -> Vector f
{-# INLINE izipWith5 #-}
izipWith5 :: (Int -> a -> b -> c -> d -> e -> f)
-> Vector a
-> Vector b
-> Vector c
-> Vector d
-> Vector e
-> Vector f
izipWith5 = (Int -> a -> b -> c -> d -> e -> f)
-> Vector a
-> Vector b
-> Vector c
-> Vector d
-> Vector e
-> Vector f
forall (v :: * -> *) a b c d e f.
(Vector v a, Vector v b, Vector v c, Vector v d, Vector v e,
 Vector v f) =>
(Int -> a -> b -> c -> d -> e -> f)
-> v a -> v b -> v c -> v d -> v e -> v f
G.izipWith5

izipWith6 :: (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 :: (Int -> a -> b -> c -> d -> e -> f -> g)
-> Vector a
-> Vector b
-> Vector c
-> Vector d
-> Vector e
-> Vector f
-> Vector g
izipWith6 = (Int -> a -> b -> c -> d -> e -> f -> g)
-> Vector a
-> Vector b
-> Vector c
-> Vector d
-> Vector e
-> Vector f
-> Vector g
forall (v :: * -> *) a b c d e f g.
(Vector v a, Vector v b, Vector v c, Vector v d, Vector v e,
 Vector v f, Vector v g) =>
(Int -> a -> b -> c -> d -> e -> f -> g)
-> v a -> v b -> v c -> v d -> v e -> v f -> v g
G.izipWith6

-- | Elementwise pairing of array elements.
zip :: Vector a -> Vector b -> Vector (a, b)
{-# INLINE zip #-}
zip :: Vector a -> Vector b -> Vector (a, b)
zip = Vector a -> Vector b -> Vector (a, b)
forall (v :: * -> *) a b.
(Vector v a, Vector v b, Vector v (a, b)) =>
v a -> v b -> v (a, b)
G.zip

-- | zip together three vectors into a vector of triples
zip3 :: Vector a -> Vector b -> Vector c -> Vector (a, b, c)
{-# INLINE zip3 #-}
zip3 :: Vector a -> Vector b -> Vector c -> Vector (a, b, c)
zip3 = Vector a -> Vector b -> Vector c -> Vector (a, b, c)
forall (v :: * -> *) a b c.
(Vector v a, Vector v b, Vector v c, Vector v (a, b, c)) =>
v a -> v b -> v c -> v (a, b, c)
G.zip3

zip4 :: Vector a -> Vector b -> Vector c -> Vector d
     -> Vector (a, b, c, d)
{-# INLINE zip4 #-}
zip4 :: Vector a -> Vector b -> Vector c -> Vector d -> Vector (a, b, c, d)
zip4 = Vector a -> Vector b -> Vector c -> Vector d -> Vector (a, b, c, d)
forall (v :: * -> *) a b c d.
(Vector v a, Vector v b, Vector v c, Vector v d,
 Vector v (a, b, c, d)) =>
v a -> v b -> v c -> v d -> v (a, b, c, d)
G.zip4

zip5 :: Vector a -> Vector b -> Vector c -> Vector d -> Vector e
     -> Vector (a, b, c, d, e)
{-# INLINE zip5 #-}
zip5 :: Vector a
-> Vector b
-> Vector c
-> Vector d
-> Vector e
-> Vector (a, b, c, d, e)
zip5 = Vector a
-> Vector b
-> Vector c
-> Vector d
-> Vector e
-> Vector (a, b, c, d, e)
forall (v :: * -> *) a b c d e.
(Vector v a, Vector v b, Vector v c, Vector v d, Vector v e,
 Vector v (a, b, c, d, e)) =>
v a -> v b -> v c -> v d -> v e -> v (a, b, c, d, e)
G.zip5

zip6 :: Vector a -> Vector b -> Vector c -> Vector d -> Vector e -> Vector f
     -> Vector (a, b, c, d, e, f)
{-# INLINE zip6 #-}
zip6 :: Vector a
-> Vector b
-> Vector c
-> Vector d
-> Vector e
-> Vector f
-> Vector (a, b, c, d, e, f)
zip6 = Vector a
-> Vector b
-> Vector c
-> Vector d
-> Vector e
-> Vector f
-> Vector (a, b, c, d, e, f)
forall (v :: * -> *) a b c d e f.
(Vector v a, Vector v b, Vector v c, Vector v d, Vector v e,
 Vector v f, Vector v (a, b, c, d, e, f)) =>
v a -> v b -> v c -> v d -> v e -> v f -> v (a, b, c, d, e, f)
G.zip6

-- Unzipping
-- ---------

-- | /O(min(m,n))/ Unzip a vector of pairs.
unzip :: Vector (a, b) -> (Vector a, Vector b)
{-# INLINE unzip #-}
unzip :: Vector (a, b) -> (Vector a, Vector b)
unzip = Vector (a, b) -> (Vector a, Vector b)
forall (v :: * -> *) a b.
(Vector v a, Vector v b, Vector v (a, b)) =>
v (a, b) -> (v a, v b)
G.unzip

unzip3 :: Vector (a, b, c) -> (Vector a, Vector b, Vector c)
{-# INLINE unzip3 #-}
unzip3 :: Vector (a, b, c) -> (Vector a, Vector b, Vector c)
unzip3 = Vector (a, b, c) -> (Vector a, Vector b, Vector c)
forall (v :: * -> *) a b c.
(Vector v a, Vector v b, Vector v c, Vector v (a, b, c)) =>
v (a, b, c) -> (v a, v b, v c)
G.unzip3

unzip4 :: Vector (a, b, c, d) -> (Vector a, Vector b, Vector c, Vector d)
{-# INLINE unzip4 #-}
unzip4 :: Vector (a, b, c, d) -> (Vector a, Vector b, Vector c, Vector d)
unzip4 = Vector (a, b, c, d) -> (Vector a, Vector b, Vector c, Vector d)
forall (v :: * -> *) a b c d.
(Vector v a, Vector v b, Vector v c, Vector v d,
 Vector v (a, b, c, d)) =>
v (a, b, c, d) -> (v a, v b, v c, v d)
G.unzip4

unzip5 :: Vector (a, b, c, d, e)
       -> (Vector a, Vector b, Vector c, Vector d, Vector e)
{-# INLINE unzip5 #-}
unzip5 :: Vector (a, b, c, d, e)
-> (Vector a, Vector b, Vector c, Vector d, Vector e)
unzip5 = Vector (a, b, c, d, e)
-> (Vector a, Vector b, Vector c, Vector d, Vector e)
forall (v :: * -> *) a b c d e.
(Vector v a, Vector v b, Vector v c, Vector v d, Vector v e,
 Vector v (a, b, c, d, e)) =>
v (a, b, c, d, e) -> (v a, v b, v c, v d, v e)
G.unzip5

unzip6 :: Vector (a, b, c, d, e, f)
       -> (Vector a, Vector b, Vector c, Vector d, Vector e, Vector f)
{-# INLINE unzip6 #-}
unzip6 :: Vector (a, b, c, d, e, f)
-> (Vector a, Vector b, Vector c, Vector d, Vector e, Vector f)
unzip6 = Vector (a, b, c, d, e, f)
-> (Vector a, Vector b, Vector c, Vector d, Vector e, Vector f)
forall (v :: * -> *) a b c d e f.
(Vector v a, Vector v b, Vector v c, Vector v d, Vector v e,
 Vector v f, Vector v (a, b, c, d, e, f)) =>
v (a, b, c, d, e, f) -> (v a, v b, v c, v d, v e, v f)
G.unzip6

-- Monadic zipping
-- ---------------

-- | /O(min(m,n))/ Zip the two vectors with the monadic action and yield a
-- vector of results
zipWithM :: Monad m => (a -> b -> m c) -> Vector a -> Vector b -> m (Vector c)
{-# INLINE zipWithM #-}
zipWithM :: (a -> b -> m c) -> Vector a -> Vector b -> m (Vector c)
zipWithM = (a -> b -> m c) -> Vector a -> Vector b -> m (Vector c)
forall (m :: * -> *) (v :: * -> *) a b c.
(Monad m, Vector v a, Vector v b, Vector v c) =>
(a -> b -> m c) -> v a -> v b -> m (v c)
G.zipWithM

-- | /O(min(m,n))/ Zip the two vectors with a monadic action that also takes
-- the element index and yield a vector of results
izipWithM :: Monad m => (Int -> a -> b -> m c) -> Vector a -> Vector b -> m (Vector c)
{-# INLINE izipWithM #-}
izipWithM :: (Int -> a -> b -> m c) -> Vector a -> Vector b -> m (Vector c)
izipWithM = (Int -> a -> b -> m c) -> Vector a -> Vector b -> m (Vector c)
forall (m :: * -> *) (v :: * -> *) a b c.
(Monad m, Vector v a, Vector v b, Vector v c) =>
(Int -> a -> b -> m c) -> v a -> v b -> m (v c)
G.izipWithM

-- | /O(min(m,n))/ Zip the two vectors with the monadic action and ignore the
-- results
zipWithM_ :: Monad m => (a -> b -> m c) -> Vector a -> Vector b -> m ()
{-# INLINE zipWithM_ #-}
zipWithM_ :: (a -> b -> m c) -> Vector a -> Vector b -> m ()
zipWithM_ = (a -> b -> m c) -> Vector a -> Vector b -> m ()
forall (m :: * -> *) (v :: * -> *) a b c.
(Monad m, Vector v a, Vector v b) =>
(a -> b -> m c) -> v a -> v b -> m ()
G.zipWithM_

-- | /O(min(m,n))/ Zip the two vectors with a monadic action that also takes
-- the element index and ignore the results
izipWithM_ :: Monad m => (Int -> a -> b -> m c) -> Vector a -> Vector b -> m ()
{-# INLINE izipWithM_ #-}
izipWithM_ :: (Int -> a -> b -> m c) -> Vector a -> Vector b -> m ()
izipWithM_ = (Int -> a -> b -> m c) -> Vector a -> Vector b -> m ()
forall (m :: * -> *) (v :: * -> *) a b c.
(Monad m, Vector v a, Vector v b) =>
(Int -> a -> b -> m c) -> v a -> v b -> m ()
G.izipWithM_

-- Filtering
-- ---------

-- | /O(n)/ Drop elements that do not satisfy the predicate
filter :: (a -> Bool) -> Vector a -> Vector a
{-# INLINE filter #-}
filter :: (a -> Bool) -> Vector a -> Vector a
filter = (a -> Bool) -> Vector a -> Vector a
forall (v :: * -> *) a. Vector v a => (a -> Bool) -> v a -> v a
G.filter

-- | /O(n)/ Drop elements that do not satisfy the predicate which is applied to
-- values and their indices
ifilter :: (Int -> a -> Bool) -> Vector a -> Vector a
{-# INLINE ifilter #-}
ifilter :: (Int -> a -> Bool) -> Vector a -> Vector a
ifilter = (Int -> a -> Bool) -> Vector a -> Vector a
forall (v :: * -> *) a.
Vector v a =>
(Int -> a -> Bool) -> v a -> v a
G.ifilter

-- | /O(n)/ Drop repeated adjacent elements.
uniq :: (Eq a) => Vector a -> Vector a
{-# INLINE uniq #-}
uniq :: Vector a -> Vector a
uniq = Vector a -> Vector a
forall (v :: * -> *) a. (Vector v a, Eq a) => v a -> v a
G.uniq

-- | /O(n)/ Drop elements when predicate returns Nothing
mapMaybe :: (a -> Maybe b) -> Vector a -> Vector b
{-# INLINE mapMaybe #-}
mapMaybe :: (a -> Maybe b) -> Vector a -> Vector b
mapMaybe = (a -> Maybe b) -> Vector a -> Vector b
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> Maybe b) -> v a -> v b
G.mapMaybe

-- | /O(n)/ Drop elements when predicate, applied to index and value, returns Nothing
imapMaybe :: (Int -> a -> Maybe b) -> Vector a -> Vector b
{-# INLINE imapMaybe #-}
imapMaybe :: (Int -> a -> Maybe b) -> Vector a -> Vector b
imapMaybe = (Int -> a -> Maybe b) -> Vector a -> Vector b
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(Int -> a -> Maybe b) -> v a -> v b
G.imapMaybe

-- | /O(n)/ Return a Vector of all the `Just` values.
--
-- @since 0.12.2.0
catMaybes :: Vector (Maybe a) -> Vector a
{-# INLINE catMaybes #-}
catMaybes :: Vector (Maybe a) -> Vector a
catMaybes = (Maybe a -> Maybe a) -> Vector (Maybe a) -> Vector a
forall a b. (a -> Maybe b) -> Vector a -> Vector b
mapMaybe Maybe a -> Maybe a
forall a. a -> a
id

-- | /O(n)/ Drop elements that do not satisfy the monadic predicate
filterM :: Monad m => (a -> m Bool) -> Vector a -> m (Vector a)
{-# INLINE filterM #-}
filterM :: (a -> m Bool) -> Vector a -> m (Vector a)
filterM = (a -> m Bool) -> Vector a -> m (Vector a)
forall (m :: * -> *) (v :: * -> *) a.
(Monad m, Vector v a) =>
(a -> m Bool) -> v a -> m (v a)
G.filterM

-- | /O(n)/ Apply monadic function to each element of vector and
-- discard elements returning Nothing.
--
-- @since 0.12.2.0
mapMaybeM :: Monad m => (a -> m (Maybe b)) -> Vector a -> m (Vector b)
{-# INLINE mapMaybeM #-}
mapMaybeM :: (a -> m (Maybe b)) -> Vector a -> m (Vector b)
mapMaybeM = (a -> m (Maybe b)) -> Vector a -> m (Vector b)
forall (m :: * -> *) (v :: * -> *) a b.
(Monad m, Vector v a, Vector v b) =>
(a -> m (Maybe b)) -> v a -> m (v b)
G.mapMaybeM

-- | /O(n)/ Apply monadic function to each element of vector and its index.
-- Discards elements returning Nothing.
--
-- @since 0.12.2.0
imapMaybeM :: Monad m => (Int -> a -> m (Maybe b)) -> Vector a -> m (Vector b)
{-# INLINE imapMaybeM #-}
imapMaybeM :: (Int -> a -> m (Maybe b)) -> Vector a -> m (Vector b)
imapMaybeM = (Int -> a -> m (Maybe b)) -> Vector a -> m (Vector b)
forall (m :: * -> *) (v :: * -> *) a b.
(Monad m, Vector v a, Vector v b) =>
(Int -> a -> m (Maybe b)) -> v a -> m (v b)
G.imapMaybeM

-- | /O(n)/ Yield the longest prefix of elements satisfying the predicate.
-- Current implementation is not copy-free, unless the result vector is
-- fused away.
takeWhile :: (a -> Bool) -> Vector a -> Vector a
{-# INLINE takeWhile #-}
takeWhile :: (a -> Bool) -> Vector a -> Vector a
takeWhile = (a -> Bool) -> Vector a -> Vector a
forall (v :: * -> *) a. Vector v a => (a -> Bool) -> v a -> v a
G.takeWhile

-- | /O(n)/ Drop the longest prefix of elements that satisfy the predicate
-- without copying.
dropWhile :: (a -> Bool) -> Vector a -> Vector a
{-# INLINE dropWhile #-}
dropWhile :: (a -> Bool) -> Vector a -> Vector a
dropWhile = (a -> Bool) -> Vector a -> Vector a
forall (v :: * -> *) a. Vector v a => (a -> Bool) -> v a -> v a
G.dropWhile

-- Parititioning
-- -------------

-- | /O(n)/ Split the vector in two parts, the first one containing those
-- elements that satisfy the predicate and the second one those that don't. The
-- relative order of the elements is preserved at the cost of a sometimes
-- reduced performance compared to 'unstablePartition'.
partition :: (a -> Bool) -> Vector a -> (Vector a, Vector a)
{-# INLINE partition #-}
partition :: (a -> Bool) -> Vector a -> (Vector a, Vector a)
partition = (a -> Bool) -> Vector a -> (Vector a, Vector a)
forall (v :: * -> *) a.
Vector v a =>
(a -> Bool) -> v a -> (v a, v a)
G.partition

-- | /O(n)/ Split the vector in two parts, the first one containing those
-- elements that satisfy the predicate and the second one those that don't.
-- The order of the elements is not preserved but the operation is often
-- faster than 'partition'.
unstablePartition :: (a -> Bool) -> Vector a -> (Vector a, Vector a)
{-# INLINE unstablePartition #-}
unstablePartition :: (a -> Bool) -> Vector a -> (Vector a, Vector a)
unstablePartition = (a -> Bool) -> Vector a -> (Vector a, Vector a)
forall (v :: * -> *) a.
Vector v a =>
(a -> Bool) -> v a -> (v a, v a)
G.unstablePartition

-- | /O(n)/ Split the vector into two parts, the first one containing the
-- @`Left`@ elements and the second containing the @`Right`@ elements.
-- The relative order of the elements is preserved.
--
-- @since 0.12.1.0
partitionWith :: (a -> Either b c) -> Vector a -> (Vector b, Vector c)
{-# INLINE partitionWith #-}
partitionWith :: (a -> Either b c) -> Vector a -> (Vector b, Vector c)
partitionWith = (a -> Either b c) -> Vector a -> (Vector b, Vector c)
forall (v :: * -> *) a b c.
(Vector v a, Vector v b, Vector v c) =>
(a -> Either b c) -> v a -> (v b, v c)
G.partitionWith

-- | /O(n)/ Split the vector into the longest prefix of elements that satisfy
-- the predicate and the rest without copying.
span :: (a -> Bool) -> Vector a -> (Vector a, Vector a)
{-# INLINE span #-}
span :: (a -> Bool) -> Vector a -> (Vector a, Vector a)
span = (a -> Bool) -> Vector a -> (Vector a, Vector a)
forall (v :: * -> *) a.
Vector v a =>
(a -> Bool) -> v a -> (v a, v a)
G.span

-- | /O(n)/ Split the vector into the longest prefix of elements that do not
-- satisfy the predicate and the rest without copying.
break :: (a -> Bool) -> Vector a -> (Vector a, Vector a)
{-# INLINE break #-}
break :: (a -> Bool) -> Vector a -> (Vector a, Vector a)
break = (a -> Bool) -> Vector a -> (Vector a, Vector a)
forall (v :: * -> *) a.
Vector v a =>
(a -> Bool) -> v a -> (v a, v a)
G.break

-- Searching
-- ---------

infix 4 `elem`
-- | /O(n)/ Check if the vector contains an element
elem :: Eq a => a -> Vector a -> Bool
{-# INLINE elem #-}
elem :: a -> Vector a -> Bool
elem = a -> Vector a -> Bool
forall (v :: * -> *) a. (Vector v a, Eq a) => a -> v a -> Bool
G.elem

infix 4 `notElem`
-- | /O(n)/ Check if the vector does not contain an element (inverse of 'elem')
notElem :: Eq a => a -> Vector a -> Bool
{-# INLINE notElem #-}
notElem :: a -> Vector a -> Bool
notElem = a -> Vector a -> Bool
forall (v :: * -> *) a. (Vector v a, Eq a) => a -> v a -> Bool
G.notElem

-- | /O(n)/ Yield 'Just' the first element matching the predicate or 'Nothing'
-- if no such element exists.
find :: (a -> Bool) -> Vector a -> Maybe a
{-# INLINE find #-}
find :: (a -> Bool) -> Vector a -> Maybe a
find = (a -> Bool) -> Vector a -> Maybe a
forall (v :: * -> *) a. Vector v a => (a -> Bool) -> v a -> Maybe a
G.find

-- | /O(n)/ Yield 'Just' the index of the first element matching the predicate
-- or 'Nothing' if no such element exists.
findIndex :: (a -> Bool) -> Vector a -> Maybe Int
{-# INLINE findIndex #-}
findIndex :: (a -> Bool) -> Vector a -> Maybe Int
findIndex = (a -> Bool) -> Vector a -> Maybe Int
forall (v :: * -> *) a.
Vector v a =>
(a -> Bool) -> v a -> Maybe Int
G.findIndex

-- | /O(n)/ Yield the indices of elements satisfying the predicate in ascending
-- order.
findIndices :: (a -> Bool) -> Vector a -> Vector Int
{-# INLINE findIndices #-}
findIndices :: (a -> Bool) -> Vector a -> Vector Int
findIndices = (a -> Bool) -> Vector a -> Vector Int
forall (v :: * -> *) a.
(Vector v a, Vector v Int) =>
(a -> Bool) -> v a -> v Int
G.findIndices

-- | /O(n)/ Yield 'Just' the index of the first occurence of the given element or
-- 'Nothing' if the vector does not contain the element. This is a specialised
-- version of 'findIndex'.
elemIndex :: Eq a => a -> Vector a -> Maybe Int
{-# INLINE elemIndex #-}
elemIndex :: a -> Vector a -> Maybe Int
elemIndex = a -> Vector a -> Maybe Int
forall (v :: * -> *) a. (Vector v a, Eq a) => a -> v a -> Maybe Int
G.elemIndex

-- | /O(n)/ Yield the indices of all occurences of the given element in
-- ascending order. This is a specialised version of 'findIndices'.
elemIndices :: Eq a => a -> Vector a -> Vector Int
{-# INLINE elemIndices #-}
elemIndices :: a -> Vector a -> Vector Int
elemIndices = a -> Vector a -> Vector Int
forall (v :: * -> *) a.
(Vector v a, Vector v Int, Eq a) =>
a -> v a -> v Int
G.elemIndices

-- Folding
-- -------

-- | /O(n)/ Left fold
foldl :: (a -> b -> a) -> a -> Vector b -> a
{-# INLINE foldl #-}
foldl :: (a -> b -> a) -> a -> Vector b -> a
foldl = (a -> b -> a) -> a -> Vector b -> a
forall (v :: * -> *) b a.
Vector v b =>
(a -> b -> a) -> a -> v b -> a
G.foldl

-- | /O(n)/ Left fold on non-empty vectors
foldl1 :: (a -> a -> a) -> Vector a -> a
{-# INLINE foldl1 #-}
foldl1 :: (a -> a -> a) -> Vector a -> a
foldl1 = (a -> a -> a) -> Vector a -> a
forall (v :: * -> *) a. Vector v a => (a -> a -> a) -> v a -> a
G.foldl1

-- | /O(n)/ Left fold with strict accumulator
foldl' :: (a -> b -> a) -> a -> Vector b -> a
{-# INLINE foldl' #-}
foldl' :: (a -> b -> a) -> a -> Vector b -> a
foldl' = (a -> b -> a) -> a -> Vector b -> a
forall (v :: * -> *) b a.
Vector v b =>
(a -> b -> a) -> a -> v b -> a
G.foldl'

-- | /O(n)/ Left fold on non-empty vectors with strict accumulator
foldl1' :: (a -> a -> a) -> Vector a -> a
{-# INLINE foldl1' #-}
foldl1' :: (a -> a -> a) -> Vector a -> a
foldl1' = (a -> a -> a) -> Vector a -> a
forall (v :: * -> *) a. Vector v a => (a -> a -> a) -> v a -> a
G.foldl1'

-- | /O(n)/ Right fold
foldr :: (a -> b -> b) -> b -> Vector a -> b
{-# INLINE foldr #-}
foldr :: (a -> b -> b) -> b -> Vector a -> b
foldr = (a -> b -> b) -> b -> Vector a -> b
forall (v :: * -> *) a b.
Vector v a =>
(a -> b -> b) -> b -> v a -> b
G.foldr

-- | /O(n)/ Right fold on non-empty vectors
foldr1 :: (a -> a -> a) -> Vector a -> a
{-# INLINE foldr1 #-}
foldr1 :: (a -> a -> a) -> Vector a -> a
foldr1 = (a -> a -> a) -> Vector a -> a
forall (v :: * -> *) a. Vector v a => (a -> a -> a) -> v a -> a
G.foldr1

-- | /O(n)/ Right fold with a strict accumulator
foldr' :: (a -> b -> b) -> b -> Vector a -> b
{-# INLINE foldr' #-}
foldr' :: (a -> b -> b) -> b -> Vector a -> b
foldr' = (a -> b -> b) -> b -> Vector a -> b
forall (v :: * -> *) a b.
Vector v a =>
(a -> b -> b) -> b -> v a -> b
G.foldr'

-- | /O(n)/ Right fold on non-empty vectors with strict accumulator
foldr1' :: (a -> a -> a) -> Vector a -> a
{-# INLINE foldr1' #-}
foldr1' :: (a -> a -> a) -> Vector a -> a
foldr1' = (a -> a -> a) -> Vector a -> a
forall (v :: * -> *) a. Vector v a => (a -> a -> a) -> v a -> a
G.foldr1'

-- | /O(n)/ Left fold (function applied to each element and its index)
ifoldl :: (a -> Int -> b -> a) -> a -> Vector b -> a
{-# INLINE ifoldl #-}
ifoldl :: (a -> Int -> b -> a) -> a -> Vector b -> a
ifoldl = (a -> Int -> b -> a) -> a -> Vector b -> a
forall (v :: * -> *) b a.
Vector v b =>
(a -> Int -> b -> a) -> a -> v b -> a
G.ifoldl

-- | /O(n)/ Left fold with strict accumulator (function applied to each element
-- and its index)
ifoldl' :: (a -> Int -> b -> a) -> a -> Vector b -> a
{-# INLINE ifoldl' #-}
ifoldl' :: (a -> Int -> b -> a) -> a -> Vector b -> a
ifoldl' = (a -> Int -> b -> a) -> a -> Vector b -> a
forall (v :: * -> *) b a.
Vector v b =>
(a -> Int -> b -> a) -> a -> v b -> a
G.ifoldl'

-- | /O(n)/ Right fold (function applied to each element and its index)
ifoldr :: (Int -> a -> b -> b) -> b -> Vector a -> b
{-# INLINE ifoldr #-}
ifoldr :: (Int -> a -> b -> b) -> b -> Vector a -> b
ifoldr = (Int -> a -> b -> b) -> b -> Vector a -> b
forall (v :: * -> *) a b.
Vector v a =>
(Int -> a -> b -> b) -> b -> v a -> b
G.ifoldr

-- | /O(n)/ Right fold with strict accumulator (function applied to each
-- element and its index)
ifoldr' :: (Int -> a -> b -> b) -> b -> Vector a -> b
{-# INLINE ifoldr' #-}
ifoldr' :: (Int -> a -> b -> b) -> b -> Vector a -> b
ifoldr' = (Int -> a -> b -> b) -> b -> Vector a -> b
forall (v :: * -> *) a b.
Vector v a =>
(Int -> a -> b -> b) -> b -> v a -> b
G.ifoldr'

-- | /O(n)/ Map each element of the structure to a monoid, and combine
-- the results. It uses same implementation as corresponding method of
-- 'Foldable' type cless. Note it's implemented in terms of 'foldr'
-- and won't fuse with functions that traverse vector from left to
-- right ('map', 'generate', etc.).
--
-- @since 0.12.2.0
foldMap :: (Monoid m) => (a -> m) -> Vector a -> m
{-# INLINE foldMap #-}
foldMap :: (a -> m) -> Vector a -> m
foldMap = (a -> m) -> Vector a -> m
forall m (v :: * -> *) a.
(Monoid m, Vector v a) =>
(a -> m) -> v a -> m
G.foldMap

-- | /O(n)/ 'foldMap' which is strict in accumulator. It uses same
-- implementation as corresponding method of 'Foldable' type class.
-- Note it's implemented in terms of 'foldl'' so it fuses in most
-- contexts.
--
-- @since 0.12.2.0
foldMap' :: (Monoid m) => (a -> m) -> Vector a -> m
{-# INLINE foldMap' #-}
foldMap' :: (a -> m) -> Vector a -> m
foldMap' = (a -> m) -> Vector a -> m
forall m (v :: * -> *) a.
(Monoid m, Vector v a) =>
(a -> m) -> v a -> m
G.foldMap'


-- Specialised folds
-- -----------------

-- | /O(n)/ Check if all elements satisfy the predicate.
--
-- ==== __Examples__
--
-- >>> import qualified Data.Vector as V
-- >>> V.all even $ V.fromList [2, 4, 12 :: Int]
-- True
-- >>> V.all even $ V.fromList [2, 4, 13 :: Int]
-- False
-- >>> V.all even (V.empty :: V.Vector Int)
-- True
all :: (a -> Bool) -> Vector a -> Bool
{-# INLINE all #-}
all :: (a -> Bool) -> Vector a -> Bool
all = (a -> Bool) -> Vector a -> Bool
forall (v :: * -> *) a. Vector v a => (a -> Bool) -> v a -> Bool
G.all

-- | /O(n)/ Check if any element satisfies the predicate.
--
-- ==== __Examples__
--
-- >>> import qualified Data.Vector as V
-- >>> V.any even $ V.fromList [1, 3, 7 :: Int]
-- False
-- >>> V.any even $ V.fromList [3, 2, 13 :: Int]
-- True
-- >>> V.any even (V.empty :: V.Vector Int)
-- False
any :: (a -> Bool) -> Vector a -> Bool
{-# INLINE any #-}
any :: (a -> Bool) -> Vector a -> Bool
any = (a -> Bool) -> Vector a -> Bool
forall (v :: * -> *) a. Vector v a => (a -> Bool) -> v a -> Bool
G.any

-- | /O(n)/ Check if all elements are 'True'
--
-- ==== __Examples__
--
-- >>> import qualified Data.Vector as V
-- >>> V.and $ V.fromList [True, False]
-- False
-- >>> V.and V.empty
-- True
and :: Vector Bool -> Bool
{-# INLINE and #-}
and :: Vector Bool -> Bool
and = Vector Bool -> Bool
forall (v :: * -> *). Vector v Bool => v Bool -> Bool
G.and

-- | /O(n)/ Check if any element is 'True'
--
-- ==== __Examples__
--
-- >>> import qualified Data.Vector as V
-- >>> V.or $ V.fromList [True, False]
-- True
-- >>> V.or V.empty
-- False
or :: Vector Bool -> Bool
{-# INLINE or #-}
or :: Vector Bool -> Bool
or = Vector Bool -> Bool
forall (v :: * -> *). Vector v Bool => v Bool -> Bool
G.or

-- | /O(n)/ Compute the sum of the elements
--
-- ==== __Examples__
--
-- >>> import qualified Data.Vector as V
-- >>> V.sum $ V.fromList [300,20,1 :: Int]
-- 321
-- >>> V.sum (V.empty :: V.Vector Int)
-- 0
sum :: Num a => Vector a -> a
{-# INLINE sum #-}
sum :: Vector a -> a
sum = Vector a -> a
forall (v :: * -> *) a. (Vector v a, Num a) => v a -> a
G.sum

-- | /O(n)/ Compute the produce of the elements
--
-- ==== __Examples__
--
-- >>> import qualified Data.Vector as V
-- >>> V.product $ V.fromList [1,2,3,4 :: Int]
-- 24
-- >>> V.product (V.empty :: V.Vector Int)
-- 1
product :: Num a => Vector a -> a
{-# INLINE product #-}
product :: Vector a -> a
product = Vector a -> a
forall (v :: * -> *) a. (Vector v a, Num a) => v a -> a
G.product

-- | /O(n)/ Yield the maximum element of the vector. The vector may not be
-- empty.
--
-- ==== __Examples__
--
-- >>> import qualified Data.Vector as V
-- >>> V.maximum $ V.fromList [2.0, 1.0]
-- 2.0
maximum :: Ord a => Vector a -> a
{-# INLINE maximum #-}
maximum :: Vector a -> a
maximum = Vector a -> a
forall (v :: * -> *) a. (Vector v a, Ord a) => v a -> a
G.maximum

-- | /O(n)/ Yield the maximum element of the vector according to the given
-- comparison function. The vector may not be empty.
maximumBy :: (a -> a -> Ordering) -> Vector a -> a
{-# INLINE maximumBy #-}
maximumBy :: (a -> a -> Ordering) -> Vector a -> a
maximumBy = (a -> a -> Ordering) -> Vector a -> a
forall (v :: * -> *) a.
Vector v a =>
(a -> a -> Ordering) -> v a -> a
G.maximumBy

-- | /O(n)/ Yield the minimum element of the vector. The vector may not be
-- empty.
--
-- ==== __Examples__
--
-- >>> import qualified Data.Vector as V
-- >>> V.minimum $ V.fromList [2.0, 1.0]
-- 1.0
minimum :: Ord a => Vector a -> a
{-# INLINE minimum #-}
minimum :: Vector a -> a
minimum = Vector a -> a
forall (v :: * -> *) a. (Vector v a, Ord a) => v a -> a
G.minimum

-- | /O(n)/ Yield the minimum element of the vector according to the given
-- comparison function. The vector may not be empty.
minimumBy :: (a -> a -> Ordering) -> Vector a -> a
{-# INLINE minimumBy #-}
minimumBy :: (a -> a -> Ordering) -> Vector a -> a
minimumBy = (a -> a -> Ordering) -> Vector a -> a
forall (v :: * -> *) a.
Vector v a =>
(a -> a -> Ordering) -> v a -> a
G.minimumBy

-- | /O(n)/ Yield the index of the maximum element of the vector. The vector
-- may not be empty.
maxIndex :: Ord a => Vector a -> Int
{-# INLINE maxIndex #-}
maxIndex :: Vector a -> Int
maxIndex = Vector a -> Int
forall (v :: * -> *) a. (Vector v a, Ord a) => v a -> Int
G.maxIndex

-- | /O(n)/ Yield the index of the maximum element of the vector according to
-- the given comparison function. The vector may not be empty.
maxIndexBy :: (a -> a -> Ordering) -> Vector a -> Int
{-# INLINE maxIndexBy #-}
maxIndexBy :: (a -> a -> Ordering) -> Vector a -> Int
maxIndexBy = (a -> a -> Ordering) -> Vector a -> Int
forall (v :: * -> *) a.
Vector v a =>
(a -> a -> Ordering) -> v a -> Int
G.maxIndexBy

-- | /O(n)/ Yield the index of the minimum element of the vector. The vector
-- may not be empty.
minIndex :: Ord a => Vector a -> Int
{-# INLINE minIndex #-}
minIndex :: Vector a -> Int
minIndex = Vector a -> Int
forall (v :: * -> *) a. (Vector v a, Ord a) => v a -> Int
G.minIndex

-- | /O(n)/ Yield the index of the minimum element of the vector according to
-- the given comparison function. The vector may not be empty.
minIndexBy :: (a -> a -> Ordering) -> Vector a -> Int
{-# INLINE minIndexBy #-}
minIndexBy :: (a -> a -> Ordering) -> Vector a -> Int
minIndexBy = (a -> a -> Ordering) -> Vector a -> Int
forall (v :: * -> *) a.
Vector v a =>
(a -> a -> Ordering) -> v a -> Int
G.minIndexBy

-- Monadic folds
-- -------------

-- | /O(n)/ Monadic fold
foldM :: Monad m => (a -> b -> m a) -> a -> Vector b -> m a
{-# INLINE foldM #-}
foldM :: (a -> b -> m a) -> a -> Vector b -> m a
foldM = (a -> b -> m a) -> a -> Vector b -> m a
forall (m :: * -> *) (v :: * -> *) b a.
(Monad m, Vector v b) =>
(a -> b -> m a) -> a -> v b -> m a
G.foldM

-- | /O(n)/ Monadic fold (action applied to each element and its index)
ifoldM :: Monad m => (a -> Int -> b -> m a) -> a -> Vector b -> m a
{-# INLINE ifoldM #-}
ifoldM :: (a -> Int -> b -> m a) -> a -> Vector b -> m a
ifoldM = (a -> Int -> b -> m a) -> a -> Vector b -> m a
forall (m :: * -> *) (v :: * -> *) b a.
(Monad m, Vector v b) =>
(a -> Int -> b -> m a) -> a -> v b -> m a
G.ifoldM

-- | /O(n)/ Monadic fold over non-empty vectors
fold1M :: Monad m => (a -> a -> m a) -> Vector a -> m a
{-# INLINE fold1M #-}
fold1M :: (a -> a -> m a) -> Vector a -> m a
fold1M = (a -> a -> m a) -> Vector a -> m a
forall (m :: * -> *) (v :: * -> *) a.
(Monad m, Vector v a) =>
(a -> a -> m a) -> v a -> m a
G.fold1M

-- | /O(n)/ Monadic fold with strict accumulator
foldM' :: Monad m => (a -> b -> m a) -> a -> Vector b -> m a
{-# INLINE foldM' #-}
foldM' :: (a -> b -> m a) -> a -> Vector b -> m a
foldM' = (a -> b -> m a) -> a -> Vector b -> m a
forall (m :: * -> *) (v :: * -> *) b a.
(Monad m, Vector v b) =>
(a -> b -> m a) -> a -> v b -> m a
G.foldM'

-- | /O(n)/ Monadic fold with strict accumulator (action applied to each
-- element and its index)
ifoldM' :: Monad m => (a -> Int -> b -> m a) -> a -> Vector b -> m a
{-# INLINE ifoldM' #-}
ifoldM' :: (a -> Int -> b -> m a) -> a -> Vector b -> m a
ifoldM' = (a -> Int -> b -> m a) -> a -> Vector b -> m a
forall (m :: * -> *) (v :: * -> *) b a.
(Monad m, Vector v b) =>
(a -> Int -> b -> m a) -> a -> v b -> m a
G.ifoldM'

-- | /O(n)/ Monadic fold over non-empty vectors with strict accumulator
fold1M' :: Monad m => (a -> a -> m a) -> Vector a -> m a
{-# INLINE fold1M' #-}
fold1M' :: (a -> a -> m a) -> Vector a -> m a
fold1M' = (a -> a -> m a) -> Vector a -> m a
forall (m :: * -> *) (v :: * -> *) a.
(Monad m, Vector v a) =>
(a -> a -> m a) -> v a -> m a
G.fold1M'

-- | /O(n)/ Monadic fold that discards the result
foldM_ :: Monad m => (a -> b -> m a) -> a -> Vector b -> m ()
{-# INLINE foldM_ #-}
foldM_ :: (a -> b -> m a) -> a -> Vector b -> m ()
foldM_ = (a -> b -> m a) -> a -> Vector b -> m ()
forall (m :: * -> *) (v :: * -> *) b a.
(Monad m, Vector v b) =>
(a -> b -> m a) -> a -> v b -> m ()
G.foldM_

-- | /O(n)/ Monadic fold that discards the result (action applied to each
-- element and its index)
ifoldM_ :: Monad m => (a -> Int -> b -> m a) -> a -> Vector b -> m ()
{-# INLINE ifoldM_ #-}
ifoldM_ :: (a -> Int -> b -> m a) -> a -> Vector b -> m ()
ifoldM_ = (a -> Int -> b -> m a) -> a -> Vector b -> m ()
forall (m :: * -> *) (v :: * -> *) b a.
(Monad m, Vector v b) =>
(a -> Int -> b -> m a) -> a -> v b -> m ()
G.ifoldM_

-- | /O(n)/ Monadic fold over non-empty vectors that discards the result
fold1M_ :: Monad m => (a -> a -> m a) -> Vector a -> m ()
{-# INLINE fold1M_ #-}
fold1M_ :: (a -> a -> m a) -> Vector a -> m ()
fold1M_ = (a -> a -> m a) -> Vector a -> m ()
forall (m :: * -> *) (v :: * -> *) a.
(Monad m, Vector v a) =>
(a -> a -> m a) -> v a -> m ()
G.fold1M_

-- | /O(n)/ Monadic fold with strict accumulator that discards the result
foldM'_ :: Monad m => (a -> b -> m a) -> a -> Vector b -> m ()
{-# INLINE foldM'_ #-}
foldM'_ :: (a -> b -> m a) -> a -> Vector b -> m ()
foldM'_ = (a -> b -> m a) -> a -> Vector b -> m ()
forall (m :: * -> *) (v :: * -> *) b a.
(Monad m, Vector v b) =>
(a -> b -> m a) -> a -> v b -> m ()
G.foldM'_

-- | /O(n)/ Monadic fold with strict accumulator that discards the result
-- (action applied to each element and its index)
ifoldM'_ :: Monad m => (a -> Int -> b -> m a) -> a -> Vector b -> m ()
{-# INLINE ifoldM'_ #-}
ifoldM'_ :: (a -> Int -> b -> m a) -> a -> Vector b -> m ()
ifoldM'_ = (a -> Int -> b -> m a) -> a -> Vector b -> m ()
forall (m :: * -> *) (v :: * -> *) b a.
(Monad m, Vector v b) =>
(a -> Int -> b -> m a) -> a -> v b -> m ()
G.ifoldM'_

-- | /O(n)/ Monadic fold over non-empty vectors with strict accumulator
-- that discards the result
fold1M'_ :: Monad m => (a -> a -> m a) -> Vector a -> m ()
{-# INLINE fold1M'_ #-}
fold1M'_ :: (a -> a -> m a) -> Vector a -> m ()
fold1M'_ = (a -> a -> m a) -> Vector a -> m ()
forall (m :: * -> *) (v :: * -> *) a.
(Monad m, Vector v a) =>
(a -> a -> m a) -> v a -> m ()
G.fold1M'_

-- Monadic sequencing
-- ------------------

-- | Evaluate each action and collect the results
sequence :: Monad m => Vector (m a) -> m (Vector a)
{-# INLINE sequence #-}
sequence :: Vector (m a) -> m (Vector a)
sequence = Vector (m a) -> m (Vector a)
forall (m :: * -> *) (v :: * -> *) a.
(Monad m, Vector v a, Vector v (m a)) =>
v (m a) -> m (v a)
G.sequence

-- | Evaluate each action and discard the results
sequence_ :: Monad m => Vector (m a) -> m ()
{-# INLINE sequence_ #-}
sequence_ :: Vector (m a) -> m ()
sequence_ = Vector (m a) -> m ()
forall (m :: * -> *) (v :: * -> *) a.
(Monad m, Vector v (m a)) =>
v (m a) -> m ()
G.sequence_

-- Prefix sums (scans)
-- -------------------

-- | /O(n)/ Prescan
--
-- @
-- prescanl f z = 'init' . 'scanl' f z
-- @
--
-- Example: @prescanl (+) 0 \<1,2,3,4\> = \<0,1,3,6\>@
--
prescanl :: (a -> b -> a) -> a -> Vector b -> Vector a
{-# INLINE prescanl #-}
prescanl :: (a -> b -> a) -> a -> Vector b -> Vector a
prescanl = (a -> b -> a) -> a -> Vector b -> Vector a
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> b -> a) -> a -> v b -> v a
G.prescanl

-- | /O(n)/ Prescan with strict accumulator
prescanl' :: (a -> b -> a) -> a -> Vector b -> Vector a
{-# INLINE prescanl' #-}
prescanl' :: (a -> b -> a) -> a -> Vector b -> Vector a
prescanl' = (a -> b -> a) -> a -> Vector b -> Vector a
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> b -> a) -> a -> v b -> v a
G.prescanl'

-- | /O(n)/ Scan
--
-- @
-- postscanl f z = 'tail' . 'scanl' f z
-- @
--
-- Example: @postscanl (+) 0 \<1,2,3,4\> = \<1,3,6,10\>@
--
postscanl :: (a -> b -> a) -> a -> Vector b -> Vector a
{-# INLINE postscanl #-}
postscanl :: (a -> b -> a) -> a -> Vector b -> Vector a
postscanl = (a -> b -> a) -> a -> Vector b -> Vector a
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> b -> a) -> a -> v b -> v a
G.postscanl

-- | /O(n)/ Scan with strict accumulator
postscanl' :: (a -> b -> a) -> a -> Vector b -> Vector a
{-# INLINE postscanl' #-}
postscanl' :: (a -> b -> a) -> a -> Vector b -> Vector a
postscanl' = (a -> b -> a) -> a -> Vector b -> Vector a
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> b -> a) -> a -> v b -> v a
G.postscanl'

-- | /O(n)/ Haskell-style scan
--
-- > scanl f z <x1,...,xn> = <y1,...,y(n+1)>
-- >   where y1 = z
-- >         yi = f y(i-1) x(i-1)
--
-- Example: @scanl (+) 0 \<1,2,3,4\> = \<0,1,3,6,10\>@
--
scanl :: (a -> b -> a) -> a -> Vector b -> Vector a
{-# INLINE scanl #-}
scanl :: (a -> b -> a) -> a -> Vector b -> Vector a
scanl = (a -> b -> a) -> a -> Vector b -> Vector a
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> b -> a) -> a -> v b -> v a
G.scanl

-- | /O(n)/ Haskell-style scan with strict accumulator
scanl' :: (a -> b -> a) -> a -> Vector b -> Vector a
{-# INLINE scanl' #-}
scanl' :: (a -> b -> a) -> a -> Vector b -> Vector a
scanl' = (a -> b -> a) -> a -> Vector b -> Vector a
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> b -> a) -> a -> v b -> v a
G.scanl'

-- | /O(n)/ Scan over a vector with its index
--
-- @since 0.12.0.0
iscanl :: (Int -> a -> b -> a) -> a -> Vector b -> Vector a
{-# INLINE iscanl #-}
iscanl :: (Int -> a -> b -> a) -> a -> Vector b -> Vector a
iscanl = (Int -> a -> b -> a) -> a -> Vector b -> Vector a
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(Int -> a -> b -> a) -> a -> v b -> v a
G.iscanl

-- | /O(n)/ Scan over a vector (strictly) with its index
--
-- @since 0.12.0.0
iscanl' :: (Int -> a -> b -> a) -> a -> Vector b -> Vector a
{-# INLINE iscanl' #-}
iscanl' :: (Int -> a -> b -> a) -> a -> Vector b -> Vector a
iscanl' = (Int -> a -> b -> a) -> a -> Vector b -> Vector a
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(Int -> a -> b -> a) -> a -> v b -> v a
G.iscanl'

-- | /O(n)/ Scan over a non-empty vector
--
-- > scanl f <x1,...,xn> = <y1,...,yn>
-- >   where y1 = x1
-- >         yi = f y(i-1) xi
--
scanl1 :: (a -> a -> a) -> Vector a -> Vector a
{-# INLINE scanl1 #-}
scanl1 :: (a -> a -> a) -> Vector a -> Vector a
scanl1 = (a -> a -> a) -> Vector a -> Vector a
forall (v :: * -> *) a. Vector v a => (a -> a -> a) -> v a -> v a
G.scanl1

-- | /O(n)/ Scan over a non-empty vector with a strict accumulator
scanl1' :: (a -> a -> a) -> Vector a -> Vector a
{-# INLINE scanl1' #-}
scanl1' :: (a -> a -> a) -> Vector a -> Vector a
scanl1' = (a -> a -> a) -> Vector a -> Vector a
forall (v :: * -> *) a. Vector v a => (a -> a -> a) -> v a -> v a
G.scanl1'

-- | /O(n)/ Right-to-left prescan
--
-- @
-- prescanr f z = 'reverse' . 'prescanl' (flip f) z . 'reverse'
-- @
--
prescanr :: (a -> b -> b) -> b -> Vector a -> Vector b
{-# INLINE prescanr #-}
prescanr :: (a -> b -> b) -> b -> Vector a -> Vector b
prescanr = (a -> b -> b) -> b -> Vector a -> Vector b
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> b -> b) -> b -> v a -> v b
G.prescanr

-- | /O(n)/ Right-to-left prescan with strict accumulator
prescanr' :: (a -> b -> b) -> b -> Vector a -> Vector b
{-# INLINE prescanr' #-}
prescanr' :: (a -> b -> b) -> b -> Vector a -> Vector b
prescanr' = (a -> b -> b) -> b -> Vector a -> Vector b
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> b -> b) -> b -> v a -> v b
G.prescanr'

-- | /O(n)/ Right-to-left scan
postscanr :: (a -> b -> b) -> b -> Vector a -> Vector b
{-# INLINE postscanr #-}
postscanr :: (a -> b -> b) -> b -> Vector a -> Vector b
postscanr = (a -> b -> b) -> b -> Vector a -> Vector b
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> b -> b) -> b -> v a -> v b
G.postscanr

-- | /O(n)/ Right-to-left scan with strict accumulator
postscanr' :: (a -> b -> b) -> b -> Vector a -> Vector b
{-# INLINE postscanr' #-}
postscanr' :: (a -> b -> b) -> b -> Vector a -> Vector b
postscanr' = (a -> b -> b) -> b -> Vector a -> Vector b
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> b -> b) -> b -> v a -> v b
G.postscanr'

-- | /O(n)/ Right-to-left Haskell-style scan
scanr :: (a -> b -> b) -> b -> Vector a -> Vector b
{-# INLINE scanr #-}
scanr :: (a -> b -> b) -> b -> Vector a -> Vector b
scanr = (a -> b -> b) -> b -> Vector a -> Vector b
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> b -> b) -> b -> v a -> v b
G.scanr

-- | /O(n)/ Right-to-left Haskell-style scan with strict accumulator
scanr' :: (a -> b -> b) -> b -> Vector a -> Vector b
{-# INLINE scanr' #-}
scanr' :: (a -> b -> b) -> b -> Vector a -> Vector b
scanr' = (a -> b -> b) -> b -> Vector a -> Vector b
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> b -> b) -> b -> v a -> v b
G.scanr'

-- | /O(n)/ Right-to-left scan over a vector with its index
--
-- @since 0.12.0.0
iscanr :: (Int -> a -> b -> b) -> b -> Vector a -> Vector b
{-# INLINE iscanr #-}
iscanr :: (Int -> a -> b -> b) -> b -> Vector a -> Vector b
iscanr = (Int -> a -> b -> b) -> b -> Vector a -> Vector b
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(Int -> a -> b -> b) -> b -> v a -> v b
G.iscanr

-- | /O(n)/ Right-to-left scan over a vector (strictly) with its index
--
-- @since 0.12.0.0
iscanr' :: (Int -> a -> b -> b) -> b -> Vector a -> Vector b
{-# INLINE iscanr' #-}
iscanr' :: (Int -> a -> b -> b) -> b -> Vector a -> Vector b
iscanr' = (Int -> a -> b -> b) -> b -> Vector a -> Vector b
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(Int -> a -> b -> b) -> b -> v a -> v b
G.iscanr'

-- | /O(n)/ Right-to-left scan over a non-empty vector
scanr1 :: (a -> a -> a) -> Vector a -> Vector a
{-# INLINE scanr1 #-}
scanr1 :: (a -> a -> a) -> Vector a -> Vector a
scanr1 = (a -> a -> a) -> Vector a -> Vector a
forall (v :: * -> *) a. Vector v a => (a -> a -> a) -> v a -> v a
G.scanr1

-- | /O(n)/ Right-to-left scan over a non-empty vector with a strict
-- accumulator
scanr1' :: (a -> a -> a) -> Vector a -> Vector a
{-# INLINE scanr1' #-}
scanr1' :: (a -> a -> a) -> Vector a -> Vector a
scanr1' = (a -> a -> a) -> Vector a -> Vector a
forall (v :: * -> *) a. Vector v a => (a -> a -> a) -> v a -> v a
G.scanr1'

-- Comparisons
-- ------------------------

-- | /O(n)/ Check if two vectors are equal using supplied equality
-- predicate.
--
-- @since 0.12.2.0
eqBy :: (a -> b -> Bool) -> Vector a -> Vector b -> Bool
{-# INLINE eqBy #-}
eqBy :: (a -> b -> Bool) -> Vector a -> Vector b -> Bool
eqBy = (a -> b -> Bool) -> Vector a -> Vector b -> Bool
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> b -> Bool) -> v a -> v b -> Bool
G.eqBy

-- | /O(n)/ Compare two vectors using supplied comparison function for
-- vector elements. Comparison works same as for lists.
--
-- > cmpBy compare == compare
--
-- @since 0.12.2.0
cmpBy :: (a -> b -> Ordering) -> Vector a -> Vector b -> Ordering
cmpBy :: (a -> b -> Ordering) -> Vector a -> Vector b -> Ordering
cmpBy = (a -> b -> Ordering) -> Vector a -> Vector b -> Ordering
forall (v :: * -> *) a b.
(Vector v a, Vector v b) =>
(a -> b -> Ordering) -> v a -> v b -> Ordering
G.cmpBy

-- Conversions - Lists
-- ------------------------

-- | /O(n)/ Convert a vector to a list
toList :: Vector a -> [a]
{-# INLINE toList #-}
toList :: Vector a -> [a]
toList = Vector a -> [a]
forall (v :: * -> *) a. Vector v a => v a -> [a]
G.toList

-- | /O(n)/ Convert a list to a vector
fromList :: [a] -> Vector a
{-# INLINE fromList #-}
fromList :: [a] -> Vector a
fromList = [a] -> Vector a
forall (v :: * -> *) a. Vector v a => [a] -> v a
G.fromList

-- | /O(n)/ Convert the first @n@ elements of a list to a vector
--
-- @
-- fromListN n xs = 'fromList' ('take' n xs)
-- @
fromListN :: Int -> [a] -> Vector a
{-# INLINE fromListN #-}
fromListN :: Int -> [a] -> Vector a
fromListN = Int -> [a] -> Vector a
forall (v :: * -> *) a. Vector v a => Int -> [a] -> v a
G.fromListN

-- Conversions - Arrays
-- -----------------------------

-- | /O(1)/ Convert an array to a vector.
--
-- @since 0.12.2.0
fromArray :: Array a -> Vector a
{-# INLINE fromArray #-}
fromArray :: Array a -> Vector a
fromArray Array a
x = Int -> Int -> Array a -> Vector a
forall a. Int -> Int -> Array a -> Vector a
Vector Int
0 (Array a -> Int
forall a. Array a -> Int
sizeofArray Array a
x) Array a
x

-- | /O(n)/ Convert a vector to an array.
--
-- @since 0.12.2.0
toArray :: Vector a -> Array a
{-# INLINE toArray #-}
toArray :: Vector a -> Array a
toArray (Vector Int
offset Int
size Array a
arr)
  | Int
offset Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 Bool -> Bool -> Bool
&& Int
size Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Array a -> Int
forall a. Array a -> Int
sizeofArray Array a
arr = Array a
arr
  | Bool
otherwise = Array a -> Int -> Int -> Array a
forall a. Array a -> Int -> Int -> Array a
cloneArray Array a
arr Int
offset Int
size

-- Conversions - Mutable vectors
-- -----------------------------

-- | /O(1)/ Unsafe convert a mutable vector to an immutable one without
-- copying. The mutable vector may not be used after this operation.
unsafeFreeze :: PrimMonad m => MVector (PrimState m) a -> m (Vector a)
{-# INLINE unsafeFreeze #-}
unsafeFreeze :: MVector (PrimState m) a -> m (Vector a)
unsafeFreeze = MVector (PrimState m) a -> m (Vector a)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Mutable v (PrimState m) a -> m (v a)
G.unsafeFreeze

-- | /O(1)/ Unsafely convert an immutable vector to a mutable one without
-- copying. The immutable vector may not be used after this operation.
unsafeThaw :: PrimMonad m => Vector a -> m (MVector (PrimState m) a)
{-# INLINE unsafeThaw #-}
unsafeThaw :: Vector a -> m (MVector (PrimState m) a)
unsafeThaw = Vector a -> m (MVector (PrimState m) a)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
v a -> m (Mutable v (PrimState m) a)
G.unsafeThaw

-- | /O(n)/ Yield a mutable copy of the immutable vector.
thaw :: PrimMonad m => Vector a -> m (MVector (PrimState m) a)
{-# INLINE thaw #-}
thaw :: Vector a -> m (MVector (PrimState m) a)
thaw = Vector a -> m (MVector (PrimState m) a)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
v a -> m (Mutable v (PrimState m) a)
G.thaw

-- | /O(n)/ Yield an immutable copy of the mutable vector.
freeze :: PrimMonad m => MVector (PrimState m) a -> m (Vector a)
{-# INLINE freeze #-}
freeze :: MVector (PrimState m) a -> m (Vector a)
freeze = MVector (PrimState m) a -> m (Vector a)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Mutable v (PrimState m) a -> m (v a)
G.freeze

-- | /O(n)/ Copy an immutable vector into a mutable one. The two vectors must
-- have the same length. This is not checked.
unsafeCopy :: PrimMonad m => MVector (PrimState m) a -> Vector a -> m ()
{-# INLINE unsafeCopy #-}
unsafeCopy :: MVector (PrimState m) a -> Vector a -> m ()
unsafeCopy = MVector (PrimState m) a -> Vector a -> m ()
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Mutable v (PrimState m) a -> v a -> m ()
G.unsafeCopy

-- | /O(n)/ Copy an immutable vector into a mutable one. The two vectors must
-- have the same length.
copy :: PrimMonad m => MVector (PrimState m) a -> Vector a -> m ()
{-# INLINE copy #-}
copy :: MVector (PrimState m) a -> Vector a -> m ()
copy = MVector (PrimState m) a -> Vector a -> m ()
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
Mutable v (PrimState m) a -> v a -> m ()
G.copy