diff options
Diffstat (limited to 'lib/Numeric/LinearAlgebra/Instances.hs')
-rw-r--r-- | lib/Numeric/LinearAlgebra/Instances.hs | 276 |
1 files changed, 0 insertions, 276 deletions
diff --git a/lib/Numeric/LinearAlgebra/Instances.hs b/lib/Numeric/LinearAlgebra/Instances.hs deleted file mode 100644 index 04a9d88..0000000 --- a/lib/Numeric/LinearAlgebra/Instances.hs +++ /dev/null | |||
@@ -1,276 +0,0 @@ | |||
1 | {-# LANGUAGE UndecidableInstances, FlexibleInstances #-} | ||
2 | ----------------------------------------------------------------------------- | ||
3 | {- | | ||
4 | Module : Numeric.LinearAlgebra.Instances | ||
5 | Copyright : (c) Alberto Ruiz 2006 | ||
6 | License : GPL-style | ||
7 | |||
8 | Maintainer : Alberto Ruiz (aruiz at um dot es) | ||
9 | Stability : provisional | ||
10 | Portability : portable | ||
11 | |||
12 | This module exports Show, Read, Eq, Num, Fractional, and Floating instances for Vector and Matrix. | ||
13 | |||
14 | In the context of the standard numeric operators, one-component vectors and matrices automatically expand to match the dimensions of the other operand. | ||
15 | |||
16 | -} | ||
17 | ----------------------------------------------------------------------------- | ||
18 | |||
19 | module Numeric.LinearAlgebra.Instances( | ||
20 | ) where | ||
21 | |||
22 | import Numeric.LinearAlgebra.Linear | ||
23 | import Numeric.GSL.Vector | ||
24 | import Data.Packed.Matrix | ||
25 | import Data.Complex | ||
26 | import Data.List(transpose,intersperse) | ||
27 | import Data.Packed.Internal.Vector | ||
28 | |||
29 | #ifndef VECTOR | ||
30 | import Foreign(Storable) | ||
31 | #endif | ||
32 | |||
33 | ------------------------------------------------------------------ | ||
34 | |||
35 | instance (Show a, Element a) => (Show (Matrix a)) where | ||
36 | show m = (sizes++) . dsp . map (map show) . toLists $ m | ||
37 | where sizes = "("++show (rows m)++"><"++show (cols m)++")\n" | ||
38 | |||
39 | dsp as = (++" ]") . (" ["++) . init . drop 2 . unlines . map (" , "++) . map unwords' $ transpose mtp | ||
40 | where | ||
41 | mt = transpose as | ||
42 | longs = map (maximum . map length) mt | ||
43 | mtp = zipWith (\a b -> map (pad a) b) longs mt | ||
44 | pad n str = replicate (n - length str) ' ' ++ str | ||
45 | unwords' = concat . intersperse ", " | ||
46 | |||
47 | #ifndef VECTOR | ||
48 | |||
49 | instance (Show a, Storable a) => (Show (Vector a)) where | ||
50 | show v = (show (dim v))++" |> " ++ show (toList v) | ||
51 | |||
52 | #endif | ||
53 | |||
54 | ------------------------------------------------------------------ | ||
55 | |||
56 | instance (Element a, Read a) => Read (Matrix a) where | ||
57 | readsPrec _ s = [((rs><cs) . read $ listnums, rest)] | ||
58 | where (thing,rest) = breakAt ']' s | ||
59 | (dims,listnums) = breakAt ')' thing | ||
60 | cs = read . init . fst. breakAt ')' . snd . breakAt '<' $ dims | ||
61 | rs = read . snd . breakAt '(' .init . fst . breakAt '>' $ dims | ||
62 | |||
63 | #ifdef VECTOR | ||
64 | |||
65 | instance (Element a, Read a) => Read (Vector a) where | ||
66 | readsPrec _ s = [(fromList . read $ listnums, rest)] | ||
67 | where (thing,trest) = breakAt ']' s | ||
68 | (dims,listnums) = breakAt ' ' (dropWhile (==' ') thing) | ||
69 | rest = drop 31 trest | ||
70 | #else | ||
71 | |||
72 | instance (Element a, Read a) => Read (Vector a) where | ||
73 | readsPrec _ s = [((d |>) . read $ listnums, rest)] | ||
74 | where (thing,rest) = breakAt ']' s | ||
75 | (dims,listnums) = breakAt '>' thing | ||
76 | d = read . init . fst . breakAt '|' $ dims | ||
77 | |||
78 | #endif | ||
79 | |||
80 | breakAt c l = (a++[c],tail b) where | ||
81 | (a,b) = break (==c) l | ||
82 | |||
83 | ------------------------------------------------------------------ | ||
84 | |||
85 | adaptScalar f1 f2 f3 x y | ||
86 | | dim x == 1 = f1 (x@>0) y | ||
87 | | dim y == 1 = f3 x (y@>0) | ||
88 | | otherwise = f2 x y | ||
89 | |||
90 | #ifndef VECTOR | ||
91 | |||
92 | instance Linear Vector a => Eq (Vector a) where | ||
93 | (==) = equal | ||
94 | |||
95 | #endif | ||
96 | |||
97 | instance Num (Vector Float) where | ||
98 | (+) = adaptScalar addConstant add (flip addConstant) | ||
99 | negate = scale (-1) | ||
100 | (*) = adaptScalar scale mul (flip scale) | ||
101 | signum = vectorMapF Sign | ||
102 | abs = vectorMapF Abs | ||
103 | fromInteger = fromList . return . fromInteger | ||
104 | |||
105 | instance Num (Vector Double) where | ||
106 | (+) = adaptScalar addConstant add (flip addConstant) | ||
107 | negate = scale (-1) | ||
108 | (*) = adaptScalar scale mul (flip scale) | ||
109 | signum = vectorMapR Sign | ||
110 | abs = vectorMapR Abs | ||
111 | fromInteger = fromList . return . fromInteger | ||
112 | |||
113 | instance Num (Vector (Complex Double)) where | ||
114 | (+) = adaptScalar addConstant add (flip addConstant) | ||
115 | negate = scale (-1) | ||
116 | (*) = adaptScalar scale mul (flip scale) | ||
117 | signum = vectorMapC Sign | ||
118 | abs = vectorMapC Abs | ||
119 | fromInteger = fromList . return . fromInteger | ||
120 | |||
121 | instance Num (Vector (Complex Float)) where | ||
122 | (+) = adaptScalar addConstant add (flip addConstant) | ||
123 | negate = scale (-1) | ||
124 | (*) = adaptScalar scale mul (flip scale) | ||
125 | signum = vectorMapQ Sign | ||
126 | abs = vectorMapQ Abs | ||
127 | fromInteger = fromList . return . fromInteger | ||
128 | |||
129 | instance Linear Matrix a => Eq (Matrix a) where | ||
130 | (==) = equal | ||
131 | |||
132 | instance (Linear Matrix a, Num (Vector a)) => Num (Matrix a) where | ||
133 | (+) = liftMatrix2Auto (+) | ||
134 | (-) = liftMatrix2Auto (-) | ||
135 | negate = liftMatrix negate | ||
136 | (*) = liftMatrix2Auto (*) | ||
137 | signum = liftMatrix signum | ||
138 | abs = liftMatrix abs | ||
139 | fromInteger = (1><1) . return . fromInteger | ||
140 | |||
141 | --------------------------------------------------- | ||
142 | |||
143 | instance (Linear Vector a, Num (Vector a)) => Fractional (Vector a) where | ||
144 | fromRational n = fromList [fromRational n] | ||
145 | (/) = adaptScalar f divide g where | ||
146 | r `f` v = scaleRecip r v | ||
147 | v `g` r = scale (recip r) v | ||
148 | |||
149 | ------------------------------------------------------- | ||
150 | |||
151 | instance (Linear Vector a, Fractional (Vector a), Num (Matrix a)) => Fractional (Matrix a) where | ||
152 | fromRational n = (1><1) [fromRational n] | ||
153 | (/) = liftMatrix2Auto (/) | ||
154 | |||
155 | --------------------------------------------------------- | ||
156 | |||
157 | instance Floating (Vector Float) where | ||
158 | sin = vectorMapF Sin | ||
159 | cos = vectorMapF Cos | ||
160 | tan = vectorMapF Tan | ||
161 | asin = vectorMapF ASin | ||
162 | acos = vectorMapF ACos | ||
163 | atan = vectorMapF ATan | ||
164 | sinh = vectorMapF Sinh | ||
165 | cosh = vectorMapF Cosh | ||
166 | tanh = vectorMapF Tanh | ||
167 | asinh = vectorMapF ASinh | ||
168 | acosh = vectorMapF ACosh | ||
169 | atanh = vectorMapF ATanh | ||
170 | exp = vectorMapF Exp | ||
171 | log = vectorMapF Log | ||
172 | sqrt = vectorMapF Sqrt | ||
173 | (**) = adaptScalar (vectorMapValF PowSV) (vectorZipF Pow) (flip (vectorMapValF PowVS)) | ||
174 | pi = fromList [pi] | ||
175 | |||
176 | ------------------------------------------------------------- | ||
177 | |||
178 | instance Floating (Vector Double) where | ||
179 | sin = vectorMapR Sin | ||
180 | cos = vectorMapR Cos | ||
181 | tan = vectorMapR Tan | ||
182 | asin = vectorMapR ASin | ||
183 | acos = vectorMapR ACos | ||
184 | atan = vectorMapR ATan | ||
185 | sinh = vectorMapR Sinh | ||
186 | cosh = vectorMapR Cosh | ||
187 | tanh = vectorMapR Tanh | ||
188 | asinh = vectorMapR ASinh | ||
189 | acosh = vectorMapR ACosh | ||
190 | atanh = vectorMapR ATanh | ||
191 | exp = vectorMapR Exp | ||
192 | log = vectorMapR Log | ||
193 | sqrt = vectorMapR Sqrt | ||
194 | (**) = adaptScalar (vectorMapValR PowSV) (vectorZipR Pow) (flip (vectorMapValR PowVS)) | ||
195 | pi = fromList [pi] | ||
196 | |||
197 | ------------------------------------------------------------- | ||
198 | |||
199 | instance Floating (Vector (Complex Double)) where | ||
200 | sin = vectorMapC Sin | ||
201 | cos = vectorMapC Cos | ||
202 | tan = vectorMapC Tan | ||
203 | asin = vectorMapC ASin | ||
204 | acos = vectorMapC ACos | ||
205 | atan = vectorMapC ATan | ||
206 | sinh = vectorMapC Sinh | ||
207 | cosh = vectorMapC Cosh | ||
208 | tanh = vectorMapC Tanh | ||
209 | asinh = vectorMapC ASinh | ||
210 | acosh = vectorMapC ACosh | ||
211 | atanh = vectorMapC ATanh | ||
212 | exp = vectorMapC Exp | ||
213 | log = vectorMapC Log | ||
214 | sqrt = vectorMapC Sqrt | ||
215 | (**) = adaptScalar (vectorMapValC PowSV) (vectorZipC Pow) (flip (vectorMapValC PowVS)) | ||
216 | pi = fromList [pi] | ||
217 | |||
218 | ----------------------------------------------------------- | ||
219 | |||
220 | instance Floating (Vector (Complex Float)) where | ||
221 | sin = vectorMapQ Sin | ||
222 | cos = vectorMapQ Cos | ||
223 | tan = vectorMapQ Tan | ||
224 | asin = vectorMapQ ASin | ||
225 | acos = vectorMapQ ACos | ||
226 | atan = vectorMapQ ATan | ||
227 | sinh = vectorMapQ Sinh | ||
228 | cosh = vectorMapQ Cosh | ||
229 | tanh = vectorMapQ Tanh | ||
230 | asinh = vectorMapQ ASinh | ||
231 | acosh = vectorMapQ ACosh | ||
232 | atanh = vectorMapQ ATanh | ||
233 | exp = vectorMapQ Exp | ||
234 | log = vectorMapQ Log | ||
235 | sqrt = vectorMapQ Sqrt | ||
236 | (**) = adaptScalar (vectorMapValQ PowSV) (vectorZipQ Pow) (flip (vectorMapValQ PowVS)) | ||
237 | pi = fromList [pi] | ||
238 | |||
239 | ----------------------------------------------------------- | ||
240 | |||
241 | instance (Linear Vector a, Floating (Vector a), Fractional (Matrix a)) => Floating (Matrix a) where | ||
242 | sin = liftMatrix sin | ||
243 | cos = liftMatrix cos | ||
244 | tan = liftMatrix tan | ||
245 | asin = liftMatrix asin | ||
246 | acos = liftMatrix acos | ||
247 | atan = liftMatrix atan | ||
248 | sinh = liftMatrix sinh | ||
249 | cosh = liftMatrix cosh | ||
250 | tanh = liftMatrix tanh | ||
251 | asinh = liftMatrix asinh | ||
252 | acosh = liftMatrix acosh | ||
253 | atanh = liftMatrix atanh | ||
254 | exp = liftMatrix exp | ||
255 | log = liftMatrix log | ||
256 | (**) = liftMatrix2Auto (**) | ||
257 | sqrt = liftMatrix sqrt | ||
258 | pi = (1><1) [pi] | ||
259 | |||
260 | --------------------------------------------------------------- | ||
261 | |||
262 | -- instance (Storable a, Num (Vector a)) => Monoid (Vector a) where | ||
263 | -- mempty = 0 { idim = 0 } | ||
264 | -- mappend a b = mconcat [a,b] | ||
265 | -- mconcat = j . filter ((>0).dim) | ||
266 | -- where j [] = mempty | ||
267 | -- j l = join l | ||
268 | |||
269 | --------------------------------------------------------------- | ||
270 | |||
271 | -- instance (NFData a, Storable a) => NFData (Vector a) where | ||
272 | -- rnf = rnf . (@>0) | ||
273 | -- | ||
274 | -- instance (NFData a, Element a) => NFData (Matrix a) where | ||
275 | -- rnf = rnf . flatten | ||
276 | |||