j3-fortran / fortran_proposals

Proposals for the Fortran Standard Committee
175 stars 14 forks source link

FALLTHROUGH #292

Open tkoenig1 opened 1 year ago

tkoenig1 commented 1 year ago

Consider the slightly contrived example of character classification, where a subroutine should print "Hexadecimal digit" if a character passed to it is a hexadecimal digit, both "Hexadecimal digit" and "Decimal digit" if it is both, and "Something else" otherwise.

This would currently be done with something like

  subroutine foo(x)
    character, intent(in) :: x
    select case(x)
    case ('a':'f','A':'F')
       print '(A)',"Hexadecimal digit"
    case ('0':'9')
       print '(A)',"Hexadecimal digit"
       print '(A)',"Decimal digit"
    case default
       print '(A)',"Something else"
    end select
  end subroutine foo

which has code duplication for the print '(A)',"Hexadecimal digit" statement.

I would propose a way to be able to fall through to the next case statement, for example by specifying a FALLTHROUGH statement, so the code above could look like

  subroutine foo(x)
    character, intent(in) :: x
    select case(x)
    case ('a':'f','A':'F')
       print '(A)',"Hexadecimal digit"
       fallthrough
    case ('0':'9')
       print '(A)',"Decimal digit"
    case default
       print '(A)',"Something else"
    end select
  end subroutine foo

To give this some statistics, maybe from a somewhat remote area: gcc mandates a note for fallthrough in its case statements, for C++. I count 479 occurences in the source of the compiler proper.

ivan-pi commented 1 year ago

Many solvers (ODE, nonlinear system, ..) have an interface that expects the caller to provide distinct callbacks for the function and it's Jacobian. Others however expect both will be calculated in the same subroutine depending on an integer flag.

As an example, here is the callback for MINPACK's HYBRJ subroutine:

      SUBROUTINE FCN(N,X,FVEC,FJAC,LDFJAC,IFLAG)
      INTEGER N, LDFJAC, IFLAG
      DOUBLE PRECISION X(N),FVEC(N),FJAC(LDFJAC,N)
C     ---------
C     IF IFLAG = 1 CALCULATE THE FUNCTIONS AT X AND
C     RETURN THIS VECTOR IN FVEC. DO NOT ALTER FJAC.
C     IF IFLAG = 2 CALCULATE THE JACOBIAN AT X AND
C     RETURN THIS MATRIX IN FJAC. DO NOT ALTER FVEC
      END

If a new nonlinear solver expected that both F and FJAC be calculated in the same call, the fallthrough statement would be a minimally intrusive way to add a third iflag:

! iflag = 1, evaluate f only
! iflag = 2, evaluate fjac only
! iflag = 3, evaluate both f and fjac

select case(iflag)
case(1,3) 
   ! evaluate function
   f(1) = x*y
   f(2) = sin(x)*y**2
   if (iflag == 3) fallthrough
case(2)
   ! evaluate jacobian
   fjac(1,1) = y
   fjac(2,1) = cos(x)*y**2
   fjac(1,2) = x
   fjac(2,2) = 2*sin(x)*y
end select

In contrast some solvers expect three distinct callbacks, e.g. in GSL leading to duplication:

gsl_multiroot_function_fdf FDF;

FDF.f = &powell_f;
FDF.df = &powell_df;
FDF.fdf = &powell_fdf;

I like the idea of fallthrough. It looks better than the alternatives:

C IF/ELSEIF Alternative
      IF (IFLAG .EQ. 1 .OR. IFLAG .EQ. 3) THEN
      F(1) = X(1)*X(2)
      F(2) = SIN(X(1)) * X(2)**2
      ELSE IF (IFLAG .EQ. 2 .OR. IFLAG .EQ. 3) THEN
      FJAC(1,1) = X(2)
      FJAC(2,1) = COS(X(1)) * X(2)**2
      FJAC(1,2) = X(1)
      FJAC(2,2) = 2 * SIN(X(1)) * X(2)
      END IF
      RETURN
C
C Arithmetic IF Alternative
      IF (IFLAG - 2) 10, 20, 10
   10 F(1) = X(1)*X(2)
      F(2) = SIN(X(1)) * X(2)**2
      IF (IFLAG .EQ. 1) GO TO 30
   20 FJAC(1,1) = X(2)
      FJAC(2,1) = COS(X(1)) * X(2)**2
      FJAC(1,2) = X(1)
      FJAC(2,2) = SIN(X(1)) * (2 * X(2))
   30 RETURN
C
C Computed GO TO Alternative
      GO TO ( 10, 20 ), IFLAG
   10 CONTINUE
      F(1) = X(1)*X(2)
      F(2) = SIN(X(1)) * X(2)**2
      IF (IFLAG .EQ. 1) GO TO 30
   20 CONTINUE
      FJAC(1,1) = X(2)
      FJAC(2,1) = COS(X(1)) * X(2)**2
      FJAC(1,2) = X(1)
      FJAC(2,2) = 2 * SIN(X(1)) * X(2)
   30 RETURN

For completeness, here is the same function in C++ using the standard [[fallthrough]] attribute (requires C++17):

// c_fcn.cpp
//
// To compile, enter:
//    g++ -Wall -std=c++17 c_fcn.cpp
//
// The [[fallthrough]] attribute in the null statement is there
// to silence warnings in case of implicit fallthrough (-Wimplicit-fallthrough)

#include <cmath>

extern "C" {

void c_fcn(int n, float *x, float *f, float *fjac, int iflag) 
{
    switch (iflag) 
    {
        case 1:
        case 3:
            f[0] = x[0]*x[1];
            f[1] = std::sin(x[0]) * (x[1]*x[1]);
            if (iflag == 1) 
                break;
            [[fallthrough]];
        case 2:
            // Column 1
            fjac[0] = x[1];
            fjac[1] = std::cos(x[0]) * (x[1]*x[1]);
            // Column 2
            fjac[2] = x[0];
            fjac[3] = 2 * std::sin(x[0]) * x[1];
    }
}

} // extern "C"
tkoenig1 commented 1 year ago
select case(iflag)
case(1,3) 
   ! evaluate function
   f(1) = x*y
   f(2) = sin(x)*y**2
   if (iflag == 3) fallthrough
case(2)
   ! evaluate jacobian
   fjac(1,1) = y
   fjac(2,1) = cos(x)*y**2
   fjac(1,2) = x
   fjac(2,2) = 2*sin(x)*y
end select

Nice use case.

If FALLTHROUGH would then, in effect, work a GOTO to the next CASE, so it can be put into control statements.

Question: Would it then make sense to use EXIT to leave a SELECT CASE (and SELECT TYPE and SELECT RANK) statement? It would then also be possible to add label-select-case-stmt, like the label-do-stmt, to have the same type of flexibility, as in DO loops.

The case above could then be reformulated into

icases: select case(iflag)
case(1,3) 
   ! evaluate function
   f(1) = x*y
   f(2) = sin(x)*y**2
   if (iflag == 1 ) exit  ! or exit icases
case(2)
   ! evaluate jacobian
   fjac(1,1) = y
   fjac(2,1) = cos(x)*y**2
   fjac(1,2) = x
   fjac(2,2) = 2*sin(x)*y
end select

This could also be done with a GOTO, but a more structured way is better, IMHO (also, like the DO loops).

klausler commented 1 year ago

That would be ambiguous with the behavior already defined for Fortran, which has construct labels and EXIT construct-name today (11.1.12, R1156). Construct labels require that their names appear on the END SELECT statement, but apart from that discrepancy, this feature already has well-defined semantics and works with every compiler that I can find except NAG.

tkoenig1 commented 1 year ago

You're right, I had actually overlooked

R1141   select-case-stmt    is [case-construct-name:] SELECT CASE (case-expr)

in F2018.

So, strike out that part of the proposal.

What is left is two options: Either use FALLTHROUGH in a way so that it can be included, for example, in conditional statements, or restrict it so it can only be the last statement of a block following the CASE statement. This would make the example above into

icases: select case(iflag)
case(1,3) 
   ! evaluate function
   f(1) = x*y
   f(2) = sin(x)*y**2
   if (iflag == 1) exit icases
   fallthrough
case(2)
   ! evaluate jacobian
   fjac(1,1) = y
   fjac(2,1) = cos(x)*y**2
   fjac(1,2) = x
   fjac(2,2) = 2*sin(x)*y
end select icases

which would be less intrusive, but there would be an asymmetry between exit and fallthrough (which I would not mind too much).

Preferences? Other suggestions?

FortranFan commented 1 year ago

I like the idea of fallthrough. It looks better than the alternatives:

I disagree in the case of the shown example for a fallthrough, especially if a IF construct is needed to get it to work anyway. I think a far better alternative is

      ! iflag = 1, evaluate f only
      ! iflag = 2, evaluate fjac only
      ! iflag = 3, evaluate both f and fjac
      if ( iand(iflag,1) == 1 ) then 
         ! evaluate function
         f(1) = x(1)*x(2)
         f(2) = sin(x(1))*(x(2)**2)
      end if
      if ( iand(iflag,2) == 2 ) then 
         ! evaluate jacobian
         fjac(1,1) = x(2)
         fjac(2,1) = cos(x(1))*(x(2)**2)
         fjac(1,2) = x(1)
         fjac(2,2) = 2*sin(x(1))*x(2)
      end if
FortranFan commented 1 year ago

which has code duplication for the print '(A)',"Hexadecimal digit" statement.

You can better write your code as below in which case there will no code duplication and no need for a confusing and what will often be difficult to notice fallthrough:

subroutine foo(x)
    character, intent(in) :: x
    select case(x)
    case ('a':'f','A':'F')
       print '(A)',"Hexadecimal digit"
    case ('0':'9')
       print '(A)',"Hexadecimal digit or Decimal digit"
    case default
       print '(A)',"Something else"
    end select
  end subroutine foo