Dear all,
I have created two wrappers around DGEMM and DGEMV. The syntax of DGEMM and DGEMV is cumbersome and I want to be able to call them in an easy way in my projects.
So here are my two wrappers saved in a module
module mod_numerical
implicit none
private
! BLAS function wrappers
public :: mtimes_matvec, mtimes_matmat
!===============================================================================!
! NOTE: The functions mtimes_matvec and mtimes_matmat are wrappers around
! dgemv and dgemm (from BLAS library). To compile this module, please add flag mkl
! or -llapack -lblas. Below is an example from intel website:
! Windows* OS: ifort /Qmkl src\dgemm_example.f
! Linux* OS, macOS*: ifort -mkl src/dgemm_example.f
function mtimes_matvec(A,B) result (C)
real(8), intent(in) :: A(:,:),B(:)
real(8) :: C(size(A,1))
if ( size (A ,2)/= size (B)) then
error stop 'mtimes_matvec : size doesn''t conform '
endif
!C := alpha *op(A)* op(B) + beta *C,
call dgemv('N',size (A ,1) , size (A ,2) ,1d0 ,A, size (A ,1) , B ,1 ,0d0 ,C ,1)
end function mtimes_matvec
function mtimes_matmat(A,B) result (C)
! Function inputs:
real(8), intent(in) :: A(:,:),B(:,:)
! Function result (it is an allocatable dummy array)
real(8), allocatable :: C(:,:) !C(size(A,1),size(B,2))
! Local variables:
integer :: istat
if ( size (A ,2)/= size (B,1)) then
error stop 'mtimes_matmat : size doesn''t conform '
endif
allocate( C(size(A,1),size(B,2)), stat=istat)
if (istat/=0) then
error stop "mtimes_matmat: Allocation failed!"
endif
!C := alpha *op(A)* op(B) + beta *C,
CALL DGEMM('N','N',size (A ,1) ,size(B,2),size(A,2),1.0d0,A,size (A ,1),B,size(B,1),0.0d0,C,size(A,1))
end function mtimes_matmat
!===============================================================================!
end module mod_numerical
and here is a simple test program
program test
use mod_numerical, only: mtimes_matvec, mtimes_matmat
implicit none
call test_DGEMM_DGEMV()
write(*,*) "Program will close..."
pause
contains
subroutine test_DGEMM_DGEMV()
! y = A*x and C=A*B
integer, parameter :: n1=100, n2=100, n3=100
real(8) :: err_y
real(8), allocatable :: A(:,:), B(:,:),x(:)
real(8), allocatable :: y(:), y1(:), C(:,:), C1(:,:)
allocate(A(n1,n2),x(n2),B(n2,n3))
call RANDOM_NUMBER(A)
call RANDOM_NUMBER(x)
! Matrix-vector multiplication
y = matmul(A,x)
y1 = mtimes_matvec(A,x)
! Matrix-matrix multiplication
C = matmul(A,B)
C1 = mtimes_matmat(A,B)
! Check that intrinsic matmul and mtimes_matvec,mtimes_matvec
! give same results
write(*,*) "Is y=y1?", all(y==y1)
write(*,*) "Is C=C1?", all(C==C1)
err_y = maxval(abs(y-y1))
write(*,*) "maxval(abs(y-y1)) = ", err_y
end subroutine test_DGEMM_DGEMV
end program test
To my surprise, the test for mtimes_matvec failed, in that y and y1 are not equal. The difference seems very small though (this is the same in ifort and ifx). Is this to be expected?
Is y=y1? F
Is C=C1? T
maxval(abs(y-y1)) = 7.105427357601002E-015
Program will closeā¦
Fortran Pause - Enter command or to continue.
Thanks, any feedback (also on how I wrote the wrappers) is appreciated!