Should the ENTRY statement be used in new code?

The ENTRY statement was declared obsolescent in Fortran 2008, and I have not used it for serious codes, but it looks like a convenient way of defining several functions that have the same arguments and results. For the code below, defining separate normal, sech, laplace, and uniform functions would take more lines of repetitive code. Using ENTRY it is clear that they are all pure elemental functions that have a real(kind=dp) argument and return a real(kind=dp) result.

module pdf_mod
implicit none
integer, parameter :: dp = kind(1.0d0)
real(kind=dp), parameter :: pi = 3.141592653589793238462643_dp, &
                            sqrt_two = 1.414213562373095_dp
contains
pure elemental function pdf(x) result(y)
! probability density functions
real(kind=dp), intent(in) :: x
real(kind=dp)             :: y
entry normal(x)  result(y) ; y = exp(-0.5*x**2)/sqrt(2*pi)      ; return 
entry sech(x)    result(y) ; y = 0.5_dp/cosh(pi*x/2)            ; return
entry laplace(x) result(y) ; y = exp(-sqrt_two*abs(x))/sqrt_two ; return
entry uniform(x) result(y) ; y = merge(1.0_dp,0.0_dp,x>=0.0_dp .and. x <= 1.0_dp); return
end function pdf
end module pdf_mod
!
program test_pdf
use pdf_mod
implicit none
real(kind=dp) :: x(2)
x = [0.0_dp,3.0_dp]
write (*,"(a10,2f8.4)") "x",x,"normal",normal(x),"sech",sech(x), &
                        "laplace",laplace(x),"uniform",uniform(x)
end program test_pdf

Output:

         x  0.0000  3.0000
    normal  0.3989  0.0044
      sech  0.5000  0.0090
   laplace  0.7071  0.0102
   uniform  1.0000  0.0000

I’ve seen ENTRY used to create essentially modules in Fortran 77. Where the global data (with SAVE attributes) are in the main part and then the entries are like the module procedures. It’s profoundly weird and unnecessary nowadays. :slight_smile:

I think what you really want here is Fortran to just be less verbose about declaring things. Maybe with some sort of inferred typing or multiple dispatch. We’ll never get that since it would break backward compatibility with the truly awful implicit typing feature.

1 Like

Since the application isn’t TKR-distinct maybe the closest modern approach would be via abstract interface

No, OP (and anyone wishing along such lines) appear not as well served by facilities in the language standard itself but by more modern IDEs/editors for Fortran with code completion facilities that find advancing assistance with increasing usage.

Intellisense/IntelliCode in Visual Studio provide such options for C#, Visual Basic, C++ coders whereby most of the function body such as normal or uniform, etc. in the original post would get completed with just a few key strokes leaving the coder to simply introduce the primary instruction(s) such as result(y) ; y = exp(-0.5*x**2)/sqrt(2*pi).

I am a definite NO for the use of ENTRY.

I can’t recall when ENTRY was included in the Fortran standard, but CDC/Cyber’s early ENTRY implementation (pre F77) broke a lot of my coding rules. It implied you could use variables that were set by other calls/entry which implied static allocation of local variables that might not have been initialised. It was very difficult to convert ENTRY to other compilers that did not have the same rules.

Based on that experience, I never considered ENTRY a robust coding approach, which I suspect others have experienced.

Sharing the same argument list format is hardly a significant saving and I think is (was) not a requirement of ENTRY ? There are lots of real functions with an argument x !

There are other coding approaches that can achieve the same outcome, requiring a cleaner identification of shared variables, such as via a MODULE.

Mixing old features marked “deleted” or “obsolescent” in combination with new features such as modules or internal programs can cause mysterious problems.

Here is a program that shows how ENTRY can be confusing.

program tstentry
integer i,j,k
i = 7
call xentry(i,j)
print *,i,j

k = 11
call yentry(j,i,k)
print *,i,j

call zentry(j)
print *,j

end program

subroutine xentry(i,j)
integer i,j,k,l
save l
j = 2*i
l = 1
return

entry yentry(j,i,k)
j = 3*i
l = 2*k
return

entry zentry(j)
j = 3*l
return
end subroutine
1 Like