NAME

zgglse - solve the linear equality-constrained least squares (LSE) problem


SYNOPSIS

  SUBROUTINE ZGGLSE( M, N, P, A, LDA, B, LDB, C, D, X, WORK, LDWORK, 
 *      INFO)
  DOUBLE COMPLEX A(LDA,*), B(LDB,*), C(*), D(*), X(*), WORK(*)
  INTEGER M, N, P, LDA, LDB, LDWORK, INFO
  SUBROUTINE ZGGLSE_64( M, N, P, A, LDA, B, LDB, C, D, X, WORK, 
 *      LDWORK, INFO)
  DOUBLE COMPLEX A(LDA,*), B(LDB,*), C(*), D(*), X(*), WORK(*)
  INTEGER*8 M, N, P, LDA, LDB, LDWORK, INFO

F95 INTERFACE

  SUBROUTINE GGLSE( [M], [N], [P], A, [LDA], B, [LDB], C, D, X, [WORK], 
 *       [LDWORK], [INFO])
  COMPLEX(8), DIMENSION(:) :: C, D, X, WORK
  COMPLEX(8), DIMENSION(:,:) :: A, B
  INTEGER :: M, N, P, LDA, LDB, LDWORK, INFO
  SUBROUTINE GGLSE_64( [M], [N], [P], A, [LDA], B, [LDB], C, D, X, 
 *       [WORK], [LDWORK], [INFO])
  COMPLEX(8), DIMENSION(:) :: C, D, X, WORK
  COMPLEX(8), DIMENSION(:,:) :: A, B
  INTEGER(8) :: M, N, P, LDA, LDB, LDWORK, INFO

C INTERFACE

#include <sunperf.h>

void zgglse(int m, int n, int p, doublecomplex *a, int lda, doublecomplex *b, int ldb, doublecomplex *c, doublecomplex *d, doublecomplex *x, int *info);

void zgglse_64(long m, long n, long p, doublecomplex *a, long lda, doublecomplex *b, long ldb, doublecomplex *c, doublecomplex *d, doublecomplex *x, long *info);


PURPOSE

zgglse solves the linear equality-constrained least squares (LSE) problem:

        minimize || c - A*x ||_2   subject to   B*x = d

where A is an M-by-N matrix, B is a P-by-N matrix, c is a given M-vector, and d is a given P-vector. It is assumed that

P <= N <= M+P, and

         rank(B) = P and  rank( ( A ) ) = N.
                              ( ( B ) )

These conditions ensure that the LSE problem has a unique solution, which is obtained using a GRQ factorization of the matrices B and A.


ARGUMENTS