ssyr2k


NAME

ssyr2k - perform one of the symmetric rank 2k operations C := alpha*A*B' + alpha*B*A' + beta*C or C := alpha*A'*B + alpha*B'*A + beta*C


SYNOPSIS

  SUBROUTINE SSYR2K( UPLO, TRANSA, N, K, ALPHA, A, LDA, B, LDB, BETA, 
 *      C, LDC)
  CHARACTER * 1 UPLO, TRANSA
  INTEGER N, K, LDA, LDB, LDC
  REAL ALPHA, BETA
  REAL A(LDA,*), B(LDB,*), C(LDC,*)
 
  SUBROUTINE SSYR2K_64( UPLO, TRANSA, N, K, ALPHA, A, LDA, B, LDB, 
 *      BETA, C, LDC)
  CHARACTER * 1 UPLO, TRANSA
  INTEGER*8 N, K, LDA, LDB, LDC
  REAL ALPHA, BETA
  REAL A(LDA,*), B(LDB,*), C(LDC,*)
 

F95 INTERFACE

  SUBROUTINE SYR2K( UPLO, [TRANSA], [N], [K], ALPHA, A, [LDA], B, [LDB], 
 *       BETA, C, [LDC])
  CHARACTER(LEN=1) :: UPLO, TRANSA
  INTEGER :: N, K, LDA, LDB, LDC
  REAL :: ALPHA, BETA
  REAL, DIMENSION(:,:) :: A, B, C
 
  SUBROUTINE SYR2K_64( UPLO, [TRANSA], [N], [K], ALPHA, A, [LDA], B, 
 *       [LDB], BETA, C, [LDC])
  CHARACTER(LEN=1) :: UPLO, TRANSA
  INTEGER(8) :: N, K, LDA, LDB, LDC
  REAL :: ALPHA, BETA
  REAL, DIMENSION(:,:) :: A, B, C
 

C INTERFACE

#include <sunperf.h>

void ssyr2k(char uplo, char transa, int n, int k, float alpha, float *a, int lda, float *b, int ldb, float beta, float *c, int ldc);

void ssyr2k_64(char uplo, char transa, long n, long k, float alpha, float *a, long lda, float *b, long ldb, float beta, float *c, long ldc);


PURPOSE

ssyr2k K performs one of the symmetric rank 2k operations C := alpha*A*B' + alpha*B*A' + beta*C or C := alpha*A'*B + alpha*B'*A + beta*C where alpha and beta are scalars, C is an n by n symmetric matrix and A and B are n by k matrices in the first case and k by n matrices in the second case.


ARGUMENTS

* UPLO (input)
On entry, UPLO specifies whether the upper or lower triangular part of the array C is to be referenced as follows:

UPLO = 'U' or 'u' Only the upper triangular part of C is to be referenced.

UPLO = 'L' or 'l' Only the lower triangular part of C is to be referenced.

Unchanged on exit.

* TRANSA (input)
On entry, TRANSA specifies the operation to be performed as follows:

TRANSA = 'N' or 'n' C := alpha*A*B' + alpha*B*A' + beta*C.

TRANSA = 'T' or 't' C := alpha*A'*B + alpha*B'*A + beta*C.

TRANSA = 'C' or 'c' C := alpha*A'*B + alpha*B'*A + beta*C.

Unchanged on exit.

* N (input)
On entry, N specifies the order of the matrix C. N must be at least zero. Unchanged on exit.

* K (input)
On entry with TRANSA = 'N' or 'n', K specifies the number of columns of the matrices A and B, and on entry with TRANSA = 'T' or 't' or 'C' or 'c', K specifies the number of rows of the matrices A and B. K must be at least zero. Unchanged on exit.

* ALPHA (input)
On entry, ALPHA specifies the scalar alpha. Unchanged on exit.

* A (input)
k when TRANSA = 'N' or 'n', and is n otherwise. Before entry with TRANSA = 'N' or 'n', the leading n by k part of the array A must contain the matrix A, otherwise the leading k by n part of the array A must contain the matrix A. Unchanged on exit.

* LDA (input)
On entry, LDA specifies the first dimension of A as declared in the calling (sub) program. When TRANSA = 'N' or 'n' then LDA must be at least max( 1, n ), otherwise LDA must be at least max( 1, k ). Unchanged on exit.

* B (input)
k when TRANSA = 'N' or 'n', and is n otherwise. Before entry with TRANSA = 'N' or 'n', the leading n by k part of the array B must contain the matrix B, otherwise the leading k by n part of the array B must contain the matrix B. Unchanged on exit.

* LDB (input)
On entry, LDB specifies the first dimension of B as declared in the calling (sub) program. When TRANSA = 'N' or 'n' then LDB must be at least max( 1, n ), otherwise LDB must be at least max( 1, k ). Unchanged on exit.

* BETA (input)
On entry, BETA specifies the scalar beta. Unchanged on exit.

* C (input/output)

Before entry with UPLO = 'U' or 'u', the leading n by n upper triangular part of the array C must contain the upper triangular part of the symmetric matrix and the strictly lower triangular part of C is not referenced. On exit, the upper triangular part of the array C is overwritten by the upper triangular part of the updated matrix.

Before entry with UPLO = 'L' or 'l', the leading n by n lower triangular part of the array C must contain the lower triangular part of the symmetric matrix and the strictly upper triangular part of C is not referenced. On exit, the lower triangular part of the array C is overwritten by the lower triangular part of the updated matrix.

* LDC (input)
On entry, LDC specifies the first dimension of C as declared in the calling (sub) program. LDC must be at least max( 1, n ). Unchanged on exit.