Contents


NAME

     sgels - solve overdetermined or underdetermined real  linear
     systems  involving  an  M-by-N  matrix  A, or its transpose,
     using a QR or LQ factorization of A

SYNOPSIS

     SUBROUTINE SGELS(TRANSA, M, N, NRHS, A, LDA, B, LDB, WORK, LDWORK,
           INFO)

     CHARACTER * 1 TRANSA
     INTEGER M, N, NRHS, LDA, LDB, LDWORK, INFO
     REAL A(LDA,*), B(LDB,*), WORK(*)

     SUBROUTINE SGELS_64(TRANSA, M, N, NRHS, A, LDA, B, LDB, WORK, LDWORK,
           INFO)

     CHARACTER * 1 TRANSA
     INTEGER*8 M, N, NRHS, LDA, LDB, LDWORK, INFO
     REAL A(LDA,*), B(LDB,*), WORK(*)

  F95 INTERFACE
     SUBROUTINE GELS([TRANSA], [M], [N], [NRHS], A, [LDA], B, [LDB], [WORK],
            LDWORK, [INFO])

     CHARACTER(LEN=1) :: TRANSA
     INTEGER :: M, N, NRHS, LDA, LDB, LDWORK, INFO
     REAL, DIMENSION(:) :: WORK
     REAL, DIMENSION(:,:) :: A, B

     SUBROUTINE GELS_64([TRANSA], [M], [N], [NRHS], A, [LDA], B, [LDB],
            [WORK], LDWORK, [INFO])

     CHARACTER(LEN=1) :: TRANSA
     INTEGER(8) :: M, N, NRHS, LDA, LDB, LDWORK, INFO
     REAL, DIMENSION(:) :: WORK
     REAL, DIMENSION(:,:) :: A, B

  C INTERFACE
     #include <sunperf.h>

     void sgels (char, int, int, int, float*, int,  float*,  int,
               int*);

     void sgels_64 (char, long, long, long, float*, long, float*,
               long, long*);

PURPOSE

     sgels solves overdetermined or underdetermined  real  linear
     systems  involving  an  M-by-N  matrix  A, or its transpose,
     using a QR or LQ factorization of A.  It is assumed  that  A
     has full rank.

     The following options are provided:

     1. If TRANS = 'N' and m >= n:  find the least squares  solu-
     tion of
        an overdetermined system, i.e., solve the  least  squares
     problem
                     minimize || B - A*X ||.

     2. If TRANS = 'N' and m < n:  find the minimum norm solution
     of
        an underdetermined system A * X = B.

     3. If TRANS = 'T' and m >= n:  find the minimum  norm  solu-
     tion of
        an undetermined system A**T * X = B.

     4. If TRANS = 'T' and m < n:  find the least  squares  solu-
     tion of
        an overdetermined system, i.e., solve the  least  squares
     problem
                     minimize || B - A**T * X ||.

     Several right hand side vectors b and solution vectors x can
     be  handled in a single call; they are stored as the columns
     of the M-by-NRHS right hand side matrix B and the  N-by-NRHS
     solution matrix X.

ARGUMENTS

     TRANSA (input)
               = 'N': the linear system involves A;
               = 'T': the linear system involves A**T.

               TRANSA is defaulted to 'N' for F95 INTERFACE.

     M (input) The number of rows of the matrix A.  M >= 0.

     N (input) The number of columns of the matrix A.  N >= 0.

     NRHS (input)
               The number of right hand sides, i.e.,  the  number
               of columns of the matrices B and X. NRHS >=0.
     A (input/output)
               On entry, the M-by-N matrix A.  On exit, if  M  >=
               N,  A is overwritten by details of its QR factori-
               zation as returned by SGEQRF; if  M  <   N,  A  is
               overwritten  by details of its LQ factorization as
               returned by SGELQF.

     LDA (input)
               The leading dimension of  the  array  A.   LDA  >=
               max(1,M).

     B (input/output)
               On entry, the matrix B of right hand side vectors,
               stored columnwise; B is M-by-NRHS if TRANSA = 'N',
               or N-by-NRHS if TRANSA  =  'T'.   On  exit,  B  is
               overwritten   by   the  solution  vectors,  stored
               columnwise:  if TRANSA = 'N' and m >= n, rows 1 to
               n of B contain the least squares solution vectors;
               the residual sum of squares for  the  solution  in
               each column is given by the sum of squares of ele-
               ments N+1 to M in that column; if TRANSA = 'N' and
               m  <  n, rows 1 to N of B contain the minimum norm
               solution vectors; if TRANSA = 'T' and m >= n, rows
               1 to M of B contain the minimum norm solution vec-
               tors; if TRANSA = 'T' and m < n, rows 1 to M of  B
               contain  the  least  squares solution vectors; the
               residual sum of squares for the solution  in  each
               column  is given by the sum of squares of elements
               M+1 to N in that column.

     LDB (input)
               The leading dimension  of  the  array  B.  LDB  >=
               MAX(1,M,N).

     WORK (workspace)
               On exit, if INFO = 0, WORK(1) returns the  optimal
               LDWORK.

     LDWORK (output)
               The dimension of the array WORK.  LDWORK  >=  max(
               1,  MN  +  max( MN, NRHS ) ).  For optimal perfor-
               mance, LDWORK >= max( 1, MN + max( MN,  NRHS  )*NB
               ).   where  MN  =  min(M,N)  and NB is the optimum
               block size.

               If LDWORK = -1, then a workspace query is assumed;
               the  routine  only  calculates the optimal size of
               the WORK array, returns this value  as  the  first
               entry  of  the  WORK  array,  and no error message
               related to LDWORK is issued by XERBLA.

     INFO (output)
               = 0:  successful exit
               < 0:  if INFO = -i, the i-th argument had an ille-
               gal value