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