]> gitweb.michael.orlitzky.com - numerical-analysis.git/blobdiff - src/FixedVector.hs
Remove reimplemented vector functions from FixedVector.hs.
[numerical-analysis.git] / src / FixedVector.hs
index 0a5312a981fb08ebc45cc67a08c21fc288899d8a..844b9b59e1f12c03e86afe336c2c494494666ea2 100644 (file)
@@ -14,10 +14,22 @@ import Normed
 
 -- | The Vn newtype simply wraps (Vector v a) so that we avoid
 --   undecidable instances.
-newtype Vn a = Vn a
+newtype Vn v a = Vn (v a)
 
+-- | Declare the dimension of the wrapper to be the dimension of what
+--   it contains.
+type instance V.Dim (Vn v) = V.Dim v
 
-instance (Show a, V.Vector v a) => Show (Vn (v a)) where
+instance (V.Vector v a) => V.Vector (Vn v) a where
+  -- | Fortunately, 'Fun' is an instance of 'Functor'. The
+  --   'V.construct' defined on our contained type will return a
+  --   'Fun', and we simply slap our constructor on top with fmap.
+  construct = fmap Vn V.construct
+
+  -- | Defer to the V.inspect defined on the contained type.
+  inspect (Vn v1) = V.inspect v1
+
+instance (Show a, V.Vector v a) => Show (Vn v a) where
   -- | Display vectors as ordinary tuples. This is poor practice, but
   --   these results are primarily displayed interactively and
   --   convenience trumps correctness (said the guy who insists his
@@ -50,14 +62,14 @@ instance (Show a, V.Vector v a) => Show (Vn (v a)) where
 --   >>> v1 == v3
 --   False
 --
-instance (Eq a, V.Vector v a, V.Vector v Bool) => Eq (Vn (v a)) where
+instance (Eq a, V.Vector v a, V.Vector v Bool) => Eq (Vn v a) where
   (Vn v1) == (Vn v2) = V.foldl (&&) True (V.zipWith (==) v1 v2)
 
 
 -- | The use of 'Num' here is of course incorrect (otherwise, we
 --   wouldn't have to throw errors). But it's really nice to be able
 --   to use normal addition/subtraction.
-instance (Num a, V.Vector v a) => Num (Vn (v a)) where
+instance (Num a, V.Vector v a) => Num (Vn v a) where
   -- | Componentwise addition.
   --
   --   Examples:
@@ -86,7 +98,7 @@ instance (Num a, V.Vector v a) => Num (Vn (v a)) where
   --
   --   Examples:
   --
-  --   >>> let v1 = fromInteger 17 :: Vn (Vec3 Int)
+  --   >>> let v1 = fromInteger 17 :: Vn Vec3 Int
   --   (17,17,17)
   --
   fromInteger x = Vn $ V.replicate (fromInteger x)
@@ -94,10 +106,14 @@ instance (Num a, V.Vector v a) => Num (Vn (v a)) where
   abs = error "absolute value of vectors is undefined"
   signum = error "signum of vectors is undefined"
 
-instance Functor Vn where
-  fmap f (Vn v1) = Vn (f v1)
 
-instance (RealFloat a, Ord a, V.Vector v a) => Normed (Vn (v a)) where
+-- | This is probably useless, since the vectors we usually contain
+--   aren't functor instances.
+instance (Functor v) => Functor (Vn v) where
+  fmap f (Vn v1) = Vn (f `fmap` v1)
+
+
+instance (RealFloat a, Ord a, V.Vector v a) => Normed (Vn v a) where
   -- | The infinity norm. We don't use V.maximum here because it
   --   relies on a type constraint that the vector be non-empty and I
   --   don't know how to pattern match it away.
@@ -135,7 +151,7 @@ instance (RealFloat a, Ord a, V.Vector v a) => Normed (Vn (v a)) where
 --   >>> dot v1 v2
 --   32
 --
-dot :: (Num a, V.Vector v a) => Vn (v a) -> Vn (v a) -> a
+dot :: (Num a, V.Vector v a) => Vn v a -> Vn v a -> a
 dot (Vn v1) (Vn v2) = V.sum $ V.zipWith (*) v1 v2
 
 
@@ -148,28 +164,16 @@ dot (Vn v1) (Vn v2) = V.sum $ V.zipWith (*) v1 v2
 --   >>> angle v1 v2 == pi/2.0
 --   True
 --
-angle :: (RealFloat a, V.Vector v a) => Vn (v a) -> Vn (v a) -> a
+angle :: (RealFloat a, V.Vector v a) => Vn v a -> Vn v a -> a
 angle v1 v2 =
   acos theta
   where
     theta = (v1 `dot` v2) / norms
     norms = (norm v1) * (norm v2)
 
--- | Unsafe indexing.
---
---   Examples:
---
---   >>> let v1 = make3d (1,2,3)
---   >>> v1 ! 2
---   3
---   >>> v1 ! 3
---   *** Exception: Data.Vector.Fixed.!: index out of range
---
-(!) :: (V.Vector v a) => Vn (v a) -> Int -> a
-(!) (Vn v1) idx = v1 V.! idx
-
 
 -- | Safe indexing.
+--
 --   Examples:
 --
 --   >>> let v1 = make3d (1,2,3)
@@ -178,16 +182,18 @@ angle v1 v2 =
 --   >>> v1 !? 3
 --   Nothing
 --
-(!?) :: (V.Vector v a) => Vn (v a) -> Int -> Maybe a
-(!?) v1@(Vn v2) idx
-  | idx < 0 || idx >= V.length v2 = Nothing
-  | otherwise                     = Just $ v1 ! idx
+(!?) :: (V.Vector v a) => v a -> Int -> Maybe a
+(!?) v1 idx
+  | idx < 0 || idx >= V.length v1 = Nothing
+  | otherwise                     = Just $ v1 V.! idx
 
 
--- * Two- and three-dimensional wrappers.
+
+
+-- * Low-dimension vector wrappers.
 --
--- These two wrappers are instances of 'Vector', so they inherit all
--- of the userful instances defined above. But, they use fixed
+-- These wrappers are instances of 'Vector', so they inherit all of
+-- the userful instances defined above. But, they use fixed
 -- constructors, so you can pattern match out the individual
 -- components.
 
@@ -203,6 +209,12 @@ instance V.Vector Vec3D a where
   inspect (Vec3D x y z) (V.Fun f) = f x y z
   construct = V.Fun Vec3D
 
+data Vec4D a = Vec4D a a a a
+type instance V.Dim Vec4D = V.N4
+instance V.Vector Vec4D a where
+  inspect (Vec4D w x y z) (V.Fun f) = f w x y z
+  construct = V.Fun Vec4D
+
 
 -- | Convenience function for creating 2d vectors.
 --
@@ -215,7 +227,7 @@ instance V.Vector Vec3D a where
 --   >>> (x,y)
 --   (1,2)
 --
-make2d :: forall a. (a,a) -> Vn (Vec2D a)
+make2d :: forall a. (a,a) -> Vn Vec2D a
 make2d (x,y) = Vn (Vec2D x y)
 
 
@@ -230,5 +242,20 @@ make2d (x,y) = Vn (Vec2D x y)
 --   >>> (x,y,z)
 --   (1,2,3)
 --
-make3d :: forall a. (a,a,a) -> Vn (Vec3D a)
+make3d :: forall a. (a,a,a) -> Vn Vec3D a
 make3d (x,y,z) = Vn (Vec3D x y z)
+
+
+-- | Convenience function for creating 4d vectors.
+--
+--   Examples:
+--
+--   >>> let v1 = make4d (1,2,3,4)
+--   >>> v1
+--   (1,2,3,4)
+--   >>> let Vn (Vec4D w x y z) = v1
+--   >>> (w,x,y,z)
+--   (1,2,3,4)
+--
+make4d :: forall a. (a,a,a,a) -> Vn Vec4D a
+make4d (w,x,y,z) = Vn (Vec4D w x y z)