57 SUBROUTINE cerrec( PATH, NUNIT )
73 parameter ( nmax = 4, lw = nmax*( nmax+2 ) )
75 parameter ( one = 1.0e0, zero = 0.0e0 )
78 INTEGER I, IFST, ILST, INFO, J, M, NT
83 REAL RW( lw ), S( nmax ), SEP( nmax )
84 COMPLEX A( nmax, nmax ), B( nmax, nmax ),
85 $ c( nmax, nmax ), work( lw ), x( nmax )
96 COMMON / infoc / infot, nout, ok, lerr
97 COMMON / srnamc / srnamt
122 CALL ctrsyl(
'X',
'N', 1, 0, 0, a, 1, b, 1, c, 1, scale, info )
123 CALL chkxer(
'CTRSYL', infot, nout, lerr, ok )
125 CALL ctrsyl(
'N',
'X', 1, 0, 0, a, 1, b, 1, c, 1, scale, info )
126 CALL chkxer(
'CTRSYL', infot, nout, lerr, ok )
128 CALL ctrsyl(
'N',
'N', 0, 0, 0, a, 1, b, 1, c, 1, scale, info )
129 CALL chkxer(
'CTRSYL', infot, nout, lerr, ok )
131 CALL ctrsyl(
'N',
'N', 1, -1, 0, a, 1, b, 1, c, 1, scale, info )
132 CALL chkxer(
'CTRSYL', infot, nout, lerr, ok )
134 CALL ctrsyl(
'N',
'N', 1, 0, -1, a, 1, b, 1, c, 1, scale, info )
135 CALL chkxer(
'CTRSYL', infot, nout, lerr, ok )
137 CALL ctrsyl(
'N',
'N', 1, 2, 0, a, 1, b, 1, c, 2, scale, info )
138 CALL chkxer(
'CTRSYL', infot, nout, lerr, ok )
140 CALL ctrsyl(
'N',
'N', 1, 0, 2, a, 1, b, 1, c, 1, scale, info )
141 CALL chkxer(
'CTRSYL', infot, nout, lerr, ok )
143 CALL ctrsyl(
'N',
'N', 1, 2, 0, a, 2, b, 1, c, 1, scale, info )
144 CALL chkxer(
'CTRSYL', infot, nout, lerr, ok )
153 CALL ctrexc(
'X', 1, a, 1, b, 1, ifst, ilst, info )
154 CALL chkxer(
'CTREXC', infot, nout, lerr, ok )
156 CALL ctrexc(
'N', 0, a, 1, b, 1, ifst, ilst, info )
157 CALL chkxer(
'CTREXC', infot, nout, lerr, ok )
160 CALL ctrexc(
'N', 2, a, 1, b, 1, ifst, ilst, info )
161 CALL chkxer(
'CTREXC', infot, nout, lerr, ok )
163 CALL ctrexc(
'V', 2, a, 2, b, 1, ifst, ilst, info )
164 CALL chkxer(
'CTREXC', infot, nout, lerr, ok )
168 CALL ctrexc(
'V', 1, a, 1, b, 1, ifst, ilst, info )
169 CALL chkxer(
'CTREXC', infot, nout, lerr, ok )
172 CALL ctrexc(
'V', 1, a, 1, b, 1, ifst, ilst, info )
173 CALL chkxer(
'CTREXC', infot, nout, lerr, ok )
177 CALL ctrexc(
'V', 1, a, 1, b, 1, ifst, ilst, info )
178 CALL chkxer(
'CTREXC', infot, nout, lerr, ok )
181 CALL ctrexc(
'V', 1, a, 1, b, 1, ifst, ilst, info )
182 CALL chkxer(
'CTREXC', infot, nout, lerr, ok )
189 CALL ctrsna(
'X',
'A', sel, 0, a, 1, b, 1, c, 1, s, sep, 1, m,
190 $ work, 1, rw, info )
191 CALL chkxer(
'CTRSNA', infot, nout, lerr, ok )
193 CALL ctrsna(
'B',
'X', sel, 0, a, 1, b, 1, c, 1, s, sep, 1, m,
194 $ work, 1, rw, info )
195 CALL chkxer(
'CTRSNA', infot, nout, lerr, ok )
197 CALL ctrsna(
'B',
'A', sel, -1, a, 1, b, 1, c, 1, s, sep, 1, m,
198 $ work, 1, rw, info )
199 CALL chkxer(
'CTRSNA', infot, nout, lerr, ok )
201 CALL ctrsna(
'V',
'A', sel, 2, a, 1, b, 1, c, 1, s, sep, 2, m,
202 $ work, 2, rw, info )
203 CALL chkxer(
'CTRSNA', infot, nout, lerr, ok )
205 CALL ctrsna(
'B',
'A', sel, 2, a, 2, b, 1, c, 2, s, sep, 2, m,
206 $ work, 2, rw, info )
207 CALL chkxer(
'CTRSNA', infot, nout, lerr, ok )
209 CALL ctrsna(
'B',
'A', sel, 2, a, 2, b, 2, c, 1, s, sep, 2, m,
210 $ work, 2, rw, info )
211 CALL chkxer(
'CTRSNA', infot, nout, lerr, ok )
213 CALL ctrsna(
'B',
'A', sel, 1, a, 1, b, 1, c, 1, s, sep, 0, m,
214 $ work, 1, rw, info )
215 CALL chkxer(
'CTRSNA', infot, nout, lerr, ok )
217 CALL ctrsna(
'B',
'S', sel, 2, a, 2, b, 2, c, 2, s, sep, 1, m,
218 $ work, 1, rw, info )
219 CALL chkxer(
'CTRSNA', infot, nout, lerr, ok )
221 CALL ctrsna(
'B',
'A', sel, 2, a, 2, b, 2, c, 2, s, sep, 2, m,
222 $ work, 1, rw, info )
223 CALL chkxer(
'CTRSNA', infot, nout, lerr, ok )
231 CALL ctrsen(
'X',
'N', sel, 0, a, 1, b, 1, x, m, s( 1 ), sep( 1 ),
233 CALL chkxer(
'CTRSEN', infot, nout, lerr, ok )
235 CALL ctrsen(
'N',
'X', sel, 0, a, 1, b, 1, x, m, s( 1 ), sep( 1 ),
237 CALL chkxer(
'CTRSEN', infot, nout, lerr, ok )
239 CALL ctrsen(
'N',
'N', sel, -1, a, 1, b, 1, x, m, s( 1 ),
240 $ sep( 1 ), work, 1, info )
241 CALL chkxer(
'CTRSEN', infot, nout, lerr, ok )
243 CALL ctrsen(
'N',
'N', sel, 2, a, 1, b, 1, x, m, s( 1 ), sep( 1 ),
245 CALL chkxer(
'CTRSEN', infot, nout, lerr, ok )
247 CALL ctrsen(
'N',
'V', sel, 2, a, 2, b, 1, x, m, s( 1 ), sep( 1 ),
249 CALL chkxer(
'CTRSEN', infot, nout, lerr, ok )
251 CALL ctrsen(
'N',
'V', sel, 2, a, 2, b, 2, x, m, s( 1 ), sep( 1 ),
253 CALL chkxer(
'CTRSEN', infot, nout, lerr, ok )
255 CALL ctrsen(
'E',
'V', sel, 3, a, 3, b, 3, x, m, s( 1 ), sep( 1 ),
257 CALL chkxer(
'CTRSEN', infot, nout, lerr, ok )
259 CALL ctrsen(
'V',
'V', sel, 3, a, 3, b, 3, x, m, s( 1 ), sep( 1 ),
261 CALL chkxer(
'CTRSEN', infot, nout, lerr, ok )
267 WRITE( nout, fmt = 9999 )path, nt
269 WRITE( nout, fmt = 9998 )path
272 9999
FORMAT( 1x, a3,
' routines passed the tests of the error exits (',
273 $ i3,
' tests done)' )
274 9998
FORMAT(
' *** ', a3,
' routines failed the tests of the error ',
subroutine cerrec(PATH, NUNIT)
CERREC
subroutine ctrsna(JOB, HOWMNY, SELECT, N, T, LDT, VL, LDVL, VR, LDVR, S, SEP, MM, M, WORK, LDWORK, RWORK, INFO)
CTRSNA
subroutine ctrsyl(TRANA, TRANB, ISGN, M, N, A, LDA, B, LDB, C, LDC, SCALE, INFO)
CTRSYL
subroutine chkxer(SRNAMT, INFOT, NOUT, LERR, OK)
subroutine ctrsen(JOB, COMPQ, SELECT, N, T, LDT, Q, LDQ, W, M, S, SEP, WORK, LWORK, INFO)
CTRSEN
subroutine ctrexc(COMPQ, N, T, LDT, Q, LDQ, IFST, ILST, INFO)
CTREXC