SSYR2K performs one of the symmetric rank 2k operations C := alphaABT + alphaBAT + betaC, or C := alphaATB + alphaBTA + betaC, 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.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=1), | intent(in) | :: | uplo | |||
character(len=1), | intent(in) | :: | trans | |||
integer(kind=ilp), | intent(in) | :: | n | |||
integer(kind=ilp), | intent(in) | :: | k | |||
real(kind=sp), | intent(in) | :: | alpha | |||
real(kind=sp), | intent(in) | :: | a(lda,*) | |||
integer(kind=ilp), | intent(in) | :: | lda | |||
real(kind=sp), | intent(in) | :: | b(ldb,*) | |||
integer(kind=ilp), | intent(in) | :: | ldb | |||
real(kind=sp), | intent(in) | :: | beta | |||
real(kind=sp), | intent(inout) | :: | c(ldc,*) | |||
integer(kind=ilp), | intent(in) | :: | ldc |
pure subroutine stdlib_ssyr2k(uplo,trans,n,k,alpha,a,lda,b,ldb,beta,c,ldc) !! SSYR2K performs one of the symmetric rank 2k operations !! C := alpha*A*B**T + alpha*B*A**T + beta*C, !! or !! C := alpha*A**T*B + alpha*B**T*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. ! -- reference blas level3 routine -- ! -- reference blas is a software package provided by univ. of tennessee, -- ! -- univ. of california berkeley, univ. of colorado denver and nag ltd..-- ! Scalar Arguments real(sp), intent(in) :: alpha, beta integer(ilp), intent(in) :: k, lda, ldb, ldc, n character, intent(in) :: trans, uplo ! Array Arguments real(sp), intent(in) :: a(lda,*), b(ldb,*) real(sp), intent(inout) :: c(ldc,*) ! ===================================================================== ! Intrinsic Functions intrinsic :: max ! Local Scalars real(sp) :: temp1, temp2 integer(ilp) :: i, info, j, l, nrowa logical(lk) :: upper ! test the input parameters. if (stdlib_lsame(trans,'N')) then nrowa = n else nrowa = k end if upper = stdlib_lsame(uplo,'U') info = 0 if ((.not.upper) .and. (.not.stdlib_lsame(uplo,'L'))) then info = 1 else if ((.not.stdlib_lsame(trans,'N')) .and.(.not.stdlib_lsame(trans,'T')) .and.(& .not.stdlib_lsame(trans,'C'))) then info = 2 else if (n<0) then info = 3 else if (k<0) then info = 4 else if (lda<max(1,nrowa)) then info = 7 else if (ldb<max(1,nrowa)) then info = 9 else if (ldc<max(1,n)) then info = 12 end if if (info/=0) then call stdlib_xerbla('SSYR2K',info) return end if ! quick return if possible. if ((n==0) .or. (((alpha==zero).or.(k==0)).and. (beta==one))) return ! and when alpha.eq.zero. if (alpha==zero) then if (upper) then if (beta==zero) then do j = 1,n do i = 1,j c(i,j) = zero end do end do else do j = 1,n do i = 1,j c(i,j) = beta*c(i,j) end do end do end if else if (beta==zero) then do j = 1,n do i = j,n c(i,j) = zero end do end do else do j = 1,n do i = j,n c(i,j) = beta*c(i,j) end do end do end if end if return end if ! start the operations. if (stdlib_lsame(trans,'N')) then ! form c := alpha*a*b**t + alpha*b*a**t + c. if (upper) then do j = 1,n if (beta==zero) then do i = 1,j c(i,j) = zero end do else if (beta/=one) then do i = 1,j c(i,j) = beta*c(i,j) end do end if do l = 1,k if ((a(j,l)/=zero) .or. (b(j,l)/=zero)) then temp1 = alpha*b(j,l) temp2 = alpha*a(j,l) do i = 1,j c(i,j) = c(i,j) + a(i,l)*temp1 +b(i,l)*temp2 end do end if end do end do else do j = 1,n if (beta==zero) then do i = j,n c(i,j) = zero end do else if (beta/=one) then do i = j,n c(i,j) = beta*c(i,j) end do end if do l = 1,k if ((a(j,l)/=zero) .or. (b(j,l)/=zero)) then temp1 = alpha*b(j,l) temp2 = alpha*a(j,l) do i = j,n c(i,j) = c(i,j) + a(i,l)*temp1 +b(i,l)*temp2 end do end if end do end do end if else ! form c := alpha*a**t*b + alpha*b**t*a + c. if (upper) then do j = 1,n do i = 1,j temp1 = zero temp2 = zero do l = 1,k temp1 = temp1 + a(l,i)*b(l,j) temp2 = temp2 + b(l,i)*a(l,j) end do if (beta==zero) then c(i,j) = alpha*temp1 + alpha*temp2 else c(i,j) = beta*c(i,j) + alpha*temp1 +alpha*temp2 end if end do end do else do j = 1,n do i = j,n temp1 = zero temp2 = zero do l = 1,k temp1 = temp1 + a(l,i)*b(l,j) temp2 = temp2 + b(l,i)*a(l,j) end do if (beta==zero) then c(i,j) = alpha*temp1 + alpha*temp2 else c(i,j) = beta*c(i,j) + alpha*temp1 +alpha*temp2 end if end do end do end if end if return end subroutine stdlib_ssyr2k