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