202X feature: Conditional Expressions

Even if you find all the available Fortran compilers behave as you show here, the language standard is such one cannot make any assumptions whatsoever with the evaluation of argument expressions in the MERGE intrinsic!

Yeah, that’s also my current understanding. So, even if gfortran evaluates only one of the arguments, I cannot “utilize” that behavior in my codes… (I think this is also related to the topic of && and || in other proposals.)

1 Like

First, there are sufficient differences in the semantics involved with conditional expressions, particularly with chaining, to make the analogy with user-defined operators inapplicable here.

I agree about the semantic differences, but I was referring to parsing. Any Fortran 2018 compiler should already be able to parse this expression.

Secondly, the rules with the order of operations are fraught with so many practical difficulties, one has to bring in a beginning and ending token anyway for any deterministic usage, the tokens being parentheses.

Can you give an example of one of these practical difficulties?

1 Like

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

Something fun you can do is modify it slightly so it’s like this.

module m_ifthen
    implicit none
contains
    pure function if(condition, then, else) result(val)
       logical, intent(in) :: condition
       real, intent(in), optional :: then, else
       real, allocatable :: val
 
       if (condition) then
          if (present(then)) val = then
       else
          if (present(else)) val = else
       end if
    end function if
end module m_ifthen

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, if(present(d), then=d, else=if(x < 1, then=epsilon(x), else=spacing(x))))
    
        print *, a, b, c
    end subroutine test_ifthen
    
    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)
end program demo

Thanks for sharing your code, and I think it is interesting to use optional arguments this way (I think this kind of “function approach” is actually sufficient for many cases, particularly for primitive scalar variables like integers and reals).

But I am afraid when tval and fval is an object of some derived type, copy operation probably occurs inside the function, which might lead to some pitfall, e.g. when the object has a pointer component for another component in the same object. (Because I sometimes use such types, some concern…)

FWIW, the ternary expression in C++ seems to return the reference to the objects (i.e. no copy), but I’m not sure this is a common behavior in other languages also.

struct Foo { int dat; };
int main() {
    int n;
    Foo a, b;
    cin >> n;
    cout << "addr(a)   = " << &a << endl;
    cout << "addr(b)   = " << &b << endl;
    cout << "addr(a,b) = " << &( n > 0 ? a : b ) << endl;
}

$ echo 2 | ./a.out
addr(a)   = 0x7fff5d84a508
addr(b)   = 0x7fff5d84a504
addr(a,b) = 0x7fff5d84a508

$ echo -2 | ./a.out
addr(a)   = 0x7fff5b223508
addr(b)   = 0x7fff5b223504
addr(a,b) = 0x7fff5b223504

Based on the pointer idea of @septc I rewrote the code here that shows how operators can implement the example functionality. Using .if. is optional.

module m_ifthen
implicit none
interface operator(.if.)
   module procedure if_op
endinterface
interface operator(.then.)
   module procedure then_op
endinterface
interface operator(.else.)
   module procedure else_op
endinterface
contains
function if_op(condition) result(val)
   logical, intent(in) :: condition
   logical :: val
   val = condition
endfunction if_op

function then_op(condition, then_val) result(val)
   logical, intent(in) :: condition
   real, target, intent(in) :: then_val
   real, pointer :: val
   val => null()
   if(condition) then
      val => then_val
   endif
endfunction then_op

function else_op(then_val, else_val) result(val)
   real, pointer, intent(in) :: then_val
   real, intent(in) :: else_val
   real :: val
   if(associated(then_val)) then
      val = then_val
   else
      val = else_val
   endif
endfunction else_op
endmodule m_ifthen

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, .if.present(d) .then. d .else. (.if.(x < 1) .then. epsilon(x) .else. spacing(x)))

   print *, a, b, c
endsubroutine test_ifthen

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)
endsubroutine sub
endmodule m_test

program demo
use m_test
implicit none
call test_ifthen(0.5)
endprogram demo
1 Like

Thanks, I have also written the pointer version of awvwgk’s code below, which worked as expected with gfortran. So if templates are available, this kind of thing may be written in a general way (or even with “include” approach, if definitely needed.) (Btw, syntax color is all red for some reason…)

module test_mod
    implicit none
    type Foo
        integer :: dat
    endtype
contains

function ifthen( cond, tval, fval ) result(ptr)
    logical                     :: cond
    type(Foo), optional, target :: tval, fval
    type(Foo), pointer          :: ptr

    if (cond) then
        if (present(tval)) ptr => tval
    else
        if (present(fval)) ptr => fval
    end if
end

end module

program main
    use iso_c_binding
    use test_mod
    type(Foo), target :: a, b
    integer n
    read *, n

    print *, "addr(a)   = ", c_loc( a )
    print *, "addr(b)   = ", c_loc( b )
    print *, "addr(a,b) = ", c_loc( ifthen( n > 0, a, b ) )
end

Great point! Using the idea you can do the named parameters too.

module m_ifthen
   implicit none
contains
   function if(condition, then, else) result(val)
      logical, intent(in) :: condition
      real, intent(in), optional, target :: then, else
      real, pointer :: val
      val => null()
      if (condition) then
         if (present(then)) val => then
      else
         if (present(else)) val => else
      end if
   end function if
end module m_ifthen

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, if(present(d), then=d, else=if(x < 1, then=epsilon(x), else=spacing(x))))
   
       print *, a, b, c
   end subroutine test_ifthen
   
   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)
end program demo

Noticed from this example that how nice it is to not have reserved keywords in Fortran. Few days back somebody commented that Fortran should have kept keywords reserved!

1 Like

Unfortunately, we can’t have both pointers and pure procedures. Using a pointer based ifthen function doesn’t allow to use it in a pure context anymore.

Should we nullify the unassociated pointer before returning it or is it guaranteed that an unassociated pointer result of function is always nullified?