module Data.Vector.Instances () where
import Prelude hiding ((++), drop, length)
import Control.Applicative
import Control.Monad
import Data.Semigroup
#ifdef MIN_VERSION_hashable
import Data.Hashable (Hashable(..))
#endif
import Data.Key
import Data.Functor.Bind
import Data.Functor.Extend
import Data.Functor.Plus
import Data.Pointed
import Data.Monoid (Monoid(..))
import qualified Data.Vector as Vector
import qualified Data.Vector.Generic as G
#if MIN_VERSION_vector(0,11,0)
import qualified Data.Vector.Fusion.Bundle as Stream
import Data.Vector.Fusion.Bundle.Size
#else
import qualified Data.Vector.Fusion.Stream as Stream
import Data.Vector.Fusion.Stream.Size
#endif
import Data.Vector (Vector,(++),drop,length,imap,ifoldr, ifoldl, izipWith,(!?),(//), generate)
import qualified Data.Vector as Vector
import qualified Data.Vector.Unboxed as Unboxed
import qualified Data.Vector.Storable as Storable
import qualified Data.Vector.Primitive as Primitive
type instance Key Vector = Int
instance Keyed Vector where
mapWithKey = Vector.imap
instance Zip Vector where
zipWith = Vector.zipWith
instance ZipWithKey Vector where
zipWithKey = Vector.izipWith
instance Indexable Vector where
index = (Vector.!)
instance Lookup Vector where
lookup = flip (!?)
instance Adjustable Vector where
adjust f n v = case v !? n of
Just a -> v // [(n, f a)]
Nothing -> v
replace n a v = v // [(n,a)]
instance FoldableWithKey Vector where
foldrWithKey = Vector.ifoldr
foldlWithKey = Vector.ifoldl
instance Apply Vector where
fs <.> as =
G.unstream $ Stream.sized results (Exact n)
where
n = Vector.length fs * Vector.length as
results = Stream.concatMap body $ G.stream fs
body f = Stream.map f $ G.stream as
instance Pointed Vector where
point = Vector.singleton
instance Bind Vector where
v >>- f = Vector.concatMap f v
instance Alt Vector where
(<!>) = (++)
instance Plus Vector where
zero = Vector.empty
instance TraversableWithKey Vector where
traverseWithKey f v
= Vector.fromListN (Vector.length v) <$> traverseWithKey f (Vector.toList v)
instance Extend Vector where
duplicated v = generate (length v) (`drop` v)
extended f v = generate (length v) (\n -> f (drop n v))
#if !(MIN_VERSION_vector(0,12,0))
instance Semigroup (Vector a) where
(<>) = (++)
instance Unboxed.Unbox a => Semigroup (Unboxed.Vector a) where
(<>) = (Unboxed.++)
instance Storable.Storable a => Semigroup (Storable.Vector a) where
(<>) = (Storable.++)
instance Primitive.Prim a => Semigroup (Primitive.Vector a) where
(<>) = (Primitive.++)
#endif
#ifdef MIN_VERSION_hashable
instance (Hashable a) => Hashable (Vector a) where
hashWithSalt salt = hashWithSalt salt . Vector.toList
instance (Unboxed.Unbox a, Hashable a) => Hashable (Unboxed.Vector a) where
hashWithSalt salt = hashWithSalt salt . Unboxed.toList
instance (Storable.Storable a, Hashable a) => Hashable (Storable.Vector a) where
hashWithSalt salt = hashWithSalt salt . Storable.toList
instance (Primitive.Prim a, Hashable a) => Hashable (Primitive.Vector a) where
hashWithSalt salt = hashWithSalt salt . Primitive.toList
#endif