LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zerrrfp.f
Go to the documentation of this file.
1*> \brief \b ZERRRFP
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8* Definition:
9* ===========
10*
11* SUBROUTINE ZERRRFP( NUNIT )
12*
13* .. Scalar Arguments ..
14* INTEGER NUNIT
15* ..
16*
17*
18*> \par Purpose:
19* =============
20*>
21*> \verbatim
22*>
23*> ZERRRFP tests the error exits for the COMPLEX*16 driver routines
24*> for solving linear systems of equations.
25*>
26*> ZDRVRFP tests the COMPLEX*16 LAPACK RFP routines:
27*> ZTFSM, ZTFTRI, ZHFRK, ZTFTTP, ZTFTTR, ZPFTRF, ZPFTRS, ZTPTTF,
28*> ZTPTTR, ZTRTTF, and ZTRTTP
29*> \endverbatim
30*
31* Arguments:
32* ==========
33*
34*> \param[in] NUNIT
35*> \verbatim
36*> NUNIT is INTEGER
37*> The unit number for output.
38*> \endverbatim
39*
40* Authors:
41* ========
42*
43*> \author Univ. of Tennessee
44*> \author Univ. of California Berkeley
45*> \author Univ. of Colorado Denver
46*> \author NAG Ltd.
47*
48*> \ingroup complex16_lin
49*
50* =====================================================================
51 SUBROUTINE zerrrfp( NUNIT )
52*
53* -- LAPACK test routine --
54* -- LAPACK is a software package provided by Univ. of Tennessee, --
55* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
56*
57* .. Scalar Arguments ..
58 INTEGER NUNIT
59* ..
60*
61* =====================================================================
62*
63* ..
64* .. Local Scalars ..
65 INTEGER INFO
66 DOUBLE PRECISION ALPHA, BETA
67 COMPLEX*16 CALPHA
68* ..
69* .. Local Arrays ..
70 COMPLEX*16 A( 1, 1), B( 1, 1)
71* ..
72* .. External Subroutines ..
73 EXTERNAL chkxer, ztfsm, ztftri, zhfrk, ztfttp, ztfttr,
75 + ztrttp
76* ..
77* .. Scalars in Common ..
78 LOGICAL LERR, OK
79 CHARACTER*32 SRNAMT
80 INTEGER INFOT, NOUT
81* ..
82* .. Intrinsic Functions ..
83 INTRINSIC dcmplx
84* ..
85* .. Common blocks ..
86 COMMON / infoc / infot, nout, ok, lerr
87 COMMON / srnamc / srnamt
88* ..
89* .. Executable Statements ..
90*
91 nout = nunit
92 ok = .true.
93 a( 1, 1 ) = dcmplx( 1.0d0 , 1.0d0 )
94 b( 1, 1 ) = dcmplx( 1.0d0 , 1.0d0 )
95 alpha = 1.0d0
96 calpha = dcmplx( 1.0d0 , 1.0d0 )
97 beta = 1.0d0
98*
99 srnamt = 'ZPFTRF'
100 infot = 1
101 CALL zpftrf( '/', 'U', 0, a, info )
102 CALL chkxer( 'ZPFTRF', infot, nout, lerr, ok )
103 infot = 2
104 CALL zpftrf( 'N', '/', 0, a, info )
105 CALL chkxer( 'ZPFTRF', infot, nout, lerr, ok )
106 infot = 3
107 CALL zpftrf( 'N', 'U', -1, a, info )
108 CALL chkxer( 'ZPFTRF', infot, nout, lerr, ok )
109*
110 srnamt = 'ZPFTRS'
111 infot = 1
112 CALL zpftrs( '/', 'U', 0, 0, a, b, 1, info )
113 CALL chkxer( 'ZPFTRS', infot, nout, lerr, ok )
114 infot = 2
115 CALL zpftrs( 'N', '/', 0, 0, a, b, 1, info )
116 CALL chkxer( 'ZPFTRS', infot, nout, lerr, ok )
117 infot = 3
118 CALL zpftrs( 'N', 'U', -1, 0, a, b, 1, info )
119 CALL chkxer( 'ZPFTRS', infot, nout, lerr, ok )
120 infot = 4
121 CALL zpftrs( 'N', 'U', 0, -1, a, b, 1, info )
122 CALL chkxer( 'ZPFTRS', infot, nout, lerr, ok )
123 infot = 7
124 CALL zpftrs( 'N', 'U', 0, 0, a, b, 0, info )
125 CALL chkxer( 'ZPFTRS', infot, nout, lerr, ok )
126*
127 srnamt = 'ZPFTRI'
128 infot = 1
129 CALL zpftri( '/', 'U', 0, a, info )
130 CALL chkxer( 'ZPFTRI', infot, nout, lerr, ok )
131 infot = 2
132 CALL zpftri( 'N', '/', 0, a, info )
133 CALL chkxer( 'ZPFTRI', infot, nout, lerr, ok )
134 infot = 3
135 CALL zpftri( 'N', 'U', -1, a, info )
136 CALL chkxer( 'ZPFTRI', infot, nout, lerr, ok )
137*
138 srnamt = 'ZTFSM '
139 infot = 1
140 CALL ztfsm( '/', 'L', 'U', 'C', 'U', 0, 0, calpha, a, b, 1 )
141 CALL chkxer( 'ZTFSM ', infot, nout, lerr, ok )
142 infot = 2
143 CALL ztfsm( 'N', '/', 'U', 'C', 'U', 0, 0, calpha, a, b, 1 )
144 CALL chkxer( 'ZTFSM ', infot, nout, lerr, ok )
145 infot = 3
146 CALL ztfsm( 'N', 'L', '/', 'C', 'U', 0, 0, calpha, a, b, 1 )
147 CALL chkxer( 'ZTFSM ', infot, nout, lerr, ok )
148 infot = 4
149 CALL ztfsm( 'N', 'L', 'U', '/', 'U', 0, 0, calpha, a, b, 1 )
150 CALL chkxer( 'ZTFSM ', infot, nout, lerr, ok )
151 infot = 5
152 CALL ztfsm( 'N', 'L', 'U', 'C', '/', 0, 0, calpha, a, b, 1 )
153 CALL chkxer( 'ZTFSM ', infot, nout, lerr, ok )
154 infot = 6
155 CALL ztfsm( 'N', 'L', 'U', 'C', 'U', -1, 0, calpha, a, b, 1 )
156 CALL chkxer( 'ZTFSM ', infot, nout, lerr, ok )
157 infot = 7
158 CALL ztfsm( 'N', 'L', 'U', 'C', 'U', 0, -1, calpha, a, b, 1 )
159 CALL chkxer( 'ZTFSM ', infot, nout, lerr, ok )
160 infot = 11
161 CALL ztfsm( 'N', 'L', 'U', 'C', 'U', 0, 0, calpha, a, b, 0 )
162 CALL chkxer( 'ZTFSM ', infot, nout, lerr, ok )
163*
164 srnamt = 'ZTFTRI'
165 infot = 1
166 CALL ztftri( '/', 'L', 'N', 0, a, info )
167 CALL chkxer( 'ZTFTRI', infot, nout, lerr, ok )
168 infot = 2
169 CALL ztftri( 'N', '/', 'N', 0, a, info )
170 CALL chkxer( 'ZTFTRI', infot, nout, lerr, ok )
171 infot = 3
172 CALL ztftri( 'N', 'L', '/', 0, a, info )
173 CALL chkxer( 'ZTFTRI', infot, nout, lerr, ok )
174 infot = 4
175 CALL ztftri( 'N', 'L', 'N', -1, a, info )
176 CALL chkxer( 'ZTFTRI', infot, nout, lerr, ok )
177*
178 srnamt = 'ZTFTTR'
179 infot = 1
180 CALL ztfttr( '/', 'U', 0, a, b, 1, info )
181 CALL chkxer( 'ZTFTTR', infot, nout, lerr, ok )
182 infot = 2
183 CALL ztfttr( 'N', '/', 0, a, b, 1, info )
184 CALL chkxer( 'ZTFTTR', infot, nout, lerr, ok )
185 infot = 3
186 CALL ztfttr( 'N', 'U', -1, a, b, 1, info )
187 CALL chkxer( 'ZTFTTR', infot, nout, lerr, ok )
188 infot = 6
189 CALL ztfttr( 'N', 'U', 0, a, b, 0, info )
190 CALL chkxer( 'ZTFTTR', infot, nout, lerr, ok )
191*
192 srnamt = 'ZTRTTF'
193 infot = 1
194 CALL ztrttf( '/', 'U', 0, a, 1, b, info )
195 CALL chkxer( 'ZTRTTF', infot, nout, lerr, ok )
196 infot = 2
197 CALL ztrttf( 'N', '/', 0, a, 1, b, info )
198 CALL chkxer( 'ZTRTTF', infot, nout, lerr, ok )
199 infot = 3
200 CALL ztrttf( 'N', 'U', -1, a, 1, b, info )
201 CALL chkxer( 'ZTRTTF', infot, nout, lerr, ok )
202 infot = 5
203 CALL ztrttf( 'N', 'U', 0, a, 0, b, info )
204 CALL chkxer( 'ZTRTTF', infot, nout, lerr, ok )
205*
206 srnamt = 'ZTFTTP'
207 infot = 1
208 CALL ztfttp( '/', 'U', 0, a, b, info )
209 CALL chkxer( 'ZTFTTP', infot, nout, lerr, ok )
210 infot = 2
211 CALL ztfttp( 'N', '/', 0, a, b, info )
212 CALL chkxer( 'ZTFTTP', infot, nout, lerr, ok )
213 infot = 3
214 CALL ztfttp( 'N', 'U', -1, a, b, info )
215 CALL chkxer( 'ZTFTTP', infot, nout, lerr, ok )
216*
217 srnamt = 'ZTPTTF'
218 infot = 1
219 CALL ztpttf( '/', 'U', 0, a, b, info )
220 CALL chkxer( 'ZTPTTF', infot, nout, lerr, ok )
221 infot = 2
222 CALL ztpttf( 'N', '/', 0, a, b, info )
223 CALL chkxer( 'ZTPTTF', infot, nout, lerr, ok )
224 infot = 3
225 CALL ztpttf( 'N', 'U', -1, a, b, info )
226 CALL chkxer( 'ZTPTTF', infot, nout, lerr, ok )
227*
228 srnamt = 'ZTRTTP'
229 infot = 1
230 CALL ztrttp( '/', 0, a, 1, b, info )
231 CALL chkxer( 'ZTRTTP', infot, nout, lerr, ok )
232 infot = 2
233 CALL ztrttp( 'U', -1, a, 1, b, info )
234 CALL chkxer( 'ZTRTTP', infot, nout, lerr, ok )
235 infot = 4
236 CALL ztrttp( 'U', 0, a, 0, b, info )
237 CALL chkxer( 'ZTRTTP', infot, nout, lerr, ok )
238*
239 srnamt = 'ZTPTTR'
240 infot = 1
241 CALL ztpttr( '/', 0, a, b, 1, info )
242 CALL chkxer( 'ZTPTTR', infot, nout, lerr, ok )
243 infot = 2
244 CALL ztpttr( 'U', -1, a, b, 1, info )
245 CALL chkxer( 'ZTPTTR', infot, nout, lerr, ok )
246 infot = 5
247 CALL ztpttr( 'U', 0, a, b, 0, info )
248 CALL chkxer( 'ZTPTTR', infot, nout, lerr, ok )
249*
250 srnamt = 'ZHFRK '
251 infot = 1
252 CALL zhfrk( '/', 'U', 'N', 0, 0, alpha, a, 1, beta, b )
253 CALL chkxer( 'ZHFRK ', infot, nout, lerr, ok )
254 infot = 2
255 CALL zhfrk( 'N', '/', 'N', 0, 0, alpha, a, 1, beta, b )
256 CALL chkxer( 'ZHFRK ', infot, nout, lerr, ok )
257 infot = 3
258 CALL zhfrk( 'N', 'U', '/', 0, 0, alpha, a, 1, beta, b )
259 CALL chkxer( 'ZHFRK ', infot, nout, lerr, ok )
260 infot = 4
261 CALL zhfrk( 'N', 'U', 'N', -1, 0, alpha, a, 1, beta, b )
262 CALL chkxer( 'ZHFRK ', infot, nout, lerr, ok )
263 infot = 5
264 CALL zhfrk( 'N', 'U', 'N', 0, -1, alpha, a, 1, beta, b )
265 CALL chkxer( 'ZHFRK ', infot, nout, lerr, ok )
266 infot = 8
267 CALL zhfrk( 'N', 'U', 'N', 0, 0, alpha, a, 0, beta, b )
268 CALL chkxer( 'ZHFRK ', infot, nout, lerr, ok )
269*
270* Print a summary line.
271*
272 IF( ok ) THEN
273 WRITE( nout, fmt = 9999 )
274 ELSE
275 WRITE( nout, fmt = 9998 )
276 END IF
277*
278 9999 FORMAT( 1x, 'COMPLEX*16 RFP routines passed the tests of the ',
279 $ 'error exits' )
280 9998 FORMAT( ' *** RFP routines failed the tests of the error ',
281 $ 'exits ***' )
282 RETURN
283*
284* End of ZERRRFP
285*
286 END
subroutine chkxer(srnamt, infot, nout, lerr, ok)
Definition cblat2.f:3224
subroutine zhfrk(transr, uplo, trans, n, k, alpha, a, lda, beta, c)
ZHFRK performs a Hermitian rank-k operation for matrix in RFP format.
Definition zhfrk.f:168
subroutine zpftrf(transr, uplo, n, a, info)
ZPFTRF
Definition zpftrf.f:211
subroutine zpftri(transr, uplo, n, a, info)
ZPFTRI
Definition zpftri.f:212
subroutine zpftrs(transr, uplo, n, nrhs, a, b, ldb, info)
ZPFTRS
Definition zpftrs.f:220
subroutine ztfsm(transr, side, uplo, trans, diag, m, n, alpha, a, b, ldb)
ZTFSM solves a matrix equation (one operand is a triangular matrix in RFP format).
Definition ztfsm.f:298
subroutine ztftri(transr, uplo, diag, n, a, info)
ZTFTRI
Definition ztftri.f:221
subroutine ztfttp(transr, uplo, n, arf, ap, info)
ZTFTTP copies a triangular matrix from the rectangular full packed format (TF) to the standard packed...
Definition ztfttp.f:208
subroutine ztfttr(transr, uplo, n, arf, a, lda, info)
ZTFTTR copies a triangular matrix from the rectangular full packed format (TF) to the standard full f...
Definition ztfttr.f:216
subroutine ztpttf(transr, uplo, n, ap, arf, info)
ZTPTTF copies a triangular matrix from the standard packed format (TP) to the rectangular full packed...
Definition ztpttf.f:207
subroutine ztpttr(uplo, n, ap, a, lda, info)
ZTPTTR copies a triangular matrix from the standard packed format (TP) to the standard full format (T...
Definition ztpttr.f:104
subroutine ztrttf(transr, uplo, n, a, lda, arf, info)
ZTRTTF copies a triangular matrix from the standard full format (TR) to the rectangular full packed f...
Definition ztrttf.f:216
subroutine ztrttp(uplo, n, a, lda, ap, info)
ZTRTTP copies a triangular matrix from the standard full format (TR) to the standard packed format (T...
Definition ztrttp.f:104
subroutine zerrrfp(nunit)
ZERRRFP
Definition zerrrfp.f:52