ZGEMM performs one of the matrix-matrix operations C := alphaop( A )op( B ) + betaC, where op( X ) is one of op( X ) = X or op( X ) = XT or op( X ) = X*H, alpha and beta are scalars, and A, B and C are matrices, with op( A ) an m by k matrix, op( B ) a k by n matrix and C an m by n matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=1), | intent(in) | :: | transa | |||
character(len=1), | intent(in) | :: | transb | |||
integer(kind=ilp), | intent(in) | :: | m | |||
integer(kind=ilp), | intent(in) | :: | n | |||
integer(kind=ilp), | intent(in) | :: | k | |||
complex(kind=dp), | intent(in) | :: | alpha | |||
complex(kind=dp), | intent(in) | :: | a(lda,*) | |||
integer(kind=ilp), | intent(in) | :: | lda | |||
complex(kind=dp), | intent(in) | :: | b(ldb,*) | |||
integer(kind=ilp), | intent(in) | :: | ldb | |||
complex(kind=dp), | intent(in) | :: | beta | |||
complex(kind=dp), | intent(inout) | :: | c(ldc,*) | |||
integer(kind=ilp), | intent(in) | :: | ldc |
pure subroutine stdlib_zgemm(transa,transb,m,n,k,alpha,a,lda,b,ldb,beta,c,ldc) !! ZGEMM performs one of the matrix-matrix operations !! C := alpha*op( A )*op( B ) + beta*C, !! where op( X ) is one of !! op( X ) = X or op( X ) = X**T or op( X ) = X**H, !! alpha and beta are scalars, and A, B and C are matrices, with op( A ) !! an m by k matrix, op( B ) a k by n matrix and C an m by n matrix. ! -- 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(dp), intent(in) :: alpha, beta integer(ilp), intent(in) :: k, lda, ldb, ldc, m, n character, intent(in) :: transa, transb ! Array Arguments complex(dp), intent(in) :: a(lda,*), b(ldb,*) complex(dp), intent(inout) :: c(ldc,*) ! ===================================================================== ! Intrinsic Functions intrinsic :: conjg,max ! Local Scalars complex(dp) :: temp integer(ilp) :: i, info, j, l, nrowa, nrowb logical(lk) :: conja, conjb, nota, notb ! set nota and notb as true if a and b respectively are not ! conjugated or transposed, set conja and conjb as true if a and ! b respectively are to be transposed but not conjugated and set ! nrowa and nrowb as the number of rows of a and b respectively. nota = stdlib_lsame(transa,'N') notb = stdlib_lsame(transb,'N') conja = stdlib_lsame(transa,'C') conjb = stdlib_lsame(transb,'C') if (nota) then nrowa = m else nrowa = k end if if (notb) then nrowb = k else nrowb = n end if ! test the input parameters. info = 0 if ((.not.nota) .and. (.not.conja) .and.(.not.stdlib_lsame(transa,'T'))) then info = 1 else if ((.not.notb) .and. (.not.conjb) .and.(.not.stdlib_lsame(transb,'T'))) & then info = 2 else if (m<0) then info = 3 else if (n<0) then info = 4 else if (k<0) then info = 5 else if (lda<max(1,nrowa)) then info = 8 else if (ldb<max(1,nrowb)) then info = 10 else if (ldc<max(1,m)) then info = 13 end if if (info/=0) then call stdlib_xerbla('ZGEMM ',info) return end if ! quick return if possible. if ((m==0) .or. (n==0) .or.(((alpha==czero).or. (k==0)).and. (beta==cone))) & return ! and when alpha.eq.czero. if (alpha==czero) then if (beta==czero) then do j = 1,n do i = 1,m c(i,j) = czero end do end do else do j = 1,n do i = 1,m c(i,j) = beta*c(i,j) end do end do end if return end if ! start the operations. if (notb) then if (nota) then ! form c := alpha*a*b + beta*c. do j = 1,n if (beta==czero) then do i = 1,m c(i,j) = czero end do else if (beta/=cone) then do i = 1,m c(i,j) = beta*c(i,j) end do end if do l = 1,k temp = alpha*b(l,j) do i = 1,m c(i,j) = c(i,j) + temp*a(i,l) end do end do end do else if (conja) then ! form c := alpha*a**h*b + beta*c. do j = 1,n do i = 1,m temp = czero do l = 1,k temp = temp + conjg(a(l,i))*b(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 ! form c := alpha*a**t*b + beta*c do j = 1,n do i = 1,m temp = czero do l = 1,k temp = temp + a(l,i)*b(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 else if (nota) then if (conjb) then ! form c := alpha*a*b**h + beta*c. do j = 1,n if (beta==czero) then do i = 1,m c(i,j) = czero end do else if (beta/=cone) then do i = 1,m c(i,j) = beta*c(i,j) end do end if do l = 1,k temp = alpha*conjg(b(j,l)) do i = 1,m c(i,j) = c(i,j) + temp*a(i,l) end do end do end do else ! form c := alpha*a*b**t + beta*c do j = 1,n if (beta==czero) then do i = 1,m c(i,j) = czero end do else if (beta/=cone) then do i = 1,m c(i,j) = beta*c(i,j) end do end if do l = 1,k temp = alpha*b(j,l) do i = 1,m c(i,j) = c(i,j) + temp*a(i,l) end do end do end do end if else if (conja) then if (conjb) then ! form c := alpha*a**h*b**h + beta*c. do j = 1,n do i = 1,m temp = czero do l = 1,k temp = temp + conjg(a(l,i))*conjg(b(j,l)) 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 ! form c := alpha*a**h*b**t + beta*c do j = 1,n do i = 1,m temp = czero do l = 1,k temp = temp + conjg(a(l,i))*b(j,l) 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 else if (conjb) then ! form c := alpha*a**t*b**h + beta*c do j = 1,n do i = 1,m temp = czero do l = 1,k temp = temp + a(l,i)*conjg(b(j,l)) 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 ! form c := alpha*a**t*b**t + beta*c do j = 1,n do i = 1,m temp = czero do l = 1,k temp = temp + a(l,i)*b(j,l) 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_zgemm