X-Git-Url: http://gitweb.michael.orlitzky.com/?a=blobdiff_plain;f=src%2FFixedVector.hs;h=402b02eeb531c743f3bd324a8ad3ad4652f8ef3b;hb=fb559d85500b113d9b1c74e8b6e3a033369154b9;hp=531c0fd7b9155a1db0987959f6544fcbf8747cfc;hpb=e73e40c515938df4de629dbc88463c5d88bca7c8;p=numerical-analysis.git diff --git a/src/FixedVector.hs b/src/FixedVector.hs index 531c0fd..402b02e 100644 --- a/src/FixedVector.hs +++ b/src/FixedVector.hs @@ -8,17 +8,19 @@ module FixedVector where import Data.List (intercalate) -import Data.Vector.Fixed as V -import Data.Vector.Fixed.Boxed +import qualified Data.Vector.Fixed as V 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, Vector v a) => Show (Vn (v a)) where +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 @@ -33,7 +35,7 @@ instance (Show a, Vector v a) => Show (Vn (v a)) where show (Vn v1) = "(" ++ (intercalate "," element_strings) ++ ")" where - v1l = toList v1 + v1l = V.toList v1 element_strings = Prelude.map show v1l @@ -51,14 +53,14 @@ instance (Show a, Vector v a) => Show (Vn (v a)) where -- >>> v1 == v3 -- False -- -instance (Eq a, Vector v a, 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, Vector v a) => Num (Vn (v a)) where +instance (Num a, V.Vector v a) => Num (Vn v a) where -- | Componentwise addition. -- -- Examples: @@ -87,7 +89,7 @@ instance (Num a, 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) @@ -95,10 +97,14 @@ instance (Num a, 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, 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. @@ -136,7 +142,7 @@ instance (RealFloat a, Ord a, Vector v a) => Normed (Vn (v a)) where -- >>> dot v1 v2 -- 32 -- -dot :: (Num a, 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 @@ -149,7 +155,7 @@ dot (Vn v1) (Vn v2) = V.sum $ V.zipWith (*) v1 v2 -- >>> angle v1 v2 == pi/2.0 -- True -- -angle :: (RealFloat a, 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 @@ -157,6 +163,109 @@ 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: +-- +-- >>> let v1 = make3d (1,2,3) +-- >>> v1 !? 2 +-- Just 3 +-- >>> 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 + + +-- | 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. +-- +-- 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. + +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 + +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 + +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. -- -- Examples: @@ -164,12 +273,12 @@ angle v1 v2 = -- >>> let v1 = make2d (1,2) -- >>> v1 -- (1,2) +-- >>> let Vn (Vec2D x y) = v1 +-- >>> (x,y) +-- (1,2) -- -make2d :: forall a. (a,a) -> Vn (Vec2 a) -make2d (x,y) = - Vn v1 - where - v1 = vec $ con |> x |> y :: Vec2 a +make2d :: forall a. (a,a) -> Vn Vec2D a +make2d (x,y) = Vn (Vec2D x y) -- | Convenience function for creating 3d vectors. @@ -179,9 +288,24 @@ make2d (x,y) = -- >>> 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 (Vec3 a) -make3d (x,y,z) = - Vn v1 - where - v1 = vec $ con |> x |> y |> z :: Vec3 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)