]> gitweb.michael.orlitzky.com - numerical-analysis.git/blob - src/Normed.hs
6f34a8dca406c13393896179b6b08c023874e9a3
[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 import NumericPrelude hiding ( abs )
12 import Algebra.Absolute ( abs )
13 import qualified Algebra.Absolute as Absolute
14 import qualified Algebra.Algebraic as Algebraic
15 import Algebra.Algebraic ( root )
16 import qualified Algebra.RealField as RealField
17 import qualified Algebra.ToInteger as ToInteger
18 import qualified Algebra.ToRational as ToRational ( C )
19 import Data.Vector.Fixed ( S, Z )
20 import qualified Data.Vector.Fixed as V (
21 Arity,
22 map,
23 maximum )
24 import Data.Vector.Fixed.Boxed ( Vec )
25
26 import Linear.Vector ( element_sum )
27
28 class Normed a where
29 norm_p :: (ToInteger.C c, Algebraic.C b, Absolute.C b) => c -> a -> b
30 norm_infty :: (RealField.C b) => a -> b
31
32 -- | The "usual" norm. Defaults to the Euclidean norm.
33 norm :: (Algebraic.C b, Absolute.C b) => a -> b
34 norm = norm_p (2 :: Integer)
35
36 -- Define instances for common numeric types.
37 instance Normed Integer where
38 norm_p _ = abs . fromInteger
39 norm_infty = abs . fromInteger
40
41 instance Normed Rational where
42 norm_p _ = abs . fromRational'
43 norm_infty = abs . fromRational'
44
45 instance Epsilon e => Normed (BigFloat e) where
46 norm_p _ = abs . fromRational' . toRational
47 norm_infty = abs . fromRational' . toRational
48
49 instance Normed Float where
50 norm_p _ = abs . fromRational' . toRational
51 norm_infty = abs . fromRational' . toRational
52
53 instance Normed Double where
54 norm_p _ = abs . fromRational' . toRational
55 norm_infty = abs . fromRational' . toRational
56
57
58 -- | 'Normed' instance for vectors of length zero. These are easy.
59 instance Normed (Vec Z a) where
60 norm_p _ = const (fromInteger 0)
61 norm_infty = const (fromInteger 0)
62
63
64 -- | 'Normed' instance for vectors of length greater than zero. We
65 -- need to know that the length is non-zero in order to invoke
66 -- V.maximum. We will generally be working with n-by-1 /matrices/
67 -- instead of vectors, but sometimes it's convenient to have these
68 -- instances anyway.
69 --
70 -- Examples:
71 --
72 -- >>> import Data.Vector.Fixed (mk3)
73 -- >>> import Linear.Vector (Vec3)
74 -- >>> let b = mk3 1 2 3 :: Vec3 Double
75 -- >>> norm_p 1 b :: Double
76 -- 6.0
77 -- >>> norm b == sqrt 14
78 -- True
79 -- >>> norm_infty b :: Double
80 -- 3.0
81 --
82 instance (V.Arity n, Absolute.C a, ToRational.C a, Ord a)
83 => Normed (Vec (S n) a) where
84 norm_p p x =
85 (root p') $ element_sum $ V.map element_function x
86 where
87 element_function y = fromRational' $ (toRational y)^p'
88 p' = toInteger p
89
90 norm_infty x = fromRational' $ toRational $ V.maximum $ V.map abs x