]> gitweb.michael.orlitzky.com - numerical-analysis.git/blobdiff - src/Normed.hs
Remove old comment from Normed.
[numerical-analysis.git] / src / Normed.hs
index b60c2b12fe84d51e0bf83b60ce0f958af55f7c10..f339ebfd6757a86123f8111c4cb1bb7f5ef35534 100644 (file)
@@ -1,29 +1,45 @@
 {-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE RebindableSyntax #-}
 
 -- | The 'Normed' class represents elements of a normed vector
 --   space. We define instances for all common numeric types.
 module Normed
 where
 
-import Data.Number.BigFloat
+import BigFloat
+
+import NumericPrelude hiding (abs)
+import Algebra.Absolute (abs)
+import qualified Algebra.Absolute as Absolute
+import qualified Algebra.Algebraic as Algebraic
+import qualified Algebra.RealField as RealField
+import qualified Algebra.ToInteger as ToInteger
 
 class Normed a where
-  norm_p :: (Integral c, RealFrac b) => c -> a -> b
-  norm_infty :: RealFrac b => a -> b
+  norm_p :: (ToInteger.C c, Algebraic.C b, Absolute.C b) => c -> a -> b
+  norm_infty :: (RealField.C b) => a -> b
+
+  -- | The "usual" norm. Defaults to the Euclidean norm.
+  norm :: (Algebraic.C b, Absolute.C b) => a -> b
+  norm = norm_p (2 :: Integer)
 
 -- Define instances for common numeric types.
 instance Normed Integer where
-  norm_p _ = fromInteger
-  norm_infty = fromInteger
+  norm_p _ = abs . fromInteger
+  norm_infty = abs . fromInteger
 
 instance Normed Rational where
-  norm_p _ = fromRational
-  norm_infty = fromRational
+  norm_p _ = abs . fromRational'
+  norm_infty = abs . fromRational'
 
 instance Epsilon e => Normed (BigFloat e) where
-  norm_p _ = fromRational . toRational
-  norm_infty = fromRational . toRational
+  norm_p _ = abs . fromRational' . toRational
+  norm_infty = abs . fromRational' . toRational
+
+instance Normed Float where
+  norm_p _ = abs . fromRational' . toRational
+  norm_infty = abs . fromRational' . toRational
 
 instance Normed Double where
-  norm_p _ = fromRational . toRational
-  norm_infty = fromRational . toRational
+  norm_p _ = abs . fromRational' . toRational
+  norm_infty = abs . fromRational' . toRational