LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
cerrtz.f
Go to the documentation of this file.
1*> \brief \b CERRTZ
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 CERRTZ( PATH, NUNIT )
12*
13* .. Scalar Arguments ..
14* CHARACTER*3 PATH
15* INTEGER NUNIT
16* ..
17*
18*
19*> \par Purpose:
20* =============
21*>
22*> \verbatim
23*>
24*> CERRTZ tests the error exits for CTZRZF.
25*> \endverbatim
26*
27* Arguments:
28* ==========
29*
30*> \param[in] PATH
31*> \verbatim
32*> PATH is CHARACTER*3
33*> The LAPACK path name for the routines to be tested.
34*> \endverbatim
35*>
36*> \param[in] NUNIT
37*> \verbatim
38*> NUNIT is INTEGER
39*> The unit number for output.
40*> \endverbatim
41*
42* Authors:
43* ========
44*
45*> \author Univ. of Tennessee
46*> \author Univ. of California Berkeley
47*> \author Univ. of Colorado Denver
48*> \author NAG Ltd.
49*
50*> \ingroup complex_lin
51*
52* =====================================================================
53 SUBROUTINE cerrtz( PATH, NUNIT )
54*
55* -- LAPACK test routine --
56* -- LAPACK is a software package provided by Univ. of Tennessee, --
57* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
58*
59* .. Scalar Arguments ..
60 CHARACTER*3 PATH
61 INTEGER NUNIT
62* ..
63*
64* =====================================================================
65*
66* .. Parameters ..
67 INTEGER NMAX
68 parameter( nmax = 2 )
69* ..
70* .. Local Scalars ..
71 CHARACTER*2 C2
72 INTEGER INFO
73* ..
74* .. Local Arrays ..
75 COMPLEX A( NMAX, NMAX ), TAU( NMAX ), W( NMAX )
76* ..
77* .. External Functions ..
78 LOGICAL LSAMEN
79 EXTERNAL lsamen
80* ..
81* .. External Subroutines ..
82 EXTERNAL alaesm, chkxer, ctzrzf
83* ..
84* .. Scalars in Common ..
85 LOGICAL LERR, OK
86 CHARACTER*32 SRNAMT
87 INTEGER INFOT, NOUT
88* ..
89* .. Common blocks ..
90 COMMON / infoc / infot, nout, ok, lerr
91 COMMON / srnamc / srnamt
92* ..
93* .. Intrinsic Functions ..
94 INTRINSIC cmplx
95* ..
96* .. Executable Statements ..
97*
98 nout = nunit
99 c2 = path( 2: 3 )
100 a( 1, 1 ) = cmplx( 1.e+0, -1.e+0 )
101 a( 1, 2 ) = cmplx( 2.e+0, -2.e+0 )
102 a( 2, 2 ) = cmplx( 3.e+0, -3.e+0 )
103 a( 2, 1 ) = cmplx( 4.e+0, -4.e+0 )
104 w( 1 ) = cmplx( 0.e+0, 0.e+0 )
105 w( 2 ) = cmplx( 0.e+0, 0.e+0 )
106 ok = .true.
107*
108* Test error exits for the trapezoidal routines.
109*
110 WRITE( nout, fmt = * )
111 IF( lsamen( 2, c2, 'TZ' ) ) THEN
112*
113* CTZRZF
114*
115 srnamt = 'CTZRZF'
116 infot = 1
117 CALL ctzrzf( -1, 0, a, 1, tau, w, 1, info )
118 CALL chkxer( 'CTZRZF', infot, nout, lerr, ok )
119 infot = 2
120 CALL ctzrzf( 1, 0, a, 1, tau, w, 1, info )
121 CALL chkxer( 'CTZRZF', infot, nout, lerr, ok )
122 infot = 4
123 CALL ctzrzf( 2, 2, a, 1, tau, w, 1, info )
124 CALL chkxer( 'CTZRZF', infot, nout, lerr, ok )
125 infot = 7
126 CALL ctzrzf( 2, 2, a, 2, tau, w, 0, info )
127 CALL chkxer( 'CTZRZF', infot, nout, lerr, ok )
128 infot = 7
129 CALL ctzrzf( 2, 3, a, 2, tau, w, 1, info )
130 CALL chkxer( 'CTZRZF', infot, nout, lerr, ok )
131 END IF
132*
133* Print a summary line.
134*
135 CALL alaesm( path, ok, nout )
136*
137 RETURN
138*
139* End of CERRTZ
140*
141 END
subroutine alaesm(path, ok, nout)
ALAESM
Definition alaesm.f:63
subroutine chkxer(srnamt, infot, nout, lerr, ok)
Definition cblat2.f:3224
subroutine cerrtz(path, nunit)
CERRTZ
Definition cerrtz.f:54
subroutine ctzrzf(m, n, a, lda, tau, work, lwork, info)
CTZRZF
Definition ctzrzf.f:151