OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
derrlqtp.f
Go to the documentation of this file.
1*> \brief \b DERRLQTP
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 DERRLQTP( 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*> DERRLQTP tests the error exits for the REAL routines
25*> that use the LQT decomposition of a triangular-pentagonal matrix.
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 double_lin
52*
53* =====================================================================
54 SUBROUTINE derrlqtp( PATH, NUNIT )
55 IMPLICIT NONE
56*
57* -- LAPACK test routine --
58* -- LAPACK is a software package provided by Univ. of Tennessee, --
59* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
60*
61* .. Scalar Arguments ..
62 CHARACTER*3 PATH
63 INTEGER NUNIT
64* ..
65*
66* =====================================================================
67*
68* .. Parameters ..
69 INTEGER NMAX
70 parameter( nmax = 2 )
71* ..
72* .. Local Scalars ..
73 INTEGER I, INFO, J
74* ..
75* .. Local Arrays ..
76 DOUBLE PRECISION A( NMAX, NMAX ), T( NMAX, NMAX ), W( NMAX ),
77 $ B( NMAX, NMAX ), C( NMAX, NMAX )
78* ..
79* .. External Subroutines ..
80 EXTERNAL alaesm, chkxer, dtplqt2, dtplqt,
81 $ dtpmlqt
82* ..
83* .. Scalars in Common ..
84 LOGICAL LERR, OK
85 CHARACTER*32 SRNAMT
86 INTEGER INFOT, NOUT
87* ..
88* .. Common blocks ..
89 COMMON / infoc / infot, nout, ok, lerr
90 COMMON / srnamc / srnamt
91* ..
92* .. Intrinsic Functions ..
93 INTRINSIC dble
94* ..
95* .. Executable Statements ..
96*
97 nout = nunit
98 WRITE( nout, fmt = * )
99*
100* Set the variables to innocuous values.
101*
102 DO j = 1, nmax
103 DO i = 1, nmax
104 a( i, j ) = 1.d0 / dble( i+j )
105 c( i, j ) = 1.d0 / dble( i+j )
106 t( i, j ) = 1.d0 / dble( i+j )
107 END DO
108 w( j ) = 0.0
109 END DO
110 ok = .true.
111*
112* Error exits for TPLQT factorization
113*
114* DTPLQT
115*
116 srnamt = 'DTPLQT'
117 infot = 1
118 CALL dtplqt( -1, 1, 0, 1, a, 1, b, 1, t, 1, w, info )
119 CALL chkxer( 'DTPLQT', infot, nout, lerr, ok )
120 infot = 2
121 CALL dtplqt( 1, -1, 0, 1, a, 1, b, 1, t, 1, w, info )
122 CALL chkxer( 'DTPLQT', infot, nout, lerr, ok )
123 infot = 3
124 CALL dtplqt( 0, 1, -1, 1, a, 1, b, 1, t, 1, w, info )
125 CALL chkxer( 'DTPLQT', infot, nout, lerr, ok )
126 infot = 3
127 CALL dtplqt( 0, 1, 1, 1, a, 1, b, 1, t, 1, w, info )
128 CALL chkxer( 'DTPLQT', infot, nout, lerr, ok )
129 infot = 4
130 CALL dtplqt( 0, 1, 0, 0, a, 1, b, 1, t, 1, w, info )
131 CALL chkxer( 'dtplqt', INFOT, NOUT, LERR, OK )
132 INFOT = 4
133 CALL DTPLQT( 1, 1, 0, 2, A, 1, B, 1, T, 1, W, INFO )
134 CALL CHKXER( 'dtplqt', INFOT, NOUT, LERR, OK )
135 INFOT = 6
136 CALL DTPLQT( 2, 1, 0, 2, A, 1, B, 1, T, 1, W, INFO )
137 CALL CHKXER( 'dtplqt', INFOT, NOUT, LERR, OK )
138 INFOT = 8
139 CALL DTPLQT( 2, 1, 0, 1, A, 2, B, 1, T, 1, W, INFO )
140 CALL CHKXER( 'dtplqt', INFOT, NOUT, LERR, OK )
141 INFOT = 10
142 CALL DTPLQT( 2, 2, 1, 2, A, 2, B, 2, T, 1, W, INFO )
143 CALL CHKXER( 'dtplqt', INFOT, NOUT, LERR, OK )
144*
145* DTPLQT2
146*
147 SRNAMT = 'dtplqt2'
148 INFOT = 1
149 CALL DTPLQT2( -1, 0, 0, A, 1, B, 1, T, 1, INFO )
150 CALL CHKXER( 'dtplqt2', INFOT, NOUT, LERR, OK )
151 INFOT = 2
152 CALL DTPLQT2( 0, -1, 0, A, 1, B, 1, T, 1, INFO )
153 CALL CHKXER( 'dtplqt2', INFOT, NOUT, LERR, OK )
154 INFOT = 3
155 CALL DTPLQT2( 0, 0, -1, A, 1, B, 1, T, 1, INFO )
156 CALL CHKXER( 'dtplqt2', INFOT, NOUT, LERR, OK )
157 INFOT = 5
158 CALL DTPLQT2( 2, 2, 0, A, 1, B, 2, T, 2, INFO )
159 CALL CHKXER( 'dtplqt2', INFOT, NOUT, LERR, OK )
160 INFOT = 7
161 CALL DTPLQT2( 2, 2, 0, A, 2, B, 1, T, 2, INFO )
162 CALL CHKXER( 'dtplqt2', INFOT, NOUT, LERR, OK )
163 INFOT = 9
164 CALL DTPLQT2( 2, 2, 0, A, 2, B, 2, T, 1, INFO )
165 CALL CHKXER( 'dtplqt2', INFOT, NOUT, LERR, OK )
166*
167* DTPMLQT
168*
169 SRNAMT = 'dtpmlqt'
170 INFOT = 1
171 CALL DTPMLQT( '/', 'N', 0, 0, 0, 0, 1, a, 1, t, 1, b, 1, c, 1,
172 $ w, info )
173 CALL chkxer( 'DTPMLQT', infot, nout, lerr, ok )
174 infot = 2
175 CALL dtpmlqt( 'L', '/', 0, 0, 0, 0, 1, a, 1, t, 1, b, 1, c, 1,
176 $ w, info )
177 CALL chkxer( 'DTPMLQT', infot, nout, lerr, ok )
178 infot = 3
179 CALL dtpmlqt( 'L', 'N', -1, 0, 0, 0, 1, a, 1, t, 1, b, 1, c, 1,
180 $ w, info )
181 CALL chkxer( 'DTPMLQT', infot, nout, lerr, ok )
182 infot = 4
183 CALL dtpmlqt( 'L', 'N', 0, -1, 0, 0, 1, a, 1, t, 1, b, 1, c, 1,
184 $ w, info )
185 CALL chkxer( 'DTPMLQT', infot, nout, lerr, ok )
186 infot = 5
187 CALL dtpmlqt( 'L', 'n', 0, 0, -1, 0, 1, A, 1, T, 1, B, 1, C, 1,
188 $ W, INFO )
189 INFOT = 6
190 CALL DTPMLQT( 'l', 'n', 0, 0, 0, -1, 1, A, 1, T, 1, B, 1, C, 1,
191 $ W, INFO )
192 CALL CHKXER( 'dtpmlqt', INFOT, NOUT, LERR, OK )
193 INFOT = 7
194 CALL DTPMLQT( 'l', 'n', 0, 0, 0, 0, 0, A, 1, T, 1, B, 1, C, 1,
195 $ W, INFO )
196 CALL CHKXER( 'dtpmlqt', INFOT, NOUT, LERR, OK )
197 INFOT = 9
198 CALL DTPMLQT( 'r', 'n', 2, 2, 2, 1, 1, A, 1, T, 1, B, 1, C, 1,
199 $ W, INFO )
200 CALL CHKXER( 'dtpmlqt', INFOT, NOUT, LERR, OK )
201 INFOT = 11
202 CALL DTPMLQT( 'r', 'n', 1, 1, 1, 1, 1, A, 1, T, 0, B, 1, C, 1,
203 $ W, INFO )
204 CALL CHKXER( 'dtpmlqt', INFOT, NOUT, LERR, OK )
205 INFOT = 13
206 CALL DTPMLQT( 'l', 'n', 1, 1, 1, 1, 1, A, 1, T, 1, B, 0, C, 1,
207 $ W, INFO )
208 CALL CHKXER( 'dtpmlqt', INFOT, NOUT, LERR, OK )
209 INFOT = 15
210 CALL DTPMLQT( 'l', 'n', 1, 1, 1, 1, 1, A, 1, T, 1, B, 1, C, 0,
211 $ W, INFO )
212 CALL CHKXER( 'dtpmlqt', INFOT, NOUT, LERR, OK )
213*
214* Print a summary line.
215*
216 CALL ALAESM( PATH, OK, NOUT )
217*
218 RETURN
219*
220* End of DERRLQTP
221*
222 END
subroutine chkxer(srnamt, infot, nout, lerr, ok)
Definition cblat2.f:3196
subroutine alaesm(path, ok, nout)
ALAESM
Definition alaesm.f:63
subroutine dtplqt(m, n, l, mb, a, lda, b, ldb, t, ldt, work, info)
DTPLQT
Definition dtplqt.f:189
subroutine dtplqt2(m, n, l, a, lda, b, ldb, t, ldt, info)
DTPLQT2 computes a LQ factorization of a real or complex "triangular-pentagonal" matrix,...
Definition dtplqt2.f:177
subroutine dtpmlqt(side, trans, m, n, k, l, mb, v, ldv, t, ldt, a, lda, b, ldb, work, info)
DTPMLQT
Definition dtpmlqt.f:214
subroutine derrlqtp(path, nunit)
DERRLQTP
Definition derrlqtp.f:55