LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dtrtrs.f
Go to the documentation of this file.
1*> \brief \b DTRTRS
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download DTRTRS + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dtrtrs.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dtrtrs.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dtrtrs.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE DTRTRS( UPLO, TRANS, DIAG, N, NRHS, A, LDA, B, LDB,
20* INFO )
21*
22* .. Scalar Arguments ..
23* CHARACTER DIAG, TRANS, UPLO
24* INTEGER INFO, LDA, LDB, N, NRHS
25* ..
26* .. Array Arguments ..
27* DOUBLE PRECISION A( LDA, * ), B( LDB, * )
28* ..
29*
30*
31*> \par Purpose:
32* =============
33*>
34*> \verbatim
35*>
36*> DTRTRS solves a triangular system of the form
37*>
38*> A * X = B or A**T * X = B,
39*>
40*> where A is a triangular matrix of order N, and B is an N-by-NRHS matrix.
41*>
42*> This subroutine verifies that A is nonsingular, but callers should note that only exact
43*> singularity is detected. It is conceivable for one or more diagonal elements of A to be
44*> subnormally tiny numbers without this subroutine signalling an error.
45*>
46*> If a possible loss of numerical precision due to near-singular matrices is a concern, the
47*> caller should verify that A is nonsingular within some tolerance before calling this subroutine.
48*> \endverbatim
49*
50* Arguments:
51* ==========
52*
53*> \param[in] UPLO
54*> \verbatim
55*> UPLO is CHARACTER*1
56*> = 'U': A is upper triangular;
57*> = 'L': A is lower triangular.
58*> \endverbatim
59*>
60*> \param[in] TRANS
61*> \verbatim
62*> TRANS is CHARACTER*1
63*> Specifies the form of the system of equations:
64*> = 'N': A * X = B (No transpose)
65*> = 'T': A**T * X = B (Transpose)
66*> = 'C': A**H * X = B (Conjugate transpose = Transpose)
67*> \endverbatim
68*>
69*> \param[in] DIAG
70*> \verbatim
71*> DIAG is CHARACTER*1
72*> = 'N': A is non-unit triangular;
73*> = 'U': A is unit triangular.
74*> \endverbatim
75*>
76*> \param[in] N
77*> \verbatim
78*> N is INTEGER
79*> The order of the matrix A. N >= 0.
80*> \endverbatim
81*>
82*> \param[in] NRHS
83*> \verbatim
84*> NRHS is INTEGER
85*> The number of right hand sides, i.e., the number of columns
86*> of the matrix B. NRHS >= 0.
87*> \endverbatim
88*>
89*> \param[in] A
90*> \verbatim
91*> A is DOUBLE PRECISION array, dimension (LDA,N)
92*> The triangular matrix A. If UPLO = 'U', the leading N-by-N
93*> upper triangular part of the array A contains the upper
94*> triangular matrix, and the strictly lower triangular part of
95*> A is not referenced. If UPLO = 'L', the leading N-by-N lower
96*> triangular part of the array A contains the lower triangular
97*> matrix, and the strictly upper triangular part of A is not
98*> referenced. If DIAG = 'U', the diagonal elements of A are
99*> also not referenced and are assumed to be 1.
100*> \endverbatim
101*>
102*> \param[in] LDA
103*> \verbatim
104*> LDA is INTEGER
105*> The leading dimension of the array A. LDA >= max(1,N).
106*> \endverbatim
107*>
108*> \param[in,out] B
109*> \verbatim
110*> B is DOUBLE PRECISION array, dimension (LDB,NRHS)
111*> On entry, the right hand side matrix B.
112*> On exit, if INFO = 0, the solution matrix X.
113*> \endverbatim
114*>
115*> \param[in] LDB
116*> \verbatim
117*> LDB is INTEGER
118*> The leading dimension of the array B. LDB >= max(1,N).
119*> \endverbatim
120*>
121*> \param[out] INFO
122*> \verbatim
123*> INFO is INTEGER
124*> = 0: successful exit
125*> < 0: if INFO = -i, the i-th argument had an illegal value
126*> > 0: if INFO = i, the i-th diagonal element of A is exactly zero,
127*> indicating that the matrix is singular and the solutions
128*> X have not been computed.
129*> \endverbatim
130*
131* Authors:
132* ========
133*
134*> \author Univ. of Tennessee
135*> \author Univ. of California Berkeley
136*> \author Univ. of Colorado Denver
137*> \author NAG Ltd.
138*
139*> \ingroup trtrs
140*
141* =====================================================================
142 SUBROUTINE dtrtrs( UPLO, TRANS, DIAG, N, NRHS, A, LDA, B, LDB,
143 $ INFO )
144*
145* -- LAPACK computational routine --
146* -- LAPACK is a software package provided by Univ. of Tennessee, --
147* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
148*
149* .. Scalar Arguments ..
150 CHARACTER DIAG, TRANS, UPLO
151 INTEGER INFO, LDA, LDB, N, NRHS
152* ..
153* .. Array Arguments ..
154 DOUBLE PRECISION A( LDA, * ), B( LDB, * )
155* ..
156*
157* =====================================================================
158*
159* .. Parameters ..
160 DOUBLE PRECISION ZERO, ONE
161 parameter( zero = 0.0d+0, one = 1.0d+0 )
162* ..
163* .. Local Scalars ..
164 LOGICAL NOUNIT
165* ..
166* .. External Functions ..
167 LOGICAL LSAME
168 EXTERNAL lsame
169* ..
170* .. External Subroutines ..
171 EXTERNAL dtrsm, xerbla
172* ..
173* .. Intrinsic Functions ..
174 INTRINSIC max
175* ..
176* .. Executable Statements ..
177*
178* Test the input parameters.
179*
180 info = 0
181 nounit = lsame( diag, 'N' )
182 IF( .NOT.lsame( uplo, 'U' ) .AND.
183 $ .NOT.lsame( uplo, 'L' ) ) THEN
184 info = -1
185 ELSE IF( .NOT.lsame( trans, 'N' ) .AND. .NOT.
186 $ lsame( trans, 'T' ) .AND.
187 $ .NOT.lsame( trans, 'C' ) ) THEN
188 info = -2
189 ELSE IF( .NOT.nounit .AND. .NOT.lsame( diag, 'U' ) ) THEN
190 info = -3
191 ELSE IF( n.LT.0 ) THEN
192 info = -4
193 ELSE IF( nrhs.LT.0 ) THEN
194 info = -5
195 ELSE IF( lda.LT.max( 1, n ) ) THEN
196 info = -7
197 ELSE IF( ldb.LT.max( 1, n ) ) THEN
198 info = -9
199 END IF
200 IF( info.NE.0 ) THEN
201 CALL xerbla( 'DTRTRS', -info )
202 RETURN
203 END IF
204*
205* Quick return if possible
206*
207 IF( n.EQ.0 )
208 $ RETURN
209*
210* Check for singularity.
211*
212 IF( nounit ) THEN
213 DO 10 info = 1, n
214 IF( a( info, info ).EQ.zero )
215 $ RETURN
216 10 CONTINUE
217 END IF
218 info = 0
219*
220* Solve A * x = b or A**T * x = b.
221*
222 CALL dtrsm( 'Left', uplo, trans, diag, n, nrhs, one, a, lda, b,
223 $ ldb )
224*
225 RETURN
226*
227* End of DTRTRS
228*
229 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine dtrsm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)
DTRSM
Definition dtrsm.f:181
subroutine dtrtrs(uplo, trans, diag, n, nrhs, a, lda, b, ldb, info)
DTRTRS
Definition dtrtrs.f:144