LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
zerrac.f
Go to the documentation of this file.
1 *> \brief \b ZERRAC
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 ZERRAC( NUNIT )
12 *
13 * .. Scalar Arguments ..
14 * INTEGER NUNIT
15 * ..
16 *
17 *
18 *> \par Purpose:
19 * =============
20 *>
21 *> \verbatim
22 *>
23 *> ZERRPX tests the error exits for ZCPOSV.
24 *> \endverbatim
25 *
26 * Arguments:
27 * ==========
28 *
29 *> \param[in] NUNIT
30 *> \verbatim
31 *> NUNIT is INTEGER
32 *> The unit number for output.
33 *> \endverbatim
34 *
35 * Authors:
36 * ========
37 *
38 *> \author Univ. of Tennessee
39 *> \author Univ. of California Berkeley
40 *> \author Univ. of Colorado Denver
41 *> \author NAG Ltd.
42 *
43 *> \date November 2011
44 *
45 *> \ingroup complex16_lin
46 *
47 * =====================================================================
48  SUBROUTINE zerrac( NUNIT )
49 *
50 * -- LAPACK test routine (version 3.4.0) --
51 * -- LAPACK is a software package provided by Univ. of Tennessee, --
52 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
53 * November 2011
54 *
55 * .. Scalar Arguments ..
56  INTEGER nunit
57 * ..
58 *
59 * =====================================================================
60 *
61 * .. Parameters ..
62  INTEGER nmax
63  parameter( nmax = 4 )
64 * ..
65 * .. Local Scalars ..
66  INTEGER i, info, iter, j
67 * ..
68 * .. Local Arrays ..
69  COMPLEX*16 a( nmax, nmax ), af( nmax, nmax ), b( nmax ),
70  $ c( nmax ), r( nmax ), r1( nmax ), r2( nmax ),
71  $ w( 2*nmax ), x( nmax )
72  DOUBLE PRECISION rwork( nmax )
73  COMPLEX*16 work(nmax*nmax)
74  COMPLEX swork(nmax*nmax)
75 * ..
76 * .. External Subroutines ..
77  EXTERNAL chkxer, zcposv
78 * ..
79 * .. Scalars in Common ..
80  LOGICAL lerr, ok
81  CHARACTER*32 srnamt
82  INTEGER infot, nout
83 * ..
84 * .. Common blocks ..
85  common / infoc / infot, nout, ok, lerr
86  common / srnamc / srnamt
87 * ..
88 * .. Intrinsic Functions ..
89  INTRINSIC dble
90 * ..
91 * .. Executable Statements ..
92 *
93  nout = nunit
94  WRITE( nout, fmt = * )
95 *
96 * Set the variables to innocuous values.
97 *
98  DO 20 j = 1, nmax
99  DO 10 i = 1, nmax
100  a( i, j ) = 1.d0 / dble( i+j )
101  af( i, j ) = 1.d0 / dble( i+j )
102  10 continue
103  b( j ) = 0.d0
104  r1( j ) = 0.d0
105  r2( j ) = 0.d0
106  w( j ) = 0.d0
107  x( j ) = 0.d0
108  c( j ) = 0.d0
109  r( j ) = 0.d0
110  20 continue
111  ok = .true.
112 *
113  srnamt = 'ZCPOSV'
114  infot = 1
115  CALL zcposv('/',0,0,a,1,b,1,x,1,work,swork,rwork,iter,info)
116  CALL chkxer( 'ZCPOSV', infot, nout, lerr, ok )
117  infot = 2
118  CALL zcposv('U',-1,0,a,1,b,1,x,1,work,swork,rwork,iter,info)
119  CALL chkxer( 'ZCPOSV', infot, nout, lerr, ok )
120  infot = 3
121  CALL zcposv('U',0,-1,a,1,b,1,x,1,work,swork,rwork,iter,info)
122  CALL chkxer( 'ZCPOSV', infot, nout, lerr, ok )
123  infot = 5
124  CALL zcposv('U',2,1,a,1,b,2,x,2,work,swork,rwork,iter,info)
125  CALL chkxer( 'ZCPOSV', infot, nout, lerr, ok )
126  infot = 7
127  CALL zcposv('U',2,1,a,2,b,1,x,2,work,swork,rwork,iter,info)
128  CALL chkxer( 'ZCPOSV', infot, nout, lerr, ok )
129  infot = 9
130  CALL zcposv('U',2,1,a,2,b,2,x,1,work,swork,rwork,iter,info)
131  CALL chkxer( 'ZCPOSV', infot, nout, lerr, ok )
132 *
133 * Print a summary line.
134 *
135  IF( ok ) THEN
136  WRITE( nout, fmt = 9999 )'ZCPOSV'
137  ELSE
138  WRITE( nout, fmt = 9998 )'ZCPOSV'
139  END IF
140 *
141  9999 format( 1x, a6, ' drivers passed the tests of the error exits' )
142  9998 format( ' *** ', a6, ' drivers failed the tests of the error ',
143  $ 'exits ***' )
144 *
145  return
146 *
147 * End of ZERRAC
148 *
149  END