1+ * > \brief \b CLARFB0C2 applies a block reflector or its conjugate-transpose
2+ * to a rectangular matrix with a 0 block while constructing the explicit Q
3+ * factor
4+ *
5+ * =========== DOCUMENTATION ===========
6+ *
7+ * Online html documentation available at
8+ * http://www.netlib.org/lapack/explore-html/
9+ *
10+ *
11+ * Definition:
12+ * ===========
13+ *
14+ * SUBROUTINE CLARFB0C2(C2I, SIDE, TRANS, DIRECT, STOREV, M, N,
15+ * $ K, V, LDV, T, LDT, C, LDC)
16+ * ! Scalar arguments
17+ * INTEGER M, N, K, LDV, LDC, LDT
18+ * CHARACTER SIDE, TRANS, DIRECT, STOREV
19+ * ! True means that we are assuming C2 is the identity matrix
20+ * ! and thus don't reference whatever is present in C2
21+ * ! at the beginning.
22+ * LOGICAL C2I
23+ * ! Array arguments
24+ * COMPLEX V(LDV,*), C(LDC,*), T(LDT,*)
25+ *
26+ *
27+ * > \par Purpose:
28+ * =============
29+ * >
30+ * > \verbatim
31+ * >
32+ * > CLARFB0C2 applies a real block reflector H or its transpose H**H to a
33+ * > complex m by n matrix C with a 0 block, while computing the explicit Q factor
34+ * > \endverbatim
35+ *
36+ * Arguments:
37+ * ==========
38+ *
39+ * > \param[in] C2I
40+ * > \verbatim
41+ * > C2I is LOGICAL
42+ * > = .TRUE.: Assume the nonzero block of C is the identity matrix
43+ * > = .FALSE.: Use existing data in the nonzero block of C
44+ * > \endverbatim
45+ * >
46+ * > \param[in] SIDE
47+ * > \verbatim
48+ * > SIDE is CHARACTER*1
49+ * > = 'L': apply H or H**H from the Left
50+ * > = 'R': apply H or H**H from the Right
51+ * > \endverbatim
52+ * >
53+ * > \param[in] TRANS
54+ * > \verbatim
55+ * > TRANS is CHARACTER*1
56+ * > = 'N': apply H (No transpose)
57+ * > = 'C': apply H**H (Conjugate transpose)
58+ * > \endverbatim
59+ * >
60+ * > \param[in] DIRECT
61+ * > \verbatim
62+ * > DIRECT is CHARACTER*1
63+ * > Indicates how H is formed from a product of elementary
64+ * > reflectors
65+ * > = 'F': H = H(1) H(2) . . . H(k) (Forward)
66+ * > = 'B': H = H(k) . . . H(2) H(1) (Backward)
67+ * > \endverbatim
68+ * >
69+ * > \param[in] STOREV
70+ * > \verbatim
71+ * > STOREV is CHARACTER*1
72+ * > Indicates how the vectors which define the elementary
73+ * > reflectors are stored:
74+ * > = 'C': Columnwise
75+ * > = 'R': Rowwise
76+ * > \endverbatim
77+ * >
78+ * > \param[in] M
79+ * > \verbatim
80+ * > M is INTEGER
81+ * > The number of rows of the matrix C.
82+ * > \endverbatim
83+ * >
84+ * > \param[in] N
85+ * > \verbatim
86+ * > N is INTEGER
87+ * > The number of columns of the matrix C.
88+ * > \endverbatim
89+ * >
90+ * > \param[in] K
91+ * > \verbatim
92+ * > K is INTEGER
93+ * > The order of the matrix T (= the number of elementary
94+ * > reflectors whose product defines the block reflector).
95+ * > If SIDE = 'L', M >= K >= 0;
96+ * > if SIDE = 'R', N >= K >= 0.
97+ * > \endverbatim
98+ * >
99+ * > \param[in] V
100+ * > \verbatim
101+ * > V is COMPLEX array, dimension
102+ * > (LDV,K) if STOREV = 'C'
103+ * > (LDV,M) if STOREV = 'R' and SIDE = 'L'
104+ * > (LDV,N) if STOREV = 'R' and SIDE = 'R'
105+ * > See Further Details.
106+ * > \endverbatim
107+ * >
108+ * > \param[in] LDV
109+ * > \verbatim
110+ * > LDV is INTEGER
111+ * > The leading dimension of the array V.
112+ * > If STOREV = 'C' and SIDE = 'L', LDV >= max(1,M);
113+ * > if STOREV = 'C' and SIDE = 'R', LDV >= max(1,N);
114+ * > if STOREV = 'R', LDV >= K.
115+ * > \endverbatim
116+ * >
117+ * > \param[in] T
118+ * > \verbatim
119+ * > T is COMPLEX array, dimension (LDT,K)
120+ * > The triangular K-by-K matrix T in the representation of the
121+ * > block reflector.
122+ * > \endverbatim
123+ * >
124+ * > \param[in] LDT
125+ * > \verbatim
126+ * > LDT is INTEGER
127+ * > The leading dimension of the array T. LDT >= K.
128+ * > \endverbatim
129+ * >
130+ * > \param[in,out] C
131+ * > \verbatim
132+ * > C is COMPLEX array, dimension (LDC,N)
133+ * > On entry, the M-by-N matrix C.
134+ * > On exit, C is overwritten by H*C or H**H*C or C*H or C*H**H.
135+ * > \endverbatim
136+ * >
137+ * > \param[in] LDC
138+ * > \verbatim
139+ * > LDC is INTEGER
140+ * > The leading dimension of the array C. LDC >= max(1,M).
141+ * > \endverbatim
142+ *
143+ * Authors:
144+ * ========
145+ *
146+ * > \author Univ. of Tennessee
147+ * > \author Univ. of California Berkeley
148+ * > \author Univ. of Colorado Denver
149+ * > \author NAG Ltd.
150+ *
151+ * > \ingroup larfb
152+ *
153+ * > \par Further Details:
154+ * =====================
155+ * >
156+ * > \verbatim
157+ * >
158+ * > The shape of the matrix V and the storage of the vectors which define
159+ * > the H(i) is best illustrated by the following example with n = 5 and
160+ * > k = 3. The triangular part of V (including its diagonal) is not
161+ * > referenced.
162+ * >
163+ * > DIRECT = 'F' and STOREV = 'C': DIRECT = 'F' and STOREV = 'R':
164+ * >
165+ * > V = ( 1 ) V = ( 1 v1 v1 v1 v1 )
166+ * > ( v1 1 ) ( 1 v2 v2 v2 )
167+ * > ( v1 v2 1 ) ( 1 v3 v3 )
168+ * > ( v1 v2 v3 )
169+ * > ( v1 v2 v3 )
170+ * >
171+ * > DIRECT = 'B' and STOREV = 'C': DIRECT = 'B' and STOREV = 'R':
172+ * >
173+ * > V = ( v1 v2 v3 ) V = ( v1 v1 1 )
174+ * > ( v1 v2 v3 ) ( v2 v2 v2 1 )
175+ * > ( 1 v2 v3 ) ( v3 v3 v3 v3 1 )
176+ * > ( 1 v3 )
177+ * > ( 1 )
178+ * > \endverbatim
179+ * >
180+ * =====================================================================
1181 SUBROUTINE CLARFB0C2 (C2I , SIDE , TRANS , DIRECT , STOREV , M , N ,
2182 $ K , V , LDV , T , LDT , C , LDC )
3183 ! Scalar arguments
@@ -9,7 +189,7 @@ SUBROUTINE CLARFB0C2(C2I, SIDE, TRANS, DIRECT, STOREV, M, N,
9189 LOGICAL C2I
10190
11191 ! Array arguments
12- COMPLEX*8 V(LDV,*), C(LDC,*), T(LDT,*)
192+ COMPLEX V(LDV,*), C(LDC,*), T(LDT,*)
13193 ! Local scalars
14194 LOGICAL QR, LQ, QL, DIRF, COLV, SIDEL, SIDER,
15195 $ TRANST
@@ -22,7 +202,7 @@ SUBROUTINE CLARFB0C2(C2I, SIDE, TRANS, DIRECT, STOREV, M, N,
22202 ! External Subroutines
23203 EXTERNAL CGEMM, CTRMM
24204 ! Parameters
25- COMPLEX*8 ONE, ZERO, NEG_ONE
205+ COMPLEX ONE, ZERO, NEG_ONE
26206 PARAMETER(ONE=(1.0E+0, 0.0E+0),
27207 $ ZERO = (0.0E+0, 0.0E+0),
28208 $ NEG_ONE = (-1.0E+0, 0.0E+0))
0 commit comments