Mercurial > hg > octave-lyh
comparison libcruft/lapack/cung2r.f @ 7789:82be108cc558
First attempt at single precision tyeps
* * *
corrections to qrupdate single precision routines
* * *
prefer demotion to single over promotion to double
* * *
Add single precision support to log2 function
* * *
Trivial PROJECT file update
* * *
Cache optimized hermitian/transpose methods
* * *
Add tests for tranpose/hermitian and ChangeLog entry for new transpose code
author | David Bateman <dbateman@free.fr> |
---|---|
date | Sun, 27 Apr 2008 22:34:17 +0200 |
parents | |
children |
comparison
equal
deleted
inserted
replaced
7788:45f5faba05a2 | 7789:82be108cc558 |
---|---|
1 SUBROUTINE CUNG2R( M, N, K, A, LDA, TAU, WORK, INFO ) | |
2 * | |
3 * -- LAPACK routine (version 3.1) -- | |
4 * Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd.. | |
5 * November 2006 | |
6 * | |
7 * .. Scalar Arguments .. | |
8 INTEGER INFO, K, LDA, M, N | |
9 * .. | |
10 * .. Array Arguments .. | |
11 COMPLEX A( LDA, * ), TAU( * ), WORK( * ) | |
12 * .. | |
13 * | |
14 * Purpose | |
15 * ======= | |
16 * | |
17 * CUNG2R generates an m by n complex matrix Q with orthonormal columns, | |
18 * which is defined as the first n columns of a product of k elementary | |
19 * reflectors of order m | |
20 * | |
21 * Q = H(1) H(2) . . . H(k) | |
22 * | |
23 * as returned by CGEQRF. | |
24 * | |
25 * Arguments | |
26 * ========= | |
27 * | |
28 * M (input) INTEGER | |
29 * The number of rows of the matrix Q. M >= 0. | |
30 * | |
31 * N (input) INTEGER | |
32 * The number of columns of the matrix Q. M >= N >= 0. | |
33 * | |
34 * K (input) INTEGER | |
35 * The number of elementary reflectors whose product defines the | |
36 * matrix Q. N >= K >= 0. | |
37 * | |
38 * A (input/output) COMPLEX array, dimension (LDA,N) | |
39 * On entry, the i-th column must contain the vector which | |
40 * defines the elementary reflector H(i), for i = 1,2,...,k, as | |
41 * returned by CGEQRF in the first k columns of its array | |
42 * argument A. | |
43 * On exit, the m by n matrix Q. | |
44 * | |
45 * LDA (input) INTEGER | |
46 * The first dimension of the array A. LDA >= max(1,M). | |
47 * | |
48 * TAU (input) COMPLEX array, dimension (K) | |
49 * TAU(i) must contain the scalar factor of the elementary | |
50 * reflector H(i), as returned by CGEQRF. | |
51 * | |
52 * WORK (workspace) COMPLEX array, dimension (N) | |
53 * | |
54 * INFO (output) INTEGER | |
55 * = 0: successful exit | |
56 * < 0: if INFO = -i, the i-th argument has an illegal value | |
57 * | |
58 * ===================================================================== | |
59 * | |
60 * .. Parameters .. | |
61 COMPLEX ONE, ZERO | |
62 PARAMETER ( ONE = ( 1.0E+0, 0.0E+0 ), | |
63 $ ZERO = ( 0.0E+0, 0.0E+0 ) ) | |
64 * .. | |
65 * .. Local Scalars .. | |
66 INTEGER I, J, L | |
67 * .. | |
68 * .. External Subroutines .. | |
69 EXTERNAL CLARF, CSCAL, XERBLA | |
70 * .. | |
71 * .. Intrinsic Functions .. | |
72 INTRINSIC MAX | |
73 * .. | |
74 * .. Executable Statements .. | |
75 * | |
76 * Test the input arguments | |
77 * | |
78 INFO = 0 | |
79 IF( M.LT.0 ) THEN | |
80 INFO = -1 | |
81 ELSE IF( N.LT.0 .OR. N.GT.M ) THEN | |
82 INFO = -2 | |
83 ELSE IF( K.LT.0 .OR. K.GT.N ) THEN | |
84 INFO = -3 | |
85 ELSE IF( LDA.LT.MAX( 1, M ) ) THEN | |
86 INFO = -5 | |
87 END IF | |
88 IF( INFO.NE.0 ) THEN | |
89 CALL XERBLA( 'CUNG2R', -INFO ) | |
90 RETURN | |
91 END IF | |
92 * | |
93 * Quick return if possible | |
94 * | |
95 IF( N.LE.0 ) | |
96 $ RETURN | |
97 * | |
98 * Initialise columns k+1:n to columns of the unit matrix | |
99 * | |
100 DO 20 J = K + 1, N | |
101 DO 10 L = 1, M | |
102 A( L, J ) = ZERO | |
103 10 CONTINUE | |
104 A( J, J ) = ONE | |
105 20 CONTINUE | |
106 * | |
107 DO 40 I = K, 1, -1 | |
108 * | |
109 * Apply H(i) to A(i:m,i:n) from the left | |
110 * | |
111 IF( I.LT.N ) THEN | |
112 A( I, I ) = ONE | |
113 CALL CLARF( 'Left', M-I+1, N-I, A( I, I ), 1, TAU( I ), | |
114 $ A( I, I+1 ), LDA, WORK ) | |
115 END IF | |
116 IF( I.LT.M ) | |
117 $ CALL CSCAL( M-I, -TAU( I ), A( I+1, I ), 1 ) | |
118 A( I, I ) = ONE - TAU( I ) | |
119 * | |
120 * Set A(1:i-1,i) to zero | |
121 * | |
122 DO 30 L = 1, I - 1 | |
123 A( L, I ) = ZERO | |
124 30 CONTINUE | |
125 40 CONTINUE | |
126 RETURN | |
127 * | |
128 * End of CUNG2R | |
129 * | |
130 END |