LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
zgttrs.f
Go to the documentation of this file.
1 *> \brief \b ZGTTRS
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download ZGTTRS + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zgttrs.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zgttrs.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgttrs.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE ZGTTRS( TRANS, N, NRHS, DL, D, DU, DU2, IPIV, B, LDB,
22 * INFO )
23 *
24 * .. Scalar Arguments ..
25 * CHARACTER TRANS
26 * INTEGER INFO, LDB, N, NRHS
27 * ..
28 * .. Array Arguments ..
29 * INTEGER IPIV( * )
30 * COMPLEX*16 B( LDB, * ), D( * ), DL( * ), DU( * ), DU2( * )
31 * ..
32 *
33 *
34 *> \par Purpose:
35 * =============
36 *>
37 *> \verbatim
38 *>
39 *> ZGTTRS solves one of the systems of equations
40 *> A * X = B, A**T * X = B, or A**H * X = B,
41 *> with a tridiagonal matrix A using the LU factorization computed
42 *> by ZGTTRF.
43 *> \endverbatim
44 *
45 * Arguments:
46 * ==========
47 *
48 *> \param[in] TRANS
49 *> \verbatim
50 *> TRANS is CHARACTER*1
51 *> Specifies the form of the system of equations.
52 *> = 'N': A * X = B (No transpose)
53 *> = 'T': A**T * X = B (Transpose)
54 *> = 'C': A**H * X = B (Conjugate transpose)
55 *> \endverbatim
56 *>
57 *> \param[in] N
58 *> \verbatim
59 *> N is INTEGER
60 *> The order of the matrix A.
61 *> \endverbatim
62 *>
63 *> \param[in] NRHS
64 *> \verbatim
65 *> NRHS is INTEGER
66 *> The number of right hand sides, i.e., the number of columns
67 *> of the matrix B. NRHS >= 0.
68 *> \endverbatim
69 *>
70 *> \param[in] DL
71 *> \verbatim
72 *> DL is COMPLEX*16 array, dimension (N-1)
73 *> The (n-1) multipliers that define the matrix L from the
74 *> LU factorization of A.
75 *> \endverbatim
76 *>
77 *> \param[in] D
78 *> \verbatim
79 *> D is COMPLEX*16 array, dimension (N)
80 *> The n diagonal elements of the upper triangular matrix U from
81 *> the LU factorization of A.
82 *> \endverbatim
83 *>
84 *> \param[in] DU
85 *> \verbatim
86 *> DU is COMPLEX*16 array, dimension (N-1)
87 *> The (n-1) elements of the first super-diagonal of U.
88 *> \endverbatim
89 *>
90 *> \param[in] DU2
91 *> \verbatim
92 *> DU2 is COMPLEX*16 array, dimension (N-2)
93 *> The (n-2) elements of the second super-diagonal of U.
94 *> \endverbatim
95 *>
96 *> \param[in] IPIV
97 *> \verbatim
98 *> IPIV is INTEGER array, dimension (N)
99 *> The pivot indices; for 1 <= i <= n, row i of the matrix was
100 *> interchanged with row IPIV(i). IPIV(i) will always be either
101 *> i or i+1; IPIV(i) = i indicates a row interchange was not
102 *> required.
103 *> \endverbatim
104 *>
105 *> \param[in,out] B
106 *> \verbatim
107 *> B is COMPLEX*16 array, dimension (LDB,NRHS)
108 *> On entry, the matrix of right hand side vectors B.
109 *> On exit, B is overwritten by the solution vectors X.
110 *> \endverbatim
111 *>
112 *> \param[in] LDB
113 *> \verbatim
114 *> LDB is INTEGER
115 *> The leading dimension of the array B. LDB >= max(1,N).
116 *> \endverbatim
117 *>
118 *> \param[out] INFO
119 *> \verbatim
120 *> INFO is INTEGER
121 *> = 0: successful exit
122 *> < 0: if INFO = -k, the k-th argument had an illegal value
123 *> \endverbatim
124 *
125 * Authors:
126 * ========
127 *
128 *> \author Univ. of Tennessee
129 *> \author Univ. of California Berkeley
130 *> \author Univ. of Colorado Denver
131 *> \author NAG Ltd.
132 *
133 *> \date September 2012
134 *
135 *> \ingroup complex16GTcomputational
136 *
137 * =====================================================================
138  SUBROUTINE zgttrs( TRANS, N, NRHS, DL, D, DU, DU2, IPIV, B, LDB,
139  $ info )
140 *
141 * -- LAPACK computational routine (version 3.4.2) --
142 * -- LAPACK is a software package provided by Univ. of Tennessee, --
143 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
144 * September 2012
145 *
146 * .. Scalar Arguments ..
147  CHARACTER TRANS
148  INTEGER INFO, LDB, N, NRHS
149 * ..
150 * .. Array Arguments ..
151  INTEGER IPIV( * )
152  COMPLEX*16 B( ldb, * ), D( * ), DL( * ), DU( * ), DU2( * )
153 * ..
154 *
155 * =====================================================================
156 *
157 * .. Local Scalars ..
158  LOGICAL NOTRAN
159  INTEGER ITRANS, J, JB, NB
160 * ..
161 * .. External Functions ..
162  INTEGER ILAENV
163  EXTERNAL ilaenv
164 * ..
165 * .. External Subroutines ..
166  EXTERNAL xerbla, zgtts2
167 * ..
168 * .. Intrinsic Functions ..
169  INTRINSIC max, min
170 * ..
171 * .. Executable Statements ..
172 *
173  info = 0
174  notran = ( trans.EQ.'N' .OR. trans.EQ.'n' )
175  IF( .NOT.notran .AND. .NOT.( trans.EQ.'T' .OR. trans.EQ.
176  $ 't' ) .AND. .NOT.( trans.EQ.'C' .OR. trans.EQ.'c' ) ) THEN
177  info = -1
178  ELSE IF( n.LT.0 ) THEN
179  info = -2
180  ELSE IF( nrhs.LT.0 ) THEN
181  info = -3
182  ELSE IF( ldb.LT.max( n, 1 ) ) THEN
183  info = -10
184  END IF
185  IF( info.NE.0 ) THEN
186  CALL xerbla( 'ZGTTRS', -info )
187  RETURN
188  END IF
189 *
190 * Quick return if possible
191 *
192  IF( n.EQ.0 .OR. nrhs.EQ.0 )
193  $ RETURN
194 *
195 * Decode TRANS
196 *
197  IF( notran ) THEN
198  itrans = 0
199  ELSE IF( trans.EQ.'T' .OR. trans.EQ.'t' ) THEN
200  itrans = 1
201  ELSE
202  itrans = 2
203  END IF
204 *
205 * Determine the number of right-hand sides to solve at a time.
206 *
207  IF( nrhs.EQ.1 ) THEN
208  nb = 1
209  ELSE
210  nb = max( 1, ilaenv( 1, 'ZGTTRS', trans, n, nrhs, -1, -1 ) )
211  END IF
212 *
213  IF( nb.GE.nrhs ) THEN
214  CALL zgtts2( itrans, n, nrhs, dl, d, du, du2, ipiv, b, ldb )
215  ELSE
216  DO 10 j = 1, nrhs, nb
217  jb = min( nrhs-j+1, nb )
218  CALL zgtts2( itrans, n, jb, dl, d, du, du2, ipiv, b( 1, j ),
219  $ ldb )
220  10 CONTINUE
221  END IF
222 *
223 * End of ZGTTRS
224 *
225  END
subroutine zgttrs(TRANS, N, NRHS, DL, D, DU, DU2, IPIV, B, LDB, INFO)
ZGTTRS
Definition: zgttrs.f:140
subroutine zgtts2(ITRANS, N, NRHS, DL, D, DU, DU2, IPIV, B, LDB)
ZGTTS2 solves a system of linear equations with a tridiagonal matrix using the LU factorization compu...
Definition: zgtts2.f:130
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62