LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine zerrqrtp ( character*3  PATH,
integer  NUNIT 
)

ZERRQRTP

Purpose:
 ZERRQRTP tests the error exits for the COMPLEX*16 routines
 that use the QRT 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.
Date
November 2011

Definition at line 57 of file zerrqrtp.f.

57  IMPLICIT NONE
58 *
59 * -- LAPACK test routine (version 3.4.0) --
60 * -- LAPACK is a software package provided by Univ. of Tennessee, --
61 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
62 * November 2011
63 *
64 * .. Scalar Arguments ..
65  CHARACTER*3 path
66  INTEGER nunit
67 * ..
68 *
69 * =====================================================================
70 *
71 * .. Parameters ..
72  INTEGER nmax
73  parameter ( nmax = 2 )
74 * ..
75 * .. Local Scalars ..
76  INTEGER i, info, j
77 * ..
78 * .. Local Arrays ..
79  COMPLEX*16 a( nmax, nmax ), t( nmax, nmax ), w( nmax ),
80  $ b( nmax, nmax ), c( nmax, nmax )
81 * ..
82 * .. External Subroutines ..
83  EXTERNAL alaesm, chkxer, ztpqrt2, ztpqrt,
84  $ ztpmqrt
85 * ..
86 * .. Scalars in Common ..
87  LOGICAL lerr, ok
88  CHARACTER*32 srnamt
89  INTEGER infot, nout
90 * ..
91 * .. Common blocks ..
92  COMMON / infoc / infot, nout, ok, lerr
93  COMMON / srnamc / srnamt
94 * ..
95 * .. Intrinsic Functions ..
96  INTRINSIC dble, dcmplx
97 * ..
98 * .. Executable Statements ..
99 *
100  nout = nunit
101  WRITE( nout, fmt = * )
102 *
103 * Set the variables to innocuous values.
104 *
105  DO j = 1, nmax
106  DO i = 1, nmax
107  a( i, j ) = 1.d0 / dcmplx(dble( i+j ),0.d0)
108  c( i, j ) = 1.d0 / dcmplx(dble( i+j ),0.d0)
109  t( i, j ) = 1.d0 / dcmplx(dble( i+j ),0.d0)
110  END DO
111  w( j ) = dcmplx(0.d0,0.d0)
112  END DO
113  ok = .true.
114 *
115 * Error exits for TPQRT factorization
116 *
117 * ZTPQRT
118 *
119  srnamt = 'ZTPQRT'
120  infot = 1
121  CALL ztpqrt( -1, 1, 0, 1, a, 1, b, 1, t, 1, w, info )
122  CALL chkxer( 'ZTPQRT', infot, nout, lerr, ok )
123  infot = 2
124  CALL ztpqrt( 1, -1, 0, 1, a, 1, b, 1, t, 1, w, info )
125  CALL chkxer( 'ZTPQRT', infot, nout, lerr, ok )
126  infot = 3
127  CALL ztpqrt( 0, 1, -1, 1, a, 1, b, 1, t, 1, w, info )
128  CALL chkxer( 'ZTPQRT', infot, nout, lerr, ok )
129  infot = 3
130  CALL ztpqrt( 0, 1, 1, 1, a, 1, b, 1, t, 1, w, info )
131  CALL chkxer( 'ZTPQRT', infot, nout, lerr, ok )
132  infot = 4
133  CALL ztpqrt( 0, 1, 0, 0, a, 1, b, 1, t, 1, w, info )
134  CALL chkxer( 'ZTPQRT', infot, nout, lerr, ok )
135  infot = 4
136  CALL ztpqrt( 0, 1, 0, 2, a, 1, b, 1, t, 1, w, info )
137  CALL chkxer( 'ZTPQRT', infot, nout, lerr, ok )
138  infot = 6
139  CALL ztpqrt( 1, 2, 0, 2, a, 1, b, 1, t, 1, w, info )
140  CALL chkxer( 'ZTPQRT', infot, nout, lerr, ok )
141  infot = 8
142  CALL ztpqrt( 2, 1, 0, 1, a, 1, b, 1, t, 1, w, info )
143  CALL chkxer( 'ZTPQRT', infot, nout, lerr, ok )
144  infot = 10
145  CALL ztpqrt( 2, 2, 1, 2, a, 2, b, 2, t, 1, w, info )
146  CALL chkxer( 'ZTPQRT', infot, nout, lerr, ok )
147 *
148 * ZTPQRT2
149 *
150  srnamt = 'ZTPQRT2'
151  infot = 1
152  CALL ztpqrt2( -1, 0, 0, a, 1, b, 1, t, 1, info )
153  CALL chkxer( 'ZTPQRT2', infot, nout, lerr, ok )
154  infot = 2
155  CALL ztpqrt2( 0, -1, 0, a, 1, b, 1, t, 1, info )
156  CALL chkxer( 'ZTPQRT2', infot, nout, lerr, ok )
157  infot = 3
158  CALL ztpqrt2( 0, 0, -1, a, 1, b, 1, t, 1, info )
159  CALL chkxer( 'ZTPQRT2', infot, nout, lerr, ok )
160  infot = 5
161  CALL ztpqrt2( 2, 2, 0, a, 1, b, 2, t, 2, info )
162  CALL chkxer( 'ZTPQRT2', infot, nout, lerr, ok )
163  infot = 7
164  CALL ztpqrt2( 2, 2, 0, a, 2, b, 1, t, 2, info )
165  CALL chkxer( 'ZTPQRT2', infot, nout, lerr, ok )
166  infot = 9
167  CALL ztpqrt2( 2, 2, 0, a, 2, b, 2, t, 1, info )
168  CALL chkxer( 'ZTPQRT2', infot, nout, lerr, ok )
169 *
170 * ZTPMQRT
171 *
172  srnamt = 'ZTPMQRT'
173  infot = 1
174  CALL ztpmqrt( '/', 'N', 0, 0, 0, 0, 1, a, 1, t, 1, b, 1, c, 1,
175  $ w, info )
176  CALL chkxer( 'ZTPMQRT', infot, nout, lerr, ok )
177  infot = 2
178  CALL ztpmqrt( 'L', '/', 0, 0, 0, 0, 1, a, 1, t, 1, b, 1, c, 1,
179  $ w, info )
180  CALL chkxer( 'ZTPMQRT', infot, nout, lerr, ok )
181  infot = 3
182  CALL ztpmqrt( 'L', 'N', -1, 0, 0, 0, 1, a, 1, t, 1, b, 1, c, 1,
183  $ w, info )
184  CALL chkxer( 'ZTPMQRT', infot, nout, lerr, ok )
185  infot = 4
186  CALL ztpmqrt( 'L', 'N', 0, -1, 0, 0, 1, a, 1, t, 1, b, 1, c, 1,
187  $ w, info )
188  CALL chkxer( 'ZTPMQRT', infot, nout, lerr, ok )
189  infot = 5
190  CALL ztpmqrt( 'L', 'N', 0, 0, -1, 0, 1, a, 1, t, 1, b, 1, c, 1,
191  $ w, info )
192  infot = 6
193  CALL ztpmqrt( 'L', 'N', 0, 0, 0, -1, 1, a, 1, t, 1, b, 1, c, 1,
194  $ w, info )
195  CALL chkxer( 'ZTPMQRT', infot, nout, lerr, ok )
196  infot = 7
197  CALL ztpmqrt( 'L', 'N', 0, 0, 0, 0, 0, a, 1, t, 1, b, 1, c, 1,
198  $ w, info )
199  CALL chkxer( 'ZTPMQRT', infot, nout, lerr, ok )
200  infot = 9
201  CALL ztpmqrt( 'R', 'N', 1, 2, 1, 1, 1, a, 1, t, 1, b, 1, c, 1,
202  $ w, info )
203  CALL chkxer( 'ZTPMQRT', infot, nout, lerr, ok )
204  infot = 9
205  CALL ztpmqrt( 'L', 'N', 2, 1, 1, 1, 1, a, 1, t, 1, b, 1, c, 1,
206  $ w, info )
207  CALL chkxer( 'ZTPMQRT', infot, nout, lerr, ok )
208  infot = 11
209  CALL ztpmqrt( 'R', 'N', 1, 1, 1, 1, 1, a, 1, t, 0, b, 1, c, 1,
210  $ w, info )
211  CALL chkxer( 'ZTPMQRT', infot, nout, lerr, ok )
212  infot = 13
213  CALL ztpmqrt( 'L', 'N', 1, 1, 1, 1, 1, a, 1, t, 1, b, 0, c, 1,
214  $ w, info )
215  CALL chkxer( 'ZTPMQRT', infot, nout, lerr, ok )
216  infot = 15
217  CALL ztpmqrt( 'L', 'N', 1, 1, 1, 1, 1, a, 1, t, 1, b, 1, c, 0,
218  $ w, info )
219  CALL chkxer( 'ZTPMQRT', infot, nout, lerr, ok )
220 *
221 * Print a summary line.
222 *
223  CALL alaesm( path, ok, nout )
224 *
225  RETURN
226 *
227 * End of ZERRQRT
228 *
subroutine ztpqrt(M, N, L, NB, A, LDA, B, LDB, T, LDT, WORK, INFO)
ZTPQRT
Definition: ztpqrt.f:191
subroutine alaesm(PATH, OK, NOUT)
ALAESM
Definition: alaesm.f:65
subroutine ztpmqrt(SIDE, TRANS, M, N, K, L, NB, V, LDV, T, LDT, A, LDA, B, LDB, WORK, INFO)
ZTPMQRT
Definition: ztpmqrt.f:218
subroutine ztpqrt2(M, N, L, A, LDA, B, LDB, T, LDT, INFO)
ZTPQRT2 computes a QR factorization of a real or complex "triangular-pentagonal" matrix, which is composed of a triangular block and a pentagonal block, using the compact WY representation for Q.
Definition: ztpqrt2.f:175
subroutine chkxer(SRNAMT, INFOT, NOUT, LERR, OK)
Definition: cblat2.f:3199

Here is the call graph for this function:

Here is the caller graph for this function: