]> gitweb.michael.orlitzky.com - numerical-analysis.git/blobdiff - src/Linear/Vector.hs
A huge pile of crap upon Matrix/Vector.
[numerical-analysis.git] / src / Linear / Vector.hs
index 7cc5e005ef22dab30af2ad8d0721550eecffd070..9774dcd40c8132413ddd541a2a65be8976a462e1 100644 (file)
@@ -11,6 +11,7 @@ import Data.List (intercalate)
 import Data.Vector.Fixed (
   Dim,
   Fun(..),
+  N1,
   N2,
   N3,
   N4,
@@ -20,119 +21,74 @@ import Data.Vector.Fixed (
   toList,
   )
 import qualified Data.Vector.Fixed as V (
-  eq,
-  foldl,
   length,
-  map,
-  replicate,
-  sum,
-  zipWith
   )
 
 import Normed
 
--- | The Vn newtype simply wraps (Vector v a) so that we avoid
---   undecidable instances.
-newtype Vn v a = Vn (v a)
 
--- | Declare the dimension of the wrapper to be the dimension of what
---   it contains.
-type instance Dim (Vn v) = Dim v
+-- * Low-dimension vector wrappers.
+--
+-- 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.
 
-instance (Vector v a) => Vector (Vn v) a where
-  -- | Fortunately, 'Fun' is an instance of 'Functor'. The
-  --   'construct' defined on our contained type will return a
-  --   'Fun', and we simply slap our constructor on top with fmap.
-  construct = fmap Vn construct
+data D1 a = D1 a
+type instance Dim D1 = N1
+instance Vector D1 a where
+  inspect (D1 x) (Fun f) = f x
+  construct = Fun D1
 
-  -- | Defer to the inspect defined on the contained type.
-  inspect (Vn v1) = inspect v1
+data D2 a = D2 a a
+type instance Dim D2 = N2
+instance Vector D2 a where
+  inspect (D2 x y) (Fun f) = f x y
+  construct = Fun D2
 
-instance (Show a, 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
-  --   vector lengths be statically checked at compile-time).
-  --
-  --   Examples:
-  --
-  --   >>> let v1 = make2d (1,2)
-  --   >>> show v1
-  --   (1,2)
-  --
-  show (Vn v1) =
-    "(" ++ (intercalate "," element_strings) ++ ")"
-    where
-      v1l = toList v1
-      element_strings = Prelude.map show v1l
+data D3 a = D3 a a a
+type instance Dim D3 = N3
+instance Vector D3 a where
+  inspect (D3 x y z) (Fun f) = f x y z
+  construct = Fun D3
+
+data D4 a = D4 a a a a
+type instance Dim D4 = N4
+instance Vector D4 a where
+  inspect (D4 w x y z) (Fun f) = f w x y z
+  construct = Fun D4
 
 
--- | We would really like to say, "anything that is a vector of
---   equatable things is itself equatable." The 'Vn' class
---   allows us to express this without a GHC battle.
+-- | Unsafe indexing.
 --
 --   Examples:
 --
---   >>> let v1 = make2d (1,2)
---   >>> let v2 = make2d (1,2)
---   >>> let v3 = make2d (3,4)
---   >>> v1 == v2
---   True
---   >>> v1 == v3
---   False
+--   >>> let v1 = Vec2D 1 2
+--   >>> v1 ! 1
+--   2
 --
-instance (Eq a, Vector v a) => Eq (Vn v a) where
-  (Vn v1) == (Vn v2) = v1 `V.eq` 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, Vector v a) => Num (Vn v a) where
-  -- | Componentwise addition.
-  --
-  --   Examples:
-  --
-  --   >>> let v1 = make2d (1,2)
-  --   >>> let v2 = make2d (3,4)
-  --   >>> v1 + v2
-  --   (4,6)
-  --
-  (Vn v1) + (Vn v2) = Vn $ V.zipWith (+) v1 v2
-
-  -- | Componentwise subtraction.
-  --
-  --   Examples:
-  --
-  --   >>> let v1 = make2d (1,2)
-  --   >>> let v2 = make2d (3,4)
-  --   >>> v1 - v2
-  --   (-2,-2)
-  --
-  (Vn v1) - (Vn v2) = Vn $ V.zipWith (-) v1 v2
+(!) :: (Vector v a) => v a -> Int -> a
+(!) v1 idx = (toList v1) !! idx
 
-  -- | Create an n-vector whose components are all equal to the given
-  --   integer. The result type must be specified since otherwise the
-  --   length n would be unknown.
-  --
-  --   Examples:
-  --
-  --   >>> let v1 = fromInteger 17 :: Vn Vec3 Int
-  --   (17,17,17)
-  --
-  fromInteger x = Vn $ V.replicate (fromInteger x)
-  (*) = error "multiplication of vectors is undefined"
-  abs = error "absolute value of vectors is undefined"
-  signum = error "signum of vectors is undefined"
+-- | Safe indexing.
+--
+--   Examples:
+--
+--   >>> let v1 = Vec3D 1 2 3
+--   >>> v1 !? 2
+--   Just 3
+--   >>> v1 !? 3
+--   Nothing
+--
+(!?) :: (Vector v a) => v a -> Int -> Maybe a
+(!?) v1 idx
+  | idx < 0 || idx >= V.length v1 = Nothing
+  | otherwise                     = Just $ v1 ! idx
 
 
--- | 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, Vector v a) => Normed (Vn v a) where
+--instance (RealFloat a, Ord a, 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.
@@ -143,7 +99,7 @@ instance (RealFloat a, Ord a, Vector v a) => Normed (Vn v a) where
   --   >>> norm_infty v1
   --   5
   --
-  norm_infty (Vn v1) = realToFrac $ V.foldl max 0 v1
+--  norm_infty (Vn v1) = realToFrac $ V.foldl max 0 v1
 
   -- | Generic p-norms. The usual norm in R^n is (norm_p 2).
   --
@@ -155,78 +111,16 @@ instance (RealFloat a, Ord a, Vector v a) => Normed (Vn v a) where
   --   >>> norm_p 2 v1
   --   5.0
   --
-  norm_p p (Vn v1) =
-    realToFrac $ root $ V.sum $ V.map (exponentiate . abs) v1
-    where
-      exponentiate = (** (fromIntegral p))
-      root = (** (recip (fromIntegral p)))
-
--- | Dot (standard inner) product.
---
---   Examples:
---
---   >>> let v1 = make3d (1,2,3)
---   >>> let v2 = make3d (4,5,6)
---   >>> dot v1 v2
---   32
---
-dot :: (Num a, Vector v a) => Vn v a -> Vn v a -> a
-dot (Vn v1) (Vn v2) = V.sum $ V.zipWith (*) v1 v2
-
-
--- | The angle between @v1@ and @v2@ in Euclidean space.
---
---   Examples:
---
---   >>> let v1 = make2d (1.0, 0.0)
---   >>> let v2 = make2d (0.0, 1.0)
---   >>> angle v1 v2 == pi/2.0
---   True
---
-angle :: (RealFloat a, 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)
+--  norm_p p (Vn v1) =
+--    realToFrac $ root $ V.sum $ V.map (exponentiate . abs) v1
+--    where
+--      exponentiate = (** (fromIntegral p))
+--      root = (** (recip (fromIntegral p)))
 
 
--- | Unsafe indexing.
---
---   Examples:
---
---   >>> let v1 = make2d (1,2)
---   >>> v1 ! 1
---   2
---
-(!) :: (Vector v a) => v a -> Int -> a
-(!) v1 idx = (toList v1) !! idx
 
--- | Safe indexing.
---
---   Examples:
---
---   >>> let v1 = make3d (1,2,3)
---   >>> v1 !? 2
---   Just 3
---   >>> v1 !? 3
---   Nothing
---
-(!?) :: (Vector v a) => v a -> Int -> Maybe a
-(!?) v1 idx
-  | idx < 0 || idx >= V.length v1 = Nothing
-  | otherwise                     = Just $ v1 ! idx
 
 
-
-
--- * Low-dimension vector wrappers.
---
--- 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.
-
 -- | Convenient constructor for 2D vectors.
 --
 --   Examples:
@@ -241,65 +135,3 @@ angle v1 v2 =
 --   >>> fixed_point g eps u0
 --   (1.0728549599342185,1.0820591495686167)
 --
-data Vec2D a = Vec2D a a
-type instance Dim Vec2D = N2
-instance Vector Vec2D a where
-  inspect (Vec2D x y) (Fun f) = f x y
-  construct = Fun Vec2D
-
-data Vec3D a = Vec3D a a a
-type instance Dim Vec3D = N3
-instance Vector Vec3D a where
-  inspect (Vec3D x y z) (Fun f) = f x y z
-  construct = Fun Vec3D
-
-data Vec4D a = Vec4D a a a a
-type instance Dim Vec4D = N4
-instance Vector Vec4D a where
-  inspect (Vec4D w x y z) (Fun f) = f w x y z
-  construct = Fun Vec4D
-
-
--- | Convenience function for creating 2d vectors.
---
---   Examples:
---
---   >>> let v1 = make2d (1,2)
---   >>> v1
---   (1,2)
---   >>> let Vn (Vec2D x y) = v1
---   >>> (x,y)
---   (1,2)
---
-make2d :: forall a. (a,a) -> Vn Vec2D a
-make2d (x,y) = Vn (Vec2D x y)
-
-
--- | Convenience function for creating 3d vectors.
---
---   Examples:
---
---   >>> let v1 = make3d (1,2,3)
---   >>> v1
---   (1,2,3)
---   >>> let Vn (Vec3D x y z) = v1
---   >>> (x,y,z)
---   (1,2,3)
---
-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)