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