From 9bd0e10d2c4a18c21269d520190a5d6b65b6390f Mon Sep 17 00:00:00 2001 From: Michael Orlitzky Date: Mon, 4 Feb 2013 20:22:47 -0500 Subject: [PATCH] Clean up imports in FixedVector.hs. --- src/FixedVector.hs | 76 +++++++++++++++++++++++++++++----------------- 1 file changed, 48 insertions(+), 28 deletions(-) diff --git a/src/FixedVector.hs b/src/FixedVector.hs index 844b9b5..1bb828d 100644 --- a/src/FixedVector.hs +++ b/src/FixedVector.hs @@ -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,18 +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 (V.Vector v a) => V.Vector (Vn v) a where +instance (Vector v a) => Vector (Vn v) a where -- | Fortunately, 'Fun' is an instance of 'Functor'. The - -- 'V.construct' defined on our contained type will return a + -- 'construct' defined on our contained type will return a -- 'Fun', and we simply slap our constructor on top with fmap. - construct = fmap Vn V.construct + construct = fmap Vn construct - -- | Defer to the V.inspect defined on the contained type. - inspect (Vn v1) = V.inspect v1 + -- | Defer to the inspect defined on the contained type. + inspect (Vn v1) = inspect v1 -instance (Show a, V.Vector v a) => Show (Vn v a) where +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 @@ -44,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 @@ -62,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: @@ -113,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. @@ -151,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 @@ -164,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 @@ -182,10 +202,10 @@ angle v1 v2 = -- >>> v1 !? 3 -- Nothing -- -(!?) :: (V.Vector v a) => v a -> Int -> Maybe a +(!?) :: (Vector v a) => v a -> Int -> Maybe a (!?) v1 idx | idx < 0 || idx >= V.length v1 = Nothing - | otherwise = Just $ v1 V.! idx + | otherwise = Just $ v1 ! idx @@ -198,22 +218,22 @@ angle v1 v2 = -- 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. -- 2.49.0