Take the code block below, but put every code block INTO ITS OWN FILE.
module mod_1
contains
function optval(x,y) result(z)
real(kind=8), intent(in), optional :: x
real(kind=8), intent(in) :: y
real(kind=8) :: z
if(present(x)) then
z=x
else
z=y
end if
end function optval
end module mod_1
module mod_2
use mod_1, only: optval
contains
subroutine sub1(r2i,t,s)
real(kind=8), intent(inout) :: r2i(:,:)
real(kind=8), intent(in) :: t
real(kind=8), intent(in), optional :: s
integer :: i,j
do i=1,size(r2i,2)
do j=1,size(r2i,1)
if(r2i(j,i)>t) r2i(j,i)=r2i(j,i)/optval(s,3.0D0)
end do
end do
end subroutine sub1
subroutine sub2(r2i,t,s)
real(kind=8), intent(inout) :: r2i(:,:)
real(kind=8), intent(in) :: t
real(kind=8), intent(in), optional :: s
integer :: i,j
do i=1,size(r2i,2)
do j=1,size(r2i,1)
if(present(s)) then
if(r2i(j,i)>t) r2i(j,i)=r2i(j,i)/s
else
if(r2i(j,i)>t) r2i(j,i)=r2i(j,i)/3.0D0
end if
end do
end do
end subroutine sub2
end module mod_2
and
program test
use mod_2, only: sub1, sub2
implicit none
real(kind=8), allocatable :: x(:,:)
real(kind=8) :: t1,t2
integer :: i
allocate(x(1000000,100))
do i=1,4
call random_number(x)
call cpu_time(t1)
call sub2(x,0.2D0)
call cpu_time(t2)
write(*,"(*(g0:"",""))") "t1: ", i, t2-t1
end do
do i=1,4
call random_number(x)
call cpu_time(t1)
call sub1(x,0.2D0)
call cpu_time(t2)
write(*,"(*(g0:"",""))") "t2: ", i, t2-t1
end do
end program test
compile with
#!/bin/bash
fc=ifort
$fc -O3 -c sub1.f90
$fc -O3 -c sub2.f90
$fc -O3 -c main.f90
$fc -O3 -o test main.o sub1.o sub2.o
and check what you get.
I got:
t1: ,1,.9718500000000008E-01
t1: ,2,.9703800000000018E-01
t1: ,3,.9721100000000016E-01
t1: ,4,.9707200000000027E-01
t2: ,1,.4253720000000003
t2: ,2,.4263209999999997
t2: ,3,.4262069999999998
t2: ,4,.4255380000000004
This is of course an oversimplified example and there are several fixes to this particular code of which some are trivial, others not.
However, in more complex examples or when functions like optval
sit in large libraries there is no guarantee that these fixes works.
I understand that the stdlib optval
functionality is meant to make fortran more handy. But an inexperienced programmer or somebody not familiar with 2500 pages of ifort manual may come to the conclusion that stdlib is anything else than hpc.