Previous: sggbal Up: ../lapack-s.html Next: sgghrd
 NAME
      SGGGLM - solve a generalized linear regression model (GLM)
      problem
 SYNOPSIS
      SUBROUTINE SGGGLM( N, M, P, A, LDA, B, LDB, D, X, Y, WORK,
                         LWORK, INFO )
          INTEGER        INFO, LDA, LDB, LWORK, M, N, P
          REAL           A( LDA, * ), B( LDB, * ), D( * ), WORK( *
                         ), X( * ), Y( * )
 PURPOSE
      SGGGLM solves a generalized linear regression model (GLM)
      problem:
              minimize y'*y     subject to    d = A*x + B*y
                x,y
      using a generalized QR factorization of A and B, where A is
      an N-by-M matrix, B is a given N-by-P matrix, and d is a
      given N vector.  It is also assumed that M <= N <= M+P and
                 rank(A) = M    and    rank([ A B ]) = N.
      Under these assumptions, the constrained equation is always
      consistent, and there is a unique solution x and a minimal
      2-norm solution y.
      In particular, if matrix B is square nonsingular, then the
      problem GLM is equivalent to the following weighted linear
      least squares problem
                   minimize || inv(B)*(b-A*x) ||
                      x
      where ||.|| is vector 2-norm, and inv(B) denotes the inverse
      of matrix B.
 ARGUMENTS
      N       (input) INTEGER
              The number of rows of the matrices A and B.  N >= 0.
      M       (input) INTEGER
              The number of columns of the matrix A.  M >= 0.
      P       (input) INTEGER
              The number of columns of the matrix B.  P >= 0.
              Assume that M <= N <= M+P.
      A       (input/output) REAL array, dimension (LDA,M)
              On entry, the N-by-M matrix A.  On exit, A is
              destroyed.
      LDA     (input) INTEGER
              The leading dimension of the array A. LDA >= max(
              1,N ).
      B       (input/output) REAL array, dimension (LDB,P)
              On entry, the N-by-P matrix B.  On exit, B is des-
              troyed.
      LDB     (input) INTEGER
              The leading dimension of the array B. LDB >= max(
              1,N ).
      D       (input) REAL array, dimension (N)
              On entry, D is the left hand side of the GLM equa-
              tion.  On exit, D is destroyed.
      X       (output) REAL array, dimension (M)
              Y       (output) REAL array, dimension (P) On exit,
              X and Y are the solutions of the GLM problem.
      WORK    (workspace) REAL array, dimension ( LWORK )
              On exit, if INFO = 0, WORK(1) returns the optimal
              LWORK.
      LWORK   (input) INTEGER
              The dimension of the array WORK. LWORK >=
              M+P+max(N,M,P).  For optimum performance, LWORK >=
              M+P+max(N,M,P)*max(NB1,NB2), where NB1 is the
              optimal blocksize for the QR factorization of an N-
              by-M matrix A.  NB2 is the optimal blocksize for the
              RQ factorization of an N-by-P matrix B.
      INFO    (output) INTEGER
              = 0:  successful exit.
              < 0:  if INFO = -i, the i-th argument had an illegal
              value.