3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download CTPTRS + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/ctptrs.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/ctptrs.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ctptrs.f">
21 * SUBROUTINE CTPTRS( UPLO, TRANS, DIAG, N, NRHS, AP, B, LDB, INFO )
23 * .. Scalar Arguments ..
24 * CHARACTER DIAG, TRANS, UPLO
25 * INTEGER INFO, LDB, N, NRHS
27 * .. Array Arguments ..
28 * COMPLEX AP( * ), B( LDB, * )
37 *> CTPTRS solves a triangular system of the form
39 *> A * X = B, A**T * X = B, or A**H * X = B,
41 *> where A is a triangular matrix of order N stored in packed format,
42 *> and B is an N-by-NRHS matrix. A check is made to verify that A is
51 *> UPLO is CHARACTER*1
52 *> = 'U': A is upper triangular;
53 *> = 'L': A is lower triangular.
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)
67 *> DIAG is CHARACTER*1
68 *> = 'N': A is non-unit triangular;
69 *> = 'U': A is unit triangular.
75 *> The order of the matrix A. N >= 0.
81 *> The number of right hand sides, i.e., the number of columns
82 *> of the matrix B. NRHS >= 0.
87 *> AP is COMPLEX array, dimension (N*(N+1)/2)
88 *> The upper or lower triangular matrix A, packed columnwise in
89 *> a linear array. The j-th column of A is stored in the array
91 *> if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
92 *> if UPLO = 'L', AP(i + (j-1)*(2*n-j)/2) = A(i,j) for j<=i<=n.
97 *> B is COMPLEX array, dimension (LDB,NRHS)
98 *> On entry, the right hand side matrix B.
99 *> On exit, if INFO = 0, the solution matrix X.
105 *> The leading dimension of the array B. LDB >= max(1,N).
111 *> = 0: successful exit
112 *> < 0: if INFO = -i, the i-th argument had an illegal value
113 *> > 0: if INFO = i, the i-th diagonal element of A is zero,
114 *> indicating that the matrix is singular and the
115 *> solutions X have not been computed.
121 *> \author Univ. of Tennessee
122 *> \author Univ. of California Berkeley
123 *> \author Univ. of Colorado Denver
126 *> \date November 2011
128 *> \ingroup complexOTHERcomputational
130 * =====================================================================
131 SUBROUTINE CTPTRS( UPLO, TRANS, DIAG, N, NRHS, AP, B, LDB, INFO )
133 * -- LAPACK computational routine (version 3.4.0) --
134 * -- LAPACK is a software package provided by Univ. of Tennessee, --
135 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
138 * .. Scalar Arguments ..
139 CHARACTER DIAG, TRANS, UPLO
140 INTEGER INFO, LDB, N, NRHS
142 * .. Array Arguments ..
143 COMPLEX AP( * ), B( LDB, * )
146 * =====================================================================
150 PARAMETER ( ZERO = ( 0.0E+0, 0.0E+0 ) )
152 * .. Local Scalars ..
153 LOGICAL NOUNIT, UPPER
156 * .. External Functions ..
160 * .. External Subroutines ..
161 EXTERNAL CTPSV, XERBLA
163 * .. Intrinsic Functions ..
166 * .. Executable Statements ..
168 * Test the input parameters.
171 UPPER = LSAME( UPLO, 'U' )
172 NOUNIT = LSAME( DIAG, 'N' )
173 IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
175 ELSE IF( .NOT.LSAME( TRANS, 'N' ) .AND. .NOT.
176 $ LSAME( TRANS, 'T' ) .AND. .NOT.LSAME( TRANS, 'C' ) ) THEN
178 ELSE IF( .NOT.NOUNIT .AND. .NOT.LSAME( DIAG, 'U' ) ) THEN
180 ELSE IF( N.LT.0 ) THEN
182 ELSE IF( NRHS.LT.0 ) THEN
184 ELSE IF( LDB.LT.MAX( 1, N ) ) THEN
188 CALL XERBLA( 'CTPTRS', -INFO )
192 * Quick return if possible
197 * Check for singularity.
203 IF( AP( JC+INFO-1 ).EQ.ZERO )
210 IF( AP( JC ).EQ.ZERO )
212 JC = JC + N - INFO + 1
218 * Solve A * x = b, A**T * x = b, or A**H * x = b.
221 CALL CTPSV( UPLO, TRANS, DIAG, N, AP, B( 1, J ), 1 )