LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ zerrlqtp()

subroutine zerrlqtp ( character*3  path,
integer  nunit 
)

ZERRLQTP

Purpose:
 ZERRLQTP tests the error exits for the complex routines
 that use the LQT decomposition of a triangular-pentagonal matrix.
Parameters
[in]PATH
          PATH is CHARACTER*3
          The LAPACK path name for the routines to be tested.
[in]NUNIT
          NUNIT is INTEGER
          The unit number for output.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 54 of file zerrlqtp.f.

55 IMPLICIT NONE
56*
57* -- LAPACK test routine --
58* -- LAPACK is a software package provided by Univ. of Tennessee, --
59* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
60*
61* .. Scalar Arguments ..
62 CHARACTER*3 PATH
63 INTEGER NUNIT
64* ..
65*
66* =====================================================================
67*
68* .. Parameters ..
69 INTEGER NMAX
70 parameter( nmax = 2 )
71* ..
72* .. Local Scalars ..
73 INTEGER I, INFO, J
74* ..
75* .. Local Arrays ..
76 COMPLEX*16 A( NMAX, NMAX ), T( NMAX, NMAX ), W( NMAX ),
77 $ B( NMAX, NMAX ), C( NMAX, NMAX )
78* ..
79* .. External Subroutines ..
80 EXTERNAL alaesm, chkxer, ztplqt2, ztplqt,
81 $ ztpmlqt
82* ..
83* .. Scalars in Common ..
84 LOGICAL LERR, OK
85 CHARACTER*32 SRNAMT
86 INTEGER INFOT, NOUT
87* ..
88* .. Common blocks ..
89 COMMON / infoc / infot, nout, ok, lerr
90 COMMON / srnamc / srnamt
91* ..
92* .. Intrinsic Functions ..
93 INTRINSIC dble, dcmplx
94* ..
95* .. Executable Statements ..
96*
97 nout = nunit
98 WRITE( nout, fmt = * )
99*
100* Set the variables to innocuous values.
101*
102 DO j = 1, nmax
103 DO i = 1, nmax
104 a( i, j ) = 1.d0 / dcmplx( dble( i+j ), 0.d0 )
105 c( i, j ) = 1.d0 / dcmplx( dble( i+j ), 0.d0 )
106 t( i, j ) = 1.d0 / dcmplx( dble( i+j ), 0.d0 )
107 END DO
108 w( j ) = 0.0
109 END DO
110 ok = .true.
111*
112* Error exits for TPLQT factorization
113*
114* ZTPLQT
115*
116 srnamt = 'ZTPLQT'
117 infot = 1
118 CALL ztplqt( -1, 1, 0, 1, a, 1, b, 1, t, 1, w, info )
119 CALL chkxer( 'ZTPLQT', infot, nout, lerr, ok )
120 infot = 2
121 CALL ztplqt( 1, -1, 0, 1, a, 1, b, 1, t, 1, w, info )
122 CALL chkxer( 'ZTPLQT', infot, nout, lerr, ok )
123 infot = 3
124 CALL ztplqt( 0, 1, -1, 1, a, 1, b, 1, t, 1, w, info )
125 CALL chkxer( 'ZTPLQT', infot, nout, lerr, ok )
126 infot = 3
127 CALL ztplqt( 0, 1, 1, 1, a, 1, b, 1, t, 1, w, info )
128 CALL chkxer( 'ZTPLQT', infot, nout, lerr, ok )
129 infot = 4
130 CALL ztplqt( 0, 1, 0, 0, a, 1, b, 1, t, 1, w, info )
131 CALL chkxer( 'ZTPLQT', infot, nout, lerr, ok )
132 infot = 4
133 CALL ztplqt( 1, 1, 0, 2, a, 1, b, 1, t, 1, w, info )
134 CALL chkxer( 'ZTPLQT', infot, nout, lerr, ok )
135 infot = 6
136 CALL ztplqt( 2, 1, 0, 2, a, 1, b, 1, t, 1, w, info )
137 CALL chkxer( 'ZTPLQT', infot, nout, lerr, ok )
138 infot = 8
139 CALL ztplqt( 2, 1, 0, 1, a, 2, b, 1, t, 1, w, info )
140 CALL chkxer( 'ZTPLQT', infot, nout, lerr, ok )
141 infot = 10
142 CALL ztplqt( 2, 2, 1, 2, a, 2, b, 2, t, 1, w, info )
143 CALL chkxer( 'ZTPLQT', infot, nout, lerr, ok )
144*
145* ZTPLQT2
146*
147 srnamt = 'ZTPLQT2'
148 infot = 1
149 CALL ztplqt2( -1, 0, 0, a, 1, b, 1, t, 1, info )
150 CALL chkxer( 'ZTPLQT2', infot, nout, lerr, ok )
151 infot = 2
152 CALL ztplqt2( 0, -1, 0, a, 1, b, 1, t, 1, info )
153 CALL chkxer( 'ZTPLQT2', infot, nout, lerr, ok )
154 infot = 3
155 CALL ztplqt2( 0, 0, -1, a, 1, b, 1, t, 1, info )
156 CALL chkxer( 'ZTPLQT2', infot, nout, lerr, ok )
157 infot = 5
158 CALL ztplqt2( 2, 2, 0, a, 1, b, 2, t, 2, info )
159 CALL chkxer( 'ZTPLQT2', infot, nout, lerr, ok )
160 infot = 7
161 CALL ztplqt2( 2, 2, 0, a, 2, b, 1, t, 2, info )
162 CALL chkxer( 'ZTPLQT2', infot, nout, lerr, ok )
163 infot = 9
164 CALL ztplqt2( 2, 2, 0, a, 2, b, 2, t, 1, info )
165 CALL chkxer( 'ZTPLQT2', infot, nout, lerr, ok )
166*
167* ZTPMLQT
168*
169 srnamt = 'ZTPMLQT'
170 infot = 1
171 CALL ztpmlqt( '/', 'N', 0, 0, 0, 0, 1, a, 1, t, 1, b, 1, c, 1,
172 $ w, info )
173 CALL chkxer( 'ZTPMLQT', infot, nout, lerr, ok )
174 infot = 2
175 CALL ztpmlqt( 'L', '/', 0, 0, 0, 0, 1, a, 1, t, 1, b, 1, c, 1,
176 $ w, info )
177 CALL chkxer( 'ZTPMLQT', infot, nout, lerr, ok )
178 infot = 3
179 CALL ztpmlqt( 'L', 'N', -1, 0, 0, 0, 1, a, 1, t, 1, b, 1, c, 1,
180 $ w, info )
181 CALL chkxer( 'ZTPMLQT', infot, nout, lerr, ok )
182 infot = 4
183 CALL ztpmlqt( 'L', 'N', 0, -1, 0, 0, 1, a, 1, t, 1, b, 1, c, 1,
184 $ w, info )
185 CALL chkxer( 'ZTPMLQT', infot, nout, lerr, ok )
186 infot = 5
187 CALL ztpmlqt( 'L', 'N', 0, 0, -1, 0, 1, a, 1, t, 1, b, 1, c, 1,
188 $ w, info )
189 infot = 6
190 CALL ztpmlqt( 'L', 'N', 0, 0, 0, -1, 1, a, 1, t, 1, b, 1, c, 1,
191 $ w, info )
192 CALL chkxer( 'ZTPMLQT', infot, nout, lerr, ok )
193 infot = 7
194 CALL ztpmlqt( 'L', 'N', 0, 0, 0, 0, 0, a, 1, t, 1, b, 1, c, 1,
195 $ w, info )
196 CALL chkxer( 'ZTPMLQT', infot, nout, lerr, ok )
197 infot = 9
198 CALL ztpmlqt( 'R', 'N', 2, 2, 2, 1, 1, a, 1, t, 1, b, 1, c, 1,
199 $ w, info )
200 CALL chkxer( 'ZTPMLQT', infot, nout, lerr, ok )
201 infot = 11
202 CALL ztpmlqt( 'R', 'N', 1, 1, 1, 1, 1, a, 1, t, 0, b, 1, c, 1,
203 $ w, info )
204 CALL chkxer( 'ZTPMLQT', infot, nout, lerr, ok )
205 infot = 13
206 CALL ztpmlqt( 'L', 'N', 1, 1, 1, 1, 1, a, 1, t, 1, b, 0, c, 1,
207 $ w, info )
208 CALL chkxer( 'ZTPMLQT', infot, nout, lerr, ok )
209 infot = 15
210 CALL ztpmlqt( 'L', 'N', 1, 1, 1, 1, 1, a, 1, t, 1, b, 1, c, 0,
211 $ w, info )
212 CALL chkxer( 'ZTPMLQT', infot, nout, lerr, ok )
213*
214* Print a summary line.
215*
216 CALL alaesm( path, ok, nout )
217*
218 RETURN
219*
220* End of ZERRLQTP
221*
subroutine alaesm(path, ok, nout)
ALAESM
Definition alaesm.f:63
subroutine chkxer(srnamt, infot, nout, lerr, ok)
Definition cblat2.f:3224
subroutine ztplqt2(m, n, l, a, lda, b, ldb, t, ldt, info)
ZTPLQT2 computes a LQ factorization of a real or complex "triangular-pentagonal" matrix,...
Definition ztplqt2.f:177
subroutine ztplqt(m, n, l, mb, a, lda, b, ldb, t, ldt, work, info)
ZTPLQT
Definition ztplqt.f:189
subroutine ztpmlqt(side, trans, m, n, k, l, mb, v, ldv, t, ldt, a, lda, b, ldb, work, info)
ZTPMLQT
Definition ztpmlqt.f:214
Here is the call graph for this function:
Here is the caller graph for this function: