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
strti2.f
Go to the documentation of this file.
1  SUBROUTINE strti2( 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 * STRTI2 computes the inverse of a real upper or lower triangular
20 * matrix.
21 *
22 * This is the Level 2 BLAS version of the algorithm.
23 *
24 * Arguments
25 * =========
26 *
27 * UPLO (input) CHARACTER*1
28 * Specifies whether the matrix A is upper or lower triangular.
29 * = 'U': Upper triangular
30 * = 'L': Lower triangular
31 *
32 * DIAG (input) CHARACTER*1
33 * Specifies whether or not the matrix A is unit triangular.
34 * = 'N': Non-unit triangular
35 * = 'U': Unit triangular
36 *
37 * N (input) INTEGER
38 * The order of the matrix A. N >= 0.
39 *
40 * A (input/output) REAL array, dimension (LDA,N)
41 * On entry, the triangular matrix A. If UPLO = 'U', the
42 * leading n by n upper triangular part of the array A contains
43 * the upper triangular matrix, and the strictly lower
44 * triangular part of A is not referenced. If UPLO = 'L', the
45 * leading n by n lower triangular part of the array A contains
46 * the lower triangular matrix, and the strictly upper
47 * triangular part of A is not referenced. If DIAG = 'U', the
48 * diagonal elements of A are also not referenced and are
49 * assumed to be 1.
50 *
51 * On exit, the (triangular) inverse of the original matrix, in
52 * the same storage format.
53 *
54 * LDA (input) INTEGER
55 * The leading dimension of the array A. LDA >= max(1,N).
56 *
57 * INFO (output) INTEGER
58 * = 0: successful exit
59 * < 0: if INFO = -k, the k-th argument had an illegal value
60 *
61 * =====================================================================
62 *
63 * .. Parameters ..
64  REAL one
65  parameter( one = 1.0e+0 )
66 * ..
67 * .. Local Scalars ..
68  LOGICAL nounit, upper
69  INTEGER j
70  REAL ajj
71 * ..
72 * .. External Functions ..
73  LOGICAL lsame
74  EXTERNAL lsame
75 * ..
76 * .. External Subroutines ..
77  EXTERNAL sscal, strmv, xerbla
78 * ..
79 * .. Intrinsic Functions ..
80  INTRINSIC max
81 * ..
82 * .. Executable Statements ..
83 *
84 * Test the input parameters.
85 *
86  info = 0
87  upper = lsame( uplo, 'U' )
88  nounit = lsame( diag, 'N' )
89  IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
90  info = -1
91  ELSE IF( .NOT.nounit .AND. .NOT.lsame( diag, 'U' ) ) THEN
92  info = -2
93  ELSE IF( n.LT.0 ) THEN
94  info = -3
95  ELSE IF( lda.LT.max( 1, n ) ) THEN
96  info = -5
97  END IF
98  IF( info.NE.0 ) THEN
99  CALL xerbla( 'STRTI2', -info )
100  return
101  END IF
102 *
103  IF( upper ) THEN
104 *
105 * Compute inverse of upper triangular matrix.
106 *
107  DO 10 j = 1, n
108  IF( nounit ) THEN
109  a( j, j ) = one / a( j, j )
110  ajj = -a( j, j )
111  ELSE
112  ajj = -one
113  END IF
114 *
115 * Compute elements 1:j-1 of j-th column.
116 *
117  CALL strmv( 'Upper', 'No transpose', diag, j-1, a, lda,
118  $ a( 1, j ), 1 )
119  CALL sscal( j-1, ajj, a( 1, j ), 1 )
120  10 continue
121  ELSE
122 *
123 * Compute inverse of lower triangular matrix.
124 *
125  DO 20 j = n, 1, -1
126  IF( nounit ) THEN
127  a( j, j ) = one / a( j, j )
128  ajj = -a( j, j )
129  ELSE
130  ajj = -one
131  END IF
132  IF( j.LT.n ) THEN
133 *
134 * Compute elements j+1:n of j-th column.
135 *
136  CALL strmv( 'Lower', 'No transpose', diag, n-j,
137  $ a( j+1, j+1 ), lda, a( j+1, j ), 1 )
138  CALL sscal( n-j, ajj, a( j+1, j ), 1 )
139  END IF
140  20 continue
141  END IF
142 *
143  return
144 *
145 * End of STRTI2
146 *
147  END