X-Git-Url: http://gitweb.michael.orlitzky.com/?a=blobdiff_plain;f=src%2FNormed.hs;h=28fbd2878a2d02641820081da67578ba1166bce3;hb=d7e9e90017f1c9e6f515b6b5ab16d34966be070f;hp=b60c2b12fe84d51e0bf83b60ce0f958af55f7c10;hpb=74e79199dcfec0639133ae9990dc33a2c5a095f0;p=numerical-analysis.git diff --git a/src/Normed.hs b/src/Normed.hs index b60c2b1..28fbd28 100644 --- a/src/Normed.hs +++ b/src/Normed.hs @@ -1,29 +1,91 @@ {-# 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 +-- Ensure that we don't use the Lattice.C "max" function, that +-- only works on Integer/Bool. +import NumericPrelude hiding ( abs, max ) +import Algebra.Absolute ( abs ) +import qualified Algebra.Absolute as Absolute ( C ) +import qualified Algebra.Algebraic as Algebraic ( C ) +import Algebra.Algebraic ( root ) +import qualified Algebra.RealField as RealField ( C ) +import qualified Algebra.ToInteger as ToInteger ( C ) +import qualified Algebra.ToRational as ToRational ( C ) +import qualified Data.Vector.Fixed as V ( + Arity, + foldl, + map ) +import Data.Vector.Fixed.Boxed ( Vec ) +import qualified Prelude as P ( max ) +import Linear.Vector ( element_sum ) + + +-- | Instances of the 'Normed' class know how to compute their own +-- p-norms for p=1,2,...,infinity. +-- 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 2-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 + + +-- | 'Normed' instance for vectors of any length. We will generally be +-- working with n-by-1 /matrices/ instead of vectors, but sometimes +-- it's convenient to have these instances anyway. +-- +-- Examples: +-- +-- >>> import Data.Vector.Fixed (mk3) +-- >>> import Linear.Vector (Vec0, Vec3) +-- >>> let b = mk3 1 2 3 :: Vec3 Double +-- >>> norm_p 1 b :: Double +-- 6.0 +-- >>> norm b == sqrt 14 +-- True +-- >>> norm_infty b :: Double +-- 3.0 +-- +-- >>> let b = undefined :: Vec0 Int +-- >>> norm b +-- 0.0 +-- +instance (V.Arity n, Absolute.C a, ToRational.C a, Ord a) + => Normed (Vec n a) where + norm_p p x = + (root p') $ element_sum $ V.map element_function x + where + element_function y = fromRational' $ (toRational y)^p' + p' = toInteger p + + norm_infty x = fromRational' $ toRational $ (V.foldl P.max 0) $ V.map abs x