202X feature: Conditional Expressions

I was wondering whether we could already implement a function ifthen which allows the most basic handling of conditional expressions (like absent arguments). Here is an implementation I was able to come up with:

module m_ifthen
   implicit none
contains
   pure function ifthen(condition, tval, fval) result(val)
      logical, intent(in) :: condition
      real, intent(in), optional :: tval, fval
      real, allocatable :: val

      if (condition) then
         if (present(tval)) val = tval
      else
         if (present(fval)) val = fval
      end if
   end function ifthen
end module m_ifthen

It exploits that we can return an unallocated value from a function, which is handled as if not present when passed to an optional argument. Up to this point everything works without changing the semantics of the function call beyond things we can do in Fortran today. What we of course can’t do is have an expression which is not evaluated due to short circuiting in this context.

Taking the example from the proposal we can already write something that looks like the proposed conditional expression:

module m_test
   use m_ifthen
   implicit none
contains
   subroutine test_ifthen(x, d)
      real, intent(in) :: x
      real, intent(in), optional :: d
      real :: a, b, c

      call sub(a, b, c, ifthen(present(d), d, ifthen(x < 1, epsilon(x), spacing(x))))

      print *, a, b, c
   end subroutine test_ifthen

   subroutine test_merge(x, d)
      real, intent(in) :: x
      real, intent(in), optional :: d
      real :: a, b, c

      call sub(a, b, c, merge(d, merge(epsilon(x), spacing(x), x < 1), present(d)))

      print *, a, b, c
   end subroutine test_merge

   subroutine sub(a, b, c, d)
      real, intent(out) :: a, b, c
      real, intent(in) :: d
      a = sqrt(d)
      b = sqrt(a)
      c = sqrt(b)
   end subroutine sub
end module m_test

program demo
   use m_test
   implicit none
   call test_ifthen(0.5)
   call test_merge(0.5)
end program demo

I tested the above example with four compilers (gfortran 9.2, ifort 19.0, nagfor 7.0, nvfortran 21.3), while all compilers correctly evaluate the ifthen function, nvfortran does not short-circuit the evaluation of the merge function and gives a segmentation fault.

3 Likes