]> gitweb.michael.orlitzky.com - numerical-analysis.git/blob - src/FixedVector.hs
531c0fd7b9155a1db0987959f6544fcbf8747cfc
[numerical-analysis.git] / src / FixedVector.hs
1 {-# LANGUAGE FlexibleContexts #-}
2 {-# LANGUAGE FlexibleInstances #-}
3 {-# LANGUAGE MultiParamTypeClasses #-}
4 {-# LANGUAGE ScopedTypeVariables #-}
5 {-# LANGUAGE TypeFamilies #-}
6
7 module FixedVector
8 where
9
10 import Data.List (intercalate)
11 import Data.Vector.Fixed as V
12 import Data.Vector.Fixed.Boxed
13
14 import Normed
15
16 -- | The Vn newtype simply wraps (Vector v a) so that we avoid
17 -- undecidable instances.
18 newtype Vn a = Vn a
19
20
21 instance (Show a, Vector v a) => Show (Vn (v a)) where
22 -- | Display vectors as ordinary tuples. This is poor practice, but
23 -- these results are primarily displayed interactively and
24 -- convenience trumps correctness (said the guy who insists his
25 -- vector lengths be statically checked at compile-time).
26 --
27 -- Examples:
28 --
29 -- >>> let v1 = make2d (1,2)
30 -- >>> show v1
31 -- (1,2)
32 --
33 show (Vn v1) =
34 "(" ++ (intercalate "," element_strings) ++ ")"
35 where
36 v1l = toList v1
37 element_strings = Prelude.map show v1l
38
39
40 -- | We would really like to say, "anything that is a vector of
41 -- equatable things is itself equatable." The 'Vn' class
42 -- allows us to express this without a GHC battle.
43 --
44 -- Examples:
45 --
46 -- >>> let v1 = make2d (1,2)
47 -- >>> let v2 = make2d (1,2)
48 -- >>> let v3 = make2d (3,4)
49 -- >>> v1 == v2
50 -- True
51 -- >>> v1 == v3
52 -- False
53 --
54 instance (Eq a, Vector v a, Vector v Bool) => Eq (Vn (v a)) where
55 (Vn v1) == (Vn v2) = V.foldl (&&) True (V.zipWith (==) v1 v2)
56
57
58 -- | The use of 'Num' here is of course incorrect (otherwise, we
59 -- wouldn't have to throw errors). But it's really nice to be able
60 -- to use normal addition/subtraction.
61 instance (Num a, Vector v a) => Num (Vn (v a)) where
62 -- | Componentwise addition.
63 --
64 -- Examples:
65 --
66 -- >>> let v1 = make2d (1,2)
67 -- >>> let v2 = make2d (3,4)
68 -- >>> v1 + v2
69 -- (4,6)
70 --
71 (Vn v1) + (Vn v2) = Vn $ V.zipWith (+) v1 v2
72
73 -- | Componentwise subtraction.
74 --
75 -- Examples:
76 --
77 -- >>> let v1 = make2d (1,2)
78 -- >>> let v2 = make2d (3,4)
79 -- >>> v1 - v2
80 -- (-2,-2)
81 --
82 (Vn v1) - (Vn v2) = Vn $ V.zipWith (-) v1 v2
83
84 -- | Create an n-vector whose components are all equal to the given
85 -- integer. The result type must be specified since otherwise the
86 -- length n would be unknown.
87 --
88 -- Examples:
89 --
90 -- >>> let v1 = fromInteger 17 :: Vn (Vec3 Int)
91 -- (17,17,17)
92 --
93 fromInteger x = Vn $ V.replicate (fromInteger x)
94 (*) = error "multiplication of vectors is undefined"
95 abs = error "absolute value of vectors is undefined"
96 signum = error "signum of vectors is undefined"
97
98 instance Functor Vn where
99 fmap f (Vn v1) = Vn (f v1)
100
101 instance (RealFloat a, Ord a, Vector v a) => Normed (Vn (v a)) where
102 -- | The infinity norm. We don't use V.maximum here because it
103 -- relies on a type constraint that the vector be non-empty and I
104 -- don't know how to pattern match it away.
105 --
106 -- Examples:
107 --
108 -- >>> let v1 = make3d (1,5,2)
109 -- >>> norm_infty v1
110 -- 5
111 --
112 norm_infty (Vn v1) = fromRational $ toRational $ V.foldl max 0 v1
113
114 -- | Generic p-norms. The usual norm in R^n is (norm_p 2).
115 --
116 -- Examples:
117 --
118 -- >>> let v1 = make2d (3,4)
119 -- >>> norm_p 1 v1
120 -- 7.0
121 -- >>> norm_p 2 v1
122 -- 5.0
123 --
124 norm_p p (Vn v1) =
125 fromRational $ toRational $ root $ V.sum $ V.map (exponentiate . abs) v1
126 where
127 exponentiate = (** (fromIntegral p))
128 root = (** (recip (fromIntegral p)))
129
130 -- | Dot (standard inner) product.
131 --
132 -- Examples:
133 --
134 -- >>> let v1 = make3d (1,2,3)
135 -- >>> let v2 = make3d (4,5,6)
136 -- >>> dot v1 v2
137 -- 32
138 --
139 dot :: (Num a, Vector v a) => Vn (v a) -> Vn (v a) -> a
140 dot (Vn v1) (Vn v2) = V.sum $ V.zipWith (*) v1 v2
141
142
143 -- | The angle between @v1@ and @v2@ in Euclidean space.
144 --
145 -- Examples:
146 --
147 -- >>> let v1 = make2d (1.0, 0.0)
148 -- >>> let v2 = make2d (0.0, 1.0)
149 -- >>> angle v1 v2 == pi/2.0
150 -- True
151 --
152 angle :: (RealFloat a, Vector v a) => Vn (v a) -> Vn (v a) -> a
153 angle v1 v2 =
154 acos theta
155 where
156 theta = (v1 `dot` v2) / norms
157 norms = (norm v1) * (norm v2)
158
159
160 -- | Convenience function for creating 2d vectors.
161 --
162 -- Examples:
163 --
164 -- >>> let v1 = make2d (1,2)
165 -- >>> v1
166 -- (1,2)
167 --
168 make2d :: forall a. (a,a) -> Vn (Vec2 a)
169 make2d (x,y) =
170 Vn v1
171 where
172 v1 = vec $ con |> x |> y :: Vec2 a
173
174
175 -- | Convenience function for creating 3d vectors.
176 --
177 -- Examples:
178 --
179 -- >>> let v1 = make3d (1,2,3)
180 -- >>> v1
181 -- (1,2,3)
182 --
183 make3d :: forall a. (a,a,a) -> Vn (Vec3 a)
184 make3d (x,y,z) =
185 Vn v1
186 where
187 v1 = vec $ con |> x |> y |> z :: Vec3 a