I would like to confirm how the multiple logical intersection is evaluated. For example, I have the following code:
do i=1,sz
if (sz-i >= 1 .and. &
x(i) == 1 .and. &
x(i+1) == 2) then
! When i=sz then it fails giving an
! above upper bound error at 3rd expression
end if
end do
It is obvious that at first all three expressions are evaluated and at last the intersection. Is there any compiler option to stop evaluation at first false? Tia
There is no short-circuiting of logical expressions in Fortran. The standard defines the order of evaluation to be arbitrary so that compilers may reorder them as they see fit.
That is, Fortran 2023 introduces support for conditional expressions that will allow compilers to do what is commonly referred to as short-circuit evaluations.
in the meantime, nest the conditionals so the ones you need to short-circuit
are only executed conditionally. That way you can have tests on the value of
i, etc. Need more info to know if you need other tests on the value of “i” or not
but if you nest them then the inner test is only performed when the outer conditionals
are true. The same as short-circuting but a bit more verbose
if (sz-i >= 1 .and. x(i) == 1 )then
if( x(i+1) == 2) then
! When i=sz then it fails giving an
! above upper bound error at 3rd expression
endif
end if
Here’s a solution. It’s horrible for readability and will possibly have some negative consequences for performance, but it does work:
module shortcircuit_mod
implicit none
private
public fused_and
interface fused_and
module procedure fused_and1
module procedure fused_and2
module procedure fused_and3
end interface
abstract interface
logical function logical_func()
end function
end interface
contains
logical function fused_and1(f1) result(res)
procedure(logical_func) :: f1
res = f1()
end function
logical function fused_and2(f1, f2) result(res)
procedure(logical_func) :: f1, f2
res = .false.
if (.not. f1()) return
res = f2()
end function
logical function fused_and3(f1, f2, f3) result(res)
procedure(logical_func) :: f1, f2, f3
res = .false.
if (.not. f1()) return
if (.not. f2()) return
res = f3()
end function
end module
program main
use shortcircuit_mod, only: fused_and
integer :: sz, i
integer, allocatable :: x(:)
x = [3, 1, 3, 1, 2, 1]
sz = size(x) - 1
do i = 1, sz
write(*,*) 'Evaluate at i = ', i
if (fused_and(sz_minus_i_ge_1, xi_eq_1, xip1_eq_2)) then
error stop 'Error: and conditions triggered'
end if
end do
contains
logical function sz_minus_i_ge_1() result(res)
write(*,*) '1: Eval sz_minus_i_ge_1'
res = sz - i >= 1
end function
logical function xi_eq_1() result(res)
write(*,*) '2: Eval xi_eq_1'
res = x(i) == 1
end function
logical function xip1_eq_2() result(res)
write(*,*) '3: Eval xip1_eq_2'
res = x(i + 1) == 2
end function
end program
Output from example:
Evaluate at i = 1
1: Eval sz_minus_i_ge_1
2: Eval xi_eq_1
Evaluate at i = 2
1: Eval sz_minus_i_ge_1
2: Eval xi_eq_1
3: Eval xip1_eq_2
Evaluate at i = 3
1: Eval sz_minus_i_ge_1
2: Eval xi_eq_1
Evaluate at i = 4
1: Eval sz_minus_i_ge_1
2: Eval xi_eq_1
3: Eval xip1_eq_2
Error: and conditions triggered
As you’ll see, evaluations for i = 1 and i = 3 short circuit at the second function. The fused_all interface could also be expanded for more arguments if needed.
The new facility in Fortran 2023 with logical expressions helps with what OP asked, “option to stop evaluation at first false”
The semantics with MERGE does not necessarily help with that, it may do so with one processor but not with others i.e., it will be a YMMV situation and thus MERGE is not the way to go with OP’s case.
Even with that new ? facility, I expect many programmers will continue to use nested if statements to achieve this same goal. It is often clearer and easier for a human reader to follow, as evidenced by the previous example in this thread.
program test
implicit none
integer, parameter :: sz = 4
integer :: i
integer, dimension(4) :: x = [ (merge(1, 2, mod(i, 2) .ne. 0), i=1,sz) ]
print *, x
do i=1,sz
if ( merge( x(i).eq.1 .and. x(i+1).eq.2, .false., merge(.true., .false., i.le.(sz-1)) ) ) then
print *, 'i = ', i, '; x(i) = ', x(i), '; x(i+1) = ', x(i+1)
end if
end do
end program test
Yes it’s not easy to read this condition so I would like to prefer nested if conditions.
Maybe additionally the bound-check always should be switched off.