diff options
author | Alberto Ruiz <aruiz@um.es> | 2015-06-05 16:45:23 +0200 |
---|---|---|
committer | Alberto Ruiz <aruiz@um.es> | 2015-06-05 16:45:23 +0200 |
commit | 5d967adae38d7fe80443b57b40ae89cd15db5e18 (patch) | |
tree | f6cce41d547d539f7f0cb8b92e0273d3ecab5d45 /packages/base/src/Internal | |
parent | 64df799c68817054705a99e9ee02723603fae29e (diff) |
move lapack
Diffstat (limited to 'packages/base/src/Internal')
-rw-r--r-- | packages/base/src/Internal/LAPACK.hs | 558 |
1 files changed, 558 insertions, 0 deletions
diff --git a/packages/base/src/Internal/LAPACK.hs b/packages/base/src/Internal/LAPACK.hs new file mode 100644 index 0000000..9cab3f8 --- /dev/null +++ b/packages/base/src/Internal/LAPACK.hs | |||
@@ -0,0 +1,558 @@ | |||
1 | {-# LANGUAGE TypeOperators #-} | ||
2 | |||
3 | ----------------------------------------------------------------------------- | ||
4 | -- | | ||
5 | -- Module : Numeric.LinearAlgebra.LAPACK | ||
6 | -- Copyright : (c) Alberto Ruiz 2006-14 | ||
7 | -- License : BSD3 | ||
8 | -- Maintainer : Alberto Ruiz | ||
9 | -- Stability : provisional | ||
10 | -- | ||
11 | -- Functional interface to selected LAPACK functions (<http://www.netlib.org/lapack>). | ||
12 | -- | ||
13 | ----------------------------------------------------------------------------- | ||
14 | |||
15 | |||
16 | module Internal.LAPACK where | ||
17 | |||
18 | import Internal.Devel | ||
19 | import Internal.Vector | ||
20 | import Internal.Matrix | ||
21 | import Internal.Conversion | ||
22 | import Internal.Element | ||
23 | |||
24 | import Foreign.Ptr(nullPtr) | ||
25 | import Foreign.C.Types | ||
26 | import Control.Monad(when) | ||
27 | import System.IO.Unsafe(unsafePerformIO) | ||
28 | import Data.Vector.Storable(fromList) | ||
29 | |||
30 | ----------------------------------------------------------------------------------- | ||
31 | |||
32 | type TMMM t = t ..> t ..> t ..> Ok | ||
33 | |||
34 | type R = Double | ||
35 | type C = Complex Double | ||
36 | type F = Float | ||
37 | type Q = Complex Float | ||
38 | |||
39 | foreign import ccall unsafe "multiplyR" dgemmc :: CInt -> CInt -> TMMM R | ||
40 | foreign import ccall unsafe "multiplyC" zgemmc :: CInt -> CInt -> TMMM C | ||
41 | foreign import ccall unsafe "multiplyF" sgemmc :: CInt -> CInt -> TMMM F | ||
42 | foreign import ccall unsafe "multiplyQ" cgemmc :: CInt -> CInt -> TMMM Q | ||
43 | foreign import ccall unsafe "multiplyI" c_multiplyI :: CInt ::> CInt ::> CInt ::> Ok | ||
44 | |||
45 | isT Matrix{order = ColumnMajor} = 0 | ||
46 | isT Matrix{order = RowMajor} = 1 | ||
47 | |||
48 | tt x@Matrix{order = ColumnMajor} = x | ||
49 | tt x@Matrix{order = RowMajor} = trans x | ||
50 | |||
51 | multiplyAux f st a b = unsafePerformIO $ do | ||
52 | when (cols a /= rows b) $ error $ "inconsistent dimensions in matrix product "++ | ||
53 | show (rows a,cols a) ++ " x " ++ show (rows b, cols b) | ||
54 | s <- createMatrix ColumnMajor (rows a) (cols b) | ||
55 | app3 (f (isT a) (isT b)) mat (tt a) mat (tt b) mat s st | ||
56 | return s | ||
57 | |||
58 | -- | Matrix product based on BLAS's /dgemm/. | ||
59 | multiplyR :: Matrix Double -> Matrix Double -> Matrix Double | ||
60 | multiplyR a b = {-# SCC "multiplyR" #-} multiplyAux dgemmc "dgemmc" a b | ||
61 | |||
62 | -- | Matrix product based on BLAS's /zgemm/. | ||
63 | multiplyC :: Matrix (Complex Double) -> Matrix (Complex Double) -> Matrix (Complex Double) | ||
64 | multiplyC a b = multiplyAux zgemmc "zgemmc" a b | ||
65 | |||
66 | -- | Matrix product based on BLAS's /sgemm/. | ||
67 | multiplyF :: Matrix Float -> Matrix Float -> Matrix Float | ||
68 | multiplyF a b = multiplyAux sgemmc "sgemmc" a b | ||
69 | |||
70 | -- | Matrix product based on BLAS's /cgemm/. | ||
71 | multiplyQ :: Matrix (Complex Float) -> Matrix (Complex Float) -> Matrix (Complex Float) | ||
72 | multiplyQ a b = multiplyAux cgemmc "cgemmc" a b | ||
73 | |||
74 | multiplyI :: Matrix CInt -> Matrix CInt -> Matrix CInt | ||
75 | multiplyI a b = unsafePerformIO $ do | ||
76 | when (cols a /= rows b) $ error $ | ||
77 | "inconsistent dimensions in matrix product "++ shSize a ++ " x " ++ shSize b | ||
78 | s <- createMatrix ColumnMajor (rows a) (cols b) | ||
79 | app3 c_multiplyI omat a omat b omat s "c_multiplyI" | ||
80 | return s | ||
81 | |||
82 | ----------------------------------------------------------------------------- | ||
83 | |||
84 | type TSVD t = t ..> t ..> R :> t ..> Ok | ||
85 | |||
86 | foreign import ccall unsafe "svd_l_R" dgesvd :: TSVD R | ||
87 | foreign import ccall unsafe "svd_l_C" zgesvd :: TSVD C | ||
88 | foreign import ccall unsafe "svd_l_Rdd" dgesdd :: TSVD R | ||
89 | foreign import ccall unsafe "svd_l_Cdd" zgesdd :: TSVD C | ||
90 | |||
91 | -- | Full SVD of a real matrix using LAPACK's /dgesvd/. | ||
92 | svdR :: Matrix Double -> (Matrix Double, Vector Double, Matrix Double) | ||
93 | svdR = svdAux dgesvd "svdR" . fmat | ||
94 | |||
95 | -- | Full SVD of a real matrix using LAPACK's /dgesdd/. | ||
96 | svdRd :: Matrix Double -> (Matrix Double, Vector Double, Matrix Double) | ||
97 | svdRd = svdAux dgesdd "svdRdd" . fmat | ||
98 | |||
99 | -- | Full SVD of a complex matrix using LAPACK's /zgesvd/. | ||
100 | svdC :: Matrix (Complex Double) -> (Matrix (Complex Double), Vector Double, Matrix (Complex Double)) | ||
101 | svdC = svdAux zgesvd "svdC" . fmat | ||
102 | |||
103 | -- | Full SVD of a complex matrix using LAPACK's /zgesdd/. | ||
104 | svdCd :: Matrix (Complex Double) -> (Matrix (Complex Double), Vector Double, Matrix (Complex Double)) | ||
105 | svdCd = svdAux zgesdd "svdCdd" . fmat | ||
106 | |||
107 | svdAux f st x = unsafePerformIO $ do | ||
108 | u <- createMatrix ColumnMajor r r | ||
109 | s <- createVector (min r c) | ||
110 | v <- createMatrix ColumnMajor c c | ||
111 | app4 f mat x mat u vec s mat v st | ||
112 | return (u,s,v) | ||
113 | where r = rows x | ||
114 | c = cols x | ||
115 | |||
116 | |||
117 | -- | Thin SVD of a real matrix, using LAPACK's /dgesvd/ with jobu == jobvt == \'S\'. | ||
118 | thinSVDR :: Matrix Double -> (Matrix Double, Vector Double, Matrix Double) | ||
119 | thinSVDR = thinSVDAux dgesvd "thinSVDR" . fmat | ||
120 | |||
121 | -- | Thin SVD of a complex matrix, using LAPACK's /zgesvd/ with jobu == jobvt == \'S\'. | ||
122 | thinSVDC :: Matrix (Complex Double) -> (Matrix (Complex Double), Vector Double, Matrix (Complex Double)) | ||
123 | thinSVDC = thinSVDAux zgesvd "thinSVDC" . fmat | ||
124 | |||
125 | -- | Thin SVD of a real matrix, using LAPACK's /dgesdd/ with jobz == \'S\'. | ||
126 | thinSVDRd :: Matrix Double -> (Matrix Double, Vector Double, Matrix Double) | ||
127 | thinSVDRd = thinSVDAux dgesdd "thinSVDRdd" . fmat | ||
128 | |||
129 | -- | Thin SVD of a complex matrix, using LAPACK's /zgesdd/ with jobz == \'S\'. | ||
130 | thinSVDCd :: Matrix (Complex Double) -> (Matrix (Complex Double), Vector Double, Matrix (Complex Double)) | ||
131 | thinSVDCd = thinSVDAux zgesdd "thinSVDCdd" . fmat | ||
132 | |||
133 | thinSVDAux f st x = unsafePerformIO $ do | ||
134 | u <- createMatrix ColumnMajor r q | ||
135 | s <- createVector q | ||
136 | v <- createMatrix ColumnMajor q c | ||
137 | app4 f mat x mat u vec s mat v st | ||
138 | return (u,s,v) | ||
139 | where r = rows x | ||
140 | c = cols x | ||
141 | q = min r c | ||
142 | |||
143 | |||
144 | -- | Singular values of a real matrix, using LAPACK's /dgesvd/ with jobu == jobvt == \'N\'. | ||
145 | svR :: Matrix Double -> Vector Double | ||
146 | svR = svAux dgesvd "svR" . fmat | ||
147 | |||
148 | -- | Singular values of a complex matrix, using LAPACK's /zgesvd/ with jobu == jobvt == \'N\'. | ||
149 | svC :: Matrix (Complex Double) -> Vector Double | ||
150 | svC = svAux zgesvd "svC" . fmat | ||
151 | |||
152 | -- | Singular values of a real matrix, using LAPACK's /dgesdd/ with jobz == \'N\'. | ||
153 | svRd :: Matrix Double -> Vector Double | ||
154 | svRd = svAux dgesdd "svRd" . fmat | ||
155 | |||
156 | -- | Singular values of a complex matrix, using LAPACK's /zgesdd/ with jobz == \'N\'. | ||
157 | svCd :: Matrix (Complex Double) -> Vector Double | ||
158 | svCd = svAux zgesdd "svCd" . fmat | ||
159 | |||
160 | svAux f st x = unsafePerformIO $ do | ||
161 | s <- createVector q | ||
162 | app2 g mat x vec s st | ||
163 | return s | ||
164 | where r = rows x | ||
165 | c = cols x | ||
166 | q = min r c | ||
167 | g ra ca pa nb pb = f ra ca pa 0 0 nullPtr nb pb 0 0 nullPtr | ||
168 | |||
169 | |||
170 | -- | Singular values and all right singular vectors of a real matrix, using LAPACK's /dgesvd/ with jobu == \'N\' and jobvt == \'A\'. | ||
171 | rightSVR :: Matrix Double -> (Vector Double, Matrix Double) | ||
172 | rightSVR = rightSVAux dgesvd "rightSVR" . fmat | ||
173 | |||
174 | -- | Singular values and all right singular vectors of a complex matrix, using LAPACK's /zgesvd/ with jobu == \'N\' and jobvt == \'A\'. | ||
175 | rightSVC :: Matrix (Complex Double) -> (Vector Double, Matrix (Complex Double)) | ||
176 | rightSVC = rightSVAux zgesvd "rightSVC" . fmat | ||
177 | |||
178 | rightSVAux f st x = unsafePerformIO $ do | ||
179 | s <- createVector q | ||
180 | v <- createMatrix ColumnMajor c c | ||
181 | app3 g mat x vec s mat v st | ||
182 | return (s,v) | ||
183 | where r = rows x | ||
184 | c = cols x | ||
185 | q = min r c | ||
186 | g ra ca pa = f ra ca pa 0 0 nullPtr | ||
187 | |||
188 | |||
189 | -- | Singular values and all left singular vectors of a real matrix, using LAPACK's /dgesvd/ with jobu == \'A\' and jobvt == \'N\'. | ||
190 | leftSVR :: Matrix Double -> (Matrix Double, Vector Double) | ||
191 | leftSVR = leftSVAux dgesvd "leftSVR" . fmat | ||
192 | |||
193 | -- | Singular values and all left singular vectors of a complex matrix, using LAPACK's /zgesvd/ with jobu == \'A\' and jobvt == \'N\'. | ||
194 | leftSVC :: Matrix (Complex Double) -> (Matrix (Complex Double), Vector Double) | ||
195 | leftSVC = leftSVAux zgesvd "leftSVC" . fmat | ||
196 | |||
197 | leftSVAux f st x = unsafePerformIO $ do | ||
198 | u <- createMatrix ColumnMajor r r | ||
199 | s <- createVector q | ||
200 | app3 g mat x mat u vec s st | ||
201 | return (u,s) | ||
202 | where r = rows x | ||
203 | c = cols x | ||
204 | q = min r c | ||
205 | g ra ca pa ru cu pu nb pb = f ra ca pa ru cu pu nb pb 0 0 nullPtr | ||
206 | |||
207 | ----------------------------------------------------------------------------- | ||
208 | |||
209 | foreign import ccall unsafe "eig_l_R" dgeev :: R ..> R ..> C :> R ..> Ok | ||
210 | foreign import ccall unsafe "eig_l_C" zgeev :: C ..> C ..> C :> C ..> Ok | ||
211 | foreign import ccall unsafe "eig_l_S" dsyev :: CInt -> R ..> R :> R ..> Ok | ||
212 | foreign import ccall unsafe "eig_l_H" zheev :: CInt -> C ..> R :> C ..> Ok | ||
213 | |||
214 | eigAux f st m = unsafePerformIO $ do | ||
215 | l <- createVector r | ||
216 | v <- createMatrix ColumnMajor r r | ||
217 | app3 g mat m vec l mat v st | ||
218 | return (l,v) | ||
219 | where r = rows m | ||
220 | g ra ca pa = f ra ca pa 0 0 nullPtr | ||
221 | |||
222 | |||
223 | -- | Eigenvalues and right eigenvectors of a general complex matrix, using LAPACK's /zgeev/. | ||
224 | -- The eigenvectors are the columns of v. The eigenvalues are not sorted. | ||
225 | eigC :: Matrix (Complex Double) -> (Vector (Complex Double), Matrix (Complex Double)) | ||
226 | eigC = eigAux zgeev "eigC" . fmat | ||
227 | |||
228 | eigOnlyAux f st m = unsafePerformIO $ do | ||
229 | l <- createVector r | ||
230 | app2 g mat m vec l st | ||
231 | return l | ||
232 | where r = rows m | ||
233 | g ra ca pa nl pl = f ra ca pa 0 0 nullPtr nl pl 0 0 nullPtr | ||
234 | |||
235 | -- | Eigenvalues of a general complex matrix, using LAPACK's /zgeev/ with jobz == \'N\'. | ||
236 | -- The eigenvalues are not sorted. | ||
237 | eigOnlyC :: Matrix (Complex Double) -> Vector (Complex Double) | ||
238 | eigOnlyC = eigOnlyAux zgeev "eigOnlyC" . fmat | ||
239 | |||
240 | -- | Eigenvalues and right eigenvectors of a general real matrix, using LAPACK's /dgeev/. | ||
241 | -- The eigenvectors are the columns of v. The eigenvalues are not sorted. | ||
242 | eigR :: Matrix Double -> (Vector (Complex Double), Matrix (Complex Double)) | ||
243 | eigR m = (s', v'') | ||
244 | where (s,v) = eigRaux (fmat m) | ||
245 | s' = fixeig1 s | ||
246 | v' = toRows $ trans v | ||
247 | v'' = fromColumns $ fixeig (toList s') v' | ||
248 | |||
249 | eigRaux :: Matrix Double -> (Vector (Complex Double), Matrix Double) | ||
250 | eigRaux m = unsafePerformIO $ do | ||
251 | l <- createVector r | ||
252 | v <- createMatrix ColumnMajor r r | ||
253 | app3 g mat m vec l mat v "eigR" | ||
254 | return (l,v) | ||
255 | where r = rows m | ||
256 | g ra ca pa = dgeev ra ca pa 0 0 nullPtr | ||
257 | |||
258 | fixeig1 s = toComplex' (subVector 0 r (asReal s), subVector r r (asReal s)) | ||
259 | where r = dim s | ||
260 | |||
261 | fixeig [] _ = [] | ||
262 | fixeig [_] [v] = [comp' v] | ||
263 | fixeig ((r1:+i1):(r2:+i2):r) (v1:v2:vs) | ||
264 | | r1 == r2 && i1 == (-i2) = toComplex' (v1,v2) : toComplex' (v1, mapVector negate v2) : fixeig r vs | ||
265 | | otherwise = comp' v1 : fixeig ((r2:+i2):r) (v2:vs) | ||
266 | fixeig _ _ = error "fixeig with impossible inputs" | ||
267 | |||
268 | |||
269 | -- | Eigenvalues of a general real matrix, using LAPACK's /dgeev/ with jobz == \'N\'. | ||
270 | -- The eigenvalues are not sorted. | ||
271 | eigOnlyR :: Matrix Double -> Vector (Complex Double) | ||
272 | eigOnlyR = fixeig1 . eigOnlyAux dgeev "eigOnlyR" . fmat | ||
273 | |||
274 | |||
275 | ----------------------------------------------------------------------------- | ||
276 | |||
277 | eigSHAux f st m = unsafePerformIO $ do | ||
278 | l <- createVector r | ||
279 | v <- createMatrix ColumnMajor r r | ||
280 | app3 f mat m vec l mat v st | ||
281 | return (l,v) | ||
282 | where r = rows m | ||
283 | |||
284 | -- | Eigenvalues and right eigenvectors of a symmetric real matrix, using LAPACK's /dsyev/. | ||
285 | -- The eigenvectors are the columns of v. | ||
286 | -- The eigenvalues are sorted in descending order (use 'eigS'' for ascending order). | ||
287 | eigS :: Matrix Double -> (Vector Double, Matrix Double) | ||
288 | eigS m = (s', fliprl v) | ||
289 | where (s,v) = eigS' (fmat m) | ||
290 | s' = fromList . reverse . toList $ s | ||
291 | |||
292 | -- | 'eigS' in ascending order | ||
293 | eigS' :: Matrix Double -> (Vector Double, Matrix Double) | ||
294 | eigS' = eigSHAux (dsyev 1) "eigS'" . fmat | ||
295 | |||
296 | -- | Eigenvalues and right eigenvectors of a hermitian complex matrix, using LAPACK's /zheev/. | ||
297 | -- The eigenvectors are the columns of v. | ||
298 | -- The eigenvalues are sorted in descending order (use 'eigH'' for ascending order). | ||
299 | eigH :: Matrix (Complex Double) -> (Vector Double, Matrix (Complex Double)) | ||
300 | eigH m = (s', fliprl v) | ||
301 | where (s,v) = eigH' (fmat m) | ||
302 | s' = fromList . reverse . toList $ s | ||
303 | |||
304 | -- | 'eigH' in ascending order | ||
305 | eigH' :: Matrix (Complex Double) -> (Vector Double, Matrix (Complex Double)) | ||
306 | eigH' = eigSHAux (zheev 1) "eigH'" . fmat | ||
307 | |||
308 | |||
309 | -- | Eigenvalues of a symmetric real matrix, using LAPACK's /dsyev/ with jobz == \'N\'. | ||
310 | -- The eigenvalues are sorted in descending order. | ||
311 | eigOnlyS :: Matrix Double -> Vector Double | ||
312 | eigOnlyS = vrev . fst. eigSHAux (dsyev 0) "eigS'" . fmat | ||
313 | |||
314 | -- | Eigenvalues of a hermitian complex matrix, using LAPACK's /zheev/ with jobz == \'N\'. | ||
315 | -- The eigenvalues are sorted in descending order. | ||
316 | eigOnlyH :: Matrix (Complex Double) -> Vector Double | ||
317 | eigOnlyH = vrev . fst. eigSHAux (zheev 0) "eigH'" . fmat | ||
318 | |||
319 | vrev = flatten . flipud . reshape 1 | ||
320 | |||
321 | ----------------------------------------------------------------------------- | ||
322 | foreign import ccall unsafe "linearSolveR_l" dgesv :: TMMM R | ||
323 | foreign import ccall unsafe "linearSolveC_l" zgesv :: TMMM C | ||
324 | foreign import ccall unsafe "cholSolveR_l" dpotrs :: TMMM R | ||
325 | foreign import ccall unsafe "cholSolveC_l" zpotrs :: TMMM C | ||
326 | |||
327 | linearSolveSQAux g f st a b | ||
328 | | n1==n2 && n1==r = unsafePerformIO . g $ do | ||
329 | s <- createMatrix ColumnMajor r c | ||
330 | app3 f mat a mat b mat s st | ||
331 | return s | ||
332 | | otherwise = error $ st ++ " of nonsquare matrix" | ||
333 | where n1 = rows a | ||
334 | n2 = cols a | ||
335 | r = rows b | ||
336 | c = cols b | ||
337 | |||
338 | -- | Solve a real linear system (for square coefficient matrix and several right-hand sides) using the LU decomposition, based on LAPACK's /dgesv/. For underconstrained or overconstrained systems use 'linearSolveLSR' or 'linearSolveSVDR'. See also 'lusR'. | ||
339 | linearSolveR :: Matrix Double -> Matrix Double -> Matrix Double | ||
340 | linearSolveR a b = linearSolveSQAux id dgesv "linearSolveR" (fmat a) (fmat b) | ||
341 | |||
342 | mbLinearSolveR :: Matrix Double -> Matrix Double -> Maybe (Matrix Double) | ||
343 | mbLinearSolveR a b = linearSolveSQAux mbCatch dgesv "linearSolveR" (fmat a) (fmat b) | ||
344 | |||
345 | |||
346 | -- | Solve a complex linear system (for square coefficient matrix and several right-hand sides) using the LU decomposition, based on LAPACK's /zgesv/. For underconstrained or overconstrained systems use 'linearSolveLSC' or 'linearSolveSVDC'. See also 'lusC'. | ||
347 | linearSolveC :: Matrix (Complex Double) -> Matrix (Complex Double) -> Matrix (Complex Double) | ||
348 | linearSolveC a b = linearSolveSQAux id zgesv "linearSolveC" (fmat a) (fmat b) | ||
349 | |||
350 | mbLinearSolveC :: Matrix (Complex Double) -> Matrix (Complex Double) -> Maybe (Matrix (Complex Double)) | ||
351 | mbLinearSolveC a b = linearSolveSQAux mbCatch zgesv "linearSolveC" (fmat a) (fmat b) | ||
352 | |||
353 | -- | Solves a symmetric positive definite system of linear equations using a precomputed Cholesky factorization obtained by 'cholS'. | ||
354 | cholSolveR :: Matrix Double -> Matrix Double -> Matrix Double | ||
355 | cholSolveR a b = linearSolveSQAux id dpotrs "cholSolveR" (fmat a) (fmat b) | ||
356 | |||
357 | -- | Solves a Hermitian positive definite system of linear equations using a precomputed Cholesky factorization obtained by 'cholH'. | ||
358 | cholSolveC :: Matrix (Complex Double) -> Matrix (Complex Double) -> Matrix (Complex Double) | ||
359 | cholSolveC a b = linearSolveSQAux id zpotrs "cholSolveC" (fmat a) (fmat b) | ||
360 | |||
361 | ----------------------------------------------------------------------------------- | ||
362 | foreign import ccall unsafe "linearSolveLSR_l" dgels :: TMMM R | ||
363 | foreign import ccall unsafe "linearSolveLSC_l" zgels :: TMMM C | ||
364 | foreign import ccall unsafe "linearSolveSVDR_l" dgelss :: Double -> TMMM R | ||
365 | foreign import ccall unsafe "linearSolveSVDC_l" zgelss :: Double -> TMMM C | ||
366 | |||
367 | linearSolveAux f st a b = unsafePerformIO $ do | ||
368 | r <- createMatrix ColumnMajor (max m n) nrhs | ||
369 | app3 f mat a mat b mat r st | ||
370 | return r | ||
371 | where m = rows a | ||
372 | n = cols a | ||
373 | nrhs = cols b | ||
374 | |||
375 | -- | Least squared error solution of an overconstrained real linear system, or the minimum norm solution of an underconstrained system, using LAPACK's /dgels/. For rank-deficient systems use 'linearSolveSVDR'. | ||
376 | linearSolveLSR :: Matrix Double -> Matrix Double -> Matrix Double | ||
377 | linearSolveLSR a b = subMatrix (0,0) (cols a, cols b) $ | ||
378 | linearSolveAux dgels "linearSolverLSR" (fmat a) (fmat b) | ||
379 | |||
380 | -- | Least squared error solution of an overconstrained complex linear system, or the minimum norm solution of an underconstrained system, using LAPACK's /zgels/. For rank-deficient systems use 'linearSolveSVDC'. | ||
381 | linearSolveLSC :: Matrix (Complex Double) -> Matrix (Complex Double) -> Matrix (Complex Double) | ||
382 | linearSolveLSC a b = subMatrix (0,0) (cols a, cols b) $ | ||
383 | linearSolveAux zgels "linearSolveLSC" (fmat a) (fmat b) | ||
384 | |||
385 | -- | Minimum norm solution of a general real linear least squares problem Ax=B using the SVD, based on LAPACK's /dgelss/. Admits rank-deficient systems but it is slower than 'linearSolveLSR'. The effective rank of A is determined by treating as zero those singular valures which are less than rcond times the largest singular value. If rcond == Nothing machine precision is used. | ||
386 | linearSolveSVDR :: Maybe Double -- ^ rcond | ||
387 | -> Matrix Double -- ^ coefficient matrix | ||
388 | -> Matrix Double -- ^ right hand sides (as columns) | ||
389 | -> Matrix Double -- ^ solution vectors (as columns) | ||
390 | linearSolveSVDR (Just rcond) a b = subMatrix (0,0) (cols a, cols b) $ | ||
391 | linearSolveAux (dgelss rcond) "linearSolveSVDR" (fmat a) (fmat b) | ||
392 | linearSolveSVDR Nothing a b = linearSolveSVDR (Just (-1)) (fmat a) (fmat b) | ||
393 | |||
394 | -- | Minimum norm solution of a general complex linear least squares problem Ax=B using the SVD, based on LAPACK's /zgelss/. Admits rank-deficient systems but it is slower than 'linearSolveLSC'. The effective rank of A is determined by treating as zero those singular valures which are less than rcond times the largest singular value. If rcond == Nothing machine precision is used. | ||
395 | linearSolveSVDC :: Maybe Double -- ^ rcond | ||
396 | -> Matrix (Complex Double) -- ^ coefficient matrix | ||
397 | -> Matrix (Complex Double) -- ^ right hand sides (as columns) | ||
398 | -> Matrix (Complex Double) -- ^ solution vectors (as columns) | ||
399 | linearSolveSVDC (Just rcond) a b = subMatrix (0,0) (cols a, cols b) $ | ||
400 | linearSolveAux (zgelss rcond) "linearSolveSVDC" (fmat a) (fmat b) | ||
401 | linearSolveSVDC Nothing a b = linearSolveSVDC (Just (-1)) (fmat a) (fmat b) | ||
402 | |||
403 | ----------------------------------------------------------------------------------- | ||
404 | |||
405 | foreign import ccall unsafe "chol_l_H" zpotrf :: TMM C | ||
406 | foreign import ccall unsafe "chol_l_S" dpotrf :: TMM R | ||
407 | |||
408 | cholAux f st a = do | ||
409 | r <- createMatrix ColumnMajor n n | ||
410 | app2 f mat a mat r st | ||
411 | return r | ||
412 | where n = rows a | ||
413 | |||
414 | -- | Cholesky factorization of a complex Hermitian positive definite matrix, using LAPACK's /zpotrf/. | ||
415 | cholH :: Matrix (Complex Double) -> Matrix (Complex Double) | ||
416 | cholH = unsafePerformIO . cholAux zpotrf "cholH" . fmat | ||
417 | |||
418 | -- | Cholesky factorization of a real symmetric positive definite matrix, using LAPACK's /dpotrf/. | ||
419 | cholS :: Matrix Double -> Matrix Double | ||
420 | cholS = unsafePerformIO . cholAux dpotrf "cholS" . fmat | ||
421 | |||
422 | -- | Cholesky factorization of a complex Hermitian positive definite matrix, using LAPACK's /zpotrf/ ('Maybe' version). | ||
423 | mbCholH :: Matrix (Complex Double) -> Maybe (Matrix (Complex Double)) | ||
424 | mbCholH = unsafePerformIO . mbCatch . cholAux zpotrf "cholH" . fmat | ||
425 | |||
426 | -- | Cholesky factorization of a real symmetric positive definite matrix, using LAPACK's /dpotrf/ ('Maybe' version). | ||
427 | mbCholS :: Matrix Double -> Maybe (Matrix Double) | ||
428 | mbCholS = unsafePerformIO . mbCatch . cholAux dpotrf "cholS" . fmat | ||
429 | |||
430 | ----------------------------------------------------------------------------------- | ||
431 | |||
432 | type TMVM t = t ..> t :> t ..> Ok | ||
433 | |||
434 | foreign import ccall unsafe "qr_l_R" dgeqr2 :: TMVM R | ||
435 | foreign import ccall unsafe "qr_l_C" zgeqr2 :: TMVM C | ||
436 | |||
437 | -- | QR factorization of a real matrix, using LAPACK's /dgeqr2/. | ||
438 | qrR :: Matrix Double -> (Matrix Double, Vector Double) | ||
439 | qrR = qrAux dgeqr2 "qrR" . fmat | ||
440 | |||
441 | -- | QR factorization of a complex matrix, using LAPACK's /zgeqr2/. | ||
442 | qrC :: Matrix (Complex Double) -> (Matrix (Complex Double), Vector (Complex Double)) | ||
443 | qrC = qrAux zgeqr2 "qrC" . fmat | ||
444 | |||
445 | qrAux f st a = unsafePerformIO $ do | ||
446 | r <- createMatrix ColumnMajor m n | ||
447 | tau <- createVector mn | ||
448 | app3 f mat a vec tau mat r st | ||
449 | return (r,tau) | ||
450 | where | ||
451 | m = rows a | ||
452 | n = cols a | ||
453 | mn = min m n | ||
454 | |||
455 | foreign import ccall unsafe "c_dorgqr" dorgqr :: TMVM R | ||
456 | foreign import ccall unsafe "c_zungqr" zungqr :: TMVM C | ||
457 | |||
458 | -- | build rotation from reflectors | ||
459 | qrgrR :: Int -> (Matrix Double, Vector Double) -> Matrix Double | ||
460 | qrgrR = qrgrAux dorgqr "qrgrR" | ||
461 | -- | build rotation from reflectors | ||
462 | qrgrC :: Int -> (Matrix (Complex Double), Vector (Complex Double)) -> Matrix (Complex Double) | ||
463 | qrgrC = qrgrAux zungqr "qrgrC" | ||
464 | |||
465 | qrgrAux f st n (a, tau) = unsafePerformIO $ do | ||
466 | res <- createMatrix ColumnMajor (rows a) n | ||
467 | app3 f mat (fmat a) vec (subVector 0 n tau') mat res st | ||
468 | return res | ||
469 | where | ||
470 | tau' = vjoin [tau, constantD 0 n] | ||
471 | |||
472 | ----------------------------------------------------------------------------------- | ||
473 | foreign import ccall unsafe "hess_l_R" dgehrd :: TMVM R | ||
474 | foreign import ccall unsafe "hess_l_C" zgehrd :: TMVM C | ||
475 | |||
476 | -- | Hessenberg factorization of a square real matrix, using LAPACK's /dgehrd/. | ||
477 | hessR :: Matrix Double -> (Matrix Double, Vector Double) | ||
478 | hessR = hessAux dgehrd "hessR" . fmat | ||
479 | |||
480 | -- | Hessenberg factorization of a square complex matrix, using LAPACK's /zgehrd/. | ||
481 | hessC :: Matrix (Complex Double) -> (Matrix (Complex Double), Vector (Complex Double)) | ||
482 | hessC = hessAux zgehrd "hessC" . fmat | ||
483 | |||
484 | hessAux f st a = unsafePerformIO $ do | ||
485 | r <- createMatrix ColumnMajor m n | ||
486 | tau <- createVector (mn-1) | ||
487 | app3 f mat a vec tau mat r st | ||
488 | return (r,tau) | ||
489 | where m = rows a | ||
490 | n = cols a | ||
491 | mn = min m n | ||
492 | |||
493 | ----------------------------------------------------------------------------------- | ||
494 | foreign import ccall unsafe "schur_l_R" dgees :: TMMM R | ||
495 | foreign import ccall unsafe "schur_l_C" zgees :: TMMM C | ||
496 | |||
497 | -- | Schur factorization of a square real matrix, using LAPACK's /dgees/. | ||
498 | schurR :: Matrix Double -> (Matrix Double, Matrix Double) | ||
499 | schurR = schurAux dgees "schurR" . fmat | ||
500 | |||
501 | -- | Schur factorization of a square complex matrix, using LAPACK's /zgees/. | ||
502 | schurC :: Matrix (Complex Double) -> (Matrix (Complex Double), Matrix (Complex Double)) | ||
503 | schurC = schurAux zgees "schurC" . fmat | ||
504 | |||
505 | schurAux f st a = unsafePerformIO $ do | ||
506 | u <- createMatrix ColumnMajor n n | ||
507 | s <- createMatrix ColumnMajor n n | ||
508 | app3 f mat a mat u mat s st | ||
509 | return (u,s) | ||
510 | where n = rows a | ||
511 | |||
512 | ----------------------------------------------------------------------------------- | ||
513 | foreign import ccall unsafe "lu_l_R" dgetrf :: TMVM R | ||
514 | foreign import ccall unsafe "lu_l_C" zgetrf :: C ..> R :> C ..> Ok | ||
515 | |||
516 | -- | LU factorization of a general real matrix, using LAPACK's /dgetrf/. | ||
517 | luR :: Matrix Double -> (Matrix Double, [Int]) | ||
518 | luR = luAux dgetrf "luR" . fmat | ||
519 | |||
520 | -- | LU factorization of a general complex matrix, using LAPACK's /zgetrf/. | ||
521 | luC :: Matrix (Complex Double) -> (Matrix (Complex Double), [Int]) | ||
522 | luC = luAux zgetrf "luC" . fmat | ||
523 | |||
524 | luAux f st a = unsafePerformIO $ do | ||
525 | lu <- createMatrix ColumnMajor n m | ||
526 | piv <- createVector (min n m) | ||
527 | app3 f mat a vec piv mat lu st | ||
528 | return (lu, map (pred.round) (toList piv)) | ||
529 | where n = rows a | ||
530 | m = cols a | ||
531 | |||
532 | ----------------------------------------------------------------------------------- | ||
533 | |||
534 | type Tlus t = t ..> Double :> t ..> t ..> Ok | ||
535 | |||
536 | foreign import ccall unsafe "luS_l_R" dgetrs :: Tlus R | ||
537 | foreign import ccall unsafe "luS_l_C" zgetrs :: Tlus C | ||
538 | |||
539 | -- | Solve a real linear system from a precomputed LU decomposition ('luR'), using LAPACK's /dgetrs/. | ||
540 | lusR :: Matrix Double -> [Int] -> Matrix Double -> Matrix Double | ||
541 | lusR a piv b = lusAux dgetrs "lusR" (fmat a) piv (fmat b) | ||
542 | |||
543 | -- | Solve a real linear system from a precomputed LU decomposition ('luC'), using LAPACK's /zgetrs/. | ||
544 | lusC :: Matrix (Complex Double) -> [Int] -> Matrix (Complex Double) -> Matrix (Complex Double) | ||
545 | lusC a piv b = lusAux zgetrs "lusC" (fmat a) piv (fmat b) | ||
546 | |||
547 | lusAux f st a piv b | ||
548 | | n1==n2 && n2==n =unsafePerformIO $ do | ||
549 | x <- createMatrix ColumnMajor n m | ||
550 | app4 f mat a vec piv' mat b mat x st | ||
551 | return x | ||
552 | | otherwise = error $ st ++ " on LU factorization of nonsquare matrix" | ||
553 | where n1 = rows a | ||
554 | n2 = cols a | ||
555 | n = rows b | ||
556 | m = cols b | ||
557 | piv' = fromList (map (fromIntegral.succ) piv) :: Vector Double | ||
558 | |||