dorm2r - multiply a general matrix by the orthogonal matrix from a QR factorization determined by sgeqrf (unblocked algorithm)
SUBROUTINE DORM2R( SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC, WORK, INFO ) CHARACTER*1 SIDE, TRANS INTEGER INFO, K, LDA, LDC, M, N DOUBLE PRECISION A(LDA,*), C(LDC,*), TAU(*), WORK(*) SUBROUTINE DORM2R_64( SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC, WORK, INFO ) CHARACTER*1 SIDE, TRANS INTEGER*8 INFO, K, LDA, LDC, M, N DOUBLE PRECISION A(LDA,*), C(LDC,*), TAU(*), WORK(*) F95 INTERFACE SUBROUTINE ORM2R( SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC, WORK, INFO ) INTEGER :: M, N, K, LDA, LDC, INFO CHARACTER(LEN=1) :: SIDE, TRANS REAL(8), DIMENSION(:,:) :: A, C REAL(8), DIMENSION(:) :: TAU, WORK SUBROUTINE ORM2R_64( SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC, WORK, INFO ) INTEGER(8) :: M, N, K, LDA, LDC, INFO CHARACTER(LEN=1) :: SIDE, TRANS REAL(8), DIMENSION(:,:) :: A, C REAL(8), DIMENSION(:) :: TAU, WORK C INTERFACE #include <sunperf.h> void dorm2r (char side, char trans, int m, int n, int k, double *a, int lda, double *tau, double *c, int ldc, int *info); void dorm2r_64 (char side, char trans, long m, long n, long k, double *a, long lda, double *tau, double *c, long ldc, long *info);
Oracle Solaris Studio Performance Library                           dorm2r(3P)
NAME
       dorm2r  -  multiply a general matrix by the orthogonal matrix from a QR
       factorization determined by sgeqrf (unblocked algorithm)
SYNOPSIS
       SUBROUTINE DORM2R( SIDE, TRANS, M, N, K, A, LDA,  TAU,  C,  LDC,  WORK,
                 INFO )
       CHARACTER*1 SIDE, TRANS
       INTEGER INFO, K, LDA, LDC, M, N
       DOUBLE PRECISION A(LDA,*), C(LDC,*), TAU(*), WORK(*)
       SUBROUTINE  DORM2R_64( SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC, WORK,
                 INFO )
       CHARACTER*1 SIDE, TRANS
       INTEGER*8 INFO, K, LDA, LDC, M, N
       DOUBLE PRECISION A(LDA,*), C(LDC,*), TAU(*), WORK(*)
   F95 INTERFACE
       SUBROUTINE ORM2R( SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC, WORK, INFO
                 )
       INTEGER :: M, N, K, LDA, LDC, INFO
       CHARACTER(LEN=1) :: SIDE, TRANS
       REAL(8), DIMENSION(:,:) :: A, C
       REAL(8), DIMENSION(:) :: TAU, WORK
       SUBROUTINE  ORM2R_64(  SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC, WORK,
                 INFO )
       INTEGER(8) :: M, N, K, LDA, LDC, INFO
       CHARACTER(LEN=1) :: SIDE, TRANS
       REAL(8), DIMENSION(:,:) :: A, C
       REAL(8), DIMENSION(:) :: TAU, WORK
   C INTERFACE
       #include <sunperf.h>
       void dorm2r (char side, char trans, int m, int n, int k, double *a, int
                 lda, double *tau, double *c, int ldc, int *info);
       void  dorm2r_64  (char side, char trans, long m, long n, long k, double
                 *a, long lda, double *tau, double *c, long ldc, long *info);
PURPOSE
       dorm2r overwrites the general real m by n matrix C with
       Q * C  if SIDE = 'L' and TRANS = 'N', or
       Q**T* C  if SIDE = 'L' and TRANS = 'T', or
       C * Q  if SIDE = 'R' and TRANS = 'N', or
       C * Q**T if SIDE = 'R' and TRANS = 'T',
       where Q is a real orthogonal matrix defined as the product of k elemen-
       tary reflectors
       Q = H(1) H(2) . . . H(k)
       as  returned by DGEQRF. Q is of order m if SIDE = 'L' and of order n if
       SIDE = 'R'.
ARGUMENTS
       SIDE (input)
                 SIDE is CHARACTER*1
                 = 'L': apply Q or Q**T from the Left
                 = 'R': apply Q or Q**T from the Right
       TRANS (input)
                 TRANS is CHARACTER*1
                 = 'N': apply Q  (No transpose)
                 = 'T': apply Q**T (Transpose)
       M (input)
                 M is INTEGER
                 The number of rows of the matrix C. M >= 0.
       N (input)
                 N is INTEGER
                 The number of columns of the matrix C. N >= 0.
       K (input)
                 K is INTEGER
                 The number of elementary reflectors whose product defines
                 the matrix Q.
                 If SIDE = 'L', M >= K >= 0;
                 if SIDE = 'R', N >= K >= 0.
       A (input)
                 A is DOUBLE PRECISION array, dimension (LDA,K)
                 The i-th column must contain the vector which defines the
                 elementary reflector H(i), for i = 1,2,...,k, as returned by
                 DGEQRF in the first k columns of its array argument A.
                 A is modified by the routine but restored on exit.
       LDA (input)
                 LDA is INTEGER
                 The leading dimension of the array A.
                 If SIDE = 'L', LDA >= max(1,M);
                 if SIDE = 'R', LDA >= max(1,N).
       TAU (input)
                 TAU is DOUBLE PRECISION array, dimension (K)
                 TAU(i) must contain the scalar factor of the elementary
                 reflector H(i), as returned by DGEQRF.
       C (input/output)
                 C is DOUBLE PRECISION array, 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)
                 LDC is INTEGER
                 The leading dimension of the array C. LDC >= max(1,M).
       WORK (output)
                 WORK is DOUBLE PRECISION array, dimension
                 (N) if SIDE = 'L',
                 (M) if SIDE = 'R'
       INFO (output)
                 INFO is INTEGER
                 = 0: successful exit
                 < 0: if INFO = -i, the i-th argument had an illegal value
                                  7 Nov 2015                        dorm2r(3P)