Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

sggglm (3p)

Name

sggglm - Markov linear model (GLM) problem

Synopsis

SUBROUTINE SGGGLM(N, M, P, A, LDA, B, LDB, D, X, Y, WORK, LDWORK,
INFO)

INTEGER N, M, P, LDA, LDB, LDWORK, INFO
REAL A(LDA,*), B(LDB,*), D(*), X(*), Y(*), WORK(*)

SUBROUTINE SGGGLM_64(N, M, P, A, LDA, B, LDB, D, X, Y, WORK, LDWORK,
INFO)

INTEGER*8 N, M, P, LDA, LDB, LDWORK, INFO
REAL A(LDA,*), B(LDB,*), D(*), X(*), Y(*), WORK(*)




F95 INTERFACE
SUBROUTINE GGGLM(N, M, P, A, LDA, B, LDB, D, X, Y, WORK,
LDWORK, INFO)

INTEGER :: N, M, P, LDA, LDB, LDWORK, INFO
REAL, DIMENSION(:) :: D, X, Y, WORK
REAL, DIMENSION(:,:) :: A, B

SUBROUTINE GGGLM_64(N, M, P, A, LDA, B, LDB, D, X, Y, WORK,
LDWORK, INFO)

INTEGER(8) :: N, M, P, LDA, LDB, LDWORK, INFO
REAL, DIMENSION(:) :: D, X, Y, WORK
REAL, DIMENSION(:,:) :: A, B




C INTERFACE
#include <sunperf.h>

void  sggglm(int n, int m, int p, float *a, int lda, float *b, int ldb,
float *d, float *x, float *y, int *info);

void sggglm_64(long n, long m, long p, float *a, long  lda,  float  *b,
long ldb, float *d, float *x, float *y, long *info);

Description

Oracle Solaris Studio Performance Library                           sggglm(3P)



NAME
       sggglm - solve a general Gauss-Markov linear model (GLM) problem


SYNOPSIS
       SUBROUTINE SGGGLM(N, M, P, A, LDA, B, LDB, D, X, Y, WORK, LDWORK,
             INFO)

       INTEGER N, M, P, LDA, LDB, LDWORK, INFO
       REAL A(LDA,*), B(LDB,*), D(*), X(*), Y(*), WORK(*)

       SUBROUTINE SGGGLM_64(N, M, P, A, LDA, B, LDB, D, X, Y, WORK, LDWORK,
             INFO)

       INTEGER*8 N, M, P, LDA, LDB, LDWORK, INFO
       REAL A(LDA,*), B(LDB,*), D(*), X(*), Y(*), WORK(*)




   F95 INTERFACE
       SUBROUTINE GGGLM(N, M, P, A, LDA, B, LDB, D, X, Y, WORK,
              LDWORK, INFO)

       INTEGER :: N, M, P, LDA, LDB, LDWORK, INFO
       REAL, DIMENSION(:) :: D, X, Y, WORK
       REAL, DIMENSION(:,:) :: A, B

       SUBROUTINE GGGLM_64(N, M, P, A, LDA, B, LDB, D, X, Y, WORK,
              LDWORK, INFO)

       INTEGER(8) :: N, M, P, LDA, LDB, LDWORK, INFO
       REAL, DIMENSION(:) :: D, X, Y, WORK
       REAL, DIMENSION(:,:) :: A, B




   C INTERFACE
       #include <sunperf.h>

       void  sggglm(int n, int m, int p, float *a, int lda, float *b, int ldb,
                 float *d, float *x, float *y, int *info);

       void sggglm_64(long n, long m, long p, float *a, long  lda,  float  *b,
                 long ldb, float *d, float *x, float *y, long *info);



PURPOSE
       sggglm solves a general Gauss-Markov linear model (GLM) problem:

               minimize || y ||_2   subject to   d = A*x + B*y
                   x

       where A is an N-by-M matrix, B is an N-by-P matrix, and d is a given N-
       vector. It is 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, which
       is obtained using a generalized QR factorization of A and B.

       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)*(d-A*x) ||_2
                        x

       where inv(B) denotes the inverse of B.


ARGUMENTS
       N (input) The number of rows of the matrices A and B.  N >= 0.


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


       P (input) The number of columns of the matrix B.  P >= N-M.


       A (input/output)
                 On entry, the N-by-M matrix A.  On exit, A is destroyed.


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


       B (input/output)
                 On entry, the N-by-P matrix B.  On exit, B is destroyed.


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


       D (input/output)
                 On  entry,  D  is the left hand side of the GLM equation.  On
                 exit, D is destroyed.


       X (output)
                 On exit, X and Y are the solutions of the GLM problem.


       Y (output)
                 See the description of X.


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


       LDWORK (input)
                 The dimension of the array WORK. LDWORK >= max(1,N+M+P).  For
                 optimum  performance, LDWORK >= M+min(N,P)+max(N,P)*NB, where
                 NB is an upper bound for the optimal blocksizes  for  SGEQRF,
                 SGERQF, SORMQR and SORMRQ.

                 If  LDWORK  = -1, then a workspace query is assumed; the rou-
                 tine 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 illegal value.




                                  7 Nov 2015                        sggglm(3P)