From bd4568f6d35d814481d246f48b44ebc651f1534d Mon Sep 17 00:00:00 2001 From: Michael Orlitzky Date: Sun, 3 Feb 2013 17:20:38 -0500 Subject: [PATCH] Add 2d/3d wrapper types for easy pattern matching. Implement both safe and unsafe indexing. --- src/FixedVector.hs | 85 +++++++++++++++++++++++++++++++++++----------- 1 file changed, 66 insertions(+), 19 deletions(-) diff --git a/src/FixedVector.hs b/src/FixedVector.hs index 531c0fd..0a5312a 100644 --- a/src/FixedVector.hs +++ b/src/FixedVector.hs @@ -8,8 +8,7 @@ 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 @@ -18,7 +17,7 @@ import Normed newtype Vn a = Vn a -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 +32,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 +50,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: @@ -98,7 +97,7 @@ instance (Num a, Vector v a) => Num (Vn (v a)) where instance Functor Vn where fmap f (Vn v1) = Vn (f v1) -instance (RealFloat a, Ord a, Vector v a) => Normed (Vn (v a)) where +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 +135,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,13 +148,61 @@ 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 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) +-- >>> 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 + + +-- * Two- and three-dimensional wrappers. +-- +-- These two 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 + -- | Convenience function for creating 2d vectors. -- @@ -164,12 +211,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 +226,9 @@ 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) -- 2.43.2