Reputation: 11
I am having a hard time understanding Fortran interfaces. The test code code pasted at the end of the question compiles just fine on ifort <=version 15, but causes a catastrophic compiler error on versions 16 and later. Same on gfortran (seg fault while compiling). On g95, however, compilation ends with the following error
In file test.f90:79
call rk4(y, dydx, x, h, yout1, der, pars,*10)
1
Error: Interface of actual procedure does not match interface of dummy procedure at (1)
In file test.f90:81
call rk4(y, dydx, x, h/2.d0, yout2, der, pars,*10)
1
Error: Interface of actual procedure does not match interface of dummy procedure at (1)
In file test.f90:85
call rk4(yout2, dydx2, x+h/2.d0, h/2.d0, yout2, der, pars,*10)
1
Error: Interface of actual procedure does not match interface of dummy procedure at (1)
but I am not sure what I am doing wrong...
module RK
implicit none
contains
SUBROUTINE rk4(y, dydx, x, h, yout, der, pars, *)
IMPLICIT NONE
integer, parameter :: dp=kind(1.d0)
REAL(dp), DIMENSION(:), INTENT(IN) :: y,dydx,pars
REAL(dp), INTENT(IN) :: x,h
REAL(dp), DIMENSION(:), INTENT(OUT) :: yout
REAL(dp) :: h6,hh,xh
REAL(dp), DIMENSION(size(y)) :: dym,dyt,yt
INTERFACE
SUBROUTINE der(x,y,dydx,pars,*)
IMPLICIT NONE
integer, parameter :: dp=kind(1.d0)
REAL(dp), INTENT(IN) :: x
REAL(dp), DIMENSION(:), INTENT(IN) :: pars
REAL(dp), DIMENSION(:), INTENT(IN) :: y
REAL(dp), DIMENSION(:), INTENT(OUT) :: dydx
END SUBROUTINE der
END INTERFACE
hh = h*0.5d0
h6 = h/6.d0
xh = x + hh
yt(:)=y(:)+hh*dydx(:)
call der(xh, yt, dyt, pars,*10)
yt(:)=y(:)+hh*dyt(:)
call der(xh, yt, dym, pars,*10)
yt(:)=y(:)+h*dym(:)
dym(:)=dyt(:)+dym(:)
call der(x+h, yt, dyt, pars,*10)
yout(:)=y(:)+h6*(dydx(:)+dyt(:)+2.d0*dym(:))
return
10 return 1
end subroutine
subroutine adaptive_RK4(y,dydx,x,h,yout2,yerr,der,pars,*)
implicit none
integer, parameter :: dp=kind(1.d0)
REAL (dp) :: h, x
REAL (dp), DIMENSION (:) :: y, dydx, yout2, yerr, pars
REAL (dp), DIMENSION (size(y)) :: dydx2, yout1
intent(in) :: y, dydx, x, h, pars
intent(out) :: yout2, yerr
INTERFACE
SUBROUTINE der(x,y,dydx,pars,*)
IMPLICIT NONE
integer, parameter :: dp=kind(1.d0)
REAL(dp), INTENT(IN) :: x
REAL(dp), DIMENSION(:), INTENT(IN) :: pars
REAL(dp), DIMENSION(:), INTENT(IN) :: y
REAL(dp), DIMENSION(:), INTENT(OUT) :: dydx
END SUBROUTINE der
END INTERFACE
call rk4(y, dydx, x, h, yout1, der, pars,*10)
call rk4(y, dydx, x, h/2.d0, yout2, der, pars,*10)
call der(x+h/2.d0, yout2, dydx2, pars,*10)
call rk4(yout2, dydx2, x+h/2.d0, h/2.d0, yout2, der, pars,*10)
yerr(:)=yout2(:)-yout1(:)
yout2(:)=(16.d0*yout2(:)-yout1(:))/15.d0
return
10 return 1
end subroutine
end module
module derivative
implicit none
contains
SUBROUTINE derr(x,y,dydx,pars,*)
IMPLICIT NONE
integer, parameter :: dp=kind(1.d0)
REAL(dp), INTENT(IN) :: x
REAL(dp), DIMENSION(:), INTENT(IN) :: pars
REAL(dp), DIMENSION(:), INTENT(IN) :: y
REAL(dp), DIMENSION(:), INTENT(OUT) :: dydx
dydx=(pars+y)*x
return
END SUBROUTINE derr
end module
program test
use rk
use derivative
implicit none
integer, parameter :: dp=kind(1.d0)
real(dp), dimension(2) :: y,pars,dydx, yout, yerr
real(dp) :: x
y=(/0.1d0,2.d0/)
pars=(/0.7d0,3.d0/)
x=2.1d0
call derr(x,y,dydx,pars,*10)
write(*,*) dydx
call adaptive_RK4(y,dydx,x,0.0001d0,yout,yerr,derr,pars,*10)
stop
10 write(*,*) "some error"
end program
Upvotes: 1
Views: 430
Reputation: 59998
The code runs fine in gfortran version 6 and 7.
Gfortran version 4.8 crashes, but that is the compiler's problem. A compiler should never crash, even if the code is bad.
The same holds for Intel Fortran. If it crashes during compilation it is the compiler's fault.
Now, the code is really not great and uses features which may be difficult for the compiler. When it comes to things against standards, gfortran 6 complains of:
interface2.f90:81:9:
call rk4(yout2, dydx2, x+h/2.d0, h/2.d0, yout2, der, pars,*10)
1
Warning: Same actual argument associated with INTENT(IN) argument ‘y’ and INTENT(OUT) argument ‘yout’ at (1)
It is not allowed in Fortran to pass the same variable in to arguments in this way. The compiler will assume that the intent(in)
argument never changes, but it does change when you modify yout
. This can cause serious problems.
For the G95 compile time error, I think the compiler is wrong and the error message is bogus. The interface blocks in rk4
and adaptive_rk4
are exactly the same.
I strongly advise you to clean-up the code, get rid of the alternate exit feature and it will be much easier for the compilers to compile the code. I expect it is due to your excessive use of the alternate return feature which is not tested too much.
For your next questions, definitely read [mcve] very carefully. It is necessary to make your code much shorter for your future questions. THIS is the actual MCVE you should ask about and which can be used as a base for a bug report:
module m
implicit none
contains
subroutine a(d)
interface
subroutine d(*)
end subroutine d
end interface
10 return 1
end subroutine
subroutine b(d)
interface
subroutine d(*)
end subroutine d
end interface
call a(d)
end subroutine
end module
Compare it with the very long code you gave us. This can't really be reduced any more without the compiler crash disappearing (both ifort 17 and gcc 4.8). The problem is clearly in the dummy procedure (even though it is not actually called anywhere), which uses the alternate return feature and the compiler cannot treat it properly.
Upvotes: 1
Reputation: 41
I replaced the alternate returns from the instances of DERR / DER and then the compilation worked in Intel Fortran (XE 2017). I also agree that it's advisable to (1) clean the code up and (2) avoid the use of alternate returns.
Upvotes: 0