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
zerrge.f
Go to the documentation of this file.
1  SUBROUTINE zerrge( 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 * ZERRGE tests the error exits for the COMPLEX*16 routines
18 * for general matrices.
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*2 c2
37  INTEGER i, info, j
38  DOUBLE PRECISION anrm, ccond, rcond
39 * ..
40 * .. Local Arrays ..
41  INTEGER ip( nmax )
42  INTEGER hl( 2 ), hpiv( 2 )
43  DOUBLE PRECISION r( nmax ), r1( nmax ), r2( nmax )
44  COMPLEX*16 a( nmax, nmax ), af( nmax, nmax ), b( nmax ),
45  $ w( 2*nmax ), x( nmax )
46 * ..
47 * .. External Functions ..
48  LOGICAL lsamen
49  EXTERNAL lsamen
50 * ..
51 * .. External Subroutines ..
52  EXTERNAL alaesm, chkxer, zgbcon, zgbequ, zgbrfs, zgbtf2,
53  $ zgbtrf, zgbtrs, zgecon, zgeequ, zgerfs, zgetf2,
54  $ zgetrf, zgetri, zgetrs
55 * ..
56 * .. Scalars in Common ..
57  LOGICAL lerr, ok
58  CHARACTER*32 srnamt
59  INTEGER infot, nout
60 * ..
61 * .. Common blocks ..
62  common / infoc / infot, nout, ok, lerr
63  common / srnamc / srnamt
64 * ..
65 * .. Intrinsic Functions ..
66  INTRINSIC dble, dcmplx
67 * ..
68 * .. Executable Statements ..
69 *
70  nout = nunit
71  WRITE( nout, fmt = * )
72  c2 = path( 2: 3 )
73 *
74 * Disable PLASMA warnings/errors
75 *
76  CALL plasma_disable( plasma_warnings, info )
77  CALL plasma_disable( plasma_errors, info )
78 *
79 * Set the variables to innocuous values.
80 *
81  DO 20 j = 1, nmax
82  DO 10 i = 1, nmax
83  a( i, j ) = dcmplx( 1.d0 / dble( i+j ),
84  $ -1.d0 / dble( i+j ) )
85  af( i, j ) = dcmplx( 1.d0 / dble( i+j ),
86  $ -1.d0 / dble( i+j ) )
87  10 continue
88  b( j ) = 0.d0
89  r1( j ) = 0.d0
90  r2( j ) = 0.d0
91  w( j ) = 0.d0
92  x( j ) = 0.d0
93  ip( j ) = j
94  20 continue
95  ok = .true.
96 *
97 * Test error exits of the routines that use the LU decomposition
98 * of a general matrix.
99 *
100  IF( lsamen( 2, c2, 'GE' ) ) THEN
101 *
102 * ZGETRF
103 *
104 *
105 * ALLOCATE L and IPIV
106 *
108  $ 2, 1, hl, hpiv, info )
109 *
110 * ZGETRF
111 *
112  srnamt = 'ZGETRF'
113  infot = 1
114  CALL plasma_zgetrf_incpiv( -1, 0, a, 1, hl, hpiv, info )
115  CALL chkxer( 'ZGETRF', infot, nout, info, ok )
116  infot = 2
117  CALL plasma_zgetrf_incpiv( 0, -1, a, 1, hl, hpiv, info )
118  CALL chkxer( 'ZGETRF', infot, nout, info, ok )
119  infot = 4
120  CALL plasma_zgetrf_incpiv( 2, 1, a, 1, hl, hpiv, info )
121  CALL chkxer( 'ZGETRF', infot, nout, info, ok )
122 *
123 * ZGETRS
124 *
125  srnamt = 'ZGETRS'
126  infot = 103
127  CALL plasma_zgetrs_incpiv( '/', -1, 0, a, 1, hl, hpiv,
128  $ b, 1, info )
129  CALL chkxer( 'ZGETRS', infot, nout, info, ok )
130  infot = 2
131  CALL plasma_zgetrs_incpiv( plasmanotrans, -1, 0, a, 1, hl,
132  $ hpiv, b, 1, info )
133  CALL chkxer( 'ZGETRS', infot, nout, info, ok )
134  infot = 3
135  CALL plasma_zgetrs_incpiv( plasmanotrans, 0, -1, a, 1, hl,
136  $ hpiv, b, 1, info )
137  CALL chkxer( 'ZGETRS', infot, nout, info, ok )
138  infot = 5
139  CALL plasma_zgetrs_incpiv( plasmanotrans, 2, 1, a, 1, hl,
140  $ hpiv, b, 2, info )
141  CALL chkxer( 'ZGETRS', infot, nout, info, ok )
142  infot = 9
143  CALL plasma_zgetrs_incpiv( plasmanotrans, 2, 1, a, 2, hl,
144  $ hpiv, b, 1, info )
145  CALL chkxer( 'ZGETRS', infot, nout, info, ok )
146 *
147 * DEALLOCATE L and IPIV
148 *
149  CALL plasma_dealloc_handle( hl, info )
150  CALL plasma_dealloc_handle( hpiv, info )
151 *
152 * LAPACK Interface
153 * ZGETRF
154 *
155  srnamt = 'ZGETRF'
156  infot = 1
157  CALL plasma_zgetrf( -1, 0, a, 1, ip, info )
158  CALL chkxer( 'ZGETRF', infot, nout, info, ok )
159  infot = 2
160  CALL plasma_zgetrf( 0, -1, a, 1, ip, info )
161  CALL chkxer( 'ZGETRF', infot, nout, info, ok )
162  infot = 4
163  CALL plasma_zgetrf( 2, 1, a, 1, ip, info )
164  CALL chkxer( 'ZGETRF', infot, nout, info, ok )
165 *
166 * ZGETRS
167 *
168  srnamt = 'ZGETRS'
169  infot = 1
170  CALL plasma_zgetrs( '/', 0, 0, a, 1, ip,
171  $ b, 1, info )
172  CALL chkxer( 'ZGETRS', infot, nout, info, ok )
173  infot = 2
174  CALL plasma_zgetrs( plasmanotrans, -1, 0, a, 1, ip,
175  $ b, 1, info )
176  CALL chkxer( 'ZGETRS', infot, nout, info, ok )
177  infot = 3
178  CALL plasma_zgetrs( plasmanotrans, 0, -1, a, 1, ip,
179  $ b, 1, info )
180  CALL chkxer( 'ZGETRS', infot, nout, info, ok )
181  infot = 5
182  CALL plasma_zgetrs( plasmanotrans, 2, 1, a, 1, ip,
183  $ b, 2, info )
184  CALL chkxer( 'ZGETRS', infot, nout, info, ok )
185  infot = 8
186  CALL plasma_zgetrs( plasmanotrans, 2, 1, a, 2, ip,
187  $ b, 1, info )
188  CALL chkxer( 'ZGETRS', infot, nout, info, ok )
189 *
190  END IF
191 *
192 * Print a summary line.
193 *
194  CALL alaesm( path, ok, nout )
195 *
196 * Enable PLASMA warnings/errors
197 *
198  CALL plasma_enable( plasma_warnings, info )
199  CALL plasma_enable( plasma_errors, info )
200 *
201  return
202 *
203 * End of ZERRGE
204 *
205  END