Question about entry function

Here is an example test case that works with GFortran:

SUBROUTINE dinvr(x)
IMPLICIT NONE
DOUBLE PRECISION x
DOUBLE PRECISION big,small,zx,zy,zz, zsmall, zbig
LOGICAL qcond
INTRINSIC abs,max,min
LOGICAL qxmon
SAVE

qxmon(zx,zy,zz) = zx .LE. zy .AND. zy .LE. zz

qcond = .NOT. qxmon(small,x,big)

print *, "small = ", small
print *, "x = ", x
print *, "big = ", big

print *, 'qcond = ', qcond
IF (qcond) error stop

return

entry distinv(zsmall, zbig)

small = zsmall
big = zbig

end subroutine

program entry_10
implicit none
double precision :: x
x = 0.5d0

call distinv(0.0d0, 1.0d0)

call dinvr(x)
end program

This prints:

$ gfortran a.f90 && ./a.out
 small =    0.0000000000000000     
 x =   0.50000000000000000     
 big =    1.0000000000000000     
 qcond =  F

Now if we remove the “return” statement from before “entry distinv(zsmall, zbig)”:

SUBROUTINE dinvr(x)
IMPLICIT NONE
DOUBLE PRECISION x
DOUBLE PRECISION big,small,zx,zy,zz, zsmall, zbig
LOGICAL qcond
INTRINSIC abs,max,min
LOGICAL qxmon
SAVE

qxmon(zx,zy,zz) = zx .LE. zy .AND. zy .LE. zz

qcond = .NOT. qxmon(small,x,big)

print *, "small = ", small
print *, "x = ", x
print *, "big = ", big

print *, 'qcond = ', qcond
IF (qcond) error stop

entry distinv(zsmall, zbig)

small = zsmall
big = zbig

end subroutine

program entry_10
implicit none
double precision :: x
x = 0.5d0

call distinv(0.0d0, 1.0d0)

call dinvr(x)
end program

We obtain:

$ gfortran -g a.f90 && ./a.out
 small =    0.0000000000000000     
 x =   0.50000000000000000     
 big =    1.0000000000000000     
 qcond =  F

Program received signal SIGSEGV: Segmentation fault - invalid memory reference.

Backtrace for this error:
#0  0x100497bd3 in ???
#1  0x100496cc3 in ???
#2  0x1869d04e3 in ???
#3  0x100023d67 in master.0.dinvr
	at /Users/ondrej/repos/scipy/a.f90:18
zsh: segmentation fault  ./a.out

Is this a bug in GFortran, or is the above code incorrect?

1 Like

The code is incorrect. The dummy arguments zsmall and zbig are not associated, but they are referenced on the rhs of the two assignment statements. In the original code with the return statement, those two dummy arguments were not referenced.

1 Like

Thanks @RonShepard ! So the zsmall and zbig variables can only be used if distinv was called, otherwise if dinvr was called, the code cannot touch them?

Yes. When dinvr() is called, the only dummy argument that is associated with an actual argument is x, so that is the only dummy argumment that can be referenced.

When distinv() is called, the dummy arguments zsmall and zbig are associated with actual arguments, so they can be referenced. If x were referenced, then you would probably get another seg fault.

1 Like

Small nitpick: There is no function here, there is an ENTRY statement in a subroutine subprogram. I got all excited thinking it would be about ENTRY statement in function subprogram, because I recently discovered an obscure corner of semantics about ENTRY statetements with RESULT clause in function subprograms.

If the characteristics of the result of the function named in the ENTRY statement are the same as the characteristics of the result of the function named in the FUNCTION statement, their result names identify the same entity, although their names need not be the same. Otherwise, they are storage associated and shall all be nonpointer, nonallocatable scalar variables that are default integer, default real, double precision real, default complex, or default logical.

This is an association between names, say X and Y, that can be asserted by adding

ENTRY never_used1(N) RESULT(X)
ENTRY never_used2(N) RESULT(Y)

at the end of a function subprogram. This can catch you out, if you were hoping that any association between those names would be found in the specification part of the subprogram.

1 Like

One feature of entry points is that they cannot be called from within the procedure. In the case of functions, that means that one function entry cannot reference another function entry. Because of that, the X and Y results will never both be active at the same time. I’m unsure what are the consequences of that restriction with recursion (which was not allowed in f77).

When code with entry points is converted into a module, then that restriction is removed. One module function can reference another module function. And now that recursion is the default, they can even do so recursively.

1 Like

Thanks @RonShepard and @themos !

This explains it. I am learning many new things about Fortran now when we need to implement them. :slight_smile: