PLASMA  2.4.5
PLASMA - Parallel Linear Algebra for Scalable Multi-core Architectures
 All Data Structures Namespaces Files Functions Variables Typedefs Enumerations Enumerator Macros Groups
cerrqr.f
Go to the documentation of this file.
1  SUBROUTINE cerrqr( PATH, NUNIT )
2 *
3  include 'plasmaf.h'
4 *
5 * -- LAPACK test routine (version 3.1) --
6 * Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
7 * November 2006
8 *
9 * .. Scalar Arguments ..
10  CHARACTER*3 path
11  INTEGER nunit
12 * ..
13 *
14 * Purpose
15 * =======
16 *
17 * CERRQR tests the error exits for the COMPLEX routines
18 * that use the QR decomposition of a general matrix.
19 *
20 * Arguments
21 * =========
22 *
23 * PATH (input) CHARACTER*3
24 * The LAPACK path name for the routines to be tested.
25 *
26 * NUNIT (input) INTEGER
27 * The unit number for output.
28 *
29 * =====================================================================
30 *
31 * .. Parameters ..
32  INTEGER nmax
33  parameter( nmax = 2 )
34 * ..
35 * .. Local Scalars ..
36  INTEGER i, info, j
37 * ..
38 * .. Local Arrays ..
39  COMPLEX a( nmax, nmax ), af( nmax, nmax ), b( nmax ),
40  $ w( nmax ), x( nmax )
41  INTEGER ht( 2 )
42 * ..
43 * .. External Subroutines ..
44  EXTERNAL alaesm, cgeqr2, cgeqrf, chkxer, cung2r,
45  $ cungqr, cunm2r, cunmqr
46 * ..
47 * .. Scalars in Common ..
48  LOGICAL lerr, ok
49  CHARACTER*32 srnamt
50  INTEGER infot, nout
51 * ..
52 * .. Common blocks ..
53  common / infoc / infot, nout, ok, lerr
54  common / srnamc / srnamt
55 * ..
56 * .. Intrinsic Functions ..
57  INTRINSIC cmplx, real
58 * ..
59 * .. Executable Statements ..
60 *
61  nout = nunit
62  WRITE( nout, fmt = * )
63 *
64 * Disable PLASMA warnings/errors
65 *
66  CALL plasma_disable( plasma_warnings, info )
67  CALL plasma_disable( plasma_errors, info )
68 *
69 * Set the variables to innocuous values.
70 *
71  DO 20 j = 1, nmax
72  DO 10 i = 1, nmax
73  a( i, j ) = cmplx( 1. / REAL( I+J ), -1. / REAL( I+J ) )
74  af( i, j ) = cmplx( 1. / REAL( I+J ), -1. / REAL( I+J ) )
75  10 continue
76  b( j ) = 0.
77  w( j ) = 0.
78  x( j ) = 0.
79  20 continue
80  ok = .true.
81 *
82 * Allocate HT
83 *
84  CALL plasma_alloc_workspace_cgeqrf( 2, 2, ht, info )
85 *
86 * Error exits for QR factorization
87 *
88 * CGEQRF
89 *
90  srnamt = 'CGEQRF'
91  infot = 1
92  CALL plasma_cgeqrf( -1, 0, a, 1, ht, info )
93  CALL chkxer( 'CGEQRF', infot, nout, info, ok )
94  infot = 2
95  CALL plasma_cgeqrf( 0, -1, a, 1, ht, info )
96  CALL chkxer( 'CGEQRF', infot, nout, info, ok )
97  infot = 4
98  CALL plasma_cgeqrf( 2, 1, a, 1, ht, info )
99  CALL chkxer( 'CGEQRF', infot, nout, info, ok )
100 *
101 * CGEQRS
102 *
103  srnamt = 'CGEQRS'
104  infot = 1
105  CALL plasma_cgeqrs( -1, 0, 0, a, 1, x, b, 1, info )
106  CALL chkxer( 'CGEQRS', infot, nout, info, ok )
107  infot = 2
108  CALL plasma_cgeqrs( 0, -1, 0, a, 1, x, b, 1, info )
109  CALL chkxer( 'CGEQRS', infot, nout, info, ok )
110  infot = 2
111  CALL plasma_cgeqrs( 1, 2, 0, a, 2, x, b, 2, info )
112  CALL chkxer( 'CGEQRS', infot, nout, info, ok )
113  infot = 3
114  CALL plasma_cgeqrs( 0, 0, -1, a, 1, x, b, 1, info )
115  CALL chkxer( 'CGEQRS', infot, nout, info, ok )
116  infot = 5
117  CALL plasma_cgeqrs( 2, 1, 0, a, 1, x, b, 2, info )
118  CALL chkxer( 'CGEQRS', infot, nout, info, ok )
119  infot = 8
120  CALL plasma_cgeqrs( 2, 1, 0, a, 2, x, b, 1, info )
121  CALL chkxer( 'CGEQRS', infot, nout, info, ok )
122 *
123 * CUNGQR
124 *
125  srnamt = 'CUNGQR'
126  infot = 1
127  CALL plasma_cungqr( -1, 0, 0, a, 1, ht, w, 1, info )
128  CALL chkxer( 'CUNGQR', infot, nout, info, ok )
129  infot = 2
130  CALL plasma_cungqr( 0, -1, 0, a, 1, ht, w, 1, info )
131  CALL chkxer( 'CUNGQR', infot, nout, info, ok )
132  infot = 2
133  CALL plasma_cungqr( 1, 2, 0, a, 1, ht, w, 2, info )
134  CALL chkxer( 'CUNGQR', infot, nout, info, ok )
135  infot = 3
136  CALL plasma_cungqr( 0, 0, -1, a, 1, ht, w, 1, info )
137  CALL chkxer( 'CUNGQR', infot, nout, info, ok )
138  infot = 3
139  CALL plasma_cungqr( 1, 1, 2, a, 1, ht, w, 1, info )
140  CALL chkxer( 'CUNGQR', infot, nout, info, ok )
141  infot = 5
142  CALL plasma_cungqr( 2, 2, 0, a, 1, ht, w, 2, info )
143  CALL chkxer( 'CUNGQR', infot, nout, info, ok )
144  infot = 8
145  CALL plasma_cungqr( 2, 2, 0, a, 2, ht, w, 1, info )
146  CALL chkxer( 'CUNGQR', infot, nout, info, ok )
147 *
148 * PLASMA_CUNMQR
149 *
150  srnamt = 'CUNMQR'
151  infot = 1
152  CALL plasma_cunmqr( '/', plasmaconjtrans, 0, 0, 0, a, 1, ht, af,
153  $ 1, info )
154  CALL chkxer( 'CUNMQR', infot, nout, info, ok )
155  infot = 2
156  CALL plasma_cunmqr( plasmaleft, '/', 0, 0, 0, a, 1, ht, af, 1,
157  $ info )
158  CALL chkxer( 'CUNMQR', infot, nout, info, ok )
159  infot = 3
160  CALL plasma_cunmqr( plasmaleft, plasmaconjtrans, -1, 0, 0, a, 1,
161  $ ht, af, 1, info )
162  CALL chkxer( 'CUNMQR', infot, nout, info, ok )
163  infot = 4
164  CALL plasma_cunmqr( plasmaleft, plasmaconjtrans, 0, -1, 0, a, 1,
165  $ ht, af, 1, info )
166  CALL chkxer( 'CUNMQR', infot, nout, info, ok )
167  infot = 5
168  CALL plasma_cunmqr( plasmaleft, plasmaconjtrans, 0, 0, -1, a, 1,
169  $ ht, af, 1, info )
170  CALL chkxer( 'CUNMQR', infot, nout, info, ok )
171 * INFOT = 5
172 * CALL PLASMA_CUNMQR( PLASMALEFT, PLASMACONJTRANS, 0, 1, 1, A, 1, HT,
173 * 4 AF, 1, INFO )
174 * CALL CHKXER( 'CUNMQR', INFOT, NOUT, INFO, OK )
175 * INFOT = 5
176 * CALL PLASMA_CUNMQR( PLASMALEFT, PLASMACONJTRANS, 1, 0, 1, A, 1, HT,
177 * 4 AF, 1, INFO )
178 * CALL CHKXER( 'CUNMQR', INFOT, NOUT, INFO, OK )
179 * INFOT = 7
180 * CALL PLASMA_CUNMQR( PLASMALEFT, PLASMACONJTRANS, 2, 1, 0, A, 1, HT,
181 * 4 AF, 2, INFO )
182 * CALL CHKXER( 'CUNMQR', INFOT, NOUT, INFO, OK )
183 * INFOT = 7
184 * CALL PLASMA_CUNMQR( PLASMALEFT, PLASMACONJTRANS, 1, 2, 0, A, 1, HT,
185 * 4 AF, 1, INFO )
186 * CALL CHKXER( 'CUNMQR', INFOT, NOUT, INFO, OK )
187 * INFOT = 10
188 * CALL PLASMA_CUNMQR( PLASMALEFT, PLASMACONJTRANS, 1, 2, 0, A, 1, HT,
189 * 4 AF, 1, INFO )
190 * CALL CHKXER( 'CUNMQR', INFOT, NOUT, INFO, OK )
191 * INFOT = 10
192 * CALL PLASMA_CUNMQR( PLASMALEFT, PLASMACONJTRANS, 2, 1, 0, A, 1, HT,
193 * 4 AF, 2, INFO )
194 * CALL CHKXER( 'CUNMQR', INFOT, NOUT, INFO, OK )
195 *
196 * Print a summary line.
197 *
198  CALL alaesm( path, ok, nout )
199 *
200 * Deallocate HT
201 *
202  CALL plasma_dealloc_handle( ht, info )
203 *
204 * Enable PLASMA warnings/errors
205 *
206  CALL plasma_enable( plasma_warnings, info )
207  CALL plasma_enable( plasma_errors, info )
208 *
209  return
210 *
211 * End of CERRQR
212 *
213  END