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