Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

sopmtr (3p)

Name

sopmtr - N matrix C with SIDE = 'L' SIDE = 'R' TRANS = 'N'

Synopsis

SUBROUTINE SOPMTR(SIDE, UPLO, TRANS, M, N, AP, TAU, C, LDC, WORK,
INFO)

CHARACTER*1 SIDE, UPLO, TRANS
INTEGER M, N, LDC, INFO
REAL AP(*), TAU(*), C(LDC,*), WORK(*)

SUBROUTINE SOPMTR_64(SIDE, UPLO, TRANS, M, N, AP, TAU, C, LDC, WORK,
INFO)

CHARACTER*1 SIDE, UPLO, TRANS
INTEGER*8 M, N, LDC, INFO
REAL AP(*), TAU(*), C(LDC,*), WORK(*)




F95 INTERFACE
SUBROUTINE OPMTR(SIDE, UPLO, TRANS, M, N, AP, TAU, C, LDC,
WORK, INFO)

CHARACTER(LEN=1) :: SIDE, UPLO, TRANS
INTEGER :: M, N, LDC, INFO
REAL, DIMENSION(:) :: AP, TAU, WORK
REAL, DIMENSION(:,:) :: C

SUBROUTINE OPMTR_64(SIDE, UPLO, TRANS, M, N, AP, TAU, C, LDC,
WORK, INFO)

CHARACTER(LEN=1) :: SIDE, UPLO, TRANS
INTEGER(8) :: M, N, LDC, INFO
REAL, DIMENSION(:) :: AP, TAU, WORK
REAL, DIMENSION(:,:) :: C




C INTERFACE
#include <sunperf.h>

void sopmtr(char side, char uplo, char trans, int m, int n, float  *ap,
float *tau, float *c, int ldc, int *info);

void  sopmtr_64(char side, char uplo, char trans, long m, long n, float
*ap, float *tau, float *c, long ldc, long *info);

Description

Oracle Solaris Studio Performance Library                           sopmtr(3P)



NAME
       sopmtr  -  overwrite the general real M-by-N matrix C with   SIDE = 'L'
       SIDE = 'R' TRANS = 'N'


SYNOPSIS
       SUBROUTINE SOPMTR(SIDE, UPLO, TRANS, M, N, AP, TAU, C, LDC, WORK,
             INFO)

       CHARACTER*1 SIDE, UPLO, TRANS
       INTEGER M, N, LDC, INFO
       REAL AP(*), TAU(*), C(LDC,*), WORK(*)

       SUBROUTINE SOPMTR_64(SIDE, UPLO, TRANS, M, N, AP, TAU, C, LDC, WORK,
             INFO)

       CHARACTER*1 SIDE, UPLO, TRANS
       INTEGER*8 M, N, LDC, INFO
       REAL AP(*), TAU(*), C(LDC,*), WORK(*)




   F95 INTERFACE
       SUBROUTINE OPMTR(SIDE, UPLO, TRANS, M, N, AP, TAU, C, LDC,
              WORK, INFO)

       CHARACTER(LEN=1) :: SIDE, UPLO, TRANS
       INTEGER :: M, N, LDC, INFO
       REAL, DIMENSION(:) :: AP, TAU, WORK
       REAL, DIMENSION(:,:) :: C

       SUBROUTINE OPMTR_64(SIDE, UPLO, TRANS, M, N, AP, TAU, C, LDC,
              WORK, INFO)

       CHARACTER(LEN=1) :: SIDE, UPLO, TRANS
       INTEGER(8) :: M, N, LDC, INFO
       REAL, DIMENSION(:) :: AP, TAU, WORK
       REAL, DIMENSION(:,:) :: C




   C INTERFACE
       #include <sunperf.h>

       void sopmtr(char side, char uplo, char trans, int m, int n, float  *ap,
                 float *tau, float *c, int ldc, int *info);

       void  sopmtr_64(char side, char uplo, char trans, long m, long n, float
                 *ap, float *tau, float *c, long ldc, long *info);



PURPOSE
       sopmtr overwrites the general real M-by-N matrix C with

                       SIDE = 'L'     SIDE = 'R'
       TRANS = 'N':      Q * C          C * Q
       TRANS = 'T':      Q**T * C       C * Q**T

       where Q is a real orthogonal matrix of order nq, with nq = m if SIDE  =
       'L'  and nq = n if SIDE = 'R'. Q is defined as the product of nq-1 ele-
       mentary reflectors, as returned by SSPTRD using packed storage:

       if UPLO = 'U', Q = H(nq-1) . . . H(2) H(1);

       if UPLO = 'L', Q = H(1) H(2) . . . H(nq-1).


ARGUMENTS
       SIDE (input)
                 = 'L': apply Q or Q**T from the Left;
                 = 'R': apply Q or Q**T from the Right.


       UPLO (input)
                 = 'U': Upper triangular packed storage used in previous  call
                 to SSPTRD;
                 =  'L': Lower triangular packed storage used in previous call
                 to SSPTRD.


       TRANS (input)
                 = 'N':  No transpose, apply Q;
                 = 'T':  Transpose, apply Q**T.


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


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


       AP (input)
                 dimension
                 (M*(M+1)/2) if SIDE = 'L'
                 (N*(N+1)/2) if SIDE = 'R'
                 The  vectors  which  define  the  elementary  reflectors,  as
                 returned  by  SSPTRD.   AP  is  modified  by  the routine but
                 restored on exit.


       TAU (input)
                 dimension
                 (M-1) if SIDE = 'L'
                 (N-1) if SIDE = 'R'
                 TAU(i) must contain  the  scalar  factor  of  the  elementary
                 reflector H(i), as returned by SSPTRD.


       C (input/output)
                 dimension (LDC,N)
                 On entry, the M-by-N matrix C.
                 On  exit, C is overwritten by Q*C or Q**T*C or C*Q**T or C*Q.


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


       WORK (workspace)
                 dimension
                 (N) if SIDE = 'L'
                 (M) if SIDE = 'R'


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




                                  7 Nov 2015                        sopmtr(3P)