LAPACK  3.9.0
LAPACK: Linear Algebra PACKage
zerrunhr_col.f
Go to the documentation of this file.
1 *> \brief \b ZERRUNHR_COL
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 ZERRUNHR_COL( 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 *> ZERRUNHR_COL tests the error exits for ZUNHR_COL that does
25 *> Householder reconstruction from the ouput of tall-skinny
26 *> factorization ZLATSQR.
27 *> \endverbatim
28 *
29 * Arguments:
30 * ==========
31 *
32 *> \param[in] PATH
33 *> \verbatim
34 *> PATH is CHARACTER*3
35 *> The LAPACK path name for the routines to be tested.
36 *> \endverbatim
37 *>
38 *> \param[in] NUNIT
39 *> \verbatim
40 *> NUNIT is INTEGER
41 *> The unit number for output.
42 *> \endverbatim
43 *
44 * Authors:
45 * ========
46 *
47 *> \author Univ. of Tennessee
48 *> \author Univ. of California Berkeley
49 *> \author Univ. of Colorado Denver
50 *> \author NAG Ltd.
51 *
52 *> \date November 2019
53 *
54 *> \ingroup complex16_lin
55 *
56 * =====================================================================
57  SUBROUTINE zerrunhr_col( PATH, NUNIT )
58  IMPLICIT NONE
59 *
60 * -- LAPACK test routine (version 3.9.0) --
61 * -- LAPACK is a software package provided by Univ. of Tennessee, --
62 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
63 * November 2019
64 *
65 * .. Scalar Arguments ..
66  CHARACTER(LEN=3) PATH
67  INTEGER NUNIT
68 * ..
69 *
70 * =====================================================================
71 *
72 * .. Parameters ..
73  INTEGER NMAX
74  parameter( nmax = 2 )
75 * ..
76 * .. Local Scalars ..
77  INTEGER I, INFO, J
78 * ..
79 * .. Local Arrays ..
80  COMPLEX*16 A( NMAX, NMAX ), T( NMAX, NMAX ), D(NMAX)
81 * ..
82 * .. External Subroutines ..
83  EXTERNAL alaesm, chkxer, zunhr_col
84 * ..
85 * .. Scalars in Common ..
86  LOGICAL LERR, OK
87  CHARACTER(LEN=32) SRNAMT
88  INTEGER INFOT, NOUT
89 * ..
90 * .. Common blocks ..
91  COMMON / infoc / infot, nout, ok, lerr
92  COMMON / srnamc / srnamt
93 * ..
94 * .. Intrinsic Functions ..
95  INTRINSIC dble, dcmplx
96 * ..
97 * .. Executable Statements ..
98 *
99  nout = nunit
100  WRITE( nout, fmt = * )
101 *
102 * Set the variables to innocuous values.
103 *
104  DO j = 1, nmax
105  DO i = 1, nmax
106  a( i, j ) = dcmplx( 1.d+0 / dble( i+j ) )
107  t( i, j ) = dcmplx( 1.d+0 / dble( i+j ) )
108  END DO
109  d( j ) = ( 0.d+0, 0.d+0 )
110  END DO
111  ok = .true.
112 *
113 * Error exits for Householder reconstruction
114 *
115 * ZUNHR_COL
116 *
117  srnamt = 'ZUNHR_COL'
118 *
119  infot = 1
120  CALL zunhr_col( -1, 0, 1, a, 1, t, 1, d, info )
121  CALL chkxer( 'ZUNHR_COL', infot, nout, lerr, ok )
122 *
123  infot = 2
124  CALL zunhr_col( 0, -1, 1, a, 1, t, 1, d, info )
125  CALL chkxer( 'ZUNHR_COL', infot, nout, lerr, ok )
126  CALL zunhr_col( 1, 2, 1, a, 1, t, 1, d, info )
127  CALL chkxer( 'ZUNHR_COL', infot, nout, lerr, ok )
128 *
129  infot = 3
130  CALL zunhr_col( 0, 0, -1, a, 1, t, 1, d, info )
131  CALL chkxer( 'ZUNHR_COL', infot, nout, lerr, ok )
132 *
133  CALL zunhr_col( 0, 0, 0, a, 1, t, 1, d, info )
134  CALL chkxer( 'ZUNHR_COL', infot, nout, lerr, ok )
135 *
136  infot = 5
137  CALL zunhr_col( 0, 0, 1, a, -1, t, 1, d, info )
138  CALL chkxer( 'ZUNHR_COL', infot, nout, lerr, ok )
139 *
140  CALL zunhr_col( 0, 0, 1, a, 0, t, 1, d, info )
141  CALL chkxer( 'ZUNHR_COL', infot, nout, lerr, ok )
142 *
143  CALL zunhr_col( 2, 0, 1, a, 1, t, 1, d, info )
144  CALL chkxer( 'ZUNHR_COL', infot, nout, lerr, ok )
145 *
146  infot = 7
147  CALL zunhr_col( 0, 0, 1, a, 1, t, -1, d, info )
148  CALL chkxer( 'ZUNHR_COL', infot, nout, lerr, ok )
149 *
150  CALL zunhr_col( 0, 0, 1, a, 1, t, 0, d, info )
151  CALL chkxer( 'ZUNHR_COL', infot, nout, lerr, ok )
152 *
153  CALL zunhr_col( 4, 3, 2, a, 4, t, 1, d, info )
154  CALL chkxer( 'ZUNHR_COL', infot, nout, lerr, ok )
155 *
156 * Print a summary line.
157 *
158  CALL alaesm( path, ok, nout )
159 *
160  RETURN
161 *
162 * End of ZERRUNHR_COL
163 *
164  END
alaesm
subroutine alaesm(PATH, OK, NOUT)
ALAESM
Definition: alaesm.f:65
zerrunhr_col
subroutine zerrunhr_col(PATH, NUNIT)
ZERRUNHR_COL
Definition: zerrunhr_col.f:58
zunhr_col
subroutine zunhr_col(M, N, NB, A, LDA, T, LDT, D, INFO)
ZUNHR_COL
Definition: zunhr_col.f:260
chkxer
subroutine chkxer(SRNAMT, INFOT, NOUT, LERR, OK)
Definition: cblat2.f:3199