LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
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 *> \date November 2011
52 *
53 *> \ingroup single_lin
54 *
55 * =====================================================================
56  SUBROUTINE serrps( PATH, NUNIT )
57 *
58 * -- LAPACK test routine (version 3.4.0) --
59 * -- LAPACK is a software package provided by Univ. of Tennessee, --
60 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
61 * November 2011
62 *
63 * .. Scalar Arguments ..
64  INTEGER NUNIT
65  CHARACTER*3 PATH
66 * ..
67 *
68 * =====================================================================
69 *
70 * .. Parameters ..
71  INTEGER NMAX
72  parameter ( nmax = 4 )
73 * ..
74 * .. Local Scalars ..
75  INTEGER I, INFO, J, RANK
76 * ..
77 * .. Local Arrays ..
78  REAL A( nmax, nmax ), WORK( 2*nmax )
79  INTEGER PIV( nmax )
80 * ..
81 * .. External Subroutines ..
82  EXTERNAL alaesm, chkxer, spstf2, spstrf
83 * ..
84 * .. Scalars in Common ..
85  INTEGER INFOT, NOUT
86  LOGICAL LERR, OK
87  CHARACTER*32 SRNAMT
88 * ..
89 * .. Common blocks ..
90  COMMON / infoc / infot, nout, ok, lerr
91  COMMON / srnamc / srnamt
92 * ..
93 * .. Intrinsic Functions ..
94  INTRINSIC real
95 * ..
96 * .. Executable Statements ..
97 *
98  nout = nunit
99  WRITE( nout, fmt = * )
100 *
101 * Set the variables to innocuous values.
102 *
103  DO 110 j = 1, nmax
104  DO 100 i = 1, nmax
105  a( i, j ) = 1.0 / REAL( i+j )
106 *
107  100 CONTINUE
108  piv( j ) = j
109  work( j ) = 0.
110  work( nmax+j ) = 0.
111 *
112  110 CONTINUE
113  ok = .true.
114 *
115 *
116 * Test error exits of the routines that use the Cholesky
117 * decomposition of a symmetric positive semidefinite matrix.
118 *
119 * SPSTRF
120 *
121  srnamt = 'SPSTRF'
122  infot = 1
123  CALL spstrf( '/', 0, a, 1, piv, rank, -1.0, work, info )
124  CALL chkxer( 'SPSTRF', infot, nout, lerr, ok )
125  infot = 2
126  CALL spstrf( 'U', -1, a, 1, piv, rank, -1.0, work, info )
127  CALL chkxer( 'SPSTRF', infot, nout, lerr, ok )
128  infot = 4
129  CALL spstrf( 'U', 2, a, 1, piv, rank, -1.0, work, info )
130  CALL chkxer( 'SPSTRF', infot, nout, lerr, ok )
131 *
132 * SPSTF2
133 *
134  srnamt = 'SPSTF2'
135  infot = 1
136  CALL spstf2( '/', 0, a, 1, piv, rank, -1.0, work, info )
137  CALL chkxer( 'SPSTF2', infot, nout, lerr, ok )
138  infot = 2
139  CALL spstf2( 'U', -1, a, 1, piv, rank, -1.0, work, info )
140  CALL chkxer( 'SPSTF2', infot, nout, lerr, ok )
141  infot = 4
142  CALL spstf2( 'U', 2, a, 1, piv, rank, -1.0, work, info )
143  CALL chkxer( 'SPSTF2', infot, nout, lerr, ok )
144 *
145 *
146 * Print a summary line.
147 *
148  CALL alaesm( path, ok, nout )
149 *
150  RETURN
151 *
152 * End of SERRPS
153 *
154  END
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:143
subroutine alaesm(PATH, OK, NOUT)
ALAESM
Definition: alaesm.f:65
subroutine serrps(PATH, NUNIT)
SERRPS
Definition: serrps.f:57
subroutine chkxer(SRNAMT, INFOT, NOUT, LERR, OK)
Definition: cblat2.f:3199
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:143