Passing a generic procedure as actual argument?

I’ve always thought it is forbidden. Only recently I found a disturbing sentence in MFE 2018 (sec. 5.12, p.88):

The actual argument may be a generic procedure name (Section 5.18); if it is also a specific name, only the specific procedure is passed

The second part, after semicolon, is OK, but the generic? How could that be possible? The two compilers I checked (gfortran and ifort) seem not to support generics. Trying to pass log intrinsic function (which is generic-only name):

  intrinsic log, sin
  real :: x0, x1, res
  call calka(log,x0,x1,res)

results in

5 |   call calka(log,x0,x1,res)     
  |             1

Error: Intrinsic ‘log’ at (1) is not allowed as an actual argument

If I change log to sin (which is both generic and specific name), it works fine, as expected. Similarly for user-written generic procedure

MODULE swapping
  INTERFACE swap
    module procedure swapreal, swapinteger
  END INTERFACE swap
CONTAINS
  SUBROUTINE swapreal(a,b) 
  ...

Attempt to call testsub(swap,...) results in

Error: Symbol at (1) is not appropriate for an expression

Again, substituting specific swapreal or swapinteger makes it work fine.

I checked old MFE 90/95 (2nd edition) which states (sec 5.12, p. 87):

The procedure that is passed must be an external or module procedure and its specific name must be passed when it also has a generic name

Any comments? Am I misinterpreting the clause? Apparently there were some changes to the topic in following Fortran standards, as MFE 90/95 explicitly prohibits internal procedures as arguments, while the 2018 version allows them.

I tried to find relevant info in the Standard, to no success.

3 Likes

What does it mean “if it is also a specific name”? Is this saying if the generic name can be resolved to a specific name at the call site? How can that be done? It seems to me you only know what specific name to use once you call the function inside the calka subroutine.

I agree that it should be forbidden. Two example programs:

! t_generic_1.f90                       27-Nov-21                       John Collins
! ****************************************************************************************

MODULE m

        INTERFACE gen1
        MODULE PROCEDURE gen1_a
        MODULE PROCEDURE gen1_b
        END INTERFACE

        CONTAINS
        SUBROUTINE gen1_a(i)
        INTEGER :: i
        WRITE(*,*)"In gen1_a"
        END SUBROUTINE gen1_a

        SUBROUTINE gen1_b(r)
        REAL :: r
        WRITE(*,*)"In gen1_b"
        END SUBROUTINE gen1_b

END MODULE m ! ***************************************************************************

PROGRAM t_generic

        USE m

        CALL caller(gen1)

END PROGRAM t_generic ! ******************************************************************

SUBROUTINE caller(s)
        EXTERNAL s
        CALL s(42)
END SUBROUTINE caller ! ******************************************************************

This fails - for example, gfortran:

john@impala:~/projects/WinFPT/fpt/fpttest$ gfortran t_generic_1.f90
t_generic_1.f90:29:13:

  CALL caller(gen1)
             1
Error: GENERIC procedure ‘gen1’ is not allowed as an actual argument at (1)

Now one that works:

! t_generic_2.f90                       27-Nov-21                       John Collins
! ****************************************************************************************

MODULE m

        INTERFACE gen1
        MODULE PROCEDURE gen1
        MODULE PROCEDURE gen1_b
        END INTERFACE

        CONTAINS
        SUBROUTINE gen1(i)
        INTEGER :: i
        WRITE(*,*)"In gen1"
        END SUBROUTINE gen1

        SUBROUTINE gen1_b(r)
        REAL :: r
        WRITE(*,*)"In gen1_b"
        END SUBROUTINE gen1_b

END MODULE m ! ***************************************************************************

PROGRAM t_generic

        USE m

        CALL caller(gen1)

END PROGRAM t_generic ! ******************************************************************

SUBROUTINE caller(s)
        EXTERNAL s
        CALL s(42.0)
END SUBROUTINE caller ! ******************************************************************

Under gfortran:

john@impala:~/projects/WinFPT/fpt/fpttest$ gfortran t_generic_2.f90
john@impala:~/projects/WinFPT/fpt/fpttest$ ./a.out

In gen1

The difference is that there is a specific routine, gen1, with the same name as the generic. What is actually passed is the specific routine. Note that the argument to gen1 in caller is REAL and the generic interface should therefore select gen1_b. But it never has the opportunity.

Apologies for the formatting - how do I stop the interface from reformatting the code?

John

2 Likes

You should place all code in a section fenced by three back-ticks, like this:

```
insert code here
```

You can add the language name to get syntax highlighting.

```fortran
insert code here
```
1 Like

Thank you!

1 Like

@Jcollins you can click the pencil button (Edit) to edit your post and format it correctly using the suggestion that @ivanpribec wrote. Let me know if you run into problems.

I did not immediately see why there was a restriction. Great example. If you precede a line
with something like
```fortran
Fortran code goes here
and is followed by
```
that will prevent the formatting and even highlight the Fortran code. That works for text too if you
use “text” instead of “fortran”; although indenting four or more characters will do something similar. There are a couple of ways, but especially for Fortran code that is my favorite.

You can also make a long code listing only appear if clicked on by

    [details="My code"]
    ```fortran
    program showit
       write(*,*)'Hello!'
    end program showit
    ```
    [/details]

which produces the arrow you can click on

My code
    program showit
       write(*,*)'Hello!'
    end program showit

which you can also do as one of the options under the “gear” icon in the edit icon bar, as that is getting hard to type unless you cut and paste; so it is easier to just add the “fortran” lines and then mark the code and click the gear and select “hide” to get the “details” lines added.

2 Likes

The wording in the standard you want is C1534: " A procedure-name shall be the name of an external, internal, module, or dummy procedure, a specific intrinsic function listed in Table 16.2, or a procedure pointer." In the standard, the italicized part is actually in the “obsolescent” small font, since the notion of specific names for intrinsic procedures is obsolescent. Note that this means the only generic intrinsic procedures you can pass as an actual argument are those which have a specific name in that table (which then identifies which specific it is.)

This text also rules out passing a generic interface name unless it is the same as a specific procedure.

2 Likes

Attention @m_b_metcalf , please note the above sentence in the 2018 edition of MFE which can come across as confusing to readers. Perhaps you would consider discussing this with your coauthors to see if it will be beneficial for your readers to rephrase the sentence? Introducing an accompanying example that clarifies the rules in the standard may be helpful in a future revision as well?

I agree that the MFE wording is confusing. I checked my copy to see if there was additional context that might apply, but it’s really just a restatement of part of the constraint I quoted.

The reality is that you cannot pass a generic procedure name as an argument. That you can pass a specific name that is the same as a generic is not quite the same thing!

1 Like

Thanks, @sblionel for the pointer and explanation, which fully agrees with my understanding of the topic.

If, however, the notion of specific names for intrinsic procedures is obsolescent, what would be the right way to, say, compute an integral of sine or logarithm, using a procedure that expects a function as argument? Wrapping the intrinsic into a user-written function, say my_sin and passing that one?

@msz59 Yes, that’s what I would recommend.

Thank you for drawing this to our attention. The offending sentence will be removed in the next printing.

Regards,

Mike Metcalf

2 Likes