Why no logical ==?

Currently, x .and. y .eqv. z parses as (x .and. y) .eqv. z.

Following the current grammar, x .and. y == z parses as x .and. (y == z) (though it is semantically invalid).

This is because == has higher precedence than .and. while .eqv. has lower precedence. This is from table 10.1 in the F2018 standard.

So if logical == were permitted with the current grammar, x .and. y .eqv. z would mean something different than x .and. y == z, which could be confusing.

If the precedence of .eqv. were moved up to be the same as ==, it would change the meaning of x .and. y .eqv. z and so not be backward compatible.

The third option would be to move the precedence of == down to be the same as .eqv.. I can’t find a problem with that but am curious is anyone else does.

And of course there is still the problem of user-defined == and whether this would break current extensions. For compilers that allow this as an extension, what is the precedence of logical ==?

Because the algorithm is generic and must work for all intrinsic types and kinds, including logical.

I don’t really see what the fuss is about. We always used .eqv. and .neqv. with logicals because that’s what the language says. It isn’t difficult to realize that a different type requires different operators.
There are definitely more important things (IMHO) for the compiler writers to spend their precious time on.
Where we did encounter problem was passing the logical to c since that did expose the different implementations that @sblionel described.

3 Likes

This one is easy: breaking backward compatiblity.

One of the use cases discussed upthread involves writing generic subroutines or functions that are intended work for all types and kinds. I can see how having the same operator for all types and kinds would simplify that task.

1 Like

Do you have an example?

@ashe

The variables are numeric:
a == b .and. c == d

In the standard == has precedence over .and., so it is interpreted as
(a == b) .and. (c == d)

If you lower the precedence of == at the same level as .eqv., then .and. has precedence and it gets:
a == (b .and. c) == d

—> compilation error

So instead you make logical == have the same precedence as all other usages of ==, rather than it being an alias for .eqv.. I think that avoid the backwards compatibility issue and makes more sense overall.

2 Likes

+1

But that’s entirely too logical for a committee!

Try pushing this all the way up to the attention of possible worklist items for a standard revision, chances are high it will be dead on arrival, see this paper for some background:

  • you see there are sentences in the standard document that state “==” shall have the same semantics as “.EQ.”,
  • since “.EQ.” does not support operation on intrinsic logical type, nor can “==”.

Cheers,

1 Like

If you remove the module ifort/ifx runs the following example it gets the same results as if you use the module with ifort and gfortran. The overload (which is standard-conforming) and the Intel extension produce the same result for the default LOGICAL kind. It would take a rather long general procedure to support all the logical kinds so they could be combined in expressions and passed as arguments and get the expected kind put it is possible; but the extension already handles that. Since == and .EQ. are bound as the same operator (if you define overload “==” you also overload “.EQ.”) and at least the ifort/ifx and nvfortran compilers already support this as an extension I am confused by those statements.

module logical_ops
!use,intrinsic :: iso_fortran_env, only : logical8, logical16, logical32, logical64
use,intrinsic :: iso_fortran_env, only : int8, int16, int32, int64
implicit none
integer,parameter :: logical8=1, logical16=2, logical32=4,logical64=8 ! compiler-dependent kludge
interface operator(==); module procedure equal;    end interface
interface operator(/=); module procedure notequal; end interface
contains
logical function equal(l1, l2); logical, intent(in) :: l1, l2; equal = l1 .eqv. l2; end 
logical function notequal(l1, l2); logical, intent(in) :: l1, l2; notequal = l1 .neqv. l2; end 
end module
program testit
use logical_ops
implicit none
logical :: l=.false.,m=.false.,n=.false.
   print *,'L.AND.M.EQ.N', l.and.m.eq.n
   print *,'L.AND.(M.EQ.N)',l.and.(m.eq.n)
   print *,'(L.AND.M).EQ.N',(l.and.m).eq.n
   print *
   print *,'L.AND.M.EQV.N',l.and.m.eqv.n
   print *,'L.AND.(M.EQV.N)',l.and.(m.eqv.n)
   print *,'(L.AND.M).EQV.N',(l.and.m).eqv.n
   print *
   print *,'L.AND.M == N',l.and.m==n
   print *,'L.AND.(M == N)',l.and.(m==n)
   print *,'(L.AND.M) == N',(l.and.m)==n
end program testit

So “ifort testit.f90” and “nvfortran testit.f90” and “ifx testit.f90” work with an extension without the module,
and an overload produces the same results with “gfortran testit.f90” and “ifx -stand=f90” as the extension I do not see that it would break anything to standardize the behavior to the same extend as a more general overload module would with at least those compilers. The problem would be with a further extension that included being able to interchange LOGICAL and INTEGER values.

The fact it is such a common extension and has been for a very long time, and that it is rather intuitive is the reason it appears in so much legacy code. If you try something like " (a.eq.1).and.(b<0)" and it works you are unlikely to think that is non-standard until a compiler warning or error tells you otherwise. Expressions mixing integer and logical are another matter, as that would break some old codes to define TRUE as a particular bit pattern and/or require a rule for converting arbitrary INTEGER values to a LOGICAL value.

1 Like

As discussed above, this would break non-standard -but non uncommon- codes that were written for compilers that accept (extension) == as an alias to .eqv.

I don’t say it’s a good reason, but it looks like a pragmatic reason. On the one hand, one might say that non-standard extensions should not be an obstacle to new features in the language. On the other hand I’m not sure that having == as an alias to .eqv. is critical enough to justifiy breaking existing code.

But wouldn’t it be easier just to overload the == operator for logicals as demonstrated above and use the overloaded operator in those generic algorithms? It would be standard conforming and reduce the complexity/verbosity in your algorithms.

I have used a lot of compilers and do not know of any that equivalence .eqv. and ==. ifort/ifx and nvfortran without the overload produce the same result as with the overload in the example above… That is, == uses the same precedence as it does for other arguments.

Thank you all for explaining why allowing logical==logical in a future standard would be a bad idea. Of course == can be overloaded to achieve that, but people who did would become unpopular with whoever tried to use their work.

These are acceptable in ifort/ifx, for example:

 1 .eq. .true.      F
 0 .eq. .true.      F
 -1 .eq. .true.     T
 3 .eq. .true.      F
 2 .eq. .true.      F
 0 .eq. .true.      F
 .true. + .true.    F
 .true. + 0         -1

Maybe you’re right, maybe it was in the past and no existing compiler today does that, I don’t know…

However, the ambiguities described in the gfortran doc still hold. People could be surprised if
a .and. b == c
was interpreted as
a .and. (b == c)
for logical types, while
a + b == c
is interpreted as
(a + b) == c
for numeric types…

I think it should be the choice and responsibility of developers to overload == for logical types in their projects if they wish to do so and if they know what they are doing.

1 Like

I think the bigger issue is for new users expecting .eqv. to have the same precedence of == if they know about .eqv. at all instead of the more intuitive ==. Even though I long ago “switched” to .eqv. and .neqv. (as all the compilers I had used for years allowed the extension “==” it had not occurred to me it was non-standard until I encountered one that complained about it) I still always use parenthesis for anyone else that follows more than for myself. The same goes for things like “AIJ” that I think cause a lot of confusion.

I hope this will serve those who come later and have the same question even though I do not agree with the reasons as I have seen this question many times in the past. If Fortran Discourse had an FAQ for Fortran questions the OPs original question would be a very good candidate.

ChatGPT will tell you what most people believe about a topic, whether or not it is true.
I don’t think the standard needs to be changed.

Q. Is it valid to compare two logical variables in Fortran using == ? If not, how should you do it?

A. Yes, it is valid to compare two logical variables in Fortran using the == operator. The == operator is used to compare two values for equality, and it can be used with a logical data type in Fortran.

Q. Actually it is non-standard to use == or .eq. to compare logical variables in Fortran. You should use the standard-conforming .eqv.

A. You are correct. While many Fortran compilers will accept the == or .eq. operators for comparing logical variables, they are not strictly standard-conforming. The Fortran standard specifies that the .eqv. operator should be used for comparing logical variables.

1 Like

What are the practical scenarios where you need to employ .eqv. and .neqv.?

and I would add “…and what you would like to hear…”. In that sense, ChatGPT is an excellent bullshiter