From: Michael Orlitzky Date: Sun, 3 Feb 2013 20:09:30 +0000 (-0500) Subject: Add cleaner Show instance for Vn. X-Git-Url: http://gitweb.michael.orlitzky.com/?p=numerical-analysis.git;a=commitdiff_plain;h=e15cc4256054bfaa60cd7ed167c0448957c85ed2 Add cleaner Show instance for Vn. Fix compiler warnings in FixedVector.hs. Add more doctests to FixedVector.hs. --- diff --git a/src/FixedVector.hs b/src/FixedVector.hs index c01ae60..6dabfb6 100644 --- a/src/FixedVector.hs +++ b/src/FixedVector.hs @@ -7,16 +7,35 @@ module FixedVector where +import Data.List (intercalate) import Data.Vector.Fixed as V import Data.Vector.Fixed.Boxed -import Data.Vector.Fixed.Internal import Normed -- | The Vn newtype simply wraps (Vector v a) so that we avoid -- undecidable instances. newtype Vn a = Vn a - deriving (Show) + + +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 + -- | We would really like to say, "anything that is a vector of -- equatable things is itself equatable." The 'Vn' class @@ -35,6 +54,7 @@ newtype Vn a = Vn a 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. @@ -46,11 +66,30 @@ instance (Num a, Vector v a) => Num (Vn (v a)) where -- >>> let v1 = make2d (1,2) -- >>> let v2 = make2d (3,4) -- >>> v1 + v2 - -- Vn fromList [4,6] + -- (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 + + -- | 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" @@ -60,11 +99,28 @@ instance Functor Vn where fmap f (Vn v1) = Vn (f v1) instance (RealFloat a, Ord a, Vector v a) => Normed (Vn (v a)) where - -- 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. + -- | 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. + -- + -- Examples: + -- + -- >>> let v1 = make3d (1,5,2) + -- >>> norm_infty v1 + -- 5 + -- norm_infty (Vn v1) = fromRational $ toRational $ V.foldl max 0 v1 + -- | Generic p-norms. The usual norm in R^n is (norm_p 2). + -- + -- Examples: + -- + -- >>> let v1 = make2d (3,4) + -- >>> norm_p 1 v1 + -- 7.0 + -- >>> norm_p 2 v1 + -- 5.0 + -- norm_p p (Vn v1) = fromRational $ toRational $ root $ V.sum $ V.map (exponentiate . abs) v1 where @@ -72,25 +128,58 @@ instance (RealFloat a, Ord a, Vector v a) => Normed (Vn (v a)) where 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_p 2 v1) * (norm_p 2 v2) + norms = (norm_p (2 :: Integer) v1) * (norm_p (2 :: Integer) v2) + --- | Convenience function for 2d vectors. +-- | Convenience function for creating 2d vectors. +-- +-- Examples: +-- +-- >>> let v1 = make2d (1,2) +-- >>> v1 +-- (1,2) +-- make2d :: forall a. (a,a) -> Vn (Vec2 a) make2d (x,y) = Vn v1 where v1 = vec $ con |> x |> y :: Vec2 a --- | Convenience function for 3d vectors. + +-- | Convenience function for creating 3d vectors. +-- +-- Examples: +-- +-- >>> let v1 = make3d (1,2,3) +-- >>> v1 +-- (1,2,3) +-- make3d :: forall a. (a,a,a) -> Vn (Vec3 a) make3d (x,y,z) = Vn v1