root / src / lapack / double / dorml2.f @ 10
Historique | Voir | Annoter | Télécharger (5,2 ko)
1 | 1 | pfleura2 | SUBROUTINE DORML2( SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC, |
---|---|---|---|
2 | 1 | pfleura2 | $ WORK, INFO ) |
3 | 1 | pfleura2 | * |
4 | 1 | pfleura2 | * -- LAPACK routine (version 3.2) -- |
5 | 1 | pfleura2 | * -- LAPACK is a software package provided by Univ. of Tennessee, -- |
6 | 1 | pfleura2 | * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..-- |
7 | 1 | pfleura2 | * November 2006 |
8 | 1 | pfleura2 | * |
9 | 1 | pfleura2 | * .. Scalar Arguments .. |
10 | 1 | pfleura2 | CHARACTER SIDE, TRANS |
11 | 1 | pfleura2 | INTEGER INFO, K, LDA, LDC, M, N |
12 | 1 | pfleura2 | * .. |
13 | 1 | pfleura2 | * .. Array Arguments .. |
14 | 1 | pfleura2 | DOUBLE PRECISION A( LDA, * ), C( LDC, * ), TAU( * ), WORK( * ) |
15 | 1 | pfleura2 | * .. |
16 | 1 | pfleura2 | * |
17 | 1 | pfleura2 | * Purpose |
18 | 1 | pfleura2 | * ======= |
19 | 1 | pfleura2 | * |
20 | 1 | pfleura2 | * DORML2 overwrites the general real m by n matrix C with |
21 | 1 | pfleura2 | * |
22 | 1 | pfleura2 | * Q * C if SIDE = 'L' and TRANS = 'N', or |
23 | 1 | pfleura2 | * |
24 | 1 | pfleura2 | * Q'* C if SIDE = 'L' and TRANS = 'T', or |
25 | 1 | pfleura2 | * |
26 | 1 | pfleura2 | * C * Q if SIDE = 'R' and TRANS = 'N', or |
27 | 1 | pfleura2 | * |
28 | 1 | pfleura2 | * C * Q' if SIDE = 'R' and TRANS = 'T', |
29 | 1 | pfleura2 | * |
30 | 1 | pfleura2 | * where Q is a real orthogonal matrix defined as the product of k |
31 | 1 | pfleura2 | * elementary reflectors |
32 | 1 | pfleura2 | * |
33 | 1 | pfleura2 | * Q = H(k) . . . H(2) H(1) |
34 | 1 | pfleura2 | * |
35 | 1 | pfleura2 | * as returned by DGELQF. Q is of order m if SIDE = 'L' and of order n |
36 | 1 | pfleura2 | * if SIDE = 'R'. |
37 | 1 | pfleura2 | * |
38 | 1 | pfleura2 | * Arguments |
39 | 1 | pfleura2 | * ========= |
40 | 1 | pfleura2 | * |
41 | 1 | pfleura2 | * SIDE (input) CHARACTER*1 |
42 | 1 | pfleura2 | * = 'L': apply Q or Q' from the Left |
43 | 1 | pfleura2 | * = 'R': apply Q or Q' from the Right |
44 | 1 | pfleura2 | * |
45 | 1 | pfleura2 | * TRANS (input) CHARACTER*1 |
46 | 1 | pfleura2 | * = 'N': apply Q (No transpose) |
47 | 1 | pfleura2 | * = 'T': apply Q' (Transpose) |
48 | 1 | pfleura2 | * |
49 | 1 | pfleura2 | * M (input) INTEGER |
50 | 1 | pfleura2 | * The number of rows of the matrix C. M >= 0. |
51 | 1 | pfleura2 | * |
52 | 1 | pfleura2 | * N (input) INTEGER |
53 | 1 | pfleura2 | * The number of columns of the matrix C. N >= 0. |
54 | 1 | pfleura2 | * |
55 | 1 | pfleura2 | * K (input) INTEGER |
56 | 1 | pfleura2 | * The number of elementary reflectors whose product defines |
57 | 1 | pfleura2 | * the matrix Q. |
58 | 1 | pfleura2 | * If SIDE = 'L', M >= K >= 0; |
59 | 1 | pfleura2 | * if SIDE = 'R', N >= K >= 0. |
60 | 1 | pfleura2 | * |
61 | 1 | pfleura2 | * A (input) DOUBLE PRECISION array, dimension |
62 | 1 | pfleura2 | * (LDA,M) if SIDE = 'L', |
63 | 1 | pfleura2 | * (LDA,N) if SIDE = 'R' |
64 | 1 | pfleura2 | * The i-th row must contain the vector which defines the |
65 | 1 | pfleura2 | * elementary reflector H(i), for i = 1,2,...,k, as returned by |
66 | 1 | pfleura2 | * DGELQF in the first k rows of its array argument A. |
67 | 1 | pfleura2 | * A is modified by the routine but restored on exit. |
68 | 1 | pfleura2 | * |
69 | 1 | pfleura2 | * LDA (input) INTEGER |
70 | 1 | pfleura2 | * The leading dimension of the array A. LDA >= max(1,K). |
71 | 1 | pfleura2 | * |
72 | 1 | pfleura2 | * TAU (input) DOUBLE PRECISION array, dimension (K) |
73 | 1 | pfleura2 | * TAU(i) must contain the scalar factor of the elementary |
74 | 1 | pfleura2 | * reflector H(i), as returned by DGELQF. |
75 | 1 | pfleura2 | * |
76 | 1 | pfleura2 | * C (input/output) DOUBLE PRECISION array, dimension (LDC,N) |
77 | 1 | pfleura2 | * On entry, the m by n matrix C. |
78 | 1 | pfleura2 | * On exit, C is overwritten by Q*C or Q'*C or C*Q' or C*Q. |
79 | 1 | pfleura2 | * |
80 | 1 | pfleura2 | * LDC (input) INTEGER |
81 | 1 | pfleura2 | * The leading dimension of the array C. LDC >= max(1,M). |
82 | 1 | pfleura2 | * |
83 | 1 | pfleura2 | * WORK (workspace) DOUBLE PRECISION array, dimension |
84 | 1 | pfleura2 | * (N) if SIDE = 'L', |
85 | 1 | pfleura2 | * (M) if SIDE = 'R' |
86 | 1 | pfleura2 | * |
87 | 1 | pfleura2 | * INFO (output) INTEGER |
88 | 1 | pfleura2 | * = 0: successful exit |
89 | 1 | pfleura2 | * < 0: if INFO = -i, the i-th argument had an illegal value |
90 | 1 | pfleura2 | * |
91 | 1 | pfleura2 | * ===================================================================== |
92 | 1 | pfleura2 | * |
93 | 1 | pfleura2 | * .. Parameters .. |
94 | 1 | pfleura2 | DOUBLE PRECISION ONE |
95 | 1 | pfleura2 | PARAMETER ( ONE = 1.0D+0 ) |
96 | 1 | pfleura2 | * .. |
97 | 1 | pfleura2 | * .. Local Scalars .. |
98 | 1 | pfleura2 | LOGICAL LEFT, NOTRAN |
99 | 1 | pfleura2 | INTEGER I, I1, I2, I3, IC, JC, MI, NI, NQ |
100 | 1 | pfleura2 | DOUBLE PRECISION AII |
101 | 1 | pfleura2 | * .. |
102 | 1 | pfleura2 | * .. External Functions .. |
103 | 1 | pfleura2 | LOGICAL LSAME |
104 | 1 | pfleura2 | EXTERNAL LSAME |
105 | 1 | pfleura2 | * .. |
106 | 1 | pfleura2 | * .. External Subroutines .. |
107 | 1 | pfleura2 | EXTERNAL DLARF, XERBLA |
108 | 1 | pfleura2 | * .. |
109 | 1 | pfleura2 | * .. Intrinsic Functions .. |
110 | 1 | pfleura2 | INTRINSIC MAX |
111 | 1 | pfleura2 | * .. |
112 | 1 | pfleura2 | * .. Executable Statements .. |
113 | 1 | pfleura2 | * |
114 | 1 | pfleura2 | * Test the input arguments |
115 | 1 | pfleura2 | * |
116 | 1 | pfleura2 | INFO = 0 |
117 | 1 | pfleura2 | LEFT = LSAME( SIDE, 'L' ) |
118 | 1 | pfleura2 | NOTRAN = LSAME( TRANS, 'N' ) |
119 | 1 | pfleura2 | * |
120 | 1 | pfleura2 | * NQ is the order of Q |
121 | 1 | pfleura2 | * |
122 | 1 | pfleura2 | IF( LEFT ) THEN |
123 | 1 | pfleura2 | NQ = M |
124 | 1 | pfleura2 | ELSE |
125 | 1 | pfleura2 | NQ = N |
126 | 1 | pfleura2 | END IF |
127 | 1 | pfleura2 | IF( .NOT.LEFT .AND. .NOT.LSAME( SIDE, 'R' ) ) THEN |
128 | 1 | pfleura2 | INFO = -1 |
129 | 1 | pfleura2 | ELSE IF( .NOT.NOTRAN .AND. .NOT.LSAME( TRANS, 'T' ) ) THEN |
130 | 1 | pfleura2 | INFO = -2 |
131 | 1 | pfleura2 | ELSE IF( M.LT.0 ) THEN |
132 | 1 | pfleura2 | INFO = -3 |
133 | 1 | pfleura2 | ELSE IF( N.LT.0 ) THEN |
134 | 1 | pfleura2 | INFO = -4 |
135 | 1 | pfleura2 | ELSE IF( K.LT.0 .OR. K.GT.NQ ) THEN |
136 | 1 | pfleura2 | INFO = -5 |
137 | 1 | pfleura2 | ELSE IF( LDA.LT.MAX( 1, K ) ) THEN |
138 | 1 | pfleura2 | INFO = -7 |
139 | 1 | pfleura2 | ELSE IF( LDC.LT.MAX( 1, M ) ) THEN |
140 | 1 | pfleura2 | INFO = -10 |
141 | 1 | pfleura2 | END IF |
142 | 1 | pfleura2 | IF( INFO.NE.0 ) THEN |
143 | 1 | pfleura2 | CALL XERBLA( 'DORML2', -INFO ) |
144 | 1 | pfleura2 | RETURN |
145 | 1 | pfleura2 | END IF |
146 | 1 | pfleura2 | * |
147 | 1 | pfleura2 | * Quick return if possible |
148 | 1 | pfleura2 | * |
149 | 1 | pfleura2 | IF( M.EQ.0 .OR. N.EQ.0 .OR. K.EQ.0 ) |
150 | 1 | pfleura2 | $ RETURN |
151 | 1 | pfleura2 | * |
152 | 1 | pfleura2 | IF( ( LEFT .AND. NOTRAN ) .OR. ( .NOT.LEFT .AND. .NOT.NOTRAN ) ) |
153 | 1 | pfleura2 | $ THEN |
154 | 1 | pfleura2 | I1 = 1 |
155 | 1 | pfleura2 | I2 = K |
156 | 1 | pfleura2 | I3 = 1 |
157 | 1 | pfleura2 | ELSE |
158 | 1 | pfleura2 | I1 = K |
159 | 1 | pfleura2 | I2 = 1 |
160 | 1 | pfleura2 | I3 = -1 |
161 | 1 | pfleura2 | END IF |
162 | 1 | pfleura2 | * |
163 | 1 | pfleura2 | IF( LEFT ) THEN |
164 | 1 | pfleura2 | NI = N |
165 | 1 | pfleura2 | JC = 1 |
166 | 1 | pfleura2 | ELSE |
167 | 1 | pfleura2 | MI = M |
168 | 1 | pfleura2 | IC = 1 |
169 | 1 | pfleura2 | END IF |
170 | 1 | pfleura2 | * |
171 | 1 | pfleura2 | DO 10 I = I1, I2, I3 |
172 | 1 | pfleura2 | IF( LEFT ) THEN |
173 | 1 | pfleura2 | * |
174 | 1 | pfleura2 | * H(i) is applied to C(i:m,1:n) |
175 | 1 | pfleura2 | * |
176 | 1 | pfleura2 | MI = M - I + 1 |
177 | 1 | pfleura2 | IC = I |
178 | 1 | pfleura2 | ELSE |
179 | 1 | pfleura2 | * |
180 | 1 | pfleura2 | * H(i) is applied to C(1:m,i:n) |
181 | 1 | pfleura2 | * |
182 | 1 | pfleura2 | NI = N - I + 1 |
183 | 1 | pfleura2 | JC = I |
184 | 1 | pfleura2 | END IF |
185 | 1 | pfleura2 | * |
186 | 1 | pfleura2 | * Apply H(i) |
187 | 1 | pfleura2 | * |
188 | 1 | pfleura2 | AII = A( I, I ) |
189 | 1 | pfleura2 | A( I, I ) = ONE |
190 | 1 | pfleura2 | CALL DLARF( SIDE, MI, NI, A( I, I ), LDA, TAU( I ), |
191 | 1 | pfleura2 | $ C( IC, JC ), LDC, WORK ) |
192 | 1 | pfleura2 | A( I, I ) = AII |
193 | 1 | pfleura2 | 10 CONTINUE |
194 | 1 | pfleura2 | RETURN |
195 | 1 | pfleura2 | * |
196 | 1 | pfleura2 | * End of DORML2 |
197 | 1 | pfleura2 | * |
198 | 1 | pfleura2 | END |