]> gitweb.michael.orlitzky.com - numerical-analysis.git/blob - src/FixedVector.hs
402b02eeb531c743f3bd324a8ad3ad4652f8ef3b
[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 qualified Data.Vector.Fixed as V
12
13 import Normed
14
15 -- | The Vn newtype simply wraps (Vector v a) so that we avoid
16 -- undecidable instances.
17 newtype Vn v a = Vn (v a)
18
19 -- | Declare the dimension of the wrapper to be the dimension of what
20 -- it contains.
21 type instance V.Dim (Vn v) = V.Dim v
22
23 instance (Show a, V.Vector v a) => Show (Vn v a) where
24 -- | Display vectors as ordinary tuples. This is poor practice, but
25 -- these results are primarily displayed interactively and
26 -- convenience trumps correctness (said the guy who insists his
27 -- vector lengths be statically checked at compile-time).
28 --
29 -- Examples:
30 --
31 -- >>> let v1 = make2d (1,2)
32 -- >>> show v1
33 -- (1,2)
34 --
35 show (Vn v1) =
36 "(" ++ (intercalate "," element_strings) ++ ")"
37 where
38 v1l = V.toList v1
39 element_strings = Prelude.map show v1l
40
41
42 -- | We would really like to say, "anything that is a vector of
43 -- equatable things is itself equatable." The 'Vn' class
44 -- allows us to express this without a GHC battle.
45 --
46 -- Examples:
47 --
48 -- >>> let v1 = make2d (1,2)
49 -- >>> let v2 = make2d (1,2)
50 -- >>> let v3 = make2d (3,4)
51 -- >>> v1 == v2
52 -- True
53 -- >>> v1 == v3
54 -- False
55 --
56 instance (Eq a, V.Vector v a, V.Vector v Bool) => Eq (Vn v a) where
57 (Vn v1) == (Vn v2) = V.foldl (&&) True (V.zipWith (==) v1 v2)
58
59
60 -- | The use of 'Num' here is of course incorrect (otherwise, we
61 -- wouldn't have to throw errors). But it's really nice to be able
62 -- to use normal addition/subtraction.
63 instance (Num a, V.Vector v a) => Num (Vn v a) where
64 -- | Componentwise addition.
65 --
66 -- Examples:
67 --
68 -- >>> let v1 = make2d (1,2)
69 -- >>> let v2 = make2d (3,4)
70 -- >>> v1 + v2
71 -- (4,6)
72 --
73 (Vn v1) + (Vn v2) = Vn $ V.zipWith (+) v1 v2
74
75 -- | Componentwise subtraction.
76 --
77 -- Examples:
78 --
79 -- >>> let v1 = make2d (1,2)
80 -- >>> let v2 = make2d (3,4)
81 -- >>> v1 - v2
82 -- (-2,-2)
83 --
84 (Vn v1) - (Vn v2) = Vn $ V.zipWith (-) v1 v2
85
86 -- | Create an n-vector whose components are all equal to the given
87 -- integer. The result type must be specified since otherwise the
88 -- length n would be unknown.
89 --
90 -- Examples:
91 --
92 -- >>> let v1 = fromInteger 17 :: Vn Vec3 Int
93 -- (17,17,17)
94 --
95 fromInteger x = Vn $ V.replicate (fromInteger x)
96 (*) = error "multiplication of vectors is undefined"
97 abs = error "absolute value of vectors is undefined"
98 signum = error "signum of vectors is undefined"
99
100
101 -- | This is probably useless, since the vectors we usually contain
102 -- aren't functor instances.
103 instance (Functor v) => Functor (Vn v) where
104 fmap f (Vn v1) = Vn (f `fmap` v1)
105
106
107 instance (RealFloat a, Ord a, V.Vector v a) => Normed (Vn v a) where
108 -- | The infinity norm. We don't use V.maximum here because it
109 -- relies on a type constraint that the vector be non-empty and I
110 -- don't know how to pattern match it away.
111 --
112 -- Examples:
113 --
114 -- >>> let v1 = make3d (1,5,2)
115 -- >>> norm_infty v1
116 -- 5
117 --
118 norm_infty (Vn v1) = fromRational $ toRational $ V.foldl max 0 v1
119
120 -- | Generic p-norms. The usual norm in R^n is (norm_p 2).
121 --
122 -- Examples:
123 --
124 -- >>> let v1 = make2d (3,4)
125 -- >>> norm_p 1 v1
126 -- 7.0
127 -- >>> norm_p 2 v1
128 -- 5.0
129 --
130 norm_p p (Vn v1) =
131 fromRational $ toRational $ root $ V.sum $ V.map (exponentiate . abs) v1
132 where
133 exponentiate = (** (fromIntegral p))
134 root = (** (recip (fromIntegral p)))
135
136 -- | Dot (standard inner) product.
137 --
138 -- Examples:
139 --
140 -- >>> let v1 = make3d (1,2,3)
141 -- >>> let v2 = make3d (4,5,6)
142 -- >>> dot v1 v2
143 -- 32
144 --
145 dot :: (Num a, V.Vector v a) => Vn v a -> Vn v a -> a
146 dot (Vn v1) (Vn v2) = V.sum $ V.zipWith (*) v1 v2
147
148
149 -- | The angle between @v1@ and @v2@ in Euclidean space.
150 --
151 -- Examples:
152 --
153 -- >>> let v1 = make2d (1.0, 0.0)
154 -- >>> let v2 = make2d (0.0, 1.0)
155 -- >>> angle v1 v2 == pi/2.0
156 -- True
157 --
158 angle :: (RealFloat a, V.Vector v a) => Vn v a -> Vn v a -> a
159 angle v1 v2 =
160 acos theta
161 where
162 theta = (v1 `dot` v2) / norms
163 norms = (norm v1) * (norm v2)
164
165
166 -- | The length of a vector.
167 --
168 -- Examples:
169 --
170 -- >>> let v1 = make2d (1,2)
171 -- >>> length v1
172 -- 2
173 --
174 length :: (V.Vector v a) => Vn v a -> Int
175 length (Vn v1) = V.length v1
176
177
178 -- | Unsafe indexing.
179 --
180 -- Examples:
181 --
182 -- >>> let v1 = make3d (1,2,3)
183 -- >>> v1 ! 2
184 -- 3
185 -- >>> v1 ! 3
186 -- *** Exception: Data.Vector.Fixed.!: index out of range
187 --
188 (!) :: (V.Vector v a) => Vn v a -> Int -> a
189 (!) (Vn v1) idx = v1 V.! idx
190
191
192 -- | Safe indexing.
193 --
194 -- Examples:
195 --
196 -- >>> let v1 = make3d (1,2,3)
197 -- >>> v1 !? 2
198 -- Just 3
199 -- >>> v1 !? 3
200 -- Nothing
201 --
202 (!?) :: (V.Vector v a) => Vn v a -> Int -> Maybe a
203 (!?) v1@(Vn v2) idx
204 | idx < 0 || idx >= V.length v2 = Nothing
205 | otherwise = Just $ v1 ! idx
206
207
208 -- | Convert vector to a list.
209 --
210 -- Examples:
211 --
212 -- >>> let v1 = make2d (1,2)
213 -- >>> toList v1
214 -- [1,2]
215 --
216 toList :: (V.Vector v a) => Vn v a -> [a]
217 toList (Vn v1) = V.toList v1
218
219
220 -- | Convert a list to a vector.
221 --
222 -- Examples:
223 --
224 -- >>> fromList [1,2] :: Vn Vec2D Int
225 -- (1,2)
226 --
227 fromList :: (V.Vector v a) => [a] -> Vn v a
228 fromList xs = Vn $ V.fromList xs
229
230 -- | Map a function over a vector.
231 --
232 -- Examples:
233 --
234 -- >>> let v1 = make2d (1,2)
235 -- >>> map (*2) v1
236 -- (2,4)
237 --
238 map :: (V.Vector v a, V.Vector v b) => (a -> b) -> Vn v a -> Vn v b
239 map f (Vn vs) = Vn $ V.map f vs
240
241
242
243 -- * Low-dimension vector wrappers.
244 --
245 -- These wrappers are instances of 'Vector', so they inherit all of
246 -- the userful instances defined above. But, they use fixed
247 -- constructors, so you can pattern match out the individual
248 -- components.
249
250 data Vec2D a = Vec2D a a
251 type instance V.Dim Vec2D = V.N2
252 instance V.Vector Vec2D a where
253 inspect (Vec2D x y) (V.Fun f) = f x y
254 construct = V.Fun Vec2D
255
256 data Vec3D a = Vec3D a a a
257 type instance V.Dim Vec3D = V.N3
258 instance V.Vector Vec3D a where
259 inspect (Vec3D x y z) (V.Fun f) = f x y z
260 construct = V.Fun Vec3D
261
262 data Vec4D a = Vec4D a a a a
263 type instance V.Dim Vec4D = V.N4
264 instance V.Vector Vec4D a where
265 inspect (Vec4D w x y z) (V.Fun f) = f w x y z
266 construct = V.Fun Vec4D
267
268
269 -- | Convenience function for creating 2d vectors.
270 --
271 -- Examples:
272 --
273 -- >>> let v1 = make2d (1,2)
274 -- >>> v1
275 -- (1,2)
276 -- >>> let Vn (Vec2D x y) = v1
277 -- >>> (x,y)
278 -- (1,2)
279 --
280 make2d :: forall a. (a,a) -> Vn Vec2D a
281 make2d (x,y) = Vn (Vec2D x y)
282
283
284 -- | Convenience function for creating 3d vectors.
285 --
286 -- Examples:
287 --
288 -- >>> let v1 = make3d (1,2,3)
289 -- >>> v1
290 -- (1,2,3)
291 -- >>> let Vn (Vec3D x y z) = v1
292 -- >>> (x,y,z)
293 -- (1,2,3)
294 --
295 make3d :: forall a. (a,a,a) -> Vn Vec3D a
296 make3d (x,y,z) = Vn (Vec3D x y z)
297
298
299 -- | Convenience function for creating 4d vectors.
300 --
301 -- Examples:
302 --
303 -- >>> let v1 = make4d (1,2,3,4)
304 -- >>> v1
305 -- (1,2,3,4)
306 -- >>> let Vn (Vec4D w x y z) = v1
307 -- >>> (w,x,y,z)
308 -- (1,2,3,4)
309 --
310 make4d :: forall a. (a,a,a,a) -> Vn Vec4D a
311 make4d (w,x,y,z) = Vn (Vec4D w x y z)