CSYRK performs one of the symmetric rank k operations C := alphaAAT + betaC, or C := alphaATA + betaC, where alpha and beta are scalars, C is an n by n symmetric matrix and A is an n by k matrix in the first case and a k by n matrix 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 | |||
complex(kind=sp), | intent(in) | :: | alpha | |||
complex(kind=sp), | intent(in) | :: | a(lda,*) | |||
integer(kind=ilp), | intent(in) | :: | lda | |||
complex(kind=sp), | intent(in) | :: | beta | |||
complex(kind=sp), | intent(inout) | :: | c(ldc,*) | |||
integer(kind=ilp), | intent(in) | :: | ldc |
pure subroutine stdlib_csyrk(uplo,trans,n,k,alpha,a,lda,beta,c,ldc) !! CSYRK performs one of the symmetric rank k operations !! C := alpha*A*A**T + beta*C, !! or !! C := alpha*A**T*A + beta*C, !! where alpha and beta are scalars, C is an n by n symmetric matrix !! and A is an n by k matrix in the first case and a k by n matrix !! 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 complex(sp), intent(in) :: alpha, beta integer(ilp), intent(in) :: k, lda, ldc, n character, intent(in) :: trans, uplo ! Array Arguments complex(sp), intent(in) :: a(lda,*) complex(sp), intent(inout) :: c(ldc,*) ! ===================================================================== ! Intrinsic Functions intrinsic :: max ! Local Scalars complex(sp) :: temp 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'))) & 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 (ldc<max(1,n)) then info = 10 end if if (info/=0) then call stdlib_xerbla('CSYRK ',info) return end if ! quick return if possible. if ((n==0) .or. (((alpha==czero).or.(k==0)).and. (beta==cone))) return ! and when alpha.eq.czero. if (alpha==czero) then if (upper) then if (beta==czero) then do j = 1,n do i = 1,j c(i,j) = czero 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==czero) then do j = 1,n do i = j,n c(i,j) = czero 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*a**t + beta*c. if (upper) then do j = 1,n if (beta==czero) then do i = 1,j c(i,j) = czero end do else if (beta/=cone) then do i = 1,j c(i,j) = beta*c(i,j) end do end if do l = 1,k if (a(j,l)/=czero) then temp = alpha*a(j,l) do i = 1,j c(i,j) = c(i,j) + temp*a(i,l) end do end if end do end do else do j = 1,n if (beta==czero) then do i = j,n c(i,j) = czero end do else if (beta/=cone) then do i = j,n c(i,j) = beta*c(i,j) end do end if do l = 1,k if (a(j,l)/=czero) then temp = alpha*a(j,l) do i = j,n c(i,j) = c(i,j) + temp*a(i,l) end do end if end do end do end if else ! form c := alpha*a**t*a + beta*c. if (upper) then do j = 1,n do i = 1,j temp = czero do l = 1,k temp = temp + a(l,i)*a(l,j) end do if (beta==czero) then c(i,j) = alpha*temp else c(i,j) = alpha*temp + beta*c(i,j) end if end do end do else do j = 1,n do i = j,n temp = czero do l = 1,k temp = temp + a(l,i)*a(l,j) end do if (beta==czero) then c(i,j) = alpha*temp else c(i,j) = alpha*temp + beta*c(i,j) end if end do end do end if end if return end subroutine stdlib_csyrk