]> gitweb.michael.orlitzky.com - numerical-analysis.git/blobdiff - src/FixedVector.hs
Clean up imports in FixedVector.hs.
[numerical-analysis.git] / src / FixedVector.hs
index 402b02eeb531c743f3bd324a8ad3ad4652f8ef3b..1bb828d243444be2e33d86442b2cdff7e88dba3a 100644 (file)
@@ -8,7 +8,27 @@ module FixedVector
 where
 
 import Data.List (intercalate)
-import qualified Data.Vector.Fixed as V
+import Data.Vector.Fixed (
+  Dim,
+  Fun(..),
+  N1,
+  N2,
+  N3,
+  N4,
+  Vector(..),
+  (!),
+  construct,
+  inspect,
+  toList,
+  )
+import qualified Data.Vector.Fixed as V (
+  foldl,
+  length,
+  map,
+  replicate,
+  sum,
+  zipWith
+  )
 
 import Normed
 
@@ -18,9 +38,18 @@ 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
+type instance Dim (Vn v) = Dim v
 
-instance (Show a, V.Vector v a) => Show (Vn v a) where
+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
+
+  -- | Defer to the inspect defined on the contained type.
+  inspect (Vn v1) = inspect v1
+
+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
@@ -35,7 +64,7 @@ instance (Show a, V.Vector v a) => Show (Vn v a) where
   show (Vn v1) =
     "(" ++ (intercalate "," element_strings) ++ ")"
     where
-      v1l = V.toList v1
+      v1l = toList v1
       element_strings = Prelude.map show v1l
 
 
@@ -53,14 +82,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, Vector v a, 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, Vector v a) => Num (Vn v a) where
   -- | Componentwise addition.
   --
   --   Examples:
@@ -104,7 +133,7 @@ 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
+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.
@@ -142,7 +171,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, Vector v a) => Vn v a -> Vn v a -> a
 dot (Vn v1) (Vn v2) = V.sum $ V.zipWith (*) v1 v2
 
 
@@ -155,7 +184,7 @@ 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, Vector v a) => Vn v a -> Vn v a -> a
 angle v1 v2 =
   acos theta
   where
@@ -163,32 +192,6 @@ angle v1 v2 =
     norms = (norm v1) * (norm v2)
 
 
--- | The length of a vector.
---
---   Examples:
---
---   >>> let v1 = make2d (1,2)
---   >>> length v1
---   2
---
-length :: (V.Vector v a) => Vn v a -> Int
-length (Vn v1) = V.length v1
-
-
--- | 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:
@@ -199,45 +202,12 @@ length (Vn v1) = V.length v1
 --   >>> v1 !? 3
 --   Nothing
 --
-(!?) :: (V.Vector v a) => Vn v a -> Int -> Maybe a
-(!?) v1@(Vn v2) idx
-  | idx < 0 || idx >= V.length v2 = Nothing
+(!?) :: (Vector v a) => v a -> Int -> Maybe a
+(!?) v1 idx
+  | idx < 0 || idx >= V.length v1 = Nothing
   | otherwise                     = Just $ v1 ! idx
 
 
--- | Convert vector to a list.
---
---   Examples:
---
---   >>> let v1 = make2d (1,2)
---   >>> toList v1
---   [1,2]
---
-toList :: (V.Vector v a) => Vn v a -> [a]
-toList (Vn v1) = V.toList v1
-
-
--- | Convert a list to a vector.
---
---   Examples:
---
---   >>> fromList [1,2] :: Vn Vec2D Int
---   (1,2)
---
-fromList :: (V.Vector v a) => [a] -> Vn v a
-fromList xs = Vn $ V.fromList xs
-
--- | Map a function over a vector.
---
---   Examples:
---
---   >>> let v1 = make2d (1,2)
---   >>> map (*2) v1
---   (2,4)
---
-map :: (V.Vector v a, V.Vector v b) => (a -> b) -> Vn v a -> Vn v b
-map f (Vn vs) = Vn $ V.map f vs
-
 
 
 -- * Low-dimension vector wrappers.
@@ -248,22 +218,22 @@ map f (Vn vs) = Vn $ V.map f vs
 -- components.
 
 data Vec2D a = Vec2D a a
-type instance V.Dim Vec2D = V.N2
-instance V.Vector Vec2D a where
-  inspect (Vec2D x y) (V.Fun f) = f x y
-  construct = V.Fun Vec2D
+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 V.Dim Vec3D = V.N3
-instance V.Vector Vec3D a where
-  inspect (Vec3D x y z) (V.Fun f) = f x y z
-  construct = V.Fun Vec3D
+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 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
+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.