1 SUBROUTINE ZTRTRS( UPLO, TRANS, DIAG, N, NRHS, A, LDA, B, LDB,
2 $ INFO )
3 *
4 * -- LAPACK routine (version 3.2) --
5 * -- LAPACK is a software package provided by Univ. of Tennessee, --
6 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
7 * November 2006
8 *
9 * .. Scalar Arguments ..
10 CHARACTER DIAG, TRANS, UPLO
11 INTEGER INFO, LDA, LDB, N, NRHS
12 * ..
13 * .. Array Arguments ..
14 COMPLEX*16 A( LDA, * ), B( LDB, * )
15 * ..
16 *
17 * Purpose
18 * =======
19 *
20 * ZTRTRS solves a triangular system of the form
21 *
22 * A * X = B, A**T * X = B, or A**H * X = B,
23 *
24 * where A is a triangular matrix of order N, and B is an N-by-NRHS
25 * matrix. A check is made to verify that A is nonsingular.
26 *
27 * Arguments
28 * =========
29 *
30 * UPLO (input) CHARACTER*1
31 * = 'U': A is upper triangular;
32 * = 'L': A is lower triangular.
33 *
34 * TRANS (input) CHARACTER*1
35 * Specifies the form of the system of equations:
36 * = 'N': A * X = B (No transpose)
37 * = 'T': A**T * X = B (Transpose)
38 * = 'C': A**H * X = B (Conjugate transpose)
39 *
40 * DIAG (input) CHARACTER*1
41 * = 'N': A is non-unit triangular;
42 * = 'U': A is unit triangular.
43 *
44 * N (input) INTEGER
45 * The order of the matrix A. N >= 0.
46 *
47 * NRHS (input) INTEGER
48 * The number of right hand sides, i.e., the number of columns
49 * of the matrix B. NRHS >= 0.
50 *
51 * A (input) COMPLEX*16 array, dimension (LDA,N)
52 * The triangular matrix A. If UPLO = 'U', the leading N-by-N
53 * upper triangular part of the array A contains the upper
54 * triangular matrix, and the strictly lower triangular part of
55 * A is not referenced. If UPLO = 'L', the leading N-by-N lower
56 * triangular part of the array A contains the lower triangular
57 * matrix, and the strictly upper triangular part of A is not
58 * referenced. If DIAG = 'U', the diagonal elements of A are
59 * also not referenced and are assumed to be 1.
60 *
61 * LDA (input) INTEGER
62 * The leading dimension of the array A. LDA >= max(1,N).
63 *
64 * B (input/output) COMPLEX*16 array, dimension (LDB,NRHS)
65 * On entry, the right hand side matrix B.
66 * On exit, if INFO = 0, the solution matrix X.
67 *
68 * LDB (input) INTEGER
69 * The leading dimension of the array B. LDB >= max(1,N).
70 *
71 * INFO (output) INTEGER
72 * = 0: successful exit
73 * < 0: if INFO = -i, the i-th argument had an illegal value
74 * > 0: if INFO = i, the i-th diagonal element of A is zero,
75 * indicating that the matrix is singular and the solutions
76 * X have not been computed.
77 *
78 * =====================================================================
79 *
80 * .. Parameters ..
81 COMPLEX*16 ZERO, ONE
82 PARAMETER ( ZERO = ( 0.0D+0, 0.0D+0 ),
83 $ ONE = ( 1.0D+0, 0.0D+0 ) )
84 * ..
85 * .. Local Scalars ..
86 LOGICAL NOUNIT
87 * ..
88 * .. External Functions ..
89 LOGICAL LSAME
90 EXTERNAL LSAME
91 * ..
92 * .. External Subroutines ..
93 EXTERNAL XERBLA, ZTRSM
94 * ..
95 * .. Intrinsic Functions ..
96 INTRINSIC MAX
97 * ..
98 * .. Executable Statements ..
99 *
100 * Test the input parameters.
101 *
102 INFO = 0
103 NOUNIT = LSAME( DIAG, 'N' )
104 IF( .NOT.LSAME( UPLO, 'U' ) .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
105 INFO = -1
106 ELSE IF( .NOT.LSAME( TRANS, 'N' ) .AND. .NOT.
107 $ LSAME( TRANS, 'T' ) .AND. .NOT.LSAME( TRANS, 'C' ) ) THEN
108 INFO = -2
109 ELSE IF( .NOT.NOUNIT .AND. .NOT.LSAME( DIAG, 'U' ) ) THEN
110 INFO = -3
111 ELSE IF( N.LT.0 ) THEN
112 INFO = -4
113 ELSE IF( NRHS.LT.0 ) THEN
114 INFO = -5
115 ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
116 INFO = -7
117 ELSE IF( LDB.LT.MAX( 1, N ) ) THEN
118 INFO = -9
119 END IF
120 IF( INFO.NE.0 ) THEN
121 CALL XERBLA( 'ZTRTRS', -INFO )
122 RETURN
123 END IF
124 *
125 * Quick return if possible
126 *
127 IF( N.EQ.0 )
128 $ RETURN
129 *
130 * Check for singularity.
131 *
132 IF( NOUNIT ) THEN
133 DO 10 INFO = 1, N
134 IF( A( INFO, INFO ).EQ.ZERO )
135 $ RETURN
136 10 CONTINUE
137 END IF
138 INFO = 0
139 *
140 * Solve A * x = b, A**T * x = b, or A**H * x = b.
141 *
142 CALL ZTRSM( 'Left', UPLO, TRANS, DIAG, N, NRHS, ONE, A, LDA, B,
143 $ LDB )
144 *
145 RETURN
146 *
147 * End of ZTRTRS
148 *
149 END
2 $ INFO )
3 *
4 * -- LAPACK routine (version 3.2) --
5 * -- LAPACK is a software package provided by Univ. of Tennessee, --
6 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
7 * November 2006
8 *
9 * .. Scalar Arguments ..
10 CHARACTER DIAG, TRANS, UPLO
11 INTEGER INFO, LDA, LDB, N, NRHS
12 * ..
13 * .. Array Arguments ..
14 COMPLEX*16 A( LDA, * ), B( LDB, * )
15 * ..
16 *
17 * Purpose
18 * =======
19 *
20 * ZTRTRS solves a triangular system of the form
21 *
22 * A * X = B, A**T * X = B, or A**H * X = B,
23 *
24 * where A is a triangular matrix of order N, and B is an N-by-NRHS
25 * matrix. A check is made to verify that A is nonsingular.
26 *
27 * Arguments
28 * =========
29 *
30 * UPLO (input) CHARACTER*1
31 * = 'U': A is upper triangular;
32 * = 'L': A is lower triangular.
33 *
34 * TRANS (input) CHARACTER*1
35 * Specifies the form of the system of equations:
36 * = 'N': A * X = B (No transpose)
37 * = 'T': A**T * X = B (Transpose)
38 * = 'C': A**H * X = B (Conjugate transpose)
39 *
40 * DIAG (input) CHARACTER*1
41 * = 'N': A is non-unit triangular;
42 * = 'U': A is unit triangular.
43 *
44 * N (input) INTEGER
45 * The order of the matrix A. N >= 0.
46 *
47 * NRHS (input) INTEGER
48 * The number of right hand sides, i.e., the number of columns
49 * of the matrix B. NRHS >= 0.
50 *
51 * A (input) COMPLEX*16 array, dimension (LDA,N)
52 * The triangular matrix A. If UPLO = 'U', the leading N-by-N
53 * upper triangular part of the array A contains the upper
54 * triangular matrix, and the strictly lower triangular part of
55 * A is not referenced. If UPLO = 'L', the leading N-by-N lower
56 * triangular part of the array A contains the lower triangular
57 * matrix, and the strictly upper triangular part of A is not
58 * referenced. If DIAG = 'U', the diagonal elements of A are
59 * also not referenced and are assumed to be 1.
60 *
61 * LDA (input) INTEGER
62 * The leading dimension of the array A. LDA >= max(1,N).
63 *
64 * B (input/output) COMPLEX*16 array, dimension (LDB,NRHS)
65 * On entry, the right hand side matrix B.
66 * On exit, if INFO = 0, the solution matrix X.
67 *
68 * LDB (input) INTEGER
69 * The leading dimension of the array B. LDB >= max(1,N).
70 *
71 * INFO (output) INTEGER
72 * = 0: successful exit
73 * < 0: if INFO = -i, the i-th argument had an illegal value
74 * > 0: if INFO = i, the i-th diagonal element of A is zero,
75 * indicating that the matrix is singular and the solutions
76 * X have not been computed.
77 *
78 * =====================================================================
79 *
80 * .. Parameters ..
81 COMPLEX*16 ZERO, ONE
82 PARAMETER ( ZERO = ( 0.0D+0, 0.0D+0 ),
83 $ ONE = ( 1.0D+0, 0.0D+0 ) )
84 * ..
85 * .. Local Scalars ..
86 LOGICAL NOUNIT
87 * ..
88 * .. External Functions ..
89 LOGICAL LSAME
90 EXTERNAL LSAME
91 * ..
92 * .. External Subroutines ..
93 EXTERNAL XERBLA, ZTRSM
94 * ..
95 * .. Intrinsic Functions ..
96 INTRINSIC MAX
97 * ..
98 * .. Executable Statements ..
99 *
100 * Test the input parameters.
101 *
102 INFO = 0
103 NOUNIT = LSAME( DIAG, 'N' )
104 IF( .NOT.LSAME( UPLO, 'U' ) .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
105 INFO = -1
106 ELSE IF( .NOT.LSAME( TRANS, 'N' ) .AND. .NOT.
107 $ LSAME( TRANS, 'T' ) .AND. .NOT.LSAME( TRANS, 'C' ) ) THEN
108 INFO = -2
109 ELSE IF( .NOT.NOUNIT .AND. .NOT.LSAME( DIAG, 'U' ) ) THEN
110 INFO = -3
111 ELSE IF( N.LT.0 ) THEN
112 INFO = -4
113 ELSE IF( NRHS.LT.0 ) THEN
114 INFO = -5
115 ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
116 INFO = -7
117 ELSE IF( LDB.LT.MAX( 1, N ) ) THEN
118 INFO = -9
119 END IF
120 IF( INFO.NE.0 ) THEN
121 CALL XERBLA( 'ZTRTRS', -INFO )
122 RETURN
123 END IF
124 *
125 * Quick return if possible
126 *
127 IF( N.EQ.0 )
128 $ RETURN
129 *
130 * Check for singularity.
131 *
132 IF( NOUNIT ) THEN
133 DO 10 INFO = 1, N
134 IF( A( INFO, INFO ).EQ.ZERO )
135 $ RETURN
136 10 CONTINUE
137 END IF
138 INFO = 0
139 *
140 * Solve A * x = b, A**T * x = b, or A**H * x = b.
141 *
142 CALL ZTRSM( 'Left', UPLO, TRANS, DIAG, N, NRHS, ONE, A, LDA, B,
143 $ LDB )
144 *
145 RETURN
146 *
147 * End of ZTRTRS
148 *
149 END