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
cerrvx.f
Go to the documentation of this file.
1  SUBROUTINE cerrvx( PATH, NUNIT )
2 *
3  include 'plasmaf.h'
4 *
5 * -- LAPACK test routine (version 3.1.1) --
6 * Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
7 * January 2007
8 *
9 * .. Scalar Arguments ..
10  CHARACTER*3 path
11  INTEGER nunit
12 * ..
13 *
14 * Purpose
15 * =======
16 *
17 * CERRVX tests the error exits for the COMPLEX driver routines
18 * for solving linear systems of equations.
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 = 4 )
34 * ..
35 * .. Local Scalars ..
36  CHARACTER eq
37  CHARACTER*2 c2
38  INTEGER i, info, j
39  REAL rcond
40 * ..
41 * .. Local Arrays ..
42  INTEGER hl( 2 ), hpiv( 2 )
43  INTEGER ip( nmax )
44  REAL c( nmax ), r( nmax ), r1( nmax ), r2( nmax ),
45  $ rf( nmax ), rw( nmax )
46  COMPLEX a( nmax, nmax ), af( nmax, nmax ), b( nmax ),
47  $ w( 2*nmax ), x( nmax ), iw( nmax )
48 * ..
49 * .. External Functions ..
50  LOGICAL lsamen
51  EXTERNAL lsamen
52 * ..
53 * .. External Subroutines ..
54  EXTERNAL cgbsv, cgbsvx, cgesv, cgesvx, cgtsv, cgtsvx,
55  $ chesv, chesvx, chkxer, chpsv, chpsvx, cpbsv,
56  $ cpbsvx, cposv, cposvx, cppsv, cppsvx, cptsv,
57  $ cptsvx, cspsv, cspsvx, csysv, csysvx
58 * ..
59 * .. Scalars in Common ..
60  LOGICAL lerr, ok
61  CHARACTER*32 srnamt
62  INTEGER infot, nout
63 * ..
64 * .. Common blocks ..
65  common / infoc / infot, nout, ok, lerr
66  common / srnamc / srnamt
67 * ..
68 * .. Intrinsic Functions ..
69  INTRINSIC cmplx, real
70 * ..
71 * .. Executable Statements ..
72 *
73  nout = nunit
74  WRITE( nout, fmt = * )
75  c2 = path( 2: 3 )
76 *
77 * Disable PLASMA warnings/errors
78 *
79  CALL plasma_disable( plasma_warnings, info )
80  CALL plasma_disable( plasma_errors, info )
81 *
82 * Set the variables to innocuous values.
83 *
84  DO 20 j = 1, nmax
85  DO 10 i = 1, nmax
86  a( i, j ) = cmplx( 1. / REAL( I+J ), -1. / REAL( I+J ) )
87  af( i, j ) = cmplx( 1. / REAL( I+J ), -1. / REAL( I+J ) )
88  10 continue
89  b( j ) = 0.
90  r1( j ) = 0.
91  r2( j ) = 0.
92  w( j ) = 0.
93  x( j ) = 0.
94  c( j ) = 0.
95  r( j ) = 0.
96  ip( j ) = j
97  20 continue
98  eq = ' '
99  ok = .true.
100 *
101  IF( lsamen( 2, c2, 'GE' ) ) THEN
102 *
103 * ALLOCATE HL and HPIV
104 *
106  $ 2, 1, hl, hpiv, info )
107 *
108 *
109 * CGESV
110 *
111  srnamt = 'CGESV '
112  infot = 1
113  CALL plasma_cgesv_incpiv( -1, 0, a, 1, hl, hpiv, b, 1, info )
114  CALL chkxer( 'CGESV ', infot, nout, info, ok )
115  infot = 2
116  CALL plasma_cgesv_incpiv( 0, -1, a, 1, hl, hpiv, b, 1, info )
117  CALL chkxer( 'CGESV ', infot, nout, info, ok )
118  infot = 4
119  CALL plasma_cgesv_incpiv( 2, 1, a, 1, hl, hpiv, b, 2, info )
120  CALL chkxer( 'CGESV ', infot, nout, info, ok )
121  infot = 8
122  CALL plasma_cgesv_incpiv( 2, 1, a, 2, hl, hpiv, b, 1, info )
123  CALL chkxer( 'CGESV ', infot, nout, info, ok )
124 *
125 * DEALLOCATE HL and HPIV
126 *
127  CALL plasma_dealloc_handle( hl, info )
128  CALL plasma_dealloc_handle( hpiv, info )
129 *
130 *
131 * CGESV
132 *
133  srnamt = 'CGESV '
134  infot = 1
135  CALL plasma_cgesv( -1, 0, a, 1, iwork, b, 1, info )
136  CALL chkxer( 'CGESV ', infot, nout, info, ok )
137  infot = 2
138  CALL plasma_cgesv( 0, -1, a, 1, iwork, b, 1, info )
139  CALL chkxer( 'CGESV ', infot, nout, info, ok )
140  infot = 4
141  CALL plasma_cgesv( 2, 1, a, 1, iwork, b, 2, info )
142  CALL chkxer( 'CGESV ', infot, nout, info, ok )
143  infot = 8
144  CALL plasma_cgesv( 2, 1, a, 2, iwork, b, 1, info )
145  CALL chkxer( 'CGESV ', infot, nout, info, ok )
146 *
147  ELSE IF( lsamen( 2, c2, 'PO' ) ) THEN
148 *
149 * CPOSV
150 *
151  srnamt = 'CPOSV '
152  infot = 1
153  CALL plasma_cposv( '/', 0, 0, a, 1, b, 1, info )
154  CALL chkxer( 'CPOSV ', infot, nout, info, ok )
155  infot = 2
156  CALL plasma_cposv( plasmaupper, -1, 0, a, 1, b, 1, info )
157  CALL chkxer( 'CPOSV ', infot, nout, info, ok )
158  infot = 3
159  CALL plasma_cposv( plasmaupper, 0, -1, a, 1, b, 1, info )
160  CALL chkxer( 'CPOSV ', infot, nout, info, ok )
161  infot = 5
162  CALL plasma_cposv( plasmaupper, 2, 0, a, 1, b, 2, info )
163  CALL chkxer( 'CPOSV ', infot, nout, info, ok )
164  infot = 7
165  CALL plasma_cposv( plasmaupper, 2, 0, a, 2, b, 1, info )
166  CALL chkxer( 'CPOSV ', infot, nout, info, ok )
167 *
168 * CPOSVX
169 *
170  srnamt = 'CPOSVX'
171  infot = 1
172  CALL cposvx( '/', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
173  $ rcond, r1, r2, w, iw, info )
174  CALL chkxer( 'CPOSVX', infot, nout, info, ok )
175  infot = 2
176  CALL cposvx( 'N', '/', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
177  $ rcond, r1, r2, w, iw, info )
178  CALL chkxer( 'CPOSVX', infot, nout, info, ok )
179  infot = 3
180  CALL cposvx( 'N', 'U', -1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
181  $ rcond, r1, r2, w, iw, info )
182  CALL chkxer( 'CPOSVX', infot, nout, info, ok )
183  infot = 4
184  CALL cposvx( 'N', 'U', 0, -1, a, 1, af, 1, eq, c, b, 1, x, 1,
185  $ rcond, r1, r2, w, iw, info )
186  CALL chkxer( 'CPOSVX', infot, nout, info, ok )
187  infot = 6
188  CALL cposvx( 'N', 'U', 2, 0, a, 1, af, 2, eq, c, b, 2, x, 2,
189  $ rcond, r1, r2, w, iw, info )
190  CALL chkxer( 'CPOSVX', infot, nout, info, ok )
191  infot = 8
192  CALL cposvx( 'N', 'U', 2, 0, a, 2, af, 1, eq, c, b, 2, x, 2,
193  $ rcond, r1, r2, w, iw, info )
194  CALL chkxer( 'CPOSVX', infot, nout, info, ok )
195  infot = 9
196  eq = '/'
197  CALL cposvx( 'F', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
198  $ rcond, r1, r2, w, iw, info )
199  CALL chkxer( 'CPOSVX', infot, nout, info, ok )
200  infot = 10
201  eq = 'Y'
202  CALL cposvx( 'F', 'U', 1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
203  $ rcond, r1, r2, w, iw, info )
204  CALL chkxer( 'CPOSVX', infot, nout, info, ok )
205  infot = 12
206  CALL cposvx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 1, x, 2,
207  $ rcond, r1, r2, w, iw, info )
208  CALL chkxer( 'CPOSVX', infot, nout, info, ok )
209  infot = 14
210  CALL cposvx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 2, x, 1,
211  $ rcond, r1, r2, w, iw, info )
212  CALL chkxer( 'CPOSVX', infot, nout, info, ok )
213  END IF
214 *
215 * Print a summary line.
216 *
217  IF( ok ) THEN
218  WRITE( nout, fmt = 9999 )path
219  ELSE
220  WRITE( nout, fmt = 9998 )path
221  END IF
222 *
223  9999 format( 1x, a3, ' drivers passed the tests of the error exits' )
224  9998 format( ' *** ', a3, ' drivers failed the tests of the error ',
225  $ 'exits ***' )
226 *
227 * Enable PLASMA warnings/errors
228 *
229  CALL plasma_enable( plasma_warnings, info )
230  CALL plasma_enable( plasma_errors, info )
231 *
232  return
233 *
234 * End of CERRVX
235 *
236  END