LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
serrps.f
Go to the documentation of this file.
1*> \brief \b SERRPS
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 SERRPS( PATH, NUNIT )
12*
13* .. Scalar Arguments ..
14* INTEGER NUNIT
15* CHARACTER*3 PATH
16* ..
17*
18*
19*> \par Purpose:
20* =============
21*>
22*> \verbatim
23*>
24*> SERRPS tests the error exits for the REAL routines
25*> for SPSTRF..
26*> \endverbatim
27*
28* Arguments:
29* ==========
30*
31*> \param[in] PATH
32*> \verbatim
33*> PATH is CHARACTER*3
34*> The LAPACK path name for the routines to be tested.
35*> \endverbatim
36*>
37*> \param[in] NUNIT
38*> \verbatim
39*> NUNIT is INTEGER
40*> The unit number for output.
41*> \endverbatim
42*
43* Authors:
44* ========
45*
46*> \author Univ. of Tennessee
47*> \author Univ. of California Berkeley
48*> \author Univ. of Colorado Denver
49*> \author NAG Ltd.
50*
51*> \ingroup single_lin
52*
53* =====================================================================
54 SUBROUTINE serrps( PATH, NUNIT )
55*
56* -- LAPACK test routine --
57* -- LAPACK is a software package provided by Univ. of Tennessee, --
58* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
59*
60* .. Scalar Arguments ..
61 INTEGER NUNIT
62 CHARACTER*3 PATH
63* ..
64*
65* =====================================================================
66*
67* .. Parameters ..
68 INTEGER NMAX
69 parameter( nmax = 4 )
70* ..
71* .. Local Scalars ..
72 INTEGER I, INFO, J, RANK
73* ..
74* .. Local Arrays ..
75 REAL A( NMAX, NMAX ), WORK( 2*NMAX )
76 INTEGER PIV( NMAX )
77* ..
78* .. External Subroutines ..
79 EXTERNAL alaesm, chkxer, spstf2, spstrf
80* ..
81* .. Scalars in Common ..
82 INTEGER INFOT, NOUT
83 LOGICAL LERR, OK
84 CHARACTER*32 SRNAMT
85* ..
86* .. Common blocks ..
87 COMMON / infoc / infot, nout, ok, lerr
88 COMMON / srnamc / srnamt
89* ..
90* .. Intrinsic Functions ..
91 INTRINSIC real
92* ..
93* .. Executable Statements ..
94*
95 nout = nunit
96 WRITE( nout, fmt = * )
97*
98* Set the variables to innocuous values.
99*
100 DO 110 j = 1, nmax
101 DO 100 i = 1, nmax
102 a( i, j ) = 1.0 / real( i+j )
103*
104 100 CONTINUE
105 piv( j ) = j
106 work( j ) = 0.
107 work( nmax+j ) = 0.
108*
109 110 CONTINUE
110 ok = .true.
111*
112*
113* Test error exits of the routines that use the Cholesky
114* decomposition of a symmetric positive semidefinite matrix.
115*
116* SPSTRF
117*
118 srnamt = 'SPSTRF'
119 infot = 1
120 CALL spstrf( '/', 0, a, 1, piv, rank, -1.0, work, info )
121 CALL chkxer( 'SPSTRF', infot, nout, lerr, ok )
122 infot = 2
123 CALL spstrf( 'U', -1, a, 1, piv, rank, -1.0, work, info )
124 CALL chkxer( 'SPSTRF', infot, nout, lerr, ok )
125 infot = 4
126 CALL spstrf( 'U', 2, a, 1, piv, rank, -1.0, work, info )
127 CALL chkxer( 'SPSTRF', infot, nout, lerr, ok )
128*
129* SPSTF2
130*
131 srnamt = 'SPSTF2'
132 infot = 1
133 CALL spstf2( '/', 0, a, 1, piv, rank, -1.0, work, info )
134 CALL chkxer( 'SPSTF2', infot, nout, lerr, ok )
135 infot = 2
136 CALL spstf2( 'U', -1, a, 1, piv, rank, -1.0, work, info )
137 CALL chkxer( 'SPSTF2', infot, nout, lerr, ok )
138 infot = 4
139 CALL spstf2( 'U', 2, a, 1, piv, rank, -1.0, work, info )
140 CALL chkxer( 'SPSTF2', infot, nout, lerr, ok )
141*
142*
143* Print a summary line.
144*
145 CALL alaesm( path, ok, nout )
146*
147 RETURN
148*
149* End of SERRPS
150*
151 END
subroutine alaesm(path, ok, nout)
ALAESM
Definition alaesm.f:63
subroutine chkxer(srnamt, infot, nout, lerr, ok)
Definition cblat2.f:3224
subroutine spstf2(uplo, n, a, lda, piv, rank, tol, work, info)
SPSTF2 computes the Cholesky factorization with complete pivoting of a real symmetric positive semide...
Definition spstf2.f:141
subroutine spstrf(uplo, n, a, lda, piv, rank, tol, work, info)
SPSTRF computes the Cholesky factorization with complete pivoting of a real symmetric positive semide...
Definition spstrf.f:141
subroutine serrps(path, nunit)
SERRPS
Definition serrps.f:55