#if __GLASGOW_HASKELL__ >= 800
#endif
module Data.Utils.Vector
( Vector
, (<%>)
, nil
, cons
, generate
, (!?)
, (!)
, vhead
, vtail
, (<+>)
, (<->)
, sqNorm
, sqDiff
, KnownNat
, natVal
) where
import Data.Proxy
import qualified Data.Vector as V
import GHC.TypeLits
import GHC.TypeLits.Witnesses
import Data.MyPrelude
data Vector :: Nat -> * -> * where
Vector :: KnownNat n => V.Vector a -> Vector n a
instance Eq a => Eq (Vector n a) where
Vector xs == Vector ys = xs == ys
instance Show a => Show (Vector n a) where
showsPrec p (Vector xs) = showsPrec p xs
instance Functor (Vector n) where
fmap f (Vector v) = Vector (f <$> v)
instance forall n. KnownNat n => Applicative (Vector n) where
pure x = let n = natVal (Proxy :: Proxy n) in Vector (V.replicate (fromIntegral n) x)
Vector fs <*> Vector xs = Vector (V.zipWith ($) fs xs)
instance Foldable (Vector n) where
foldMap f (Vector xs) = foldMap f xs
instance Traversable (Vector n) where
sequenceA (Vector xs) = Vector <$> sequenceA xs
instance (KnownNat n, Read a) => Read (Vector n a) where
readsPrec p s = let xs = readsPrec p s :: [(V.Vector a, String)]
n' = fromIntegral (natVal (Proxy :: Proxy n))
in [(Vector ys, t) | (ys, t) <- xs, length ys == n']
instance (NFData a) => NFData (Vector n a) where
rnf (Vector v) = rnf v
(<%>) :: Num a => Vector n a -> Vector n a -> a
Vector v <%> Vector w = V.sum $ V.zipWith (*) v w
nil :: Vector 0 a
nil = Vector V.empty
cons :: forall a n. a -> Vector n a -> Vector (n + 1) a
cons x (Vector xs) = withNatOp (%+) (Proxy :: Proxy n) (Proxy :: Proxy 1) $ Vector $ V.cons x xs
generate :: forall n a. KnownNat n => (Int -> a) -> Vector n a
generate = Vector . V.generate (fromIntegral $ natVal (Proxy :: Proxy n))
(!?) :: Vector n a -> Int -> Maybe a
Vector v !? i = v V.!? i
(!) :: Vector n a -> Int -> a
v ! i = fromMaybe (error "Data.Utils.Vector.!: invalid index") (v !? i)
vhead :: (1 <= n) => Vector n a -> a
vhead (Vector v) = V.head v
vtail :: forall a n. (1 <= n) => Vector n a -> Vector (n 1) a
vtail (Vector v) = withNatOp (%-) (Proxy :: Proxy n) (Proxy :: Proxy 1) $ Vector (V.tail v)
infixl 6 <+>
(<+>) :: (Num a, KnownNat n) => Vector n a -> Vector n a -> Vector n a
v <+> w = (+) <$> v <*> w
infixl 6 <->
(<->) :: (Num a, KnownNat n) => Vector n a -> Vector n a -> Vector n a
v <-> w = () <$> v <*> w
sqNorm :: Num a => Vector n a -> a
sqNorm v = v <%> v
sqDiff :: (Num a, KnownNat n) => Vector n a -> Vector n a -> a
sqDiff v w = sqNorm (v <-> w)