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