pic_blas_interfaces Module

pic_blas_interfaces.F90 provides the interfaces for the BLAS routines the idea is to have a two level interface, first pic_blas_xyz which is the way programmers will use BLAS, it’ll do some checks and then call the “overloaded” BLAS interfaces to call the correct BLAS routine


Uses

  • module~~pic_blas_interfaces~~UsesGraph module~pic_blas_interfaces pic_blas_interfaces module~pic_types pic_types module~pic_blas_interfaces->module~pic_types iso_fortran_env iso_fortran_env module~pic_types->iso_fortran_env

Interfaces

public interface pic_asum

general interface of the BLAS ASUM routines, will call SASUM, DASUM, SCASUM, DZASUM

Usage: result = pic_asum(x, incx)

where x is a vector and incx is the increment, this will return the sum of the absolute values of the elements of x.

The vector x must be an allocatable array, we deduce the shape from it. The increment incx is 1 by default.

  • private function pic_sasum(x) result(res)

    interface for single precision absolute sum

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: x(:)

    Return Value real(kind=sp)

  • private function pic_dasum(x) result(res)

    interface for double precision absolute sum

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: x(:)

    Return Value real(kind=dp)

  • private function pic_scasum(x) result(res)

    interface for single precision complex absolute sum

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(in) :: x(:)

    Return Value real(kind=sp)

  • private function pic_dzasum(x) result(res)

    interface for double precision complex absolute sum

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(in) :: x(:)

    Return Value real(kind=dp)

public interface pic_axpy

general interface of the BLAS AXPY routines, will call SAXPY, DAXPY, CAXPY, ZAXPY

Usage: call pic_axpy(n, alpha, x, incx, y, incy)

where n is the number of elements, alpha is the scaling factor, x is the input vector, incx is the increment for x, y is the output vector, and incy is the increment for y.

The vectors x and y must be allocatable arrays, we deduce the shapes from them. The increments incx and incy are 1 by default.

  • private subroutine pic_saxpy(x, y, alpha)

    interface for single precision AXPY

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: x(:)
    real(kind=sp), intent(inout) :: y(:)
    real(kind=sp), intent(in), optional :: alpha
  • private subroutine pic_daxpy(x, y, alpha)

    interface for double precision AXPY

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: x(:)
    real(kind=dp), intent(inout) :: y(:)
    real(kind=dp), intent(in), optional :: alpha
  • private subroutine pic_caxpy(x, y, alpha)

    interface for single precision complex AXPY

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(in) :: x(:)
    complex(kind=sp), intent(inout) :: y(:)
    complex(kind=sp), intent(in), optional :: alpha
  • private subroutine pic_zaxpy(x, y, alpha)

    interface for double precision complex AXPY

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(in) :: x(:)
    complex(kind=dp), intent(inout) :: y(:)
    complex(kind=dp), intent(in), optional :: alpha

public interface pic_copy

general interface of the BLAS COPY routines, will call SCOPY, DCOPY, CCOPY, ZCOPY

Usage: call pic_copy(x, y)

where x is the input vector, y is the output vector. The vectors x and y must be allocatable arrays, we deduce the shapes from them.

  • private subroutine pic_scopy(x, y)

    interface for single precision copy

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: x(:)
    real(kind=sp), intent(inout) :: y(:)
  • private subroutine pic_dcopy(x, y)

    interface for double precision copy

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: x(:)
    real(kind=dp), intent(inout) :: y(:)
  • private subroutine pic_ccopy(x, y)

    interface for single precision complex copy

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(in) :: x(:)
    complex(kind=sp), intent(inout) :: y(:)
  • private subroutine pic_zcopy(x, y)

    interface for double precision complex copy

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(in) :: x(:)
    complex(kind=dp), intent(inout) :: y(:)

public interface pic_dot

general interface of the BLAS DOT routines, will call SDOT, DDOT, CDOTC, ZDOTC

Usage: result = pic_dot(x, y)

where x is the input vector, y is the output vector. The vectors x and y must be allocatable arrays, we deduce the shapes from them.

  • private function pic_sdot(x, y) result(res)

    interface for single precision dot product

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: x(:)
    real(kind=sp), intent(in) :: y(:)

    Return Value real(kind=sp)

  • private function pic_ddot(x, y) result(res)

    interface for double precision dot product

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: x(:)
    real(kind=dp), intent(in) :: y(:)

    Return Value real(kind=dp)

  • private function pic_cdotc(x, y) result(res)

    interface for single precision complex dot product

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(in) :: x(:)
    complex(kind=sp), intent(in) :: y(:)

    Return Value complex(kind=sp)

  • private function pic_zdotc(x, y) result(res)

    interface for double precision complex dot product

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(in) :: x(:)
    complex(kind=dp), intent(in) :: y(:)

    Return Value complex(kind=dp)

public interface pic_gemm

general interface of the BLAS GEMM routines, will call SGEMM, DGEMM, CGEMM, ZGEMM

Usage: call pic_gemm(A, B, C, [optional] transa, [optional] transb, [optional] alpha, [optional] beta)

where A, B, C are matrices, transa and transb are optional transpose options, alpha and beta are optional scaling factors

By default, if not specified transA and transB are “N” (no transpose), and alpha and beta are 1.0 and 0.0 respectively.

The matrices A, B, C must be allocatable arrays, we deduce the shapes from them.

  • private pure subroutine pic_sgemm(A, B, C, transa, transb, alpha, beta)

    interface for single precision matrix multiplication

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: A(:,:)
    real(kind=sp), intent(in) :: B(:,:)
    real(kind=sp), intent(inout) :: C(:,:)
    character(len=1), intent(in), optional :: transa
    character(len=1), intent(in), optional :: transb
    real(kind=sp), intent(in), optional :: alpha
    real(kind=sp), intent(in), optional :: beta
  • private pure subroutine pic_dgemm(A, B, C, transa, transb, alpha, beta)

    interface for single precision matrix multiplication

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: A(:,:)
    real(kind=dp), intent(in) :: B(:,:)
    real(kind=dp), intent(inout) :: C(:,:)
    character(len=1), intent(in), optional :: transa
    character(len=1), intent(in), optional :: transb
    real(kind=dp), intent(in), optional :: alpha
    real(kind=dp), intent(in), optional :: beta
  • private pure subroutine pic_zgemm(A, B, C, transa, transb, alpha, beta)

    interface for single precision matrix multiplication

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(in) :: A(:,:)
    complex(kind=dp), intent(in) :: B(:,:)
    complex(kind=dp), intent(inout) :: C(:,:)
    character(len=1), intent(in), optional :: transa
    character(len=1), intent(in), optional :: transb
    complex(kind=dp), intent(in), optional :: alpha
    complex(kind=dp), intent(in), optional :: beta

public interface pic_gemv

general interface of the BLAS GEMV routines, will call SGEMV, DGEMV, CGEMV, ZGEMV

Usage: call pic_gemv(A, x, y, [optional] transa, [optional] alpha, [optional] beta)

where A is a matrix, x and y are vectors, transa is an optional transpose option, alpha and beta are optional scaling factors.

The matrix A must be an allocatable array, we deduce the shapes from it. TransA is “N” (no transpose) by default. And alpha and beta are 1.0 and 0.0 respectively.

  • private pure subroutine pic_sgemv(A, x, y, trans_a, alpha, beta)

    interface for single precision matrix-vector multiplication

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: A(:,:)
    real(kind=sp), intent(in) :: x(:)
    real(kind=sp), intent(inout) :: y(:)
    character(len=1), intent(in), optional :: trans_a
    real(kind=sp), intent(in), optional :: alpha
    real(kind=sp), intent(in), optional :: beta
  • private pure subroutine pic_dgemv(A, x, y, trans_a, alpha, beta)

    interface for double precision matrix-vector multiplication

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: A(:,:)
    real(kind=dp), intent(in) :: x(:)
    real(kind=dp), intent(inout) :: y(:)
    character(len=1), intent(in), optional :: trans_a
    real(kind=dp), intent(in), optional :: alpha
    real(kind=dp), intent(in), optional :: beta

public interface pic_iamax

general interface of the BLAS IAMAX routines, will call ISAMAX, IDAMAX, ICAMAX, IZAMAX

Usage: idx = pic_iamax(x, incx)

where x is the input vector, incx is the increment. The vector x must be an allocatable array, we deduce the shape from it. The increment incx is 1 by default.

  • private function pic_isamax(x) result(idx)

    interface for single precision index of maximum absolute value

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: x(:)

    Return Value integer(kind=default_int)

  • private function pic_idamax(x) result(idx)

    interface for double precision index of maximum absolute value

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: x(:)

    Return Value integer(kind=default_int)

  • private function pic_icamax(x) result(idx)

    interface for single precision complex index of maximum absolute value

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(in) :: x(:)

    Return Value integer(kind=default_int)

  • private function pic_izamax(x) result(idx)

    interface for double precision complex index of maximum absolute value

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(in) :: x(:)

    Return Value integer(kind=default_int)

public interface pic_scal

general interface of the BLAS SCAL routines, will call SSCAL, DSCAL, CSCAL, ZSCAL

Usage: call pic_scal(x, [optional] alpha)

where x is the input vector, alpha is the scaling factor. The vector x must be an allocatable array, we deduce the shape from it. The scaling factor alpha is 1.0 by default.

  • private subroutine pic_sscal(x, alpha)

    interface for single precision scaling

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(inout) :: x(:)
    real(kind=sp), intent(in), optional :: alpha
  • private subroutine pic_dscal(x, alpha)

    interface for double precision scaling

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(inout) :: x(:)
    real(kind=dp), intent(in), optional :: alpha
  • private subroutine pic_cscal(x, alpha)

    interface for single precision complex scaling

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(inout) :: x(:)
    complex(kind=sp), intent(in), optional :: alpha
  • private subroutine pic_zscal(x, alpha)

    interface for double precision complex scaling

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(inout) :: x(:)
    complex(kind=dp), intent(in), optional :: alpha

private interface blas_asum

this is the interface for the BLAS ASUM routines, it will call SASUM, DASUM, SCASUM, DZASUM Usage: result = blas_asum(x, incx) where x is the input vector, incx is the increment.

This is not a public interface, it is used internally by pic_asum

  • private pure function dasum(n, x, incx) result(res_dasum)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=default_int), intent(in) :: n
    real(kind=dp), intent(in) :: x(*)
    integer(kind=default_int), intent(in) :: incx

    Return Value real(kind=dp)

  • private pure function dzasum(n, x, incx) result(res_dzasum)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=default_int), intent(in) :: n
    complex(kind=dp), intent(in) :: x(*)
    integer(kind=default_int), intent(in) :: incx

    Return Value real(kind=dp)

  • private pure function sasum(n, x, incx) result(res_sasum)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=default_int), intent(in) :: n
    real(kind=sp), intent(in) :: x(*)
    integer(kind=default_int), intent(in) :: incx

    Return Value real(kind=sp)

  • private pure function scasum(n, x, incx) result(res_scasum)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=default_int), intent(in) :: n
    complex(kind=sp), intent(in) :: x(*)
    integer(kind=default_int), intent(in) :: incx

    Return Value real(kind=sp)

private interface blas_axpy

explicit interface for BLAS AXPY routines

Usage: call blas_axpy(n, alpha, x, incx, y, incy)

This is not a public interface, it is used internally by pic_axpy

  • private pure subroutine caxpy(n, alpha, x, incx, y, incy)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=default_int), intent(in) :: n
    complex(kind=sp), intent(in) :: alpha
    complex(kind=sp), intent(in) :: x(*)
    integer(kind=default_int), intent(in) :: incx
    complex(kind=sp), intent(inout) :: y(*)
    integer(kind=default_int), intent(in) :: incy
  • private pure subroutine daxpy(n, alpha, x, incx, y, incy)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=default_int), intent(in) :: n
    real(kind=dp), intent(in) :: alpha
    real(kind=dp), intent(in) :: x(*)
    integer(kind=default_int), intent(in) :: incx
    real(kind=dp), intent(inout) :: y(*)
    integer(kind=default_int), intent(in) :: incy
  • private pure subroutine saxpy(n, alpha, x, incx, y, incy)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=default_int), intent(in) :: n
    real(kind=sp), intent(in) :: alpha
    real(kind=sp), intent(in) :: x(*)
    integer(kind=default_int), intent(in) :: incx
    real(kind=sp), intent(inout) :: y(*)
    integer(kind=default_int), intent(in) :: incy
  • private pure subroutine zaxpy(n, alpha, x, incx, y, incy)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=default_int), intent(in) :: n
    complex(kind=dp), intent(in) :: alpha
    complex(kind=dp), intent(in) :: x(*)
    integer(kind=default_int), intent(in) :: incx
    complex(kind=dp), intent(inout) :: y(*)
    integer(kind=default_int), intent(in) :: incy

private interface blas_copy

explicit interface for BLAS COPY routines

Usage: call blas_copy(x, y)

This is not a public interface, it is used internally by pic_copy

  • private pure subroutine ccopy(n, x, incx, y, incy)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=default_int), intent(in) :: n
    complex(kind=sp), intent(in) :: x(*)
    integer(kind=default_int), intent(in) :: incx
    complex(kind=sp), intent(inout) :: y(*)
    integer(kind=default_int), intent(in) :: incy
  • private pure subroutine dcopy(n, x, incx, y, incy)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=default_int), intent(in) :: n
    real(kind=dp), intent(in) :: x(*)
    integer(kind=default_int), intent(in) :: incx
    real(kind=dp), intent(inout) :: y(*)
    integer(kind=default_int), intent(in) :: incy
  • private pure subroutine scopy(n, x, incx, y, incy)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=default_int), intent(in) :: n
    real(kind=sp), intent(in) :: x(*)
    integer(kind=default_int), intent(in) :: incx
    real(kind=sp), intent(inout) :: y(*)
    integer(kind=default_int), intent(in) :: incy
  • private pure subroutine zcopy(n, x, incx, y, incy)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=default_int), intent(in) :: n
    complex(kind=dp), intent(in) :: x(*)
    integer(kind=default_int), intent(in) :: incx
    complex(kind=dp), intent(inout) :: y(*)
    integer(kind=default_int), intent(in) :: incy

private interface blas_dot

explicit interface for BLAS DOT routines

Usage: result = blas_dot(x, y, incx, incy, n) This is not a public interface, it is used internally by pic_dot

  • private pure function cdotc(n, x, incx, y, incy) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=default_int), intent(in) :: n
    complex(kind=sp), intent(in) :: x(*)
    integer(kind=default_int), intent(in) :: incx
    complex(kind=sp), intent(in) :: y(*)
    integer(kind=default_int), intent(in) :: incy

    Return Value complex(kind=sp)

  • private pure function ddot(n, x, incx, y, incy) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=default_int), intent(in) :: n
    real(kind=dp), intent(in) :: x(*)
    integer(kind=default_int), intent(in) :: incx
    real(kind=dp), intent(in) :: y(*)
    integer(kind=default_int), intent(in) :: incy

    Return Value real(kind=dp)

  • private pure function sdot(n, x, incx, y, incy) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=default_int), intent(in) :: n
    real(kind=sp), intent(in) :: x(*)
    integer(kind=default_int), intent(in) :: incx
    real(kind=sp), intent(in) :: y(*)
    integer(kind=default_int), intent(in) :: incy

    Return Value real(kind=sp)

  • private pure function zdotc(n, x, incx, y, incy) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=default_int), intent(in) :: n
    complex(kind=dp), intent(in) :: x(*)
    integer(kind=default_int), intent(in) :: incx
    complex(kind=dp), intent(in) :: y(*)
    integer(kind=default_int), intent(in) :: incy

    Return Value complex(kind=dp)

private interface blas_gemm

explicit interface for BLAS GEMM routines

Usage: call blas_gemm(transa, transb, m, n, k, alpha, a, lda, b, ldb, beta, c, ldc)

This is not a public interface, it is used internally by pic_gemm

  • private pure subroutine cgemm(transa, transb, m, n, k, alpha, a, lda, b, ldb, beta, c, ldc)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transa
    character(len=1), intent(in) :: transb
    integer(kind=default_int), intent(in) :: m
    integer(kind=default_int), intent(in) :: n
    integer(kind=default_int), intent(in) :: k
    complex(kind=sp), intent(in) :: alpha
    complex(kind=sp), intent(in) :: a(lda,*)
    integer(kind=default_int), intent(in) :: lda
    complex(kind=sp), intent(in) :: b(ldb,*)
    integer(kind=default_int), intent(in) :: ldb
    complex(kind=sp), intent(in) :: beta
    complex(kind=sp), intent(inout) :: c(ldc,*)
    integer(kind=default_int), intent(in) :: ldc
  • private pure subroutine dgemm(transa, transb, m, n, k, alpha, a, lda, b, ldb, beta, c, ldc)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transa
    character(len=1), intent(in) :: transb
    integer(kind=default_int), intent(in) :: m
    integer(kind=default_int), intent(in) :: n
    integer(kind=default_int), intent(in) :: k
    real(kind=dp), intent(in) :: alpha
    real(kind=dp), intent(in) :: a(lda,*)
    integer(kind=default_int), intent(in) :: lda
    real(kind=dp), intent(in) :: b(ldb,*)
    integer(kind=default_int), intent(in) :: ldb
    real(kind=dp), intent(in) :: beta
    real(kind=dp), intent(inout) :: c(ldc,*)
    integer(kind=default_int), intent(in) :: ldc
  • private pure subroutine sgemm(transa, transb, m, n, k, alpha, a, lda, b, ldb, beta, c, ldc)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transa
    character(len=1), intent(in) :: transb
    integer(kind=default_int), intent(in) :: m
    integer(kind=default_int), intent(in) :: n
    integer(kind=default_int), intent(in) :: k
    real(kind=sp), intent(in) :: alpha
    real(kind=sp), intent(in) :: a(lda,*)
    integer(kind=default_int), intent(in) :: lda
    real(kind=sp), intent(in) :: b(ldb,*)
    integer(kind=default_int), intent(in) :: ldb
    real(kind=sp), intent(in) :: beta
    real(kind=sp), intent(inout) :: c(ldc,*)
    integer(kind=default_int), intent(in) :: ldc
  • private pure subroutine zgemm(transa, transb, m, n, k, alpha, a, lda, b, ldb, beta, c, ldc)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transa
    character(len=1), intent(in) :: transb
    integer(kind=default_int), intent(in) :: m
    integer(kind=default_int), intent(in) :: n
    integer(kind=default_int), intent(in) :: k
    complex(kind=dp), intent(in) :: alpha
    complex(kind=dp), intent(in) :: a(lda,*)
    integer(kind=default_int), intent(in) :: lda
    complex(kind=dp), intent(in) :: b(ldb,*)
    integer(kind=default_int), intent(in) :: ldb
    complex(kind=dp), intent(in) :: beta
    complex(kind=dp), intent(inout) :: c(ldc,*)
    integer(kind=default_int), intent(in) :: ldc

private interface blas_gemv

explicit interface for BLAS GEMV routines

Usage: call blas_gemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)

This is not a public interface, it is used internally by pic_gemv

  • private pure subroutine cgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: trans
    integer(kind=default_int), intent(in) :: m
    integer(kind=default_int), intent(in) :: n
    complex(kind=sp), intent(in) :: alpha
    complex(kind=sp), intent(in) :: a(lda,*)
    integer(kind=default_int), intent(in) :: lda
    complex(kind=sp), intent(in) :: x(*)
    integer(kind=default_int), intent(in) :: incx
    complex(kind=sp), intent(in) :: beta
    complex(kind=sp), intent(inout) :: y(*)
    integer(kind=default_int), intent(in) :: incy
  • private pure subroutine dgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: trans
    integer(kind=default_int), intent(in) :: m
    integer(kind=default_int), intent(in) :: n
    real(kind=dp), intent(in) :: alpha
    real(kind=dp), intent(in) :: a(lda,*)
    integer(kind=default_int), intent(in) :: lda
    real(kind=dp), intent(in) :: x(*)
    integer(kind=default_int), intent(in) :: incx
    real(kind=dp), intent(in) :: beta
    real(kind=dp), intent(inout) :: y(*)
    integer(kind=default_int), intent(in) :: incy
  • private pure subroutine sgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: trans
    integer(kind=default_int), intent(in) :: m
    integer(kind=default_int), intent(in) :: n
    real(kind=sp), intent(in) :: alpha
    real(kind=sp), intent(in) :: a(lda,*)
    integer(kind=default_int), intent(in) :: lda
    real(kind=sp), intent(in) :: x(*)
    integer(kind=default_int), intent(in) :: incx
    real(kind=sp), intent(in) :: beta
    real(kind=sp), intent(inout) :: y(*)
    integer(kind=default_int), intent(in) :: incy
  • private pure subroutine zgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: trans
    integer(kind=default_int), intent(in) :: m
    integer(kind=default_int), intent(in) :: n
    complex(kind=dp), intent(in) :: alpha
    complex(kind=dp), intent(in) :: a(lda,*)
    integer(kind=default_int), intent(in) :: lda
    complex(kind=dp), intent(in) :: x(*)
    integer(kind=default_int), intent(in) :: incx
    complex(kind=dp), intent(in) :: beta
    complex(kind=dp), intent(inout) :: y(*)
    integer(kind=default_int), intent(in) :: incy

private interface blas_iamax

explicit interface for BLAS IAMAX routines

Usage: idx = blas_iamax(x, incx)

This is not a public interface, it is used internally by pic_iamax

  • private pure function icamax(n, x, incx) result(idx)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=default_int), intent(in) :: n
    complex(kind=sp), intent(in) :: x(*)
    integer(kind=default_int), intent(in) :: incx

    Return Value integer(kind=default_int)

  • private pure function idamax(n, x, incx) result(idx)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=default_int), intent(in) :: n
    real(kind=dp), intent(in) :: x(*)
    integer(kind=default_int), intent(in) :: incx

    Return Value integer(kind=default_int)

  • private pure function isamax(n, x, incx) result(idx)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=default_int), intent(in) :: n
    real(kind=sp), intent(in) :: x(*)
    integer(kind=default_int), intent(in) :: incx

    Return Value integer(kind=default_int)

  • private pure function izamax(n, x, incx) result(idx)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=default_int), intent(in) :: n
    complex(kind=dp), intent(in) :: x(*)
    integer(kind=default_int), intent(in) :: incx

    Return Value integer(kind=default_int)

private interface blas_scal

explicit interface for BLAS SCAL routines

Usage: call blas_scal(n, alpha, x, incx)

This is not a public interface, it is used internally by pic_scal

  • private pure subroutine cscal(n, alpha, x, incx)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=default_int), intent(in) :: n
    complex(kind=sp), intent(in) :: alpha
    complex(kind=sp), intent(inout) :: x(*)
    integer(kind=default_int), intent(in) :: incx
  • private pure subroutine dscal(n, alpha, x, incx)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=default_int), intent(in) :: n
    real(kind=dp), intent(in) :: alpha
    real(kind=dp), intent(inout) :: x(*)
    integer(kind=default_int), intent(in) :: incx
  • private pure subroutine sscal(n, alpha, x, incx)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=default_int), intent(in) :: n
    real(kind=sp), intent(in) :: alpha
    real(kind=sp), intent(inout) :: x(*)
    integer(kind=default_int), intent(in) :: incx
  • private pure subroutine zscal(n, alpha, x, incx)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=default_int), intent(in) :: n
    complex(kind=dp), intent(in) :: alpha
    complex(kind=dp), intent(inout) :: x(*)
    integer(kind=default_int), intent(in) :: incx

Functions

private function pic_cdotc(x, y) result(res)

interface for single precision complex dot product

Arguments

Type IntentOptional Attributes Name
complex(kind=sp), intent(in) :: x(:)
complex(kind=sp), intent(in) :: y(:)

Return Value complex(kind=sp)

private function pic_dasum(x) result(res)

interface for double precision absolute sum

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(in) :: x(:)

Return Value real(kind=dp)

private function pic_ddot(x, y) result(res)

interface for double precision dot product

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(in) :: x(:)
real(kind=dp), intent(in) :: y(:)

Return Value real(kind=dp)

private function pic_dzasum(x) result(res)

interface for double precision complex absolute sum

Arguments

Type IntentOptional Attributes Name
complex(kind=dp), intent(in) :: x(:)

Return Value real(kind=dp)

private function pic_icamax(x) result(idx)

interface for single precision complex index of maximum absolute value

Arguments

Type IntentOptional Attributes Name
complex(kind=sp), intent(in) :: x(:)

Return Value integer(kind=default_int)

private function pic_idamax(x) result(idx)

interface for double precision index of maximum absolute value

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(in) :: x(:)

Return Value integer(kind=default_int)

private function pic_isamax(x) result(idx)

interface for single precision index of maximum absolute value

Arguments

Type IntentOptional Attributes Name
real(kind=sp), intent(in) :: x(:)

Return Value integer(kind=default_int)

private function pic_izamax(x) result(idx)

interface for double precision complex index of maximum absolute value

Arguments

Type IntentOptional Attributes Name
complex(kind=dp), intent(in) :: x(:)

Return Value integer(kind=default_int)

private function pic_sasum(x) result(res)

interface for single precision absolute sum

Arguments

Type IntentOptional Attributes Name
real(kind=sp), intent(in) :: x(:)

Return Value real(kind=sp)

private function pic_scasum(x) result(res)

interface for single precision complex absolute sum

Arguments

Type IntentOptional Attributes Name
complex(kind=sp), intent(in) :: x(:)

Return Value real(kind=sp)

private function pic_sdot(x, y) result(res)

interface for single precision dot product

Arguments

Type IntentOptional Attributes Name
real(kind=sp), intent(in) :: x(:)
real(kind=sp), intent(in) :: y(:)

Return Value real(kind=sp)

private function pic_zdotc(x, y) result(res)

interface for double precision complex dot product

Arguments

Type IntentOptional Attributes Name
complex(kind=dp), intent(in) :: x(:)
complex(kind=dp), intent(in) :: y(:)

Return Value complex(kind=dp)


Subroutines

private subroutine pic_caxpy(x, y, alpha)

interface for single precision complex AXPY

Arguments

Type IntentOptional Attributes Name
complex(kind=sp), intent(in) :: x(:)
complex(kind=sp), intent(inout) :: y(:)
complex(kind=sp), intent(in), optional :: alpha

private subroutine pic_ccopy(x, y)

interface for single precision complex copy

Arguments

Type IntentOptional Attributes Name
complex(kind=sp), intent(in) :: x(:)
complex(kind=sp), intent(inout) :: y(:)

private subroutine pic_cscal(x, alpha)

interface for single precision complex scaling

Arguments

Type IntentOptional Attributes Name
complex(kind=sp), intent(inout) :: x(:)
complex(kind=sp), intent(in), optional :: alpha

private subroutine pic_daxpy(x, y, alpha)

interface for double precision AXPY

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(in) :: x(:)
real(kind=dp), intent(inout) :: y(:)
real(kind=dp), intent(in), optional :: alpha

private subroutine pic_dcopy(x, y)

interface for double precision copy

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(in) :: x(:)
real(kind=dp), intent(inout) :: y(:)

private pure subroutine pic_dgemm(A, B, C, transa, transb, alpha, beta)

interface for single precision matrix multiplication

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(in) :: A(:,:)
real(kind=dp), intent(in) :: B(:,:)
real(kind=dp), intent(inout) :: C(:,:)
character(len=1), intent(in), optional :: transa
character(len=1), intent(in), optional :: transb
real(kind=dp), intent(in), optional :: alpha
real(kind=dp), intent(in), optional :: beta

private pure subroutine pic_dgemv(A, x, y, trans_a, alpha, beta)

interface for double precision matrix-vector multiplication

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(in) :: A(:,:)
real(kind=dp), intent(in) :: x(:)
real(kind=dp), intent(inout) :: y(:)
character(len=1), intent(in), optional :: trans_a
real(kind=dp), intent(in), optional :: alpha
real(kind=dp), intent(in), optional :: beta

private subroutine pic_dscal(x, alpha)

interface for double precision scaling

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(inout) :: x(:)
real(kind=dp), intent(in), optional :: alpha

private subroutine pic_saxpy(x, y, alpha)

interface for single precision AXPY

Arguments

Type IntentOptional Attributes Name
real(kind=sp), intent(in) :: x(:)
real(kind=sp), intent(inout) :: y(:)
real(kind=sp), intent(in), optional :: alpha

private subroutine pic_scopy(x, y)

interface for single precision copy

Arguments

Type IntentOptional Attributes Name
real(kind=sp), intent(in) :: x(:)
real(kind=sp), intent(inout) :: y(:)

private pure subroutine pic_sgemm(A, B, C, transa, transb, alpha, beta)

interface for single precision matrix multiplication

Arguments

Type IntentOptional Attributes Name
real(kind=sp), intent(in) :: A(:,:)
real(kind=sp), intent(in) :: B(:,:)
real(kind=sp), intent(inout) :: C(:,:)
character(len=1), intent(in), optional :: transa
character(len=1), intent(in), optional :: transb
real(kind=sp), intent(in), optional :: alpha
real(kind=sp), intent(in), optional :: beta

private pure subroutine pic_sgemv(A, x, y, trans_a, alpha, beta)

interface for single precision matrix-vector multiplication

Arguments

Type IntentOptional Attributes Name
real(kind=sp), intent(in) :: A(:,:)
real(kind=sp), intent(in) :: x(:)
real(kind=sp), intent(inout) :: y(:)
character(len=1), intent(in), optional :: trans_a
real(kind=sp), intent(in), optional :: alpha
real(kind=sp), intent(in), optional :: beta

private subroutine pic_sscal(x, alpha)

interface for single precision scaling

Arguments

Type IntentOptional Attributes Name
real(kind=sp), intent(inout) :: x(:)
real(kind=sp), intent(in), optional :: alpha

private subroutine pic_zaxpy(x, y, alpha)

interface for double precision complex AXPY

Arguments

Type IntentOptional Attributes Name
complex(kind=dp), intent(in) :: x(:)
complex(kind=dp), intent(inout) :: y(:)
complex(kind=dp), intent(in), optional :: alpha

private subroutine pic_zcopy(x, y)

interface for double precision complex copy

Arguments

Type IntentOptional Attributes Name
complex(kind=dp), intent(in) :: x(:)
complex(kind=dp), intent(inout) :: y(:)

private pure subroutine pic_zgemm(A, B, C, transa, transb, alpha, beta)

interface for single precision matrix multiplication

Arguments

Type IntentOptional Attributes Name
complex(kind=dp), intent(in) :: A(:,:)
complex(kind=dp), intent(in) :: B(:,:)
complex(kind=dp), intent(inout) :: C(:,:)
character(len=1), intent(in), optional :: transa
character(len=1), intent(in), optional :: transb
complex(kind=dp), intent(in), optional :: alpha
complex(kind=dp), intent(in), optional :: beta

private subroutine pic_zscal(x, alpha)

interface for double precision complex scaling

Arguments

Type IntentOptional Attributes Name
complex(kind=dp), intent(inout) :: x(:)
complex(kind=dp), intent(in), optional :: alpha