]> gitweb.michael.orlitzky.com - numerical-analysis.git/blob - src/Normed.hs
src/Normed.hs: combine zero- and nonzero-length implementations.
[numerical-analysis.git] / src / Normed.hs
1 {-# LANGUAGE FlexibleInstances #-}
2 {-# LANGUAGE RebindableSyntax #-}
3
4 -- | The 'Normed' class represents elements of a normed vector
5 -- space. We define instances for all common numeric types.
6 module Normed
7 where
8
9 import BigFloat
10
11 -- Ensure that we don't use the Lattice.C "max" function, that
12 -- only works on Integer/Bool.
13 import NumericPrelude hiding ( abs, max )
14 import Algebra.Absolute ( abs )
15 import qualified Algebra.Absolute as Absolute ( C )
16 import qualified Algebra.Algebraic as Algebraic ( C )
17 import Algebra.Algebraic ( root )
18 import qualified Algebra.RealField as RealField ( C )
19 import qualified Algebra.ToInteger as ToInteger ( C )
20 import qualified Algebra.ToRational as ToRational ( C )
21 import qualified Data.Vector.Fixed as V (
22 Arity,
23 foldl,
24 map )
25 import Data.Vector.Fixed.Boxed ( Vec )
26 import qualified Prelude as P ( max )
27 import Linear.Vector ( element_sum )
28
29
30 -- | Instances of the 'Normed' class know how to compute their own
31 -- p-norms for p=1,2,...,infinity.
32 --
33 class Normed a where
34 norm_p :: (ToInteger.C c, Algebraic.C b, Absolute.C b) => c -> a -> b
35 norm_infty :: (RealField.C b) => a -> b
36
37 -- | The \"usual\" norm. Defaults to the 2-norm.
38 norm :: (Algebraic.C b, Absolute.C b) => a -> b
39 norm = norm_p (2 :: Integer)
40
41 -- Define instances for common numeric types.
42 instance Normed Integer where
43 norm_p _ = abs . fromInteger
44 norm_infty = abs . fromInteger
45
46 instance Normed Rational where
47 norm_p _ = abs . fromRational'
48 norm_infty = abs . fromRational'
49
50 instance Epsilon e => Normed (BigFloat e) where
51 norm_p _ = abs . fromRational' . toRational
52 norm_infty = abs . fromRational' . toRational
53
54 instance Normed Float where
55 norm_p _ = abs . fromRational' . toRational
56 norm_infty = abs . fromRational' . toRational
57
58 instance Normed Double where
59 norm_p _ = abs . fromRational' . toRational
60 norm_infty = abs . fromRational' . toRational
61
62
63 -- | 'Normed' instance for vectors of any length. We will generally be
64 -- working with n-by-1 /matrices/ instead of vectors, but sometimes
65 -- it's convenient to have these instances anyway.
66 --
67 -- Examples:
68 --
69 -- >>> import Data.Vector.Fixed (mk3)
70 -- >>> import Linear.Vector (Vec0, Vec3)
71 -- >>> let b = mk3 1 2 3 :: Vec3 Double
72 -- >>> norm_p 1 b :: Double
73 -- 6.0
74 -- >>> norm b == sqrt 14
75 -- True
76 -- >>> norm_infty b :: Double
77 -- 3.0
78 --
79 -- >>> let b = undefined :: Vec0 Int
80 -- >>> norm b
81 -- 0.0
82 --
83 instance (V.Arity n, Absolute.C a, ToRational.C a, Ord a)
84 => Normed (Vec n a) where
85 norm_p p x =
86 (root p') $ element_sum $ V.map element_function x
87 where
88 element_function y = fromRational' $ (toRational y)^p'
89 p' = toInteger p
90
91 norm_infty x = fromRational' $ toRational $ (V.foldl P.max 0) $ V.map abs x