SEARCH
NEW RPMS
DIRECTORIES
ABOUT
FAQ
VARIOUS
BLOG
DONATE


YUM REPOSITORY

 
 

MAN page from openSUSE Leap 42 blas-man-3.5.0-9.1.noarch.rpm

chbmv.f

Section: LAPACK (3)
Updated: Fri Nov 4 2016
Index 

NAME

chbmv.f -  

SYNOPSIS


 

Functions/Subroutines


subroutine CHBMV (UPLO, N, K, ALPHA, A, LDA, X, INCX, BETA, Y, INCY)
CHBMV  

Function/Subroutine Documentation

 

subroutine CHBMV (character UPLO, integer N, integer K, complex ALPHA, complex, dimension(lda,*) A, integer LDA, complex, dimension(*) X, integer INCX, complex BETA, complex, dimension(*) Y, integer INCY)

CHBMV

Purpose:

 CHBMV  performs the matrix-vector  operation    y := alpha*A*x + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n hermitian band matrix, with k super-diagonals.


 

Parameters:

UPLO

          UPLO is CHARACTER*1           On entry, UPLO specifies whether the upper or lower           triangular part of the band matrix A is being supplied as           follows:              UPLO = 'U' or 'u'   The upper triangular part of A is                                  being supplied.              UPLO = 'L' or 'l'   The lower triangular part of A is                                  being supplied.


N

          N is INTEGER           On entry, N specifies the order of the matrix A.           N must be at least zero.


K

          K is INTEGER           On entry, K specifies the number of super-diagonals of the           matrix A. K must satisfy  0 .le. K.


ALPHA

          ALPHA is COMPLEX           On entry, ALPHA specifies the scalar alpha.


A

          A is COMPLEX array of DIMENSION ( LDA, n ).           Before entry with UPLO = 'U' or 'u', the leading ( k + 1 )           by n part of the array A must contain the upper triangular           band part of the hermitian matrix, supplied column by           column, with the leading diagonal of the matrix in row           ( k + 1 ) of the array, the first super-diagonal starting at           position 2 in row k, and so on. The top left k by k triangle           of the array A is not referenced.           The following program segment will transfer the upper           triangular part of a hermitian band matrix from conventional           full matrix storage to band storage:                 DO 20, J = 1, N                    M = K + 1 - J                    DO 10, I = MAX( 1, J - K ), J                       A( M + I, J ) = matrix( I, J )              10    CONTINUE              20 CONTINUE           Before entry with UPLO = 'L' or 'l', the leading ( k + 1 )           by n part of the array A must contain the lower triangular           band part of the hermitian matrix, supplied column by           column, with the leading diagonal of the matrix in row 1 of           the array, the first sub-diagonal starting at position 1 in           row 2, and so on. The bottom right k by k triangle of the           array A is not referenced.           The following program segment will transfer the lower           triangular part of a hermitian band matrix from conventional           full matrix storage to band storage:                 DO 20, J = 1, N                    M = 1 - J                    DO 10, I = J, MIN( N, J + K )                       A( M + I, J ) = matrix( I, J )              10    CONTINUE              20 CONTINUE           Note that the imaginary parts of the diagonal elements need           not be set and are assumed to be zero.


LDA

          LDA is INTEGER           On entry, LDA specifies the first dimension of A as declared           in the calling (sub) program. LDA must be at least           ( k + 1 ).


X

          X is COMPLEX array of DIMENSION at least           ( 1 + ( n - 1 )*abs( INCX ) ).           Before entry, the incremented array X must contain the           vector x.


INCX

          INCX is INTEGER           On entry, INCX specifies the increment for the elements of           X. INCX must not be zero.


BETA

          BETA is COMPLEX           On entry, BETA specifies the scalar beta.


Y

          Y is COMPLEX array of DIMENSION at least           ( 1 + ( n - 1 )*abs( INCY ) ).           Before entry, the incremented array Y must contain the           vector y. On exit, Y is overwritten by the updated vector y.


INCY

          INCY is INTEGER           On entry, INCY specifies the increment for the elements of           Y. INCY must not be zero.


 

Author:

Univ. of Tennessee

Univ. of California Berkeley

Univ. of Colorado Denver

NAG Ltd.

Date:

November 2011

Further Details:

  Level 2 Blas routine.  The vector and matrix arguments are not referenced when N = 0, or M = 0  -- Written on 22-October-1986.     Jack Dongarra, Argonne National Lab.     Jeremy Du Croz, Nag Central Office.     Sven Hammarling, Nag Central Office.     Richard Hanson, Sandia National Labs.


 

Definition at line 189 of file chbmv.f.

189 *190 *  -- Reference BLAS level2 routine (version 3.4.0) --191 *  -- Reference BLAS is a software package provided by Univ. of Tennessee,    --192 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--193 *     November 2011194 *195 *     .. Scalar Arguments ..196       COMPLEX alpha,beta197       INTEGER incx,incy,k,lda,n198       CHARACTER uplo199 *     ..200 *     .. Array Arguments ..201       COMPLEX a(lda,*),x(*),y(*)202 *     ..203 *204 *  =====================================================================205 *206 *     .. Parameters ..207       COMPLEX one208       parameter(one= (1.0e+0,0.0e+0))209       COMPLEX zero210       parameter(zero= (0.0e+0,0.0e+0))211 *     ..212 *     .. Local Scalars ..213       COMPLEX temp1,temp2214       INTEGER i,info,ix,iy,j,jx,jy,kplus1,kx,ky,l215 *     ..216 *     .. External Functions ..217       LOGICAL lsame218       EXTERNAL lsame219 *     ..220 *     .. External Subroutines ..221       EXTERNAL xerbla222 *     ..223 *     .. Intrinsic Functions ..224       INTRINSIC conjg,max,min,real225 *     ..226 *227 *     Test the input parameters.228 *229       info = 0230       IF (.NOT.lsame(uplo,'U') .AND. .NOT.lsame(uplo,'L')) THEN231           info = 1232       ELSE IF (n.LT.0) THEN233           info = 2234       ELSE IF (k.LT.0) THEN235           info = 3236       ELSE IF (lda.LT. (k+1)) THEN237           info = 6238       ELSE IF (incx.EQ.0) THEN239           info = 8240       ELSE IF (incy.EQ.0) THEN241           info = 11242       END IF243       IF (info.NE.0) THEN244           CALL xerbla('CHBMV ',info)245           RETURN246       END IF247 *248 *     Quick return if possible.249 *250       IF ((n.EQ.0) .OR. ((alpha.EQ.zero).AND. (beta.EQ.one))) RETURN251 *252 *     Set up the start points in  X  and  Y.253 *254       IF (incx.GT.0) THEN255           kx = 1256       ELSE257           kx = 1 - (n-1)*incx258       END IF259       IF (incy.GT.0) THEN260           ky = 1261       ELSE262           ky = 1 - (n-1)*incy263       END IF264 *265 *     Start the operations. In this version the elements of the array A266 *     are accessed sequentially with one pass through A.267 *268 *     First form  y := beta*y.269 *270       IF (beta.NE.one) THEN271           IF (incy.EQ.1) THEN272               IF (beta.EQ.zero) THEN273                   DO 10 i = 1,n274                       y(i) = zero275    10             CONTINUE276               ELSE277                   DO 20 i = 1,n278                       y(i) = beta*y(i)279    20             CONTINUE280               END IF281           ELSE282               iy = ky283               IF (beta.EQ.zero) THEN284                   DO 30 i = 1,n285                       y(iy) = zero286                       iy = iy + incy287    30             CONTINUE288               ELSE289                   DO 40 i = 1,n290                       y(iy) = beta*y(iy)291                       iy = iy + incy292    40             CONTINUE293               END IF294           END IF295       END IF296       IF (alpha.EQ.zero) RETURN297       IF (lsame(uplo,'U')) THEN298 *299 *        Form  y  when upper triangle of A is stored.300 *301           kplus1 = k + 1302           IF ((incx.EQ.1) .AND. (incy.EQ.1)) THEN303               DO 60 j = 1,n304                   temp1 = alpha*x(j)305                   temp2 = zero306                   l = kplus1 - j307                   DO 50 i = max(1,j-k),j - 1308                       y(i) = y(i) + temp1*a(l+i,j)309                       temp2 = temp2 + conjg(a(l+i,j))*x(i)310    50             CONTINUE311                   y(j) = y(j) + temp1*REAL(A(KPLUS1,J)) + alpha*temp2312    60         CONTINUE313           ELSE314               jx = kx315               jy = ky316               DO 80 j = 1,n317                   temp1 = alpha*x(jx)318                   temp2 = zero319                   ix = kx320                   iy = ky321                   l = kplus1 - j322                   DO 70 i = max(1,j-k),j - 1323                       y(iy) = y(iy) + temp1*a(l+i,j)324                       temp2 = temp2 + conjg(a(l+i,j))*x(ix)325                       ix = ix + incx326                       iy = iy + incy327    70             CONTINUE328                   y(jy) = y(jy) + temp1*REAL(A(KPLUS1,J)) + alpha*temp2329                   jx = jx + incx330                   jy = jy + incy331                   IF (j.GT.k) THEN332                       kx = kx + incx333                       ky = ky + incy334                   END IF335    80         CONTINUE336           END IF337       ELSE338 *339 *        Form  y  when lower triangle of A is stored.340 *341           IF ((incx.EQ.1) .AND. (incy.EQ.1)) THEN342               DO 100 j = 1,n343                   temp1 = alpha*x(j)344                   temp2 = zero345                   y(j) = y(j) + temp1*REAL(a(1,j))346                   l = 1 - j347                   DO 90 i = j + 1,min(n,j+k)348                       y(i) = y(i) + temp1*a(l+i,j)349                       temp2 = temp2 + conjg(a(l+i,j))*x(i)350    90             CONTINUE351                   y(j) = y(j) + alpha*temp2352   100         CONTINUE353           ELSE354               jx = kx355               jy = ky356               DO 120 j = 1,n357                   temp1 = alpha*x(jx)358                   temp2 = zero359                   y(jy) = y(jy) + temp1*REAL(a(1,j))360                   l = 1 - j361                   ix = jx362                   iy = jy363                   DO 110 i = j + 1,min(n,j+k)364                       ix = ix + incx365                       iy = iy + incy366                       y(iy) = y(iy) + temp1*a(l+i,j)367                       temp2 = temp2 + conjg(a(l+i,j))*x(ix)368   110             CONTINUE369                   y(jy) = y(jy) + alpha*temp2370                   jx = jx + incx371                   jy = jy + incy372   120         CONTINUE373           END IF374       END IF375 *376       RETURN377 *378 *     End of CHBMV .379 *
 

Author

Generated automatically by Doxygen for LAPACK from the source code.


 

Index

NAME
SYNOPSIS
Functions/Subroutines
Function/Subroutine Documentation
subroutine CHBMV (character UPLO, integer N, integer K, complex ALPHA, complex, dimension(lda,*) A, integer LDA, complex, dimension(*) X, integer INCX, complex BETA, complex, dimension(*) Y, integer INCY)
Author

This document was created byman2html,using the manual pages.