Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

dtpqrt (3p)

Name

dtpqrt - tagonal" matrix C, which is composed of a triangular block A and pen- tagonal block B, using the compact WY representation for Q

Synopsis

SUBROUTINE DTPQRT(M, N, L, NB, A, LDA, B, LDB, T, LDT, WORK, INFO)


INTEGER INFO, LDA, LDB, LDT, N, M, L, NB

DOUBLE PRECISION A(LDA,*), B(LDB,*), T(LDT,*), WORK(*)


SUBROUTINE DTPQRT_64(M, N, L, NB, A, LDA, B, LDB, T, LDT, WORK, INFO)


INTEGER*8 INFO, LDA, LDB, LDT, N, M, L, NB

DOUBLE PRECISION A(LDA,*), B(LDB,*), T(LDT,*), WORK(*)


F95 INTERFACE
SUBROUTINE TPQRT(M, N, L, NB, A, LDA, B, LDB, T, LDT, WORK, INFO)


INTEGER :: M, N, L, NB, LDA, LDB, LDT, INFO

REAL(8), DIMENSION(:,:) :: A, B, T

REAL(8), DIMENSION(:) :: WORK


SUBROUTINE TPQRT_64(M, N, L, NB, A, LDA, B, LDB, T, LDT, WORK, INFO)


INTEGER(8) :: M, N, L, NB, LDA, LDB, LDT, INFO

REAL(8), DIMENSION(:,:) :: A, B, T

REAL(8), DIMENSION(:) :: WORK


C INTERFACE
#include <sunperf.h>

void  dtpqrt  (int  m, int n, int l, int nb, double *a, int lda, double
*b, int ldb, double *t, int ldt, int *info);


void dtpqrt_64 (long m, long n, long l, long nb, double *a,  long  lda,
double *b, long ldb, double *t, long ldt, long *info);

Description

Oracle Solaris Studio Performance Library                           dtpqrt(3P)



NAME
       dtpqrt  - compute a blocked QR factorization of a real "triangular-pen-
       tagonal" matrix C, which is composed of a triangular block A  and  pen-
       tagonal block B, using the compact WY representation for Q


SYNOPSIS
       SUBROUTINE DTPQRT(M, N, L, NB, A, LDA, B, LDB, T, LDT, WORK, INFO)


       INTEGER INFO, LDA, LDB, LDT, N, M, L, NB

       DOUBLE PRECISION A(LDA,*), B(LDB,*), T(LDT,*), WORK(*)


       SUBROUTINE DTPQRT_64(M, N, L, NB, A, LDA, B, LDB, T, LDT, WORK, INFO)


       INTEGER*8 INFO, LDA, LDB, LDT, N, M, L, NB

       DOUBLE PRECISION A(LDA,*), B(LDB,*), T(LDT,*), WORK(*)


   F95 INTERFACE
       SUBROUTINE TPQRT(M, N, L, NB, A, LDA, B, LDB, T, LDT, WORK, INFO)


       INTEGER :: M, N, L, NB, LDA, LDB, LDT, INFO

       REAL(8), DIMENSION(:,:) :: A, B, T

       REAL(8), DIMENSION(:) :: WORK


       SUBROUTINE TPQRT_64(M, N, L, NB, A, LDA, B, LDB, T, LDT, WORK, INFO)


       INTEGER(8) :: M, N, L, NB, LDA, LDB, LDT, INFO

       REAL(8), DIMENSION(:,:) :: A, B, T

       REAL(8), DIMENSION(:) :: WORK


   C INTERFACE
       #include <sunperf.h>

       void  dtpqrt  (int  m, int n, int l, int nb, double *a, int lda, double
                 *b, int ldb, double *t, int ldt, int *info);


       void dtpqrt_64 (long m, long n, long l, long nb, double *a,  long  lda,
                 double *b, long ldb, double *t, long ldt, long *info);


PURPOSE
       dtpqrt  computes  a blocked QR factorization of a real "triangular-pen-
       tagonal" matrix C, which is composed of a triangular block A  and  pen-
       tagonal block B, using the compact WY representation for Q.


ARGUMENTS
       M (input)
                 M is INTEGER
                 The number of rows of the matrix B.
                 M >= 0.


       N (input)
                 N is INTEGER
                 The  number  of columns of the matrix B, and the order of the
                 triangular matrix A.
                 N >= 0.


       L (input)
                 L is INTEGER
                 The number of rows of the upper trapezoidal part of B.
                 MIN(M,N) >= L >= 0. See Further Details.


       NB (input)
                 NB is INTEGER
                 The block size to be used in the blocked QR.
                 N >= NB >= 1.


       A (input/output)
                 A is DOUBLE PRECISION array, dimension (LDA,N)
                 On entry, the upper triangular N-by-N matrix A.
                 On exit, the elements on and above the diagonal of the  array
                 contain the upper triangular matrix R.


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


       B (input/output)
                 B is DOUBLE PRECISION array, dimension (LDB,N)
                 On  entry, the pentagonal M-by-N matrix B. The first M-L rows
                 are rectangular, and the last L rows are upper trapezoidal.
                 On exit, B contains the  pentagonal  matrix  V.  See  Further
                 Details.


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


       T (output)
                 T is DOUBLE PRECISION array, dimension (LDT,N)
                 The  upper triangular block reflectors stored in compact form
                 as  a  sequence  of  upper  triangular  blocks.  See  Further
                 Details.


       LDT (input)
                 LDT is INTEGER
                 The leading dimension of the array T.
                 LDT >= NB.


       WORK (output)
                 WORK is DOUBLE PRECISION array, dimension (NB*N)


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


FURTHER DETAILS
       The input matrix C is a (N+M)-by-N matrix

                    C = [ A ]
                        [ B ]

       where  A is an upper triangular N-by-N matrix, and B is M-by-N pentago-
       nal matrix consisting of a (M-L)-by-N rectangular matrix B1 on top of a
       L-by-N upper trapezoidal matrix B2:

                    B = [ B1 ]  <- (M-L)-by-N rectangular
                        [ B2 ]  <-     L-by-N upper trapezoidal.

       The upper trapezoidal matrix B2 consists of the first L rows of a N-by-
       N upper triangular matrix, where 0 <= L <= MIN(M,N). If L=0, B is  rec-
       tangular M-by-N; if M=L=N, B is upper triangular.

       The  matrix  W stores the elementary reflectors H(i) in the i-th column
       below the diagonal (of A) in the (N+M)-by-N input matrix C

                    C = [ A ]  <- upper triangular N-by-N
                        [ B ]  <- M-by-N pentagonal

       so that W can be represented as

                    W = [ I ]  <- identity, N-by-N
                        [ V ]  <- M-by-N, same form as B.

       Thus, all of information needed for W is contained on exit in B,  which
       we call V above.  Note that V has the same form as B; that is,

                    V = [ V1 ] <- (M-L)-by-N rectangular
                        [ V2 ] <-     L-by-N upper trapezoidal.

       The columns of V represent the vectors which define the H(i)'s.

       The number of blocks is B = ceiling(N/NB), where each block is of order
       NB except for the last block, which is of order IB = N - (B-1)*NB.  For
       each of the B blocks, a upper triangular block reflector factor is com-
       puted: T1, T2, ..., TB.  The NB-by-NB (and IB-by-IB for the last block)
       T's are stored in the NB-by-N matrix T as

                    T = [T1 T2 ... TB].




                                  7 Nov 2015                        dtpqrt(3P)