📄 scfblas.f
字号:
** Set NOTA and NOTB as true if A and B respectively are not* transposed, and set NROWA, NCOLA and NROWB as the number of rows* and columns of A and the number of rows of B respectively.* NOTA = LSAME( TRANSA, 'N' ) NOTB = LSAME( TRANSB, 'N' ) IF( NOTA )THEN NROWA = M NCOLA = K ELSE NROWA = K NCOLA = M END IF IF( NOTB )THEN NROWB = K ELSE NROWB = N END IF** Test the input parameters.* INFO = 0 IF( ( .NOT.NOTA ).AND. $ ( .NOT.LSAME( TRANSA, 'T' ) ).AND. $ ( .NOT.LSAME( TRANSA, 'C' ) ) )THEN INFO = 1 ELSE IF( ( .NOT.NOTB ).AND. $ ( .NOT.LSAME( TRANSB, 'T' ) ).AND. $ ( .NOT.LSAME( TRANSB, 'C' ) ) )THEN INFO = 2 ELSE IF( M.LT.0 )THEN INFO = 3 ELSE IF( N.LT.0 )THEN INFO = 4 ELSE IF( K.LT.0 )THEN INFO = 5 ELSE IF( LDA.LT.MAX( 1, NROWA ) )THEN INFO = 8 ELSE IF( LDB.LT.MAX( 1, NROWB ) )THEN INFO = 10 ELSE IF( LDC.LT.MAX( 1, M ) )THEN INFO = 13 END IF IF( INFO.NE.0 )THEN CALL XERBLA( 'DGEMM ', INFO ) RETURN END IF** Quick return if possible.* IF( ( M.EQ.0 ).OR.( N.EQ.0 ).OR. $ ( ( ( ALPHA.EQ.ZERO ).or.( K.EQ.0 ) ).AND.( BETA.EQ.ONE ) ) ) $ RETURN** Start the operations.* IF( K.EQ.0 )THEN** Form C := beta*C.* IF( BETA.EQ.ZERO )THEN DO 20, J = 1, N DO 10, I = 1, M C( I, J ) = ZERO 10 CONTINUE 20 CONTINUE ELSE DO 40, J = 1, N DO 30, I = 1, M C( I, J ) = BETA*C( I, J ) 30 CONTINUE 40 CONTINUE END IF ELSE IF( NOTB )THEN** Form C := alpha*op( A )*B + beta*C.* DO 50, J = 1, N CALL DGEMV ( TRANSA, NROWA, NCOLA, $ ALPHA, A, LDA, B( 1, J ), 1, $ BETA, C( 1, J ), 1 ) 50 CONTINUE ELSE** Form C := alpha*op( A )*B' + beta*C.* DO 60, J = 1, N CALL DGEMV ( TRANSA, NROWA, NCOLA, $ ALPHA, A, LDA, B( J, 1 ), LDB, $ BETA, C( 1, J ), 1 ) 60 CONTINUE END IF* RETURN** End of DGEMM .* END LOGICAL FUNCTION LSAME ( CA, CB )* .. Scalar Arguments .. CHARACTER*1 CA, CB* ..** Purpose* =======** LSAME tests if CA is the same letter as CB regardless of case.* CB is assumed to be an upper case letter. LSAME returns .TRUE. if* CA is either the same as CB or the equivalent lower case letter.** N.B. This version of the routine is only correct for ASCII code.* Installers must modify the routine for other character-codes.** For EBCDIC systems the constant IOFF must be changed to -64.* For CDC systems using 6-12 bit representations, the system-* specific code in comments must be activated.** Parameters* ==========** CA - CHARACTER*1* CB - CHARACTER*1* On entry, CA and CB specify characters to be compared.* Unchanged on exit.*** Auxiliary routine for Level 2 Blas.** -- Written on 20-July-1986* Richard Hanson, Sandia National Labs.* Jeremy Du Croz, Nag Central Office.** .. Parameters .. INTEGER IOFF PARAMETER ( IOFF=32 )* .. Intrinsic Functions .. INTRINSIC ICHAR* .. Executable Statements ..** Test if the characters are equal* LSAME = CA .EQ. CB** Now test for equivalence* IF ( .NOT.LSAME ) THEN LSAME = ICHAR(CA) - IOFF .EQ. ICHAR(CB) END IF* RETURN** The following comments contain code for CDC systems using 6-12 bit* representations.** .. Parameters ..* INTEGER ICIRFX* PARAMETER ( ICIRFX=62 )* .. Scalar Arguments ..* CHARACTER*1 CB* .. Array Arguments ..* CHARACTER*1 CA(*)* .. Local Scalars ..* INTEGER IVAL* .. Intrinsic Functions ..* INTRINSIC ICHAR, CHAR* .. Executable Statements ..** See if the first character in string CA equals string CB.** LSAME = CA(1) .EQ. CB .AND. CA(1) .NE. CHAR(ICIRFX)** IF (LSAME) RETURN** The characters are not identical. Now check them for equivalence.* Look for the 'escape' character, circumflex, followed by the* letter.** IVAL = ICHAR(CA(2))* IF (IVAL.GE.ICHAR('A') .AND. IVAL.LE.ICHAR('Z')) THEN* LSAME = CA(1) .EQ. CHAR(ICIRFX) .AND. CA(2) .EQ. CB* END IF** RETURN** End of LSAME.* END SUBROUTINE XERBLA ( SRNAME, INFO )* .. Scalar Arguments .. INTEGER INFO CHARACTER*6 SRNAME* ..** Purpose* =======** XERBLA is an error handler for the Level 2 BLAS routines.** It is called by the Level 2 BLAS routines if an input parameter is* invalid.** Installers should consider modifying the STOP statement in order to* call system-specific exception-handling facilities.** Parameters* ==========** SRNAME - CHARACTER*6.* On entry, SRNAME specifies the name of the routine which* called XERBLA.** INFO - INTEGER.* On entry, INFO specifies the position of the invalid* parameter in the parameter-list of the calling routine.*** Auxiliary routine for Level 2 Blas.** Written on 20-July-1986.** .. Executable Statements ..* WRITE (*,99999) SRNAME, INFO* STOP*99999 FORMAT ( ' ** On entry to ', A6, ' parameter number ', I2, $ ' had an illegal value' )** End of XERBLA.* END double precision function ddot(n,dx,incx,dy,incy)cc forms the dot product of two vectors.c uses unrolled loops for increments equal to one.c jack dongarra, linpack, 3/11/78.c double precision dx(1),dy(1),dtemp integer i,incx,incy,ix,iy,m,mp1,nc ddot = 0.0d0 dtemp = 0.0d0 if(n.le.0)return if(incx.eq.1.and.incy.eq.1)go to 20cc code for unequal increments or equal incrementsc not equal to 1c ix = 1 iy = 1 if(incx.lt.0)ix = (-n+1)*incx + 1 if(incy.lt.0)iy = (-n+1)*incy + 1 do 10 i = 1,n dtemp = dtemp + dx(ix)*dy(iy) ix = ix + incx iy = iy + incy 10 continue ddot = dtemp returncc code for both increments equal to 1ccc clean-up loopc 20 m = mod(n,5) if( m .eq. 0 ) go to 40 do 30 i = 1,m dtemp = dtemp + dx(i)*dy(i) 30 continue if( n .lt. 5 ) go to 60 40 mp1 = m + 1 do 50 i = mp1,n,5 dtemp = dtemp + dx(i)*dy(i) + dx(i + 1)*dy(i + 1) + * dx(i + 2)*dy(i + 2) + dx(i + 3)*dy(i + 3) + dx(i + 4)*dy(i + 4) 50 continue 60 ddot = dtemp return end subroutine daxpy(n,da,dx,incx,dy,incy)cc constant times a vector plus a vector.c uses unrolled loops for increments equal to one.c jack dongarra, linpack, 3/11/78.c double precision dx(1),dy(1),da integer i,incx,incy,ix,iy,m,mp1,nc if(n.le.0)return if (da .eq. 0.0d0) return if(incx.eq.1.and.incy.eq.1)go to 20cc code for unequal increments or equal incrementsc not equal to 1c ix = 1 iy = 1 if(incx.lt.0)ix = (-n+1)*incx + 1 if(incy.lt.0)iy = (-n+1)*incy + 1 do 10 i = 1,n dy(iy) = dy(iy) + da*dx(ix) ix = ix + incx iy = iy + incy 10 continue returncc code for both increments equal to 1ccc clean-up loopc 20 m = mod(n,4) if( m .eq. 0 ) go to 40 do 30 i = 1,m dy(i) = dy(i) + da*dx(i) 30 continue if( n .lt. 4 ) return 40 mp1 = m + 1 do 50 i = mp1,n,4 dy(i) = dy(i) + da*dx(i) dy(i + 1) = dy(i + 1) + da*dx(i + 1) dy(i + 2) = dy(i + 2) + da*dx(i + 2) dy(i + 3) = dy(i + 3) + da*dx(i + 3) 50 continue return end subroutine dscal(n,da,dx,incx)cc scales a vector by a constant.c uses unrolled loops for increment equal to one.c jack dongarra, linpack, 3/11/78.c double precision da,dx(1) integer i,incx,m,mp1,n,nincxc if(n.le.0)return if(incx.eq.1)go to 20cc code for increment not equal to 1c nincx = n*incx do 10 i = 1,nincx,incx dx(i) = da*dx(i) 10 continue returncc code for increment equal to 1ccc clean-up loopc 20 m = mod(n,5) if( m .eq. 0 ) go to 40 do 30 i = 1,m dx(i) = da*dx(i) 30 continue if( n .lt. 5 ) return 40 mp1 = m + 1 do 50 i = mp1,n,5 dx(i) = da*dx(i) dx(i + 1) = da*dx(i + 1) dx(i + 2) = da*dx(i + 2) dx(i + 3) = da*dx(i + 3) dx(i + 4) = da*dx(i + 4) 50 continue return end subroutine dcopy(n,a,ia,b,ib) implicit real*8 (a-h,o-z) dimension a(ia,*), b(ib,*)cc copy a into bc do 10 i = 1,n b(1,i) = a(1,i) 10 continuec end subroutine drot(n,sx,incx,sy,incy,sc,ss) implicit real*8 (a-h,o-z)cc b l a s subprogramc description of parameterscc --input--c n number of elements in input vector(s)c sx double precision vector with n elementsc incx storage spacing between elements of sxc sy single precision vector with n elementsc incy storage spacing between elements of syc sc element of rotation matrixc ss element of rotation matrixcc --output--c sx rotated vector sx (unchanged if n .le. 0)c sy rotated vector sy (unchanged if n .le. 0)cc multiply the 2 x 2 matrix ( sc ss) times the 2 x n matrix (sx**t)c (-ss sc) (sy**t)c where **t indicates transpose. the elements of sx are inc sx(lx+i*incx), i = 0 to n-1, where lx = 1 if incx .ge. 0, elsec lx = (-incx)*n, and similarly for sy using ly and incy. dimension sx(*),sy(*) data zero,one/0.d0,1.d0/ if(n .le. 0 .or. (ss .eq. zero .and. sc .eq. one)) go to 40 if(.not. (incx .eq. incy .and. incx .gt. 0)) go to 20c nsteps=incx*n do 10 i=1,nsteps,incx w=sx(i) z=sy(i) sx(i)=sc*w+ss*z sy(i)=-ss*w+sc*z 10 continue go to 40c 20 continue kx=1 ky=1c if(incx .lt. 0) kx=1-(n-1)*incx if(incy .lt. 0) ky=1-(n-1)*incyc do 30 i=1,n w=sx(kx) z=sy(ky) sx(kx)=sc*w+ss*z sy(ky)=-ss*w+sc*z kx=kx+incx ky=ky+incy 30 continue 40 continuec return end
⌨️ 快捷键说明
复制代码
Ctrl + C
搜索代码
Ctrl + F
全屏模式
F11
切换主题
Ctrl + Shift + D
显示快捷键
?
增大字号
Ctrl + =
减小字号
Ctrl + -