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
zpot02.f
Go to the documentation of this file.
1  SUBROUTINE zpot02( UPLO, N, NRHS, A, LDA, X, LDX, B, LDB, RWORK,
2  $ 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, ldb, ldx, n, nrhs
11  DOUBLE PRECISION resid
12 * ..
13 * .. Array Arguments ..
14  DOUBLE PRECISION rwork( * )
15  COMPLEX*16 a( lda, * ), b( ldb, * ), x( ldx, * )
16 * ..
17 *
18 * Purpose
19 * =======
20 *
21 * ZPOT02 computes the residual for the solution of a Hermitian system
22 * of linear equations A*x = b:
23 *
24 * RESID = norm( B - A*X ) / ( norm(A) * norm(X) + norm(RHS))* N * EPS )
25 *
26 * where EPS is the machine epsilon.
27 *
28 * Arguments
29 * =========
30 *
31 * UPLO (input) CHARACTER*1
32 * Specifies whether the upper or lower triangular part of the
33 * Hermitian matrix A is stored:
34 * = 'U': Upper triangular
35 * = 'L': Lower triangular
36 *
37 * N (input) INTEGER
38 * The number of rows and columns of the matrix A. N >= 0.
39 *
40 * NRHS (input) INTEGER
41 * The number of columns of B, the matrix of right hand sides.
42 * NRHS >= 0.
43 *
44 * A (input) COMPLEX*16 array, dimension (LDA,N)
45 * The original Hermitian matrix A.
46 *
47 * LDA (input) INTEGER
48 * The leading dimension of the array A. LDA >= max(1,N)
49 *
50 * X (input) COMPLEX*16 array, dimension (LDX,NRHS)
51 * The computed solution vectors for the system of linear
52 * equations.
53 *
54 * LDX (input) INTEGER
55 * The leading dimension of the array X. LDX >= max(1,N).
56 *
57 * B (input/output) COMPLEX*16 array, dimension (LDB,NRHS)
58 * On entry, the right hand side vectors for the system of
59 * linear equations.
60 * On exit, B is overwritten with the difference B - A*X.
61 *
62 * LDB (input) INTEGER
63 * The leading dimension of the array B. LDB >= max(1,N).
64 *
65 * RWORK (workspace) DOUBLE PRECISION array, dimension (N)
66 *
67 * RESID (output) DOUBLE PRECISION
68 * The maximum over the number of right hand sides of
69 * norm( B - A*X ) / ( norm(A) * norm(X) + norm(RHS))* N * EPS )
70 *
71 * =====================================================================
72 *
73 * .. Parameters ..
74  DOUBLE PRECISION zero, one
75  parameter( zero = 0.0d+0, one = 1.0d+0 )
76  COMPLEX*16 cone
77  parameter( cone = ( 1.0d+0, 0.0d+0 ) )
78 * ..
79 * .. Local Scalars ..
80  INTEGER j
81  DOUBLE PRECISION anorm, bnorm, eps, xnorm, rhsnorm
82 * ..
83 * .. External Functions ..
84  DOUBLE PRECISION dlamch, dzasum, zlanhe, clange
85  EXTERNAL dlamch, dzasum, zlanhe, clange
86 * ..
87 * .. External Subroutines ..
88  EXTERNAL zhemm
89 * ..
90 * .. Intrinsic Functions ..
91  INTRINSIC max
92 * ..
93 * .. Executable Statements ..
94 *
95 * Quick exit if N = 0 or NRHS = 0.
96 *
97  IF( n.LE.0 .OR. nrhs.LE.0 ) THEN
98  resid = zero
99  return
100  END IF
101 *
102 * Exit with RESID = 1/EPS if ANORM = 0.
103 *
104  eps = dlamch( 'Epsilon' )
105  anorm = zlanhe( '1', uplo, n, a, lda, rwork )
106  rhsnorm = clange( '1', n, nrhs, b, ldb, rwork )
107  IF( anorm.LE.zero ) THEN
108  resid = one / eps
109  return
110  END IF
111 *
112 * Compute B - A*X
113 *
114  CALL zhemm( 'Left', uplo, n, nrhs, -cone, a, lda, x, ldx, cone, b,
115  $ ldb )
116 *
117 * Compute the maximum over the number of right hand sides of
118 * norm( B - A*X ) / ( norm(A) * norm(X) * EPS ) .
119 *
120  resid = zero
121  DO 10 j = 1, nrhs
122  bnorm = dzasum( n, b( 1, j ), 1 )
123  xnorm = dzasum( n, x( 1, j ), 1 )
124  IF( xnorm.LE.zero ) THEN
125  resid = one / eps
126  ELSE
127  resid = max( resid, ( bnorm) / ((anorm * xnorm + rhsnorm)*
128  $ n *eps ))
129  END IF
130  10 continue
131 *
132  return
133 *
134 * End of ZPOT02
135 *
136  END