LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
serrrfp.f
Go to the documentation of this file.
1 *> \brief \b SERRRFP
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 SERRRFP( NUNIT )
12 *
13 * .. Scalar Arguments ..
14 * INTEGER NUNIT
15 * ..
16 *
17 *
18 *> \par Purpose:
19 * =============
20 *>
21 *> \verbatim
22 *>
23 *> SERRRFP tests the error exits for the REAL driver routines
24 *> for solving linear systems of equations.
25 *>
26 *> SDRVRFP tests the REAL LAPACK RFP routines:
27 *> STFSM, STFTRI, SSFRK, STFTTP, STFTTR, SPFTRF, SPFTRS, STPTTF,
28 *> STPTTR, STRTTF, and STRTTP
29 *> \endverbatim
30 *
31 * Arguments:
32 * ==========
33 *
34 *> \param[in] NUNIT
35 *> \verbatim
36 *> NUNIT is INTEGER
37 *> The unit number for output.
38 *> \endverbatim
39 *
40 * Authors:
41 * ========
42 *
43 *> \author Univ. of Tennessee
44 *> \author Univ. of California Berkeley
45 *> \author Univ. of Colorado Denver
46 *> \author NAG Ltd.
47 *
48 *> \date November 2011
49 *
50 *> \ingroup single_lin
51 *
52 * =====================================================================
53  SUBROUTINE serrrfp( NUNIT )
54 *
55 * -- LAPACK test routine (version 3.4.0) --
56 * -- LAPACK is a software package provided by Univ. of Tennessee, --
57 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
58 * November 2011
59 *
60 * .. Scalar Arguments ..
61  INTEGER NUNIT
62 * ..
63 *
64 * =====================================================================
65 *
66 * ..
67 * .. Local Scalars ..
68  INTEGER INFO
69  REAL ALPHA, BETA
70 * ..
71 * .. Local Arrays ..
72  REAL A( 1, 1), B( 1, 1)
73 * ..
74 * .. External Subroutines ..
75  EXTERNAL chkxer, stfsm, stftri, ssfrk, stfttp, stfttr,
77  + strttp
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 * .. Executable Statements ..
89 *
90  nout = nunit
91  ok = .true.
92  a( 1, 1 ) = 1.0e+0
93  b( 1, 1 ) = 1.0e+0
94  alpha = 1.0e+0
95  beta = 1.0e+0
96 *
97  srnamt = 'SPFTRF'
98  infot = 1
99  CALL spftrf( '/', 'U', 0, a, info )
100  CALL chkxer( 'SPFTRF', infot, nout, lerr, ok )
101  infot = 2
102  CALL spftrf( 'N', '/', 0, a, info )
103  CALL chkxer( 'SPFTRF', infot, nout, lerr, ok )
104  infot = 3
105  CALL spftrf( 'N', 'U', -1, a, info )
106  CALL chkxer( 'SPFTRF', infot, nout, lerr, ok )
107 *
108  srnamt = 'SPFTRS'
109  infot = 1
110  CALL spftrs( '/', 'U', 0, 0, a, b, 1, info )
111  CALL chkxer( 'SPFTRS', infot, nout, lerr, ok )
112  infot = 2
113  CALL spftrs( 'N', '/', 0, 0, a, b, 1, info )
114  CALL chkxer( 'SPFTRS', infot, nout, lerr, ok )
115  infot = 3
116  CALL spftrs( 'N', 'U', -1, 0, a, b, 1, info )
117  CALL chkxer( 'SPFTRS', infot, nout, lerr, ok )
118  infot = 4
119  CALL spftrs( 'N', 'U', 0, -1, a, b, 1, info )
120  CALL chkxer( 'SPFTRS', infot, nout, lerr, ok )
121  infot = 7
122  CALL spftrs( 'N', 'U', 0, 0, a, b, 0, info )
123  CALL chkxer( 'SPFTRS', infot, nout, lerr, ok )
124 *
125  srnamt = 'SPFTRI'
126  infot = 1
127  CALL spftri( '/', 'U', 0, a, info )
128  CALL chkxer( 'SPFTRI', infot, nout, lerr, ok )
129  infot = 2
130  CALL spftri( 'N', '/', 0, a, info )
131  CALL chkxer( 'SPFTRI', infot, nout, lerr, ok )
132  infot = 3
133  CALL spftri( 'N', 'U', -1, a, info )
134  CALL chkxer( 'SPFTRI', infot, nout, lerr, ok )
135 *
136  srnamt = 'STFSM '
137  infot = 1
138  CALL stfsm( '/', 'L', 'U', 'T', 'U', 0, 0, alpha, a, b, 1 )
139  CALL chkxer( 'STFSM ', infot, nout, lerr, ok )
140  infot = 2
141  CALL stfsm( 'N', '/', 'U', 'T', 'U', 0, 0, alpha, a, b, 1 )
142  CALL chkxer( 'STFSM ', infot, nout, lerr, ok )
143  infot = 3
144  CALL stfsm( 'N', 'L', '/', 'T', 'U', 0, 0, alpha, a, b, 1 )
145  CALL chkxer( 'STFSM ', infot, nout, lerr, ok )
146  infot = 4
147  CALL stfsm( 'N', 'L', 'U', '/', 'U', 0, 0, alpha, a, b, 1 )
148  CALL chkxer( 'STFSM ', infot, nout, lerr, ok )
149  infot = 5
150  CALL stfsm( 'N', 'L', 'U', 'T', '/', 0, 0, alpha, a, b, 1 )
151  CALL chkxer( 'STFSM ', infot, nout, lerr, ok )
152  infot = 6
153  CALL stfsm( 'N', 'L', 'U', 'T', 'U', -1, 0, alpha, a, b, 1 )
154  CALL chkxer( 'STFSM ', infot, nout, lerr, ok )
155  infot = 7
156  CALL stfsm( 'N', 'L', 'U', 'T', 'U', 0, -1, alpha, a, b, 1 )
157  CALL chkxer( 'STFSM ', infot, nout, lerr, ok )
158  infot = 11
159  CALL stfsm( 'N', 'L', 'U', 'T', 'U', 0, 0, alpha, a, b, 0 )
160  CALL chkxer( 'STFSM ', infot, nout, lerr, ok )
161 *
162  srnamt = 'STFTRI'
163  infot = 1
164  CALL stftri( '/', 'L', 'N', 0, a, info )
165  CALL chkxer( 'STFTRI', infot, nout, lerr, ok )
166  infot = 2
167  CALL stftri( 'N', '/', 'N', 0, a, info )
168  CALL chkxer( 'STFTRI', infot, nout, lerr, ok )
169  infot = 3
170  CALL stftri( 'N', 'L', '/', 0, a, info )
171  CALL chkxer( 'STFTRI', infot, nout, lerr, ok )
172  infot = 4
173  CALL stftri( 'N', 'L', 'N', -1, a, info )
174  CALL chkxer( 'STFTRI', infot, nout, lerr, ok )
175 *
176  srnamt = 'STFTTR'
177  infot = 1
178  CALL stfttr( '/', 'U', 0, a, b, 1, info )
179  CALL chkxer( 'STFTTR', infot, nout, lerr, ok )
180  infot = 2
181  CALL stfttr( 'N', '/', 0, a, b, 1, info )
182  CALL chkxer( 'STFTTR', infot, nout, lerr, ok )
183  infot = 3
184  CALL stfttr( 'N', 'U', -1, a, b, 1, info )
185  CALL chkxer( 'STFTTR', infot, nout, lerr, ok )
186  infot = 6
187  CALL stfttr( 'N', 'U', 0, a, b, 0, info )
188  CALL chkxer( 'STFTTR', infot, nout, lerr, ok )
189 *
190  srnamt = 'STRTTF'
191  infot = 1
192  CALL strttf( '/', 'U', 0, a, 1, b, info )
193  CALL chkxer( 'STRTTF', infot, nout, lerr, ok )
194  infot = 2
195  CALL strttf( 'N', '/', 0, a, 1, b, info )
196  CALL chkxer( 'STRTTF', infot, nout, lerr, ok )
197  infot = 3
198  CALL strttf( 'N', 'U', -1, a, 1, b, info )
199  CALL chkxer( 'STRTTF', infot, nout, lerr, ok )
200  infot = 5
201  CALL strttf( 'N', 'U', 0, a, 0, b, info )
202  CALL chkxer( 'STRTTF', infot, nout, lerr, ok )
203 *
204  srnamt = 'STFTTP'
205  infot = 1
206  CALL stfttp( '/', 'U', 0, a, b, info )
207  CALL chkxer( 'STFTTP', infot, nout, lerr, ok )
208  infot = 2
209  CALL stfttp( 'N', '/', 0, a, b, info )
210  CALL chkxer( 'STFTTP', infot, nout, lerr, ok )
211  infot = 3
212  CALL stfttp( 'N', 'U', -1, a, b, info )
213  CALL chkxer( 'STFTTP', infot, nout, lerr, ok )
214 *
215  srnamt = 'STPTTF'
216  infot = 1
217  CALL stpttf( '/', 'U', 0, a, b, info )
218  CALL chkxer( 'STPTTF', infot, nout, lerr, ok )
219  infot = 2
220  CALL stpttf( 'N', '/', 0, a, b, info )
221  CALL chkxer( 'STPTTF', infot, nout, lerr, ok )
222  infot = 3
223  CALL stpttf( 'N', 'U', -1, a, b, info )
224  CALL chkxer( 'STPTTF', infot, nout, lerr, ok )
225 *
226  srnamt = 'STRTTP'
227  infot = 1
228  CALL strttp( '/', 0, a, 1, b, info )
229  CALL chkxer( 'STRTTP', infot, nout, lerr, ok )
230  infot = 2
231  CALL strttp( 'U', -1, a, 1, b, info )
232  CALL chkxer( 'STRTTP', infot, nout, lerr, ok )
233  infot = 4
234  CALL strttp( 'U', 0, a, 0, b, info )
235  CALL chkxer( 'STRTTP', infot, nout, lerr, ok )
236 *
237  srnamt = 'STPTTR'
238  infot = 1
239  CALL stpttr( '/', 0, a, b, 1, info )
240  CALL chkxer( 'STPTTR', infot, nout, lerr, ok )
241  infot = 2
242  CALL stpttr( 'U', -1, a, b, 1, info )
243  CALL chkxer( 'STPTTR', infot, nout, lerr, ok )
244  infot = 5
245  CALL stpttr( 'U', 0, a, b, 0, info )
246  CALL chkxer( 'STPTTR', infot, nout, lerr, ok )
247 *
248  srnamt = 'SSFRK '
249  infot = 1
250  CALL ssfrk( '/', 'U', 'N', 0, 0, alpha, a, 1, beta, b )
251  CALL chkxer( 'SSFRK ', infot, nout, lerr, ok )
252  infot = 2
253  CALL ssfrk( 'N', '/', 'N', 0, 0, alpha, a, 1, beta, b )
254  CALL chkxer( 'SSFRK ', infot, nout, lerr, ok )
255  infot = 3
256  CALL ssfrk( 'N', 'U', '/', 0, 0, alpha, a, 1, beta, b )
257  CALL chkxer( 'SSFRK ', infot, nout, lerr, ok )
258  infot = 4
259  CALL ssfrk( 'N', 'U', 'N', -1, 0, alpha, a, 1, beta, b )
260  CALL chkxer( 'SSFRK ', infot, nout, lerr, ok )
261  infot = 5
262  CALL ssfrk( 'N', 'U', 'N', 0, -1, alpha, a, 1, beta, b )
263  CALL chkxer( 'SSFRK ', infot, nout, lerr, ok )
264  infot = 8
265  CALL ssfrk( 'N', 'U', 'N', 0, 0, alpha, a, 0, beta, b )
266  CALL chkxer( 'SSFRK ', infot, nout, lerr, ok )
267 *
268 * Print a summary line.
269 *
270  IF( ok ) THEN
271  WRITE( nout, fmt = 9999 )
272  ELSE
273  WRITE( nout, fmt = 9998 )
274  END IF
275 *
276  9999 FORMAT( 1x, 'REAL RFP routines passed the tests of ',
277  $ 'the error exits' )
278  9998 FORMAT( ' *** RFP routines failed the tests of the error ',
279  $ 'exits ***' )
280  RETURN
281 *
282 * End of SERRRFP
283 *
284  END
subroutine strttp(UPLO, N, A, LDA, AP, INFO)
STRTTP copies a triangular matrix from the standard full format (TR) to the standard packed format (T...
Definition: strttp.f:106
subroutine chkxer(SRNAMT, INFOT, NOUT, LERR, OK)
Definition: cblat2.f:3199
subroutine ssfrk(TRANSR, UPLO, TRANS, N, K, ALPHA, A, LDA, BETA, C)
SSFRK performs a symmetric rank-k operation for matrix in RFP format.
Definition: ssfrk.f:168
subroutine spftrf(TRANSR, UPLO, N, A, INFO)
SPFTRF
Definition: spftrf.f:200
subroutine serrrfp(NUNIT)
SERRRFP
Definition: serrrfp.f:54
subroutine strttf(TRANSR, UPLO, N, A, LDA, ARF, INFO)
STRTTF copies a triangular matrix from the standard full format (TR) to the rectangular full packed f...
Definition: strttf.f:196
subroutine stpttf(TRANSR, UPLO, N, AP, ARF, INFO)
STPTTF copies a triangular matrix from the standard packed format (TP) to the rectangular full packed...
Definition: stpttf.f:188
subroutine spftri(TRANSR, UPLO, N, A, INFO)
SPFTRI
Definition: spftri.f:193
subroutine stfttr(TRANSR, UPLO, N, ARF, A, LDA, INFO)
STFTTR copies a triangular matrix from the rectangular full packed format (TF) to the standard full f...
Definition: stfttr.f:198
subroutine stftri(TRANSR, UPLO, DIAG, N, A, INFO)
STFTRI
Definition: stftri.f:203
subroutine spftrs(TRANSR, UPLO, N, NRHS, A, B, LDB, INFO)
SPFTRS
Definition: spftrs.f:201
subroutine stfsm(TRANSR, SIDE, UPLO, TRANS, DIAG, M, N, ALPHA, A, B, LDB)
STFSM solves a matrix equation (one operand is a triangular matrix in RFP format).
Definition: stfsm.f:279
subroutine stpttr(UPLO, N, AP, A, LDA, INFO)
STPTTR copies a triangular matrix from the standard packed format (TP) to the standard full format (T...
Definition: stpttr.f:106
subroutine stfttp(TRANSR, UPLO, N, ARF, AP, INFO)
STFTTP copies a triangular matrix from the rectangular full packed format (TF) to the standard packed...
Definition: stfttp.f:189