LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dsyconvf.f
Go to the documentation of this file.
1*> \brief \b DSYCONVF
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download DSYCONVF + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dsyconvf.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dsyconvf.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dsyconvf.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE DSYCONVF( UPLO, WAY, N, A, LDA, E, IPIV, INFO )
20*
21* .. Scalar Arguments ..
22* CHARACTER UPLO, WAY
23* INTEGER INFO, LDA, N
24* ..
25* .. Array Arguments ..
26* INTEGER IPIV( * )
27* DOUBLE PRECISION A( LDA, * ), E( * )
28* ..
29*
30*
31*> \par Purpose:
32* =============
33*>
34*> \verbatim
35*> If parameter WAY = 'C':
36*> DSYCONVF converts the factorization output format used in
37*> DSYTRF provided on entry in parameter A into the factorization
38*> output format used in DSYTRF_RK (or DSYTRF_BK) that is stored
39*> on exit in parameters A and E. It also converts in place details of
40*> the interchanges stored in IPIV from the format used in DSYTRF into
41*> the format used in DSYTRF_RK (or DSYTRF_BK).
42*>
43*> If parameter WAY = 'R':
44*> DSYCONVF performs the conversion in reverse direction, i.e.
45*> converts the factorization output format used in DSYTRF_RK
46*> (or DSYTRF_BK) provided on entry in parameters A and E into
47*> the factorization output format used in DSYTRF that is stored
48*> on exit in parameter A. It also converts in place details of
49*> the interchanges stored in IPIV from the format used in DSYTRF_RK
50*> (or DSYTRF_BK) into the format used in DSYTRF.
51*> \endverbatim
52*
53* Arguments:
54* ==========
55*
56*> \param[in] UPLO
57*> \verbatim
58*> UPLO is CHARACTER*1
59*> Specifies whether the details of the factorization are
60*> stored as an upper or lower triangular matrix A.
61*> = 'U': Upper triangular
62*> = 'L': Lower triangular
63*> \endverbatim
64*>
65*> \param[in] WAY
66*> \verbatim
67*> WAY is CHARACTER*1
68*> = 'C': Convert
69*> = 'R': Revert
70*> \endverbatim
71*>
72*> \param[in] N
73*> \verbatim
74*> N is INTEGER
75*> The order of the matrix A. N >= 0.
76*> \endverbatim
77*>
78*> \param[in,out] A
79*> \verbatim
80*> A is DOUBLE PRECISION array, dimension (LDA,N)
81*>
82*> 1) If WAY ='C':
83*>
84*> On entry, contains factorization details in format used in
85*> DSYTRF:
86*> a) all elements of the symmetric block diagonal
87*> matrix D on the diagonal of A and on superdiagonal
88*> (or subdiagonal) of A, and
89*> b) If UPLO = 'U': multipliers used to obtain factor U
90*> in the superdiagonal part of A.
91*> If UPLO = 'L': multipliers used to obtain factor L
92*> in the superdiagonal part of A.
93*>
94*> On exit, contains factorization details in format used in
95*> DSYTRF_RK or DSYTRF_BK:
96*> a) ONLY diagonal elements of the symmetric block diagonal
97*> matrix D on the diagonal of A, i.e. D(k,k) = A(k,k);
98*> (superdiagonal (or subdiagonal) elements of D
99*> are stored on exit in array E), and
100*> b) If UPLO = 'U': factor U in the superdiagonal part of A.
101*> If UPLO = 'L': factor L in the subdiagonal part of A.
102*>
103*> 2) If WAY = 'R':
104*>
105*> On entry, contains factorization details in format used in
106*> DSYTRF_RK or DSYTRF_BK:
107*> a) ONLY diagonal elements of the symmetric block diagonal
108*> matrix D on the diagonal of A, i.e. D(k,k) = A(k,k);
109*> (superdiagonal (or subdiagonal) elements of D
110*> are stored on exit in array E), and
111*> b) If UPLO = 'U': factor U in the superdiagonal part of A.
112*> If UPLO = 'L': factor L in the subdiagonal part of A.
113*>
114*> On exit, contains factorization details in format used in
115*> DSYTRF:
116*> a) all elements of the symmetric block diagonal
117*> matrix D on the diagonal of A and on superdiagonal
118*> (or subdiagonal) of A, and
119*> b) If UPLO = 'U': multipliers used to obtain factor U
120*> in the superdiagonal part of A.
121*> If UPLO = 'L': multipliers used to obtain factor L
122*> in the superdiagonal part of A.
123*> \endverbatim
124*>
125*> \param[in] LDA
126*> \verbatim
127*> LDA is INTEGER
128*> The leading dimension of the array A. LDA >= max(1,N).
129*> \endverbatim
130*>
131*> \param[in,out] E
132*> \verbatim
133*> E is DOUBLE PRECISION array, dimension (N)
134*>
135*> 1) If WAY ='C':
136*>
137*> On entry, just a workspace.
138*>
139*> On exit, contains the superdiagonal (or subdiagonal)
140*> elements of the symmetric block diagonal matrix D
141*> with 1-by-1 or 2-by-2 diagonal blocks, where
142*> If UPLO = 'U': E(i) = D(i-1,i), i=2:N, E(1) is set to 0;
143*> If UPLO = 'L': E(i) = D(i+1,i), i=1:N-1, E(N) is set to 0.
144*>
145*> 2) If WAY = 'R':
146*>
147*> On entry, contains the superdiagonal (or subdiagonal)
148*> elements of the symmetric block diagonal matrix D
149*> with 1-by-1 or 2-by-2 diagonal blocks, where
150*> If UPLO = 'U': E(i) = D(i-1,i),i=2:N, E(1) not referenced;
151*> If UPLO = 'L': E(i) = D(i+1,i),i=1:N-1, E(N) not referenced.
152*>
153*> On exit, is not changed
154*> \endverbatim
155*.
156*> \param[in,out] IPIV
157*> \verbatim
158*> IPIV is INTEGER array, dimension (N)
159*>
160*> 1) If WAY ='C':
161*> On entry, details of the interchanges and the block
162*> structure of D in the format used in DSYTRF.
163*> On exit, details of the interchanges and the block
164*> structure of D in the format used in DSYTRF_RK
165*> ( or DSYTRF_BK).
166*>
167*> 1) If WAY ='R':
168*> On entry, details of the interchanges and the block
169*> structure of D in the format used in DSYTRF_RK
170*> ( or DSYTRF_BK).
171*> On exit, details of the interchanges and the block
172*> structure of D in the format used in DSYTRF.
173*> \endverbatim
174*>
175*> \param[out] INFO
176*> \verbatim
177*> INFO is INTEGER
178*> = 0: successful exit
179*> < 0: if INFO = -i, the i-th argument had an illegal value
180*> \endverbatim
181*
182* Authors:
183* ========
184*
185*> \author Univ. of Tennessee
186*> \author Univ. of California Berkeley
187*> \author Univ. of Colorado Denver
188*> \author NAG Ltd.
189*
190*> \ingroup syconvf
191*
192*> \par Contributors:
193* ==================
194*>
195*> \verbatim
196*>
197*> November 2017, Igor Kozachenko,
198*> Computer Science Division,
199*> University of California, Berkeley
200*>
201*> \endverbatim
202* =====================================================================
203 SUBROUTINE dsyconvf( UPLO, WAY, N, A, LDA, E, IPIV, INFO )
204*
205* -- LAPACK computational routine --
206* -- LAPACK is a software package provided by Univ. of Tennessee, --
207* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
208*
209* .. Scalar Arguments ..
210 CHARACTER UPLO, WAY
211 INTEGER INFO, LDA, N
212* ..
213* .. Array Arguments ..
214 INTEGER IPIV( * )
215 DOUBLE PRECISION A( LDA, * ), E( * )
216* ..
217*
218* =====================================================================
219*
220* .. Parameters ..
221 DOUBLE PRECISION ZERO
222 parameter( zero = 0.0d+0 )
223* ..
224* .. External Functions ..
225 LOGICAL LSAME
226 EXTERNAL lsame
227*
228* .. External Subroutines ..
229 EXTERNAL dswap, xerbla
230* .. Local Scalars ..
231 LOGICAL UPPER, CONVERT
232 INTEGER I, IP
233* ..
234* .. Executable Statements ..
235*
236 info = 0
237 upper = lsame( uplo, 'U' )
238 convert = lsame( way, 'C' )
239 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
240 info = -1
241 ELSE IF( .NOT.convert .AND. .NOT.lsame( way, 'R' ) ) THEN
242 info = -2
243 ELSE IF( n.LT.0 ) THEN
244 info = -3
245 ELSE IF( lda.LT.max( 1, n ) ) THEN
246 info = -5
247
248 END IF
249 IF( info.NE.0 ) THEN
250 CALL xerbla( 'DSYCONVF', -info )
251 RETURN
252 END IF
253*
254* Quick return if possible
255*
256 IF( n.EQ.0 )
257 $ RETURN
258*
259 IF( upper ) THEN
260*
261* Begin A is UPPER
262*
263 IF ( convert ) THEN
264*
265* Convert A (A is upper)
266*
267*
268* Convert VALUE
269*
270* Assign superdiagonal entries of D to array E and zero out
271* corresponding entries in input storage A
272*
273 i = n
274 e( 1 ) = zero
275 DO WHILE ( i.GT.1 )
276 IF( ipiv( i ).LT.0 ) THEN
277 e( i ) = a( i-1, i )
278 e( i-1 ) = zero
279 a( i-1, i ) = zero
280 i = i - 1
281 ELSE
282 e( i ) = zero
283 END IF
284 i = i - 1
285 END DO
286*
287* Convert PERMUTATIONS and IPIV
288*
289* Apply permutations to submatrices of upper part of A
290* in factorization order where i decreases from N to 1
291*
292 i = n
293 DO WHILE ( i.GE.1 )
294 IF( ipiv( i ).GT.0 ) THEN
295*
296* 1-by-1 pivot interchange
297*
298* Swap rows i and IPIV(i) in A(1:i,N-i:N)
299*
300 ip = ipiv( i )
301 IF( i.LT.n ) THEN
302 IF( ip.NE.i ) THEN
303 CALL dswap( n-i, a( i, i+1 ), lda,
304 $ a( ip, i+1 ), lda )
305 END IF
306 END IF
307*
308 ELSE
309*
310* 2-by-2 pivot interchange
311*
312* Swap rows i-1 and IPIV(i) in A(1:i,N-i:N)
313*
314 ip = -ipiv( i )
315 IF( i.LT.n ) THEN
316 IF( ip.NE.(i-1) ) THEN
317 CALL dswap( n-i, a( i-1, i+1 ), lda,
318 $ a( ip, i+1 ), lda )
319 END IF
320 END IF
321*
322* Convert IPIV
323* There is no interchange of rows i and and IPIV(i),
324* so this should be reflected in IPIV format for
325* *SYTRF_RK ( or *SYTRF_BK)
326*
327 ipiv( i ) = i
328*
329 i = i - 1
330*
331 END IF
332 i = i - 1
333 END DO
334*
335 ELSE
336*
337* Revert A (A is upper)
338*
339*
340* Revert PERMUTATIONS and IPIV
341*
342* Apply permutations to submatrices of upper part of A
343* in reverse factorization order where i increases from 1 to N
344*
345 i = 1
346 DO WHILE ( i.LE.n )
347 IF( ipiv( i ).GT.0 ) THEN
348*
349* 1-by-1 pivot interchange
350*
351* Swap rows i and IPIV(i) in A(1:i,N-i:N)
352*
353 ip = ipiv( i )
354 IF( i.LT.n ) THEN
355 IF( ip.NE.i ) THEN
356 CALL dswap( n-i, a( ip, i+1 ), lda,
357 $ a( i, i+1 ), lda )
358 END IF
359 END IF
360*
361 ELSE
362*
363* 2-by-2 pivot interchange
364*
365* Swap rows i-1 and IPIV(i) in A(1:i,N-i:N)
366*
367 i = i + 1
368 ip = -ipiv( i )
369 IF( i.LT.n ) THEN
370 IF( ip.NE.(i-1) ) THEN
371 CALL dswap( n-i, a( ip, i+1 ), lda,
372 $ a( i-1, i+1 ), lda )
373 END IF
374 END IF
375*
376* Convert IPIV
377* There is one interchange of rows i-1 and IPIV(i-1),
378* so this should be recorded in two consecutive entries
379* in IPIV format for *SYTRF
380*
381 ipiv( i ) = ipiv( i-1 )
382*
383 END IF
384 i = i + 1
385 END DO
386*
387* Revert VALUE
388* Assign superdiagonal entries of D from array E to
389* superdiagonal entries of A.
390*
391 i = n
392 DO WHILE ( i.GT.1 )
393 IF( ipiv( i ).LT.0 ) THEN
394 a( i-1, i ) = e( i )
395 i = i - 1
396 END IF
397 i = i - 1
398 END DO
399*
400* End A is UPPER
401*
402 END IF
403*
404 ELSE
405*
406* Begin A is LOWER
407*
408 IF ( convert ) THEN
409*
410* Convert A (A is lower)
411*
412*
413* Convert VALUE
414* Assign subdiagonal entries of D to array E and zero out
415* corresponding entries in input storage A
416*
417 i = 1
418 e( n ) = zero
419 DO WHILE ( i.LE.n )
420 IF( i.LT.n .AND. ipiv(i).LT.0 ) THEN
421 e( i ) = a( i+1, i )
422 e( i+1 ) = zero
423 a( i+1, i ) = zero
424 i = i + 1
425 ELSE
426 e( i ) = zero
427 END IF
428 i = i + 1
429 END DO
430*
431* Convert PERMUTATIONS and IPIV
432*
433* Apply permutations to submatrices of lower part of A
434* in factorization order where k increases from 1 to N
435*
436 i = 1
437 DO WHILE ( i.LE.n )
438 IF( ipiv( i ).GT.0 ) THEN
439*
440* 1-by-1 pivot interchange
441*
442* Swap rows i and IPIV(i) in A(i:N,1:i-1)
443*
444 ip = ipiv( i )
445 IF ( i.GT.1 ) THEN
446 IF( ip.NE.i ) THEN
447 CALL dswap( i-1, a( i, 1 ), lda,
448 $ a( ip, 1 ), lda )
449 END IF
450 END IF
451*
452 ELSE
453*
454* 2-by-2 pivot interchange
455*
456* Swap rows i+1 and IPIV(i) in A(i:N,1:i-1)
457*
458 ip = -ipiv( i )
459 IF ( i.GT.1 ) THEN
460 IF( ip.NE.(i+1) ) THEN
461 CALL dswap( i-1, a( i+1, 1 ), lda,
462 $ a( ip, 1 ), lda )
463 END IF
464 END IF
465*
466* Convert IPIV
467* There is no interchange of rows i and and IPIV(i),
468* so this should be reflected in IPIV format for
469* *SYTRF_RK ( or *SYTRF_BK)
470*
471 ipiv( i ) = i
472*
473 i = i + 1
474*
475 END IF
476 i = i + 1
477 END DO
478*
479 ELSE
480*
481* Revert A (A is lower)
482*
483*
484* Revert PERMUTATIONS and IPIV
485*
486* Apply permutations to submatrices of lower part of A
487* in reverse factorization order where i decreases from N to 1
488*
489 i = n
490 DO WHILE ( i.GE.1 )
491 IF( ipiv( i ).GT.0 ) THEN
492*
493* 1-by-1 pivot interchange
494*
495* Swap rows i and IPIV(i) in A(i:N,1:i-1)
496*
497 ip = ipiv( i )
498 IF ( i.GT.1 ) THEN
499 IF( ip.NE.i ) THEN
500 CALL dswap( i-1, a( ip, 1 ), lda,
501 $ a( i, 1 ), lda )
502 END IF
503 END IF
504*
505 ELSE
506*
507* 2-by-2 pivot interchange
508*
509* Swap rows i+1 and IPIV(i) in A(i:N,1:i-1)
510*
511 i = i - 1
512 ip = -ipiv( i )
513 IF ( i.GT.1 ) THEN
514 IF( ip.NE.(i+1) ) THEN
515 CALL dswap( i-1, a( ip, 1 ), lda,
516 $ a( i+1, 1 ), lda )
517 END IF
518 END IF
519*
520* Convert IPIV
521* There is one interchange of rows i+1 and IPIV(i+1),
522* so this should be recorded in consecutive entries
523* in IPIV format for *SYTRF
524*
525 ipiv( i ) = ipiv( i+1 )
526*
527 END IF
528 i = i - 1
529 END DO
530*
531* Revert VALUE
532* Assign subdiagonal entries of D from array E to
533* subdiagonal entries of A.
534*
535 i = 1
536 DO WHILE ( i.LE.n-1 )
537 IF( ipiv( i ).LT.0 ) THEN
538 a( i + 1, i ) = e( i )
539 i = i + 1
540 END IF
541 i = i + 1
542 END DO
543*
544 END IF
545*
546* End A is LOWER
547*
548 END IF
549
550 RETURN
551*
552* End of DSYCONVF
553*
554 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine dswap(n, dx, incx, dy, incy)
DSWAP
Definition dswap.f:82
subroutine dsyconvf(uplo, way, n, a, lda, e, ipiv, info)
DSYCONVF
Definition dsyconvf.f:204