LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ cerrunhr_col()

subroutine cerrunhr_col ( character(len=3)  path,
integer  nunit 
)

CERRUNHR_COL

Purpose:
 CERRUNHR_COL tests the error exits for CUNHR_COL that does
 Householder reconstruction from the output of tall-skinny
 factorization CLATSQR.
Parameters
[in]PATH
          PATH is CHARACTER*3
          The LAPACK path name for the routines to be tested.
[in]NUNIT
          NUNIT is INTEGER
          The unit number for output.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 55 of file cerrunhr_col.f.

56 IMPLICIT NONE
57*
58* -- LAPACK test routine --
59* -- LAPACK is a software package provided by Univ. of Tennessee, --
60* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
61*
62* .. Scalar Arguments ..
63 CHARACTER(LEN=3) PATH
64 INTEGER NUNIT
65* ..
66*
67* =====================================================================
68*
69* .. Parameters ..
70 INTEGER NMAX
71 parameter( nmax = 2 )
72* ..
73* .. Local Scalars ..
74 INTEGER I, INFO, J
75* ..
76* .. Local Arrays ..
77 COMPLEX A( NMAX, NMAX ), T( NMAX, NMAX ), D(NMAX)
78* ..
79* .. External Subroutines ..
80 EXTERNAL alaesm, chkxer, cunhr_col
81* ..
82* .. Scalars in Common ..
83 LOGICAL LERR, OK
84 CHARACTER(LEN=32) SRNAMT
85 INTEGER INFOT, NOUT
86* ..
87* .. Common blocks ..
88 COMMON / infoc / infot, nout, ok, lerr
89 COMMON / srnamc / srnamt
90* ..
91* .. Intrinsic Functions ..
92 INTRINSIC real, cmplx
93* ..
94* .. Executable Statements ..
95*
96 nout = nunit
97 WRITE( nout, fmt = * )
98*
99* Set the variables to innocuous values.
100*
101 DO j = 1, nmax
102 DO i = 1, nmax
103 a( i, j ) = cmplx( 1.e+0 / real( i+j ) )
104 t( i, j ) = cmplx( 1.e+0 / real( i+j ) )
105 END DO
106 d( j ) = ( 0.e+0, 0.e+0 )
107 END DO
108 ok = .true.
109*
110* Error exits for Householder reconstruction
111*
112* CUNHR_COL
113*
114 srnamt = 'CUNHR_COL'
115*
116 infot = 1
117 CALL cunhr_col( -1, 0, 1, a, 1, t, 1, d, info )
118 CALL chkxer( 'CUNHR_COL', infot, nout, lerr, ok )
119*
120 infot = 2
121 CALL cunhr_col( 0, -1, 1, a, 1, t, 1, d, info )
122 CALL chkxer( 'CUNHR_COL', infot, nout, lerr, ok )
123 CALL cunhr_col( 1, 2, 1, a, 1, t, 1, d, info )
124 CALL chkxer( 'CUNHR_COL', infot, nout, lerr, ok )
125*
126 infot = 3
127 CALL cunhr_col( 0, 0, -1, a, 1, t, 1, d, info )
128 CALL chkxer( 'CUNHR_COL', infot, nout, lerr, ok )
129*
130 CALL cunhr_col( 0, 0, 0, a, 1, t, 1, d, info )
131 CALL chkxer( 'CUNHR_COL', infot, nout, lerr, ok )
132*
133 infot = 5
134 CALL cunhr_col( 0, 0, 1, a, -1, t, 1, d, info )
135 CALL chkxer( 'CUNHR_COL', infot, nout, lerr, ok )
136*
137 CALL cunhr_col( 0, 0, 1, a, 0, t, 1, d, info )
138 CALL chkxer( 'CUNHR_COL', infot, nout, lerr, ok )
139*
140 CALL cunhr_col( 2, 0, 1, a, 1, t, 1, d, info )
141 CALL chkxer( 'CUNHR_COL', infot, nout, lerr, ok )
142*
143 infot = 7
144 CALL cunhr_col( 0, 0, 1, a, 1, t, -1, d, info )
145 CALL chkxer( 'CUNHR_COL', infot, nout, lerr, ok )
146*
147 CALL cunhr_col( 0, 0, 1, a, 1, t, 0, d, info )
148 CALL chkxer( 'CUNHR_COL', infot, nout, lerr, ok )
149*
150 CALL cunhr_col( 4, 3, 2, a, 4, t, 1, d, info )
151 CALL chkxer( 'CUNHR_COL', infot, nout, lerr, ok )
152*
153* Print a summary line.
154*
155 CALL alaesm( path, ok, nout )
156*
157 RETURN
158*
159* End of CERRUNHR_COL
160*
subroutine alaesm(path, ok, nout)
ALAESM
Definition alaesm.f:63
subroutine chkxer(srnamt, infot, nout, lerr, ok)
Definition cblat2.f:3224
subroutine cunhr_col(m, n, nb, a, lda, t, ldt, d, info)
CUNHR_COL
Definition cunhr_col.f:259
Here is the call graph for this function:
Here is the caller graph for this function: