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