1       SUBROUTINE ZLSETS( M, P, N, A, AF, LDA, B, BF, LDB, C, CF, D, DF,
  2      $                   X, WORK, LWORK, RWORK, RESULT )
  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       INTEGER            LDA, LDB, LWORK, M, N, P
 10 *     ..
 11 *     .. Array Arguments ..
 12 *
 13 *  Purpose
 14 *  =======
 15 *
 16 *  ZLSETS tests ZGGLSE - a subroutine for solving linear equality
 17 *  constrained least square problem (LSE).
 18 *
 19 *  Arguments
 20 *  =========
 21 *
 22 *  M       (input) INTEGER
 23 *          The number of rows of the matrix A.  M >= 0.
 24 *
 25 *  P       (input) INTEGER
 26 *          The number of rows of the matrix B.  P >= 0.
 27 *
 28 *  N       (input) INTEGER
 29 *          The number of columns of the matrices A and B.  N >= 0.
 30 *
 31 *  A       (input) COMPLEX*16 array, dimension (LDA,N)
 32 *          The M-by-N matrix A.
 33 *
 34 *  AF      (workspace) COMPLEX*16 array, dimension (LDA,N)
 35 *
 36 *  LDA     (input) INTEGER
 37 *          The leading dimension of the arrays A, AF, Q and R.
 38 *          LDA >= max(M,N).
 39 *
 40 *  B       (input) COMPLEX*16 array, dimension (LDB,N)
 41 *          The P-by-N matrix A.
 42 *
 43 *  BF      (workspace) COMPLEX*16 array, dimension (LDB,N)
 44 *
 45 *  LDB     (input) INTEGER
 46 *          The leading dimension of the arrays B, BF, V and S.
 47 *          LDB >= max(P,N).
 48 *
 49 *  C       (input) COMPLEX*16 array, dimension( M )
 50 *          the vector C in the LSE problem.
 51 *
 52 *  CF      (workspace) COMPLEX*16 array, dimension( M )
 53 *
 54 *  D       (input) COMPLEX*16 array, dimension( P )
 55 *          the vector D in the LSE problem.
 56 *
 57 *  DF      (workspace) COMPLEX*16 array, dimension( P )
 58 *
 59 *  X       (output) COMPLEX*16 array, dimension( N )
 60 *          solution vector X in the LSE problem.
 61 *
 62 *  WORK    (workspace) COMPLEX*16 array, dimension (LWORK)
 63 *
 64 *  LWORK   (input) INTEGER
 65 *          The dimension of the array WORK.
 66 *
 67 *  RWORK   (workspace) DOUBLE PRECISION array, dimension (M)
 68 *
 69 *  RESULT  (output) DOUBLE PRECISION array, dimension (2)
 70 *          The test ratios:
 71 *            RESULT(1) = norm( A*x - c )/ norm(A)*norm(X)*EPS
 72 *            RESULT(2) = norm( B*x - d )/ norm(B)*norm(X)*EPS
 73 *
 74 *  ====================================================================
 75 *
 76       DOUBLE PRECISION   RESULT2 ), RWORK( * )
 77       COMPLEX*16         A( LDA, * ), AF( LDA, * ), B( LDB, * ),
 78      $                   BF( LDB, * ), C( * ), CF( * ), D( * ), DF( * ),
 79      $                   WORK( LWORK ), X( * )
 80 *     ..
 81 *     .. Local Scalars ..
 82       INTEGER            INFO
 83 *     ..
 84 *     .. External Subroutines ..
 85       EXTERNAL           ZCOPY, ZGET02, ZGGLSE, ZLACPY
 86 *     ..
 87 *     .. Executable Statements ..
 88 *
 89 *     Copy the matrices A and B to the arrays AF and BF,
 90 *     and the vectors C and D to the arrays CF and DF,
 91 *
 92       CALL ZLACPY( 'Full', M, N, A, LDA, AF, LDA )
 93       CALL ZLACPY( 'Full', P, N, B, LDB, BF, LDB )
 94       CALL ZCOPY( M, C, 1, CF, 1 )
 95       CALL ZCOPY( P, D, 1, DF, 1 )
 96 *
 97 *     Solve LSE problem
 98 *
 99       CALL ZGGLSE( M, N, P, AF, LDA, BF, LDB, CF, DF, X, WORK, LWORK,
100      $             INFO )
101 *
102 *     Test the residual for the solution of LSE
103 *
104 *     Compute RESULT(1) = norm( A*x - c ) / norm(A)*norm(X)*EPS
105 *
106       CALL ZCOPY( M, C, 1, CF, 1 )
107       CALL ZCOPY( P, D, 1, DF, 1 )
108       CALL ZGET02( 'No transpose', M, N, 1, A, LDA, X, N, CF, M, RWORK,
109      $             RESULT1 ) )
110 *
111 *     Compute result(2) = norm( B*x - d ) / norm(B)*norm(X)*EPS
112 *
113       CALL ZGET02( 'No transpose', P, N, 1, B, LDB, X, N, DF, P, RWORK,
114      $             RESULT2 ) )
115 *
116       RETURN
117 *
118 *     End of ZLSETS
119 *
120       END