LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
cerrqrtp.f
Go to the documentation of this file.
1 *> \brief \b CERRQRTP
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 CERRQRTP( 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 *> CERRQRTP tests the error exits for the REAL routines
25 *> that use the QRT decomposition of a triangular-pentagonal matrix.
26 *> \endverbatim
27 *
28 * Arguments:
29 * ==========
30 *
31 *> \param[in] PATH
32 *> \verbatim
33 *> PATH is CHARACTER*3
34 *> The LAPACK path name for the routines to be tested.
35 *> \endverbatim
36 *>
37 *> \param[in] NUNIT
38 *> \verbatim
39 *> NUNIT is INTEGER
40 *> The unit number for output.
41 *> \endverbatim
42 *
43 * Authors:
44 * ========
45 *
46 *> \author Univ. of Tennessee
47 *> \author Univ. of California Berkeley
48 *> \author Univ. of Colorado Denver
49 *> \author NAG Ltd.
50 *
51 *> \date November 2011
52 *
53 *> \ingroup complex_lin
54 *
55 * =====================================================================
56  SUBROUTINE cerrqrtp( PATH, NUNIT )
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 a( nmax, nmax ), t( nmax, nmax ), w( nmax ),
80  $ b( nmax, nmax ), c( nmax, nmax )
81 * ..
82 * .. External Subroutines ..
83  EXTERNAL alaesm, chkxer, ctpqrt2, ctpqrt,
84  $ ctpmqrt
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 float, cmplx
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.0 / cmplx(float( i+j ),0.0)
108  c( i, j ) = 1.0 / cmplx(float( i+j ),0.0)
109  t( i, j ) = 1.0 / cmplx(float( i+j ),0.0)
110  END DO
111  w( j ) = cmplx(0.0,0.0)
112  END DO
113  ok = .true.
114 *
115 * Error exits for TPQRT factorization
116 *
117 * CTPQRT
118 *
119  srnamt = 'CTPQRT'
120  infot = 1
121  CALL ctpqrt( -1, 1, 0, 1, a, 1, b, 1, t, 1, w, info )
122  CALL chkxer( 'CTPQRT', infot, nout, lerr, ok )
123  infot = 2
124  CALL ctpqrt( 1, -1, 0, 1, a, 1, b, 1, t, 1, w, info )
125  CALL chkxer( 'CTPQRT', infot, nout, lerr, ok )
126  infot = 3
127  CALL ctpqrt( 0, 1, -1, 1, a, 1, b, 1, t, 1, w, info )
128  CALL chkxer( 'CTPQRT', infot, nout, lerr, ok )
129  infot = 3
130  CALL ctpqrt( 0, 1, 1, 1, a, 1, b, 1, t, 1, w, info )
131  CALL chkxer( 'CTPQRT', infot, nout, lerr, ok )
132  infot = 4
133  CALL ctpqrt( 0, 1, 0, 0, a, 1, b, 1, t, 1, w, info )
134  CALL chkxer( 'CTPQRT', infot, nout, lerr, ok )
135  infot = 4
136  CALL ctpqrt( 0, 1, 0, 2, a, 1, b, 1, t, 1, w, info )
137  CALL chkxer( 'CTPQRT', infot, nout, lerr, ok )
138  infot = 6
139  CALL ctpqrt( 1, 2, 0, 2, a, 1, b, 1, t, 1, w, info )
140  CALL chkxer( 'CTPQRT', infot, nout, lerr, ok )
141  infot = 8
142  CALL ctpqrt( 2, 1, 0, 1, a, 1, b, 1, t, 1, w, info )
143  CALL chkxer( 'CTPQRT', infot, nout, lerr, ok )
144  infot = 10
145  CALL ctpqrt( 2, 2, 1, 2, a, 2, b, 2, t, 1, w, info )
146  CALL chkxer( 'CTPQRT', infot, nout, lerr, ok )
147 *
148 * CTPQRT2
149 *
150  srnamt = 'CTPQRT2'
151  infot = 1
152  CALL ctpqrt2( -1, 0, 0, a, 1, b, 1, t, 1, info )
153  CALL chkxer( 'CTPQRT2', infot, nout, lerr, ok )
154  infot = 2
155  CALL ctpqrt2( 0, -1, 0, a, 1, b, 1, t, 1, info )
156  CALL chkxer( 'CTPQRT2', infot, nout, lerr, ok )
157  infot = 3
158  CALL ctpqrt2( 0, 0, -1, a, 1, b, 1, t, 1, info )
159  CALL chkxer( 'CTPQRT2', infot, nout, lerr, ok )
160  infot = 5
161  CALL ctpqrt2( 2, 2, 0, a, 1, b, 2, t, 2, info )
162  CALL chkxer( 'CTPQRT2', infot, nout, lerr, ok )
163  infot = 7
164  CALL ctpqrt2( 2, 2, 0, a, 2, b, 1, t, 2, info )
165  CALL chkxer( 'CTPQRT2', infot, nout, lerr, ok )
166  infot = 9
167  CALL ctpqrt2( 2, 2, 0, a, 2, b, 2, t, 1, info )
168  CALL chkxer( 'CTPQRT2', infot, nout, lerr, ok )
169 *
170 * CTPMQRT
171 *
172  srnamt = 'CTPMQRT'
173  infot = 1
174  CALL ctpmqrt( '/', 'N', 0, 0, 0, 0, 1, a, 1, t, 1, b, 1, c, 1,
175  $ w, info )
176  CALL chkxer( 'CTPMQRT', infot, nout, lerr, ok )
177  infot = 2
178  CALL ctpmqrt( 'L', '/', 0, 0, 0, 0, 1, a, 1, t, 1, b, 1, c, 1,
179  $ w, info )
180  CALL chkxer( 'CTPMQRT', infot, nout, lerr, ok )
181  infot = 3
182  CALL ctpmqrt( 'L', 'N', -1, 0, 0, 0, 1, a, 1, t, 1, b, 1, c, 1,
183  $ w, info )
184  CALL chkxer( 'CTPMQRT', infot, nout, lerr, ok )
185  infot = 4
186  CALL ctpmqrt( 'L', 'N', 0, -1, 0, 0, 1, a, 1, t, 1, b, 1, c, 1,
187  $ w, info )
188  CALL chkxer( 'CTPMQRT', infot, nout, lerr, ok )
189  infot = 5
190  CALL ctpmqrt( 'L', 'N', 0, 0, -1, 0, 1, a, 1, t, 1, b, 1, c, 1,
191  $ w, info )
192  infot = 6
193  CALL ctpmqrt( 'L', 'N', 0, 0, 0, -1, 1, a, 1, t, 1, b, 1, c, 1,
194  $ w, info )
195  CALL chkxer( 'CTPMQRT', infot, nout, lerr, ok )
196  infot = 7
197  CALL ctpmqrt( 'L', 'N', 0, 0, 0, 0, 0, a, 1, t, 1, b, 1, c, 1,
198  $ w, info )
199  CALL chkxer( 'CTPMQRT', infot, nout, lerr, ok )
200  infot = 9
201  CALL ctpmqrt( 'R', 'N', 1, 2, 1, 1, 1, a, 1, t, 1, b, 1, c, 1,
202  $ w, info )
203  CALL chkxer( 'CTPMQRT', infot, nout, lerr, ok )
204  infot = 9
205  CALL ctpmqrt( 'L', 'N', 2, 1, 1, 1, 1, a, 1, t, 1, b, 1, c, 1,
206  $ w, info )
207  CALL chkxer( 'CTPMQRT', infot, nout, lerr, ok )
208  infot = 11
209  CALL ctpmqrt( 'R', 'N', 1, 1, 1, 1, 1, a, 1, t, 0, b, 1, c, 1,
210  $ w, info )
211  CALL chkxer( 'CTPMQRT', infot, nout, lerr, ok )
212  infot = 13
213  CALL ctpmqrt( 'L', 'N', 1, 1, 1, 1, 1, a, 1, t, 1, b, 0, c, 1,
214  $ w, info )
215  CALL chkxer( 'CTPMQRT', infot, nout, lerr, ok )
216  infot = 15
217  CALL ctpmqrt( 'L', 'N', 1, 1, 1, 1, 1, a, 1, t, 1, b, 1, c, 0,
218  $ w, info )
219  CALL chkxer( 'CTPMQRT', infot, nout, lerr, ok )
220 *
221 * Print a summary line.
222 *
223  CALL alaesm( path, ok, nout )
224 *
225  return
226 *
227 * End of CERRQRT
228 *
229  END