PLASMA  2.4.5
PLASMA - Parallel Linear Algebra for Scalable Multi-core Architectures
 All Data Structures Namespaces Files Functions Variables Typedefs Enumerations Enumerator Macros Groups
strtri.f
Go to the documentation of this file.
1  SUBROUTINE strtri( UPLO, DIAG, N, A, LDA, INFO )
2 *
3 * -- LAPACK routine (version 3.2) --
4 * -- LAPACK is a software package provided by Univ. of Tennessee, --
5 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
6 * November 2006
7 *
8 * .. Scalar Arguments ..
9  CHARACTER diag, uplo
10  INTEGER info, lda, n
11 * ..
12 * .. Array Arguments ..
13  REAL a( lda, * )
14 * ..
15 *
16 * Purpose
17 * =======
18 *
19 * STRTRI computes the inverse of a real upper or lower triangular
20 * matrix A.
21 *
22 * This is the Level 3 BLAS version of the algorithm.
23 *
24 * Arguments
25 * =========
26 *
27 * UPLO (input) CHARACTER*1
28 * = 'U': A is upper triangular;
29 * = 'L': A is lower triangular.
30 *
31 * DIAG (input) CHARACTER*1
32 * = 'N': A is non-unit triangular;
33 * = 'U': A is unit triangular.
34 *
35 * N (input) INTEGER
36 * The order of the matrix A. N >= 0.
37 *
38 * A (input/output) REAL array, dimension (LDA,N)
39 * On entry, the triangular matrix A. If UPLO = 'U', the
40 * leading N-by-N upper triangular part of the array A contains
41 * the upper triangular matrix, and the strictly lower
42 * triangular part of A is not referenced. If UPLO = 'L', the
43 * leading N-by-N lower triangular part of the array A contains
44 * the lower triangular matrix, and the strictly upper
45 * triangular part of A is not referenced. If DIAG = 'U', the
46 * diagonal elements of A are also not referenced and are
47 * assumed to be 1.
48 * On exit, the (triangular) inverse of the original matrix, in
49 * the same storage format.
50 *
51 * LDA (input) INTEGER
52 * The leading dimension of the array A. LDA >= max(1,N).
53 *
54 * INFO (output) INTEGER
55 * = 0: successful exit
56 * < 0: if INFO = -i, the i-th argument had an illegal value
57 * > 0: if INFO = i, A(i,i) is exactly zero. The triangular
58 * matrix is singular and its inverse can not be computed.
59 *
60 * =====================================================================
61 *
62 * .. Parameters ..
63  REAL one, zero
64  parameter( one = 1.0e+0, zero = 0.0e+0 )
65 * ..
66 * .. Local Scalars ..
67  LOGICAL nounit, upper
68  INTEGER j, jb, nb, nn
69 * ..
70 * .. External Functions ..
71  LOGICAL lsame
72  INTEGER ilaenv
73  EXTERNAL lsame, ilaenv
74 * ..
75 * .. External Subroutines ..
76  EXTERNAL strmm, strsm, strti2, xerbla
77 * ..
78 * .. Intrinsic Functions ..
79  INTRINSIC max, min
80 * ..
81 * .. Executable Statements ..
82 *
83 * Test the input parameters.
84 *
85  info = 0
86  upper = lsame( uplo, 'U' )
87  nounit = lsame( diag, 'N' )
88  IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
89  info = -1
90  ELSE IF( .NOT.nounit .AND. .NOT.lsame( diag, 'U' ) ) THEN
91  info = -2
92  ELSE IF( n.LT.0 ) THEN
93  info = -3
94  ELSE IF( lda.LT.max( 1, n ) ) THEN
95  info = -5
96  END IF
97  IF( info.NE.0 ) THEN
98  CALL xerbla( 'STRTRI', -info )
99  return
100  END IF
101 *
102 * Quick return if possible
103 *
104  IF( n.EQ.0 )
105  $ return
106 *
107 * Check for singularity if non-unit.
108 *
109  IF( nounit ) THEN
110  DO 10 info = 1, n
111  IF( a( info, info ).EQ.zero )
112  $ return
113  10 continue
114  info = 0
115  END IF
116 *
117 * Determine the block size for this environment.
118 *
119  nb = ilaenv( 1, 'STRTRI', uplo // diag, n, -1, -1, -1 )
120  IF( nb.LE.1 .OR. nb.GE.n ) THEN
121 *
122 * Use unblocked code
123 *
124  CALL strti2( uplo, diag, n, a, lda, info )
125  ELSE
126 *
127 * Use blocked code
128 *
129  IF( upper ) THEN
130 *
131 * Compute inverse of upper triangular matrix
132 *
133  DO 20 j = 1, n, nb
134  jb = min( nb, n-j+1 )
135 *
136 * Compute rows 1:j-1 of current block column
137 *
138  CALL strmm( 'Left', 'Upper', 'No transpose', diag, j-1,
139  $ jb, one, a, lda, a( 1, j ), lda )
140  CALL strsm( 'Right', 'Upper', 'No transpose', diag, j-1,
141  $ jb, -one, a( j, j ), lda, a( 1, j ), lda )
142 *
143 * Compute inverse of current diagonal block
144 *
145  CALL strti2( 'Upper', diag, jb, a( j, j ), lda, info )
146  20 continue
147  ELSE
148 *
149 * Compute inverse of lower triangular matrix
150 *
151  nn = ( ( n-1 ) / nb )*nb + 1
152  DO 30 j = nn, 1, -nb
153  jb = min( nb, n-j+1 )
154  IF( j+jb.LE.n ) THEN
155 *
156 * Compute rows j+jb:n of current block column
157 *
158  CALL strmm( 'Left', 'Lower', 'No transpose', diag,
159  $ n-j-jb+1, jb, one, a( j+jb, j+jb ), lda,
160  $ a( j+jb, j ), lda )
161  CALL strsm( 'Right', 'Lower', 'No transpose', diag,
162  $ n-j-jb+1, jb, -one, a( j, j ), lda,
163  $ a( j+jb, j ), lda )
164  END IF
165 *
166 * Compute inverse of current diagonal block
167 *
168  CALL strti2( 'Lower', diag, jb, a( j, j ), lda, info )
169  30 continue
170  END IF
171  END IF
172 *
173  return
174 *
175 * End of STRTRI
176 *
177  END