{-# LANGUAGE CPP #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE MultiParamTypeClasses, FlexibleContexts, FlexibleInstances, UndecidableInstances #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RoleAnnotations #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE DeriveGeneric #-}
#ifndef MIN_VERSION_hashable
#define MIN_VERSION_hashable(x,y,z) 1
#endif
#ifndef MIN_VERSION_reflection
#define MIN_VERSION_reflection(x,y,z) 1
#endif
#ifndef MIN_VERSION_transformers
#define MIN_VERSION_transformers(x,y,z) 1
#endif
#ifndef MIN_VERSION_base
#define MIN_VERSION_base(x,y,z) 1
#endif
module Linear.V
( V(V,toVector)
#ifdef MIN_VERSION_template_haskell
, int
#endif
, dim
, Dim(..)
, reifyDim
, reifyVector
, reifyDimNat
, reifyVectorNat
, fromVector
, Finite(..)
, _V, _V'
) where
import Control.Applicative
import Control.DeepSeq (NFData)
import Control.Monad
import Control.Monad.Fix
import Control.Monad.Trans.State
import Control.Monad.Zip
import Control.Lens as Lens
import Data.Binary as Binary
import Data.Bytes.Serial
import Data.Complex
import Data.Data
import Data.Distributive
import Data.Foldable as Foldable
import qualified Data.Foldable.WithIndex as WithIndex
import Data.Functor.Bind
import Data.Functor.Classes
import Data.Functor.Rep as Rep
import qualified Data.Functor.WithIndex as WithIndex
import Data.Hashable
import Data.Hashable.Lifted
import Data.Kind
import Data.Reflection as R
import Data.Serialize as Cereal
import qualified Data.Traversable.WithIndex as WithIndex
import qualified Data.Vector as V
import Data.Vector (Vector)
import qualified Data.Vector.Generic as G
import qualified Data.Vector.Unboxed as U
import qualified Data.Vector.Generic.Mutable as M
import Foreign.Ptr
import Foreign.Storable
import GHC.TypeLits
import GHC.Generics (Generic, Generic1)
#if !(MIN_VERSION_reflection(1,3,0)) && defined(MIN_VERSION_template_haskell)
import Language.Haskell.TH
#endif
import Linear.Epsilon
import Linear.Metric
import Linear.Vector
import Prelude as P
#if !(MIN_VERSION_base(4,11,0))
import Data.Semigroup
#endif
import System.Random (Random(..))
class Dim n where
reflectDim :: p n -> Int
type role V nominal representational
class Finite v where
type Size (v :: Type -> Type) :: Nat
toV :: v a -> V (Size v) a
default toV :: Foldable v => v a -> V (Size v) a
toV = Vector a -> V (Size v) a
forall k (n :: k) a. Vector a -> V n a
V (Vector a -> V (Size v) a)
-> (v a -> Vector a) -> v a -> V (Size v) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> Vector a
forall a. [a] -> Vector a
V.fromList ([a] -> Vector a) -> (v a -> [a]) -> v a -> Vector a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
Foldable.toList
fromV :: V (Size v) a -> v a
instance Finite Complex where
type Size Complex = 2
toV :: Complex a -> V (Size Complex) a
toV (a
a :+ a
b) = Vector a -> V 2 a
forall k (n :: k) a. Vector a -> V n a
V (Int -> [a] -> Vector a
forall a. Int -> [a] -> Vector a
V.fromListN Int
2 [a
a, a
b])
fromV :: V (Size Complex) a -> Complex a
fromV (V Vector a
v) = (Vector a
v Vector a -> Int -> a
forall a. Vector a -> Int -> a
V.! Int
0) a -> a -> Complex a
forall a. a -> a -> Complex a
:+ (Vector a
v Vector a -> Int -> a
forall a. Vector a -> Int -> a
V.! Int
1)
_V :: (Finite u, Finite v) => Iso (V (Size u) a) (V (Size v) b) (u a) (v b)
_V :: Iso (V (Size u) a) (V (Size v) b) (u a) (v b)
_V = (V (Size u) a -> u a)
-> (v b -> V (Size v) b)
-> Iso (V (Size u) a) (V (Size v) b) (u a) (v b)
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso V (Size u) a -> u a
forall (v :: * -> *) a. Finite v => V (Size v) a -> v a
fromV v b -> V (Size v) b
forall (v :: * -> *) a. Finite v => v a -> V (Size v) a
toV
_V' :: Finite v => Iso (V (Size v) a) (V (Size v) b) (v a) (v b)
_V' :: Iso (V (Size v) a) (V (Size v) b) (v a) (v b)
_V' = (V (Size v) a -> v a)
-> (v b -> V (Size v) b)
-> Iso (V (Size v) a) (V (Size v) b) (v a) (v b)
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso V (Size v) a -> v a
forall (v :: * -> *) a. Finite v => V (Size v) a -> v a
fromV v b -> V (Size v) b
forall (v :: * -> *) a. Finite v => v a -> V (Size v) a
toV
instance Finite (V (n :: Nat)) where
type Size (V n) = n
toV :: V n a -> V (Size (V n)) a
toV = V n a -> V (Size (V n)) a
forall a. a -> a
id
fromV :: V (Size (V n)) a -> V n a
fromV = V (Size (V n)) a -> V n a
forall a. a -> a
id
newtype V n a = V { V n a -> Vector a
toVector :: V.Vector a } deriving (V n a -> V n a -> Bool
(V n a -> V n a -> Bool) -> (V n a -> V n a -> Bool) -> Eq (V n a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall k (n :: k) a. Eq a => V n a -> V n a -> Bool
/= :: V n a -> V n a -> Bool
$c/= :: forall k (n :: k) a. Eq a => V n a -> V n a -> Bool
== :: V n a -> V n a -> Bool
$c== :: forall k (n :: k) a. Eq a => V n a -> V n a -> Bool
Eq,Eq (V n a)
Eq (V n a)
-> (V n a -> V n a -> Ordering)
-> (V n a -> V n a -> Bool)
-> (V n a -> V n a -> Bool)
-> (V n a -> V n a -> Bool)
-> (V n a -> V n a -> Bool)
-> (V n a -> V n a -> V n a)
-> (V n a -> V n a -> V n a)
-> Ord (V n a)
V n a -> V n a -> Bool
V n a -> V n a -> Ordering
V n a -> V n a -> V n a
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall k (n :: k) a. Ord a => Eq (V n a)
forall k (n :: k) a. Ord a => V n a -> V n a -> Bool
forall k (n :: k) a. Ord a => V n a -> V n a -> Ordering
forall k (n :: k) a. Ord a => V n a -> V n a -> V n a
min :: V n a -> V n a -> V n a
$cmin :: forall k (n :: k) a. Ord a => V n a -> V n a -> V n a
max :: V n a -> V n a -> V n a
$cmax :: forall k (n :: k) a. Ord a => V n a -> V n a -> V n a
>= :: V n a -> V n a -> Bool
$c>= :: forall k (n :: k) a. Ord a => V n a -> V n a -> Bool
> :: V n a -> V n a -> Bool
$c> :: forall k (n :: k) a. Ord a => V n a -> V n a -> Bool
<= :: V n a -> V n a -> Bool
$c<= :: forall k (n :: k) a. Ord a => V n a -> V n a -> Bool
< :: V n a -> V n a -> Bool
$c< :: forall k (n :: k) a. Ord a => V n a -> V n a -> Bool
compare :: V n a -> V n a -> Ordering
$ccompare :: forall k (n :: k) a. Ord a => V n a -> V n a -> Ordering
$cp1Ord :: forall k (n :: k) a. Ord a => Eq (V n a)
Ord,Int -> V n a -> ShowS
[V n a] -> ShowS
V n a -> String
(Int -> V n a -> ShowS)
-> (V n a -> String) -> ([V n a] -> ShowS) -> Show (V n a)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall k (n :: k) a. Show a => Int -> V n a -> ShowS
forall k (n :: k) a. Show a => [V n a] -> ShowS
forall k (n :: k) a. Show a => V n a -> String
showList :: [V n a] -> ShowS
$cshowList :: forall k (n :: k) a. Show a => [V n a] -> ShowS
show :: V n a -> String
$cshow :: forall k (n :: k) a. Show a => V n a -> String
showsPrec :: Int -> V n a -> ShowS
$cshowsPrec :: forall k (n :: k) a. Show a => Int -> V n a -> ShowS
Show,ReadPrec [V n a]
ReadPrec (V n a)
Int -> ReadS (V n a)
ReadS [V n a]
(Int -> ReadS (V n a))
-> ReadS [V n a]
-> ReadPrec (V n a)
-> ReadPrec [V n a]
-> Read (V n a)
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
forall k (n :: k) a. Read a => ReadPrec [V n a]
forall k (n :: k) a. Read a => ReadPrec (V n a)
forall k (n :: k) a. Read a => Int -> ReadS (V n a)
forall k (n :: k) a. Read a => ReadS [V n a]
readListPrec :: ReadPrec [V n a]
$creadListPrec :: forall k (n :: k) a. Read a => ReadPrec [V n a]
readPrec :: ReadPrec (V n a)
$creadPrec :: forall k (n :: k) a. Read a => ReadPrec (V n a)
readList :: ReadS [V n a]
$creadList :: forall k (n :: k) a. Read a => ReadS [V n a]
readsPrec :: Int -> ReadS (V n a)
$creadsPrec :: forall k (n :: k) a. Read a => Int -> ReadS (V n a)
Read,V n a -> ()
(V n a -> ()) -> NFData (V n a)
forall a. (a -> ()) -> NFData a
forall k (n :: k) a. NFData a => V n a -> ()
rnf :: V n a -> ()
$crnf :: forall k (n :: k) a. NFData a => V n a -> ()
NFData
,(forall x. V n a -> Rep (V n a) x)
-> (forall x. Rep (V n a) x -> V n a) -> Generic (V n a)
forall x. Rep (V n a) x -> V n a
forall x. V n a -> Rep (V n a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall k (n :: k) a x. Rep (V n a) x -> V n a
forall k (n :: k) a x. V n a -> Rep (V n a) x
$cto :: forall k (n :: k) a x. Rep (V n a) x -> V n a
$cfrom :: forall k (n :: k) a x. V n a -> Rep (V n a) x
Generic,(forall a. V n a -> Rep1 (V n) a)
-> (forall a. Rep1 (V n) a -> V n a) -> Generic1 (V n)
forall a. Rep1 (V n) a -> V n a
forall a. V n a -> Rep1 (V n) a
forall k (n :: k) a. Rep1 (V n) a -> V n a
forall k (n :: k) a. V n a -> Rep1 (V n) a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cto1 :: forall k (n :: k) a. Rep1 (V n) a -> V n a
$cfrom1 :: forall k (n :: k) a. V n a -> Rep1 (V n) a
Generic1
)
dim :: forall n a. Dim n => V n a -> Int
dim :: V n a -> Int
dim V n a
_ = Proxy n -> Int
forall k (n :: k) (p :: k -> *). Dim n => p n -> Int
reflectDim (Proxy n
forall k (t :: k). Proxy t
Proxy :: Proxy n)
{-# INLINE dim #-}
instance KnownNat n => Dim (n :: Nat) where
reflectDim :: p n -> Int
reflectDim = Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Integer -> Int) -> (p n -> Integer) -> p n -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p n -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal
{-# INLINE reflectDim #-}
instance (Dim n, Random a) => Random (V n a) where
random :: g -> (V n a, g)
random = State g (V n a) -> g -> (V n a, g)
forall s a. State s a -> s -> (a, s)
runState (Vector a -> V n a
forall k (n :: k) a. Vector a -> V n a
V (Vector a -> V n a)
-> StateT g Identity (Vector a) -> State g (V n a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> StateT g Identity a -> StateT g Identity (Vector a)
forall (m :: * -> *) a. Monad m => Int -> m a -> m (Vector a)
V.replicateM (Proxy n -> Int
forall k (n :: k) (p :: k -> *). Dim n => p n -> Int
reflectDim (Proxy n
forall k (t :: k). Proxy t
Proxy :: Proxy n)) ((g -> (a, g)) -> StateT g Identity a
forall (m :: * -> *) s a. Monad m => (s -> (a, s)) -> StateT s m a
state g -> (a, g)
forall a g. (Random a, RandomGen g) => g -> (a, g)
random))
randomR :: (V n a, V n a) -> g -> (V n a, g)
randomR (V Vector a
ls,V Vector a
hs) = State g (V n a) -> g -> (V n a, g)
forall s a. State s a -> s -> (a, s)
runState (Vector a -> V n a
forall k (n :: k) a. Vector a -> V n a
V (Vector a -> V n a)
-> StateT g Identity (Vector a) -> State g (V n a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> a -> StateT g Identity a)
-> Vector a -> Vector a -> StateT g Identity (Vector a)
forall (m :: * -> *) a b c.
Monad m =>
(a -> b -> m c) -> Vector a -> Vector b -> m (Vector c)
V.zipWithM (\a
l a
h -> (g -> (a, g)) -> StateT g Identity a
forall (m :: * -> *) s a. Monad m => (s -> (a, s)) -> StateT s m a
state ((g -> (a, g)) -> StateT g Identity a)
-> (g -> (a, g)) -> StateT g Identity a
forall a b. (a -> b) -> a -> b
$ (a, a) -> g -> (a, g)
forall a g. (Random a, RandomGen g) => (a, a) -> g -> (a, g)
randomR (a
l,a
h)) Vector a
ls Vector a
hs)
data ReifiedDim (s :: Type)
retagDim :: (Proxy s -> a) -> proxy (ReifiedDim s) -> a
retagDim :: (Proxy s -> a) -> proxy (ReifiedDim s) -> a
retagDim Proxy s -> a
f proxy (ReifiedDim s)
_ = Proxy s -> a
f Proxy s
forall k (t :: k). Proxy t
Proxy
{-# INLINE retagDim #-}
instance Reifies s Int => Dim (ReifiedDim s) where
reflectDim :: p (ReifiedDim s) -> Int
reflectDim = (Proxy s -> Int) -> p (ReifiedDim s) -> Int
forall s a (proxy :: * -> *).
(Proxy s -> a) -> proxy (ReifiedDim s) -> a
retagDim Proxy s -> Int
forall k (s :: k) a (proxy :: k -> *). Reifies s a => proxy s -> a
reflect
{-# INLINE reflectDim #-}
reifyDimNat :: Int -> (forall (n :: Nat). KnownNat n => Proxy n -> r) -> r
reifyDimNat :: Int -> (forall (n :: Nat). KnownNat n => Proxy n -> r) -> r
reifyDimNat Int
i forall (n :: Nat). KnownNat n => Proxy n -> r
f = Integer -> (forall (n :: Nat). KnownNat n => Proxy n -> r) -> r
forall r.
Integer -> (forall (n :: Nat). KnownNat n => Proxy n -> r) -> r
R.reifyNat (Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i) forall (n :: Nat). KnownNat n => Proxy n -> r
f
{-# INLINE reifyDimNat #-}
reifyVectorNat :: forall a r. Vector a -> (forall (n :: Nat). KnownNat n => V n a -> r) -> r
reifyVectorNat :: Vector a -> (forall (n :: Nat). KnownNat n => V n a -> r) -> r
reifyVectorNat Vector a
v forall (n :: Nat). KnownNat n => V n a -> r
f = Integer -> (forall (n :: Nat). KnownNat n => Proxy n -> r) -> r
forall r.
Integer -> (forall (n :: Nat). KnownNat n => Proxy n -> r) -> r
reifyNat (Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Integer) -> Int -> Integer
forall a b. (a -> b) -> a -> b
$ Vector a -> Int
forall a. Vector a -> Int
V.length Vector a
v) ((forall (n :: Nat). KnownNat n => Proxy n -> r) -> r)
-> (forall (n :: Nat). KnownNat n => Proxy n -> r) -> r
forall a b. (a -> b) -> a -> b
$ \(Proxy n
Proxy :: Proxy n) -> V n a -> r
forall (n :: Nat). KnownNat n => V n a -> r
f (Vector a -> V n a
forall k (n :: k) a. Vector a -> V n a
V Vector a
v :: V n a)
{-# INLINE reifyVectorNat #-}
reifyDim :: Int -> (forall (n :: Type). Dim n => Proxy n -> r) -> r
reifyDim :: Int -> (forall n. Dim n => Proxy n -> r) -> r
reifyDim Int
i forall n. Dim n => Proxy n -> r
f = Int -> (forall s. Reifies s Int => Proxy s -> r) -> r
forall a r. a -> (forall s. Reifies s a => Proxy s -> r) -> r
R.reify Int
i ((Proxy (ReifiedDim s) -> r) -> Proxy s -> r
forall n a (proxy :: * -> *).
(Proxy (ReifiedDim n) -> a) -> proxy n -> a
go Proxy (ReifiedDim s) -> r
forall n. Dim n => Proxy n -> r
f) where
go :: (Proxy (ReifiedDim n) -> a) -> proxy n -> a
go :: (Proxy (ReifiedDim n) -> a) -> proxy n -> a
go Proxy (ReifiedDim n) -> a
g proxy n
_ = Proxy (ReifiedDim n) -> a
g Proxy (ReifiedDim n)
forall k (t :: k). Proxy t
Proxy
{-# INLINE reifyDim #-}
reifyVector :: forall a r. Vector a -> (forall (n :: Type). Dim n => V n a -> r) -> r
reifyVector :: Vector a -> (forall n. Dim n => V n a -> r) -> r
reifyVector Vector a
v forall n. Dim n => V n a -> r
f = Int -> (forall n. Dim n => Proxy n -> r) -> r
forall r. Int -> (forall n. Dim n => Proxy n -> r) -> r
reifyDim (Vector a -> Int
forall a. Vector a -> Int
V.length Vector a
v) ((forall n. Dim n => Proxy n -> r) -> r)
-> (forall n. Dim n => Proxy n -> r) -> r
forall a b. (a -> b) -> a -> b
$ \(Proxy n
Proxy :: Proxy n) -> V n a -> r
forall n. Dim n => V n a -> r
f (Vector a -> V n a
forall k (n :: k) a. Vector a -> V n a
V Vector a
v :: V n a)
{-# INLINE reifyVector #-}
instance Dim n => Dim (V n a) where
reflectDim :: p (V n a) -> Int
reflectDim p (V n a)
_ = Proxy n -> Int
forall k (n :: k) (p :: k -> *). Dim n => p n -> Int
reflectDim (Proxy n
forall k (t :: k). Proxy t
Proxy :: Proxy n)
{-# INLINE reflectDim #-}
instance (Dim n, Semigroup a) => Semigroup (V n a) where
<> :: V n a -> V n a -> V n a
(<>) = (a -> a -> a) -> V n a -> V n a -> V n a
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Semigroup a => a -> a -> a
(<>)
instance (Dim n, Monoid a) => Monoid (V n a) where
mempty :: V n a
mempty = a -> V n a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
forall a. Monoid a => a
mempty
#if !(MIN_VERSION_base(4,11,0))
mappend = liftA2 mappend
#endif
instance Functor (V n) where
fmap :: (a -> b) -> V n a -> V n b
fmap a -> b
f (V Vector a
as) = Vector b -> V n b
forall k (n :: k) a. Vector a -> V n a
V ((a -> b) -> Vector a -> Vector b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f Vector a
as)
{-# INLINE fmap #-}
instance WithIndex.FunctorWithIndex Int (V n) where
imap :: (Int -> a -> b) -> V n a -> V n b
imap Int -> a -> b
f (V Vector a
as) = Vector b -> V n b
forall k (n :: k) a. Vector a -> V n a
V ((Int -> a -> b) -> Vector a -> Vector b
forall i (f :: * -> *) a b.
FunctorWithIndex i f =>
(i -> a -> b) -> f a -> f b
Lens.imap Int -> a -> b
f Vector a
as)
{-# INLINE imap #-}
instance Foldable (V n) where
fold :: V n m -> m
fold (V Vector m
as) = Vector m -> m
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold Vector m
as
{-# INLINE fold #-}
foldMap :: (a -> m) -> V n a -> m
foldMap a -> m
f (V Vector a
as) = (a -> m) -> Vector a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
Foldable.foldMap a -> m
f Vector a
as
{-# INLINE foldMap #-}
foldr :: (a -> b -> b) -> b -> V n a -> b
foldr a -> b -> b
f b
z (V Vector a
as) = (a -> b -> b) -> b -> Vector a -> b
forall a b. (a -> b -> b) -> b -> Vector a -> b
V.foldr a -> b -> b
f b
z Vector a
as
{-# INLINE foldr #-}
foldl :: (b -> a -> b) -> b -> V n a -> b
foldl b -> a -> b
f b
z (V Vector a
as) = (b -> a -> b) -> b -> Vector a -> b
forall a b. (a -> b -> a) -> a -> Vector b -> a
V.foldl b -> a -> b
f b
z Vector a
as
{-# INLINE foldl #-}
foldr' :: (a -> b -> b) -> b -> V n a -> b
foldr' a -> b -> b
f b
z (V Vector a
as) = (a -> b -> b) -> b -> Vector a -> b
forall a b. (a -> b -> b) -> b -> Vector a -> b
V.foldr' a -> b -> b
f b
z Vector a
as
{-# INLINE foldr' #-}
foldl' :: (b -> a -> b) -> b -> V n a -> b
foldl' b -> a -> b
f b
z (V Vector a
as) = (b -> a -> b) -> b -> Vector a -> b
forall a b. (a -> b -> a) -> a -> Vector b -> a
V.foldl' b -> a -> b
f b
z Vector a
as
{-# INLINE foldl' #-}
foldr1 :: (a -> a -> a) -> V n a -> a
foldr1 a -> a -> a
f (V Vector a
as) = (a -> a -> a) -> Vector a -> a
forall a. (a -> a -> a) -> Vector a -> a
V.foldr1 a -> a -> a
f Vector a
as
{-# INLINE foldr1 #-}
foldl1 :: (a -> a -> a) -> V n a -> a
foldl1 a -> a -> a
f (V Vector a
as) = (a -> a -> a) -> Vector a -> a
forall a. (a -> a -> a) -> Vector a -> a
V.foldl1 a -> a -> a
f Vector a
as
{-# INLINE foldl1 #-}
length :: V n a -> Int
length (V Vector a
as) = Vector a -> Int
forall a. Vector a -> Int
V.length Vector a
as
{-# INLINE length #-}
null :: V n a -> Bool
null (V Vector a
as) = Vector a -> Bool
forall a. Vector a -> Bool
V.null Vector a
as
{-# INLINE null #-}
toList :: V n a -> [a]
toList (V Vector a
as) = Vector a -> [a]
forall a. Vector a -> [a]
V.toList Vector a
as
{-# INLINE toList #-}
elem :: a -> V n a -> Bool
elem a
a (V Vector a
as) = a -> Vector a -> Bool
forall a. Eq a => a -> Vector a -> Bool
V.elem a
a Vector a
as
{-# INLINE elem #-}
maximum :: V n a -> a
maximum (V Vector a
as) = Vector a -> a
forall a. Ord a => Vector a -> a
V.maximum Vector a
as
{-# INLINE maximum #-}
minimum :: V n a -> a
minimum (V Vector a
as) = Vector a -> a
forall a. Ord a => Vector a -> a
V.minimum Vector a
as
{-# INLINE minimum #-}
sum :: V n a -> a
sum (V Vector a
as) = Vector a -> a
forall a. Num a => Vector a -> a
V.sum Vector a
as
{-# INLINE sum #-}
product :: V n a -> a
product (V Vector a
as) = Vector a -> a
forall a. Num a => Vector a -> a
V.product Vector a
as
{-# INLINE product #-}
instance WithIndex.FoldableWithIndex Int (V n) where
ifoldMap :: (Int -> a -> m) -> V n a -> m
ifoldMap Int -> a -> m
f (V Vector a
as) = (Int -> a -> m) -> Vector a -> m
forall i (f :: * -> *) m a.
(FoldableWithIndex i f, Monoid m) =>
(i -> a -> m) -> f a -> m
ifoldMap Int -> a -> m
f Vector a
as
{-# INLINE ifoldMap #-}
instance Traversable (V n) where
traverse :: (a -> f b) -> V n a -> f (V n b)
traverse a -> f b
f (V Vector a
as) = Vector b -> V n b
forall k (n :: k) a. Vector a -> V n a
V (Vector b -> V n b) -> f (Vector b) -> f (V n b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> f b) -> Vector a -> f (Vector b)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse a -> f b
f Vector a
as
{-# INLINE traverse #-}
instance WithIndex.TraversableWithIndex Int (V n) where
itraverse :: (Int -> a -> f b) -> V n a -> f (V n b)
itraverse Int -> a -> f b
f (V Vector a
as) = Vector b -> V n b
forall k (n :: k) a. Vector a -> V n a
V (Vector b -> V n b) -> f (Vector b) -> f (V n b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Int -> a -> f b) -> Vector a -> f (Vector b)
forall i (t :: * -> *) (f :: * -> *) a b.
(TraversableWithIndex i t, Applicative f) =>
(i -> a -> f b) -> t a -> f (t b)
itraverse Int -> a -> f b
f Vector a
as
{-# INLINE itraverse #-}
#if !MIN_VERSION_lens(5,0,0)
instance Lens.FunctorWithIndex Int (V n) where imap = WithIndex.imap
instance Lens.FoldableWithIndex Int (V n) where ifoldMap = WithIndex.ifoldMap
instance Lens.TraversableWithIndex Int (V n) where itraverse = WithIndex.itraverse
#endif
instance Apply (V n) where
V Vector (a -> b)
as <.> :: V n (a -> b) -> V n a -> V n b
<.> V Vector a
bs = Vector b -> V n b
forall k (n :: k) a. Vector a -> V n a
V (((a -> b) -> a -> b) -> Vector (a -> b) -> Vector a -> Vector b
forall a b c. (a -> b -> c) -> Vector a -> Vector b -> Vector c
V.zipWith (a -> b) -> a -> b
forall a. a -> a
id Vector (a -> b)
as Vector a
bs)
{-# INLINE (<.>) #-}
instance Dim n => Applicative (V n) where
pure :: a -> V n a
pure = Vector a -> V n a
forall k (n :: k) a. Vector a -> V n a
V (Vector a -> V n a) -> (a -> Vector a) -> a -> V n a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> a -> Vector a
forall a. Int -> a -> Vector a
V.replicate (Proxy n -> Int
forall k (n :: k) (p :: k -> *). Dim n => p n -> Int
reflectDim (Proxy n
forall k (t :: k). Proxy t
Proxy :: Proxy n))
{-# INLINE pure #-}
V Vector (a -> b)
as <*> :: V n (a -> b) -> V n a -> V n b
<*> V Vector a
bs = Vector b -> V n b
forall k (n :: k) a. Vector a -> V n a
V (((a -> b) -> a -> b) -> Vector (a -> b) -> Vector a -> Vector b
forall a b c. (a -> b -> c) -> Vector a -> Vector b -> Vector c
V.zipWith (a -> b) -> a -> b
forall a. a -> a
id Vector (a -> b)
as Vector a
bs)
{-# INLINE (<*>) #-}
instance Bind (V n) where
V Vector a
as >>- :: V n a -> (a -> V n b) -> V n b
>>- a -> V n b
f = Vector b -> V n b
forall k (n :: k) a. Vector a -> V n a
V (Vector b -> V n b) -> Vector b -> V n b
forall a b. (a -> b) -> a -> b
$ Int -> (Int -> b) -> Vector b
forall a. Int -> (Int -> a) -> Vector a
V.generate (Vector a -> Int
forall a. Vector a -> Int
V.length Vector a
as) ((Int -> b) -> Vector b) -> (Int -> b) -> Vector b
forall a b. (a -> b) -> a -> b
$ \Int
i ->
V n b -> Vector b
forall k (n :: k) a. V n a -> Vector a
toVector (a -> V n b
f (Vector a
as Vector a -> Int -> a
forall a. Vector a -> Int -> a
`V.unsafeIndex` Int
i)) Vector b -> Int -> b
forall a. Vector a -> Int -> a
`V.unsafeIndex` Int
i
{-# INLINE (>>-) #-}
instance Dim n => Monad (V n) where
#if !(MIN_VERSION_base(4,11,0))
return = V . V.replicate (reflectDim (Proxy :: Proxy n))
{-# INLINE return #-}
#endif
V Vector a
as >>= :: V n a -> (a -> V n b) -> V n b
>>= a -> V n b
f = Vector b -> V n b
forall k (n :: k) a. Vector a -> V n a
V (Vector b -> V n b) -> Vector b -> V n b
forall a b. (a -> b) -> a -> b
$ Int -> (Int -> b) -> Vector b
forall a. Int -> (Int -> a) -> Vector a
V.generate (Proxy n -> Int
forall k (n :: k) (p :: k -> *). Dim n => p n -> Int
reflectDim (Proxy n
forall k (t :: k). Proxy t
Proxy :: Proxy n)) ((Int -> b) -> Vector b) -> (Int -> b) -> Vector b
forall a b. (a -> b) -> a -> b
$ \Int
i ->
V n b -> Vector b
forall k (n :: k) a. V n a -> Vector a
toVector (a -> V n b
f (Vector a
as Vector a -> Int -> a
forall a. Vector a -> Int -> a
`V.unsafeIndex` Int
i)) Vector b -> Int -> b
forall a. Vector a -> Int -> a
`V.unsafeIndex` Int
i
{-# INLINE (>>=) #-}
instance Dim n => Additive (V n) where
zero :: V n a
zero = a -> V n a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
0
{-# INLINE zero #-}
liftU2 :: (a -> a -> a) -> V n a -> V n a -> V n a
liftU2 a -> a -> a
f (V Vector a
as) (V Vector a
bs) = Vector a -> V n a
forall k (n :: k) a. Vector a -> V n a
V ((a -> a -> a) -> Vector a -> Vector a -> Vector a
forall a b c. (a -> b -> c) -> Vector a -> Vector b -> Vector c
V.zipWith a -> a -> a
f Vector a
as Vector a
bs)
{-# INLINE liftU2 #-}
liftI2 :: (a -> b -> c) -> V n a -> V n b -> V n c
liftI2 a -> b -> c
f (V Vector a
as) (V Vector b
bs) = Vector c -> V n c
forall k (n :: k) a. Vector a -> V n a
V ((a -> b -> c) -> Vector a -> Vector b -> Vector c
forall a b c. (a -> b -> c) -> Vector a -> Vector b -> Vector c
V.zipWith a -> b -> c
f Vector a
as Vector b
bs)
{-# INLINE liftI2 #-}
instance (Dim n, Num a) => Num (V n a) where
V Vector a
as + :: V n a -> V n a -> V n a
+ V Vector a
bs = Vector a -> V n a
forall k (n :: k) a. Vector a -> V n a
V (Vector a -> V n a) -> Vector a -> V n a
forall a b. (a -> b) -> a -> b
$ (a -> a -> a) -> Vector a -> Vector a -> Vector a
forall a b c. (a -> b -> c) -> Vector a -> Vector b -> Vector c
V.zipWith a -> a -> a
forall a. Num a => a -> a -> a
(+) Vector a
as Vector a
bs
{-# INLINE (+) #-}
V Vector a
as - :: V n a -> V n a -> V n a
- V Vector a
bs = Vector a -> V n a
forall k (n :: k) a. Vector a -> V n a
V (Vector a -> V n a) -> Vector a -> V n a
forall a b. (a -> b) -> a -> b
$ (a -> a -> a) -> Vector a -> Vector a -> Vector a
forall a b c. (a -> b -> c) -> Vector a -> Vector b -> Vector c
V.zipWith (-) Vector a
as Vector a
bs
{-# INLINE (-) #-}
V Vector a
as * :: V n a -> V n a -> V n a
* V Vector a
bs = Vector a -> V n a
forall k (n :: k) a. Vector a -> V n a
V (Vector a -> V n a) -> Vector a -> V n a
forall a b. (a -> b) -> a -> b
$ (a -> a -> a) -> Vector a -> Vector a -> Vector a
forall a b c. (a -> b -> c) -> Vector a -> Vector b -> Vector c
V.zipWith a -> a -> a
forall a. Num a => a -> a -> a
(*) Vector a
as Vector a
bs
{-# INLINE (*) #-}
negate :: V n a -> V n a
negate = (a -> a) -> V n a -> V n a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Num a => a -> a
negate
{-# INLINE negate #-}
abs :: V n a -> V n a
abs = (a -> a) -> V n a -> V n a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Num a => a -> a
abs
{-# INLINE abs #-}
signum :: V n a -> V n a
signum = (a -> a) -> V n a -> V n a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Num a => a -> a
signum
{-# INLINE signum #-}
fromInteger :: Integer -> V n a
fromInteger = a -> V n a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a -> V n a) -> (Integer -> a) -> Integer -> V n a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> a
forall a. Num a => Integer -> a
fromInteger
{-# INLINE fromInteger #-}
instance (Dim n, Fractional a) => Fractional (V n a) where
recip :: V n a -> V n a
recip = (a -> a) -> V n a -> V n a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Fractional a => a -> a
recip
{-# INLINE recip #-}
V Vector a
as / :: V n a -> V n a -> V n a
/ V Vector a
bs = Vector a -> V n a
forall k (n :: k) a. Vector a -> V n a
V (Vector a -> V n a) -> Vector a -> V n a
forall a b. (a -> b) -> a -> b
$ (a -> a -> a) -> Vector a -> Vector a -> Vector a
forall a b c. (a -> b -> c) -> Vector a -> Vector b -> Vector c
V.zipWith a -> a -> a
forall a. Fractional a => a -> a -> a
(/) Vector a
as Vector a
bs
{-# INLINE (/) #-}
fromRational :: Rational -> V n a
fromRational = a -> V n a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a -> V n a) -> (Rational -> a) -> Rational -> V n a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rational -> a
forall a. Fractional a => Rational -> a
fromRational
{-# INLINE fromRational #-}
instance (Dim n, Floating a) => Floating (V n a) where
pi :: V n a
pi = a -> V n a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
forall a. Floating a => a
pi
{-# INLINE pi #-}
exp :: V n a -> V n a
exp = (a -> a) -> V n a -> V n a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
exp
{-# INLINE exp #-}
sqrt :: V n a -> V n a
sqrt = (a -> a) -> V n a -> V n a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
sqrt
{-# INLINE sqrt #-}
log :: V n a -> V n a
log = (a -> a) -> V n a -> V n a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
log
{-# INLINE log #-}
V Vector a
as ** :: V n a -> V n a -> V n a
** V Vector a
bs = Vector a -> V n a
forall k (n :: k) a. Vector a -> V n a
V (Vector a -> V n a) -> Vector a -> V n a
forall a b. (a -> b) -> a -> b
$ (a -> a -> a) -> Vector a -> Vector a -> Vector a
forall a b c. (a -> b -> c) -> Vector a -> Vector b -> Vector c
V.zipWith a -> a -> a
forall a. Floating a => a -> a -> a
(**) Vector a
as Vector a
bs
{-# INLINE (**) #-}
logBase :: V n a -> V n a -> V n a
logBase (V Vector a
as) (V Vector a
bs) = Vector a -> V n a
forall k (n :: k) a. Vector a -> V n a
V (Vector a -> V n a) -> Vector a -> V n a
forall a b. (a -> b) -> a -> b
$ (a -> a -> a) -> Vector a -> Vector a -> Vector a
forall a b c. (a -> b -> c) -> Vector a -> Vector b -> Vector c
V.zipWith a -> a -> a
forall a. Floating a => a -> a -> a
logBase Vector a
as Vector a
bs
{-# INLINE logBase #-}
sin :: V n a -> V n a
sin = (a -> a) -> V n a -> V n a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
sin
{-# INLINE sin #-}
tan :: V n a -> V n a
tan = (a -> a) -> V n a -> V n a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
tan
{-# INLINE tan #-}
cos :: V n a -> V n a
cos = (a -> a) -> V n a -> V n a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
cos
{-# INLINE cos #-}
asin :: V n a -> V n a
asin = (a -> a) -> V n a -> V n a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
asin
{-# INLINE asin #-}
atan :: V n a -> V n a
atan = (a -> a) -> V n a -> V n a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
atan
{-# INLINE atan #-}
acos :: V n a -> V n a
acos = (a -> a) -> V n a -> V n a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
acos
{-# INLINE acos #-}
sinh :: V n a -> V n a
sinh = (a -> a) -> V n a -> V n a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
sinh
{-# INLINE sinh #-}
tanh :: V n a -> V n a
tanh = (a -> a) -> V n a -> V n a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
tanh
{-# INLINE tanh #-}
cosh :: V n a -> V n a
cosh = (a -> a) -> V n a -> V n a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
cosh
{-# INLINE cosh #-}
asinh :: V n a -> V n a
asinh = (a -> a) -> V n a -> V n a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
asinh
{-# INLINE asinh #-}
atanh :: V n a -> V n a
atanh = (a -> a) -> V n a -> V n a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
atanh
{-# INLINE atanh #-}
acosh :: V n a -> V n a
acosh = (a -> a) -> V n a -> V n a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> a
forall a. Floating a => a -> a
acosh
{-# INLINE acosh #-}
instance Dim n => Distributive (V n) where
distribute :: f (V n a) -> V n (f a)
distribute f (V n a)
f = Vector (f a) -> V n (f a)
forall k (n :: k) a. Vector a -> V n a
V (Vector (f a) -> V n (f a)) -> Vector (f a) -> V n (f a)
forall a b. (a -> b) -> a -> b
$ Int -> (Int -> f a) -> Vector (f a)
forall a. Int -> (Int -> a) -> Vector a
V.generate (Proxy n -> Int
forall k (n :: k) (p :: k -> *). Dim n => p n -> Int
reflectDim (Proxy n
forall k (t :: k). Proxy t
Proxy :: Proxy n)) ((Int -> f a) -> Vector (f a)) -> (Int -> f a) -> Vector (f a)
forall a b. (a -> b) -> a -> b
$ \Int
i -> (V n a -> a) -> f (V n a) -> f a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(V Vector a
v) -> Vector a -> Int -> a
forall a. Vector a -> Int -> a
V.unsafeIndex Vector a
v Int
i) f (V n a)
f
{-# INLINE distribute #-}
instance Hashable a => Hashable (V n a) where
hashWithSalt :: Int -> V n a -> Int
hashWithSalt Int
s0 (V Vector a
v) =
(Int -> a -> Int) -> Int -> Vector a -> Int
forall a b. (a -> b -> a) -> a -> Vector b -> a
V.foldl' (\Int
s a
a -> Int
s Int -> a -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` a
a) Int
s0 Vector a
v
Int -> Int -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Vector a -> Int
forall a. Vector a -> Int
V.length Vector a
v
instance Dim n => Hashable1 (V n) where
liftHashWithSalt :: (Int -> a -> Int) -> Int -> V n a -> Int
liftHashWithSalt Int -> a -> Int
h Int
s0 (V Vector a
v) =
(Int -> a -> Int) -> Int -> Vector a -> Int
forall a b. (a -> b -> a) -> a -> Vector b -> a
V.foldl' (\Int
s a
a -> Int -> a -> Int
h Int
s a
a) Int
s0 Vector a
v
Int -> Int -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Vector a -> Int
forall a. Vector a -> Int
V.length Vector a
v
{-# INLINE liftHashWithSalt #-}
instance (Dim n, Storable a) => Storable (V n a) where
sizeOf :: V n a -> Int
sizeOf V n a
_ = Proxy n -> Int
forall k (n :: k) (p :: k -> *). Dim n => p n -> Int
reflectDim (Proxy n
forall k (t :: k). Proxy t
Proxy :: Proxy n) Int -> Int -> Int
forall a. Num a => a -> a -> a
* a -> Int
forall a. Storable a => a -> Int
sizeOf (a
forall a. HasCallStack => a
undefined:: a)
{-# INLINE sizeOf #-}
alignment :: V n a -> Int
alignment V n a
_ = a -> Int
forall a. Storable a => a -> Int
alignment (a
forall a. HasCallStack => a
undefined :: a)
{-# INLINE alignment #-}
poke :: Ptr (V n a) -> V n a -> IO ()
poke Ptr (V n a)
ptr (V Vector a
xs) = [Int] -> (Int -> IO ()) -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
Foldable.forM_ [Int
0..Proxy n -> Int
forall k (n :: k) (p :: k -> *). Dim n => p n -> Int
reflectDim (Proxy n
forall k (t :: k). Proxy t
Proxy :: Proxy n)Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1] ((Int -> IO ()) -> IO ()) -> (Int -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Int
i ->
Ptr a -> Int -> a -> IO ()
forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr a
ptr' Int
i (Vector a -> Int -> a
forall a. Vector a -> Int -> a
V.unsafeIndex Vector a
xs Int
i)
where ptr' :: Ptr a
ptr' = Ptr (V n a) -> Ptr a
forall a b. Ptr a -> Ptr b
castPtr Ptr (V n a)
ptr
{-# INLINE poke #-}
peek :: Ptr (V n a) -> IO (V n a)
peek Ptr (V n a)
ptr = Vector a -> V n a
forall k (n :: k) a. Vector a -> V n a
V (Vector a -> V n a) -> IO (Vector a) -> IO (V n a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> (Int -> IO a) -> IO (Vector a)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
V.generateM (Proxy n -> Int
forall k (n :: k) (p :: k -> *). Dim n => p n -> Int
reflectDim (Proxy n
forall k (t :: k). Proxy t
Proxy :: Proxy n)) (Ptr a -> Int -> IO a
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr a
ptr')
where ptr' :: Ptr a
ptr' = Ptr (V n a) -> Ptr a
forall a b. Ptr a -> Ptr b
castPtr Ptr (V n a)
ptr
{-# INLINE peek #-}
instance (Dim n, Epsilon a) => Epsilon (V n a) where
nearZero :: V n a -> Bool
nearZero = a -> Bool
forall a. Epsilon a => a -> Bool
nearZero (a -> Bool) -> (V n a -> a) -> V n a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. V n a -> a
forall (f :: * -> *) a. (Metric f, Num a) => f a -> a
quadrance
{-# INLINE nearZero #-}
instance Dim n => Metric (V n) where
dot :: V n a -> V n a -> a
dot (V Vector a
a) (V Vector a
b) = Vector a -> a
forall a. Num a => Vector a -> a
V.sum (Vector a -> a) -> Vector a -> a
forall a b. (a -> b) -> a -> b
$ (a -> a -> a) -> Vector a -> Vector a -> Vector a
forall a b c. (a -> b -> c) -> Vector a -> Vector b -> Vector c
V.zipWith a -> a -> a
forall a. Num a => a -> a -> a
(*) Vector a
a Vector a
b
{-# INLINE dot #-}
fromVector :: forall n a. Dim n => Vector a -> Maybe (V n a)
fromVector :: Vector a -> Maybe (V n a)
fromVector Vector a
v
| Vector a -> Int
forall a. Vector a -> Int
V.length Vector a
v Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Proxy n -> Int
forall k (n :: k) (p :: k -> *). Dim n => p n -> Int
reflectDim (Proxy n
forall k (t :: k). Proxy t
Proxy :: Proxy n) = V n a -> Maybe (V n a)
forall a. a -> Maybe a
Just (Vector a -> V n a
forall k (n :: k) a. Vector a -> V n a
V Vector a
v)
| Bool
otherwise = Maybe (V n a)
forall a. Maybe a
Nothing
#if !(MIN_VERSION_reflection(1,3,0)) && defined(MIN_VERSION_template_haskell)
data Z
data D (n :: *)
data SD (n :: *)
data PD (n :: *)
instance Reifies Z Int where
reflect _ = 0
{-# INLINE reflect #-}
retagD :: (Proxy n -> a) -> proxy (D n) -> a
retagD f _ = f Proxy
{-# INLINE retagD #-}
retagSD :: (Proxy n -> a) -> proxy (SD n) -> a
retagSD f _ = f Proxy
{-# INLINE retagSD #-}
retagPD :: (Proxy n -> a) -> proxy (PD n) -> a
retagPD f _ = f Proxy
{-# INLINE retagPD #-}
instance Reifies n Int => Reifies (D n) Int where
reflect = (\n -> n+n) <$> retagD reflect
{-# INLINE reflect #-}
instance Reifies n Int => Reifies (SD n) Int where
reflect = (\n -> n+n+1) <$> retagSD reflect
{-# INLINE reflect #-}
instance Reifies n Int => Reifies (PD n) Int where
reflect = (\n -> n+n-1) <$> retagPD reflect
{-# INLINE reflect #-}
int :: Int -> TypeQ
int n = case quotRem n 2 of
(0, 0) -> conT ''Z
(q,-1) -> conT ''PD `appT` int q
(q, 0) -> conT ''D `appT` int q
(q, 1) -> conT ''SD `appT` int q
_ -> error "ghc is bad at math"
#endif
instance Dim n => Representable (V n) where
type Rep (V n) = Int
tabulate :: (Rep (V n) -> a) -> V n a
tabulate = Vector a -> V n a
forall k (n :: k) a. Vector a -> V n a
V (Vector a -> V n a)
-> ((Int -> a) -> Vector a) -> (Int -> a) -> V n a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> (Int -> a) -> Vector a
forall a. Int -> (Int -> a) -> Vector a
V.generate (Proxy n -> Int
forall k (n :: k) (p :: k -> *). Dim n => p n -> Int
reflectDim (Proxy n
forall k (t :: k). Proxy t
Proxy :: Proxy n))
{-# INLINE tabulate #-}
index :: V n a -> Rep (V n) -> a
index (V Vector a
xs) Rep (V n)
i = Vector a
xs Vector a -> Int -> a
forall a. Vector a -> Int -> a
V.! Int
Rep (V n)
i
{-# INLINE index #-}
type instance Index (V n a) = Int
type instance IxValue (V n a) = a
instance Ixed (V n a) where
ix :: Index (V n a) -> Traversal' (V n a) (IxValue (V n a))
ix Index (V n a)
i IxValue (V n a) -> f (IxValue (V n a))
f v :: V n a
v@(V Vector a
as)
| Int
Index (V n a)
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 Bool -> Bool -> Bool
|| Int
Index (V n a)
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Vector a -> Int
forall a. Vector a -> Int
V.length Vector a
as = V n a -> f (V n a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure V n a
v
| Bool
otherwise = Int -> (a -> f a) -> V n a -> f (V n a)
forall k (n :: k) a. Int -> Lens' (V n a) a
vLens Int
Index (V n a)
i a -> f a
IxValue (V n a) -> f (IxValue (V n a))
f V n a
v
{-# INLINE ix #-}
instance Dim n => MonadZip (V n) where
mzip :: V n a -> V n b -> V n (a, b)
mzip (V Vector a
as) (V Vector b
bs) = Vector (a, b) -> V n (a, b)
forall k (n :: k) a. Vector a -> V n a
V (Vector (a, b) -> V n (a, b)) -> Vector (a, b) -> V n (a, b)
forall a b. (a -> b) -> a -> b
$ Vector a -> Vector b -> Vector (a, b)
forall a b. Vector a -> Vector b -> Vector (a, b)
V.zip Vector a
as Vector b
bs
mzipWith :: (a -> b -> c) -> V n a -> V n b -> V n c
mzipWith a -> b -> c
f (V Vector a
as) (V Vector b
bs) = Vector c -> V n c
forall k (n :: k) a. Vector a -> V n a
V (Vector c -> V n c) -> Vector c -> V n c
forall a b. (a -> b) -> a -> b
$ (a -> b -> c) -> Vector a -> Vector b -> Vector c
forall a b c. (a -> b -> c) -> Vector a -> Vector b -> Vector c
V.zipWith a -> b -> c
f Vector a
as Vector b
bs
instance Dim n => MonadFix (V n) where
mfix :: (a -> V n a) -> V n a
mfix a -> V n a
f = (Rep (V n) -> a) -> V n a
forall (f :: * -> *) a. Representable f => (Rep f -> a) -> f a
tabulate ((Rep (V n) -> a) -> V n a) -> (Rep (V n) -> a) -> V n a
forall a b. (a -> b) -> a -> b
$ \Rep (V n)
r -> let a :: a
a = V n a -> Rep (V n) -> a
forall (f :: * -> *) a. Representable f => f a -> Rep f -> a
Rep.index (a -> V n a
f a
a) Rep (V n)
r in a
a
instance Each (V n a) (V n b) a b where
each :: (a -> f b) -> V n a -> f (V n b)
each = (a -> f b) -> V n a -> f (V n b)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse
{-# INLINE each #-}
instance (Bounded a, Dim n) => Bounded (V n a) where
minBound :: V n a
minBound = a -> V n a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
forall a. Bounded a => a
minBound
{-# INLINE minBound #-}
maxBound :: V n a
maxBound = a -> V n a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
forall a. Bounded a => a
maxBound
{-# INLINE maxBound #-}
vConstr :: Constr
vConstr :: Constr
vConstr = DataType -> String -> [String] -> Fixity -> Constr
mkConstr DataType
vDataType String
"variadic" [] Fixity
Prefix
{-# NOINLINE vConstr #-}
vDataType :: DataType
vDataType :: DataType
vDataType = String -> [Constr] -> DataType
mkDataType String
"Linear.V.V" [Constr
vConstr]
{-# NOINLINE vDataType #-}
instance (Typeable (V n), Typeable (V n a), Dim n, Data a) => Data (V n a) where
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> V n a -> c (V n a)
gfoldl forall d b. Data d => c (d -> b) -> d -> c b
f forall g. g -> c g
z (V Vector a
as) = ([a] -> V n a) -> c ([a] -> V n a)
forall g. g -> c g
z (Vector a -> V n a
forall k (n :: k) a. Vector a -> V n a
V (Vector a -> V n a) -> ([a] -> Vector a) -> [a] -> V n a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> Vector a
forall a. [a] -> Vector a
V.fromList) c ([a] -> V n a) -> [a] -> c (V n a)
forall d b. Data d => c (d -> b) -> d -> c b
`f` Vector a -> [a]
forall a. Vector a -> [a]
V.toList Vector a
as
toConstr :: V n a -> Constr
toConstr V n a
_ = Constr
vConstr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (V n a)
gunfold forall b r. Data b => c (b -> r) -> c r
k forall r. r -> c r
z Constr
c = case Constr -> Int
constrIndex Constr
c of
Int
1 -> c ([a] -> V n a) -> c (V n a)
forall b r. Data b => c (b -> r) -> c r
k (([a] -> V n a) -> c ([a] -> V n a)
forall r. r -> c r
z (Vector a -> V n a
forall k (n :: k) a. Vector a -> V n a
V (Vector a -> V n a) -> ([a] -> Vector a) -> [a] -> V n a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> Vector a
forall a. [a] -> Vector a
V.fromList))
Int
_ -> String -> c (V n a)
forall a. HasCallStack => String -> a
error String
"gunfold"
dataTypeOf :: V n a -> DataType
dataTypeOf V n a
_ = DataType
vDataType
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (V n a))
dataCast1 forall d. Data d => c (t d)
f = c (t a) -> Maybe (c (V n a))
forall k1 k2 (c :: k1 -> *) (t :: k2 -> k1) (t' :: k2 -> k1)
(a :: k2).
(Typeable t, Typeable t') =>
c (t a) -> Maybe (c (t' a))
gcast1 c (t a)
forall d. Data d => c (t d)
f
instance Dim n => Serial1 (V n) where
serializeWith :: (a -> m ()) -> V n a -> m ()
serializeWith = (a -> m ()) -> V n a -> m ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_
deserializeWith :: m a -> m (V n a)
deserializeWith m a
f = V n (m a) -> m (V n a)
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
sequenceA (V n (m a) -> m (V n a)) -> V n (m a) -> m (V n a)
forall a b. (a -> b) -> a -> b
$ m a -> V n (m a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure m a
f
instance (Dim n, Serial a) => Serial (V n a) where
serialize :: V n a -> m ()
serialize = (a -> m ()) -> V n a -> m ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ a -> m ()
forall a (m :: * -> *). (Serial a, MonadPut m) => a -> m ()
serialize
deserialize :: m (V n a)
deserialize = V n (m a) -> m (V n a)
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
sequenceA (V n (m a) -> m (V n a)) -> V n (m a) -> m (V n a)
forall a b. (a -> b) -> a -> b
$ m a -> V n (m a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure m a
forall a (m :: * -> *). (Serial a, MonadGet m) => m a
deserialize
instance (Dim n, Binary a) => Binary (V n a) where
put :: V n a -> Put
put = (a -> Put) -> V n a -> Put
forall (f :: * -> *) (m :: * -> *) a.
(Serial1 f, MonadPut m) =>
(a -> m ()) -> f a -> m ()
serializeWith a -> Put
forall t. Binary t => t -> Put
Binary.put
get :: Get (V n a)
get = Get a -> Get (V n a)
forall (f :: * -> *) (m :: * -> *) a.
(Serial1 f, MonadGet m) =>
m a -> m (f a)
deserializeWith Get a
forall t. Binary t => Get t
Binary.get
instance (Dim n, Serialize a) => Serialize (V n a) where
put :: Putter (V n a)
put = (a -> PutM ()) -> Putter (V n a)
forall (f :: * -> *) (m :: * -> *) a.
(Serial1 f, MonadPut m) =>
(a -> m ()) -> f a -> m ()
serializeWith a -> PutM ()
forall t. Serialize t => Putter t
Cereal.put
get :: Get (V n a)
get = Get a -> Get (V n a)
forall (f :: * -> *) (m :: * -> *) a.
(Serial1 f, MonadGet m) =>
m a -> m (f a)
deserializeWith Get a
forall t. Serialize t => Get t
Cereal.get
instance Eq1 (V n) where
liftEq :: (a -> b -> Bool) -> V n a -> V n b -> Bool
liftEq a -> b -> Bool
f0 (V Vector a
as0) (V Vector b
bs0) = (a -> b -> Bool) -> [a] -> [b] -> Bool
forall t t. (t -> t -> Bool) -> [t] -> [t] -> Bool
go a -> b -> Bool
f0 (Vector a -> [a]
forall a. Vector a -> [a]
V.toList Vector a
as0) (Vector b -> [b]
forall a. Vector a -> [a]
V.toList Vector b
bs0) where
go :: (t -> t -> Bool) -> [t] -> [t] -> Bool
go t -> t -> Bool
_ [] [] = Bool
True
go t -> t -> Bool
f (t
a:[t]
as) (t
b:[t]
bs) = t -> t -> Bool
f t
a t
b Bool -> Bool -> Bool
&& (t -> t -> Bool) -> [t] -> [t] -> Bool
go t -> t -> Bool
f [t]
as [t]
bs
go t -> t -> Bool
_ [t]
_ [t]
_ = Bool
False
instance Ord1 (V n) where
liftCompare :: (a -> b -> Ordering) -> V n a -> V n b -> Ordering
liftCompare a -> b -> Ordering
f0 (V Vector a
as0) (V Vector b
bs0) = (a -> b -> Ordering) -> [a] -> [b] -> Ordering
forall t t. (t -> t -> Ordering) -> [t] -> [t] -> Ordering
go a -> b -> Ordering
f0 (Vector a -> [a]
forall a. Vector a -> [a]
V.toList Vector a
as0) (Vector b -> [b]
forall a. Vector a -> [a]
V.toList Vector b
bs0) where
go :: (t -> t -> Ordering) -> [t] -> [t] -> Ordering
go t -> t -> Ordering
f (t
a:[t]
as) (t
b:[t]
bs) = t -> t -> Ordering
f t
a t
b Ordering -> Ordering -> Ordering
forall a. Monoid a => a -> a -> a
`mappend` (t -> t -> Ordering) -> [t] -> [t] -> Ordering
go t -> t -> Ordering
f [t]
as [t]
bs
go t -> t -> Ordering
_ [] [] = Ordering
EQ
go t -> t -> Ordering
_ [t]
_ [] = Ordering
GT
go t -> t -> Ordering
_ [] [t]
_ = Ordering
LT
instance Show1 (V n) where
liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> V n a -> ShowS
liftShowsPrec Int -> a -> ShowS
_ [a] -> ShowS
g Int
d (V Vector a
as) = Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) (ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ String -> ShowS
showString String
"V " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> ShowS
g (Vector a -> [a]
forall a. Vector a -> [a]
V.toList Vector a
as)
instance Dim n => Read1 (V n) where
liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (V n a)
liftReadsPrec Int -> ReadS a
_ ReadS [a]
g Int
d = Bool -> ReadS (V n a) -> ReadS (V n a)
forall a. Bool -> ReadS a -> ReadS a
readParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) (ReadS (V n a) -> ReadS (V n a)) -> ReadS (V n a) -> ReadS (V n a)
forall a b. (a -> b) -> a -> b
$ \String
r ->
[ (Vector a -> V n a
forall k (n :: k) a. Vector a -> V n a
V ([a] -> Vector a
forall a. [a] -> Vector a
V.fromList [a]
as), String
r2)
| (String
"V",String
r1) <- ReadS String
lex String
r
, ([a]
as, String
r2) <- ReadS [a]
g String
r1
, [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [a]
as Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Proxy n -> Int
forall k (n :: k) (p :: k -> *). Dim n => p n -> Int
reflectDim (Proxy n
forall k (t :: k). Proxy t
Proxy :: Proxy n)
]
data instance U.Vector (V n a) = V_VN {-# UNPACK #-} !Int !(U.Vector a)
data instance U.MVector s (V n a) = MV_VN {-# UNPACK #-} !Int !(U.MVector s a)
instance (Dim n, U.Unbox a) => U.Unbox (V n a)
instance (Dim n, U.Unbox a) => M.MVector U.MVector (V n a) where
{-# INLINE basicLength #-}
{-# INLINE basicUnsafeSlice #-}
{-# INLINE basicOverlaps #-}
{-# INLINE basicUnsafeNew #-}
{-# INLINE basicUnsafeRead #-}
{-# INLINE basicUnsafeWrite #-}
basicLength :: MVector s (V n a) -> Int
basicLength (MV_VN n _) = Int
n
basicUnsafeSlice :: Int -> Int -> MVector s (V n a) -> MVector s (V n a)
basicUnsafeSlice Int
m Int
n (MV_VN _ v) = Int -> MVector s a -> MVector s (V n a)
forall k s (n :: k) a. Int -> MVector s a -> MVector s (V n a)
MV_VN Int
n (Int -> Int -> MVector s a -> MVector s a
forall (v :: * -> * -> *) a s.
MVector v a =>
Int -> Int -> v s a -> v s a
M.basicUnsafeSlice (Int
dInt -> Int -> Int
forall a. Num a => a -> a -> a
*Int
m) (Int
dInt -> Int -> Int
forall a. Num a => a -> a -> a
*Int
n) MVector s a
v)
where d :: Int
d = Proxy n -> Int
forall k (n :: k) (p :: k -> *). Dim n => p n -> Int
reflectDim (Proxy n
forall k (t :: k). Proxy t
Proxy :: Proxy n)
basicOverlaps :: MVector s (V n a) -> MVector s (V n a) -> Bool
basicOverlaps (MV_VN _ v) (MV_VN _ u) = MVector s a -> MVector s a -> Bool
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> v s a -> Bool
M.basicOverlaps MVector s a
v MVector s a
u
basicUnsafeNew :: Int -> m (MVector (PrimState m) (V n a))
basicUnsafeNew Int
n = (MVector (PrimState m) a -> MVector (PrimState m) (V n a))
-> m (MVector (PrimState m) a) -> m (MVector (PrimState m) (V n a))
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM (Int -> MVector (PrimState m) a -> MVector (PrimState m) (V n a)
forall k s (n :: k) a. Int -> MVector s a -> MVector s (V n a)
MV_VN Int
n) (Int -> m (MVector (PrimState m) a)
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
Int -> m (v (PrimState m) a)
M.basicUnsafeNew (Int
dInt -> Int -> Int
forall a. Num a => a -> a -> a
*Int
n))
where d :: Int
d = Proxy n -> Int
forall k (n :: k) (p :: k -> *). Dim n => p n -> Int
reflectDim (Proxy n
forall k (t :: k). Proxy t
Proxy :: Proxy n)
basicUnsafeRead :: MVector (PrimState m) (V n a) -> Int -> m (V n a)
basicUnsafeRead (MV_VN _ v) Int
i =
(Vector a -> V n a) -> m (Vector a) -> m (V n a)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM Vector a -> V n a
forall k (n :: k) a. Vector a -> V n a
V (m (Vector a) -> m (V n a)) -> m (Vector a) -> m (V n a)
forall a b. (a -> b) -> a -> b
$ Int -> (Int -> m a) -> m (Vector a)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
V.generateM Int
d (\Int
j -> MVector (PrimState m) a -> Int -> m a
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> m a
M.basicUnsafeRead MVector (PrimState m) a
v (Int
dInt -> Int -> Int
forall a. Num a => a -> a -> a
*Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
j))
where d :: Int
d = Proxy n -> Int
forall k (n :: k) (p :: k -> *). Dim n => p n -> Int
reflectDim (Proxy n
forall k (t :: k). Proxy t
Proxy :: Proxy n)
basicUnsafeWrite :: MVector (PrimState m) (V n a) -> Int -> V n a -> m ()
basicUnsafeWrite (MV_VN _ v0) Int
i (V Vector a
vn0) = let d0 :: Int
d0 = Vector a -> Int
forall a. Vector a -> Int
V.length Vector a
vn0 in MVector (PrimState m) a -> Vector a -> Int -> Int -> Int -> m ()
forall (m :: * -> *) (v :: * -> *) a (v :: * -> * -> *).
(Vector v a, PrimMonad m, MVector v a) =>
v (PrimState m) a -> v a -> Int -> Int -> Int -> m ()
go MVector (PrimState m) a
v0 Vector a
vn0 Int
d0 (Int
d0Int -> Int -> Int
forall a. Num a => a -> a -> a
*Int
i) Int
0
where
go :: v (PrimState m) a -> v a -> Int -> Int -> Int -> m ()
go v (PrimState m) a
v v a
vn Int
d Int
o Int
j
| Int
j Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
d = () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = do
a
a <- v a -> Int -> m a
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, Monad m) =>
v a -> Int -> m a
G.basicUnsafeIndexM v a
vn Int
j
v (PrimState m) a -> Int -> a -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> a -> m ()
M.basicUnsafeWrite v (PrimState m) a
v Int
o a
a
v (PrimState m) a -> v a -> Int -> Int -> Int -> m ()
go v (PrimState m) a
v v a
vn Int
d (Int
oInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) (Int
jInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
basicInitialize :: MVector (PrimState m) (V n a) -> m ()
basicInitialize (MV_VN _ v) = MVector (PrimState m) a -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> m ()
M.basicInitialize MVector (PrimState m) a
v
{-# INLINE basicInitialize #-}
instance (Dim n, U.Unbox a) => G.Vector U.Vector (V n a) where
{-# INLINE basicUnsafeFreeze #-}
{-# INLINE basicUnsafeThaw #-}
{-# INLINE basicLength #-}
{-# INLINE basicUnsafeSlice #-}
{-# INLINE basicUnsafeIndexM #-}
basicUnsafeFreeze :: Mutable Vector (PrimState m) (V n a) -> m (Vector (V n a))
basicUnsafeFreeze (MV_VN n v) = (Vector a -> Vector (V n a)) -> m (Vector a) -> m (Vector (V n a))
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM ( Int -> Vector a -> Vector (V n a)
forall k (n :: k) a. Int -> Vector a -> Vector (V n a)
V_VN Int
n) (Mutable Vector (PrimState m) a -> m (Vector a)
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, PrimMonad m) =>
Mutable v (PrimState m) a -> m (v a)
G.basicUnsafeFreeze MVector (PrimState m) a
Mutable Vector (PrimState m) a
v)
basicUnsafeThaw :: Vector (V n a) -> m (Mutable Vector (PrimState m) (V n a))
basicUnsafeThaw ( V_VN n v) = (MVector (PrimState m) a -> MVector (PrimState m) (V n a))
-> m (MVector (PrimState m) a) -> m (MVector (PrimState m) (V n a))
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM (Int -> MVector (PrimState m) a -> MVector (PrimState m) (V n a)
forall k s (n :: k) a. Int -> MVector s a -> MVector s (V n a)
MV_VN Int
n) (Vector a -> m (Mutable Vector (PrimState m) a)
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, PrimMonad m) =>
v a -> m (Mutable v (PrimState m) a)
G.basicUnsafeThaw Vector a
v)
basicLength :: Vector (V n a) -> Int
basicLength ( V_VN n _) = Int
n
basicUnsafeSlice :: Int -> Int -> Vector (V n a) -> Vector (V n a)
basicUnsafeSlice Int
m Int
n (V_VN _ v) = Int -> Vector a -> Vector (V n a)
forall k (n :: k) a. Int -> Vector a -> Vector (V n a)
V_VN Int
n (Int -> Int -> Vector a -> Vector a
forall (v :: * -> *) a. Vector v a => Int -> Int -> v a -> v a
G.basicUnsafeSlice (Int
dInt -> Int -> Int
forall a. Num a => a -> a -> a
*Int
m) (Int
dInt -> Int -> Int
forall a. Num a => a -> a -> a
*Int
n) Vector a
v)
where d :: Int
d = Proxy n -> Int
forall k (n :: k) (p :: k -> *). Dim n => p n -> Int
reflectDim (Proxy n
forall k (t :: k). Proxy t
Proxy :: Proxy n)
basicUnsafeIndexM :: Vector (V n a) -> Int -> m (V n a)
basicUnsafeIndexM (V_VN _ v) Int
i =
(Vector a -> V n a) -> m (Vector a) -> m (V n a)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM Vector a -> V n a
forall k (n :: k) a. Vector a -> V n a
V (m (Vector a) -> m (V n a)) -> m (Vector a) -> m (V n a)
forall a b. (a -> b) -> a -> b
$ Int -> (Int -> m a) -> m (Vector a)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
V.generateM Int
d (\Int
j -> Vector a -> Int -> m a
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, Monad m) =>
v a -> Int -> m a
G.basicUnsafeIndexM Vector a
v (Int
dInt -> Int -> Int
forall a. Num a => a -> a -> a
*Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
j))
where d :: Int
d = Proxy n -> Int
forall k (n :: k) (p :: k -> *). Dim n => p n -> Int
reflectDim (Proxy n
forall k (t :: k). Proxy t
Proxy :: Proxy n)
vLens :: Int -> Lens' (V n a) a
vLens :: Int -> Lens' (V n a) a
vLens Int
i = \a -> f a
f (V Vector a
v) -> a -> f a
f (Vector a
v Vector a -> Int -> a
forall a. Vector a -> Int -> a
V.! Int
i) f a -> (a -> V n a) -> f (V n a)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \a
a -> Vector a -> V n a
forall k (n :: k) a. Vector a -> V n a
V (Vector a
v Vector a -> [(Int, a)] -> Vector a
forall a. Vector a -> [(Int, a)] -> Vector a
V.// [(Int
i, a
a)])
{-# INLINE vLens #-}
instance ( 1 <= n) => Field1 (V n a) (V n a) a a where _1 :: (a -> f a) -> V n a -> f (V n a)
_1 = Int -> Lens (V n a) (V n a) a a
forall k (n :: k) a. Int -> Lens' (V n a) a
vLens Int
0
instance ( 2 <= n) => Field2 (V n a) (V n a) a a where _2 :: (a -> f a) -> V n a -> f (V n a)
_2 = Int -> Lens (V n a) (V n a) a a
forall k (n :: k) a. Int -> Lens' (V n a) a
vLens Int
1
instance ( 3 <= n) => Field3 (V n a) (V n a) a a where _3 :: (a -> f a) -> V n a -> f (V n a)
_3 = Int -> Lens (V n a) (V n a) a a
forall k (n :: k) a. Int -> Lens' (V n a) a
vLens Int
2
instance ( 4 <= n) => Field4 (V n a) (V n a) a a where _4 :: (a -> f a) -> V n a -> f (V n a)
_4 = Int -> Lens (V n a) (V n a) a a
forall k (n :: k) a. Int -> Lens' (V n a) a
vLens Int
3
instance ( 5 <= n) => Field5 (V n a) (V n a) a a where _5 :: (a -> f a) -> V n a -> f (V n a)
_5 = Int -> Lens (V n a) (V n a) a a
forall k (n :: k) a. Int -> Lens' (V n a) a
vLens Int
4
instance ( 6 <= n) => Field6 (V n a) (V n a) a a where _6 :: (a -> f a) -> V n a -> f (V n a)
_6 = Int -> Lens (V n a) (V n a) a a
forall k (n :: k) a. Int -> Lens' (V n a) a
vLens Int
5
instance ( 7 <= n) => Field7 (V n a) (V n a) a a where _7 :: (a -> f a) -> V n a -> f (V n a)
_7 = Int -> Lens (V n a) (V n a) a a
forall k (n :: k) a. Int -> Lens' (V n a) a
vLens Int
6
instance ( 8 <= n) => Field8 (V n a) (V n a) a a where _8 :: (a -> f a) -> V n a -> f (V n a)
_8 = Int -> Lens (V n a) (V n a) a a
forall k (n :: k) a. Int -> Lens' (V n a) a
vLens Int
7
instance ( 9 <= n) => Field9 (V n a) (V n a) a a where _9 :: (a -> f a) -> V n a -> f (V n a)
_9 = Int -> Lens (V n a) (V n a) a a
forall k (n :: k) a. Int -> Lens' (V n a) a
vLens Int
8
instance (10 <= n) => Field10 (V n a) (V n a) a a where _10 :: (a -> f a) -> V n a -> f (V n a)
_10 = Int -> Lens (V n a) (V n a) a a
forall k (n :: k) a. Int -> Lens' (V n a) a
vLens Int
9
instance (11 <= n) => Field11 (V n a) (V n a) a a where _11 :: (a -> f a) -> V n a -> f (V n a)
_11 = Int -> Lens (V n a) (V n a) a a
forall k (n :: k) a. Int -> Lens' (V n a) a
vLens Int
10
instance (12 <= n) => Field12 (V n a) (V n a) a a where _12 :: (a -> f a) -> V n a -> f (V n a)
_12 = Int -> Lens (V n a) (V n a) a a
forall k (n :: k) a. Int -> Lens' (V n a) a
vLens Int
11
instance (13 <= n) => Field13 (V n a) (V n a) a a where _13 :: (a -> f a) -> V n a -> f (V n a)
_13 = Int -> Lens (V n a) (V n a) a a
forall k (n :: k) a. Int -> Lens' (V n a) a
vLens Int
12
instance (14 <= n) => Field14 (V n a) (V n a) a a where _14 :: (a -> f a) -> V n a -> f (V n a)
_14 = Int -> Lens (V n a) (V n a) a a
forall k (n :: k) a. Int -> Lens' (V n a) a
vLens Int
13
instance (15 <= n) => Field15 (V n a) (V n a) a a where _15 :: (a -> f a) -> V n a -> f (V n a)
_15 = Int -> Lens (V n a) (V n a) a a
forall k (n :: k) a. Int -> Lens' (V n a) a
vLens Int
14
instance (16 <= n) => Field16 (V n a) (V n a) a a where _16 :: (a -> f a) -> V n a -> f (V n a)
_16 = Int -> Lens (V n a) (V n a) a a
forall k (n :: k) a. Int -> Lens' (V n a) a
vLens Int
15
instance (17 <= n) => Field17 (V n a) (V n a) a a where _17 :: (a -> f a) -> V n a -> f (V n a)
_17 = Int -> Lens (V n a) (V n a) a a
forall k (n :: k) a. Int -> Lens' (V n a) a
vLens Int
16
instance (18 <= n) => Field18 (V n a) (V n a) a a where _18 :: (a -> f a) -> V n a -> f (V n a)
_18 = Int -> Lens (V n a) (V n a) a a
forall k (n :: k) a. Int -> Lens' (V n a) a
vLens Int
17
instance (19 <= n) => Field19 (V n a) (V n a) a a where _19 :: (a -> f a) -> V n a -> f (V n a)
_19 = Int -> Lens (V n a) (V n a) a a
forall k (n :: k) a. Int -> Lens' (V n a) a
vLens Int
18