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
cpot03.f
Go to the documentation of this file.
1  SUBROUTINE cpot03( UPLO, N, A, LDA, AINV, LDAINV, WORK, LDWORK,
2  $ rwork, rcond, resid )
3 *
4 * -- LAPACK test routine (version 3.1) --
5 * Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
6 * November 2006
7 *
8 * .. Scalar Arguments ..
9  CHARACTER uplo
10  INTEGER lda, ldainv, ldwork, n
11  REAL rcond, resid
12 * ..
13 * .. Array Arguments ..
14  REAL rwork( * )
15  COMPLEX a( lda, * ), ainv( ldainv, * ),
16  $ work( ldwork, * )
17 * ..
18 *
19 * Purpose
20 * =======
21 *
22 * CPOT03 computes the residual for a Hermitian matrix times its
23 * inverse:
24 * norm( I - A*AINV ) / ( N * norm(A) * norm(AINV) * EPS ),
25 * where EPS is the machine epsilon.
26 *
27 * Arguments
28 * ==========
29 *
30 * UPLO (input) CHARACTER*1
31 * Specifies whether the upper or lower triangular part of the
32 * Hermitian matrix A is stored:
33 * = 'U': Upper triangular
34 * = 'L': Lower triangular
35 *
36 * N (input) INTEGER
37 * The number of rows and columns of the matrix A. N >= 0.
38 *
39 * A (input) COMPLEX array, dimension (LDA,N)
40 * The original Hermitian matrix A.
41 *
42 * LDA (input) INTEGER
43 * The leading dimension of the array A. LDA >= max(1,N)
44 *
45 * AINV (input/output) COMPLEX array, dimension (LDAINV,N)
46 * On entry, the inverse of the matrix A, stored as a Hermitian
47 * matrix in the same format as A.
48 * In this version, AINV is expanded into a full matrix and
49 * multiplied by A, so the opposing triangle of AINV will be
50 * changed; i.e., if the upper triangular part of AINV is
51 * stored, the lower triangular part will be used as work space.
52 *
53 * LDAINV (input) INTEGER
54 * The leading dimension of the array AINV. LDAINV >= max(1,N).
55 *
56 * WORK (workspace) COMPLEX array, dimension (LDWORK,N)
57 *
58 * LDWORK (input) INTEGER
59 * The leading dimension of the array WORK. LDWORK >= max(1,N).
60 *
61 * RWORK (workspace) REAL array, dimension (N)
62 *
63 * RCOND (output) REAL
64 * The reciprocal of the condition number of A, computed as
65 * ( 1/norm(A) ) / norm(AINV).
66 *
67 * RESID (output) REAL
68 * norm(I - A*AINV) / ( N * norm(A) * norm(AINV) * EPS )
69 *
70 * =====================================================================
71 *
72 * .. Parameters ..
73  REAL zero, one
74  parameter( zero = 0.0e+0, one = 1.0e+0 )
75  COMPLEX czero, cone
76  parameter( czero = ( 0.0e+0, 0.0e+0 ),
77  $ cone = ( 1.0e+0, 0.0e+0 ) )
78 * ..
79 * .. Local Scalars ..
80  INTEGER i, j
81  REAL ainvnm, anorm, eps
82 * ..
83 * .. External Functions ..
84  LOGICAL lsame
85  REAL clange, clanhe, slamch
86  EXTERNAL lsame, clange, clanhe, slamch
87 * ..
88 * .. External Subroutines ..
89  EXTERNAL chemm
90 * ..
91 * .. Intrinsic Functions ..
92  INTRINSIC conjg, real
93 * ..
94 * .. Executable Statements ..
95 *
96 * Quick exit if N = 0.
97 *
98  IF( n.LE.0 ) THEN
99  rcond = one
100  resid = zero
101  return
102  END IF
103 *
104 * Exit with RESID = 1/EPS if ANORM = 0 or AINVNM = 0.
105 *
106  eps = slamch( 'Epsilon' )
107  anorm = clanhe( '1', uplo, n, a, lda, rwork )
108  ainvnm = clanhe( '1', uplo, n, ainv, ldainv, rwork )
109  IF( anorm.LE.zero .OR. ainvnm.LE.zero ) THEN
110  rcond = zero
111  resid = one / eps
112  return
113  END IF
114  rcond = ( one/anorm ) / ainvnm
115 *
116 * Expand AINV into a full matrix and call CHEMM to multiply
117 * AINV on the left by A.
118 *
119  IF( lsame( uplo, 'U' ) ) THEN
120  DO 20 j = 1, n
121  DO 10 i = 1, j - 1
122  ainv( j, i ) = conjg( ainv( i, j ) )
123  10 continue
124  20 continue
125  ELSE
126  DO 40 j = 1, n
127  DO 30 i = j + 1, n
128  ainv( j, i ) = conjg( ainv( i, j ) )
129  30 continue
130  40 continue
131  END IF
132  CALL chemm( 'Left', uplo, n, n, -cone, a, lda, ainv, ldainv,
133  $ czero, work, ldwork )
134 *
135 * Add the identity matrix to WORK .
136 *
137  DO 50 i = 1, n
138  work( i, i ) = work( i, i ) + cone
139  50 continue
140 *
141 * Compute norm(I - A*AINV) / (N * norm(A) * norm(AINV) * EPS)
142 *
143  resid = clange( '1', n, n, work, ldwork, rwork )
144 *
145  resid = ( ( resid*rcond )/eps ) / REAL( n )
146 *
147  return
148 *
149 * End of CPOT03
150 *
151  END