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