module TwoTuple
where
+import Vector
+
+
data TwoTuple a = TwoTuple a a
deriving (Eq, Show)
instance Functor TwoTuple where
f `fmap` (TwoTuple x1 y1) = TwoTuple (f x1) (f y1)
+instance (RealFloat a) => Vector (TwoTuple a) where
+ -- The standard Euclidean 2-norm. We need RealFloat for the square
+ -- root.
+ norm (TwoTuple x1 y1) = fromRational $ toRational (sqrt(x1^2 + y1^2))
+-- | It's not correct to use Num here, but I really don't want to have
+-- to define my own addition and subtraction.
instance Num a => Num (TwoTuple a) where
-- Standard componentwise addition.
(TwoTuple x1 y1) + (TwoTuple x2 y2) =
--- /dev/null
+{-# LANGUAGE FlexibleInstances #-}
+
+-- | The 'Vector' class represents elements of a normed vector
+-- space. We define instances for all common numeric types.
+module Vector
+where
+
+import Data.Number.BigFloat
+
+class Vector a where
+ norm :: RealFrac b => a -> b
+
+-- Define instances for common numeric types.
+instance Vector Integer where
+ norm = fromInteger
+
+instance Vector Rational where
+ norm = fromRational
+
+instance Epsilon e => Vector (BigFloat e) where
+ norm = fromRational . toRational
+
+instance Vector Double where
+ norm = fromRational . toRational